[project @ 2005-02-03 10:32:11 by ross]
[ghc-base.git] / GHC / Ptr.lhs
index 39d842d..222524c 100644 (file)
@@ -1,5 +1,5 @@
 \begin{code}
-{-# OPTIONS -fno-implicit-prelude #-}
+{-# OPTIONS_GHC -fno-implicit-prelude #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  GHC.Ptr
@@ -14,6 +14,7 @@
 --
 -----------------------------------------------------------------------------
 
+-- #hide
 module GHC.Ptr where
 
 import GHC.Base
@@ -26,9 +27,11 @@ data Ptr a = Ptr Addr# deriving (Eq, Ord)
 -- array of objects, which may be marshalled to or from Haskell values
 -- of type @a@.
 --
---  The type @a@ will normally be an instance of class
+-- The type @a@ will often be an instance of class
 -- 'Foreign.Storable.Storable' which provides the marshalling operations.
-
+-- However this is not essential, and you can provide your own operations
+-- to access the pointer.  For example you might write small foreign
+-- functions to get or set the fields of a C @struct@.
 
 -- |The constant 'nullPtr' contains a distinguished value of 'Ptr'
 -- that is not associated with a valid memory location.
@@ -60,42 +63,76 @@ alignPtr addr@(Ptr a) (I# i)
 minusPtr :: Ptr a -> Ptr b -> Int
 minusPtr (Ptr a1) (Ptr a2) = I# (minusAddr# a1 a2)
 
-instance CCallable   (Ptr a)
-instance CReturnable (Ptr a)
-
 ------------------------------------------------------------------------
 -- Function pointers for the default calling convention.
 
 data FunPtr a = FunPtr Addr# deriving (Eq, Ord)
--- ^ A value of type @'FunPtr' a@ is a pointer to a piece of code. It
--- may be the pointer to a C function or to a Haskell function created
--- using @foreign export dynamic@.  A @foreign export
--- dynamic@ should normally be declared to produce a
--- 'FunPtr' of the correct type.  For example:
+-- ^ A value of type @'FunPtr' a@ is a pointer to a function callable
+-- from foreign code.  The type @a@ will normally be a /foreign type/,
+-- a function type with zero or more arguments where
+--
+-- * the argument types are /marshallable foreign types/,
+--   i.e. 'Char', 'Int', 'Prelude.Double', 'Prelude.Float',
+--   'Bool', 'Data.Int.Int8', 'Data.Int.Int16', 'Data.Int.Int32',
+--   'Data.Int.Int64', 'Data.Word.Word8', 'Data.Word.Word16',
+--   'Data.Word.Word32', 'Data.Word.Word64', @'Ptr' a@, @'FunPtr' a@,
+--   @'Foreign.StablePtr.StablePtr' a@ or a renaming of any of these
+--   using @newtype@.
+-- 
+-- * the return type is either a marshallable foreign type or has the form
+--   @'Prelude.IO' t@ where @t@ is a marshallable foreign type or @()@.
+--
+-- A value of type @'FunPtr' a@ may be a pointer to a foreign function,
+-- either returned by another foreign function or imported with a
+-- a static address import like
+--
+-- > foreign import ccall "stdlib.h &free"
+-- >   p_free :: FunPtr (Ptr a -> IO ())
+--
+-- or a pointer to a Haskell function created using a /wrapper/ stub
+-- declared to produce a 'FunPtr' of the correct type.  For example:
 --
 -- > type Compare = Int -> Int -> Bool
--- > foreign export dynamic mkCompare :: Compare -> IO (FunPtr Compare)
+-- > foreign import ccall "wrapper"
+-- >   mkCompare :: Compare -> IO (FunPtr Compare)
+--
+-- Calls to wrapper stubs like @mkCompare@ allocate storage, which
+-- should be released with 'Foreign.Ptr.freeHaskellFunPtr' when no
+-- longer required.
+--
+-- To convert 'FunPtr' values to corresponding Haskell functions, one
+-- can define a /dynamic/ stub for the specific foreign type, e.g.
+--
+-- > type IntFunction = CInt -> IO ()
+-- > foreign import ccall "dynamic" 
+-- >   mkFun :: FunPtr IntFunction -> IntFunction
 
 -- |The constant 'nullFunPtr' contains a
--- distinguished value of 'Ptr' that is not
--- associated with a valid memory location
+-- distinguished value of 'FunPtr' that is not
+-- associated with a valid memory location.
 nullFunPtr :: FunPtr a
 nullFunPtr = FunPtr nullAddr#
 
--- |Casts a 'FunPtr' to a 'FunPtr' of a different type
+-- |Casts a 'FunPtr' to a 'FunPtr' of a different type.
 castFunPtr :: FunPtr a -> FunPtr b
 castFunPtr (FunPtr addr) = FunPtr addr
 
--- |Casts a 'FunPtr' to a 'Ptr'
+-- |Casts a 'FunPtr' to a 'Ptr'.
+--
+-- /Note:/ this is valid only on architectures where data and function
+-- pointers range over the same set of addresses, and should only be used
+-- for bindings to external libraries whose interface already relies on
+-- this assumption.
 castFunPtrToPtr :: FunPtr a -> Ptr b
 castFunPtrToPtr (FunPtr addr) = Ptr addr
 
--- |Casts a 'Ptr' to a 'FunPtr'
+-- |Casts a 'Ptr' to a 'FunPtr'.
+--
+-- /Note:/ this is valid only on architectures where data and function
+-- pointers range over the same set of addresses, and should only be used
+-- for bindings to external libraries whose interface already relies on
+-- this assumption.
 castPtrToFunPtr :: Ptr a -> FunPtr b
 castPtrToFunPtr (Ptr addr) = FunPtr addr
-
-instance CCallable   (FunPtr a)
-instance CReturnable (FunPtr a)
-
 \end{code}