Re: [GHC] #5610: Improve "Unacceptable argument type in foreign declaration" error message

2012-08-29 Thread GHC
#5610: Improve "Unacceptable argument type in foreign declaration" error message
+---
  Reporter:  bgamari|  Owner:   
   
  Type:  feature request| Status:  new  
   
  Priority:  high   |  Milestone:  7.4.1
   
 Component:  Compiler (Type checker)|Version:  7.6.1-rc1
   
Resolution: |   Keywords:   
   
Os:  Unknown/Multiple   |   Architecture:  
Unknown/Multiple
   Failure:  Incorrect warning at compile-time  | Difficulty:  Unknown  
   
  Testcase: |  Blockedby:   
   
  Blocking: |Related:   
   
+---

Comment(by bos):

 Incidentally, Lemming's observation that requiring constructors to be
 imported breaks encapsulation seems correct.

 I have run into exactly the situation he describes, where an aliased
 `CInt` is now causing compilation of a number of modules to break in 7.6.
 I have to fix this by [https://github.com/bos/text-
 icu/commit/24b63f085d5d1ebe131c95e1f16e90159b8f6562 importing both] the
 alias and `CInt`, which feels quite unsatisfactory.

 Furthermore, making compilation work with GHC 7.6 now introduces warnings
 on versions of GHC prior to 7.4:

 {{{
 Data/Text/ICU/Normalize.hsc:45:1:
 Warning: The import item `CInt(..)' suggests that
  `CInt' has (in-scope) constructors or class methods,
  but it has none
 }}}

 I make a habit of building with `-Werror` on my continuous integration
 host, but the calisthenics required to keep things warning-clean across
 multiple GHC versions are getting a bit rigorous.

-- 
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] #5610: Improve "Unacceptable argument type in foreign declaration" error message

2012-08-29 Thread GHC
#5610: Improve "Unacceptable argument type in foreign declaration" error message
+---
  Reporter:  bgamari|  Owner:   
   
  Type:  feature request| Status:  new  
   
  Priority:  high   |  Milestone:  7.4.1
   
 Component:  Compiler (Type checker)|Version:  7.6.1-rc1
   
Resolution: |   Keywords:   
   
Os:  Unknown/Multiple   |   Architecture:  
Unknown/Multiple
   Failure:  Incorrect warning at compile-time  | Difficulty:  Unknown  
   
  Testcase: |  Blockedby:   
   
  Blocking: |Related:   
   
+---
Changes (by bos):

  * version:  7.3 => 7.6.1-rc1


-- 
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] #5610: Improve "Unacceptable argument type in foreign declaration" error message

2012-08-29 Thread GHC
#5610: Improve "Unacceptable argument type in foreign declaration" error message
+---
  Reporter:  bgamari|  Owner:   
   
  Type:  feature request| Status:  new  
   
  Priority:  high   |  Milestone:  7.4.1
   
 Component:  Compiler (Type checker)|Version:  7.3  
   
Resolution: |   Keywords:   
   
Os:  Unknown/Multiple   |   Architecture:  
Unknown/Multiple
   Failure:  Incorrect warning at compile-time  | Difficulty:  Unknown  
   
  Testcase: |  Blockedby:   
   
  Blocking: |Related:   
   
+---
Changes (by bos):

 * cc: bos@… (added)
  * type:  bug => feature request
  * failure:  GHC rejects valid program => Incorrect warning at compile-
  time
  * architecture:  x86_64 (amd64) => Unknown/Multiple
  * keywords:  zlib =>
  * os:  Linux => Unknown/Multiple


-- 
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] #5610: Improve "Unacceptable argument type in foreign declaration" error message

2012-08-29 Thread GHC
#5610: Improve "Unacceptable argument type in foreign declaration" error message
+---
  Reporter:  bgamari|  Owner:
  Type:  bug| Status:  new   
  Priority:  high   |  Milestone:  7.4.1 
 Component:  Compiler (Type checker)|Version:  7.3   
Resolution: |   Keywords:  zlib  
Os:  Linux  |   Architecture:  x86_64 (amd64)
   Failure:  GHC rejects valid program  | Difficulty:  Unknown   
  Testcase: |  Blockedby:
  Blocking: |Related:
+---
Changes (by bos):

  * owner:  simonmar =>
  * status:  closed => new
  * resolution:  fixed =>


Comment:

 Here is the error message reported by GHC 7.6.1 rc1:

 {{{
 Data/Text/ICU/Error/Internal.hsc:163:1:
 Unacceptable argument type in foreign declaration: CInt
 When checking declaration:
   foreign import ccall unsafe "static hs_text_icu.h __hs_u_errorName"
 u_errorName
 :: UErrorCode -> CString
 }}}

 This is the same message as the old error, and is very confusing.

 Can the much more comprehensible and actionable language from the 7.4
 warning please be reintroduced?

 {{{
 Error: newtype `CInt' is used in an FFI declaration,
  but its constructor is not in scope.
 }}}

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


[GHC] #7202: Linux bindists don't work on new distros

2012-08-29 Thread GHC
#7202: Linux bindists don't work on new distros
---+
 Reporter:  bos|  Owner:  
 Type:  bug| Status:  new 
 Priority:  normal |  Component:  Build System
  Version:  7.4.2  |   Keywords:  
   Os:  Linux  |   Architecture:  Unknown/Multiple
  Failure:  Installing GHC failed  |   Testcase:  
Blockedby: |   Blocking:  
  Related: |  
---+
 All of the binary distributions are built on systems that have
 libgmp.so.3. On newer Linux distros (I use Fedora 17), libgmp.so.3 is no
 longer available because it's been superseded by a new version of GMP.
 This problem will probably become more widespread as uptake of the new
 version of GMP spreads.

 One possible workaround would be to ship with a copy of libgmp.so.3 that
 is installed along with GHC if there isn't already a copy present.

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


[GHC] #7201: ghc assumes that ld can understand --hash-size [regression]

2012-08-29 Thread GHC
#7201: ghc assumes that ld can understand --hash-size [regression]
-+--
 Reporter:  bos  |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:  7.6.1-rc1|   Keywords:  
   Os:  Linux|   Architecture:  Unknown/Multiple
  Failure:  GHC doesn't work at all  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
 On my Fedora 17 box, I'm using gold as the default linker, and I cannot
 link any packages built with GHC 7.6 because GHC seems to be passing an
 invalid argument to the linker.

 {{{
 $ cabal install -v random
 [... blah blah blah ...]
 /bin/ld -x --hash-size=31 --reduce-memory-overheads -r -o
 dist/build/HSrandom-1.0.1.1.o dist/build/System/Random.o
 /bin/ld: --hash-size=31: unknown option
 /bin/ld: use the --help option for usage information
 Failed to install random-1.0.1.1
 }}}

 This does not happen with GHC 7.4 or earlier.

-- 
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] #7200: template-haskell-2.7.0.0 fails to build with GHC 7.0.4 due to missing pragma

2012-08-29 Thread GHC
#7200: template-haskell-2.7.0.0 fails to build with GHC 7.0.4 due to missing
pragma
-+--
Reporter:  tibbe |   Owner:  igloo   
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Template Haskell  | Version:  7.0.4   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonpj):

  * owner:  => igloo


Comment:

 Ian can you act on this?

-- 
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] #7200: template-haskell-2.7.0.0 fails to build with GHC 7.0.4 due to missing pragma

2012-08-29 Thread GHC
#7200: template-haskell-2.7.0.0 fails to build with GHC 7.0.4 due to missing
pragma
-+--
Reporter:  tibbe |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Template Haskell  | Version:  7.0.4   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by tibbe):

 Replying to [comment:3 simonpj]:
 > But this is for 7.0.4 which has been out for ages.  It's a non-issue
 presumably for 7.6 and the current th lib?

 Yes, it's not an issue for at least 7.2 and later. I typically try to
 support the last 3 releases of GHC in my libraries (not counting 7.2 as it
 was a tech preview). Lots of distros are still on 7.0.

-- 
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] #7200: template-haskell-2.7.0.0 fails to build with GHC 7.0.4 due to missing pragma

2012-08-29 Thread GHC
#7200: template-haskell-2.7.0.0 fails to build with GHC 7.0.4 due to missing
pragma
-+--
Reporter:  tibbe |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Template Haskell  | Version:  7.0.4   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonpj):

 But this is for 7.0.4 which has been out for ages.  It's a non-issue
 presumably for 7.6 and the current th lib?

-- 
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] #7200: template-haskell-2.7.0.0 fails to build with GHC 7.0.4 due to missing pragma

2012-08-29 Thread GHC
#7200: template-haskell-2.7.0.0 fails to build with GHC 7.0.4 due to missing
pragma
-+--
Reporter:  tibbe |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Template Haskell  | Version:  7.0.4   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by tibbe):

 Making a 2.7.0.1 bugfix release would be nice. I don't know if that would
 be an issue given template-haskell's somewhat special relationship with
 the compiler.

-- 
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] #7200: template-haskell-2.7.0.0 fails to build with GHC 7.0.4 due to missing pragma

2012-08-29 Thread GHC
#7200: template-haskell-2.7.0.0 fails to build with GHC 7.0.4 due to missing
pragma
-+--
Reporter:  tibbe |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Template Haskell  | Version:  7.0.4   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonpj):

  * difficulty:  => Unknown


Comment:

 `PprLib` has `{-# LANGUAGE FlexibleInstances #-}` now.  Maybe it didn't in
 2.7.0.0.

 I'm not sure what to do here, or who should do it.

 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


[GHC] #7200: template-haskell-2.7.0.0 fails to build with GHC 7.0.4 due to missing pragma

2012-08-29 Thread GHC
#7200: template-haskell-2.7.0.0 fails to build with GHC 7.0.4 due to missing
pragma
--+-
 Reporter:  tibbe |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Template Haskell
  Version:  7.0.4 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 It looks like there's a missing pragma:

 {{{
 [1 of 7] Compiling Language.Haskell.TH.Syntax.Internals (
 Language/Haskell/TH/Syntax/Internals.hs,
 dist/build/Language/Haskell/TH/Syntax/Internals.o )
 [2 of 7] Compiling Language.Haskell.TH.Syntax (
 Language/Haskell/TH/Syntax.hs, dist/build/Language/Haskell/TH/Syntax.o )
 [3 of 7] Compiling Language.Haskell.TH.PprLib (
 Language/Haskell/TH/PprLib.hs, dist/build/Language/Haskell/TH/PprLib.o )

 Language/Haskell/TH/PprLib.hs:55:10:
 Illegal instance declaration for `Show Doc'
   (All instance types must be of the form (T t1 ... tn)
where T is not a synonym.
Use -XTypeSynonymInstances if you want to disable this.)
 In the instance declaration for `Show Doc'
 }}}

-- 
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] #7199: Standalone deriving Show at GHCi prompt causes divergence when printing

2012-08-29 Thread GHC
#7199: Standalone deriving Show at GHCi prompt causes divergence when printing
-+--
  Reporter:  dpmulligan  |  Owner:
  Type:  bug | Status:  closed
  Priority:  normal  |  Milestone:
 Component:  GHCi|Version:  7.4.1 
Resolution:  invalid |   Keywords:  deriving, divergence, ghci
Os:  Linux   |   Architecture:  x86   
   Failure:  GHCi crash  | Difficulty:  Unknown   
  Testcase:  |  Blockedby:
  Blocking:  |Related:
-+--
Changes (by simonpj):

  * status:  new => closed
  * difficulty:  => Unknown
  * resolution:  => invalid


Comment:

 This code
 {{{
   instance Show Bool'
 }}}
 does not derive a `Show` instance.  To do that you need to either say
 {{{
   data Bool' = T' | F'  deriving( Show )
 }}}
 or you can use standalone deriving (with `-XStandaloneDeriving`):
 {{{
   deriving instance Show Bool'
 }}}
 By merely saying `instance Show Bool'` you are using ordinary Haskell 98
 to define an instance, filling in the default methods as desribed in the
 language specficiation.  So it's as if you'd typed
 {{{
   instance Show Bool' where
 show x = showsPrec 0 x ""
 showsPrec _ x s = show x ++ s
 }}}
 (The default declarations come from the library.)  Since each method is
 defined in terms of the other, the result diverges.

 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


[GHC] #7199: Standalone deriving Show at GHCi prompt causes divergence when printing

2012-08-29 Thread GHC
#7199: Standalone deriving Show at GHCi prompt causes divergence when printing
+---
 Reporter:  dpmulligan  |  Owner:
 Type:  bug | Status:  new   
 Priority:  normal  |  Component:  GHCi  
  Version:  7.4.1   |   Keywords:  deriving, divergence, ghci
   Os:  Linux   |   Architecture:  x86   
  Failure:  GHCi crash  |   Testcase:
Blockedby:  |   Blocking:
  Related:  |  
+---
 Deriving a show instance for a data type (defined either with the standard
 Haskell 98 syntax or with GADT syntax) within GHCi using the command:

 {{{
 instance Show 
 }}}

 causes divergence/stack overflow when printing values of that type.  The
 issue does not manifest itself when you use the standard deriving
 mechanism within a Haskell source file.

 Minimum example necessary to replicate:

 {{{
 module Main (
   main
 )
 where

   -- At GHCi prompt type
   --   instance Show Bool'
   -- then
   --   True'
   -- to get a stack overflow
   data Bool'
 = True'
 | False'

   main = return ()
 }}}

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


[GHC] #7198: New codegen more than doubles compile time of T3294

2012-08-29 Thread GHC
#7198: New codegen more than doubles compile time of T3294
-+--
Reporter:  simonmar  |   Owner:  simonmar
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.4.2   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:  #4258 |  
-+--
 I did some preliminary investigation, and there seem to be a couple of
 things going on.

 First, the stack allocator generates lots of unnecessary reloads at a
 continuation, for variables that are not used.  These would be cleaned up
 by the sinking pass (if we were running the sinking pass), but generating
 them in the first place costs compile time.

 Second, there is a large nested `let` expression of the form

 {{{
 let x = let y = let z = ...
 in  f z
 in  f y
 }}}

 where each let binding has a lot of free variables.  So the body of each
 let ends up copying a ton of variables out of its closure to build the
 inner let binding's closure.  These sequences look like:

 {{{
 x1 = [R1+8]
 x2 = [R1+16]
 ...
 [Hp-32] = x1
 [Hp-24] = x2
 ...
 }}}

 now `CmmSink` can't currently inline all the locals because knowing that
 `[R1+8]` doesn't alias `[Hp-32]` is tricky (see comments in `CmmSink`).
 However, again, we're not even running the sinking pass because this is
 `-O0`.  The fact that we generate all this code in the first place is a
 problem.  The old code generator generated

 {{{
 [Hp-32] = [R1+8]
 [Hp-24] = [R1+16]
 ...
 }}}

 which amounts to a lot less `Cmm`, and a lot less trouble for the register
 allocator later.

 One thing we could do is flatten out the `let`s, on the grounds that the
 inner let binding has a lot of free variables that need to be copied when
 the `let` is nested.  This could be based on a heuristic about the number
 of free variables and the amount of extra allocation that would be
 entailed if the `let` is never entered.

-- 
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] #7197: ghc panic: Irrefutable pattern failed

2012-08-29 Thread GHC
#7197: ghc panic: Irrefutable pattern failed
-+--
  Reporter:  illusionoflife  |  Owner:
  Type:  bug | Status:  closed
  Priority:  normal  |  Milestone:
 Component:  Compiler|Version:  7.4.2 
Resolution:  duplicate   |   Keywords:
Os:  Linux   |   Architecture:  x86_64 (amd64)
   Failure:  Compile-time crash  | Difficulty:  Unknown   
  Testcase:  |  Blockedby:
  Blocking:  |Related:
-+--
Changes (by simonpj):

  * status:  new => closed
  * difficulty:  => Unknown
  * resolution:  => duplicate


Comment:

 Thanks.  Always worth searching Trac first... this is just a dup of #7093,
 #7079, #7039, #6051.  Already fixed, happily.

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


[GHC] #7197: ghc panic: Irrefutable pattern failed

2012-08-29 Thread GHC
#7197: ghc panic: Irrefutable pattern failed
+---
 Reporter:  illusionoflife  |  Owner:
 Type:  bug | Status:  new   
 Priority:  normal  |  Component:  Compiler  
  Version:  7.4.2   |   Keywords:
   Os:  Linux   |   Architecture:  x86_64 (amd64)
  Failure:  Compile-time crash  |   Testcase:
Blockedby:  |   Blocking:
  Related:  |  
+---
 I get following error, when trying to compile following snippet:
 {{{
 module BooleanFunction where

 class BooleanFunction a where
   arity :: a -> Int

 instance BooleanFunction Bool where
   arity _ = 0
 instance BooleanFunction a => BooleanFunction  Bool -> a where
   arity _ = 1 + arity a
 }}}
 {{{
 [1 of 1] Compiling BooleanFunction  ( BooleanFunction.hs,
 BooleanFunction.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.4.2 for x86_64-unknown-linux):
 compiler/rename/RnSource.lhs:430:14-81: Irrefutable pattern failed
 for pattern Data.Maybe.Just (inst_tyvars,
 _,
 SrcLoc.L _ cls,
 _)


 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

 }}}

-- 
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] #7175: Panic when wrongly using a type family as return types for GADTs

2012-08-29 Thread GHC
#7175: Panic when wrongly using a type family as return types for GADTs
-+--
Reporter:  goldfire  |   Owner: 
Type:  bug   |  Status:  merge  
Priority:  normal|   Milestone: 
   Component:  Compiler  | Version:  7.6.1-rc1  
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash 
  Difficulty:  Unknown   |Testcase:  typecheck/should_fail/T7175
   Blockedby:|Blocking: 
 Related:|  
-+--
Changes (by simonpj):

  * status:  new => merge
  * difficulty:  => Unknown
  * testcase:  => typecheck/should_fail/T7175


Comment:

 Thanks!  Fixed.  Pls merge to 7.6

-- 
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] #7175: Panic when wrongly using a type family as return types for GADTs

2012-08-29 Thread GHC
#7175: Panic when wrongly using a type family as return types for GADTs
+---
 Reporter:  goldfire|  Owner:  
 Type:  bug | Status:  new 
 Priority:  normal  |  Component:  Compiler
  Version:  7.6.1-rc1   |   Keywords:  
   Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple
  Failure:  Compile-time crash  |   Testcase:  
Blockedby:  |   Blocking:  
  Related:  |  
+---

Comment(by simonpj@…):

 commit d0ddde58f928a6b156d8061c406226c4fbb7cd22
 {{{
 Author: Simon Peyton Jones 
 Date:   Wed Aug 29 11:33:33 2012 +0100

 Fail earlier if there's an error in a type declaration

 This change means that we don't recover from erroneous type
 declarations, thereby reporting fewer errors.  But trying to
 recover confused GHC (leading to a pattern match failure in
 the compiler Trac #7175), and it turned out to be tricky
 to fix that.

 So this patch takes the more conservative path of failing
 earlier, perhaps reporting fewer real errors.

  compiler/typecheck/TcTyClsDecls.lhs |7 ---
  1 files changed, 4 insertions(+), 3 deletions(-)
 }}}

-- 
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] #7196: Desugarer needs an extra case for casts in coercions

2012-08-29 Thread GHC
#7196: Desugarer needs an extra case for casts in coercions
-+--
Reporter:  simonpj   |   Owner:
Type:  bug   |  Status:  merge 
Priority:  normal|   Milestone:
   Component:  Compiler  | Version:  7.4.2 
Keywords:|  Os:  Unknown/Multiple  
Architecture:  Unknown/Multiple  | Failure:  None/Unknown  
  Difficulty:  Unknown   |Testcase:  typecheck/should_compile/T7196
   Blockedby:|Blocking:
 Related:|  
-+--
Changes (by simonpj):

 * cc: ganesh@… (added)
  * status:  new => merge
  * testcase:  => typecheck/should_compile/T7196


Comment:

 Please merge this to 7.6.

 Thanks for the test case, Ganesh.

 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] #7196: Desugarer needs an extra case for casts in coercions

2012-08-29 Thread GHC
#7196: Desugarer needs an extra case for casts in coercions
-+--
Reporter:  simonpj   |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.4.2   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonpj@…):

 commit f27c631a16a17b8ad740d7d28c6ff267fb189c2c
 {{{
 Author: Simon Peyton Jones 
 Date:   Wed Aug 29 10:57:48 2012 +0100

 Fix Trac #7196 by adding a case to the desugarer

 Pls merge to 7.6

  compiler/deSugar/DsBinds.lhs  |   11 ++-
  compiler/typecheck/TcEvidence.lhs |   21 +++--
  2 files changed, 17 insertions(+), 15 deletions(-)
 }}}

-- 
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] #314: #line pragmas not respected inside nested comments

2012-08-29 Thread GHC
#314: #line pragmas not respected inside nested comments
+---
  Reporter:  nobody |  Owner:  
  Type:  bug| Status:  new 
  Priority:  high   |  Milestone:  7.8.1   
 Component:  Compiler (Parser)  |Version:  6.4 
Resolution:  None   |   Keywords:  
Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown   | Difficulty:  Unknown 
  Testcase:  read032|  Blockedby:  
  Blocking: |Related:  
+---
Changes (by simonmar):

  * priority:  low => high
  * milestone:  _|_ => 7.8.1


Comment:

 In case it isn't clear from the previous comment:

  * GHC uses `#line` pragmas to determine what source files were visited by
 the C preprocessor, and tracks dependencies on these for recompilation

  * The lexer currently ignores `#line` pragmas inside `{- .. -}` comments,
 and hence  it misses any preprocessor dependencies inside `{- .. -}`

 I'm raising the priority of this bug.

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