[Haskell-cafe] Haskell & monads for newbies
Bulat Ziganshin
bulat.ziganshin at gmail.com
Mon Jul 16 01:55:55 EDT 2007
Hello Andrew,
Monday, July 16, 2007, 1:06:42 AM, you wrote:
> I have a vague recollection of somebody muttering something about
> ByteStrings and memory-mapped files...?
http://www.haskell.org/library/StreamsBeta.tar.gz
you can either open m/m file with openBinaryMMFile and use it to
read/write any data including ByteStrings or use the following code
that maps file into memory and allow to use it as ByteString
-- -----------------------------------------------------------------------------
-- Mapping file contents into ByteString / memory buffer
#if defined(__GLASGOW_HASKELL__)
#if defined(USE_BYTE_STRING)
-- | Like mmapBinaryFilePtr, but returns ByteString representing
-- the entire file contents.
mmapBinaryFileBS :: FilePath -> IO ByteString
mmapBinaryFileBS f = do
(fp,l) <- mmapBinaryFilePtr f
return $ fromForeignPtr fp 0 l
#endif
-- | Like 'readFile', this reads an entire file directly into a
-- 'ByteString', but it is even more efficient. It involves directly
-- mapping the file to memory. This has the advantage that the contents
-- of the file never need to be copied. Also, under memory pressure the
-- page may simply be discarded, while in the case of readFile it would
-- need to be written to swap. You can run into bus
-- errors if the file is modified.
mmapBinaryFilePtr :: FilePath -> IO (ForeignPtr a, Int)
mmapBinaryFilePtr f = do
fd <- openBinaryFD f ReadMode
len <- fdFileSize fd
l <- checkedFromIntegral len $ do -- some files are >4GB at those days ;)
fail $ "mmapBinaryFilePtr: file '"++f++"' is too big ("++show len++" bytes) !"
-- Don't bother mmaping small files because each mmapped file takes up
-- at least one full VM block.
if l < mmap_limit
then do fp <- mallocForeignPtrBytes l
withForeignPtr fp $ \p-> fdGetBuf fd p l
fdClose fd
return (fp, l)
else do
mmfd <- myOpenMMap fd ReadMode
p <- myMMap mmfd ReadMode 0 l
let unmap = do myUnMMap p l
myCloseMMap mmfd
fdClose fd
return ()
fp <- FC.newForeignPtr p unmap
return (fp, l)
where mmap_limit = 16*1024
#endif
--
Best regards,
Bulat mailto:Bulat.Ziganshin at gmail.com
More information about the Haskell-Cafe
mailing list