3

I am learning recursion schemes and it has proven very helpful to me to implement them specific to the list type. However, I got stuck on apomorphisms.

Here is an implementation of tails in terms of apo I recently found:

import Data.Functor.Foldable

tailsApo :: [a] -> [[a]]
tailsApo = apo coalgTails
    where
    coalgTails = \case
        [] -> Cons [] (Left [])
        li@(_:xs) -> Cons li (Right xs)

Unfortunately, I couldn't import Data.Functor.Foldable with GHCi, because I get a package not found error. Another search revealed this implemenation of apo specific to lists:

apoList :: ([b] -> Maybe (a, Either [b] [a])) -> [b] -> [a]
apoList f b = case f b of
    Nothing -> []
    Just (x, Left c)  -> x : apoL f c
    Just (x, Right e) -> x : e

Obviously, apoList's first argument doesn't match with tailsApo. I'd expext the type to be something like apoList :: ([b] -> Either (a, b) [a])) -> [b] -> [a].

There seems to be no more beginner friendly information on this subject. I appreciate any help.

duplode
  • 31,361
  • 7
  • 69
  • 130
scriptum
  • 3,839
  • 1
  • 12
  • 26

2 Answers2

2

The type is

apo :: (a ->           Base t   (Either t  a  ))      -- g :: a -> Base t r
    ->  a -> t 

apo  g  a =  rec a  where                             -- rec = apo g :: a -> t
             rec = embed . fmap (either id rec) . g  
{-
type family                           Base t :: * -> * 
embed                ::               Base t    t -> t
fmap (either id rec) :: Base t   r -> Base t    t
      either id rec  ::          r ->           t            r ~ Either t a
          g :: a ->     Base t   r                           r ~ Either t a
rec = apo g :: a ->                                  t
-}

Here a is the seed. For t ~ [b] we'll have

type instance Base [b] = ListF b
data                     ListF b r = Nil | Cons b r

Base t (Either t a) ~    ListF b (Either [b] a) 
                    ~                Maybe     (b, Either [b] a)

so overall it'll be

apoList :: (a -> Maybe (b, Either [b] a)) -> a -> [b] 
apoList coalg a = case coalg a of
   Nothing           -> []  -- (embed  Nil       )                       -- either
   Just (b, Left bs) -> b : bs   -- no more seed, no more steps to do!   --   id    $ bs
   Just (b, Right a) -> b : apoList coalg a  -- new seed, go on!         --   apo g $ a
                     -- ^^^^^  (embed (Cons b bs))

so

apoTails :: [a] -> [[a]]      -- [[a]] ~ [b], b ~ [a]
apoTails = apoList tailsCoalg
  where
  -- tailsCoalg :: [a] -> Maybe ([a], Either [[a]] [a])
  tailsCoalg []       = Just ([], Left [])
  tailsCoalg s@(_:xs) = Just (s, Right xs)

edit: a simpler apoList with a simpler typed coalgebra,

apoListE :: (a -> Either [b] (b, a)) -> a -> [b] 
apoListE coalg a = case coalg a of
   Left bs      -> bs             -- final tail, whether empty or non-empty 
   Right (b, a) -> b : apoListE coalg a     -- new element and seed, go on!

seems to be easier to use:

apoTailsE :: [a] -> [[a]]
apoTailsE = apoListE tailsCoalgE
  where
  -- tailsCoalgE :: [a] -> Either [[a]] ([a], [a])
  tailsCoalgE []       = Left [[]]
  tailsCoalgE s@(_:xs) = Right (s, xs)

Looks like the two types are equivalent:

type instance Base [b] = ListF b
data                     ListF b r = Nil | Cons b r

Base t (Either t a) ~    ListF b (Either [b] a) 
                    ~                Maybe     (b, Either [b] a)
                    ~                              Either [b] (b, a)
--------------------------------------------------------------------
Maybe (b, Either [b] a)  ~  Either [b] (b, a) 

{ Nothing,               ~  { Left [], 
  Just (b, Left bs),          Left (b:bs), 
  Just (b, Right a)           Right (b, a)
}                           }
Will Ness
  • 62,652
  • 8
  • 86
  • 167
2

Data.Functor.Foldable is provided by the recursion-schemes package. The type of apo there is:

apo :: Corecursive t => (a -> Base t (Either t a)) -> a -> t 

Here, t is the structure being generated by the unfold, and Base t is its base functor. Broadly speaking, the base functor represents one level of the recursive structure, the idea being that if we indefinitely nest it within itself we get a type equivalent to that of the whole structure -- in fact, that is precisely what Fix from Data.Functor.Foldable does. (On a meta note, there doesn't seem to be a Q&A here specifically about Base in recursion-schemes; it could be useful to have one.)

Base for lists is:

data ListF a b = Nil | Cons a b

So apo specialises to:

apo @[_] :: (b -> ListF a (Either [a] b)) -> b -> [a]

If we want to write it without using the recursion-scheme infrastructure, we can use the fact that ListF a b is isomorphic to Maybe (a, b):

Nil     | Cons  a  b
Nothing | Just (a, b)

In terms of Maybe (a, b), the signature would then become:

apoList :: (b -> Maybe (a, Either [a] b)) -> b -> [a]

In the coalgebra (that is, the function argument to apo), Nothing (or Nil, in the recursion-schemes version) signal the generation of the list should be stopped by capping it with an empty tail. That is why you still need Maybe, even if you are also using Either to short-circuit the unfold in other ways.

The implementation of this apoList is pretty much like the one in your question, except that this signature doesn't restrict the seed (of b type) to a list, and flips the roles of Left and Right (so that Left signals short-circuiting):

apoList :: (b -> Maybe (a, Either [a] b)) -> b -> [a]
apoList f b = case f b of
    Nothing -> []
    Just (x, Left e) -> x : e
    Just (x, Right c) -> x : apoList f c
duplode
  • 31,361
  • 7
  • 69
  • 130
  • Very revealing, thank you. I was hoping to get an answer from you, since you are the author of my first code snippet. Actually, I ran across the type definition `(a -> Base t (Either t a)) -> a -> t ` but couldn't get anything out of it because of the `Base` part. – scriptum May 26 '19 at 13:07