5

Is there a name for a recursion scheme that's like a catamorphism, but that allows peeking at the final result while it's still running? Here's a slighly contrived example:

toPercents :: Floating a => [a] -> [a]
toPercents xs = result
  where
  (total, result) = foldr go (0, []) xs
  go x ~(t, r) = (x + t, 100*x/total:r)

{-
>>> toPercents [1,2,3]
[16.666666666666668,33.333333333333336,50.0]
-}

This example uses total at each step of the fold, even though its value isn't known until the end. (Obviously, this relies on laziness to work.)

3 Answers3

3

Though this is not necessarily what you were looking for, we can encode the laziness trick with a hylomorphism:

{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TemplateHaskell #-}

import Data.Functor.Foldable
import Data.Functor.Foldable.TH

data CappedList c a = Cap c | CCons a (CappedList c a)
    deriving (Eq, Show, Ord, Functor, Foldable, Traversable)
makeBaseFunctor ''CappedList

-- The seq here has no counterpart in the implementation in the question.
-- It improves performance quite noticeably. Other seqs might be added for
-- some of the other "s", as well as for the percentage; the returns, however,
-- are diminishing.
toPercents :: Floating a => [a] -> [a]
toPercents = snd . hylo percAlg sumCal . (0,)
    where
    sumCal = \case
        (s, []) -> CapF s
        (s, a : as) -> s `seq` CConsF a (s + a, as)
    percAlg = \case
        CapF s -> (s, [])
        CConsF a (s, as) -> (s, (a * 100 / s) : as)

This corresponds to the laziness trick because, thanks to hylo fusion, the intermediate CappedList never actually gets built, and toPercents consumes the input list in a single pass. The point of using CappedList is, as moonGoose puts it, placing the sum at the bottom of the (virtual) intermediate structure, so that the list rebuilding being done with percAlg can have access to it from the start.

(It is perhaps worth noting that, even though it is done in a single pass, it seems difficult to get nice-and-constant memory usage from this trick, be it with my version or with yours. Suggestions on this front are welcome.)

duplode
  • 33,731
  • 7
  • 79
  • 150
  • My intuition is that you can't get constant memory use + single pass; roughly, constant memory use => you can emit the list element-by-element => you already know the total => you must have already looked at all the later elements. Is the aim of your answer to demonstrate how to do this without laziness? If so, why not just foldr/cata into an `(listF,total) :: (a -> [a],a)` pair and `uncurry ($)` it? – moonGoose May 15 '19 at 15:51
  • @moonGoose (1) I feel your intuition is right, indeed. (2) I might be wrong about this, but I think this implementation relies on laziness in a similar way to the OP's: the hylomorphism is done in a single pass, and the percentages emitted by `percAlg` depend on the cap of the (virtual) intermediate list. – duplode May 15 '19 at 22:05
  • (2) (In the nicest possible way) So what is the advantage of your implementation over a straightforward `foldr` to catamorphism translation? I suppose it does let you split up the `sum` from the `map`. It's worth observing that this only works because one of the catamorphisms (essentially `map (/total)`) you have reexpressed as an anamorphism, which is possible in the example given but not in general. – moonGoose May 15 '19 at 22:42
  • @moonGoose Arguable advantages include splitting up sum and map, as well as not having to functionalize the algebra. On the anamorphism, while I see your point, if something is expressible through multiple recursion schemes I feel it is fair game to take advantage of that. (Also, the anamorphic part of the hylomorphism here is the sum one, rather than the map one.) – duplode May 15 '19 at 23:23
  • 1
    Ah good points. I see now that the `CapF` trick has essentially let you express a cata as an ana which just puts the cata result at the bottom of the structure, thus the other cata has access to it from the start. Now I'm wondering about generalizing Capped over other structures such that you could use this trick for any cata pair. – moonGoose May 15 '19 at 23:51
  • @moonGoose That's a neat summary; I'm borrowing it for the answer :) The trick is especially nice when, unlike here, you can avoid roping that result up from the depths (a nice simple example is `span`). – duplode May 16 '19 at 00:25
2

I don't think there's explicitly a scheme for allowing function 1 to peek at each step at the end result of function 2. It seems like a somewhat odd one to want though. I think that in the end, it's going to boil down to either 1) running function 2, then running function 1 with the known result of function 2 (ie. two passes, which I think is the only way to get constant memory in your example) or 2) running them side-by-side, creating a function thunk (or relying on laziness) to combine them at the end.

The lazy foldr version you gave of course translates naturally into a catamorphism. Here's the functionalized catamorphism version,

{-# LANGUAGE LambdaCase #-}

import Data.Functor.Foldable    

toPercents :: Floating a => [a] -> [a]
toPercents = uncurry ($) . cata alg
  where
    alg = \case
        Nil -> (const [], 0)
        Cons x (f,s) ->  (\t -> 100*x / t : f t, s + x)

It doesn't seem nice stylistically to have to hand-parallelize the two catamorphisms though, particularly as then it doesn't encode the fact that neither stepwise-relies on the other. Hoogle finds bicotraverse, but it's unnecessarily general, so let's write our algebra-parallelization operator (&&&&),

import Control.Arrow

(&&&&) :: Functor f => (f a -> c) -> (f b -> d) -> f (a,b) -> (c,d)
f1 &&&& f2 = (f1 . fmap fst &&& f2 . fmap snd)

toPercents' :: Floating a => [a] -> [a]
toPercents' = uncurry ($) . cata (algList &&&& algSum)

algSum :: (Num a) => ListF a a -> a
algSum = \case
    Nil -> fromInteger 0
    Cons x !s -> s + x

algList :: (Fractional a) => ListF a (a -> [a]) -> (a -> [a])   
algList = \case
    Nil -> const []
    Cons x s -> (\t -> 100*x / t : s t) 
duplode
  • 33,731
  • 7
  • 79
  • 150
moonGoose
  • 1,510
  • 6
  • 14
0

Just crazy experiment. I think we can fuse smth.

Also fix = hylo (\(Cons f a) -> f a) (join Cons) and we can replace on fix

toPercents :: Floating a => [a] -> [a]
toPercents xs = result
  where
    (_, result) = hylo (\(Cons f a) -> f a) (join Cons) $ \(~(total, _)) -> 
      let
        alg Nil = (0, [])
        alg (Cons x (a, as)) = (x + a, 100 * x / total: as)
      in
        cata alg xs
xgrommx
  • 461
  • 3
  • 15