Re: [GHC] #7375: Building ghc fails because it is looking for an old version of libgmp

2012-11-08 Thread GHC
#7375: Building ghc fails because it is looking for an old version of libgmp
--+-
  Reporter:  mimosa   |  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  
 Component:  Compiler |Version:  7.4.2   
Resolution:  fixed|   Keywords:  
Os:  Linux|   Architecture:  Unknown/Multiple
   Failure:  Building GHC failed  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  5743
--+-

Comment(by simonmar):

 As long as `libgmp.so` doesn't point to `libgmp.so.3`, the GHC build
 should not depend on `libgmp.so.3`.

 Some background here: GHC is written in Haskell and therefore needs a
 working GHC to build it.  We call this the stage 0 compiler, which is
 used to build a stage 1 compiler, which finally builds the stage 2
 compiler, and the stage 2 is what we install.

 Now, in your case probably the stage 0 compiler you're using was built
 against `libgmp.so.3`, so you need that on your system to run it.
 Furthermore, stage 1 will also depend on `libgmp.so.3` because it was
 built by stage 0.  But stage 2 should not depend on `libgmp.so.3`, it
 should depend on whatever version is linked to from `libgmp.so` on your
 system (but you do need to have a `libgmp.so` somewhere, otherwise GHC
 will build its own `libgmp` and use that).

 GHCi won't even start up if you don't have the right `libgmp` installed,
 since the binary itself depends on it.

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


[GHC] #7398: RULES don't apply to a newtype constructor

2012-11-08 Thread GHC
#7398: RULES don't apply to a newtype constructor
+---
Reporter:  shachaf  |  Owner:  
Type:  bug  | Status:  new 
Priority:  normal   |  Component:  Compiler
 Version:  7.6.1|   Keywords:  
  Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
 Failure:  Incorrect result at runtime  |  Blockedby:  
Blocking:   |Related:  
+---
 For some reason, RULES that involve a newtype constructor never seem to
 fire. The following program demonstrates the problem:

 {{{
 module Main where

 newtype Foo a = Foo { unFoo :: a }
   deriving Show

 foo :: a - Foo a
 foo = Foo

 {-# RULES rule Foo  forall v.  Foo v = error Foo #-}
 {-# RULES rule foo  forall v.  foo v = error foo #-}

 main :: IO ()
 main = do
 print (Foo ())
 print (foo ())
 }}}

 rule foo fires, but rule Foo doesn't. The program prints

 {{{
 Foo {unFoo = ()}
 D: foo
 }}}

 Note that this doesn't seem to affect selectors, only constructors.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7398
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] #7399: Test Posix004 fails in test-suite

2012-11-08 Thread GHC
#7399: Test Posix004 fails in test-suite
+---
Reporter:  paulh|  Owner:
Type:  bug  | Status:  new   
Priority:  normal   |  Component:  Compiler  
 Version:  7.6.1|   Keywords:
  Os:  Linux|   Architecture:  x86_64 (amd64)
 Failure:  Incorrect result at runtime  |  Blockedby:
Blocking:   |Related:
+---
 After a standard build of ghc-7.6.1 on debian wheezy, the test-suite fails
 on the test posix004.

 The error given is:

 Wrong exit code (expected 0 , actual 1 )
 Stdout:

 Stderr:
 posix004: unexpected termination cause

 *** unexpected failure for posix004(normal)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7399
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] #4012: Compilation results are not deterministic

2012-11-08 Thread GHC
#4012: Compilation results are not deterministic
---+
  Reporter:  kili  |  Owner:  igloo   
  Type:  bug   | Status:  new 
  Priority:  high  |  Milestone:  7.6.2   
 Component:  Compiler  |Version:  6.12.2  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Other | Difficulty:  Difficult (2-5 days)
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by igloo):

 I think this is only really a problem when ghc ''generates'' the same name
 at both the top level and in an expression. Is it feasible to generate
 e.g. 'tlvl' for top-level names, and 'lvl' for let/lambda-bound names?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4012#comment:32
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] #4012: Compilation results are not deterministic

2012-11-08 Thread GHC
#4012: Compilation results are not deterministic
---+
  Reporter:  kili  |  Owner:  
  Type:  bug   | Status:  new 
  Priority:  high  |  Milestone:  7.6.2   
 Component:  Compiler  |Version:  6.12.2  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  Other | Difficulty:  Difficult (2-5 days)
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by igloo):

  * owner:  igloo =


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4012#comment:33
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] #7395: DefaultSignatures conflict with default implementations

2012-11-08 Thread GHC
#7395: DefaultSignatures conflict with default implementations
--+-
Reporter:  cgaebel|   Owner:   
Type:  bug|  Status:  new  
Priority:  normal |   Milestone:   
   Component:  Compiler   | Version:  7.6.1
Keywords:  DefaultSignatures  |  Os:  Unknown/Multiple 
Architecture:  Unknown/Multiple   | Failure:  GHC rejects valid program
  Difficulty:  Unknown|Testcase:   
   Blockedby: |Blocking:   
 Related: |  
--+-
Changes (by hvr):

 * cc: hvr@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7395#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] #7375: Building ghc fails because it is looking for an old version of libgmp

2012-11-08 Thread GHC
#7375: Building ghc fails because it is looking for an old version of libgmp
--+-
  Reporter:  mimosa   |  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  normal   |  Milestone:  
 Component:  Compiler |Version:  7.4.2   
Resolution:  fixed|   Keywords:  
Os:  Linux|   Architecture:  Unknown/Multiple
   Failure:  Building GHC failed  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  5743
--+-

Comment(by mimosa):

 Thanks for explaining about the bootstrapping. I didn't realise there were
 ''three'' stages.

 FWIW I just built GHC again with a doctored version of the build script
 that doesn't build gmp - it just uses a symlink. (It does, however, build
 libffi. I just wanted to change the treatment of gmp.)
 And (as you say) GHCi won't even start up without that symlink. libgmp.so
 points at libgmp.so.10.05 (the system version).

 This doesn't seem to be what would be expected given what you say about
 stage 2, and it may be something wrong with my package. However the real
 package (with the old gmp) does actually work, and the Salix devs don't
 seem to mind having a package like that. The package should also work on
 Slackware itself, and on other compatible Slackware-derived distros.

 More generally, I don't see how a package could be made that doesn't
 require some hack, because the stage 0 compiler needs the old gmp. That
 wasn't a problem when it wasn't old, but as soon as any given distro
 upgrades to a more recent gmp, that GHC can surely only build on it either
 with a symlink or a magic library.

 That wouldn't matter except that in the world of Haskell, it seems any
 given version of ghc will continue to have currency some time after it has
 been superseded, because it forms part of a software distribution
 (haskell-platform) and may also be needed by other software (such as
 xmonad).

 So my concrete suggestion is the following. Why not ship any such
 libraries with the GHC source so it can still build on a system that
 doesn't have them any more? If my suggestion is feasible, it would entail
 building gmp (and whatever other libraries) as a very first step before
 executing the stage 0 GHC binary, if those libraries are not present on
 the build system in the versions needed.

 I appreciate that this isn't really any cleaner than leaving each distro's
 packagers to do effectively the same thing, because ultimately, as I
 understand it, GHC can't be built strictly from source because of the
 bootstrapping problem; but it would satisfy the letter of the law. It
 would also mean the work would be done once (by you guys) instead of once
 each per distro. And at least for libffi(#5743), there are people patching
 the source to avoid hackish packaging. The rules are the rules, and all
 that.

 Maybe GHC could become more widely represented in the Linux ecosystem that
 way.

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


[GHC] #7400: Strange closure type 17 internal error

2012-11-08 Thread GHC
#7400: Strange closure type 17 internal error
-+--
Reporter:  ropoctl   |  Owner:
Type:  bug   | Status:  new   
Priority:  normal|  Component:  Runtime System
 Version:  7.4.2 |   Keywords:
  Os:  Linux |   Architecture:  x86_64 (amd64)
 Failure:  None/Unknown  |  Blockedby:
Blocking:|Related:
-+--
 resample: internal error: evacuate(static): strange closure type 17
 (GHC version 7.4.2 for x86_64_unknown_linux)
 Please report this as a GHC bug:
 http://www.haskell.org/ghc/reportabug

 {{{
 module Resample where

 import Data.List
 import qualified Data.ByteString as B
 import qualified Data.ByteString.Char8 as BC
 import qualified Data.ByteString.Lazy.Char8 as BL
 import qualified Data.ByteString.Lazy as BB

 import qualified Data.Vector as V
 import System.Random.Mersenne
 import Control.Monad (liftM, replicateM_)

 readCollapsed :: FilePath - IO [(Int, B.ByteString)]
 readCollapsed f = ((map (either error id) . unfoldr parse) . BL.lines)
 `fmap` BL.readFile f

 parse :: [BL.ByteString] - Maybe (Either String (Int, B.ByteString),
 [BL.ByteString])
 parse (c:sq:rest) =
 Just (Right (read $ BL.unpack c, B.concat $ BL.toChunks sq), rest)
 parse [] = Nothing
 parse fs = let showStanza = unlines (map BL.unpack fs)
err = Left $ Resample: illegal number of lines:  ++
 showStanza
in Just (err, [])

 uncollapse :: (Int, B.ByteString) - [B.ByteString]
 uncollapse (c, sq) = take c $ repeat sq

 randomPick' mt vec len = liftM (vec V.!) $ liftM ((flip mod) len) (random
 mt)

 main :: IO ()
 main = do
 sqvec - liftM (V.fromList . Prelude.concatMap uncollapse) $
 readCollapsed /dev/stdin
 let seqlen = V.length sqvec
 mtgen - newMTGen Nothing
 replicateM_ 3000 $ BC.putStrLn = randomPick' mtgen sqvec seqlen
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7400
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] #3072: considerations for management of shared libs

2012-11-08 Thread GHC
#3072: considerations for management of shared libs
-+--
Reporter:  duncan|   Owner:  igloo   
Type:  feature request   |  Status:  new 
Priority:  low   |   Milestone:  7.6.2   
   Component:  Package system| Version:  6.10.1  
Keywords:|  Os:  Linux   
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by ian@…):

 commit 7dd7008f98c76024288899b8cea607141c91ada5
 {{{
 Author: Ian Lynagh i...@well-typed.com
 Date:   Thu Nov 8 21:46:46 2012 +

 Give dynamic libraries, as well as programs, RPATHs

 Based on a patch from markwright in #3072.

  rules/build-package-way.mk |4 ++--
  rules/build-prog.mk|   25 -
  rules/distdir-way-opts.mk  |   12 
  3 files changed, 26 insertions(+), 15 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3072#comment:17
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] #3072: considerations for management of shared libs

2012-11-08 Thread GHC
#3072: considerations for management of shared libs
--+-
  Reporter:  duncan   |  Owner:  igloo   
  Type:  feature request  | Status:  closed  
  Priority:  low  |  Milestone:  7.6.2   
 Component:  Package system   |Version:  6.10.1  
Resolution:  fixed|   Keywords:  
Os:  Linux|   Architecture:  Unknown/Multiple
   Failure:  None/Unknown | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by igloo):

  * status:  new = closed
  * resolution:  = fixed


Comment:

 I think we now do as much as we can, so I'm closing this ticket.

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


Re: [GHC] #7299: threadDelay broken in ghci, Mac OS X

2012-11-08 Thread GHC
#7299: threadDelay broken in ghci, Mac OS X
-+--
Reporter:  tmcdonell |   Owner:
Type:  bug   |  Status:  new   
Priority:  highest   |   Milestone:  7.6.2 
   Component:  GHCi  | Version:  7.6.1 
Keywords:|  Os:  MacOS X   
Architecture:  Unknown/Multiple  | Failure:  GHCi crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:|Blocking:
 Related:|  
-+--
Changes (by chak):

 * cc: chak@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7299#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] #5544: threadDelay with large values crashes the IO manager on 64-bit OS X

2012-11-08 Thread GHC
#5544: threadDelay with large values crashes the IO manager on 64-bit OS X
-+--
  Reporter:  carlhowells |  Owner:
  Type:  bug | Status:  new   
  Priority:  high|  Milestone:  7.4.3 
 Component:  Runtime System  |Version:  7.2.1 
Resolution:  |   Keywords:
Os:  MacOS X |   Architecture:  x86_64 (amd64)
   Failure:  None/Unknown| Difficulty:  Unknown   
  Testcase:  |  Blockedby:
  Blocking:  |Related:
-+--
Changes (by kazu-yamamoto):

  * owner:  tibbe =
  * status:  closed = new
  * resolution:  worksforme =


Comment:

 This bug happens 100% with GHC 7.4.1 (64bit) and GHC 7.6.1 (64bit) on my
 MacOS 10.8.2 (MacBook Air).

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