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

Safe HaskellSafe
LanguageHaskell2010

Streaming.Bracketed.Internal

Synopsis

Documentation

>>> import           Data.Foldable
>>> import           Control.Monad
>>> import           System.IO
>>> import           System.FilePath
>>> import           System.Directory
>>> import           Streaming
>>> import qualified Streaming.Prelude             as S
>>> import qualified Streaming.Bracketed           as R

newtype Bracketed a r Source #

A resource management decorator for the Stream type.

a is the type of yielded elements, r the type of the final result.

It is not parameterized by a base monad because the underlying Streams are always over IO.

Constructors

Bracketed 

Fields

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 #

*> performs sequential composition.

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 #

data Finstack Source #

A stack of finalizers, accompanied by its length.

Finalizers at the head of the list correspond to deeper levels of nesting.

Constructors

Finstack !Int [IO ()] 

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

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

>>> R.with (R.clear (S.yield True)) S.toList
[True] :> ()

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

Lift a Stream that performs resource allocation to a Bracketed.

The first argument allocates the resource, the second is a function that deallocates it.

>>> R.with (R.bracketed (putStrLn "alloc") (\() -> putStrLn "dealloc") (\() -> S.yield True)) S.toList
alloc
dealloc
[True] :> ()

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.

>>> R.with (pure True) S.toList
[] :> True

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.

>>> R.with_ (R.clear (S.each "abcd" *> pure True)) (S.toList . S.take 2)
"ab" :> ()

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, like map.

>>> R.with (S.map succ `R.over` R.clear (S.each "abcd")) S.toList
"bcde" :> ()

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, like take.

>>> R.with (S.take 2 `R.over_` R.clear (S.each "abdc")) S.toList
"ab" :> ()

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.

reset :: Int -> IORef Finstack -> IO () Source #

Executes all finalizers that lie above a certain level.

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.