diff options
author | Alberto Ruiz <aruiz@um.es> | 2007-09-12 19:09:47 +0000 |
---|---|---|
committer | Alberto Ruiz <aruiz@um.es> | 2007-09-12 19:09:47 +0000 |
commit | 0ff13d993b880739295de343bca62f06fac5ca0c (patch) | |
tree | 252a51b4314c19c04a9eda87973eeaae63167a41 /lib/Data/Packed/Internal/Vector.hs | |
parent | cd937c2be2900b8f13506d9ae7c731ad43d74e05 (diff) |
documentation
Diffstat (limited to 'lib/Data/Packed/Internal/Vector.hs')
-rw-r--r-- | lib/Data/Packed/Internal/Vector.hs | 62 |
1 files changed, 51 insertions, 11 deletions
diff --git a/lib/Data/Packed/Internal/Vector.hs b/lib/Data/Packed/Internal/Vector.hs index 0d9dc70..f0ef8b6 100644 --- a/lib/Data/Packed/Internal/Vector.hs +++ b/lib/Data/Packed/Internal/Vector.hs | |||
@@ -12,6 +12,7 @@ | |||
12 | -- Vector implementation | 12 | -- Vector implementation |
13 | -- | 13 | -- |
14 | ----------------------------------------------------------------------------- | 14 | ----------------------------------------------------------------------------- |
15 | -- #hide | ||
15 | 16 | ||
16 | module Data.Packed.Internal.Vector where | 17 | module Data.Packed.Internal.Vector where |
17 | 18 | ||
@@ -24,34 +25,39 @@ import Debug.Trace(trace) | |||
24 | import Foreign.C.String(peekCString) | 25 | import Foreign.C.String(peekCString) |
25 | import Foreign.C.Types | 26 | import Foreign.C.Types |
26 | 27 | ||
27 | 28 | -- | A one-dimensional array of objects stored in a contiguous memory block. | |
28 | data Vector t = V { dim :: Int | 29 | data Vector t = V { dim :: Int -- ^ number of elements |
29 | , fptr :: ForeignPtr t | 30 | , fptr :: ForeignPtr t -- ^ foreign pointer to the memory block |
30 | , ptr :: Ptr t | 31 | , ptr :: Ptr t -- ^ ordinary pointer to the actual starting address (usually the same) |
31 | } | 32 | } |
32 | 33 | ||
34 | -- | check the error code and touch foreign ptr of vector arguments (if any) | ||
33 | check :: String -> [Vector a] -> IO Int -> IO () | 35 | check :: String -> [Vector a] -> IO Int -> IO () |
34 | check msg ls f = do | 36 | check msg ls f = do |
35 | err <- f | 37 | err <- f |
36 | when (err/=0) $ if err > 999 -- FIXME, it should be 1024 | 38 | when (err/=0) $ if err > 1024 |
37 | then (error (msg++": "++errorCode err)) | 39 | then (error (msg++": "++errorCode err)) -- our errors |
38 | else do | 40 | else do -- GSL errors |
39 | ps <- gsl_strerror err | 41 | ps <- gsl_strerror err |
40 | s <- peekCString ps | 42 | s <- peekCString ps |
41 | error (msg++": "++s) | 43 | error (msg++": "++s) |
42 | mapM_ (touchForeignPtr . fptr) ls | 44 | mapM_ (touchForeignPtr . fptr) ls |
43 | return () | 45 | return () |
44 | 46 | ||
47 | -- | description of GSL error codes | ||
45 | foreign import ccall "aux.h gsl_strerror" gsl_strerror :: Int -> IO (Ptr CChar) | 48 | foreign import ccall "aux.h gsl_strerror" gsl_strerror :: Int -> IO (Ptr CChar) |
46 | 49 | ||
50 | -- | signature of foreign functions admitting C-style vectors | ||
47 | type Vc t s = Int -> Ptr t -> s | 51 | type Vc t s = Int -> Ptr t -> s |
48 | -- not yet admitted by my haddock version | 52 | -- not yet admitted by my haddock version |
49 | -- infixr 5 :> | 53 | -- infixr 5 :> |
50 | -- type t :> s = Vc t s | 54 | -- type t :> s = Vc t s |
51 | 55 | ||
56 | -- | adaptation of our vectors to be admitted by foreign functions: @f \/\/ vec v@ | ||
52 | vec :: Vector t -> (Vc t s) -> s | 57 | vec :: Vector t -> (Vc t s) -> s |
53 | vec v f = f (dim v) (ptr v) | 58 | vec v f = f (dim v) (ptr v) |
54 | 59 | ||
60 | -- | allocates memory for a new vector | ||
55 | createVector :: Storable a => Int -> IO (Vector a) | 61 | createVector :: Storable a => Int -> IO (Vector a) |
56 | createVector n = do | 62 | createVector n = do |
57 | when (n <= 0) $ error ("trying to createVector of dim "++show n) | 63 | when (n <= 0) $ error ("trying to createVector of dim "++show n) |
@@ -60,6 +66,12 @@ createVector n = do | |||
60 | --putStrLn ("\n---------> V"++show n) | 66 | --putStrLn ("\n---------> V"++show n) |
61 | return $ V n fp p | 67 | return $ V n fp p |
62 | 68 | ||
69 | {- | creates a Vector from a list: | ||
70 | |||
71 | @> fromList [2,3,5,7] | ||
72 | 4 |> [2.0,3.0,5.0,7.0]@ | ||
73 | |||
74 | -} | ||
63 | fromList :: Storable a => [a] -> Vector a | 75 | fromList :: Storable a => [a] -> Vector a |
64 | fromList l = unsafePerformIO $ do | 76 | fromList l = unsafePerformIO $ do |
65 | v <- createVector (length l) | 77 | v <- createVector (length l) |
@@ -67,14 +79,25 @@ fromList l = unsafePerformIO $ do | |||
67 | f // vec v // check "fromList" [] | 79 | f // vec v // check "fromList" [] |
68 | return v | 80 | return v |
69 | 81 | ||
82 | {- | extracts the Vector elements to a list | ||
83 | |||
84 | @> toList (linspace 5 (1,10)) | ||
85 | [1.0,3.25,5.5,7.75,10.0]@ | ||
86 | |||
87 | -} | ||
70 | toList :: Storable a => Vector a -> [a] | 88 | toList :: Storable a => Vector a -> [a] |
71 | toList v = unsafePerformIO $ peekArray (dim v) (ptr v) | 89 | toList v = unsafePerformIO $ peekArray (dim v) (ptr v) |
72 | 90 | ||
91 | -- | an alternative to 'fromList' with explicit dimension, used also in the instances for Show (Vector a). | ||
92 | (|>) :: (Storable a) => Int -> [a] -> Vector a | ||
93 | infixl 9 |> | ||
73 | n |> l = if length l == n then fromList l else error "|> with wrong size" | 94 | n |> l = if length l == n then fromList l else error "|> with wrong size" |
74 | 95 | ||
96 | -- | access to Vector elements without range checking | ||
75 | at' :: Storable a => Vector a -> Int -> a | 97 | at' :: Storable a => Vector a -> Int -> a |
76 | at' v n = unsafePerformIO $ peekElemOff (ptr v) n | 98 | at' v n = unsafePerformIO $ peekElemOff (ptr v) n |
77 | 99 | ||
100 | -- | access to Vector elements with range checking. | ||
78 | at :: Storable a => Vector a -> Int -> a | 101 | at :: Storable a => Vector a -> Int -> a |
79 | at v n | n >= 0 && n < dim v = at' v n | 102 | at v n | n >= 0 && n < dim v = at' v n |
80 | | otherwise = error "vector index out of range" | 103 | | otherwise = error "vector index out of range" |
@@ -82,9 +105,14 @@ at v n | n >= 0 && n < dim v = at' v n | |||
82 | instance (Show a, Storable a) => (Show (Vector a)) where | 105 | instance (Show a, Storable a) => (Show (Vector a)) where |
83 | show v = (show (dim v))++" |> " ++ show (toList v) | 106 | show v = (show (dim v))++" |> " ++ show (toList v) |
84 | 107 | ||
85 | -- | creates a Vector taking a number of consecutive toList from another Vector | 108 | {- | takes a number of consecutive elements from a Vector |
109 | |||
110 | @> subVector 2 3 (fromList [1..10]) | ||
111 | 3 |> [3.0,4.0,5.0]@ | ||
112 | |||
113 | -} | ||
86 | subVector :: Storable t => Int -- ^ index of the starting element | 114 | subVector :: Storable t => Int -- ^ index of the starting element |
87 | -> Int -- ^ number of toList to extract | 115 | -> Int -- ^ number of elements to extract |
88 | -> Vector t -- ^ source | 116 | -> Vector t -- ^ source |
89 | -> Vector t -- ^ result | 117 | -> Vector t -- ^ result |
90 | subVector k l (v@V {dim=n, ptr=p, fptr=fp}) | 118 | subVector k l (v@V {dim=n, ptr=p, fptr=fp}) |
@@ -100,13 +128,23 @@ subVector' k l (v@V {dim=n, ptr=p, fptr=fp}) | |||
100 | | otherwise = v {dim=l, ptr=advancePtr p k} | 128 | | otherwise = v {dim=l, ptr=advancePtr p k} |
101 | 129 | ||
102 | 130 | ||
103 | -- | Reads a vector position. | 131 | {- | Reads a vector position: |
132 | |||
133 | @> fromList [0..9] \@\> 7 | ||
134 | 7.0@ | ||
135 | |||
136 | -} | ||
104 | (@>) :: Storable t => Vector t -> Int -> t | 137 | (@>) :: Storable t => Vector t -> Int -> t |
105 | infixl 9 @> | 138 | infixl 9 @> |
106 | (@>) = at | 139 | (@>) = at |
107 | 140 | ||
108 | 141 | ||
109 | -- | creates a new Vector by joining a list of Vectors | 142 | {- | creates a new Vector by joining a list of Vectors |
143 | |||
144 | @> join [fromList [1..5], constant 1 3] | ||
145 | 8 |> [1.0,2.0,3.0,4.0,5.0,1.0,1.0,1.0]@ | ||
146 | |||
147 | -} | ||
110 | join :: Storable t => [Vector t] -> Vector t | 148 | join :: Storable t => [Vector t] -> Vector t |
111 | join [] = error "joining zero vectors" | 149 | join [] = error "joining zero vectors" |
112 | join as = unsafePerformIO $ do | 150 | join as = unsafePerformIO $ do |
@@ -131,9 +169,11 @@ asComplex v = V { dim = dim v `div` 2, fptr = castForeignPtr (fptr v), ptr = ca | |||
131 | 169 | ||
132 | ---------------------------------------------------------------- | 170 | ---------------------------------------------------------------- |
133 | 171 | ||
172 | -- | map on Vectors | ||
134 | liftVector :: (Storable a, Storable b) => (a-> b) -> Vector a -> Vector b | 173 | liftVector :: (Storable a, Storable b) => (a-> b) -> Vector a -> Vector b |
135 | liftVector f = fromList . map f . toList | 174 | liftVector f = fromList . map f . toList |
136 | 175 | ||
176 | -- | zipWith for Vectors | ||
137 | liftVector2 :: (Storable a, Storable b, Storable c) => (a-> b -> c) -> Vector a -> Vector b -> Vector c | 177 | liftVector2 :: (Storable a, Storable b, Storable c) => (a-> b -> c) -> Vector a -> Vector b -> Vector c |
138 | liftVector2 f u v = fromList $ zipWith f (toList u) (toList v) | 178 | liftVector2 f u v = fromList $ zipWith f (toList u) (toList v) |
139 | 179 | ||