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

« back to all changes in this revision

Viewing changes to libraries/bytestring/Data/ByteString/Unsafe.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
{-# LANGUAGE CPP #-}
 
2
-- We cannot actually specify all the language pragmas, see ghc ticket #
 
3
-- If we could, these are what they would be:
 
4
{- LANGUAGE MagicHash -}
 
5
 
 
6
-- |
 
7
-- Module      : Data.ByteString.Unsafe
 
8
-- License     : BSD-style
 
9
-- Maintainer  : dons@cse.unsw.edu.au, duncan@haskell.org
 
10
-- Stability   : experimental
 
11
-- Portability : portable
 
12
--
 
13
-- A module containing unsafe 'ByteString' operations.
 
14
--
 
15
-- While these functions have a stable API and you may use these functions in
 
16
-- applications, do carefully consider the documented pre-conditions;
 
17
-- incorrect use can break referential transparency or worse.
 
18
--
 
19
module Data.ByteString.Unsafe (
 
20
 
 
21
        -- * Unchecked access
 
22
        unsafeHead,             -- :: ByteString -> Word8
 
23
        unsafeTail,             -- :: ByteString -> ByteString
 
24
        unsafeIndex,            -- :: ByteString -> Int -> Word8
 
25
        unsafeTake,             -- :: Int -> ByteString -> ByteString
 
26
        unsafeDrop,             -- :: Int -> ByteString -> ByteString
 
27
 
 
28
        -- * Low level interaction with CStrings
 
29
        -- ** Using ByteStrings with functions for CStrings
 
30
        unsafeUseAsCString,     -- :: ByteString -> (CString -> IO a) -> IO a
 
31
        unsafeUseAsCStringLen,  -- :: ByteString -> (CStringLen -> IO a) -> IO a
 
32
 
 
33
        -- ** Converting CStrings to ByteStrings
 
34
        unsafePackCString,      -- :: CString -> IO ByteString
 
35
        unsafePackCStringLen,   -- :: CStringLen -> IO ByteString
 
36
        unsafePackMallocCString,-- :: CString -> IO ByteString
 
37
 
 
38
#if defined(__GLASGOW_HASKELL__)
 
39
        unsafePackAddress,          -- :: Addr# -> IO ByteString
 
40
        unsafePackAddressLen,       -- :: Int -> Addr# -> IO ByteString
 
41
        unsafePackCStringFinalizer, -- :: Ptr Word8 -> Int -> IO () -> IO ByteString
 
42
        unsafeFinalize,             -- :: ByteString -> IO ()
 
43
#endif
 
44
 
 
45
  ) where
 
46
 
 
47
import Data.ByteString.Internal
 
48
 
 
49
import Foreign.ForeignPtr       (newForeignPtr_, newForeignPtr, withForeignPtr)
 
50
import Foreign.Ptr              (Ptr, plusPtr, castPtr)
 
51
 
 
52
import Foreign.Storable         (Storable(..))
 
53
import Foreign.C.String         (CString, CStringLen)
 
54
 
 
55
#ifndef __NHC__
 
56
import Control.Exception        (assert)
 
57
#endif
 
58
 
 
59
import Data.Word                (Word8)
 
60
 
 
61
#if defined(__GLASGOW_HASKELL__)
 
62
import qualified Foreign.ForeignPtr as FC (finalizeForeignPtr)
 
63
import qualified Foreign.Concurrent as FC (newForeignPtr)
 
64
 
 
65
--import Data.Generics            (Data(..), Typeable(..))
 
66
 
 
67
import GHC.Prim                 (Addr#)
 
68
import GHC.Ptr                  (Ptr(..))
 
69
#endif
 
70
 
 
71
-- An alternative to Control.Exception (assert) for nhc98
 
72
#ifdef __NHC__
 
73
#define assert  assertS "__FILE__ : __LINE__"
 
74
assertS :: String -> Bool -> a -> a
 
75
assertS _ True  = id
 
76
assertS s False = error ("assertion failed at "++s)
 
77
#endif
 
78
 
 
79
-- -----------------------------------------------------------------------------
 
80
--
 
81
-- Useful macros, until we have bang patterns
 
82
--
 
83
 
 
84
#define STRICT1(f) f a | a `seq` False = undefined
 
85
#define STRICT2(f) f a b | a `seq` b `seq` False = undefined
 
86
#define STRICT3(f) f a b c | a `seq` b `seq` c `seq` False = undefined
 
87
#define STRICT4(f) f a b c d | a `seq` b `seq` c `seq` d `seq` False = undefined
 
88
#define STRICT5(f) f a b c d e | a `seq` b `seq` c `seq` d `seq` e `seq` False = undefined
 
89
 
 
90
-- ---------------------------------------------------------------------
 
91
--
 
92
-- Extensions to the basic interface
 
93
--
 
94
 
 
95
-- | A variety of 'head' for non-empty ByteStrings. 'unsafeHead' omits the
 
96
-- check for the empty case, so there is an obligation on the programmer
 
97
-- to provide a proof that the ByteString is non-empty.
 
98
unsafeHead :: ByteString -> Word8
 
99
unsafeHead (PS x s l) = assert (l > 0) $
 
100
    inlinePerformIO $ withForeignPtr x $ \p -> peekByteOff p s
 
101
{-# INLINE unsafeHead #-}
 
102
 
 
103
-- | A variety of 'tail' for non-empty ByteStrings. 'unsafeTail' omits the
 
104
-- check for the empty case. As with 'unsafeHead', the programmer must
 
105
-- provide a separate proof that the ByteString is non-empty.
 
106
unsafeTail :: ByteString -> ByteString
 
107
unsafeTail (PS ps s l) = assert (l > 0) $ PS ps (s+1) (l-1)
 
108
{-# INLINE unsafeTail #-}
 
109
 
 
110
-- | Unsafe 'ByteString' index (subscript) operator, starting from 0, returning a 'Word8'
 
111
-- This omits the bounds check, which means there is an accompanying
 
112
-- obligation on the programmer to ensure the bounds are checked in some
 
113
-- other way.
 
114
unsafeIndex :: ByteString -> Int -> Word8
 
115
unsafeIndex (PS x s l) i = assert (i >= 0 && i < l) $
 
116
    inlinePerformIO $ withForeignPtr x $ \p -> peekByteOff p (s+i)
 
117
{-# INLINE unsafeIndex #-}
 
118
 
 
119
-- | A variety of 'take' which omits the checks on @n@ so there is an
 
120
-- obligation on the programmer to provide a proof that @0 <= n <= 'length' xs@.
 
121
unsafeTake :: Int -> ByteString -> ByteString
 
122
unsafeTake n (PS x s l) = assert (0 <= n && n <= l) $ PS x s n
 
123
{-# INLINE unsafeTake #-}
 
124
 
 
125
-- | A variety of 'drop' which omits the checks on @n@ so there is an
 
126
-- obligation on the programmer to provide a proof that @0 <= n <= 'length' xs@.
 
127
unsafeDrop  :: Int -> ByteString -> ByteString
 
128
unsafeDrop n (PS x s l) = assert (0 <= n && n <= l) $ PS x (s+n) (l-n)
 
129
{-# INLINE unsafeDrop #-}
 
130
 
 
131
 
 
132
#if defined(__GLASGOW_HASKELL__)
 
133
-- | /O(n)/ Pack a null-terminated sequence of bytes, pointed to by an
 
134
-- Addr\# (an arbitrary machine address assumed to point outside the
 
135
-- garbage-collected heap) into a @ByteString@. A much faster way to
 
136
-- create an Addr\# is with an unboxed string literal, than to pack a
 
137
-- boxed string. A unboxed string literal is compiled to a static @char
 
138
-- []@ by GHC. Establishing the length of the string requires a call to
 
139
-- @strlen(3)@, so the Addr# must point to a null-terminated buffer (as
 
140
-- is the case with "string"# literals in GHC). Use 'unsafePackAddressLen'
 
141
-- if you know the length of the string statically.
 
142
--
 
143
-- An example:
 
144
--
 
145
-- > literalFS = unsafePackAddress "literal"#
 
146
--
 
147
-- This function is /unsafe/. If you modify the buffer pointed to by the
 
148
-- original Addr# this modification will be reflected in the resulting
 
149
-- @ByteString@, breaking referential transparency.
 
150
--
 
151
-- Note this also won't work if you Add# has embedded '\0' characters in
 
152
-- the string (strlen will fail).
 
153
--
 
154
unsafePackAddress :: Addr# -> IO ByteString
 
155
unsafePackAddress addr# = do
 
156
    p <- newForeignPtr_ (castPtr cstr)
 
157
    l <- c_strlen cstr
 
158
    return $ PS p 0 (fromIntegral l)
 
159
  where
 
160
    cstr :: CString
 
161
    cstr = Ptr addr#
 
162
{-# INLINE unsafePackAddress #-}
 
163
 
 
164
-- | /O(1)/ 'unsafePackAddressLen' provides constant-time construction of
 
165
-- 'ByteStrings' which is ideal for string literals. It packs a sequence
 
166
-- of bytes into a 'ByteString', given a raw 'Addr#' to the string, and
 
167
-- the length of the string.
 
168
--
 
169
-- This function is /unsafe/ in two ways:
 
170
--
 
171
-- * the length argument is assumed to be correct. If the length
 
172
-- argument is incorrect, it is possible to overstep the end of the
 
173
-- byte array.
 
174
--
 
175
-- * if the underying Addr# is later modified, this change will be
 
176
-- reflected in resulting @ByteString@, breaking referential
 
177
-- transparency.
 
178
--
 
179
-- If in doubt, don't use these functions.
 
180
--
 
181
unsafePackAddressLen :: Int -> Addr# -> IO ByteString
 
182
unsafePackAddressLen len addr# = do
 
183
    p <- newForeignPtr_ (Ptr addr#)
 
184
    return $ PS p 0 len
 
185
{-# INLINE unsafePackAddressLen #-}
 
186
 
 
187
-- | /O(1)/ Construct a 'ByteString' given a Ptr Word8 to a buffer, a
 
188
-- length, and an IO action representing a finalizer. This function is
 
189
-- not available on Hugs.
 
190
--
 
191
-- This function is /unsafe/, it is possible to break referential
 
192
-- transparency by modifying the underlying buffer pointed to by the
 
193
-- first argument. Any changes to the original buffer will be reflected
 
194
-- in the resulting @ByteString@.
 
195
--
 
196
unsafePackCStringFinalizer :: Ptr Word8 -> Int -> IO () -> IO ByteString
 
197
unsafePackCStringFinalizer p l f = do
 
198
    fp <- FC.newForeignPtr p f
 
199
    return $ PS fp 0 l
 
200
 
 
201
-- | Explicitly run the finaliser associated with a 'ByteString'.
 
202
-- References to this value after finalisation may generate invalid memory
 
203
-- references.
 
204
--
 
205
-- This function is /unsafe/, as there may be other
 
206
-- 'ByteStrings' referring to the same underlying pages. If you use
 
207
-- this, you need to have a proof of some kind that all 'ByteString's
 
208
-- ever generated from the underlying byte array are no longer live.
 
209
--
 
210
unsafeFinalize :: ByteString -> IO ()
 
211
unsafeFinalize (PS p _ _) = FC.finalizeForeignPtr p
 
212
 
 
213
#endif
 
214
 
 
215
------------------------------------------------------------------------
 
216
-- Packing CStrings into ByteStrings
 
217
 
 
218
-- | /O(n)/ Build a @ByteString@ from a @CString@. This value will have /no/
 
219
-- finalizer associated to it, and will not be garbage collected by
 
220
-- Haskell. The ByteString length is calculated using /strlen(3)/,
 
221
-- and thus the complexity is a /O(n)/.
 
222
--
 
223
-- This function is /unsafe/. If the @CString@ is later modified, this
 
224
-- change will be reflected in the resulting @ByteString@, breaking
 
225
-- referential transparency.
 
226
--
 
227
unsafePackCString :: CString -> IO ByteString
 
228
unsafePackCString cstr = do
 
229
    fp <- newForeignPtr_ (castPtr cstr)
 
230
    l <- c_strlen cstr
 
231
    return $! PS fp 0 (fromIntegral l)
 
232
 
 
233
-- | /O(1)/ Build a @ByteString@ from a @CStringLen@. This value will
 
234
-- have /no/ finalizer associated with it, and will not be garbage
 
235
-- collected by Haskell. This operation has /O(1)/ complexity as we
 
236
-- already know the final size, so no /strlen(3)/ is required.
 
237
--
 
238
-- This funtion is /unsafe/. If the original @CStringLen@ is later
 
239
-- modified, this change will be reflected in the resulting @ByteString@,
 
240
-- breaking referential transparency.
 
241
--
 
242
unsafePackCStringLen :: CStringLen -> IO ByteString
 
243
unsafePackCStringLen (ptr,len) = do
 
244
    fp <- newForeignPtr_ (castPtr ptr)
 
245
    return $! PS fp 0 (fromIntegral len)
 
246
 
 
247
-- | /O(n)/ Build a @ByteString@ from a malloced @CString@. This value will
 
248
-- have a @free(3)@ finalizer associated to it.
 
249
--
 
250
-- This funtion is /unsafe/. If the original @CString@ is later
 
251
-- modified, this change will be reflected in the resulting @ByteString@,
 
252
-- breaking referential transparency.
 
253
--
 
254
-- This function is also unsafe if you call its finalizer twice,
 
255
-- which will result in a /double free/ error, or if you pass it
 
256
-- a CString not allocated with 'malloc'.
 
257
--
 
258
unsafePackMallocCString :: CString -> IO ByteString
 
259
unsafePackMallocCString cstr = do
 
260
    fp <- newForeignPtr c_free_finalizer (castPtr cstr)
 
261
    len <- c_strlen cstr
 
262
    return $! PS fp 0 (fromIntegral len)
 
263
 
 
264
-- ---------------------------------------------------------------------
 
265
 
 
266
-- | /O(1) construction/ Use a @ByteString@ with a function requiring a
 
267
-- @CString@.
 
268
--
 
269
-- This function does zero copying, and merely unwraps a @ByteString@ to
 
270
-- appear as a @CString@. It is /unsafe/ in two ways:
 
271
--
 
272
-- * After calling this function the @CString@ shares the underlying
 
273
-- byte buffer with the original @ByteString@. Thus modifying the
 
274
-- @CString@, either in C, or using poke, will cause the contents of the
 
275
-- @ByteString@ to change, breaking referential transparency. Other
 
276
-- @ByteStrings@ created by sharing (such as those produced via 'take'
 
277
-- or 'drop') will also reflect these changes. Modifying the @CString@
 
278
-- will break referential transparency. To avoid this, use
 
279
-- @useAsCString@, which makes a copy of the original @ByteString@.
 
280
--
 
281
-- * @CStrings@ are often passed to functions that require them to be
 
282
-- null-terminated. If the original @ByteString@ wasn't null terminated,
 
283
-- neither will the @CString@ be. It is the programmers responsibility
 
284
-- to guarantee that the @ByteString@ is indeed null terminated. If in
 
285
-- doubt, use @useAsCString@.
 
286
--
 
287
unsafeUseAsCString :: ByteString -> (CString -> IO a) -> IO a
 
288
unsafeUseAsCString (PS ps s _) ac = withForeignPtr ps $ \p -> ac (castPtr p `plusPtr` s)
 
289
 
 
290
-- | /O(1) construction/ Use a @ByteString@ with a function requiring a
 
291
-- @CStringLen@.
 
292
-- 
 
293
-- This function does zero copying, and merely unwraps a @ByteString@ to
 
294
-- appear as a @CStringLen@. It is /unsafe/:
 
295
--
 
296
-- * After calling this function the @CStringLen@ shares the underlying
 
297
-- byte buffer with the original @ByteString@. Thus modifying the
 
298
-- @CStringLen@, either in C, or using poke, will cause the contents of the
 
299
-- @ByteString@ to change, breaking referential transparency. Other
 
300
-- @ByteStrings@ created by sharing (such as those produced via 'take'
 
301
-- or 'drop') will also reflect these changes. Modifying the @CStringLen@
 
302
-- will break referential transparency. To avoid this, use
 
303
-- @useAsCStringLen@, which makes a copy of the original @ByteString@.
 
304
--
 
305
unsafeUseAsCStringLen :: ByteString -> (CStringLen -> IO a) -> IO a
 
306
unsafeUseAsCStringLen (PS ps s l) f = withForeignPtr ps $ \p -> f (castPtr p `plusPtr` s,l)