summaryrefslogtreecommitdiff
path: root/packages
diff options
context:
space:
mode:
Diffstat (limited to 'packages')
-rw-r--r--packages/base/hmatrix.cabal3
-rw-r--r--packages/base/src/Internal/Algorithms.hs5
-rw-r--r--packages/base/src/Internal/CG.hs2
-rw-r--r--packages/base/src/Internal/Container.hs2
-rw-r--r--packages/base/src/Internal/Devel.hs6
-rw-r--r--packages/base/src/Internal/Element.hs14
-rw-r--r--packages/base/src/Internal/IO.hs14
-rw-r--r--packages/base/src/Internal/LAPACK.hs4
-rw-r--r--packages/base/src/Internal/Matrix.hs22
-rw-r--r--packages/base/src/Internal/Modular.hs2
-rw-r--r--packages/base/src/Internal/Numeric.hs5
-rw-r--r--packages/base/src/Internal/Random.hs2
-rw-r--r--packages/base/src/Internal/ST.hs3
-rw-r--r--packages/base/src/Internal/Sparse.hs2
-rw-r--r--packages/base/src/Internal/Static.hs4
-rw-r--r--packages/base/src/Internal/Tools.hs61
-rw-r--r--packages/base/src/Internal/Util.hs2
-rw-r--r--packages/base/src/Internal/Vector.hs58
-rw-r--r--packages/base/src/Internal/Vectorized.hs5
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Data.hs4
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Devel.hs2
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Static.hs2
-rw-r--r--packages/base/src/Numeric/Vector.hs2
23 files changed, 92 insertions, 134 deletions
diff --git a/packages/base/hmatrix.cabal b/packages/base/hmatrix.cabal
index a487928..0ab4821 100644
--- a/packages/base/hmatrix.cabal
+++ b/packages/base/hmatrix.cabal
@@ -47,8 +47,7 @@ library
47 Numeric.LinearAlgebra.HMatrix 47 Numeric.LinearAlgebra.HMatrix
48 Numeric.LinearAlgebra.Static 48 Numeric.LinearAlgebra.Static
49 49
50 other-modules: Internal.Tools 50 other-modules: Internal.Vector
51 Internal.Vector
52 Internal.Devel 51 Internal.Devel
53 Internal.Vectorized 52 Internal.Vectorized
54 Internal.Matrix 53 Internal.Matrix
diff --git a/packages/base/src/Internal/Algorithms.hs b/packages/base/src/Internal/Algorithms.hs
index 328af22..aaf6fbb 100644
--- a/packages/base/src/Internal/Algorithms.hs
+++ b/packages/base/src/Internal/Algorithms.hs
@@ -27,12 +27,9 @@ import Internal.Matrix
27import Internal.Element 27import Internal.Element
28import Internal.Conversion 28import Internal.Conversion
29import Internal.LAPACK as LAPACK 29import Internal.LAPACK as LAPACK
30import Internal.Numeric
30import Data.List(foldl1') 31import Data.List(foldl1')
31import Data.Array 32import Data.Array
32import Internal.Numeric
33import Data.Vector.Storable(fromList)
34
35-- :i mul
36 33
37{- | Generic linear algebra functions for double precision real and complex matrices. 34{- | Generic linear algebra functions for double precision real and complex matrices.
38 35
diff --git a/packages/base/src/Internal/CG.hs b/packages/base/src/Internal/CG.hs
index 1193b18..fd14212 100644
--- a/packages/base/src/Internal/CG.hs
+++ b/packages/base/src/Internal/CG.hs
@@ -16,7 +16,6 @@ import Internal.Sparse
16import Numeric.Vector() 16import Numeric.Vector()
17import Internal.Algorithms(linearSolveLS, relativeError, pnorm, NormType(..)) 17import Internal.Algorithms(linearSolveLS, relativeError, pnorm, NormType(..))
18import Control.Arrow((***)) 18import Control.Arrow((***))
19import Data.Vector.Storable(fromList)
20 19
21{- 20{-
22import Util.Misc(debug, debugMat) 21import Util.Misc(debug, debugMat)
@@ -30,7 +29,6 @@ infix 0 ///
30v /// b = debugMat b 2 asRow v 29v /// b = debugMat b 2 asRow v
31-} 30-}
32 31
33type R = Double
34type V = Vector R 32type V = Vector R
35 33
36data CGState = CGState 34data CGState = CGState
diff --git a/packages/base/src/Internal/Container.hs b/packages/base/src/Internal/Container.hs
index 216e31e..f6355b2 100644
--- a/packages/base/src/Internal/Container.hs
+++ b/packages/base/src/Internal/Container.hs
@@ -24,14 +24,12 @@
24 24
25module Internal.Container where 25module Internal.Container where
26 26
27import Internal.Tools
28import Internal.Vector 27import Internal.Vector
29import Internal.Matrix 28import Internal.Matrix
30import Internal.Element 29import Internal.Element
31import Internal.Numeric 30import Internal.Numeric
32import Data.Complex 31import Data.Complex
33import Internal.Algorithms(Field,linearSolveSVD) 32import Internal.Algorithms(Field,linearSolveSVD)
34import Data.Vector.Storable(fromList)
35 33
36------------------------------------------------------------------ 34------------------------------------------------------------------
37 35
diff --git a/packages/base/src/Internal/Devel.hs b/packages/base/src/Internal/Devel.hs
index 61d2c85..b8e04ef 100644
--- a/packages/base/src/Internal/Devel.hs
+++ b/packages/base/src/Internal/Devel.hs
@@ -11,7 +11,6 @@
11module Internal.Devel where 11module Internal.Devel where
12 12
13 13
14import Internal.Tools ( (//) )
15import Control.Monad ( when ) 14import Control.Monad ( when )
16import Foreign.C.Types ( CInt ) 15import Foreign.C.Types ( CInt )
17--import Foreign.Storable.Complex () 16--import Foreign.Storable.Complex ()
@@ -19,6 +18,11 @@ import Foreign.Ptr(Ptr)
19import Control.Exception as E ( SomeException, catch ) 18import Control.Exception as E ( SomeException, catch )
20 19
21 20
21-- | postfix function application (@flip ($)@)
22(//) :: x -> (x -> y) -> y
23infixl 0 //
24(//) = flip ($)
25
22-- hmm.. 26-- hmm..
23ww2 w1 o1 w2 o2 f = w1 o1 $ w2 o2 . f 27ww2 w1 o1 w2 o2 f = w1 o1 $ w2 o2 . f
24ww3 w1 o1 w2 o2 w3 o3 f = w1 o1 $ ww2 w2 o2 w3 o3 . f 28ww3 w1 o1 w2 o2 w3 o3 f = w1 o1 $ ww2 w2 o2 w3 o3 . f
diff --git a/packages/base/src/Internal/Element.hs b/packages/base/src/Internal/Element.hs
index 61a75d8..55bff67 100644
--- a/packages/base/src/Internal/Element.hs
+++ b/packages/base/src/Internal/Element.hs
@@ -21,15 +21,14 @@
21 21
22module Internal.Element where 22module Internal.Element where
23 23
24import Internal.Tools
25import Internal.Vector 24import Internal.Vector
26import Internal.Matrix 25import Internal.Matrix
27import Internal.Vectorized 26import Internal.Vectorized
28import qualified Internal.ST as ST 27import qualified Internal.ST as ST
29import Data.Array 28import Data.Array
30import Text.Printf 29import Text.Printf
31import Data.Vector.Storable(fromList)
32import Data.List(transpose,intersperse) 30import Data.List(transpose,intersperse)
31import Data.List.Split(chunksOf)
33import Foreign.Storable(Storable) 32import Foreign.Storable(Storable)
34import Control.Monad(liftM) 33import Control.Monad(liftM)
35 34
@@ -165,6 +164,15 @@ m ?? (er,ec) = extractR m moder rs modec cs
165 164
166-------------------------------------------------------------------------------- 165--------------------------------------------------------------------------------
167 166
167-- | obtains the common value of a property of a list
168common :: (Eq a) => (b->a) -> [b] -> Maybe a
169common f = commonval . map f
170 where
171 commonval :: (Eq a) => [a] -> Maybe a
172 commonval [] = Nothing
173 commonval [a] = Just a
174 commonval (a:b:xs) = if a==b then commonval (b:xs) else Nothing
175
168 176
169-- | creates a matrix from a vertical list of matrices 177-- | creates a matrix from a vertical list of matrices
170joinVert :: Element t => [Matrix t] -> Matrix t 178joinVert :: Element t => [Matrix t] -> Matrix t
@@ -210,7 +218,7 @@ adaptBlocks ms = ms' where
210 rs = map (compatdim . map rows) ms 218 rs = map (compatdim . map rows) ms
211 cs = map (compatdim . map cols) (transpose ms) 219 cs = map (compatdim . map cols) (transpose ms)
212 szs = sequence [rs,cs] 220 szs = sequence [rs,cs]
213 ms' = splitEvery bc $ zipWith g szs (concat ms) 221 ms' = chunksOf bc $ zipWith g szs (concat ms)
214 222
215 g [Just nr,Just nc] m 223 g [Just nr,Just nc] m
216 | nr == r && nc == c = m 224 | nr == r && nc == c = m
diff --git a/packages/base/src/Internal/IO.hs b/packages/base/src/Internal/IO.hs
index e594a1c..a899cfd 100644
--- a/packages/base/src/Internal/IO.hs
+++ b/packages/base/src/Internal/IO.hs
@@ -16,16 +16,26 @@ module Internal.IO (
16 loadMatrix, loadMatrix', saveMatrix 16 loadMatrix, loadMatrix', saveMatrix
17) where 17) where
18 18
19import Internal.Tools
20import Internal.Devel 19import Internal.Devel
21import Internal.Vector 20import Internal.Vector
22import Internal.Matrix 21import Internal.Matrix
23import Internal.Vectorized 22import Internal.Vectorized
24import Text.Printf(printf) 23import Text.Printf(printf)
25import Data.List(intersperse) 24import Data.List(intersperse,transpose)
26import Data.Complex 25import Data.Complex
27 26
28 27
28-- | Formatting tool
29table :: String -> [[String]] -> String
30table sep as = unlines . map unwords' $ transpose mtp
31 where
32 mt = transpose as
33 longs = map (maximum . map length) mt
34 mtp = zipWith (\a b -> map (pad a) b) longs mt
35 pad n str = replicate (n - length str) ' ' ++ str
36 unwords' = concat . intersperse sep
37
38
29 39
30{- | Creates a string from a matrix given a separator and a function to show each entry. Using 40{- | Creates a string from a matrix given a separator and a function to show each entry. Using
31this function the user can easily define any desired display function: 41this function the user can easily define any desired display function:
diff --git a/packages/base/src/Internal/LAPACK.hs b/packages/base/src/Internal/LAPACK.hs
index 9cab3f8..d6a2e6e 100644
--- a/packages/base/src/Internal/LAPACK.hs
+++ b/packages/base/src/Internal/LAPACK.hs
@@ -20,19 +20,15 @@ import Internal.Vector
20import Internal.Matrix 20import Internal.Matrix
21import Internal.Conversion 21import Internal.Conversion
22import Internal.Element 22import Internal.Element
23
24import Foreign.Ptr(nullPtr) 23import Foreign.Ptr(nullPtr)
25import Foreign.C.Types 24import Foreign.C.Types
26import Control.Monad(when) 25import Control.Monad(when)
27import System.IO.Unsafe(unsafePerformIO) 26import System.IO.Unsafe(unsafePerformIO)
28import Data.Vector.Storable(fromList)
29 27
30----------------------------------------------------------------------------------- 28-----------------------------------------------------------------------------------
31 29
32type TMMM t = t ..> t ..> t ..> Ok 30type TMMM t = t ..> t ..> t ..> Ok
33 31
34type R = Double
35type C = Complex Double
36type F = Float 32type F = Float
37type Q = Complex Float 33type Q = Complex Float
38 34
diff --git a/packages/base/src/Internal/Matrix.hs b/packages/base/src/Internal/Matrix.hs
index 44365d0..d715cbf 100644
--- a/packages/base/src/Internal/Matrix.hs
+++ b/packages/base/src/Internal/Matrix.hs
@@ -16,12 +16,9 @@
16 16
17module Internal.Matrix where 17module Internal.Matrix where
18 18
19
20import Internal.Tools ( splitEvery, fi, compatdim, (//) )
21import Internal.Vector 19import Internal.Vector
22import Internal.Devel 20import Internal.Devel
23import Internal.Vectorized 21import Internal.Vectorized
24import Data.Vector.Storable ( unsafeWith, fromList )
25import Foreign.Marshal.Alloc ( free ) 22import Foreign.Marshal.Alloc ( free )
26import Foreign.Ptr ( Ptr ) 23import Foreign.Ptr ( Ptr )
27import Foreign.Storable ( Storable ) 24import Foreign.Storable ( Storable )
@@ -30,7 +27,7 @@ import Foreign.C.Types ( CInt(..) )
30import Foreign.C.String ( CString, newCString ) 27import Foreign.C.String ( CString, newCString )
31import System.IO.Unsafe ( unsafePerformIO ) 28import System.IO.Unsafe ( unsafePerformIO )
32import Control.DeepSeq ( NFData(..) ) 29import Control.DeepSeq ( NFData(..) )
33 30import Data.List.Split(chunksOf)
34 31
35----------------------------------------------------------------- 32-----------------------------------------------------------------
36 33
@@ -150,7 +147,22 @@ type t ::> s = Mt t s
150 147
151-- | the inverse of 'Data.Packed.Matrix.fromLists' 148-- | the inverse of 'Data.Packed.Matrix.fromLists'
152toLists :: (Element t) => Matrix t -> [[t]] 149toLists :: (Element t) => Matrix t -> [[t]]
153toLists m = splitEvery (cols m) . toList . flatten $ m 150toLists m = chunksOf (cols m) . toList . flatten $ m
151
152
153
154-- | common value with \"adaptable\" 1
155compatdim :: [Int] -> Maybe Int
156compatdim [] = Nothing
157compatdim [a] = Just a
158compatdim (a:b:xs)
159 | a==b = compatdim (b:xs)
160 | a==1 = compatdim (b:xs)
161 | b==1 = compatdim (a:xs)
162 | otherwise = Nothing
163
164
165
154 166
155-- | Create a matrix from a list of vectors. 167-- | Create a matrix from a list of vectors.
156-- All vectors must have the same dimension, 168-- All vectors must have the same dimension,
diff --git a/packages/base/src/Internal/Modular.hs b/packages/base/src/Internal/Modular.hs
index 1116b96..cf50a05 100644
--- a/packages/base/src/Internal/Modular.hs
+++ b/packages/base/src/Internal/Modular.hs
@@ -29,13 +29,11 @@ import Internal.Vector
29import Internal.Matrix hiding (mat,size) 29import Internal.Matrix hiding (mat,size)
30import Internal.Numeric 30import Internal.Numeric
31import Internal.Element 31import Internal.Element
32import Internal.Tools
33import Internal.Container 32import Internal.Container
34import Internal.Util(Indexable(..),gaussElim) 33import Internal.Util(Indexable(..),gaussElim)
35import GHC.TypeLits 34import GHC.TypeLits
36import Data.Proxy(Proxy) 35import Data.Proxy(Proxy)
37import Foreign.ForeignPtr(castForeignPtr) 36import Foreign.ForeignPtr(castForeignPtr)
38import Data.Vector.Storable(fromList,unsafeToForeignPtr, unsafeFromForeignPtr)
39import Foreign.Storable 37import Foreign.Storable
40import Data.Ratio 38import Data.Ratio
41 39
diff --git a/packages/base/src/Internal/Numeric.hs b/packages/base/src/Internal/Numeric.hs
index af665a4..879daf8 100644
--- a/packages/base/src/Internal/Numeric.hs
+++ b/packages/base/src/Internal/Numeric.hs
@@ -18,7 +18,6 @@
18 18
19module Internal.Numeric where 19module Internal.Numeric where
20 20
21import Internal.Tools
22import Internal.Vector 21import Internal.Vector
23import Internal.Matrix 22import Internal.Matrix
24import Internal.Element 23import Internal.Element
@@ -26,7 +25,7 @@ import Internal.ST as ST
26import Internal.Conversion 25import Internal.Conversion
27import Internal.Vectorized 26import Internal.Vectorized
28import Internal.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ,multiplyI) 27import Internal.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ,multiplyI)
29import Data.Vector.Storable(fromList) 28import Data.List.Split(chunksOf)
30 29
31-------------------------------------------------------------------------------- 30--------------------------------------------------------------------------------
32 31
@@ -617,7 +616,7 @@ m2=(4><3)
617-} 616-}
618kronecker :: (Product t) => Matrix t -> Matrix t -> Matrix t 617kronecker :: (Product t) => Matrix t -> Matrix t -> Matrix t
619kronecker a b = fromBlocks 618kronecker a b = fromBlocks
620 . splitEvery (cols a) 619 . chunksOf (cols a)
621 . map (reshape (cols b)) 620 . map (reshape (cols b))
622 . toRows 621 . toRows
623 $ flatten a `outer` flatten b 622 $ flatten a `outer` flatten b
diff --git a/packages/base/src/Internal/Random.hs b/packages/base/src/Internal/Random.hs
index c44c272..8c792eb 100644
--- a/packages/base/src/Internal/Random.hs
+++ b/packages/base/src/Internal/Random.hs
@@ -25,8 +25,6 @@ import Internal.Matrix
25import Internal.Numeric 25import Internal.Numeric
26import Internal.Algorithms 26import Internal.Algorithms
27import System.Random(randomIO) 27import System.Random(randomIO)
28import Data.Vector.Storable(fromList)
29
30 28
31-- | Obtains a matrix whose rows are pseudorandom samples from a multivariate 29-- | Obtains a matrix whose rows are pseudorandom samples from a multivariate
32-- Gaussian distribution. 30-- Gaussian distribution.
diff --git a/packages/base/src/Internal/ST.hs b/packages/base/src/Internal/ST.hs
index 25e7969..ae75a1b 100644
--- a/packages/base/src/Internal/ST.hs
+++ b/packages/base/src/Internal/ST.hs
@@ -32,9 +32,6 @@ module Internal.ST (
32import Internal.Vector 32import Internal.Vector
33import Internal.Matrix 33import Internal.Matrix
34import Internal.Vectorized 34import Internal.Vectorized
35import Data.Vector.Storable(unsafeWith)
36
37
38import Control.Monad.ST(ST, runST) 35import Control.Monad.ST(ST, runST)
39import Foreign.Storable(Storable, peekElemOff, pokeElemOff) 36import Foreign.Storable(Storable, peekElemOff, pokeElemOff)
40 37
diff --git a/packages/base/src/Internal/Sparse.hs b/packages/base/src/Internal/Sparse.hs
index 930bc99..b365c15 100644
--- a/packages/base/src/Internal/Sparse.hs
+++ b/packages/base/src/Internal/Sparse.hs
@@ -14,9 +14,7 @@ import Internal.Vector
14import Internal.Matrix 14import Internal.Matrix
15import Internal.Numeric 15import Internal.Numeric
16import Internal.Container 16import Internal.Container
17import Internal.Tools
18import qualified Data.Vector.Storable as V 17import qualified Data.Vector.Storable as V
19import Data.Vector.Storable(fromList)
20import Data.Function(on) 18import Data.Function(on)
21import Control.Arrow((***)) 19import Control.Arrow((***))
22import Control.Monad(when) 20import Control.Monad(when)
diff --git a/packages/base/src/Internal/Static.hs b/packages/base/src/Internal/Static.hs
index 48327e5..01c2205 100644
--- a/packages/base/src/Internal/Static.hs
+++ b/packages/base/src/Internal/Static.hs
@@ -25,8 +25,8 @@ module Internal.Static where
25 25
26import GHC.TypeLits 26import GHC.TypeLits
27import qualified Numeric.LinearAlgebra as LA 27import qualified Numeric.LinearAlgebra as LA
28import Numeric.LinearAlgebra hiding (konst,size) 28import Numeric.LinearAlgebra hiding (konst,size,R,C)
29import Internal.Vector as D 29import Internal.Vector as D hiding (R,C)
30import Internal.ST 30import Internal.ST
31import Data.Proxy(Proxy) 31import Data.Proxy(Proxy)
32import Foreign.Storable(Storable) 32import Foreign.Storable(Storable)
diff --git a/packages/base/src/Internal/Tools.hs b/packages/base/src/Internal/Tools.hs
deleted file mode 100644
index 47115bc..0000000
--- a/packages/base/src/Internal/Tools.hs
+++ /dev/null
@@ -1,61 +0,0 @@
1-- |
2-- Module : Internal.Tools
3-- Copyright : (c) Alberto Ruiz 2007-15
4-- License : BSD3
5-- Maintainer : Alberto Ruiz
6-- Stability : provisional
7--
8
9module Internal.Tools where
10
11import Data.List(transpose,intersperse)
12import Foreign.C.Types(CInt)
13import Data.List.Split
14
15type I = CInt
16
17splitEvery :: Int -> [e] -> [[e]]
18splitEvery = chunksOf
19
20-- | postfix function application (@flip ($)@)
21(//) :: x -> (x -> y) -> y
22infixl 0 //
23(//) = flip ($)
24
25-- | specialized fromIntegral
26fi :: Int -> CInt
27fi = fromIntegral
28
29-- | specialized fromIntegral
30ti :: CInt -> Int
31ti = fromIntegral
32
33-- | obtains the common value of a property of a list
34common :: (Eq a) => (b->a) -> [b] -> Maybe a
35common f = commonval . map f
36 where
37 commonval :: (Eq a) => [a] -> Maybe a
38 commonval [] = Nothing
39 commonval [a] = Just a
40 commonval (a:b:xs) = if a==b then commonval (b:xs) else Nothing
41
42-- | common value with \"adaptable\" 1
43compatdim :: [Int] -> Maybe Int
44compatdim [] = Nothing
45compatdim [a] = Just a
46compatdim (a:b:xs)
47 | a==b = compatdim (b:xs)
48 | a==1 = compatdim (b:xs)
49 | b==1 = compatdim (a:xs)
50 | otherwise = Nothing
51
52-- | Formatting tool
53table :: String -> [[String]] -> String
54table sep as = unlines . map unwords' $ transpose mtp
55 where
56 mt = transpose as
57 longs = map (maximum . map length) mt
58 mtp = zipWith (\a b -> map (pad a) b) longs mt
59 pad n str = replicate (n - length str) ' ' ++ str
60 unwords' = concat . intersperse sep
61
diff --git a/packages/base/src/Internal/Util.hs b/packages/base/src/Internal/Util.hs
index 9900770..e9cf155 100644
--- a/packages/base/src/Internal/Util.hs
+++ b/packages/base/src/Internal/Util.hs
@@ -56,7 +56,6 @@ module Internal.Util(
56 gaussElim 56 gaussElim
57) where 57) where
58 58
59import Internal.Tools
60import Internal.Vector 59import Internal.Vector
61import Internal.Matrix hiding (size) 60import Internal.Matrix hiding (size)
62import Internal.Numeric 61import Internal.Numeric
@@ -76,7 +75,6 @@ import Data.List(intercalate,sortBy)
76import Data.Function(on) 75import Data.Function(on)
77import Control.Arrow((&&&)) 76import Control.Arrow((&&&))
78import Data.Complex 77import Data.Complex
79import Data.Vector.Storable(fromList)
80 78
81type ℝ = Double 79type ℝ = Double
82type ℕ = Int 80type ℕ = Int
diff --git a/packages/base/src/Internal/Vector.hs b/packages/base/src/Internal/Vector.hs
index 27ee13c..0e9161d 100644
--- a/packages/base/src/Internal/Vector.hs
+++ b/packages/base/src/Internal/Vector.hs
@@ -10,38 +10,56 @@
10-- Stability : provisional 10-- Stability : provisional
11-- 11--
12 12
13module Internal.Vector where 13module Internal.Vector(
14 14 I,Z,R,C,
15import Internal.Tools 15 fi,ti,
16import Foreign.Marshal.Array ( peekArray, copyArray, advancePtr ) 16 Vector, fromList, unsafeToForeignPtr, unsafeFromForeignPtr, unsafeWith,
17import Foreign.ForeignPtr ( ForeignPtr, castForeignPtr ) 17 createVector, vec,
18import Foreign.Ptr ( Ptr ) 18 toList, dim, (@>), at', (|>),
19 vjoin, subVector, takesV, idxs,
20 buildVector,
21 asReal, asComplex,
22 toByteString,fromByteString,
23 zipVector, unzipVector, zipVectorWith, unzipVectorWith,
24 foldVector, foldVectorG, foldVectorWithIndex, foldLoop,
25 mapVector, mapVectorM, mapVectorM_,
26 mapVectorWithIndex, mapVectorWithIndexM, mapVectorWithIndexM_
27) where
28
29import Foreign.Marshal.Array
30import Foreign.ForeignPtr
31import Foreign.Ptr
19import Foreign.Storable 32import Foreign.Storable
20 ( Storable, peekElemOff, pokeElemOff, sizeOf ) 33import Foreign.C.Types(CInt)
21import Foreign.C.Types ( CInt ) 34import Data.Int(Int64)
22import Data.Complex ( Complex ) 35import Data.Complex
23import System.IO.Unsafe ( unsafePerformIO ) 36import System.IO.Unsafe(unsafePerformIO)
24import GHC.ForeignPtr ( mallocPlainForeignPtrBytes ) 37import GHC.ForeignPtr(mallocPlainForeignPtrBytes)
25import GHC.Base ( realWorld#, IO(IO), when ) 38import GHC.Base(realWorld#, IO(IO), when)
26import qualified Data.Vector.Storable as Vector 39import qualified Data.Vector.Storable as Vector
27 ( Vector, slice, length ) 40import Data.Vector.Storable(Vector, fromList, unsafeToForeignPtr, unsafeFromForeignPtr, unsafeWith)
28import Data.Vector.Storable
29 ( fromList, unsafeToForeignPtr, unsafeFromForeignPtr, unsafeWith )
30
31 41
32#ifdef BINARY 42#ifdef BINARY
33
34import Data.Binary 43import Data.Binary
35import Control.Monad(replicateM) 44import Control.Monad(replicateM)
36import qualified Data.ByteString.Internal as BS 45import qualified Data.ByteString.Internal as BS
37import Data.Vector.Storable.Internal(updPtr) 46import Data.Vector.Storable.Internal(updPtr)
38import Foreign.Ptr(plusPtr)
39
40#endif 47#endif
41 48
49type I = CInt
50type Z = Int64
51type R = Double
52type C = Complex Double
53
54
55-- | specialized fromIntegral
56fi :: Int -> CInt
57fi = fromIntegral
42 58
59-- | specialized fromIntegral
60ti :: CInt -> Int
61ti = fromIntegral
43 62
44type Vector = Vector.Vector
45 63
46-- | Number of elements 64-- | Number of elements
47dim :: (Storable t) => Vector t -> Int 65dim :: (Storable t) => Vector t -> Int
diff --git a/packages/base/src/Internal/Vectorized.hs b/packages/base/src/Internal/Vectorized.hs
index ddb14c9..b9b8239 100644
--- a/packages/base/src/Internal/Vectorized.hs
+++ b/packages/base/src/Internal/Vectorized.hs
@@ -14,10 +14,8 @@
14 14
15module Internal.Vectorized where 15module Internal.Vectorized where
16 16
17import Internal.Tools
18import Internal.Vector 17import Internal.Vector
19import Internal.Devel 18import Internal.Devel
20
21import Data.Complex 19import Data.Complex
22import Foreign.Marshal.Alloc(free,malloc) 20import Foreign.Marshal.Alloc(free,malloc)
23import Foreign.Marshal.Array(newArray,copyArray) 21import Foreign.Marshal.Array(newArray,copyArray)
@@ -26,9 +24,8 @@ import Foreign.Storable(peek,Storable)
26import Foreign.C.Types 24import Foreign.C.Types
27import Foreign.C.String 25import Foreign.C.String
28import System.IO.Unsafe(unsafePerformIO) 26import System.IO.Unsafe(unsafePerformIO)
29
30import Control.Monad(when) 27import Control.Monad(when)
31import Data.Vector.Storable ( unsafeWith ) 28
32 29
33 30
34fromei x = fromIntegral (fromEnum x) :: CInt 31fromei x = fromIntegral (fromEnum x) :: CInt
diff --git a/packages/base/src/Numeric/LinearAlgebra/Data.hs b/packages/base/src/Numeric/LinearAlgebra/Data.hs
index 196ada9..06485e6 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Data.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Data.hs
@@ -88,12 +88,11 @@ module Numeric.LinearAlgebra.Data(
88 separable, 88 separable,
89 fromArray2D, 89 fromArray2D,
90 module Data.Complex, 90 module Data.Complex,
91 I,F, 91 R,C,I,Z,F,
92 Vector, Matrix, GMatrix, nRows, nCols 92 Vector, Matrix, GMatrix, nRows, nCols
93 93
94) where 94) where
95 95
96import Internal.Tools
97import Internal.Vector 96import Internal.Vector
98import Internal.Vectorized 97import Internal.Vectorized
99import Internal.Matrix hiding (size) 98import Internal.Matrix hiding (size)
@@ -105,6 +104,5 @@ import Internal.Util hiding ((&),(#))
105import Data.Complex 104import Data.Complex
106import Internal.Sparse 105import Internal.Sparse
107import Internal.Modular 106import Internal.Modular
108import Data.Vector.Storable(fromList)
109 107
110 108
diff --git a/packages/base/src/Numeric/LinearAlgebra/Devel.hs b/packages/base/src/Numeric/LinearAlgebra/Devel.hs
index 4d5b5cb..1a70663 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Devel.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Devel.hs
@@ -68,7 +68,6 @@ module Numeric.LinearAlgebra.Devel(
68 68
69) where 69) where
70 70
71import Internal.Tools
72import Internal.Foreign 71import Internal.Foreign
73import Internal.Devel 72import Internal.Devel
74import Internal.ST 73import Internal.ST
@@ -76,5 +75,4 @@ import Internal.Vector
76import Internal.Matrix 75import Internal.Matrix
77import Internal.Element 76import Internal.Element
78import Internal.Sparse 77import Internal.Sparse
79import Data.Vector.Storable (unsafeToForeignPtr, unsafeFromForeignPtr )
80 78
diff --git a/packages/base/src/Numeric/LinearAlgebra/Static.hs b/packages/base/src/Numeric/LinearAlgebra/Static.hs
index 04c4151..dee5b2c 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Static.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Static.hs
@@ -65,7 +65,7 @@ import Numeric.LinearAlgebra hiding (
65 row,col,vector,matrix,linspace,toRows,toColumns, 65 row,col,vector,matrix,linspace,toRows,toColumns,
66 (<\>),fromList,takeDiag,svd,eig,eigSH,eigSH', 66 (<\>),fromList,takeDiag,svd,eig,eigSH,eigSH',
67 eigenvalues,eigenvaluesSH,eigenvaluesSH',build, 67 eigenvalues,eigenvaluesSH,eigenvaluesSH',build,
68 qr,size,app,mul,dot,chol,range) 68 qr,size,app,mul,dot,chol,range,R,C)
69import qualified Numeric.LinearAlgebra as LA 69import qualified Numeric.LinearAlgebra as LA
70import Data.Proxy(Proxy) 70import Data.Proxy(Proxy)
71import Internal.Static 71import Internal.Static
diff --git a/packages/base/src/Numeric/Vector.hs b/packages/base/src/Numeric/Vector.hs
index 7525890..076f485 100644
--- a/packages/base/src/Numeric/Vector.hs
+++ b/packages/base/src/Numeric/Vector.hs
@@ -19,11 +19,9 @@
19 19
20module Numeric.Vector () where 20module Numeric.Vector () where
21 21
22import Internal.Tools
23import Internal.Vectorized 22import Internal.Vectorized
24import Internal.Vector 23import Internal.Vector
25import Internal.Numeric 24import Internal.Numeric
26import Data.Vector.Storable(fromList)
27import Internal.Conversion 25import Internal.Conversion
28 26
29------------------------------------------------------------------- 27-------------------------------------------------------------------