Re: [GHC] #4370: Bring back monad comprehensions

2011-08-05 Thread GHC
#4370: Bring back monad comprehensions
--+-
  Reporter:  simonpj  |  Owner:  
  Type:  feature request  | Status:  new 
  Priority:  normal   |  Milestone:  _|_ 
 Component:  Compiler |Version:  6.12.3  
Resolution:   |   Keywords:  
  Testcase:   |  Blockedby:  
Difficulty:   | Os:  Unknown/Multiple
  Blocking:   |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown |  
--+-
Changes (by lelf):

 * cc: anton.nik@… (added)


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


Re: [GHC] #4370: Bring back monad comprehensions

2011-07-26 Thread GHC
#4370: Bring back monad comprehensions
--+-
  Reporter:  simonpj  |  Owner:  
  Type:  feature request  | Status:  new 
  Priority:  normal   |  Milestone:  _|_ 
 Component:  Compiler |Version:  6.12.3  
Resolution:   |   Keywords:  
  Testcase:   |  Blockedby:  
Difficulty:   | Os:  Unknown/Multiple
  Blocking:   |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown |  
--+-
Changes (by simonpj):

  * owner:  simonpj =
  * priority:  high = normal
  * status:  patch = new
  * milestone:  7.2.1 = _|_


Comment:

 George, concerning your question, the trouble is that (as the user manual
 says) we check that the `fmap` function in scope has type
 {{{
   fmap :: forall a b. (a-b) - n a - n b
 }}}
 Why those foralls?  Because we are going to apply `fmap` to lots of
 different arguments.  See Section 4.4 of http://research.microsoft.com/en-
 us/um/people/simonpj/papers/list-comp/list-comp.pdf for a discussion of
 why we ask for polymorphism.

 So I don't know how to give you what you want here... but I can also see
 your problem.

 In short, its not just an implementation bug; there's something
 substantial to think about here.  I'll re-open the ticket, to keep track
 of the question, but I'm not sure how to proceed.

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-07-18 Thread GHC
#4370: Bring back monad comprehensions
--+-
  Reporter:  simonpj  |  Owner:  simonpj 
  Type:  feature request  | Status:  patch   
  Priority:  high |  Milestone:  7.2.1   
 Component:  Compiler |Version:  6.12.3  
Resolution:   |   Keywords:  
  Testcase:   |  Blockedby:  
Difficulty:   | Os:  Unknown/Multiple
  Blocking:   |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown |  
--+-
Changes (by simonpj):

  * owner:  = simonpj


Comment:

 OK I have applied the munzip change.  Ian can you merge?  That leaves
 George's question still to be attended to.

 Simon
 {{{
 commit 2ceacbc35d9c5f4bc6cbcfa46f64d333f9dc53c7
 Author: George Giorgidze giorgi...@gmail.com
 Date:   Mon Jul 4 21:01:12 2011 +0200

 Move the munzip function in the Zip type class;

 ---

  Control/Monad/Zip.hs |   14 ++
  1 files changed, 10 insertions(+), 4 deletions(-)

 diff --git a/Control/Monad/Zip.hs b/Control/Monad/Zip.hs index
 8c431bd..9d71a53 100644
 --- a/Control/Monad/Zip.hs
 +++ b/Control/Monad/Zip.hs
 @@ -3,6 +3,7 @@
  -- |
  -- Module  :  Control.Monad.Zip
  -- Copyright   :  (c) Nils Schweinsberg 2011,
 +--(c) George Giorgidze 2011
  --(c) University Tuebingen 2011
  -- License :  BSD-style (see the file libraries/base/LICENSE)
  -- Maintainer  :  librar...@haskell.org @@ -40,8 +41,13 @@ class Monad m
 = MonadZip m where
  mzipWith :: (a - b - c) - m a - m b - m c
  mzipWith f ma mb = liftM (uncurry f) (mzip ma mb)

 -instance MonadZip [] where
 -mzip = zip
 +munzip :: m (a,b) - (m a, m b)
 +munzip mab = (liftM fst mab, liftM snd mab)
 +-- munzip is a member of the class because sometimes
 +-- you can implement it more efficiently than the
 +-- above default code.  See Trac #4370 comment by giorgidze

 -munzip :: MonadZip m = m (a,b) - (m a, m b) -munzip mab = (liftM fst
 mab, liftM snd mab)
 +instance MonadZip [] where
 +mzip = zip
 +mzipWith = zipWith
 +munzip   = unzip
 }}}

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-07-06 Thread GHC
#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


Re: [GHC] #4370: Bring back monad comprehensions

2011-07-04 Thread GHC
#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 |  
--+-
Changes (by giorgidze):

  * owner:  nsch =
  * status:  closed = new
  * resolution:  fixed =


Comment:

 Currently, the munzip function is not a member of the MonadZip class. It
 has the following type signature and definition:

 {{{
 munzip :: MonadZip m = m (a,b) - (m a, m b)
 munzip mab = (liftM fst mab, liftM snd mab)
 }}}

 When developing monad comprehension examples for various MonadZip
 instances, I found that it is useful to allow a MonadZip instance to
 provide more efficient unzipping function.

 I suggest we make the munzip function a member of the MonadZip class by
 using the current definition as a default implementation. The laws that
 the munzip member should satisfy is already documented in the module.

 The small patch that is attached to this trac ticket implements the
 proposed change.

 Cheers, George

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


Re: [GHC] #4370: Bring back monad comprehensions

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

Comment(by nsch):

 Sorry for the late reply. Yes that sounds pretty good. :)

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


Re: [GHC] #4370: Bring back monad comprehensions

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

Comment(by simonpj):

 I intended it.  It seems reasonable that
  * `-XMonadComprehensions` makes list comprehensions be interpreted as
 monad comprehensions
  * `-XTransformListComp` adds the SQL-like comprehension support, to
 either list or monad comprehensions
  * Ditto for `-XParallelListComp`

 Admittedly `TransformListComp` then is not necessarily about '''list'''
 comprehensions.  Maybe is should be `TransformComp`; and similarly for
 `ParallelComp`?

 That woudl be doable; we'd have to go through a cycle of deprecation to
 encourage people to adopt the new flag name.

 Does the logic make sense though?

 Simon

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


Re: [GHC] #4370: Bring back monad comprehensions

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

Comment(by simonpj):

 Hurrah. I'm glad it is proving useful.  I always wonder which of GHC's
 features are used, and how much!

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


Re: [GHC] #4370: Bring back monad comprehensions

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

Comment(by nsch):

 The userguide looks fine, I have just one more question. Last time I
 checked MonadComprehensions didn't allow transform or parallel
 statements by default. Did you change that on purpose or did I forgot to
 test that properly before sending in those patches?

 {{{
 GHCi, version 7.1.20110504: http://www.haskell.org/ghc/  :? for help

 Prelude :set -XMonadComprehensions
 Prelude [ x | x - [1..], then take 5 ]

 interactive:0:19:
 Unexpected transform statement in a monad comprehension
 Use -XTransformListComp
 Prelude [ x+y | x - [1,2] | y - [1,2] ]

 interactive:0:18:
 Unexpected parallel statement in a monad comprehension
 Use -XParallelListComp
 }}}

 Those errors shouldn't occur…

 I currently cannot get the latest version to see whether or not this is
 already fixed (my local git is messed up somehow), but I guess it's not.
 :)

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


Re: [GHC] #4370: Bring back monad comprehensions

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

Comment(by simonpj):

 Nils, if you felt up to it, it would be a fine thing to have a page on the
 Hsakell Wiki describing monad comprehensions and what you can do with the.
 There's plenty of precedent for this; see Collaborative documentation at
 http://haskell.org/haskellwiki/GHC.  With a relatively complex feature the
 user-manual documentation isn't that helpful, whereas on a more discursive
 page you can give lots of examples. You could use your blog post as a
 basis.

 BTW can you check the changes I made to the user manual to ensure I didn't
 get anything wrong?  Thanks.

 Simon

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-05-04 Thread GHC
#4370: Bring back monad comprehensions
--+-
  Reporter:  simonpj  |  Owner:  nsch
  Type:  feature request  | Status:  closed  
  Priority:  normal   |  Milestone:  7.4.1   
 Component:  Compiler |Version:  6.12.3  
Resolution:  fixed|   Keywords:  
  Testcase:   |  Blockedby:  
Difficulty:   | Os:  Unknown/Multiple
  Blocking:   |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown |  
--+-
Changes (by simonpj):

  * status:  patch = closed
  * resolution:  = fixed


Comment:

 OK. I've merged the monad-comprehension branch with the master!  Hooray.
 Check it out and see if it works for you.  Thanks for your work on this.

 I have ''not'' done anything about updating Cabal to know about
 !MonadComprehensions.  I'm not sure what the protocol for that is.

 Simon

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


Re: [GHC] #4370: Bring back monad comprehensions

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

Comment(by nsch):

 I migrated all patches to git and resolved some conflicts. I also added a
 munzip to the `Control.Monad.Zip` module which is convenient to have and
 also is refered to in our paper.

 Files will get attached, the old ones should be ignored (there's no way to
 delete them?). Patching should be done via `git am file` where `file`
 is

  * `ghc-0001-monad-comprehensions-compiler.patch` and `ghc-0002-monad-
 comprehensions-user-guide.patch` in the ghc git root directory
  * `testsuite-0001-monad-comprehensions-test-suite.patch` in the
 `testsuite` git directory
  * `base-0001-monad-comprehensions-Group-and-Zip-monad.patch` in the
 `libraries/base` git directory
  * `Cabal-0001-monad-comprehensions-cabal-extensions.patch` in the
 `libraries/Cabal` git directory

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


Re: [GHC] #4370: Bring back monad comprehensions

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

Comment(by simonpj):

 Oh, apologies; I should have mentioned that I rolled up my sleeves three
 days ago and did the migration myself. I'm deep in hacking mode now.

 Simon

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


Re: [GHC] #4370: Bring back monad comprehensions

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

Comment(by nsch):

 Cool ok. :) Although you might want to use my base-patch anyway since it
 got that extra munzip function in it which is missing in the previous
 patches (or you add it by hand of course).

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


Re: [GHC] #4370: Bring back monad comprehensions

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

Comment(by nsch):

 So, any news? Have you had the time to take a look at my patches? It's
 been a while since the last update and I just thought I'd ask whether or
 not you forgot about it? :)


 - Nils

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


Re: [GHC] #4370: Bring back monad comprehensions

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

Comment(by simonpj):

 No, I have not looked at them.  But neither have I forgotten.  The ICFP
 deadline was 24 March and I was totally focused on that.  April is also
 ridiculously busy.  The first two weeks of May are much better. We plan to
 release GHC 7.2 sometime in mid to late May, and it will have your stuff
 in it by hook or by crook.

 Simon

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-03-04 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  nsch
Type:  feature request   |   Status:  patch   
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 user guide documentation is done, patch attached.

 A compiled version is available at:
 http://n-sch.de/hdocs/ghc/html/users_guide/syntax-extns.html#monad-
 comprehensions

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-03-04 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  nsch
Type:  feature request   |   Status:  patch   
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):

 This patch adds `MonadComprehensions` to the `Language.Haskell.Extension`
 library of the `Cabal` package and fixes the only test in the testsuite
 that got broken by my monad comprehension patch (T4437).

 It also fixes some of the references to the user guide.

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-03-04 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  nsch
Type:  feature request   |   Status:  patch   
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):

 Thanks for all your work here. I'm travelling at the moment, and then the
 ICFP deadline presses, but I'll review can commit  your patches for the
 upcoming 7.2 release.

 One thing: earlier in the ticket you give the desugaring rules.  Could you
 transfer them to a GHC wiki page, linked from the Contributed
 documentation section of
 http://hackage.haskell.org/trac/ghc/wiki/Commentary?  To make sense of it
 you, probably want to cut/paste a summary of the goal, and an overview of
 the implementation.  Nothing too detailed, becuase documentation separate
 from code tends to go out of date.  Just a road-map of where to look for
 the changes, and any watch out for this points you tripped over.
 Worth pointing back to this roadmap and the desugaring rules from comments
 in the code.

 Simon

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


Re: [GHC] #4370: Bring back monad comprehensions

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

Comment(by nsch):

 Patch for the testsuite added. One note: I've added a
 `expected_broken_for(4370, ['ghci','hpc'])` flag to all tests wich use the
 grouping statement, since ghci still fails with grouping statements…

 I also fixed a few bugs in the compiler (mostly minor bugs in the error
 messages) and will upload the new version aswell.

 Unless somebody comes up with a solution to that ghci error I'd suggest to
 apply these patches and open a separate bug ticket, so someone with the
 necessary expertise will be able to fix it. I will continue to try to fix
 that ghci bug, but currently I don't see why this happens at all (ghci
 even generates different core code, see http://npaste.de/zV/ (ghci) vs
 http://npaste.de/zW/ (ghc) – the `=` on line 31 of the ghci code makes
 no sense at all…).

 So, to commit these patches you should apply...

  * `monad-comprehensions-final.patch` and `mc-user-guide.patch` to the
 main repo
  * `mc-testsuite.patch` to the testsuite
  * `group_zip.patch` to the `base` package
  * `mc-cabal-extensions.patch` to the `Cabal` package

 The alpha version and that git commit can be ignored.

 And just to let you know, I'll be on vacations next week, so I won't be
 able to do any work. I'll add that wiki entry when I come back.

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-03-01 Thread GHC
#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):

 You should be able to apply these two patches to ghc.git and the base
 (darcs) package.

 The base patch is pretty much final, the compiler patch is almost done
 (some comments still use the old `zipM` name instead of the new `mzip`
 etc), but you should be able to see if you can reproduce the error we were
 talking about.

 However, we didn't manage to test this with the latest HEAD because of
 #4990 and #4991, but it worked fine with the version a couple of days ago…

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-03-01 Thread GHC
#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):

 I just did a rebuild with the darcs repo and everything did work as
 expected (we were using git before). I'll upload the darcs patch for the
 compiler aswell.

 So to test this you should:

  * Apply the `group_zip.patch` patch to the base library and
  * apply the `monad-comprehension-alpha.patch` patch to the main ghc repo.

 There should be no conflicts/errors.

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-03-01 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  nsch
Type:  feature request   |   Status:  patch   
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
-+--
Changes (by igloo):

  * status:  new = patch


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


Re: [GHC] #4370: Bring back monad comprehensions

2011-02-22 Thread GHC
#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):

 OK, thats weird.  I'll wait until you've got a patch I can reproduce it
 with.

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-02-21 Thread GHC
#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):

 Hmmm, I found one more strange bug. Maybe you could help me understanding
 it, I can't really see why/where it happens.

 The error occurs when I try to load a .hs file with one single grouping
 statement in ghci:

 {{{
 {-# LANGUAGE MonadComprehensions #-}

 foo = [ a | a - [5], then group by a ] :: [[Int]]
 }}}

 The error message itself is pretty long, so I posted it on a pastebin:
 http://npaste.de/y9/

 The strange thing is, that I can compile that file just fine (after adding
 a `main = print foo`) and it passes the core validation `-dcore-lint`. I
 can also define that statement directly in ghci:

 {{{
 Prelude :set -XMonadComprehensions
 Prelude let foo = [ x | x - [5], then group by x ]
 Prelude foo
 [[5]]
 }}}

 But for some reason, I can not load it from a file. All other statements
 work as expected, and as far as I can tell I haven't touched any ghci
 code. At least none that should be somehow special for grouping
 statements.

 If it is of any help, I posted a diff of my current changes on my
 pastebin: http://npaste.de/yB/
 This diff won't apply to current HEAD, and it's not final at all. Just to
 give you a quick summary of what I've done so far.

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-02-21 Thread GHC
#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):

 I suggest you add `-dcore-lint` to your `ghci` command line too.

 Without being able to reproduce it's hard for me to comment. It's
 certainly very wierd that it's ok in GHCi but not in batch mode.

 Simon

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-02-21 Thread GHC
#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 igloo):

 Does it happen in batch mode even without `-O`?

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-02-21 Thread GHC
#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):

 Replying to [comment:38 simonpj]:
  I suggest you add `-dcore-lint` to your `ghci` command line too.

 `-dcore-lint` doesn't change anything. It fails with the same error.

 Replying to [comment:39 igloo]:
  Does it happen in batch mode even without `-O`?

 There's no `-O` involved?

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-02-18 Thread GHC
#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):

 That sounds good.  Well done!  From the sound of it you managed to follow
 my suggestions in the exchanges above? Anyway I'll take a look when you
 have the patches ready.  Do highlight any bits you feel are less than
 beautiful, in case I can think of a nicer way to do it.

 Simon

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-02-16 Thread GHC
#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):

 Good news! I'm almost done with the implementation. Monad comprehensions
 now support:

   * Binding statements: `[ x + y | x - Just 1, y - Just 2 ]` = `Just 3`
   * Guards: `[ x | x - [1..5], x = 3 ]` = `[1,2,3]`
   * Transform statements: `[ x | x - [1..5], then take 2 ]` = `[1,2]`
   * Grouping statements: `[ x | x - [1,1,2,2,3,3], then group by x ]` =
 `[[1,1],[2,2],[3,3]]`
   * Parallel/zip statements: `[ (x,y) | x - [1,2] | y - [3,4] ]` =
 `[(1,3),(2,4)]`

 All these features are enabled by default if you use the
 `MonadComprehensions`
 language flag. Note, that there are different requirements for some of
 those statements:

   * Guards require a `MonadPlus` instance since it's using `guard` from
 `Control.Monad`
   * Grouping requires a `MonadGroup` instance, a new type class which we
 added
 to the `base` package (unless you use a different grouping function
 via
 `then group by x using ..`)
   * Parallel statements require a `MonadZip` instance, another new type
 class
 for the `base` package.

 At least for now, both new type classes were put into `base` since they're
 supposed to be used by the endusers (people might come up with their own
 groupable/zipable monads). If you have any concerns with that I could move
 them
 out of `base` into another package of course.

 In the next couple of days I'll clean up the code a bit, add/complete the
 documentation, add some tests to the testsuite and finally merge our
 working
 repo with current head before I sent in those patches (you want git
 patches,
 right?).

 As usual - if you have any concerns, please let me know!

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-02-09 Thread GHC
#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):

 The fact that you want to construct the dictionary argument to mmap in the
 desugarer is suspicious.  It's the type checker that builds dictionary
 values, and rightly so because doing so can fail, if there isn't a
 suitable instance; and the need for such an instance might influence the
 infrerred type of the function.

 As you know, the general plan is to attache overloaded methods to the
 syntax tree, and many `Stmts` have such methods attached (`SyntaxExpr`).

 Can't you use the same approach?  Maybe if you explain more of what you
 are doing?

 Simon

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-02-09 Thread GHC
#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
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #4370: Bring back monad comprehensions

2011-02-09 Thread GHC
#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):

 I think what you want the type checker to do is to give you a term,
 attached to the `GroupStmt` of type
 {{{
   imap :: forall a b. (a-b) - m a - m b
 }}}
 where `m` is the type of the monad.  Then you can instantiate this `imap`
 in the desugarer, with explicit applications, just as is done with plain
 `map` now.

 So the type checker need only produce '''one''' term, with the above type.
 That should not be hard.

 Simon

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-02-09 Thread GHC
#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):

 That looks sweet, but how would you typecheck that? My naiv implementation

 {{{
  -- Type check 'mmap' with 'forall a b. (a - b) - m_ty a - m_ty
 b'
; mmap_op' - tcSyntaxOp MCompOrigin mmap_op $
  mkForAllTy alphaTyVar $ mkForAllTy betaTyVar $
  (alphaTy `mkFunTy` betaTy)
  `mkFunTy`
  (m_ty `mkAppTy` alphaTy)
  `mkFunTy`
  (m_ty `mkAppTy` betaTy)
 }}}

 fails on compilation:

 {{{
 Couldn't match expected type `forall a b. (a - b) - [a] - [b]'
 with actual type `(a - b) - m a - m b'
 In a stmt of a monad comprehension: then group by x using groupWith
 }}}

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-02-09 Thread GHC
#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):

 Never mind my last post. I got it figured out. Late night work's paying
 off - monad comprehensions finally support the `group` statement. :)

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-02-08 Thread GHC
#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):

 I have a more technical question about the core language generation in the
 desugarer. I'm trying to use a function from the GHC.Exts library to
 simplify
 core generation a bit and since I only lookup the functions `Id` I have to
 manually apply all the types etc. to the function. The code looks
 something
 like this:

 {{{
   do { [..]
  ; mmap_id  - dsLookupGlobalId mmapName -- new function from GHC.Exts
  ; let -- Apply types  arguments to 'mmap'
tupleElem n = mkApps (Var mmap_id)
 -- Types:
 -- mmap :: forall (m :: * - *) a b. Monad
 m = ..
 [ Type m_ty, Type a_ty, Type b_ty
 -- Arguments:
 , .. ]
 ; [..] }
 }}}

 But that expression is missing one more type argument for that `Monad m
 =`
 predicate, which leads to the following error (for a simple example with
 lists
 and integers):

 {{{
 C:\Users\Nils\dev\hiwi\ghc\inplace\binghc-stage2.exe -dcore-lint
 mc_group.hs
 [2 of 2] Compiling Main ( mc_group.hs, mc_group.o )
 *** Core Lint errors : in result of Desugar ***
 no location info:
 In the expression: GHC.Exts.mmap
  @ []
  @ (GHC.Types.Int, GHC.Types.Int)
  @ GHC.Types.Int
  (\ (ds_dqc :: (GHC.Types.Int, GHC.Types.Int)) -
 case ds_dqc of _ { (ds_dq9, _) - ds_dq9 })
 Argument value doesn't match argument type:
 Fun type:
 GHC.Base.Monad [] =
 ((GHC.Types.Int, GHC.Types.Int) - GHC.Types.Int)
 - [(GHC.Types.Int, GHC.Types.Int)]
 - [GHC.Types.Int]
 Arg type: (GHC.Types.Int, GHC.Types.Int) - GHC.Types.Int
 Arg:
 \ (ds_dqc :: (GHC.Types.Int, GHC.Types.Int)) -
   case ds_dqc of _ { (ds_dq9, _) - ds_dq9 }
 }}}

 Comparing this core dump with other core dumps, it's clear that there
 should be
 another argument `GHC.Base.$fMonad[]` (for this example) to the `mmap`
 function, but I don't know what kind of argument that is and how to get
 it. So
 my question is pretty simple: What function will get me that missing
 argument?

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-02-08 Thread GHC
#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
-+--
Changes (by spl):

 * cc: leather@… (added)


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


Re: [GHC] #4370: Bring back monad comprehensions

2011-01-25 Thread GHC
#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
-+--
Changes (by pumpkin):

 * cc: pumpkingod@… (added)


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


Re: [GHC] #4370: Bring back monad comprehensions

2011-01-10 Thread GHC
#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):

 I didn't highlight enough above, but my suggestion is to add a new `Stmt`
 constructor, namely `ReturnStmt` to use as the last `Stmt` of a block.
 Rather than using `ExprStmt` which, as you say, isn't really right.   Oh,
 if you prefer to call it `BodyStmt` that's fine too.

 Re second point, yes, the whole idea would be to remove the `body`
 argument from `tcExpr` and instead have it deal only with a `[Stmt]`.

 Make sense?

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-01-08 Thread Ian Lynagh
On Fri, Jan 07, 2011 at 12:42:58PM -, GHC wrote:
 
  context as we a) don't need () anymore since we're already at the last
  statements

Wow, I hadn't realised RebindableSyntax lets you rebind () etc in the
middle of a do block.


Thanks
Ian


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


Re: [GHC] #4370: Bring back monad comprehensions

2011-01-07 Thread GHC
#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):

 Ok, I've been working on that a bit and have a couple of questions...

 First, am I suppossed to use the existing `ExprStmt` for the last
 statement of
 a `HsDo` expression or add a separate `BodyStmt`? The reason I ask is that
 those 2 other arguments to `ExprStmt` are pretty much redundant in our
 body
 context as we a) don't need () anymore since we're already at the last
 statements and b) always carry around the type of the expression anyway,
 thus
 needing no extra PostTcType (atleast I think so...). And in addition to
 those
 two points an extra `BodyStmt` would make it easier to distinguish the
 `BodyStmt` from a usual `ExprStmt`.

 Second question is about the typechecking/desugaring functions which don't
 explicitely accept a `HsDo` expression. Currently they usually get 2
 arguments,
 the first one beeing the statements, the second one the body. Am I
 supposed to
 change these aswell, or will something like

 {{{
 -- compiler/typecheck/TcExpr.lhs
 tcExpr (HsDo do_or_lc stmts _) res_ty
   = tcDoStmts do_or_lc stmts' body res_ty
   where (stmts', L _ (ExprStmt body _ _)) = (init stmts, last stmts)
 }}}

 be ok aswell?

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


Re: [GHC] #4370: Bring back monad comprehensions

2011-01-01 Thread GHC
#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):

 I agree about `HsStmtContext`.  However I have another idea to suggest
 about `HsDo`, for you to consider.

 At the moment, the last qualifier in a do-block is pulled out as the
 body of the do, so that `HsDo` has two arguments:
  * The `[Stmt]` list
  * The final `HsExpr` which is the body
 Now, the last qualifier is a bit special, because it must be an
 expression, not a binding form.  But only a bit. My thought is this:
  * Remove the `HsExpr` field of the `HsDo` constructor; instead that field
 simply becomes the last item in the `[Stmt]`.
  * For do-blocks, insist that the last `Stmt` in the list is an
 `ExprStmt`.  (This could be done in the renamer.)
  * For list comprehensions, add a new `Stmt` constructor, `ReturnStmt`,
 which carries the `return` rebindable-syntax term.  (The one you dislike
 attaching to `HsDo`.)
  * The last `Stmt` for a `ListComp` or `MonadComp` must be a `ReturnStmt`.
 Moveover, `ReturnStmt` would only be allowed for `ListComp` and
 `MonadComp`.  We already have constraints of that kind.For example,
 `TransformStmt` isn't allowed in parallel arrays.

 I think that things used to be like this, and in a fit of mistaken zeal I
 thought it'd be neater to pull out the final `Stmt` specially, but I now
 think that was probably a bad plan.

 How does that sound?  There would be a fair bit of knock-on changes, but
 it'd be pretty rountine refactoring I think. It might be worth making this
 change, validating, and then adding your stuff on top, as a second patch.

 Simon

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


Re: [GHC] #4370: Bring back monad comprehensions

2010-12-30 Thread GHC
#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):

 I made a few changes in order to get rid of that ``SyntaxTable`` as well:

 {{{
   | 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
 (SyntaxExpr id)  -- The 'return' function, see Note
  -- [Monad Comprehensions]
 PostTcType   -- Type of the whole expression
 }}}

 {{{
   | TransformStmt
  [LStmt idL]-- Stmts are the ones to the left of the 'then'

  [idR]  -- After renaming, the IDs are the binders
 occurring
 -- within this transform statement that are used
 after it

  (LHsExpr idR)  -- then f

  (Maybe (LHsExpr idR))  -- by e (optional)

  (SyntaxExpr idR)   -- The 'return' function for inner monad
 -- comprehensions and...
  (SyntaxExpr idR)   -- ...the '(=)' operator.
 -- See Note [Monad Comprehensions]

   | GroupStmt
  [LStmt idL]  -- Stmts to the *left* of the 'group'
   -- which generates the tuples to be grouped

  [(idR, idR)] -- See Note [GroupStmt binder map]

  (Maybe (LHsExpr idR))  -- by e (optional)

  (Either-- using f
  (LHsExpr idR)  --   Left f  = explicit using f
  (SyntaxExpr idR))  --   Right f = implicit; filled in with
 'groupWith'

  (SyntaxExpr idR)   -- The 'return' function for inner monad
 -- comprehensions and...
  (SyntaxExpr idR)   -- ...the '(=)' operator.
 -- See Note [Monad Comprehensions]
 }}}

 {{{
 Note [Monad Comprehensions]
 ~~~
 Monad comprehensions require seperate 'return' and '=' functions. These
 functions are stored in the 'HsDo' expression and
 'GroupStmt'/'TransformStmt'
 statements. The 'return' function is used to lift the body of the monad
 comprehension:

   [ body | stmts ] -   stmts = \env - return body

 In 'then ..' and 'then group ..' statements, the 'return' function is
 required
 for nested monad comprehensions, for example a simple 'TransformStmt'...

   [ body | stmts, then f, rest ]   -   f [ env | stmts ] = \env' - [
 body | rest ]

 ...will desugar the same way as above, thus requiring to call 'return' on
 'env'
 again.

 In any other context than 'MonadComp', both fields for 'return' and '='
 will
 stay bottom.
 }}}

 Does that sound reasonable?

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


Re: [GHC] #4370: Bring back monad comprehensions

2010-12-30 Thread GHC
#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):

 A note on my comment above:

 I would prefer to use the `MonadComp` context to store the `return`
 function instead of the `HsDo` expression. But unfortunately the
 `HsStmtContext` in the `HsDo` expression has the argument `Name` instead
 of `id`. This makes it impossible to lookup/typecheck/desugar `return`
 correctly, since all those steps require different types. However,
 changing this type from `Name` to the more general `id` requires a *lot*
 of changes everywhere in the code - and I'm not sure if that's worth it.
 In fact, it requires so many changes that I'd suggest to open a separate
 ticket if you really want us to put that `return` function into the
 `MonadComp` context instead of the `HsDo` expression.

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


Re: [GHC] #4370: Bring back monad comprehensions

2010-12-22 Thread GHC
#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):

 I've just got rid of that `SyntaxTable` on `MDoExpr`.  As discussed above,
 it's a relic, and getting rid of it tidied up the code quite a bit.
 You'll want to pull the patch before recording yours
 {{{
 Wed Dec 22 05:22:10 PST 2010  simo...@microsoft.com
   * Tidy up rebindable syntax for MDo

   For a long time an 'mdo' expression has had a SyntaxTable
   attached to it.  However, we're busy deprecating SyntaxTables
   in favour of rebindable syntax attached to individual Stmts,
   and MDoExpr was totally inconsistent with DoExpr in this
   regard.

   This patch tidies it all up.  Now there's no SyntaxTable on
   MDoExpr, and 'modo' is generally handled much more like 'do'.

   There is resulting small change in behaviour: now MonadFix is
   required only if you actually *use* recursion in mdo. This
   seems consistent with the implicit dependency analysis that
   is done for mdo.

   Still to do:
 * Deal with #4148 (this patch is on the way)
 * Get rid of the last remaining SyntaxTable on HsCmdTop

 M ./compiler/deSugar/Coverage.lhs -6 +1
 M ./compiler/deSugar/DsArrows.lhs -2 +2
 M ./compiler/deSugar/DsExpr.lhs -36 +32
 M ./compiler/hsSyn/HsExpr.lhs -12 +7
 M ./compiler/hsSyn/HsUtils.lhs -1 +1
 M ./compiler/parser/Parser.y.pp -1 +3
 M ./compiler/rename/RnBinds.lhs -1 +1
 M ./compiler/rename/RnExpr.lhs -39 +15
 M ./compiler/rename/RnExpr.lhs-boot -1 +1
 M ./compiler/typecheck/TcHsSyn.lhs -14 +4
 M ./compiler/typecheck/TcMatches.lhs -21 +7
 M ./compiler/typecheck/TcRnDriver.lhs -1 +2
 }}}

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


Re: [GHC] #4370: Bring back monad comprehensions

2010-12-17 Thread GHC
#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):

 Drat, I'd forgotten that the renamer does one step and the typechecker the
 next. That is annoying; I can't see a neat way to do this. Oh well, it's
 not a big deal.  What you have done seems fine.   Please document (in the
 data type declaration) the fact that the 'guard' field is used only for
 monad comprehensions, and is otherwise bottom.

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


Re: [GHC] #4370: Bring back monad comprehensions

2010-12-16 Thread GHC
#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
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #4370: Bring back monad comprehensions

2010-12-16 Thread GHC
#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):

 Replying to [comment:16 simonpj]:
  No, I wasn't clear enough.  I meant:
   * Typecheck `()` using `tcSyntaxOp` just as you are doing now,
 producing `e_bind`
   * Ditto `guard`, producing `e_guard`
   * Now construct the expression `(\x. e_bind (e_guard x))`, or `(e_bind
 . e_guard)`, whichever is easier, and stick that in the `ExprStmt`. For
 the latter you'll need to add the three type arguments to `(.)`.

 Then I don't understand you. How/where am I supposed to look those
 functions up? I thought that should be done in the renamer?

 At the moment this is what I do:

 First, look up the names of those two functions. Pass them to the
 typechecker via the `ExprStmt`.

 {{{
 -- rename/RnExpr.lhs
 rnStmt (MonadComp _) (L loc (ExprStmt expr _ _ _)) thing_inside
 -- ...
 ; (then_op, fvs1)  - lookupSyntaxName thenMName
 ; (guard_op, fvs3) - lookupSyntaxName guardMName
 -- ...
 ; return (([L loc (ExprStmt expr' then_op guard_op
 placeHolderType)], thing), ...
 }}}

 Then typecheck everything, using `tcSyntaxOp` and pass the typechecked
 versions to the desugarer:

 {{{
 -- typecheck/TcMatches.lhs
 tcMcStmt _ (ExprStmt rhs then_op guard_op _) res_ty thing_inside

 -- ...
 ; guard_op'  - tcSyntaxOp MCompOrigin guard_op
(mkFunTy test_ty rhs_ty)
 ; then_op'   - tcSyntaxOp MCompOrigin then_op
(mkFunTys [rhs_ty, new_res_ty] res_ty)
 -- ...
 ; return (ExprStmt rhs' then_op' guard_op' rhs_ty, thing) }
 }}}

 And in the desugarer I finally put both functions and the thing
 together:

 {{{
 -- deSugar/DsListComp.lhs
 go (ExprStmt rhs then_exp guard_exp _) stmts
   = do { rhs'   - dsLExpr rhs
; guard_exp' - dsExpr guard_exp
; then_exp'  - dsExpr then_exp
; rest   - goL stmts
; return $ mkApps then_exp' [ mkApps guard_exp' [rhs']
, rest ] }
 }}}

 Of course, I could compose both functions right away in the typechecker,
 but I'd still need to look them up in the renamer. Or are you suggesting
 to me to do all three steps at once?

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


Re: [GHC] #4370: Bring back monad comprehensions

2010-12-14 Thread GHC
#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):

  I actually tried that, but I cannot typecheck that `(() . guard)`
 function in the typechecker using `tcSyntaxOp` since it results in some
 GHC panic error message on runtime. It's a bit difficult to reproduce
 right now since it requires quite a few changes - but if you think the
 exact error message would be helpful I can get it.

 No, I wasn't clear enough.  I meant:
  * Typecheck `()` using `tcSyntaxOp` just as you are doing now,
 producing `e_bind`
  * Ditto `guard`, producing `e_guard`
  * Now construct the expression `(\x. e_bind (e_guard x))`, or `(e_bind .
 e_guard)`, whichever is easier, and stick that in the `ExprStmt`. For the
 latter you'll need to add the three type arguments to `(.)`.

 Do not attempt to typecheck `(() . guard)`, because the programmer
 didn't write that, and we don't want type error messages to mention that
 program fragment.

 Does that make more sense?

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


Re: [GHC] #4370: Bring back monad comprehensions

2010-12-13 Thread GHC
#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 

Re: [GHC] #4370: Bring back monad comprehensions

2010-12-13 Thread GHC
#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):

 Replying to [comment:14 simonpj]:
  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.

 I'll get ridd of it. I didn't like it anyway. :)

  Here you mean `guard` is looked up '''only''' for monad
 comprehensions, I assume?

 Yes.

  In other cases, the `guard` field stays as bottom?

 Yes.

  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 actually tried that, but I cannot typecheck that `(() . guard)`
 function in the typechecker using `tcSyntaxOp` since it results in some
 GHC panic error message on runtime. It's a bit difficult to reproduce
 right now since it requires quite a few changes - but if you think the
 exact error message would be helpful I can get it.

 However, I'm not sure if this is the right way to typecheck this
 expression, but using `tcMonoExpr` is obvisouly wrong and I didn't see any
 other usefull functions.

  Do you think you could write the documentation first?

 I'll work on that. Thanks for the examples.

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


Re: [GHC] #4370: Bring back monad comprehensions

2010-12-11 Thread GHC
#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):

 I finished the typechecker/desugarer on generators and guards for monad
 comprehensions
 ([http://blog.n-sch.de/2010/11/27/fun-with-monad-comprehensions/ Fun with
 monad comprehensions])
 and want to give you a quick summary on what
 I've done so far. If you have any concerns about those changes, please let
 me
 know.


 === main/DynFlags.lhs ===

  * New `MonadComprehensions` flag.


 === 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).

  * 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.


 === parser/Parser.y.pp ===

  * Whenever a list comprehension is found and `MonadComprehensions` is
 turned
on, the new `MonadComp` context is passed to the `HsDo` expression
 instead
of the old `ListComprehension` context.


 === 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`. This makes sure that we don't get `Not in scope: `guard'`
 error
messages inside other `HsDo` expressions, like do blocks or regular
 list
comprehensions.

 === typecheck/TcTcExpr.lhs ===

  * New rule in `tcDoStmts` for monad comprehensions. A complete new
typechecking function `tcMcStmt` is used to typecheck monad
 comprehension
statements. 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. `ParStmt`s will require an

  * The `body` (as in `[ body | .. ]`) is typechecked to the type `a` where
 the
resulting type of the whole monad comprehension is typechecked to type
 `m a`.
See the note on typechecking/desugaring below.


 === deSugar/DsExpr.lhs ===

  * New `dsMonadComp` function which is used to desugar monad
 comprehensions
into core expressions. I decided that it would be the easiest way to
 just
create a new typechecking rule and rewrite the whole desugaring part
 for
monad comprehensions since you cannot just translate monad
 comprehensions
into do-blocks/list comprehensions and reuse existing desugarers.
 However,
I was able to reuse (aka copy  paste) a lot of the existing desugaring
 code
of do-blocks (and mdo-blocks).


 === Typechecking/desugaring ===

 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.
 This `PostTcTable` is a list of typechecked functions and their names
 which can
 be used in the desugarer to build core expressions with those functions.
 This
 technic is already used with `MDoExpr`s (typecheck/TcMatches.lhs +276 
 deSugar/DsExpr.lhs +818), but I don't know if its the most elegant way to
 solve
 this issue. Any thoughts on this?

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


Re: [GHC] #4370: Bring back monad comprehensions

2010-11-27 Thread GHC
#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
-+--
Changes (by tyler):

 * cc: ty...@… (added)


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


Re: [GHC] #4370: Bring back monad comprehensions

2010-11-15 Thread GHC
#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
-+--
Changes (by igloo):

  * type:  bug = feature request
  * milestone:  = 7.2.1


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


Re: [GHC] #4370: Bring back monad comprehensions

2010-10-24 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  nsch
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by gidyn):

 * cc: gid...@… (added)


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


Re: [GHC] #4370: Bring back monad comprehensions

2010-10-15 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  nsch
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by nsch):

  * owner:  = nsch


Comment:

 Thank you for the detailed reply, Simon. I'm currently working for George
 and his research group and I'm going to take on this task in the next
 couple of weeks. Those advices will be a great help.

 - Nils Schweinsberg

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


Re: [GHC] #4370: Bring back monad comprehensions

2010-10-11 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by sebf):

 * cc: s...@… (added)


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


Re: [GHC] #4370: Bring back monad comprehensions

2010-10-07 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by nsch):

 * cc: m...@… (added)


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


[GHC] #4370: Bring back monad comprehensions

2010-10-06 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
 George Giorgidze writes: My colleagues and I are working on Haskell [http
 ://www-db.informatik.uni-tuebingen.de/files/weijers/IFL2010complete.pdf
 embedded DSL for data-intensive and data-parallel applications]. The idea
 is to provide the Haskell list prelude combinators to manipulate database-
 resident data. The combinators are not executed in Haskell runtime,
 instead they are compiled down to SQL, executed on relational database
 systems and the results are marshalled back to Haskell for further in-heap
 processing or generation of new database-able embedded programs.

 Although programming with the standard list processing combinators is
 feasible, the embedded programs are much more concisely formulated using
 the list comprehension notation, especially, when extended with
 [http://research.microsoft.com/en-us/um/people/simonpj/papers/list-comp/
 'order by' and 'group by' constructs].

 Unfortunately, in Haskell, the list comprehension notation is only
 available for processing lists.

 In order to support the list comprehension notation, we have built a
 quasiquter that desugars the list comprehension notation, but, instead of
 generating code using the Haskell list prelude combinators the quasiquter
 generates code that uses list processing combinators from our embedded
 language.

 Although the quasiquoting approach worked for us, it has a number of
 drawbacks:

   * Introduces extra syntactic noise
   * Error messages are hard to understand as they refer to enerated code
   * Needs to be re-implemented for every list-based embedded language

 One way to address the aforementioned drawbacks is to define our queries
 as a monad (similar to list monad) and use the monad comprehension
 notation. The do notation can be used but it is less suited for query
 languages.

 Unfortunately monad comprehensions were removed from Haskell, prior to
 Haskell 98. However, I think that the notation is extremely useful not
 only for lists, but for other list like data structures, list-based query
 languages (see above), maybe even for wider range of EDSLs and monads. I
 think the feature deserves to be supported at least as a GHC language
 extension.

 Thus, I would like to propose to design and implement the monad
 comprehension notation as a GHC language extension. I am willing to invest
 some time and contribute to this effort.

 One can also look at how recently introduced 'order by' and 'group by'
 constructs generalise to monad comprehensions. If that works, one could
 implement even more stylish monad comprehension notation.

 Feedback from GHC users and developers would be very much appreciated.

   * Do you think that this is a good idea?

   * Would you use monad comprehensions (if available) for your
 library/EDSL/application?

   * Do you think that it would be hard to integrate this extension into
 current GHC codebase?

   * Have you already thought about how to generalise 'order by' and 'group
 by' to monad comprehensions?

   * Have you already thought about how to address the original objections
 to the monad comprehension notation?

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


Re: [GHC] #4370: Bring back monad comprehensions

2010-10-06 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by simonpj):

 * cc: giorgi...@… (added)


Comment:

 Max replies:
  One can also look at how recently introduced 'order by' and 'group by'
  constructs generalise to monad comprehensions. If that works, one
  could implement even more stylish monad comprehension notation.

 They do: see the comments by Michael Adams at
 http://haskell.org/haskellwiki/Simonpj/Talk:ListComp. Last I checked, the
 code there was slightly buggy but correct in spirit.

 What ''doesn't'' generalise is the zip comprehensions extension:
 {{{
 [(x, y) | x - xs | y - ys] == zip xs ys
 }}}
 The required operator :: `m a - m b - m (a, b)` is that of the !ZipList
 applicative functor, not that of the standard applicative functor for
 lists. Probably to generalise this you need a new typeclass like this one
 (copied from my own library):
 {{{
 class Functor z = Zippable z where
 -- Naturality:
 --  fmap (first f)  (zip_ as bs) == zip_ (fmap f as) bs
 --  fmap (second f) (zip_ as bs) == zip_ as (fmap f bs)
 --
 -- Information preservation:
 --  fmap fst (zip_ as bs) == as
 --  fmap snd (zip_ as bs) == bs

 zip_ :: z a - z b - z (a, b)
 zip_ = zipWith_ (,)

 zipWith_ :: (a - b - c) - z a - z b - z c
 zipWith_ f as bs = fmap (uncurry f) (zip_ as bs)
 }}}
 It probably needs some extra laws to say how it interacts with the Monad
 operators.

   * Do you think that it would be hard to integrate this extension into
 current GHC codebase?

 Pretty easy IMHO. The list comprehensions are already half-set up for this
 job, and you should be able to reuse lots of the code that handles the
 monad notation desugaring.

   * Have you already thought about how to generalise 'order by' and
  'group by' to monad comprehensions?

 See above.

   * Have you already thought about how to address the original objections
 to
 the monad comprehension notation?

 I thought it was rejected because it caused newbies to get confusing type
 error messages: they expected *list* error messages but got errors
 mentioning a scary *Monad* thing. Personally I'm not sure how to solve
 that, but if it's only available as an extension this won't cause a
 problem.

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


Re: [GHC] #4370: Bring back monad comprehensions

2010-10-06 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by simonpj):

 Yes, I think this would be a reasonable thing to implement.  Provided it
 doesn't make the code in the compiler become horrid, I'd be happy to have
 this as a patch.  It should fit in quite smoothly, and should not affect
 people who don't use it.  (I'm assuming you intend it as a language
 extension. The original objections were indeed solely to do with
 unexpected error messages.)

 As Max says, much of the machinery is there already.  But there are quite
 a lot of deatils to think about.

  * In the '''renamer''', there is special case code for `mdo`, but
 otherwise list comprehensinos and do-notation is handled uniformly.  I
 think we've deprecated `mdo` in favour of `do {..rec..}`, which would mean
 we could get rid of the mdo code altogether, but I'm not sure we've
 reached consensus; see #4148.  Cleaning up this corner would be v helpful.

  * In the '''type checker''', there is special case code for list
 comprehensions, separate from do-notation.  You could simply use the do-
 notation code, but that would lose the `group by` and `zip` stuff, which
 only appears in the list comprehension code.  So you could:
* Disable the group-by stuff when supporting monad comprehensions; but
 that would be annoying when you really want to use group-by in the same
 module as a monad comprehension.
* Implement `group by` etc in the monad case too.  See Max's comments.

  * In the '''desugarer''' there is special desguaring code for list
 comprehensions, to get it into foldr/build form.  You could probably still
 get the same effect by steering the desugaring by the ''types'' rather the
 ''syntactic form'' of the comprehension.

 Things to watch out for

  * Rebindable syntax currently works for do-notation but not for list
 comprehensions.  A natural consequence of the change would be to support
 rebindable syntax for comprehensions too, which would be a good thing.

  * There is a parallel-array comprehension form too, also handled by the
 same code. eg `[: a+1 | a - as :]`.  We don't want to mess it up.

  * More surprisingly, guards on a function definition are ''also'' handled
 by the same code. Eg
 {{{
   f x | Just y - g x
   , y3
   = blah
 }}}
   Here the guards are just `Stmts`, where `Stmt` is the primitive
 component of a comprehension.  So again, we don't want to mess them up.

 I'm happy to advise on this project, but unlikely to take the initiative.

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


Re: [GHC] #4370: Bring back monad comprehensions

2010-10-06 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by ganesh):

 * cc: ganesh (added)


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


Re: [GHC] #4370: Bring back monad comprehensions

2010-10-06 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by ezyang):

 * cc: ezy...@… (added)


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


Re: [GHC] #4370: Bring back monad comprehensions

2010-10-06 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by jweijers):

 * cc: jeroen.weij...@… (added)


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


Re: [GHC] #4370: Bring back monad comprehensions

2010-10-06 Thread GHC
#4370: Bring back monad comprehensions
-+--
Reporter:  simonpj   |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.12.3  
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by bos):

 * cc: b...@… (added)


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