summaryrefslogtreecommitdiff
path: root/packages/hmatrix/src/Numeric/GSL
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2014-05-21 09:57:03 +0200
committerAlberto Ruiz <aruiz@um.es>2014-05-21 09:57:03 +0200
commite07c3dee7235496b71a89233106d93f6cc94ada1 (patch)
tree1ad29c3fc93ee076ad68e3ee759c9a3357f9cd5b /packages/hmatrix/src/Numeric/GSL
parent92de588b82945bb251a056c34a8ef0c00cb00e5a (diff)
Numeric.Container and Numeric.LinearAlgebra moved to base
Diffstat (limited to 'packages/hmatrix/src/Numeric/GSL')
-rw-r--r--packages/hmatrix/src/Numeric/GSL/Fitting.hs2
-rw-r--r--packages/hmatrix/src/Numeric/GSL/IO.hs42
-rw-r--r--packages/hmatrix/src/Numeric/GSL/LinearAlgebra.hs38
-rw-r--r--packages/hmatrix/src/Numeric/GSL/Random.hs84
-rw-r--r--packages/hmatrix/src/Numeric/GSL/Vector.hs107
5 files changed, 267 insertions, 6 deletions
diff --git a/packages/hmatrix/src/Numeric/GSL/Fitting.hs b/packages/hmatrix/src/Numeric/GSL/Fitting.hs
index 0a92373..93fb281 100644
--- a/packages/hmatrix/src/Numeric/GSL/Fitting.hs
+++ b/packages/hmatrix/src/Numeric/GSL/Fitting.hs
@@ -116,7 +116,7 @@ err (model,deriv) dat vsol = zip sol errs where
116 dof = length dat - (rows cov) 116 dof = length dat - (rows cov)
117 chi = norm2 (fromList $ cost (resMs model) dat sol) 117 chi = norm2 (fromList $ cost (resMs model) dat sol)
118 js = fromLists $ jacobian (resDs deriv) dat sol 118 js = fromLists $ jacobian (resDs deriv) dat sol
119 cov = inv $ trans js <> js 119 cov = inv $ trans js <.> js
120 errs = toList $ scalar c * sqrt (takeDiag cov) 120 errs = toList $ scalar c * sqrt (takeDiag cov)
121 121
122 122
diff --git a/packages/hmatrix/src/Numeric/GSL/IO.hs b/packages/hmatrix/src/Numeric/GSL/IO.hs
new file mode 100644
index 0000000..0d6031a
--- /dev/null
+++ b/packages/hmatrix/src/Numeric/GSL/IO.hs
@@ -0,0 +1,42 @@
1-----------------------------------------------------------------------------
2-- |
3-- Module : Numeric.GSL.IO
4-- Copyright : (c) Alberto Ruiz 2007-14
5-- License : GPL
6-- Maintainer : Alberto Ruiz
7-- Stability : provisional
8--
9-----------------------------------------------------------------------------
10
11module Numeric.GSL.IO (
12 saveMatrix,
13 fwriteVector, freadVector, fprintfVector, fscanfVector,
14 fileDimensions, loadMatrix, fromFile
15) where
16
17import Data.Packed
18import Numeric.GSL.Vector
19import System.Process(readProcess)
20
21
22{- | obtains the number of rows and columns in an ASCII data file
23 (provisionally using unix's wc).
24-}
25fileDimensions :: FilePath -> IO (Int,Int)
26fileDimensions fname = do
27 wcres <- readProcess "wc" ["-w",fname] ""
28 contents <- readFile fname
29 let tot = read . head . words $ wcres
30 c = length . head . dropWhile null . map words . lines $ contents
31 if tot > 0
32 then return (tot `div` c, c)
33 else return (0,0)
34
35-- | Loads a matrix from an ASCII file formatted as a 2D table.
36loadMatrix :: FilePath -> IO (Matrix Double)
37loadMatrix file = fromFile file =<< fileDimensions file
38
39-- | Loads a matrix from an ASCII file (the number of rows and columns must be known in advance).
40fromFile :: FilePath -> (Int,Int) -> IO (Matrix Double)
41fromFile filename (r,c) = reshape c `fmap` fscanfVector filename (r*c)
42
diff --git a/packages/hmatrix/src/Numeric/GSL/LinearAlgebra.hs b/packages/hmatrix/src/Numeric/GSL/LinearAlgebra.hs
index 8bd0cc2..17e2258 100644
--- a/packages/hmatrix/src/Numeric/GSL/LinearAlgebra.hs
+++ b/packages/hmatrix/src/Numeric/GSL/LinearAlgebra.hs
@@ -9,13 +9,13 @@
9----------------------------------------------------------------------------- 9-----------------------------------------------------------------------------
10 10
11module Numeric.GSL.LinearAlgebra ( 11module Numeric.GSL.LinearAlgebra (
12 randomVector, 12 RandDist(..), randomVector,
13 saveMatrix, 13 saveMatrix,
14 fwriteVector, freadVector, fprintfVector, fscanfVector 14 fwriteVector, freadVector, fprintfVector, fscanfVector,
15 fileDimensions, loadMatrix, fromFile
15) where 16) where
16 17
17import Data.Packed 18import Data.Packed
18import Numeric.LinearAlgebra.Base(RandDist(..))
19import Numeric.GSL.Internal hiding (TV,TM,TCV,TCM) 19import Numeric.GSL.Internal hiding (TV,TM,TCV,TCM)
20 20
21import Foreign.Marshal.Alloc(free) 21import Foreign.Marshal.Alloc(free)
@@ -23,11 +23,16 @@ import Foreign.Ptr(Ptr)
23import Foreign.C.Types 23import Foreign.C.Types
24import Foreign.C.String(newCString) 24import Foreign.C.String(newCString)
25import System.IO.Unsafe(unsafePerformIO) 25import System.IO.Unsafe(unsafePerformIO)
26import System.Process(readProcess)
26 27
27fromei x = fromIntegral (fromEnum x) :: CInt 28fromei x = fromIntegral (fromEnum x) :: CInt
28 29
29----------------------------------------------------------------------- 30-----------------------------------------------------------------------
30 31
32data RandDist = Uniform -- ^ uniform distribution in [0,1)
33 | Gaussian -- ^ normal distribution with mean zero and standard deviation one
34 deriving Enum
35
31-- | Obtains a vector of pseudorandom elements from the the mt19937 generator in GSL, with a given seed. Use randomIO to get a random seed. 36-- | Obtains a vector of pseudorandom elements from the the mt19937 generator in GSL, with a given seed. Use randomIO to get a random seed.
32randomVector :: Int -- ^ seed 37randomVector :: Int -- ^ seed
33 -> RandDist -- ^ distribution 38 -> RandDist -- ^ distribution
@@ -35,10 +40,10 @@ randomVector :: Int -- ^ seed
35 -> Vector Double 40 -> Vector Double
36randomVector seed dist n = unsafePerformIO $ do 41randomVector seed dist n = unsafePerformIO $ do
37 r <- createVector n 42 r <- createVector n
38 app1 (c_random_vector_GSL (fi seed) ((fi.fromEnum) dist)) vec r "randomVectorGSL" 43 app1 (c_random_vector (fi seed) ((fi.fromEnum) dist)) vec r "randomVector"
39 return r 44 return r
40 45
41foreign import ccall unsafe "random_vector_GSL" c_random_vector_GSL :: CInt -> CInt -> TV 46foreign import ccall unsafe "random_vector" c_random_vector :: CInt -> CInt -> TV
42 47
43-------------------------------------------------------------------------------- 48--------------------------------------------------------------------------------
44 49
@@ -105,3 +110,26 @@ type PD = Ptr Double --
105type TV = CInt -> PD -> IO CInt -- 110type TV = CInt -> PD -> IO CInt --
106type TM = CInt -> CInt -> PD -> IO CInt -- 111type TM = CInt -> CInt -> PD -> IO CInt --
107 112
113--------------------------------------------------------------------------------
114
115{- | obtains the number of rows and columns in an ASCII data file
116 (provisionally using unix's wc).
117-}
118fileDimensions :: FilePath -> IO (Int,Int)
119fileDimensions fname = do
120 wcres <- readProcess "wc" ["-w",fname] ""
121 contents <- readFile fname
122 let tot = read . head . words $ wcres
123 c = length . head . dropWhile null . map words . lines $ contents
124 if tot > 0
125 then return (tot `div` c, c)
126 else return (0,0)
127
128-- | Loads a matrix from an ASCII file formatted as a 2D table.
129loadMatrix :: FilePath -> IO (Matrix Double)
130loadMatrix file = fromFile file =<< fileDimensions file
131
132-- | Loads a matrix from an ASCII file (the number of rows and columns must be known in advance).
133fromFile :: FilePath -> (Int,Int) -> IO (Matrix Double)
134fromFile filename (r,c) = reshape c `fmap` fscanfVector filename (r*c)
135
diff --git a/packages/hmatrix/src/Numeric/GSL/Random.hs b/packages/hmatrix/src/Numeric/GSL/Random.hs
new file mode 100644
index 0000000..2872b17
--- /dev/null
+++ b/packages/hmatrix/src/Numeric/GSL/Random.hs
@@ -0,0 +1,84 @@
1-----------------------------------------------------------------------------
2-- |
3-- Module : Numeric.GSL.Random
4-- Copyright : (c) Alberto Ruiz 2009-14
5-- License : GPL
6--
7-- Maintainer : Alberto Ruiz
8-- Stability : provisional
9--
10-- Random vectors and matrices.
11--
12-----------------------------------------------------------------------------
13
14module Numeric.GSL.Random (
15 Seed,
16 RandDist(..),
17 randomVector,
18 gaussianSample,
19 uniformSample,
20 rand, randn
21) where
22
23import Numeric.GSL.Vector
24import Numeric.Container
25import Numeric.LinearAlgebra(Seed,RandDist(..),cholSH)
26import System.Random(randomIO)
27
28
29
30
31-- | Obtains a matrix whose rows are pseudorandom samples from a multivariate
32-- Gaussian distribution.
33gaussianSample :: Seed
34 -> Int -- ^ number of rows
35 -> Vector Double -- ^ mean vector
36 -> Matrix Double -- ^ covariance matrix
37 -> Matrix Double -- ^ result
38gaussianSample seed n med cov = m where
39 c = dim med
40 meds = konst' 1 n `outer` med
41 rs = reshape c $ randomVector seed Gaussian (c * n)
42 m = rs `mXm` cholSH cov `add` meds
43
44-- | Obtains a matrix whose rows are pseudorandom samples from a multivariate
45-- uniform distribution.
46uniformSample :: Seed
47 -> Int -- ^ number of rows
48 -> [(Double,Double)] -- ^ ranges for each column
49 -> Matrix Double -- ^ result
50uniformSample seed n rgs = m where
51 (as,bs) = unzip rgs
52 a = fromList as
53 cs = zipWith subtract as bs
54 d = dim a
55 dat = toRows $ reshape n $ randomVector seed Uniform (n*d)
56 am = konst' 1 n `outer` a
57 m = fromColumns (zipWith scale cs dat) `add` am
58
59-- | pseudorandom matrix with uniform elements between 0 and 1
60randm :: RandDist
61 -> Int -- ^ rows
62 -> Int -- ^ columns
63 -> IO (Matrix Double)
64randm d r c = do
65 seed <- randomIO
66 return (reshape c $ randomVector seed d (r*c))
67
68-- | pseudorandom matrix with uniform elements between 0 and 1
69rand :: Int -> Int -> IO (Matrix Double)
70rand = randm Uniform
71
72{- | pseudorandom matrix with normal elements
73
74>>> x <- randn 3 5
75>>> disp 3 x
763x5
770.386 -1.141 0.491 -0.510 1.512
780.069 -0.919 1.022 -0.181 0.745
790.313 -0.670 -0.097 -1.575 -0.583
80
81-}
82randn :: Int -> Int -> IO (Matrix Double)
83randn = randm Gaussian
84
diff --git a/packages/hmatrix/src/Numeric/GSL/Vector.hs b/packages/hmatrix/src/Numeric/GSL/Vector.hs
new file mode 100644
index 0000000..af79f32
--- /dev/null
+++ b/packages/hmatrix/src/Numeric/GSL/Vector.hs
@@ -0,0 +1,107 @@
1-----------------------------------------------------------------------------
2-- |
3-- Module : Numeric.GSL.Vector
4-- Copyright : (c) Alberto Ruiz 2007-14
5-- License : GPL
6-- Maintainer : Alberto Ruiz
7-- Stability : provisional
8--
9-----------------------------------------------------------------------------
10
11module Numeric.GSL.Vector (
12 randomVector,
13 saveMatrix,
14 fwriteVector, freadVector, fprintfVector, fscanfVector
15) where
16
17import Data.Packed
18import Numeric.LinearAlgebra(RandDist(..))
19import Numeric.GSL.Internal hiding (TV,TM,TCV,TCM)
20
21import Foreign.Marshal.Alloc(free)
22import Foreign.Ptr(Ptr)
23import Foreign.C.Types
24import Foreign.C.String(newCString)
25import System.IO.Unsafe(unsafePerformIO)
26
27fromei x = fromIntegral (fromEnum x) :: CInt
28
29-----------------------------------------------------------------------
30
31-- | Obtains a vector of pseudorandom elements from the the mt19937 generator in GSL, with a given seed. Use randomIO to get a random seed.
32randomVector :: Int -- ^ seed
33 -> RandDist -- ^ distribution
34 -> Int -- ^ vector size
35 -> Vector Double
36randomVector seed dist n = unsafePerformIO $ do
37 r <- createVector n
38 app1 (c_random_vector_GSL (fi seed) ((fi.fromEnum) dist)) vec r "randomVectorGSL"
39 return r
40
41foreign import ccall unsafe "random_vector_GSL" c_random_vector_GSL :: CInt -> CInt -> TV
42
43--------------------------------------------------------------------------------
44
45-- | Saves a matrix as 2D ASCII table.
46saveMatrix :: FilePath
47 -> String -- ^ format (%f, %g, %e)
48 -> Matrix Double
49 -> IO ()
50saveMatrix filename fmt m = do
51 charname <- newCString filename
52 charfmt <- newCString fmt
53 let o = if orderOf m == RowMajor then 1 else 0
54 app1 (matrix_fprintf charname charfmt o) mat m "matrix_fprintf"
55 free charname
56 free charfmt
57
58foreign import ccall unsafe "matrix_fprintf" matrix_fprintf :: Ptr CChar -> Ptr CChar -> CInt -> TM
59
60--------------------------------------------------------------------------------
61
62-- | Loads a vector from an ASCII file (the number of elements must be known in advance).
63fscanfVector :: FilePath -> Int -> IO (Vector Double)
64fscanfVector filename n = do
65 charname <- newCString filename
66 res <- createVector n
67 app1 (gsl_vector_fscanf charname) vec res "gsl_vector_fscanf"
68 free charname
69 return res
70
71foreign import ccall unsafe "vector_fscanf" gsl_vector_fscanf:: Ptr CChar -> TV
72
73-- | Saves the elements of a vector, with a given format (%f, %e, %g), to an ASCII file.
74fprintfVector :: FilePath -> String -> Vector Double -> IO ()
75fprintfVector filename fmt v = do
76 charname <- newCString filename
77 charfmt <- newCString fmt
78 app1 (gsl_vector_fprintf charname charfmt) vec v "gsl_vector_fprintf"
79 free charname
80 free charfmt
81
82foreign import ccall unsafe "vector_fprintf" gsl_vector_fprintf :: Ptr CChar -> Ptr CChar -> TV
83
84-- | Loads a vector from a binary file (the number of elements must be known in advance).
85freadVector :: FilePath -> Int -> IO (Vector Double)
86freadVector filename n = do
87 charname <- newCString filename
88 res <- createVector n
89 app1 (gsl_vector_fread charname) vec res "gsl_vector_fread"
90 free charname
91 return res
92
93foreign import ccall unsafe "vector_fread" gsl_vector_fread:: Ptr CChar -> TV
94
95-- | Saves the elements of a vector to a binary file.
96fwriteVector :: FilePath -> Vector Double -> IO ()
97fwriteVector filename v = do
98 charname <- newCString filename
99 app1 (gsl_vector_fwrite charname) vec v "gsl_vector_fwrite"
100 free charname
101
102foreign import ccall unsafe "vector_fwrite" gsl_vector_fwrite :: Ptr CChar -> TV
103
104type PD = Ptr Double --
105type TV = CInt -> PD -> IO CInt --
106type TM = CInt -> CInt -> PD -> IO CInt --
107