[GHC] #2607: Inlining defeats selector thunk optimisation

2008-09-18 Thread GHC
#2607: Inlining defeats selector thunk optimisation
-+--
Reporter:  simonmar  |   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Milestone:  _|_
   Component:  Compiler  | Version:  6.8.3  
Severity:  normal|Keywords: 
  Difficulty:  Unknown   |Testcase: 
Architecture:  Unknown   |  Os:  Unknown
-+--
 From a [http://www.haskell.org/pipermail/haskell-
 cafe/2008-September/047665.html post on haskell-cafe].

 Lev Walkin wrote:

  I wondered why would a contemporary GHC 6.8.3 exhibit such a leak?
  After all, the technique was known in 2000 (and afir by Wadler in '87)
  and one would assume Joe English's reference to most other Haskell
  systems ought to mean GHC.

 Thanks for this nice example - Don Stewart pointed me to it, and  Simon PJ
 and I just spent some time this morning diagnosing it.

 Incedentally, with GHC 6.8 you can just run the program with +RTS -hT to
 get a basic space profile, there's no need to compile it for profiling -
 this is tremendously useful for quick profiling jobs.  And in this case we
 see the the heap is filling up with (:) and Tree constructors, no thunks.

 Here's the short story:  GHC does have the space leak optimisation you
 refer to, and it is working correctly, but it doesn't cover all the cases
 you might want it to cover.  In particular, optimisations sometimes
 interact badly with the space leak avoidance, and that's what is happening
 here.  We've known about the problem for some time, but this is the first
 time I've seen a nice small example that demonstrates it.

 {{{
  -- Lazily build a tree out of a sequence of tree-building events
  build :: [TreeEvent] - ([UnconsumedEvent], [Tree String])
  build (Start str : es) =
  let (es', subnodes) = build es
  (spill, siblings) = build es'
  in (spill, (Tree str subnodes : siblings))
  build (Leaf str : es) =
  let (spill, siblings) = build es
  in (spill, Tree str [] : siblings)
  build (Stop : es) = (es, [])
  build [] = ([], [])
 }}}

 So here's the long story.  Look at the first equation for build:
 {{{
  build (Start str : es) =
  let (es', subnodes) = build es
  (spill, siblings) = build es'
  in (spill, (Tree str subnodes : siblings))
 }}}
 this turns into
 {{{
   x = build es
   es' = fst x
   subnodes = snd x

   y = build es'
   spill = fst y
   siblings = snd y
 }}}
 now, it's the siblings binding we're interested in, because this one is
 never demanded - in this example, subnodes ends up being an infinite
 list of trees, and we never get to evaluate siblings.  So anything
 referred to by siblings will remain in the heap.

 The space-leak avoidance optimisation works on all those fst and snd
 bindings: in a binding like siblings = snd y, when y is evaluated to a
 pair, the GC will automatically reduce snd y, so releasing the first
 component of the pair.  This all works fine.

 But the optimiser sees the above code and spots that es' only occurs once,
 in the right hand side of the binding for y, and so it inlines it.  Now we
 have

 {{{
   x = build es
   subnodes = snd x

   y = build (fst x)
   spill = fst y
   siblings = snd y
 }}}

 Now, usually this is a good idea, but in this case we lost the special
 space-leak avoidance on the fst x expression, because it is now embedded
 in an expression.  In fact in this case the thunk goes away entirely,
 because build is strict.

 But now, when the program runs, the thunk for siblings retains y, which
 retains x, which evaluates to a pair, the second component of which
 evaluates to an infintely growing list of Trees (the first components is a
 chain of fst y expressions that constantly get reduced by the GC and
 don't take up any space).

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2607
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] #2608: Direct support for unit tests in Cabal

2008-09-18 Thread GHC
#2608: Direct support for unit tests in Cabal
-+--
Reporter:  kaol  |   Owner:   
Type:  proposal  |  Status:  new  
Priority:  normal|   Component:  libraries (other)
 Version:  6.6.1 |Severity:  minor
Keywords:|Testcase:   
Architecture:  Unknown   |  Os:  Unknown  
-+--
 I'm passing along Debian wishlist bug [http://bugs.debian.org/458495
 #458495] for your consideration. The patch is for version 6.6.1 and it
 won't apply cleanly on HEAD, but I can adapt it to HEAD if you think it's
 worth having.

 I didn't look overly much if something like this has been already
 implemented. My apologies if this is just more noise.

 
 It would be nice if there was a simple way to build and run tests for
 Cabalized packages.

 Cabal provides a test target, but by default it does nothing.
 Furthermore, you can't really build test cases using the Cabal
 infrastructure, since any executables that you list get installed.
 Searching on Google for how to integrate a test suite into Cabal turns
 up suggestions such as make a system() call from runTests to

 The attached patch adds two new flags to the build information for
 executables and libraries:

 {{{
   * do-not-install: if set to True, keeps an executable that it's set on
 from being installed.  This is necessary to keep test suites from
 ending up in $prefix/bin, but may be useful for other build-time
 utilities.

   * is-test: if set to True on an executable, the executable will be
 invoked by the test target of the setup script.  Note that this
 doesn't attempt to be at all smart about building the executable(s);
 it just blindly invokes the test command(s) and returns a failure if
 any of them fail.
 }}}

 The patch should be fairly straightforward.  The need to do suppression
 of installing executables in compiler-specific code is a bit ugly;
 this could maybe be cleaned up with an equivalent to withExe that drops
 non-installed executables and by writing and using a similar routine for
 libraries.

 This also changes the API of Cabal: runTests now takes an integer as
 its first argument, indicating the verbosity level provided as an
 argument on the command-line.  The Boolean that was passed before
 didn't have any purpose I could see and was always False, so it
 shouldn't be hard to adapt existing code to this change.  On the other
 hand, the API can be preserved by just hard-coding a verbosity level.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2608
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] #1502: GHC should integrate better with mingw

2008-09-18 Thread GHC
#1502: GHC should integrate better with mingw
-+--
 Reporter:  eivuokko |  Owner: 
 Type:  feature request  | Status:  new
 Priority:  normal   |  Milestone:  6.12 branch
Component:  Compiler |Version:  6.6.1  
 Severity:  normal   | Resolution: 
 Keywords:  windows  | Difficulty:  Unknown
 Testcase:   |   Architecture:  Unknown
   Os:  Windows  |  
-+--
Comment (by claus):

 Instead of including the mingw installer, how about preserving the
 internal directory layout of the bits of mingw that get included?

 That would avoid the need for extra `-B` flags in ghc, cabal, hsc2hs, ..,
 it would make gcc much less prone to picking up the wrong
 executables/libraries/include files from other places, allowing it to work
 as intended (its build-in paths start searching relative to the gcc
 executable, allowing relocation). See this cvs-ghc thread for more
 details:

 ghc head on windows: gcc.exe: installation problem, cannot exec `cc1': No
 such file or directory

 http://www.haskell.org/pipermail/cvs-ghc/2008-September/045161.html

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1502#comment:5
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2555: Template Haskell does not respect -package and -hide constraints

2008-09-18 Thread GHC
#2555: Template Haskell does not respect -package and -hide constraints
--+-
 Reporter:  guest |  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone:  6.12 branch
Component:  Compiler  |Version:  6.8.2  
 Severity:  normal| Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Unknown
   Os:  Linux |  
--+-
Changes (by simonpj):

  * milestone:  6.10 branch = 6.12 branch

Comment:

 OK.  If you come across it again, please let us know and we'll take the
 opportunity to get more specific info.  Meanwhile, we're stuck.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2555#comment:5
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #738: ghc can't load files with selinux Enforcing

2008-09-18 Thread GHC
#738: ghc can't load files with selinux Enforcing
+---
 Reporter:  [EMAIL PROTECTED]  |  Owner:  
 Type:  feature request | Status:  reopened
 Priority:  normal  |  Milestone:  6.10.1  
Component:  Runtime System  |Version:  6.6.1   
 Severity:  normal  | Resolution:  
 Keywords:  selinux | Difficulty:  Moderate (1 day)
 Testcase:  |   Architecture:  x86 
   Os:  Linux   |  
+---
Changes (by simonmar):

  * priority:  high = normal

Comment:

 Couple of notes:

  * Fedora is shipping with `allow_execmem` turned on these days, so the
 issue only affects people that turn it off manually.

  * In order to reproduce the problem, you need to turn off both
 `allow_execmem` and `allow_execstack` using `setsebool`.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/738#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] #2609: Compiling with -O2 is 7x slower than -O

2008-09-18 Thread GHC
#2609: Compiling with -O2 is 7x slower than -O
-+--
Reporter:  simonpj   |   Owner: 
Type:  compile-time performance bug  |  Status:  new
Priority:  normal|   Milestone: 
   Component:  Compiler  | Version:  6.8.3  
Severity:  normal|Keywords: 
  Difficulty:  Unknown   |Testcase: 
Architecture:  Unknown   |  Os:  Unknown
-+--
 Serge writes that compiling !DoCon with `-O2 -fvia-C` does not gain more
 performance, but leads to 7 times longer compilation.  That seems a big
 slow down, worth looking into.

 The offending !DoCon bundle is attached

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2609
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] #2604: Suggest -XDeriveDataTypeable with newtype too

2008-09-18 Thread GHC
#2604: Suggest -XDeriveDataTypeable with newtype too
+---
 Reporter:  kaol|  Owner: 
 Type:  feature request | Status:  closed 
 Priority:  normal  |  Milestone: 
Component:  Compiler|Version:  6.8.2  
 Severity:  trivial | Resolution:  fixed  
 Keywords:  | Difficulty:  Unknown
 Testcase:  deriving/should_fail/T2604  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Changes (by simonpj):

  * testcase:  = deriving/should_fail/T2604
  * difficulty:  = Unknown
  * status:  new = closed
  * resolution:  = fixed

Comment:

 At last!  A bug I can fix quickly!  Thanks for the suggestion.
 {{{
 Wed Sep 17 14:51:04 BST 2008  [EMAIL PROTECTED]
   * Improve error reporting for 'deriving' (Trac #2604)
 }}}
 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2604#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] #955: more object-code blow-up in ghc-6.8.3 vs. ghc-6.4.2 (both with optimization)

2008-09-18 Thread GHC
#955: more object-code blow-up in ghc-6.8.3 vs. ghc-6.4.2 (both with
optimization)
--+-
 Reporter:  [EMAIL PROTECTED] |  Owner:  
 Type:  run-time performance bug  | Status:  closed  
 Priority:  high  |  Milestone:  6.10.1  
Component:  Compiler  |Version:  6.8.3   
 Severity:  normal| Resolution:  fixed   
 Keywords:  object-code blow-up   | Difficulty:  Unknown 
 Testcase:|   Architecture:  Multiple
   Os:  Multiple  |  
--+-
Comment (by simonpj):

 Just to say that I've now fixed those odd WARNINGs too.
 {{{
 Wed Sep 17 17:29:10 BST 2008  [EMAIL PROTECTED]
   * Fix nasty infelicity: do not short-cut empty substitution in the
 simplifier

   I was perplexed about why an arity-related WARN was tripping. It took
   me _day_ (sigh) to find that it was because SimplEnv.substExpr was
 taking
   a short cut when the substitution was empty, thereby not subsituting for
   Ids in scope, which must be done (CoreSubst Note [Extending the Subst]).

   The fix is a matter of deleting the optimisation.  Same with
   CoreSubst.substSpec, although I don't know if that actually caused a
   problem.
 }}}
 Great to have this ticket closed at last.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/955#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] #2610: File permission-related proposals

2008-09-18 Thread GHC
#2610: File permission-related proposals
---+
Reporter:  igloo   |   Owner: 
Type:  task|  Status:  new
Priority:  normal  |   Milestone:  6.12 branch
   Component:  libraries/base  | Version:  6.8.3  
Severity:  normal  |Keywords: 
  Difficulty:  Unknown |Testcase: 
Architecture:  Unknown |  Os:  Unknown
---+
 Once 6.10 is out of the way, we should file some permission-related
 proposals.

 `openTempFile` and `openBinaryTempFile` mask the file permissions of the
 file they create with 0o600. However, we would like to use it for
 implementing things like `writeFileAtomic`, in which case we want the
 default file permissions to be used.

 `System.Directory` has an internal `copyPermissions` function, but it
 should be exported.
 This is not the same as `getPermissions s = setPermissions d` as the
 Permissions type that the latter uses doesn't hold all the permissions
 info that we want.

 Even better would be to make the Permissions type abstract, so that it
 /can/ contain all the info we want. Functions in the unix and Win32
 packages would be able to do more with this type than the portable
 interface.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2610
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] #2611: print022 fails

2008-09-18 Thread GHC
#2611: print022 fails
+---
Reporter:  igloo|   Owner: 
Type:  bug  |  Status:  new
Priority:  normal   |   Milestone:  6.10 branch
   Component:  GHCi | Version:  6.9
Severity:  normal   |Keywords: 
  Difficulty:  Unknown  |Testcase:  print022   
Architecture:  Unknown  |  Os:  Unknown
+---
 print022 fails:
 {{{
 -test = C 1 32 1.2 1.23 'x' 1 1.2 1.23
 +test = C 1 32 1.2 1.23 'x' (I# 1) (F# 1.2) (D# 1.23)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2611
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] #1364: Finalizers not guaranteed to run before the program exits

2008-09-18 Thread GHC
#1364: Finalizers not guaranteed to run before the program exits
--+-
 Reporter:  [EMAIL PROTECTED]  |  Owner:  simonmar
 Type:  feature request   | Status:  new 
 Priority:  normal|  Milestone:  6.10.1  
Component:  Runtime System|Version:  6.6.1   
 Severity:  normal| Resolution:  
 Keywords:| Difficulty:  Moderate (1 day)
 Testcase:|   Architecture:  Unknown 
   Os:  Unknown   |  
--+-
Comment (by Svarog):

 Replying to [comment:12 simonmar]:

 I've just uploaded updated patches for the base lib, the testsuite and ghc
 to address these issues.

 The new ghc patch just adds a comment in Weak.c to mention that finalizers
 rely on weak pointers
 in weak_ptr_list always being in the same order (which is currently the
 case).

   * we shouldn't be extending the `Foreign.ForeignPtr` API, as it is set
 in stone
 by the FFI spec and would need at the very least a library proposal
 to
 change it.  I had imagined that we would keep the same API, and just
 implement C
 finalizers differently.
 

 As discussed on IRC, addForeignPtrFinalizer only needs to work with C
 functions so I renamed addForeignPtrFinalizerC to addForeignPtrFinalizer.
 That way the API stays the same.
 To use Haskell finalizers addForeignPtrConcFinalizer should be used.

   * The implementation doesn't seem to respect the ordering of
 finalizers.
 Finalizers are supposed to run in the same order that they were added
 to the
 `ForeignPtr` (which is why we have that horrible `IORef` attached to
 `ForeignPtr`s).  It looks like C finalizers will run in an arbitrary
 order.
 

 Weak pointers are always kept in the same order and each C finalizer is
 attached to its own weak pointer. All C finalizers attached to a
 particular `ForeignPtr` should execute in correct order. I've updated one
 of the tests in the testsuite to check for this.

 As discussed on IRC I added code that throws a run-time error if Haskell
 and C finalizers are mixed on the same `ForeignPtr`. I've added another
 test to the testsuite to check this as well.

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