summaryrefslogtreecommitdiff
path: root/lib/Data
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Data')
-rw-r--r--lib/Data/Packed/Internal/Matrix.hs9
-rw-r--r--lib/Data/Packed/Internal/Vector.hs47
-rw-r--r--lib/Data/Packed/Vector.hs6
3 files changed, 51 insertions, 11 deletions
diff --git a/lib/Data/Packed/Internal/Matrix.hs b/lib/Data/Packed/Internal/Matrix.hs
index ccc652a..01d2ccf 100644
--- a/lib/Data/Packed/Internal/Matrix.hs
+++ b/lib/Data/Packed/Internal/Matrix.hs
@@ -22,7 +22,6 @@ import Data.Packed.Internal.Vector
22 22
23import Foreign hiding (xor) 23import Foreign hiding (xor)
24import Complex 24import Complex
25import Foreign.C.String
26import Foreign.C.Types 25import Foreign.C.Types
27 26
28----------------------------------------------------------------- 27-----------------------------------------------------------------
@@ -353,10 +352,4 @@ fromComplex z = (r,i) where
353 352
354-- | loads a matrix from an ASCII file (the number of rows and columns must be known in advance). 353-- | loads a matrix from an ASCII file (the number of rows and columns must be known in advance).
355fromFile :: FilePath -> (Int,Int) -> IO (Matrix Double) 354fromFile :: FilePath -> (Int,Int) -> IO (Matrix Double)
356fromFile filename (r,c) = do 355fromFile filename (r,c) = reshape c `fmap` fscanfVector filename (r*c)
357 charname <- newCString filename
358 res <- createMatrix RowMajor r c
359 app1 (c_gslReadMatrix charname) mat res "gslReadMatrix"
360 free charname
361 return res
362foreign import ccall "matrix_fscanf" c_gslReadMatrix:: Ptr CChar -> TM
diff --git a/lib/Data/Packed/Internal/Vector.hs b/lib/Data/Packed/Internal/Vector.hs
index 1b572a5..5784861 100644
--- a/lib/Data/Packed/Internal/Vector.hs
+++ b/lib/Data/Packed/Internal/Vector.hs
@@ -18,7 +18,8 @@ module Data.Packed.Internal.Vector where
18 18
19import Data.Packed.Internal.Common 19import Data.Packed.Internal.Common
20import Foreign 20import Foreign
21import Foreign.C.Types(CInt) 21import Foreign.C.String
22import Foreign.C.Types(CInt,CChar)
22import Complex 23import Complex
23import Control.Monad(when) 24import Control.Monad(when)
24 25
@@ -255,3 +256,47 @@ foldVectorG f s0 v = foldLoop g s0 (dim v)
255 where g !k !s = f k (at' v) s 256 where g !k !s = f k (at' v) s
256 {-# INLINE g #-} -- Thanks to Ryan Ingram (http://permalink.gmane.org/gmane.comp.lang.haskell.cafe/46479) 257 {-# INLINE g #-} -- Thanks to Ryan Ingram (http://permalink.gmane.org/gmane.comp.lang.haskell.cafe/46479)
257{-# INLINE foldVectorG #-} 258{-# INLINE foldVectorG #-}
259
260-------------------------------------------------------------------
261
262-- | Loads a vector from an ASCII file (the number of elements must be known in advance).
263fscanfVector :: FilePath -> Int -> IO (Vector Double)
264fscanfVector filename n = do
265 charname <- newCString filename
266 res <- createVector n
267 app1 (gsl_vector_fscanf charname) vec res "gsl_vector_fscanf"
268 free charname
269 return res
270
271foreign import ccall "vector_fscanf" gsl_vector_fscanf:: Ptr CChar -> TV
272
273-- | Saves the elements of a vector, with a given format (%f, %e, %g), to an ASCII file.
274fprintfVector :: FilePath -> String -> Vector Double -> IO ()
275fprintfVector filename fmt v = do
276 charname <- newCString filename
277 charfmt <- newCString fmt
278 app1 (gsl_vector_fprintf charname charfmt) vec v "gsl_vector_fprintf"
279 free charname
280 free charfmt
281
282foreign import ccall "vector_fprintf" gsl_vector_fprintf :: Ptr CChar -> Ptr CChar -> TV
283
284-- | Loads a vector from a binary file (the number of elements must be known in advance).
285freadVector :: FilePath -> Int -> IO (Vector Double)
286freadVector filename n = do
287 charname <- newCString filename
288 res <- createVector n
289 app1 (gsl_vector_fread charname) vec res "gsl_vector_fread"
290 free charname
291 return res
292
293foreign import ccall "vector_fread" gsl_vector_fread:: Ptr CChar -> TV
294
295-- | Saves the elements of a vector to a binary file.
296fwriteVector :: FilePath -> Vector Double -> IO ()
297fwriteVector filename v = do
298 charname <- newCString filename
299 app1 (gsl_vector_fwrite charname) vec v "gsl_vector_fwrite"
300 free charname
301
302foreign import ccall "vector_fwrite" gsl_vector_fwrite :: Ptr CChar -> TV
diff --git a/lib/Data/Packed/Vector.hs b/lib/Data/Packed/Vector.hs
index e53d455..c657e10 100644
--- a/lib/Data/Packed/Vector.hs
+++ b/lib/Data/Packed/Vector.hs
@@ -8,7 +8,7 @@
8-- Stability : provisional 8-- Stability : provisional
9-- Portability : portable 9-- Portability : portable
10-- 10--
11-- A representation of 1D arrays suitable for numeric computations using external libraries. 11-- 1D arrays suitable for numeric computations using external libraries.
12-- 12--
13----------------------------------------------------------------------------- 13-----------------------------------------------------------------------------
14 14
@@ -19,8 +19,10 @@ module Data.Packed.Vector (
19 subVector, join, 19 subVector, join,
20 constant, linspace, 20 constant, linspace,
21 vectorMax, vectorMin, vectorMaxIndex, vectorMinIndex, 21 vectorMax, vectorMin, vectorMaxIndex, vectorMinIndex,
22 mapVector, zipVector,
23 fscanfVector, fprintfVector, freadVector, fwriteVector,
22 liftVector, liftVector2, 24 liftVector, liftVector2,
23 foldLoop, foldVector, foldVectorG, mapVector, zipVector 25 foldLoop, foldVector, foldVectorG
24) where 26) where
25 27
26import Data.Packed.Internal 28import Data.Packed.Internal