b46acc1bea1d9f2602230fdc3753912ed762e344
[ghc-base.git] / Foreign / Ptr.hs
1 {-# LANGUAGE CPP
2            , NoImplicitPrelude
3            , ForeignFunctionInterface
4            , MagicHash
5            , GeneralizedNewtypeDeriving
6   #-}
7
8 -----------------------------------------------------------------------------
9 -- |
10 -- Module      :  Foreign.Ptr
11 -- Copyright   :  (c) The FFI task force 2001
12 -- License     :  BSD-style (see the file libraries/base/LICENSE)
13 -- 
14 -- Maintainer  :  ffi@haskell.org
15 -- Stability   :  provisional
16 -- Portability :  portable
17 --
18 -- This module provides typed pointers to foreign data.  It is part
19 -- of the Foreign Function Interface (FFI) and will normally be
20 -- imported via the "Foreign" module.
21 --
22 -----------------------------------------------------------------------------
23
24 module Foreign.Ptr (
25
26     -- * Data pointers
27
28     Ptr,      -- data Ptr a
29     nullPtr,      -- :: Ptr a
30     castPtr,      -- :: Ptr a -> Ptr b
31     plusPtr,      -- :: Ptr a -> Int -> Ptr b
32     alignPtr,     -- :: Ptr a -> Int -> Ptr a
33     minusPtr,     -- :: Ptr a -> Ptr b -> Int
34
35     -- * Function pointers
36
37     FunPtr,      -- data FunPtr a
38     nullFunPtr,      -- :: FunPtr a
39     castFunPtr,      -- :: FunPtr a -> FunPtr b
40     castFunPtrToPtr, -- :: FunPtr a -> Ptr b
41     castPtrToFunPtr, -- :: Ptr a -> FunPtr b
42
43     freeHaskellFunPtr, -- :: FunPtr a -> IO ()
44     -- Free the function pointer created by foreign export dynamic.
45
46 #ifndef __NHC__
47     -- * Integral types with lossless conversion to and from pointers
48     IntPtr,
49     ptrToIntPtr,
50     intPtrToPtr,
51     WordPtr,
52     ptrToWordPtr,
53     wordPtrToPtr
54 #endif
55  ) where
56
57 #ifdef __GLASGOW_HASKELL__
58 import GHC.Ptr
59 import GHC.Base
60 import GHC.Num
61 import GHC.Read
62 import GHC.Real
63 import GHC.Show
64 import GHC.Enum
65 import GHC.Word         ( Word(..) )
66
67 -- import Data.Int
68 import Data.Word
69 #else
70 import Control.Monad    ( liftM )
71 import Foreign.C.Types
72 #endif
73
74 import Data.Bits
75 import Data.Typeable
76 import Foreign.Storable ( Storable(..) )
77
78 #ifdef __NHC__
79 import NHC.FFI
80   ( Ptr
81   , nullPtr
82   , castPtr
83   , plusPtr
84   , alignPtr
85   , minusPtr
86   , FunPtr
87   , nullFunPtr
88   , castFunPtr
89   , castFunPtrToPtr
90   , castPtrToFunPtr
91   , freeHaskellFunPtr
92   )
93 #endif
94
95 #ifdef __HUGS__
96 import Hugs.Ptr
97 #endif
98
99 #ifdef __GLASGOW_HASKELL__
100 -- | Release the storage associated with the given 'FunPtr', which
101 -- must have been obtained from a wrapper stub.  This should be called
102 -- whenever the return value from a foreign import wrapper function is
103 -- no longer required; otherwise, the storage it uses will leak.
104 foreign import ccall unsafe "freeHaskellFunctionPtr"
105     freeHaskellFunPtr :: FunPtr a -> IO ()
106 #endif
107
108 #ifndef __NHC__
109 # include "HsBaseConfig.h"
110 # include "CTypes.h"
111
112 # ifdef __GLASGOW_HASKELL__
113 -- | An unsigned integral type that can be losslessly converted to and from
114 -- @Ptr@. This type is also compatible with the C99 type @uintptr_t@, and
115 -- can be marshalled to and from that type safely.
116 INTEGRAL_TYPE(WordPtr,tyConWordPtr,"WordPtr",Word)
117         -- Word and Int are guaranteed pointer-sized in GHC
118
119 -- | A signed integral type that can be losslessly converted to and from
120 -- @Ptr@.  This type is also compatible with the C99 type @intptr_t@, and
121 -- can be marshalled to and from that type safely.
122 INTEGRAL_TYPE(IntPtr,tyConIntPtr,"IntPtr",Int)
123         -- Word and Int are guaranteed pointer-sized in GHC
124
125 -- | casts a @Ptr@ to a @WordPtr@
126 ptrToWordPtr :: Ptr a -> WordPtr
127 ptrToWordPtr (Ptr a#) = WordPtr (W# (int2Word# (addr2Int# a#)))
128
129 -- | casts a @WordPtr@ to a @Ptr@
130 wordPtrToPtr :: WordPtr -> Ptr a
131 wordPtrToPtr (WordPtr (W# w#)) = Ptr (int2Addr# (word2Int# w#))
132
133 -- | casts a @Ptr@ to an @IntPtr@
134 ptrToIntPtr :: Ptr a -> IntPtr
135 ptrToIntPtr (Ptr a#) = IntPtr (I# (addr2Int# a#))
136
137 -- | casts an @IntPtr@ to a @Ptr@
138 intPtrToPtr :: IntPtr -> Ptr a
139 intPtrToPtr (IntPtr (I# i#)) = Ptr (int2Addr# i#)
140
141 # else /* !__GLASGOW_HASKELL__ */
142
143 INTEGRAL_TYPE(WordPtr,tyConWordPtr,"WordPtr",CUIntPtr)
144 INTEGRAL_TYPE(IntPtr,tyConIntPtr,"IntPtr",CIntPtr)
145
146 {-# CFILES cbits/PrelIOUtils.c #-}
147
148 foreign import ccall unsafe "__hscore_to_uintptr"
149     ptrToWordPtr :: Ptr a -> WordPtr
150
151 foreign import ccall unsafe "__hscore_from_uintptr"
152     wordPtrToPtr :: WordPtr -> Ptr a
153
154 foreign import ccall unsafe "__hscore_to_intptr"
155     ptrToIntPtr :: Ptr a -> IntPtr
156
157 foreign import ccall unsafe "__hscore_from_intptr"
158     intPtrToPtr :: IntPtr -> Ptr a
159
160 # endif /* !__GLASGOW_HASKELL__ */
161 #endif /* !__NHC_ */