Re: [GHC] #836: rebindable if-then-else syntax

2011-02-28 Thread GHC
#836: rebindable if-then-else syntax
+---
  Reporter:  nibro  |  Owner:  igloo   
  Type:  feature request| Status:  closed  
  Priority:  normal |  Milestone:  _|_ 
 Component:  Compiler (Parser)  |Version:  7.0.1   
Resolution:  fixed  |   Keywords:  
  Testcase:  N/A|  Blockedby:  
Difficulty:  Unknown| Os:  Unknown/Multiple
  Blocking: |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown   |  
+---
Changes (by spl):

 * cc: leather@… (added)


-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2011-02-28 Thread GHC
#836: rebindable if-then-else syntax
+---
  Reporter:  nibro  |  Owner:  igloo   
  Type:  feature request| Status:  closed  
  Priority:  normal |  Milestone:  _|_ 
 Component:  Compiler (Parser)  |Version:  7.0.1   
Resolution:  fixed  |   Keywords:  
  Testcase:  N/A|  Blockedby:  
Difficulty:  Unknown| Os:  Unknown/Multiple
  Blocking: |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown   |  
+---

Comment(by simonpj):

 I think it may have to be CPP here.  No obvious alternative.

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2011-02-28 Thread GHC
#836: rebindable if-then-else syntax
+---
  Reporter:  nibro  |  Owner:  igloo   
  Type:  feature request| Status:  closed  
  Priority:  normal |  Milestone:  _|_ 
 Component:  Compiler (Parser)  |Version:  7.0.1   
Resolution:  fixed  |   Keywords:  
  Testcase:  N/A|  Blockedby:  
Difficulty:  Unknown| Os:  Unknown/Multiple
  Blocking: |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown   |  
+---
Changes (by Lemming):

 * cc: ghc@… (added)
  * version:  6.13 => 7.0.1


Comment:

 I develop NumericPrelude, that makes extensive use of rebinded number
 literals. I really appreciate separation of importing Prelude
 (NoImplicitPrelude) and rebindable syntax (RebindableSyntax). However, it
 seems that there is currently no way to write NumericPrelude in a way that
 it and its importers work on both GHC-6.12 and GHC-7.0. Any ideas other
 than CPP hacks?

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-11-12 Thread GHC
#836: rebindable if-then-else syntax
+---
  Reporter:  nibro  |  Owner:  igloo   
  Type:  feature request| Status:  closed  
  Priority:  normal |  Milestone:  _|_ 
 Component:  Compiler (Parser)  |Version:  6.13
Resolution:  fixed  |   Keywords:  
  Testcase:  N/A|  Blockedby:  
Difficulty:  Unknown| Os:  Unknown/Multiple
  Blocking: |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown   |  
+---
Changes (by igloo):

  * status:  patch => closed
  * resolution:  => fixed


Comment:

 This patch:
 {{{
 Fri Nov 12 13:00:11 GMT 2010  simo...@microsoft.com
   * A (final) re-engineering of the new typechecker
 }}}
 depended on this, so I ended up merging it.

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-22 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  igloo   
Type:  feature request|   Status:  patch   
Priority:  normal |Milestone:  _|_ 
   Component:  Compiler (Parser)  |  Version:  6.13
Keywords: | Testcase:  N/A 
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-
Changes (by simonpj):

  * owner:  SamAnklesaria => igloo


Comment:

 Thank you. I have reviewed, modified somewhat, and pushed.
 Main modifications were
  * Take advantage of the `Nothing` in `HsIf` to avoid having to consult
 the options flags
  * Use `RebindableSyntax` flag for all rebindable syntax
  * Add documentation

 The patches are these
 {{{
 Fri Oct 22 07:34:00 PDT 2010  simo...@microsoft.com
   * Add rebindable syntax for if-then-else

   There are two main changes

* New LANGUAGE option RebindableSyntax, which implies NoImplicitPrelude

* if-the-else becomes rebindable, with function name "ifThenElse"
  (but case expressions are unaffected)

   Thanks to Sam Anklesaria for doing most of the work here

 M ./compiler/cmm/CmmParse.y -2 +2
 M ./compiler/deSugar/Coverage.lhs -2 +2
 M ./compiler/deSugar/DsArrows.lhs -9 +15
 M ./compiler/deSugar/DsExpr.lhs -2 +8
 M ./compiler/deSugar/DsMeta.hs -2 +2
 M ./compiler/deSugar/Match.lhs -1 +1
 M ./compiler/hsSyn/Convert.lhs -2 +2
 M ./compiler/hsSyn/HsExpr.lhs -8 +19
 M ./compiler/hsSyn/HsUtils.lhs -2 +5
 M ./compiler/main/DynFlags.hs +4
 M ./compiler/parser/Parser.y.pp -1 +1
 M ./compiler/rename/RnEnv.lhs -5 +5
 M ./compiler/rename/RnExpr.lhs -8 +12
 M ./compiler/rename/RnNames.lhs -1 +1
 M ./compiler/typecheck/Inst.lhs -2 +2
 M ./compiler/typecheck/TcArrows.lhs -6 +12
 M ./compiler/typecheck/TcExpr.lhs -5 +15
 M ./compiler/typecheck/TcHsSyn.lhs -9 +7
 M ./compiler/typecheck/TcRnTypes.lhs +2
 M ./docs/users_guide/flags.xml +6
 M ./docs/users_guide/glasgow_exts.xml -2 +10

 -- base package
 Fri Oct 22 07:31:57 PDT 2010  simo...@microsoft.com
   * Remove redundant imports, now that NoImplicitPrelude does not imply
 RebindableSyntax

 M ./Control/OldException.hs -1
 M ./Data/Dynamic.hs -1
 M ./Data/Typeable.hs -1 +1
 M ./Foreign/Marshal/Alloc.hs -1
 M ./GHC/Conc/IO.hs -1
 M ./GHC/Conc/Signal.hs -1
 M ./GHC/Conc/Sync.lhs -1
 M ./GHC/ForeignPtr.hs -1
 M ./GHC/IO/Handle/FD.hs -1
 M ./GHC/Pack.lhs -1
 M ./GHC/ST.lhs -1
 M ./GHC/Unicode.hs -1
 M ./System/Event/Control.hs -1
 M ./System/Event/Manager.hs -1 +1
 M ./System/Timeout.hs -1

 -- testsuite
 Fri Oct 22 07:30:53 PDT 2010  simo...@microsoft.com
   * Use the RebindableSyntax flag, not NoImplicitPrelude

 M ./tests/ghc-regress/rebindable/DoParamM.hs -1 +1
 M ./tests/ghc-regress/rebindable/DoRestrictedM.hs -1 +1
 M ./tests/ghc-regress/rebindable/T303.hs -1 +1
 M ./tests/ghc-regress/rebindable/rebindable1.hs -1 +1
 M ./tests/ghc-regress/rebindable/rebindable2.hs -1 +1
 M ./tests/ghc-regress/rebindable/rebindable3.hs -1 +1
 M ./tests/ghc-regress/rebindable/rebindable4.hs -1 +1
 M ./tests/ghc-regress/rebindable/rebindable5.hs -1 +1
 M ./tests/ghc-regress/rebindable/rebindable6.hs -1 +1
 M ./tests/ghc-regress/rebindable/rebindable7.hs -1 +1
 M ./tests/ghc-regress/rebindable/rebindable8.hs -1 +1
 M ./tests/ghc-regress/rebindable/rebindable9.hs -1 +1

 Thu Oct 21 15:06:35 PDT 2010  am...@amsay.net
   * trac #836 tests

 M ./tests/ghc-regress/rebindable/all.T +1
 A ./tests/ghc-regress/rebindable/rebindable10.hs
 A ./tests/ghc-regress/rebindable/rebindable10.stdout
 }}}
 I'm agnostic about whether to slip this into 7.0

 Simon

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-21 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  patch
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-
Changes (by SamAnklesaria):

  * status:  new => patch


-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-21 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by malcolm.wall...@…):

 Just to note that, in any eventuality, !RebindableIfStatements is
 certainly the wrong name, since these are not statements, but expressions.

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-21 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by simonpj):

 My thoughts

  * Like igloo, I would much prefer a `RebindableSyntax` flag (using
 `ImplicitPrelude` is anyway a hack) than one for 'if' alone.  I really
 don't want `RebindableIf`.

  * There is no difficulty with using the old typing rule for `if` when
 `RebindableSyntax` is off, and the new one when it is on. (That isn't the
 way other rebindable syntax is done, but it doesn't matter.)  Doing that
 means that the Prelude doesn't need to export `ifThenElse`

  * Many libraries use if, but few (none?) use both (a) rebindable syntax
 and (b) `if` with an unlifted return type. That would be the unsupported
 combination under the new scheme.  But there's a way out in that case: use
 `case`.

 In short, my proposal is:
  * Add `RebindableSyntax` flag. (It might imply `NoImplicitPrelude`.)
  * Choose which typing rule to use for `if` based on the flag

 Simon

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-20 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by igloo):

 Replying to [comment:26 SamAnklesaria]:
 > As there are many libraries that use `if` syntax where a polymorphic
 function would not suffice, I've decided to make rebindable syntax only
 accessible through a language extension flag (currently named
 RebindableIfStatements).

 I think it would be better to have a `RebindableSyntax` extension, and to
 make the other rebindable syntaxes use it too, rather than
 `NoImplicitPrelude`.

 > While the function `ifThenElse` is a part of the Prelude regardless

 It should probably be in `GHC.Exts` rather than `Prelude`, and might be
 worth a library proposal to put it somewhere more public (Not sure where;
 maybe `Data.Function`?).

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-20 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by SamAnklesaria):

 As there are many libraries that use `if` syntax where a polymorphic
 function would not suffice, I've decided to make rebindable syntax only
 accessible through a language extension flag (currently named
 RebindableIfStatements). While the function `ifThenElse` is a part of the
 Prelude regardless, it is not substituted for `if` statements unless
 RebindableIfStatements is on.

 Is this okay?

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-18 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by simonpj):

 No, the `base` library does not use rebindable syntax.  But it does need
 `-fno-implicit-prelude` because when compiling the base library the
 `Prelude` does not yet exist!   So it's ok to use non-rebindable syntax in
 `base`.

 Simon

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-18 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by isaacdupree):

 As SamAnklesaria noted, where using rebindable syntax, it'll still be
 possible to use "case" directly to accomplish primitive "if" / unboxed
 results, if both rebindable and unboxed-if are needed in the same module.
 SimonPJ, so the base library certainly needs not to implicitly import the
 Prelude -- but is it truly okay for it to use non-rebindable syntax? (we
 know currently that it compiles and runs correctly with rebindable
 syntax.)  I guess we'll see.

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-18 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by simonpj):

 There's no decent way out of this.If one argument to `ifThenElse` is a
 `Double#` it would be passed in a different register than if it was a
 pointer.  So no single blob of code for `ifThenElse` will do.  That's why
 GHC doesn't allow parametric polymorphism for unboxed types.

 I think the best we can do is to say that if rebindable syntax is off, we
 use the old if-then-else typing rule, and if it's on we use the new one.
 Sadly that means that if you want rebindable syntax you can't use if-then-
 else with an unboxed result type.

 Moreover, currently rebindable syntax is invoked by `-fno-implicit-
 prelude` (a rather odd flag to invoke it), and that in turn is necessarily
 used in compiling the `base` library.  So we'd have to separate the two
 flags, which is probably a good thing anyway.

 It's not easy to choose which path to take based on the type of the
 alternatives, because the choice has to be made during typechecking, when
 the type of the alternatives is itself being worked out.  Also it'd be
 very odd to have two different ways of typing `if`.

 Simon

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-16 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by batterseapower):

 Maybe you could only use the ifThenElse if the type of the if branches has
 a lifted kind?

 Alternatively:

 {{{
 if e1 then e2 :: Int# else e3 :: Int# ==> case (ifThenElse e1 True False)
 of True -> e2; False -> e2
 }}}

 However, I'm not sure if this is a useful translation. It might be clearer
 if I knew what the use cases for rebindable ifThenElse were.

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-15 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by SamAnklesaria):

 I've come across a problem with making `if` syntax into a function. Many
 uses from GHC's base library are for branches with kind # that don't match
 the * kind expected by my polymorphic `ifThenElse` function. I could
 switch all such occurrences to `case` statements, but that wouldn't
 prevent other libraries from having the same problems. Is there any way to
 make polymorphic (Bool -> a -> a -> a) functions handle things like Int#?
 I'm kinda stuck. Thanks.

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-13 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by simonpj):

 Sam: yes, adding a `SyntaxExpr` to `HsIf` sounds just right.

 Maybe `ifThenElse` rather than `if_then_else`?  More consistent with thre
 rest of the Haskell libraries.

 Simon

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-12 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by dherington):

 I'd like to lobby against using `cond` as the magic name of the function.
 I don't like preempting such a useful (and commonly used) name.  (Plus,
 for those of us who know Lisp, we'd expect `cond` to have a different
 type, probably `[(Bool, a)] -> a -> a`.)  I would suggest `if_then_else`.

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-12 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by SamAnklesaria):

 I intend to make `if` use whichever `cond` is in scope, as in the original
 suggestion. As I understand it, the `>>=` used in `do` notation is stored
 as a `SyntaxExpr` contained in the various types used by do notation. I'll
 give `HsIf` an extra field for a `SyntaxExpr` giving the `cond` function
 used.

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-12 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by batterseapower):

 If you use rebindable syntax then GHC will use whatever (>>=) and return
 operators are in scope at the site of the "do" notation. Those operators
 do not necessarily have to be part of a typeclass -- you are free to give
 them monomorphic types if you so wish.

 {{{
 {-# LANGUAGE NoImplicitPrelude #-}

 import Prelude (fromInteger, print, error)

 foo = let _ >>= _ = ">>="
   _ >> _ = ">>"
   return _ = "return"
   fail = error
   in (do { x <- return 1; return 3 }, do { return 3 }, do { return 1;
 return 3 } )

 main = print foo
 }}}

 Results in

 {{{
 (">>=","return",">>")
 }}}

 See the users guide at
 http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/syntax-extns.html
 #rebindable-syntax.

 Simon is just arguing that the same principle should apply here.

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-12 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by vivian):

 I'm not arguing about simonpj's decision directly above.

 I am curious though, doesn't `do' notation require overloaded bind and
 return which are members of a typeclass?

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-12 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-

Comment(by simonpj):

 Sam, you've taken ownership -- great!  Before invsting time in
 implementing something, do please sketch the design you propose to
 implement.

 I strongly suggest treating if-then-else exactly like other rebindable
 syntax, and ''not'' the type-cless stuff that vivian suggested.  (A user
 can always import an overloaded `cond`.)

 There's also the minor but important issue of what to call the rebindable
 identifier: `cond` or `ifThenElse`.  I don't feel strongly.

 Simon

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-10-11 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  SamAnklesaria
Type:  feature request|   Status:  new  
Priority:  normal |Milestone:  _|_  
   Component:  Compiler (Parser)  |  Version:  6.13 
Keywords: | Testcase:  N/A  
   Blockedby: |   Difficulty:  Unknown  
  Os:  Unknown/Multiple   | Blocking:   
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown 
--+-
Changes (by SamAnklesaria):

  * owner:  => SamAnklesaria


-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-09-14 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  
Type:  feature request|   Status:  new 
Priority:  normal |Milestone:  _|_ 
   Component:  Compiler (Parser)  |  Version:  6.13
Keywords: | Testcase:  N/A 
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by nibro):

 To clarify my original proposal:

 I want {{{if e then a else b}}} to translate to {{{cond e a b}}} for
 whatever {{{cond}}} is in scope, whatever its type. A pure syntactic
 interpretation, making no semantic considerations whatsoever, exactly as
 simonpj writes in
 [http://hackage.haskell.org/trac/ghc/ticket/836#comment:6 comment 6].

 I don't want to involve {{{case}}} in this, as I consider {{{case}}} to be
 more primitive. The whole point of the proposal is that {{{if e then a
 else b}}} should ''not'' be equal to
 {{{
 cond e a b = case e of
True -> a
False -> b
 }}}
 This should be the default (Prelude) implementation of {{{cond}}}, nothing
 more.

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-09-14 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  
Type:  feature request|   Status:  new 
Priority:  normal |Milestone:  _|_ 
   Component:  Compiler (Parser)  |  Version:  6.13
Keywords: | Testcase:  N/A 
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by simonpj):

 Well I don't know how to give `cond` two types, ''regardless'' of how
 rebindable syntax is handled!

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-09-14 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  
Type:  feature request|   Status:  new 
Priority:  normal |Milestone:  _|_ 
   Component:  Compiler (Parser)  |  Version:  6.13
Keywords: | Testcase:  N/A 
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by vivian):

 Yes, I apologise, I have made a mistake.

 Because I want my overloaded function `cond` to have types:
 {{{
 cond :: Bool -> a -> a -> a
 cond :: et b -> (b -> et a) -> et a -> et a
 }}}
 depending on whether the return (final) type is `a` (default) or `et a ~
 ErrorT e m a`.

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-09-14 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  
Type:  feature request|   Status:  new 
Priority:  normal |Milestone:  _|_ 
   Component:  Compiler (Parser)  |  Version:  6.13
Keywords: | Testcase:  N/A 
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by simonpj):

 Well, it's true that there can be only one `cond` in scope, but it can
 have an overloaded type. You suggested
 {{{
  cond :: IfThenElse a => Bool -> a -> a -> a
 }}}
 Very well, define your class etc in `MyCondModule` and import that
 overloaded `cond`.

 Simon

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-09-14 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  
Type:  feature request|   Status:  new 
Priority:  normal |Milestone:  _|_ 
   Component:  Compiler (Parser)  |  Version:  6.13
Keywords: | Testcase:  N/A 
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by vivian):

 Great!

 What is not yet clear to me (a relative ghc non-cognito), is that the
 "overloaded type" of `cond` can be bound to one function:
 {{{
 cond  :: Boot -> t -> t -> t -- standard `case Bool of`
 equivalent
 cond' :: Bool -> Int -> Char -> Foo  -- arbitrary user instantiation
 condition :: (Error e, Monad m)  -- slightly different type
 signature
   => ErrorT e m b -> (b -> ErrorT e m a) -> ErrorT e m a -> Error
 T e m a
 }}}
 (Note there was an error in the previous type signature for the first
 argument of condition)

 With respect to the pedantics of function names, I think that
 `if_then_else` is more indicative (visually and semantically) of the "if
 ... then ... else ..." construct than `cond`.  (I defer to historical
 arguments over CamelCase versus under_score versus ifthenelse).

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-09-13 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  
Type:  feature request|   Status:  new 
Priority:  normal |Milestone:  _|_ 
   Component:  Compiler (Parser)  |  Version:  6.13
Keywords: | Testcase:  N/A 
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by simonpj):

 But "the" `cond` that is in scope could be overloaded, if you made it so.
 Just say
 {{{
 import MyCondModule( cond )
 }}}
 and if `MyCondModule.cond` has an overloaded type then that's what'll
 happen. In short, your desire is just a special case of "use whatever
 `cond` is in scope".

 OK, I think I'm happy to implement this.

 Hmm.  Do we call it `cond` or `ifthenelse`?

 Simon

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-09-13 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  
Type:  feature request|   Status:  new 
Priority:  normal |Milestone:  _|_ 
   Component:  Compiler (Parser)  |  Version:  6.13
Keywords: | Testcase:  N/A 
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by vivian):

 I think of 'if then else' as less fundamental than 'case' and so the last
 point seems to not be a problem.

 If "if then else" is bound to '''the''' in scope variable 'cond' then 'if
 then else' can't be used in two different ways in the same module, which
 is why I suggested class overloading, which can select the appropriate
 instance from the return type in the context.

 LogicT defines a 'soft cut', which is similar to
 {{{
 condition :: (Error e, Monad m)
   => ErrorT e m a -> (b -> ErrorT e m a) -> ErrorT e m a -> Error
 T e m a
 condition e1 e2 e3 = ErrorT $ do
   b <- runErrrorT e1
   case b of
  Left _   -> runErrorT e3
  Right b' -> runErrorT (e2 b')
 }}}
 and it would nice to be able to rebind this to "if then else"

 A contrived example:
 {{{
 loadDefaults filename = if (openFile filename)
then (\handle -> do
 version <- loadConfiguration
 handle
 if version < 2
then addNewFeatures
else $ return ())
else defaultConfiguration
 }}}

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-09-09 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  
Type:  feature request|   Status:  new 
Priority:  normal |Milestone:  _|_ 
   Component:  Compiler (Parser)  |  Version:  6.13
Keywords: | Testcase:  N/A 
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-

Comment(by simonpj):

 The main ticket is, I believe, suggesting that when rebindable syntax is
 enabled, then whenever GHC sees
 {{{
 if e1 then e2 else e3
 }}}
 it behaves precisely as if you'd written
 {{{
 cond e1 e2 e3
 }}}
 from ''both'' the point of view of typechecking, ''and'' the point of view
 of desugaring.  So, for example if
 {{{
 cond :: Bool -> Int -> Char
 }}}
 then you could write
 {{{
 if x>y then 3 else 'c'
 }}}
 That seems entirely feasible to me.   The question of overloading then
 becomes quite orthogonal.  For example, if the imported `cond` had this
 type:
 {{{
 cond :: IfThenElse a => Bool -> a -> a -> a
 }}}
 then that'd be fine.  The term `if e1 then e2 else e3` would typecheck and
 desugar as if you'd written `cond e1 e2 e3`.  I think that would satisfy
 vivian without any need for special support.

 My main question is this: what about `case`?  The proposal would mean that
 `if-then-else` was different to
 {{{
 case e1 of
   True -> e2
   False -> e3
 }}}
 Maybe that's ok.  Maybe it's even desirable.  But I don't see how to
 generalise the story to case expressions, at least not without a lot more
 elaboration.

 Simon

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2010-09-04 Thread GHC
#836: rebindable if-then-else syntax
--+-
Reporter:  nibro  |Owner:  
Type:  feature request|   Status:  new 
Priority:  normal |Milestone:  _|_ 
   Component:  Compiler (Parser)  |  Version:  6.13
Keywords: | Testcase:  N/A 
   Blockedby: |   Difficulty:  Unknown 
  Os:  Unknown/Multiple   | Blocking:  
Architecture:  Unknown/Multiple   |  Failure:  None/Unknown
--+-
Changes (by vivian):

 * cc: haskell.vivian.mcph...@… (added)
  * failure:  => None/Unknown
  * version:  6.4.2 => 6.13
  * component:  Compiler => Compiler (Parser)


Comment:

 The do notation is syntactic sugar on top of (>>=) and return.

 Why not syntactic sugar for "if ... then ... else."

 With language Extension 'OverlappingInstances' it is possible to have a
 default definition

 {{{
 class IfThenElse a where
 if_then_else :: Bool -> a -> a -> a

 instance IfThenElse a where
 if_then_else b t f = case b of
True  -> t
False -> f
 }}}

 And then monads such as LogicT
 [http://hackage.haskell.org/package/logict-0.2.1] and other code regions
 with a requirement for custom ifte can overload their own.

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2008-11-27 Thread GHC
#836: rebindable if-then-else syntax
-+--
Reporter:  nibro |Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  _|_ 
   Component:  Compiler  |  Version:  6.4.2   
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:  N/A   |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by PHO):

 * cc: [EMAIL PROTECTED] (added)

-- 
Ticket URL: 
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] #836: rebindable if-then-else syntax

2006-10-21 Thread GHC
#836: rebindable if-then-else syntax
-+--
 Reporter:  nibro|  Owner: 
 Type:  feature request  | Status:  new
 Priority:  normal   |  Milestone:  _|_
Component:  Compiler |Version:  6.4.2  
 Severity:  normal   | Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:  N/A  |   Architecture:  Unknown
   Os:  Unknown  |  
-+--
Changes (by igloo):

  * milestone:  => _|_
  * testcase:  => N/A

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs