Remove Control.Parallel*, now in package parallel
[haskell-directory.git] / GHC / Ptr.lhs
1 \begin{code}
2 {-# OPTIONS_GHC -fno-implicit-prelude #-}
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.Ptr
6 -- Copyright   :  (c) The FFI Task Force, 2000-2002
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  ffi@haskell.org
10 -- Stability   :  internal
11 -- Portability :  non-portable (GHC Extensions)
12 --
13 -- The 'Ptr' and 'FunPtr' types and operations.
14 --
15 -----------------------------------------------------------------------------
16
17 -- #hide
18 module GHC.Ptr where
19
20 import GHC.Base
21 import GHC.Show
22 import GHC.Num
23 import GHC.List ( length, replicate )
24 import Numeric          ( showHex )
25
26 #include "MachDeps.h"
27
28 ------------------------------------------------------------------------
29 -- Data pointers.
30
31 data Ptr a = Ptr Addr# deriving (Eq, Ord)
32 -- ^ A value of type @'Ptr' a@ represents a pointer to an object, or an
33 -- array of objects, which may be marshalled to or from Haskell values
34 -- of type @a@.
35 --
36 -- The type @a@ will often be an instance of class
37 -- 'Foreign.Storable.Storable' which provides the marshalling operations.
38 -- However this is not essential, and you can provide your own operations
39 -- to access the pointer.  For example you might write small foreign
40 -- functions to get or set the fields of a C @struct@.
41
42 -- |The constant 'nullPtr' contains a distinguished value of 'Ptr'
43 -- that is not associated with a valid memory location.
44 nullPtr :: Ptr a
45 nullPtr = Ptr nullAddr#
46
47 -- |The 'castPtr' function casts a pointer from one type to another.
48 castPtr :: Ptr a -> Ptr b
49 castPtr (Ptr addr) = Ptr addr
50
51 -- |Advances the given address by the given offset in bytes.
52 plusPtr :: Ptr a -> Int -> Ptr b
53 plusPtr (Ptr addr) (I# d) = Ptr (plusAddr# addr d)
54
55 -- |Given an arbitrary address and an alignment constraint,
56 -- 'alignPtr' yields the next higher address that fulfills the
57 -- alignment constraint.  An alignment constraint @x@ is fulfilled by
58 -- any address divisible by @x@.  This operation is idempotent.
59 alignPtr :: Ptr a -> Int -> Ptr a
60 alignPtr addr@(Ptr a) (I# i)
61   = case remAddr# a i of {
62       0# -> addr;
63       n -> Ptr (plusAddr# a (i -# n)) }
64
65 -- |Computes the offset required to get from the first to the second
66 -- argument.  We have 
67 --
68 -- > p2 == p1 `plusPtr` (p2 `minusPtr` p1)
69 minusPtr :: Ptr a -> Ptr b -> Int
70 minusPtr (Ptr a1) (Ptr a2) = I# (minusAddr# a1 a2)
71
72 ------------------------------------------------------------------------
73 -- Function pointers for the default calling convention.
74
75 data FunPtr a = FunPtr Addr# deriving (Eq, Ord)
76 -- ^ A value of type @'FunPtr' a@ is a pointer to a function callable
77 -- from foreign code.  The type @a@ will normally be a /foreign type/,
78 -- a function type with zero or more arguments where
79 --
80 -- * the argument types are /marshallable foreign types/,
81 --   i.e. 'Char', 'Int', 'Prelude.Double', 'Prelude.Float',
82 --   'Bool', 'Data.Int.Int8', 'Data.Int.Int16', 'Data.Int.Int32',
83 --   'Data.Int.Int64', 'Data.Word.Word8', 'Data.Word.Word16',
84 --   'Data.Word.Word32', 'Data.Word.Word64', @'Ptr' a@, @'FunPtr' a@,
85 --   @'Foreign.StablePtr.StablePtr' a@ or a renaming of any of these
86 --   using @newtype@.
87 -- 
88 -- * the return type is either a marshallable foreign type or has the form
89 --   @'Prelude.IO' t@ where @t@ is a marshallable foreign type or @()@.
90 --
91 -- A value of type @'FunPtr' a@ may be a pointer to a foreign function,
92 -- either returned by another foreign function or imported with a
93 -- a static address import like
94 --
95 -- > foreign import ccall "stdlib.h &free"
96 -- >   p_free :: FunPtr (Ptr a -> IO ())
97 --
98 -- or a pointer to a Haskell function created using a /wrapper/ stub
99 -- declared to produce a 'FunPtr' of the correct type.  For example:
100 --
101 -- > type Compare = Int -> Int -> Bool
102 -- > foreign import ccall "wrapper"
103 -- >   mkCompare :: Compare -> IO (FunPtr Compare)
104 --
105 -- Calls to wrapper stubs like @mkCompare@ allocate storage, which
106 -- should be released with 'Foreign.Ptr.freeHaskellFunPtr' when no
107 -- longer required.
108 --
109 -- To convert 'FunPtr' values to corresponding Haskell functions, one
110 -- can define a /dynamic/ stub for the specific foreign type, e.g.
111 --
112 -- > type IntFunction = CInt -> IO ()
113 -- > foreign import ccall "dynamic" 
114 -- >   mkFun :: FunPtr IntFunction -> IntFunction
115
116 -- |The constant 'nullFunPtr' contains a
117 -- distinguished value of 'FunPtr' that is not
118 -- associated with a valid memory location.
119 nullFunPtr :: FunPtr a
120 nullFunPtr = FunPtr nullAddr#
121
122 -- |Casts a 'FunPtr' to a 'FunPtr' of a different type.
123 castFunPtr :: FunPtr a -> FunPtr b
124 castFunPtr (FunPtr addr) = FunPtr addr
125
126 -- |Casts a 'FunPtr' to a 'Ptr'.
127 --
128 -- /Note:/ this is valid only on architectures where data and function
129 -- pointers range over the same set of addresses, and should only be used
130 -- for bindings to external libraries whose interface already relies on
131 -- this assumption.
132 castFunPtrToPtr :: FunPtr a -> Ptr b
133 castFunPtrToPtr (FunPtr addr) = Ptr addr
134
135 -- |Casts a 'Ptr' to a 'FunPtr'.
136 --
137 -- /Note:/ this is valid only on architectures where data and function
138 -- pointers range over the same set of addresses, and should only be used
139 -- for bindings to external libraries whose interface already relies on
140 -- this assumption.
141 castPtrToFunPtr :: Ptr a -> FunPtr b
142 castPtrToFunPtr (Ptr addr) = FunPtr addr
143
144
145 ------------------------------------------------------------------------
146 -- Show instances for Ptr and FunPtr
147 -- I have absolutely no idea why the WORD_SIZE_IN_BITS stuff is here
148
149 #if (WORD_SIZE_IN_BITS == 32 || WORD_SIZE_IN_BITS == 64)
150 instance Show (Ptr a) where
151    showsPrec p (Ptr a) rs = pad_out (showHex (word2Integer(int2Word#(addr2Int# a))) "") rs
152      where
153         -- want 0s prefixed to pad it out to a fixed length.
154        pad_out ls rs = 
155           '0':'x':(replicate (2*SIZEOF_HSPTR - length ls) '0') ++ ls ++ rs
156        -- word2Integer :: Word# -> Integer (stolen from Word.lhs)
157        word2Integer w = case word2Integer# w of
158                         (# s, d #) -> J# s d
159
160 instance Show (FunPtr a) where
161    showsPrec p = showsPrec p . castFunPtrToPtr
162 #endif
163 \end{code}
164