#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 simonpj):
Replying to [comment:13 nsch]:
> If you have any concerns about those changes, please let me know.
>
>
> === hsSyn/HsExpr.lhs ===
>
> * New `MonadComp` context is added to the `HsStmtContext` data type. It
> currently gets a `PostTcTable` argument, very simliar to the
`MDoExpr`
> context (see the note about typechecking/desugaring below).
I'm afraid that the `PostTcTable` in `MDoExpr` is misleading. As you'll
see, it's the ''only'' use of `PostTcTable` and it shouldn't really be
there. Instead each individual `BindStmt` or `ExprStmt` carries its own
evidence. eg `RecStmt` has `mfix` and `return`, etc. One reason for this
is that in principle the monad doesn't need to stay the same throughout!
Eg someone wanted
{{{
(>>=) :: m1 a -> (a -> m2 b) -> m2 b
}}}
So you should find you can do without the `PostTcTable` on `MonadComp`
altogether.
> * The `ExprStmt` constructor got another `SyntaxExpr` argument, where
the
> `guard` operation is added by the renamer and later on assures that
we have
> an instance of `MonadPlus` in the typechecker.
OK, but only for `ExprStmts` that are within a `MonadComp`. Make sure this
is documented in the type declaration.
> === rename/RnExpr.lhs ===
>
> * New rule in the `rnStmt` function for `ExprStmt`s inside monad
> comprehensions, where the `guard` function is looked up and added to
the
> `ExprStmt`.
Here you mean "`guard` is looked up '''only''' for monad comprehensions",
I assume?
In other cases, the `guard` field stays as bottom?
Actually, on reflection, consider this.
{{{
do notation: do { e ; Q } --> e >> do { Q }
monad comp: [ e | g; Q ] --> guard g >> [ e | Q ]
}}}
Which suggests that you can typecheck the `ExprStmt` of a monad
comprhension
in the above way, and then attach a `SyntaxExpr` of ( (>>) . guard ) to
the `ExprStmt`.
Then you'd only need the one field. The `(>>)` and `guard` would be
looked up
(they are rebindable) but the compose operation `(.)` is the real built-in
one,
not rebindable. This would be much neater than having two fields, one of
which
is usually bottom.
(I think you suggested this before.)
> The `BindStmt` rule is very similiar to the typechecking rule
> for `BindStmt` inside do-blocks, the `ExprStmt` is typechecked to
type
> `bool` (to allow rebindable syntax) and the `guard` function (the new
> argument to the `ExprStmt` constructor) is typechecked to `bool ->
res_ty`.
> The `LetStmt`s haven't been touched and work the same for every
context
> anyway. I'm currently working on the `TransformStmt` and `GroupStmt`,
so
> they're missing right now.
Do you think you could write the documentation first? We'll need it
sooner or later,
and soonre is better. In particular, the story that a monad comprension
type-checks
just as if you were typechecking the desugared version. So we need to
give the desugaring
in the manual. Something like
{{{
[ e | p <- r; Q ] --> r >>= (\p -> [e | Q])
}}}
and so on for each form. That's the easiest way to explain how
`TransformStmt` and `GroupStmt`
behave in monad comprehensions; and once it's written down, it'll be
easier to
understand the code. This desugaring table should appear in the user
manual.
> As mentioned above, the body should be typechecked to type `a`. However,
to be
> able to `return` this body to the final `m a` type I need a typechecked
version
> of the `return` function in the desugarer. Because I don't wanted to
modify the
> body syntax tree in the typechecker (it lead to some strange looking
error
> messages etc) I added that `PostTcTable` argument to the `MonadComp`
context.
I can see why you want it there, because the `HsDo` constructor looks like
this:
{{{
| 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
PostTcType -- Type of the whole expression
}}}
So you want a `SyntaxExpr` to accompany hte `LHsExpr`. But just as you
only
need the `guard` operator on the `ExprStmts` in a monad comprehension, so
you only
need the `return` operator for monad comprehensions. So for the latter
case it
makes some sense to have it on the `MonadComp` constructor.
So, I suggest you nuke the `PostTcTable` on `MonadComp`, and replace it
with
one `SyntaxExpr` for `return`.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4370#comment:14>
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