#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 giorgidze):
Jeroen and I have written down desugaring rules for basic and SQL-like
monad comprehensions. The rules were written by generalising SQL-like list
comprehension translation rules given in the paper called "Comprehensive
Comprehensions".
The desuguaring rules for monad comprehensions are using only monadic
bind, return, guard and mzip combiantors. This can be useful for Nils as
he implements "then" and "then group" constructs. Of course, the rules
that precisely mirror the implementation can also be devised once the
translation is implemented.
The combinator mzip is a method of MonadZip class that is a subclass of
Monad for those monads that support zipping. Just like monad comprehension
guards which are only allowed for MonadPlus instances (already implemented
by Nils), parallel (zip) monad comprehensions would only be allowed for
monads that are in MonadZip. Later, in this trac ticket, I will post
proposal defining MonadZip class together with the (monadic version of)
zip laws that MonadZip instances should satisfy.
The monad comprehension desugaring rules are obtained by performing the
following generalisations on the translation given in the paper:
* replace |map| with |mmap| that is defined as |mmap f ma = ma >>= (return
. f)|
* replace |concat| with |join| that is defined as |join ma = ma >>= id|
* replace |if g then [()] else []| with |guard g|
* replace |zip| with |mzip|
* inline the definitions of |mmap| and |join|
Here are the rules:
{{{
-- Variables : x and y
-- Expressions : e, f and g
-- Patterns : w
-- Qualifiers : p, q and r
[ e | q ] = [| q |] >>= (return . (\q_v -> e))
-- (.)_v rules, note that _v is a postfix rule application
(w <- e)_v = w
(let w = d)_v = w
(g)_v = ()
(p , q)_v = (p_v,q_v)
(p | v)_v = (p_v,q_v)
(q, then f)_v = q_v
(q, then f by e)_v = q_v
(q, then group by e using f)_v = q_v
(q, then group using f)_v = q_v
-- [|.|] rules
[| w <- e |] = e
[| let w = d |] = return d
[| g |] = guard g
[| p, q |] = ([| p |] >>= (return . (\p_v -> [| q |] >>= (return . (\q_v
-> (p_v,q_v)))))) >>= id
[| p | q |] = mzip [| p |] [| q |]
[| q, then f |] = f [| q |]
[| q, then f by e |] = f (\q_v -> e) [| q |]
[| q, then group by e using f |] = (f (\q_v -> e) [| q |]) >>= (return .
(unzip q_v))
[| q, then group using f |] = (f [| q |]) >>= (return . (unzip q_v))
-- unzip (.) rules. Note that unzip is a desugaring rule (i.e., not a
function to be included in the generated code)
unzip () = id
unzip x = id
unzip (w1,w2) = \e -> ((unzip w1) (e >>= (return .(\(x,y) -> x))), (unzip
w2) (e >>= (return . (\(x,y) -> y))))
}}}
Note that |then group by e| case is missing. The SQL-like list
comprehensions use |groupWith| (see GHC.Exts module) as a default when
|using| clause is absent. Maybe we should have a class providing default
grouping method for certain monads. Another (possibly less attractive)
option is to always require grouping function.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4370#comment:17>
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