Re: [GHC] #1702: type operator precedences don't work in contexts

2009-04-11 Thread GHC
#1702: type operator precedences don't work in contexts
--+-
Reporter:  b.hil...@ntlworld.com  |Owner:  
Type:  bug|   Status:  new 
Priority:  normal |Milestone:  6.12 branch 
   Component:  Compiler   |  Version:  6.8 
Severity:  normal |   Resolution:  
Keywords: |   Difficulty:  Unknown 
Testcase: |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   |  
--+-
Changes (by igloo):

  * milestone:  6.10 branch = 6.12 branch

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1702#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] #1702: type operator precedences don't work in contexts

2007-11-13 Thread GHC
#1702: type operator precedences don't work in contexts
---+
 Reporter:  [EMAIL PROTECTED]  |  Owner: 
 Type:  bug| Status:  new
 Priority:  normal |  Milestone:  6.10 branch
Component:  Compiler   |Version:  6.8
 Severity:  normal | Resolution: 
 Keywords: | Difficulty:  Unknown
 Testcase: |   Architecture:  Multiple   
   Os:  Multiple   |  
---+
Changes (by simonmar):

  * os:  MacOS X = Multiple
  * architecture:  powerpc = Multiple

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1702#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] #1702: type operator precedences don't work in contexts

2007-09-24 Thread GHC
#1702: type operator precedences don't work in contexts
--+-
Reporter:  [EMAIL PROTECTED]  |Owner: 
Type:  bug|   Status:  new
Priority:  normal |Milestone:  6.10 branch
   Component:  Compiler   |  Version:  6.8
Severity:  normal |   Resolution: 
Keywords: |   Difficulty:  Unknown
  Os:  MacOS X| Testcase: 
Architecture:  powerpc|  
--+-
Comment (by simonpj):

 See also #1727

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1702
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] #1702: type operator precedences don't work in contexts

2007-09-18 Thread GHC
#1702: type operator precedences don't work in contexts
--+-
Reporter:  [EMAIL PROTECTED]  |Owner: 
Type:  bug|   Status:  new
Priority:  normal |Milestone:  6.10   
   Component:  Compiler   |  Version:  6.8
Severity:  normal |   Resolution: 
Keywords: |   Difficulty:  Unknown
  Os:  MacOS X| Testcase: 
Architecture:  powerpc|  
--+-
Changes (by igloo):

  * milestone:  = 6.10

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1702
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] #1702: type operator precedences don't work in contexts

2007-09-17 Thread GHC
#1702: type operator precedences don't work in contexts
+---
  Reporter:  [EMAIL PROTECTED]  |  Owner: 
  Type:  bug| Status:  new
  Priority:  normal |  Milestone: 
 Component:  Compiler   |Version:  6.8
  Severity:  normal |   Keywords: 
Difficulty:  Unknown| Os:  MacOS X
  Testcase: |   Architecture:  powerpc
+---
Type contexts don't parse correctly when a type class is used infix. The
 following example:

 infixr 4 :=:
 infixl 3 :+:
 infix 2 `Disjoint`
 
 labelZip :: (n :=: a `Disjoint` m :=: b) = n - m - [a] - [b] -
 [n :=: a :+: m :=: b]

 gives the error:

 Type constructor `:=:' used as a class
 In the type `(:=: n (a Disjoint (m :=: b))) =
  n - m - [a] - [b] - [(n :=: a) :+: (m :=: b)]'
 In the type signature for `labelZip':
   labelZip :: (:=: n (a Disjoint (m :=: b))) =
   n - m - [a] - [b] - [(n :=: a) :+: (m :=: b)]

 where the parenthesised version works.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1702
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] #1702: type operator precedences don't work in contexts

2007-09-17 Thread GHC
#1702: type operator precedences don't work in contexts
--+-
Reporter:  [EMAIL PROTECTED]  |Owner: 
Type:  bug|   Status:  new
Priority:  normal |Milestone: 
   Component:  Compiler   |  Version:  6.8
Severity:  normal |   Resolution: 
Keywords: |   Difficulty:  Unknown
  Os:  MacOS X| Testcase: 
Architecture:  powerpc|  
--+-
Old description:

 Type contexts don't parse correctly when a type class is used infix. The
 following example:

 infixr 4 :=:
 infixl 3 :+:
 infix 2 `Disjoint`
 
 labelZip :: (n :=: a `Disjoint` m :=: b) = n - m - [a] - [b] -
 [n :=: a :+: m :=: b]

 gives the error:

 Type constructor `:=:' used as a class
 In the type `(:=: n (a Disjoint (m :=: b))) =
  n - m - [a] - [b] - [(n :=: a) :+: (m :=: b)]'
 In the type signature for `labelZip':
   labelZip :: (:=: n (a Disjoint (m :=: b))) =
   n - m - [a] - [b] - [(n :=: a) :+: (m :=: b)]

 where the parenthesised version works.

New description:

 Type contexts don't parse correctly when a type class is used infix. The
 following example:
 {{{
 infixr 4 :=:
 infixl 3 :+:
 infix 2 `Disjoint`
 
 labelZip :: (n :=: a `Disjoint` m :=: b) = n - m - [a] - [b] -
 [n :=: a :+: m :=: b]
 }}}
 gives the error:
 {{{
 Type constructor `:=:' used as a class
 In the type `(:=: n (a Disjoint (m :=: b))) =
  n - m - [a] - [b] - [(n :=: a) :+: (m :=: b)]'
 In the type signature for `labelZip':
   labelZip :: (:=: n (a Disjoint (m :=: b))) =
   n - m - [a] - [b] - [(n :=: a) :+: (m :=: b)]
 }}}
 where the parenthesised version works.

Comment (by simonpj):

 Absolutely right, good report.

 It's really a structural flaw with historical origins.  Infix expressions
 (including types) are sorted out by the ''renamer'' not the ''parser''.
 This is a Good Thing.  However, before the advent of infixity in types,
 the ''parser'' decides what the class is in the context of a type
 signature.  But with infix stuff, the parser can't do that.

 Solution: defer the unravelling of contexts until the renamer, removing it
 from the parser.  I'll get to this but not until after ICFP.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1702
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] #1702: type operator precedences don't work in contexts

2007-09-17 Thread GHC
#1702: type operator precedences don't work in contexts
--+-
Reporter:  [EMAIL PROTECTED]  |Owner: 
Type:  bug|   Status:  new
Priority:  normal |Milestone: 
   Component:  Compiler   |  Version:  6.8
Severity:  normal |   Resolution: 
Keywords: |   Difficulty:  Unknown
  Os:  MacOS X| Testcase: 
Architecture:  powerpc|  
--+-
Old description:

 Type contexts don't parse correctly when a type class is used infix. The
 following example:
 {{{
 infixr 4 :=:
 infixl 3 :+:
 infix 2 `Disjoint`
 
 labelZip :: (n :=: a `Disjoint` m :=: b) = n - m - [a] - [b] -
 [n :=: a :+: m :=: b]
 }}}
 gives the error:
 {{{
 Type constructor `:=:' used as a class
 In the type `(:=: n (a Disjoint (m :=: b))) =
  n - m - [a] - [b] - [(n :=: a) :+: (m :=: b)]'
 In the type signature for `labelZip':
   labelZip :: (:=: n (a Disjoint (m :=: b))) =
   n - m - [a] - [b] - [(n :=: a) :+: (m :=: b)]
 }}}
 where the parenthesised version works.

New description:

 Type contexts don't parse correctly when a type class is used infix. The
 following example:
 {{{
 infixr 4 :=:
 infixl 3 :+:
 infix 2 `Disjoint`
 
 labelZip :: (n :=: a `Disjoint` m :=: b)
  = n - m - [a] - [b] - [n :=: a :+: m :=: b]
 }}}
 gives the error:
 {{{
 Type constructor `:=:' used as a class
 In the type `(:=: n (a Disjoint (m :=: b))) =
  n - m - [a] - [b] - [(n :=: a) :+: (m :=: b)]'
 In the type signature for `labelZip':
   labelZip :: (:=: n (a Disjoint (m :=: b))) =
   n - m - [a] - [b] - [(n :=: a) :+: (m :=: b)]
 }}}
 where the parenthesised version works.

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