How can I combine the CheckingFuelMonad with a State monad in Hoopl?

故事扮演 提交于 2019-12-10 13:00:00

问题


I am using the Hoopl library and would like to carry some state around while rewriting. The rewrite functions are polymorphic regarding the monad used, but I cannot figure out how to combine a State monad with one of the library's Fuel monads.

Below is a minimal example. MyMonad is a synonym combining Hoopl's CheckingFuelMonad and a State monad carrying a flag. Stmt is just a placeholder for my intermediate language and isn't really important.

{-# LANGUAGE GADTs, RankNTypes #-}

import Compiler.Hoopl
import Control.Monad.State

type MyMonad = CheckingFuelMonad (State Bool)

data Stmt e x where
  Bind :: () -> Stmt O O

rewriter :: forall e x. Stmt e x -> Fact x () -> MyMonad (Maybe (Graph Stmt e x))
rewriter (Bind ()) () = return $ do
  f <- get
  if f 
   then return $ Just emptyGraph
   else return Nothing

But this will not compile -- GHC complains that rewrite has the wrong type:

Couldn't match expected type `Graph' Block Stmt e x'
       against inferred type `Maybe (g n O O)'
  Expected type: CheckingFuelMonad
                   (State Bool) (Maybe (Graph Stmt e x))
  Inferred type: CheckingFuelMonad
                   (State Bool) (Maybe (Maybe (g n O O)))

Is what I want to do possible? How can I write the rewrite function correctly?


回答1:


A browse through hoopl code reveals that CheckingFuelMonad isn't an instance of MonadTrans, and you can't make it one, since its constructors are not exported. You can however wrap a StateT around CheckingFuelMonad, like so:

{-# LANGUAGE GADTs, RankNTypes #-}

import Compiler.Hoopl
import Control.Monad.State

type MyMonad = StateT Bool SimpleFuelMonad

data Stmt e x where
  Bind :: () -> Stmt O O

rewriter :: forall e x. Stmt e x -> Fact x () -> MyMonad (Maybe (Graph Stmt e x))
rewriter (Bind ()) () = do
  f <- get
  if f
   then return $ Just emptyGraph
   else return Nothing



回答2:


Well, the immediate cause of your current error is simple. What is the final expression if f is true? If we take this:

rewriter :: forall e x. Stmt e x -> Fact x () -> MyMonad (Maybe (Graph Stmt e x))
rewriter (Bind ()) () = return $ do
  f <- get
  if f 
   then return $ Just emptyGraph
   else return Nothing

...and remove everything but the True branch we get:

rewriter :: forall e x. Stmt e x -> Fact x () -> MyMonad (Maybe (Graph Stmt e x))
rewriter (Bind ()) () = return $ do
  return $ Just emptyGraph

...which simplifies to:

rewriter :: forall e x. Stmt e x -> Fact x () -> MyMonad (Maybe (Graph Stmt e x))
rewriter (Bind ()) () = return $ return $ Just emptyGraph

What's the type of return $ return $ Just emptyGraph?

(Monad m1, Monad m2, GraphRep g) => m1 (m2 (Maybe (g n O O)))

In other words, you've got an extra return in there. (Monad m) => CheckingFuelMonad m is itself a Monad, even though CheckingFuelMonad doesn't seem to be defined as a monad transformer, so you've only got one monad layer to return with.



来源:https://stackoverflow.com/questions/6495320/how-can-i-combine-the-checkingfuelmonad-with-a-state-monad-in-hoopl

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!