Break with traverse / traverse_?

I do wonder when you’d actually need this? :thinking:
I think I’ve never used this, because I’d just first filter on what I want to traverse and then just traverse.
Like, takeWhile upToBreakPoint xs or filter whichToDo xs and then just traverse over the result.

I’m really wondering in which situations this would not work. Would anyone have an example where a takeWhile or filter (or something similar) wouldn’t work out?

EDIT: I guess if the breaking or not depends on (the result of) the action taken during the traversing? :thinking: I have not encountered this situation before, but it’s not too wild. I guess a custom exception and try would also solve this, maybe?
But I think I’d just use ExceptT in that situation. It’s adding one runExceptT and then like one or two ExceptT constructors, I guess.

2 Likes

so, am I using either and ExceptT correctly?


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

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

vs

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

Note that the behavior is subtly different, and I’m unsure how to replicate it with ExceptT.

I’d actually prefer:

foldFor :: Foldable t => t a -> b -> (a -> b -> b) -> b
foldFor foldable def function = foldr function def foldable

baz :: [Int] -> IO [Int]
baz count = foldFor count (pure []) $ \u k ->
    if even u
        then [u] <$ putStrLn (show u <> " is even!")
        else const (u:) <$> print u <*> k

The first and the set of second and third examples aren’t equivalent semantically, anyways, but IIRC that’s a limitation of ExceptT (and why Snoyman went after it on FP Complete).

I think you COULD regain it by compositing ExceptT and StateT? But then… well, maybe later, I’m having very aggravating VPS issues.


Ugh, adding StateT to save the state of ExceptT would require MTL. Sheesh.

2 Likes

Would you want the last element of the returned list to be the first element that “violated” the invariant/check? That’s what bar and baz seem to do.

My intuition would say for (takeWhile odd count) $ \c -> c <$ print c.
And if you’d want to check that there aren’t any evens in there:

let (odds, rest) = break even count
case rest of
  c :_ -> putStrLn $ show c <> " is even!")
  [] -> ...
-- and decide if you want to run it in both situations,
-- or maybe only if all counts are "not even".

Like, why do all the printing and checking inside of a loop?
Feels very imperative and as you see it brings a lot of annoyances trying to fit this into the functional paradigm.


Also, I just realized I often just make a looping definition if I need to run actions and continue or stop at some point:

loop [] = pure []
loop (c:cs)
  | even c = putStrLn (show c <> " is even!") >> pure [] -- or [c]
  | otherwise = print c >> (c:) <$> go cs

Which is sort of foldr inlined, I guess. :thinking: It’s about as big a definition as baz, maybe even slightly less.

And if I use folds I mostly format them like this:

baz :: [Int] -> IO [Int]
baz =
    foldr go $ pure []
  where
    go u acc
      | even u = [u] <$ putStrLn (show u <> " is even!")
      | otherwise = print u >> (u:) <$> acc
1 Like

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]
3 Likes

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.

2 Likes

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.

1 Like

@tomjaguarpaw I like your solution here, but my use case needs the last returned value in the current iteration. Does this early exit work with foldM also, used in a nested loop as shown below (I didn’t compile this code)

runExceptT $ forM_ [maxFactor, maxFactor -1..minFactor] $ \left ->
  runExceptT $ foldM (go left) Nothing [maxFactor, maxFactor -1..minFactor]
where
  go l pal r = case palindrome (>=) l pal r of
    Left p -> ME.throwError p
    Right p -> return p

The intent is to break out of the two loops when a Left is returned by the function palindrome.

Hi @bruce-wayne

Do you mean like this? If not, could you say more about what you mean?

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

baz :: [Int] -> IO ([Int], Maybe Int)
baz count = runEff $ \io -> do
  (as, ma) <- yieldToList $ \y -> do
    withEarlyReturn $ \ret -> do
      for_ count $ \a -> do
        yield y a
        if even a
          then do
            returnEarly ret (Just a)
          else
            effIO io (print a)

      pure Nothing

  let message = case ma of
        Just a -> show a <> " is even!"
        Nothing -> "There was no even element"

  effIO io (putStrLn message)

  pure (as, ma)
-- ghci> baz [1, 3, 5, 7]
-- 1
-- 3
-- 5
-- 7
-- There was no even element
-- ([1,3,5,7],Nothing)
-- ghci> baz [1, 3, 4, 5, 7]
-- 1
-- 3
-- 4 is even!
-- ([1,3,4],Just 4)

I take it this is a separate question? If so, yes, it works with foldM, but there’s no real need for foldM if you’re using Bluefin. It’s probably easier just to use for_ and evalState:

import Control.Monad (foldM, when)
import Bluefin.EarlyReturn (returnEarly, withEarlyReturn)
import Bluefin.IO (effIO, runEff)
import Bluefin.Jump (jumpTo, withJump)
import Bluefin.State (evalState, get, put)
import Bluefin.Stream (yield, yieldToList)
import Data.Foldable (for_)

runningSumUntilNegativeFoldM l = runEff $ \io -> do
  withJump $ \done -> do
    (\f -> foldM f 0 l) $ \soFar i -> do
      when (i < 0) $
        jumpTo done
      let next = soFar + i
      effIO io (print next)
      pure next

    pure ()
-- ghci> runningSumUntilNegativeFoldM [1, 2, 3, 4, -1, 5]
-- 1
-- 3
-- 6
-- 10


runningSumUntilNegativeFor l = runEff $ \io -> do
  withJump $ \done -> do
    evalState 0 $ \total -> do
      for_ l $ \i -> do
        when (i < 0) $
          jumpTo done
        soFar <- get total
        let next = soFar + i
        effIO io (print next)
        put total next
-- ghci> runningSumUntilNegativeFor [1, 2, 3, 4, -1, 5]
-- 1
-- 3
-- 6
-- 10

@tomjaguarpaw I’m not using Bluefin, the set of packages that’re available are predefined, and Bluefin isn’t in there. Basically, I’ve two nested loops, and the inner loop calls a function that returns an Either. If it’s a Left, the code should break out of both loops and return the value wrapped in the Either. If it’s a Right, the wrapped value should be passed into the next function call. Please see a crude attempt below.

run :: (Monad m) => ExceptT a m a -> m a
run = (pure . either id id =<<) . ME.runExceptT

largestPalindrome :: Integer -> Integer -> Palindrome
largestPalindrome minFactor maxFactor =
  run $ forM [maxFactor, maxFactor -1..minFactor] $ \left ->
    runExceptT $ foldM (go left) Nothing [maxFactor, maxFactor -1..minFactor]

If you’d prefer a separate question, I can certainly create one.

Well, how about this? But it’s quite hard to know exactly what you want without more details.

import Data.Foldable (for_)
import Control.Monad (foldM)
import Control.Monad.Identity (runIdentity)
import Control.Monad.Trans.Except (ExceptT, runExceptT, throwE)

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

data Palindrome

palindrome :: (b -> b -> Bool) -> b -> Maybe b -> b -> (Either Palindrome (Maybe b))
palindrome _ _ _ _ = undefined

largestPalindrome :: Integer -> Integer -> Maybe Palindrome
largestPalindrome minFactor maxFactor =
  runIdentity $ runEarlyReturn $ do
    for_ [maxFactor, maxFactor -1..minFactor] $ \left -> do
      foldM (go left) Nothing [maxFactor, maxFactor -1..minFactor]
    pure Nothing
  where
    go l pal r = case palindrome (>=) l pal r of
      Left p -> throwE (Just p)
      Right p -> return p

No, that’s OK. I was just trying to understand if you were asking two separate things, or just mentioning two aspects of the same thing.

Unfortunately, this didn’t produce the intended result, certainly not due to your code, but my inept attempt at describing the problem. I’m actually trying to come up with Haskell code for the following Python program, which is also my writing.

I’ve to do something else now, but I’ll come back to it this weekend.

1 Like