module Data.StorableVector.Lazy (
Vector(SV, chunks),
ChunkSize(ChunkSize),
chunkSize,
defaultChunkSize,
empty,
singleton,
fromChunks,
pack,
unpack,
packWith,
unpackWith,
unfoldr,
unfoldrResult,
sample,
sampleN,
iterate,
repeat,
cycle,
replicate,
null,
length,
equal,
index,
cons,
append,
extendL,
concat,
sliceVertical,
snoc,
map,
reverse,
foldl,
foldl',
foldr,
foldMap,
monoidConcatMap,
any,
all,
maximum,
minimum,
pointer,
viewL,
viewR,
switchL,
switchR,
scanl,
mapAccumL,
mapAccumR,
crochetL,
take,
takeEnd,
drop,
splitAt,
dropMarginRem,
dropMargin,
dropWhile,
takeWhile,
span,
filter,
zipWith,
zipWith3,
zipWith4,
zipWithAppend,
zipWithLastPattern,
zipWithLastPattern3,
zipWithLastPattern4,
zipWithSize,
zipWithSize3,
zipWithSize4,
sieve,
deinterleave,
interleaveFirstPattern,
pad,
compact,
fromChunk,
hGetContentsAsync,
hGetContentsSync,
hPut,
readFileAsync,
writeFile,
appendFile,
interact,
crochetLChunk,
padAlt,
cancelNullVector,
moduleError,
) where
import qualified Data.List as List
import qualified Data.StorableVector as V
import qualified Data.StorableVector.Base as VB
import qualified Data.StorableVector.Lazy.PointerPrivate as Ptr
import qualified Numeric.NonNegative.Class as NonNeg
import qualified Data.List.HT as ListHT
import Data.Tuple.HT (mapPair, mapFst, mapSnd, swap, )
import Data.Maybe.HT (toMaybe, )
import Data.Maybe (fromMaybe, )
import Foreign.Storable (Storable)
import Data.Monoid (Monoid, mempty, mappend, mconcat, )
import Control.Monad (liftM, liftM2, liftM3, liftM4, mfilter, )
import qualified System.IO as IO
import System.IO (openBinaryFile, IOMode(WriteMode, ReadMode, AppendMode),
hClose, Handle)
import Control.DeepSeq (NFData, rnf)
import Control.Exception (bracket, catch, )
import qualified System.IO.Error as Exc
import qualified System.Unsafe as Unsafe
import qualified Test.QuickCheck as QC
import qualified Prelude as P
import Data.Either (Either(Left, Right), either, )
import Data.Maybe (Maybe(Just, Nothing), maybe, )
import Data.Function (const, flip, id, ($), (.), )
import Data.Tuple (fst, snd, uncurry, )
import Data.Bool (Bool(True,False), not, (&&), )
import Data.Ord (Ord, (<), (>), (<=), (>=), min, max, )
import Data.Eq (Eq, (==), )
import Control.Monad (mapM_, fmap, (=<<), (>>=), (>>), return, )
import Text.Show (Show, showsPrec, showParen, showString, show, )
import Prelude
(IO, error, IOError,
FilePath, String, succ,
Num, Int, sum, (+), (), divMod, mod, fromInteger, )
newtype Vector a = SV {chunks :: [V.Vector a]}
instance (Storable a) => Monoid (Vector a) where
mempty = empty
mappend = append
mconcat = concat
instance (Storable a, Eq a) => Eq (Vector a) where
(==) = equal
instance (Storable a, Show a) => Show (Vector a) where
showsPrec p xs =
showParen (p>=10)
(showString "VectorLazy.fromChunks " .
showsPrec 10 (chunks xs))
instance (Storable a, QC.Arbitrary a) => QC.Arbitrary (Vector a) where
arbitrary = liftM2 pack QC.arbitrary QC.arbitrary
instance (Storable a) => NFData (Vector a) where
rnf = rnf . List.map rnf . chunks
newtype ChunkSize = ChunkSize Int
deriving (Eq, Ord, Show)
instance QC.Arbitrary ChunkSize where
arbitrary = fmap ChunkSize $ QC.choose (1,2048)
instance Num ChunkSize where
(ChunkSize x) + (ChunkSize y) = ChunkSize (x+y)
() = moduleError "ChunkSize.-" "intentionally unimplemented"
(*) = moduleError "ChunkSize.*" "intentionally unimplemented"
abs = moduleError "ChunkSize.abs" "intentionally unimplemented"
signum = moduleError "ChunkSize.signum" "intentionally unimplemented"
fromInteger = ChunkSize . fromInteger
instance Monoid ChunkSize where
mempty = ChunkSize 0
mappend (ChunkSize x) (ChunkSize y) = ChunkSize (x+y)
mconcat = ChunkSize . sum . List.map (\(ChunkSize c) -> c)
instance NonNeg.C ChunkSize where
split = NonNeg.splitDefault (\(ChunkSize c) -> c) ChunkSize
chunkSize :: Int -> ChunkSize
chunkSize x =
ChunkSize $
if x>0
then x
else moduleError "chunkSize" ("no positive number: " List.++ show x)
defaultChunkSize :: ChunkSize
defaultChunkSize =
ChunkSize 1024
empty :: (Storable a) => Vector a
empty = SV []
singleton :: (Storable a) => a -> Vector a
singleton x = SV [V.singleton x]
fromChunks :: (Storable a) => [V.Vector a] -> Vector a
fromChunks = SV
pack :: (Storable a) => ChunkSize -> [a] -> Vector a
pack size = unfoldr size ListHT.viewL
unpack :: (Storable a) => Vector a -> [a]
unpack = List.concatMap V.unpack . chunks
packWith :: (Storable b) => ChunkSize -> (a -> b) -> [a] -> Vector b
packWith size f = unfoldr size (fmap (mapFst f) . ListHT.viewL)
unpackWith :: (Storable a) => (a -> b) -> Vector a -> [b]
unpackWith f = List.concatMap (V.unpackWith f) . chunks
unfoldr :: (Storable b) =>
ChunkSize ->
(a -> Maybe (b,a)) ->
a ->
Vector b
unfoldr (ChunkSize size) f =
SV .
List.unfoldr (cancelNullVector . V.unfoldrN size f =<<) .
Just
unfoldrResult :: (Storable b) =>
ChunkSize ->
(a -> Either c (b, a)) ->
a ->
(Vector b, c)
unfoldrResult (ChunkSize size) f =
let recourse a0 =
let (chunk, a1) =
V.unfoldrResultN size Right (either (Left . Left) Right . f) a0
in either
((,) (if V.null chunk then [] else [chunk]))
(mapFst (chunk :) . recourse) a1
in mapFst SV . recourse
sample :: (Storable a) => ChunkSize -> (Int -> a) -> Vector a
sample size f =
unfoldr size (\i -> Just (f i, succ i)) 0
sampleN :: (Storable a) => ChunkSize -> Int -> (Int -> a) -> Vector a
sampleN size n f =
unfoldr size (\i -> toMaybe (i<n) (f i, succ i)) 0
iterate :: Storable a => ChunkSize -> (a -> a) -> a -> Vector a
iterate size f = unfoldr size (\x -> Just (x, f x))
repeat :: Storable a => ChunkSize -> a -> Vector a
repeat (ChunkSize size) =
SV . List.repeat . V.replicate size
cycle :: Storable a => Vector a -> Vector a
cycle =
SV . List.cycle . chunks
replicate :: Storable a => ChunkSize -> Int -> a -> Vector a
replicate (ChunkSize size) n x =
let (numChunks, rest) = divMod n size
in append
(SV (List.replicate numChunks (V.replicate size x)))
(fromChunk (V.replicate rest x))
null :: (Storable a) => Vector a -> Bool
null = List.null . chunks
length :: Vector a -> Int
length = sum . List.map V.length . chunks
equal :: (Storable a, Eq a) => Vector a -> Vector a -> Bool
equal (SV xs0) (SV ys0) =
let recourse (x:xs) (y:ys) =
let l = min (V.length x) (V.length y)
(xPrefix, xSuffix) = V.splitAt l x
(yPrefix, ySuffix) = V.splitAt l y
build z zs =
if V.null z then zs else z:zs
in xPrefix == yPrefix &&
recourse (build xSuffix xs) (build ySuffix ys)
recourse [] [] = True
recourse _ _ = False
in recourse xs0 ys0
index :: (Storable a) => Vector a -> Int -> a
index (SV xs) n =
if n < 0
then
moduleError "index"
("negative index: " List.++ show n)
else
List.foldr
(\x k m0 ->
let m1 = m0 V.length x
in if m1 < 0
then VB.unsafeIndex x m0
else k m1)
(\m -> moduleError "index"
("index too large: " List.++ show n
List.++ ", length = " List.++ show (nm)))
xs n
cons :: Storable a => a -> Vector a -> Vector a
cons x = SV . (V.singleton x :) . chunks
infixr 5 `append`
append :: Storable a => Vector a -> Vector a -> Vector a
append (SV xs) (SV ys) = SV (xs List.++ ys)
extendL :: Storable a => ChunkSize -> V.Vector a -> Vector a -> Vector a
extendL (ChunkSize size) x (SV yt) =
SV $
maybe
[x]
(\(y,ys) ->
if V.length x + V.length y <= size
then V.append x y : ys
else x:yt)
(ListHT.viewL yt)
concat :: (Storable a) => [Vector a] -> Vector a
concat = SV . List.concat . List.map chunks
sliceVertical :: (Storable a) => Int -> Vector a -> [Vector a]
sliceVertical n =
List.unfoldr (\x -> toMaybe (not (null x)) (splitAt n x))
snoc :: Storable a => Vector a -> a -> Vector a
snoc xs x = append xs $ singleton x
map :: (Storable x, Storable y) =>
(x -> y)
-> Vector x
-> Vector y
map f = SV . List.map (V.map f) . chunks
reverse :: Storable a => Vector a -> Vector a
reverse =
SV . List.reverse . List.map V.reverse . chunks
foldl :: Storable b => (a -> b -> a) -> a -> Vector b -> a
foldl f x0 = List.foldl (V.foldl f) x0 . chunks
foldl' :: Storable b => (a -> b -> a) -> a -> Vector b -> a
foldl' f x0 = List.foldl' (V.foldl f) x0 . chunks
foldr :: Storable b => (b -> a -> a) -> a -> Vector b -> a
foldr f x0 = List.foldr (flip (V.foldr f)) x0 . chunks
foldMap :: (Storable a, Monoid m) => (a -> m) -> Vector a -> m
foldMap f = List.foldr (mappend . V.foldMap f) mempty . chunks
monoidConcatMap :: (Storable a, Monoid m) => (a -> m) -> Vector a -> m
monoidConcatMap = foldMap
any :: (Storable a) => (a -> Bool) -> Vector a -> Bool
any p = List.any (V.any p) . chunks
all :: (Storable a) => (a -> Bool) -> Vector a -> Bool
all p = List.all (V.all p) . chunks
maximum, _maximum :: (Storable a, Ord a) => Vector a -> a
maximum = List.maximum . List.map V.maximum . chunks
_maximum = List.foldl1' max . List.map V.maximum . chunks
minimum, _minimum :: (Storable a, Ord a) => Vector a -> a
minimum = List.minimum . List.map V.minimum . chunks
_minimum = List.foldl1' min . List.map V.minimum . chunks
pointer :: Storable a => Vector a -> Ptr.Pointer a
pointer = Ptr.cons . chunks
viewL :: Storable a => Vector a -> Maybe (a, Vector a)
viewL (SV xs0) =
do (x,xs) <- ListHT.viewL xs0
(y,ys) <- V.viewL x
return (y, append (fromChunk ys) (SV xs))
viewR :: Storable a => Vector a -> Maybe (Vector a, a)
viewR (SV xs0) =
do xsp <- ListHT.viewR xs0
let (xs,x) = xsp
let (ys,y) = fromMaybe (moduleError "viewR" "last chunk empty") (V.viewR x)
return (append (SV xs) (fromChunk ys), y)
switchL :: Storable a => b -> (a -> Vector a -> b) -> Vector a -> b
switchL n j =
maybe n (uncurry j) . viewL
switchR :: Storable a => b -> (Vector a -> a -> b) -> Vector a -> b
switchR n j =
maybe n (uncurry j) . viewR
scanl :: (Storable a, Storable b) =>
(a -> b -> a) -> a -> Vector b -> Vector a
scanl f start =
cons start . snd .
mapAccumL (\acc -> (\b -> (b,b)) . f acc) start
mapAccumL :: (Storable a, Storable b) =>
(acc -> a -> (acc, b)) -> acc -> Vector a -> (acc, Vector b)
mapAccumL f start =
mapSnd SV .
List.mapAccumL (V.mapAccumL f) start .
chunks
mapAccumR :: (Storable a, Storable b) =>
(acc -> a -> (acc, b)) -> acc -> Vector a -> (acc, Vector b)
mapAccumR f start =
mapSnd SV .
List.mapAccumR (V.mapAccumR f) start .
chunks
crochetLChunk :: (Storable x, Storable y) =>
(x -> acc -> Maybe (y, acc))
-> acc
-> V.Vector x
-> (V.Vector y, Maybe acc)
crochetLChunk = V.crochetLResult
crochetL :: (Storable x, Storable y) =>
(x -> acc -> Maybe (y, acc))
-> acc
-> Vector x
-> Vector y
crochetL f acc0 =
SV . List.unfoldr (\(xt,acc) ->
do (x,xs) <- ListHT.viewL xt
acc' <- acc
return $ mapSnd ((,) xs) $ V.crochetLResult f acc' x) .
flip (,) (Just acc0) .
chunks
take :: (Storable a) => Int -> Vector a -> Vector a
take 0 _ = empty
take _ (SV []) = empty
take n (SV (x:xs)) =
let m = V.length x
in if m<=n
then SV $ (x:) $ chunks $ take (nm) $ SV xs
else fromChunk (V.take n x)
takeEnd :: (Storable a) => Int -> Vector a -> Vector a
takeEnd n xs =
List.foldl (flip drop) xs $ List.map V.length $ chunks $ drop n xs
drop :: (Storable a) => Int -> Vector a -> Vector a
drop _ (SV []) = empty
drop n (SV (x:xs)) =
let m = V.length x
in if m<=n
then drop (nm) (SV xs)
else SV (V.drop n x : xs)
splitAt :: (Storable a) => Int -> Vector a -> (Vector a, Vector a)
splitAt n0 =
let recourse 0 xs = ([], xs)
recourse _ [] = ([], [])
recourse n (x:xs) =
let m = V.length x
in if m<=n
then mapFst (x:) $ recourse (nm) xs
else mapPair ((:[]), (:xs)) $ V.splitAt n x
in mapPair (SV, SV) . recourse n0 . chunks
dropMarginRem :: (Storable a) => Int -> Int -> Vector a -> (Int, Vector a)
dropMarginRem n m xs =
List.foldl'
(\(mi,xsi) k -> (mik, drop k xsi))
(m,xs)
(List.map V.length $ chunks $ take m $ drop n xs)
dropMargin :: (Storable a) => Int -> Int -> Vector a -> Vector a
dropMargin n m xs =
List.foldl' (flip drop) xs
(List.map V.length $ chunks $ take m $ drop n xs)
dropWhile :: (Storable a) => (a -> Bool) -> Vector a -> Vector a
dropWhile _ (SV []) = empty
dropWhile p (SV (x:xs)) =
let y = V.dropWhile p x
in if V.null y
then dropWhile p (SV xs)
else SV (y:xs)
takeWhile :: (Storable a) => (a -> Bool) -> Vector a -> Vector a
takeWhile _ (SV []) = empty
takeWhile p (SV (x:xs)) =
let y = V.takeWhile p x
in if V.length y < V.length x
then fromChunk y
else SV (x : chunks (takeWhile p (SV xs)))
span, _span :: (Storable a) => (a -> Bool) -> Vector a -> (Vector a, Vector a)
span p =
let recourse [] = ([],[])
recourse (x:xs) =
let (y,z) = V.span p x
in if V.null z
then mapFst (x:) (recourse xs)
else (chunks $ fromChunk y, (z:xs))
in mapPair (SV, SV) . recourse . chunks
_span p =
let recourse (SV []) = (empty, empty)
recourse (SV (x:xs)) =
let (y,z) = V.span p x
in if V.length y == 0
then mapFst (SV . (x:) . chunks) (recourse (SV xs))
else (SV [y], SV (z:xs))
in recourse
filter :: (Storable a) => (a -> Bool) -> Vector a -> Vector a
filter p =
SV . List.filter (not . V.null) . List.map (V.filter p) . chunks
zipWith :: (Storable a, Storable b, Storable c) =>
(a -> b -> c)
-> Vector a
-> Vector b
-> Vector c
zipWith = zipWithCont (const empty) (const empty)
zipWith3 :: (Storable a, Storable b, Storable c, Storable d) =>
(a -> b -> c -> d)
-> Vector a
-> Vector b
-> Vector c
-> Vector d
zipWith3 f as0 bs0 cs0 =
let recourse at@(a:_) bt@(b:_) ct@(c:_) =
let z = V.zipWith3 f a b c
n = V.length z
in z : recourse
(chunks $ drop n $ fromChunks at)
(chunks $ drop n $ fromChunks bt)
(chunks $ drop n $ fromChunks ct)
recourse _ _ _ = []
in fromChunks $ recourse (chunks as0) (chunks bs0) (chunks cs0)
zipWith4 :: (Storable a, Storable b, Storable c, Storable d, Storable e) =>
(a -> b -> c -> d -> e)
-> Vector a
-> Vector b
-> Vector c
-> Vector d
-> Vector e
zipWith4 f as0 bs0 cs0 ds0 =
let recourse at@(a:_) bt@(b:_) ct@(c:_) dt@(d:_) =
let z = V.zipWith4 f a b c d
n = V.length z
in z : recourse
(chunks $ drop n $ fromChunks at)
(chunks $ drop n $ fromChunks bt)
(chunks $ drop n $ fromChunks ct)
(chunks $ drop n $ fromChunks dt)
recourse _ _ _ _ = []
in fromChunks $
recourse (chunks as0) (chunks bs0) (chunks cs0) (chunks ds0)
zipWithAppend :: (Storable a) =>
(a -> a -> a)
-> Vector a
-> Vector a
-> Vector a
zipWithAppend = zipWithCont id id
zipWithCont :: (Storable a, Storable b, Storable c) =>
(Vector a -> Vector c)
-> (Vector b -> Vector c)
-> (a -> b -> c)
-> Vector a
-> Vector b
-> Vector c
zipWithCont ga gb f as0 bs0 =
let recourse at@(a:_) bt@(b:_) =
let z = V.zipWith f a b
n = V.length z
in z : recourse
(chunks $ drop n $ fromChunks at)
(chunks $ drop n $ fromChunks bt)
recourse [] bs = chunks $ gb $ fromChunks bs
recourse as [] = chunks $ ga $ fromChunks as
in fromChunks $ recourse (chunks as0) (chunks bs0)
zipWithLastPattern :: (Storable a, Storable b, Storable c) =>
(a -> b -> c)
-> Vector a
-> Vector b
-> Vector c
zipWithLastPattern f =
crochetL (\y -> liftM (mapFst (flip f y)) . Ptr.viewL) . pointer
zipWithLastPattern3 ::
(Storable a, Storable b, Storable c, Storable d) =>
(a -> b -> c -> d) ->
(Vector a -> Vector b -> Vector c -> Vector d)
zipWithLastPattern3 f s0 s1 =
crochetL (\z (xt,yt) ->
liftM2
(\(x,xs) (y,ys) -> (f x y z, (xs,ys)))
(Ptr.viewL xt)
(Ptr.viewL yt))
(pointer s0, pointer s1)
zipWithLastPattern4 ::
(Storable a, Storable b, Storable c, Storable d, Storable e) =>
(a -> b -> c -> d -> e) ->
(Vector a -> Vector b -> Vector c -> Vector d -> Vector e)
zipWithLastPattern4 f s0 s1 s2 =
crochetL (\w (xt,yt,zt) ->
liftM3
(\(x,xs) (y,ys) (z,zs) -> (f x y z w, (xs,ys,zs)))
(Ptr.viewL xt)
(Ptr.viewL yt)
(Ptr.viewL zt))
(pointer s0, pointer s1, pointer s2)
zipWithSize :: (Storable a, Storable b, Storable c) =>
ChunkSize
-> (a -> b -> c)
-> Vector a
-> Vector b
-> Vector c
zipWithSize size f s0 s1 =
unfoldr size (\(xt,yt) ->
liftM2
(\(x,xs) (y,ys) -> (f x y, (xs,ys)))
(Ptr.viewL xt)
(Ptr.viewL yt))
(pointer s0, pointer s1)
zipWithSize3 ::
(Storable a, Storable b, Storable c, Storable d) =>
ChunkSize -> (a -> b -> c -> d) ->
(Vector a -> Vector b -> Vector c -> Vector d)
zipWithSize3 size f s0 s1 s2 =
unfoldr size (\(xt,yt,zt) ->
liftM3
(\(x,xs) (y,ys) (z,zs) -> (f x y z, (xs,ys,zs)))
(Ptr.viewL xt)
(Ptr.viewL yt)
(Ptr.viewL zt))
(pointer s0, pointer s1, pointer s2)
zipWithSize4 ::
(Storable a, Storable b, Storable c, Storable d, Storable e) =>
ChunkSize -> (a -> b -> c -> d -> e) ->
(Vector a -> Vector b -> Vector c -> Vector d -> Vector e)
zipWithSize4 size f s0 s1 s2 s3 =
unfoldr size (\(xt,yt,zt,wt) ->
liftM4
(\(x,xs) (y,ys) (z,zs) (w,ws) -> (f x y z w, (xs,ys,zs,ws)))
(Ptr.viewL xt)
(Ptr.viewL yt)
(Ptr.viewL zt)
(Ptr.viewL wt))
(pointer s0, pointer s1, pointer s2, pointer s3)
sieve :: (Storable a) => Int -> Vector a -> Vector a
sieve n =
fromChunks . List.filter (not . V.null) . snd .
List.mapAccumL
(\offset chunk ->
(mod (offset V.length chunk) n,
V.sieve n $ V.drop offset chunk)) 0 .
chunks
deinterleave :: (Storable a) => Int -> Vector a -> [Vector a]
deinterleave n =
P.map (sieve n) . P.take n . P.iterate (switchL empty (flip const))
interleaveFirstPattern, _interleaveFirstPattern ::
(Storable a) => [Vector a] -> Vector a
interleaveFirstPattern [] = empty
interleaveFirstPattern vss@(vs:_) =
let pattern = List.map V.length $ chunks vs
split xs =
snd $
List.mapAccumL
(\x n -> swap $ mapFst (V.concat . chunks) $ splitAt n x)
xs pattern
in fromChunks $ List.map V.interleave $
List.transpose $ List.map split vss
_interleaveFirstPattern [] = empty
_interleaveFirstPattern vss@(vs:_) =
fromChunks . snd .
List.mapAccumL
(\xss n ->
swap $
mapFst (V.interleave . List.map (V.concat . chunks)) $
List.unzip $ List.map (splitAt n) xss)
vss .
List.map V.length . chunks $ vs
pad :: (Storable a) => ChunkSize -> a -> Int -> Vector a -> Vector a
pad size y n0 =
let recourse n xt =
if n<=0
then xt
else
case xt of
[] -> chunks $ replicate size n y
x:xs -> x : recourse (n V.length x) xs
in SV . recourse n0 . chunks
padAlt :: (Storable a) => ChunkSize -> a -> Int -> Vector a -> Vector a
padAlt size x n xs =
append xs
(let m = length xs
in if n>m
then replicate size (nm) x
else empty)
compact :: (Storable a) => ChunkSize -> Vector a -> Vector a
compact size (SV xs) =
SV $ List.map V.concat $
compactGen
(\x y -> mfilter (<=size) $ Just $ mappend x y)
(ChunkSize . V.length) xs
compactGen :: (b -> b -> Maybe b) -> (a -> b) -> [a] -> [[a]]
compactGen _ _ [] = []
compactGen plus measure (x0:xs0) =
uncurry (:) $ mapFst (x0:) $
List.foldr
(\y go s0 ->
let ym = measure y
in case plus s0 ym of
Just s1 -> mapFst (y:) $ go s1
Nothing -> ([], uncurry (:) $ mapFst (y:) $ go ym))
(const ([], [])) xs0 (measure x0)
cancelNullVector :: (V.Vector a, b) -> Maybe (V.Vector a, b)
cancelNullVector y =
toMaybe (not (V.null (fst y))) y
fromChunk :: (Storable a) => V.Vector a -> Vector a
fromChunk x =
if V.null x
then empty
else SV [x]
hGetContentsAsync :: Storable a =>
ChunkSize -> Handle -> IO (IOError, Vector a)
hGetContentsAsync (ChunkSize size) h =
let go =
Unsafe.interleaveIO $
flip catch (\err -> return (err,[])) $
do v <- V.hGet h size
if V.null v
then hClose h >>
return (Exc.mkIOError Exc.eofErrorType
"StorableVector.Lazy.hGetContentsAsync" (Just h) Nothing, [])
else fmap (mapSnd (v:)) go
in fmap (mapSnd SV) go
hGetContentsSync :: Storable a =>
ChunkSize -> Handle -> IO (Vector a)
hGetContentsSync (ChunkSize size) h =
let go =
do v <- V.hGet h size
if V.null v
then return []
else fmap (v:) go
in fmap SV go
hPut :: Storable a => Handle -> Vector a -> IO ()
hPut h = mapM_ (V.hPut h) . chunks
readFileAsync :: Storable a => ChunkSize -> FilePath -> IO (IOError, Vector a)
readFileAsync size path =
openBinaryFile path ReadMode >>= hGetContentsAsync size
writeFile :: Storable a => FilePath -> Vector a -> IO ()
writeFile path =
bracket (openBinaryFile path WriteMode) hClose . flip hPut
appendFile :: Storable a => FilePath -> Vector a -> IO ()
appendFile path =
bracket (openBinaryFile path AppendMode) hClose . flip hPut
interact :: Storable a => ChunkSize -> (Vector a -> Vector a) -> IO ()
interact (ChunkSize size) f =
let
hGetContents h =
let go =
Unsafe.interleaveIO $
do v <- V.hGet h size
if V.null v
then return []
else fmap (v:) go
in go
in mapM_ (V.hPut IO.stdout) . chunks . f . SV =<< hGetContents IO.stdin
moduleError :: String -> String -> a
moduleError fun msg =
error ("Data.StorableVector.Lazy." List.++ fun List.++ ':':' ':msg)