Skip to content

Instantly share code, notes, and snippets.

@masterdezign
Forked from nkpart/CrazyIO.hs
Created December 19, 2015 13:27
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save masterdezign/010ecc14bec7a570eedf to your computer and use it in GitHub Desktop.
Save masterdezign/010ecc14bec7a570eedf to your computer and use it in GitHub Desktop.
CrazyIO - binary deserialization using mmaped I/O and Data.Vector.Storable
{-# LANGUAGE ScopedTypeVariables #-}
module CrazyIO (module CrazyIO, mmapFileByteString) where
import qualified Data.Vector.Storable as V
import qualified Data.ByteString as BS
import qualified Data.ByteString.Internal as BS
import Foreign
import System.IO.MMap
crazyLoad :: forall a. Storable a => FilePath -> Maybe (Int64, Int) -> IO (V.Vector a)
crazyLoad name range =
do (ptr,offset,size) <- mmapFileForeignPtr name ReadOnly range
return $
V.unsafeFromForeignPtr
ptr
offset
(size `div`
sizeOf (undefined :: a))
crazyLoadReinterpret :: Storable a => FilePath -> Maybe (Int64, Int) -> (BS.ByteString -> IO BS.ByteString) -> IO (V.Vector a)
crazyLoadReinterpret name range f = do
-- It would sometimes be useful to load a lazy bytestring here. However
-- in testing it proved to just result in ERROR being thrown somewhere.
v <- mmapFileByteString name range
x <- f v
return $ byteStringToVector x
byteStringToVector :: (Storable a) => BS.ByteString -> V.Vector a
byteStringToVector bs = vec where
vec = V.unsafeFromForeignPtr (castForeignPtr fptr) (scale off) (scale len)
(fptr, off, len) = BS.toForeignPtr bs
scale = (`div` sizeOfElem vec)
sizeOfElem :: (Storable a) => V.Vector a -> Int
sizeOfElem vec = sizeOf (undefined `asTypeOf` V.head vec)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment