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

 Today, George and I have written down a number of proposals that concern
 generalisation of SQL-like list comprehensions to monad comprehensions. We
 also briefly discussed the proposals with Torsten.

 The proposals mainly involve library additions (GHC.Exts could be one
 option). Feedback from Haskell community members who expressed their
 interest in the ongoing work on the monad comprehension extension by
 signing up to this trac ticket would be very much appreciated.

 Note that in the following we assume the type class hierarchy of the
 current Haskell Prelude where Monad is not defined as a subclass of
 Functor.

 The SQL-like list comprehension notation provides 'then group by e'
 clause. Note that 'using f' clause is omitted. This means that default
 groupWith function (defined in GHC.Exts module) is used for grouping. In
 other words 'then group by e' is equivalent to 'then group by e using
 groupWith'.

 --| The groupWith function uses the user supplied function which projects
 an element out of every list element in order to first sort the input list
 and then to form groups by equality on these projected elements.


 {{{
 groupWith :: Ord b => (a -> b) -> [a] -> [[a]]
 }}}



 Obviously this function is only suitable as a default grouping function
 for lists.

 In the following we outline a number of options of supporting default
 grouping functions for the monad comprehension notation.

 (OPTION 1) MonadGroup type class WITHOUT restrictions on the type t of
 projected out values allowing MonadGroup instances to introduce
 restrictions on t.


 {{{
 class Monad m => MonadGroup m t where
  mgroupWith :: (a -> t) -> m a -> m (m a)
 }}}


 Here we propose not to have any restrictions on the type t, as this will
 limit the usability of the class. This class will not impose any extra
 laws as is done by the Monad, MonadPlus and MonadZip (see below) classes.
 The class is defined to merely introduce a default grouping function for
 certain monads.

 Note that we defined the type class as a multiparameter type class, so
 that instances can put restrictions on the variable t (when flexible
 instances are enabled). With flexible instance enabled  one could use the
 groupWith function introduced by the SQL like list comprehensions, which
 requires Ord t (makes sense for lists). One would only require Eq t for
 sets, for example.

 Using this class `q, then group by e' is desugared into:


 {{{
 mgroupWith (\q_v -> e) [| q |] >>= (return . unzip q_v)
 }}}


 (OPTION 2) MonadGroup typeclass WITH the Eq restriction on the type t of
 projected out values and additional requirements on what mgroupWith should
 actually return.


 {{{
 class (Monad m, Eq t) => MonadGroup m t where
   mgroupWith :: (a -> t) -> m a -> m (m a)
 }}}


 Here the type `t` is constraint to be a member of the Eq class. With this
 extra requirement in place one can formulate a law that requires that an
 instance provides a function that actually performs grouping. Something
 along the lines:


 {{{
 r = mgroupWith f e
 1.) forall c `from` r. (forall e1, e2 `from` c. f e1 == f e2)
 2.) forall c1, c2 `from` r. (not (Exists e1 `from` c1, e2 `from` c2. c1 /=
 c2. f e1 == f e2))
 }}}


 The first law states that all elements in one `group` must yield the same
 value when applied to f.

 The second law states that no two elements from two different groups may
 yield the same value when applied to f.

 Unlike the implementation of SQL-like list comprehensions where the
 groupWith function also performs sorting we don't think it's necessary to
 require this in general, or formalise this in a law as this would exclude
 unordered collections (such as Sets).

 One can also ask whether such restrictions (including Eq constrain) should
 be placed on functions in the using clause as well (i.e., non-default
 grouping functions).


 The following three options are somewhat more far fetched. We nevertheless
 mention them for completeness.

 (OPTION 3) Always require explicit grouping function for monad
 comprehensions

 (OPTION 4) Use whatever mgroupWith function is in scope without
 introducing a new type class.

 (OPTION 5) Remove the special identifier 'group' from the monad
 comprehension syntax and by using typed directed translation apply current
 'then group' translation rules when the grouping function f returns a
 value of type m a -> m (m a).

 But this option would add even more magic to the notation as the type of
 the function f would change the types of the already bound variables.
 Currently this is done with the use of the explicit special identifier
 'group' .

 We would prefer option 1 currently, we are however open to suggestions.
 Option 2 adds a law that we feel will, for certain cases, be overly
 restricting. Therefor it may be acceptable to trade the ease of reasoning
 (the laws from option 2) for general usability (option 1). There is in
 this scenario nothing preventing users to write instances that obey to the
 above two laws for cases where this makes sense (such as lists).

 ----------------------------

 Furthermore we propose a MonadZip class that is used for parallel monad
 comprehensions.

 We propose the following class:


 {{{
 class Monad m => MonadZip m where

  mzip :: m a -> m b -> m (a,b)
  mzip = mzipWith (,)

  mzipWith :: (a -> b -> c) -> m a -> m b -> m c
  mzipWith f ma mb = mmap (uncurry f) (mzip ma mb)
 }}}


 where mmap and munzip are defined as:


 {{{
 mmap :: Monad m => (a -> b) -> m a -> m b
 mmap f ma = ma >>= (return . f)

 munzip :: Monad m => m (a,b) -> (m a, m b)
 munzip mab = (mmap fst mab, mmap snd mab)

 }}}

 with the following two laws:


 {{{
 -- Naturality :
 mmap (f *** g) (mzip ma mb) = mzip (mmap f ma) (mmap g mb)

 }}}

 and


 {{{
 -- Information Preservation:
 mmap (const ()) ma = mmap (const ()) mb
 ==>
 munzip (mzip ma mb) = (ma, mb)
 }}}



 This laws are just monadic versions of the laws given in the Max's earlier
 post with one change: we only require information preservation law to be
 enforced for structures of same shape (or actions of same effect in
 monadic terminology).

 The laws leave the behaviour of mzip unspecified when the two structures
 are of different shape. The MonadZip instance may implement a "cut of
 behaviour" similar to zip function on lists or fail.

 We are open for comments on the proposals above.

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