Re: [GHC] #7395: DefaultSignatures conflict with default implementations

2012-11-19 Thread GHC
#7395: DefaultSignatures conflict with default implementations
--+-
Reporter:  cgaebel|   Owner:   
Type:  feature request|  Status:  new  
Priority:  normal |   Milestone:   
   Component:  Compiler   | Version:  7.6.1
Keywords:  DefaultSignatures  |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple   | Failure:  GHC rejects valid program
  Difficulty:  Unknown|Testcase:   
   Blockedby: |Blocking:   
 Related:  7346   |  
--+-
Changes (by PHO):

 * cc: pho@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7395#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] #7395: DefaultSignatures conflict with default implementations

2012-11-13 Thread GHC
#7395: DefaultSignatures conflict with default implementations
--+-
Reporter:  cgaebel|   Owner:   
Type:  bug|  Status:  new  
Priority:  normal |   Milestone:   
   Component:  Compiler   | Version:  7.6.1
Keywords:  DefaultSignatures  |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple   | Failure:  GHC rejects valid program
  Difficulty:  Unknown|Testcase:   
   Blockedby: |Blocking:   
 Related:  7346   |  
--+-

Comment(by simonpj):

 See email debate here
 [http://www.haskell.org/pipermail/libraries/2012-November/018750.html]

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7395#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] #7395: DefaultSignatures conflict with default implementations

2012-11-13 Thread GHC
#7395: DefaultSignatures conflict with default implementations
--+-
Reporter:  cgaebel|   Owner:   
Type:  feature request|  Status:  new  
Priority:  normal |   Milestone:   
   Component:  Compiler   | Version:  7.6.1
Keywords:  DefaultSignatures  |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple   | Failure:  GHC rejects valid program
  Difficulty:  Unknown|Testcase:   
   Blockedby: |Blocking:   
 Related:  7346   |  
--+-
Changes (by simonpj):

  * type:  bug = feature request


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7395#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] #7395: DefaultSignatures conflict with default implementations

2012-11-12 Thread GHC
#7395: DefaultSignatures conflict with default implementations
--+-
Reporter:  cgaebel|   Owner:   
Type:  bug|  Status:  new  
Priority:  normal |   Milestone:   
   Component:  Compiler   | Version:  7.6.1
Keywords:  DefaultSignatures  |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple   | Failure:  GHC rejects valid program
  Difficulty:  Unknown|Testcase:   
   Blockedby: |Blocking:   
 Related:  7346   |  
--+-
Changes (by dreixel):

  * related:  = 7346


Comment:

 Replying to [comment:7 hvr]:
  just a thought:
 
  ...what if the default-signature implementation would be only selectable
 by using the `deriving` facilities for auto-derivable classes?

 I can see the advantages, but there are also some problems. First, it only
 works if ALL the methods of the class have defaults (with signature or
 not). Second, when using normal deriving (not standalone) the compiler has
 to figure out the context for the instance, and this is not easy in
 general...

 See also #7346.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7395#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] #7395: DefaultSignatures conflict with default implementations

2012-11-11 Thread GHC
#7395: DefaultSignatures conflict with default implementations
--+-
Reporter:  cgaebel|   Owner:   
Type:  bug|  Status:  new  
Priority:  normal |   Milestone:   
   Component:  Compiler   | Version:  7.6.1
Keywords:  DefaultSignatures  |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple   | Failure:  GHC rejects valid program
  Difficulty:  Unknown|Testcase:   
   Blockedby: |Blocking:   
 Related: |  
--+-
Changes (by basvandijk):

 * cc: v.dijk.bas@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7395#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] #7395: DefaultSignatures conflict with default implementations

2012-11-09 Thread GHC
#7395: DefaultSignatures conflict with default implementations
--+-
Reporter:  cgaebel|   Owner:   
Type:  bug|  Status:  new  
Priority:  normal |   Milestone:   
   Component:  Compiler   | Version:  7.6.1
Keywords:  DefaultSignatures  |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple   | Failure:  GHC rejects valid program
  Difficulty:  Unknown|Testcase:   
   Blockedby: |Blocking:   
 Related: |  
--+-

Comment(by hvr):

 just a thought:

 ...what if the default-signature implementation would be only selectable
 by using the `deriving` facilities for auto-derivable classes? I.e. by
 using

 {{{
 #!hs
 data A = A { unA :: Int }
 deriving (Generic,Klass)
 }}}
 or
 {{{
 #!hs
 data A = A { unA :: Int }
 deriving Generic

 deriving instance Klass A
 }}}

 would both result in `A` getting the default-signature based
 implementation, wheras

 {{{
 #!hs
 data A = A { unA :: Int }
 deriving Generic

 instance Klass A
 }}}

 would get the ordinary default implementation (as if the default-
 signature implementation wasn't there). Wouldn't this help the issue at
 hand by making the choice explicit?

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


Re: [GHC] #7395: DefaultSignatures conflict with default implementations

2012-11-09 Thread GHC
#7395: DefaultSignatures conflict with default implementations
--+-
Reporter:  cgaebel|   Owner:   
Type:  bug|  Status:  new  
Priority:  normal |   Milestone:   
   Component:  Compiler   | Version:  7.6.1
Keywords:  DefaultSignatures  |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple   | Failure:  GHC rejects valid program
  Difficulty:  Unknown|Testcase:   
   Blockedby: |Blocking:   
 Related: |  
--+-

Comment(by cgaebel):

 +1 to hvr's idea. This would have the additional (very awesome) benefit of
 allowing the deriving of Show, Read, Eq, Ord, etc. to be implemented in a
 library (Prelude?) instead of living as compiler magic.

 This bug just got a whole lot more exciting.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7395#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] #7395: DefaultSignatures conflict with default implementations

2012-11-08 Thread GHC
#7395: DefaultSignatures conflict with default implementations
--+-
Reporter:  cgaebel|   Owner:   
Type:  bug|  Status:  new  
Priority:  normal |   Milestone:   
   Component:  Compiler   | Version:  7.6.1
Keywords:  DefaultSignatures  |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple   | Failure:  GHC rejects valid program
  Difficulty:  Unknown|Testcase:   
   Blockedby: |Blocking:   
 Related: |  
--+-
Changes (by hvr):

 * cc: hvr@… (added)


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


Re: [GHC] #7395: DefaultSignatures conflict with default implementations

2012-11-05 Thread GHC
#7395: DefaultSignatures conflict with default implementations
--+-
Reporter:  cgaebel|   Owner:   
Type:  bug|  Status:  new  
Priority:  normal |   Milestone:   
   Component:  Compiler   | Version:  7.6.1
Keywords:  DefaultSignatures  |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple   | Failure:  GHC rejects valid program
  Difficulty:  Unknown|Testcase:  http://hpaste.org/77290  
   Blockedby: |Blocking:   
 Related: |  
--+-
Changes (by simonpj):

  * difficulty:  = Unknown


Comment:

 You did not attach a test case!

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7395#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] #7395: DefaultSignatures conflict with default implementations

2012-11-05 Thread GHC
#7395: DefaultSignatures conflict with default implementations
--+-
Reporter:  cgaebel|   Owner:   
Type:  bug|  Status:  new  
Priority:  normal |   Milestone:   
   Component:  Compiler   | Version:  7.6.1
Keywords:  DefaultSignatures  |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple   | Failure:  GHC rejects valid program
  Difficulty:  Unknown|Testcase:  http://hpaste.org/77290  
   Blockedby: |Blocking:   
 Related: |  
--+-

Comment(by tibbe):

 A test case is linked under the Test Case attribute above. Here's the
 same test case, inlined:

 {{{
 {-# LANGUAGE DefaultSignatures, TypeOperators, FlexibleContexts,
 DeriveGeneric #-}
 module Main ( main ) where

 import GHC.Generics

 class Klass a where
 func :: a - Int
 func _ = 0

 -- This implementation is incompatible with the one above. What should
 -- happen instead is that this instance is selected whenever
 availible,
 -- and the one above should be used as a fallback.
 default func :: (Generic a, GKlass (Rep a)) = a - Int
 func = gfunc . from

 class GKlass f where
 gfunc :: f a - Int

 instance GKlass U1 where
  gfunc _ = 0

 instance Klass a = GKlass (K1 i a) where
 gfunc = (+1) . func . unK1

 instance GKlass a = GKlass (M1 i c a) where
 gfunc = gfunc . unM1

 instance (GKlass a, GKlass b) = GKlass (a :*: b) where
 gfunc (x :*: y) = 1 + gfunc x + gfunc y

 instance (GKlass a, GKlass b) = GKlass (a :+: b) where
 gfunc (L1 x) = 1 + gfunc x
 gfunc (R1 x) = 1 + gfunc x

 instance Klass Int where
 func = id

 data A = A { unA :: Int }
 deriving Generic

 -- A has a Generic instance. Therefore, should use gfunc.
 instance Klass A

 data B = B { unB :: Int }

 -- B does not have a Generic instance. Therefore, should use func.
 instance Klass B

 main :: IO ()
 main = print (func $ A 3, func $ B 3)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7395#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] #7395: DefaultSignatures conflict with default implementations

2012-11-05 Thread GHC
#7395: DefaultSignatures conflict with default implementations
--+-
Reporter:  cgaebel|   Owner:   
Type:  bug|  Status:  new  
Priority:  normal |   Milestone:   
   Component:  Compiler   | Version:  7.6.1
Keywords:  DefaultSignatures  |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple   | Failure:  GHC rejects valid program
  Difficulty:  Unknown|Testcase:   
   Blockedby: |Blocking:   
 Related: |  
--+-
Changes (by igloo):

  * testcase:  http://hpaste.org/77290 =


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7395#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] #7395: DefaultSignatures conflict with default implementations

2012-11-05 Thread GHC
#7395: DefaultSignatures conflict with default implementations
--+-
Reporter:  cgaebel|   Owner:   
Type:  bug|  Status:  new  
Priority:  normal |   Milestone:   
   Component:  Compiler   | Version:  7.6.1
Keywords:  DefaultSignatures  |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple   | Failure:  GHC rejects valid program
  Difficulty:  Unknown|Testcase:   
   Blockedby: |Blocking:   
 Related: |  
--+-

Comment(by cgaebel):

 Doesn't GHC already backtrack for things like UndecidableInstances? Or
 does it do something else? Can we apply that here?

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