Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Transform input output :: * -> * -> *
- consume :: Consume input output -> Transform input output
- produce :: (input -> Produce output) -> Transform input output
- 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 :: Transform (Vector a) a
- distinctBy :: (Eq comparable, Hashable comparable) => (element -> comparable) -> Transform element element
- distinct :: (Eq element, Hashable element) => Transform element element
- builderChunks :: Transform Builder ByteString
- executeIO :: Transform (IO a) a
- mapInIO :: (a -> IO b) -> Transform a b
- runState :: (a -> State s b) -> s -> Transform a (s, b)
- execState :: (a -> State s b) -> s -> Transform a s
- evalState :: (a -> State s b) -> s -> Transform a b
- parseBytes :: Parser parsed -> Transform ByteString (Either Text parsed)
- parseText :: Parser parsed -> Transform Text (Either Text parsed)
- bufferize :: Int -> Transform element element
- concurrently :: Int -> Transform input output -> Transform input output
- async :: Int -> Transform input input
- deleteFile :: Transform FilePath (Either IOException ())
- appendBytesToFile :: Transform (FilePath, ByteString) (Either IOException ())
- writeTextToFile :: Transform (FilePath, Text) (Either IOException ())
- traceWithCounter :: (Int -> String) -> Transform a a
Documentation
Potoki integration
Basics
distinctBy :: (Eq comparable, Hashable comparable) => (element -> comparable) -> Transform element element Source #
runState :: (a -> State s b) -> s -> Transform a (s, b) 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.
Concurrency
concurrently :: 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.
async :: Int -> Transform input input Source #
A transform, which fetches the inputs asynchronously on the specified number of threads.
File IO
deleteFile :: Transform FilePath (Either IOException ()) Source #
appendBytesToFile :: Transform (FilePath, ByteString) (Either IOException ()) Source #
writeTextToFile :: Transform (FilePath, Text) (Either IOException ()) Source #