{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -fno-warn-missing-signatures #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Data.Packed.Internal.Numeric
-- Copyright   :  (c) Alberto Ruiz 2010-14
-- License     :  BSD3
-- Maintainer  :  Alberto Ruiz
-- Stability   :  provisional
--
-----------------------------------------------------------------------------

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

--------------------------------------------------------------------------------

-- | Basic element-by-element functions for numeric containers
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
    -- | element by element multiplication
    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       -- ^ size
          -> e                -- ^ default value
          -> [(IndexOf c, e)] -- ^ association list
          -> c e              -- ^ result
    accum' :: c e             -- ^ initial structure
          -> (e -> e -> e)    -- ^ update function
          -> [(IndexOf c, e)] -- ^ association list
          -> c e              -- ^ result

    -- | scale the element by element reciprocal of the object:
    --
    -- @scaleRecip 2 (fromList [5,i]) == 2 |> [0.4 :+ 0.0,0.0 :+ (-2.0)]@
    scaleRecip  :: Fractional e => e -> c e -> c e
    -- | element by element division
    divide      :: Fractional e => c e -> c e -> c e
    --
    -- element by element inverse tangent
    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' = forall a. a -> a
id
    size' :: Vector I -> IndexOf Vector
size' = 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 = forall a. Eq a => a -> a -> Bool
(==)
    scalar' :: I -> Vector I
scalar' = forall a. Storable a => a -> Vector a
V.singleton
    konst' :: I -> IndexOf Vector -> Vector I
konst' = forall a. Element a => a -> Int -> Vector a
constantD
    build' :: IndexOf Vector -> ArgOf Vector I -> Vector I
build' = forall {a} {t} {a}.
(Integral a, Num t, Storable a) =>
a -> (t -> a) -> Vector a
buildV
    cmap' :: forall b. Element b => (I -> b) -> Vector I -> Vector b
cmap' = forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
mapVector
    atIndex' :: Vector I -> IndexOf Vector -> I
atIndex' = forall t. Storable t => Vector t -> Int -> t
(@>)
    minIndex' :: Vector I -> IndexOf Vector
minIndex'     = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"minIndex"   (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector I -> I
toScalarI FunCodeS
MinIdx)
    maxIndex' :: Vector I -> IndexOf Vector
maxIndex'     = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"maxIndex"   (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector I -> I
toScalarI FunCodeS
MaxIdx)
    minElement' :: Vector I -> I
minElement'   = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"minElement" (FunCodeS -> Vector I -> I
toScalarI FunCodeS
Min)
    maxElement' :: Vector I -> I
maxElement'   = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"maxElement" (FunCodeS -> Vector I -> I
toScalarI FunCodeS
Max)
    sumElements' :: Vector I -> I
sumElements'  = forall c a.
(TransRaw c (I -> Ptr a -> IO I)
 ~ (I -> Ptr I -> I -> Ptr 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' :: Ord I => Vector I -> Vector I
step' = Vector I -> Vector I
stepI
    find' :: (I -> Bool) -> Vector I -> [IndexOf Vector]
find' = forall {a}. Storable a => (a -> Bool) -> Vector a -> [Int]
findV
    assoc' :: IndexOf Vector -> I -> [(IndexOf Vector, I)] -> Vector I
assoc' = 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' = forall {t} {t :: * -> *} {t}.
(Storable t, Foldable t) =>
Vector t -> (t -> t -> t) -> t (Int, t) -> Vector t
accumV
    ccompare' :: Ord I => Vector I -> Vector I -> Vector I
ccompare' = forall {t} {t}.
Element t =>
(Vector t -> Vector t -> t) -> Vector t -> Vector t -> t
compareCV 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' = 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 forall a.
Element a =>
Vector I -> Vector a -> Vector a -> Vector a -> Vector a
selectV
    scaleRecip :: Fractional I => I -> Vector I -> Vector I
scaleRecip = forall a. HasCallStack => a
undefined -- cannot match
    divide :: Fractional I => Vector I -> Vector I -> Vector I
divide = forall a. HasCallStack => a
undefined
    arctan2' :: Fractional I => Vector I -> Vector I -> Vector I
arctan2' = forall a. HasCallStack => a
undefined
    cmod' :: Integral I => I -> Vector I -> Vector I
cmod' I
m Vector I
x
        | I
m 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 = forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"cmod 0 on vector of size "forall a. [a] -> [a] -> [a]
++(forall a. Show a => a -> [Char]
show forall a b. (a -> b) -> a -> b
$ forall t. Storable t => Vector t -> Int
dim Vector I
x)
    fromInt' :: Vector I -> Vector I
fromInt' = forall a. a -> a
id
    toInt' :: Vector I -> Vector I
toInt'   = 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' = forall a. a -> a
id
    size' :: Vector Z -> IndexOf Vector
size' = 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 = forall a. Eq a => a -> a -> Bool
(==)
    scalar' :: Z -> Vector Z
scalar' = forall a. Storable a => a -> Vector a
V.singleton
    konst' :: Z -> IndexOf Vector -> Vector Z
konst' = forall a. Element a => a -> Int -> Vector a
constantD
    build' :: IndexOf Vector -> ArgOf Vector Z -> Vector Z
build' = forall {a} {t} {a}.
(Integral a, Num t, Storable a) =>
a -> (t -> a) -> Vector a
buildV
    cmap' :: forall b. Element b => (Z -> b) -> Vector Z -> Vector b
cmap' = forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
mapVector
    atIndex' :: Vector Z -> IndexOf Vector -> Z
atIndex' = forall t. Storable t => Vector t -> Int -> t
(@>)
    minIndex' :: Vector Z -> IndexOf Vector
minIndex'     = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"minIndex"   (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector Z -> Z
toScalarL FunCodeS
MinIdx)
    maxIndex' :: Vector Z -> IndexOf Vector
maxIndex'     = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"maxIndex"   (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector Z -> Z
toScalarL FunCodeS
MaxIdx)
    minElement' :: Vector Z -> Z
minElement'   = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"minElement" (FunCodeS -> Vector Z -> Z
toScalarL FunCodeS
Min)
    maxElement' :: Vector Z -> Z
maxElement'   = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"maxElement" (FunCodeS -> Vector Z -> Z
toScalarL FunCodeS
Max)
    sumElements' :: Vector Z -> Z
sumElements'  = forall c a.
(TransRaw c (I -> Ptr a -> IO I)
 ~ (I -> Ptr Z -> I -> Ptr 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' :: Ord Z => Vector Z -> Vector Z
step' = Vector Z -> Vector Z
stepL
    find' :: (Z -> Bool) -> Vector Z -> [IndexOf Vector]
find' = forall {a}. Storable a => (a -> Bool) -> Vector a -> [Int]
findV
    assoc' :: IndexOf Vector -> Z -> [(IndexOf Vector, Z)] -> Vector Z
assoc' = 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' = forall {t} {t :: * -> *} {t}.
(Storable t, Foldable t) =>
Vector t -> (t -> t -> t) -> t (Int, t) -> Vector t
accumV
    ccompare' :: Ord Z => Vector Z -> Vector Z -> Vector I
ccompare' = forall {t} {t}.
Element t =>
(Vector t -> Vector t -> t) -> Vector t -> Vector t -> t
compareCV 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' = 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 forall a.
Element a =>
Vector I -> Vector a -> Vector a -> Vector a -> Vector a
selectV
    scaleRecip :: Fractional Z => Z -> Vector Z -> Vector Z
scaleRecip = forall a. HasCallStack => a
undefined -- cannot match
    divide :: Fractional Z => Vector Z -> Vector Z -> Vector Z
divide = forall a. HasCallStack => a
undefined
    arctan2' :: Fractional Z => Vector Z -> Vector Z -> Vector Z
arctan2' = forall a. HasCallStack => a
undefined
    cmod' :: Integral Z => Z -> Vector Z -> Vector Z
cmod' Z
m Vector Z
x
        | Z
m 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 = forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"cmod 0 on vector of size "forall a. [a] -> [a] -> [a]
++(forall a. Show a => a -> [Char]
show forall a b. (a -> b) -> a -> b
$ 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'   = forall a. a -> a
id
    toZ' :: Vector Z -> Vector Z
toZ'     = forall a. a -> a
id



instance Container Vector Float
  where
    conj' :: Vector Float -> Vector Float
conj' = forall a. a -> a
id
    size' :: Vector Float -> IndexOf Vector
size' = 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 = forall a. Eq a => a -> a -> Bool
(==)
    scalar' :: Float -> Vector Float
scalar' = forall a. Storable a => a -> Vector a
V.singleton
    konst' :: Float -> IndexOf Vector -> Vector Float
konst' = forall a. Element a => a -> Int -> Vector a
constantD
    build' :: IndexOf Vector -> ArgOf Vector Float -> Vector Float
build' = forall {a} {t} {a}.
(Integral a, Num t, Storable a) =>
a -> (t -> a) -> Vector a
buildV
    cmap' :: forall b. Element b => (Float -> b) -> Vector Float -> Vector b
cmap' = forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
mapVector
    atIndex' :: Vector Float -> IndexOf Vector -> Float
atIndex' = forall t. Storable t => Vector t -> Int -> t
(@>)
    minIndex' :: Vector Float -> IndexOf Vector
minIndex'     = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"minIndex"   (forall a b. (RealFrac a, Integral b) => a -> b
round forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector Float -> Float
toScalarF FunCodeS
MinIdx)
    maxIndex' :: Vector Float -> IndexOf Vector
maxIndex'     = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"maxIndex"   (forall a b. (RealFrac a, Integral b) => a -> b
round forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector Float -> Float
toScalarF FunCodeS
MaxIdx)
    minElement' :: Vector Float -> Float
minElement'   = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"minElement" (FunCodeS -> Vector Float -> Float
toScalarF FunCodeS
Min)
    maxElement' :: Vector Float -> Float
maxElement'   = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
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' :: Ord Float => Vector Float -> Vector Float
step' = Vector Float -> Vector Float
stepF
    find' :: (Float -> Bool) -> Vector Float -> [IndexOf Vector]
find' = forall {a}. Storable a => (a -> Bool) -> Vector a -> [Int]
findV
    assoc' :: IndexOf Vector
-> Float -> [(IndexOf Vector, Float)] -> Vector Float
assoc' = 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' = forall {t} {t :: * -> *} {t}.
(Storable t, Foldable t) =>
Vector t -> (t -> t -> t) -> t (Int, t) -> Vector t
accumV
    ccompare' :: Ord Float => Vector Float -> Vector Float -> Vector I
ccompare' = forall {t} {t}.
Element t =>
(Vector t -> Vector t -> t) -> Vector t -> Vector t -> t
compareCV 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' = 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 forall a.
Element a =>
Vector I -> Vector a -> Vector a -> Vector a -> Vector a
selectV
    scaleRecip :: Fractional Float => Float -> Vector Float -> Vector Float
scaleRecip = FunCodeSV -> Float -> Vector Float -> Vector Float
vectorMapValF FunCodeSV
Recip
    divide :: Fractional Float => Vector Float -> Vector Float -> Vector Float
divide = FunCodeVV -> Vector Float -> Vector Float -> Vector Float
vectorZipF FunCodeVV
Div
    arctan2' :: Fractional Float => Vector Float -> Vector Float -> Vector Float
arctan2' = FunCodeVV -> Vector Float -> Vector Float -> Vector Float
vectorZipF FunCodeVV
ATan2
    cmod' :: Integral Float => Float -> Vector Float -> Vector Float
cmod' = 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'   = (forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (SingleOf t)
single :: Vector R-> Vector Float) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (c :: * -> *) e. Container c e => c Z -> c e
fromZ'
    toZ' :: Vector Float -> Vector Z
toZ'     = forall (c :: * -> *) e. Container c e => c e -> c Z
toZ' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (DoubleOf t)
double


instance Container Vector Double
  where
    conj' :: Vector R -> Vector R
conj' = forall a. a -> a
id
    size' :: Vector R -> IndexOf Vector
size' = 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 = forall a. Eq a => a -> a -> Bool
(==)
    scalar' :: R -> Vector R
scalar' = forall a. Storable a => a -> Vector a
V.singleton
    konst' :: R -> IndexOf Vector -> Vector R
konst' = forall a. Element a => a -> Int -> Vector a
constantD
    build' :: IndexOf Vector -> ArgOf Vector R -> Vector R
build' = forall {a} {t} {a}.
(Integral a, Num t, Storable a) =>
a -> (t -> a) -> Vector a
buildV
    cmap' :: forall b. Element b => (R -> b) -> Vector R -> Vector b
cmap' = forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
mapVector
    atIndex' :: Vector R -> IndexOf Vector -> R
atIndex' = forall t. Storable t => Vector t -> Int -> t
(@>)
    minIndex' :: Vector R -> IndexOf Vector
minIndex'     = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"minIndex"   (forall a b. (RealFrac a, Integral b) => a -> b
round forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector R -> R
toScalarR FunCodeS
MinIdx)
    maxIndex' :: Vector R -> IndexOf Vector
maxIndex'     = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"maxIndex"   (forall a b. (RealFrac a, Integral b) => a -> b
round forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeS -> Vector R -> R
toScalarR FunCodeS
MaxIdx)
    minElement' :: Vector R -> R
minElement'   = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"minElement" (FunCodeS -> Vector R -> R
toScalarR FunCodeS
Min)
    maxElement' :: Vector R -> R
maxElement'   = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
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' :: Ord R => Vector R -> Vector R
step' = Vector R -> Vector R
stepD
    find' :: (R -> Bool) -> Vector R -> [IndexOf Vector]
find' = forall {a}. Storable a => (a -> Bool) -> Vector a -> [Int]
findV
    assoc' :: IndexOf Vector -> R -> [(IndexOf Vector, R)] -> Vector R
assoc' = 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' = forall {t} {t :: * -> *} {t}.
(Storable t, Foldable t) =>
Vector t -> (t -> t -> t) -> t (Int, t) -> Vector t
accumV
    ccompare' :: Ord R => Vector R -> Vector R -> Vector I
ccompare' = forall {t} {t}.
Element t =>
(Vector t -> Vector t -> t) -> Vector t -> Vector t -> t
compareCV 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' = 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 forall a.
Element a =>
Vector I -> Vector a -> Vector a -> Vector a -> Vector a
selectV
    scaleRecip :: Fractional R => R -> Vector R -> Vector R
scaleRecip = FunCodeSV -> R -> Vector R -> Vector R
vectorMapValR FunCodeSV
Recip
    divide :: Fractional R => Vector R -> Vector R -> Vector R
divide = FunCodeVV -> Vector R -> Vector R -> Vector R
vectorZipR FunCodeVV
Div
    arctan2' :: Fractional R => Vector R -> Vector R -> Vector R
arctan2' = FunCodeVV -> Vector R -> Vector R -> Vector R
vectorZipR FunCodeVV
ATan2
    cmod' :: Integral R => R -> Vector R -> Vector R
cmod' = 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' = 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 = forall a. Eq a => a -> a -> Bool
(==)
    scalar' :: Complex R -> Vector (Complex R)
scalar' = forall a. Storable a => a -> Vector a
V.singleton
    konst' :: Complex R -> IndexOf Vector -> Vector (Complex R)
konst' = forall a. Element a => a -> Int -> Vector a
constantD
    build' :: IndexOf Vector -> ArgOf Vector (Complex R) -> Vector (Complex R)
build' = forall {a} {t} {a}.
(Integral a, Num t, Storable a) =>
a -> (t -> a) -> Vector a
buildV
    cmap' :: forall b.
Element b =>
(Complex R -> b) -> Vector (Complex R) -> Vector b
cmap' = forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
mapVector
    atIndex' :: Vector (Complex R) -> IndexOf Vector -> Complex R
atIndex' = forall t. Storable t => Vector t -> Int -> t
(@>)
    minIndex' :: Vector (Complex R) -> IndexOf Vector
minIndex'     = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"minIndex" (forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (c :: * -> *) e. Container c e => c e -> c e -> c e
mul forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> *) e. Container c e => c e -> c e
conj'))
    maxIndex' :: Vector (Complex R) -> IndexOf Vector
maxIndex'     = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"maxIndex" (forall (c :: * -> *) e. Container c e => c e -> IndexOf c
maxIndex' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (c :: * -> *) e. Container c e => c e -> c e -> c e
mul forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> *) e. Container c e => c e -> c e
conj'))
    minElement' :: Vector (Complex R) -> Complex R
minElement'   = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"minElement" (forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex' forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex')
    maxElement' :: Vector (Complex R) -> Complex R
maxElement'   = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"maxElement" (forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex' forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> 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' :: Ord (Complex R) => Vector (Complex R) -> Vector (Complex R)
step' = forall a. HasCallStack => a
undefined -- cannot match
    find' :: (Complex R -> Bool) -> Vector (Complex R) -> [IndexOf Vector]
find' = forall {a}. Storable a => (a -> Bool) -> Vector a -> [Int]
findV
    assoc' :: IndexOf Vector
-> Complex R -> [(IndexOf Vector, Complex R)] -> Vector (Complex R)
assoc' = 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' = forall {t} {t :: * -> *} {t}.
(Storable t, Foldable t) =>
Vector t -> (t -> t -> t) -> t (Int, t) -> Vector t
accumV
    ccompare' :: Ord (Complex R) =>
Vector (Complex R) -> Vector (Complex R) -> Vector I
ccompare' = forall a. HasCallStack => a
undefined -- cannot match
    cselect' :: Vector I
-> Vector (Complex R)
-> Vector (Complex R)
-> Vector (Complex R)
-> Vector (Complex R)
cselect' = 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 forall a.
Element a =>
Vector I -> Vector a -> Vector a -> Vector a -> Vector a
selectV
    scaleRecip :: Fractional (Complex R) =>
Complex R -> Vector (Complex R) -> Vector (Complex R)
scaleRecip = FunCodeSV -> Complex R -> Vector (Complex R) -> Vector (Complex R)
vectorMapValC FunCodeSV
Recip
    divide :: Fractional (Complex R) =>
Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
divide = FunCodeVV
-> Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
vectorZipC FunCodeVV
Div
    arctan2' :: Fractional (Complex R) =>
Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
arctan2' = FunCodeVV
-> Vector (Complex R) -> Vector (Complex R) -> Vector (Complex R)
vectorZipC FunCodeVV
ATan2
    cmod' :: Integral (Complex R) =>
Complex R -> Vector (Complex R) -> Vector (Complex R)
cmod' = forall a. HasCallStack => a
undefined
    fromInt' :: Vector I -> Vector (Complex R)
fromInt' = forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (ComplexOf t)
complex forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector I -> Vector R
int2DoubleV
    toInt' :: Vector (Complex R) -> Vector I
toInt'   = forall (c :: * -> *) e. Container c e => c e -> c I
toInt' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex
    fromZ' :: Vector Z -> Vector (Complex R)
fromZ'   = forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (ComplexOf t)
complex forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Z -> Vector R
long2DoubleV
    toZ' :: Vector (Complex R) -> Vector Z
toZ'     = forall (c :: * -> *) e. Container c e => c e -> c Z
toZ' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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' = 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 = forall a. Eq a => a -> a -> Bool
(==)
    scalar' :: Complex Float -> Vector (Complex Float)
scalar' = forall a. Storable a => a -> Vector a
V.singleton
    konst' :: Complex Float -> IndexOf Vector -> Vector (Complex Float)
konst' = forall a. Element a => a -> Int -> Vector a
constantD
    build' :: IndexOf Vector
-> ArgOf Vector (Complex Float) -> Vector (Complex Float)
build' = forall {a} {t} {a}.
(Integral a, Num t, Storable a) =>
a -> (t -> a) -> Vector a
buildV
    cmap' :: forall b.
Element b =>
(Complex Float -> b) -> Vector (Complex Float) -> Vector b
cmap' = forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
mapVector
    atIndex' :: Vector (Complex Float) -> IndexOf Vector -> Complex Float
atIndex' = forall t. Storable t => Vector t -> Int -> t
(@>)
    minIndex' :: Vector (Complex Float) -> IndexOf Vector
minIndex'     = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"minIndex" (forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (c :: * -> *) e. Container c e => c e -> c e -> c e
mul forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> *) e. Container c e => c e -> c e
conj'))
    maxIndex' :: Vector (Complex Float) -> IndexOf Vector
maxIndex'     = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"maxIndex" (forall (c :: * -> *) e. Container c e => c e -> IndexOf c
maxIndex' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (c :: * -> *) e. Container c e => c e -> c e -> c e
mul forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> *) e. Container c e => c e -> c e
conj'))
    minElement' :: Vector (Complex Float) -> Complex Float
minElement'   = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"minElement" (forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex' forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex')
    maxElement' :: Vector (Complex Float) -> Complex Float
maxElement'   = forall {t} {t}.
Storable t =>
[Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
"maxElement" (forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex' forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> 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' :: Ord (Complex Float) =>
Vector (Complex Float) -> Vector (Complex Float)
step' = forall a. HasCallStack => a
undefined -- cannot match
    find' :: (Complex Float -> Bool)
-> Vector (Complex Float) -> [IndexOf Vector]
find' = forall {a}. Storable a => (a -> Bool) -> Vector a -> [Int]
findV
    assoc' :: IndexOf Vector
-> Complex Float
-> [(IndexOf Vector, Complex Float)]
-> Vector (Complex Float)
assoc' = 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' = forall {t} {t :: * -> *} {t}.
(Storable t, Foldable t) =>
Vector t -> (t -> t -> t) -> t (Int, t) -> Vector t
accumV
    ccompare' :: Ord (Complex Float) =>
Vector (Complex Float) -> Vector (Complex Float) -> Vector I
ccompare' = forall a. HasCallStack => a
undefined -- cannot match
    cselect' :: Vector I
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
cselect' = 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 forall a.
Element a =>
Vector I -> Vector a -> Vector a -> Vector a -> Vector a
selectV
    scaleRecip :: Fractional (Complex Float) =>
Complex Float -> Vector (Complex Float) -> Vector (Complex Float)
scaleRecip = FunCodeSV
-> Complex Float
-> Vector (Complex Float)
-> Vector (Complex Float)
vectorMapValQ FunCodeSV
Recip
    divide :: Fractional (Complex Float) =>
Vector (Complex Float)
-> Vector (Complex Float) -> Vector (Complex Float)
divide = FunCodeVV
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
vectorZipQ FunCodeVV
Div
    arctan2' :: Fractional (Complex Float) =>
Vector (Complex Float)
-> Vector (Complex Float) -> Vector (Complex Float)
arctan2' = FunCodeVV
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
vectorZipQ FunCodeVV
ATan2
    cmod' :: Integral (Complex Float) =>
Complex Float -> Vector (Complex Float) -> Vector (Complex Float)
cmod' = forall a. HasCallStack => a
undefined
    fromInt' :: Vector I -> Vector (Complex Float)
fromInt' = forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (ComplexOf t)
complex forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector I -> Vector Float
int2floatV
    toInt' :: Vector (Complex Float) -> Vector I
toInt'   = forall (c :: * -> *) e. Container c e => c e -> c I
toInt' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex
    fromZ' :: Vector Z -> Vector (Complex Float)
fromZ' = forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (ComplexOf t)
complex forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (SingleOf t)
single forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Z -> Vector R
long2DoubleV
    toZ' :: Vector (Complex Float) -> Vector Z
toZ'   = forall (c :: * -> *) e. Container c e => c e -> c Z
toZ' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (c :: * -> *).
(Convert t, Complexable c) =>
c t -> c (DoubleOf t)
double forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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' = forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix forall (c :: * -> *) e. Container c e => c e -> c e
conj'
    size' :: Matrix a -> IndexOf Matrix
size' = forall t. Matrix t -> (Int, Int)
size
    scale' :: a -> Matrix a -> Matrix a
scale' a
x = forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix (forall (c :: * -> *) e. Container c e => e -> c e -> c e
scale' a
x)
    addConstant :: a -> Matrix a -> Matrix a
addConstant a
x = forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix (forall (c :: * -> *) e. Container c e => e -> c e -> c e
addConstant a
x)
    add' :: Matrix a -> Matrix a -> Matrix a
add' = forall t a b.
(Element t, Element a, Element b) =>
(Vector a -> Vector b -> Vector t)
-> Matrix a -> Matrix b -> Matrix t
liftMatrix2 forall (c :: * -> *) e. Container c e => c e -> c e -> c e
add'
    sub :: Matrix a -> Matrix a -> Matrix a
sub = forall t a b.
(Element t, Element a, Element b) =>
(Vector a -> Vector b -> Vector t)
-> Matrix a -> Matrix b -> Matrix t
liftMatrix2 forall (c :: * -> *) e. Container c e => c e -> c e -> c e
sub
    mul :: Matrix a -> Matrix a -> Matrix a
mul = forall t a b.
(Element t, Element a, Element b) =>
(Vector a -> Vector b -> Vector t)
-> Matrix a -> Matrix b -> Matrix t
liftMatrix2 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 = forall t. Matrix t -> Int
cols Matrix a
a forall a. Eq a => a -> a -> Bool
== forall t. Matrix t -> Int
cols Matrix a
b Bool -> Bool -> Bool
&& forall t. Element t => Matrix t -> Vector t
flatten Matrix a
a forall (c :: * -> *) e. Container c e => c e -> c e -> Bool
`equal` forall t. Element t => Matrix t -> Vector t
flatten Matrix a
b
    scalar' :: a -> Matrix a
scalar' a
x = (Int
1forall a. Storable a => Int -> Int -> [a] -> Matrix a
><Int
1) [a
x]
    konst' :: a -> IndexOf Matrix -> Matrix a
konst' a
v (Int
r,Int
c) = forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
RowMajor Int
r Int
c (forall (c :: * -> *) e. Container c e => e -> IndexOf c -> c e
konst' a
v (Int
rforall a. Num a => a -> a -> a
*Int
c))
    build' :: IndexOf Matrix -> ArgOf Matrix a -> Matrix a
build' = 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' :: forall b. Element b => (a -> b) -> Matrix a -> Matrix b
cmap' a -> b
f = forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix (forall a b.
(Storable a, Storable b) =>
(a -> b) -> Vector a -> Vector b
mapVector a -> b
f)
    atIndex' :: Matrix a -> IndexOf Matrix -> a
atIndex' = forall t. Storable t => Matrix t -> (Int, Int) -> t
(@@>)
    minIndex' :: Matrix a -> IndexOf Matrix
minIndex' = forall {t} {t}. [Char] -> (Matrix t -> t) -> Matrix t -> t
emptyErrorM [Char]
"minIndex of Matrix" forall a b. (a -> b) -> a -> b
$
                \Matrix a
m -> forall a. Integral a => a -> a -> (a, a)
divMod (forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex' forall a b. (a -> b) -> a -> b
$ forall t. Element t => Matrix t -> Vector t
flatten Matrix a
m) (forall t. Matrix t -> Int
cols Matrix a
m)
    maxIndex' :: Matrix a -> IndexOf Matrix
maxIndex' = forall {t} {t}. [Char] -> (Matrix t -> t) -> Matrix t -> t
emptyErrorM [Char]
"maxIndex of Matrix" forall a b. (a -> b) -> a -> b
$
                \Matrix a
m -> forall a. Integral a => a -> a -> (a, a)
divMod (forall (c :: * -> *) e. Container c e => c e -> IndexOf c
maxIndex' forall a b. (a -> b) -> a -> b
$ forall t. Element t => Matrix t -> Vector t
flatten Matrix a
m) (forall t. Matrix t -> Int
cols Matrix a
m)
    minElement' :: Matrix a -> a
minElement' = forall {t} {t}. [Char] -> (Matrix t -> t) -> Matrix t -> t
emptyErrorM [Char]
"minElement of Matrix" (forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex' forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex')
    maxElement' :: Matrix a -> a
maxElement' = forall {t} {t}. [Char] -> (Matrix t -> t) -> Matrix t -> t
emptyErrorM [Char]
"maxElement of Matrix" (forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex' forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (c :: * -> *) e. Container c e => c e -> IndexOf c
maxIndex')
    sumElements' :: Matrix a -> a
sumElements' = forall (c :: * -> *) e. Container c e => c e -> e
sumElements' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Element t => Matrix t -> Vector t
flatten
    prodElements' :: Matrix a -> a
prodElements' = forall (c :: * -> *) e. Container c e => c e -> e
prodElements' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Element t => Matrix t -> Vector t
flatten
    step' :: Ord a => Matrix a -> Matrix a
step' = forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix forall (c :: * -> *) e. (Container c e, Ord e) => c e -> c e
step'
    find' :: (a -> Bool) -> Matrix a -> [IndexOf Matrix]
find' = forall {a}. Element a => (a -> Bool) -> Matrix a -> [(Int, Int)]
findM
    assoc' :: IndexOf Matrix -> a -> [(IndexOf Matrix, a)] -> Matrix a
assoc' = 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' = forall {t} {t :: * -> *} {t}.
(Element t, Foldable t) =>
Matrix t -> (t -> t -> t) -> t ((Int, Int), t) -> Matrix t
accumM
    ccompare' :: Ord a => Matrix a -> Matrix a -> Matrix I
ccompare' = 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' = forall {t}.
(Num t, Container Vector t) =>
Matrix I -> Matrix t -> Matrix t -> Matrix t -> Matrix t
selectM
    scaleRecip :: Fractional a => a -> Matrix a -> Matrix a
scaleRecip a
x = forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix (forall (c :: * -> *) e.
(Container c e, Fractional e) =>
e -> c e -> c e
scaleRecip a
x)
    divide :: Fractional a => Matrix a -> Matrix a -> Matrix a
divide = forall t a b.
(Element t, Element a, Element b) =>
(Vector a -> Vector b -> Vector t)
-> Matrix a -> Matrix b -> Matrix t
liftMatrix2 forall (c :: * -> *) e.
(Container c e, Fractional e) =>
c e -> c e -> c e
divide
    arctan2' :: Fractional a => Matrix a -> Matrix a -> Matrix a
arctan2' = forall t a b.
(Element t, Element a, Element b) =>
(Vector a -> Vector b -> Vector t)
-> Matrix a -> Matrix b -> Matrix t
liftMatrix2 forall (c :: * -> *) e.
(Container c e, Fractional e) =>
c e -> c e -> c e
arctan2'
    cmod' :: Integral a => a -> Matrix a -> Matrix a
cmod' a
m Matrix a
x
        | a
m forall a. Eq a => a -> a -> Bool
/= a
0    = forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix (forall (c :: * -> *) e.
(Container c e, Integral e) =>
e -> c e -> c e
cmod' a
m) Matrix a
x
        | Bool
otherwise = forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"cmod 0 on matrix "forall a. [a] -> [a] -> [a]
++forall t. Matrix t -> [Char]
shSize Matrix a
x
    fromInt' :: Matrix I -> Matrix a
fromInt' = forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix forall (c :: * -> *) e. Container c e => c I -> c e
fromInt'
    toInt' :: Matrix a -> Matrix I
toInt' = forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix forall (c :: * -> *) e. Container c e => c e -> c I
toInt'
    fromZ' :: Matrix Z -> Matrix a
fromZ' = forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix forall (c :: * -> *) e. Container c e => c Z -> c e
fromZ'
    toZ' :: Matrix a -> Matrix Z
toZ'   = forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix forall (c :: * -> *) e. Container c e => c e -> c Z
toZ'


emptyErrorV :: [Char] -> (Vector t -> t) -> Vector t -> t
emptyErrorV [Char]
msg Vector t -> t
f Vector t
v =
    if forall t. Storable t => Vector t -> Int
dim Vector t
v forall a. Ord a => a -> a -> Bool
> Int
0
        then Vector t -> t
f Vector t
v
        else forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
msg forall a. [a] -> [a] -> [a]
++ [Char]
" of empty Vector"

emptyErrorM :: [Char] -> (Matrix t -> t) -> Matrix t -> t
emptyErrorM [Char]
msg Matrix t -> t
f Matrix t
m =
    if forall t. Matrix t -> Int
rows Matrix t
m forall a. Ord a => a -> a -> Bool
> Int
0 Bool -> Bool -> Bool
&& forall t. Matrix t -> Int
cols Matrix t
m forall a. Ord a => a -> a -> Bool
> Int
0
        then Matrix t -> t
f Matrix t
m
        else forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
msgforall a. [a] -> [a] -> [a]
++[Char]
" "forall a. [a] -> [a] -> [a]
++forall t. Matrix t -> [Char]
shSize Matrix t
m

--------------------------------------------------------------------------------

-- | create a structure with a single element
--
-- >>> let v = fromList [1..3::Double]
-- >>> v / scalar (norm2 v)
-- fromList [0.2672612419124244,0.5345224838248488,0.8017837257372732]
--
scalar :: Container c e => e -> c e
scalar :: forall (c :: * -> *) e. Container c e => e -> c e
scalar = forall (c :: * -> *) e. Container c e => e -> c e
scalar'

-- | complex conjugate
conj :: Container c e => c e -> c e
conj :: forall (c :: * -> *) e. Container c e => c e -> c e
conj = forall (c :: * -> *) e. Container c e => c e -> c e
conj'


arctan2 :: (Fractional e, Container c e) => c e -> c e -> c e
arctan2 :: forall e (c :: * -> *).
(Fractional e, Container c e) =>
c e -> c e -> c e
arctan2 = forall (c :: * -> *) e.
(Container c e, Fractional e) =>
c e -> c e -> c e
arctan2'

-- | 'mod' for integer arrays
--
-- >>> cmod 3 (range 5)
-- fromList [0,1,2,0,1]
cmod :: (Integral e, Container c e) => e -> c e -> c e
cmod :: forall e (c :: * -> *).
(Integral e, Container c e) =>
e -> c e -> c e
cmod = forall (c :: * -> *) e.
(Container c e, Integral e) =>
e -> c e -> c e
cmod'

-- |
-- >>>fromInt ((2><2) [0..3]) :: Matrix (Complex Double)
-- (2><2)
-- [ 0.0 :+ 0.0, 1.0 :+ 0.0
-- , 2.0 :+ 0.0, 3.0 :+ 0.0 ]
--
fromInt :: (Container c e) => c I -> c e
fromInt :: forall (c :: * -> *) e. Container c e => c I -> c e
fromInt = forall (c :: * -> *) e. Container c e => c I -> c e
fromInt'

toInt :: (Container c e) => c e -> c I
toInt :: forall (c :: * -> *) e. Container c e => c e -> c I
toInt = forall (c :: * -> *) e. Container c e => c e -> c I
toInt'

fromZ :: (Container c e) => c Z -> c e
fromZ :: forall (c :: * -> *) e. Container c e => c Z -> c e
fromZ = forall (c :: * -> *) e. Container c e => c Z -> c e
fromZ'

toZ :: (Container c e) => c e -> c Z
toZ :: forall (c :: * -> *) e. Container c e => c e -> c Z
toZ = forall (c :: * -> *) e. Container c e => c e -> c Z
toZ'

-- | like 'fmap' (cannot implement instance Functor because of Element class constraint)
cmap :: (Element b, Container c e) => (e -> b) -> c e -> c b
cmap :: forall b (c :: * -> *) e.
(Element b, Container c e) =>
(e -> b) -> c e -> c b
cmap = forall (c :: * -> *) e b.
(Container c e, Element b) =>
(e -> b) -> c e -> c b
cmap'

-- | generic indexing function
--
-- >>> vector [1,2,3] `atIndex` 1
-- 2.0
--
-- >>> matrix 3 [0..8] `atIndex` (2,0)
-- 6.0
--
atIndex :: Container c e => c e -> IndexOf c -> e
atIndex :: forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex = forall (c :: * -> *) e. Container c e => c e -> IndexOf c -> e
atIndex'

-- | index of minimum element
minIndex :: Container c e => c e -> IndexOf c
minIndex :: forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex = forall (c :: * -> *) e. Container c e => c e -> IndexOf c
minIndex'

-- | index of maximum element
maxIndex :: Container c e => c e -> IndexOf c
maxIndex :: forall (c :: * -> *) e. Container c e => c e -> IndexOf c
maxIndex = forall (c :: * -> *) e. Container c e => c e -> IndexOf c
maxIndex'

-- | value of minimum element
minElement :: Container c e => c e -> e
minElement :: forall (c :: * -> *) e. Container c e => c e -> e
minElement = forall (c :: * -> *) e. Container c e => c e -> e
minElement'

-- | value of maximum element
maxElement :: Container c e => c e -> e
maxElement :: forall (c :: * -> *) e. Container c e => c e -> e
maxElement = forall (c :: * -> *) e. Container c e => c e -> e
maxElement'

-- | the sum of elements
sumElements :: Container c e => c e -> e
sumElements :: forall (c :: * -> *) e. Container c e => c e -> e
sumElements = forall (c :: * -> *) e. Container c e => c e -> e
sumElements'

-- | the product of elements
prodElements :: Container c e => c e -> e
prodElements :: forall (c :: * -> *) e. Container c e => c e -> e
prodElements = forall (c :: * -> *) e. Container c e => c e -> e
prodElements'


-- | A more efficient implementation of @cmap (\\x -> if x>0 then 1 else 0)@
--
-- >>> step $ linspace 5 (-1,1::Double)
-- 5 |> [0.0,0.0,0.0,1.0,1.0]
--
step
  :: (Ord e, Container c e)
    => c e
    -> c e
step :: forall e (c :: * -> *). (Ord e, Container c e) => c e -> c e
step = forall (c :: * -> *) e. (Container c e, Ord e) => c e -> c e
step'


-- | Element by element version of @case compare a b of {LT -> l; EQ -> e; GT -> g}@.
--
-- Arguments with any dimension = 1 are automatically expanded:
--
-- >>> cond ((1><4)[1..]) ((3><1)[1..]) 0 100 ((3><4)[1..]) :: Matrix Double
-- (3><4)
-- [ 100.0,   2.0,   3.0,  4.0
-- ,   0.0, 100.0,   7.0,  8.0
-- ,   0.0,   0.0, 100.0, 12.0 ]
--
-- >>> let chop x = cond (abs x) 1E-6 0 0 x
--
cond
    :: (Ord e, Container c e, Container c x)
    => c e -- ^ a
    -> c e -- ^ b
    -> c x -- ^ l
    -> c x -- ^ e
    -> c x -- ^ g
    -> c x -- ^ result
cond :: forall e (c :: * -> *) x.
(Ord e, Container c e, Container c x) =>
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 = forall (c :: * -> *) e.
Container c e =>
c I -> c e -> c e -> c e -> c e
cselect' (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 index of elements which satisfy a predicate
--
-- >>> find (>0) (ident 3 :: Matrix Double)
-- [(0,0),(1,1),(2,2)]
--
find
  :: Container c e
    => (e -> Bool)
    -> c e
    -> [IndexOf c]
find :: forall (c :: * -> *) e.
Container c e =>
(e -> Bool) -> c e -> [IndexOf c]
find = forall (c :: * -> *) e.
Container c e =>
(e -> Bool) -> c e -> [IndexOf c]
find'


-- | Create a structure from an association list
--
-- >>> assoc 5 0 [(3,7),(1,4)] :: Vector Double
-- fromList [0.0,4.0,0.0,7.0,0.0]
--
-- >>> assoc (2,3) 0 [((0,2),7),((1,0),2*i-3)] :: Matrix (Complex Double)
-- (2><3)
--  [    0.0 :+ 0.0, 0.0 :+ 0.0, 7.0 :+ 0.0
--  , (-3.0) :+ 2.0, 0.0 :+ 0.0, 0.0 :+ 0.0 ]
--
assoc
  :: Container c e
    => IndexOf c        -- ^ size
    -> e                -- ^ default value
    -> [(IndexOf c, e)] -- ^ association list
    -> c e              -- ^ result
assoc :: forall (c :: * -> *) e.
Container c e =>
IndexOf c -> e -> [(IndexOf c, e)] -> c e
assoc = forall (c :: * -> *) e.
Container c e =>
IndexOf c -> e -> [(IndexOf c, e)] -> c e
assoc'


-- | Modify a structure using an update function
--
-- >>> accum (ident 5) (+) [((1,1),5),((0,3),3)] :: Matrix Double
-- (5><5)
--  [ 1.0, 0.0, 0.0, 3.0, 0.0
--  , 0.0, 6.0, 0.0, 0.0, 0.0
--  , 0.0, 0.0, 1.0, 0.0, 0.0
--  , 0.0, 0.0, 0.0, 1.0, 0.0
--  , 0.0, 0.0, 0.0, 0.0, 1.0 ]
--
-- computation of histogram:
--
-- >>> accum (konst 0 7) (+) (map (flip (,) 1) [4,5,4,1,5,2,5]) :: Vector Double
-- fromList [0.0,1.0,1.0,0.0,2.0,3.0,0.0]
--
accum
  :: Container c e
    => c e              -- ^ initial structure
    -> (e -> e -> e)    -- ^ update function
    -> [(IndexOf c, e)] -- ^ association list
    -> c e              -- ^ result
accum :: forall (c :: * -> *) e.
Container c e =>
c e -> (e -> e -> e) -> [(IndexOf c, e)] -> c e
accum = 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 7 3 :: Vector Float
    -- fromList [7.0,7.0,7.0]
    --
    -- >>> konst i (3::Int,4::Int)
    -- (3><4)
    --  [ 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
    --  , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0
    --  , 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0, 0.0 :+ 1.0 ]
    --
    konst :: e -> d -> c e

instance Container Vector e => Konst e Int Vector
  where
    konst :: e -> Int -> Vector e
konst = 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 = 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

--------------------------------------------------------------------------------

--------------------------------------------------------------------------------

-- | Matrix product and related functions
class (Num e, Element e) => Product e where
    -- | matrix product
    multiply :: Matrix e -> Matrix e -> Matrix e
    -- | sum of absolute value of elements (differs in complex case from @norm1@)
    absSum     :: Vector e -> RealOf e
    -- | sum of absolute value of elements
    norm1      :: Vector e -> RealOf e
    -- | euclidean norm
    norm2      :: Floating e => Vector e -> RealOf e
    -- | element of maximum magnitude
    normInf    :: Vector e -> RealOf e

instance Product Float where
    norm2 :: Floating Float => Vector Float -> RealOf Float
norm2      = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (FunCodeS -> Vector Float -> Float
toScalarF FunCodeS
Norm2)
    absSum :: Vector Float -> RealOf Float
absSum     = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (FunCodeS -> Vector Float -> Float
toScalarF FunCodeS
AbsSum)
    norm1 :: Vector Float -> RealOf Float
norm1      = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (FunCodeS -> Vector Float -> Float
toScalarF FunCodeS
AbsSum)
    normInf :: Vector Float -> RealOf Float
normInf    = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (forall (c :: * -> *) e. Container c e => c e -> e
maxElement 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   = forall {c :: * -> *} {e} {t} {t}.
(IndexOf c ~ (Int, Int), Container c e, Num e) =>
(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 :: Floating R => Vector R -> RealOf R
norm2      = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (FunCodeS -> Vector R -> R
toScalarR FunCodeS
Norm2)
    absSum :: Vector R -> RealOf R
absSum     = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (FunCodeS -> Vector R -> R
toScalarR FunCodeS
AbsSum)
    norm1 :: Vector R -> RealOf R
norm1      = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (FunCodeS -> Vector R -> R
toScalarR FunCodeS
AbsSum)
    normInf :: Vector R -> RealOf R
normInf    = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (forall (c :: * -> *) e. Container c e => c e -> e
maxElement 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   = forall {c :: * -> *} {e} {t} {t}.
(IndexOf c ~ (Int, Int), Container c e, Num e) =>
(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 :: Floating (Complex Float) =>
Vector (Complex Float) -> RealOf (Complex Float)
norm2      = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (FunCodeS -> Vector (Complex Float) -> Float
toScalarQ FunCodeS
Norm2)
    absSum :: Vector (Complex Float) -> RealOf (Complex Float)
absSum     = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (FunCodeS -> Vector (Complex Float) -> Float
toScalarQ FunCodeS
AbsSum)
    norm1 :: Vector (Complex Float) -> RealOf (Complex Float)
norm1      = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (forall (c :: * -> *) e. Container c e => c e -> e
sumElements forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex 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    = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (forall (c :: * -> *) e. Container c e => c e -> e
maxElement forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex 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   = forall {c :: * -> *} {e} {t} {t}.
(IndexOf c ~ (Int, Int), Container c e, Num e) =>
(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 :: Floating (Complex R) => Vector (Complex R) -> RealOf (Complex R)
norm2      = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (FunCodeS -> Vector (Complex R) -> R
toScalarC FunCodeS
Norm2)
    absSum :: Vector (Complex R) -> RealOf (Complex R)
absSum     = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (FunCodeS -> Vector (Complex R) -> R
toScalarC FunCodeS
AbsSum)
    norm1 :: Vector (Complex R) -> RealOf (Complex R)
norm1      = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (forall (c :: * -> *) e. Container c e => c e -> e
sumElements forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex 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    = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (forall (c :: * -> *) e. Container c e => c e -> e
maxElement forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t (c :: * -> *).
(Convert t, Complexable c, RealElement t) =>
c (Complex t) -> (c t, c t)
fromComplex 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   = forall {c :: * -> *} {e} {t} {t}.
(IndexOf c ~ (Int, Int), Container c e, Num e) =>
(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 :: Floating I => Vector I -> RealOf I
norm2      = forall a. HasCallStack => a
undefined
    absSum :: Vector I -> RealOf I
absSum     = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (forall (c :: * -> *) e. Container c e => c e -> e
sumElements forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeV -> Vector I -> Vector I
vectorMapI FunCodeV
Abs)
    norm1 :: Vector I -> RealOf I
norm1      = forall e. Product e => Vector e -> RealOf e
absSum
    normInf :: Vector I -> RealOf I
normInf    = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (forall (c :: * -> *) e. Container c e => c e -> e
maxElement 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   = forall {c :: * -> *} {e} {t} {t}.
(IndexOf c ~ (Int, Int), Container c e, Num e) =>
(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 :: Floating Z => Vector Z -> RealOf Z
norm2      = forall a. HasCallStack => a
undefined
    absSum :: Vector Z -> RealOf Z
absSum     = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (forall (c :: * -> *) e. Container c e => c e -> e
sumElements forall b c a. (b -> c) -> (a -> b) -> a -> c
. FunCodeV -> Vector Z -> Vector Z
vectorMapL FunCodeV
Abs)
    norm1 :: Vector Z -> RealOf Z
norm1      = forall e. Product e => Vector e -> RealOf e
absSum
    normInf :: Vector Z -> RealOf Z
normInf    = forall {t} {t}.
(Storable t, Num t) =>
(Vector t -> t) -> Vector t -> t
emptyVal (forall (c :: * -> *) e. Container c e => c e -> e
maxElement 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   = forall {c :: * -> *} {e} {t} {t}.
(IndexOf c ~ (Int, Int), Container c e, Num e) =>
(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 forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& Int
x2 forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
|| Int
r forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
|| Int
c forall a. Eq a => a -> a -> Bool
== Int
0 = 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  = forall t. Matrix t -> Int
rows Matrix t
a
    x1 :: Int
x1 = forall t. Matrix t -> Int
cols Matrix t
a
    x2 :: Int
x2 = forall t. Matrix t -> Int
rows Matrix t
b
    c :: Int
c  = forall t. Matrix t -> Int
cols Matrix t
b

emptyVal :: (Vector t -> t) -> Vector t -> t
emptyVal Vector t -> t
f Vector t
v =
    if forall t. Storable t => Vector t -> Int
dim Vector t
v forall a. Ord a => a -> a -> Bool
> Int
0
        then Vector t -> t
f Vector t
v
        else t
0

-- FIXME remove unused C wrappers
-- | unconjugated dot product
udot :: Product e => Vector e -> Vector e -> e
udot :: forall e. Product e => Vector e -> Vector e -> e
udot Vector e
u Vector e
v
    | forall t. Storable t => Vector t -> Int
dim Vector e
u forall a. Eq a => a -> a -> Bool
== forall t. Storable t => Vector t -> Int
dim Vector e
v = Matrix e -> e
val (forall a. Storable a => Vector a -> Matrix a
asRow Vector e
u forall e. Product e => Matrix e -> Matrix e -> Matrix e
`multiply` forall a. Storable a => Vector a -> Matrix a
asColumn Vector e
v)
    | Bool
otherwise = forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"different dimensions "forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> [Char]
show (forall t. Storable t => Vector t -> Int
dim Vector e
u)forall a. [a] -> [a] -> [a]
++[Char]
" and "forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> [Char]
show (forall t. Storable t => Vector t -> Int
dim Vector e
v)forall a. [a] -> [a] -> [a]
++[Char]
" in dot product"
  where
    val :: Matrix e -> e
val Matrix e
m | forall t. Storable t => Vector t -> Int
dim Vector e
u forall a. Ord a => a -> a -> Bool
> Int
0 = Matrix e
mforall t. Storable t => Matrix t -> (Int, Int) -> t
@@>(Int
0,Int
0)
          | Bool
otherwise = e
0

----------------------------------------------------------

-- synonym for matrix product
mXm :: Product t => Matrix t -> Matrix t -> Matrix t
mXm :: forall e. Product e => Matrix e -> Matrix e -> Matrix e
mXm = forall e. Product e => Matrix e -> Matrix e -> Matrix e
multiply

-- matrix - vector product
mXv :: Product t => Matrix t -> Vector t -> Vector t
mXv :: forall t. Product t => Matrix t -> Vector t -> Vector t
mXv Matrix t
m Vector t
v = forall t. Element t => Matrix t -> Vector t
flatten forall a b. (a -> b) -> a -> b
$ Matrix t
m forall e. Product e => Matrix e -> Matrix e -> Matrix e
`mXm` (forall a. Storable a => Vector a -> Matrix a
asColumn Vector t
v)

-- vector - matrix product
vXm :: Product t => Vector t -> Matrix t -> Vector t
vXm :: forall t. Product t => Vector t -> Matrix t -> Vector t
vXm Vector t
v Matrix t
m = forall t. Element t => Matrix t -> Vector t
flatten forall a b. (a -> b) -> a -> b
$ (forall a. Storable a => Vector a -> Matrix a
asRow Vector t
v) forall e. Product e => Matrix e -> Matrix e -> Matrix e
`mXm` Matrix t
m

{- | Outer product of two vectors.

>>> fromList [1,2,3] `outer` fromList [5,2,3]
(3><3)
 [  5.0, 2.0, 3.0
 , 10.0, 4.0, 6.0
 , 15.0, 6.0, 9.0 ]

-}
outer :: (Product t) => Vector t -> Vector t -> Matrix t
outer :: forall t. Product t => Vector t -> Vector t -> Matrix t
outer Vector t
u Vector t
v = forall a. Storable a => Vector a -> Matrix a
asColumn Vector t
u forall e. Product e => Matrix e -> Matrix e -> Matrix e
`multiply` forall a. Storable a => Vector a -> Matrix a
asRow Vector t
v

{- | Kronecker product of two matrices.

@m1=(2><3)
 [ 1.0,  2.0, 0.0
 , 0.0, -1.0, 3.0 ]
m2=(4><3)
 [  1.0,  2.0,  3.0
 ,  4.0,  5.0,  6.0
 ,  7.0,  8.0,  9.0
 , 10.0, 11.0, 12.0 ]@

>>> kronecker m1 m2
(8><9)
 [  1.0,  2.0,  3.0,   2.0,   4.0,   6.0,  0.0,  0.0,  0.0
 ,  4.0,  5.0,  6.0,   8.0,  10.0,  12.0,  0.0,  0.0,  0.0
 ,  7.0,  8.0,  9.0,  14.0,  16.0,  18.0,  0.0,  0.0,  0.0
 , 10.0, 11.0, 12.0,  20.0,  22.0,  24.0,  0.0,  0.0,  0.0
 ,  0.0,  0.0,  0.0,  -1.0,  -2.0,  -3.0,  3.0,  6.0,  9.0
 ,  0.0,  0.0,  0.0,  -4.0,  -5.0,  -6.0, 12.0, 15.0, 18.0
 ,  0.0,  0.0,  0.0,  -7.0,  -8.0,  -9.0, 21.0, 24.0, 27.0
 ,  0.0,  0.0,  0.0, -10.0, -11.0, -12.0, 30.0, 33.0, 36.0 ]

-}
kronecker :: (Product t) => Matrix t -> Matrix t -> Matrix t
kronecker :: forall e. Product e => Matrix e -> Matrix e -> Matrix e
kronecker Matrix t
a Matrix t
b = forall t. Element t => [[Matrix t]] -> Matrix t
fromBlocks
              forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e. Int -> [e] -> [[e]]
chunksOf (forall t. Matrix t -> Int
cols Matrix t
a)
              forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall t. Storable t => Int -> Vector t -> Matrix t
reshape (forall t. Matrix t -> Int
cols Matrix t
b))
              forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Element t => Matrix t -> [Vector t]
toRows
              forall a b. (a -> b) -> a -> b
$ forall t. Element t => Matrix t -> Vector t
flatten Matrix t
a forall t. Product t => Vector t -> Vector t -> Matrix t
`outer` 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 :: forall (c :: * -> *). Complexable c => c (RealOf R) -> c R
real = forall a. a -> a
id
    complex :: forall (c :: * -> *). Complexable c => c R -> c (ComplexOf R)
complex = forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c e -> c (Complex e)
comp'
    single :: forall (c :: * -> *). Complexable c => c R -> c (SingleOf R)
single = forall (c :: * -> *) a b.
(Complexable c, Precision a b) =>
c b -> c a
single'
    double :: forall (c :: * -> *). Complexable c => c R -> c (DoubleOf R)
double = forall a. a -> a
id
    toComplex :: forall (c :: * -> *).
(Complexable c, RealElement R) =>
(c R, c R) -> c (Complex R)
toComplex = forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
(c e, c e) -> c (Complex e)
toComplex'
    fromComplex :: forall (c :: * -> *).
(Complexable c, RealElement R) =>
c (Complex R) -> (c R, c R)
fromComplex = forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c (Complex e) -> (c e, c e)
fromComplex'

instance Convert Float where
    real :: forall (c :: * -> *). Complexable c => c (RealOf Float) -> c Float
real = forall a. a -> a
id
    complex :: forall (c :: * -> *).
Complexable c =>
c Float -> c (ComplexOf Float)
complex = forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c e -> c (Complex e)
comp'
    single :: forall (c :: * -> *).
Complexable c =>
c Float -> c (SingleOf Float)
single = forall a. a -> a
id
    double :: forall (c :: * -> *).
Complexable c =>
c Float -> c (DoubleOf Float)
double = forall (c :: * -> *) a b.
(Complexable c, Precision a b) =>
c a -> c b
double'
    toComplex :: forall (c :: * -> *).
(Complexable c, RealElement Float) =>
(c Float, c Float) -> c (Complex Float)
toComplex = forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
(c e, c e) -> c (Complex e)
toComplex'
    fromComplex :: forall (c :: * -> *).
(Complexable c, RealElement Float) =>
c (Complex Float) -> (c Float, c Float)
fromComplex = forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c (Complex e) -> (c e, c e)
fromComplex'

instance Convert (Complex Double) where
    real :: forall (c :: * -> *).
Complexable c =>
c (RealOf (Complex R)) -> c (Complex R)
real = forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c e -> c (Complex e)
comp'
    complex :: forall (c :: * -> *).
Complexable c =>
c (Complex R) -> c (ComplexOf (Complex R))
complex = forall a. a -> a
id
    single :: forall (c :: * -> *).
Complexable c =>
c (Complex R) -> c (SingleOf (Complex R))
single = forall (c :: * -> *) a b.
(Complexable c, Precision a b) =>
c b -> c a
single'
    double :: forall (c :: * -> *).
Complexable c =>
c (Complex R) -> c (DoubleOf (Complex R))
double = forall a. a -> a
id
    toComplex :: forall (c :: * -> *).
(Complexable c, RealElement (Complex R)) =>
(c (Complex R), c (Complex R)) -> c (Complex (Complex R))
toComplex = forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
(c e, c e) -> c (Complex e)
toComplex'
    fromComplex :: forall (c :: * -> *).
(Complexable c, RealElement (Complex R)) =>
c (Complex (Complex R)) -> (c (Complex R), c (Complex R))
fromComplex = forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c (Complex e) -> (c e, c e)
fromComplex'

instance Convert (Complex Float) where
    real :: forall (c :: * -> *).
Complexable c =>
c (RealOf (Complex Float)) -> c (Complex Float)
real = forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
c e -> c (Complex e)
comp'
    complex :: forall (c :: * -> *).
Complexable c =>
c (Complex Float) -> c (ComplexOf (Complex Float))
complex = forall a. a -> a
id
    single :: forall (c :: * -> *).
Complexable c =>
c (Complex Float) -> c (SingleOf (Complex Float))
single = forall a. a -> a
id
    double :: forall (c :: * -> *).
Complexable c =>
c (Complex Float) -> c (DoubleOf (Complex Float))
double = forall (c :: * -> *) a b.
(Complexable c, Precision a b) =>
c a -> c b
double'
    toComplex :: forall (c :: * -> *).
(Complexable c, RealElement (Complex Float)) =>
(c (Complex Float), c (Complex Float))
-> c (Complex (Complex Float))
toComplex = forall (c :: * -> *) e.
(Complexable c, RealElement e) =>
(c e, c e) -> c (Complex e)
toComplex'
    fromComplex :: forall (c :: * -> *).
(Complexable c, RealElement (Complex Float)) =>
c (Complex (Complex Float))
-> (c (Complex Float), c (Complex Float))
fromComplex = 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 = 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 = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (Integral a, Num b) => a -> b
fromIntegral [a
0 .. (a
rcforall a. Num a => a -> a -> a
-a
1)]
          cs :: [t]
cs = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (Integral a, Num b) => a -> b
fromIntegral [a
0 .. (a
ccforall a. Num a => a -> a -> a
-a
1)]

buildV :: a -> (t -> a) -> Vector a
buildV a
n t -> a
f = forall a. Storable a => [a] -> Vector a
fromList [t -> a
f t
k | t
k <- [t]
ks]
    where ks :: [t]
ks = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (Integral a, Num b) => a -> b
fromIntegral [a
0 .. (a
nforall a. Num a => a -> a -> a
-a
1)]

--------------------------------------------------------

-- | Creates a square matrix with a given diagonal.
diag :: (Num a, Element a) => Vector a -> Matrix a
diag :: forall a. (Num a, Element a) => Vector a -> Matrix a
diag Vector a
v = 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 = forall t. Storable t => Vector t -> Int
dim Vector a
v

-- | creates the identity matrix of given dimension
ident :: (Num a, Element a) => Int -> Matrix a
ident :: forall a. (Num a, Element a) => Int -> Matrix a
ident Int
n = forall a. (Num a, Element a) => Vector a -> Matrix a
diag (forall a. Element a => a -> Int -> Vector a
constantD a
1 Int
n)

--------------------------------------------------------

findV :: (a -> Bool) -> Vector a -> [Int]
findV a -> Bool
p Vector a
x = forall a b.
Storable a =>
(Int -> a -> b -> b) -> b -> Vector a -> b
foldVectorWithIndex Int -> a -> [Int] -> [Int]
g [] Vector a
x where
    g :: Int -> a -> [Int] -> [Int]
g Int
k a
z [Int]
l = if a -> Bool
p a
z then Int
kforall a. a -> [a] -> [a]
:[Int]
l else [Int]
l

findM :: (a -> Bool) -> Matrix a -> [(Int, Int)]
findM a -> Bool
p Matrix a
x = forall a b. (a -> b) -> [a] -> [b]
map ((forall a. Integral a => a -> a -> (a, a)
`divMod` forall t. Matrix t -> Int
cols Matrix a
x)) forall a b. (a -> b) -> a -> b
$ forall {a}. Storable a => (a -> Bool) -> Vector a -> [Int]
findV a -> Bool
p (forall t. Element t => Matrix t -> Vector t
flatten Matrix a
x)

assocV :: Int -> t -> t (Int, t) -> Vector t
assocV Int
n t
z t (Int, t)
xs = forall t. Storable t => (forall s. ST s (STVector s t)) -> Vector t
ST.runSTVector forall a b. (a -> b) -> a -> b
$ do
        STVector s t
v <- forall t s. Storable t => t -> Int -> ST s (STVector s t)
ST.newVector t
z Int
n
        forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Int
k,t
x) -> 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
        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 t. Storable t => (forall s. ST s (STMatrix s t)) -> Matrix t
ST.runSTMatrix forall a b. (a -> b) -> a -> b
$ do
        STMatrix s t
m <- forall t s. Storable t => t -> Int -> Int -> ST s (STMatrix s t)
ST.newMatrix t
z Int
r Int
c
        forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\((Int
i,Int
j),t
x) -> 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
        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 t. Storable t => (forall s. ST s (STVector s t)) -> Vector t
ST.runSTVector forall a b. (a -> b) -> a -> b
$ do
        STVector s t
v <- forall t s. Storable t => Vector t -> ST s (STVector s t)
ST.thawVector Vector t
v0
        forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Int
k,t
x) -> 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
        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 t. Storable t => (forall s. ST s (STMatrix s t)) -> Matrix t
ST.runSTMatrix forall a b. (a -> b) -> a -> b
$ do
        STMatrix s t
m <- forall t s. Element t => Matrix t -> ST s (STMatrix s t)
ST.thawMatrix Matrix t
m0
        forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\((Int
i,Int
j),t
x) -> 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
        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 = forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
RowMajor (forall t. Matrix t -> Int
rows Matrix e
a'') (forall t. Matrix t -> Int
cols Matrix e
a'') forall a b. (a -> b) -> a -> b
$ 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]
_) = forall t. Element t => [Matrix t] -> [Matrix t]
conformMs [Matrix e
a,Matrix e
b]
    [Vector e
a', Vector e
b'] = forall a b. (a -> b) -> [a] -> [b]
map 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'] = 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 = forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
RowMajor (forall t. Matrix t -> Int
rows Matrix t
a'') (forall t. Matrix t -> Int
cols Matrix t
a'') forall a b. (a -> b) -> a -> b
$ forall (c :: * -> *) e.
Container c e =>
c I -> c e -> c e -> c e -> c e
cselect' (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]
_) = forall t. Element t => [Matrix t] -> [Matrix t]
conformMs [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'] = forall a b. (a -> b) -> [a] -> [b]
map 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 (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'] = forall t. Element t => [Vector t] -> [Vector t]
conformVs [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 = 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 = forall (c :: * -> *) e. Container c e => c e -> c e
conj forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Matrix t -> Matrix t
trans

instance CTrans (Complex Float)
  where
    ctrans :: Matrix (Complex Float) -> Matrix (Complex Float)
ctrans = forall (c :: * -> *) e. Container c e => c e -> c e
conj forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Matrix t -> Matrix t
trans

class Transposable m mt | m -> mt, mt -> m
  where
    -- | conjugate transpose
    tr  :: m -> mt
    -- | transpose
    tr' :: m -> mt

instance (CTrans t, Container Vector t) => Transposable (Matrix t) (Matrix t)
  where
    tr :: Matrix t -> Matrix t
tr  = forall t. CTrans t => Matrix t -> Matrix t
ctrans
    tr' :: Matrix t -> Matrix t
tr' = 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 = 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 = 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 = 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 = 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 = forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Testable t => t -> (Bool, IO ())
checkT

--------------------------------------------------------------------------------