Re: [GHC] #2044: Can't unify error in debugger

2008-04-16 Thread GHC
#2044: Can't unify error in debugger
+---
 Reporter:  r6144   |  Owner:  mnislaih
 Type:  bug | Status:  assigned
 Priority:  normal  |  Milestone:  6.8.3   
Component:  GHCi|Version:  6.8.2   
 Severity:  normal  | Resolution:  
 Keywords:  | Difficulty:  Unknown 
 Testcase:  |   Architecture:  x86 
   Os:  Linux   |  
+---
Comment (by mnislaih):

 I tried with boxy tyvars and that makes the trick almost.
 The problem now is in the side-effect free unification procedure living in
 types/Unify.hs (previously TcGadt.hs). It fails when asked, at some point
 later in the debugger, to unify the type of rsRandomArray with itself.

 I think I will simply switch to boxyUnify here too, and that should
 suffice to close this ticket.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2044#comment:12
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] #2044: Can't unify error in debugger

2008-04-16 Thread GHC
#2044: Can't unify error in debugger
+---
 Reporter:  r6144   |  Owner:  mnislaih
 Type:  bug | Status:  assigned
 Priority:  normal  |  Milestone:  6.8.3   
Component:  GHCi|Version:  6.8.2   
 Severity:  normal  | Resolution:  
 Keywords:  | Difficulty:  Unknown 
 Testcase:  |   Architecture:  x86 
   Os:  Linux   |  
+---
Comment (by mnislaih):

 Oops, I mean the type of `buildBuf`

 {{{
 buildBuf :: ST s (forall s'. ST s' (STUArray s' Idx Double))
 }}}

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


Re: [GHC] #2044: Can't unify error in debugger

2008-04-16 Thread GHC
#2044: Can't unify error in debugger
+---
 Reporter:  r6144   |  Owner:  mnislaih
 Type:  bug | Status:  assigned
 Priority:  normal  |  Milestone:  6.8.3   
Component:  GHCi|Version:  6.8.2   
 Severity:  normal  | Resolution:  
 Keywords:  | Difficulty:  Unknown 
 Testcase:  |   Architecture:  x86 
   Os:  Linux   |  
+---
Comment (by simonpj):

 I don't understand your debugger well enough to give you a coherent
 response.  My guess is that `newBoxyTyVar` will get you past the current
 cant unify, albeit perhaps present some other part of your debugger with
 a polymorphic type it didn't expect.

 I suggest you have a chat with Simon M and/or Bernie initially.

 Meanwhile this bug is only going to affect people using the more exotic
 GHC extensions, I think.

 Still, doing something less unfriendly than crashing would be a useful
 step forward, and you can probably do that regardless?

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2044#comment:11
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] #2220: Subprocesses do not close open FDs

2008-04-16 Thread GHC
#2220: Subprocesses do not close open FDs
+---
 Reporter:  Baughn  |  Owner:   
 Type:  bug | Status:  closed   
 Priority:  normal  |  Milestone:   
Component:  Runtime System  |Version:  6.8.2
 Severity:  normal  | Resolution:  duplicate
 Keywords:  | Difficulty:  Unknown  
 Testcase:  |   Architecture:  Multiple 
   Os:  Multiple|  
+---
Changes (by simonmar):

  * status:  new = closed
  * difficulty:  = Unknown
  * resolution:  = duplicate

Comment:

 See #1780, and the discussion on haskell-cafe that is linked from it.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2220#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] #2220: Subprocesses do not close open FDs

2008-04-16 Thread GHC
#2220: Subprocesses do not close open FDs
---+
 Reporter:  Baughn |  Owner:   
 Type:  bug| Status:  closed   
 Priority:  normal |  Milestone:   
Component:  libraries/process  |Version:  6.8.2
 Severity:  normal | Resolution:  duplicate
 Keywords: | Difficulty:  Unknown  
 Testcase: |   Architecture:  Multiple 
   Os:  Multiple   |  
---+
Changes (by simonmar):

  * component:  Runtime System = libraries/process

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2220#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] #2218: ghci leaks memory on :reload etc

2008-04-16 Thread GHC
#2218: ghci leaks memory on :reload etc
+---
 Reporter:  ganesh  |  Owner: 
 Type:  bug | Status:  new
 Priority:  normal  |  Milestone: 
Component:  GHCi|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Linux   |  
+---
Changes (by simonmar):

  * difficulty:  = Unknown

Comment:

 Object code is not GC'd, but byte-code certainly should be.  It's not
 impossible we have a space leak though.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2218#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] #2218: ghci leaks memory on :reload etc

2008-04-16 Thread GHC
#2218: ghci leaks memory on :reload etc
+---
 Reporter:  ganesh  |  Owner: 
 Type:  bug | Status:  new
 Priority:  normal  |  Milestone: 
Component:  GHCi|Version:  6.8.2  
 Severity:  normal  | Resolution: 
 Keywords:  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Linux   |  
+---
Comment (by ganesh):

 OK, since the behaviour I described isn't known I'll provide proper
 reproduction instructions.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2218#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] #2222: Template Haskell: reify returns incorrect types when ommiting type signatures

2008-04-16 Thread GHC
#: Template Haskell: reify returns incorrect types when ommiting type
signatures
--+-
 Reporter:  fons  |  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone: 
Component:  Template Haskell  |Version:  6.8.2  
 Severity:  major | Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Unknown
   Os:  Multiple  |  
--+-
Changes (by simonpj):

  * difficulty:  = Unknown

Comment:

 OK, so there are several things going on here.

 1.  For `a`, you are hitting the Monomorphism Restriction.  Since `a` is
 monomorphic, it gets type `t0`, where `t0` is a unification variable.
 Right at the very end of the module we might see `(f a)` where `f :: Int
 - Int`, and then (but only then) we'd discover that `t0` is really `Int`.
 The difficulty is that reification (for local variables) can ask for the
 type of a variable before all the evidence is in. A much more direct
 examples would be
 {{{
   \x. ... $( ...reify 'x'... ) ...
 }}}
 The type of `x` may not be determined by the time the splice runs.  I
 can't see a way round this, except by making reification illegal for local
 variables, or perhaps for non-rigid ones, or something.

 2.  Although you wrote your definitions in order `b,c,d`, and they are not
 recursive, GHC is treating them as a mutually recursive group, and, as
 luck would have it, checks `d` first.  So the reification inside `d` see's
 `c`'s type before `c`'s right hand side has been examined, and we are back
 in situation (1).

 Why are they treated as mutually recursive?  Here's the comment from
 `RnSource`:
 {{{
 Note [Splices]
 ~~
 Consider
 f = ...
 h = ...$(thing f)...

 The splice can expand into literally anything, so when we do dependency
 analysis we must assume that it might mention 'f'.  So we simply treat
 all locally-defined names as mentioned by any splice.  This is terribly
 brutal, but I don't see what else to do.  For example, it'll mean
 that every locally-defined thing will appear to be used, so no unused-
 binding
 warnings.  But if we miss the dependency, then we might typecheck
 'h' before 'f', and that will crash the type checker because 'f' isn't
 in scope.

 Currently, I'm not treating a splice as also mentioning every import,
 which is a bit inconsistent -- but there are a lot of them.  We might
 thereby get some bogus unused-import warnings, but we won't crash the
 type checker.  Not very satisfactory really.
 }}}
 Remember that TH allows dynamic binding!

 Again, I don't see a good way around this either.

 You might say that you expect TH splices to be run top-to-bottom, but what
 if one at the bottom is used further up:
 {{{
   f = ...g...
   ...
   h = $(bar 4)
   g = $(foo 3)
 }}}
 Now we have to run the splice for `g` before we can get a type for `g`;
 and we need a type for `g` before we can typecheck `f`.


 Anyway I hope that explains some of what is going on.  The real issues
 here are ones of design, rather than bugs of implementation.  Good design
 ideas would be very welcome -- the TH design is clearly warty in places.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/#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] #989: Windows native port

2008-04-16 Thread GHC
#989: Windows native port
--+-
 Reporter:  simonmar  |  Owner:
 Type:  task  | Status:  new   
 Priority:  normal|  Milestone:  _|_   
Component:  Compiler  |Version:
 Severity:  normal| Resolution:
 Keywords:| Difficulty:  Difficult (1 week)
 Testcase:  N/A   |   Architecture:  x86   
   Os:  Windows   |  
--+-
Changes (by sharpe):

  * version:  6.7 =

Comment:

 Win port of gmp at [http://fp.gladman.plus.com/computing/gmp4win.htm],
 perhaps move gmp out of dist altogether and only link w/ .so or .dll?

 Support utils (cgprof, hp2ps,.. etc.) need minor modifications to build
 and keep cl from choking on e.g. some exotic C macros (and simple ones
 such as macros suffixed with semi-colon).

 RTS is more challenging as it contains a mix of C89, C99, C++ code which
 gcc happily compiles; minor inconsistencies (STATIC_INLINE here, static
 inline there), gcc extensions not supported by cl, inline assembly, void
 pointer arithmetic etc.

 Adapting the build system is pretty terrible (esp. proper
 autoconf,libtool), custom make rules, custom config.h, custom mk files and
 some custom Makefile.win32 do the trick but are more difficult to maintain
 in the future (cmake?).

 Used winsock is deprecated, also i will need to look into signal handling
 as this doesn't behave properly (mingw?).

 Registered boot attempts fail with alignment errors, as of yet not
 resolved (-mix gcc/cl?); will continue on unregistered 6.4 series builds.

 Haven't got to real low-level stuff, YASM seems ok and is easily
 integrated w/ VS2008.

 prepping the environment is pretty easy once you've got around the unixy
 build system
 (include vcvars variables PATH,LIBPATH,INCLUDE etc.), btw utils/pwd does
 not work in mingw using series 6.8.2 (easily resolved).

 merging changes will be another fun item.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/989#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] #989: Windows native port

2008-04-16 Thread GHC
#989: Windows native port
--+-
 Reporter:  simonmar  |  Owner:
 Type:  task  | Status:  new   
 Priority:  normal|  Milestone:  _|_   
Component:  Compiler  |Version:
 Severity:  normal| Resolution:
 Keywords:| Difficulty:  Difficult (1 week)
 Testcase:  N/A   |   Architecture:  x86   
   Os:  Windows   |  
--+-
Changes (by NeilMitchell):

 * cc: [EMAIL PROTECTED] (added)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/989#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] #2223: Int64.toInteger

2008-04-16 Thread GHC
#2223: Int64.toInteger
---+
Reporter:  gnezdo  |   Owner:
Type:  bug |  Status:  new   
Priority:  normal  |   Component:  Runtime System
 Version:  6.8.2   |Severity:  major 
Keywords:  |Testcase:
Architecture:  x86 |  Os:  Linux 
---+
 {{{
 GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
 Loading package base ... linking ... done.
 Prelude 0 == (-1 `Data.Bits.shift` 32 :: Data.Int.Int64)
 False
 Prelude 0 == toInteger (-1 `Data.Bits.shift` 32 :: Data.Int.Int64)
 True
 -- ^^^ BUG
 }}}

 The problem appears to be in the recently changed
 rts/PrimOps.cmm::int64ToIntegerzh_fast:
 {{{
if ( hi != 0  hi != 0x )  {
   words_needed = 2;
} else {
// minimum is one word
words_needed = 1;
}
 }}}

 So, 0x becomes 0.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2223
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] #2224: -fhpc inteferes/prevents rewrite rules from firing

2008-04-16 Thread GHC
#2224: -fhpc inteferes/prevents rewrite rules from firing
---+
Reporter:  dons|   Owner:  [EMAIL PROTECTED]
Type:  bug |  Status:  new
Priority:  normal  |   Component:  Code Coverage  
 Version:  6.8.2   |Severity:  normal 
Keywords:  rules, hpc  |Testcase: 
Architecture:  Unknown |  Os:  Unknown
---+
 Use case:

 I'm writing tests for rewrite rules, and using HPC to determine if rules
 were fired (and their code exercised). HPC is quite cool here, since it
 lets us see which rules fired, without needing to explicitly export
 functions to test.

 However, -fhpc seems to prevent many rules from firing (likely due to
 ticks getting in the way?)

 For example:

 {{{
 import qualified  Data.ByteString.Char8 as C

 main = print (C.pack literal)
 }}}

 When compiled normally, triggers a nice rewrite rule:

 {{{
 $ ghc -O2 A.hs -ddump-simpl-stats A.hs -c

 1 ByteString pack/packAddress
 }}}

 Now with -fhpc:

 {{{
 2 RuleFired
 1 unpack
 1 unpack-list
 }}}

 What's the best way to ensure the same code is exercised with and without
 -fhpc here? (I'd quite like to get this working, since rewrite rules
 benefit from testing.)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2224
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] #2213: -Wall incorrectly warns Defined but not used for functions exported via RULES

2008-04-16 Thread GHC
#2213: -Wall incorrectly warns Defined but not used for functions exported via
RULES
-+--
Reporter:  dons  |Owner:  dons
Type:  bug   |   Status:  assigned
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  6.8.2   
Severity:  normal|   Resolution:  
Keywords:| Testcase:  
Architecture:  Unknown   |   Os:  Unknown 
-+--
Changes (by dons):

  * status:  new = assigned
  * owner:  = dons

Comment:

 Ah, worked this one out.

 `-fglasgow-exts` is needed to enable rules, otherwise they're considered
 comments. (Hence the type error in this rule is silently ignored).

 Note however, strangely, `-frewrite-rules` *doesn't* fix this.

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


[GHC] #2225: hackage library encoding-0.4 crashes ghc 6.8.2

2008-04-16 Thread GHC
#2225: hackage library encoding-0.4 crashes ghc 6.8.2
+---
Reporter:  guest|   Owner:  
Type:  bug  |  Status:  new 
Priority:  normal   |   Component:  Compiler
 Version:  6.8.2|Severity:  normal  
Keywords:   |Testcase:  
Architecture:  Unknown  |  Os:  Unknown 
+---
 This is on i386 ubuntu gutsy.  Output of runghc Setup.hs build is:

 {{{
 encoding-0.4$ runghc Setup.hs build
 Preprocessing library encoding-0.4...
 Building encoding-0.4...
 [ 1 of 37] Compiling Data.Encoding.Helper.Template (
 Data/Encoding/Helper/Template.hs, dist/build/Data/Enco\
 ding/Helper/Template.o )
 [ 2 of 37] Compiling Data.Encoding.GB18030Data (
 Data/Encoding/GB18030Data.hs, dist/build/Data/Encoding/GB1\
 8030Data.o )
 [ 3 of 37] Compiling Data.Encoding.Base ( Data/Encoding/Base.hs,
 dist/build/Data/Encoding/Base.o )
 [ 4 of 37] Compiling Data.Encoding.GB18030 ( Data/Encoding/GB18030.hs,
 dist/build/Data/Encoding/GB18030.o )
 [ 5 of 37] Compiling Data.Encoding.KOI8U ( Data/Encoding/KOI8U.hs,
 dist/build/Data/Encoding/KOI8U.o )
 [ 6 of 37] Compiling Data.Encoding.KOI8R ( Data/Encoding/KOI8R.hs,
 dist/build/Data/Encoding/KOI8R.o )
 [ 7 of 37] Compiling Data.Encoding.CP1258 ( Data/Encoding/CP1258.hs,
 dist/build/Data/Encoding/CP1258.o )
 Loading package base ... linking ... done.
 Loading package pretty-1.0.0.0 ... linking ... done.
 Loading package array-0.1.0.0 ... linking ... done.
 Loading package packedstring-0.1.0.0 ... linking ... done.
 Loading package containers-0.1.0.1 ... linking ... done.
 Loading package template-haskell ... linking ... done.
 Loading package bytestring-0.9.0.1 ... linking ... done.
 ghc-6.8.2: internal error: loadObj: can't map
 `dist/build/Data/Encoding/Helper/Template.o'
 (GHC version 6.8.2 for i386_unknown_linux)
 Please report this as a GHC bug:
 http://www.haskell.org/ghc/reportabug
 encoding-0.4$

 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2225
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] #2224: -fhpc inteferes/prevents rewrite rules from firing

2008-04-16 Thread GHC
#2224: -fhpc inteferes/prevents rewrite rules from firing
--+-
Reporter:  dons   |Owner:  [EMAIL PROTECTED]
Type:  bug|   Status:  new
Priority:  normal |Milestone: 
   Component:  Code Coverage  |  Version:  6.8.2  
Severity:  normal |   Resolution: 
Keywords:  rules, hpc | Testcase: 
Architecture:  Unknown|   Os:  Unknown
--+-
Comment (by AndyGill):

 I'm not sure what to do here. To match code that contains ticks, and
 rewrite them requires either
  * removing ticks - generally a bad idea!
  * recreating the ticks, which is hard/impossible to do in some cases.

 I suppose we could have an option to ignore ticks in rules, but this leads
 to false positives.


 Also consider:
 {{{
   {-# RULES
 pack/packAddress forall s . pack (unpackCString# s) = B.packAddress
 s
#-}
 }}}

 pack and unpackCString are strict, so we have tick equivalence!


 {{{

 tick1pack(tick2unpackCString# (tick3 s))
 }}}

 is the same as
 {{{
tick1,2,3pack(unpackCString# s)
 }}}
 The tick lifting has given us the original match.

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