{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
module Internal.Numeric where
import Internal.Vector
import Internal.Matrix
import Internal.Element
import Internal.ST as ST
import Internal.Conversion
import Internal.Vectorized
import Internal.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ,multiplyI,multiplyL)
import Data.List.Split(chunksOf)
import qualified Data.Vector.Storable as V
type family IndexOf (c :: * -> *)
type instance IndexOf Vector = Int
type instance IndexOf Matrix = (Int,Int)
type family ArgOf (c :: * -> *) a
type instance ArgOf Vector a = a -> a
type instance ArgOf Matrix a = a -> a -> a
class Element e => Container c e
where
conj' :: c e -> c e
size' :: c e -> IndexOf c
scalar' :: e -> c e
scale' :: e -> c e -> c e
addConstant :: e -> c e -> c e
add' :: c e -> c e -> c e
sub :: c e -> c e -> c e
mul :: c e -> c e -> c e
equal :: c e -> c e -> Bool
cmap' :: (Element b) => (e -> b) -> c e -> c b
konst' :: e -> IndexOf c -> c e
build' :: IndexOf c -> (ArgOf c e) -> c e
atIndex' :: c e -> IndexOf c -> e
minIndex' :: c e -> IndexOf c
maxIndex' :: c e -> IndexOf c
minElement' :: c e -> e
maxElement' :: c e -> e
sumElements' :: c e -> e
prodElements' :: c e -> e
step' :: Ord e => c e -> c e
ccompare' :: Ord e => c e -> c e -> c I
cselect' :: c I -> c e -> c e -> c e -> c e
find' :: (e -> Bool) -> c e -> [IndexOf c]
assoc' :: IndexOf c
-> e
-> [(IndexOf c, e)]
-> c e
accum' :: c e
-> (e -> e -> e)
-> [(IndexOf c, e)]
-> c e
scaleRecip :: Fractional e => e -> c e -> c e
divide :: Fractional e => c e -> c e -> c e
arctan2' :: Fractional e => c e -> c e -> c e
cmod' :: Integral e => e -> c e -> c e
fromInt' :: c I -> c e
toInt' :: c e -> c I
fromZ' :: c Z -> c e
toZ' :: c e -> c Z
instance Container Vector I
where
conj' :: Vector I -> Vector I
conj' = Vector I -> Vector I
forall a. a -> a
id
size' :: Vector I -> IndexOf Vector
size' = Vector I -> IndexOf Vector
forall t. Storable t => Vector t -> Int
dim
scale' :: I -> Vector I -> Vector I
scale' = FunCodeSV -> I -> Vector I -> Vector I
vectorMapValI FunCodeSV
Scale
addConstant :: I -> Vector I -> Vector I
addConstant = FunCodeSV -> I -> Vector I -> Vector I
vectorMapValI FunCodeSV
AddConstant
add' :: Vector I -> Vector I -> Vector I
add' = FunCodeVV -> Vector I -> Vector I -> Vector I
vectorZipI FunCodeVV
Add
sub :: Vector I -> Vector I -> Vector I
sub = FunCodeVV -> Vector I -> Vector I -> Vector I
vectorZipI FunCodeVV
Sub
mul :: Vector I -> Vector I -> Vector I
mul = FunCodeVV -> Vector I -> Vector I -> Vector I
vectorZipI FunCodeVV
Mul
equal :: Vector I -> Vector I -> Bool
equal = Vector I -> Vector I -> Bool
forall a. Eq a => a -> a -> Bool
(==)
scalar' :: I -> Vector I
scalar' = I -> Vector I
forall a. Storable a => a -> Vector a
V.singleton
konst' :: I -> IndexOf Vector -> Vector I
konst' = I -> IndexOf Vector -> Vector I
forall a. Element a => a -> Int -> Vector a
constantD
build' :: IndexOf Vector -> ArgOf Vector I -> Vector I
build' = IndexOf Vector -> ArgOf Vector I -> Vector I
forall a t a.
(Integral a, Num t, Storable a) =>
a -> (t -> a) -> Vector a
buildV
cmap' :: (I -> b) -> Vector I -> Vector b
cmap' = (I -> b) -> Vector I -> Vector b
forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
mapVector
atIndex' :: Vector I -> IndexOf Vector -> I
atIndex' = Vector I -> IndexOf Vector -> I
forall t. Storable t => Vector t -> Int -> t
(@>)
minIndex' :: Vector I -> IndexOf Vector
minIndex' = [Char] -> (Vector I -> Int) -> Vector I -> Int
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"minIndex" (I -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (I -> Int) -> (Vector I -> I) -> Vector I -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector I -> I
toScalarI FunCodeS
MinIdx)
maxIndex' :: Vector I -> IndexOf Vector
maxIndex' = [Char] -> (Vector I -> Int) -> Vector I -> Int
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"maxIndex" (I -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (I -> Int) -> (Vector I -> I) -> Vector I -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector I -> I
toScalarI FunCodeS
MaxIdx)
minElement' :: Vector I -> I
minElement' = [Char] -> (Vector I -> I) -> Vector I -> I
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"minElement" (FunCodeS -> Vector I -> I
toScalarI FunCodeS
Min)
maxElement' :: Vector I -> I
maxElement' = [Char] -> (Vector I -> I) -> Vector I -> I
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"maxElement" (FunCodeS -> Vector I -> I
toScalarI FunCodeS
Max)
sumElements' :: Vector I -> I
sumElements' = I -> Vector I -> I
forall c a.
(TransRaw c (I -> Ptr a -> IO I) ~ (I -> Ptr I -> I :> IO I),
TransArray c, Storable a) =>
I -> c -> a
sumI I
1
prodElements' :: Vector I -> I
prodElements' = I -> Vector I -> I
prodI I
1
step' :: Vector I -> Vector I
step' = Vector I -> Vector I
stepI
find' :: (I -> Bool) -> Vector I -> [IndexOf Vector]
find' = (I -> Bool) -> Vector I -> [IndexOf Vector]
forall t. Storable t => (t -> Bool) -> Vector t -> [Int]
findV
assoc' :: IndexOf Vector -> I -> [(IndexOf Vector, I)] -> Vector I
assoc' = IndexOf Vector -> I -> [(IndexOf Vector, I)] -> Vector I
forall t (t :: * -> *).
(Storable t, Foldable t) =>
Int -> t -> t (Int, t) -> Vector t
assocV
accum' :: Vector I -> (I -> I -> I) -> [(IndexOf Vector, I)] -> Vector I
accum' = Vector I -> (I -> I -> I) -> [(IndexOf Vector, I)] -> Vector I
forall t (t :: * -> *) t.
(Storable t, Foldable t) =>
Vector t -> (t -> t -> t) -> t (Int, t) -> Vector t
accumV
ccompare' :: Vector I -> Vector I -> Vector I
ccompare' = (Vector I -> Vector I -> Vector I)
-> Vector I -> Vector I -> Vector I
forall t t.
Element t =>
(Vector t -> Vector t -> t) -> Vector t -> Vector t -> t
compareCV Vector I -> Vector I -> Vector I
forall a. (Element a, Ord a) => Vector a -> Vector a -> Vector I
compareV
cselect' :: Vector I -> Vector I -> Vector I -> Vector I -> Vector I
cselect' = (Vector I -> Vector I -> Vector I -> Vector I -> Vector I)
-> Vector I -> Vector I -> Vector I -> Vector I -> Vector I
forall e t.
Container Vector e =>
(Vector I -> Vector e -> Vector e -> Vector e -> t)
-> Vector I -> Vector e -> Vector e -> Vector e -> t
selectCV Vector I -> Vector I -> Vector I -> Vector I -> Vector I
forall a.
Element a =>
Vector I -> Vector a -> Vector a -> Vector a -> Vector a
selectV
scaleRecip :: I -> Vector I -> Vector I
scaleRecip = I -> Vector I -> Vector I
forall a. HasCallStack => a
undefined
divide :: Vector I -> Vector I -> Vector I
divide = Vector I -> Vector I -> Vector I
forall a. HasCallStack => a
undefined
arctan2' :: Vector I -> Vector I -> Vector I
arctan2' = Vector I -> Vector I -> Vector I
forall a. HasCallStack => a
undefined
cmod' :: I -> Vector I -> Vector I
cmod' I
m Vector I
x
| I
m I -> I -> Bool
forall a. Eq a => a -> a -> Bool
/= I
0 = FunCodeSV -> I -> Vector I -> Vector I
vectorMapValI FunCodeSV
ModVS I
m Vector I
x
| Bool
otherwise = [Char] -> Vector I
forall a. HasCallStack => [Char] -> a
error ([Char] -> Vector I) -> [Char] -> Vector I
forall a b. (a -> b) -> a -> b
$ [Char]
"cmod 0 on vector of size "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++(Int -> [Char]
forall a. Show a => a -> [Char]
show (Int -> [Char]) -> Int -> [Char]
forall a b. (a -> b) -> a -> b
$ Vector I -> Int
forall t. Storable t => Vector t -> Int
dim Vector I
x)
fromInt' :: Vector I -> Vector I
fromInt' = Vector I -> Vector I
forall a. a -> a
id
toInt' :: Vector I -> Vector I
toInt' = Vector I -> Vector I
forall a. a -> a
id
fromZ' :: Vector Z -> Vector I
fromZ' = Vector Z -> Vector I
long2intV
toZ' :: Vector I -> Vector Z
toZ' = Vector I -> Vector Z
int2longV
instance Container Vector Z
where
conj' :: Vector Z -> Vector Z
conj' = Vector Z -> Vector Z
forall a. a -> a
id
size' :: Vector Z -> IndexOf Vector
size' = Vector Z -> IndexOf Vector
forall t. Storable t => Vector t -> Int
dim
scale' :: Z -> Vector Z -> Vector Z
scale' = FunCodeSV -> Z -> Vector Z -> Vector Z
vectorMapValL FunCodeSV
Scale
addConstant :: Z -> Vector Z -> Vector Z
addConstant = FunCodeSV -> Z -> Vector Z -> Vector Z
vectorMapValL FunCodeSV
AddConstant
add' :: Vector Z -> Vector Z -> Vector Z
add' = FunCodeVV -> Vector Z -> Vector Z -> Vector Z
vectorZipL FunCodeVV
Add
sub :: Vector Z -> Vector Z -> Vector Z
sub = FunCodeVV -> Vector Z -> Vector Z -> Vector Z
vectorZipL FunCodeVV
Sub
mul :: Vector Z -> Vector Z -> Vector Z
mul = FunCodeVV -> Vector Z -> Vector Z -> Vector Z
vectorZipL FunCodeVV
Mul
equal :: Vector Z -> Vector Z -> Bool
equal = Vector Z -> Vector Z -> Bool
forall a. Eq a => a -> a -> Bool
(==)
scalar' :: Z -> Vector Z
scalar' = Z -> Vector Z
forall a. Storable a => a -> Vector a
V.singleton
konst' :: Z -> IndexOf Vector -> Vector Z
konst' = Z -> IndexOf Vector -> Vector Z
forall a. Element a => a -> Int -> Vector a
constantD
build' :: IndexOf Vector -> ArgOf Vector Z -> Vector Z
build' = IndexOf Vector -> ArgOf Vector Z -> Vector Z
forall a t a.
(Integral a, Num t, Storable a) =>
a -> (t -> a) -> Vector a
buildV
cmap' :: (Z -> b) -> Vector Z -> Vector b
cmap' = (Z -> b) -> Vector Z -> Vector b
forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
mapVector
atIndex' :: Vector Z -> IndexOf Vector -> Z
atIndex' = Vector Z -> IndexOf Vector -> Z
forall t. Storable t => Vector t -> Int -> t
(@>)
minIndex' :: Vector Z -> IndexOf Vector
minIndex' = [Char] -> (Vector Z -> Int) -> Vector Z -> Int
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"minIndex" (Z -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Z -> Int) -> (Vector Z -> Z) -> Vector Z -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector Z -> Z
toScalarL FunCodeS
MinIdx)
maxIndex' :: Vector Z -> IndexOf Vector
maxIndex' = [Char] -> (Vector Z -> Int) -> Vector Z -> Int
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"maxIndex" (Z -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Z -> Int) -> (Vector Z -> Z) -> Vector Z -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector Z -> Z
toScalarL FunCodeS
MaxIdx)
minElement' :: Vector Z -> Z
minElement' = [Char] -> (Vector Z -> Z) -> Vector Z -> Z
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"minElement" (FunCodeS -> Vector Z -> Z
toScalarL FunCodeS
Min)
maxElement' :: Vector Z -> Z
maxElement' = [Char] -> (Vector Z -> Z) -> Vector Z -> Z
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"maxElement" (FunCodeS -> Vector Z -> Z
toScalarL FunCodeS
Max)
sumElements' :: Vector Z -> Z
sumElements' = Z -> Vector Z -> Z
forall c a.
(TransRaw c (I -> Ptr a -> IO I) ~ (I -> Ptr Z -> Z :> IO I),
TransArray c, Storable a) =>
Z -> c -> a
sumL Z
1
prodElements' :: Vector Z -> Z
prodElements' = Z -> Vector Z -> Z
prodL Z
1
step' :: Vector Z -> Vector Z
step' = Vector Z -> Vector Z
stepL
find' :: (Z -> Bool) -> Vector Z -> [IndexOf Vector]
find' = (Z -> Bool) -> Vector Z -> [IndexOf Vector]
forall t. Storable t => (t -> Bool) -> Vector t -> [Int]
findV
assoc' :: IndexOf Vector -> Z -> [(IndexOf Vector, Z)] -> Vector Z
assoc' = IndexOf Vector -> Z -> [(IndexOf Vector, Z)] -> Vector Z
forall t (t :: * -> *).
(Storable t, Foldable t) =>
Int -> t -> t (Int, t) -> Vector t
assocV
accum' :: Vector Z -> (Z -> Z -> Z) -> [(IndexOf Vector, Z)] -> Vector Z
accum' = Vector Z -> (Z -> Z -> Z) -> [(IndexOf Vector, Z)] -> Vector Z
forall t (t :: * -> *) t.
(Storable t, Foldable t) =>
Vector t -> (t -> t -> t) -> t (Int, t) -> Vector t
accumV
ccompare' :: Vector Z -> Vector Z -> Vector I
ccompare' = (Vector Z -> Vector Z -> Vector I)
-> Vector Z -> Vector Z -> Vector I
forall t t.
Element t =>
(Vector t -> Vector t -> t) -> Vector t -> Vector t -> t
compareCV Vector Z -> Vector Z -> Vector I
forall a. (Element a, Ord a) => Vector a -> Vector a -> Vector I
compareV
cselect' :: Vector I -> Vector Z -> Vector Z -> Vector Z -> Vector Z
cselect' = (Vector I -> Vector Z -> Vector Z -> Vector Z -> Vector Z)
-> Vector I -> Vector Z -> Vector Z -> Vector Z -> Vector Z
forall e t.
Container Vector e =>
(Vector I -> Vector e -> Vector e -> Vector e -> t)
-> Vector I -> Vector e -> Vector e -> Vector e -> t
selectCV Vector I -> Vector Z -> Vector Z -> Vector Z -> Vector Z
forall a.
Element a =>
Vector I -> Vector a -> Vector a -> Vector a -> Vector a
selectV
scaleRecip :: Z -> Vector Z -> Vector Z
scaleRecip = Z -> Vector Z -> Vector Z
forall a. HasCallStack => a
undefined
divide :: Vector Z -> Vector Z -> Vector Z
divide = Vector Z -> Vector Z -> Vector Z
forall a. HasCallStack => a
undefined
arctan2' :: Vector Z -> Vector Z -> Vector Z
arctan2' = Vector Z -> Vector Z -> Vector Z
forall a. HasCallStack => a
undefined
cmod' :: Z -> Vector Z -> Vector Z
cmod' Z
m Vector Z
x
| Z
m Z -> Z -> Bool
forall a. Eq a => a -> a -> Bool
/= Z
0 = FunCodeSV -> Z -> Vector Z -> Vector Z
vectorMapValL FunCodeSV
ModVS Z
m Vector Z
x
| Bool
otherwise = [Char] -> Vector Z
forall a. HasCallStack => [Char] -> a
error ([Char] -> Vector Z) -> [Char] -> Vector Z
forall a b. (a -> b) -> a -> b
$ [Char]
"cmod 0 on vector of size "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++(Int -> [Char]
forall a. Show a => a -> [Char]
show (Int -> [Char]) -> Int -> [Char]
forall a b. (a -> b) -> a -> b
$ Vector Z -> Int
forall t. Storable t => Vector t -> Int
dim Vector Z
x)
fromInt' :: Vector I -> Vector Z
fromInt' = Vector I -> Vector Z
int2longV
toInt' :: Vector Z -> Vector I
toInt' = Vector Z -> Vector I
long2intV
fromZ' :: Vector Z -> Vector Z
fromZ' = Vector Z -> Vector Z
forall a. a -> a
id
toZ' :: Vector Z -> Vector Z
toZ' = Vector Z -> Vector Z
forall a. a -> a
id
instance Container Vector Float
where
conj' :: Vector Float -> Vector Float
conj' = Vector Float -> Vector Float
forall a. a -> a
id
size' :: Vector Float -> IndexOf Vector
size' = Vector Float -> IndexOf Vector
forall t. Storable t => Vector t -> Int
dim
scale' :: Float -> Vector Float -> Vector Float
scale' = FunCodeSV -> Float -> Vector Float -> Vector Float
vectorMapValF FunCodeSV
Scale
addConstant :: Float -> Vector Float -> Vector Float
addConstant = FunCodeSV -> Float -> Vector Float -> Vector Float
vectorMapValF FunCodeSV
AddConstant
add' :: Vector Float -> Vector Float -> Vector Float
add' = FunCodeVV -> Vector Float -> Vector Float -> Vector Float
vectorZipF FunCodeVV
Add
sub :: Vector Float -> Vector Float -> Vector Float
sub = FunCodeVV -> Vector Float -> Vector Float -> Vector Float
vectorZipF FunCodeVV
Sub
mul :: Vector Float -> Vector Float -> Vector Float
mul = FunCodeVV -> Vector Float -> Vector Float -> Vector Float
vectorZipF FunCodeVV
Mul
equal :: Vector Float -> Vector Float -> Bool
equal = Vector Float -> Vector Float -> Bool
forall a. Eq a => a -> a -> Bool
(==)
scalar' :: Float -> Vector Float
scalar' = Float -> Vector Float
forall a. Storable a => a -> Vector a
V.singleton
konst' :: Float -> IndexOf Vector -> Vector Float
konst' = Float -> IndexOf Vector -> Vector Float
forall a. Element a => a -> Int -> Vector a
constantD
build' :: IndexOf Vector -> ArgOf Vector Float -> Vector Float
build' = IndexOf Vector -> ArgOf Vector Float -> Vector Float
forall a t a.
(Integral a, Num t, Storable a) =>
a -> (t -> a) -> Vector a
buildV
cmap' :: (Float -> b) -> Vector Float -> Vector b
cmap' = (Float -> b) -> Vector Float -> Vector b
forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
mapVector
atIndex' :: Vector Float -> IndexOf Vector -> Float
atIndex' = Vector Float -> IndexOf Vector -> Float
forall t. Storable t => Vector t -> Int -> t
(@>)
minIndex' :: Vector Float -> IndexOf Vector
minIndex' = [Char] -> (Vector Float -> Int) -> Vector Float -> Int
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"minIndex" (Float -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round (Float -> Int) -> (Vector Float -> Float) -> Vector Float -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector Float -> Float
toScalarF FunCodeS
MinIdx)
maxIndex' :: Vector Float -> IndexOf Vector
maxIndex' = [Char] -> (Vector Float -> Int) -> Vector Float -> Int
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"maxIndex" (Float -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round (Float -> Int) -> (Vector Float -> Float) -> Vector Float -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector Float -> Float
toScalarF FunCodeS
MaxIdx)
minElement' :: Vector Float -> Float
minElement' = [Char] -> (Vector Float -> Float) -> Vector Float -> Float
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"minElement" (FunCodeS -> Vector Float -> Float
toScalarF FunCodeS
Min)
maxElement' :: Vector Float -> Float
maxElement' = [Char] -> (Vector Float -> Float) -> Vector Float -> Float
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"maxElement" (FunCodeS -> Vector Float -> Float
toScalarF FunCodeS
Max)
sumElements' :: Vector Float -> Float
sumElements' = Vector Float -> Float
sumF
prodElements' :: Vector Float -> Float
prodElements' = Vector Float -> Float
prodF
step' :: Vector Float -> Vector Float
step' = Vector Float -> Vector Float
stepF
find' :: (Float -> Bool) -> Vector Float -> [IndexOf Vector]
find' = (Float -> Bool) -> Vector Float -> [IndexOf Vector]
forall t. Storable t => (t -> Bool) -> Vector t -> [Int]
findV
assoc' :: IndexOf Vector
-> Float -> [(IndexOf Vector, Float)] -> Vector Float
assoc' = IndexOf Vector
-> Float -> [(IndexOf Vector, Float)] -> Vector Float
forall t (t :: * -> *).
(Storable t, Foldable t) =>
Int -> t -> t (Int, t) -> Vector t
assocV
accum' :: Vector Float
-> (Float -> Float -> Float)
-> [(IndexOf Vector, Float)]
-> Vector Float
accum' = Vector Float
-> (Float -> Float -> Float)
-> [(IndexOf Vector, Float)]
-> Vector Float
forall t (t :: * -> *) t.
(Storable t, Foldable t) =>
Vector t -> (t -> t -> t) -> t (Int, t) -> Vector t
accumV
ccompare' :: Vector Float -> Vector Float -> Vector I
ccompare' = (Vector Float -> Vector Float -> Vector I)
-> Vector Float -> Vector Float -> Vector I
forall t t.
Element t =>
(Vector t -> Vector t -> t) -> Vector t -> Vector t -> t
compareCV Vector Float -> Vector Float -> Vector I
forall a. (Element a, Ord a) => Vector a -> Vector a -> Vector I
compareV
cselect' :: Vector I
-> Vector Float -> Vector Float -> Vector Float -> Vector Float
cselect' = (Vector I
-> Vector Float -> Vector Float -> Vector Float -> Vector Float)
-> Vector I
-> Vector Float
-> Vector Float
-> Vector Float
-> Vector Float
forall e t.
Container Vector e =>
(Vector I -> Vector e -> Vector e -> Vector e -> t)
-> Vector I -> Vector e -> Vector e -> Vector e -> t
selectCV Vector I
-> Vector Float -> Vector Float -> Vector Float -> Vector Float
forall a.
Element a =>
Vector I -> Vector a -> Vector a -> Vector a -> Vector a
selectV
scaleRecip :: Float -> Vector Float -> Vector Float
scaleRecip = FunCodeSV -> Float -> Vector Float -> Vector Float
vectorMapValF FunCodeSV
Recip
divide :: Vector Float -> Vector Float -> Vector Float
divide = FunCodeVV -> Vector Float -> Vector Float -> Vector Float
vectorZipF FunCodeVV
Div
arctan2' :: Vector Float -> Vector Float -> Vector Float
arctan2' = FunCodeVV -> Vector Float -> Vector Float -> Vector Float
vectorZipF FunCodeVV
ATan2
cmod' :: Float -> Vector Float -> Vector Float
cmod' = Float -> Vector Float -> Vector Float
forall a. HasCallStack => a
undefined
fromInt' :: Vector I -> Vector Float
fromInt' = Vector I -> Vector Float
int2floatV
toInt' :: Vector Float -> Vector I
toInt' = Vector Float -> Vector I
float2IntV
fromZ' :: Vector Z -> Vector Float
fromZ' = (Vector R -> Vector Float
forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (SingleOf t)
single :: Vector R-> Vector Float) (Vector R -> Vector Float)
-> (Vector Z -> Vector R) -> Vector Z -> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Z -> Vector R
forall (c :: * -> *) e. Container c e => c Z -> c e
fromZ'
toZ' :: Vector Float -> Vector Z
toZ' = Vector R -> Vector Z
forall (c :: * -> *) e. Container c e => c e -> c Z
toZ' (Vector R -> Vector Z)
-> (Vector Float -> Vector R) -> Vector Float -> Vector Z
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Float -> Vector R
forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (DoubleOf t)
double
instance Container Vector Double
where
conj' :: Vector R -> Vector R
conj' = Vector R -> Vector R
forall a. a -> a
id
size' :: Vector R -> IndexOf Vector
size' = Vector R -> IndexOf Vector
forall t. Storable t => Vector t -> Int
dim
scale' :: R -> Vector R -> Vector R
scale' = FunCodeSV -> R -> Vector R -> Vector R
vectorMapValR FunCodeSV
Scale
addConstant :: R -> Vector R -> Vector R
addConstant = FunCodeSV -> R -> Vector R -> Vector R
vectorMapValR FunCodeSV
AddConstant
add' :: Vector R -> Vector R -> Vector R
add' = FunCodeVV -> Vector R -> Vector R -> Vector R
vectorZipR FunCodeVV
Add
sub :: Vector R -> Vector R -> Vector R
sub = FunCodeVV -> Vector R -> Vector R -> Vector R
vectorZipR FunCodeVV
Sub
mul :: Vector R -> Vector R -> Vector R
mul = FunCodeVV -> Vector R -> Vector R -> Vector R
vectorZipR FunCodeVV
Mul
equal :: Vector R -> Vector R -> Bool
equal = Vector R -> Vector R -> Bool
forall a. Eq a => a -> a -> Bool
(==)
scalar' :: R -> Vector R
scalar' = R -> Vector R
forall a. Storable a => a -> Vector a
V.singleton
konst' :: R -> IndexOf Vector -> Vector R
konst' = R -> IndexOf Vector -> Vector R
forall a. Element a => a -> Int -> Vector a
constantD
build' :: IndexOf Vector -> ArgOf Vector R -> Vector R
build' = IndexOf Vector -> ArgOf Vector R -> Vector R
forall a t a.
(Integral a, Num t, Storable a) =>
a -> (t -> a) -> Vector a
buildV
cmap' :: (R -> b) -> Vector R -> Vector b
cmap' = (R -> b) -> Vector R -> Vector b
forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
mapVector
atIndex' :: Vector R -> IndexOf Vector -> R
atIndex' = Vector R -> IndexOf Vector -> R
forall t. Storable t => Vector t -> Int -> t
(@>)
minIndex' :: Vector R -> IndexOf Vector
minIndex' = [Char] -> (Vector R -> Int) -> Vector R -> Int
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"minIndex" (R -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round (R -> Int) -> (Vector R -> R) -> Vector R -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector R -> R
toScalarR FunCodeS
MinIdx)
maxIndex' :: Vector R -> IndexOf Vector
maxIndex' = [Char] -> (Vector R -> Int) -> Vector R -> Int
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"maxIndex" (R -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round (R -> Int) -> (Vector R -> R) -> Vector R -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector R -> R
toScalarR FunCodeS
MaxIdx)
minElement' :: Vector R -> R
minElement' = [Char] -> (Vector R -> R) -> Vector R -> R
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"minElement" (FunCodeS -> Vector R -> R
toScalarR FunCodeS
Min)
maxElement' :: Vector R -> R
maxElement' = [Char] -> (Vector R -> R) -> Vector R -> R
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"maxElement" (FunCodeS -> Vector R -> R
toScalarR FunCodeS
Max)
sumElements' :: Vector R -> R
sumElements' = Vector R -> R
sumR
prodElements' :: Vector R -> R
prodElements' = Vector R -> R
prodR
step' :: Vector R -> Vector R
step' = Vector R -> Vector R
stepD
find' :: (R -> Bool) -> Vector R -> [IndexOf Vector]
find' = (R -> Bool) -> Vector R -> [IndexOf Vector]
forall t. Storable t => (t -> Bool) -> Vector t -> [Int]
findV
assoc' :: IndexOf Vector -> R -> [(IndexOf Vector, R)] -> Vector R
assoc' = IndexOf Vector -> R -> [(IndexOf Vector, R)] -> Vector R
forall t (t :: * -> *).
(Storable t, Foldable t) =>
Int -> t -> t (Int, t) -> Vector t
assocV
accum' :: Vector R -> (R -> R -> R) -> [(IndexOf Vector, R)] -> Vector R
accum' = Vector R -> (R -> R -> R) -> [(IndexOf Vector, R)] -> Vector R
forall t (t :: * -> *) t.
(Storable t, Foldable t) =>
Vector t -> (t -> t -> t) -> t (Int, t) -> Vector t
accumV
ccompare' :: Vector R -> Vector R -> Vector I
ccompare' = (Vector R -> Vector R -> Vector I)
-> Vector R -> Vector R -> Vector I
forall t t.
Element t =>
(Vector t -> Vector t -> t) -> Vector t -> Vector t -> t
compareCV Vector R -> Vector R -> Vector I
forall a. (Element a, Ord a) => Vector a -> Vector a -> Vector I
compareV
cselect' :: Vector I -> Vector R -> Vector R -> Vector R -> Vector R
cselect' = (Vector I -> Vector R -> Vector R -> Vector R -> Vector R)
-> Vector I -> Vector R -> Vector R -> Vector R -> Vector R
forall e t.
Container Vector e =>
(Vector I -> Vector e -> Vector e -> Vector e -> t)
-> Vector I -> Vector e -> Vector e -> Vector e -> t
selectCV Vector I -> Vector R -> Vector R -> Vector R -> Vector R
forall a.
Element a =>
Vector I -> Vector a -> Vector a -> Vector a -> Vector a
selectV
scaleRecip :: R -> Vector R -> Vector R
scaleRecip = FunCodeSV -> R -> Vector R -> Vector R
vectorMapValR FunCodeSV
Recip
divide :: Vector R -> Vector R -> Vector R
divide = FunCodeVV -> Vector R -> Vector R -> Vector R
vectorZipR FunCodeVV
Div
arctan2' :: Vector R -> Vector R -> Vector R
arctan2' = FunCodeVV -> Vector R -> Vector R -> Vector R
vectorZipR FunCodeVV
ATan2
cmod' :: R -> Vector R -> Vector R
cmod' = R -> Vector R -> Vector R
forall a. HasCallStack => a
undefined
fromInt' :: Vector I -> Vector R
fromInt' = Vector I -> Vector R
int2DoubleV
toInt' :: Vector R -> Vector I
toInt' = Vector R -> Vector I
double2IntV
fromZ' :: Vector Z -> Vector R
fromZ' = Vector Z -> Vector R
long2DoubleV
toZ' :: Vector R -> Vector Z
toZ' = Vector R -> Vector Z
double2longV
instance Container Vector (Complex Double)
where
conj' :: Vector (Complex R) -> Vector (Complex R)
conj' = Vector (Complex R) -> Vector (Complex R)
conjugateC
size' :: Vector (Complex R) -> IndexOf Vector
size' = Vector (Complex R) -> IndexOf Vector
forall t. Storable t => Vector t -> Int
dim
scale' :: Complex R -> Vector (Complex R) -> Vector (Complex R)
scale' = FunCodeSV -> Complex R -> Vector (Complex R) -> Vector (Complex R)
vectorMapValC FunCodeSV
Scale
addConstant :: Complex R -> Vector (Complex R) -> Vector (Complex R)
addConstant = FunCodeSV -> Complex R -> Vector (Complex R) -> Vector (Complex R)
vectorMapValC FunCodeSV
AddConstant
add' :: Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
add' = FunCodeVV
-> Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
vectorZipC FunCodeVV
Add
sub :: Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
sub = FunCodeVV
-> Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
vectorZipC FunCodeVV
Sub
mul :: Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
mul = FunCodeVV
-> Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
vectorZipC FunCodeVV
Mul
equal :: Vector (Complex R) -> Vector (Complex R) -> Bool
equal = Vector (Complex R) -> Vector (Complex R) -> Bool
forall a. Eq a => a -> a -> Bool
(==)
scalar' :: Complex R -> Vector (Complex R)
scalar' = Complex R -> Vector (Complex R)
forall a. Storable a => a -> Vector a
V.singleton
konst' :: Complex R -> IndexOf Vector -> Vector (Complex R)
konst' = Complex R -> IndexOf Vector -> Vector (Complex R)
forall a. Element a => a -> Int -> Vector a
constantD
build' :: IndexOf Vector -> ArgOf Vector (Complex R) -> Vector (Complex R)
build' = IndexOf Vector -> ArgOf Vector (Complex R) -> Vector (Complex R)
forall a t a.
(Integral a, Num t, Storable a) =>
a -> (t -> a) -> Vector a
buildV
cmap' :: (Complex R -> b) -> Vector (Complex R) -> Vector b
cmap' = (Complex R -> b) -> Vector (Complex R) -> Vector b
forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
mapVector
atIndex' :: Vector (Complex R) -> IndexOf Vector -> Complex R
atIndex' = Vector (Complex R) -> IndexOf Vector -> Complex R
forall t. Storable t => Vector t -> Int -> t
(@>)
minIndex' :: Vector (Complex R) -> IndexOf Vector
minIndex' = [Char] -> (Vector (Complex R) -> Int) -> Vector (Complex R) -> Int
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"minIndex" (Vector R -> Int
forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex' (Vector R -> Int)
-> (Vector (Complex R) -> Vector R) -> Vector (Complex R) -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector R, Vector R) -> Vector R
forall a b. (a, b) -> a
fst ((Vector R, Vector R) -> Vector R)
-> (Vector (Complex R) -> (Vector R, Vector R))
-> Vector (Complex R)
-> Vector R
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (Complex R) -> (Vector R, Vector R)
forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex (Vector (Complex R) -> (Vector R, Vector R))
-> (Vector (Complex R) -> Vector (Complex R))
-> Vector (Complex R)
-> (Vector R, Vector R)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
forall (c :: * -> *) e. Container c e => c e -> c e -> c e
mul (Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R))
-> (Vector (Complex R) -> Vector (Complex R))
-> Vector (Complex R)
-> Vector (Complex R)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Vector (Complex R) -> Vector (Complex R)
forall (c :: * -> *) e. Container c e => c e -> c e
conj'))
maxIndex' :: Vector (Complex R) -> IndexOf Vector
maxIndex' = [Char] -> (Vector (Complex R) -> Int) -> Vector (Complex R) -> Int
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"maxIndex" (Vector R -> Int
forall (c :: * -> *) e. Container c e => c e -> IndexOf c
maxIndex' (Vector R -> Int)
-> (Vector (Complex R) -> Vector R) -> Vector (Complex R) -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector R, Vector R) -> Vector R
forall a b. (a, b) -> a
fst ((Vector R, Vector R) -> Vector R)
-> (Vector (Complex R) -> (Vector R, Vector R))
-> Vector (Complex R)
-> Vector R
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (Complex R) -> (Vector R, Vector R)
forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex (Vector (Complex R) -> (Vector R, Vector R))
-> (Vector (Complex R) -> Vector (Complex R))
-> Vector (Complex R)
-> (Vector R, Vector R)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
forall (c :: * -> *) e. Container c e => c e -> c e -> c e
mul (Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R))
-> (Vector (Complex R) -> Vector (Complex R))
-> Vector (Complex R)
-> Vector (Complex R)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Vector (Complex R) -> Vector (Complex R)
forall (c :: * -> *) e. Container c e => c e -> c e
conj'))
minElement' :: Vector (Complex R) -> Complex R
minElement' = [Char]
-> (Vector (Complex R) -> Complex R)
-> Vector (Complex R)
-> Complex R
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"minElement" (Vector (Complex R) -> Int -> Complex R
forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex' (Vector (Complex R) -> Int -> Complex R)
-> (Vector (Complex R) -> Int) -> Vector (Complex R) -> Complex R
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Vector (Complex R) -> Int
forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex')
maxElement' :: Vector (Complex R) -> Complex R
maxElement' = [Char]
-> (Vector (Complex R) -> Complex R)
-> Vector (Complex R)
-> Complex R
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"maxElement" (Vector (Complex R) -> Int -> Complex R
forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex' (Vector (Complex R) -> Int -> Complex R)
-> (Vector (Complex R) -> Int) -> Vector (Complex R) -> Complex R
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Vector (Complex R) -> Int
forall (c :: * -> *) e. Container c e => c e -> IndexOf c
maxIndex')
sumElements' :: Vector (Complex R) -> Complex R
sumElements' = Vector (Complex R) -> Complex R
sumC
prodElements' :: Vector (Complex R) -> Complex R
prodElements' = Vector (Complex R) -> Complex R
prodC
step' :: Vector (Complex R) -> Vector (Complex R)
step' = Vector (Complex R) -> Vector (Complex R)
forall a. HasCallStack => a
undefined
find' :: (Complex R -> Bool) -> Vector (Complex R) -> [IndexOf Vector]
find' = (Complex R -> Bool) -> Vector (Complex R) -> [IndexOf Vector]
forall t. Storable t => (t -> Bool) -> Vector t -> [Int]
findV
assoc' :: IndexOf Vector
-> Complex R -> [(IndexOf Vector, Complex R)] -> Vector (Complex R)
assoc' = IndexOf Vector
-> Complex R -> [(IndexOf Vector, Complex R)] -> Vector (Complex R)
forall t (t :: * -> *).
(Storable t, Foldable t) =>
Int -> t -> t (Int, t) -> Vector t
assocV
accum' :: Vector (Complex R)
-> (Complex R -> Complex R -> Complex R)
-> [(IndexOf Vector, Complex R)]
-> Vector (Complex R)
accum' = Vector (Complex R)
-> (Complex R -> Complex R -> Complex R)
-> [(IndexOf Vector, Complex R)]
-> Vector (Complex R)
forall t (t :: * -> *) t.
(Storable t, Foldable t) =>
Vector t -> (t -> t -> t) -> t (Int, t) -> Vector t
accumV
ccompare' :: Vector (Complex R) -> Vector (Complex R) -> Vector I
ccompare' = Vector (Complex R) -> Vector (Complex R) -> Vector I
forall a. HasCallStack => a
undefined
cselect' :: Vector I
-> Vector (Complex R)
-> Vector (Complex R)
-> Vector (Complex R)
-> Vector (Complex R)
cselect' = (Vector I
-> Vector (Complex R)
-> Vector (Complex R)
-> Vector (Complex R)
-> Vector (Complex R))
-> Vector I
-> Vector (Complex R)
-> Vector (Complex R)
-> Vector (Complex R)
-> Vector (Complex R)
forall e t.
Container Vector e =>
(Vector I -> Vector e -> Vector e -> Vector e -> t)
-> Vector I -> Vector e -> Vector e -> Vector e -> t
selectCV Vector I
-> Vector (Complex R)
-> Vector (Complex R)
-> Vector (Complex R)
-> Vector (Complex R)
forall a.
Element a =>
Vector I -> Vector a -> Vector a -> Vector a -> Vector a
selectV
scaleRecip :: Complex R -> Vector (Complex R) -> Vector (Complex R)
scaleRecip = FunCodeSV -> Complex R -> Vector (Complex R) -> Vector (Complex R)
vectorMapValC FunCodeSV
Recip
divide :: Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
divide = FunCodeVV
-> Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
vectorZipC FunCodeVV
Div
arctan2' :: Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
arctan2' = FunCodeVV
-> Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
vectorZipC FunCodeVV
ATan2
cmod' :: Complex R -> Vector (Complex R) -> Vector (Complex R)
cmod' = Complex R -> Vector (Complex R) -> Vector (Complex R)
forall a. HasCallStack => a
undefined
fromInt' :: Vector I -> Vector (Complex R)
fromInt' = Vector R -> Vector (Complex R)
forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (ComplexOf t)
complex (Vector R -> Vector (Complex R))
-> (Vector I -> Vector R) -> Vector I -> Vector (Complex R)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector I -> Vector R
int2DoubleV
toInt' :: Vector (Complex R) -> Vector I
toInt' = Vector R -> Vector I
forall (c :: * -> *) e. Container c e => c e -> c I
toInt' (Vector R -> Vector I)
-> (Vector (Complex R) -> Vector R)
-> Vector (Complex R)
-> Vector I
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector R, Vector R) -> Vector R
forall a b. (a, b) -> a
fst ((Vector R, Vector R) -> Vector R)
-> (Vector (Complex R) -> (Vector R, Vector R))
-> Vector (Complex R)
-> Vector R
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (Complex R) -> (Vector R, Vector R)
forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex
fromZ' :: Vector Z -> Vector (Complex R)
fromZ' = Vector R -> Vector (Complex R)
forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (ComplexOf t)
complex (Vector R -> Vector (Complex R))
-> (Vector Z -> Vector R) -> Vector Z -> Vector (Complex R)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Z -> Vector R
long2DoubleV
toZ' :: Vector (Complex R) -> Vector Z
toZ' = Vector R -> Vector Z
forall (c :: * -> *) e. Container c e => c e -> c Z
toZ' (Vector R -> Vector Z)
-> (Vector (Complex R) -> Vector R)
-> Vector (Complex R)
-> Vector Z
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector R, Vector R) -> Vector R
forall a b. (a, b) -> a
fst ((Vector R, Vector R) -> Vector R)
-> (Vector (Complex R) -> (Vector R, Vector R))
-> Vector (Complex R)
-> Vector R
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (Complex R) -> (Vector R, Vector R)
forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex
instance Container Vector (Complex Float)
where
conj' :: Vector (Complex Float) -> Vector (Complex Float)
conj' = Vector (Complex Float) -> Vector (Complex Float)
conjugateQ
size' :: Vector (Complex Float) -> IndexOf Vector
size' = Vector (Complex Float) -> IndexOf Vector
forall t. Storable t => Vector t -> Int
dim
scale' :: Complex Float -> Vector (Complex Float) -> Vector (Complex Float)
scale' = FunCodeSV
-> Complex Float
-> Vector (Complex Float)
-> Vector (Complex Float)
vectorMapValQ FunCodeSV
Scale
addConstant :: Complex Float -> Vector (Complex Float) -> Vector (Complex Float)
addConstant = FunCodeSV
-> Complex Float
-> Vector (Complex Float)
-> Vector (Complex Float)
vectorMapValQ FunCodeSV
AddConstant
add' :: Vector (Complex Float)
-> Vector (Complex Float) -> Vector (Complex Float)
add' = FunCodeVV
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
vectorZipQ FunCodeVV
Add
sub :: Vector (Complex Float)
-> Vector (Complex Float) -> Vector (Complex Float)
sub = FunCodeVV
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
vectorZipQ FunCodeVV
Sub
mul :: Vector (Complex Float)
-> Vector (Complex Float) -> Vector (Complex Float)
mul = FunCodeVV
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
vectorZipQ FunCodeVV
Mul
equal :: Vector (Complex Float) -> Vector (Complex Float) -> Bool
equal = Vector (Complex Float) -> Vector (Complex Float) -> Bool
forall a. Eq a => a -> a -> Bool
(==)
scalar' :: Complex Float -> Vector (Complex Float)
scalar' = Complex Float -> Vector (Complex Float)
forall a. Storable a => a -> Vector a
V.singleton
konst' :: Complex Float -> IndexOf Vector -> Vector (Complex Float)
konst' = Complex Float -> IndexOf Vector -> Vector (Complex Float)
forall a. Element a => a -> Int -> Vector a
constantD
build' :: IndexOf Vector
-> ArgOf Vector (Complex Float) -> Vector (Complex Float)
build' = IndexOf Vector
-> ArgOf Vector (Complex Float) -> Vector (Complex Float)
forall a t a.
(Integral a, Num t, Storable a) =>
a -> (t -> a) -> Vector a
buildV
cmap' :: (Complex Float -> b) -> Vector (Complex Float) -> Vector b
cmap' = (Complex Float -> b) -> Vector (Complex Float) -> Vector b
forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
mapVector
atIndex' :: Vector (Complex Float) -> IndexOf Vector -> Complex Float
atIndex' = Vector (Complex Float) -> IndexOf Vector -> Complex Float
forall t. Storable t => Vector t -> Int -> t
(@>)
minIndex' :: Vector (Complex Float) -> IndexOf Vector
minIndex' = [Char]
-> (Vector (Complex Float) -> Int) -> Vector (Complex Float) -> Int
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"minIndex" (Vector Float -> Int
forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex' (Vector Float -> Int)
-> (Vector (Complex Float) -> Vector Float)
-> Vector (Complex Float)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector Float, Vector Float) -> Vector Float
forall a b. (a, b) -> a
fst ((Vector Float, Vector Float) -> Vector Float)
-> (Vector (Complex Float) -> (Vector Float, Vector Float))
-> Vector (Complex Float)
-> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (Complex Float) -> (Vector Float, Vector Float)
forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex (Vector (Complex Float) -> (Vector Float, Vector Float))
-> (Vector (Complex Float) -> Vector (Complex Float))
-> Vector (Complex Float)
-> (Vector Float, Vector Float)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector (Complex Float)
-> Vector (Complex Float) -> Vector (Complex Float)
forall (c :: * -> *) e. Container c e => c e -> c e -> c e
mul (Vector (Complex Float)
-> Vector (Complex Float) -> Vector (Complex Float))
-> (Vector (Complex Float) -> Vector (Complex Float))
-> Vector (Complex Float)
-> Vector (Complex Float)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Vector (Complex Float) -> Vector (Complex Float)
forall (c :: * -> *) e. Container c e => c e -> c e
conj'))
maxIndex' :: Vector (Complex Float) -> IndexOf Vector
maxIndex' = [Char]
-> (Vector (Complex Float) -> Int) -> Vector (Complex Float) -> Int
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"maxIndex" (Vector Float -> Int
forall (c :: * -> *) e. Container c e => c e -> IndexOf c
maxIndex' (Vector Float -> Int)
-> (Vector (Complex Float) -> Vector Float)
-> Vector (Complex Float)
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector Float, Vector Float) -> Vector Float
forall a b. (a, b) -> a
fst ((Vector Float, Vector Float) -> Vector Float)
-> (Vector (Complex Float) -> (Vector Float, Vector Float))
-> Vector (Complex Float)
-> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (Complex Float) -> (Vector Float, Vector Float)
forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex (Vector (Complex Float) -> (Vector Float, Vector Float))
-> (Vector (Complex Float) -> Vector (Complex Float))
-> Vector (Complex Float)
-> (Vector Float, Vector Float)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector (Complex Float)
-> Vector (Complex Float) -> Vector (Complex Float)
forall (c :: * -> *) e. Container c e => c e -> c e -> c e
mul (Vector (Complex Float)
-> Vector (Complex Float) -> Vector (Complex Float))
-> (Vector (Complex Float) -> Vector (Complex Float))
-> Vector (Complex Float)
-> Vector (Complex Float)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Vector (Complex Float) -> Vector (Complex Float)
forall (c :: * -> *) e. Container c e => c e -> c e
conj'))
minElement' :: Vector (Complex Float) -> Complex Float
minElement' = [Char]
-> (Vector (Complex Float) -> Complex Float)
-> Vector (Complex Float)
-> Complex Float
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"minElement" (Vector (Complex Float) -> Int -> Complex Float
forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex' (Vector (Complex Float) -> Int -> Complex Float)
-> (Vector (Complex Float) -> Int)
-> Vector (Complex Float)
-> Complex Float
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Vector (Complex Float) -> Int
forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex')
maxElement' :: Vector (Complex Float) -> Complex Float
maxElement' = [Char]
-> (Vector (Complex Float) -> Complex Float)
-> Vector (Complex Float)
-> Complex Float
forall t p.
Storable t =>
[Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
"maxElement" (Vector (Complex Float) -> Int -> Complex Float
forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex' (Vector (Complex Float) -> Int -> Complex Float)
-> (Vector (Complex Float) -> Int)
-> Vector (Complex Float)
-> Complex Float
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Vector (Complex Float) -> Int
forall (c :: * -> *) e. Container c e => c e -> IndexOf c
maxIndex')
sumElements' :: Vector (Complex Float) -> Complex Float
sumElements' = Vector (Complex Float) -> Complex Float
sumQ
prodElements' :: Vector (Complex Float) -> Complex Float
prodElements' = Vector (Complex Float) -> Complex Float
prodQ
step' :: Vector (Complex Float) -> Vector (Complex Float)
step' = Vector (Complex Float) -> Vector (Complex Float)
forall a. HasCallStack => a
undefined
find' :: (Complex Float -> Bool)
-> Vector (Complex Float) -> [IndexOf Vector]
find' = (Complex Float -> Bool)
-> Vector (Complex Float) -> [IndexOf Vector]
forall t. Storable t => (t -> Bool) -> Vector t -> [Int]
findV
assoc' :: IndexOf Vector
-> Complex Float
-> [(IndexOf Vector, Complex Float)]
-> Vector (Complex Float)
assoc' = IndexOf Vector
-> Complex Float
-> [(IndexOf Vector, Complex Float)]
-> Vector (Complex Float)
forall t (t :: * -> *).
(Storable t, Foldable t) =>
Int -> t -> t (Int, t) -> Vector t
assocV
accum' :: Vector (Complex Float)
-> (Complex Float -> Complex Float -> Complex Float)
-> [(IndexOf Vector, Complex Float)]
-> Vector (Complex Float)
accum' = Vector (Complex Float)
-> (Complex Float -> Complex Float -> Complex Float)
-> [(IndexOf Vector, Complex Float)]
-> Vector (Complex Float)
forall t (t :: * -> *) t.
(Storable t, Foldable t) =>
Vector t -> (t -> t -> t) -> t (Int, t) -> Vector t
accumV
ccompare' :: Vector (Complex Float) -> Vector (Complex Float) -> Vector I
ccompare' = Vector (Complex Float) -> Vector (Complex Float) -> Vector I
forall a. HasCallStack => a
undefined
cselect' :: Vector I
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
cselect' = (Vector I
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float))
-> Vector I
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
forall e t.
Container Vector e =>
(Vector I -> Vector e -> Vector e -> Vector e -> t)
-> Vector I -> Vector e -> Vector e -> Vector e -> t
selectCV Vector I
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
forall a.
Element a =>
Vector I -> Vector a -> Vector a -> Vector a -> Vector a
selectV
scaleRecip :: Complex Float -> Vector (Complex Float) -> Vector (Complex Float)
scaleRecip = FunCodeSV
-> Complex Float
-> Vector (Complex Float)
-> Vector (Complex Float)
vectorMapValQ FunCodeSV
Recip
divide :: Vector (Complex Float)
-> Vector (Complex Float) -> Vector (Complex Float)
divide = FunCodeVV
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
vectorZipQ FunCodeVV
Div
arctan2' :: Vector (Complex Float)
-> Vector (Complex Float) -> Vector (Complex Float)
arctan2' = FunCodeVV
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
vectorZipQ FunCodeVV
ATan2
cmod' :: Complex Float -> Vector (Complex Float) -> Vector (Complex Float)
cmod' = Complex Float -> Vector (Complex Float) -> Vector (Complex Float)
forall a. HasCallStack => a
undefined
fromInt' :: Vector I -> Vector (Complex Float)
fromInt' = Vector Float -> Vector (Complex Float)
forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (ComplexOf t)
complex (Vector Float -> Vector (Complex Float))
-> (Vector I -> Vector Float) -> Vector I -> Vector (Complex Float)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector I -> Vector Float
int2floatV
toInt' :: Vector (Complex Float) -> Vector I
toInt' = Vector Float -> Vector I
forall (c :: * -> *) e. Container c e => c e -> c I
toInt' (Vector Float -> Vector I)
-> (Vector (Complex Float) -> Vector Float)
-> Vector (Complex Float)
-> Vector I
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector Float, Vector Float) -> Vector Float
forall a b. (a, b) -> a
fst ((Vector Float, Vector Float) -> Vector Float)
-> (Vector (Complex Float) -> (Vector Float, Vector Float))
-> Vector (Complex Float)
-> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (Complex Float) -> (Vector Float, Vector Float)
forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex
fromZ' :: Vector Z -> Vector (Complex Float)
fromZ' = Vector Float -> Vector (Complex Float)
forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (ComplexOf t)
complex (Vector Float -> Vector (Complex Float))
-> (Vector Z -> Vector Float) -> Vector Z -> Vector (Complex Float)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector R -> Vector Float
forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (SingleOf t)
single (Vector R -> Vector Float)
-> (Vector Z -> Vector R) -> Vector Z -> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Z -> Vector R
long2DoubleV
toZ' :: Vector (Complex Float) -> Vector Z
toZ' = Vector R -> Vector Z
forall (c :: * -> *) e. Container c e => c e -> c Z
toZ' (Vector R -> Vector Z)
-> (Vector (Complex Float) -> Vector R)
-> Vector (Complex Float)
-> Vector Z
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Float -> Vector R
forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (DoubleOf t)
double (Vector Float -> Vector R)
-> (Vector (Complex Float) -> Vector Float)
-> Vector (Complex Float)
-> Vector R
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector Float, Vector Float) -> Vector Float
forall a b. (a, b) -> a
fst ((Vector Float, Vector Float) -> Vector Float)
-> (Vector (Complex Float) -> (Vector Float, Vector Float))
-> Vector (Complex Float)
-> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (Complex Float) -> (Vector Float, Vector Float)
forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex
instance (Num a, Element a, Container Vector a) => Container Matrix a
where
conj' :: Matrix a -> Matrix a
conj' = (Vector a -> Vector a) -> Matrix a -> Matrix a
forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix Vector a -> Vector a
forall (c :: * -> *) e. Container c e => c e -> c e
conj'
size' :: Matrix a -> IndexOf Matrix
size' = Matrix a -> IndexOf Matrix
forall t. Matrix t -> (Int, Int)
size
scale' :: a -> Matrix a -> Matrix a
scale' a
x = (Vector a -> Vector a) -> Matrix a -> Matrix a
forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix (a -> Vector a -> Vector a
forall (c :: * -> *) e. Container c e => e -> c e -> c e
scale' a
x)
addConstant :: a -> Matrix a -> Matrix a
addConstant a
x = (Vector a -> Vector a) -> Matrix a -> Matrix a
forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix (a -> Vector a -> Vector a
forall (c :: * -> *) e. Container c e => e -> c e -> c e
addConstant a
x)
add' :: Matrix a -> Matrix a -> Matrix a
add' = (Vector a -> Vector a -> Vector a)
-> Matrix a -> Matrix a -> Matrix a
forall t a b.
(Element t, Element a, Element b) =>
(Vector a -> Vector b -> Vector t)
-> Matrix a -> Matrix b -> Matrix t
liftMatrix2 Vector a -> Vector a -> Vector a
forall (c :: * -> *) e. Container c e => c e -> c e -> c e
add'
sub :: Matrix a -> Matrix a -> Matrix a
sub = (Vector a -> Vector a -> Vector a)
-> Matrix a -> Matrix a -> Matrix a
forall t a b.
(Element t, Element a, Element b) =>
(Vector a -> Vector b -> Vector t)
-> Matrix a -> Matrix b -> Matrix t
liftMatrix2 Vector a -> Vector a -> Vector a
forall (c :: * -> *) e. Container c e => c e -> c e -> c e
sub
mul :: Matrix a -> Matrix a -> Matrix a
mul = (Vector a -> Vector a -> Vector a)
-> Matrix a -> Matrix a -> Matrix a
forall t a b.
(Element t, Element a, Element b) =>
(Vector a -> Vector b -> Vector t)
-> Matrix a -> Matrix b -> Matrix t
liftMatrix2 Vector a -> Vector a -> Vector a
forall (c :: * -> *) e. Container c e => c e -> c e -> c e
mul
equal :: Matrix a -> Matrix a -> Bool
equal Matrix a
a Matrix a
b = Matrix a -> Int
forall t. Matrix t -> Int
cols Matrix a
a Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Matrix a -> Int
forall t. Matrix t -> Int
cols Matrix a
b Bool -> Bool -> Bool
&& Matrix a -> Vector a
forall t. Element t => Matrix t -> Vector t
flatten Matrix a
a Vector a -> Vector a -> Bool
forall (c :: * -> *) e. Container c e => c e -> c e -> Bool
`equal` Matrix a -> Vector a
forall t. Element t => Matrix t -> Vector t
flatten Matrix a
b
scalar' :: a -> Matrix a
scalar' a
x = (Int
1Int -> Int -> [a] -> Matrix a
forall a. Storable a => Int -> Int -> [a] -> Matrix a
><Int
1) [a
x]
konst' :: a -> IndexOf Matrix -> Matrix a
konst' a
v (r,c) = MatrixOrder -> Int -> Int -> Vector a -> Matrix a
forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
RowMajor Int
r Int
c (a -> IndexOf Vector -> Vector a
forall (c :: * -> *) e. Container c e => e -> IndexOf c -> c e
konst' a
v (Int
rInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
c))
build' :: IndexOf Matrix -> ArgOf Matrix a -> Matrix a
build' = IndexOf Matrix -> ArgOf Matrix a -> Matrix a
forall a a t t t.
(Integral a, Integral a, Num t, Num t, Element t) =>
(a, a) -> (t -> t -> t) -> Matrix t
buildM
cmap' :: (a -> b) -> Matrix a -> Matrix b
cmap' a -> b
f = (Vector a -> Vector b) -> Matrix a -> Matrix b
forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix ((a -> b) -> Vector a -> Vector b
forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
mapVector a -> b
f)
atIndex' :: Matrix a -> IndexOf Matrix -> a
atIndex' = Matrix a -> IndexOf Matrix -> a
forall t. Storable t => Matrix t -> (Int, Int) -> t
(@@>)
minIndex' :: Matrix a -> IndexOf Matrix
minIndex' = [Char] -> (Matrix a -> (Int, Int)) -> Matrix a -> (Int, Int)
forall t p. [Char] -> (Matrix t -> p) -> Matrix t -> p
emptyErrorM [Char]
"minIndex of Matrix" ((Matrix a -> (Int, Int)) -> Matrix a -> (Int, Int))
-> (Matrix a -> (Int, Int)) -> Matrix a -> (Int, Int)
forall a b. (a -> b) -> a -> b
$
\Matrix a
m -> Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
divMod (Vector a -> IndexOf Vector
forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex' (Vector a -> IndexOf Vector) -> Vector a -> IndexOf Vector
forall a b. (a -> b) -> a -> b
$ Matrix a -> Vector a
forall t. Element t => Matrix t -> Vector t
flatten Matrix a
m) (Matrix a -> Int
forall t. Matrix t -> Int
cols Matrix a
m)
maxIndex' :: Matrix a -> IndexOf Matrix
maxIndex' = [Char] -> (Matrix a -> (Int, Int)) -> Matrix a -> (Int, Int)
forall t p. [Char] -> (Matrix t -> p) -> Matrix t -> p
emptyErrorM [Char]
"maxIndex of Matrix" ((Matrix a -> (Int, Int)) -> Matrix a -> (Int, Int))
-> (Matrix a -> (Int, Int)) -> Matrix a -> (Int, Int)
forall a b. (a -> b) -> a -> b
$
\Matrix a
m -> Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
divMod (Vector a -> IndexOf Vector
forall (c :: * -> *) e. Container c e => c e -> IndexOf c
maxIndex' (Vector a -> IndexOf Vector) -> Vector a -> IndexOf Vector
forall a b. (a -> b) -> a -> b
$ Matrix a -> Vector a
forall t. Element t => Matrix t -> Vector t
flatten Matrix a
m) (Matrix a -> Int
forall t. Matrix t -> Int
cols Matrix a
m)
minElement' :: Matrix a -> a
minElement' = [Char] -> (Matrix a -> a) -> Matrix a -> a
forall t p. [Char] -> (Matrix t -> p) -> Matrix t -> p
emptyErrorM [Char]
"minElement of Matrix" (Matrix a -> (Int, Int) -> a
forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex' (Matrix a -> (Int, Int) -> a)
-> (Matrix a -> (Int, Int)) -> Matrix a -> a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Matrix a -> (Int, Int)
forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex')
maxElement' :: Matrix a -> a
maxElement' = [Char] -> (Matrix a -> a) -> Matrix a -> a
forall t p. [Char] -> (Matrix t -> p) -> Matrix t -> p
emptyErrorM [Char]
"maxElement of Matrix" (Matrix a -> (Int, Int) -> a
forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex' (Matrix a -> (Int, Int) -> a)
-> (Matrix a -> (Int, Int)) -> Matrix a -> a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Matrix a -> (Int, Int)
forall (c :: * -> *) e. Container c e => c e -> IndexOf c
maxIndex')
sumElements' :: Matrix a -> a
sumElements' = Vector a -> a
forall (c :: * -> *) e. Container c e => c e -> e
sumElements' (Vector a -> a) -> (Matrix a -> Vector a) -> Matrix a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix a -> Vector a
forall t. Element t => Matrix t -> Vector t
flatten
prodElements' :: Matrix a -> a
prodElements' = Vector a -> a
forall (c :: * -> *) e. Container c e => c e -> e
prodElements' (Vector a -> a) -> (Matrix a -> Vector a) -> Matrix a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix a -> Vector a
forall t. Element t => Matrix t -> Vector t
flatten
step' :: Matrix a -> Matrix a
step' = (Vector a -> Vector a) -> Matrix a -> Matrix a
forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix Vector a -> Vector a
forall (c :: * -> *) e. (Container c e, Ord e) => c e -> c e
step'
find' :: (a -> Bool) -> Matrix a -> [IndexOf Matrix]
find' = (a -> Bool) -> Matrix a -> [IndexOf Matrix]
forall t. Element t => (t -> Bool) -> Matrix t -> [(Int, Int)]
findM
assoc' :: IndexOf Matrix -> a -> [(IndexOf Matrix, a)] -> Matrix a
assoc' = IndexOf Matrix -> a -> [(IndexOf Matrix, a)] -> Matrix a
forall t (t :: * -> *).
(Storable t, Foldable t) =>
(Int, Int) -> t -> t ((Int, Int), t) -> Matrix t
assocM
accum' :: Matrix a -> (a -> a -> a) -> [(IndexOf Matrix, a)] -> Matrix a
accum' = Matrix a -> (a -> a -> a) -> [(IndexOf Matrix, a)] -> Matrix a
forall t (t :: * -> *) t.
(Element t, Foldable t) =>
Matrix t -> (t -> t -> t) -> t ((Int, Int), t) -> Matrix t
accumM
ccompare' :: Matrix a -> Matrix a -> Matrix I
ccompare' = Matrix a -> Matrix a -> Matrix I
forall e.
(Container Vector e, Ord e) =>
Matrix e -> Matrix e -> Matrix I
compareM
cselect' :: Matrix I -> Matrix a -> Matrix a -> Matrix a -> Matrix a
cselect' = Matrix I -> Matrix a -> Matrix a -> Matrix a -> Matrix a
forall t.
(Num t, Container Vector t) =>
Matrix I -> Matrix t -> Matrix t -> Matrix t -> Matrix t
selectM
scaleRecip :: a -> Matrix a -> Matrix a
scaleRecip a
x = (Vector a -> Vector a) -> Matrix a -> Matrix a
forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix (a -> Vector a -> Vector a
forall (c :: * -> *) e.
(Container c e, Fractional e) =>
e -> c e -> c e
scaleRecip a
x)
divide :: Matrix a -> Matrix a -> Matrix a
divide = (Vector a -> Vector a -> Vector a)
-> Matrix a -> Matrix a -> Matrix a
forall t a b.
(Element t, Element a, Element b) =>
(Vector a -> Vector b -> Vector t)
-> Matrix a -> Matrix b -> Matrix t
liftMatrix2 Vector a -> Vector a -> Vector a
forall (c :: * -> *) e.
(Container c e, Fractional e) =>
c e -> c e -> c e
divide
arctan2' :: Matrix a -> Matrix a -> Matrix a
arctan2' = (Vector a -> Vector a -> Vector a)
-> Matrix a -> Matrix a -> Matrix a
forall t a b.
(Element t, Element a, Element b) =>
(Vector a -> Vector b -> Vector t)
-> Matrix a -> Matrix b -> Matrix t
liftMatrix2 Vector a -> Vector a -> Vector a
forall (c :: * -> *) e.
(Container c e, Fractional e) =>
c e -> c e -> c e
arctan2'
cmod' :: a -> Matrix a -> Matrix a
cmod' a
m Matrix a
x
| a
m a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
0 = (Vector a -> Vector a) -> Matrix a -> Matrix a
forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix (a -> Vector a -> Vector a
forall (c :: * -> *) e.
(Container c e, Integral e) =>
e -> c e -> c e
cmod' a
m) Matrix a
x
| Bool
otherwise = [Char] -> Matrix a
forall a. HasCallStack => [Char] -> a
error ([Char] -> Matrix a) -> [Char] -> Matrix a
forall a b. (a -> b) -> a -> b
$ [Char]
"cmod 0 on matrix "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++Matrix a -> [Char]
forall t. Matrix t -> [Char]
shSize Matrix a
x
fromInt' :: Matrix I -> Matrix a
fromInt' = (Vector I -> Vector a) -> Matrix I -> Matrix a
forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix Vector I -> Vector a
forall (c :: * -> *) e. Container c e => c I -> c e
fromInt'
toInt' :: Matrix a -> Matrix I
toInt' = (Vector a -> Vector I) -> Matrix a -> Matrix I
forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix Vector a -> Vector I
forall (c :: * -> *) e. Container c e => c e -> c I
toInt'
fromZ' :: Matrix Z -> Matrix a
fromZ' = (Vector Z -> Vector a) -> Matrix Z -> Matrix a
forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix Vector Z -> Vector a
forall (c :: * -> *) e. Container c e => c Z -> c e
fromZ'
toZ' :: Matrix a -> Matrix Z
toZ' = (Vector a -> Vector Z) -> Matrix a -> Matrix Z
forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix Vector a -> Vector Z
forall (c :: * -> *) e. Container c e => c e -> c Z
toZ'
emptyErrorV :: [Char] -> (Vector t -> p) -> Vector t -> p
emptyErrorV [Char]
msg Vector t -> p
f Vector t
v =
if Vector t -> Int
forall t. Storable t => Vector t -> Int
dim Vector t
v Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then Vector t -> p
f Vector t
v
else [Char] -> p
forall a. HasCallStack => [Char] -> a
error ([Char] -> p) -> [Char] -> p
forall a b. (a -> b) -> a -> b
$ [Char]
msg [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" of empty Vector"
emptyErrorM :: [Char] -> (Matrix t -> p) -> Matrix t -> p
emptyErrorM [Char]
msg Matrix t -> p
f Matrix t
m =
if Matrix t -> Int
forall t. Matrix t -> Int
rows Matrix t
m Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
&& Matrix t -> Int
forall t. Matrix t -> Int
cols Matrix t
m Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then Matrix t -> p
f Matrix t
m
else [Char] -> p
forall a. HasCallStack => [Char] -> a
error ([Char] -> p) -> [Char] -> p
forall a b. (a -> b) -> a -> b
$ [Char]
msg[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
" "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++Matrix t -> [Char]
forall t. Matrix t -> [Char]
shSize Matrix t
m
scalar :: Container c e => e -> c e
scalar :: e -> c e
scalar = e -> c e
forall (c :: * -> *) e. Container c e => e -> c e
scalar'
conj :: Container c e => c e -> c e
conj :: c e -> c e
conj = c e -> c e
forall (c :: * -> *) e. Container c e => c e -> c e
conj'
arctan2 :: (Fractional e, Container c e) => c e -> c e -> c e
arctan2 :: c e -> c e -> c e
arctan2 = c e -> c e -> c e
forall (c :: * -> *) e.
(Container c e, Fractional e) =>
c e -> c e -> c e
arctan2'
cmod :: (Integral e, Container c e) => e -> c e -> c e
cmod :: e -> c e -> c e
cmod = e -> c e -> c e
forall (c :: * -> *) e.
(Container c e, Integral e) =>
e -> c e -> c e
cmod'
fromInt :: (Container c e) => c I -> c e
fromInt :: c I -> c e
fromInt = c I -> c e
forall (c :: * -> *) e. Container c e => c I -> c e
fromInt'
toInt :: (Container c e) => c e -> c I
toInt :: c e -> c I
toInt = c e -> c I
forall (c :: * -> *) e. Container c e => c e -> c I
toInt'
fromZ :: (Container c e) => c Z -> c e
fromZ :: c Z -> c e
fromZ = c Z -> c e
forall (c :: * -> *) e. Container c e => c Z -> c e
fromZ'
toZ :: (Container c e) => c e -> c Z
toZ :: c e -> c Z
toZ = c e -> c Z
forall (c :: * -> *) e. Container c e => c e -> c Z
toZ'
cmap :: (Element b, Container c e) => (e -> b) -> c e -> c b
cmap :: (e -> b) -> c e -> c b
cmap = (e -> b) -> c e -> c b
forall (c :: * -> *) e b.
(Container c e, Element b) =>
(e -> b) -> c e -> c b
cmap'
atIndex :: Container c e => c e -> IndexOf c -> e
atIndex :: c e -> IndexOf c -> e
atIndex = c e -> IndexOf c -> e
forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex'
minIndex :: Container c e => c e -> IndexOf c
minIndex :: c e -> IndexOf c
minIndex = c e -> IndexOf c
forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex'
maxIndex :: Container c e => c e -> IndexOf c
maxIndex :: c e -> IndexOf c
maxIndex = c e -> IndexOf c
forall (c :: * -> *) e. Container c e => c e -> IndexOf c
maxIndex'
minElement :: Container c e => c e -> e
minElement :: c e -> e
minElement = c e -> e
forall (c :: * -> *) e. Container c e => c e -> e
minElement'
maxElement :: Container c e => c e -> e
maxElement :: c e -> e
maxElement = c e -> e
forall (c :: * -> *) e. Container c e => c e -> e
maxElement'
sumElements :: Container c e => c e -> e
sumElements :: c e -> e
sumElements = c e -> e
forall (c :: * -> *) e. Container c e => c e -> e
sumElements'
prodElements :: Container c e => c e -> e
prodElements :: c e -> e
prodElements = c e -> e
forall (c :: * -> *) e. Container c e => c e -> e
prodElements'
step
:: (Ord e, Container c e)
=> c e
-> c e
step :: c e -> c e
step = c e -> c e
forall (c :: * -> *) e. (Container c e, Ord e) => c e -> c e
step'
cond
:: (Ord e, Container c e, Container c x)
=> c e
-> c e
-> c x
-> c x
-> c x
-> c x
cond :: c e -> c e -> c x -> c x -> c x -> c x
cond c e
a c e
b c x
l c x
e c x
g = c I -> c x -> c x -> c x -> c x
forall (c :: * -> *) e.
Container c e =>
c I -> c e -> c e -> c e -> c e
cselect' (c e -> c e -> c I
forall (c :: * -> *) e. (Container c e, Ord e) => c e -> c e -> c I
ccompare' c e
a c e
b) c x
l c x
e c x
g
find
:: Container c e
=> (e -> Bool)
-> c e
-> [IndexOf c]
find :: (e -> Bool) -> c e -> [IndexOf c]
find = (e -> Bool) -> c e -> [IndexOf c]
forall (c :: * -> *) e.
Container c e =>
(e -> Bool) -> c e -> [IndexOf c]
find'
assoc
:: Container c e
=> IndexOf c
-> e
-> [(IndexOf c, e)]
-> c e
assoc :: IndexOf c -> e -> [(IndexOf c, e)] -> c e
assoc = IndexOf c -> e -> [(IndexOf c, e)] -> c e
forall (c :: * -> *) e.
Container c e =>
IndexOf c -> e -> [(IndexOf c, e)] -> c e
assoc'
accum
:: Container c e
=> c e
-> (e -> e -> e)
-> [(IndexOf c, e)]
-> c e
accum :: c e -> (e -> e -> e) -> [(IndexOf c, e)] -> c e
accum = c e -> (e -> e -> e) -> [(IndexOf c, e)] -> c e
forall (c :: * -> *) e.
Container c e =>
c e -> (e -> e -> e) -> [(IndexOf c, e)] -> c e
accum'
class Konst e d c | d -> c, c -> d
where
konst :: e -> d -> c e
instance Container Vector e => Konst e Int Vector
where
konst :: e -> Int -> Vector e
konst = e -> Int -> Vector e
forall (c :: * -> *) e. Container c e => e -> IndexOf c -> c e
konst'
instance (Num e, Container Vector e) => Konst e (Int,Int) Matrix
where
konst :: e -> (Int, Int) -> Matrix e
konst = e -> (Int, Int) -> Matrix e
forall (c :: * -> *) e. Container c e => e -> IndexOf c -> c e
konst'
class ( Container Vector t
, Container Matrix t
, Konst t Int Vector
, Konst t (Int,Int) Matrix
, CTrans t
, Product t
, Additive (Vector t)
, Additive (Matrix t)
, Linear t Vector
, Linear t Matrix
) => Numeric t
instance Numeric Double
instance Numeric (Complex Double)
instance Numeric Float
instance Numeric (Complex Float)
instance Numeric I
instance Numeric Z
class (Num e, Element e) => Product e where
multiply :: Matrix e -> Matrix e -> Matrix e
absSum :: Vector e -> RealOf e
norm1 :: Vector e -> RealOf e
norm2 :: Floating e => Vector e -> RealOf e
normInf :: Vector e -> RealOf e
instance Product Float where
norm2 :: Vector Float -> RealOf Float
norm2 = (Vector Float -> Float) -> Vector Float -> Float
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (FunCodeS -> Vector Float -> Float
toScalarF FunCodeS
Norm2)
absSum :: Vector Float -> RealOf Float
absSum = (Vector Float -> Float) -> Vector Float -> Float
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (FunCodeS -> Vector Float -> Float
toScalarF FunCodeS
AbsSum)
norm1 :: Vector Float -> RealOf Float
norm1 = (Vector Float -> Float) -> Vector Float -> Float
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (FunCodeS -> Vector Float -> Float
toScalarF FunCodeS
AbsSum)
normInf :: Vector Float -> RealOf Float
normInf = (Vector Float -> Float) -> Vector Float -> Float
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (Vector Float -> Float
forall (c :: * -> *) e. Container c e => c e -> e
maxElement (Vector Float -> Float)
-> (Vector Float -> Vector Float) -> Vector Float -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeV -> Vector Float -> Vector Float
vectorMapF FunCodeV
Abs)
multiply :: Matrix Float -> Matrix Float -> Matrix Float
multiply = (Matrix Float -> Matrix Float -> Matrix Float)
-> Matrix Float -> Matrix Float -> Matrix Float
forall (c :: * -> *) e t t.
(Container c e, Num e, IndexOf c ~ (Int, Int)) =>
(Matrix t -> Matrix t -> c e) -> Matrix t -> Matrix t -> c e
emptyMul Matrix Float -> Matrix Float -> Matrix Float
multiplyF
instance Product Double where
norm2 :: Vector R -> RealOf R
norm2 = (Vector R -> R) -> Vector R -> R
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (FunCodeS -> Vector R -> R
toScalarR FunCodeS
Norm2)
absSum :: Vector R -> RealOf R
absSum = (Vector R -> R) -> Vector R -> R
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (FunCodeS -> Vector R -> R
toScalarR FunCodeS
AbsSum)
norm1 :: Vector R -> RealOf R
norm1 = (Vector R -> R) -> Vector R -> R
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (FunCodeS -> Vector R -> R
toScalarR FunCodeS
AbsSum)
normInf :: Vector R -> RealOf R
normInf = (Vector R -> R) -> Vector R -> R
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (Vector R -> R
forall (c :: * -> *) e. Container c e => c e -> e
maxElement (Vector R -> R) -> (Vector R -> Vector R) -> Vector R -> R
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeV -> Vector R -> Vector R
vectorMapR FunCodeV
Abs)
multiply :: Matrix R -> Matrix R -> Matrix R
multiply = (Matrix R -> Matrix R -> Matrix R)
-> Matrix R -> Matrix R -> Matrix R
forall (c :: * -> *) e t t.
(Container c e, Num e, IndexOf c ~ (Int, Int)) =>
(Matrix t -> Matrix t -> c e) -> Matrix t -> Matrix t -> c e
emptyMul Matrix R -> Matrix R -> Matrix R
multiplyR
instance Product (Complex Float) where
norm2 :: Vector (Complex Float) -> RealOf (Complex Float)
norm2 = (Vector (Complex Float) -> Float)
-> Vector (Complex Float) -> Float
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (FunCodeS -> Vector (Complex Float) -> Float
toScalarQ FunCodeS
Norm2)
absSum :: Vector (Complex Float) -> RealOf (Complex Float)
absSum = (Vector (Complex Float) -> Float)
-> Vector (Complex Float) -> Float
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (FunCodeS -> Vector (Complex Float) -> Float
toScalarQ FunCodeS
AbsSum)
norm1 :: Vector (Complex Float) -> RealOf (Complex Float)
norm1 = (Vector (Complex Float) -> Float)
-> Vector (Complex Float) -> Float
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (Vector Float -> Float
forall (c :: * -> *) e. Container c e => c e -> e
sumElements (Vector Float -> Float)
-> (Vector (Complex Float) -> Vector Float)
-> Vector (Complex Float)
-> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector Float, Vector Float) -> Vector Float
forall a b. (a, b) -> a
fst ((Vector Float, Vector Float) -> Vector Float)
-> (Vector (Complex Float) -> (Vector Float, Vector Float))
-> Vector (Complex Float)
-> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (Complex Float) -> (Vector Float, Vector Float)
forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex (Vector (Complex Float) -> (Vector Float, Vector Float))
-> (Vector (Complex Float) -> Vector (Complex Float))
-> Vector (Complex Float)
-> (Vector Float, Vector Float)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeV -> Vector (Complex Float) -> Vector (Complex Float)
vectorMapQ FunCodeV
Abs)
normInf :: Vector (Complex Float) -> RealOf (Complex Float)
normInf = (Vector (Complex Float) -> Float)
-> Vector (Complex Float) -> Float
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (Vector Float -> Float
forall (c :: * -> *) e. Container c e => c e -> e
maxElement (Vector Float -> Float)
-> (Vector (Complex Float) -> Vector Float)
-> Vector (Complex Float)
-> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector Float, Vector Float) -> Vector Float
forall a b. (a, b) -> a
fst ((Vector Float, Vector Float) -> Vector Float)
-> (Vector (Complex Float) -> (Vector Float, Vector Float))
-> Vector (Complex Float)
-> Vector Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (Complex Float) -> (Vector Float, Vector Float)
forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex (Vector (Complex Float) -> (Vector Float, Vector Float))
-> (Vector (Complex Float) -> Vector (Complex Float))
-> Vector (Complex Float)
-> (Vector Float, Vector Float)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeV -> Vector (Complex Float) -> Vector (Complex Float)
vectorMapQ FunCodeV
Abs)
multiply :: Matrix (Complex Float)
-> Matrix (Complex Float) -> Matrix (Complex Float)
multiply = (Matrix (Complex Float)
-> Matrix (Complex Float) -> Matrix (Complex Float))
-> Matrix (Complex Float)
-> Matrix (Complex Float)
-> Matrix (Complex Float)
forall (c :: * -> *) e t t.
(Container c e, Num e, IndexOf c ~ (Int, Int)) =>
(Matrix t -> Matrix t -> c e) -> Matrix t -> Matrix t -> c e
emptyMul Matrix (Complex Float)
-> Matrix (Complex Float) -> Matrix (Complex Float)
multiplyQ
instance Product (Complex Double) where
norm2 :: Vector (Complex R) -> RealOf (Complex R)
norm2 = (Vector (Complex R) -> R) -> Vector (Complex R) -> R
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (FunCodeS -> Vector (Complex R) -> R
toScalarC FunCodeS
Norm2)
absSum :: Vector (Complex R) -> RealOf (Complex R)
absSum = (Vector (Complex R) -> R) -> Vector (Complex R) -> R
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (FunCodeS -> Vector (Complex R) -> R
toScalarC FunCodeS
AbsSum)
norm1 :: Vector (Complex R) -> RealOf (Complex R)
norm1 = (Vector (Complex R) -> R) -> Vector (Complex R) -> R
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (Vector R -> R
forall (c :: * -> *) e. Container c e => c e -> e
sumElements (Vector R -> R)
-> (Vector (Complex R) -> Vector R) -> Vector (Complex R) -> R
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector R, Vector R) -> Vector R
forall a b. (a, b) -> a
fst ((Vector R, Vector R) -> Vector R)
-> (Vector (Complex R) -> (Vector R, Vector R))
-> Vector (Complex R)
-> Vector R
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (Complex R) -> (Vector R, Vector R)
forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex (Vector (Complex R) -> (Vector R, Vector R))
-> (Vector (Complex R) -> Vector (Complex R))
-> Vector (Complex R)
-> (Vector R, Vector R)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeV -> Vector (Complex R) -> Vector (Complex R)
vectorMapC FunCodeV
Abs)
normInf :: Vector (Complex R) -> RealOf (Complex R)
normInf = (Vector (Complex R) -> R) -> Vector (Complex R) -> R
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (Vector R -> R
forall (c :: * -> *) e. Container c e => c e -> e
maxElement (Vector R -> R)
-> (Vector (Complex R) -> Vector R) -> Vector (Complex R) -> R
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector R, Vector R) -> Vector R
forall a b. (a, b) -> a
fst ((Vector R, Vector R) -> Vector R)
-> (Vector (Complex R) -> (Vector R, Vector R))
-> Vector (Complex R)
-> Vector R
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector (Complex R) -> (Vector R, Vector R)
forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex (Vector (Complex R) -> (Vector R, Vector R))
-> (Vector (Complex R) -> Vector (Complex R))
-> Vector (Complex R)
-> (Vector R, Vector R)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeV -> Vector (Complex R) -> Vector (Complex R)
vectorMapC FunCodeV
Abs)
multiply :: Matrix (Complex R) -> Matrix (Complex R) -> Matrix (Complex R)
multiply = (Matrix (Complex R) -> Matrix (Complex R) -> Matrix (Complex R))
-> Matrix (Complex R) -> Matrix (Complex R) -> Matrix (Complex R)
forall (c :: * -> *) e t t.
(Container c e, Num e, IndexOf c ~ (Int, Int)) =>
(Matrix t -> Matrix t -> c e) -> Matrix t -> Matrix t -> c e
emptyMul Matrix (Complex R) -> Matrix (Complex R) -> Matrix (Complex R)
multiplyC
instance Product I where
norm2 :: Vector I -> RealOf I
norm2 = Vector I -> RealOf I
forall a. HasCallStack => a
undefined
absSum :: Vector I -> RealOf I
absSum = (Vector I -> I) -> Vector I -> I
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (Vector I -> I
forall (c :: * -> *) e. Container c e => c e -> e
sumElements (Vector I -> I) -> (Vector I -> Vector I) -> Vector I -> I
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeV -> Vector I -> Vector I
vectorMapI FunCodeV
Abs)
norm1 :: Vector I -> RealOf I
norm1 = Vector I -> RealOf I
forall e. Product e => Vector e -> RealOf e
absSum
normInf :: Vector I -> RealOf I
normInf = (Vector I -> I) -> Vector I -> I
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (Vector I -> I
forall (c :: * -> *) e. Container c e => c e -> e
maxElement (Vector I -> I) -> (Vector I -> Vector I) -> Vector I -> I
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeV -> Vector I -> Vector I
vectorMapI FunCodeV
Abs)
multiply :: Matrix I -> Matrix I -> Matrix I
multiply = (Matrix I -> Matrix I -> Matrix I)
-> Matrix I -> Matrix I -> Matrix I
forall (c :: * -> *) e t t.
(Container c e, Num e, IndexOf c ~ (Int, Int)) =>
(Matrix t -> Matrix t -> c e) -> Matrix t -> Matrix t -> c e
emptyMul (I -> Matrix I -> Matrix I -> Matrix I
multiplyI I
1)
instance Product Z where
norm2 :: Vector Z -> RealOf Z
norm2 = Vector Z -> RealOf Z
forall a. HasCallStack => a
undefined
absSum :: Vector Z -> RealOf Z
absSum = (Vector Z -> Z) -> Vector Z -> Z
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (Vector Z -> Z
forall (c :: * -> *) e. Container c e => c e -> e
sumElements (Vector Z -> Z) -> (Vector Z -> Vector Z) -> Vector Z -> Z
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeV -> Vector Z -> Vector Z
vectorMapL FunCodeV
Abs)
norm1 :: Vector Z -> RealOf Z
norm1 = Vector Z -> RealOf Z
forall e. Product e => Vector e -> RealOf e
absSum
normInf :: Vector Z -> RealOf Z
normInf = (Vector Z -> Z) -> Vector Z -> Z
forall t p. (Storable t, Num p) => (Vector t -> p) -> Vector t -> p
emptyVal (Vector Z -> Z
forall (c :: * -> *) e. Container c e => c e -> e
maxElement (Vector Z -> Z) -> (Vector Z -> Vector Z) -> Vector Z -> Z
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeV -> Vector Z -> Vector Z
vectorMapL FunCodeV
Abs)
multiply :: Matrix Z -> Matrix Z -> Matrix Z
multiply = (Matrix Z -> Matrix Z -> Matrix Z)
-> Matrix Z -> Matrix Z -> Matrix Z
forall (c :: * -> *) e t t.
(Container c e, Num e, IndexOf c ~ (Int, Int)) =>
(Matrix t -> Matrix t -> c e) -> Matrix t -> Matrix t -> c e
emptyMul (Z -> Matrix Z -> Matrix Z -> Matrix Z
multiplyL Z
1)
emptyMul :: (Matrix t -> Matrix t -> c e) -> Matrix t -> Matrix t -> c e
emptyMul Matrix t -> Matrix t -> c e
m Matrix t
a Matrix t
b
| Int
x1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& Int
x2 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
|| Int
r Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
|| Int
c Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = e -> IndexOf c -> c e
forall (c :: * -> *) e. Container c e => e -> IndexOf c -> c e
konst' e
0 (Int
r,Int
c)
| Bool
otherwise = Matrix t -> Matrix t -> c e
m Matrix t
a Matrix t
b
where
r :: Int
r = Matrix t -> Int
forall t. Matrix t -> Int
rows Matrix t
a
x1 :: Int
x1 = Matrix t -> Int
forall t. Matrix t -> Int
cols Matrix t
a
x2 :: Int
x2 = Matrix t -> Int
forall t. Matrix t -> Int
rows Matrix t
b
c :: Int
c = Matrix t -> Int
forall t. Matrix t -> Int
cols Matrix t
b
emptyVal :: (Vector t -> p) -> Vector t -> p
emptyVal Vector t -> p
f Vector t
v =
if Vector t -> Int
forall t. Storable t => Vector t -> Int
dim Vector t
v Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
then Vector t -> p
f Vector t
v
else p
0
udot :: Product e => Vector e -> Vector e -> e
udot :: Vector e -> Vector e -> e
udot Vector e
u Vector e
v
| Vector e -> Int
forall t. Storable t => Vector t -> Int
dim Vector e
u Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Vector e -> Int
forall t. Storable t => Vector t -> Int
dim Vector e
v = Matrix e -> e
val (Vector e -> Matrix e
forall a. Storable a => Vector a -> Matrix a
asRow Vector e
u Matrix e -> Matrix e -> Matrix e
forall e. Product e => Matrix e -> Matrix e -> Matrix e
`multiply` Vector e -> Matrix e
forall a. Storable a => Vector a -> Matrix a
asColumn Vector e
v)
| Bool
otherwise = [Char] -> e
forall a. HasCallStack => [Char] -> a
error ([Char] -> e) -> [Char] -> e
forall a b. (a -> b) -> a -> b
$ [Char]
"different dimensions "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++Int -> [Char]
forall a. Show a => a -> [Char]
show (Vector e -> Int
forall t. Storable t => Vector t -> Int
dim Vector e
u)[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
" and "[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++Int -> [Char]
forall a. Show a => a -> [Char]
show (Vector e -> Int
forall t. Storable t => Vector t -> Int
dim Vector e
v)[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++[Char]
" in dot product"
where
val :: Matrix e -> e
val Matrix e
m | Vector e -> Int
forall t. Storable t => Vector t -> Int
dim Vector e
u Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 = Matrix e
mMatrix e -> (Int, Int) -> e
forall t. Storable t => Matrix t -> (Int, Int) -> t
@@>(Int
0,Int
0)
| Bool
otherwise = e
0
mXm :: Product t => Matrix t -> Matrix t -> Matrix t
mXm :: Matrix t -> Matrix t -> Matrix t
mXm = Matrix t -> Matrix t -> Matrix t
forall e. Product e => Matrix e -> Matrix e -> Matrix e
multiply
mXv :: Product t => Matrix t -> Vector t -> Vector t
mXv :: Matrix t -> Vector t -> Vector t
mXv Matrix t
m Vector t
v = Matrix t -> Vector t
forall t. Element t => Matrix t -> Vector t
flatten (Matrix t -> Vector t) -> Matrix t -> Vector t
forall a b. (a -> b) -> a -> b
$ Matrix t
m Matrix t -> Matrix t -> Matrix t
forall e. Product e => Matrix e -> Matrix e -> Matrix e
`mXm` (Vector t -> Matrix t
forall a. Storable a => Vector a -> Matrix a
asColumn Vector t
v)
vXm :: Product t => Vector t -> Matrix t -> Vector t
vXm :: Vector t -> Matrix t -> Vector t
vXm Vector t
v Matrix t
m = Matrix t -> Vector t
forall t. Element t => Matrix t -> Vector t
flatten (Matrix t -> Vector t) -> Matrix t -> Vector t
forall a b. (a -> b) -> a -> b
$ (Vector t -> Matrix t
forall a. Storable a => Vector a -> Matrix a
asRow Vector t
v) Matrix t -> Matrix t -> Matrix t
forall e. Product e => Matrix e -> Matrix e -> Matrix e
`mXm` Matrix t
m
outer :: (Product t) => Vector t -> Vector t -> Matrix t
outer :: Vector t -> Vector t -> Matrix t
outer Vector t
u Vector t
v = Vector t -> Matrix t
forall a. Storable a => Vector a -> Matrix a
asColumn Vector t
u Matrix t -> Matrix t -> Matrix t
forall e. Product e => Matrix e -> Matrix e -> Matrix e
`multiply` Vector t -> Matrix t
forall a. Storable a => Vector a -> Matrix a
asRow Vector t
v
kronecker :: (Product t) => Matrix t -> Matrix t -> Matrix t
kronecker :: Matrix t -> Matrix t -> Matrix t
kronecker Matrix t
a Matrix t
b = [[Matrix t]] -> Matrix t
forall t. Element t => [[Matrix t]] -> Matrix t
fromBlocks
([[Matrix t]] -> Matrix t)
-> (Matrix t -> [[Matrix t]]) -> Matrix t -> Matrix t
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Matrix t] -> [[Matrix t]]
forall e. Int -> [e] -> [[e]]
chunksOf (Matrix t -> Int
forall t. Matrix t -> Int
cols Matrix t
a)
([Matrix t] -> [[Matrix t]])
-> (Matrix t -> [Matrix t]) -> Matrix t -> [[Matrix t]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Vector t -> Matrix t) -> [Vector t] -> [Matrix t]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Vector t -> Matrix t
forall t. Storable t => Int -> Vector t -> Matrix t
reshape (Matrix t -> Int
forall t. Matrix t -> Int
cols Matrix t
b))
([Vector t] -> [Matrix t])
-> (Matrix t -> [Vector t]) -> Matrix t -> [Matrix t]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix t -> [Vector t]
forall t. Element t => Matrix t -> [Vector t]
toRows
(Matrix t -> Matrix t) -> Matrix t -> Matrix t
forall a b. (a -> b) -> a -> b
$ Matrix t -> Vector t
forall t. Element t => Matrix t -> Vector t
flatten Matrix t
a Vector t -> Vector t -> Matrix t
forall t. Product t => Vector t -> Vector t -> Matrix t
`outer` Matrix t -> Vector t
forall t. Element t => Matrix t -> Vector t
flatten Matrix t
b
class Convert t where
real :: Complexable c => c (RealOf t) -> c t
complex :: Complexable c => c t -> c (ComplexOf t)
single :: Complexable c => c t -> c (SingleOf t)
double :: Complexable c => c t -> c (DoubleOf t)
toComplex :: (Complexable c, RealElement t) => (c t, c t) -> c (Complex t)
fromComplex :: (Complexable c, RealElement t) => c (Complex t) -> (c t, c t)
instance Convert Double where
real :: c (RealOf R) -> c R
real = c (RealOf R) -> c R
forall a. a -> a
id
complex :: c R -> c (ComplexOf R)
complex = c R -> c (ComplexOf R)
forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c e -> c (Complex e)
comp'
single :: c R -> c (SingleOf R)
single = c R -> c (SingleOf R)
forall (c :: * -> *) a b.
(Complexable c, Precision a b) =>
c b -> c a
single'
double :: c R -> c (DoubleOf R)
double = c R -> c (DoubleOf R)
forall a. a -> a
id
toComplex :: (c R, c R) -> c (Complex R)
toComplex = (c R, c R) -> c (Complex R)
forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
(c e, c e) -> c (Complex e)
toComplex'
fromComplex :: c (Complex R) -> (c R, c R)
fromComplex = c (Complex R) -> (c R, c R)
forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c (Complex e) -> (c e, c e)
fromComplex'
instance Convert Float where
real :: c (RealOf Float) -> c Float
real = c (RealOf Float) -> c Float
forall a. a -> a
id
complex :: c Float -> c (ComplexOf Float)
complex = c Float -> c (ComplexOf Float)
forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c e -> c (Complex e)
comp'
single :: c Float -> c (SingleOf Float)
single = c Float -> c (SingleOf Float)
forall a. a -> a
id
double :: c Float -> c (DoubleOf Float)
double = c Float -> c (DoubleOf Float)
forall (c :: * -> *) a b.
(Complexable c, Precision a b) =>
c a -> c b
double'
toComplex :: (c Float, c Float) -> c (Complex Float)
toComplex = (c Float, c Float) -> c (Complex Float)
forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
(c e, c e) -> c (Complex e)
toComplex'
fromComplex :: c (Complex Float) -> (c Float, c Float)
fromComplex = c (Complex Float) -> (c Float, c Float)
forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c (Complex e) -> (c e, c e)
fromComplex'
instance Convert (Complex Double) where
real :: c (RealOf (Complex R)) -> c (Complex R)
real = c (RealOf (Complex R)) -> c (Complex R)
forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c e -> c (Complex e)
comp'
complex :: c (Complex R) -> c (ComplexOf (Complex R))
complex = c (Complex R) -> c (ComplexOf (Complex R))
forall a. a -> a
id
single :: c (Complex R) -> c (SingleOf (Complex R))
single = c (Complex R) -> c (SingleOf (Complex R))
forall (c :: * -> *) a b.
(Complexable c, Precision a b) =>
c b -> c a
single'
double :: c (Complex R) -> c (DoubleOf (Complex R))
double = c (Complex R) -> c (DoubleOf (Complex R))
forall a. a -> a
id
toComplex :: (c (Complex R), c (Complex R)) -> c (Complex (Complex R))
toComplex = (c (Complex R), c (Complex R)) -> c (Complex (Complex R))
forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
(c e, c e) -> c (Complex e)
toComplex'
fromComplex :: c (Complex (Complex R)) -> (c (Complex R), c (Complex R))
fromComplex = c (Complex (Complex R)) -> (c (Complex R), c (Complex R))
forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c (Complex e) -> (c e, c e)
fromComplex'
instance Convert (Complex Float) where
real :: c (RealOf (Complex Float)) -> c (Complex Float)
real = c (RealOf (Complex Float)) -> c (Complex Float)
forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c e -> c (Complex e)
comp'
complex :: c (Complex Float) -> c (ComplexOf (Complex Float))
complex = c (Complex Float) -> c (ComplexOf (Complex Float))
forall a. a -> a
id
single :: c (Complex Float) -> c (SingleOf (Complex Float))
single = c (Complex Float) -> c (SingleOf (Complex Float))
forall a. a -> a
id
double :: c (Complex Float) -> c (DoubleOf (Complex Float))
double = c (Complex Float) -> c (DoubleOf (Complex Float))
forall (c :: * -> *) a b.
(Complexable c, Precision a b) =>
c a -> c b
double'
toComplex :: (c (Complex Float), c (Complex Float))
-> c (Complex (Complex Float))
toComplex = (c (Complex Float), c (Complex Float))
-> c (Complex (Complex Float))
forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
(c e, c e) -> c (Complex e)
toComplex'
fromComplex :: c (Complex (Complex Float))
-> (c (Complex Float), c (Complex Float))
fromComplex = c (Complex (Complex Float))
-> (c (Complex Float), c (Complex Float))
forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c (Complex e) -> (c e, c e)
fromComplex'
type family RealOf x
type instance RealOf Double = Double
type instance RealOf (Complex Double) = Double
type instance RealOf Float = Float
type instance RealOf (Complex Float) = Float
type instance RealOf I = I
type instance RealOf Z = Z
type ComplexOf x = Complex (RealOf x)
type family SingleOf x
type instance SingleOf Double = Float
type instance SingleOf Float = Float
type instance SingleOf (Complex a) = Complex (SingleOf a)
type family DoubleOf x
type instance DoubleOf Double = Double
type instance DoubleOf Float = Double
type instance DoubleOf (Complex a) = Complex (DoubleOf a)
type family ElementOf c
type instance ElementOf (Vector a) = a
type instance ElementOf (Matrix a) = a
buildM :: (a, a) -> (t -> t -> t) -> Matrix t
buildM (a
rc,a
cc) t -> t -> t
f = [[t]] -> Matrix t
forall t. Element t => [[t]] -> Matrix t
fromLists [ [t -> t -> t
f t
r t
c | t
c <- [t]
cs] | t
r <- [t]
rs ]
where rs :: [t]
rs = (a -> t) -> [a] -> [t]
forall a b. (a -> b) -> [a] -> [b]
map a -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral [a
0 .. (a
rca -> a -> a
forall a. Num a => a -> a -> a
-a
1)]
cs :: [t]
cs = (a -> t) -> [a] -> [t]
forall a b. (a -> b) -> [a] -> [b]
map a -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral [a
0 .. (a
cca -> a -> a
forall a. Num a => a -> a -> a
-a
1)]
buildV :: a -> (t -> a) -> Vector a
buildV a
n t -> a
f = [a] -> Vector a
forall a. Storable a => [a] -> Vector a
fromList [t -> a
f t
k | t
k <- [t]
ks]
where ks :: [t]
ks = (a -> t) -> [a] -> [t]
forall a b. (a -> b) -> [a] -> [b]
map a -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral [a
0 .. (a
na -> a -> a
forall a. Num a => a -> a -> a
-a
1)]
diag :: (Num a, Element a) => Vector a -> Matrix a
diag :: Vector a -> Matrix a
diag Vector a
v = a -> Vector a -> Int -> Int -> Matrix a
forall t. Storable t => t -> Vector t -> Int -> Int -> Matrix t
diagRect a
0 Vector a
v Int
n Int
n where n :: Int
n = Vector a -> Int
forall t. Storable t => Vector t -> Int
dim Vector a
v
ident :: (Num a, Element a) => Int -> Matrix a
ident :: Int -> Matrix a
ident Int
n = Vector a -> Matrix a
forall a. (Num a, Element a) => Vector a -> Matrix a
diag (a -> Int -> Vector a
forall a. Element a => a -> Int -> Vector a
constantD a
1 Int
n)
findV :: (t -> Bool) -> Vector t -> [Int]
findV t -> Bool
p Vector t
x = (Int -> t -> [Int] -> [Int]) -> [Int] -> Vector t -> [Int]
forall a b.
Storable a =>
(Int -> a -> b -> b) -> b -> Vector a -> b
foldVectorWithIndex Int -> t -> [Int] -> [Int]
g [] Vector t
x where
g :: Int -> t -> [Int] -> [Int]
g Int
k t
z [Int]
l = if t -> Bool
p t
z then Int
kInt -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
l else [Int]
l
findM :: (t -> Bool) -> Matrix t -> [(Int, Int)]
findM t -> Bool
p Matrix t
x = (Int -> (Int, Int)) -> [Int] -> [(Int, Int)]
forall a b. (a -> b) -> [a] -> [b]
map ((Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
`divMod` Matrix t -> Int
forall t. Matrix t -> Int
cols Matrix t
x)) ([Int] -> [(Int, Int)]) -> [Int] -> [(Int, Int)]
forall a b. (a -> b) -> a -> b
$ (t -> Bool) -> Vector t -> [Int]
forall t. Storable t => (t -> Bool) -> Vector t -> [Int]
findV t -> Bool
p (Matrix t -> Vector t
forall t. Element t => Matrix t -> Vector t
flatten Matrix t
x)
assocV :: Int -> t -> t (Int, t) -> Vector t
assocV Int
n t
z t (Int, t)
xs = (forall s. ST s (STVector s t)) -> Vector t
forall t. Storable t => (forall s. ST s (STVector s t)) -> Vector t
ST.runSTVector ((forall s. ST s (STVector s t)) -> Vector t)
-> (forall s. ST s (STVector s t)) -> Vector t
forall a b. (a -> b) -> a -> b
$ do
STVector s t
v <- t -> Int -> ST s (STVector s t)
forall t s. Storable t => t -> Int -> ST s (STVector s t)
ST.newVector t
z Int
n
((Int, t) -> ST s ()) -> t (Int, t) -> ST s ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Int
k,t
x) -> STVector s t -> Int -> t -> ST s ()
forall t s. Storable t => STVector s t -> Int -> t -> ST s ()
ST.writeVector STVector s t
v Int
k t
x) t (Int, t)
xs
STVector s t -> ST s (STVector s t)
forall (m :: * -> *) a. Monad m => a -> m a
return STVector s t
v
assocM :: (Int, Int) -> t -> t ((Int, Int), t) -> Matrix t
assocM (Int
r,Int
c) t
z t ((Int, Int), t)
xs = (forall s. ST s (STMatrix s t)) -> Matrix t
forall t. Storable t => (forall s. ST s (STMatrix s t)) -> Matrix t
ST.runSTMatrix ((forall s. ST s (STMatrix s t)) -> Matrix t)
-> (forall s. ST s (STMatrix s t)) -> Matrix t
forall a b. (a -> b) -> a -> b
$ do
STMatrix s t
m <- t -> Int -> Int -> ST s (STMatrix s t)
forall t s. Storable t => t -> Int -> Int -> ST s (STMatrix s t)
ST.newMatrix t
z Int
r Int
c
(((Int, Int), t) -> ST s ()) -> t ((Int, Int), t) -> ST s ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\((Int
i,Int
j),t
x) -> STMatrix s t -> Int -> Int -> t -> ST s ()
forall t s.
Storable t =>
STMatrix s t -> Int -> Int -> t -> ST s ()
ST.writeMatrix STMatrix s t
m Int
i Int
j t
x) t ((Int, Int), t)
xs
STMatrix s t -> ST s (STMatrix s t)
forall (m :: * -> *) a. Monad m => a -> m a
return STMatrix s t
m
accumV :: Vector t -> (t -> t -> t) -> t (Int, t) -> Vector t
accumV Vector t
v0 t -> t -> t
f t (Int, t)
xs = (forall s. ST s (STVector s t)) -> Vector t
forall t. Storable t => (forall s. ST s (STVector s t)) -> Vector t
ST.runSTVector ((forall s. ST s (STVector s t)) -> Vector t)
-> (forall s. ST s (STVector s t)) -> Vector t
forall a b. (a -> b) -> a -> b
$ do
STVector s t
v <- Vector t -> ST s (STVector s t)
forall t s. Storable t => Vector t -> ST s (STVector s t)
ST.thawVector Vector t
v0
((Int, t) -> ST s ()) -> t (Int, t) -> ST s ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Int
k,t
x) -> STVector s t -> Int -> (t -> t) -> ST s ()
forall t s.
Storable t =>
STVector s t -> Int -> (t -> t) -> ST s ()
ST.modifyVector STVector s t
v Int
k (t -> t -> t
f t
x)) t (Int, t)
xs
STVector s t -> ST s (STVector s t)
forall (m :: * -> *) a. Monad m => a -> m a
return STVector s t
v
accumM :: Matrix t -> (t -> t -> t) -> t ((Int, Int), t) -> Matrix t
accumM Matrix t
m0 t -> t -> t
f t ((Int, Int), t)
xs = (forall s. ST s (STMatrix s t)) -> Matrix t
forall t. Storable t => (forall s. ST s (STMatrix s t)) -> Matrix t
ST.runSTMatrix ((forall s. ST s (STMatrix s t)) -> Matrix t)
-> (forall s. ST s (STMatrix s t)) -> Matrix t
forall a b. (a -> b) -> a -> b
$ do
STMatrix s t
m <- Matrix t -> ST s (STMatrix s t)
forall t s. Element t => Matrix t -> ST s (STMatrix s t)
ST.thawMatrix Matrix t
m0
(((Int, Int), t) -> ST s ()) -> t ((Int, Int), t) -> ST s ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\((Int
i,Int
j),t
x) -> STMatrix s t -> Int -> Int -> (t -> t) -> ST s ()
forall t s.
Storable t =>
STMatrix s t -> Int -> Int -> (t -> t) -> ST s ()
ST.modifyMatrix STMatrix s t
m Int
i Int
j (t -> t -> t
f t
x)) t ((Int, Int), t)
xs
STMatrix s t -> ST s (STMatrix s t)
forall (m :: * -> *) a. Monad m => a -> m a
return STMatrix s t
m
compareM :: Matrix e -> Matrix e -> Matrix I
compareM Matrix e
a Matrix e
b = MatrixOrder -> Int -> Int -> Vector I -> Matrix I
forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
RowMajor (Matrix e -> Int
forall t. Matrix t -> Int
rows Matrix e
a'') (Matrix e -> Int
forall t. Matrix t -> Int
cols Matrix e
a'') (Vector I -> Matrix I) -> Vector I -> Matrix I
forall a b. (a -> b) -> a -> b
$ Vector e -> Vector e -> Vector I
forall (c :: * -> *) e. (Container c e, Ord e) => c e -> c e -> c I
ccompare' Vector e
a' Vector e
b'
where
args :: [Matrix e]
args@(Matrix e
a'':[Matrix e]
_) = [Matrix e] -> [Matrix e]
forall t. Element t => [Matrix t] -> [Matrix t]
conformMs [Matrix e
a,Matrix e
b]
[Vector e
a', Vector e
b'] = (Matrix e -> Vector e) -> [Matrix e] -> [Vector e]
forall a b. (a -> b) -> [a] -> [b]
map Matrix e -> Vector e
forall t. Element t => Matrix t -> Vector t
flatten [Matrix e]
args
compareCV :: (Vector t -> Vector t -> t) -> Vector t -> Vector t -> t
compareCV Vector t -> Vector t -> t
f Vector t
a Vector t
b = Vector t -> Vector t -> t
f Vector t
a' Vector t
b'
where
[Vector t
a', Vector t
b'] = [Vector t] -> [Vector t]
forall t. Element t => [Vector t] -> [Vector t]
conformVs [Vector t
a,Vector t
b]
selectM :: Matrix I -> Matrix t -> Matrix t -> Matrix t -> Matrix t
selectM Matrix I
c Matrix t
l Matrix t
e Matrix t
t = MatrixOrder -> Int -> Int -> Vector t -> Matrix t
forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
RowMajor (Matrix t -> Int
forall t. Matrix t -> Int
rows Matrix t
a'') (Matrix t -> Int
forall t. Matrix t -> Int
cols Matrix t
a'') (Vector t -> Matrix t) -> Vector t -> Matrix t
forall a b. (a -> b) -> a -> b
$ Vector I -> Vector t -> Vector t -> Vector t -> Vector t
forall (c :: * -> *) e.
Container c e =>
c I -> c e -> c e -> c e -> c e
cselect' (Vector t -> Vector I
forall (c :: * -> *) e. Container c e => c e -> c I
toInt Vector t
c') Vector t
l' Vector t
e' Vector t
t'
where
args :: [Matrix t]
args@(Matrix t
a'':[Matrix t]
_) = [Matrix t] -> [Matrix t]
forall t. Element t => [Matrix t] -> [Matrix t]
conformMs [Matrix I -> Matrix t
forall (c :: * -> *) e. Container c e => c I -> c e
fromInt Matrix I
c,Matrix t
l,Matrix t
e,Matrix t
t]
[Vector t
c', Vector t
l', Vector t
e', Vector t
t'] = (Matrix t -> Vector t) -> [Matrix t] -> [Vector t]
forall a b. (a -> b) -> [a] -> [b]
map Matrix t -> Vector t
forall t. Element t => Matrix t -> Vector t
flatten [Matrix t]
args
selectCV :: (Vector I -> Vector e -> Vector e -> Vector e -> t)
-> Vector I -> Vector e -> Vector e -> Vector e -> t
selectCV Vector I -> Vector e -> Vector e -> Vector e -> t
f Vector I
c Vector e
l Vector e
e Vector e
t = Vector I -> Vector e -> Vector e -> Vector e -> t
f (Vector e -> Vector I
forall (c :: * -> *) e. Container c e => c e -> c I
toInt Vector e
c') Vector e
l' Vector e
e' Vector e
t'
where
[Vector e
c', Vector e
l', Vector e
e', Vector e
t'] = [Vector e] -> [Vector e]
forall t. Element t => [Vector t] -> [Vector t]
conformVs [Vector I -> Vector e
forall (c :: * -> *) e. Container c e => c I -> c e
fromInt Vector I
c,Vector e
l,Vector e
e,Vector e
t]
class CTrans t
where
ctrans :: Matrix t -> Matrix t
ctrans = Matrix t -> Matrix t
forall t. Matrix t -> Matrix t
trans
instance CTrans Float
instance CTrans R
instance CTrans I
instance CTrans Z
instance CTrans C
where
ctrans :: Matrix (Complex R) -> Matrix (Complex R)
ctrans = Matrix (Complex R) -> Matrix (Complex R)
forall (c :: * -> *) e. Container c e => c e -> c e
conj (Matrix (Complex R) -> Matrix (Complex R))
-> (Matrix (Complex R) -> Matrix (Complex R))
-> Matrix (Complex R)
-> Matrix (Complex R)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix (Complex R) -> Matrix (Complex R)
forall t. Matrix t -> Matrix t
trans
instance CTrans (Complex Float)
where
ctrans :: Matrix (Complex Float) -> Matrix (Complex Float)
ctrans = Matrix (Complex Float) -> Matrix (Complex Float)
forall (c :: * -> *) e. Container c e => c e -> c e
conj (Matrix (Complex Float) -> Matrix (Complex Float))
-> (Matrix (Complex Float) -> Matrix (Complex Float))
-> Matrix (Complex Float)
-> Matrix (Complex Float)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Matrix (Complex Float) -> Matrix (Complex Float)
forall t. Matrix t -> Matrix t
trans
class Transposable m mt | m -> mt, mt -> m
where
tr :: m -> mt
tr' :: m -> mt
instance (CTrans t, Container Vector t) => Transposable (Matrix t) (Matrix t)
where
tr :: Matrix t -> Matrix t
tr = Matrix t -> Matrix t
forall t. CTrans t => Matrix t -> Matrix t
ctrans
tr' :: Matrix t -> Matrix t
tr' = Matrix t -> Matrix t
forall t. Matrix t -> Matrix t
trans
class Additive c
where
add :: c -> c -> c
class Linear t c
where
scale :: t -> c t -> c t
instance Container Vector t => Linear t Vector
where
scale :: t -> Vector t -> Vector t
scale = t -> Vector t -> Vector t
forall (c :: * -> *) e. Container c e => e -> c e -> c e
scale'
instance Container Matrix t => Linear t Matrix
where
scale :: t -> Matrix t -> Matrix t
scale = t -> Matrix t -> Matrix t
forall (c :: * -> *) e. Container c e => e -> c e -> c e
scale'
instance Container Vector t => Additive (Vector t)
where
add :: Vector t -> Vector t -> Vector t
add = Vector t -> Vector t -> Vector t
forall (c :: * -> *) e. Container c e => c e -> c e -> c e
add'
instance Container Matrix t => Additive (Matrix t)
where
add :: Matrix t -> Matrix t -> Matrix t
add = Matrix t -> Matrix t -> Matrix t
forall (c :: * -> *) e. Container c e => c e -> c e -> c e
add'
class Testable t
where
checkT :: t -> (Bool, IO())
ioCheckT :: t -> IO (Bool, IO())
ioCheckT = (Bool, IO ()) -> IO (Bool, IO ())
forall (m :: * -> *) a. Monad m => a -> m a
return ((Bool, IO ()) -> IO (Bool, IO ()))
-> (t -> (Bool, IO ())) -> t -> IO (Bool, IO ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> (Bool, IO ())
forall t. Testable t => t -> (Bool, IO ())
checkT