Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- data Next item result = result ~ Step item => Next
- data Step item
- class TerminableStream item interface | interface -> item where
- next :: TerminableStream item interface => interface (Step item)
- type Producer action item = Vendor (Const Void) (Next item) action
- type ProducerPlus up action item = Vendor up (Next item) action
- empty :: forall up item action. ProducerPlus up action item
- singleton :: forall up item action. Job up action item -> ProducerPlus up action item
- effect :: forall up action item. action item -> ProducerPlus up action item
- each :: forall up foldable item action. Foldable foldable => foldable item -> ProducerPlus up action item
- append :: forall up item action. ProducerPlus up action item -> ProducerPlus up action item -> ProducerPlus up action item
- null :: forall action item. Monad action => StateT (Producer action item) action Bool
- head :: forall action item. Monad action => StateT (Producer action item) action (Step item)
- pop :: forall action item. Monad action => StateT (Producer action item) action (Step item)
- push :: forall up action item. Monad action => item -> StateT (ProducerPlus up action item) action ()
- unfoldPure :: forall state up item action. (state -> Step (item, state)) -> state -> ProducerPlus up action item
- unfoldEffect :: forall state up item action. (state -> action (Step (item, state))) -> state -> ProducerPlus up action item
- unfoldJob :: forall state up item action. (state -> Job up action (Step (item, state))) -> state -> ProducerPlus up action item
- type Pipe action item1 item2 = Vendor (Next item1) (Next item2) action
- type PipePlus up action item1 item2 = TerminableStream item1 up => Vendor up (Next item2) action
- cons :: forall item action up. Job up action item -> PipePlus up action item item
- map :: forall item1 item2 action up. (item1 -> Job up action item2) -> PipePlus up action item1 item2
- concat :: forall item action up. PipePlus up action [item] item
- takeWhile :: forall item action up. (item -> Job up action Bool) -> PipePlus up action item item
- dropWhile :: forall item action up. (item -> Job up action Bool) -> PipePlus up action item item
- group :: forall up item action. Eq item => PipePlus up action item (Positive, item)
- intersperse :: forall item action up. Job up action item -> PipePlus up action item item
- beforeEach :: forall item action up. Job up action item -> PipePlus up action item item
- concatMapJob :: forall item1 item2 action up. (item1 -> Job up action [item2]) -> PipePlus up action item1 item2
- concatMapProducer :: forall item1 item2 action. (item1 -> Producer action item2) -> Pipe action item1 item2
- type Consumer action item product = Job (Next item) action product
- type ConsumerPlus up action item product = TerminableStream item up => Job up action product
- foldPure :: Fold item product -> ConsumerPlus up action item product
- foldEffect :: EffectfulFold action item product -> ConsumerPlus up action item product
- foldJob :: forall item product action up. EffectfulFold (Job up action) item product -> ConsumerPlus up action item product
- toList :: forall up action item. ConsumerPlus up action item [item]
- run :: forall up action item. ConsumerPlus up action item ()
- newtype Stream action item = Stream (Producer action item)
Next
See Next.Interface
data Next item result Source #
A basic dynamic interface for a possibly-finite stream
Once End
is returned from a Next
request, it is expected that the stream
will thenceforth return End
and perform no side effects in response to any
subsequent Next
requests.
Instances
TerminableStream item (Next item) Source # | |
The result obtained from a Next
request
Item item | An item obtained from the stream |
End | Indicates that the stream has ended and there are no more items |
Instances
Foldable Step Source # | |
Defined in Next.Interface.Type fold :: Monoid m => Step m -> m # foldMap :: Monoid m => (a -> m) -> Step a -> m # foldMap' :: Monoid m => (a -> m) -> Step a -> m # foldr :: (a -> b -> b) -> b -> Step a -> b # foldr' :: (a -> b -> b) -> b -> Step a -> b # foldl :: (b -> a -> b) -> b -> Step a -> b # foldl' :: (b -> a -> b) -> b -> Step a -> b # foldr1 :: (a -> a -> a) -> Step a -> a # foldl1 :: (a -> a -> a) -> Step a -> a # elem :: Eq a => a -> Step a -> Bool # maximum :: Ord a => Step a -> a # | |
Traversable Step Source # | |
Functor Step Source # | |
Show item => Show (Step item) Source # | |
Eq item => Eq (Step item) Source # | |
Ord item => Ord (Step item) Source # | |
Defined in Next.Interface.Type |
class TerminableStream item interface | interface -> item where Source #
An interface for which Next
is one of possibly many supported requests
liftNext :: Next item result -> interface result Source #
Lift a Next
request into a larger interface
Instances
TerminableStream item (Next item) Source # | |
Producer
See Next.Producer
type ProducerPlus up action item = Vendor up (Next item) action Source #
empty :: forall up item action. ProducerPlus up action item Source #
The empty stream
singleton :: forall up item action. Job up action item -> ProducerPlus up action item Source #
Yields one item, then stops
effect :: forall up action item. action item -> ProducerPlus up action item Source #
A single item obtained by performing an effect
each :: forall up foldable item action. Foldable foldable => foldable item -> ProducerPlus up action item Source #
Yields all the items from the given list
append :: forall up item action. ProducerPlus up action item -> ProducerPlus up action item -> ProducerPlus up action item Source #
Yields all the items of the first stream, followed by all the items of the second
null :: forall action item. Monad action => StateT (Producer action item) action Bool Source #
Test whether the state is an empty stream
head :: forall action item. Monad action => StateT (Producer action item) action (Step item) Source #
Peek at the first item in the stream state
pop :: forall action item. Monad action => StateT (Producer action item) action (Step item) Source #
Take the first item from the stream
push :: forall up action item. Monad action => item -> StateT (ProducerPlus up action item) action () Source #
Add an item to the front of the stream state
unfoldPure :: forall state up item action. (state -> Step (item, state)) -> state -> ProducerPlus up action item Source #
unfoldEffect :: forall state up item action. (state -> action (Step (item, state))) -> state -> ProducerPlus up action item Source #
unfoldJob :: forall state up item action. (state -> Job up action (Step (item, state))) -> state -> ProducerPlus up action item Source #
Pipe
See Next.Pipe
type PipePlus up action item1 item2 = TerminableStream item1 up => Vendor up (Next item2) action Source #
Like Pipe
, but with a more general upstream interface
which can be anything in the TerminableStream
class
This type is like Pipe
except that it has an extra type parameter
representing the upstream interface, hence its name is "pipe plus".
:: forall item action up. Job up action item | This job produces an item to add to the front of the list |
-> PipePlus up action item item |
Add one item to the beginning of a stream
:: forall item1 item2 action up. (item1 -> Job up action item2) | For each input item, this job produces an output item |
-> PipePlus up action item1 item2 |
Apply a function to each item in the stream
:: forall item action up. (item -> Job up action Bool) | True if this is the sort of thing we'd like to keep |
-> PipePlus up action item item |
Yields the longest prefix matching the predicate and discards the rest
:: forall item action up. (item -> Job up action Bool) | True if this is the sort of thing we'd like to get rid of |
-> PipePlus up action item item |
Discards the longest prefix matching the predicate and yields the rest
group :: forall up item action. Eq item => PipePlus up action item (Positive, item) Source #
Removes consecutive duplicate items, and yields each item along with the size of the repetition
For example, "Hrmm..."
groups into
[(1, 'H'), (1, 'r'), (2, 'm'), (3, '.')]
:: forall item action up. Job up action item | This job generates items that will be inserted in between the items of the original list |
-> PipePlus up action item item |
Add an item between each pair of items of a stream
The length of the stream is modified as \case{ 0 -> 0; n -> (2 * n) - 1 }
.
:: forall item action up. Job up action item | This job generates items that will be inserted before each of the items of the original list |
-> PipePlus up action item item |
Add an item before each item in a stream
The length of the stream is doubled.
:: forall item1 item2 action up. (item1 -> Job up action [item2]) | For each input item, this job produces any number of output items |
-> PipePlus up action item1 item2 |
Applies the function to each result obtained from upstream, and yields each result from the list to the downstream
:: forall item1 item2 action. (item1 -> Producer action item2) | For each item from the input list, this vendor generates any number of actions to yield in the resulting list |
-> Pipe action item1 item2 |
Like concatMapJob
, but the function gives a Producer
instead of a Job
Consumer
See Next.Consumer
type ConsumerPlus up action item product = TerminableStream item up => Job up action product Source #
Like Consumer
, but with a more general upstream interface
which can be anything in the TerminableStream
class
This type is like Consumer
except that it has an extra type parameter
representing the upstream interface, hence its name is "consumer plus".
foldPure :: Fold item product -> ConsumerPlus up action item product Source #
Run the stream completely, collecting results using a pure fold
See Fold.Pure
foldEffect :: EffectfulFold action item product -> ConsumerPlus up action item product Source #
Run the stream completely, collecting results using an effectful fold
See Fold.Effectful
foldJob :: forall item product action up. EffectfulFold (Job up action) item product -> ConsumerPlus up action item product Source #
Run the stream completely, collecting results using a
fold that operates in the Job
context
See Fold.Effectful
toList :: forall up action item. ConsumerPlus up action item [item] Source #
Consumes all items and returns them as a list
run :: forall up action item. ConsumerPlus up action item () Source #
Like toList
, but discards the results
Stream
See Next.Stream
newtype Stream action item Source #
Instances
Applicative (Stream action) Source # | |
Defined in Next.Stream.Type pure :: a -> Stream action a # (<*>) :: Stream action (a -> b) -> Stream action a -> Stream action b # liftA2 :: (a -> b -> c) -> Stream action a -> Stream action b -> Stream action c # (*>) :: Stream action a -> Stream action b -> Stream action b # (<*) :: Stream action a -> Stream action b -> Stream action a # | |
Functor (Stream action) Source # | |
Monad (Stream action) Source # | |
Monoid (Stream action item) Source # | |
Semigroup (Stream action item) Source # | |