A recursion scheme from Int -> Int?

348 views Asked by At

The foldr identity is

foldr (:) []

More generally, with folds you can either destroy structure and end up with a summary value or inject structure in such a way that you end up with the same output structure.

[Int] -> [Int] or [Int] -> Int or [Int] -> ?

I'm wondering if there a similar identity with unfoldr/l.

I know how to get

Int -> [Int]

with unfold/ana.

I'm looking for some kind of way to go from

Int -> Int

with a recursion scheme.

2

There are 2 answers

0
duplode On BEST ANSWER

Taking a cue from your remark about factorials, we can note that natural numbers can be treated as a recursive data structure:

data Nat = Zero | Succ Nat

In terms of the recursion-schemes machinery, the corresponding base functor would be:

data NatF a = ZeroF | SuccF a
    deriving (Functor)

NatF, however, is isomorphic to Maybe. That being so, recursion-schemes conveniently makes Maybe the base functor of the Natural type from base. For instance, here is the type of ana specialised to Natural:

ana @Natural :: (a -> Maybe a) -> a -> Natural

We can use it to write the identity unfold for Natural:

{-# LANGUAGE LambdaCase #-}

import Numeric.Natural
import Data.Functor.Foldable

idNatAna :: Natural -> Natural
idNatAna = ana $ \case
    0 -> Nothing
    x -> Just (x - 1)

The coalgebra we just gave to ana is project for Natural, project being the function that unwraps one layer of the recursive structure. In terms of the recursion-schemes vocabulary, ana project is the identity unfold, and cata embed is the identity fold. (In particular, project for lists is uncons from Data.List, except that it is encoded with ListF instead of Maybe.)

By the way, the factorial function can be expressed as a paramorphism on naturals (as pointed out in the note at the end of this question). We can also implement that in terms of recursion-schemes:

fact :: Natural -> Natural
fact = para $ \case
    Nothing -> 1
    Just (predec, prod) -> prod * (predec + 1)

para makes available, at each recursive step, the rest of the structure to be folded (if we were folding a list, that would be its tail). In this case, I have called the value thus provided predec because at the n-th recursive step from bottom to top predec is n - 1.

Note that user11228628's hylomorphism is probably a more efficient implementation, if you happen to care about that. (I haven't benchmarked them, though.)

0
user11228628 On

The kind of recursion scheme that deals with building up an intermediate structure and tearing it down, so that the structure doesn't appear in the input or output, is a hylomorphism, spelled hylo in recursion-schemes.

To use a hylomorphism, you need to specify an algebra (something that consumes one step of a recursive structure) and a coalgebra (something that produces one step of a recursive structure), and you need to have a data type for the kind of structure you're using, of course.

You suggested factorial, so let's look into how to write that as a hylomorphism.

One way to look at factorial is as the product of a list of numbers counting down from the initial n. In this framing, we can think of the product as our algebra, tearing down the list one cons at a time, and the count-down as our coalgebra, building up the list as n is decremented.

recursion-schemes gives us ListF as a handy base functor for lists, so we'll use that as the data type produced by the coalgebra and consumed by the algebra. Its constructors are Nil and Cons, which of course resemble the constructors for full lists, except that a ListF, like any base structure in a recursion scheme, uses a type parameter in the place that lists would use actual recursion (meaning that Cons :: a -> b -> ListF a b instead of (:) :: a -> [a] -> [a]).

So that determines our types. Now defining fact is a rather fill-in-the-blanks exercise:

import Prelude hiding (product)
import Data.Functor.Foldable

product :: ListF Int Int -> Int
product Nil = 1
product (Cons a b) = a * b

countDown :: Int -> ListF Int Int
countDown 0 = Nil
countDown n = Cons n (n - 1)

fact :: Int -> Int
fact = hylo product countDown