#4370: Bring back monad comprehensions
---------------------------------+------------------------------------------
    Reporter:  simonpj           |        Owner:  nsch        
        Type:  feature request   |       Status:  new         
    Priority:  normal            |    Milestone:  7.2.1       
   Component:  Compiler          |      Version:  6.12.3      
    Keywords:                    |     Testcase:              
   Blockedby:                    |   Difficulty:              
          Os:  Unknown/Multiple  |     Blocking:              
Architecture:  Unknown/Multiple  |      Failure:  None/Unknown
---------------------------------+------------------------------------------

Comment(by nsch):

 Replying to [comment:16 simonpj]:
 > No, I wasn't clear enough.  I meant:
 >  * Typecheck `(>>)` using `tcSyntaxOp` just as you are doing now,
 producing `e_bind`
 >  * Ditto `guard`, producing `e_guard`
 >  * Now construct the expression `(\x. e_bind (e_guard x))`, or `(e_bind
 . e_guard)`, whichever is easier, and stick that in the `ExprStmt`. For
 the latter you'll need to add the three type arguments to `(.)`.

 Then I don't understand you. How/where am I supposed to look those
 functions up? I thought that should be done in the renamer?

 At the moment this is what I do:

 First, look up the names of those two functions. Pass them to the
 typechecker via the `ExprStmt`.

 {{{
 -- rename/RnExpr.lhs
 rnStmt (MonadComp _) (L loc (ExprStmt expr _ _ _)) thing_inside
         -- ...
         ; (then_op, fvs1)  <- lookupSyntaxName thenMName
         ; (guard_op, fvs3) <- lookupSyntaxName guardMName
         -- ...
         ; return (([L loc (ExprStmt expr' then_op guard_op
 placeHolderType)], thing), ...
 }}}

 Then typecheck everything, using `tcSyntaxOp` and pass the typechecked
 versions to the desugarer:

 {{{
 -- typecheck/TcMatches.lhs
 tcMcStmt _ (ExprStmt rhs then_op guard_op _) res_ty thing_inside

         -- ...
         ; guard_op'  <- tcSyntaxOp MCompOrigin guard_op
                                    (mkFunTy test_ty rhs_ty)
         ; then_op'   <- tcSyntaxOp MCompOrigin then_op
                                    (mkFunTys [rhs_ty, new_res_ty] res_ty)
         -- ...
         ; return (ExprStmt rhs' then_op' guard_op' rhs_ty, thing) }
 }}}

 And in the desugarer I finally put both functions and the "thing"
 together:

 {{{
 -- deSugar/DsListComp.lhs
     go (ExprStmt rhs then_exp guard_exp _) stmts
       = do { rhs'       <- dsLExpr rhs
            ; guard_exp' <- dsExpr guard_exp
            ; then_exp'  <- dsExpr then_exp
            ; rest       <- goL stmts
            ; return $ mkApps then_exp' [ mkApps guard_exp' [rhs']
                                        , rest ] }
 }}}

 Of course, I could compose both functions right away in the typechecker,
 but I'd still need to look them up in the renamer. Or are you suggesting
 to me to do all three steps at once?

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4370#comment:18>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to