feat(SourceT): add fromConsumableActionStep that creates a StepT from an action that consumes some data
This commit is contained in:
parent
d35b3e9b70
commit
2947532cf2
2 changed files with 45 additions and 0 deletions
22
changelog.d/generalize-fromActionStep-to-consumable
Normal file
22
changelog.d/generalize-fromActionStep-to-consumable
Normal file
|
@ -0,0 +1,22 @@
|
||||||
|
synopsis: Add a `StepT` constructor method that consumes a resource
|
||||||
|
prs: #1533
|
||||||
|
issues: #1448
|
||||||
|
|
||||||
|
description: {
|
||||||
|
|
||||||
|
`fromActionStep` always runs the same action, which makes it impossible with such monadic actions to
|
||||||
|
"consume" a resource (that is to say to pass the modified resource to the following action), or
|
||||||
|
"unfold" an input structure.
|
||||||
|
|
||||||
|
`unfoldStep` gives this possibility.
|
||||||
|
|
||||||
|
This allows for example to build a `StepT m` directly from a `Streaming.Prelude.Stream`, by passing
|
||||||
|
`unfoldStep` the following argument:
|
||||||
|
|
||||||
|
```haskell
|
||||||
|
import Streaming.Prelude as S
|
||||||
|
|
||||||
|
action :: Stream (Of a) m r -> m (Maybe ( a, Stream (Of a) m r ))
|
||||||
|
action = S.uncons
|
||||||
|
```
|
||||||
|
}
|
|
@ -2,6 +2,7 @@
|
||||||
{-# LANGUAGE GADTs #-}
|
{-# LANGUAGE GADTs #-}
|
||||||
{-# LANGUAGE RankNTypes #-}
|
{-# LANGUAGE RankNTypes #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
{-# LANGUAGE TupleSections #-}
|
||||||
module Servant.Types.SourceT where
|
module Servant.Types.SourceT where
|
||||||
|
|
||||||
import Control.Monad.Except
|
import Control.Monad.Except
|
||||||
|
@ -312,6 +313,28 @@ fromActionStep stop action = loop where
|
||||||
| otherwise = Yield x loop
|
| otherwise = Yield x loop
|
||||||
{-# INLINE fromActionStep #-}
|
{-# INLINE fromActionStep #-}
|
||||||
|
|
||||||
|
-- | Create a `StepT' from a consumable @c@, that is to say from an input and an action that returns
|
||||||
|
-- and is called again on an updated version of that input.
|
||||||
|
--
|
||||||
|
-- >>> import qualified Streaming.Prelude as S
|
||||||
|
-- >>> foreachStep mempty print (unfoldStep S.uncons $ S.each [1..3] :: StepT IO Int)
|
||||||
|
-- 1
|
||||||
|
-- 2
|
||||||
|
-- 3
|
||||||
|
--
|
||||||
|
unfoldStep :: Functor m
|
||||||
|
=> (c -> m (Maybe (a,c)))
|
||||||
|
-- ^ Action. Return @Nothing@ to stop or @Just (a,c)@ where @a@ is the
|
||||||
|
-- output element of the action and @c@ the updated input
|
||||||
|
-> c
|
||||||
|
-- ^ Input
|
||||||
|
-> StepT m a
|
||||||
|
unfoldStep action = loop where
|
||||||
|
loop c = Effect $ step <$> action c
|
||||||
|
step Nothing = Stop
|
||||||
|
step (Just (x,t)) = Yield x $ loop t
|
||||||
|
{-# INLINE unfoldStep #-}
|
||||||
|
|
||||||
-------------------------------------------------------------------------------
|
-------------------------------------------------------------------------------
|
||||||
-- File
|
-- File
|
||||||
-------------------------------------------------------------------------------
|
-------------------------------------------------------------------------------
|
||||||
|
|
Loading…
Reference in a new issue