Re: [GHC] #1631: Make the External Package Table contain ModDetails not ModIface

2007-11-09 Thread GHC
#1631: Make the External Package Table contain ModDetails not ModIface
--+-
 Reporter:  simonpj   |  Owner: 
 Type:  task  | Status:  new
 Priority:  normal|  Milestone:  6.10 branch
Component:  Compiler  |Version:  6.6.1  
 Severity:  normal| Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Unknown
   Os:  Unknown   |  
--+-
Comment (by simonpj):

 See also #1617, and Simon's comment on the patch:
 {{{
 Wed Nov  7 08:14:54 PST 2007  Simon Marlow <[EMAIL PROTECTED]>
   * FIX #1617: reloading didn't change the :browse output as it should
   The problem was that because the interface hadn't changed, we were
   re-using the old ModIface.  Unfortunately the ModIface contains the
   GlobalRdrEnv for the module, and that *had* changed.  The fix is to
   put the new GlobalRdrEnv in the ModIface even if the interface has not
   otherwise changed.

   ModIface is not really the right place for the GlobalRdrEnv, but
   neither is ModDetails, so we should think about a better way to do
   this.
 }}}

-- 
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] #1849: Template Haskell: reify is not consistent with the special constructors ListT and TupleT

2007-11-09 Thread GHC
#1849: Template Haskell: reify is not consistent with the special constructors
ListT and TupleT
--+-
 Reporter:  guest |  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone:  6.10 branch
Component:  Template Haskell  |Version:  6.8.1  
 Severity:  normal| Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Unknown
   Os:  Unknown   |  
--+-
Comment (by simonpj):

 I think this is likely to be easily fixed, but don't want to fix it if you
 and Ian agree in the end to eliminate the ListT and TupleT constructors!
 So shall it wait pending that decision?

 Simon

-- 
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] #1849: Template Haskell: reify is not consistent with the special constructors ListT and TupleT

2007-11-09 Thread GHC
#1849: Template Haskell: reify is not consistent with the special constructors
ListT and TupleT
--+-
 Reporter:  guest |  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone:  6.10 branch
Component:  Template Haskell  |Version:  6.8.1  
 Severity:  normal| Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Unknown
   Os:  Unknown   |  
--+-
Comment (by guest):

 Replying to [comment:4 simonpj]:
 > I think this is likely to be easily fixed, but don't want to fix it if
 you and Ian agree in the end to eliminate the ListT and TupleT
 constructors!

 As I recently wrote in the template-haskell list [1], I think the special
 type constructors should be kept as long as all redundancies are
 eliminated (i.e. template-haskell should only return tuple list and arrow
 types to the user in the form of ListT ArrT and TupleT; never using ConT).

 According to that, current behaviour of reify is redundant, that's why I
 opened this ticket. Let's see what Ian thinks.

 In the same message I also proposed separating constructors from types
 themselves, ... but that's another story.

 [1] http://www.haskell.org/pipermail/template-
 haskell/2007-November/000649.html

-- 
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] #1862: DocBook XSL Stylesheets search path is incomplete

2007-11-09 Thread GHC
#1862: DocBook XSL Stylesheets search path is incomplete
---+
 Reporter:  AndreaRossato  |  Owner:   
 Type:  bug| Status:  new  
 Priority:  normal |  Milestone:   
Component:  Documentation  |Version:  6.8.1
 Severity:  normal |   Keywords:   
 Testcase: |   Architecture:  x86  
   Os:  Linux  |  
---+
 Presently the directory used by Slackware GNU/Linux and other distribution
 to store the docbook xsl stylesheets is not searched by ghc configuration
 script.

 Attached a patch to configure.ac to include that directory:
 /usr/share/xml/docbook/xsl-stylesheets*

 Regrads,
 Andrea Rossato

-- 
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] #1810: install-sh copies only a single header file to $(BIN_DIST_DIR)/includes/

2007-11-09 Thread GHC
#1810: install-sh copies only a single header file to  $(BIN_DIST_DIR)/includes/
--+-
 Reporter:  guest |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Milestone:  6.8.2   
Component:  Build System  |Version:  6.8.1   
 Severity:  normal| Resolution:  
 Keywords:| Difficulty:  Unknown 
 Testcase:|   Architecture:  Multiple
   Os:  Solaris   |  
--+-
Changes (by guest):

  * architecture:  x86 => Multiple

-- 
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] #1845: unconditional relative branch out of range (GHC version 6.8.1 for powerpc_apple_darwin)

2007-11-09 Thread GHC
#1845: unconditional relative branch out of range (GHC version 6.8.1 for
powerpc_apple_darwin)
-+--
 Reporter:  guest|  Owner: 
 Type:  bug  | Status:  new
 Priority:  normal   |  Milestone:  6.8.2  
Component:  GHCi |Version:  6.8.1  
 Severity:  normal   | Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:   |   Architecture:  powerpc
   Os:  MacOS X  |  
-+--
Comment (by ChrisKuklewicz):

 This *might* be related to bug
 [http://hackage.haskell.org/trac/ghc/ticket/1843 #1843] on OS X 10.5
 (Leopard) on ppc.

-- 
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] #1843: ghc 6.8.1 broken on Mac OS X Leopard PPC

2007-11-09 Thread GHC
#1843: ghc 6.8.1 broken on Mac OS X Leopard PPC
--+-
 Reporter:  guest |  Owner: 
 Type:  bug   | Status:  new
 Priority:  high  |  Milestone:  6.8.2  
Component:  Compiler  |Version:  6.8.1  
 Severity:  critical  | Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  powerpc
   Os:  MacOS X   |  
--+-
Comment (by ChrisKuklewicz):

 This *might* be related to bug
 [http://hackage.haskell.org/trac/ghc/ticket/1845 #1845] on OS X 10.4
 (Tiger) on ppc.

-- 
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] #1843: ghc 6.8.1 broken on Mac OS X Leopard PPC

2007-11-09 Thread GHC
#1843: ghc 6.8.1 broken on Mac OS X Leopard PPC
--+-
 Reporter:  guest |  Owner: 
 Type:  bug   | Status:  new
 Priority:  high  |  Milestone:  6.8.2  
Component:  Compiler  |Version:  6.8.1  
 Severity:  critical  | Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  powerpc
   Os:  MacOS X   |  
--+-
Comment (by guest):

 I don't have the above problem with OS X 10.4 (Tiger) on ppc with #1845,
 Christian
 {{{
 ./fail
 2
 }}}
 (but may other jumps are wrong on Leopard.)

 Does anyone have a ghc-6.8.1 on ppc without #1845?

-- 
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] #1771: hFileSize gives negative values

2007-11-09 Thread GHC
#1771: hFileSize gives negative values
+---
 Reporter:  guest   |  Owner:
 Type:  bug | Status:  new   
 Priority:  normal  |  Milestone:  6.8 branch
Component:  Compiler|Version:  6.6.1 
 Severity:  normal  | Resolution:
 Keywords:  hFileSize >2gb  | Difficulty:  Unknown   
 Testcase:  |   Architecture:  x86   
   Os:  Windows |  
+---
Changes (by guest):

  * keywords:  hFileSize => hFileSize >2gb

Comment:

 This function is _filelengthi64. But don't forget to correct hSeek/hTell
 too. It's part of "New Haskell I/O library" drama which has long, long
 story :)

 one possible temporary solution is to use my Streams library
 (http://haskell.org/haskellwiki/Library/Streams) which supports large
 files

-- 
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] #1372: Recompilation checker should consider package versions (and other factors)

2007-11-09 Thread GHC
#1372: Recompilation checker should consider package versions (and other 
factors)
--+-
 Reporter:  bringert  |  Owner:  simonmar  
 Type:  bug   | Status:  new   
 Priority:  normal|  Milestone:  6.8 branch
Component:  Compiler  |Version:  6.8.1 
 Severity:  normal| Resolution:
 Keywords:| Difficulty:  Unknown   
 Testcase:|   Architecture:  Unknown   
   Os:  Unknown   |  
--+-
Changes (by dons):

 * cc: [EMAIL PROTECTED] (added)
  * version:  6.6 => 6.8.1

Comment:

 In the xmonad head branch we've split things so that xmonad extensions are
 a library which depends on the xmonad core. Now we get a new set of
 segfaulting xmonad binaries, when people forget to clean their extensions
 library, after rebuilding the core library:

 > My xmonad segfaulted today [at `noBorders' function] since I had
 forgotten to `runhaskell Setup.lhs clean' in XMonadContrib directory.

 -- Reported by Valery V. Vorotyntsev

 Any suggestions on how we can avoid this bad user experience?

-- 
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] #1463: Module → Package loo kup in ghc-pkg?

2007-11-09 Thread GHC
#1463: Module → Package lookup in ghc-pkg?
---+
 Reporter:  [EMAIL PROTECTED]  |  Owner: 
 Type:  feature request| Status:  new
 Priority:  normal |  Milestone:  6.10 branch
Component:  Compiler   |Version:  6.6.1  
 Severity:  normal | Resolution: 
 Keywords: | Difficulty:  Unknown
 Testcase: |   Architecture:  Unknown
   Os:  Unknown|  
---+
Comment (by guest):

 it occurred to me that `ghc-pkg find-module Data.Sequence` is just a minor
 variation on `ghc-pkg list containers`, so i implemented it as such:

 http://www.haskell.org/pipermail/cvs-ghc/2007-November/039421.html

 it would still be nice to be able to combine multiple `ghc-pkg` queries
 into one, but i guess that would be another ticket?-)

-- 
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] #1463: Module → Package loo kup in ghc-pkg?

2007-11-09 Thread GHC
#1463: Module → Package lookup in ghc-pkg?
---+
 Reporter:  [EMAIL PROTECTED]  |  Owner: 
 Type:  feature request| Status:  new
 Priority:  normal |  Milestone:  6.10 branch
Component:  Compiler   |Version:  6.6.1  
 Severity:  normal | Resolution: 
 Keywords: | Difficulty:  Unknown
 Testcase: |   Architecture:  Unknown
   Os:  Unknown|  
---+
Comment (by guest):

 Replying to [comment:6 guest]:
 > i've got a minor patch that extends ghci's :info to handle module names
 as well, so
 > {{{
 > Prelude> :i Prelude Data.Maybe Distribution.System Data.Array
 Data.Sequence

 @Simons:

 i'm having a minor problem with this one: getting the info is easy enough,
 but a name might be both module and something else, so i'd like `:info` to
 check both, reporting errors only if it can't find either. but the error
 output for the existing checks seems to be hardwired deep in the call
 chain, so i don't know how to disable that for names that have successful
 module information.

-- 
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] #1863: gen-contents-index.sh doesn't work with Haddock 2

2007-11-09 Thread GHC
#1863: gen-contents-index.sh doesn't work with Haddock 2
--+-
 Reporter:  guest |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Milestone:  6.8.2   
Component:  Build System  |Version:  6.8.1   
 Severity:  normal|   Keywords:  Haddock 
 Testcase:|   Architecture:  Multiple
   Os:  Multiple  |  
--+-
 gen-contents-index.sh needs to pass -B  to Haddock if its
 version is >= 2.

-- 
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] #1843: ghc 6.8.1 broken on Mac OS X Leopard PPC

2007-11-09 Thread GHC
#1843: ghc 6.8.1 broken on Mac OS X Leopard PPC
--+-
 Reporter:  guest |  Owner: 
 Type:  bug   | Status:  new
 Priority:  high  |  Milestone:  6.8.2  
Component:  Compiler  |Version:  6.8.1  
 Severity:  critical  | Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  powerpc
   Os:  MacOS X   |  
--+-
Comment (by mokus):

 Replying to [comment:4 ChrisKuklewicz]:
 > I attempted to make 6.8.1 on a G4 with OS X 10.5 and XCode 3.0
 >
 > The stage1 compiler seems to run, but the I got _many_ of those "unknown
 scattered relocation type 4" errors.  The stage2 compiler that was
 installed simply segfaults when run.
 >
 > If I tried to compile the extra src tarball at the same time then it
 would die in the parsec package during compilation.  But that might be an
 unrelated error.

 I have had the same experience on my PowerBook G4 (building on Leopard
 using XCode 3 and ghc-6.6.1).  Regarding the parsec build issue:  based on
 the output when '-v' is added to the command-line that fails, the error
 seems to be related to the '-split-objs' option somehow making ld blow up.
 Removing '-O' from the command line apparently changes the output enough
 that it doesn't trigger the problem.

 I have no hypothesis regarding the segfault issue, but I can confirm that
 when building either 6.8.1 or head, my stage1 builds pretend to work, but
 my stage2 compilers are deader than doornails.  Anything I can do to
 provide more useful info?

-- 
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] #1843: ghc 6.8.1 broken on Mac OS X Leopard PPC

2007-11-09 Thread GHC
#1843: ghc 6.8.1 broken on Mac OS X Leopard PPC
--+-
 Reporter:  guest |  Owner: 
 Type:  bug   | Status:  new
 Priority:  high  |  Milestone:  6.8.2  
Component:  Compiler  |Version:  6.8.1  
 Severity:  critical  | Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  powerpc
   Os:  MacOS X   |  
--+-
Comment (by mokus):

 Replying to [comment:9 mokus]:
 > I have no hypothesis regarding the segfault issue, but I can confirm
 that when building either 6.8.1 or head, my stage1 builds pretend to work,
 but my stage2 compilers are deader than doornails.  Anything I can do to
 provide more useful info?
 >

 As I typed this, I realized I hadn't actually tested the stage1 ghc-
 inplace to confirm that it regularly produces vegetables.  I have now done
 so.  Simple 'hello world'-type stuff works, but just about nothing else
 does.  Here's a pretty simple program that segfaults when run after being
 compiled by stage1/ghc-inplace:


 {{{
 {-
  -  "primes.hs"
  -}

 module Main where

 import System

 primes = 2 : 3: 5 : (filter isPrime [7,9..])

 -- x %= y: "x divides y"
 x %= y = (y `rem` x) == 0

 isPrime x
 | x <= 1= False
 | isComposite x = False
 | otherwise = True
 isComposite x = any (%= x) (takeWhile (\p -> p^2 <= x) primes)

 main = do
 args <- getArgs
 let n = read (args !! 0)
 print (primes !! (n - 1))

 }}}

 Some interesting facts:  "otool -r" knows of no relocations in the
 compiled file.  There are 14 listed in the working version compiled with
 ghc-6.6.1.  When I compiled with ghc-inplace, there were 8 of the infamous
 "unknown scattered relocation type 4" messages.

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