module Next.Interface.Type
  (
    {- * Type aliases -} Next (..), Step (..),
  )
  where

import Essentials

{-| A basic dynamic interface for a possibly-finite stream

Once 'End' is returned from a v'Next' request, it is expected that the stream
will thenceforth return 'End' and perform no side effects in response to any
subsequent 'Next' requests. -}
data Next item result =
    (result ~ Step item) => Next
        -- ^ Request the next item from the stream

{-| The result obtained from a v'Next' request -}
data Step item =
    Item item -- ^ An item obtained from the stream
  | End -- ^ Indicates that the stream has ended and there are no more items
    deriving stock (forall a b. a -> Step b -> Step a
forall a b. (a -> b) -> Step a -> Step b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Step b -> Step a
$c<$ :: forall a b. a -> Step b -> Step a
fmap :: forall a b. (a -> b) -> Step a -> Step b
$cfmap :: forall a b. (a -> b) -> Step a -> Step b
Functor, forall a. Eq a => a -> Step a -> Bool
forall a. Num a => Step a -> a
forall a. Ord a => Step a -> a
forall m. Monoid m => Step m -> m
forall a. Step a -> Bool
forall a. Step a -> Int
forall a. Step a -> [a]
forall a. (a -> a -> a) -> Step a -> a
forall m a. Monoid m => (a -> m) -> Step a -> m
forall b a. (b -> a -> b) -> b -> Step a -> b
forall a b. (a -> b -> b) -> b -> Step a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => Step a -> a
$cproduct :: forall a. Num a => Step a -> a
sum :: forall a. Num a => Step a -> a
$csum :: forall a. Num a => Step a -> a
minimum :: forall a. Ord a => Step a -> a
$cminimum :: forall a. Ord a => Step a -> a
maximum :: forall a. Ord a => Step a -> a
$cmaximum :: forall a. Ord a => Step a -> a
elem :: forall a. Eq a => a -> Step a -> Bool
$celem :: forall a. Eq a => a -> Step a -> Bool
length :: forall a. Step a -> Int
$clength :: forall a. Step a -> Int
null :: forall a. Step a -> Bool
$cnull :: forall a. Step a -> Bool
toList :: forall a. Step a -> [a]
$ctoList :: forall a. Step a -> [a]
foldl1 :: forall a. (a -> a -> a) -> Step a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Step a -> a
foldr1 :: forall a. (a -> a -> a) -> Step a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Step a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> Step a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Step a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Step a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Step a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Step a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Step a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Step a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Step a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> Step a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Step a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Step a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Step a -> m
fold :: forall m. Monoid m => Step m -> m
$cfold :: forall m. Monoid m => Step m -> m
Foldable, Functor Step
Foldable Step
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Step (m a) -> m (Step a)
forall (f :: * -> *) a. Applicative f => Step (f a) -> f (Step a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Step a -> m (Step b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Step a -> f (Step b)
sequence :: forall (m :: * -> *) a. Monad m => Step (m a) -> m (Step a)
$csequence :: forall (m :: * -> *) a. Monad m => Step (m a) -> m (Step a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Step a -> m (Step b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Step a -> m (Step b)
sequenceA :: forall (f :: * -> *) a. Applicative f => Step (f a) -> f (Step a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Step (f a) -> f (Step a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Step a -> f (Step b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Step a -> f (Step b)
Traversable, Step item -> Step item -> Bool
forall item. Eq item => Step item -> Step item -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Step item -> Step item -> Bool
$c/= :: forall item. Eq item => Step item -> Step item -> Bool
== :: Step item -> Step item -> Bool
$c== :: forall item. Eq item => Step item -> Step item -> Bool
Eq, Step item -> Step item -> Bool
Step item -> Step item -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {item}. Ord item => Eq (Step item)
forall item. Ord item => Step item -> Step item -> Bool
forall item. Ord item => Step item -> Step item -> Ordering
forall item. Ord item => Step item -> Step item -> Step item
min :: Step item -> Step item -> Step item
$cmin :: forall item. Ord item => Step item -> Step item -> Step item
max :: Step item -> Step item -> Step item
$cmax :: forall item. Ord item => Step item -> Step item -> Step item
>= :: Step item -> Step item -> Bool
$c>= :: forall item. Ord item => Step item -> Step item -> Bool
> :: Step item -> Step item -> Bool
$c> :: forall item. Ord item => Step item -> Step item -> Bool
<= :: Step item -> Step item -> Bool
$c<= :: forall item. Ord item => Step item -> Step item -> Bool
< :: Step item -> Step item -> Bool
$c< :: forall item. Ord item => Step item -> Step item -> Bool
compare :: Step item -> Step item -> Ordering
$ccompare :: forall item. Ord item => Step item -> Step item -> Ordering
Ord, Int -> Step item -> ShowS
forall item. Show item => Int -> Step item -> ShowS
forall item. Show item => [Step item] -> ShowS
forall item. Show item => Step item -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Step item] -> ShowS
$cshowList :: forall item. Show item => [Step item] -> ShowS
show :: Step item -> String
$cshow :: forall item. Show item => Step item -> String
showsPrec :: Int -> Step item -> ShowS
$cshowsPrec :: forall item. Show item => Int -> Step item -> ShowS
Show)