Re: [GHC] #367: Infinite loops can hang Concurrent Haskell

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

 Replying to [comment:20 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.

 But we don't actually align the heap-check failure branch, so I'm
 confused.  Can you post the asm code you're seeing?

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

 Maybe, but it's worth measuring I think.

   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?

 I had in mind making it a transitive property - a function would get the
 alloc flag if it is guaranteed to allocate within a bounded time, so then
 any callers don't need a yield check.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/367#comment:22
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] #7255: Wrong suggestion when deriving Generic on an instantiated type

2012-09-20 Thread GHC
#7255: Wrong suggestion when deriving Generic on an instantiated type
--+-
 Reporter:  dreixel   |  Owner:  dreixel 
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Compiler
  Version:  7.6.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 The following code

 {{{
 {-# LANGUAGE DeriveGeneric  #-}
 {-# LANGUAGE StandaloneDeriving #-}
 {-# LANGUAGE FlexibleInstances  #-}

 import GHC.Generics

 data A a

 data B

 deriving instance Generic (A B)
 }}}

 gives rise to the error

 {{{
 Can't make a derived instance of `Generic (A B)':
   A must not be instantiated; try deriving `A B' instead
 In the stand-alone deriving instance for `Generic (A B)'
 }}}

 It should indeed fail, but the suggestion should be to try deriving `A a`
 instead.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7255
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] #7256: Missing dataCast1 and dataCast2 methods in Data.Data instances

2012-09-20 Thread GHC
#7256: Missing dataCast1 and dataCast2 methods in Data.Data instances
--+-
 Reporter:  dreixel   |  Owner:  dreixel 
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Compiler
  Version:  7.6.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 Having a look at `Data` instances in module `Data.Data`, `Ptr a` and
 `ForeignPtr a` are missing a `dataCast1 = gcast1` line. And `Array a b`
 seems to be missing the `dataCast2` method.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7256
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] #7257: Regression: pinned memory fragmentation

2012-09-20 Thread GHC
#7257: Regression: pinned memory fragmentation
-+--
 Reporter:  jwlato   |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:  7.6.1|   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Runtime performance bug  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
 In certain cases, ghc-7.6.1 seems to have much worse memory behavior than
 7.4.  I have attached a simplified program that I believe demonstrates the
 problem.

 {{{
 -- compiled with ghc-7.4.2 -rtsopts -O2
 ./Foo  +RTS -s
 21
3,549,666,928 bytes allocated in the heap
   55,512,376 bytes copied during GC
  335,555,096 bytes maximum residency (10 sample(s))
3,787,576 bytes maximum slop
  453 MB total memory in use (0 MB lost due to fragmentation)
 }}}

 {{{
 -- compiled with ghc-7.6.1 -rtsopts -O2
2,699,298,272 bytes allocated in the heap
   55,077,544 bytes copied during GC
  327,246,968 bytes maximum residency (11 sample(s))
3,767,408 bytes maximum slop
  858 MB total memory in use (398 MB lost due to fragmentation)
 }}}

 One of our applications uses 3-4GB more RAM when compiled with ghc-7.6.1
 compared to 7.4, all due to memory fragmentation issues.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7257
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-20 Thread GHC
#7240: Stack trace truncated too much with indirect recursion
-+--
Reporter:  nomeata   |   Owner:  nomeata 
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Profiling | Version:  7.4.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonmar):

  * difficulty:  = Unknown


Comment:

 I like your original idea (only truncating on a real loop), but I don't
 understand the explanation of why it didn't work.  Is it a bug in
 `enterCCSFun`, or just a consequence of the way it works?

 The way I like to think about this problem is in terms of equalities.  I
 want two equalities to hold:

 {{{
   push L (\x.e)  ==  \x. push L e

   let f = \x.e in E[f]   == E[\x.e]
 }}}

 I'm using `==` to mean that the stacks are the same, in some sense.
 Perhaps a more precise way is to say that the stack when evaluating `e` is
 the same in both cases.

 The first one tells us that it is ok to move a `push` inside a lambda,
 which in turn tells us that `push` scopes over the body of a lambda, which
 is the behaviour we want.

 The second one corresponds to inlining, which is a transformation that GHC
 performs all the time.  We need it to be the case that inlining a function
 does not change the stack.

 The second equality gives rise to this:

 {{{
   call (push f S) S == push f S
 }}}

 which is not satisfied by the current definition of `call` and `push`,
 because `push f S` might truncate the stack (the same applies to your
 definition too, I believe).  One definition that does work is to ignore
 the second and subsequent occurrences of labels in the stack, but that
 gives bad results for other reasons.

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


[GHC] #7258: Compiling DynFlags is jolly slow

2012-09-20 Thread GHC
#7258: Compiling DynFlags is jolly slow
-+--
Reporter:  simonpj   |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
 Compiling `DynFlags` really takes a long time these days.

 Ian thinks that it's due to the `Read` and `Show` instances he has added
 (see attached `W2.hs`.

 Simon M suggests: instead of using `Read/Show`, you could generate some
 code in `mkDerivedConstants` to use `ReadP` and `Outputable`, which should
 be much smaller and faster.

 This ticket is
  * To see if we can speed up compilation of `DynFlags`
  * To check WHY it is so slow.  Are there any lessons we can learn or ways
 to make it compile faster?  Is it tickling some asymptotically-bad corner
 of the compiler?

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7258
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] #7258: Compiling DynFlags is jolly slow

2012-09-20 Thread GHC
#7258: Compiling DynFlags is jolly slow
-+--
Reporter:  simonpj   |   Owner:  igloo   
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonpj):

  * owner:  = igloo


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7258#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] #7256: Missing dataCast1 and dataCast2 methods in Data.Data instances

2012-09-20 Thread GHC
#7256: Missing dataCast1 and dataCast2 methods in Data.Data instances
-+--
Reporter:  dreixel   |   Owner:  dreixel 
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonpj):

  * difficulty:  = Unknown


Comment:

 Any chance of a patch?  Sounds as if you know just what to do.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7256#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] #7256: Missing dataCast1 and dataCast2 methods in Data.Data instances

2012-09-20 Thread GHC
#7256: Missing dataCast1 and dataCast2 methods in Data.Data instances
-+--
Reporter:  dreixel   |   Owner:  dreixel 
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by dreixel):

 Yes, I'll take care of this, it's trivial.

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

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

Comment(by nomeata):

 Replying to [comment:5 simonmar]:
  I like your original idea (only truncating on a real loop), but I don't
 understand the explanation of why it didn't work.  Is it a bug in
 `enterCCSFun`, or just a consequence of the way it works?

 The latter, in my opinion.

  The first one tells us that it is ok to move a `push` inside a lambda,
 which in turn tells us that `push` scopes over the body of a lambda, which
 is the behaviour we want.

 I’m not sure what this means in terms of the implementation of `call` and
 `push` – or is this fulfilled by any “call-push-algebra“ (and therefore
 the current and my proposed one)?

  The second one corresponds to inlining, which is a transformation that
 GHC performs all the time.  We need it to be the case that inlining a
 function does not change the stack.
 
  The second equality gives rise to this:
 
  {{{
call (push f S) S == push f S
  }}}
 
  which is not satisfied by the current definition of `call` and `push`,
 because `push f S` might truncate the stack (the same applies to your
 definition too, I believe).  One definition that does work is to ignore
 the second and subsequent occurrences of labels in the stack, but that
 gives bad results for other reasons.

 Yes, this does not hold by my definition:
 {{{
  call (push y CAF,main,x,y,x) CAF,main,x,y,x
   == call CAF,main,x,y CAF,main,x,y,x
   == CAF,main,x,y,x
   /= CAF,main,x,y
   == (push y CAF,main,x,y,x)
 }}}

 So by the requirements you state, my definition fares just as well as
 yours.

 I thought about being explicit about recursions, i.e. shortning
 CAF,main,x,y,x,y,x,y as CAF,main,(x,y)3 (and maybe representing it by
 a special “repeat the n CC’s below” value in the CC stack). This would not
 lose any information, call could be implemented to fulfill your equation
 and the (individual) stacks would still be bounded in size. But due to the
 memorization in the current code it seems that all such stacks would stay
 around and probably consume too much memory in the presence of recursion;
 if that were acceptable then you wouldn’t have introduced any truncating
 in the first place, would you?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7240#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] #7200: template-haskell-2.7.0.0 fails to build with GHC 7.0.4 due to missing pragma

2012-09-20 Thread GHC
#7200: template-haskell-2.7.0.0 fails to build with GHC 7.0.4 due to missing
pragma
-+--
Reporter:  tibbe |   Owner:  duncan  
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 igloo):

 One possibility would be to get the info by having GHC print out
 `wired_in_pkgids`, although this list includes the dph packages that don't
 come with GHC.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7200#comment:7
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] #7255: Wrong suggestion when deriving Generic on an instantiated type

2012-09-20 Thread GHC
#7255: Wrong suggestion when deriving Generic on an instantiated type
--+-
 Reporter:  dreixel   |  Owner:  dreixel 
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Compiler
  Version:  7.6.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
Changes (by nfrisby):

 * cc: nfrisby (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7255#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] #2289: Needless reboxing of values when returning from a tight loop

2012-09-20 Thread GHC
#2289: Needless reboxing of values when returning from a tight loop
---+
Reporter:  dons|   Owner:   
  
Type:  bug |  Status:  new  
  
Priority:  lowest  |   Milestone:  7.6.2
  
   Component:  Compiler| Version:  6.8.2
  
Keywords:  boxing, loops, performance  |  Os:  Unknown/Multiple 
  
Architecture:  Unknown/Multiple| Failure:  Runtime performance 
bug
  Difficulty:  Unknown |Testcase:   
  
   Blockedby:  |Blocking:   
  
 Related:  |  
---+
Changes (by jwlato):

 * cc: jwlato@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2289#comment:29
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] #7257: Regression: pinned memory fragmentation

2012-09-20 Thread GHC
#7257: Regression: pinned memory fragmentation
-+--
 Reporter:  jwlato   |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:  7.6.1|   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Runtime performance bug  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
Changes (by akio):

 * cc: tkn.akio@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7257#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] #7257: Regression: pinned memory fragmentation

2012-09-20 Thread GHC
#7257: Regression: pinned memory fragmentation
-+--
 Reporter:  jwlato   |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:  7.6.1|   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Runtime performance bug  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--

Comment(by jwlato):

 Addendum: with ghc-7.6.1, I see the same memory behavior with multiple
 versions of ByteString and Data.Vector.Storable, but not Text,
 Data.Vector, or Data.Vector.Unboxed.

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

2012-09-20 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:22 simonmar]:
  Replying to [comment:20 ezyang]:
   Fascinatingly enough, this doesn't help all that much, since
 instruction alignments adds in nops to fill in the space savings.
 
  But we don't actually align the heap-check failure branch, so I'm
 confused.  Can you post the asm code you're seeing?

 I misspoke; actually, we're page-aligning the data section, and the
 savings aren't enough to get us to the previous page. It's technically a
 benefit, but only if the increase in size means you can't fit the entire
 code block in the instruction cache...

 {{{
 - 12 .text 001e239c  0804a770  0804a770  2770  2**4
 + 12 .text 001e23bc  0804a770  0804a770  2770  2**4
CONTENTS, ALLOC, LOAD, READONLY, CODE
 }}}

  I had in mind making it a transitive property - a function would get the
 alloc flag if it is guaranteed to allocate within a bounded time, so then
 any callers don't need a yield check.

 Hm, I guess this is good for the little blocks we generate which only have
 one exit point, and not so good if there are multiple exit points (since
 all of them would need the Alloc flag set to work.)

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