[Haskell-cafe] The relationship between F-algebras and the Free Monad

Olaf Klinke olf at aatal-apotheke.de
Mon Aug 15 20:48:14 UTC 2016


Dear Will,

I used to think of the extra parameter "a" in Free f a as the type of 
variables in the terms. So in short, while Fix f gives you the closed 
terms of your AST, Free f a gives you open terms with variables of type a.

Indeed the equations
     Fix f    = f (Fix f)
     Free f a = Pure a | Free (f (Free f a))
are related: Let
     Var a f x = Var a | App (f x)
Then
     Free f a = Fix (Var a f)
Hence the free monad is the fixed point of the functor f where you first 
sneak in free variables of type a. Moreover, given a function from 
variables to closed terms, you can turn an open term to a closed term (see 
below). Your exercise: Implement the below using catamorphisms and so on.

-- Olaf

newtype Fix f = Fix (f (Fix f))
data Free f a = Pure a | Free (f (Free f a))
data Var a f x = Var a | App (f x)

-- tofree.tofix = id
-- tofix.tofree = id
tofree :: Functor f => Free f a -> Fix (Var a f)
tofree (Pure a)  = Fix (Var a)
tofree (Free fx) = Fix (App (fmap tofree fx))

tofix :: Functor f => Fix (Var a f) -> Free f a
tofix (Fix (Var a))  = Pure a
tofix (Fix (App fx)) = Free (fmap tofix fx)

close :: Functor f => (a -> Fix f) -> Free f a -> Fix f
close evaluate (Pure a) = evaluate a
close evaluate (Free fx) = Fix (fmap (close evaluate) fx)




More information about the Haskell-Cafe mailing list