Search code examples
haskellmonadstraversalfree-monad

Printing the free monad


One can translate a free monad to any other monad, but given a value of type Free f x, I want to print the whole tree, not map every node of the AST generated to some other node in another monad.

Gabriel Gonzales uses the value directly

showProgram :: (Show a, Show r) => Free (Toy a) r -> String
showProgram (Free (Output a x)) =
    "output " ++ show a ++ "\n" ++ showProgram x
showProgram (Free (Bell x)) =
    "bell\n" ++ showProgram x
showProgram (Free Done) =
    "done\n"
showProgram (Pure r) =
    "return " ++ show r ++ "\n"

which can be abstracted away as

showF :: (x -> b) -> ((Free f x -> b) -> f (Free f x) -> b) ->  Free f x -> b
showF backLiftValue backLiftF  = fix (showFU backLiftValue backLiftF)
    where
      showFU :: (x -> b) -> ((Free f x -> b) -> f (Free f x) -> b) -> (Free f x -> b) -> Free f x -> b
      showFU backLiftValue backLiftF next = go . runIdentity . runFreeT where
          go (FreeF c ) = backLiftF next  c
          go (Pure x) =   backLiftValue x 

which is easy to call if we have a polymorphic function like (using Choice x = Choice x x as a functor)

showChoice :: forall x. (x -> String) ->  Choice x -> String
showChoice show (Choice a b) =  "Choice (" ++ show  a ++  "," ++ show b ++ ")"

But that seems quite complicated for a simple operation... What other approaches are there to go from f x -> b to Free f x -> b ?


Solution

  • Use iter and fmap:

    {-# LANGUAGE DeriveFunctor #-}
    
    import Control.Monad.Free
    
    data Choice x = Choice x x deriving (Functor)
    
    -- iter :: Functor f => (f a -> a) -> Free f a -> a
    -- iter _   (Pure a) = a
    -- iter phi (Free m) = phi (iter phi <$> m)
    
    showFreeChoice :: Show a => Free Choice a -> String
    showFreeChoice =
          iter (\(Choice l r) -> "(Choice " ++ l ++ " " ++ r ++ ")")
        . fmap (\a -> "(Pure " ++ show a ++ ")")
    

    fmap converts from Free f a to Free f b, and iter does the rest. You could factor this out, and maybe get a bit better performance:

    iter' :: Functor f => (f b -> b) -> (a -> b) -> Free f a -> b
    iter' f g = go where
      go (Pure a)  = g a
      go (Free fa) = f (go <$> fa)