Search code examples
haskelldslfree-monad

Is it possible to implement polymorphic functions in a DSL using Free


I am building a small DSL using Free Monads.

I would like to be able to have polymorphic functions in my DSL.

An example of something I would like to build is this:

{-# LANGUAGE TemplateHaskell #-}

import           Control.Monad.Free.Church

data Queue a = Queue a

data MyDsl next =
  NewQueue (Queue a -> next) |
  WriteToQueue (Queue a) a next

makeFree ''MyDsl

testProgram :: F MyDsl
testProgram = do
  (intQueue :: Queue Int) <- newQueue
  (charQueue :: Queue Char) <- newQueue
  writeToQueue intQueue 1
  writeToQueue charQueue 'c'

The way I have encoded it above I get Not in scope: type variable ‘a’ errors which makes sense. Is there a way to have polymorphic functions in a DSL using Free?

For background the reason I would like to do this is so I can have a production interpreter that uses TQueue behind the scenes and a test interpreter that uses an in memory data structure for testing.


Solution

  • You can represent your DSL with a GADT

    {-# LANGUAGE GADTs #-}
    {-# LANGUAGE StandaloneDeriving #-}
    {-# LANGUAGE DeriveFunctor #-}
    
    data Queue a = Queue a
    
    data MyDsl next where
      NewQueue :: (Queue a -> next) -> MyDsl next
      WriteToQueue :: (Queue a) -> a -> next -> MyDsl next
    
    deriving instance Functor MyDsl
    

    Neither makeFree nor makeFreeCon can generate free polymorphic monadic actions for MyDsl. You will need to write them yourself.

    {-# LANGUAGE FlexibleContexts #-}
    
    import Control.Monad.Free.Class
    
    newQueue :: (MonadFree MyDsl m) => m (Queue a)
    newQueue = wrap $ NewQueue return
    
    writeToQueue :: (MonadFree MyDsl m) => Queue a -> a -> m ()
    writeToQueue q v = liftF $ WriteToQueue q v ()
    

    Now you can write your test program.

    {-# LANGUAGE ScopedTypeVariables #-}
    
    import Control.Monad.Free.Church
    
    -- testProgram can have a more general type
    -- testProgram :: (MonadFree MyDsl m) => m ()
    testProgram :: F MyDsl ()
    testProgram = do
      (intQueue :: Queue Int) <- newQueue
      (charQueue :: Queue Char) <- newQueue
      writeToQueue intQueue 1
      writeToQueue charQueue 'c'
    

    You may find your DSL is easier to write multiple interpreters for if you parameterize the type of a queue. If you do, you'll need a type family or functional dependency to determine the type of the queue from the type of the monad.

    data MyDsl q next where
      NewQueue :: (q a -> next) -> MyDsl next
      WriteToQueue :: (q a) -> a -> next -> MyDsl next