5

I am not sure how to derive the functor instance after making a fixed point :

data FreeF f a next  = PureF a | FreeF (f next)  deriving (Functor)

data Mu f  = In { out :: f ( Mu f ) }

newtype Free f a = Free(  Mu (FreeF f a)  )

instance Functor f => Functor (Free f) where
     fmap h (Free (out -> PureF a))  = Free (In (PureF (h a)))
     fmap h (Free (out -> FreeF fn)) = Free (In (fmap undefined undefined)) --stuck

If I modify Mu to accept an extra type parameter, I can progress until... :

data Mu f a  = In { out :: f ( Mu f a )  } deriving (Functor)

newtype Free f a = Free(  Mu (FreeF f a) a )

instance Functor f => Functor (Free f ) where
     fmap h (Free (out -> PureF a))  = Free . In . PureF $ h a
     fmap h (Free (out -> FreeF fn)) = Free . In . FreeF $ fmap undefined fn 

Here I need to have undefined :: Mu (FreeF f a) a -> Mu (FreeF f b) b but mu f is a functor for the same f and here it varies in type.

What is the correct way to tackle this ?

nicolas
  • 8,208
  • 3
  • 32
  • 69

2 Answers2

4

mu f is a functor for the same f and here it varies in type.

Fortunately we're defining Functor (Free f), and we actually use this Functor instance to map over the a's in the PureF constructors. Functor (Free f) abstracts over all "internal" occurrences of a.

So, whenever we want to map over both occurrences of a, for example when we want to implement FreeF f a (Mu (FreeF f a)) -> FreeF f b (Mu (FreeF f b)), we can do that by wrapping everything up all the way back to Free, mapping, then unwrapping again.

The following checks out with your original data definitions:

newtype Free f a = Free {unFree :: Mu (FreeF f a)} -- add "unFree"

instance Functor f => Functor (Free f) where
     fmap h (Free (In (PureF a)))  = Free (In (PureF (h a)))
     fmap h (Free (In (FreeF fn))) =
       Free (In (FreeF (fmap (unFree . fmap h . Free) fn)))

Some testing:

{-# LANGUAGE UndecidableInstances, StandaloneDeriving #-}

deriving instance Show (f (Mu f)) => Show (Mu f)
deriving instance Show (Mu (FreeF f a)) => Show (Free f a)       

foo :: Free [] Int
foo = Free $ In $ FreeF [ In $ PureF 100, In $ PureF 200 ]

> fmap (+100) foo
Free {unFree = In {out = FreeF [In {out = PureF 200},In {out = PureF 300}]}}
András Kovács
  • 29,038
  • 3
  • 45
  • 94
3

I haven't done this construction before, but I think I'm seeing something. Your intuition about adding an argument to Mu is good, but you need to pass it along so that Free f fits, i.e. so that f takes two arguments instead of one:

newtype Mu f a = In { out :: f (Mu f a) a }

Mu f ought to be a Functor under suitable conditions, which would give you the instance you're looking for. What are those conditions? We need:

fmap' :: (a -> b) -> f (Mu f a) a -> f (Mu f b) b

We expect f to be functorial in its second argument, so that's no problem. So what we really need a way to get

f (Mu f a) b -> f (Mu f b) b
           ^               ^
           +--not varying--+

We can use the instance recursively to get Mu f a -> Mu f b, so it looks like we just need f to be a functor in its first argument too. Hence:

class Bifunctor f where
    bimap :: (a -> c) -> (b -> d) -> f a b -> f c d

Then you should be able to write the suitable instances

instance (Functor f) => Bifunctor (FreeF f) ...
instance (Bifunctor f) => Functor (Mu f) ...
luqui
  • 57,324
  • 7
  • 134
  • 191