#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):
The main reason I did it like that is, that we need separate `mmap`
functions
for each variable used in a group statement and one more for the statement
itself. For example, a monad comprehension like this:
{{{
[ x+y+z | x <- (someList_x :: [Int])
, y <- (someList_y :: [String])
, z <- (someList_z :: [SomeData])
, then group by x
]
}}}
would build up a context of 4 different `mmaps`:
{{{
mmap_x :: ((Int, String, SomeData) -> Int)
-> [(Int, String, SomeData)]
-> [Int]
mmap_y :: ((Int, String, SomeData) -> String)
-> [(Int, String, SomeData)]
-> [String]
mmap_z :: ((Int, String, SomeData) -> SomeData)
-> [(Int, String, SomeData)]
-> [SomeData]
mmap_unzip :: ([(Int, String, SomeData)] -> ([Int, String, SomeData]))
-> [[(Int, String, SomeData)]]
-> [([Int], [String], [SomeData])]
}}}
(see translation rules, `mmap` is basicly the same as `liftM` or just `m
>>= return . f`)
So, looking up each of those statements, typechecking it and storing it in
a
list of `SyntaxExpr` wouldn't be the nicest solution. Even more since
there
actually is nothing to "check" on those types - we know all of them
already and
the typechecker shouldn't ever fail on those functions if the rest is
correct.
Currently, list comprehensions use the same approach. They lookup `map` to
desugar group statements (see `deSugar/DsListComp.lhs`, line 147+) and
apply
the types by hand to that function. Obviously, they don't run into the
same
issue, since `map` doesn't require a dictionary.
Would it be possible to use (somehow "extract" it) that dictionary of
those
bind/return functions used by the comprehension (and not the group
statement
itself)? If not I'd propose to change (unless you have another idea):
{{{
-- hsSyn/HsExpr.lhs
| GroupStmt
-- ...
[(idR, idR)] -- See Note [GroupStmt binder map]
-- ...
}}}
into a list of `[(idR, idR, SyntaxExpr idR)]`, where the `SyntaxExpr`
would be
bottom for everything but monad comprehensions, and add another field
`SyntaxExpr idR` to the `GroupStmt` for the final `mmap unzip ..` call.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4370#comment:31>
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