add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / GHC / Stable.lhs
1 \begin{code}
2 {-# LANGUAGE NoImplicitPrelude
3            , MagicHash
4            , UnboxedTuples
5            , ForeignFunctionInterface
6   #-}
7 {-# OPTIONS_HADDOCK hide #-}
8
9 -----------------------------------------------------------------------------
10 -- |
11 -- Module      :  GHC.Stable
12 -- Copyright   :  (c) The University of Glasgow, 1992-2004
13 -- License     :  see libraries/base/LICENSE
14 -- 
15 -- Maintainer  :  ffi@haskell.org
16 -- Stability   :  internal
17 -- Portability :  non-portable (GHC Extensions)
18 --
19 -- Stable pointers.
20 --
21 -----------------------------------------------------------------------------
22
23 -- #hide
24 module GHC.Stable 
25         ( StablePtr(..)
26         , newStablePtr          -- :: a -> IO (StablePtr a)    
27         , deRefStablePtr        -- :: StablePtr a -> a
28         , freeStablePtr         -- :: StablePtr a -> IO ()
29         , castStablePtrToPtr    -- :: StablePtr a -> Ptr ()
30         , castPtrToStablePtr    -- :: Ptr () -> StablePtr a
31    ) where
32
33 import GHC.Ptr
34 import GHC.Base
35 -- import GHC.IO
36
37 -----------------------------------------------------------------------------
38 -- Stable Pointers
39
40 {- |
41 A /stable pointer/ is a reference to a Haskell expression that is
42 guaranteed not to be affected by garbage collection, i.e., it will neither be
43 deallocated nor will the value of the stable pointer itself change during
44 garbage collection (ordinary references may be relocated during garbage
45 collection).  Consequently, stable pointers can be passed to foreign code,
46 which can treat it as an opaque reference to a Haskell value.
47
48 A value of type @StablePtr a@ is a stable pointer to a Haskell
49 expression of type @a@.
50 -}
51 data StablePtr a = StablePtr (StablePtr# a)
52
53 -- |
54 -- Create a stable pointer referring to the given Haskell value.
55 --
56 newStablePtr   :: a -> IO (StablePtr a)
57 newStablePtr a = IO $ \ s ->
58     case makeStablePtr# a s of (# s', sp #) -> (# s', StablePtr sp #)
59
60 -- |
61 -- Obtain the Haskell value referenced by a stable pointer, i.e., the
62 -- same value that was passed to the corresponding call to
63 -- 'makeStablePtr'.  If the argument to 'deRefStablePtr' has
64 -- already been freed using 'freeStablePtr', the behaviour of
65 -- 'deRefStablePtr' is undefined.
66 --
67 deRefStablePtr :: StablePtr a -> IO a
68 deRefStablePtr (StablePtr sp) = IO $ \s -> deRefStablePtr# sp s
69
70 -- |
71 -- Dissolve the association between the stable pointer and the Haskell
72 -- value. Afterwards, if the stable pointer is passed to
73 -- 'deRefStablePtr' or 'freeStablePtr', the behaviour is
74 -- undefined.  However, the stable pointer may still be passed to
75 -- 'castStablePtrToPtr', but the @'Foreign.Ptr.Ptr' ()@ value returned
76 -- by 'castStablePtrToPtr', in this case, is undefined (in particular,
77 -- it may be 'Foreign.Ptr.nullPtr').  Nevertheless, the call
78 -- to 'castStablePtrToPtr' is guaranteed not to diverge.
79 --
80 foreign import ccall unsafe "hs_free_stable_ptr" freeStablePtr :: StablePtr a -> IO ()
81
82 -- |
83 -- Coerce a stable pointer to an address. No guarantees are made about
84 -- the resulting value, except that the original stable pointer can be
85 -- recovered by 'castPtrToStablePtr'.  In particular, the address may not
86 -- refer to an accessible memory location and any attempt to pass it to
87 -- the member functions of the class 'Foreign.Storable.Storable' leads to
88 -- undefined behaviour.
89 --
90 castStablePtrToPtr :: StablePtr a -> Ptr ()
91 castStablePtrToPtr (StablePtr s) = Ptr (unsafeCoerce# s)
92
93
94 -- |
95 -- The inverse of 'castStablePtrToPtr', i.e., we have the identity
96 -- 
97 -- > sp == castPtrToStablePtr (castStablePtrToPtr sp)
98 -- 
99 -- for any stable pointer @sp@ on which 'freeStablePtr' has
100 -- not been executed yet.  Moreover, 'castPtrToStablePtr' may
101 -- only be applied to pointers that have been produced by
102 -- 'castStablePtrToPtr'.
103 --
104 castPtrToStablePtr :: Ptr () -> StablePtr a
105 castPtrToStablePtr (Ptr a) = StablePtr (unsafeCoerce# a)
106
107 instance Eq (StablePtr a) where 
108     (StablePtr sp1) == (StablePtr sp2) =
109         case eqStablePtr# sp1 sp2 of
110            0# -> False
111            _  -> True
112 \end{code}