Re: [GHC] #7248: NewCodeGen does not create enough SRT labels when using SplitObjs

2012-09-18 Thread GHC
#7248: NewCodeGen does not create enough SRT labels when using SplitObjs
-+--
 Reporter:  darchon  |  Owner:   
 Type:  bug  | Status:  new  
 Priority:  normal   |  Component:  Compiler (NCG)   
  Version:  7.7  |   Keywords:  SplitObjs NCG SRT
   Os:  MacOS X  |   Architecture:  x86  
  Failure:  Building GHC failed  |   Testcase:   
Blockedby:   |   Blocking:   
  Related:   |  
-+--

Comment(by darchon):

 Some additional info.

 Build still fails as of: 9615222985f40b62410e1ccc7b6e8581c2729150

 My system:
 {{{
 OS X 10.6.8
 XCode 3.2.6
 Bootstrap: GHC 7.4.2 (i386)
 }}}

 build.mk:
 {{{
 SRC_HC_OPTS = -O -H64m
 GhcStage1HcOpts = -O -fasm
 GhcStage2HcOpts = -O2 -fasm
 GhcHcOpts   = -Rghc-timing
 GhcLibHcOpts= -O2
 GhcLibWays = v
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7248#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] #7237: CgCase fails with strict data/functions

2012-09-18 Thread GHC
#7237: CgCase fails with strict data/functions
-+--
Reporter:  jwlato|   Owner:  
Type:  bug   |  Status:  merge   
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  codeGen/should_compile/T7237
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonpj):

  * status:  new = merge
  * difficulty:  = Unknown
  * testcase:  = codeGen/should_compile/T7237


Comment:

 Thank you for reporting.  I've added a regression test too.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7237#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] #5252: UNPACK without optimisation leads to panic

2012-09-18 Thread GHC
#5252: UNPACK without optimisation leads to panic
---+
  Reporter:  simonpj   |  Owner:
  
  Type:  bug   | Status:  merge 
  
  Priority:  normal|  Milestone:
  
 Component:  Compiler  |Version:  7.6.1 
  
Resolution:|   Keywords:
  
Os:  Unknown/Multiple  |   Architecture:  
Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  
Unknown 
  Testcase:  deSugar/should_compile/T5252, T5252Take2  |  Blockedby:
  
  Blocking:|Related:
  
---+
Changes (by simonpj):

  * status:  new = merge
  * testcase:  deSugar/should_compile/T5252 =
   deSugar/should_compile/T5252, T5252Take2


Comment:

 Needs this patch too:
 {{{
 commit ba8fd081ba9b222dd5f93604d7deeaca372e4511
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Mon Sep 17 18:22:10 2012 +0100

 Make the call to chooseBoxingStrategy lazy again

 I made it strict, as an incidental consequence of this patch:

   commit 5bae803a18b17bdb158a7780e6b6ac3c520e5b39
   Author: Simon Peyton Jones simo...@microsoft.com
   Date:   Sat Sep 15 23:09:25 2012 +0100
   Fix UNPACK with -fomit-interface-pragmas.

 But it's very important that chooseBoxingStrategy is lazy, else
 (in bigger programs with lots of recursion in types) GHC can
 loop. This showed up in Data.Sequence; and I think it was making
 haddock loop as well.

 Anyway this patch makes it lazy again.

  compiler/typecheck/TcTyClsDecls.lhs |   34
 +-
  1 file changed, 17 insertions(+), 17 deletions(-)
 }}}
 Regression test added.

 Merge to 7.6 branch.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5252#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] #7240: Stack trace truncated too much with indirect recursion

2012-09-18 Thread GHC
#7240: Stack trace truncated too much with indirect recursion
--+-
 Reporter:  nomeata   |  Owner:  nomeata 
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Profiling   
  Version:  7.4.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-

Comment(by nomeata):

 Hmm, I’d prefer to update the bug description, but it seems that I do not
 have the rights for that. Anyways, here is a simpler and cleaner
 description of the problem. Consider this code:

 {{{
 module Main where
 import GHC.Stack

 f () = currentCallStack = putStrLn . renderStack
 main = boringCombinator (interestingFunction f) ()
 interestingFunction f x = boringCombinator f x
 boringCombinator f x = f x
 }}}

 Currently, it prints:
 {{{
 Stack trace:
   Main.f (callstack005.hs:4:8-50)
   Main.boringCombinator (callstack005.hs:7:24-26)
   Main.main (callstack005.hs:5:8-50)
   Main.CAF (entire-module)
 }}}
 when I, as a developer, would expect this output:
 {{{
 Stack trace:
   Main.f (callstack005.hs:4:8-50)
   Main.boringCombinator (callstack005.hs:7:24-26)
   Main.interestingFunction (callstack005.hs:6:27-46)
   Main.main (callstack005.hs:5:26-46)
   Main.boringCombinator (callstack005.hs:7:24-26)
   Main.main (callstack005.hs:5:8-50)
   Main.CAF (entire-module)
 }}}
 This output is obtained by either not truncating at all, or only
 truncating repeating segments of the callstack.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7240#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] #7224: Polymorphic kind annotations on type classes don't always work as expected

2012-09-18 Thread GHC
#7224: Polymorphic kind annotations on type classes don't always work as 
expected
+---
Reporter:  slindley |   Owner:  
 
Type:  bug  |  Status:  merge   
 
Priority:  normal   |   Milestone:  
 
   Component:  Compiler (Type checker)  | Version:  7.6.1-rc1   
 
Keywords:  kind polymorphism|  Os:  Unknown/Multiple
 
Architecture:  Unknown/Multiple | Failure:  GHC rejects valid 
program
  Difficulty:  Unknown  |Testcase:  polykinds/T7224 
 
   Blockedby:   |Blocking:  
 
 Related:   |  
+---
Changes (by simonpj):

  * status:  new = merge
  * difficulty:  = Unknown
  * testcase:  = polykinds/T7224


Comment:

 Thanks for the report.  The declaration of {{{PMonad'}}} is bogus becuase
 you are using a ''kind'' variable `i` in a ''type'', the type of
 {{{ret'}}}.  Now GHC says
 {{{
 T7224.hs:10:19:
 Kind variable `i' used as a type
 In the type `a - m i i a'
 In the class declaration for PMonad'
 }}}
 Merge to 7.6 branh.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7224#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] #7176: Failure to let kind variable remain uninstantiated when not needed

2012-09-18 Thread GHC
#7176: Failure to let kind variable remain uninstantiated when not needed
---+
  Reporter:  goldfire  |  Owner:
  Type:  bug   | Status:  closed
  Priority:  normal|  Milestone:
 Component:  Compiler  |Version:  7.6.1-rc1 
Resolution:  fixed |   Keywords:  PolyKinds TypeFamilies
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple  
   Failure:  None/Unknown  | Difficulty:  Unknown   
  Testcase:  polykinds/T7176   |  Blockedby:
  Blocking:|Related:
---+
Changes (by simonpj):

  * status:  new = closed
  * testcase:  = polykinds/T7176
  * resolution:  = fixed


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7176#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] #7230: GHC states the same kind mismatched

2012-09-18 Thread GHC
#7230: GHC states the same kind mismatched
---+
Reporter:  konn|   Owner:   
Type:  bug |  Status:  merge
Priority:  normal  |   Milestone:   
   Component:  Compiler| Version:  7.7  
Keywords:  |  Os:  MacOS X  
Architecture:  x86_64 (amd64)  | Failure:  Incorrect warning at compile-time
  Difficulty:  Unknown |Testcase:  T7230
   Blockedby:  |Blocking:   
 Related:  |  
---+
Changes (by simonpj):

  * status:  new = merge
  * difficulty:  = Unknown
  * testcase:  = T7230


Comment:

 Thanks for the example, now fixed.



 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7230#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] #7238: class methods with associated equality constraints panic

2012-09-18 Thread GHC
#7238: class methods with associated equality constraints panic
---+
Reporter:  dmwit   |   Owner:  simonpj   
Type:  bug |  Status:  merge 
Priority:  normal  |   Milestone:
   Component:  Compiler| Version:  7.6.1 
Keywords:  |  Os:  Linux 
Architecture:  x86_64 (amd64)  | Failure:  Compile-time crash
  Difficulty:  Unknown |Testcase:  polykinds/T7238   
   Blockedby:  |Blocking:
 Related:  |  
---+
Changes (by simonpj):

  * status:  new = merge
  * testcase:  = polykinds/T7238


Comment:

 Great, thanks.  Now fixed.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7238#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] #7224: Polymorphic kind annotations on type classes don't always work as expected

2012-09-18 Thread GHC
#7224: Polymorphic kind annotations on type classes don't always work as 
expected
+---
Reporter:  slindley |   Owner:  
 
Type:  bug  |  Status:  merge   
 
Priority:  normal   |   Milestone:  
 
   Component:  Compiler (Type checker)  | Version:  7.6.1-rc1   
 
Keywords:  kind polymorphism|  Os:  Unknown/Multiple
 
Architecture:  Unknown/Multiple | Failure:  GHC rejects valid 
program
  Difficulty:  Unknown  |Testcase:  polykinds/T7224 
 
   Blockedby:   |Blocking:  
 
 Related:   |  
+---

Comment(by slindley):

 Ah yes. Kind variables bound at the top level of a type class definition
 are in scope for the rest of the class definition. I guess (if the GHC
 type system was suitably adapted) it might actually be useful to allow
 kind variables in types.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7224#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] #7243: regression: acceptable foreign result types

2012-09-18 Thread GHC
#7243: regression: acceptable foreign result types
---+
Reporter:  dmwit   |   Owner:  igloo
Type:  bug |  Status:  new  
Priority:  normal  |   Milestone:  7.6.2
   Component:  Compiler (FFI)  | Version:  7.6.1
Keywords:  |  Os:  Unknown/Multiple 
Architecture:  x86_64 (amd64)  | Failure:  GHC rejects valid program
  Difficulty:  Unknown |Testcase:   
   Blockedby:  |Blocking:   
 Related:  |  
---+

Comment(by simonpj):

 See also #5610.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7243#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] #5610: Improve Unacceptable argument type in foreign declaration error message

2012-09-18 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 simonpj):

 See also #7243

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5610#comment:15
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] #7239: GHC panic: MkExternalCore died: make_lit

2012-09-18 Thread GHC
#7239: GHC panic: MkExternalCore died: make_lit
--+-
Reporter:  audunska   |   Owner:
Type:  bug|  Status:  merge 
Priority:  normal |   Milestone:
   Component:  Compiler   | Version:  7.4.1 
Keywords:  panic, MkExternalCore  |  Os:  Linux 
Architecture:  x86_64 (amd64) | Failure:  Compile-time crash
  Difficulty:  Unknown|Testcase:  ext-core/T7239
   Blockedby: |Blocking:
 Related: |  
--+-
Changes (by simonpj):

  * status:  new = merge
  * testcase:  = ext-core/T7239


Comment:

 Test added.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7239#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] #7176: Failure to let kind variable remain uninstantiated when not needed

2012-09-18 Thread GHC
#7176: Failure to let kind variable remain uninstantiated when not needed
---+
  Reporter:  goldfire  |  Owner:
  Type:  bug   | Status:  closed
  Priority:  normal|  Milestone:
 Component:  Compiler  |Version:  7.6.1-rc1 
Resolution:  fixed |   Keywords:  PolyKinds TypeFamilies
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple  
   Failure:  None/Unknown  | Difficulty:  Unknown   
  Testcase:  polykinds/T7176   |  Blockedby:
  Blocking:|Related:
---+

Comment(by simonpj):

 In the end I did the same tiny fix on the HEAD, to avoid getting tangled
 up in later changes
 {{{
 commit f4c327ad08d9df0fbafa0ad476a9ef26f8cd6abb
 Author: Simon Peyton Jones simo...@microsoft.com
 Date:   Fri Sep 14 11:12:01 2012 +0100

 When allocating a new kind variable, do so with newMetaUnique

 ---

  compiler/typecheck/TcMType.lhs |2 +-
  1 files changed, 1 insertions(+), 1 deletions(-)

 diff --git a/compiler/typecheck/TcMType.lhs
 b/compiler/typecheck/TcMType.lhs index a212f25..67ed967 100644
 --- a/compiler/typecheck/TcMType.lhs
 +++ b/compiler/typecheck/TcMType.lhs
 @@ -113,7 +113,7 @@ import Data.List( (\\), partition, mapAccumL )

  \begin{code}
  newMetaKindVar :: TcM TcKind
 -newMetaKindVar = do { uniq - newUnique
 +newMetaKindVar = do { uniq - newMetaUnique
 ; ref - newMutVar Flexi
 ; return (mkTyVarTy (mkMetaKindVar uniq ref)) }
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7176#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] #7240: Stack trace truncated too much with indirect recursion

2012-09-18 Thread GHC
#7240: Stack trace truncated too much with indirect recursion
--+-
 Reporter:  nomeata   |  Owner:  nomeata 
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Profiling   
  Version:  7.4.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-

Comment(by nomeata):

 In comment:1 I wondered if there are already unexpected effects when
 combining the current truncation policy with the ```enterFunCCS``` logic,
 and there are. Consider this program:

 {{{
 module Main where
 import GHC.Stack

 f 0  = currentCallStack = putStrLn . renderStack
 main = boringCombinator (interestingFunction1)  0
 interestingFunction1 x = interestingFunction2 x
 interestingFunction2 x = case genFun x of Just g - boringCombinator g x
 boringCombinator f x = f x
 genFun x = Just $ \y - f y
 }}}

 With no truncating policy at all, this is the stack trace:

 {{{
 Stack trace:
   Main.f (callstack005.hs:4:8-50)
   Main.genFun (callstack005.hs:9:25-27)
   Main.genFun (callstack005.hs:9:12-27)
   Main.interestingFunction2 (callstack005.hs:7:31-38)
   Main.boringCombinator (callstack005.hs:8:24-26)
   Main.interestingFunction2 (callstack005.hs:7:53-72)
   Main.interestingFunction1 (callstack005.hs:6:26-47)
   Main.boringCombinator (callstack005.hs:8:24-26)
   Main.main (callstack005.hs:5:8-49)
   Main.CAF (entire-module)
 }}}

 Note that when, in the second invocation of ```boringCombinator```, the
 thunk generated by ```genFun``` is called and ```interestingFunction1```
 is on both the stack of the call site and the function (part of the common
 prefix), so it is not appended to the stack. But with the current output,
 the result is

 {{{
 Stack trace:
   Main.f (callstack005.hs:4:8-50)
   Main.genFun (callstack005.hs:9:25-27)
   Main.genFun (callstack005.hs:9:12-27)
   Main.interestingFunction2 (callstack005.hs:7:31-38)
   Main.interestingFunction1 (callstack005.hs:6:26-47)
   Main.boringCombinator (callstack005.hs:8:24-26)
   Main.main (callstack005.hs:5:8-49)
   Main.CAF (entire-module)
 }}}

 Here, ```interestingFunction1``` was truncated from the stack between the
 first and the second invocation of  ```boringCombinator```. But it still
 lies on the stack of the thunk, so it is appended after the second
 invocation of ```boringCombinator```, suddenly reversing the order of
 things on the stack.

 So I conclude that both policies, the one in place and the one I am
 suggesting, do not behave perfectly WRT to the stack merging. (Ideally, a
 stack truncating function should commute with ```++```, but it is not
 clear to me if that is even possible without storing the whole stack).

 That leads us to the question what policy is more desired. I would argue
 that the current policy truncates too much, i.e. in the example in
 comment:3, the interesting functions would neither show up in the stack
 trace nor get cost allocated for ```f```.

 What effects would my policy have on the profiles? It would be more
 accurate about the now truncated functions: Because it only truncates
 duplicate segments, any function that is on the stack without any
 truncation will be on the stack with my policy.

 OTOH functions who appear several times will inherit the cost several
 times (```inheritCosts``` in Profiling.c). Is that acceptable? Maybe even
 desirable? ```inheritCosts``` does not seem to be time-critical, so one
 could add code that only adds the current cc’s values to the ccs if this
 cc is not already present on the ccs above (and hence was already
 counted).

 If that is algorithmically to slow we can use the information in
 ```pushCostCentre``` (where we already have it, due to ```checkLoop```)
 and save it in the ccs via ```actualPush```.

 Ok, enough analysis for now; I should now wait for feedback.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7240#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] #5610: Improve Unacceptable argument type in foreign declaration error message

2012-09-18 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 romildo):

 * cc: malaquias@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5610#comment:16
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] #367: Infinite loops can hang Concurrent Haskell

2012-09-18 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by simonmar):

 You could improve code size by omitting the `HpAlloc = 0` assignment
 (perhaps making sure that it is initialized to zero in `LOAD_THREAD_STATE`
 or something).

 Another alternative is to use `SpLim` instead of `HpLim` to trigger the
 interrupt, on the grounds that there are more stack checks than heap
 checks.  We would have to put `SpLim` in a memory location instead of a
 register, but we could move `HpLim` into a register.

 Something else we could do is add a flag on every top-level function to
 say whether it is non-allocating (rather like the `NoCafRefs` flag), and
 we could use that to optimise away many of the extra checks.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:19
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] #7116: Missing optimisation: strength reduction of floating-point multiplication

2012-09-18 Thread GHC
#7116: Missing optimisation: strength reduction of floating-point multiplication
-+--
Reporter:  simonmar  |   Owner:  pcapriotti 
Type:  bug   |  Status:  new
Priority:  normal|   Milestone:  7.8.1  
   Component:  Compiler  | Version:  7.4.2  
Keywords:|  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple  | Failure:  Runtime performance bug
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--
Changes (by simonpj):

  * owner:  = pcapriotti


Comment:

 Paolo: yes, please commit your patch.  But could you add a comment `Note
 [Strength reduction]` that explains how it works.  In particular the lit
 is always `2`, and the `op` is always `(+)`; but at either `Float` or
 `Double`.  Perhapas you can name the `op` parameter `add_op`?  And `lit`
 can be `two_lit`.  But the comment as well!

 Thanks

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7116#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] #7235: panic! when compiling happstack-server-7.0.4

2012-09-18 Thread GHC
#7235: panic! when compiling happstack-server-7.0.4
+---
  Reporter:  guest  |  Owner:  
  Type:  bug| Status:  closed  
  Priority:  normal |  Milestone:  
 Component:  Compiler   |Version:  7.4.2   
Resolution:  duplicate  |   Keywords:  
Os:  Linux  |   Architecture:  Unknown/Multiple
   Failure:  GHC rejects valid program  | Difficulty:  Unknown 
  Testcase: |  Blockedby:  
  Blocking: |Related:  
+---

Comment(by simonpj):

 Another possiblity is that `Happstack` is generating an empty
 comprehension `CompExp[]`.  In that case, what should happen?  The pretty
 printer probably shouldn't fall over.   Maybe it should print `empty
 CompE` in the pretty-printed output?  I'll do that for now, and for the
 other call to `error` in `TH.Ppr`.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7235#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] #7249: ghc no longer needs to build HS*.o ghci library files

2012-09-18 Thread GHC
#7249: ghc no longer needs to build HS*.o ghci library files
--+-
 Reporter:  juhpetersen   |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Build System
  Version:  7.6.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 I believe that ghci libraries files (HS*.o) are now redundant (and Cabal
 no longer builds them at least in trunk) so I think it would be good to
 stop ghc building them also now.

 I didn't try hard but didn't work out yet how to do this in the ghc build
 system - patching Cabal didn't seem to be sufficient.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7249
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] #1877: Change the meaning of -fextended-default-rules

2012-09-18 Thread GHC
#1877: Change the meaning of -fextended-default-rules
+---
Reporter:  simonmar |   Owner:  
Type:  task |  Status:  new 
Priority:  lowest   |   Milestone:  7.6.2   
   Component:  GHCi | Version:  6.8.1   
Keywords:   |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple | Failure:  None/Unknown
  Difficulty:  Easy (less than 1 hour)  |Testcase:  
   Blockedby:   |Blocking:  
 Related:   |  
+---

Comment(by simonpj):

 Acutally, isn't this fixed?  We now have `:set` and `:seti` in GHCi, see
 [http://www.haskell.org/ghc/docs/latest/html/users_guide/ghci-set.html
 #ghci-interactive-options the manual 2.8.3].  So can we close this ticket?

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1877#comment:17
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] #7249: ghc no longer needs to build HS*.o ghci library files

2012-09-18 Thread GHC
#7249: ghc no longer needs to build HS*.o ghci library files
-+--
Reporter:  juhpetersen   |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Build System  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonmar):

  * difficulty:  = Unknown


Comment:

 I think we're concerned that it will be slow to load the .a file when it
 was built with `-split-objs`, so someone should measure that.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7249#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] #1877: Change the meaning of -fextended-default-rules

2012-09-18 Thread GHC
#1877: Change the meaning of -fextended-default-rules
---+
  Reporter:  simonmar  |  Owner: 
  Type:  task  | Status:  closed 
  Priority:  lowest|  Milestone:  7.6.2  
 Component:  GHCi  |Version:  6.8.1  
Resolution:  fixed |   Keywords: 
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple   
   Failure:  None/Unknown  | Difficulty:  Easy (less than 1 hour)
  Testcase:|  Blockedby: 
  Blocking:|Related: 
---+
Changes (by simonmar):

  * status:  new = closed
  * resolution:  = fixed


Comment:

 Yes, I think we can.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1877#comment:18
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] #7250: Documentation of System.Mem.Weak should emphasize finalizers may be run earlier than expected

2012-09-18 Thread GHC
#7250: Documentation of System.Mem.Weak should emphasize finalizers may be run
earlier than expected
--+-
 Reporter:  edsko |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Documentation   
  Version:  7.6.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 The problem is mentioned in addFinalizer, but not in mkWeak; moreover, the
 documentation of addFinalizer reads as if this is a problem specific to
 foreign pointers, which is not (and, unrelated, ForeignPtr# does not exist
 anymore).

 It would be useful if the problem were highlighted in mkWeak, as it may
 introduce hard to find bugs in user code in cases where finalizers that
 are run too early cause problems. The behaviour of mkWeak is highly non-
 obvious.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7250
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] #5926: Add strict versions of modifyIORef and atomicModifyIORef

2012-09-18 Thread GHC
#5926: Add strict versions of modifyIORef and atomicModifyIORef
--+-
  Reporter:  joeyadams|  Owner:  simonmar
  Type:  feature request  | Status:  closed  
  Priority:  normal   |  Milestone:  7.6.1   
 Component:  libraries/base   |Version:  7.4.1   
Resolution:  fixed|   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Runtime performance bug  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-

Comment(by dons):

 For historical reference, see this 2009 thread on the issue (I was trying
 to find this thread, but google doesn't seem to like to index it).

 * [http://www.haskell.org/pipermail/haskell-cafe/2009-June/063137.html
 IORef memory leak]

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


[GHC] #7251: ghc: unrecognised flags: -fdph-par

2012-09-18 Thread GHC
#7251: ghc: unrecognised flags: -fdph-par
--+-
 Reporter:  leonardo  |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Compiler
  Version:  7.4.1 |   Keywords:  
   Os:  Windows   |   Architecture:  x86 
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 Hello,

 I have tried to compile the program that is given in
 [http://www.haskell.org/haskellwiki/GHC/Data_Parallel_Haskell] section
 1.5.4 . When I try to compile the program with

 {{{
 ghc -c -Odph -fdph-par DotP.hs
 }}}

 I get the message:

  ghc: unrecognised flags: -fdph-par
 I have installed Haskell Platfrom with GHC 7.4.1

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7251
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] #7223: Unregisterised and/or via-C compilation broken

2012-09-18 Thread GHC
#7223: Unregisterised and/or via-C compilation broken
---+
  Reporter:  simonmar  |  Owner:  simonmar
  Type:  bug   | Status:  closed  
  Priority:  highest   |  Milestone:  7.8.1   
 Component:  Compiler  |Version:  7.7 
Resolution:  fixed |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonmar):

  * status:  new = closed
  * resolution:  = fixed


Comment:

 I think this fixes it:

 commit 3f2df8a59efbbf904b57f65e1686f9dd6e8b
 {{{
 Author: Simon Marlow marlo...@gmail.com
 Date:   Tue Sep 18 14:49:16 2012 +0100

 Declare SRT labels correctly in the via-C backend
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7223#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] #7222: The text Possible fix: add an instance declaration for ... is redundant and not usually helpful

2012-09-18 Thread GHC
#7222: The text Possible fix: add an instance declaration for ... is redundant
and not usually helpful
-+--
Reporter:  maltem|   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.4.2   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  Other   
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonpj):

  * difficulty:  = Unknown


Comment:

 I think the original suggestion is right, and I've followed it, in the
 `tc-untouchables` branch.  I'll merge into HEAD, hopefully within days.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7222#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] #7252: Impossible error when deriving lower-cased type class (nameModule show{tv a9Y})

2012-09-18 Thread GHC
#7252: Impossible error when deriving lower-cased type class (nameModule show{tv
a9Y})
+---
 Reporter:  sfogarty|  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 had a student who incorrectly typed 'deriving (show)' instead of
 'deriving (Show)', and got a very interesting error, as shown below. It
 happens in both ghc and ghci. The file should of course be rejected, but
 perhaps with a different error message.

 $ cat Bug.hs
 module Types where
 data FuelEfficiency = MPG Float | LPHK Float deriving (show)
 $ ghc Bug.hs
 [1 of 1] Compiling Types( Bug.hs, Bug.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.4.2 for x86_64-unknown-linux):
 nameModule show{tv a9Y}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7252
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] #7252: Impossible error when deriving lower-cased type class (nameModule show{tv a9Y})

2012-09-18 Thread GHC
#7252: Impossible error when deriving lower-cased type class (nameModule show{tv
a9Y})
---+
Reporter:  sfogarty|Owner:
Type:  bug |   Status:  closed
Priority:  normal  |Component:  Compiler  
 Version:  7.4.2   |   Resolution:  duplicate 
Keywords:  |   Os:  Linux 
Architecture:  x86_64 (amd64)  |  Failure:  Compile-time crash
Testcase:  |Blockedby:
Blocking:  |  Related:
---+
Changes (by guest):

  * status:  new = closed
  * resolution:  = duplicate


Comment:

 This is already fixed in GHC 7.6, bug #5961.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7252#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] #7237: CgCase fails with strict data/functions

2012-09-18 Thread GHC
#7237: CgCase fails with strict data/functions
-+--
Reporter:  jwlato|   Owner:  
Type:  bug   |  Status:  merge   
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  codeGen/should_compile/T7237
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by jwlato):

 Thanks for fixing it so quickly!

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7237#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] #367: Infinite loops can hang Concurrent Haskell

2012-09-18 Thread GHC
#367: Infinite loops can hang Concurrent Haskell
--+-
  Reporter:  simonpj  |  Owner:  ezyang 
 
  Type:  bug  | Status:  new
 
  Priority:  lowest   |  Milestone:  _|_
 
 Component:  Compiler |Version:  6.4.1  
 
Resolution:  None |   Keywords:  scheduler 
allocation
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
 
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
 
  Testcase:   |  Blockedby: 
 
  Blocking:   |Related: 
 
--+-

Comment(by ezyang):

 Replying to [comment:19 simonmar]:
  You could improve code size by omitting the `HpAlloc = 0` assignment
 (perhaps making sure that it is initialized to zero in `LOAD_THREAD_STATE`
 or something).

 Fascinatingly enough, this doesn't help all that much, since instruction
 alignments adds in nops to fill in the space savings.

  Another alternative is to use `SpLim` instead of `HpLim` to trigger the
 interrupt, on the grounds that there are more stack checks than heap
 checks. We would have to put `SpLim` in a memory location instead of a
 register, but we could move `HpLim` into a register.

 To be clear, this is changing globally how preemption would work, since
 prior to this patch we were zeroing HpLim to trigger a yield. But it
 should otherwise work. I'll chase up some stats here too. (If SpLim is
 checked more often, won't we pay a performance cost for having it in a
 memory location?)

  Something else we could do is add a flag on every top-level function to
 say whether it is non-allocating (rather like the `NoCafRefs` flag), and
 we could use that to optimise away many of the extra checks.

 I don't quite understand what this means: isn't alloc = 0 in the heap
 check just this information?

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