#4370: Bring back monad comprehensions
------------------------------+---------------------------------------------
  Reporter:  simonpj          |          Owner:                  
      Type:  feature request  |         Status:  new             
  Priority:  normal           |      Milestone:  7.4.1           
 Component:  Compiler         |        Version:  6.12.3          
Resolution:                   |       Keywords:                  
  Testcase:                   |      Blockedby:                  
Difficulty:                   |             Os:  Unknown/Multiple
  Blocking:                   |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown     |  
------------------------------+---------------------------------------------

Comment(by giorgidze):

 I have developed a few examples that use RebindableSyntax? in combination
 with MonadComprehensions. Everything worked as expected for standard
 comprehensions (i.e., for the generator and filter clauses). Unfortunately
 I was not able to use RebindableSyntax? with extended comprehensions
 (i.e., with the then and then group clauses).

 Here I will just give one example that makes use of monad comprehensions
 as set comprehensions. The example demonstrates how to use
 MonadComprehensions with RebindableSyntax? and highlights problems that I
 have encountered when rebinding the fmap and mgroupWith functions used in
 the desugaring translation of monad comprehensions extended with the "then
 group" clause. I remember the problems were not present with the patch by
 Nils, but I can not say that with absolute certainty as I am not able to
 reproduce that version of GHC at the moment.

 OK let me jump to the example straight away. I will start with the
 language pragmas and necessary import statements:


 {{{
 {-# LANGUAGE RebindableSyntax, MonadComprehensions, TransformListComp #-}

 module Main where

 import Prelude (Eq, Ord, IO, String, Bool (..), Integer, map, fromInteger,
 print, odd, undefined, error)

 import qualified Data.Set as Set
 import Data.Set (Set)

 import GHC.Exts (groupWith)

 }}}
 Now let us rebind the monadic combinators that are used in the desugaring
 translation of standard comprehensions to the set specific versions (I
 could as well use Ganesh's rmonad package and RMonad instance defined in
 the package).


 {{{
 return :: a -> Set a
 return = Set.singleton

 (>>=) :: (Ord a, Ord b) => Set a -> (a -> Set b) -> Set b
 s >>= f = Set.fold Set.union Set.empty (Set.map f s)

 (>>) :: (Ord a, Ord b) => Set a -> Set b -> Set b
 s1 >> s2 = s1 >>= (\ _ -> s2)

 guard :: Bool -> Set ()
 guard False = Set.empty
 guard True  = Set.singleton ()

 fail :: String -> Set a
 fail = error

 }}}
 Now we can use standard monad comprehensions as set comprehensions:


 {{{
 set1 :: Set Integer
 set1 = Set.fromList [0 .. 9]

 set2 :: Set Integer
 set2 = [ x | x <- set1, odd x]

 }}}
 So far everything works as expected for standard monad comprehensions.

 Now let us attempt to use monad comprehensions extended with the "then
 group" clause for sets. Let me rebind the fmap and mgroupWith functions:


 {{{
 fmap :: (Ord a, Ord b) => (a -> b) -> Set a -> Set b
 fmap = Set.map

 mgroupWith :: (Ord a, Ord b) => (a -> b) -> Set a -> Set (Set a)
 mgroupWith f s = Set.fromList (map Set.fromList (groupWith f (Set.toList
 s)))

 }}}
 and consider the following example that makes use of the "then group"
 clause:


 {{{
 set3 :: Set (Set Integer)
 set3 = [ x | x <- set1, then group by x]

 }}}
 For this example the GHC type checker produces the following errors:


 {{{
 Set.hs:41:25:
     No instances for (Ord a, Ord b)
       arising from a use of `fmap'
     In the expression: fmap
     In a stmt of a monad comprehension: then group by x
     In the expression: [x | x <- set1, then group by x]

 Set.hs:41:25:
     No instance for (Ord a)
       arising from a use of `mgroupWith'
     In the expression: mgroupWith
     In a stmt of a monad comprehension: then group by x
     In the expression: [x | x <- set1, then group by x]

 }}}

 The GHC type checker does not allow constrains to be imposed on the type
 contained by the monad when the fmap and mgroupWith functions are
 rebinded.

 Simon and Nils, is it possible to relax the restriction when the
 RebindableSyntax? extension is turned on?

 Your input on this issue would be very much appreciated as it may pave the
 way for more useful applications and help to clarify the GHC documentation
 on rebindable syntax.

 Thanks in advance, George

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4370#comment:62>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to