~ubuntu-branches/ubuntu/precise/ghc/precise

« back to all changes in this revision

Viewing changes to libraries/base/Foreign/ForeignPtr.hs

  • Committer: Bazaar Package Importer
  • Author(s): Joachim Breitner
  • Date: 2011-01-17 12:49:24 UTC
  • Revision ID: james.westby@ubuntu.com-20110117124924-do1pym1jlf5o636m
Tags: upstream-7.0.1
ImportĀ upstreamĀ versionĀ 7.0.1

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
{-# OPTIONS_GHC -XNoImplicitPrelude #-}
 
2
-----------------------------------------------------------------------------
 
3
-- |
 
4
-- Module      :  Foreign.ForeignPtr
 
5
-- Copyright   :  (c) The University of Glasgow 2001
 
6
-- License     :  BSD-style (see the file libraries/base/LICENSE)
 
7
-- 
 
8
-- Maintainer  :  ffi@haskell.org
 
9
-- Stability   :  provisional
 
10
-- Portability :  portable
 
11
--
 
12
-- The 'ForeignPtr' type and operations.  This module is part of the
 
13
-- Foreign Function Interface (FFI) and will usually be imported via
 
14
-- the "Foreign" module.
 
15
--
 
16
-----------------------------------------------------------------------------
 
17
 
 
18
module Foreign.ForeignPtr
 
19
        ( 
 
20
        -- * Finalised data pointers
 
21
          ForeignPtr
 
22
        , FinalizerPtr
 
23
#if defined(__HUGS__) || defined(__GLASGOW_HASKELL__)
 
24
        , FinalizerEnvPtr
 
25
#endif
 
26
        -- ** Basic operations
 
27
        , newForeignPtr
 
28
        , newForeignPtr_
 
29
        , addForeignPtrFinalizer
 
30
#if defined(__HUGS__) || defined(__GLASGOW_HASKELL__)
 
31
        , newForeignPtrEnv
 
32
        , addForeignPtrFinalizerEnv
 
33
#endif
 
34
        , withForeignPtr
 
35
 
 
36
#ifdef __GLASGOW_HASKELL__
 
37
        , finalizeForeignPtr
 
38
#endif
 
39
 
 
40
        -- ** Low-level operations
 
41
        , unsafeForeignPtrToPtr
 
42
        , touchForeignPtr
 
43
        , castForeignPtr
 
44
 
 
45
        -- ** Allocating managed memory
 
46
        , mallocForeignPtr
 
47
        , mallocForeignPtrBytes
 
48
        , mallocForeignPtrArray
 
49
        , mallocForeignPtrArray0
 
50
        ) 
 
51
        where
 
52
 
 
53
import Foreign.Ptr
 
54
 
 
55
#ifdef __NHC__
 
56
import NHC.FFI
 
57
  ( ForeignPtr
 
58
  , FinalizerPtr
 
59
  , newForeignPtr
 
60
  , newForeignPtr_
 
61
  , addForeignPtrFinalizer
 
62
  , withForeignPtr
 
63
  , unsafeForeignPtrToPtr
 
64
  , touchForeignPtr
 
65
  , castForeignPtr
 
66
  , Storable(sizeOf)
 
67
  , malloc, mallocBytes, finalizerFree
 
68
  )
 
69
#endif
 
70
 
 
71
#ifdef __HUGS__
 
72
import Hugs.ForeignPtr
 
73
#endif
 
74
 
 
75
#ifndef __NHC__
 
76
import Foreign.Storable ( Storable(sizeOf) )
 
77
#endif
 
78
 
 
79
#ifdef __GLASGOW_HASKELL__
 
80
import GHC.Base
 
81
-- import GHC.IO
 
82
import GHC.Num
 
83
import GHC.Err          ( undefined )
 
84
import GHC.ForeignPtr
 
85
#endif
 
86
 
 
87
#if !defined(__NHC__) && !defined(__GLASGOW_HASKELL__)
 
88
import Foreign.Marshal.Alloc    ( malloc, mallocBytes, finalizerFree )
 
89
 
 
90
instance Eq (ForeignPtr a) where 
 
91
    p == q  =  unsafeForeignPtrToPtr p == unsafeForeignPtrToPtr q
 
92
 
 
93
instance Ord (ForeignPtr a) where 
 
94
    compare p q  =  compare (unsafeForeignPtrToPtr p) (unsafeForeignPtrToPtr q)
 
95
 
 
96
instance Show (ForeignPtr a) where
 
97
    showsPrec p f = showsPrec p (unsafeForeignPtrToPtr f)
 
98
#endif
 
99
 
 
100
 
 
101
#ifndef __NHC__
 
102
newForeignPtr :: FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
 
103
-- ^Turns a plain memory reference into a foreign pointer, and
 
104
-- associates a finalizer with the reference.  The finalizer will be
 
105
-- executed after the last reference to the foreign object is dropped.
 
106
-- There is no guarantee of promptness, however the finalizer will be
 
107
-- executed before the program exits.
 
108
newForeignPtr finalizer p
 
109
  = do fObj <- newForeignPtr_ p
 
110
       addForeignPtrFinalizer finalizer fObj
 
111
       return fObj
 
112
 
 
113
withForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b
 
114
-- ^This is a way to look at the pointer living inside a
 
115
-- foreign object.  This function takes a function which is
 
116
-- applied to that pointer. The resulting 'IO' action is then
 
117
-- executed. The foreign object is kept alive at least during
 
118
-- the whole action, even if it is not used directly
 
119
-- inside. Note that it is not safe to return the pointer from
 
120
-- the action and use it after the action completes. All uses
 
121
-- of the pointer should be inside the
 
122
-- 'withForeignPtr' bracket.  The reason for
 
123
-- this unsafeness is the same as for
 
124
-- 'unsafeForeignPtrToPtr' below: the finalizer
 
125
-- may run earlier than expected, because the compiler can only
 
126
-- track usage of the 'ForeignPtr' object, not
 
127
-- a 'Ptr' object made from it.
 
128
--
 
129
-- This function is normally used for marshalling data to
 
130
-- or from the object pointed to by the
 
131
-- 'ForeignPtr', using the operations from the
 
132
-- 'Storable' class.
 
133
withForeignPtr fo io
 
134
  = do r <- io (unsafeForeignPtrToPtr fo)
 
135
       touchForeignPtr fo
 
136
       return r
 
137
#endif /* ! __NHC__ */
 
138
 
 
139
#if defined(__HUGS__) || defined(__GLASGOW_HASKELL__)
 
140
-- | This variant of 'newForeignPtr' adds a finalizer that expects an
 
141
-- environment in addition to the finalized pointer.  The environment
 
142
-- that will be passed to the finalizer is fixed by the second argument to
 
143
-- 'newForeignPtrEnv'.
 
144
newForeignPtrEnv ::
 
145
    FinalizerEnvPtr env a -> Ptr env -> Ptr a -> IO (ForeignPtr a)
 
146
newForeignPtrEnv finalizer env p
 
147
  = do fObj <- newForeignPtr_ p
 
148
       addForeignPtrFinalizerEnv finalizer env fObj
 
149
       return fObj
 
150
#endif /* __HUGS__ */
 
151
 
 
152
#ifndef __GLASGOW_HASKELL__
 
153
mallocForeignPtr :: Storable a => IO (ForeignPtr a)
 
154
mallocForeignPtr = do
 
155
  r <- malloc
 
156
  newForeignPtr finalizerFree r
 
157
 
 
158
mallocForeignPtrBytes :: Int -> IO (ForeignPtr a)
 
159
mallocForeignPtrBytes n = do
 
160
  r <- mallocBytes n
 
161
  newForeignPtr finalizerFree r
 
162
#endif /* !__GLASGOW_HASKELL__ */
 
163
 
 
164
-- | This function is similar to 'Foreign.Marshal.Array.mallocArray',
 
165
-- but yields a memory area that has a finalizer attached that releases
 
166
-- the memory area.  As with 'mallocForeignPtr', it is not guaranteed that
 
167
-- the block of memory was allocated by 'Foreign.Marshal.Alloc.malloc'.
 
168
mallocForeignPtrArray :: Storable a => Int -> IO (ForeignPtr a)
 
169
mallocForeignPtrArray  = doMalloc undefined
 
170
  where
 
171
    doMalloc            :: Storable b => b -> Int -> IO (ForeignPtr b)
 
172
    doMalloc dummy size  = mallocForeignPtrBytes (size * sizeOf dummy)
 
173
 
 
174
-- | This function is similar to 'Foreign.Marshal.Array.mallocArray0',
 
175
-- but yields a memory area that has a finalizer attached that releases
 
176
-- the memory area.  As with 'mallocForeignPtr', it is not guaranteed that
 
177
-- the block of memory was allocated by 'Foreign.Marshal.Alloc.malloc'.
 
178
mallocForeignPtrArray0      :: Storable a => Int -> IO (ForeignPtr a)
 
179
mallocForeignPtrArray0 size  = mallocForeignPtrArray (size + 1)