streaming-bracketed-0.1.0.0: A resource management decorator for "streaming".

Safe HaskellSafe
LanguageHaskell2010

Streaming.Bracketed

Contents

Description

A resource management decorator for Streams.

Resource-allocating Streams are lifted to values of type Bracketed that can be combined as such, using an API that is more restricted than that of the original Streams and ensures prompt deallocation of resources.

Values of type Bracketed can later be run by supplying a Stream-consumer continuation to the with function.

>>> :{
    do -- boring setup stuff for a two-line text file 
       path <- (</> "streaming-bracketed-doctest.txt") <$> getTemporaryDirectory
       exists <- doesPathExist path
       when exists (removeFile path)
       withFile path WriteMode (for_ ["aaa","bbb"] . hPutStrLn)
       -- end of setup
       let lineStream = R.linesFromFile utf8 nativeNewlineMode path
       lines :> () <- R.with (R.over_ (S.take 1) lineStream *> R.over (S.map (map succ)) lineStream) 
                             S.toList
       return lines
    :}
["aaa","bbb","ccc"]
Synopsis

Bracketed

data Bracketed a r Source #

Instances
Bifunctor Bracketed Source #

first maps over the yielded elements.

Instance details

Defined in Streaming.Bracketed.Internal

Methods

bimap :: (a -> b) -> (c -> d) -> Bracketed a c -> Bracketed b d #

first :: (a -> b) -> Bracketed a c -> Bracketed b c #

second :: (b -> c) -> Bracketed a b -> Bracketed a c #

Monad (Bracketed a) Source # 
Instance details

Defined in Streaming.Bracketed.Internal

Methods

(>>=) :: Bracketed a a0 -> (a0 -> Bracketed a b) -> Bracketed a b #

(>>) :: Bracketed a a0 -> Bracketed a b -> Bracketed a b #

return :: a0 -> Bracketed a a0 #

fail :: String -> Bracketed a a0 #

Functor (Bracketed a) Source # 
Instance details

Defined in Streaming.Bracketed.Internal

Methods

fmap :: (a0 -> b) -> Bracketed a a0 -> Bracketed a b #

(<$) :: a0 -> Bracketed a b -> Bracketed a a0 #

Applicative (Bracketed a) Source # 
Instance details

Defined in Streaming.Bracketed.Internal

Methods

pure :: a0 -> Bracketed a a0 #

(<*>) :: Bracketed a (a0 -> b) -> Bracketed a a0 -> Bracketed a b #

liftA2 :: (a0 -> b -> c) -> Bracketed a a0 -> Bracketed a b -> Bracketed a c #

(*>) :: Bracketed a a0 -> Bracketed a b -> Bracketed a b #

(<*) :: Bracketed a a0 -> Bracketed a b -> Bracketed a a0 #

MonadIO (Bracketed a) Source # 
Instance details

Defined in Streaming.Bracketed.Internal

Methods

liftIO :: IO a0 -> Bracketed a a0 #

Lifting streams

clear :: Stream (Of x) IO r -> Bracketed x r Source #

Lift a Stream that doesn't perform allocation to a Bracketed.

bracketed :: IO a -> (a -> IO ()) -> (a -> Stream (Of x) IO r) -> Bracketed x r Source #

Lift a Stream that requires resource allocation to a Bracketed.

Consuming bracketed streams with continuations

with :: Bracketed a r -> (forall x. Stream (Of a) IO x -> IO (Of b x)) -> IO (Of b r) Source #

Consume a Bracketed stream, exhausting it.

with_ :: Bracketed a r -> (Stream (Of a) IO r -> IO b) -> IO b Source #

Consume a Bracketed stream, possibly wihout exhausting it.

Finalizers lying in unconsumed parts of the stream will not be executed until the callback returns, so better not tarry too long if you want prompt finalization.

Transforming bracketed streams

over :: (forall x. Stream (Of a) IO x -> Stream (Of b) IO x) -> Bracketed a r -> Bracketed b r Source #

Apply to the underlying stream a transformation that preserves the return value.

over_ :: (Stream (Of a) IO r -> Stream (Of b) IO r') -> Bracketed a r -> Bracketed b r' Source #

Apply to the underlying stream a transformation that might not preserve the return value.

for :: Bracketed a r -> (a -> Bracketed b x) -> Bracketed b r Source #

Replaces each element of a stream with an associated stream.

Can be useful for traversing hierachical structures.

Reading text files

linesFromFile :: TextEncoding -> NewlineMode -> FilePath -> Bracketed String () Source #

A bracketed stream of all the lines in a text file.

This is adequate for simple use cases. For more advanced ones where efficiency and memory usage are important, it's better to use a packed text representation like the one provided by the text package.

concatRanges :: TextEncoding -> NewlineMode -> [(FilePath, Int, Int)] -> Bracketed String () Source #

Given a list of text files and line ranges, create a stream of lines belonging to the concatenated ranges.