3

I came across a nice post on SO by @amalloy while looking for hylomorhism examples, that illustrate recursion scheme (RS) usage with useful discussion and full implementation:

{-# LANGUAGE DeriveFunctor #-}
import Control.Arrow ( (>>>), (<<<) )

newtype Term f = In {out :: f (Term f)}

type Algebra f a = f a -> a
type Coalgebra f a = a -> f a

cata :: (Functor f) => Algebra f a -> Term f -> a
cata fn = out >>> fmap (cata fn) >>> fn

ana :: (Functor f) => Coalgebra f a -> a -> Term f
ana f = In <<< fmap (ana f) <<< f

hylo :: Functor f => Algebra f b -> Coalgebra f a -> a -> b
hylo alg coalg = ana coalg >>> cata alg

data ChangePuzzle a = Solved Cent
                    | Pending {spend, forget :: a}
                    deriving Functor

type Cent = Int
type ChangePuzzleArgs = ([Cent], Cent)
coins :: [Cent]
coins = [50, 25, 10, 5, 1]

divide :: Coalgebra ChangePuzzle ChangePuzzleArgs
divide (_, 0) = Solved 1
divide ([], _) = Solved 0
divide (coins@(x:xs), n) | n < 0 = Solved 0
                         | otherwise = Pending (coins, n - x) (xs, n)

conquer :: Algebra ChangePuzzle Cent
conquer (Solved n) = n
conquer (Pending a b) = a + b

waysToMakeChange :: ChangePuzzleArgs -> Int
waysToMakeChange = hylo conquer divide

The code works as expected. Despite having some vague intuition for the RS aspect already, I am still wondering:

  1. since this is about counting combinations, why Solved Cent and not Solved Int? (This may sound like a nitpic, if it is even a reasonable question, but I am hoping it may be the root of the rest of the uncertainty, below, although I suspect I missed something more fundamental!).
  2. since we're later summing, in divide, Solved 0/1 presumably signifies failure/success?
  3. in conquer, what does it mean to add, a and b, of Pending? What do those 2 values (as Cents) signify, and what would their sum mean in this context?
  4. in conquer, I would have expected we just need to sum the Solveds, and the author touches on this, but it's not clear, yet, how the Pending case is contributing (eg fixing conquer (Pending a b) = 11 does have an adverse impact on functionality, and it is probably a clue that waysToMakeChange returns 11, or whatever constant that case is fixed to).
  5. in conquer, a and b are Cents, whereas in divide they're ChangePuzzleArgs (aka ([Cent], Cent)) - where does that transformation occur?

Note: being new to SO, I was not able to comment below the original answer, which may have been more appropriate, but I hope this is also useful as is.

duplode
  • 33,731
  • 7
  • 79
  • 150
maplike
  • 31
  • 4

1 Answers1

2
  1. since this is about counting combinations, why Solved Cent and not Solved Int? (This may sound like a nitpic, if it is even a reasonable question, but I am hoping it may be the root of the rest of the uncertainty, below, although I suspect I missed something more fundamental!).

I would also use Int here.

  1. since we're later summing, in divide, Solved 0/1 presumably signifies failure/success?

Yes, but it's slightly more than that. Solved 0 means "there are exactly 0 ways to generate that change amount" (i.e., failure), while Solved 1 means "there is exactly 1 way to generate that change amount" (i.e., success). In the latter case, not only we mean "success", but we also report that there is only one way to solve the task.

  1. in conquer, what does it mean to add, a and b, of Pending? What do those 2 values (as Cents) signify, and what would their sum mean in this context?

Essentially, Pending a b with a,b::Int means "the number of ways to generate that change amount can be split into two disjoint sets, the first one having a elements, and the second one having b elements".

When we divide, we return Pending ... ... to split the problem into two disjoint subcases, (coins, n - x) and (xs, n). Here coins=(x:xs). We split according to whether we want to use coin x at least one time (hence we need to generate n-x with all the coins), or we don't want to use it at all (hence we need to generate n with the other coins, only).

  1. in conquer, I would have expected we just need to sum the Solveds, and the author touches on this, but it's not clear, yet, how the Pending case is contributing (eg fixing conquer (Pending a b) = 11 does have an adverse impact on functionality, and it is probably a clue that waysToMakeChange returns 11, or whatever constant that case is fixed to).

Summing all the Solved ... is what we do. The cata magic essentially replaces the straightforward recursive sum

foo (Solved n) = n
foo (Pending case1 case2) = foo case1 + foo case2

with cata conquer where

conquer (Solved n) = n
conquer (Pending a b) = a + b

The magic of cata makes it so that inside Pending, we do not find subtrees upon which we want to recurse, but the result of the recursion, already computed.

  1. in conquer, a and b are Cents, whereas in divide they're ChangePuzzleArgs (aka ([Cent], Cent)) - where does that transformation occur?

This can be indeed subtle at first. I'll provide only a rough intuition.

After ana divide we produce a result in a fixed point of the functor ChangePuzzle. Note how ana at the end returns Term ChangePuzzle, which is the fixed point. There, the pair ([Cent], Cent) magically disappears.

Dually, the Int reappears when we use cata, even if we started from Term ChangePuzzle.

Very roughly, you can think of Term ChangePuzzle as the infinite nesting

ChangePuzzle (ChangePuzzle (ChangePuzzle ( ....

which is coherent with the fact that such a tree might be arbitrarily nested. There, the "argument" of ChangePuzzle essentially disappears.

How do we get the final Int then? Well, we get that since Solved always takes an Int argument, and not an a argument. This provides that base case that makes the final cata recursion work.

amalloy
  • 89,153
  • 8
  • 140
  • 205
chi
  • 111,837
  • 3
  • 133
  • 218
  • 1
    Agreed. I've replaced Cent with Int in the linked answer. – amalloy Dec 13 '21 at 18:23
  • @chi - thanks for confirming and the explanations! And to @amolloy for the example that got me thinking about this, and the fixes (no pun intended!). Those changes from `Cent` to `Int` (@ `Solved` and `conquer`), as I suspected also facilitate understanding. So, I will look at this again and come back if I have any follow-on/related doubts, now that I can write comments, before I *choose* the accepted answer! – maplike Dec 14 '21 at 01:57