Re: [GHC] #2467: orphan instance warnings are badly behaved

2008-12-31 Thread GHC
#2467: orphan instance warnings are badly behaved
-+--
Reporter:  duncan|Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  6.12 branch 
   Component:  Compiler  |  Version:  6.8.2   
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by simonpj):

 Indeed, your code is legitimate, and that's why warnings are just
 warnings!

 More concretely, what would you like?  A special kind of warning that
 (uniquely) does not make -Werror abort the compilation?  That seems a bit
 irregular...  But perhaps you have something in mind.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2467#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] #2615: ghci doesn't play nice with linker scripts

2008-12-31 Thread GHC
#2615: ghci doesn't play nice with linker scripts
-+--
Reporter:  AlecBerryman  |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone:  6.10.2 
   Component:  GHCi  |  Version:  6.10.1 
Severity:  normal|   Resolution: 
Keywords:|   Difficulty:  Unknown
Testcase:|   Os:  Linux  
Architecture:  Unknown/Multiple  |  
-+--
Changes (by maeder):

  * version:  6.8.3 = 6.10.1

Comment:

 This bug stops me from using template haskell (that uses ghci) and gtk in
 the sources for a cabal package.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2615#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] #2846: Impredicativity bug: GHC crash by type signature

2008-12-31 Thread GHC
#2846: Impredicativity bug: GHC crash by type signature
-+--
Reporter:  mm_freak  |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  6.12 branch 
   Component:  Compiler  |  Version:  6.10.1  
Severity:  major |   Resolution:  
Keywords:  crash, type   |   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by simonpj):

  * summary:  GHC crash by type signature = Impredicativity bug: GHC crash
  by type signature
  * milestone:  6.10.2 = 6.12 branch

Comment:

 What's happening here is that `-fglasgow-exts` implies
 `-XImpredicativeTypes` and `-XFlexibleContexts`.  Then we get a constraint
 `(Show [Num a = a])`, which should never happen.  The impredicative
 machinery should not allow polymorphism in class constraints, but that
 check isn't implemented.

 The impredicative stuff needs a proper overhaul (Dimitrios is working on
 it) so I do not propose to tweak it now.  But this should be fixed in due
 course.

 Meanwhile, I propose to '''stop''' `-fglasgow-exts` from implying
 `-XImpredicativeTypes`.  I don't want to encourage use of impredicativity
 until it's working properly.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2846#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] #2467: orphan instance warnings are badly behaved

2008-12-31 Thread GHC
#2467: orphan instance warnings are badly behaved
-+--
Reporter:  duncan|Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  6.12 branch 
   Component:  Compiler  |  Version:  6.8.2   
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by Syzygies):

 Reflecting further, I noticed that these manual sections go together
 nicely:

  5.1.2. Command line options in source files

  5.6.12. Orphan modules and instance declarations

 In particular, the phrase stands out

  in some circumstances, the OPTIONS_GHC pragma is the Right Thing.

 Moving ''-fno-warn-orphans'' from the command line to a particular orphan
 file is idiomatic GHC for my situation. I already have a module containing
 helper functions such as

 {{{
 foldrC ∷ (Foldable d, Foldable e, Foldable f) ⇒
   (c a → d (e (f a))) → (a → b → b) → b → c a → b
 foldrC gi h y = foldr (flip $ foldr (flip $ foldr h)) y . gi
 }}}

 for defining deep Foldable instances that go through a newtype and three
 layers of structure.
 {{{
 instance Foldable ((,) a) where foldr f z (_,y) = f y z
 }}}
 can arise as one of those layers, so this is a natural place to put such
 orphans.

 Instance declarations are just as hard on the programmer as on GHC itself.
 For example, ''Functor ((,) a)'' is documented in Control.Monad, but
 importing Control.Monad doesn't expose this instance.  ''Functor ((,) a)''
 is not documented in Data.Foldable, but importing Data.Foldable does
 expose this instance. This left me perplexed as to why I could define deep
 Functor instances that relied on ''Functor ((,) a)'', but I couldn't write
 ''foldr (+) 2 (1,2)'' in ghci. I was left believing that this was some
 compiler magic I didn't understand, until I started using ''ghc --show-
 iface'', and spelunking the library source code.

 If I could have one wish related to instance declarations, it wouldn't
 have to do with these orphan warnings, but rather with better control over
 duplicate instance declarations. For example, I can't import Data.Foldable
 and at the same time try to redefine ''instance Monad ((-) a)''; there is
 no ''hiding'' clause that affects instances. Perhaps this is a moot point,
 as I have yet to find a standard library instance that has a reasonable
 alternative definition. One can imagine Haskell' providing missing
 instances anytime it can prove that there is only one possible definition.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2467#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] #2856: GeneralizedNewtypeDeriving doesn't work with data families

2008-12-31 Thread GHC
#2856: GeneralizedNewtypeDeriving doesn't work with data families
--+-
Reporter:  guest  |Owner:  igloo   
Type:  merge  |   Status:  new 
Priority:  normal |Milestone:  
   Component:  Compiler   |  Version:  6.10.1  
Severity:  normal |   Resolution:  
Keywords: |   Difficulty:  Unknown 
Testcase:  deriving/should_compile/T2856  |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   |  
--+-
Changes (by simonpj):

  * testcase:  = deriving/should_compile/T2856
  * difficulty:  = Unknown
  * type:  bug = merge
  * owner:  chak = igloo

Comment:

 Good point, thank you.  Fixed by
 {{{
 Wed Dec 31 14:41:51 GMT 2008  simo...@microsoft.com
   * Fix Trac #2856: make deriving work for type families
 }}}
 Merge this only if it's easy.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2856#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] #2851: Improve error message for failed deriving

2008-12-31 Thread GHC
#2851: Improve error message for failed deriving
---+
Reporter:  guest   |Owner:  igloo   
Type:  merge   |   Status:  new 
Priority:  normal  |Milestone:  
   Component:  Compiler (Type checker) |  Version:  6.10.1  
Severity:  minor   |   Resolution:  
Keywords:  |   Difficulty:  Unknown 
Testcase:  deriving/should_fail/T2851  |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple|  
---+
Comment (by simonpj):

 PS: I did a bit more, because the previous patch suggested the same fix
 for overlapping instances, which is misleading
 {{{
 Wed Dec 31 06:35:21 PST 2008  simo...@microsoft.com
   * Improve error reporting for 'deriving'
 }}}
 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2851#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] #1496: Newtypes and type families combine to produce inconsistent FC(X) axiom sets

2008-12-31 Thread GHC
#1496: Newtypes and type families combine to produce inconsistent FC(X) axiom 
sets
+---
Reporter:  sorear   |Owner:  simonpj 
Type:  bug  |   Status:  new 
Priority:  normal   |Milestone:  6.10 branch 
   Component:  Compiler (Type checker)  |  Version:  6.7 
Severity:  critical |   Resolution:  
Keywords:   |   Difficulty:  Unknown 
Testcase:   |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple |  
+---
Comment (by simonpj):

 See #2721 for another example.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1496#comment:20
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] #2721: Newtype deriving doesn't work with type families

2008-12-31 Thread GHC
#2721: Newtype deriving doesn't work with type families
---+
Reporter:  rl  |Owner:  
Type:  bug |   Status:  new 
Priority:  normal  |Milestone:  6.10.2  
   Component:  Compiler|  Version:  6.10.1  
Severity:  normal  |   Resolution:  
Keywords:  |   Difficulty:  Unknown 
Testcase:  deriving/should_fail/T2721  |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple|  
---+
Changes (by simonpj):

  * testcase:  = deriving/should_fail/T2721

Old description:

 This assumes `-XTypeFamiles -XGeneralizedNewtypeDeriving`. Example:
 {{{
 class C a where
   type T a
   foo :: a - T a

 instance C Int where
   type T Int = Int
   foo = id

 newtype N = N Int deriving(C)
 }}}
 This happily produces an `instance C N` but no `type instance T N`. It
 should either (preferably) generate
 {{{
 type instance T N = Int
 }}}
 or fail. The example also compiles if `T` is a data family (the `Int`
 instance needs to be change accordingly). It should probably fail in this
 case.

 BTW, this also compiles fine, with rather dramatic consequences:
 {{{
 type family T a
 class C a where
   foo :: a - T a

 type instance T Int = Int
 instance C Int where
   foo = id

 type instance T N = Double
 newtype N = N Int deriving(C)
 }}}
 I guess this last example is the same bug as `#1496`. I wonder if the
 deriving clause could generate something like:
 {{{
 instance T Int ~ T N = C Int
 }}}

New description:

 This assumes `-XTypeFamiles -XGeneralizedNewtypeDeriving`. Example:
 {{{
 class C a where
   type T a
   foo :: a - T a

 instance C Int where
   type T Int = Int
   foo = id

 newtype N = N Int deriving(C)
 }}}
 This happily produces an `instance C N` but no `type instance T N`. It
 should either (preferably) generate
 {{{
 type instance T N = Int
 }}}
 or fail. The example also compiles if `T` is a data family (the `Int`
 instance needs to be change accordingly). It should probably fail in this
 case.

 BTW, this also compiles fine, with rather dramatic consequences:
 {{{
 type family T a
 class C a where
   foo :: a - T a

 type instance T Int = Int
 instance C Int where
   foo = id

 type instance T N = Double
 newtype N = N Int deriving(C)
 }}}
 I guess this last example is the same bug as #1496. I wonder if the
 deriving clause could generate something like:
 {{{
 instance T Int ~ T N = C Int
 }}}

Comment:

 Good point.  For now I'm just going to make it fail.  It's quite a bit
 more work to make it generate the extra instance, and the fact that it
 does not work at all for 'data' convinced me.

 It's annoying that you therefore cannot do newtype-deriving for a class
 with an associated type.  An alternative is to allow top-level
 declarations for associated types, and check that these exist when doing
 the instance decl. So this would be valid:
 {{{
 class C a where
   type T a
   op :: a - T a

 type instance T Int = Bool
 instance C Int where
   op x = True
 }}}
 So I'll leave this open to record the idea, but meanwhile I'll push a
 patch to make it fail uniformly.

 Simon

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


[GHC] #2904: Broken pipe when quitting ghc --show-iface file.hi | less

2008-12-31 Thread GHC
#2904: Broken pipe when quitting ghc --show-iface file.hi | less
-+--
Reporter:  Syzygies  |  Owner:  
Type:  bug   | Status:  new 
Priority:  normal|  Component:  Compiler
 Version:  6.10.1|   Severity:  trivial 
Keywords:|   Testcase:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-+--
 Here is an example of a very minor rough edge in ghc:
 {{{
 % ghc --show-iface Matrix.hi | less
 ghc: stdout: hFlush: resource vanished (Broken pipe)
 }}}
 If one quits ''less'' before reading all the output (a likely scenario),
 one sees this predictable error message.

 I'd argue that one should suppress this message, so users learn to pay
 attention to the messages they do see.

 A work-around is
 {{{
 % ghc --show-iface Matrix.hi 2 /dev/null | less
 }}}
 but this suppresses other messages one might want to see. My attempts at a
 more precise work-around get me into damned if you do, damned if you
 don't territory. For example,
 {{{
 % (ghc --show-iface Matrix.hi 2| grep -v 'Broken') | less
 }}}
 doesn't work.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2904
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] #2721: Newtype deriving doesn't work with type families

2008-12-31 Thread GHC
#2721: Newtype deriving doesn't work with type families
---+
Reporter:  rl  |Owner:  igloo   
Type:  merge   |   Status:  new 
Priority:  normal  |Milestone:  6.10.2  
   Component:  Compiler|  Version:  6.10.1  
Severity:  normal  |   Resolution:  
Keywords:  |   Difficulty:  Unknown 
Testcase:  deriving/should_fail/T2721  |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple|  
---+
Changes (by simonpj):

  * owner:  = igloo
  * type:  bug = merge

Comment:

 This is the patch
 {{{
 Wed Dec 31 16:43:00 GMT 2008  simo...@microsoft.com
   * Fix Trac #2721: reject newtype deriving if the class has associated
 types
 }}}
 Pls merge; then leave the ticket open as feature request for 6.12

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2721#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] #2467: orphan instance warnings are badly behaved

2008-12-31 Thread GHC
#2467: orphan instance warnings are badly behaved
-+--
Reporter:  duncan|Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  6.12 branch 
   Component:  Compiler  |  Version:  6.8.2   
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by ross):

 Replying to [comment:7 Syzygies]:
  It came up in my code that I needed
 
   instance Foldable ((,) a) where foldr f z (_,y) = f y z
 
  which is completely parallel to the Functor instance, but unlike the
 Functor instance is not provided by the standard libraries.
 
  There is no way that this instance can be anything but an orphan in my
 code (I shouldn't change Data.Foldable on a whim, it would make my code
 non-portable), so in this case I would argue that it is wrong for -Wall
 -Werror to abort compilation over this. I added -fno-warn-orphans, but
 that is a clunky fix which now deprives me of that warning when it might
 be relevant.

 The compiler is right: the instance is an orphan, and it's right to warn
 about it, because orphan instances are inevitably a pain.  The orphan
 instances of Monad and Functor for Prelude type constructors (which you
 noted) are a case in point; unfortunately they had to be orphans to avoid
 breaking compatibility with Haskell 98.

 The right fix in this case is to get the above instance (and one for
 Either, and Traversable instances for (,) and Either) into Data.Foldable
 and Data.Traversable.  Unfortunately that won't help you until next
 September/October (and will give you a messy changeover then).

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


[GHC] #2905: require -XGADTs in order to pattern-match GADTs

2008-12-31 Thread GHC
#2905: require -XGADTs in order to pattern-match GADTs
-+--
Reporter:  guest |  Owner: 
Type:  proposal  | Status:  new
Priority:  normal|  Component:  Compiler (Type checker)
 Version:  6.10.1|   Severity:  normal 
Keywords:|   Testcase: 
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple   
-+--
 Without -XGADTs, pattern-matching GADTs causes weird typechecking problems
 (due to the lack of implied -XRelaxedPolyRec), see this thread
 http://thread.gmane.org/gmane.comp.lang.haskell.glasgow.user/16064 , and
 some history in bug #2004

 I propose that pattern-matching against any constructor that uses
 sufficient GADT features that it's particularly confused without
 -XRelaxedPolyRec, should require -XGADTs

 (I don't understand the issue well enough to know if what I'm saying makes
 sense.  I guess ordinary data and mere existentials don't need it, even
 when defined with GADT syntax...?)

 Alternately we could just require -XRelaxedPolyRec, but that seems even
 more confusing (and it wouldn't help make code portable to other
 compilers, as GADTs are definitely being used).  Or if Haskell-prime ever
 comes around and makes -XRelaxedPolyRec default (is it planning to?), then
 the issue might be moot.  I don't think the argument (against requiring
 -XGADTs) by parallel to -XOverlappingInstances is particularly strong...
 -XOverlappingInstances has an implicit effect on a module's class
 definitions... also I don't necessarily agree with that we made that
 decision for existing flags either :-)


 --Isaac Dupree

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