Modifying functions in the typechecker?

Nils Schweinsberg ml at n-sch.de
Thu Nov 25 05:07:43 EST 2010


Hi,


I'm currently working on a GHC extension called "monad comprehensions" 
[1]. Typechecking for generators ("pat <- rhs") already works, but
filters are a bit more tricky. Basicly, it works like that:

A monad comprehension...

     [ body | E ]     -- E :: Bool

...should desugar to:

     Control.Monad.guard E >> return body

In the typechecker I typecheck E for type Bool, and see if we're in a
MonadPlus by typechecking "guard". But I have to "pass" this
guard-then-op function to the desugarer, so I created a new expression
"then_op' = (>>) . guard" and pass this function to the ExprStmt
constructor.

The code in typecheck/TcMatches.lhs looks currently like this:


     tcMcStmt _ (ExprStmt rhs then_op _) res_ty thing_inside = do
       { -- Typecheck rhs on type Bool
         rhs'        <- tcMonoExpr rhs boolTy

         -- Deal with rebindable syntax:
         --    then_op  :: rhs_ty -> new_res_ty -> res_ty
         -- See notes in tcDoStmt.
         -- After this we redefine then_op to have the following type:
         --    then_op' :: Bool -> new_res_ty -> res_ty
         --    then_op' = (>>) . guard
       ; rhs_ty      <- newFlexiTyVarTy liftedTypeKind
       ; new_res_ty  <- newFlexiTyVarTy liftedTypeKind
       ; let then_ty  = mkFunTys [rhs_ty, new_res_ty] res_ty
             guard_ty = mkFunTys [boolTy] rhs_ty
             comp_ty  = mkFunTys [then_ty, guard_ty, boolTy, new_res_ty]
                                 res_ty
       ; then_op     <- tcSyntaxOp MCompOrigin then_op then_ty
       ; guard_op    <- tcSyntaxOp MCompOrigin (HsVar guardMName)
                                               guard_ty
       ; compose_op  <- tcSyntaxOp MCompOrigin (HsVar composeName)
                                               comp_ty
       ; let then_op' = HsApp (nlHsApp (noLoc compose_op)
                                       (noLoc then_op))
                                       (noLoc guard_op)

       ; thing       <- thing_inside new_res_ty
       ; return (ExprStmt rhs' then_op' boolTy, thing) }


Is this a valid approach? Should I move the "(>>) . guard" function
somewhere else? I had a look at the renamer where "(>>)" is added to the
statement "ExprStmt" the first time, but apparently you cannot call
"tcSyntaxOp" in the typechecker on this function if you construct it
with "HsApp (compose_op `HsApp` then_op) guard_op". Is there another
function which could typecheck such a constructed expression without
telling the user what functions we've used?

I also had a look at the MDo typechecker, where they use this:


       ; let names = [mfixName, bindMName, thenMName,
                      returnMName, failMName]
       ; insts <- mapM (\name -> newMethodFromName DoOrigin name m_ty)
                       names
       ; return $ mkHsWrapCoI coi $
         HsDo (MDoExpr (names `zip` insts)) stmts' body' res_ty' }


So they can use these names with their typechecked versions in the
desugarer. But if I do this for monad comprehensions and "guard",
*every* monad comprehension will require a MonadPlus instance, which
shouldn't be necessary if there are no filter expressions.

Any advice on how this could be solved?


Thanks, Nils



[1]: http://hackage.haskell.org/trac/ghc/ticket/4370


More information about the Glasgow-haskell-users mailing list