{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
module Internal.Container where
import Internal.Vector
import Internal.Matrix
import Internal.Element
import Internal.Numeric
import Internal.Algorithms(Field,linearSolveSVD,Herm,mTm)
#if MIN_VERSION_base(4,11,0)
import Prelude hiding ((<>))
#endif
linspace :: (Fractional e, Container Vector e) => Int -> (e, e) -> Vector e
linspace :: Int -> (e, e) -> Vector e
linspace Int
0 (e, e)
_ = [e] -> Vector e
forall a. Storable a => [a] -> Vector a
fromList[]
linspace Int
1 (e
a,e
b) = [e] -> Vector e
forall a. Storable a => [a] -> Vector a
fromList[(e
ae -> e -> e
forall a. Num a => a -> a -> a
+e
b)e -> e -> e
forall a. Fractional a => a -> a -> a
/e
2]
linspace Int
n (e
a,e
b) = e -> Vector e -> Vector e
forall (c :: * -> *) e. Container c e => e -> c e -> c e
addConstant e
a (Vector e -> Vector e) -> Vector e -> Vector e
forall a b. (a -> b) -> a -> b
$ e -> Vector e -> Vector e
forall t (c :: * -> *). Linear t c => t -> c t -> c t
scale e
s (Vector e -> Vector e) -> Vector e -> Vector e
forall a b. (a -> b) -> a -> b
$ [e] -> Vector e
forall a. Storable a => [a] -> Vector a
fromList ([e] -> Vector e) -> [e] -> Vector e
forall a b. (a -> b) -> a -> b
$ (Int -> e) -> [Int] -> [e]
forall a b. (a -> b) -> [a] -> [b]
map Int -> e
forall a b. (Integral a, Num b) => a -> b
fromIntegral [Int
0 .. Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1]
where s :: e
s = (e
be -> e -> e
forall a. Num a => a -> a -> a
-e
a)e -> e -> e
forall a. Fractional a => a -> a -> a
/Int -> e
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
infixr 8 <.>
(<.>) :: Numeric t => Vector t -> Vector t -> t
<.> :: Vector t -> Vector t -> t
(<.>) = Vector t -> Vector t -> t
forall t. Numeric t => Vector t -> Vector t -> t
dot
infixr 8 #>
(#>) :: Numeric t => Matrix t -> Vector t -> Vector t
#> :: Matrix t -> Vector t -> Vector t
(#>) = Matrix t -> Vector t -> Vector t
forall t. Product t => Matrix t -> Vector t -> Vector t
mXv
app :: Numeric t => Matrix t -> Vector t -> Vector t
app :: Matrix t -> Vector t -> Vector t
app = Matrix t -> Vector t -> Vector t
forall t. Numeric t => Matrix t -> Vector t -> Vector t
(#>)
infixl 8 <#
(<#) :: Numeric t => Vector t -> Matrix t -> Vector t
<# :: Vector t -> Matrix t -> Vector t
(<#) = Vector t -> Matrix t -> Vector t
forall t. Product t => Vector t -> Matrix t -> Vector t
vXm
class Mul a b c | a b -> c where
infixl 7 <>
(<>) :: Product t => a t -> b t -> c t
instance Mul Matrix Matrix Matrix where
<> :: Matrix t -> Matrix t -> Matrix t
(<>) = Matrix t -> Matrix t -> Matrix t
forall t. Product t => Matrix t -> Matrix t -> Matrix t
mXm
instance Mul Matrix Vector Vector where
<> :: Matrix t -> Vector t -> Vector t
(<>) Matrix t
m Vector t
v = Matrix t -> Vector t
forall t. Element t => Matrix t -> Vector t
flatten (Matrix t -> Vector t) -> Matrix t -> Vector t
forall a b. (a -> b) -> a -> b
$ Matrix t
m Matrix t -> Matrix t -> Matrix t
forall (a :: * -> *) (b :: * -> *) (c :: * -> *) t.
(Mul a b c, Product t) =>
a t -> b t -> c t
<> Vector t -> Matrix t
forall a. Storable a => Vector a -> Matrix a
asColumn Vector t
v
instance Mul Vector Matrix Vector where
<> :: Vector t -> Matrix t -> Vector t
(<>) Vector t
v Matrix t
m = Matrix t -> Vector t
forall t. Element t => Matrix t -> Vector t
flatten (Matrix t -> Vector t) -> Matrix t -> Vector t
forall a b. (a -> b) -> a -> b
$ Vector t -> Matrix t
forall a. Storable a => Vector a -> Matrix a
asRow Vector t
v Matrix t -> Matrix t -> Matrix t
forall (a :: * -> *) (b :: * -> *) (c :: * -> *) t.
(Mul a b c, Product t) =>
a t -> b t -> c t
<> Matrix t
m
infixl 7 <\>
(<\>) :: (LSDiv c, Field t) => Matrix t -> c t -> c t
<\> :: Matrix t -> c t -> c t
(<\>) = Matrix t -> c t -> c t
forall (c :: * -> *) t.
(LSDiv c, Field t) =>
Matrix t -> c t -> c t
linSolve
class LSDiv c
where
linSolve :: Field t => Matrix t -> c t -> c t
instance LSDiv Vector
where
linSolve :: Matrix t -> Vector t -> Vector t
linSolve Matrix t
m Vector t
v = Matrix t -> Vector t
forall t. Element t => Matrix t -> Vector t
flatten (Matrix t -> Matrix t -> Matrix t
forall t. Field t => Matrix t -> Matrix t -> Matrix t
linearSolveSVD Matrix t
m (Int -> Vector t -> Matrix t
forall t. Storable t => Int -> Vector t -> Matrix t
reshape Int
1 Vector t
v))
instance LSDiv Matrix
where
linSolve :: Matrix t -> Matrix t -> Matrix t
linSolve = Matrix t -> Matrix t -> Matrix t
forall t. Field t => Matrix t -> Matrix t -> Matrix t
linearSolveSVD
class Build d f c e | d -> c, c -> d, f -> e, f -> d, f -> c, c e -> f, d e -> f
where
build :: d -> f -> c e
instance Container Vector e => Build Int (e -> e) Vector e
where
build :: Int -> (e -> e) -> Vector e
build = Int -> (e -> e) -> Vector e
forall (c :: * -> *) e.
Container c e =>
IndexOf c -> ArgOf c e -> c e
build'
instance (Num e, Container Vector e) => Build (Int,Int) (e -> e -> e) Matrix e
where
build :: (Int, Int) -> (e -> e -> e) -> Matrix e
build = (Int, Int) -> (e -> e -> e) -> Matrix e
forall (c :: * -> *) e.
Container c e =>
IndexOf c -> ArgOf c e -> c e
build'
dot :: (Numeric t) => Vector t -> Vector t -> t
dot :: Vector t -> Vector t -> t
dot Vector t
u Vector t
v = Vector t -> Vector t -> t
forall e. Product e => Vector e -> Vector e -> e
udot (Vector t -> Vector t
forall (c :: * -> *) e. Container c e => c e -> c e
conj Vector t
u) Vector t
v
optimiseMult :: Monoid (Matrix t) => [Matrix t] -> Matrix t
optimiseMult :: [Matrix t] -> Matrix t
optimiseMult = [Matrix t] -> Matrix t
forall a. Monoid a => [a] -> a
mconcat
meanCov :: Matrix Double -> (Vector Double, Herm Double)
meanCov :: Matrix Double -> (Vector Double, Herm Double)
meanCov Matrix Double
x = (Vector Double
med,Herm Double
cov) where
r :: Int
r = Matrix Double -> Int
forall t. Matrix t -> Int
rows Matrix Double
x
k :: Double
k = Double
1 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
r
med :: Vector Double
med = Double -> Int -> Vector Double
forall e d (c :: * -> *). Konst e d c => e -> d -> c e
konst Double
k Int
r Vector Double -> Matrix Double -> Vector Double
forall t. Product t => Vector t -> Matrix t -> Vector t
`vXm` Matrix Double
x
meds :: Matrix Double
meds = Double -> Int -> Vector Double
forall e d (c :: * -> *). Konst e d c => e -> d -> c e
konst Double
1 Int
r Vector Double -> Vector Double -> Matrix Double
forall t. Product t => Vector t -> Vector t -> Matrix t
`outer` Vector Double
med
xc :: Matrix Double
xc = Matrix Double
x Matrix Double -> Matrix Double -> Matrix Double
forall (c :: * -> *) e. Container c e => c e -> c e -> c e
`sub` Matrix Double
meds
cov :: Herm Double
cov = Double -> Herm Double -> Herm Double
forall t (c :: * -> *). Linear t c => t -> c t -> c t
scale (Double -> Double
forall a. Fractional a => a -> a
recip (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
rInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1))) (Matrix Double -> Herm Double
forall t. Numeric t => Matrix t -> Herm t
mTm Matrix Double
xc)
sortVector :: (Ord t, Element t) => Vector t -> Vector t
sortVector :: Vector t -> Vector t
sortVector = Vector t -> Vector t
forall a. (Element a, Ord a) => Vector a -> Vector a
sortV
sortIndex :: (Ord t, Element t) => Vector t -> Vector I
sortIndex :: Vector t -> Vector I
sortIndex = Vector t -> Vector I
forall a. (Element a, Ord a) => Vector a -> Vector I
sortI
ccompare :: (Ord t, Container c t) => c t -> c t -> c I
ccompare :: c t -> c t -> c I
ccompare = c t -> c t -> c I
forall (c :: * -> *) e. (Container c e, Ord e) => c e -> c e -> c I
ccompare'
cselect :: (Container c t) => c I -> c t -> c t -> c t -> c t
cselect :: c I -> c t -> c t -> c t -> c t
cselect = c I -> c t -> c t -> c t -> c t
forall (c :: * -> *) e.
Container c e =>
c I -> c e -> c e -> c e -> c e
cselect'
remap :: Element t => Matrix I -> Matrix I -> Matrix t -> Matrix t
remap :: Matrix I -> Matrix I -> Matrix t -> Matrix t
remap Matrix I
i Matrix I
j Matrix t
m
| Matrix I -> I
forall (c :: * -> *) e. Container c e => c e -> e
minElement Matrix I
i I -> I -> Bool
forall a. Ord a => a -> a -> Bool
>= I
0 Bool -> Bool -> Bool
&& Matrix I -> I
forall (c :: * -> *) e. Container c e => c e -> e
maxElement Matrix I
i I -> I -> Bool
forall a. Ord a => a -> a -> Bool
< Int -> I
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Matrix t -> Int
forall t. Matrix t -> Int
rows Matrix t
m) Bool -> Bool -> Bool
&&
Matrix I -> I
forall (c :: * -> *) e. Container c e => c e -> e
minElement Matrix I
j I -> I -> Bool
forall a. Ord a => a -> a -> Bool
>= I
0 Bool -> Bool -> Bool
&& Matrix I -> I
forall (c :: * -> *) e. Container c e => c e -> e
maxElement Matrix I
j I -> I -> Bool
forall a. Ord a => a -> a -> Bool
< Int -> I
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Matrix t -> Int
forall t. Matrix t -> Int
cols Matrix t
m) = Matrix I -> Matrix I -> Matrix t -> Matrix t
forall a. Element a => Matrix I -> Matrix I -> Matrix a -> Matrix a
remapM Matrix I
i' Matrix I
j' Matrix t
m
| Bool
otherwise = [Char] -> Matrix t
forall a. HasCallStack => [Char] -> a
error ([Char] -> Matrix t) -> [Char] -> Matrix t
forall a b. (a -> b) -> a -> b
$ [Char]
"out of range index in remap"
where
[Matrix I
i',Matrix I
j'] = [Matrix I] -> [Matrix I]
forall t. Element t => [Matrix t] -> [Matrix t]
conformMs [Matrix I
i,Matrix I
j]