~ubuntu-branches/ubuntu/trusty/haskell-mmap/trusty

« back to all changes in this revision

Viewing changes to System/IO/MMap.hs

  • Committer: Bazaar Package Importer
  • Author(s): Marco Túlio Gontijo e Silva
  • Date: 2009-07-17 10:16:51 UTC
  • Revision ID: james.westby@ubuntu.com-20090717101651-h7uetsxv03de5tq3
Tags: upstream-0.4.1
Import upstream version 0.4.1

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
{-# OPTIONS_GHC -fglasgow-exts #-}
 
2
 
 
3
module System.IO.MMap
 
4
(
 
5
     -- $mmap_intro
 
6
 
 
7
     -- * Memory mapped files strict interface
 
8
     mmapFilePtr,
 
9
     mmapFileForeignPtr,
 
10
     mmapFileByteString,
 
11
 
 
12
     -- * Memory mapped files lazy interface
 
13
     mmapFilePtrLazy,
 
14
     mmapFileForeignPtrLazy,
 
15
     mmapFileByteStringLazy,
 
16
 
 
17
     -- * Mapping mode
 
18
     Mode(..)
 
19
)
 
20
where
 
21
 
 
22
import System.IO ()
 
23
import Foreign.Ptr (Ptr,FunPtr,nullPtr,plusPtr)
 
24
import Foreign.C.Types (CInt,CLLong)
 
25
import Foreign.C.String (CString,withCString)
 
26
import Foreign.ForeignPtr (ForeignPtr,withForeignPtr,finalizeForeignPtr,newForeignPtr,newForeignPtrEnv)
 
27
import Foreign.Storable( poke )
 
28
import Foreign.Marshal.Alloc( malloc )
 
29
import Foreign.C.Error ( throwErrno )
 
30
import qualified Foreign.Concurrent( newForeignPtr )
 
31
import System.IO.Unsafe  (unsafePerformIO)
 
32
import qualified Data.ByteString.Unsafe as BS (unsafePackCStringFinalizer)
 
33
import Data.Int (Int64)
 
34
import Control.Monad  (when)
 
35
import Control.Exception   (bracket)
 
36
import qualified Data.ByteString as BS (ByteString)
 
37
import qualified Data.ByteString.Lazy as BSL  (ByteString,fromChunks)
 
38
 
 
39
-- $mmap_intro
 
40
--
 
41
-- This module is an interface to mmap(2) system call under POSIX (Unix, Linux,
 
42
-- Mac OS X) and CreateFileMapping,MapViewOfFile under Windows.
 
43
--
 
44
-- We can consider mmap as lazy IO pushed into the virtual memory
 
45
-- subsystem.
 
46
--
 
47
-- It is only safe to mmap a file if you know you are the sole user.
 
48
--
 
49
-- For more details about mmap, and its consequences, see:
 
50
--
 
51
-- * <http://opengroup.org/onlinepubs/009695399/functions/mmap.html>
 
52
--
 
53
-- * <http://www.gnu.org/software/libc/manual/html_node/Memory_002dmapped-I_002fO.html>
 
54
--
 
55
-- * <http://msdn2.microsoft.com/en-us/library/aa366781(VS.85).aspx>
 
56
--
 
57
 
 
58
-- | Mode of mapping. Three cases are supported.
 
59
data Mode = ReadOnly      -- ^ file is mapped read-only
 
60
          | ReadWrite     -- ^ file is mapped read-write
 
61
          | WriteCopy     -- ^ file is mapped read-write, but changes aren't propagated to disk
 
62
    deriving (Eq,Ord,Enum)
 
63
 
 
64
-- | The 'mmapFilePtr' function maps a file or device into memory,
 
65
-- returning a tripple containing pointer that accesses the mapped file,
 
66
-- the finalizer to run to unmap region and size of mmaped memory.
 
67
--
 
68
-- If the mmap fails for some reason, an error is thrown.
 
69
--
 
70
-- Memory mapped files will behave as if they were read lazily --
 
71
-- pages from the file will be loaded into memory on demand.
 
72
--
 
73
-- The storage manager is used to free the mapped memory. When
 
74
-- the garbage collector notices there are no further references to the
 
75
-- mapped memory, a call to munmap is made. It is not necessary to do
 
76
-- this yourself. In tight memory situations, it may be profitable to
 
77
-- use 'System.Mem.performGC' or 'finalizeForeignPtr' to force an unmap.
 
78
--
 
79
-- File must be created with correct attributes prior to mapping it
 
80
-- into memory.
 
81
--
 
82
-- If mode is 'ReadWrite' or 'WriteCopy', the returned memory region may
 
83
-- be written to with 'Foreign.Storable.poke' and friends.
 
84
--
 
85
-- Range specified may be 'Nothing', then whole file is mapped. Otherwise
 
86
-- range should be 'Just (offset,size)' where offsets is the beginning byte
 
87
-- of file region to map and size tells its length. There are no alignment
 
88
-- requirements.
 
89
--
 
90
-- If range to map extends beyond end of file, it will be resized accordingly.
 
91
--
 
92
mmapFilePtr :: FilePath                -- ^ name of file to mmap
 
93
            -> Mode                    -- ^ access mode
 
94
            -> Maybe (Int64,Int)       -- ^ range to map, maps whole file if Nothing
 
95
            -> IO (Ptr a,IO (),Int)    -- ^ pointer, finalizer and size
 
96
mmapFilePtr fp m range = do
 
97
  (ptr, size) <- mmapFilePtr' fp m range
 
98
  sizeptr <- malloc
 
99
  poke sizeptr (fromIntegral size)
 
100
  return (ptr, c_system_io_mmap_munmap sizeptr ptr, size)
 
101
 
 
102
-- | Maps region of file and returns it as 'ForeignPtr'. See 'mmapFilePtr' for details.
 
103
mmapFileForeignPtr :: FilePath                     -- ^ name of file to map
 
104
                   -> Mode                         -- ^ access mode
 
105
                   -> Maybe (Int64,Int)            -- ^ range to map, maps whole file if Nothing
 
106
                   -> IO (ForeignPtr a,Int)        -- ^ foreign pointer to beginning of region and size
 
107
mmapFileForeignPtr fp m range = do
 
108
  (ptr, size) <- mmapFilePtr' fp m range
 
109
  sizeptr <- malloc
 
110
  poke sizeptr (fromIntegral size)
 
111
  foreignptr <- newForeignPtrEnv c_system_io_mmap_munmap_funptr sizeptr ptr
 
112
  return (foreignptr,size)
 
113
 
 
114
mmapFilePtr' :: FilePath                -- ^ name of file to mmap
 
115
             -> Mode                    -- ^ access mode
 
116
             -> Maybe (Int64,Int)       -- ^ range to map, maps whole file if Nothing
 
117
             -> IO (Ptr a,Int)          -- ^ pointer and size
 
118
mmapFilePtr' filepath mode offsetsize = do
 
119
    bracket (mmapFileOpen filepath mode)
 
120
            (finalizeForeignPtr) mmap
 
121
    where
 
122
        mmap handle = do
 
123
            (offset,size) <- case offsetsize of
 
124
                Just (offset,size) -> return (offset,size)
 
125
                Nothing -> do
 
126
                    longsize <- withForeignPtr handle c_system_io_file_size
 
127
                    when (longsize > fromIntegral (maxBound :: Int)) $
 
128
                         fail ("file is longer (" ++ show longsize ++ ") than maxBound::Int")
 
129
                    return (0,fromIntegral longsize)
 
130
            withForeignPtr handle $ \handle -> do
 
131
                let align = offset `mod` fromIntegral c_system_io_granularity
 
132
                    offsetraw = offset - align
 
133
                    sizeraw = size + fromIntegral align
 
134
                ptr <- c_system_io_mmap_mmap handle (fromIntegral $ fromEnum mode) (fromIntegral offsetraw) (fromIntegral sizeraw)
 
135
                when (ptr == nullPtr) $
 
136
                      throwErrno $ "mmap of '" ++ filepath ++ "' failed"
 
137
                return (ptr `plusPtr` fromIntegral align,fromIntegral size)
 
138
 
 
139
-- | Maps region of file and returns it as 'Data.ByteString.ByteString'.
 
140
-- File is mapped in in 'ReadOnly' mode. See 'mmapFilePtr' for details
 
141
--
 
142
-- Note: this operation may break referential transparency! If
 
143
-- any other process on the system changes the file when it is mapped
 
144
-- into Haskell, the contents of your 'Data.ByteString.ByteString' may change.
 
145
--
 
146
mmapFileByteString :: FilePath                     -- ^ name of file to map
 
147
                   -> Maybe (Int64,Int)            -- ^ range to map, maps whole file if Nothing
 
148
                   -> IO BS.ByteString                -- ^ bytestring with file content
 
149
mmapFileByteString filepath offsetsize = do
 
150
    (ptr,finalizer,size) <- mmapFilePtr filepath ReadOnly offsetsize
 
151
    bytestring <- BS.unsafePackCStringFinalizer ptr size finalizer
 
152
    return bytestring
 
153
 
 
154
-- | The 'mmapFilePtrLazy' function maps a file or device into memory,
 
155
-- returning a list of tripples containing pointer that accesses the mapped file,
 
156
-- the finalizer to run to unmap that region and size of mapped memory.
 
157
--
 
158
-- If the mmap fails for some reason, an error is thrown.
 
159
--
 
160
-- Memory mapped files will behave as if they were read lazily --
 
161
-- pages from the file will be loaded into memory on demand.
 
162
--
 
163
-- The storage manager is used to free the mapped memory. When
 
164
-- the garbage collector notices there are no further references to the
 
165
-- mapped memory, a call to munmap is made. It is not necessary to do
 
166
-- this yourself. In tight memory situations, it may be profitable to
 
167
-- use 'System.Mem.performGC' or 'finalizeForeignPtr' to force an unmap.
 
168
--
 
169
-- File must be created with correct attributes prior to mapping it
 
170
-- into memory.
 
171
--
 
172
-- If mode is 'ReadWrite' or 'WriteCopy', the returned memory region may
 
173
-- be written to with 'Foreign.Storable.poke' and friends.
 
174
--
 
175
-- Range specified may be 'Nothing', then whole file is mapped. Otherwise
 
176
-- range should be 'Just (offset,size)' where offsets is the beginning byte
 
177
-- of file region to map and size tells its length. There are no alignment
 
178
-- requirements.
 
179
--
 
180
-- If range to map extends beyond end of file, it will be resized accordingly.
 
181
--
 
182
mmapFilePtrLazy :: FilePath                -- ^ name of file to mmap
 
183
            -> Mode                        -- ^ access mode
 
184
            -> Maybe (Int64,Int64)         -- ^ range to map, maps whole file if Nothing
 
185
            -> IO [(Ptr a,IO (),Int)]      -- ^ list of pointer, finalizer and size
 
186
mmapFilePtrLazy filepath mode offsetsize = do
 
187
    handle <- mmapFileOpen filepath mode
 
188
    mmap handle
 
189
    where
 
190
        mmap handle = do
 
191
            (offset,size) <- case offsetsize of
 
192
                Just (offset,size) -> return (offset,size)
 
193
                Nothing -> do
 
194
                    longsize <- withForeignPtr handle c_system_io_file_size
 
195
                    return (0,fromIntegral longsize)
 
196
            return $ map (mapChunk handle) (chunks offset size)
 
197
        mapChunk handle (offset,size) = unsafePerformIO $
 
198
            withForeignPtr handle $ \handle -> do
 
199
                let align = offset `mod` fromIntegral c_system_io_granularity
 
200
                    offsetraw = offset - align
 
201
                    sizeraw = size + fromIntegral align
 
202
                ptr <- c_system_io_mmap_mmap handle (fromIntegral $ fromEnum mode) (fromIntegral offsetraw) (fromIntegral sizeraw)
 
203
                when (ptr == nullPtr) $
 
204
                     throwErrno $ "mmap of '" ++ filepath ++ "' failed"
 
205
                sizeptr <- malloc
 
206
                poke sizeptr $ fromIntegral sizeraw
 
207
                let finalizer = c_system_io_mmap_munmap sizeptr ptr
 
208
                return (ptr `plusPtr` fromIntegral align,finalizer,fromIntegral size)
 
209
 
 
210
chunks :: Int64 -> Int64 -> [(Int64,Int)]
 
211
chunks offset size | size <= fromIntegral chunkSize = [(offset,fromIntegral size)]
 
212
                   | otherwise = let offset2 = offset + fromIntegral chunkSize `div` fromIntegral chunkSize * fromIntegral chunkSize
 
213
                                     size2 = fromIntegral (offset2 - offset)
 
214
                                 in (offset,size2) : chunks (offset2) (size-fromIntegral size2)
 
215
 
 
216
-- | Maps region of file and returns it as list of 'ForeignPtr's. See 'mmapFilePtr' for details.
 
217
-- Each chunk is mapped in on demand only.
 
218
mmapFileForeignPtrLazy :: FilePath                   -- ^ name of file to map
 
219
                   -> Mode                           -- ^ access mode
 
220
                   -> Maybe (Int64,Int64)            -- ^ range to map, maps whole file if Nothing
 
221
                   -> IO [(ForeignPtr a,Int)]        -- ^ foreign pointer to beginning of region and size
 
222
mmapFileForeignPtrLazy filepath mode offsetsize = do
 
223
    list <- mmapFilePtrLazy filepath mode offsetsize
 
224
    return (map turn list)
 
225
    where
 
226
        turn (ptr,finalizer,size) = unsafePerformIO $ do
 
227
            foreignptr <- Foreign.Concurrent.newForeignPtr ptr finalizer
 
228
            return (foreignptr,size)
 
229
 
 
230
-- | Maps region of file and returns it as 'Data.ByteString.Lazy.ByteString'.
 
231
-- File is mapped in in 'ReadOnly' mode. See 'mmapFilePtrLazy' for details.
 
232
-- Chunks are mapped in on demand.
 
233
--
 
234
-- Note: this operation may break referential transparency! If
 
235
-- any other process on the system changes the file when it is mapped
 
236
-- into Haskell, the contents of your 'Data.ByteString.Lazy.ByteString' may change.
 
237
--
 
238
mmapFileByteStringLazy :: FilePath                     -- ^ name of file to map
 
239
                       -> Maybe (Int64,Int64)          -- ^ range to map, maps whole file if Nothing
 
240
                       -> IO BSL.ByteString            -- ^ bytestring with file content
 
241
mmapFileByteStringLazy filepath offsetsize = do
 
242
    list <- mmapFilePtrLazy filepath ReadOnly offsetsize
 
243
    return (BSL.fromChunks (map turn list))
 
244
    where
 
245
        turn (ptr,finalizer,size) = unsafePerformIO $ do
 
246
            bytestring <- BS.unsafePackCStringFinalizer ptr size finalizer
 
247
            return bytestring
 
248
 
 
249
chunkSize :: Int
 
250
chunkSize = fromIntegral $ (128*1024 `div` c_system_io_granularity) * c_system_io_granularity
 
251
 
 
252
mmapFileOpen :: FilePath -> Mode -> IO (ForeignPtr ())
 
253
mmapFileOpen filepath mode = do
 
254
    ptr <- withCString filepath $ \filepath -> c_system_io_mmap_file_open filepath (fromIntegral $ fromEnum mode)
 
255
    when (ptr == nullPtr) $
 
256
        throwErrno $ "opening of '" ++ filepath ++ "' failed"
 
257
    handle <- newForeignPtr c_system_io_mmap_file_close ptr
 
258
    return handle
 
259
 
 
260
foreign import ccall unsafe "system_io_mmap_file_open"
 
261
    c_system_io_mmap_file_open :: CString -> CInt -> IO (Ptr ())
 
262
foreign import ccall unsafe "&system_io_mmap_file_close"
 
263
    c_system_io_mmap_file_close :: FunPtr(Ptr () -> IO ())
 
264
 
 
265
foreign import ccall unsafe "system_io_mmap_mmap"
 
266
    c_system_io_mmap_mmap :: Ptr () -> CInt -> CLLong -> CInt -> IO (Ptr a)
 
267
foreign import ccall unsafe "&system_io_mmap_munmap"
 
268
    c_system_io_mmap_munmap_funptr :: FunPtr(Ptr CInt -> Ptr a -> IO ())
 
269
foreign import ccall unsafe "system_io_mmap_munmap"
 
270
    c_system_io_mmap_munmap :: Ptr CInt -> Ptr a -> IO ()
 
271
 
 
272
foreign import ccall unsafe "system_io_mmap_file_size"
 
273
    c_system_io_file_size :: Ptr () -> IO (CLLong)
 
274
foreign import ccall unsafe "system_io_mmap_granularity"
 
275
    c_system_io_granularity :: CInt
 
276
 
 
277