Skip to content

Foldr and Foldl in Haskell

This blog introduces how foldr and foldl work for a better usage them. Understanding the accumulation and association support from them is crucial.

foldr: Right-associative fold of a structure, lazy in the accumulator.

foldl: Left-associative fold of a structure, lazy in the accumulator.

In short, it helps you to construct a left/right associative structure. One of the real cases is you want to construct a left associative structure inside a parser , but you parse it in a right recursive way.

Note that this is a simple note, which has been already covered by documentation, and I wrote it because at the beginning I misunderstand its feature, so I wrote some code to try.

Signature

The signature of foldr and foldl are listed below, they are listed below.

foldl :: (b -> a -> b) -> b -> t a -> b
foldr :: (a -> b -> b) -> b -> t a -> b

Two points are noteworthy:

  • the function to calculate a new accumulation with a value
  • the direction during folding execution

Accumulation and Folded Value

The f here represents the logic of how could we calculate the accumulation and a new value(new refers to the next value in t a) to emit a new accumulation and pass to the next turn of folding.

The b->a->b in foldl, which the first b is the accumulation while second a is the new value, you can memorize this easily due to we are folding t a.

The a->b->b in foldr, however, flips the arguments. The first value becomes to the new value, and the second is the accumulation.

Direction During Folding

The directions of foldr and foldl are different. In short, foldr from the right and foldl starts from the left.

The Foldable docs provides a vivid diagram about the work flow, which helps to understand them.

foldr, when applied to a binary operator, a starting value (typically the right-identity of the operator), and a list, reduces the list using the binary operator, from right to left:

foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)

foldl, when applied to a binary operator, a starting value (typically the left-identity of the operator), and a list, reduces the list using the binary operator, from left to right:

foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn

The formula shows the final result of foldr|foldl, and the document state the direction. We can use trace function to make the folding execution direction visually.

module Main where

import Debug.Trace (trace)

main :: IO ()
main = do
  print $
    foldl
      ( \acc v ->
          trace
            ("value: " ++ [v] ++ "; acculate: " ++ acc)
            v
            : acc
      )
      "_"
      "abcde"
  print $
    foldr
      ( \v acc ->
          trace
            ("value: " ++ [v] ++ "; acculate: " ++ acc)
            v
            : acc
      )
      "_"
      "abcde"

The strings printed are listed below, which demonstrate the foldl starts at the left of list and foldr starts on the right side.

value: a; acculate: _
value: b; acculate: a_
value: c; acculate: ba_
value: d; acculate: cba_
value: e; acculate: dcba_
"edcba_"
value: e; acculate: _
value: d; acculate: e_
value: c; acculate: de_
value: b; acculate: cde_
value: a; acculate: bcde_
"abcde_"

Use foldl to Construct Left Associative Structure

In real practice, after parsing an expression such as true && false || true, we may want the structure to hold this expression left associative. For example, we may want the following structure as the logical operator is left associative.

  Exprv
    { leftOperand =
        Expr
          Exprv
            { leftOperand = ExprL (LBool True),
              rightOperand = ExprL (LBool False),
              operator = LogicalAnd
            },
      rightOperand = ExprL (LBool True),
      operator = LogicalOr
    }

However, during parsing, we right recursively parse the expression, which will lead the output performs a right associative like the code snippet below. That's totally not our intention.

  Exprv
    { leftOperand =  ExprL (LBool True),
      rightOperand = 
        Expr
          Exprv
            { leftOperand = ExprL (LBool True),
              rightOperand = ExprL (LBool False),
              operator = LogicalOr
            },
      operator = LogicalAnd 
    }

This is actually caused by the parsing logic like this:

pExpression :: Parser SExpression
pExpression = do
  left <- pTerm
  maybeOp <- pOpt pOperator
  case maybeOp of
    Nothing -> return left
    Just op -> do
      maybeRight <- pOpt pExpression
      case maybeRight of
        Nothing -> throwError "missing a right operand"
        Just right ->
          return $
            Expr $
              Exprv
                { leftOperand = left,
                  rightOperand = right,
                  operator = op
                }

To solve this problem, we need to parse and store the results first, and then using foldl to construct the final expression structure. By using pMany to parse the result into a list and then foldl, we can left associatively construct the structure.

pExpression :: Parser SExpression
pExpression = do
  left <- pTerm
  rest <- pMany (pManySpaces >> ((,) <$> pAddOp <*> pTerm))
  return $ foldl (\acc (op, right) -> Expr $ Exprv acc right op) left rest

Construct Left/Right Associative Instance of Sumtype

data L = L{
  left :: T,
  right :: T
} deriving Show

data T = N Int | LL L | N' Int
  deriving Show 

main :: IO ()
main = do
  print $ foldl (\acc r -> LL $ L { left=acc, right = r}) (N' 0) $ fmap N [1,2,3,4]
  print $ foldr ((\v acc -> LL $ L { left=v, right = acc}) . N) (N' 0) [1,2,3,4]

The output structures looks like this, and here you could see the differences clearly due to the different functionality between foldr and foldl.

LL
  ( L
      { left = LL (L {left = N' 0, right = N 1}),
        right = N 2
      }
  )
LL
  ( L
      { left = N 1,
        right = LL (L {left = N 2, right = N' 0})
      }
  )