Re: [GHC] #5477: Missing space in Windows cmd.exe invocation breaks shell command invocation on Wine

2011-09-10 Thread GHC
#5477: Missing space in Windows cmd.exe invocation breaks shell command 
invocation
on Wine
-+--
Reporter:  A1kmm |   Owner: 
Type:  bug   |  Status:  patch  
Priority:  normal|   Component:  libraries/process  
 Version:  7.2.1 |Keywords: 
Testcase:|   Blockedby: 
  Os:  Windows   |Blocking: 
Architecture:  Unknown/Multiple  | Failure:  Incorrect result at runtime
-+--
Changes (by A1kmm):

  * status:  new => patch


-- 
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] #2893: Implement "Quantified contexts" proposal

2011-09-10 Thread GHC
#2893: Implement "Quantified contexts" proposal
-+--
Reporter:  porges|Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  _|_ 
   Component:  Compiler  |  Version:  6.10.1  
Keywords:  proposal  | Testcase:  
   Blockedby:|   Difficulty:  Unknown 
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--

Comment(by batterseapower):

 As the blog post points out (and I recently rediscovered) GHC already
 supports this feature in a more elaborate form. This works:

 ~~~
 {-# LANGUAGE GADTs, Rank2Types, FlexibleContexts #-}

 class Foo a where
 foo :: a -> String

 instance Foo [b] where
 foo = show . length

 data FooDict a where
 FooDict :: Foo a => FooDict a

 f :: (forall b. FooDict [b]) -> String
 f FooDict = foo "Hello" ++ foo [1, 2, 3]

 use_foo :: String
 use_foo = f FooDict
 ~~~

 But this is rejected:

 ~~~
 g :: (forall b. Foo [b]) => String
 g = foo "Hello" ++ foo [1, 2, 3]

 use_foo' :: String
 use_foo' = g
 ~~~

 So there doesn't seem to be a fundamental difficulty here.

-- 
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] #5299: ghc.exe: panic! (the 'impossible' happened)

2011-09-10 Thread GHC
#5299: ghc.exe: panic! (the 'impossible' happened)
---+
  Reporter:  guest |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  7.2.1   
 Component:  Compiler  |Version:  7.0.3   
Resolution:  worksforme|   Keywords:  
  Testcase:|  Blockedby:  
Difficulty:| Os:  Unknown/Multiple
  Blocking:|   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  |  
---+
Changes (by igloo):

  * status:  infoneeded => closed
  * resolution:  => worksforme


Comment:

 No response from submitter.

-- 
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] #5271: Compilation speed regression

2011-09-10 Thread GHC
#5271: Compilation speed regression
---+
  Reporter:  augustss  |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  7.4.1   
 Component:  Compiler  |Version:  7.0.4   
Resolution:  worksforme|   Keywords:  
  Testcase:|  Blockedby:  
Difficulty:| Os:  Unknown/Multiple
  Blocking:|   Architecture:  Unknown/Multiple
   Failure:  Compile-time performance bug  |  
---+
Changes (by igloo):

  * status:  infoneeded => closed
  * resolution:  => worksforme


Comment:

 If you still think there's a problem, please reopen and include some way
 for us to reproduce the problem.

-- 
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] #5212: waitForProcess: does not exist (No child processes)

2011-09-10 Thread GHC
#5212: waitForProcess: does not exist (No child processes)
--+-
  Reporter:  chrisdone|  Owner:  chrisdone 
  Type:  bug  | Status:  closed
  Priority:  normal   |  Milestone:
 Component:  GHC API  |Version:  6.12.3
Resolution:  worksforme   |   Keywords:
  Testcase:   |  Blockedby:
Difficulty:   | Os:  Linux 
  Blocking:   |   Architecture:  x86_64 (amd64)
   Failure:  Incorrect result at runtime  |  
--+-
Changes (by igloo):

  * status:  infoneeded => closed
  * resolution:  => worksforme


Comment:

 No response from submitter.

-- 
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] #5048: Wrong SrcSpan on AbsBinds

2011-09-10 Thread GHC
#5048: Wrong SrcSpan on AbsBinds
--+-
  Reporter:  JPMoresmau   |  Owner: 
  Type:  bug  | Status:  closed 
  Priority:  normal   |  Milestone:  7.2.1  
 Component:  GHC API  |Version:  7.0.2  
Resolution:  fixed|   Keywords:  SrcSpan
  Testcase:   |  Blockedby: 
Difficulty:   | Os:  Windows
  Blocking:   |   Architecture:  x86
   Failure:  Incorrect result at runtime  |  
--+-
Changes (by igloo):

  * status:  infoneeded => closed
  * resolution:  => fixed


Comment:

 No response from submitter, so assuming it's fixed.

-- 
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] #4987: darcs: internal error: stg_ap_v_ret (GHC version 7.0.1 for x86_64_apple_darwin)

2011-09-10 Thread GHC
#4987: darcs: internal error: stg_ap_v_ret (GHC version 7.0.1 for
x86_64_apple_darwin)
+---
  Reporter:  guest  |  Owner:
  Type:  bug| Status:  closed
  Priority:  normal |  Milestone:  7.2.1 
 Component:  Compiler   |Version:  7.0.1 
Resolution:  wontfix|   Keywords:
  Testcase: |  Blockedby:
Difficulty: | Os:  MacOS X   
  Blocking: |   Architecture:  x86_64 (amd64)
   Failure:  Runtime crash  |  
+---
Changes (by igloo):

  * status:  infoneeded => closed
  * resolution:  => wontfix


Comment:

 No testcase, so closing.

-- 
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] #4805: segfault in Data.HashTable, triggered by long Agda runs

2011-09-10 Thread GHC
#4805: segfault in Data.HashTable, triggered by long Agda runs
-+--
  Reporter:  wkahl   |  Owner: 
  Type:  bug | Status:  closed 
  Priority:  normal  |  Milestone:  7.2.1  
 Component:  libraries/base  |Version:  7.0.1  
Resolution:  invalid |   Keywords:  Data.HashTable segfault
  Testcase:  |  Blockedby: 
Difficulty:  | Os:  Linux  
  Blocking:  |   Architecture:  x86_64 (amd64) 
   Failure:  Runtime crash   |  
-+--
Changes (by igloo):

  * status:  infoneeded => closed
  * resolution:  => invalid


Comment:

 Please reopen if you have a way to reproduce 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] #4473: GHC --make switch does not set file timestamp correctly

2011-09-10 Thread GHC
#4473: GHC --make switch does not set file timestamp correctly
---+
  Reporter:  mitar |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  7.2.1   
 Component:  Compiler  |Version:  6.12.3  
Resolution:  fixed |   Keywords:  
  Testcase:|  Blockedby:  
Difficulty:| Os:  Unknown/Multiple
  Blocking:|   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  |  
---+
Changes (by igloo):

  * status:  infoneeded => closed
  * resolution:  => fixed


Comment:

 No response from submitter, so closing.

-- 
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] #3647: unify handling and error messages for -X vs. {-#LANGUAGE ...#-} pragmas/extensions

2011-09-10 Thread GHC
#3647: unify handling and error messages for -X vs. {-#LANGUAGE ...#-}
pragmas/extensions
+---
  Reporter:  eflister   |  Owner:  igloo
   
  Type:  feature request| Status:  new  
   
  Priority:  normal |  Milestone:  7.4.1
   
 Component:  Compiler (Parser)  |Version:  6.10.4   
   
Resolution: |   Keywords:  language pragma extensions 
error message warning
  Testcase: |  Blockedby:   
   
Difficulty: | Os:  Unknown/Multiple 
   
  Blocking: |   Architecture:  Unknown/Multiple 
   
   Failure:  None/Unknown   |  
+---
Changes (by igloo):

  * owner:  => igloo


-- 
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] #3647: unify handling and error messages for -X vs. {-#LANGUAGE ...#-} pragmas/extensions

2011-09-10 Thread GHC
#3647: unify handling and error messages for -X vs. {-#LANGUAGE ...#-}
pragmas/extensions
+---
  Reporter:  eflister   |  Owner:   
   
  Type:  feature request| Status:  new  
   
  Priority:  normal |  Milestone:  7.4.1
   
 Component:  Compiler (Parser)  |Version:  6.10.4   
   
Resolution: |   Keywords:  language pragma extensions 
error message warning
  Testcase: |  Blockedby:   
   
Difficulty: | Os:  Unknown/Multiple 
   
  Blocking: |   Architecture:  Unknown/Multiple 
   
   Failure:  None/Unknown   |  
+---
Changes (by igloo):

  * status:  infoneeded => new
  * milestone:  7.2.1 => 7.4.1


-- 
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] #1257: Bytecode generator can't handle unboxed tuples

2011-09-10 Thread GHC
#1257: Bytecode generator can't handle unboxed tuples
-+--
Reporter:  igloo |Owner:  
Type:  bug   |   Status:  new 
Priority:  high  |Milestone:  7.4.1   
   Component:  GHCi  |  Version:  6.6 
Keywords:| Testcase:  dsrun014
   Blockedby:|   Difficulty:  Unknown 
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by igloo):

  * priority:  normal => high
  * status:  infoneeded => new
  * milestone:  _|_ => 7.4.1


Comment:

 Let's either automatically enable `-fobject-code`, or add a suggestion to
 turn it on to the error message, and then close this ticket as wontfix.

-- 
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] #813: -optc-O2 used by default in GhcRtsHcOpts while building 6.5, leading make to fail

2011-09-10 Thread GHC
#813: -optc-O2 used by default in GhcRtsHcOpts while building 6.5, leading make
to fail
---+
  Reporter:  guest |  Owner: 
  Type:  bug   | Status:  closed 
  Priority:  normal|  Milestone:  _|_
 Component:  Compiler  |Version:  6.5
Resolution:  fixed |   Keywords: 
  Testcase:  N/A   |  Blockedby: 
Difficulty:  Unknown   | Os:  Linux  
  Blocking:|   Architecture:  powerpc
   Failure:  None/Unknown  |  
---+
Changes (by igloo):

  * status:  infoneeded => closed
  * resolution:  => fixed


Comment:

 No response, so let's assume it's fixed.

-- 
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] #68: Warnings for unitialized fields

2011-09-10 Thread GHC
#68: Warnings for unitialized fields
--+-
  Reporter:  nobody   |  Owner:  
  Type:  feature request  | Status:  closed  
  Priority:  normal   |  Milestone:  _|_ 
 Component:  Compiler |Version:  None
Resolution:  wontfix  |   Keywords:  warnings
  Testcase:   |  Blockedby:  
Difficulty:  Easy (less than 1 hour)  | Os:  Unknown/Multiple
  Blocking:   |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown |  
--+-
Changes (by igloo):

  * status:  infoneeded => closed
  * resolution:  None => wontfix


Comment:

 There doesn't seem to be a consensus that anything should be done, so I'm
 closing this ticket.

-- 
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] #5478: GHC panics when asked to derive Show for ByteArray# (was: GHC panics - Can't derive Show for primitive type ByteArray#)

2011-09-10 Thread GHC
#5478: GHC panics when asked to derive Show for ByteArray#
-+--
Reporter:  hvr   |   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Component:  Compiler  
 Version:  7.2.1 |Keywords:
Testcase:|   Blockedby:
  Os:  Unknown/Multiple  |Blocking:
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash
-+--

-- 
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] #5478: GHC panics - Can't derive Show for primitive type ByteArray#

2011-09-10 Thread GHC
#5478: GHC panics - Can't derive Show for primitive type ByteArray#
-+--
Reporter:  hvr   |   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Component:  Compiler  
 Version:  7.2.1 |Keywords:
Testcase:|   Blockedby:
  Os:  Unknown/Multiple  |Blocking:
Architecture:  Unknown/Multiple  | Failure:  Compile-time crash
-+--
 The following Haskell

 {{{
 #!hs
 {-# LANGUAGE MagicHash #-}

 import GHC.Exts

 data Foo = Foo0 ByteArray#
  deriving Show

 main = return ()
 }}}

 caused GHC to panic with

 {{{
 [1 of 1] Compiling Main ( ticket_5478.hs, ticket_5478.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.2.1 for x86_64-unknown-linux):
 Error in deriving:
 Can't derive Show for primitive type ghc-prim:GHC.Prim.ByteArray#{(w)
 tc 3f}

 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