Break with traverse / traverse_?

Is there a way to simulate a break with traverse / traverse_ that doesn’t require ExceptT?

That is to say, continue is easy, run some conditionals, pure (), and you’re on your next iteration.

For break, however, this seems to require foldr (on lazy data structures), which is substantially less ergonomic.

As traverse is a method of the Traversable type class, it wholly depends on which type you are traversing and which type your function returns.

I’m assuming you’re thinking traversing lists (or other collection-like structures). The traversable of List for example is implemented using foldr, so it is possible to “early return”. But if you want to break half-way through, you also need to use a resulting type that can do so. The easiest are probably Maybe or Either e. So instead of traverse (f :: Int -> IO b) [0..3] doing traverse (f :: Int -> Maybe b) [0..3] makes it able to break.

Now using Maybe in this way throws away any information the moment you hit a Nothing somewhere, so using Either e would be the way to return some information on the break.
And if you want to keep the IO in there, then yes, you’ll have to use a monad transformer that changes the behaviour of IO to include an “early return”, which would be something like ExceptT (or you can probably use MaybeT when using traverse_, since the results are discarded anyway).

1 Like

Is it reasonable to turn into a foldr-for-everything kind of person, since foldr seems to provide the most strength and flexibility overall?

I’m annoyed at having to use foldr for everything when I need more flexibility, but even worse, you probably lose the short-circuiting behavior when working on strict datatypes.

foldl' is tail recursive and strict. If you know that you’ll have to traverse the whole list no matter what (e.g., summing the numbers in a list), then foldl' is more space- (and probably time-) efficient than foldr. recursion - Implications of foldr vs. foldl (or foldl') - Stack Overflow

Like most things, the correct solution depends on the problem you’re trying to solve. Becoming a “foldr-for-everything person” means you’ve stopped thinking about what it is you’re trying to do, and just want an easy way out. Which is fine!

5 Likes

I generally find the exotic hacks involved with foldr to be ugly, so talking about “foldr for everything” is derisive; the original text I used, withdrawn on fear of causing offense, was “foldr ueber alles”, with an understanding of what “ueber alles” implies in its local political context.

Either case, we still have the issue wherein you have strict datatypes like Vector which cause the failure of exploiting foldr, implying that you have to resort to parameter variables, which, incidentally, I tend to default to.


Ultimately, it’d be nice to have a better solution for iterating through a data structure with short-circuiting behavior than either resorting to foldr (when the laziness of the data structure allows) or parameter variable recursion (which is an ugly emulation of a C-style loop in most cases).

I’m not calling for OCaml-style syntactical loops, but I am interested in if there’s a better functional way to trigger short-circuiting behavior when traversing a data structure than foldr or parameter variable recursion.


I mean, what you could do would be to implement a forBreak_ function, which piggybacks off traversable to implement a boolean argument, but that’d be, first, unergonomic, two, and essentially ad-hoc, when Traversable and Foldable barely follow the typeclass theme of representing mathematical concepts.

Part of the philosophy of Higher-Order Functions, besides representing iteration / recursion through a data structure, is that they are more SPECIFIC than the traditional imperative way of iterating through data structures (syntactical for), insofar as the specific HoF being used on the data structure indicates the intent of iteration / recursion.

The problem with general use of foldr, or even resorting to foldr often, is that foldr masks the intent behind the recursion / iteration, whereas map / foldl’ / traverse etc make it clearer what you’re trying to do since these are more limited in their power.


Anyways, as it turns out, Data.Vector.foldr still respects laziness, presumably via stream fusion, so at least with Data.Vector.Vector it’s still viable to use foldr to implement short-circuiting traversals.

I don’t think I quite understand what your criteria are (in particular why you want to avoid ExceptT) but it’s related to some things that I’ve been thinking about recently. I wrote an article explaining some of the concepts foldl traverses with State, foldr traverses with anything that shows why foldr is equivalent to for_ with a suitable choice of Applicative.

In case you want to avoid ExceptT but an effect system with other properties is OK, this is how I would do it in my recently-released effect system Bluefin (Hackage package bluefin):

import Control.Monad (when)
import Data.Foldable (for_)
import Bluefin.Eff (runPureEff)
import Bluefin.EarlyReturn (returnEarly, withEarlyReturn)

myElem :: Eq a => a -> [a] -> Bool
myElem a as = runPureEff $ withEarlyReturn $ \early -> do
  for_ as $ \a' -> do
    when (a' == a) $
      returnEarly early True

  pure False
-- ghci> 3 `myElem` [1..5]
-- True
-- ghci> 10 `myElem` [1..5]
-- False
2 Likes

When it comes to higher-order functions, my theory is:

  1. The imperative-syntactical for is considered harmful, because for is so general and can be used for everything. Using a higher-order function, specifically one more specialized, like fmap / specialized maps, traverse, traverse_, foldl’, etc, makes your intent clearer and results in more maintainable code.

  2. foldr is the functional equivalent of for, because anything for can do, foldr can do as well, except that foldr is even worse, because by default it’ll create a single excess thunk in a list, and using foldr for everything will generally result in space leaks (as your article shows).

  3. No higher-order function in base or combination of higher-order function and programming technique, other than for, can restore the short-circuiting behavior of imperative-syntactical for, forcing the use of foldr (provided the data structure is lazy enough) to restore short-circuiting iteration. This means that you can’t avoid the use of foldr altogether, and have to employ foldr when you need a short-circuiting recursion / loop, and there, it’s not clear whether or not you’re employing bad style with overuse of foldr or resorting to foldr because there’s no higher-order function with the necessary capabilities.

As for ExceptT, I just dislike monad transformers for often-unnecessary complexity (and I know I’m not alone). At certain scales, yes, monad transformers / effect systems make sense, but at micro-scales my skill limits me to, monad transformers just add performance and complexity overhead.


The ideal for me, would be to have a specialized higher-order function or techniques with existing HOFs that allows me to have short-circuiting capability without the philosophical baggage of foldr,

1 Like

Ah, I see. Then my example is the opposite of what you wanted. It’s interesting, because I am becoming converted to exactly the opposite stance. I want to use only for/for_ and then configure their behaviour by choosing the appropriate Applicative for it to run in. This is a continuation of an idea I proposed here at Beautiful functional programming - #53 by tomjaguarpaw. Bluefin makes this approach very easy!

2 Likes

I can understand the opposite point of view; the “more specific than for” viewpoint has the disadvantage that you’d have to learn the HOF zoo, when Haskell already has enough complex and obscure libraries already (Lens / Optics, Effect Systems, Recursion Schemes).

If you want to do everything with foldr, even in a worst case scenario, you can have foldr simulate foldl’ by putting additional data beyond the Foldable and having your reducing function interact with the data.

2 Likes

Yes, exactly, and the HOF zoo doesn’t compose, whereas a decent effect system does compose.

1 Like

Just out of curiosity at this stage, it’s trivially easy to implement

traverseB_
    :: (Foldable t, Applicative f)
    => (a -> Maybe (f b))
    -> t a
    -> f ()
traverseB_ f = foldr (\a k -> case f a of
    Nothing -> pure ()
    Just b -> b >> k) (pure ())

Is it possible to have a traverseB :: (Traversable t, Applicative f) => (a -> Maybe (f b)) -> t a -> f (t b)
as well? I think not, because you’d want a default value to replace the underlying element, could run it as traverseB :: (Traversable t, Applicative f) => (a -> Maybe (f b)) -> b -> t a -> f (t b)
instead.

On HN, there’s a few users complaining about the inability to break when they’re abusing loops; traverseB / traverseB_ / forB / forB_ in base would help get the complaints to go away, by having a standardized way to break if necessary.

Can you share a link?

1 Like

https://news.ycombinator.com/item?id=37247797

Complaints about the lack of early return, proposed solution is to ExceptT everything.

Sigh.


I just don’t like the fact that if you’re doing raw Prelude, you’re stuck using foldr for the problem, although Foldr Does Everything ™ isn’t that bad a situation.

foldr abuse is probably the correct way to go about a production codebase that has onramping as a major concern; but then you get into the fact that foldr itself has poor formatting.

I’d have preferred:
foldrFor :: t a -> b -> (a -> b -> b) -> b and foldrTraverse :: b → (a → b → b) → t a → b
as a way to say: there, you have fake for loops, now shut up about being made to use Haskell.

“Every little thing I see, looks like a glorious fold to me!”

Thanks. I still don’t understand the objection to ExceptT. It seems to solve the problem precisely.

2 Likes

My issue with ExceptT is that it’s clunky and verbose. It solves the problem, but doesn’t do it in an elegant way.

foldFor and foldTraverse would probably be better solutions for people seeking to code JS in Haskell… of course, whether that’s worth doing is a different question. Amazingly, neither the foldFor nor foldrFor names are in the Hoogle database.

https://hoogle.haskell.org/?hoogle=foldFor
https://hoogle.haskell.org/?hoogle=foldrFor
https://hoogle.haskell.org/?hoogle=foldTraverse
https://hoogle.haskell.org/?hoogle=foldrTraverse

Maybe you could give an example showing the same code implemented with ExceptT and with your preferred solution, to make the clunkiness, verbosity and inelegance of the former more obvious?

1 Like

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.

1 Like

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