Break with traverse / traverse_?

I’m actually partial to where clauses, and given the choice, I’d prefer more specialized functions to abusing foldr all day.

But it’s in the idea of a “what’s the simplest possible dialect of Haskell”? Right now, I think it comes down to Foldable, Traversable, Functor, Applicative, Monad, which is actually the standard right now, isn’t it?

With the most “accessible” dialect in mind, then foldr abuse becomes warranted, using let instead of where becomes more warranted, and so on.

Thanks! Those examples help me understand a lot more clearly what’s going on. Since I was playing around with the code anyway, here are the definitions of foo and bar with some sample outputs:

import Control.Monad.IO.Class
import Control.Monad.Trans.Except
import Data.Traversable

foo :: [Int] -> IO [Int]
foo count = (either id pure =<<) . runExceptT . for count $ \u ->
    if even u
        then throwE $ [u] <$ putStrLn (show u <> " is Even!")
        else liftIO $ u <$ print u
-- ghci> foo [1,3,5,7]
-- 1
-- 3
-- 5
-- 7
-- [1,3,5,7]
-- ghci> foo [1,3,4,5,7]
-- 1
-- 3
-- 4 is Even!
-- [4]

bar :: [Int] -> IO [Int]
bar count =
    let act a k = if even a
            then [a] <$ putStrLn (show a <> " is even!")
            else  const (a :) <$> print a <*> k in
    foldr act (pure []) count
-- ghci> bar [1,3,5,7]
-- 1
-- 3
-- 5
-- 7
-- [1,3,5,7]
-- ghci> bar [1,3,4,5,7]
-- 1
-- 3
-- 4 is even!
-- [1,3,4]

I would suggest using ExceptT and either in foo as follows:

import Control.Monad.IO.Class
import Control.Monad.Trans.Except
import Data.Traversable

foo :: [Int] -> IO [Int]
foo count = runEarlyReturn $ for count $ \u ->
  if even u
    then do
      liftIO (putStrLn (show u <> " is Even!"))
      earlyReturn [u]
    else do
      liftIO (print u)
      pure u
-- ghci> foo [1,3,5,7]
-- 1
-- 3
-- 5
-- 7
-- [1,3,5,7]
-- ghci> foo [1,3,4,5,7]
-- 1
-- 3
-- 4 is Even!
-- [4]

runEarlyReturn :: Monad m => ExceptT b m b -> m b
runEarlyReturn m = (pure . either id id) =<< runExceptT m

earlyReturn :: Monad m => a -> ExceptT a m r
earlyReturn = throwE

However, bar is more subtle. It demonstrates well the need for lightweight streams/iterators. Luckily Bluefin (package: bluefin) has them! This is what foo and bar look like in Bluefin:

import Bluefin.EarlyReturn (returnEarly, withEarlyReturn)
import Bluefin.IO (effIO, runEff)
import Bluefin.Jump (jumpTo, withJump)
import Bluefin.Stream (yield, yieldToList)
import Data.Foldable (for_)

foo :: [Int] -> IO [Int]
foo count = runEff $ \io -> do
  withEarlyReturn $ \early -> do
    (as, ()) <- yieldToList $ \y -> do
      for_ count $ \u -> do
        if even u
          then do
            effIO io (putStrLn (show u <> " is Even!"))
            returnEarly early [u]
          else do
            effIO io (print u)
            yield y u

    pure as
-- ghci> foo [1,3,5,7]
-- 1
-- 3
-- 5
-- 7
-- [1,3,5,7]
-- ghci> foo [1,3,4,5,7]
-- 1
-- 3
-- 4 is Even!
-- [4]

bar :: [Int] -> IO [Int]
bar count = runEff $ \io -> do
  (as, ()) <- yieldToList $ \y -> do
    withJump $ \break -> do
      for_ count $ \a -> do
        yield y a
        if even a
          then do
            effIO io (putStrLn (show a <> " is even!"))
            jumpTo break
          else
            effIO io (print a)

  pure as
-- ghci> bar [1,3,5,7]
-- 1
-- 3
-- 5
-- 7
-- [1,3,5,7]
-- ghci> bar [1,3,4,5,7]
-- 1
-- 3
-- 4 is even!
-- [1,3,4]
1 Like

For me, it’s a bit galling to have to reconfigure type signatures and add run* for a change that would be a one word statement in a Blub language. It feels like a lot of ceremony. It’s very surprising to me that others don’t relate to the experience of finding monad transformers a bit cumbersome in comparison to equivalent features in other languages.

1 Like

I really love Lean 4’s solution to this (see section 4), where they soup up do notation with a desugaring of imperative looking loops to monad transformers, complete with break/continue.

To make this a more fair comparison, try to implement an algorithm which relies on laziness in a Blub-like language…


…so they implemented their own miniature (version of a) Blub-like language - but will it be “forwards compatible” with e.g. implicit parallelism? Or will much of that “mini-Blub” have to be replaced with ordinary Lean?

I’m not trying to advocate for imperative style per-se here, I’d be thrilled to see a solution in a more functional style with comparable ergonomics to break.

When this thread first appeared, I remembered seeing a variant of one of the mapAccum{L,R} functions - the parameter function used Either a b to indicate whether to conclude early or keep processing the rest of the list. But so far my searches have been futile.

Perhaps someone else may recall seeing this function…

1 Like

I sympathise.

It is.

I absolutely relate. That’s why I developed Bluefin.

Bluefin supports break/continue and it doesn’t even need a new desugaring.

I am trying to advocate for a more imperative style, and I believe Bluefin hits the spot perfectly. I’d love anyone interested to try it out and give me their feedback.

Do you have a particular example in mind? I’ll implement it in Bluefin. Here’s an example I just came up with. It reads Ints and adds all the positive ones, until it reads something that’s not an Int.

addReadLinePositives :: IO Int
addReadLinePositives = runEff $ \io ->
  evalState 0 $ \state -> do
    -- Set break, a point we can jump to to exit the loop
    withJump $ \break -> forever $
      -- Set continue, a point we can jump to to continue the loop
      withJump $ \continue -> do
        -- Read the line
        line <- effIO io getLine
        i <- case readMaybe line of
          Nothing ->
            -- If it's not an Int, break
            jumpTo break
          Just i ->
            pure i

        -- If it's negative, ignore
        when (i < 0) $
          jumpTo continue

        -- Otherwise, accumulate it
        modify state (+ i)

    get state
ghci> addReadLinePositives 
1
2
3
-100
STOP
6
1 Like

Looks cool! I love the idea of a “StateRef” so to speak, it makes so much sense in retrospect.

1 Like

Yes, and just wait until you start using “ExceptionRefs”!

1 Like

Is there some library that provides early return using the delimited continuation primops recently added to GHC?

I suppose the outward interface would be similar to that of libraries that use exceptions for the same purpose.