[project @ 2003-08-31 18:41:28 by ross]
[ghc-base.git] / GHC / Ptr.lhs
1 \begin{code}
2 {-# OPTIONS -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 module GHC.Ptr where
18
19 import GHC.Base
20
21 ------------------------------------------------------------------------
22 -- Data pointers.
23
24 data Ptr a = Ptr Addr# deriving (Eq, Ord)
25 -- ^ A value of type @'Ptr' a@ represents a pointer to an object, or an
26 -- array of objects, which may be marshalled to or from Haskell values
27 -- of type @a@.
28 --
29 --  The type @a@ will normally be an instance of class
30 -- 'Foreign.Storable.Storable' which provides the marshalling operations.
31
32
33 -- |The constant 'nullPtr' contains a distinguished value of 'Ptr'
34 -- that is not associated with a valid memory location.
35 nullPtr :: Ptr a
36 nullPtr = Ptr nullAddr#
37
38 -- |The 'castPtr' function casts a pointer from one type to another.
39 castPtr :: Ptr a -> Ptr b
40 castPtr (Ptr addr) = Ptr addr
41
42 -- |Advances the given address by the given offset in bytes.
43 plusPtr :: Ptr a -> Int -> Ptr b
44 plusPtr (Ptr addr) (I# d) = Ptr (plusAddr# addr d)
45
46 -- |Given an arbitrary address and an alignment constraint,
47 -- 'alignPtr' yields the next higher address that fulfills the
48 -- alignment constraint.  An alignment constraint @x@ is fulfilled by
49 -- any address divisible by @x@.  This operation is idempotent.
50 alignPtr :: Ptr a -> Int -> Ptr a
51 alignPtr addr@(Ptr a) (I# i)
52   = case remAddr# a i of {
53       0# -> addr;
54       n -> Ptr (plusAddr# a (i -# n)) }
55
56 -- |Computes the offset required to get from the first to the second
57 -- argument.  We have 
58 --
59 -- > p2 == p1 \`'plusPtr'\` (p2 \`'minusPtr'\` p1)
60 minusPtr :: Ptr a -> Ptr b -> Int
61 minusPtr (Ptr a1) (Ptr a2) = I# (minusAddr# a1 a2)
62
63 instance CCallable   (Ptr a)
64 instance CReturnable (Ptr a)
65
66 ------------------------------------------------------------------------
67 -- Function pointers for the default calling convention.
68
69 data FunPtr a = FunPtr Addr# deriving (Eq, Ord)
70 -- ^ A value of type @'FunPtr' a@ is a pointer to a piece of code. It
71 -- may be the pointer to a C function or to a Haskell function created
72 -- using @foreign export dynamic@.  A @foreign export
73 -- dynamic@ should normally be declared to produce a
74 -- 'FunPtr' of the correct type.  For example:
75 --
76 -- > type Compare = 'Int' -> 'Int' -> 'Bool'
77 -- > foreign export dynamic mkCompare :: Compare -> 'IO' ('FunPtr' Compare)
78
79 -- |The constant 'nullFunPtr' contains a
80 -- distinguished value of 'Ptr' that is not
81 -- associated with a valid memory location
82 nullFunPtr :: FunPtr a
83 nullFunPtr = FunPtr nullAddr#
84
85 -- |Casts a 'FunPtr' to a 'FunPtr' of a different type
86 castFunPtr :: FunPtr a -> FunPtr b
87 castFunPtr (FunPtr addr) = FunPtr addr
88
89 -- |Casts a 'FunPtr' to a 'Ptr'
90 castFunPtrToPtr :: FunPtr a -> Ptr b
91 castFunPtrToPtr (FunPtr addr) = Ptr addr
92
93 -- |Casts a 'Ptr' to a 'FunPtr'
94 castPtrToFunPtr :: Ptr a -> FunPtr b
95 castPtrToFunPtr (Ptr addr) = FunPtr addr
96
97 instance CCallable   (FunPtr a)
98 instance CReturnable (FunPtr a)
99
100 \end{code}
101