supply-next-0.0.1.2: Supply-chain interface for basic streaming
Safe HaskellSafe-Inferred
LanguageGHC2021

Next

Synopsis

Next

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.

Constructors

result ~ Step item => Next

Request the next item from the stream

Instances

Instances details
TerminableStream item (Next item) Source # 
Instance details

Defined in Next.Interface.Class

Methods

liftNext :: Next item result -> Next item result Source #

data Step item Source #

The result obtained from a Next request

Constructors

Item item

An item obtained from the stream

End

Indicates that the stream has ended and there are no more items

Instances

Instances details
Foldable Step Source # 
Instance details

Defined in Next.Interface.Type

Methods

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 #

toList :: Step a -> [a] #

null :: Step a -> Bool #

length :: Step a -> Int #

elem :: Eq a => a -> Step a -> Bool #

maximum :: Ord a => Step a -> a #

minimum :: Ord a => Step a -> a #

sum :: Num a => Step a -> a #

product :: Num a => Step a -> a #

Traversable Step Source # 
Instance details

Defined in Next.Interface.Type

Methods

traverse :: Applicative f => (a -> f b) -> Step a -> f (Step b) #

sequenceA :: Applicative f => Step (f a) -> f (Step a) #

mapM :: Monad m => (a -> m b) -> Step a -> m (Step b) #

sequence :: Monad m => Step (m a) -> m (Step a) #

Functor Step Source # 
Instance details

Defined in Next.Interface.Type

Methods

fmap :: (a -> b) -> Step a -> Step b #

(<$) :: a -> Step b -> Step a #

Show item => Show (Step item) Source # 
Instance details

Defined in Next.Interface.Type

Methods

showsPrec :: Int -> Step item -> ShowS #

show :: Step item -> String #

showList :: [Step item] -> ShowS #

Eq item => Eq (Step item) Source # 
Instance details

Defined in Next.Interface.Type

Methods

(==) :: Step item -> Step item -> Bool #

(/=) :: Step item -> Step item -> Bool #

Ord item => Ord (Step item) Source # 
Instance details

Defined in Next.Interface.Type

Methods

compare :: Step item -> Step item -> Ordering #

(<) :: Step item -> Step item -> Bool #

(<=) :: Step item -> Step item -> Bool #

(>) :: Step item -> Step item -> Bool #

(>=) :: Step item -> Step item -> Bool #

max :: Step item -> Step item -> Step item #

min :: Step item -> Step item -> Step item #

class TerminableStream item interface | interface -> item where Source #

An interface for which Next is one of possibly many supported requests

Methods

liftNext :: Next item result -> interface result Source #

Lift a Next request into a larger interface

Instances

Instances details
TerminableStream item (Next item) Source # 
Instance details

Defined in Next.Interface.Class

Methods

liftNext :: Next item result -> Next item result Source #

next :: TerminableStream item interface => interface (Step item) Source #

Like Next, but polymorphic

Producer

type Producer action item = Vendor (Const Void) (Next item) action Source #

A Vendor whose upstream interface is nothing and whose downstream interface is Next

type ProducerPlus up action item = Vendor up (Next item) action Source #

A Vendor whose downstream interface is Next

This type is like Producer except that it has an extra type parameter representing the upstream interface, hence its name is "producer plus".

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

type Pipe action item1 item2 = Vendor (Next item1) (Next item2) action Source #

A Vendor whose upstream and downstream interfaces are both Next

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".

cons Source #

Arguments

:: 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

map Source #

Arguments

:: 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

concat :: forall item action up. PipePlus up action [item] item Source #

Flattens a stream of lists

takeWhile Source #

Arguments

:: 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

dropWhile Source #

Arguments

:: 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, '.')]

intersperse Source #

Arguments

:: 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 }.

beforeEach Source #

Arguments

:: 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.

concatMapJob Source #

Arguments

:: 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

concatMapProducer Source #

Arguments

:: 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

type Consumer action item product = Job (Next item) action product Source #

A Job whose upstream interface is Next

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

newtype Stream action item Source #

Constructors

Stream (Producer action item) 

Instances

Instances details
Applicative (Stream action) Source # 
Instance details

Defined in Next.Stream.Type

Methods

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 # 
Instance details

Defined in Next.Stream.Type

Methods

fmap :: (a -> b) -> Stream action a -> Stream action b #

(<$) :: a -> Stream action b -> Stream action a #

Monad (Stream action) Source # 
Instance details

Defined in Next.Stream.Type

Methods

(>>=) :: Stream action a -> (a -> Stream action b) -> Stream action b #

(>>) :: Stream action a -> Stream action b -> Stream action b #

return :: a -> Stream action a #

Monoid (Stream action item) Source # 
Instance details

Defined in Next.Stream.Type

Methods

mempty :: Stream action item #

mappend :: Stream action item -> Stream action item -> Stream action item #

mconcat :: [Stream action item] -> Stream action item #

Semigroup (Stream action item) Source # 
Instance details

Defined in Next.Stream.Type

Methods

(<>) :: Stream action item -> Stream action item -> Stream action item #

sconcat :: NonEmpty (Stream action item) -> Stream action item #

stimes :: Integral b => b -> Stream action item -> Stream action item #