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