Skip remaining steps in monad-like return

Hi, I'm looking for a good way to let the monad stack skip the remaining steps without skipping completely. View as return

in C-family languages.

For example, let's say I am using monadic actions for side effects

type MyMonad = ??
doStuff :: MyMonad ()
doStuff = do
   r <- doSomething

   -- equivalent to if (r == "X") return; in C
   dontGoPastHereIf (r == "X")

   doSomeSideEffects r

      

So I want it to only execute doSomeSideEffects

under some condition.

I know you can do something close to this with guard

and when

. Is it possible to do without nesting?

ExceptT

already allows you to exit the normal flow and return with an early result. But with ExceptT

error / miss will propogate. I only want to skip the rest of the steps in the local function

doTwoSteps :: MyMonad ()
doTwoSteps = do
  -- if I used ExceptT, an error in the first function will skip the second.
  -- But I still want to do the second step here
  doStuff
  doStuff

      

It seems like bind is >>=

already doing this. At least this is, of course, in the capabilities of a monad, but I'm not sure how to do this with monad transformers.


Here's a more complete example. This system is assumed to be running a "workflow". Each step can lead to a response that should stop the entire workflow and respond ( ExceptT

).

The workflow can be restarted by going through ApplicationState

. If a step has a previous one Continue

, we can skip the logic for this step, but we still need to complete the next step.

Is there a better way to do this? Is there some kind of monad transformer or a way to define my monad Flow

so that I can run checkShouldSkip

without being sent to action?

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}

module Main where

import Control.Monad.Except (throwError, ExceptT)
import Control.Monad.State (gets, StateT, modify)
import Data.Text (Text)

data ApplicationState = ApplicationState
    { step1Result :: Maybe StepResult
    , step2Result :: Maybe StepResult
    } deriving (Show, Eq)

data StepResult
    = Stop
    | Continue
    deriving (Show, Eq)

type Flow a = StateT ApplicationState (ExceptT Text IO) a


flow :: Flow ()
flow = do
    step1
    step2

step1 :: Flow ()
step1 = do
    ms <- gets step1Result
    checkShouldSkip ms $ do
      info <- getStuffFromAServer
      let r = runSomeLogic info
      modify $ setStep1 $ Just r
      checkShouldRespond r

  where
    getStuffFromAServer = undefined
    runSomeLogic _ = undefined
    setStep1 r s = s { step1Result = r }


step2 :: Flow ()
step2 = do
    ms <- gets step2Result
    checkShouldSkip ms $ do
      -- this will run some different logic, eventually resulting in a step result
      r <- getStuffAndRunLogic
      modify $ setStep2 $ Just r
      checkShouldRespond r

  where
    getStuffAndRunLogic = undefined
    setStep2 r s = s { step2Result = r }


checkShouldSkip :: Maybe StepResult -> Flow () -> Flow ()
checkShouldSkip (Just Continue) _ = pure () -- skip the logic, continue
checkShouldSkip (Just Stop) _ = respond "Stop" -- skip the logic, stop everything
checkShouldSkip Nothing a = a -- run the action


checkShouldRespond :: StepResult -> Flow ()
checkShouldRespond Continue = pure ()
checkShouldRespond Stop = respond "Stop" -- if a response, stop all execution


-- rename because these aren't really errors, I just want to stop everything
respond :: Text -> Flow ()
respond t = throwError t

      

+3


source to share


2 answers


You can do this with ExceptT

if you want to close the area you want to exit from:

type EarlyReturnT m a = ExceptT a m a

withEarlyReturn :: (Functor m) => EarlyReturnT m a -> m a
withEarlyReturn = fmap (either id id) . runExceptT

earlyReturn :: (Applicative m) => a -> EarlyReturnT m a
earlyReturn = ExceptT . pure . Left

      

For example:



doStuff :: Bool -> IO String
doStuff x = withEarlyReturn $ do
  lift $ putStrLn "hello"
  when x $ earlyReturn "beans"
  lift $ putStrLn "goodbye"
  return "eggs"

> doStuff False
hello
goodbye
"eggs"

> doStuff True
hello
"beans"

      

Or s ContT

, where "early return" is a continuation.

type EarlyReturnT m a = ContT a m a

withEarlyReturn
  :: (Applicative m)
  => ((a -> EarlyReturnT m a) -> EarlyReturnT m a)
  -> m a
withEarlyReturn = flip runContT pure . callCC

doStuff :: Bool -> IO String
doStuff x = withEarlyReturn $ \ earlyReturn -> do
  lift $ putStrLn "hello"
  when x $ earlyReturn "beans"
  lift $ putStrLn "goodbye"
  return "eggs"

      

+6


source


Another answer is great! I wanted to talk a little about how exactly the sequel works, so I wrote this weird thing. Hope it helps.

Act I: Trap Laid Out

We begin our journey on the low stone plains IO

, our favorite state monad:

module Lib where

step1 :: IO String
step1 = do
  print "step1 - A"
  print "step1 - B"
  pure "--step1 result--"

step2 :: String -> IO String
step2 input = do
  print input
  print "step2 - A"
  print "step2 - B"
  pure "--step2 complete--"

main :: IO ()
main = do
  result <- step1 >>= step2
  print "--done--"
  print result

      

We want to climb up and find a way to get back from the first step. Our first attempt is to introduce some dubiously typed exit mechanism:

step1 :: (String -> ???) -> IO String
step1 escape = do
  print "step1 - A"
  escape "escaped!"
  print "step1 - B"
  pure "--step1 result--"

      

We cross our fingers, hoping that the line we go to escape

will end up as line in IO String

and think about what exactly might fill those annoying question marks.

We feel like we need to grab >>=

here if we have any hope of ripping control flow away from the monad IO

. We are careful to assume that we need our own monad transformer.

newtype StrangeT inner a =
  StrangeT { runStrangeT :: a -> ??? }

lift :: IO a -> StrangeT IO a
lift io =
  StrangeT (\trapDoor -> io >>= trapDoor)

escape :: a -> StrangeT IO a
escape a =
  StrangeT (\trapDoorA -> trapDoorA a)

step1 :: StrangeT IO String
step1 = do
  lift (print "step1 - A")
  escape "escaped!"
  lift (print "step1 - B")
  pure "--step1 result--"

      

We can think of trapDoorA

as an evacuation mechanism protected by a key, and the key is any value of the type a

. When the door is open, we move on to the next step in the calculation.

What type to insert for question marks? We have boxed ourselves in the corner; in order for this code to be compiled, we can only:

newtype StrangeT inner a =
  StrangeT { runStrangeT :: (a -> inner a) -> inner a }

      

Act II: A Stranger Yet

Now we need an instance Monad (StrangeT inner)

. Unfortunately, we are faced with a big problem. StrangeT

is not a functor!

The reason for this is that an "a" appears in the "negative position":

newtype StrangeT inner a =
  StrangeT { runStrangeT :: (a -> inner a) -> inner a }
                               -- ^^^^^^^
                               -- :(

      

(For a complete discussion of this topic, see What is a contravariant functor?. )

We can use a bad trick, which is to separate the "negatives" and "positive" on two different types of variables ( a

and result

):

newtype StrangeT result inner a =
  StrangeT { runStrangeT :: (a -> inner result) -> inner result }

lift :: IO a -> StrangeT whatever IO a
lift io = StrangeT (\trapDoor -> io >>= trapDoor)

escape :: a -> StrangeT whatever IO a
escape x = StrangeT (\trapDoor -> trapDoor x)

      

It does its best. We can now cast an instance of Functor, Applicative, and Monad. Instead of trying to figure out the answers, we'll just allow type checking. Any answer that checks for type will be correct.

instance Functor (StrangeT result inner) where
  fmap a2b (StrangeT strange) =
    StrangeT $ \trapDoor -> strange (\a -> trapDoor (a2b a))
             -- ^^^^^^^^
             -- b -> inner result

      

Logic train:

  • trapDoor

    is the only way to build meaning inner result

    .

  • Type value is required b

    .

  • We have a2b :: a -> b

    and a :: a

    .

    instance Applicative (StrangeT result inner) where
      pure :: a -> StrangeT result inner a
      pure a = StrangeT $ \trapDoor -> trapDoor a
    
      (<*>) :: StrangeT result inner (a -> b) ->
               StrangeT result inner a ->
               StrangeT result inner b
      (StrangeT strangeA2B) <*> (StrangeT strangeA) =
    --          ^^^^^^^^^^                ^^^^^^^^
    --          (b -> inner result) -> inner result
    --                                    (a -> inner result) -> inner result
        StrangeT (\trapDoorB -> strangeA2B (\a2b -> strangeA (\a -> trapDoorB (a2b a))))
    --             ^^^^^^^^                 
    --             b -> inner result
    
          

Logic train:

  • We have trapDoorB :: b -> inner result

    (the only way to build an internal result), a2b :: a -> b

    and a :: a

    .

  • We need to build a StrangeT result inner b

    ;

  • Therefore, we must evaluate at some point trapDoorB (a2b a)

    .

A monadic example is about the same complex:

    instance Monad (StrangeT result inner) where
      (StrangeT strangeA) >>= a2strangeB =
         --     ^^^^^^^^
         --     (a -> inner result) -> inner result
        StrangeT
          (\trapDoorB -> strangeA (\a -> let StrangeT strangeB = a2strangeB a in strangeB (\b -> trapDoorB b)))
         -- ^^^^^^^^^                                 ^^^^^^^^
         -- b -> inner result                         (b -> inner result) -> inner result

      

There is only one way of building inner result

, which is going through trapDoorB

, so everything else is built in relation to that single goal.

Act III: Fumble

We defined a monad transformer without knowing what it does or how it works! We just split the types that looked right.

Then we should have seen it in action:

main :: IO ()
main = do
  _ <- runStrangeT (step1 >>= step2) (\a -> pure a)
  print "--done--"
  print result

      

This produces the following result:



ฮป> main
"step1 - A"
"step1 - B"
"--step1 result--"
"step2 - A"
"step2 - B"
"--done--"
"--step2 result--"

      

How frustrating! We're right where we started.

However, something peculiar happens when we define this function:

escape :: a -> StrangeT whatever IO a
escape x = StrangeT (\trapDoor -> trapDoor x)

escapeWeirdly :: a -> StrangeT whatever IO a
escapeWeirdly x = StrangeT (\trapDoor -> trapDoor x >> trapDoor x >> trapDoor x)

step1 :: StrangeT String IO String
step1 = do
  lift (print "step1 - A")
  escapeWeirdly "--step1 exit--"
  lift (print "step1 - B")
  pure "--step1 result--"

      

Output:

ฮป> main
"step1 - A"
"step1 - B"               <- trap door call #1
"--step1 result--"
"step2 - A"
"step2 - B"
"step1 - B"               <- trap door call #2
"--step1 result--"
"step2 - A"
"step2 - B"
"step1 - B"               <- trap door call #3
"--step1 result--"
"step2 - A"
"step2 - B"
"--done--"
"--step2 result--"

      

step2

runs three times! It seems that "trapDoor" encodes some concept of "everything after this point in the control flow". Calling it once triggers everything after it once. Calling it three times, it starts everything after it three times. Calling zero time ...

cut :: a -> StrangeT a IO a
cut x = StrangeT (\_ -> return x)

step1 :: (String -> StrangeT String IO String) -> StrangeT String IO String
step1 exit = do
  lift (print "step1 - A")
  cut "--step1 exit--"
  lift (print "step1 - B")
  pure "--step1 result--"

main :: IO ()
main = do
  result <- runStrangeT (step1 undefined >>= step2) pure
  print "--done--"
  print result

      

Output:

ฮป> main
"step1 - A"
"--done--"
"--step1 exit--"

      

Nothing runs! This is incredibly close to what we need.

Act IV: Success and the Price of Them

What if we could mark do-block from actions StrangeT

as required by early exit? Something very similar to our original exit mechanism:

step1 = withEscape $ \escape -> do
  lift (print "step1 - A")
  escape "--step1 exit--"
  lift (print "step1 - B")
  pure "--step1 result--"

      

Which does withEscape

, since it runs the do block as written until someone calls escape

, after which the rest of the computation will be interrupted, but any computation outside withEscape

(namely step 2 here) is done as -is.

This helper must be of type:

withEscape :: (??? -> StrangeT result inner a) -> StrangeT result inner a

      

Almost the same leap of faith that we took when we went from m a

to (a -> m a) -> m a

.

Since we are passing String

in escape

and binding the result of this calculation to the next line of the do block, we can now fill in these question marks:

withEscape :: ((a -> StrangeT result inner whatever) -> StrangeT result inner a)
              -> StrangeT result inner a

      

Triple type! We'll need to iterate over the type again to find the definition:

-- We have to call f at some point, and trapDoorA
-- is the only way to construct an inner result.
withEscape f =
  StrangeT (\trapDoorA -> let StrangeT strangeA = f ??? in strangeA trapDoorA)

-- f is passed the early exit value
withEscape f =
  StrangeT (\trapDoorA ->
    let StrangeT strangeA = f (\a -> ???) in strangeA trapDoorA)

-- We need to construct a StrangeT value
withEscape f =
  StrangeT (\trapDoorA ->
    let StrangeT strangeA = f (\a -> StrangeT (\trapDoorWhatever -> ???)) in
    strangeA trapDoorA)

-- We are going to *ignore* the trapDoorWhatever
-- we are supposed to fall into, and *instead*
-- fall through our original trapDoorA.
withEscape f =
  StrangeT (\trapDoorA ->
    let StrangeT strangeA = f (\a -> StrangeT (\_ -> trapDoor a)) in
    strangeA trapDoorA)

      

What happened here is that we stumbled upon a solution that gives us two doors. Instead of falling through the first door (which would have caused the helper to fall on something like pure

, as it would resume normal control flow), we decided to fall through the original door that we built for ourselves. Primer fans recognize this as original sin; normal people can just see it all with a confused look on their face.

Whatever works :

step1 :: StrangeT String IO String
step1 =
  withEscape $ \escape -> do
    lift (print "step1 - A")
    escape "--step1 exit--"
    lift (print "step1 - B")
    pure "--step1 result--"

step2 :: String -> StrangeT String IO String
step2 result = do
  lift (print result)
  lift (print "step2 - A")
  lift (print "step2 - B")
  pure "--step2 result--"

main :: IO ()
main = do
  result <- runStrangeT (step1 >>= step2) pure
  print "--done--"
  print result

      

Output:

ฮป> main
"step1 - A"              <- early exit
"--step1 exit--"         <- step2 runs
"step2 - A"
"step2 - B"
"--done--"               <- back to main
"--step2 result--"

      

Summary

  • As wired, it is a monad ContT

    and can be found in the transformer package. What we call trap doors is indeed an extension.

  • withEscape

    better known as callCC

    (call with ongoing continuation); it allows you to give the current continuation at the time you called the callCC

    name ( escape

    in our examples); when you activate a continuation, you can return the value immediately.

  • You can implement a lot of things with continuations, including early returns and exceptions and generators, and god knows what else. We still need to talk about delimited continuations (shift and reset). They represent something primary and fundamental to the structure of computer programming.

  • For more information, see the series of articles related to Oleg Kiselev's site . There is much more to say about sequels.

Should you ever do this in real life?

Probably not. ExceptT

tends to create fewer headaches in the long run.

But ExceptT

colder than ContT

?

Hardly.

+7


source







All Articles