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