7fcacfa8c78560e0c425b737ecac3255ea5c45e2
[ghc-base.git] / Foreign / Marshal / Utils.hs
1 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  Foreign.Marshal.Utils
5 -- Copyright   :  (c) The FFI task force 2001
6 -- License     :  BSD-style (see the file libraries/base/LICENSE)
7 -- 
8 -- Maintainer  :  ffi@haskell.org
9 -- Stability   :  provisional
10 -- Portability :  portable
11 --
12 -- Utilities for primitive marshaling
13 --
14 -----------------------------------------------------------------------------
15
16 module Foreign.Marshal.Utils (
17   -- * General marshalling utilities
18
19   -- ** Combined allocation and marshalling
20   --
21   with,          -- :: Storable a => a -> (Ptr a -> IO b) -> IO b
22   new,           -- :: Storable a => a -> IO (Ptr a)
23
24   -- ** Marshalling of Boolean values (non-zero corresponds to 'True')
25   --
26   fromBool,      -- :: Num a => Bool -> a
27   toBool,        -- :: Num a => a -> Bool
28
29   -- ** Marshalling of Maybe values
30   --
31   maybeNew,      -- :: (      a -> IO (Ptr a))
32                  -- -> (Maybe a -> IO (Ptr a))
33   maybeWith,     -- :: (      a -> (Ptr b -> IO c) -> IO c)
34                  -- -> (Maybe a -> (Ptr b -> IO c) -> IO c)
35   maybePeek,     -- :: (Ptr a -> IO        b )
36                  -- -> (Ptr a -> IO (Maybe b))
37
38   -- ** Marshalling lists of storable objects
39   --
40   withMany,      -- :: (a -> (b -> res) -> res) -> [a] -> ([b] -> res) -> res
41
42   -- ** Haskellish interface to memcpy and memmove
43   -- | (argument order: destination, source)
44   --
45   copyBytes,     -- :: Ptr a -> Ptr a -> Int -> IO ()
46   moveBytes,     -- :: Ptr a -> Ptr a -> Int -> IO ()
47 ) where
48
49 import Data.Maybe
50 import Foreign.Ptr              ( Ptr, nullPtr )
51 import Foreign.Storable         ( Storable(poke) )
52 import Foreign.C.Types          ( CSize )
53 import Foreign.Marshal.Alloc    ( malloc, alloca )
54
55 #ifdef __GLASGOW_HASKELL__
56 import GHC.Real                 ( fromIntegral )
57 import GHC.Num
58 import GHC.Base
59 #endif
60
61 #ifdef __NHC__
62 import Foreign.C.Types          ( CInt(..) )
63 #endif
64
65 -- combined allocation and marshalling
66 -- -----------------------------------
67
68 -- |Allocate a block of memory and marshal a value into it
69 -- (the combination of 'malloc' and 'poke').
70 -- The size of the area allocated is determined by the 'Foreign.Storable.sizeOf'
71 -- method from the instance of 'Storable' for the appropriate type.
72 --
73 -- The memory may be deallocated using 'Foreign.Marshal.Alloc.free' or
74 -- 'Foreign.Marshal.Alloc.finalizerFree' when no longer required.
75 --
76 new     :: Storable a => a -> IO (Ptr a)
77 new val  = 
78   do 
79     ptr <- malloc
80     poke ptr val
81     return ptr
82
83 -- |@'with' val f@ executes the computation @f@, passing as argument
84 -- a pointer to a temporarily allocated block of memory into which
85 -- @val@ has been marshalled (the combination of 'alloca' and 'poke').
86 --
87 -- The memory is freed when @f@ terminates (either normally or via an
88 -- exception), so the pointer passed to @f@ must /not/ be used after this.
89 --
90 with       :: Storable a => a -> (Ptr a -> IO b) -> IO b
91 with val f  =
92   alloca $ \ptr -> do
93     poke ptr val
94     res <- f ptr
95     return res
96
97
98 -- marshalling of Boolean values (non-zero corresponds to 'True')
99 -- -----------------------------
100
101 -- |Convert a Haskell 'Bool' to its numeric representation
102 --
103 fromBool       :: Num a => Bool -> a
104 fromBool False  = 0
105 fromBool True   = 1
106
107 -- |Convert a Boolean in numeric representation to a Haskell value
108 --
109 toBool :: Num a => a -> Bool
110 toBool  = (/= 0)
111
112
113 -- marshalling of Maybe values
114 -- ---------------------------
115
116 -- |Allocate storage and marshal a storable value wrapped into a 'Maybe'
117 --
118 -- * the 'nullPtr' is used to represent 'Nothing'
119 --
120 maybeNew :: (      a -> IO (Ptr a))
121          -> (Maybe a -> IO (Ptr a))
122 maybeNew  = maybe (return nullPtr)
123
124 -- |Converts a @withXXX@ combinator into one marshalling a value wrapped
125 -- into a 'Maybe', using 'nullPtr' to represent 'Nothing'.
126 --
127 maybeWith :: (      a -> (Ptr b -> IO c) -> IO c) 
128           -> (Maybe a -> (Ptr b -> IO c) -> IO c)
129 maybeWith  = maybe ($ nullPtr)
130
131 -- |Convert a peek combinator into a one returning 'Nothing' if applied to a
132 -- 'nullPtr' 
133 --
134 maybePeek                           :: (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
135 maybePeek peek ptr | ptr == nullPtr  = return Nothing
136                    | otherwise       = do a <- peek ptr; return (Just a)
137
138
139 -- marshalling lists of storable objects
140 -- -------------------------------------
141
142 -- |Replicates a @withXXX@ combinator over a list of objects, yielding a list of
143 -- marshalled objects
144 --
145 withMany :: (a -> (b -> res) -> res)  -- withXXX combinator for one object
146          -> [a]                       -- storable objects
147          -> ([b] -> res)              -- action on list of marshalled obj.s
148          -> res
149 withMany _       []     f = f []
150 withMany withFoo (x:xs) f = withFoo x $ \x' ->
151                               withMany withFoo xs (\xs' -> f (x':xs'))
152
153
154 -- Haskellish interface to memcpy and memmove
155 -- ------------------------------------------
156
157 -- |Copies the given number of bytes from the second area (source) into the
158 -- first (destination); the copied areas may /not/ overlap
159 --
160 copyBytes               :: Ptr a -> Ptr a -> Int -> IO ()
161 copyBytes dest src size  = do _ <- memcpy dest src (fromIntegral size)
162                               return ()
163
164 -- |Copies the given number of bytes from the second area (source) into the
165 -- first (destination); the copied areas /may/ overlap
166 --
167 moveBytes               :: Ptr a -> Ptr a -> Int -> IO ()
168 moveBytes dest src size  = do _ <- memmove dest src (fromIntegral size)
169                               return ()
170
171
172 -- auxilliary routines
173 -- -------------------
174
175 -- |Basic C routines needed for memory copying
176 --
177 foreign import ccall unsafe "string.h" memcpy  :: Ptr a -> Ptr a -> CSize -> IO (Ptr a)
178 foreign import ccall unsafe "string.h" memmove :: Ptr a -> Ptr a -> CSize -> IO (Ptr a)