grapesy
Safe HaskellNone
LanguageHaskell2010

Network.GRPC.Common.StreamElem

Description

Positioned elements

Intended for qualified import.

import Network.GRPC.Common.StreamElem qualified as StreamElem

Network.GRPC.Common (intended for unqualified import) exports StreamElem(..), but none of the operations on StreamElem.

Synopsis

Documentation

data StreamElem b a Source #

An element positioned in a stream

Constructors

StreamElem !a

Element in the stream

The final element in a stream may or may not be marked as final; if it is not, we will only discover after receiving the final element that it was in fact final. Moreover, we do not know ahead of time whether or not the final element will be marked.

When we receive an element and it is not marked final, this might therefore mean one of two things, without being able to tell which:

  • We are dealing with a stream in which the final element is not marked.

In this case, the element may or may not be the final element; if it is, the next value will be NoMoreElems (but waiting for the next value might mean a blocking call).

  • We are dealing with a stream in which the final element is marked.

In this case, this element is not final (and the final element, when we receive it, will be tagged as Final).

FinalElem !a !b

We received the final element

The final element is annotated with some additional information.

NoMoreElems !b

There are no more elements

This is used in two situations:

  • The stream didn't contain any elements at all.
  • The final element was not marked as final. See StreamElem for detailed additional discussion.

Instances

Instances details
Bifoldable StreamElem Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

bifold :: Monoid m => StreamElem m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> StreamElem a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> StreamElem a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> StreamElem a b -> c #

Bifunctor StreamElem Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

bimap :: (a -> b) -> (c -> d) -> StreamElem a c -> StreamElem b d #

first :: (a -> b) -> StreamElem a c -> StreamElem b c #

second :: (b -> c) -> StreamElem a b -> StreamElem a c #

Bitraversable StreamElem Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> StreamElem a b -> f (StreamElem c d) #

Functor (StreamElem b) Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

fmap :: (a -> b0) -> StreamElem b a -> StreamElem b b0 #

(<$) :: a -> StreamElem b b0 -> StreamElem b a #

Foldable (StreamElem b) Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

fold :: Monoid m => StreamElem b m -> m #

foldMap :: Monoid m => (a -> m) -> StreamElem b a -> m #

foldMap' :: Monoid m => (a -> m) -> StreamElem b a -> m #

foldr :: (a -> b0 -> b0) -> b0 -> StreamElem b a -> b0 #

foldr' :: (a -> b0 -> b0) -> b0 -> StreamElem b a -> b0 #

foldl :: (b0 -> a -> b0) -> b0 -> StreamElem b a -> b0 #

foldl' :: (b0 -> a -> b0) -> b0 -> StreamElem b a -> b0 #

foldr1 :: (a -> a -> a) -> StreamElem b a -> a #

foldl1 :: (a -> a -> a) -> StreamElem b a -> a #

toList :: StreamElem b a -> [a] #

null :: StreamElem b a -> Bool #

length :: StreamElem b a -> Int #

elem :: Eq a => a -> StreamElem b a -> Bool #

maximum :: Ord a => StreamElem b a -> a #

minimum :: Ord a => StreamElem b a -> a #

sum :: Num a => StreamElem b a -> a #

product :: Num a => StreamElem b a -> a #

Traversable (StreamElem b) Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

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

sequenceA :: Applicative f => StreamElem b (f a) -> f (StreamElem b a) #

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

sequence :: Monad m => StreamElem b (m a) -> m (StreamElem b a) #

(Show a, Show b) => Show (StreamElem b a) Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

showsPrec :: Int -> StreamElem b a -> ShowS #

show :: StreamElem b a -> String #

showList :: [StreamElem b a] -> ShowS #

(Eq a, Eq b) => Eq (StreamElem b a) Source # 
Instance details

Defined in Network.GRPC.Common.StreamElem

Methods

(==) :: StreamElem b a -> StreamElem b a -> Bool #

(/=) :: StreamElem b a -> StreamElem b a -> Bool #

Conversion

value :: StreamElem b a -> Maybe a Source #

Value of the element, if one is present

Returns Nothing in case of NoMoreElems

Using this function loses the information whether the item was the final item; this information can be recovered using whenDefinitelyFinal.

Iteration

Iteration

mapM_ :: forall m a b. Monad m => (StreamElem b a -> m ()) -> [a] -> b -> m () Source #

Invoke the callback for each element

The final element is marked using FinalElem; the callback is only invoked on NoMoreElems if the list is empty.

   mapM_ f ([1,2,3], b)
== do f (StreamElem 1)
      f (StreamElem 2)
      f (FinalElem 3 b)

   mapM_ f ([], b)
== do f (NoMoreElems b)

forM_ :: Monad m => [a] -> b -> (StreamElem b a -> m ()) -> m () Source #

Like mapM_, but with the arguments in opposite order

whileNext_ :: forall m a b. Monad m => m (StreamElem b a) -> (a -> m ()) -> m b Source #

Invoke a function on each NextElem, until FinalElem or NoMoreElems

collect :: Monad m => m (StreamElem b a) -> m ([a], b) Source #

Invoke the callback until FinalElem or NoMoreElems, collecting results

whenDefinitelyFinal :: Applicative m => StreamElem b a -> (b -> m ()) -> m () Source #

Do we have evidence that this element is the final one?

The callback is not called on StreamElem; this does not mean that the element was not final; see StreamElem for detailed discussion.