Re: [GHC] #2087: On a PPC Mac OS X 10.4, the RTS reports "Memory leak detected" running a program compiled with -debug -threaded -fhpc

2008-02-13 Thread GHC
#2087: On a PPC Mac OS X 10.4, the RTS reports "Memory leak detected" running a
program compiled with -debug -threaded -fhpc
+---
 Reporter:  thorkilnaur |  Owner: 
 Type:  bug | Status:  new
 Priority:  normal  |  Milestone:  6.8.3  
Component:  Runtime System  |Version:  6.9
 Severity:  normal  | Resolution: 
 Keywords:  | Difficulty:  Unknown
 Testcase:  |   Architecture:  powerpc
   Os:  MacOS X |  
+---
Comment (by thorkilnaur):

 Additional investigation strongly indicates that the uncounted blocks are
 the ones allocated by {{{hs_add_root}}} in {{{RtsStartup.c}}}:
 {{{
 void
 hs_add_root(void (*init_root)(void))
 {
 bdescr *bd;
 nat init_sp;
 Capability *cap = &MainCapability;

 if (hs_init_count <= 0) {
 barf("hs_add_root() must be called after hs_init()");
 }

 /* The initialisation stack grows downward, with sp pointing
to the last occupied word */
 init_sp = INIT_STACK_BLOCKS*BLOCK_SIZE_W;
 bd = allocGroup_lock(INIT_STACK_BLOCKS);
 init_stack = (F_ *)bd->start;
 init_stack[--init_sp] = (F_)stg_init_finish;
 if (init_root != NULL) {
 init_stack[--init_sp] = (F_)init_root;
 }

 cap->r.rSp = (P_)(init_stack + init_sp);
 StgRun((StgFunPtr)stg_init, &cap->r);

 freeGroup_lock(bd);

 startupHpc();

 // This must be done after module initialisation.
 // ToDo: make this work in the presence of multiple hs_add_root()s.
 initProfiling2();
 }
 }}}
 The memory leak is reported when a garbage collection happens to be
 initiated before the blocks are freed again. This can be confirmed by
 inserting a call to memInventory between the allocation and the free: Such
 a call reports the memory leak every time.

 So it is not actually a real memory leak, merely a weakness in the memory
 leak detector.

 I will gladly concoct a repair of this problem, but the possibilities are
 many, so I will just hesitate for a little while and see if not somebody
 else might come up with just the right solution.

 Thanks and best regards Thorkil

-- 
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] #2093: getSymbolicLinkStatus (and possibly other functions) broken on systems with large file system support

2008-02-13 Thread GHC
#2093: getSymbolicLinkStatus (and possibly other functions) broken on systems 
with
large file system support
---+
Reporter:  JeremyShaw  |   Owner:
Type:  bug |  Status:  new   
Priority:  normal  |   Component:  libraries/unix
 Version:  6.8.2   |Severity:  major 
Keywords:  |Testcase:
Architecture:  x86 |  Os:  Linux 
---+
 This thread contains more details:

 http://www.haskell.org/pipermail/haskell-cafe/2008-February/039549.html

 Basically, it appears that the unix module is built without the large
 filesystem support enabled, so it calls the 32-bit version of lstat. But
 hsc2hs includes header files that enable large file system support, so the
 offsets are for the stat64 struct. This means many fields in FileStatus
 are filled with garbage.

 I have attached a patch which adds the AC_SYS_LARGEFILE macro to
 configure.ac. This is the same macro which enables large file support in
 ghc. There could still be a problem however. For example, if you built ghc
 on a system without large file support, and but the unix module on a
 system with large file support -- then they would be out of sync. This
 patch seems better than the current situation however.

-- 
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] #2092: Quadratic amount of code generated

2008-02-13 Thread GHC
#2092: Quadratic amount of code generated
-+--
Reporter:  igloo |   Owner: 
Type:  run-time performance bug  |  Status:  new
Priority:  normal|   Milestone:  6.10 branch
   Component:  Compiler  | Version:  6.9
Severity:  normal|Keywords: 
  Difficulty:  Unknown   |Testcase: 
Architecture:  Unknown   |  Os:  Unknown
-+--
 Originally discovered by Twan van Laarhoven, here:
 http://www.haskell.org/pipermail/cvs-ghc/2008-February/040981.html

 On the HEAD, compiling this module:
 {{{
 {-# LANGUAGE MagicHash #-}

 module M1 where

 import GHC.Exts

 type FastInt = Int#

 data U = Mk1 { a :: (), b :: FastInt, c :: () }
| Mk2 { a :: (), b :: FastInt, c :: () }

 instance Eq U where
 x == y = b x ==# b y
 }}}
 with
 {{{
 ghc -c M1.hs -O -ddump-simpl
 }}}
 we see
 {{{
 M1.== :: M1.U -> M1.U -> GHC.Base.Bool
 [GlobalId]
 [Arity 2
  NoCafRefs
  Str: DmdType SS]
 M1.== =
   \ (x_a5J :: M1.U) (y_a5L :: M1.U) ->
 case case y_a5L of tpl_B2 {
M1.Mk1 ipv_B3 ipv1_B4 ipv2_B5 -> ipv1_B4;
M1.Mk2 ipv_B3 ipv1_B4 ipv2_B5 -> ipv1_B4
  }
 of wild_B1 { __DEFAULT ->
 case case x_a5J of tpl_B2 {
M1.Mk1 ipv_B3 ipv1_B4 ipv2_B5 -> ipv1_B4;
M1.Mk2 ipv_B3 ipv1_B4 ipv2_B5 -> ipv1_B4
  }
 of wild1_Xk { __DEFAULT ->
 GHC.Prim.==# wild1_Xk wild_B1
 }
 }
 }}}
 which looks good: Extract the !FastInt from one value, then the other,
 then compare.

 However, if we have this module instead:
 {{{
 module M2 where

 import GHC.Exts

 newtype FastInt = FastInt Int
 deriving Eq

 data U = Mk1 { a :: (), b :: {-# UNPACK #-} !FastInt, c :: () }
| Mk2 { a :: (), b :: {-# UNPACK #-} !FastInt, c :: () }

 instance Eq U where
 x == y = b x == b y
 }}}
 again compiling with
 {{{
 ghc -c M2.hs -O -ddump-simpl
 }}}
 we see
 {{{
 M2.== :: M2.U -> M2.U -> GHC.Base.Bool
 [GlobalId]
 [Arity 2
  NoCafRefs
  Str: DmdType SS]
 M2.== =
   \ (x_a5M :: M2.U) (y_a5O :: M2.U) ->
 case x_a5M of tpl_Xj {
   M2.Mk1 ipv_Xn rb_B6 ipv1_B5 ->
 case y_a5O of tpl1_Xl {
   M2.Mk1 ipv2_Xp rb1_Xw ipv3_XX -> GHC.Prim.==# rb_B6 rb1_Xw;
   M2.Mk2 ipv2_Xp rb1_Xw ipv3_XX -> GHC.Prim.==# rb_B6 rb1_Xw
 };
   M2.Mk2 ipv_Xn rb_B6 ipv1_B5 ->
 case y_a5O of tpl1_Xl {
   M2.Mk1 ipv2_Xp rb1_Xw ipv3_XX -> GHC.Prim.==# rb_B6 rb1_Xw;
   M2.Mk2 ipv2_Xp rb1_Xw ipv3_XX -> GHC.Prim.==# rb_B6 rb1_Xw
 }
 }
 }}}
 where the extraction of the second !FastInt happens inside the branches of
 the extraction of the first !FastInt, giving a quadratic (in the number of
 constructors) amount of code. We would expect to get code like that in the
 first example.

-- 
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] #1558: make the testsuite work with THREADS=2

2008-02-13 Thread GHC
#1558: make the testsuite work with THREADS=2
+---
 Reporter:  simonmar|  Owner: 
 Type:  bug | Status:  new
 Priority:  normal  |  Milestone:  6.10 branch
Component:  Test Suite  |Version:  6.6.1  
 Severity:  normal  | Resolution: 
 Keywords:  | Difficulty:  Easy (1 hr)
 Testcase:  |   Architecture:  Unknown
   Os:  Unknown |  
+---
Comment (by batterseapower):

 [http://bugs.python.org/issue1731717 Python ticket for the issue reported
 by Simon above]

-- 
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] #2091: heap corruption in ghc-6.8.2?

2008-02-13 Thread GHC
#2091: heap corruption in ghc-6.8.2?
--+-
 Reporter:  jeffz |  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone: 
Component:  Compiler  |Version:  6.8.2  
 Severity:  normal| Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  x86
   Os:  Windows   |  
--+-
Comment (by jeffz):

 Replying to [comment:1 simonmar]:
 > Could you explain which part(s) of the logs lead you to believe the bug
 is in GHC?  The logs are huge, and I couldn't find any clues pointing at
 GHC with a quick scan, but maybe I missed something.

 Line 2962 of ghc-valgrind4.txt looks suspicious, but the purify log is
 more precise, specifying this exactly:

 [E] FIM: Freeing invalid memory in LocalFree {36 occurrences}
 Address 0x00265650 points into a HeapAlloc'd block in unallocated
 region of the default heap
 Location of free attempt
 LocalFree  [C:\WINDOWS\system32\KERNEL32.dll]
 IsValidLocale  [C:\WINDOWS\system32\kernel32.dll]

-- 
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] #2086: Fix test openFile008(ghci) by changing testlib.py to apply cmd_prefix also for way ghci

2008-02-13 Thread GHC
#2086: Fix test openFile008(ghci) by changing testlib.py to apply cmd_prefix 
also
for way ghci
-+--
 Reporter:  thorkilnaur  |  Owner: 
 Type:  bug  | Status:  closed 
 Priority:  normal   |  Milestone: 
Component:  Test Suite   |Version:  6.9
 Severity:  normal   | Resolution:  fixed  
 Keywords:   | Difficulty:  Unknown
 Testcase:  openFile008  |   Architecture:  Unknown
   Os:  MacOS X  |  
-+--
Changes (by igloo):

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

Comment:

 Patch applied; thanks Thorkil!

-- 
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] #2091: heap corruption in ghc-6.8.2?

2008-02-13 Thread GHC
#2091: heap corruption in ghc-6.8.2?
--+-
 Reporter:  jeffz |  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone: 
Component:  Compiler  |Version:  6.8.2  
 Severity:  normal| Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  x86
   Os:  Windows   |  
--+-
Changes (by simonmar):

  * difficulty:  => Unknown

Comment:

 Could you explain which part(s) of the logs lead you to believe the bug is
 in GHC?  The logs are huge, and I couldn't find any clues pointing at GHC
 with a quick scan, but maybe I missed something.

-- 
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] #2090: Better stack management please

2008-02-13 Thread GHC
#2090: Better stack management please
-+--
 Reporter:  guest|  Owner: 
 Type:  feature request  | Status:  new
 Priority:  normal   |  Milestone: 
Component:  Runtime System   |Version:  6.8.2  
 Severity:  normal   | Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:   |   Architecture:  Unknown
   Os:  Unknown  |  
-+--
Changes (by simonmar):

  * difficulty:  => Unknown

Comment:

 Essentially there are three suggestions here, I'll deal with them one at a
 time:

 === use a different default for the max stack size (+RTS -K) ===

 I'm happy to go along with whatever is the popular opinion here.
 Personally I never encounter a program that exceeds the current stack
 limit and is not in an infinite loop, but I'm prepared to believe that
 others do.  Please let us know.

 === reduce the memory allocated to a stack when it shrinks ===

 This is not hard to implement - probably a couple of hours work, and
 confined to just one place.  It could be done possibly without even
 copying the stack: just split the TSO into two, copy the TSO structure
 into the higher bit, and leave the low bit as a !ThreadRelocated, the GC
 will clean it up.  Don't forget for this to be really useful we also need
 to do #698.

 === use a linked list of stack chunks instead of a single contiguous stack
 ===

 This is a much harder proposition - there's lots of code in the RTS that
 traverses stacks, and it would all have to change (and get more
 complicated, at that).  The current decision to use contiguous stacks was
 made consciously in order to keep things simple.  We'd need some
 convincing evidence that the lack of stack chunks is really hurting, to
 make it worthwhile doing this.  My impression is that there are more
 important things.

-- 
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] #2088: GHC messages do not reflect argument name changes

2008-02-13 Thread GHC
#2088: GHC messages do not reflect argument name changes
---+
 Reporter:  sethkurtzberg  |  Owner: 
 Type:  bug| Status:  new
 Priority:  normal |  Milestone:  6.8.3  
Component:  Compiler   |Version:  6.8.2  
 Severity:  normal | Resolution: 
 Keywords: | Difficulty:  Easy (1 hr)
 Testcase: |   Architecture:  Multiple   
   Os:  Multiple   |  
---+
Changes (by simonmar):

  * difficulty:  => Easy (1 hr)
  * milestone:  => 6.8.3

-- 
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] #2089: reading the package db is slow

2008-02-13 Thread GHC
#2089: reading the package db is slow
--+-
 Reporter:  duncan|  Owner:  
 Type:  compile-time performance bug  | Status:  new 
 Priority:  normal|  Milestone:  6.10 branch 
Component:  Driver|Version:  6.8.2   
 Severity:  minor | Resolution:  
 Keywords:| Difficulty:  Moderate (1 day)
 Testcase:|   Architecture:  x86_64 (amd64)  
   Os:  Multiple  |  
--+-
Changes (by simonmar):

  * difficulty:  => Moderate (1 day)
  * milestone:  => 6.10 branch

Comment:

 The scheme we discussed before is something like this:

  * `ghc-pkg` would automatically generate a binary cache of the package DB
whenever it changed.

  * we want to transition to using a directory of files for the package DB,
 where
a new package can be installed by dropping a file into it and running
`ghc-pkg update` to update the binary cache.

 The main sticking point here is what binary library to use.  In GHC we
 have our own binary library, but it currently isn't available for `ghc-
 pkg` - we'd have to extract it, which is difficult because it has
 dependencies on other GHC datatypes, or use a different binary library.

 If GHC were first modified to use `Data.Binary` for its interface files,
 this would be a lot easier.

-- 
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] #1540: GHC on Macs

2008-02-13 Thread Simon Marlow
> #1540: GHC on Macs
> --+---
> --
>  Reporter:  guest |  Owner:
>  Type:  task  | Status:  closed
>  Priority:  high  |  Milestone:  6.8 branch
> Component:  Build System  |Version:  6.6.1
>  Severity:  normal| Resolution:  fixed
>  Keywords:| Difficulty:  Unknown
>  Testcase:|   Architecture:  x86
>Os:  MacOS X   |
> --+---
> --
> Changes (by chak):
>
>   * status:  new => closed
>   * resolution:  => fixed
>
> Comment:
>
>  It's done.  The HEAD has all the patches, and merged patches for the 6.8
>  branch are waiting for Ian's approval to push.  I announced a trial
>  package on the [http://www.haskell.org/pipermail/glasgow-haskell-
>  users/2008-February/014298.html mailing list] and there is
>  [wiki:Building/MacOSX/Installer detailed documentation] on the wiki.
>
>  I will close this ticket. There may be bugs and missing features with the
>  current implementation, but they should be filed as separate bug reports.

Excellent, nice work!

Simon

___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs