Re: [GHC] #3927: Incomplete/overlapped pattern warnings + GADTs = inadequate

2012-10-05 Thread GHC
#3927: Incomplete/overlapped pattern warnings + GADTs = inadequate
-+--
Reporter:  simonpj   |   Owner:  simonpj 
Type:  bug   |  Status:  new 
Priority:  high  |   Milestone:  7.6.2   
   Component:  Compiler  | Version:  6.12.1  
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:  #4139 |  
-+--

Comment(by simonpj):

 See also #7294

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3927#comment:26
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] #7294: -fdefer-type-errors doesn't produce a warning

2012-10-05 Thread GHC
#7294: -fdefer-type-errors doesn't produce a warning
--+-
  Reporter:  Feuerbach|  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  
 Component:  Compiler (Type checker)  |Version:  7.6.1   
Resolution:  duplicate|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  GHC accepts invalid program  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by simonpj):

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


Comment:

 Yes, I'm afraid #3927 is the offending ticket.  Overlapping patterns are
 figured out *after* type checking, because it involves a sort of global
 analysis of the block of patterns.  Fixing overlapping-pattern warnings in
 the presence of GADTs requires some careful thought; a nice self-contained
 project.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7294#comment:4
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] #7281: GHC 7.4.2 build fails on Fedora17

2012-10-05 Thread GHC
#7281: GHC 7.4.2 build fails on Fedora17
---+
Reporter:  PaulJohnson |   Owner: 
Type:  bug |  Status:  new
Priority:  high|   Milestone:  7.6.2  
   Component:  Compiler| Version:  7.4.2  
Keywords:  |  Os:  Linux  
Architecture:  x86_64 (amd64)  | Failure:  Building GHC failed
  Difficulty:  Unknown |Testcase: 
   Blockedby:  |Blocking: 
 Related:  |  
---+
Changes (by simonmar):

  * priority:  normal = high
  * difficulty:  = Unknown
  * milestone:  = 7.6.2


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7281#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] #7264: Adding GHC's inferred type signatures to a working program can make it fail with Rank2Types

2012-10-05 Thread GHC
#7264: Adding GHC's inferred type signatures to a working program can make it 
fail
with Rank2Types
-+--
Reporter:  guest |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonpj):

 * cc: dimitris@… (added)
  * difficulty:  = Unknown


Comment:

 This is bad.  Here's a slightly cut down example:
 {{{
 {-# LANGUAGE Rank2Types #-}
 module T7264 where

 data Foo = Foo (forall r . r - String)

 mmap :: (a-b) - Maybe a - Maybe b
 mmap f (Just x) = f x
 mmap f Nothing  = Nothing

 -- mkFoo2 :: (forall r. r - String) - Maybe Foo
 mkFoo2 val = mmap Foo (Just val)
 }}}
  * The commented-out type sig is inferred, because GHC assigns unknown
 type `alpha` to `val`; then instantiates `mmap`'s type with `beta` and
 `gamma`; then unifies `beta`:=`forall r. r-String`.

  * But when the commented out type sig is provided ghc ''instantiates'' it
 at the occurrence of `val`.

 You need to call `mmap` at a polymorphic type, which means you need
 impredicativity.  Lacking `ImpredicativeTypes` the no-signature program
 should be rejected.  The fact that it isn't is a bug.

 Even if that bug is fixed, the progam shows, again, how tricky
 impredicativity is.  We don't have a decent implementation of
 `ImpredicativeTypes`.

 At least it's not a show-stopper for anyone.

 Simon

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


[GHC] #7300: Allow CAFs kept reachable by FFI to be forcibly made unreachable for GC

2012-10-05 Thread GHC
#7300: Allow CAFs kept reachable by FFI to be forcibly made unreachable for GC
-+--
 Reporter:  absence  |  Owner:  
 Type:  feature request  | Status:  new 
 Priority:  normal   |  Component:  Compiler (FFI)  
  Version:  7.4.1|   Keywords:  unsafe caf gc   
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Runtime performance bug  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
 CAFs used by a foreign exported function are kept reachable the entire
 session because GHC can't know when the function will be called from C. If
 such a CAF is an evolving expression, like an FRP network, a space leak
 occurs because (I'm guessing) the thunks that build up during iteration go
 all the way back to the initial CAF, and the GC can't start collecting
 because it considers the CAF reachable. According to JaffaCake on the
 #haskell IRC channel, the runtime is capable of sovling this problem, it
 just needs a function that tells it to consider the specific CAF
 unreachable. It is then the responsibility of the user to not call the
 foreign exported function after the CAF is forced unreachable.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7300
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] #5641: The -L flag should not exist

2012-10-05 Thread GHC
#5641: The -L flag should not exist
-+--
Reporter:  augustss  |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  7.6.2   
   Component:  Profiling | Version:  7.2.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonmar):

  * difficulty:  = Unknown


Comment:

 It means we think the suggestion is sensible, but with a priority of
 normal it isn't likely to get done by us (we only tend to get to the
 high stuff).

 Regarding this ticket specifically, `hp2ps` needs to be thrown away and
 rewritten in Haskell.  Last I heard `hp2pretty` wasn't quite there yet.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5641#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] #7262: directory 1.2 fails to build with base 4.6

2012-10-05 Thread GHC
#7262: directory 1.2 fails to build with base  4.6
+---
Reporter:  sopvop   |   Owner:  igloo   
Type:  bug  |  Status:  patch   
Priority:  high |   Milestone:  7.6.2   
   Component:  libraries/directory  | Version:  7.4.2   
Keywords:   |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple | Failure:  None/Unknown
  Difficulty:  Unknown  |Testcase:  
   Blockedby:   |Blocking:  
 Related:   |  
+---
Changes (by simonmar):

  * owner:  = igloo
  * difficulty:  = Unknown
  * priority:  normal = high
  * milestone:  = 7.6.2


Comment:

 Ian, could you look into this please?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7262#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] #7299: threadDelay broken in ghci, Mac OS X

2012-10-05 Thread GHC
#7299: threadDelay broken in ghci, Mac OS X
-+--
Reporter:  tmcdonell |   Owner:
Type:  bug   |  Status:  new   
Priority:  highest   |   Milestone:  7.6.2 
   Component:  GHCi  | Version:  7.6.1 
Keywords:|  Os:  MacOS X   
Architecture:  Unknown/Multiple  | Failure:  GHCi crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:|Blocking:
 Related:|  
-+--
Changes (by simonmar):

  * priority:  normal = highest
  * difficulty:  = Unknown
  * milestone:  = 7.6.2


Comment:

 Looks serious, thanks for the report.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7299#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] #7294: -fdefer-type-errors doesn't produce a warning

2012-10-05 Thread GHC
#7294: -fdefer-type-errors doesn't produce a warning
--+-
  Reporter:  Feuerbach|  Owner:  
  Type:  bug  | Status:  new 
  Priority:  normal   |  Milestone:  
 Component:  Compiler (Type checker)  |Version:  7.6.1   
Resolution:   |   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  GHC accepts invalid program  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by simonmar):

  * status:  closed = new
  * resolution:  duplicate =


Comment:

 The second problem mentioned is #3927, but the first problem is still
 unresolved, right?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7294#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] #7300: Allow CAFs kept reachable by FFI to be forcibly made unreachable for GC

2012-10-05 Thread GHC
#7300: Allow CAFs kept reachable by FFI to be forcibly made unreachable for GC
-+--
Reporter:  absence   |   Owner: 
Type:  feature request   |  Status:  new
Priority:  high  |   Milestone:  7.8.1  
   Component:  Compiler (FFI)| Version:  7.4.1  
Keywords:  unsafe caf gc |  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Runtime performance bug
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--
Changes (by simonmar):

  * priority:  normal = high
  * difficulty:  = Unknown
  * milestone:  = 7.8.1


Comment:

 Thanks for making a ticket.

 What I had in mind (to remind myself) is that we expose a C API from the
 RTS that would revert all the live CAFs.  This would have to be done at
 the same time as a major GC, because that is the only time that we can
 visit all the live CAFs.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7300#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] #7294: -fdefer-type-errors doesn't produce a warning

2012-10-05 Thread GHC
#7294: -fdefer-type-errors doesn't produce a warning
--+-
  Reporter:  Feuerbach|  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  
 Component:  Compiler (Type checker)  |Version:  7.6.1   
Resolution:  fixed|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  GHC accepts invalid program  | Difficulty:  Unknown 
  Testcase:  gadt/T7293, T7294|  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by simonpj):

  * status:  new = closed
  * testcase:  = gadt/T7293, T7294
  * resolution:  = fixed


Comment:

 No, it's fine now.  Without `-fdefer-type-errors` we get an error (test
 `gadt/T7293`); with `-fdefer-type-errors` we get a warning (test
 `gadt/T7294`).

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7294#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] #7293: Wrong location reported for inaccessible code with GADTs

2012-10-05 Thread GHC
#7293: Wrong location reported for inaccessible code with GADTs
---+
  Reporter:  goldfire  |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.6.1   
Resolution:  fixed |   Keywords:  GADTs   
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:  gadt/T7293|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonpj):

  * status:  new = closed
  * difficulty:  = Unknown
  * resolution:  = fixed
  * testcase:  = gadt/T7293


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7293#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] #7300: Allow CAFs kept reachable by FFI to be forcibly made unreachable for GC

2012-10-05 Thread GHC
#7300: Allow CAFs kept reachable by FFI to be forcibly made unreachable for GC
-+--
Reporter:  absence   |   Owner: 
Type:  feature request   |  Status:  new
Priority:  high  |   Milestone:  7.8.1  
   Component:  Compiler (FFI)| Version:  7.4.1  
Keywords:  unsafe caf gc |  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Runtime performance bug
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--

Comment(by ezyang):

 Of course, revertCAFs only works when the linker sets up CAFs with
 newDynCAF...

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7300#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] #7301: Got an internal error that caused GHCi to crash

2012-10-05 Thread GHC
#7301: Got an internal error that caused GHCi to crash
+---
 Reporter:  guest   |  Owner:
 Type:  bug | Status:  new   
 Priority:  normal  |  Component:  Runtime System
  Version:  7.4.1   |   Keywords:
   Os:  Windows |   Architecture:  x86_64 (amd64)
  Failure:  GHCi crash  |   Testcase:
Blockedby:  |   Blocking:
  Related:  |  
+---
 Here's the error message:

 interactive: internal error: evacuate: strange closure type 18317
 (GHC version 7.4.1 for i386_unknown_mingw32)
 Please report this as a GHC bug:
 http://www.haskell.org/ghc/reportabug

 This application has requested the Runtime to terminate it in an unusual
 way.
 Please contact the application's support team for more information.



 This happened while :load-ing a file.  GHCi had been running for quite a
 while.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7301
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] #7301: Got an internal error that caused GHCi to crash

2012-10-05 Thread GHC
#7301: Got an internal error that caused GHCi to crash
+---
 Reporter:  guest   |  Owner:
 Type:  bug | Status:  new   
 Priority:  normal  |  Component:  GHCi  
  Version:  7.4.1   |   Keywords:
   Os:  Windows |   Architecture:  x86_64 (amd64)
  Failure:  GHCi crash  |   Testcase:
Blockedby:  |   Blocking:
  Related:  |  
+---
Changes (by guest):

  * component:  Runtime System = GHCi


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7301#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] #7301: Got an internal error that caused GHCi to crash

2012-10-05 Thread GHC
#7301: Got an internal error that caused GHCi to crash
+---
 Reporter:  guest   |  Owner:  sim   
 Type:  bug | Status:  new   
 Priority:  normal  |  Component:  GHCi  
  Version:  7.4.1   |   Keywords:
   Os:  Windows |   Architecture:  x86_64 (amd64)
  Failure:  GHCi crash  |   Testcase:
Blockedby:  |   Blocking:
  Related:  |  
+---
Changes (by guest):

  * owner:  = sim


Comment:

 Forgot to add that this is not a recurring problem.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7301#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] #7301: Got an internal error that caused GHCi to crash

2012-10-05 Thread GHC
#7301: Got an internal error that caused GHCi to crash
+---
 Reporter:  guest   |  Owner:  guest 
 Type:  bug | Status:  new   
 Priority:  normal  |  Component:  GHCi  
  Version:  7.4.1   |   Keywords:
   Os:  Windows |   Architecture:  x86_64 (amd64)
  Failure:  GHCi crash  |   Testcase:
Blockedby:  |   Blocking:
  Related:  |  
+---
Changes (by guest):

  * owner:  sim = guest


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