| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Bluefin.Stream
Synopsis
- type Stream a = Coroutine a ()
- forEach :: forall a b (es :: Effects) r. (forall (e1 :: Effects). Coroutine a b e1 -> Eff (e1 :& es) r) -> (a -> Eff es b) -> Eff es r
- yieldToList :: forall a (es :: Effects) r. (forall (e1 :: Effects). Stream a e1 -> Eff (e1 :& es) r) -> Eff es ([a], r)
- yieldToReverseList :: forall a (es :: Effects) r. (forall (e :: Effects). Stream a e -> Eff (e :& es) r) -> Eff es ([a], r)
- enumerate :: forall (e2 :: Effects) (es :: Effects) a r. e2 :> es => (forall (e1 :: Effects). Stream a e1 -> Eff (e1 :& es) r) -> Stream (Int, a) e2 -> Eff es r
- enumerateFrom :: forall (e2 :: Effects) (es :: Effects) a r. e2 :> es => Int -> (forall (e1 :: Effects). Stream a e1 -> Eff (e1 :& es) r) -> Stream (Int, a) e2 -> Eff es r
- mapMaybe :: forall (e2 :: Effects) (es :: Effects) a b r. e2 :> es => (a -> Maybe b) -> (forall (e1 :: Effects). Stream a e1 -> Eff (e1 :& es) r) -> Stream b e2 -> Eff es r
- catMaybes :: forall (e2 :: Effects) (es :: Effects) a r. e2 :> es => (forall (e1 :: Effects). Stream (Maybe a) e1 -> Eff (e1 :& es) r) -> Stream a e2 -> Eff es r
- yield :: forall (e1 :: Effects) (es :: Effects) a. e1 :> es => Stream a e1 -> a -> Eff es ()
- inFoldable :: forall t (e1 :: Effects) (es :: Effects) a. (Foldable t, e1 :> es) => t a -> Stream a e1 -> Eff es ()
Handle
type Stream a = Coroutine a () #
A handle to a stream that yields values of type a. It is
implemented as a handle to a coroutine that expects values of type
() and then yields values of type a.
Handlers
Arguments
| :: forall a b (es :: Effects) r. (forall (e1 :: Effects). Coroutine a b e1 -> Eff (e1 :& es) r) | |
| -> (a -> Eff es b) | Apply this effectful function for each element of the coroutine |
| -> Eff es r |
>>> runPureEff $ yieldToList $ \y -> do
forEach (inFoldable [0 .. 3]) $ \i -> do
yield y i
yield y (i * 10)
([0, 0, 1, 10, 2, 20, 3, 30], ())
Arguments
| :: forall a (es :: Effects) r. (forall (e1 :: Effects). Stream a e1 -> Eff (e1 :& es) r) | |
| -> Eff es ([a], r) | Yielded elements and final result |
>>> runPureEff $ yieldToList $ \y -> do
yield y 1
yield y 2
yield y 100
([1,2,100], ())
Arguments
| :: forall a (es :: Effects) r. (forall (e :: Effects). Stream a e -> Eff (e :& es) r) | |
| -> Eff es ([a], r) | Yielded elements in reverse order, and final result |
This is more efficient than yieldToList because it gathers the
elements into a stack in reverse order. yieldToList then reverses
that stack.
>>> runPureEff $ yieldToReverseList $ \y -> do
yield y 1
yield y 2
yield y 100
([100,2,1], ())
Arguments
| :: forall (e2 :: Effects) (es :: Effects) a r. e2 :> es | |
| => (forall (e1 :: Effects). Stream a e1 -> Eff (e1 :& es) r) | ͘ |
| -> Stream (Int, a) e2 | |
| -> Eff es r |
Pair each element in the stream with an increasing index, starting from 0.
>>> runPureEff $ yieldToList $ enumerate (inFoldable ["A", "B", "C"]) ([(0, "A"), (1, "B"), (2, "C")], ())
Arguments
| :: forall (e2 :: Effects) (es :: Effects) a r. e2 :> es | |
| => Int | Initial value |
| -> (forall (e1 :: Effects). Stream a e1 -> Eff (e1 :& es) r) | |
| -> Stream (Int, a) e2 | |
| -> Eff es r |
Pair each element in the stream with an increasing index, starting from an inital value.
>>> runPureEff $ yieldToList $ enumerateFrom1 (inFoldable ["A", "B", "C"]) ([(1, "A"), (2, "B"), (3, "C")], ())
Arguments
| :: forall (e2 :: Effects) (es :: Effects) a r. e2 :> es | |
| => (forall (e1 :: Effects). Stream (Maybe a) e1 -> Eff (e1 :& es) r) | Input stream |
| -> Stream a e2 | |
| -> Eff es r |
Remove Nothing elements from a stream.