Skip to content

Commit 0725a12

Browse files
Giulio ForestoGiulio Foresto
Giulio Foresto
authored and
Giulio Foresto
committed
feat(SourceT): add fromConsumableActionStep that creates a StepT from an action that consumes some data
1 parent d35b3e9 commit 0725a12

File tree

2 files changed

+45
-0
lines changed

2 files changed

+45
-0
lines changed
Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
synopsis: Add a `StepT` constructor method that consumes a resource
2+
prs: #1533
3+
issues: #1448
4+
5+
description: {
6+
7+
`fromActionStep` always runs the same action, which makes it impossible with such monadic actions to
8+
"consume" a resource (that is to say to pass the modified resource to the following action), or
9+
"unfold" an input structure.
10+
11+
`fromUnfoldActionStep` gives this possibility.
12+
13+
This allows for example to build a `StepT m` directly from a `Streaming.Prelude.Stream`, by passing
14+
`fromUnfoldActionStep` the following argument:
15+
16+
```haskell
17+
import Streaming.Prelude as S
18+
19+
action :: Stream (Of a) m r -> m (Maybe ( a, Stream (Of a) m r ))
20+
action = S.uncons
21+
```
22+
}

servant/src/Servant/Types/SourceT.hs

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
{-# LANGUAGE GADTs #-}
33
{-# LANGUAGE RankNTypes #-}
44
{-# LANGUAGE ScopedTypeVariables #-}
5+
{-# LANGUAGE TupleSections #-}
56
module Servant.Types.SourceT where
67

78
import Control.Monad.Except
@@ -312,6 +313,28 @@ fromActionStep stop action = loop where
312313
| otherwise = Yield x loop
313314
{-# INLINE fromActionStep #-}
314315

316+
-- | Create a `StepT' from a consumable @c@, that is to say from an input and an action that returns
317+
-- and is called again on an updated version of that input.
318+
--
319+
-- >>> import qualified Streaming.Prelude as S
320+
-- >>> foreachStep mempty print (fromUnfoldActionStep S.uncons $ S.each [1..3] :: StepT IO Int)
321+
-- 1
322+
-- 2
323+
-- 3
324+
--
325+
fromUnfoldActionStep :: Functor m
326+
=> (c -> m (Maybe (a,c)))
327+
-- ^ Action. Return @Nothing@ to stop or @Just (a,c)@ where @a@ is the
328+
-- output element of the action and @c@ the updated input
329+
-> c
330+
-- ^ Input
331+
-> StepT m a
332+
fromUnfoldActionStep action = loop where
333+
loop c = Effect $ step <$> action c
334+
step Nothing = Stop
335+
step (Just (x,t)) = Yield x $ loop t
336+
{-# INLINE fromUnfoldActionStep #-}
337+
315338
-------------------------------------------------------------------------------
316339
-- File
317340
-------------------------------------------------------------------------------

0 commit comments

Comments
 (0)