| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Potoki.Core.Transform
Synopsis
- newtype Transform input output = Transform (Fetch input -> Acquire (Fetch output))
- consume :: Consume input output -> Transform input output
- produce :: (input -> Produce output) -> Transform input output
- mapFetch :: (Fetch a -> Fetch b) -> Transform a b
- ioTransform :: IO (Transform a b) -> Transform a b
- take :: Int -> Transform input input
- takeWhile :: (input -> Bool) -> Transform input input
- drop :: Int -> Transform input input
- mapFilter :: (input -> Maybe output) -> Transform input output
- filter :: (input -> Bool) -> Transform input input
- just :: Transform (Maybe input) input
- list :: Transform [a] a
- vector :: Vector vector a => Transform (vector a) a
- batch :: Vector vector a => Int -> Transform a (vector a)
- distinctBy :: (Eq comparable, Hashable comparable) => (element -> comparable) -> Transform element element
- distinct :: (Eq element, Hashable element) => Transform element element
- executeIO :: Transform (IO a) a
- mapInIO :: (a -> IO b) -> Transform a b
- reportProgress :: (Text -> IO ()) -> Transform a a
- handleProgressAndCountOnInterval :: NominalDiffTime -> (Int -> Int -> IO ()) -> Transform a a
- uniquify :: Eq a => Transform a a
- builderChunks :: Transform Builder ByteString
- extractLines :: Transform ByteString ByteString
- extractLinesWithoutTrail :: Transform ByteString ByteString
- extractLinesConcurrently :: Int -> Transform ByteString ByteString
- runState :: (input -> State state output) -> state -> Transform input (output, state)
- execState :: (input -> State state output) -> state -> Transform input state
- evalState :: (input -> State state output) -> state -> Transform input output
- scan :: Scanner a -> Transform ByteString (Either Text a)
- parseBytes :: Parser parsed -> Transform ByteString (Either Text parsed)
- parseText :: Parser parsed -> Transform Text (Either Text parsed)
- parseLineBytesConcurrently :: NFData a => Int -> Parser a -> Transform ByteString (Either Text a)
- parseNonEmptyLineBytesConcurrently :: NFData a => Int -> Parser a -> Transform ByteString (Either Text a)
- bufferize :: NFData element => Int -> Transform element element
- bufferizeFlushing :: Int -> Transform input [input]
- concurrently :: NFData output => Int -> Transform input output -> Transform input output
- concurrentlyInOrder :: NFData b => Int -> Transform a b -> Transform a b
- unsafeConcurrently :: NFData output => Int -> Transform input output -> Transform input output
- async :: NFData input => Int -> Transform input input
- concurrentlyWithBatching :: (NFData a, NFData b) => Int -> Int -> Transform a b -> Transform a b
- concurrentlyInOrderWithBatching :: NFData b => Int -> Int -> Transform a b -> Transform a b
- deleteFile :: Transform FilePath (Either IOException ())
- appendBytesToFile :: Transform (FilePath, ByteString) (Either IOException ())
- writeTextToFile :: Transform (FilePath, Text) (Either IOException ())
- count :: Transform a Int
- mapInIOWithCounter :: (Int -> a -> IO b) -> Transform a b
- handleCount :: (Int -> IO ()) -> Transform a a
- handleCountOnInterval :: NominalDiffTime -> (Int -> IO ()) -> Transform a a
- traceWithCounter :: (Int -> String) -> Transform a a
Documentation
newtype Transform input output Source #
Instances
| ArrowChoice Transform Source # | |
| Defined in Potoki.Core.Transform.Instances | |
| Arrow Transform Source # | |
| Defined in Potoki.Core.Transform.Instances | |
| Choice Transform Source # | |
| Strong Transform Source # | |
| Profunctor Transform Source # | |
| 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 Source # | |
Basics
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 #
handleProgressAndCountOnInterval :: NominalDiffTime -> (Int -> Int -> IO ()) -> Transform a a 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.
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
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.
concurrentlyWithBatching :: (NFData a, NFData b) => Int -> Int -> Transform a b -> Transform a b Source #
concurrentlyInOrderWithBatching :: NFData b => Int -> Int -> Transform a b -> Transform a b Source #
File IO
deleteFile :: Transform FilePath (Either IOException ()) Source #
appendBytesToFile :: Transform (FilePath, ByteString) (Either IOException ()) Source #
writeTextToFile :: Transform (FilePath, Text) (Either IOException ()) Source #
Debugging
handleCountOnInterval :: NominalDiffTime -> (Int -> IO ()) -> Transform a a Source #
Provides for progress monitoring by means of periodic measurement.