potoki-core-2.3.3: Low-level components of "potoki"

Safe HaskellNone
LanguageHaskell2010

Potoki.Core.Transform

Contents

Synopsis

Documentation

newtype Transform input output Source #

Constructors

Transform (Fetch input -> Acquire (Fetch output)) 
Instances
ArrowChoice Transform # 
Instance details

Defined in Potoki.Core.Transform.Instances

Methods

left :: Transform b c -> Transform (Either b d) (Either c d) #

right :: Transform b c -> Transform (Either d b) (Either d c) #

(+++) :: Transform b c -> Transform b' c' -> Transform (Either b b') (Either c c') #

(|||) :: Transform b d -> Transform c d -> Transform (Either b c) d #

Arrow Transform # 
Instance details

Defined in Potoki.Core.Transform.Instances

Methods

arr :: (b -> c) -> Transform b c #

first :: Transform b c -> Transform (b, d) (c, d) #

second :: Transform b c -> Transform (d, b) (d, c) #

(***) :: Transform b c -> Transform b' c' -> Transform (b, b') (c, c') #

(&&&) :: Transform b c -> Transform b c' -> Transform b (c, c') #

Choice Transform # 
Instance details

Defined in Potoki.Core.Transform.Instances

Methods

left' :: Transform a b -> Transform (Either a c) (Either b c) #

right' :: Transform a b -> Transform (Either c a) (Either c b) #

Strong Transform # 
Instance details

Defined in Potoki.Core.Transform.Instances

Methods

first' :: Transform a b -> Transform (a, c) (b, c) #

second' :: Transform a b -> Transform (c, a) (c, b) #

Profunctor Transform # 
Instance details

Defined in Potoki.Core.Transform.Instances

Methods

dimap :: (a -> b) -> (c -> d) -> Transform b c -> Transform a d #

lmap :: (a -> b) -> Transform b c -> Transform a c #

rmap :: (b -> c) -> Transform a b -> Transform a c #

(#.) :: Coercible c b => q b c -> Transform a b -> Transform a c #

(.#) :: Coercible b a => Transform b c -> q a b -> Transform a c #

Category Transform # 
Instance details

Defined in Potoki.Core.Transform.Instances

Methods

id :: Transform a a #

(.) :: Transform b c -> Transform a b -> Transform a c #

consume :: Consume input output -> Transform input output Source #

produce :: (input -> Produce output) -> Transform input output Source #

mapFetch :: (Fetch a -> Fetch b) -> Transform a b Source #

Basics

take :: Int -> Transform input input Source #

takeWhile :: (input -> Bool) -> Transform input input Source #

drop :: Int -> Transform input input Source #

mapFilter :: (input -> Maybe output) -> Transform input output Source #

filter :: (input -> Bool) -> Transform input input Source #

just :: Transform (Maybe input) input Source #

vector :: Vector vector a => Transform (vector a) a Source #

batch :: Vector vector a => Int -> Transform a (vector a) Source #

Chunk the stream to vector batches of the given size.

It's useful in combination with concurrently in cases where the lifted transform's iteration is too light. Actually, there is a composed variation of concurrently, which utilizes it: concurrentlyWithBatching.

distinctBy :: (Eq comparable, Hashable comparable) => (element -> comparable) -> Transform element element Source #

distinct :: (Eq element, Hashable element) => Transform element element Source #

executeIO :: Transform (IO a) a Source #

Execute the IO action.

mapInIO :: (a -> IO b) -> Transform a b Source #

ByteString

extractLines :: Transform ByteString ByteString Source #

Convert freeform bytestring chunks into chunks, which are strictly separated by newline no matter how long they may be.

State

runState :: (input -> State state output) -> state -> Transform input (output, state) Source #

Notice that you can control the emission of output of each step by producing a list of outputs and then composing the transform with the "list" transform.

execState :: (input -> State state output) -> state -> Transform input state Source #

evalState :: (input -> State state output) -> state -> Transform input output Source #

Parsing

parseBytes :: Parser parsed -> Transform ByteString (Either Text parsed) Source #

Lift an Attoparsec ByteString parser.

parseText :: Parser parsed -> Transform Text (Either Text parsed) Source #

Lift an Attoparsec Text parser.

parseLineBytesConcurrently :: NFData a => Int -> Parser a -> Transform ByteString (Either Text a) Source #

Lift an Attoparsec ByteString parser to a transform, which parses the lines concurrently.

parseNonEmptyLineBytesConcurrently :: NFData a => Int -> Parser a -> Transform ByteString (Either Text a) Source #

Lift an Attoparsec ByteString parser to a transform, which parses the lines concurrently.

Concurrency

bufferize :: NFData element => Int -> Transform element element Source #

bufferizeFlushing :: Int -> Transform input [input] Source #

concurrently :: NFData output => Int -> Transform input output -> Transform input output Source #

Execute the transform on the specified amount of threads. The order of the outputs produced is indiscriminate.

unsafeConcurrently :: NFData output => Int -> Transform input output -> Transform input output Source #

async :: NFData input => Int -> Transform input input Source #

A transform, which fetches the inputs asynchronously on the specified number of threads.

File IO

Debugging

mapInIOWithCounter :: (Int -> a -> IO b) -> Transform a b Source #

handleCount :: (Int -> IO ()) -> Transform a a Source #

handleCountOnInterval :: NominalDiffTime -> (Int -> IO ()) -> Transform a a Source #

Provides for progress monitoring by means of periodic measurement.

traceWithCounter :: (Int -> String) -> Transform a a Source #

Useful for debugging