| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Streaming.Bracketed.Internal
Synopsis
- newtype Bracketed a r = Bracketed {}
 - data Finstack = Finstack !Int [IO ()]
 - clear :: Stream (Of x) IO r -> Bracketed x r
 - bracketed :: IO a -> (a -> IO ()) -> (a -> Stream (Of x) IO r) -> Bracketed x r
 - with :: Bracketed a r -> (forall x. Stream (Of a) IO x -> IO (Of b x)) -> IO (Of b r)
 - with_ :: Bracketed a r -> (Stream (Of a) IO r -> IO b) -> IO b
 - over :: (forall x. Stream (Of a) IO x -> Stream (Of b) IO x) -> Bracketed a r -> Bracketed b r
 - over' :: (forall x. Stream (Of a) IO x -> Stream (Of b) IO (Of s x)) -> Bracketed a r -> Bracketed b (Of s r)
 - over_ :: (Stream (Of a) IO r -> Stream (Of b) IO r') -> Bracketed a r -> Bracketed b r'
 - for :: Bracketed a r -> (a -> Bracketed b x) -> Bracketed b r
 - reset :: Int -> IORef Finstack -> IO ()
 - linesFromFile :: TextEncoding -> NewlineMode -> FilePath -> Bracketed String ()
 - concatRanges :: TextEncoding -> NewlineMode -> [(FilePath, Int, Int)] -> Bracketed String ()
 
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.
Instances
| Bifunctor Bracketed Source # | 
  | 
| Monad (Bracketed a) Source # | |
| Functor (Bracketed a) Source # | |
| Applicative (Bracketed a) Source # | 
  | 
Defined in Streaming.Bracketed.Internal  | |
| MonadIO (Bracketed a) Source # | |
Defined in Streaming.Bracketed.Internal  | |
A stack of finalizers, accompanied by its length.
Finalizers at the head of the list correspond to deeper levels of nesting.
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' :: (forall x. Stream (Of a) IO x -> Stream (Of b) IO (Of s x)) -> Bracketed a r -> Bracketed b (Of s r) Source #
Like over, but for transformations which return some final state or summary value besides the original 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, 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.