Welcome to OGeek Q&A Community for programmer and developer-Open, Learning and Share
Welcome To Ask or Share your Answers For Others

Categories

0 votes
605 views
in Technique[技术] by (71.8m points)

haskell - Combining Free types

I've been recently teaching myself about the Free monad from the free package, but I've come across a problem with it. I would like to have different free monads for different libraries, essentially I would like to build DSLs for different contexts, but I would also like to be able to combine them together. As an example:

{-# LANGUAGE DeriveFunctor #-}
module TestingFree where

import Control.Monad.Free

data BellsF x
    = Ring x
    | Chime x
    deriving (Functor, Show)

type Bells = Free BellsF

data WhistlesF x
    = PeaWhistle x
    | SteamWhistle x
    deriving (Functor, Show)

type Whistles = Free WhistlesF

ring :: Bells ()
ring = liftF $ Ring ()

chime :: Bells ()
chime = liftF $ Chime ()

peaWhistle :: Whistles ()
peaWhistle = liftF $ PeaWhistle ()

steamWhistle :: Whistles ()
steamWhistle = liftF $ SteamWhistle ()


playBells :: Bells r -> IO r
playBells (Pure r)         = return r
playBells (Free (Ring x))  = putStrLn "RingRing!" >> playBells x
playBells (Free (Chime x)) = putStr "Ding-dong!" >> playBells x

playWhistles :: Whistles () -> IO ()
playWhistles (Pure _)                = return ()
playWhistles (Free (PeaWhistle x))   = putStrLn "Preeeet!" >> playWhistles x
playWhistles (Free (SteamWhistle x)) = putStrLn "Choo-choo!" >> playWhistles x

Now, I would like to be able to create a type BellsAndWhistles that allows me to combine the functionality of both Bells and Whistles without much effort.

Since the problem is combining monads, my first thought was to look at the Control.Monad.Trans.Free module for a quick and easy solution. Unfortunately, there are sparse examples and none showing what I want to do. Also, it seems that stacking two or more free monads doesn't work, since MonadFree has a functional dependency of m -> f. Essentially, I'd like the ability to write code like:

newtype BellsAndWhistles m a = BellsAndWhistles
    { unBellsAndWhistles :: ???
    } deriving
        ( Functor
        , Monad
        -- Whatever else needed
        )

noisy :: Monad m => BellsAndWhistles m ()
noisy = do
    lift ring
    lift peaWhistle
    lift chime
    lift steamWhistle

play :: BellsAndWhistles IO () -> IO ()
play bellsNwhistles = undefined

But in such a way that Bells and Whistles can exist in separate modules and don't have to know about each others implementations. The idea is that I can write stand alone modules for different tasks, each implementing its own DSL, and then having a way to combine them into a "larger" DSL as needed. Is there an easy way to do this?

As a bonus it'd be great to be able to leverage the different play* functions that are already written, in such a way that I can swap them out. I want to be able to use one free interpreter for debug and another in production, and it'd obviously be useful to be able to choose which DSL was being debugged individually.

See Question&Answers more detail:os

与恶龙缠斗过久,自身亦成为恶龙;凝视深渊过久,深渊将回以凝视…
Welcome To Ask or Share your Answers For Others

1 Reply

0 votes
by (71.8m points)

This is an answer based off of the paper Data types à la carte, except without type classes. I recommend reading that paper.

The trick is that instead of writing interpreters for Bells and Whistles, you define interpreters for their single functor steps, BellsF and WhistlesF, like this:

playBellsF :: BellsF (IO a) -> IO a
playBellsF (Ring  io) = putStrLn "RingRing!"  >> io
playBellsF (Chime io) = putStr   "Ding-dong!" >> io

playWhistlesF :: WhistelsF (IO a) -> IO a
playWhistlesF (PeaWhistle   io) = putStrLn "Preeeet!"   >> io
playWhistlesF (SteamWhistle io) = putStrLn "choo-choo!" >> io

If you choose not to combine them, you can just pass them to Control.Monad.Free.iterM to get back your original play functions:

playBells    :: Bells a    -> IO a
playBells    = iterM playBell

playWhistles :: Whistles a -> IO a
playWhistles = iterM playWhistlesF

... however because they deal with single steps they can be combined more easily. You can define a new combined free monad like this:

data BellsAndWhistlesF a = L (BellsF a) | R (WhistlesF a)

Then turn that into a free monad:

type BellsAndWhistles = Free BellsAndWhistlesF

Then you write an interpreter for a single step of BellsAndWhistlesF in terms of the two sub-interpreters:

playBellsAndWhistlesF :: BellsAndWhistlesF (IO a) -> IO a
playBellsAndWhistlesF (L bs) = playBellsF    bs
playBellsAndWhistlesF (R ws) = playWhistlesF ws

... and then you get the interpreter for the free monad by just passing that to iterM:

playBellsAndWhistles :: BellsAndWhistles a -> IO a
playBellsAndWhistles = iterM playBellsAndWhistlesF

So the answer to your question is that the trick to combining free monads is to preserve more information by defining intermediate interpreters for individual functor steps ("algebras"). These "algebras" are much more amenable to combination than interpreters for free monads.


与恶龙缠斗过久,自身亦成为恶龙;凝视深渊过久,深渊将回以凝视…
OGeek|极客中国-欢迎来到极客的世界,一个免费开放的程序员编程交流平台!开放,进步,分享!让技术改变生活,让极客改变未来! Welcome to OGeek Q&A Community for programmer and developer-Open, Learning and Share
Click Here to Ask a Question

...