91ae94571fab140a5c5015b820db66cb6b86b1ad
[ghc-base.git] / Foreign / Marshal / Utils.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
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
48   -- ** DEPRECATED FUNCTIONS (don\'t use; they may disappear at any time)
49   --
50   withObject     -- :: Storable a => a -> (Ptr a -> IO b) -> IO b
51 ) where
52
53 import Data.Maybe
54 import Foreign.Ptr              ( Ptr, nullPtr )
55 import Foreign.Storable         ( Storable(poke) )
56 import Foreign.C.Types          ( CSize )
57 import Foreign.Marshal.Alloc    ( malloc, alloca )
58
59 #ifdef __GLASGOW_HASKELL__
60 import GHC.IOBase
61 import GHC.Real                 ( fromIntegral )
62 import GHC.Num
63 import GHC.Base
64 #endif
65
66 #ifdef __NHC__
67 import Foreign.C.Types          ( CInt(..) )
68 #endif
69
70 -- combined allocation and marshalling
71 -- -----------------------------------
72
73 -- |Allocate a block of memory and marshal a value into it
74 -- (the combination of 'malloc' and 'poke').
75 -- The size of the area allocated is determined by the 'Foreign.Storable.sizeOf'
76 -- method from the instance of 'Storable' for the appropriate type.
77 --
78 -- The memory may be deallocated using 'Foreign.Marshal.Alloc.free' or
79 -- 'Foreign.Marshal.Alloc.finalizerFree' when no longer required.
80 --
81 new     :: Storable a => a -> IO (Ptr a)
82 new val  = 
83   do 
84     ptr <- malloc
85     poke ptr val
86     return ptr
87
88 -- |@'with' val f@ executes the computation @f@, passing as argument
89 -- a pointer to a temporarily allocated block of memory into which
90 -- 'val' has been marshalled (the combination of 'alloca' and 'poke').
91 --
92 -- The memory is freed when @f@ terminates (either normally or via an
93 -- exception), so the pointer passed to @f@ must /not/ be used after this.
94 --
95 with       :: Storable a => a -> (Ptr a -> IO b) -> IO b
96 with val f  =
97   alloca $ \ptr -> do
98     poke ptr val
99     res <- f ptr
100     return res
101
102 -- old DEPRECATED name (don't use; may disappear at any time)
103 --
104 withObject :: Storable a => a -> (Ptr a -> IO b) -> IO b
105 {-# DEPRECATED withObject "use `with' instead" #-}
106 withObject  = with
107
108
109 -- marshalling of Boolean values (non-zero corresponds to 'True')
110 -- -----------------------------
111
112 -- |Convert a Haskell 'Bool' to its numeric representation
113 --
114 fromBool       :: Num a => Bool -> a
115 fromBool False  = 0
116 fromBool True   = 1
117
118 -- |Convert a Boolean in numeric representation to a Haskell value
119 --
120 toBool :: Num a => a -> Bool
121 toBool  = (/= 0)
122
123
124 -- marshalling of Maybe values
125 -- ---------------------------
126
127 -- |Allocate storage and marshall a storable value wrapped into a 'Maybe'
128 --
129 -- * the 'nullPtr' is used to represent 'Nothing'
130 --
131 maybeNew :: (      a -> IO (Ptr a))
132          -> (Maybe a -> IO (Ptr a))
133 maybeNew  = maybe (return nullPtr)
134
135 -- |Converts a @withXXX@ combinator into one marshalling a value wrapped
136 -- into a 'Maybe', using 'nullPtr' to represent 'Nothing'.
137 --
138 maybeWith :: (      a -> (Ptr b -> IO c) -> IO c) 
139           -> (Maybe a -> (Ptr b -> IO c) -> IO c)
140 maybeWith  = maybe ($ nullPtr)
141
142 -- |Convert a peek combinator into a one returning 'Nothing' if applied to a
143 -- 'nullPtr' 
144 --
145 maybePeek                           :: (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
146 maybePeek peek ptr | ptr == nullPtr  = return Nothing
147                    | otherwise       = do a <- peek ptr; return (Just a)
148
149
150 -- marshalling lists of storable objects
151 -- -------------------------------------
152
153 -- |Replicates a @withXXX@ combinator over a list of objects, yielding a list of
154 -- marshalled objects
155 --
156 withMany :: (a -> (b -> res) -> res)  -- withXXX combinator for one object
157          -> [a]                       -- storable objects
158          -> ([b] -> res)              -- action on list of marshalled obj.s
159          -> res
160 withMany _       []     f = f []
161 withMany withFoo (x:xs) f = withFoo x $ \x' ->
162                               withMany withFoo xs (\xs' -> f (x':xs'))
163
164
165 -- Haskellish interface to memcpy and memmove
166 -- ------------------------------------------
167
168 -- |Copies the given number of bytes from the second area (source) into the
169 -- first (destination); the copied areas may /not/ overlap
170 --
171 copyBytes               :: Ptr a -> Ptr a -> Int -> IO ()
172 copyBytes dest src size  = memcpy dest src (fromIntegral size)
173
174 -- |Copies the given number of elements from the second area (source) into the
175 -- first (destination); the copied areas /may/ overlap
176 --
177 moveBytes               :: Ptr a -> Ptr a -> Int -> IO ()
178 moveBytes dest src size  = memmove dest src (fromIntegral size)
179
180
181 -- auxilliary routines
182 -- -------------------
183
184 -- |Basic C routines needed for memory copying
185 --
186 foreign import ccall unsafe "string.h" memcpy  :: Ptr a -> Ptr a -> CSize -> IO ()
187 foreign import ccall unsafe "string.h" memmove :: Ptr a -> Ptr a -> CSize -> IO ()