#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):

 I made a few changes in order to get rid of that ``SyntaxTable`` as well:

 {{{
   | HsDo        (HsStmtContext Name) -- The parameterisation is
 unimportant
                                      -- because in this context we never
 use
                                      -- the PatGuard or ParStmt variant
                 [LStmt id]           -- "do":one or more stmts
                 (LHsExpr id)         -- The body; the last expression in
 the
                                      -- 'do' of [ body | ... ] in a list
 comp
                 (SyntaxExpr id)      -- The 'return' function, see Note
                                      -- [Monad Comprehensions]
                 PostTcType           -- Type of the whole expression
 }}}

 {{{
   | TransformStmt
          [LStmt idL]    -- Stmts are the ones to the left of the 'then'

          [idR]          -- After renaming, the IDs are the binders
 occurring
                         -- within this transform statement that are used
 after it

          (LHsExpr idR)          -- "then f"

          (Maybe (LHsExpr idR))  -- "by e" (optional)

          (SyntaxExpr idR)       -- The 'return' function for inner monad
                                 -- comprehensions and...
          (SyntaxExpr idR)       -- ...the '(>>=)' operator.
                                 -- See Note [Monad Comprehensions]

   | GroupStmt
          [LStmt idL]      -- Stmts to the *left* of the 'group'
                           -- which generates the tuples to be grouped

          [(idR, idR)]     -- See Note [GroupStmt binder map]

          (Maybe (LHsExpr idR))  -- "by e" (optional)

          (Either                -- "using f"
              (LHsExpr idR)      --   Left f  => explicit "using f"
              (SyntaxExpr idR))  --   Right f => implicit; filled in with
 'groupWith'

          (SyntaxExpr idR)       -- The 'return' function for inner monad
                                 -- comprehensions and...
          (SyntaxExpr idR)       -- ...the '(>>=)' operator.
                                 -- See Note [Monad Comprehensions]
 }}}

 {{{
 Note [Monad Comprehensions]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Monad comprehensions require seperate 'return' and '>>=' functions. These
 functions are stored in the 'HsDo' expression and
 'GroupStmt'/'TransformStmt'
 statements. The 'return' function is used to "lift" the body of the monad
 comprehension:

   [ body | stmts ]                 ->   stmts >>= \env -> return body

 In 'then ..' and 'then group ..' statements, the 'return' function is
 required
 for nested monad comprehensions, for example a simple 'TransformStmt'...

   [ body | stmts, then f, rest ]   ->   f [ env | stmts ] >>= \env' -> [
 body | rest ]

 ...will desugar the same way as above, thus requiring to call 'return' on
 'env'
 again.

 In any other context than 'MonadComp', both fields for 'return' and '>>='
 will
 stay bottom.
 }}}

 Does that sound reasonable?

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4370#comment:22>
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