<div dir="ltr"><div>I've been wrestling with this for a while and I decided eventually to look for help. I've been hoping to design a domain specific embedded language in Haskell that would let me pipe a commutative monad throughout an expression written in the language. Special terms within the language will eventually have access to this monad. I've created a simplified version here to represent the main issues. </div><div><br></div><div>Here is what I'd like from the language:</div><div><br></div><div> * To use haskell syntax for substitution and pattern matching rather than implementing this myself.</div><div> * To be able to express lambdas in my language.</div><div> * To be able to embed any haskell terms including functions into the language.</div><div> * I'd like the Haskell type checker to tell me about bad terms.</div><div> * I'd like to thread a monad through the entire expression.</div><div><br></div><div>So here is the first implementation that I tried of this (full source here: <a href="http://lpaste.net/142959">http://lpaste.net/142959</a>)</div><div><br></div><div>    data Exp m x where</div><div>       Val :: m x -> Exp m x  </div><div>       Lam1 :: m (a -> Exp m b)        -> Exp m (a -> b)</div><div>       Lam2 :: m (a -> Exp m (b -> c)) -> Exp m (a -> b -> c)</div><div><br></div><div>a function liftE allows me to lift a haskell term into an expression:</div><div><br></div><div>    liftE x = Val $ return x</div><div><br></div><div>Application is a function <@> so:</div><div><br></div><div>    (<@>) :: forall m a b. Monad m => Exp m (a -> b) -> Exp m a -> Exp m b</div><div>    (<@>) (Val  f) (Val x) = Val  $ f `ap` x</div><div>    (<@>) (Lam2 f) (Val x) = Lam1 $ f >>= \f' -> x >>= \x' -> unLam1 $ f' x'</div><div>    (<@>) (Lam1 f) (Val x) = Val $ f >>= \f' -> x >>= \x' -> unVal $ f' x'</div><div><br></div><div>Seems like it might work! In fact it does typecheck.</div><div><br></div><div>So the first test expressions I'd like to try are these:</div><div><br></div><div>    mapE :: Monad m => Exp m ((a -> b) -> [a] -> [b])</div><div>    mapE = Lam2 $ return $ \ f -> Lam1 $ return $ \ xxs -></div><div>      case xxs of </div><div>        [] -> liftE []</div><div>        (x:xs) -> liftE (:) <@> liftE (f x) <@> (mapE <@> liftE f <@> liftE xs)</div><div><br></div><div>    testExpression :: Monad m => Exp m [Int]</div><div>    testExpression = mapE <@> liftE (+10) <@> liftE [1,2,3,4]</div><div><br></div><div>and just to justify doing any of this I'll create a Monad called BindCounter that counts the number of times bind is called:</div><div><br></div><div>    newtype BindCounter a = BC (Int -> (Int, a))</div><div><br></div><div>    runBC (BC f) = f 0</div><div><br></div><div>    instance Functor (BindCounter) where</div><div>      fmap f (BC x) = BC $ \t -> let (t', x') = x t in (t', f x')</div><div><br></div><div>    instance Applicative (BindCounter) where</div><div>      pure x = BC (\t -> (t,x))</div><div>      f <*> x = f >>= \f' -> x >>= \x' -> return $ f' x' </div><div><br></div><div>    instance Monad (BindCounter) where</div><div>      return = pure</div><div>      BC f >>= g = BC $ \old -></div><div>                        let (new, val) = f (old + 1)</div><div>                            BC f' = g val</div><div>                        in f' new</div><div><br></div><div>now I can try a test </div><div><br></div><div>    test = </div><div>      let (count, result) = runBC (unVal testExpression) in</div><div>        putStrLn $ "Count: " ++ show count ++ " Result: " ++ show result </div><div><br></div><div>The result in ghci is:</div><div>   Count: 36 Result: [11,12,13,14]</div><div><br></div><div>Ok so that's a lot. I was surprised I got this working. You can see from the code that my main gripe with this is I haven't found a way to remove the need to specify the number of embedded lambdas using Lam1 and Lam2 (we could easily add more) and I haven't found a way to apply a Lam to another Lam. I'm also curious if I am reinventing the wheel, I hadn't found a library yet that let's me do something similar.</div>
</div>