{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ConstrainedClassMethods #-}
module Internal.Matrix where
import Internal.Vector
import Internal.Devel
import Internal.Vectorized hiding ((#), (#!))
import Foreign.Marshal.Alloc ( free )
import Foreign.Marshal.Array(newArray)
import Foreign.Ptr ( Ptr )
import Foreign.Storable ( Storable )
import Data.Complex ( Complex )
import Foreign.C.Types ( CInt(..) )
import Foreign.C.String ( CString, newCString )
import System.IO.Unsafe ( unsafePerformIO )
import Control.DeepSeq ( NFData(..) )
import Text.Printf
data MatrixOrder = RowMajor | ColumnMajor deriving (Int -> MatrixOrder -> ShowS
[MatrixOrder] -> ShowS
MatrixOrder -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MatrixOrder] -> ShowS
$cshowList :: [MatrixOrder] -> ShowS
show :: MatrixOrder -> String
$cshow :: MatrixOrder -> String
showsPrec :: Int -> MatrixOrder -> ShowS
$cshowsPrec :: Int -> MatrixOrder -> ShowS
Show,MatrixOrder -> MatrixOrder -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MatrixOrder -> MatrixOrder -> Bool
$c/= :: MatrixOrder -> MatrixOrder -> Bool
== :: MatrixOrder -> MatrixOrder -> Bool
$c== :: MatrixOrder -> MatrixOrder -> Bool
Eq)
data Matrix t = Matrix
{ forall t. Matrix t -> Int
irows :: {-# UNPACK #-} !Int
, forall t. Matrix t -> Int
icols :: {-# UNPACK #-} !Int
, forall t. Matrix t -> Int
xRow :: {-# UNPACK #-} !Int
, forall t. Matrix t -> Int
xCol :: {-# UNPACK #-} !Int
, forall t. Matrix t -> Vector t
xdat :: {-# UNPACK #-} !(Vector t)
}
rows :: Matrix t -> Int
rows :: forall t. Matrix t -> Int
rows = forall t. Matrix t -> Int
irows
{-# INLINE rows #-}
cols :: Matrix t -> Int
cols :: forall t. Matrix t -> Int
cols = forall t. Matrix t -> Int
icols
{-# INLINE cols #-}
size :: Matrix t -> (Int, Int)
size :: forall t. Matrix t -> (Int, Int)
size Matrix t
m = (forall t. Matrix t -> Int
irows Matrix t
m, forall t. Matrix t -> Int
icols Matrix t
m)
{-# INLINE size #-}
rowOrder :: Matrix t -> Bool
rowOrder :: forall t. Matrix t -> Bool
rowOrder Matrix t
m = forall t. Matrix t -> Int
xCol Matrix t
m forall a. Eq a => a -> a -> Bool
== Int
1 Bool -> Bool -> Bool
|| forall t. Matrix t -> Int
cols Matrix t
m forall a. Eq a => a -> a -> Bool
== Int
1
{-# INLINE rowOrder #-}
colOrder :: Matrix t -> Bool
colOrder :: forall t. Matrix t -> Bool
colOrder Matrix t
m = forall t. Matrix t -> Int
xRow Matrix t
m forall a. Eq a => a -> a -> Bool
== Int
1 Bool -> Bool -> Bool
|| forall t. Matrix t -> Int
rows Matrix t
m forall a. Eq a => a -> a -> Bool
== Int
1
{-# INLINE colOrder #-}
is1d :: Matrix t -> Bool
is1d :: forall t. Matrix t -> Bool
is1d (forall t. Matrix t -> (Int, Int)
size->(Int
r,Int
c)) = Int
rforall a. Eq a => a -> a -> Bool
==Int
1 Bool -> Bool -> Bool
|| Int
cforall a. Eq a => a -> a -> Bool
==Int
1
{-# INLINE is1d #-}
isSlice :: Storable t => Matrix t -> Bool
isSlice :: forall t. Storable t => Matrix t -> Bool
isSlice m :: Matrix t
m@(forall t. Matrix t -> (Int, Int)
size->(Int
r,Int
c)) = Int
rforall a. Num a => a -> a -> a
*Int
c forall a. Ord a => a -> a -> Bool
< forall t. Storable t => Vector t -> Int
dim (forall t. Matrix t -> Vector t
xdat Matrix t
m)
{-# INLINE isSlice #-}
orderOf :: Matrix t -> MatrixOrder
orderOf :: forall t. Matrix t -> MatrixOrder
orderOf Matrix t
m = if forall t. Matrix t -> Bool
rowOrder Matrix t
m then MatrixOrder
RowMajor else MatrixOrder
ColumnMajor
showInternal :: Storable t => Matrix t -> IO ()
showInternal :: forall t. Storable t => Matrix t -> IO ()
showInternal Matrix t
m = forall r. PrintfType r => String -> r
printf String
"%dx%d %s %s %d:%d (%d)\n" Int
r Int
c String
slc String
ord Int
xr Int
xc Int
dv
where
r :: Int
r = forall t. Matrix t -> Int
rows Matrix t
m
c :: Int
c = forall t. Matrix t -> Int
cols Matrix t
m
xr :: Int
xr = forall t. Matrix t -> Int
xRow Matrix t
m
xc :: Int
xc = forall t. Matrix t -> Int
xCol Matrix t
m
slc :: String
slc = if forall t. Storable t => Matrix t -> Bool
isSlice Matrix t
m then String
"slice" else String
"full"
ord :: String
ord = if forall t. Matrix t -> Bool
is1d Matrix t
m then String
"1d" else if forall t. Matrix t -> Bool
rowOrder Matrix t
m then String
"rows" else String
"cols"
dv :: Int
dv = forall t. Storable t => Vector t -> Int
dim (forall t. Matrix t -> Vector t
xdat Matrix t
m)
trans :: Matrix t -> Matrix t
trans :: forall t. Matrix t -> Matrix t
trans m :: Matrix t
m@Matrix { irows :: forall t. Matrix t -> Int
irows = Int
r, icols :: forall t. Matrix t -> Int
icols = Int
c, xRow :: forall t. Matrix t -> Int
xRow = Int
xr, xCol :: forall t. Matrix t -> Int
xCol = Int
xc } =
Matrix t
m { irows :: Int
irows = Int
c, icols :: Int
icols = Int
r, xRow :: Int
xRow = Int
xc, xCol :: Int
xCol = Int
xr }
cmat :: (Element t) => Matrix t -> Matrix t
cmat :: forall t. Element t => Matrix t -> Matrix t
cmat Matrix t
m
| forall t. Matrix t -> Bool
rowOrder Matrix t
m = Matrix t
m
| Bool
otherwise = forall t. Element t => MatrixOrder -> Matrix t -> Matrix t
extractAll MatrixOrder
RowMajor Matrix t
m
fmat :: (Element t) => Matrix t -> Matrix t
fmat :: forall t. Element t => Matrix t -> Matrix t
fmat Matrix t
m
| forall t. Matrix t -> Bool
colOrder Matrix t
m = Matrix t
m
| Bool
otherwise = forall t. Element t => MatrixOrder -> Matrix t -> Matrix t
extractAll MatrixOrder
ColumnMajor Matrix t
m
{-# INLINE amatr #-}
amatr :: Storable a => Matrix a -> (f -> IO r) -> (CInt -> CInt -> Ptr a -> f) -> IO r
amatr :: forall a f r.
Storable a =>
Matrix a -> (f -> IO r) -> (CInt -> CInt -> Ptr a -> f) -> IO r
amatr Matrix a
x f -> IO r
f CInt -> CInt -> Ptr a -> f
g = forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
unsafeWith (forall t. Matrix t -> Vector t
xdat Matrix a
x) (f -> IO r
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> CInt -> Ptr a -> f
g CInt
r CInt
c)
where
r :: CInt
r = Int -> CInt
fi (forall t. Matrix t -> Int
rows Matrix a
x)
c :: CInt
c = Int -> CInt
fi (forall t. Matrix t -> Int
cols Matrix a
x)
{-# INLINE amat #-}
amat :: Storable a => Matrix a -> (f -> IO r) -> (CInt -> CInt -> CInt -> CInt -> Ptr a -> f) -> IO r
amat :: forall a f r.
Storable a =>
Matrix a
-> (f -> IO r)
-> (CInt -> CInt -> CInt -> CInt -> Ptr a -> f)
-> IO r
amat Matrix a
x f -> IO r
f CInt -> CInt -> CInt -> CInt -> Ptr a -> f
g = forall a b. Storable a => Vector a -> (Ptr a -> IO b) -> IO b
unsafeWith (forall t. Matrix t -> Vector t
xdat Matrix a
x) (f -> IO r
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> CInt -> CInt -> CInt -> Ptr a -> f
g CInt
r CInt
c CInt
sr CInt
sc)
where
r :: CInt
r = Int -> CInt
fi (forall t. Matrix t -> Int
rows Matrix a
x)
c :: CInt
c = Int -> CInt
fi (forall t. Matrix t -> Int
cols Matrix a
x)
sr :: CInt
sr = Int -> CInt
fi (forall t. Matrix t -> Int
xRow Matrix a
x)
sc :: CInt
sc = Int -> CInt
fi (forall t. Matrix t -> Int
xCol Matrix a
x)
instance Storable t => TransArray (Matrix t)
where
type TransRaw (Matrix t) b = CInt -> CInt -> Ptr t -> b
type Trans (Matrix t) b = CInt -> CInt -> CInt -> CInt -> Ptr t -> b
apply :: forall b r. Matrix t -> (b -> IO r) -> Trans (Matrix t) b -> IO r
apply = forall a f r.
Storable a =>
Matrix a
-> (f -> IO r)
-> (CInt -> CInt -> CInt -> CInt -> Ptr a -> f)
-> IO r
amat
{-# INLINE apply #-}
applyRaw :: forall b r.
Matrix t -> (b -> IO r) -> TransRaw (Matrix t) b -> IO r
applyRaw = forall a f r.
Storable a =>
Matrix a -> (f -> IO r) -> (CInt -> CInt -> Ptr a -> f) -> IO r
amatr
{-# INLINE applyRaw #-}
infixr 1 #
(#) :: TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
c
a # :: forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# b -> IO r
b = forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
apply c
a b -> IO r
b
{-# INLINE (#) #-}
(#!) :: (TransArray c, TransArray c1) => c1 -> c -> Trans c1 (Trans c (IO r)) -> IO r
c1
a #! :: forall c c1 r.
(TransArray c, TransArray c1) =>
c1 -> c -> Trans c1 (Trans c (IO r)) -> IO r
#! c
b = c1
a forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# c
b forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# forall a. a -> a
id
{-# INLINE (#!) #-}
copy :: Element t => MatrixOrder -> Matrix t -> IO (Matrix t)
copy :: forall t. Element t => MatrixOrder -> Matrix t -> IO (Matrix t)
copy MatrixOrder
ord Matrix t
m = forall a.
Element a =>
MatrixOrder
-> Matrix a
-> CInt
-> Vector CInt
-> CInt
-> Vector CInt
-> IO (Matrix a)
extractR MatrixOrder
ord Matrix t
m CInt
0 ([Int] -> Vector CInt
idxs[Int
0,forall t. Matrix t -> Int
rows Matrix t
mforall a. Num a => a -> a -> a
-Int
1]) CInt
0 ([Int] -> Vector CInt
idxs[Int
0,forall t. Matrix t -> Int
cols Matrix t
mforall a. Num a => a -> a -> a
-Int
1])
extractAll :: Element t => MatrixOrder -> Matrix t -> Matrix t
MatrixOrder
ord Matrix t
m = forall a. IO a -> a
unsafePerformIO (forall t. Element t => MatrixOrder -> Matrix t -> IO (Matrix t)
copy MatrixOrder
ord Matrix t
m)
flatten :: Element t => Matrix t -> Vector t
flatten :: forall t. Element t => Matrix t -> Vector t
flatten Matrix t
m
| forall t. Storable t => Matrix t -> Bool
isSlice Matrix t
m Bool -> Bool -> Bool
|| Bool -> Bool
not (forall t. Matrix t -> Bool
rowOrder Matrix t
m) = forall t. Matrix t -> Vector t
xdat (forall t. Element t => MatrixOrder -> Matrix t -> Matrix t
extractAll MatrixOrder
RowMajor Matrix t
m)
| Bool
otherwise = forall t. Matrix t -> Vector t
xdat Matrix t
m
toLists :: (Element t) => Matrix t -> [[t]]
toLists :: forall t. Element t => Matrix t -> [[t]]
toLists = forall a b. (a -> b) -> [a] -> [b]
map forall a. Storable a => Vector a -> [a]
toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Element t => Matrix t -> [Vector t]
toRows
compatdim :: [Int] -> Maybe Int
compatdim :: [Int] -> Maybe Int
compatdim [] = forall a. Maybe a
Nothing
compatdim [Int
a] = forall a. a -> Maybe a
Just Int
a
compatdim (Int
a:Int
b:[Int]
xs)
| Int
aforall a. Eq a => a -> a -> Bool
==Int
b = [Int] -> Maybe Int
compatdim (Int
bforall a. a -> [a] -> [a]
:[Int]
xs)
| Int
aforall a. Eq a => a -> a -> Bool
==Int
1 = [Int] -> Maybe Int
compatdim (Int
bforall a. a -> [a] -> [a]
:[Int]
xs)
| Int
bforall a. Eq a => a -> a -> Bool
==Int
1 = [Int] -> Maybe Int
compatdim (Int
aforall a. a -> [a] -> [a]
:[Int]
xs)
| Bool
otherwise = forall a. Maybe a
Nothing
fromRows :: Element t => [Vector t] -> Matrix t
fromRows :: forall t. Element t => [Vector t] -> Matrix t
fromRows [] = forall t. Storable t => Int -> Int -> Matrix t
emptyM Int
0 Int
0
fromRows [Vector t]
vs = case [Int] -> Maybe Int
compatdim (forall a b. (a -> b) -> [a] -> [b]
map forall t. Storable t => Vector t -> Int
dim [Vector t]
vs) of
Maybe Int
Nothing -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"fromRows expects vectors with equal sizes (or singletons), given: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall a b. (a -> b) -> [a] -> [b]
map forall t. Storable t => Vector t -> Int
dim [Vector t]
vs)
Just Int
0 -> forall t. Storable t => Int -> Int -> Matrix t
emptyM Int
r Int
0
Just Int
c -> forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
RowMajor Int
r Int
c forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Storable t => [Vector t] -> Vector t
vjoin forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall {a}. Element a => Int -> Vector a -> Vector a
adapt Int
c) forall a b. (a -> b) -> a -> b
$ [Vector t]
vs
where
r :: Int
r = forall (t :: * -> *) a. Foldable t => t a -> Int
length [Vector t]
vs
adapt :: Int -> Vector a -> Vector a
adapt Int
c Vector a
v
| Int
c forall a. Eq a => a -> a -> Bool
== Int
0 = forall a. Storable a => [a] -> Vector a
fromList[]
| forall t. Storable t => Vector t -> Int
dim Vector a
v forall a. Eq a => a -> a -> Bool
== Int
c = Vector a
v
| Bool
otherwise = forall a. Element a => a -> Int -> Vector a
constantD (Vector a
vforall t. Storable t => Vector t -> Int -> t
@>Int
0) Int
c
toRows :: Element t => Matrix t -> [Vector t]
toRows :: forall t. Element t => Matrix t -> [Vector t]
toRows Matrix t
m
| forall t. Matrix t -> Bool
rowOrder Matrix t
m = forall a b. (a -> b) -> [a] -> [b]
map Int -> Vector t
sub [Int]
rowRange
| Bool
otherwise = forall a b. (a -> b) -> [a] -> [b]
map Int -> Vector t
ext [Int]
rowRange
where
rowRange :: [Int]
rowRange = [Int
0..forall t. Matrix t -> Int
rows Matrix t
mforall a. Num a => a -> a -> a
-Int
1]
sub :: Int -> Vector t
sub Int
k = forall t. Storable t => Int -> Int -> Vector t -> Vector t
subVector (Int
kforall a. Num a => a -> a -> a
*forall t. Matrix t -> Int
xRow Matrix t
m) (forall t. Matrix t -> Int
cols Matrix t
m) (forall t. Matrix t -> Vector t
xdat Matrix t
m)
ext :: Int -> Vector t
ext Int
k = forall t. Matrix t -> Vector t
xdat forall a b. (a -> b) -> a -> b
$ forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ forall a.
Element a =>
MatrixOrder
-> Matrix a
-> CInt
-> Vector CInt
-> CInt
-> Vector CInt
-> IO (Matrix a)
extractR MatrixOrder
RowMajor Matrix t
m CInt
1 ([Int] -> Vector CInt
idxs[Int
k]) CInt
0 ([Int] -> Vector CInt
idxs[Int
0,forall t. Matrix t -> Int
cols Matrix t
mforall a. Num a => a -> a -> a
-Int
1])
fromColumns :: Element t => [Vector t] -> Matrix t
fromColumns :: forall t. Element t => [Vector t] -> Matrix t
fromColumns [Vector t]
m = forall t. Matrix t -> Matrix t
trans forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Element t => [Vector t] -> Matrix t
fromRows forall a b. (a -> b) -> a -> b
$ [Vector t]
m
toColumns :: Element t => Matrix t -> [Vector t]
toColumns :: forall t. Element t => Matrix t -> [Vector t]
toColumns Matrix t
m = forall t. Element t => Matrix t -> [Vector t]
toRows forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Matrix t -> Matrix t
trans forall a b. (a -> b) -> a -> b
$ Matrix t
m
(@@>) :: Storable t => Matrix t -> (Int,Int) -> t
infixl 9 @@>
m :: Matrix t
m@Matrix {irows :: forall t. Matrix t -> Int
irows = Int
r, icols :: forall t. Matrix t -> Int
icols = Int
c} @@> :: forall t. Storable t => Matrix t -> (Int, Int) -> t
@@> (Int
i,Int
j)
| Int
iforall a. Ord a => a -> a -> Bool
<Int
0 Bool -> Bool -> Bool
|| Int
iforall a. Ord a => a -> a -> Bool
>=Int
r Bool -> Bool -> Bool
|| Int
jforall a. Ord a => a -> a -> Bool
<Int
0 Bool -> Bool -> Bool
|| Int
jforall a. Ord a => a -> a -> Bool
>=Int
c = forall a. HasCallStack => String -> a
error String
"matrix indexing out of range"
| Bool
otherwise = forall t. Storable t => Matrix t -> Int -> Int -> t
atM' Matrix t
m Int
i Int
j
{-# INLINE (@@>) #-}
atM' :: Storable t => Matrix t -> Int -> Int -> t
atM' :: forall t. Storable t => Matrix t -> Int -> Int -> t
atM' Matrix t
m Int
i Int
j = forall t. Matrix t -> Vector t
xdat Matrix t
m forall t. Storable t => Vector t -> Int -> t
`at'` (Int
i forall a. Num a => a -> a -> a
* (forall t. Matrix t -> Int
xRow Matrix t
m) forall a. Num a => a -> a -> a
+ Int
j forall a. Num a => a -> a -> a
* (forall t. Matrix t -> Int
xCol Matrix t
m))
{-# INLINE atM' #-}
matrixFromVector :: Storable t => MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector :: forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
_ Int
1 Int
_ v :: Vector t
v@(forall t. Storable t => Vector t -> Int
dim->Int
d) = Matrix { irows :: Int
irows = Int
1, icols :: Int
icols = Int
d, xdat :: Vector t
xdat = Vector t
v, xRow :: Int
xRow = Int
d, xCol :: Int
xCol = Int
1 }
matrixFromVector MatrixOrder
_ Int
_ Int
1 v :: Vector t
v@(forall t. Storable t => Vector t -> Int
dim->Int
d) = Matrix { irows :: Int
irows = Int
d, icols :: Int
icols = Int
1, xdat :: Vector t
xdat = Vector t
v, xRow :: Int
xRow = Int
1, xCol :: Int
xCol = Int
d }
matrixFromVector MatrixOrder
o Int
r Int
c Vector t
v
| Int
r forall a. Num a => a -> a -> a
* Int
c forall a. Eq a => a -> a -> Bool
== forall t. Storable t => Vector t -> Int
dim Vector t
v = Matrix t
m
| Bool
otherwise = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"can't reshape vector dim = "forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall t. Storable t => Vector t -> Int
dim Vector t
v)forall a. [a] -> [a] -> [a]
++String
" to matrix " forall a. [a] -> [a] -> [a]
++ forall t. Matrix t -> String
shSize Matrix t
m
where
m :: Matrix t
m | MatrixOrder
o forall a. Eq a => a -> a -> Bool
== MatrixOrder
RowMajor = Matrix { irows :: Int
irows = Int
r, icols :: Int
icols = Int
c, xdat :: Vector t
xdat = Vector t
v, xRow :: Int
xRow = Int
c, xCol :: Int
xCol = Int
1 }
| Bool
otherwise = Matrix { irows :: Int
irows = Int
r, icols :: Int
icols = Int
c, xdat :: Vector t
xdat = Vector t
v, xRow :: Int
xRow = Int
1, xCol :: Int
xCol = Int
r }
createMatrix :: (Storable a) => MatrixOrder -> Int -> Int -> IO (Matrix a)
createMatrix :: forall a. Storable a => MatrixOrder -> Int -> Int -> IO (Matrix a)
createMatrix MatrixOrder
ord Int
r Int
c = do
Vector a
p <- forall a. Storable a => Int -> IO (Vector a)
createVector (Int
rforall a. Num a => a -> a -> a
*Int
c)
forall (m :: * -> *) a. Monad m => a -> m a
return (forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
ord Int
r Int
c Vector a
p)
reshape :: Storable t => Int -> Vector t -> Matrix t
reshape :: forall t. Storable t => Int -> Vector t -> Matrix t
reshape Int
0 Vector t
v = forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
RowMajor Int
0 Int
0 Vector t
v
reshape Int
c Vector t
v = forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
RowMajor (forall t. Storable t => Vector t -> Int
dim Vector t
v forall a. Integral a => a -> a -> a
`div` Int
c) Int
c Vector t
v
liftMatrix :: (Element a, Element b) => (Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix :: forall a b.
(Element a, Element b) =>
(Vector a -> Vector b) -> Matrix a -> Matrix b
liftMatrix Vector a -> Vector b
f m :: Matrix a
m@Matrix { irows :: forall t. Matrix t -> Int
irows = Int
r, icols :: forall t. Matrix t -> Int
icols = Int
c, xdat :: forall t. Matrix t -> Vector t
xdat = Vector a
d}
| forall t. Storable t => Matrix t -> Bool
isSlice Matrix a
m = forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
RowMajor Int
r Int
c (Vector a -> Vector b
f (forall t. Element t => Matrix t -> Vector t
flatten Matrix a
m))
| Bool
otherwise = forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector (forall t. Matrix t -> MatrixOrder
orderOf Matrix a
m) Int
r Int
c (Vector a -> Vector b
f Vector a
d)
liftMatrix2 :: (Element t, Element a, Element b) => (Vector a -> Vector b -> Vector t) -> Matrix a -> Matrix b -> Matrix t
liftMatrix2 :: 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 b -> Vector t
f m1 :: Matrix a
m1@(forall t. Matrix t -> (Int, Int)
size->(Int
r,Int
c)) Matrix b
m2
| (Int
r,Int
c)forall a. Eq a => a -> a -> Bool
/=forall t. Matrix t -> (Int, Int)
size Matrix b
m2 = forall a. HasCallStack => String -> a
error String
"nonconformant matrices in liftMatrix2"
| forall t. Matrix t -> Bool
rowOrder Matrix a
m1 = forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
RowMajor Int
r Int
c (Vector a -> Vector b -> Vector t
f (forall t. Element t => Matrix t -> Vector t
flatten Matrix a
m1) (forall t. Element t => Matrix t -> Vector t
flatten Matrix b
m2))
| Bool
otherwise = forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
ColumnMajor Int
r Int
c (Vector a -> Vector b -> Vector t
f (forall t. Element t => Matrix t -> Vector t
flatten (forall t. Matrix t -> Matrix t
trans Matrix a
m1)) (forall t. Element t => Matrix t -> Vector t
flatten (forall t. Matrix t -> Matrix t
trans Matrix b
m2)))
class (Storable a) => Element a where
constantD :: a -> Int -> Vector a
:: MatrixOrder -> Matrix a -> CInt -> Vector CInt -> CInt -> Vector CInt -> IO (Matrix a)
setRect :: Int -> Int -> Matrix a -> Matrix a -> IO ()
sortI :: Ord a => Vector a -> Vector CInt
sortV :: Ord a => Vector a -> Vector a
compareV :: Ord a => Vector a -> Vector a -> Vector CInt
selectV :: Vector CInt -> Vector a -> Vector a -> Vector a -> Vector a
remapM :: Matrix CInt -> Matrix CInt -> Matrix a -> Matrix a
rowOp :: Int -> a -> Int -> Int -> Int -> Int -> Matrix a -> IO ()
gemm :: Vector a -> Matrix a -> Matrix a -> Matrix a -> IO ()
reorderV :: Vector CInt-> Vector CInt-> Vector a -> Vector a
instance Element Float where
constantD :: Float -> Int -> Vector Float
constantD = forall a1 a.
(Storable a1, Storable a) =>
(Ptr a1 -> CInt -> Ptr a -> IO CInt) -> a1 -> Int -> Vector a
constantAux TConst Float
cconstantF
extractR :: MatrixOrder
-> Matrix Float
-> CInt
-> Vector CInt
-> CInt
-> Vector CInt
-> IO (Matrix Float)
extractR = forall t3 t2 c a t1 t.
(Eq t3, Eq t2, TransArray c, Storable a, Storable t1, Storable t,
Num t3, Num t2, Integral t1, Integral t) =>
(t3
-> t2
-> CInt
-> Ptr t1
-> CInt
-> Ptr t
-> Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt))
-> MatrixOrder
-> c
-> t3
-> Vector t1
-> t2
-> Vector t
-> IO (Matrix a)
extractAux Extr Float
c_extractF
setRect :: Int -> Int -> Matrix Float -> Matrix Float -> IO ()
setRect = forall c1 c.
(TransArray c1, TransArray c) =>
(CInt -> CInt -> Trans c1 (Trans c (IO CInt)))
-> Int -> Int -> c1 -> c -> IO ()
setRectAux SetRect Float
c_setRectF
sortI :: Ord Float => Vector Float -> Vector CInt
sortI = Vector Float -> Vector CInt
sortIdxF
sortV :: Ord Float => Vector Float -> Vector Float
sortV = Vector Float -> Vector Float
sortValF
compareV :: Ord Float => Vector Float -> Vector Float -> Vector CInt
compareV = Vector Float -> Vector Float -> Vector CInt
compareF
selectV :: Vector CInt
-> Vector Float -> Vector Float -> Vector Float -> Vector Float
selectV = Vector CInt
-> Vector Float -> Vector Float -> Vector Float -> Vector Float
selectF
remapM :: Matrix CInt -> Matrix CInt -> Matrix Float -> Matrix Float
remapM = Matrix CInt -> Matrix CInt -> Matrix Float -> Matrix Float
remapF
rowOp :: Int -> Float -> Int -> Int -> Int -> Int -> Matrix Float -> IO ()
rowOp = forall c a.
(TransArray c, Storable a) =>
(CInt
-> Ptr a -> CInt -> CInt -> CInt -> CInt -> Trans c (IO CInt))
-> Int -> a -> Int -> Int -> Int -> Int -> c -> IO ()
rowOpAux RowOp Float
c_rowOpF
gemm :: Vector Float
-> Matrix Float -> Matrix Float -> Matrix Float -> IO ()
gemm = forall c1 c c2 c3.
(TransArray c1, TransArray c, TransArray c2, TransArray c3) =>
Trans c3 (Trans c2 (Trans c1 (Trans c (IO CInt))))
-> c3 -> c2 -> c1 -> c -> IO ()
gemmg Tgemm Float
c_gemmF
reorderV :: Vector CInt -> Vector CInt -> Vector Float -> Vector Float
reorderV = forall c t a1 t1 a.
(TransArray c, Storable t, Storable a1, Storable t1, Storable a) =>
(CInt
-> Ptr a
-> CInt
-> Ptr t1
-> Trans c (CInt -> Ptr t -> CInt -> Ptr a1 -> IO CInt))
-> Vector t1 -> c -> Vector t -> Vector a1
reorderAux Reorder Float
c_reorderF
instance Element Double where
constantD :: Double -> Int -> Vector Double
constantD = forall a1 a.
(Storable a1, Storable a) =>
(Ptr a1 -> CInt -> Ptr a -> IO CInt) -> a1 -> Int -> Vector a
constantAux TConst Double
cconstantR
extractR :: MatrixOrder
-> Matrix Double
-> CInt
-> Vector CInt
-> CInt
-> Vector CInt
-> IO (Matrix Double)
extractR = forall t3 t2 c a t1 t.
(Eq t3, Eq t2, TransArray c, Storable a, Storable t1, Storable t,
Num t3, Num t2, Integral t1, Integral t) =>
(t3
-> t2
-> CInt
-> Ptr t1
-> CInt
-> Ptr t
-> Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt))
-> MatrixOrder
-> c
-> t3
-> Vector t1
-> t2
-> Vector t
-> IO (Matrix a)
extractAux Extr Double
c_extractD
setRect :: Int -> Int -> Matrix Double -> Matrix Double -> IO ()
setRect = forall c1 c.
(TransArray c1, TransArray c) =>
(CInt -> CInt -> Trans c1 (Trans c (IO CInt)))
-> Int -> Int -> c1 -> c -> IO ()
setRectAux SetRect Double
c_setRectD
sortI :: Ord Double => Vector Double -> Vector CInt
sortI = Vector Double -> Vector CInt
sortIdxD
sortV :: Ord Double => Vector Double -> Vector Double
sortV = Vector Double -> Vector Double
sortValD
compareV :: Ord Double => Vector Double -> Vector Double -> Vector CInt
compareV = Vector Double -> Vector Double -> Vector CInt
compareD
selectV :: Vector CInt
-> Vector Double -> Vector Double -> Vector Double -> Vector Double
selectV = Vector CInt
-> Vector Double -> Vector Double -> Vector Double -> Vector Double
selectD
remapM :: Matrix CInt -> Matrix CInt -> Matrix Double -> Matrix Double
remapM = Matrix CInt -> Matrix CInt -> Matrix Double -> Matrix Double
remapD
rowOp :: Int -> Double -> Int -> Int -> Int -> Int -> Matrix Double -> IO ()
rowOp = forall c a.
(TransArray c, Storable a) =>
(CInt
-> Ptr a -> CInt -> CInt -> CInt -> CInt -> Trans c (IO CInt))
-> Int -> a -> Int -> Int -> Int -> Int -> c -> IO ()
rowOpAux RowOp Double
c_rowOpD
gemm :: Vector Double
-> Matrix Double -> Matrix Double -> Matrix Double -> IO ()
gemm = forall c1 c c2 c3.
(TransArray c1, TransArray c, TransArray c2, TransArray c3) =>
Trans c3 (Trans c2 (Trans c1 (Trans c (IO CInt))))
-> c3 -> c2 -> c1 -> c -> IO ()
gemmg Tgemm Double
c_gemmD
reorderV :: Vector CInt -> Vector CInt -> Vector Double -> Vector Double
reorderV = forall c t a1 t1 a.
(TransArray c, Storable t, Storable a1, Storable t1, Storable a) =>
(CInt
-> Ptr a
-> CInt
-> Ptr t1
-> Trans c (CInt -> Ptr t -> CInt -> Ptr a1 -> IO CInt))
-> Vector t1 -> c -> Vector t -> Vector a1
reorderAux Reorder Double
c_reorderD
instance Element (Complex Float) where
constantD :: Complex Float -> Int -> Vector (Complex Float)
constantD = forall a1 a.
(Storable a1, Storable a) =>
(Ptr a1 -> CInt -> Ptr a -> IO CInt) -> a1 -> Int -> Vector a
constantAux TConst (Complex Float)
cconstantQ
extractR :: MatrixOrder
-> Matrix (Complex Float)
-> CInt
-> Vector CInt
-> CInt
-> Vector CInt
-> IO (Matrix (Complex Float))
extractR = forall t3 t2 c a t1 t.
(Eq t3, Eq t2, TransArray c, Storable a, Storable t1, Storable t,
Num t3, Num t2, Integral t1, Integral t) =>
(t3
-> t2
-> CInt
-> Ptr t1
-> CInt
-> Ptr t
-> Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt))
-> MatrixOrder
-> c
-> t3
-> Vector t1
-> t2
-> Vector t
-> IO (Matrix a)
extractAux Extr (Complex Float)
c_extractQ
setRect :: Int
-> Int -> Matrix (Complex Float) -> Matrix (Complex Float) -> IO ()
setRect = forall c1 c.
(TransArray c1, TransArray c) =>
(CInt -> CInt -> Trans c1 (Trans c (IO CInt)))
-> Int -> Int -> c1 -> c -> IO ()
setRectAux SetRect (Complex Float)
c_setRectQ
sortI :: Ord (Complex Float) => Vector (Complex Float) -> Vector CInt
sortI = forall a. HasCallStack => a
undefined
sortV :: Ord (Complex Float) =>
Vector (Complex Float) -> Vector (Complex Float)
sortV = forall a. HasCallStack => a
undefined
compareV :: Ord (Complex Float) =>
Vector (Complex Float) -> Vector (Complex Float) -> Vector CInt
compareV = forall a. HasCallStack => a
undefined
selectV :: Vector CInt
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
selectV = Vector CInt
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
selectQ
remapM :: Matrix CInt
-> Matrix CInt -> Matrix (Complex Float) -> Matrix (Complex Float)
remapM = Matrix CInt
-> Matrix CInt -> Matrix (Complex Float) -> Matrix (Complex Float)
remapQ
rowOp :: Int
-> Complex Float
-> Int
-> Int
-> Int
-> Int
-> Matrix (Complex Float)
-> IO ()
rowOp = forall c a.
(TransArray c, Storable a) =>
(CInt
-> Ptr a -> CInt -> CInt -> CInt -> CInt -> Trans c (IO CInt))
-> Int -> a -> Int -> Int -> Int -> Int -> c -> IO ()
rowOpAux RowOp (Complex Float)
c_rowOpQ
gemm :: Vector (Complex Float)
-> Matrix (Complex Float)
-> Matrix (Complex Float)
-> Matrix (Complex Float)
-> IO ()
gemm = forall c1 c c2 c3.
(TransArray c1, TransArray c, TransArray c2, TransArray c3) =>
Trans c3 (Trans c2 (Trans c1 (Trans c (IO CInt))))
-> c3 -> c2 -> c1 -> c -> IO ()
gemmg Tgemm (Complex Float)
c_gemmQ
reorderV :: Vector CInt
-> Vector CInt -> Vector (Complex Float) -> Vector (Complex Float)
reorderV = forall c t a1 t1 a.
(TransArray c, Storable t, Storable a1, Storable t1, Storable a) =>
(CInt
-> Ptr a
-> CInt
-> Ptr t1
-> Trans c (CInt -> Ptr t -> CInt -> Ptr a1 -> IO CInt))
-> Vector t1 -> c -> Vector t -> Vector a1
reorderAux Reorder (Complex Float)
c_reorderQ
instance Element (Complex Double) where
constantD :: Complex Double -> Int -> Vector (Complex Double)
constantD = forall a1 a.
(Storable a1, Storable a) =>
(Ptr a1 -> CInt -> Ptr a -> IO CInt) -> a1 -> Int -> Vector a
constantAux TConst (Complex Double)
cconstantC
extractR :: MatrixOrder
-> Matrix (Complex Double)
-> CInt
-> Vector CInt
-> CInt
-> Vector CInt
-> IO (Matrix (Complex Double))
extractR = forall t3 t2 c a t1 t.
(Eq t3, Eq t2, TransArray c, Storable a, Storable t1, Storable t,
Num t3, Num t2, Integral t1, Integral t) =>
(t3
-> t2
-> CInt
-> Ptr t1
-> CInt
-> Ptr t
-> Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt))
-> MatrixOrder
-> c
-> t3
-> Vector t1
-> t2
-> Vector t
-> IO (Matrix a)
extractAux Extr (Complex Double)
c_extractC
setRect :: Int
-> Int
-> Matrix (Complex Double)
-> Matrix (Complex Double)
-> IO ()
setRect = forall c1 c.
(TransArray c1, TransArray c) =>
(CInt -> CInt -> Trans c1 (Trans c (IO CInt)))
-> Int -> Int -> c1 -> c -> IO ()
setRectAux SetRect (Complex Double)
c_setRectC
sortI :: Ord (Complex Double) => Vector (Complex Double) -> Vector CInt
sortI = forall a. HasCallStack => a
undefined
sortV :: Ord (Complex Double) =>
Vector (Complex Double) -> Vector (Complex Double)
sortV = forall a. HasCallStack => a
undefined
compareV :: Ord (Complex Double) =>
Vector (Complex Double) -> Vector (Complex Double) -> Vector CInt
compareV = forall a. HasCallStack => a
undefined
selectV :: Vector CInt
-> Vector (Complex Double)
-> Vector (Complex Double)
-> Vector (Complex Double)
-> Vector (Complex Double)
selectV = Vector CInt
-> Vector (Complex Double)
-> Vector (Complex Double)
-> Vector (Complex Double)
-> Vector (Complex Double)
selectC
remapM :: Matrix CInt
-> Matrix CInt
-> Matrix (Complex Double)
-> Matrix (Complex Double)
remapM = Matrix CInt
-> Matrix CInt
-> Matrix (Complex Double)
-> Matrix (Complex Double)
remapC
rowOp :: Int
-> Complex Double
-> Int
-> Int
-> Int
-> Int
-> Matrix (Complex Double)
-> IO ()
rowOp = forall c a.
(TransArray c, Storable a) =>
(CInt
-> Ptr a -> CInt -> CInt -> CInt -> CInt -> Trans c (IO CInt))
-> Int -> a -> Int -> Int -> Int -> Int -> c -> IO ()
rowOpAux RowOp (Complex Double)
c_rowOpC
gemm :: Vector (Complex Double)
-> Matrix (Complex Double)
-> Matrix (Complex Double)
-> Matrix (Complex Double)
-> IO ()
gemm = forall c1 c c2 c3.
(TransArray c1, TransArray c, TransArray c2, TransArray c3) =>
Trans c3 (Trans c2 (Trans c1 (Trans c (IO CInt))))
-> c3 -> c2 -> c1 -> c -> IO ()
gemmg Tgemm (Complex Double)
c_gemmC
reorderV :: Vector CInt
-> Vector CInt
-> Vector (Complex Double)
-> Vector (Complex Double)
reorderV = forall c t a1 t1 a.
(TransArray c, Storable t, Storable a1, Storable t1, Storable a) =>
(CInt
-> Ptr a
-> CInt
-> Ptr t1
-> Trans c (CInt -> Ptr t -> CInt -> Ptr a1 -> IO CInt))
-> Vector t1 -> c -> Vector t -> Vector a1
reorderAux Reorder (Complex Double)
c_reorderC
instance Element (CInt) where
constantD :: CInt -> Int -> Vector CInt
constantD = forall a1 a.
(Storable a1, Storable a) =>
(Ptr a1 -> CInt -> Ptr a -> IO CInt) -> a1 -> Int -> Vector a
constantAux TConst CInt
cconstantI
extractR :: MatrixOrder
-> Matrix CInt
-> CInt
-> Vector CInt
-> CInt
-> Vector CInt
-> IO (Matrix CInt)
extractR = forall t3 t2 c a t1 t.
(Eq t3, Eq t2, TransArray c, Storable a, Storable t1, Storable t,
Num t3, Num t2, Integral t1, Integral t) =>
(t3
-> t2
-> CInt
-> Ptr t1
-> CInt
-> Ptr t
-> Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt))
-> MatrixOrder
-> c
-> t3
-> Vector t1
-> t2
-> Vector t
-> IO (Matrix a)
extractAux Extr CInt
c_extractI
setRect :: Int -> Int -> Matrix CInt -> Matrix CInt -> IO ()
setRect = forall c1 c.
(TransArray c1, TransArray c) =>
(CInt -> CInt -> Trans c1 (Trans c (IO CInt)))
-> Int -> Int -> c1 -> c -> IO ()
setRectAux SetRect CInt
c_setRectI
sortI :: Ord CInt => Vector CInt -> Vector CInt
sortI = Vector CInt -> Vector CInt
sortIdxI
sortV :: Ord CInt => Vector CInt -> Vector CInt
sortV = Vector CInt -> Vector CInt
sortValI
compareV :: Ord CInt => Vector CInt -> Vector CInt -> Vector CInt
compareV = Vector CInt -> Vector CInt -> Vector CInt
compareI
selectV :: Vector CInt
-> Vector CInt -> Vector CInt -> Vector CInt -> Vector CInt
selectV = Vector CInt
-> Vector CInt -> Vector CInt -> Vector CInt -> Vector CInt
selectI
remapM :: Matrix CInt -> Matrix CInt -> Matrix CInt -> Matrix CInt
remapM = Matrix CInt -> Matrix CInt -> Matrix CInt -> Matrix CInt
remapI
rowOp :: Int -> CInt -> Int -> Int -> Int -> Int -> Matrix CInt -> IO ()
rowOp = forall c a.
(TransArray c, Storable a) =>
(CInt
-> Ptr a -> CInt -> CInt -> CInt -> CInt -> Trans c (IO CInt))
-> Int -> a -> Int -> Int -> Int -> Int -> c -> IO ()
rowOpAux RowOp CInt
c_rowOpI
gemm :: Vector CInt -> Matrix CInt -> Matrix CInt -> Matrix CInt -> IO ()
gemm = forall c1 c c2 c3.
(TransArray c1, TransArray c, TransArray c2, TransArray c3) =>
Trans c3 (Trans c2 (Trans c1 (Trans c (IO CInt))))
-> c3 -> c2 -> c1 -> c -> IO ()
gemmg Tgemm CInt
c_gemmI
reorderV :: Vector CInt -> Vector CInt -> Vector CInt -> Vector CInt
reorderV = forall c t a1 t1 a.
(TransArray c, Storable t, Storable a1, Storable t1, Storable a) =>
(CInt
-> Ptr a
-> CInt
-> Ptr t1
-> Trans c (CInt -> Ptr t -> CInt -> Ptr a1 -> IO CInt))
-> Vector t1 -> c -> Vector t -> Vector a1
reorderAux Reorder CInt
c_reorderI
instance Element Z where
constantD :: Z -> Int -> Vector Z
constantD = forall a1 a.
(Storable a1, Storable a) =>
(Ptr a1 -> CInt -> Ptr a -> IO CInt) -> a1 -> Int -> Vector a
constantAux TConst Z
cconstantL
extractR :: MatrixOrder
-> Matrix Z
-> CInt
-> Vector CInt
-> CInt
-> Vector CInt
-> IO (Matrix Z)
extractR = forall t3 t2 c a t1 t.
(Eq t3, Eq t2, TransArray c, Storable a, Storable t1, Storable t,
Num t3, Num t2, Integral t1, Integral t) =>
(t3
-> t2
-> CInt
-> Ptr t1
-> CInt
-> Ptr t
-> Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt))
-> MatrixOrder
-> c
-> t3
-> Vector t1
-> t2
-> Vector t
-> IO (Matrix a)
extractAux Extr Z
c_extractL
setRect :: Int -> Int -> Matrix Z -> Matrix Z -> IO ()
setRect = forall c1 c.
(TransArray c1, TransArray c) =>
(CInt -> CInt -> Trans c1 (Trans c (IO CInt)))
-> Int -> Int -> c1 -> c -> IO ()
setRectAux SetRect Z
c_setRectL
sortI :: Ord Z => Vector Z -> Vector CInt
sortI = Vector Z -> Vector CInt
sortIdxL
sortV :: Ord Z => Vector Z -> Vector Z
sortV = Vector Z -> Vector Z
sortValL
compareV :: Ord Z => Vector Z -> Vector Z -> Vector CInt
compareV = Vector Z -> Vector Z -> Vector CInt
compareL
selectV :: Vector CInt -> Vector Z -> Vector Z -> Vector Z -> Vector Z
selectV = Vector CInt -> Vector Z -> Vector Z -> Vector Z -> Vector Z
selectL
remapM :: Matrix CInt -> Matrix CInt -> Matrix Z -> Matrix Z
remapM = Matrix CInt -> Matrix CInt -> Matrix Z -> Matrix Z
remapL
rowOp :: Int -> Z -> Int -> Int -> Int -> Int -> Matrix Z -> IO ()
rowOp = forall c a.
(TransArray c, Storable a) =>
(CInt
-> Ptr a -> CInt -> CInt -> CInt -> CInt -> Trans c (IO CInt))
-> Int -> a -> Int -> Int -> Int -> Int -> c -> IO ()
rowOpAux RowOp Z
c_rowOpL
gemm :: Vector Z -> Matrix Z -> Matrix Z -> Matrix Z -> IO ()
gemm = forall c1 c c2 c3.
(TransArray c1, TransArray c, TransArray c2, TransArray c3) =>
Trans c3 (Trans c2 (Trans c1 (Trans c (IO CInt))))
-> c3 -> c2 -> c1 -> c -> IO ()
gemmg Tgemm Z
c_gemmL
reorderV :: Vector CInt -> Vector CInt -> Vector Z -> Vector Z
reorderV = forall c t a1 t1 a.
(TransArray c, Storable t, Storable a1, Storable t1, Storable a) =>
(CInt
-> Ptr a
-> CInt
-> Ptr t1
-> Trans c (CInt -> Ptr t -> CInt -> Ptr a1 -> IO CInt))
-> Vector t1 -> c -> Vector t -> Vector a1
reorderAux Reorder Z
c_reorderL
subMatrix :: Element a
=> (Int,Int)
-> (Int,Int)
-> Matrix a
-> Matrix a
subMatrix :: forall a.
Element a =>
(Int, Int) -> (Int, Int) -> Matrix a -> Matrix a
subMatrix (Int
r0,Int
c0) (Int
rt,Int
ct) Matrix a
m
| Int
rt forall a. Ord a => a -> a -> Bool
<= Int
0 Bool -> Bool -> Bool
|| Int
ct forall a. Ord a => a -> a -> Bool
<= Int
0 = forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
RowMajor (forall a. Ord a => a -> a -> a
max Int
0 Int
rt) (forall a. Ord a => a -> a -> a
max Int
0 Int
ct) (forall a. Storable a => [a] -> Vector a
fromList [])
| Int
0 forall a. Ord a => a -> a -> Bool
<= Int
r0 Bool -> Bool -> Bool
&& Int
0 forall a. Ord a => a -> a -> Bool
<= Int
rt Bool -> Bool -> Bool
&& Int
r0forall a. Num a => a -> a -> a
+Int
rt forall a. Ord a => a -> a -> Bool
<= forall t. Matrix t -> Int
rows Matrix a
m Bool -> Bool -> Bool
&&
Int
0 forall a. Ord a => a -> a -> Bool
<= Int
c0 Bool -> Bool -> Bool
&& Int
0 forall a. Ord a => a -> a -> Bool
<= Int
ct Bool -> Bool -> Bool
&& Int
c0forall a. Num a => a -> a -> a
+Int
ct forall a. Ord a => a -> a -> Bool
<= forall t. Matrix t -> Int
cols Matrix a
m = Matrix a
res
| Bool
otherwise = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"wrong subMatrix "forall a. [a] -> [a] -> [a]
++forall a. Show a => a -> String
show ((Int
r0,Int
c0),(Int
rt,Int
ct))forall a. [a] -> [a] -> [a]
++String
" of "forall a. [a] -> [a] -> [a]
++forall t. Matrix t -> String
shSize Matrix a
m
where
p :: Int
p = Int
r0 forall a. Num a => a -> a -> a
* forall t. Matrix t -> Int
xRow Matrix a
m forall a. Num a => a -> a -> a
+ Int
c0 forall a. Num a => a -> a -> a
* forall t. Matrix t -> Int
xCol Matrix a
m
tot :: Int
tot | forall t. Matrix t -> Bool
rowOrder Matrix a
m = Int
ct forall a. Num a => a -> a -> a
+ (Int
rtforall a. Num a => a -> a -> a
-Int
1) forall a. Num a => a -> a -> a
* forall t. Matrix t -> Int
xRow Matrix a
m
| Bool
otherwise = Int
rt forall a. Num a => a -> a -> a
+ (Int
ctforall a. Num a => a -> a -> a
-Int
1) forall a. Num a => a -> a -> a
* forall t. Matrix t -> Int
xCol Matrix a
m
res :: Matrix a
res = Matrix a
m { irows :: Int
irows = Int
rt, icols :: Int
icols = Int
ct, xdat :: Vector a
xdat = forall t. Storable t => Int -> Int -> Vector t -> Vector t
subVector Int
p Int
tot (forall t. Matrix t -> Vector t
xdat Matrix a
m) }
maxZ :: (Num t1, Ord t1, Foldable t) => t t1 -> t1
maxZ :: forall t1 (t :: * -> *). (Num t1, Ord t1, Foldable t) => t t1 -> t1
maxZ t t1
xs = if forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum t t1
xs forall a. Eq a => a -> a -> Bool
== t1
0 then t1
0 else forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum t t1
xs
conformMs :: Element t => [Matrix t] -> [Matrix t]
conformMs :: forall t. Element t => [Matrix t] -> [Matrix t]
conformMs [Matrix t]
ms = forall a b. (a -> b) -> [a] -> [b]
map (forall t. Element t => (Int, Int) -> Matrix t -> Matrix t
conformMTo (Int
r,Int
c)) [Matrix t]
ms
where
r :: Int
r = forall t1 (t :: * -> *). (Num t1, Ord t1, Foldable t) => t t1 -> t1
maxZ (forall a b. (a -> b) -> [a] -> [b]
map forall t. Matrix t -> Int
rows [Matrix t]
ms)
c :: Int
c = forall t1 (t :: * -> *). (Num t1, Ord t1, Foldable t) => t t1 -> t1
maxZ (forall a b. (a -> b) -> [a] -> [b]
map forall t. Matrix t -> Int
cols [Matrix t]
ms)
conformVs :: Element t => [Vector t] -> [Vector t]
conformVs :: forall t. Element t => [Vector t] -> [Vector t]
conformVs [Vector t]
vs = forall a b. (a -> b) -> [a] -> [b]
map (forall {a}. Element a => Int -> Vector a -> Vector a
conformVTo Int
n) [Vector t]
vs
where
n :: Int
n = forall t1 (t :: * -> *). (Num t1, Ord t1, Foldable t) => t t1 -> t1
maxZ (forall a b. (a -> b) -> [a] -> [b]
map forall t. Storable t => Vector t -> Int
dim [Vector t]
vs)
conformMTo :: Element t => (Int, Int) -> Matrix t -> Matrix t
conformMTo :: forall t. Element t => (Int, Int) -> Matrix t -> Matrix t
conformMTo (Int
r,Int
c) Matrix t
m
| forall t. Matrix t -> (Int, Int)
size Matrix t
m forall a. Eq a => a -> a -> Bool
== (Int
r,Int
c) = Matrix t
m
| forall t. Matrix t -> (Int, Int)
size Matrix t
m forall a. Eq a => a -> a -> Bool
== (Int
1,Int
1) = forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
RowMajor Int
r Int
c (forall a. Element a => a -> Int -> Vector a
constantD (Matrix t
mforall t. Storable t => Matrix t -> (Int, Int) -> t
@@>(Int
0,Int
0)) (Int
rforall a. Num a => a -> a -> a
*Int
c))
| forall t. Matrix t -> (Int, Int)
size Matrix t
m forall a. Eq a => a -> a -> Bool
== (Int
r,Int
1) = forall t. Element t => Int -> Matrix t -> Matrix t
repCols Int
c Matrix t
m
| forall t. Matrix t -> (Int, Int)
size Matrix t
m forall a. Eq a => a -> a -> Bool
== (Int
1,Int
c) = forall t. Element t => Int -> Matrix t -> Matrix t
repRows Int
r Matrix t
m
| Bool
otherwise = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"matrix " forall a. [a] -> [a] -> [a]
++ forall t. Matrix t -> String
shSize Matrix t
m forall a. [a] -> [a] -> [a]
++ String
" cannot be expanded to " forall a. [a] -> [a] -> [a]
++ forall a a1. (Show a, Show a1) => (a1, a) -> String
shDim (Int
r,Int
c)
conformVTo :: Element t => Int -> Vector t -> Vector t
conformVTo :: forall {a}. Element a => Int -> Vector a -> Vector a
conformVTo Int
n Vector t
v
| forall t. Storable t => Vector t -> Int
dim Vector t
v forall a. Eq a => a -> a -> Bool
== Int
n = Vector t
v
| forall t. Storable t => Vector t -> Int
dim Vector t
v forall a. Eq a => a -> a -> Bool
== Int
1 = forall a. Element a => a -> Int -> Vector a
constantD (Vector t
vforall t. Storable t => Vector t -> Int -> t
@>Int
0) Int
n
| Bool
otherwise = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"vector of dim=" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall t. Storable t => Vector t -> Int
dim Vector t
v) forall a. [a] -> [a] -> [a]
++ String
" cannot be expanded to dim=" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
n
repRows :: Element t => Int -> Matrix t -> Matrix t
repRows :: forall t. Element t => Int -> Matrix t -> Matrix t
repRows Int
n Matrix t
x = forall t. Element t => [Vector t] -> Matrix t
fromRows (forall a. Int -> a -> [a]
replicate Int
n (forall t. Element t => Matrix t -> Vector t
flatten Matrix t
x))
repCols :: Element t => Int -> Matrix t -> Matrix t
repCols :: forall t. Element t => Int -> Matrix t -> Matrix t
repCols Int
n Matrix t
x = forall t. Element t => [Vector t] -> Matrix t
fromColumns (forall a. Int -> a -> [a]
replicate Int
n (forall t. Element t => Matrix t -> Vector t
flatten Matrix t
x))
shSize :: Matrix t -> [Char]
shSize :: forall t. Matrix t -> String
shSize = forall a a1. (Show a, Show a1) => (a1, a) -> String
shDim forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Matrix t -> (Int, Int)
size
shDim :: (Show a, Show a1) => (a1, a) -> [Char]
shDim :: forall a a1. (Show a, Show a1) => (a1, a) -> String
shDim (a1
r,a
c) = String
"(" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a1
r forall a. [a] -> [a] -> [a]
++String
"x"forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
c forall a. [a] -> [a] -> [a]
++String
")"
emptyM :: Storable t => Int -> Int -> Matrix t
emptyM :: forall t. Storable t => Int -> Int -> Matrix t
emptyM Int
r Int
c = forall t.
Storable t =>
MatrixOrder -> Int -> Int -> Vector t -> Matrix t
matrixFromVector MatrixOrder
RowMajor Int
r Int
c (forall a. Storable a => [a] -> Vector a
fromList[])
instance (Storable t, NFData t) => NFData (Matrix t)
where
rnf :: Matrix t -> ()
rnf Matrix t
m | Int
d forall a. Ord a => a -> a -> Bool
> Int
0 = forall a. NFData a => a -> ()
rnf (Vector t
v forall t. Storable t => Vector t -> Int -> t
@> Int
0)
| Bool
otherwise = ()
where
d :: Int
d = forall t. Storable t => Vector t -> Int
dim Vector t
v
v :: Vector t
v = forall t. Matrix t -> Vector t
xdat Matrix t
m
extractAux :: (Eq t3, Eq t2, TransArray c, Storable a, Storable t1,
Storable t, Num t3, Num t2, Integral t1, Integral t)
=> (t3 -> t2 -> CInt -> Ptr t1 -> CInt -> Ptr t
-> Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt))
-> MatrixOrder -> c -> t3 -> Vector t1 -> t2 -> Vector t -> IO (Matrix a)
t3
-> t2
-> CInt
-> Ptr t1
-> CInt
-> Ptr t
-> Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt)
f MatrixOrder
ord c
m t3
moder Vector t1
vr t2
modec Vector t
vc = do
let nr :: Int
nr = if t3
moder forall a. Eq a => a -> a -> Bool
== t3
0 then forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Vector t1
vrforall t. Storable t => Vector t -> Int -> t
@>Int
1 forall a. Num a => a -> a -> a
- Vector t1
vrforall t. Storable t => Vector t -> Int -> t
@>Int
0 forall a. Num a => a -> a -> a
+ t1
1 else forall t. Storable t => Vector t -> Int
dim Vector t1
vr
nc :: Int
nc = if t2
modec forall a. Eq a => a -> a -> Bool
== t2
0 then forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Vector t
vcforall t. Storable t => Vector t -> Int -> t
@>Int
1 forall a. Num a => a -> a -> a
- Vector t
vcforall t. Storable t => Vector t -> Int -> t
@>Int
0 forall a. Num a => a -> a -> a
+ t
1 else forall t. Storable t => Vector t -> Int
dim Vector t
vc
Matrix a
r <- forall a. Storable a => MatrixOrder -> Int -> Int -> IO (Matrix a)
createMatrix MatrixOrder
ord Int
nr Int
nc
(Vector t1
vr forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# Vector t
vc forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# c
m forall c c1 r.
(TransArray c, TransArray c1) =>
c1 -> c -> Trans c1 (Trans c (IO r)) -> IO r
#! Matrix a
r) (t3
-> t2
-> CInt
-> Ptr t1
-> CInt
-> Ptr t
-> Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt)
f t3
moder t2
modec) IO CInt -> String -> IO ()
#|String
"extract"
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix a
r
type Extr x = CInt -> CInt -> CIdxs (CIdxs (OM x (OM x (IO CInt))))
foreign import ccall unsafe "extractD" :: Extr Double
foreign import ccall unsafe "extractF" :: Extr Float
foreign import ccall unsafe "extractC" :: Extr (Complex Double)
foreign import ccall unsafe "extractQ" :: Extr (Complex Float)
foreign import ccall unsafe "extractI" :: Extr CInt
foreign import ccall unsafe "extractL" :: Extr Z
setRectAux :: (TransArray c1, TransArray c)
=> (CInt -> CInt -> Trans c1 (Trans c (IO CInt)))
-> Int -> Int -> c1 -> c -> IO ()
setRectAux :: forall c1 c.
(TransArray c1, TransArray c) =>
(CInt -> CInt -> Trans c1 (Trans c (IO CInt)))
-> Int -> Int -> c1 -> c -> IO ()
setRectAux CInt -> CInt -> Trans c1 (Trans c (IO CInt))
f Int
i Int
j c1
m c
r = (c1
m forall c c1 r.
(TransArray c, TransArray c1) =>
c1 -> c -> Trans c1 (Trans c (IO r)) -> IO r
#! c
r) (CInt -> CInt -> Trans c1 (Trans c (IO CInt))
f (Int -> CInt
fi Int
i) (Int -> CInt
fi Int
j)) IO CInt -> String -> IO ()
#|String
"setRect"
type SetRect x = I -> I -> x ::> x::> Ok
foreign import ccall unsafe "setRectD" c_setRectD :: SetRect Double
foreign import ccall unsafe "setRectF" c_setRectF :: SetRect Float
foreign import ccall unsafe "setRectC" c_setRectC :: SetRect (Complex Double)
foreign import ccall unsafe "setRectQ" c_setRectQ :: SetRect (Complex Float)
foreign import ccall unsafe "setRectI" c_setRectI :: SetRect I
foreign import ccall unsafe "setRectL" c_setRectL :: SetRect Z
sortG :: (Storable t, Storable a)
=> (CInt -> Ptr t -> CInt -> Ptr a -> IO CInt) -> Vector t -> Vector a
sortG :: forall t a.
(Storable t, Storable a) =>
(CInt -> Ptr t -> CInt -> Ptr a -> IO CInt) -> Vector t -> Vector a
sortG CInt -> Ptr t -> CInt -> Ptr a -> IO CInt
f Vector t
v = forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ do
Vector a
r <- forall a. Storable a => Int -> IO (Vector a)
createVector (forall t. Storable t => Vector t -> Int
dim Vector t
v)
(Vector t
v forall c c1 r.
(TransArray c, TransArray c1) =>
c1 -> c -> Trans c1 (Trans c (IO r)) -> IO r
#! Vector a
r) CInt -> Ptr t -> CInt -> Ptr a -> IO CInt
f IO CInt -> String -> IO ()
#|String
"sortG"
forall (m :: * -> *) a. Monad m => a -> m a
return Vector a
r
sortIdxD :: Vector Double -> Vector CInt
sortIdxD :: Vector Double -> Vector CInt
sortIdxD = forall t a.
(Storable t, Storable a) =>
(CInt -> Ptr t -> CInt -> Ptr a -> IO CInt) -> Vector t -> Vector a
sortG CV Double (CV CInt (IO CInt))
c_sort_indexD
sortIdxF :: Vector Float -> Vector CInt
sortIdxF :: Vector Float -> Vector CInt
sortIdxF = forall t a.
(Storable t, Storable a) =>
(CInt -> Ptr t -> CInt -> Ptr a -> IO CInt) -> Vector t -> Vector a
sortG CV Float (CV CInt (IO CInt))
c_sort_indexF
sortIdxI :: Vector CInt -> Vector CInt
sortIdxI :: Vector CInt -> Vector CInt
sortIdxI = forall t a.
(Storable t, Storable a) =>
(CInt -> Ptr t -> CInt -> Ptr a -> IO CInt) -> Vector t -> Vector a
sortG CV CInt (CV CInt (IO CInt))
c_sort_indexI
sortIdxL :: Vector Z -> Vector I
sortIdxL :: Vector Z -> Vector CInt
sortIdxL = forall t a.
(Storable t, Storable a) =>
(CInt -> Ptr t -> CInt -> Ptr a -> IO CInt) -> Vector t -> Vector a
sortG Z :> CV CInt (IO CInt)
c_sort_indexL
sortValD :: Vector Double -> Vector Double
sortValD :: Vector Double -> Vector Double
sortValD = forall t a.
(Storable t, Storable a) =>
(CInt -> Ptr t -> CInt -> Ptr a -> IO CInt) -> Vector t -> Vector a
sortG CV Double (CV Double (IO CInt))
c_sort_valD
sortValF :: Vector Float -> Vector Float
sortValF :: Vector Float -> Vector Float
sortValF = forall t a.
(Storable t, Storable a) =>
(CInt -> Ptr t -> CInt -> Ptr a -> IO CInt) -> Vector t -> Vector a
sortG CV Float (CV Float (IO CInt))
c_sort_valF
sortValI :: Vector CInt -> Vector CInt
sortValI :: Vector CInt -> Vector CInt
sortValI = forall t a.
(Storable t, Storable a) =>
(CInt -> Ptr t -> CInt -> Ptr a -> IO CInt) -> Vector t -> Vector a
sortG CV CInt (CV CInt (IO CInt))
c_sort_valI
sortValL :: Vector Z -> Vector Z
sortValL :: Vector Z -> Vector Z
sortValL = forall t a.
(Storable t, Storable a) =>
(CInt -> Ptr t -> CInt -> Ptr a -> IO CInt) -> Vector t -> Vector a
sortG Z :> (Z :> IO CInt)
c_sort_valL
foreign import ccall unsafe "sort_indexD" c_sort_indexD :: CV Double (CV CInt (IO CInt))
foreign import ccall unsafe "sort_indexF" c_sort_indexF :: CV Float (CV CInt (IO CInt))
foreign import ccall unsafe "sort_indexI" c_sort_indexI :: CV CInt (CV CInt (IO CInt))
foreign import ccall unsafe "sort_indexL" c_sort_indexL :: Z :> I :> Ok
foreign import ccall unsafe "sort_valuesD" c_sort_valD :: CV Double (CV Double (IO CInt))
foreign import ccall unsafe "sort_valuesF" c_sort_valF :: CV Float (CV Float (IO CInt))
foreign import ccall unsafe "sort_valuesI" c_sort_valI :: CV CInt (CV CInt (IO CInt))
foreign import ccall unsafe "sort_valuesL" c_sort_valL :: Z :> Z :> Ok
compareG :: (TransArray c, Storable t, Storable a)
=> Trans c (CInt -> Ptr t -> CInt -> Ptr a -> IO CInt)
-> c -> Vector t -> Vector a
compareG :: forall c t a.
(TransArray c, Storable t, Storable a) =>
Trans c (CInt -> Ptr t -> CInt -> Ptr a -> IO CInt)
-> c -> Vector t -> Vector a
compareG Trans c (CInt -> Ptr t -> CInt -> Ptr a -> IO CInt)
f c
u Vector t
v = forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ do
Vector a
r <- forall a. Storable a => Int -> IO (Vector a)
createVector (forall t. Storable t => Vector t -> Int
dim Vector t
v)
(c
u forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# Vector t
v forall c c1 r.
(TransArray c, TransArray c1) =>
c1 -> c -> Trans c1 (Trans c (IO r)) -> IO r
#! Vector a
r) Trans c (CInt -> Ptr t -> CInt -> Ptr a -> IO CInt)
f IO CInt -> String -> IO ()
#|String
"compareG"
forall (m :: * -> *) a. Monad m => a -> m a
return Vector a
r
compareD :: Vector Double -> Vector Double -> Vector CInt
compareD :: Vector Double -> Vector Double -> Vector CInt
compareD = forall c t a.
(TransArray c, Storable t, Storable a) =>
Trans c (CInt -> Ptr t -> CInt -> Ptr a -> IO CInt)
-> c -> Vector t -> Vector a
compareG CV Double (CV Double (CV CInt (IO CInt)))
c_compareD
compareF :: Vector Float -> Vector Float -> Vector CInt
compareF :: Vector Float -> Vector Float -> Vector CInt
compareF = forall c t a.
(TransArray c, Storable t, Storable a) =>
Trans c (CInt -> Ptr t -> CInt -> Ptr a -> IO CInt)
-> c -> Vector t -> Vector a
compareG CV Float (CV Float (CV CInt (IO CInt)))
c_compareF
compareI :: Vector CInt -> Vector CInt -> Vector CInt
compareI :: Vector CInt -> Vector CInt -> Vector CInt
compareI = forall c t a.
(TransArray c, Storable t, Storable a) =>
Trans c (CInt -> Ptr t -> CInt -> Ptr a -> IO CInt)
-> c -> Vector t -> Vector a
compareG CV CInt (CV CInt (CV CInt (IO CInt)))
c_compareI
compareL :: Vector Z -> Vector Z -> Vector CInt
compareL :: Vector Z -> Vector Z -> Vector CInt
compareL = forall c t a.
(TransArray c, Storable t, Storable a) =>
Trans c (CInt -> Ptr t -> CInt -> Ptr a -> IO CInt)
-> c -> Vector t -> Vector a
compareG Z :> (Z :> CV CInt (IO CInt))
c_compareL
foreign import ccall unsafe "compareD" c_compareD :: CV Double (CV Double (CV CInt (IO CInt)))
foreign import ccall unsafe "compareF" c_compareF :: CV Float (CV Float (CV CInt (IO CInt)))
foreign import ccall unsafe "compareI" c_compareI :: CV CInt (CV CInt (CV CInt (IO CInt)))
foreign import ccall unsafe "compareL" c_compareL :: Z :> Z :> I :> Ok
selectG :: (TransArray c, TransArray c1, TransArray c2, Storable t, Storable a)
=> Trans c2 (Trans c1 (CInt -> Ptr t -> Trans c (CInt -> Ptr a -> IO CInt)))
-> c2 -> c1 -> Vector t -> c -> Vector a
selectG :: forall c c1 c2 t a.
(TransArray c, TransArray c1, TransArray c2, Storable t,
Storable a) =>
Trans
c2 (Trans c1 (CInt -> Ptr t -> Trans c (CInt -> Ptr a -> IO CInt)))
-> c2 -> c1 -> Vector t -> c -> Vector a
selectG Trans
c2 (Trans c1 (CInt -> Ptr t -> Trans c (CInt -> Ptr a -> IO CInt)))
f c2
c c1
u Vector t
v c
w = forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ do
Vector a
r <- forall a. Storable a => Int -> IO (Vector a)
createVector (forall t. Storable t => Vector t -> Int
dim Vector t
v)
(c2
c forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# c1
u forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# Vector t
v forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# c
w forall c c1 r.
(TransArray c, TransArray c1) =>
c1 -> c -> Trans c1 (Trans c (IO r)) -> IO r
#! Vector a
r) Trans
c2 (Trans c1 (CInt -> Ptr t -> Trans c (CInt -> Ptr a -> IO CInt)))
f IO CInt -> String -> IO ()
#|String
"selectG"
forall (m :: * -> *) a. Monad m => a -> m a
return Vector a
r
selectD :: Vector CInt -> Vector Double -> Vector Double -> Vector Double -> Vector Double
selectD :: Vector CInt
-> Vector Double -> Vector Double -> Vector Double -> Vector Double
selectD = forall c c1 c2 t a.
(TransArray c, TransArray c1, TransArray c2, Storable t,
Storable a) =>
Trans
c2 (Trans c1 (CInt -> Ptr t -> Trans c (CInt -> Ptr a -> IO CInt)))
-> c2 -> c1 -> Vector t -> c -> Vector a
selectG Sel Double
c_selectD
selectF :: Vector CInt -> Vector Float -> Vector Float -> Vector Float -> Vector Float
selectF :: Vector CInt
-> Vector Float -> Vector Float -> Vector Float -> Vector Float
selectF = forall c c1 c2 t a.
(TransArray c, TransArray c1, TransArray c2, Storable t,
Storable a) =>
Trans
c2 (Trans c1 (CInt -> Ptr t -> Trans c (CInt -> Ptr a -> IO CInt)))
-> c2 -> c1 -> Vector t -> c -> Vector a
selectG Sel Float
c_selectF
selectI :: Vector CInt -> Vector CInt -> Vector CInt -> Vector CInt -> Vector CInt
selectI :: Vector CInt
-> Vector CInt -> Vector CInt -> Vector CInt -> Vector CInt
selectI = forall c c1 c2 t a.
(TransArray c, TransArray c1, TransArray c2, Storable t,
Storable a) =>
Trans
c2 (Trans c1 (CInt -> Ptr t -> Trans c (CInt -> Ptr a -> IO CInt)))
-> c2 -> c1 -> Vector t -> c -> Vector a
selectG Reorder CInt
c_selectI
selectL :: Vector CInt -> Vector Z -> Vector Z -> Vector Z -> Vector Z
selectL :: Vector CInt -> Vector Z -> Vector Z -> Vector Z -> Vector Z
selectL = forall c c1 c2 t a.
(TransArray c, TransArray c1, TransArray c2, Storable t,
Storable a) =>
Trans
c2 (Trans c1 (CInt -> Ptr t -> Trans c (CInt -> Ptr a -> IO CInt)))
-> c2 -> c1 -> Vector t -> c -> Vector a
selectG Sel Z
c_selectL
selectC :: Vector CInt
-> Vector (Complex Double)
-> Vector (Complex Double)
-> Vector (Complex Double)
-> Vector (Complex Double)
selectC :: Vector CInt
-> Vector (Complex Double)
-> Vector (Complex Double)
-> Vector (Complex Double)
-> Vector (Complex Double)
selectC = forall c c1 c2 t a.
(TransArray c, TransArray c1, TransArray c2, Storable t,
Storable a) =>
Trans
c2 (Trans c1 (CInt -> Ptr t -> Trans c (CInt -> Ptr a -> IO CInt)))
-> c2 -> c1 -> Vector t -> c -> Vector a
selectG Sel (Complex Double)
c_selectC
selectQ :: Vector CInt
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
selectQ :: Vector CInt
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
-> Vector (Complex Float)
selectQ = forall c c1 c2 t a.
(TransArray c, TransArray c1, TransArray c2, Storable t,
Storable a) =>
Trans
c2 (Trans c1 (CInt -> Ptr t -> Trans c (CInt -> Ptr a -> IO CInt)))
-> c2 -> c1 -> Vector t -> c -> Vector a
selectG Sel (Complex Float)
c_selectQ
type Sel x = CV CInt (CV x (CV x (CV x (CV x (IO CInt)))))
foreign import ccall unsafe "chooseD" c_selectD :: Sel Double
foreign import ccall unsafe "chooseF" c_selectF :: Sel Float
foreign import ccall unsafe "chooseI" c_selectI :: Sel CInt
foreign import ccall unsafe "chooseC" c_selectC :: Sel (Complex Double)
foreign import ccall unsafe "chooseQ" c_selectQ :: Sel (Complex Float)
foreign import ccall unsafe "chooseL" c_selectL :: Sel Z
remapG :: (TransArray c, TransArray c1, Storable t, Storable a)
=> (CInt -> CInt -> CInt -> CInt -> Ptr t
-> Trans c1 (Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt)))
-> Matrix t -> c1 -> c -> Matrix a
remapG :: forall c c1 t a.
(TransArray c, TransArray c1, Storable t, Storable a) =>
(CInt
-> CInt
-> CInt
-> CInt
-> Ptr t
-> Trans
c1 (Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt)))
-> Matrix t -> c1 -> c -> Matrix a
remapG CInt
-> CInt
-> CInt
-> CInt
-> Ptr t
-> Trans
c1 (Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt))
f Matrix t
i c1
j c
m = forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ do
Matrix a
r <- forall a. Storable a => MatrixOrder -> Int -> Int -> IO (Matrix a)
createMatrix MatrixOrder
RowMajor (forall t. Matrix t -> Int
rows Matrix t
i) (forall t. Matrix t -> Int
cols Matrix t
i)
(Matrix t
i forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# c1
j forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# c
m forall c c1 r.
(TransArray c, TransArray c1) =>
c1 -> c -> Trans c1 (Trans c (IO r)) -> IO r
#! Matrix a
r) CInt
-> CInt
-> CInt
-> CInt
-> Ptr t
-> Trans
c1 (Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt))
f IO CInt -> String -> IO ()
#|String
"remapG"
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix a
r
remapD :: Matrix CInt -> Matrix CInt -> Matrix Double -> Matrix Double
remapD :: Matrix CInt -> Matrix CInt -> Matrix Double -> Matrix Double
remapD = forall c c1 t a.
(TransArray c, TransArray c1, Storable t, Storable a) =>
(CInt
-> CInt
-> CInt
-> CInt
-> Ptr t
-> Trans
c1 (Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt)))
-> Matrix t -> c1 -> c -> Matrix a
remapG Rem Double
c_remapD
remapF :: Matrix CInt -> Matrix CInt -> Matrix Float -> Matrix Float
remapF :: Matrix CInt -> Matrix CInt -> Matrix Float -> Matrix Float
remapF = forall c c1 t a.
(TransArray c, TransArray c1, Storable t, Storable a) =>
(CInt
-> CInt
-> CInt
-> CInt
-> Ptr t
-> Trans
c1 (Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt)))
-> Matrix t -> c1 -> c -> Matrix a
remapG Rem Float
c_remapF
remapI :: Matrix CInt -> Matrix CInt -> Matrix CInt -> Matrix CInt
remapI :: Matrix CInt -> Matrix CInt -> Matrix CInt -> Matrix CInt
remapI = forall c c1 t a.
(TransArray c, TransArray c1, Storable t, Storable a) =>
(CInt
-> CInt
-> CInt
-> CInt
-> Ptr t
-> Trans
c1 (Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt)))
-> Matrix t -> c1 -> c -> Matrix a
remapG Rem CInt
c_remapI
remapL :: Matrix CInt -> Matrix CInt -> Matrix Z -> Matrix Z
remapL :: Matrix CInt -> Matrix CInt -> Matrix Z -> Matrix Z
remapL = forall c c1 t a.
(TransArray c, TransArray c1, Storable t, Storable a) =>
(CInt
-> CInt
-> CInt
-> CInt
-> Ptr t
-> Trans
c1 (Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt)))
-> Matrix t -> c1 -> c -> Matrix a
remapG Rem Z
c_remapL
remapC :: Matrix CInt
-> Matrix CInt
-> Matrix (Complex Double)
-> Matrix (Complex Double)
remapC :: Matrix CInt
-> Matrix CInt
-> Matrix (Complex Double)
-> Matrix (Complex Double)
remapC = forall c c1 t a.
(TransArray c, TransArray c1, Storable t, Storable a) =>
(CInt
-> CInt
-> CInt
-> CInt
-> Ptr t
-> Trans
c1 (Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt)))
-> Matrix t -> c1 -> c -> Matrix a
remapG Rem (Complex Double)
c_remapC
remapQ :: Matrix CInt -> Matrix CInt -> Matrix (Complex Float) -> Matrix (Complex Float)
remapQ :: Matrix CInt
-> Matrix CInt -> Matrix (Complex Float) -> Matrix (Complex Float)
remapQ = forall c c1 t a.
(TransArray c, TransArray c1, Storable t, Storable a) =>
(CInt
-> CInt
-> CInt
-> CInt
-> Ptr t
-> Trans
c1 (Trans c (CInt -> CInt -> CInt -> CInt -> Ptr a -> IO CInt)))
-> Matrix t -> c1 -> c -> Matrix a
remapG Rem (Complex Float)
c_remapQ
type Rem x = OM CInt (OM CInt (OM x (OM x (IO CInt))))
foreign import ccall unsafe "remapD" c_remapD :: Rem Double
foreign import ccall unsafe "remapF" c_remapF :: Rem Float
foreign import ccall unsafe "remapI" c_remapI :: Rem CInt
foreign import ccall unsafe "remapC" c_remapC :: Rem (Complex Double)
foreign import ccall unsafe "remapQ" c_remapQ :: Rem (Complex Float)
foreign import ccall unsafe "remapL" c_remapL :: Rem Z
rowOpAux :: (TransArray c, Storable a) =>
(CInt -> Ptr a -> CInt -> CInt -> CInt -> CInt -> Trans c (IO CInt))
-> Int -> a -> Int -> Int -> Int -> Int -> c -> IO ()
rowOpAux :: forall c a.
(TransArray c, Storable a) =>
(CInt
-> Ptr a -> CInt -> CInt -> CInt -> CInt -> Trans c (IO CInt))
-> Int -> a -> Int -> Int -> Int -> Int -> c -> IO ()
rowOpAux CInt -> Ptr a -> CInt -> CInt -> CInt -> CInt -> Trans c (IO CInt)
f Int
c a
x Int
i1 Int
i2 Int
j1 Int
j2 c
m = do
Ptr a
px <- forall a. Storable a => [a] -> IO (Ptr a)
newArray [a
x]
(c
m forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# forall a. a -> a
id) (CInt -> Ptr a -> CInt -> CInt -> CInt -> CInt -> Trans c (IO CInt)
f (Int -> CInt
fi Int
c) Ptr a
px (Int -> CInt
fi Int
i1) (Int -> CInt
fi Int
i2) (Int -> CInt
fi Int
j1) (Int -> CInt
fi Int
j2)) IO CInt -> String -> IO ()
#|String
"rowOp"
forall a. Ptr a -> IO ()
free Ptr a
px
type RowOp x = CInt -> Ptr x -> CInt -> CInt -> CInt -> CInt -> x ::> Ok
foreign import ccall unsafe "rowop_double" c_rowOpD :: RowOp R
foreign import ccall unsafe "rowop_float" c_rowOpF :: RowOp Float
foreign import ccall unsafe "rowop_TCD" c_rowOpC :: RowOp C
foreign import ccall unsafe "rowop_TCF" c_rowOpQ :: RowOp (Complex Float)
foreign import ccall unsafe "rowop_int32_t" c_rowOpI :: RowOp I
foreign import ccall unsafe "rowop_int64_t" c_rowOpL :: RowOp Z
foreign import ccall unsafe "rowop_mod_int32_t" c_rowOpMI :: I -> RowOp I
foreign import ccall unsafe "rowop_mod_int64_t" c_rowOpML :: Z -> RowOp Z
gemmg :: (TransArray c1, TransArray c, TransArray c2, TransArray c3)
=> Trans c3 (Trans c2 (Trans c1 (Trans c (IO CInt))))
-> c3 -> c2 -> c1 -> c -> IO ()
gemmg :: forall c1 c c2 c3.
(TransArray c1, TransArray c, TransArray c2, TransArray c3) =>
Trans c3 (Trans c2 (Trans c1 (Trans c (IO CInt))))
-> c3 -> c2 -> c1 -> c -> IO ()
gemmg Trans c3 (Trans c2 (Trans c1 (Trans c (IO CInt))))
f c3
v c2
m1 c1
m2 c
m3 = (c3
v forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# c2
m1 forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# c1
m2 forall c c1 r.
(TransArray c, TransArray c1) =>
c1 -> c -> Trans c1 (Trans c (IO r)) -> IO r
#! c
m3) Trans c3 (Trans c2 (Trans c1 (Trans c (IO CInt))))
f IO CInt -> String -> IO ()
#|String
"gemmg"
type Tgemm x = x :> x ::> x ::> x ::> Ok
foreign import ccall unsafe "gemm_double" c_gemmD :: Tgemm R
foreign import ccall unsafe "gemm_float" c_gemmF :: Tgemm Float
foreign import ccall unsafe "gemm_TCD" c_gemmC :: Tgemm C
foreign import ccall unsafe "gemm_TCF" c_gemmQ :: Tgemm (Complex Float)
foreign import ccall unsafe "gemm_int32_t" c_gemmI :: Tgemm I
foreign import ccall unsafe "gemm_int64_t" c_gemmL :: Tgemm Z
foreign import ccall unsafe "gemm_mod_int32_t" c_gemmMI :: I -> Tgemm I
foreign import ccall unsafe "gemm_mod_int64_t" c_gemmML :: Z -> Tgemm Z
reorderAux :: (TransArray c, Storable t, Storable a1, Storable t1, Storable a) =>
(CInt -> Ptr a -> CInt -> Ptr t1
-> Trans c (CInt -> Ptr t -> CInt -> Ptr a1 -> IO CInt))
-> Vector t1 -> c -> Vector t -> Vector a1
reorderAux :: forall c t a1 t1 a.
(TransArray c, Storable t, Storable a1, Storable t1, Storable a) =>
(CInt
-> Ptr a
-> CInt
-> Ptr t1
-> Trans c (CInt -> Ptr t -> CInt -> Ptr a1 -> IO CInt))
-> Vector t1 -> c -> Vector t -> Vector a1
reorderAux CInt
-> Ptr a
-> CInt
-> Ptr t1
-> Trans c (CInt -> Ptr t -> CInt -> Ptr a1 -> IO CInt)
f Vector t1
s c
d Vector t
v = forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ do
Vector a
k <- forall a. Storable a => Int -> IO (Vector a)
createVector (forall t. Storable t => Vector t -> Int
dim Vector t1
s)
Vector a1
r <- forall a. Storable a => Int -> IO (Vector a)
createVector (forall t. Storable t => Vector t -> Int
dim Vector t
v)
(Vector a
k forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# Vector t1
s forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# c
d forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# Vector t
v forall c c1 r.
(TransArray c, TransArray c1) =>
c1 -> c -> Trans c1 (Trans c (IO r)) -> IO r
#! Vector a1
r) CInt
-> Ptr a
-> CInt
-> Ptr t1
-> Trans c (CInt -> Ptr t -> CInt -> Ptr a1 -> IO CInt)
f IO CInt -> String -> IO ()
#| String
"reorderV"
forall (m :: * -> *) a. Monad m => a -> m a
return Vector a1
r
type Reorder x = CV CInt (CV CInt (CV CInt (CV x (CV x (IO CInt)))))
foreign import ccall unsafe "reorderD" c_reorderD :: Reorder Double
foreign import ccall unsafe "reorderF" c_reorderF :: Reorder Float
foreign import ccall unsafe "reorderI" c_reorderI :: Reorder CInt
foreign import ccall unsafe "reorderC" c_reorderC :: Reorder (Complex Double)
foreign import ccall unsafe "reorderQ" c_reorderQ :: Reorder (Complex Float)
foreign import ccall unsafe "reorderL" c_reorderL :: Reorder Z
reorderVector :: Element a
=> Vector CInt
-> Vector CInt
-> Vector a
-> Vector a
reorderVector :: forall a.
Element a =>
Vector CInt -> Vector CInt -> Vector a -> Vector a
reorderVector = forall a.
Element a =>
Vector CInt -> Vector CInt -> Vector a -> Vector a
reorderV
foreign import ccall unsafe "saveMatrix" c_saveMatrix
:: CString -> CString -> Double ::> Ok
saveMatrix
:: FilePath
-> String
-> Matrix Double
-> IO ()
saveMatrix :: String -> String -> Matrix Double -> IO ()
saveMatrix String
name String
format Matrix Double
m = do
CString
cname <- String -> IO CString
newCString String
name
CString
cformat <- String -> IO CString
newCString String
format
(Matrix Double
m forall c b r. TransArray c => c -> (b -> IO r) -> Trans c b -> IO r
# forall a. a -> a
id) (CString -> CString -> Double ::> IO CInt
c_saveMatrix CString
cname CString
cformat) IO CInt -> String -> IO ()
#|String
"saveMatrix"
forall a. Ptr a -> IO ()
free CString
cname
forall a. Ptr a -> IO ()
free CString
cformat
forall (m :: * -> *) a. Monad m => a -> m a
return ()