Re: [GHC] #2919: ghc panic while compiling Crypto

2009-01-13 Thread GHC
#2919: ghc panic while compiling Crypto
--+-
 Reporter:  wchogg|  Owner:
 Type:  bug   | Status:  new   
 Priority:  normal|  Milestone:
Component:  Compiler  |Version:  6.10.1
 Severity:  normal| Resolution:
 Keywords:|   Testcase:
   Os:  Linux |   Architecture:  x86   
--+-
Comment (by StephenBlackheath):

 Workaround:

 cabal install Crypto --disable-optimization

-- 
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] #2948: the type of System.Posix.Process.executeFile is not general enough

2009-01-13 Thread GHC
#2948: the type of System.Posix.Process.executeFile is not general enough
-+--
Reporter:  nr|  Owner:  
Type:  bug   | Status:  new 
Priority:  normal|  Component:  libraries/unix  
 Version:  6.10.1|   Severity:  normal  
Keywords:|   Testcase:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-+--
 Because {{{System.Posix.Process.executeFile}}} does not return, its return
 type should be {{{IO a}}}, not {{{IO ()}}}.   This change would make it
 possible to use {{{System.Posix.Process.executeFile}}} in a context that
 expects {{{IO Int}}} or {{{IO ProcessStatus}}}, for example.

 I may well have assigned this bug to the wrong library.

-- 
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] #2947: infix precedence of backtick functions defined in ghci is not reported by :info

2009-01-13 Thread GHC
#2947: infix precedence of backtick functions defined in ghci is not reported by
:info
--+-
 Reporter:  EyalLotem |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Milestone:  
Component:  GHCi  |Version:  6.10.1  
 Severity:  normal| Resolution:  
 Keywords:|   Testcase:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
--+-
Changes (by EyalLotem):

  * severity:  minor => normal

-- 
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] #2947: infix precedence of backtick functions defined in ghci is not reported by :info

2009-01-13 Thread GHC
#2947: infix precedence of backtick functions defined in ghci is not reported by
:info
--+-
 Reporter:  EyalLotem |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Milestone:  
Component:  GHCi  |Version:  6.10.1  
 Severity:  minor | Resolution:  
 Keywords:|   Testcase:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
--+-
Comment (by EyalLotem):

 In fact, the bug is more severe, the infix declaration in ghci is not used
 at all:
 {{{
 Prelude> let infixr 0 `f` ; f = (*)
 let infixr 0 `f` ; f = (*)
 Prelude> 5 `f` 3 + 4
 19
 Prelude> :info `f`
 f :: Integer -> Integer -> Integer
 -- Defined at :1:19
 }}}

-- 
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] #2947: infix precedence of backtick functions defined in ghci is not reported by :info

2009-01-13 Thread GHC
#2947: infix precedence of backtick functions defined in ghci is not reported by
:info
-+--
Reporter:  EyalLotem |  Owner:  
Type:  bug   | Status:  new 
Priority:  normal|  Component:  GHCi
 Version:  6.10.1|   Severity:  minor   
Keywords:|   Testcase:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-+--
 excerpt from ghci:
 {{{
 Prelude> let infixr 9 `f` ; f = (+)
 let infixr 9 `f` ; f = (+)
 Prelude> 5 * 3 `f` 4
 35
 Prelude> :info f
 f :: Integer -> Integer -> Integer
 -- Defined at :1:19
 Prelude> :info `f`
 f :: Integer -> Integer -> Integer
 -- Defined at :1:19
 }}}

-- 
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] #2552: SCC annotation behavior differs between toplevel and non-toplevel

2009-01-13 Thread GHC
#2552: SCC annotation behavior differs between toplevel and non-toplevel
--+-
Reporter:  Rauli  |Owner: 
Type:  bug|   Status:  new
Priority:  normal |Milestone:  6.10 branch
   Component:  Compiler   |  Version:  6.8.2  
Severity:  normal |   Resolution: 
Keywords:  scc profiling  |   Difficulty:  Unknown
Testcase: |   Os:  Linux  
Architecture:  x86|  
--+-
Changes (by BenMoseley):

 * cc: b...@moseley.name (added)

-- 
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] #2944: Mutually recursive equality constraints

2009-01-13 Thread GHC
#2944: Mutually recursive equality constraints
---+
Reporter:  MartijnVanSteenbergen   |Owner:  igloo  
Type:  merge   |   Status:  new
Priority:  normal  |Milestone: 
   Component:  Compiler (Type checker) |  Version:  6.10.1 
Severity:  normal  |   Resolution: 
Keywords:  |   Difficulty:  Unknown
Testcase:  indexed-types/should_compile/T2944  |   Os:  MacOS X
Architecture:  x86 |  
---+
Changes (by simonpj):

  * testcase:  => indexed-types/should_compile/T2944

-- 
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] #2944: Mutually recursive equality constraints

2009-01-13 Thread GHC
#2944: Mutually recursive equality constraints
+---
Reporter:  MartijnVanSteenbergen|Owner:  igloo  
Type:  merge|   Status:  new
Priority:  normal   |Milestone: 
   Component:  Compiler (Type checker)  |  Version:  6.10.1 
Severity:  normal   |   Resolution: 
Keywords:   |   Difficulty:  Unknown
Testcase:   |   Os:  MacOS X
Architecture:  x86  |  
+---
Changes (by simonpj):

  * owner:  => igloo
  * difficulty:  => Unknown
  * type:  bug => merge

Comment:

 I agree:
 {{{
 Tue Jan 13 16:27:16 GMT 2009  simo...@microsoft.com
   * Make -XTypeFamilies imply -XRelaxedPolyRec (Trac #2944)
 }}}
 It's moot whether we should merge this, but on balance, yes.

 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] #2931: Template Haskell: Quoting single letter identifier leads to a parse error at end of input.

2009-01-13 Thread GHC
#2931: Template Haskell: Quoting single letter identifier leads to a parse error
at end of input.
--+-
Reporter:  int-e  |Owner:  igloo   
Type:  merge  |   Status:  new 
Priority:  normal |Milestone:  
   Component:  Compiler (Parser)  |  Version:  6.10.1  
Severity:  normal |   Resolution:  
Keywords: |   Difficulty:  Unknown 
Testcase:  th/T2931   |   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple   |  
--+-
Changes (by simonpj):

  * testcase:  => th/T2931
  * difficulty:  => Unknown
  * type:  bug => merge
  * owner:  => igloo

Comment:

 Good point.  Fixed by
 {{{
 Tue Jan 13 17:09:48 GMT 2009  simo...@microsoft.com
   * Fix Trac #2931
 }}}
 Please merge to stable branch.  Test added.

 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] #2935: "A lazy (~) pattern cannot bind existential type variables" happens for non-existential GADTs

2009-01-13 Thread GHC
#2935: "A lazy (~) pattern cannot bind existential type variables" happens for
non-existential GADTs
-+--
Reporter:  ganesh|Owner:  
Type:  bug   |   Status:  closed  
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.10.1  
Severity:  normal|   Resolution:  wontfix 
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by simonpj):

 Changed error message
 {{{
 Tue Jan 13 16:40:20 GMT 2009  simo...@microsoft.com
   * Improve error messages slightly
 }}}
 The change is this
 {{{
 hunk ./compiler/typecheck/TcPat.lhs 981
 -   text "I can't handle pattern bindings for existentially-
 quantified constructors.",
 +   text "I can't handle pattern bindings for existential or
 GADT data constructors.",
 hunk ./compiler/typecheck/TcPat.lhs 1033
 -hang (ptext (sLit "A lazy (~) pattern cannot bind existential
 type variables"))
 +hang (ptext (sLit "A lazy (~) pattern cannot match existential or
 GADT data constructors"))
 }}}

-- 
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] #2368: ASSERT failed! file coreSyn/CorePrep.lhs line 669

2009-01-13 Thread GHC
#2368: ASSERT failed! file coreSyn/CorePrep.lhs line 669
--+-
Reporter:  batterseapower |Owner:  igloo  
Type:  bug|   Status:  new
Priority:  normal |Milestone:  6.10.2 
   Component:  Compiler   |  Version:  6.9
Severity:  normal |   Resolution: 
Keywords: |   Difficulty:  Unknown
Testcase:  simplCore/should_compile/simpl014  |   Os:  MacOS X
Architecture:  Unknown/Multiple   |  
--+-
Changes (by simonpj):

  * owner:  => igloo

Comment:

 I believe this is fixed by
 {{{
 Tue Jan 13 16:49:53 GMT 2009  simo...@microsoft.com
   * Rewrite CorePrep and improve eta expansion
 }}}
 Do not merge to the 6.10 branch (at least not yet); it's a bit radical.

 Ian: can you check you agree this is now ok, and close.

 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] #2946: tracing should be controled by a global flag (it should not be resume context specific)

2009-01-13 Thread GHC
#2946: tracing should be controled by a global flag (it should not be resume
context specific)
-+--
Reporter:  phercek   |  Owner:  
Type:  feature request   | Status:  new 
Priority:  normal|  Component:  GHCi
 Version:  6.10.1|   Severity:  minor   
Keywords:  debugger  |   Testcase:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-+--
 Instead of ":trace" and ":trace " command there should be one
 command ":set trace on/off" and a new command ":debug ".

 ":set trace" would control a global flag indicating whether tracing should
 be active or not. If tracing is active then:[[BR]]
  * ":continue" would behave like current ":trace",[[BR]]
  * forcing a value using ":force " woudl work like current ":trace
 " but ignoring breakpoitns,[[BR]]
  * ":debug " would work like current ":trace ",[[BR]]
  * and ":main ..." would start Main.main with tracing on from the very
 beginning.[[BR]]
 If tracing is not active then ":continue", ":force", ":main" would behave
 like they do now and ":debug " would be the same as current
 "".

 Reasoning:

  I believe people use tracing to get access to variables which are not
 free in the selected scope but which contributed to values in the selected
 scope. So if they want variable availability they want tracing on all the
 time if they care about speed they want tracing off all the time. With
 this change request accepted they do not need to remember which command to
 use to continue or to print a forced value. When an  is an argument
 to a ghci command and tracing is on then trace hisotry is extended, if
 tracing is off then trace history is not extended, if  is typed on
 the ghci command line directly then tracing is never extended.

  This change is not that important for manual ussage but it helps to
 simplify custom defined ghci comamnds/scripts (which e.g. will not need to
 take care whether to use ":continue" or ":trace" based on a global flag).
 This would also allow to start tracing from the very beggining of ":main"
 instead of setting a break at Main.main with a script set to ":trace" and
 then running ":main ...".

 Related discussion is here: http://www.haskell.org/pipermail/glasgow-
 haskell-users/2009-January/016436.html

 I do not know about other usage patterns for which the current state of
 tracing UI is better. If you do know then vote against 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] #2937: source file that compiled fine fails to recompile after touching it (yes, another one)

2009-01-13 Thread GHC
#2937: source file that compiled fine fails to recompile after touching it (yes,
another one)
-+--
Reporter:  rwbarton  |Owner:  igloo   
Type:  merge |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.11
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by simonpj):

  * owner:  => igloo
  * difficulty:  => Unknown
  * type:  bug => merge

Comment:

 Excellent bug thank you.  Fixed by
 {{{
 Tue Jan 13 15:32:17 GMT 2009  simo...@microsoft.com
   * Fix Trac #2937: deserialising assoicated type definitions
 }}}
 Please merge to branch.

 And Ian: could you make a test for this? It's not totally straightforward
 because it really requires the touch (or `-fforce-recomp`) in the middle.
 Thanks.

 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] #2739: GHC API crashes on template haskell splices

2009-01-13 Thread GHC
#2739: GHC API crashes on template haskell splices
-+--
Reporter:  waern |Owner:  nominolo
Type:  bug   |   Status:  assigned
Priority:  normal|Milestone:  6.10.2  
   Component:  Compiler  |  Version:  6.10.1  
Severity:  major |   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by simonpj):

 Maybe you have stumbled on a type-families bug.  But I can't tell unless I
 can reproduce it.  Can you make it happen with GHCi?  If not, how can I
 reproduce 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


Re: [GHC] #2945: trace history should not be context/resume specific but global

2009-01-13 Thread GHC
#2945: trace history should not be context/resume specific but global
--+-
 Reporter:  phercek   |  Owner:  
 Type:  feature request   | Status:  new 
 Priority:  normal|  Milestone:  
Component:  GHCi  |Version:  6.10.1  
 Severity:  normal| Resolution:  
 Keywords:  debugger  |   Testcase:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
--+-
Comment (by phercek):

 By global, I meant the same place where top level bindings are (so the
 trace history would get removed when modules are reloaded).

 May be the resume context should keep the mumber of hisotry records
 contributed from the current resume context, so that they can be purged
 when ":abandon" is issued. I do not have strong opinion about this since I
 almost never use ":abandon".

-- 
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] #2945: trace history should not be context/resume specific but global

2009-01-13 Thread GHC
#2945: trace history should not be context/resume specific but global
-+--
Reporter:  phercek   |  Owner:  
Type:  feature request   | Status:  new 
Priority:  normal|  Component:  GHCi
 Version:  6.10.1|   Severity:  normal  
Keywords:  debugger  |   Testcase:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-+--
 Currently trace history is stored in "Resume" context. I'm not aware of
 any good reason for this but it results in problems during debugging. The
 point is that one cannot extend currently active trace history using
 ":trace " while stopped at breakpoint. The nested trace history is
 extended instead. But the nested history is freed when the ":trace
 " command finishes so there is no access to the trace data. This
 makes it hard to investigate why the output of the trace command looks the
 way it was printed: it is not possible to investigate values of variables
 which contributed to the  value.

 A discussion about the reasons for global trace history is here:
  http://www.haskell.org/pipermail/glasgow-haskell-
 users/2009-January/016436.html

-- 
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] #2944: Mutually recursive equality constraints

2009-01-13 Thread GHC
#2944: Mutually recursive equality constraints
--+-
Reporter:  MartijnVanSteenbergen  |  Owner: 
Type:  bug| Status:  new
Priority:  normal |  Component:  Compiler (Type checker)
 Version:  6.10.1 |   Severity:  normal 
Keywords: |   Testcase: 
  Os:  MacOS X|   Architecture:  x86
--+-
 Given this piece of code:

 {{{
 {-# LANGUAGE TypeFamilies #-}

 class C a where
   type T a :: *

 f1 :: T a ~ () => a
 f1 = f2

 f2 :: T a ~ () => a
 f2 = f1
 }}}

 GHC complains:

 {{{
 Couldn't match expected type `T a ~ ()'
against inferred type `T a1 ~ ()'
 When matching the contexts of the signatures for
   f1 :: forall a. (T a ~ ()) => a
   f2 :: forall a. (T a ~ ()) => a
 The signature contexts in a mutually recursive group should all be
 identical
 When generalising the type(s) for f1, f2
 }}}

 Is this a bug? Enabling RelaxedPolyRec fixes the problem. Should
 TypeFamilies—just like GADTs—imply RelaxedPolyRec?

-- 
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] #1897: Ambiguous types and rejected type signatures

2009-01-13 Thread GHC
#1897: Ambiguous types and rejected  type signatures
+---
Reporter:  guest|Owner:  chak   
Type:  bug  |   Status:  reopened   
Priority:  normal   |Milestone:  6.10 branch
   Component:  Compiler (Type checker)  |  Version:  6.9
Severity:  normal   |   Resolution: 
Keywords:   |   Difficulty:  Unknown
Testcase:   |   Os:  Linux  
Architecture:  x86  |  
+---
Changes (by simonpj):

 * cc: and...@cs.uu.nl (added)

Comment:

 Here is yet another example, this time from Andres Loeh:
 {{{
 {-# LANGUAGE TypeFamilies, EmptyDataDecls, RankNTypes #-}
 module Foo where

 data X (a :: *)
 type family Y (a :: *)

 -- This works (datatype).
 i1 :: (forall a. X a) -> X Bool
 i1 x = x

 -- This works too (type family and extra arg).
 i2 :: (forall a. a -> Y a) -> Y Bool
 i2 x = x True

 -- This doesn't work (type family).
 i3 :: (forall a. Y a) -> Y Bool
 i3 x = x
 }}}
 The definition `i3` is currently rejected, because we can't determine that
 `Y alpha ~ Y Bool`, where `alpha` is an otherwise unconstrained
 unification variable, that comes from instantiating the occurrence of `x`.
 Choosing `alpha := Bool` will solve this, and in this case any solution
 will do; it's a bit like resolving an ambiguous type variable.

 It's tricky in general, though.  Suppose we had two constraints `(X alpha
 ~ X Bool)` and `(Y alpha ~ Y Char)`. Now we can't solve it so easily!

 Worse, suppose we had an instance declaration
 {{{
   type instance Y Bool = Char
 }}}
 Should we still resolve `alpha := Bool`?  Would the answer change if there
 was a ''second'' instance?
 {{{
   type instance Y Int = Char
 }}}
 Arguably, searching for all possible solutions is not terribly good.

 It's not at all obvious what the Right Thing is.

 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] #2941: HsBase.h includes termios.h which prevents us including curses.h on solaris

2009-01-13 Thread GHC
#2941: HsBase.h includes termios.h which prevents us including curses.h on 
solaris
---+
Reporter:  duncan  |Owner: 
Type:  bug |   Status:  closed 
Priority:  normal  |Milestone: 
   Component:  libraries/base  |  Version:  6.8.3  
Severity:  normal  |   Resolution:  fixed  
Keywords:  |   Difficulty:  Unknown
Testcase:  |   Os:  Solaris
Architecture:  sparc   |  
---+
Changes (by simonmar):

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

Comment:

 Fixed in 6.10.1, because we don't `#include` anything in `.hc` files.  I
 ''knew'' it was a good idea to do that!

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