Apply (monadic) function n times without making a list?

As an exercise, I was creating a function that takes an argument n, and asks the user for n numbers to add up, printing the running sum as they do so, before yielding an IO Int to the caller. This was an exercise in some tutorial, but I can’t find it anymore.

Anyway, I didn’t want to use a primitive recursive helper function, but this was the only solution I could come up with that didn’t use one.

runningSum :: Int -> IO Int
runningSum n = foldM helper 0 [1..n]
  where
    helper sum _ = do
        result <- read <$> getLine
        let sum' = sum + result
        putStr "Running sum: "; print sum'
        return sum'

But the only reason to write [1..n] is to apply the function helper n times; the actual list elements are discarded. It could just as well be defined this way:

runningSum n = foldM helper 0 (replicate n undefined)

And it would be “fine” because no element of the list is ever accessed.

I know Haskell is lazy, but still, isn’t it inefficient to create a list solely to repeat an action n times? If so, is there a better way of achieving that? Is there some standard library function to apply a function n times, and a monadic version? I imagine the latter would have the type signature Monad m => (a -> m a) -> Int -> a -> m a; something like foldM without the list. I could write this function, but I wanted to know if there was a standard, better way to repeat something N times without generating an intermediate list; is there? (iterate wouldn’t be a good suggestion, because it does generate an intermediate list).

Consider the opposite: wouldn’t it be inefficient to have a specialized function like that when there exists a strictly more powerful solution that demands a meager (arguably negligible) toll for its use? You’re still free to write a more efficient function, but it’s not a burden on library maintainers, which is great.

From a wider design standpoint, consider that your bottlenecks will most probably be in specific functions you execute, not in the control flow itself, and all high-level Haskell is about extremely expressive control flows.

Efficiency isn’t the end-all be-all, but it should at least be thought of a little bit; otherwise, why implement associative maps with trees or hash tables when you can use linked lists? Why not just use a naive fibonacci function until you have to benchmark?

I came up with these just now. These functions are pretty simple:

doTimes n f z | n > 0 = doTimes (n - 1) f (f z)
              | otherwise = z

doTimesM n f z | n > 0 = f z >>= doTimesM (n - 1) f
               | otherwise = return z

runningSum n = doTimesM n helper 0
  where
    helper sum = do ... -- otherwise exactly the same

But I imagine you’d want something like this in the standard library so that people don’t keep reinventing their own version whenever they need it.

Edit: But, does that mean that there’s no standard way to do this in Haskell?

You’ll find GHC is quite good at optimizing out lists in simple examples like yours, even at -O1. If you compile your example to Core you can see that there’s no sign of any list producers or consumers, just a recursive function with an accumulator.

A slightly more idiomatic base-only way to write this might be foldr (>=>) pure (replicate n helper) 0.

4 Likes
import Data.Semigroup

foo :: Monad m => (a -> m a) -> Int -> a -> m a
foo f n = appEndo (stimes n (Endo (>>= f))) . pure
2 Likes

Or a fancier version:

#!/usr/bin/env cabal
{- cabal:
build-depends: base, monoid-extras, semigroupoids
-}

module EndoKleisli where

import Control.Arrow
import Data.Functor.Bind
import Data.Monoid.Endomorphism
import Data.Semigroup

bar :: Bind m => (a -> m a) -> Int -> a -> m a
bar f n = runKleisli (getEndomorphism (stimes n (Endomorphism (Kleisli f))))
4 Likes

I see, you’re right. I should have checked first that it was actually inefficient in this context. I’m not used to just writing code that says to make a list and assume it’ll be optimized to just optimize away the list as needed, but, since Haskell is lazy, I’ve heard it said that lists serve more as control flow data structures sometimes than literal data structures. I guess it’s something to get used to. Thanks for the alternative code, which looks interesting. I haven’t used arrows ever before.

1 Like

Watch out, stimes on Endomorphism is the default Semigroup stimes, which doesn’t support 0 the way the specialized stimes on Endo does.

You can easily replace replicate n undefined by replicate n ().

I have done that in https://play.haskell.org/saved/lwC3lLN. It can show the Core code (click the Core button), even assembly. But TLDR as rhendric pointed out, the code is compiled to a “for i=n downto 0” loop. The only lists are due to getLine and read. The moral is to fact-check rather than armchair-opine.

I can understand if you dislike this coding style. I am sure somewhere on hackage there are already do-n-times functions. But you should not dismiss the idiom of expressing for-loops as lazy lists. I always tell students: Linked lists are a terrible data structure (any language), but in Haskell they become an excellent control structure.

3 Likes

From the perspective of structural recursion schemes, the function you seem to be looking for is the fold (catamorphism) of the natural number type.

foldNat :: a -> (a -> a) -> Int -> a
foldNat z s 0 = z
foldNat z s n = s (foldNat z s (n - 1))

Using that function you can write runningSum as follows:

runningSum :: Int -> IO Int
runningSum n = foldNat (pure 0) (>>= helper) n
  where
    helper sum = do
        result <- read <$> getLine
        let sum' = sum + result
        putStr "Running sum: "; print sum'
        return sum'

You could lift this construction to kleisli categories:

foldNat :: Monad m => m a -> (a -> m a) -> Int -> m a
foldNat z s 0 = z
foldNat z s n = s =<< foldNat z s (n - 1)

But that only saves you from writing one bind (and I don’t know what kind of effect it has on performance).

3 Likes

Non recursive on helper and no lists? I got you.

fixedSum :: Int -> IO Int
fixedSum = fix helper 0
    where
        helper h sum n
            | n <= 0    = return sum
            | otherwise = do result <- read <$> getLine
                             let sum' = sum + result
                             putStr "Running sum: "; print sum'
                             h sum' (n - 1)
1 Like

Using fix is cheating :grinning_face_with_smiling_eyes:

I think your foldr (>=>) pure is covered by concatM in Control.Monad.Loops: Control.Monad.Loops. It’s a cool function I wasn’t thinking of though, thanks for it! (Edit: Wait, not sure if that’s “Base” though. I’m on my phone now and so can’t check. But probably not.)

Also, thank you @jaror for explaining to me that I was really thinking of a catamorphism.

Control.Monad.Loops is not in base. It would be the (or one of) loop library on hackage I casually mentioned last time.

I have never used them. Even in shell scripts, I would be like for i in $(seq 0 999) and call it a day. Hot take: “It reads like math, therefore it is easy to debug”. :ghost:

1 Like

By the way, I don’t think anyone in this thread addressed this point, but list fusion should theoretically completely remove the lists for you in this case.

However, from what I can see it seems that is not actually happening. I’ll have to investigate more.

Edit: Fusion does work if you use Data.Foldable.foldlM instead of Control.Monad.foldM. That would be a bug. I have opened #25012: Control.Monad.foldM is not a good consumer (but Data.Foldable.foldlM is) · Issues · Glasgow Haskell Compiler / GHC · GitLab

9 Likes

It also turns out that runningSum n = foldl' (>>=) (pure 0) (replicate n helper) and foldr (=<<) (pure 0) (replicate n helper) also seem to be equivalent to your version, foldr (>=>) pure (replicate n helper) 0. I thought of a very similar function while trying to do something unrelated, and then remembered this post, realizing it was also a potential solution to this old problem.

Also, sorry if commenting on a post 20 days old is frowned upon; I don’t know if it is, here.

4 Likes

I do it regularly and nobody frowned at me so far. As far as I know.

Personally I like that some threads are long-lived and can be updated, for example with a relevant new solution to the original problem. (Not the case with this reply, I know.) It brings the platform closer to StackOverflow (in good ways) than to Reddit, where you might as well not bother to reply if you’re a day late.

1 Like