Re: [commit: ghc] master: Add :info! to GHCi. This shows all instances without filtering first. (2ec32a8)

2012-12-04 Thread Simon Marlow

On 03/12/12 20:13, Iavor Diatchki wrote:

Hello,

On Mon, Dec 3, 2012 at 8:44 AM, Simon Marlow marlo...@gmail.com
mailto:marlo...@gmail.com wrote:

OI know that Accessor has an Applicative instace because the operations

work.  I'd like to find the instance, so I can see how it works,
so I try:


Ok, so this is a bug: you shouldn't be able to use the instance
because it isn't in scope.  If this was a source file, then GHC
would complain that the instance was not in scope.

The bug is (sort of) documented in the Known Bugs section of the
user guide, although the documentation incorrectly says that it also
affects --make, which it doesn't (I'll fix it).


I don't think that this is the bug to blame: the instance is in scope,
it is just that it is being filtered by :info.
Here is an example:

module Test where

import Control.Applicative (pure)
import Control.Lens

example :: Accessor () ()
example = pure ()

This works just fine.  I think the issue is as follows.  The
`Applicative` instance for `Accessor` is like this:

instance Monoid r = Applicative (Accessor r)

Now, on the GHCi command line `Accessor` and `Applicative` are in scope
but `Monoid` is not.  However, there are instances of `Monoid` for
various datatypes (e.g., ()) that are also in scope, so that instance is
actually usable.


Ah, I see.  Sp that suggests a better fix: the new :info! should display 
all instances that are in scope, in contrast to the ordinary :info which 
displays only instances involving types and classes that are in scope.



As far as I understand, the current plausiblity check filters out any
instances that contain tycons that are not in-scope, which is why this
particular instance does not show up.  It looks like in some cases this
is too aggressive.

So I don't really object to having this feature, as long as we say
clearly in the documentation that it doesn't have a well-specified
behaviour, and the instances it shows may or may not actually be
available. (if we fix the bug, many of them won't be available, but
it might be useful to find out where to get them from).

Would you mind updating the docs, and close #5998?

Yeah, I'd be happy to do that.  Which documentation should I update?


The GHCi docs (docs/users_guide/ghci.xml) to add the new command.

Cheers,
Simon




-Iavor




Cheers,
 Simon



Prelude Control.Applicative Control.Lens :i Accessor
newtype Accessor r a
= Control.Lens.Internal.Accessor
{Control.Lens.Internal.__runAccessor :: r}
-- Defined in `Control.Lens.Internal'
instance Functor (Accessor r) -- Defined in `Control.Lens.Internal'
instance Gettable (Accessor r)
-- Defined in `Control.Lens.Internal’

Weird, it doesn’t show up, so what are the instances of
`Applicative`?

Prelude Control.Applicative Control.Lens :i Applicative
class Functor f = Applicative f where
pure :: a - f a
(*) :: f (a - b) - f a - f b
(*) :: f a - f b - f b
(*) :: f a - f b - f a
-- Defined in `Control.Applicative'
instance Applicative [] -- Defined in `Control.Applicative'
instance Applicative ZipList -- Defined in `Control.Applicative'
instance Monad m = Applicative (WrappedMonad m)
-- Defined in `Control.Applicative'
instance Applicative Maybe -- Defined in `Control.Applicative'
instance Applicative IO -- Defined in `Control.Applicative'
instance Applicative (Either e) -- Defined in `Control.Applicative'
instance Applicative ((-) a) -- Defined in `Control.Applicative'
instance Applicative Mutator -- Defined in `Control.Lens.Internal'
instance Applicative (Bazaar a b)
-- Defined in `Control.Lens.Internal’

It does not show up, but I'm sure that there is an instance as the
operations seem to work! It turns out that the only way to find the
instance is to not only already know that there is one and
import the
appropriate module, but to also import the modules used in the
context.
But if I already knew all of this I wouldn't have asked GHCi.

Prelude Control.Applicative Control.Lens import Data.Monoid
Prelude Control.Applicative Control.Lens Data.Monoid :i Accessor
newtype Accessor r a
= Control.Lens.Internal.Accessor
{Control.Lens.Internal.__runAccessor :: r}
-- Defined in `Control.Lens.Internal'
instance Functor (Accessor r) -- Defined in `Control.Lens.Internal'
*instance Monoid r = Applicative (Accessor r)*

-- Defined in `Control.Lens.Internal'
instance Gettable (Accessor r)
-- Defined in `Control.Lens.Internal'

In contrast, with :info! we get everything that GHCi knows
about, so
it is quite easy to 

Re: Include a new boot library

2012-12-04 Thread Simon Marlow

On 03/12/12 17:30, Mattias Lundell wrote:

Hi,

I have spent a couple of hours this weekend trying to include an extra
boot library to GHC. My aim is to experiment with the LLVM FFI
bindings as code generator instead of the text representation.


Great!


Unfortunately I am stuck in the build process. I am able to build GHC
HEAD from git and I am able to build the LLVM FFI bindings. The
problem begins when the GHC's build process tries to build the LLVM
FFI bindings. I have separated the llvm-base library and put it into
the libraries directory of GHC, I have imported a module that is
exported from the llvm-base package, I have added llvm-base to the
files: 'compiler/ghc.cabal.in http://ghc.cabal.in/', 'packages' and
'ghc.mk http://ghc.mk/'.

But I am stuck with the message:

make[1]: *** No rule to make target `cbits/extra.cpp', needed by
`libraries/llvm-base/dist-install/build/libHSllvm-base-3.0.1.0.a'.  Stop.

This is my first time hacking on GHC and the build process is new to
me.  My question is if I have forgotten something or if the problem is
in llvm-base.


Is cbits/extra.cpp built from something else?  Does llvm-base have some 
custom Cabal stuff that the GHC build system doesn't know about, maybe?


Something you'll probably run into is that the build system doesn't have 
rules for building .cpp files (C++).  You can add these by cut and 
pasting from the .c rules, which can be found in 
rules/c-suffix-rules.mk.  I'm not sure whether the .cpp files will make 
it into the *_C_SRCS variable, if not there might be other changes 
needed.  Have a look in your libraries/llvm-base/dist-install/package.mk.


Cheers,
Simon


___
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc


pgj (x86 FreeBSD HEAD), build 878, Failure

2012-12-04 Thread Builder
pgj (x86 FreeBSD HEAD), build 878

Build failed
Details: http://darcs.haskell.org/ghcBuilder/builders/pgj/878.html

git clone| Success
create mk/build.mk   | Success
get subrepos | Success
repo versions| Success
touching clean-check files   | Success
setting version date | Success
booting  | Success
configuring  | Success
creating check-remove-before | Success
compiling| Success
creating check-remove-after  | Success
compiling testremove | Success
simulating clean | Success
checking clean   | Success
making bindist   | Success
publishing bindist   | Success
testing bindist  | Success
testing  | Failure: Just (ExitFailure 15)

Build failed
Details: http://darcs.haskell.org/ghcBuilder/builders/pgj/878.html

cd ./safeHaskell/flags  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -c SafeFlags19.hs
SafeFlags19.comp.stderr 21
= SafeFlags20(normal) 405 of 3504 [21, 16, 0]
cd ./safeHaskell/flags  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -c SafeFlags20.hs  -trust base  
SafeFlags20.comp.stderr 21
= SafeFlags21(normal) 406 of 3504 [21, 16, 0]
cd ./safeHaskell/flags  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -c SafeFlags21.hs
SafeFlags21.comp.stderr 21
= SafeFlags22(normal) 407 of 3504 [21, 16, 0]
cd ./safeHaskell/flags  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -c SafeFlags22.hs
SafeFlags22.comp.stderr 21
= SafeFlags23(normal) 408 of 3504 [21, 16, 0]
cd ./safeHaskell/flags  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -c SafeFlags23.hs
SafeFlags23.comp.stderr 21
= SafeFlags24(normal) 409 of 3504 [21, 16, 0]
cd ./safeHaskell/flags  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -c SafeFlags24.hs
SafeFlags24.comp.stderr 21
= SafeFlags25(normal) 410 of 3504 [21, 16, 0]
cd ./safeHaskell/flags  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -c SafeFlags25.hs
SafeFlags25.comp.stderr 21
= SafeFlags26(normal) 411 of 3504 [21, 16, 0]
cd ./safeHaskell/flags  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -c SafeFlags26.hs
SafeFlags26.comp.stderr 21
= SafeFlags27(normal) 412 of 3504 [21, 16, 0]
cd ./safeHaskell/flags  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -c SafeFlags27.hs
SafeFlags27.comp.stderr 21
= SafeFlags28(normal) 413 of 3504 [21, 16, 0]
cd ./safeHaskell/flags  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -c SafeFlags28.hs
SafeFlags28.comp.stderr 21
= SafeFlags29(normal) 414 of 3504 [21, 16, 0]
cd ./safeHaskell/flags  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -c SafeFlags29.hs
SafeFlags29.comp.stderr 21
= Flags01(normal) 415 of 3504 [21, 16, 0]
cd ./safeHaskell/flags  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -c Flags01.hs  -XSafe  
Flags01.comp.stderr 21
= Flags02(normal) 416 of 3504 [21, 16, 0]
cd ./safeHaskell/flags  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -c Flags02.hs  -XSafe  
Flags02.comp.stderr 21
= 

pgj-freebsd-i386-stable (x86 FreeBSD STABLE), build 741, Success

2012-12-04 Thread Builder
pgj-freebsd-i386-stable (x86 FreeBSD STABLE), build 741

Build succeeded
Details: 
http://darcs.haskell.org/ghcBuilder/builders/pgj-freebsd-i386-stable/741.html

git clone| Success
create mk/build.mk   | Success
get subrepos | Success
repo versions| Success
touching clean-check files   | Success
setting version date | Success
booting  | Success
configuring  | Success
creating check-remove-before | Success
compiling| Success
creating check-remove-after  | Success
compiling testremove | Success
simulating clean | Success
checking clean   | Success
making bindist   | Success
publishing bindist   | Success
testing bindist  | Success
testing  | Success
testsuite summary| Success

Build succeeded
Details: 
http://darcs.haskell.org/ghcBuilder/builders/pgj-freebsd-i386-stable/741.html

File not deleted:compiler/ghc.cabal.old
File not deleted:inplace
File not deleted:libraries/base/include/EventConfig.h
Deleted before file: libraries/time/include/HsTimeConfig.h
File not deleted:mk/config.mk.old
File not deleted:mk/project.mk.old
File not deleted:rts/libs.depend
File not deleted:rts/package.conf.inplace
File not deleted:rts/package.conf.inplace.raw

OVERALL SUMMARY for test run started at Tue Dec  4 08:50:27 UTC 2012
3402 total tests, which gave rise to
   14436 test cases, of which
  10 caused framework failures
   11364 were skipped

2957 expected passes
  48 had missing libraries
  34 expected failures
   5 unexpected passes
  28 unexpected failures

Unexpected passes:
   ../../libraries/unix/tests  getEnvironment01 (normal)
   ../../libraries/unix/tests  getEnvironment02 (normal)
   ../../libraries/unix/tests  getGroupEntryForName (normal)
   ../../libraries/unix/tests  getUserEntryForName (normal)
   ../../libraries/unix/tests  queryfdoption01 (normal)

Unexpected failures:
   ../../libraries/directory/tests  getPermissions001 [bad exit code] 
(normal)
   ../../libraries/process/testsprocess007 [bad stdout] (normal)
   ../../libraries/unix/tests/libposix  posix005 [bad stdout] (normal)
   driver   dynHelloWorld [bad exit code] (dyn)
   driver/recomp011 recomp011 [bad stdout] (normal)
   dynlibs  T3807 [bad exit code] (normal)
   dynlibs  T5373 [bad stdout] (normal)
   ghci/scripts T5979 [bad stderr] (ghci)
   perf/haddock haddock.Cabal [stat too good] (normal)
   perf/haddock haddock.base [stat too good] (normal)
   perf/haddock haddock.compiler [stat too good] 
(normal)
   plugins  plugins01 [bad exit code] (normal)
   plugins  plugins02 [stderr mismatch] (normal)
   plugins  plugins03 [stderr mismatch] (normal)
   rts  T2615 [bad stdout] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly01 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly02 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly03 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly04 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly05 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly06 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly07 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly08 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly09 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly10 [exit code non-0] (normal)
   safeHaskell/check/pkg01  safePkg01 [bad exit code] (normal)
   typecheck/should_failT5300 [stderr mismatch] (normal)
   typecheck/should_failT5691 [stderr mismatch] (normal)

___
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc


pgj-freebsd-amd64-stable (amd64 FreeBSD STABLE), build 753, Success

2012-12-04 Thread Builder
pgj-freebsd-amd64-stable (amd64 FreeBSD STABLE), build 753

Build succeeded
Details: 
http://darcs.haskell.org/ghcBuilder/builders/pgj-freebsd-amd64-stable/753.html

git clone| Success
create mk/build.mk   | Success
get subrepos | Success
repo versions| Success
touching clean-check files   | Success
setting version date | Success
booting  | Success
configuring  | Success
creating check-remove-before | Success
compiling| Success
creating check-remove-after  | Success
compiling testremove | Success
simulating clean | Success
checking clean   | Success
making bindist   | Success
publishing bindist   | Success
testing bindist  | Success
testing  | Success
testsuite summary| Success

Build succeeded
Details: 
http://darcs.haskell.org/ghcBuilder/builders/pgj-freebsd-amd64-stable/753.html

File not deleted:compiler/ghc.cabal.old
File not deleted:inplace
File not deleted:libraries/base/include/EventConfig.h
Deleted before file: libraries/time/include/HsTimeConfig.h
File not deleted:mk/config.mk.old
File not deleted:mk/project.mk.old
File not deleted:rts/libs.depend
File not deleted:rts/package.conf.inplace
File not deleted:rts/package.conf.inplace.raw

OVERALL SUMMARY for test run started at Tue Dec  4 09:48:51 UTC 2012
3402 total tests, which gave rise to
   14436 test cases, of which
  10 caused framework failures
   11363 were skipped

2961 expected passes
  48 had missing libraries
  35 expected failures
   0 unexpected passes
  29 unexpected failures

Unexpected failures:
   ../../libraries/directory/tests  getPermissions001 [bad exit code] 
(normal)
   ../../libraries/process/testsprocess007 [bad stdout] (normal)
   ../../libraries/unix/tests/libposix  posix005 [bad stdout] (normal)
   driver   dynHelloWorld [bad exit code] (dyn)
   driver/recomp011 recomp011 [bad stdout] (normal)
   dynlibs  T3807 [bad exit code] (normal)
   dynlibs  T5373 [bad stdout] (normal)
   ghci/scripts T5979 [bad stderr] (ghci)
   perf/compilerT6048 [stat not good enough] (optasm)
   perf/haddock haddock.Cabal [stat not good enough] 
(normal)
   perf/haddock haddock.base [stat not good enough] 
(normal)
   perf/haddock haddock.compiler [stat not good enough] 
(normal)
   plugins  plugins01 [bad exit code] (normal)
   plugins  plugins02 [stderr mismatch] (normal)
   plugins  plugins03 [stderr mismatch] (normal)
   rts  T2615 [bad stdout] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly01 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly02 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly03 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly04 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly05 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly06 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly07 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly08 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly09 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly10 [exit code non-0] (normal)
   safeHaskell/check/pkg01  safePkg01 [bad exit code] (normal)
   typecheck/should_failT5300 [stderr mismatch] (normal)
   typecheck/should_failT5691 [stderr mismatch] (normal)

___
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc


pgj2 (amd64 FreeBSD HEAD), build 881, Success

2012-12-04 Thread Builder
pgj2 (amd64 FreeBSD HEAD), build 881

Build succeeded
Details: http://darcs.haskell.org/ghcBuilder/builders/pgj2/881.html

git clone| Success
create mk/build.mk   | Success
get subrepos | Success
repo versions| Success
touching clean-check files   | Success
setting version date | Success
booting  | Success
configuring  | Success
creating check-remove-before | Success
compiling| Success
creating check-remove-after  | Success
compiling testremove | Success
simulating clean | Success
checking clean   | Success
making bindist   | Success
publishing bindist   | Success
testing bindist  | Success
testing  | Success
testsuite summary| Success

Build succeeded
Details: http://darcs.haskell.org/ghcBuilder/builders/pgj2/881.html

File not deleted:compiler/ghc.cabal.old
File not deleted:includes/dist-derivedconstants
File not deleted:includes/dist-derivedconstants/header
File not deleted:includes/dist-derivedconstants/header/DerivedConstants.h
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellExports.hs
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellType.hs
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellWrappers.hs
File not deleted:includes/dist-derivedconstants/header/platformConstants
File not deleted:includes/dist-derivedconstants/header/tmp.c
File not deleted:includes/dist-derivedconstants/header/tmp.o
File not deleted:inplace
File not deleted:libraries/base/include/EventConfig.h
File not deleted:mk/config.mk.old
File not deleted:mk/project.mk.old
File not deleted:rts/libs.depend
File not deleted:rts/package.conf.inplace
File not deleted:rts/package.conf.inplace.raw

OVERALL SUMMARY for test run started at Tue Dec  4 09:49:52 UTC 2012
3504 total tests, which gave rise to
   11674 test cases, of which
   0 caused framework failures
8508 were skipped

2863 expected passes
  26 had missing libraries
  36 expected failures
  22 unexpected passes
 219 unexpected failures

Unexpected passes:
   codeGen/should_runT7319 (prof)
   profiling/should_compile  2410 (normal)
   profiling/should_compile  prof001 (normal)
   profiling/should_compile  prof002 (normal)
   profiling/should_run  5314 (prof)
   profiling/should_run  T2552 (prof)
   profiling/should_run  T3001 (prof_hb)
   profiling/should_run  T3001-2 (prof_hb)
   profiling/should_run  T5363 (prof)
   profiling/should_run  T5559 (prof)
   profiling/should_run  T680 (prof)
   profiling/should_run  T949 (prof)
   profiling/should_run  callstack001 (prof)
   profiling/should_run  callstack002 (prof)
   profiling/should_run  heapprof001 (prof)
   profiling/should_run  prof-doc-fib (prof)
   profiling/should_run  prof-doc-last (prof)
   profiling/should_run  profinline001 (prof)
   profiling/should_run  scc001 (prof)
   profiling/should_run  scc002 (prof)
   profiling/should_run  scc003 (prof)
   stranal/should_compilenewtype (optasm)

Unexpected failures:
   ../../libraries/base/tests/IO3307 [bad stderr] (normal)
   ../../libraries/base/tests/IOenvironment001 [bad stderr] (normal)
   ../../libraries/directory/tests  getPermissions001 [bad exit code] 
(normal)
   ../../libraries/hpc/tests/ghc_ghci   hpc_ghc_ghci [bad stderr] (normal)
   ../../libraries/process/testsprocess007 [bad stdout] (normal)
   ../../libraries/process/testsprocess009 [bad stdout] (normal)
   ../../libraries/unix/tests   fdReadBuf001 [bad exit code] (ghci)
   ../../libraries/unix/tests/libposix  posix005 [bad stdout] (normal)
   cabal1750 [bad stderr] (normal)
   cabalghcpkg01 [bad stderr] (normal)
   cabalghcpkg03 [bad stderr] (normal)
   cabalghcpkg05 [bad stderr] (normal)
   cabalghcpkg06 [bad stderr] (normal)
   cabalshadow [bad stderr] (normal)
   cabal/cabal01cabal01 [bad stderr] (normal)
   cabal/cabal04cabal04 [bad stderr] (normal)
   codeGen/should_compile   2578 [bad stderr] (normal)
   codeGen/should_run   cgrun068 [exit code non-0] (normal)
   deSugar/should_compile   T5252 [bad stderr] (normal)
   deSugar/should_compile   T5252Take2 [bad stderr] (normal)
   deriving/should_fail drvfail016 [bad stderr] (normal)
   driver   2566 [bad stderr] (normal)
   driver   T3364 [bad stderr] (normal)
   driver   

[commit: ghc] master: Fix pprPanic so that it doesn't throw away the SDoc part of the error. (e6ce335)

2012-12-04 Thread Erik de Castro
Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/e6ce335e8e3ba0718efd234910185e4257424562

---

commit e6ce335e8e3ba0718efd234910185e4257424562
Author: Erik de Castro Lopo er...@mega-nerd.com
Date:   Mon Dec 3 12:28:39 2012 +1100

Fix pprPanic so that it doesn't throw away the SDoc part of the error.

---

 compiler/utils/Outputable.lhs |3 ++-
 1 files changed, 2 insertions(+), 1 deletions(-)

diff --git a/compiler/utils/Outputable.lhs b/compiler/utils/Outputable.lhs
index ad0b9d7..362cd1a 100644
--- a/compiler/utils/Outputable.lhs
+++ b/compiler/utils/Outputable.lhs
@@ -898,7 +898,8 @@ plural _   = char 's'
 
 pprPanic :: String - SDoc - a
 -- ^ Throw an exception saying bug in GHC
-pprPanic= panicDoc
+pprPanic s doc
+ = throwGhcException (Panic (s ++ \n ++ showSDoc unsafeGlobalDynFlags doc))
 
 pprSorry :: String - SDoc - a
 -- ^ Throw an exception saying this isn't finished yet



___
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc


[commit: ghc] master: Revert Fix pprPanic so that it doesn't throw away the SDoc part of the error. (50905e1)

2012-12-04 Thread Ian Lynagh
Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/50905e1abeee21a5006f9c4e5a54654acff0542e

---

commit 50905e1abeee21a5006f9c4e5a54654acff0542e
Author: Ian Lynagh i...@well-typed.com
Date:   Tue Dec 4 19:36:49 2012 +

Revert Fix pprPanic so that it doesn't throw away the SDoc part of the 
error.

This reverts commit e6ce335e8e3ba0718efd234910185e4257424562.

pprPanic doesn't throw the Doc away: It gets passed in the PprPanic
constructor.

---

 compiler/utils/Outputable.lhs |3 +--
 1 files changed, 1 insertions(+), 2 deletions(-)

diff --git a/compiler/utils/Outputable.lhs b/compiler/utils/Outputable.lhs
index 362cd1a..ad0b9d7 100644
--- a/compiler/utils/Outputable.lhs
+++ b/compiler/utils/Outputable.lhs
@@ -898,8 +898,7 @@ plural _   = char 's'
 
 pprPanic :: String - SDoc - a
 -- ^ Throw an exception saying bug in GHC
-pprPanic s doc
- = throwGhcException (Panic (s ++ \n ++ showSDoc unsafeGlobalDynFlags doc))
+pprPanic= panicDoc
 
 pprSorry :: String - SDoc - a
 -- ^ Throw an exception saying this isn't finished yet



___
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc


[commit: ghc] master: Rearrange configure.ac a bit (70c4e4b)

2012-12-04 Thread Ian Lynagh
Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/70c4e4bbc56a697ad7d13e87875fe62f80956e16

---

commit 70c4e4bbc56a697ad7d13e87875fe62f80956e16
Author: Ian Lynagh ig...@earth.li
Date:   Tue Dec 4 15:12:11 2012 +

Rearrange configure.ac a bit

Anything that uses gcc needs to happen after we've made the mingw
inplace tree on Windows.

---

 configure.ac |  118 +-
 1 files changed, 59 insertions(+), 59 deletions(-)

diff --git a/configure.ac b/configure.ac
index e5841ed..de2fd03 100644
--- a/configure.ac
+++ b/configure.ac
@@ -86,62 +86,6 @@ AC_ARG_WITH([ghc],
   fi
   WithGhc=$GHC])
 
-# system libffi
-
-AC_ARG_WITH([system-libffi],
-[AC_HELP_STRING([--with-system-libffi],
-  [Use system provided libffi for RTS [default=no]])
-])
-
-AS_IF([test x$with_system_libffi = xyes],
-  [UseSystemLibFFI=YES], [UseSystemLibFFI=NO]
-)
-
-
-AC_SUBST(UseSystemLibFFI)
-
-AC_ARG_WITH([ffi-includes],
-[AC_HELP_STRING([--with-ffi-includes=ARG]
-  [Find includes for libffi in ARG [default=system default]])
-],
-[
- if test x$UseSystemLibFFI != xYES; then
-AC_MSG_WARN([--with-ffi-includes will be ignored, --with-system-libffi not 
set])
- else
-FFIIncludeDir=$withval
-LIBFFI_CFLAGS=-I $withval 
- fi
-])
-
-AC_SUBST(FFIIncludeDir)
-
-AC_ARG_WITH([ffi-libraries],
-[AC_HELP_STRING([--with-ffi-libraries=ARG]
-  [Find libffi in ARG [default=system default]])
-],
-[
- if test x$UseSystemLibFFI != xYES; then
-AC_MSG_WARN([--with-ffi-libraries will be ignored, --with-system-libffi 
not set])
- else
-FFILibDir=$withval LIBFFI_LDFLAGS=-L$withval
- fi
-])
-
-AC_SUBST(FFILibDir)
-
-AS_IF([test $UseSystemLibFFI = YES], [
- CFLAGS2=$CFLAGS
- CFLAGS=$LIBFFI_CFLAGS $CFLAGS
- LDFLAGS2=$LDFLAGS
- LDFLAGS=$LIBFFI_LDFLAGS $LDFLAGS
- AC_CHECK_LIB(ffi, ffi_call,
-  [AC_CHECK_HEADERS([ffi.h], [break], [])
-   AC_DEFINE([HAVE_LIBFFI], [1], [Define to 1 if you have libffi.])],
-  [AC_MSG_ERROR([Cannot find system libffi])])
- CFLAGS=$CFLAGS2
- LDFLAGS=$LDFLAGS2
-])
-
 dnl ** Tell the make system which OS we are using
 dnl $OSTYPE is set by the operating system to msys or cygwin or something 
 AC_SUBST(OSTYPE)
@@ -241,9 +185,6 @@ AC_SUBST([WithGhc])
 dnl ** Without optimization some INLINE trickery fails for GHCi
 SRC_CC_OPTS=-O
 
-FP_ICONV
-FP_GMP
-
 dnl
 dnl * Choose host(/target/build) platform
 dnl
@@ -428,6 +369,65 @@ then
 fi
 fi
 
+# system libffi
+
+AC_ARG_WITH([system-libffi],
+[AC_HELP_STRING([--with-system-libffi],
+  [Use system provided libffi for RTS [default=no]])
+])
+
+AS_IF([test x$with_system_libffi = xyes],
+  [UseSystemLibFFI=YES], [UseSystemLibFFI=NO]
+)
+
+
+AC_SUBST(UseSystemLibFFI)
+
+AC_ARG_WITH([ffi-includes],
+[AC_HELP_STRING([--with-ffi-includes=ARG]
+  [Find includes for libffi in ARG [default=system default]])
+],
+[
+ if test x$UseSystemLibFFI != xYES; then
+AC_MSG_WARN([--with-ffi-includes will be ignored, --with-system-libffi not 
set])
+ else
+FFIIncludeDir=$withval
+LIBFFI_CFLAGS=-I $withval 
+ fi
+])
+
+AC_SUBST(FFIIncludeDir)
+
+AC_ARG_WITH([ffi-libraries],
+[AC_HELP_STRING([--with-ffi-libraries=ARG]
+  [Find libffi in ARG [default=system default]])
+],
+[
+ if test x$UseSystemLibFFI != xYES; then
+AC_MSG_WARN([--with-ffi-libraries will be ignored, --with-system-libffi 
not set])
+ else
+FFILibDir=$withval LIBFFI_LDFLAGS=-L$withval
+ fi
+])
+
+AC_SUBST(FFILibDir)
+
+AS_IF([test $UseSystemLibFFI = YES], [
+ CFLAGS2=$CFLAGS
+ CFLAGS=$LIBFFI_CFLAGS $CFLAGS
+ LDFLAGS2=$LDFLAGS
+ LDFLAGS=$LIBFFI_LDFLAGS $LDFLAGS
+ AC_CHECK_LIB(ffi, ffi_call,
+  [AC_CHECK_HEADERS([ffi.h], [break], [])
+   AC_DEFINE([HAVE_LIBFFI], [1], [Define to 1 if you have libffi.])],
+  [AC_MSG_ERROR([Cannot find system libffi])])
+ CFLAGS=$CFLAGS2
+ LDFLAGS=$LDFLAGS2
+])
+
+FP_ICONV
+FP_GMP
+
 XCODE_VERSION()
 
 SplitObjsBroken=NO



___
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc


Re: [commit: ghc] master: Fix pprPanic so that it doesn't throw away the SDoc part of the error. (e6ce335)

2012-12-04 Thread Ian Lynagh

Hi Erik,

On Tue, Dec 04, 2012 at 03:55:21AM -0800, Erik de Castro wrote:
 
 Fix pprPanic so that it doesn't throw away the SDoc part of the error.

I've reverted this: the Doc is passed in the PanicDoc constructor, so it
shouldn't be necessary.

What problem were you trying to solve?


Thanks
Ian


___
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc


[nightly] 04-Dec-2012 build of HEAD (unreg) on x86_64-unknown-linux (cam-04-unx)

2012-12-04 Thread GHC Build Reports
Build description = HEAD (unreg) on x86_64-unknown-linux (cam-04-unx)
Build location= /64playpen/simonmar/nightly/HEAD-unreg-cam-04-unx
Build config file = /home/simonmar/nightly/site/msrc/conf-HEAD-unreg-cam-04-unx

Nightly build started on cam-04-unx at Tue Dec 4 18:20:01 GMT 2012.
 checking out new source tree ... warning: libraries/xhtml 
already present; omitting
Submodule 'libraries/Cabal' (http://darcs.haskell.org/libraries/Cabal.git/) 
registered for path 'libraries/Cabal'
Submodule 'libraries/Win32' (http://darcs.haskell.org/libraries/Win32.git/) 
registered for path 'libraries/Win32'
Submodule 'libraries/binary' (http://darcs.haskell.org/libraries/binary.git/) 
registered for path 'libraries/binary'
Submodule 'libraries/bytestring' 
(http://darcs.haskell.org/libraries/bytestring.git/) registered for path 
'libraries/bytestring'
Submodule 'libraries/containers' 
(http://darcs.haskell.org/libraries/containers.git/) registered for path 
'libraries/containers'
Submodule 'libraries/haskeline' 
(http://darcs.haskell.org/libraries/haskeline.git/) registered for path 
'libraries/haskeline'
Submodule 'libraries/pretty' (http://darcs.haskell.org/libraries/pretty.git/) 
registered for path 'libraries/pretty'
Submodule 'libraries/primitive' 
(http://darcs.haskell.org/libraries/primitive.git/) registered for path 
'libraries/primitive'
Submodule 'libraries/terminfo' 
(http://darcs.haskell.org/libraries/terminfo.git/) registered for path 
'libraries/terminfo'
Submodule 'libraries/time' (http://darcs.haskell.org/libraries/time.git/) 
registered for path 'libraries/time'
Submodule 'libraries/transformers' 
(http://darcs.haskell.org/libraries/transformers.git/) registered for path 
'libraries/transformers'
Submodule 'libraries/vector' (http://darcs.haskell.org/libraries/vector.git/) 
registered for path 'libraries/vector'
Submodule 'libraries/xhtml' (http://darcs.haskell.org/libraries/xhtml.git/) 
registered for path 'libraries/xhtml'
Cloning into 'libraries/Cabal'...
Submodule path 'libraries/Cabal': checked out 
'4b43bd95753e5f3e29d7bfbe6bba8477715ac296'
Cloning into 'libraries/Win32'...
Submodule path 'libraries/Win32': checked out 
'21335a30161c099da79ae9619c9782e5e32e4644'
Cloning into 'libraries/binary'...
Submodule path 'libraries/binary': checked out 
'2d31cea238d0d08885c457475fc354dbf2b88976'
Cloning into 'libraries/bytestring'...
Submodule path 'libraries/bytestring': checked out 
'6bd69fe27af33e878e38f4c579983f6a23120a87'
Cloning into 'libraries/containers'...
Submodule path 'libraries/containers': checked out 
'a9b7224068ae60f73baacd5f76d2c27624d90120'
Cloning into 'libraries/haskeline'...
Submodule path 'libraries/haskeline': checked out 
'6ee5fc8ccdee410486a826cadfb2a0a560d60506'
Cloning into 'libraries/pretty'...
Submodule path 'libraries/pretty': checked out 
'ab7e8d91470bb94c9e184dffbec89d0aae116f9b'
Cloning into 'libraries/primitive'...
Submodule path 'libraries/primitive': checked out 
'75c3379b6d76e914cc3c7ffd290b6b1cad7ea3e6'
Cloning into 'libraries/terminfo'...
Submodule path 'libraries/terminfo': checked out 
'579d2c324e69856ff8d1ea8b5036e30c920e1973'
Cloning into 'libraries/time'...
Submodule path 'libraries/time': checked out 
'c98806fe0c9cde7371452ec30fa2900d28d16b16'
Cloning into 'libraries/transformers'...
Submodule path 'libraries/transformers': checked out 
'a59fb93860f84ccd44178dcbbb82cfea7e02cd07'
Cloning into 'libraries/vector'...
Submodule path 'libraries/vector': checked out 
'c4c5a740ec977a4300449bc85f4707ec641be923'
Cloning into 'libraries/xhtml'...
Submodule path 'libraries/xhtml': checked out 
'fb9e0bbb69e15873682a9f25d39652099a3ccac1'
ok.
 Building stage 1 compiler... ok.
GHC Version 7.7
 Building stage 2 compiler... failed; relevant barfage 
is below.
 building testsuite tools ... failed.
 running nofib (-rtsopts -O2) ... ok.
-
Respository hashes:
.|e6ce335e8e3ba0718efd234910185e4257424562
ghc-tarballs|18e0c37f8023abf469af991e2fc2d3b024319c27
libraries/array|442ff7744fb51004c5358ec626e704f4536e3d6c
libraries/base|afb81977555a74a95de161b33e154f5cb61fab40
libraries/deepseq|420507ea418db8664a79aedaa6588b772e8c97c6
libraries/directory|2fcd7016ed71c3fdbce658ab973c3ce5aa217d76
libraries/dph|8d151264dbd8032eea7e46cb320d8e2ddd51abac
libraries/filepath|abf31a9aef45d2119a5757dafbe4adf611388ee8
libraries/ghc-prim|c2ed4a8ecffcfd8df09991e8639f665a63af069d
libraries/haskell2010|71bea78ccdbcd8bb8095dee2ebab8423e19ca959
libraries/haskell98|df1846099be1a7220e7d46aef167403eed53ebe5
libraries/hoopl|8e0ef3b7bf6d25919209f74d65c4a77c6689934d
libraries/hpc|02d402f04b2af44dd95340f1d64e81a3fcac049d
libraries/integer-gmp|a8c9be6c0a7fc56201c54c49d965c32f22b2bea8
libraries/integer-simple|30c4af5165f181ef4f089b3d245371230f0aafad
libraries/old-locale|df98c76b078de507ba2f7f23d4473c0ea09d5686

Re: [commit: ghc] master: Fix pprPanic so that it doesn't throw away the SDoc part of the error. (e6ce335)

2012-12-04 Thread Erik de Castro Lopo
Ian Lynagh wrote:

 I've reverted this: the Doc is passed in the PanicDoc constructor, so it
 shouldn't be necessary.
 
 What problem were you trying to solve?

Well, pprPanic is defined as:

pprPanic :: String - SDoc - a
-- ^ Throw an exception saying bug in GHC
pprPanic= panicDoc

and panicDoc is defined as:

panicDoc :: String - SDoc - a
panicDocx doc = throwGhcException (PprPanicx doc)

when the exception is throw it ends up in showGhcException which drops
the SDoc part of the message on the floor:

PprPanic  s _ -
showGhcException (Panic (s ++ \ndetails unavailable))

I tried to convert the SDoc to a String in this code, but that resulted
in a circular import. The obvious solution was the one in my patch.

Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/

___
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc


Re: [commit: ghc] master: Fix pprPanic so that it doesn't throw away the SDoc part of the error. (e6ce335)

2012-12-04 Thread Ian Lynagh
On Wed, Dec 05, 2012 at 08:12:59AM +1100, Erik de Castro Lopo wrote:
 
 when the exception is throw it ends up in showGhcException which drops
 the SDoc part of the message on the floor:
 
 PprPanic  s _ -
 showGhcException (Panic (s ++ \ndetails unavailable))

It's meant to end up in prettyPrintGhcErrors (called by main' in
ghc/Main.hs). Perhaps we need a second call to prettyPrintGhcErrors
earlier, using dflags0?


Thanks
Ian
-- 
Ian Lynagh, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/

___
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc


[commit: nofib] master: Add new imaginary nofib benchmark kahan (14bccff)

2012-12-04 Thread Johan Tibell
Repository : ssh://darcs.haskell.org//srv/darcs/nofib

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/14bccff2c547c0e06fe8f98607b9cf18890ef051

---

commit 14bccff2c547c0e06fe8f98607b9cf18890ef051
Author: Johan Tibell johan.tib...@gmail.com
Date:   Thu Nov 29 19:29:09 2012 -0800

Add new imaginary nofib benchmark kahan

The benchmark implements the Kahan summation algorithm and tests unboxed
arrays and floating point arithmetic in tight loops.

 .gitignore |1 +
 imaginary/Makefile |2 +-
 imaginary/kahan/Main.hs|   53 
 {gc/mutstore1 = imaginary/kahan}/Makefile |7 ++--
 imaginary/kahan/kahan.faststdout   |1 +
 imaginary/kahan/kahan.slowstdout   |1 +
 imaginary/kahan/kahan.stdout   |1 +
 7 files changed, 61 insertions(+), 5 deletions(-)


Diff suppressed because of size. To see it, use:

git show 14bccff2c547c0e06fe8f98607b9cf18890ef051

___
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc


am-deb7-64 (HEAD), build 259, Success

2012-12-04 Thread Builder
am-deb7-64 (HEAD), build 259

Build succeeded
Details: http://darcs.haskell.org/ghcBuilder/builders/am-deb7-64/259.html

git clone| Success
create mk/build.mk   | Success
get subrepos | Success
repo versions| Success
touching clean-check files   | Success
setting version date | Success
booting  | Success
configuring  | Success
creating check-remove-before | Success
compiling| Success
creating check-remove-after  | Success
compiling testremove | Success
simulating clean | Success
checking clean   | Success
making bindist   | Success
testing bindist  | Success
testing  | Success
testsuite summary| Success

Build succeeded
Details: http://darcs.haskell.org/ghcBuilder/builders/am-deb7-64/259.html

File not deleted:compiler/ghc.cabal.old
File not deleted:includes/dist-derivedconstants
File not deleted:includes/dist-derivedconstants/header
File not deleted:includes/dist-derivedconstants/header/DerivedConstants.h
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellExports.hs
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellType.hs
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellWrappers.hs
File not deleted:includes/dist-derivedconstants/header/platformConstants
File not deleted:includes/dist-derivedconstants/header/tmp.c
File not deleted:includes/dist-derivedconstants/header/tmp.o
File not deleted:inplace
File not deleted:libraries/base/include/EventConfig.h
File not deleted:mk/config.mk.old
File not deleted:mk/project.mk.old
File not deleted:rts/libs.depend
File not deleted:rts/package.conf.inplace
File not deleted:rts/package.conf.inplace.raw

OVERALL SUMMARY for test run started at Sun Dec  2 02:11:30 MSK 2012
3504 total tests, which gave rise to
   11674 test cases, of which
   0 caused framework failures
8505 were skipped

3078 expected passes
  26 had missing libraries
  35 expected failures
  23 unexpected passes
   7 unexpected failures

Unexpected passes:
   codeGen/should_runT7319 (prof)
   profiling/should_compile  2410 (normal)
   profiling/should_compile  prof001 (normal)
   profiling/should_compile  prof002 (normal)
   profiling/should_run  5314 (prof)
   profiling/should_run  T2552 (prof)
   profiling/should_run  T3001 (prof_hb)
   profiling/should_run  T3001-2 (prof_hb)
   profiling/should_run  T5363 (prof)
   profiling/should_run  T5559 (prof)
   profiling/should_run  T680 (prof)
   profiling/should_run  T949 (prof)
   profiling/should_run  callstack001 (prof)
   profiling/should_run  callstack002 (prof)
   profiling/should_run  heapprof001 (prof)
   profiling/should_run  prof-doc-fib (prof)
   profiling/should_run  prof-doc-last (prof)
   profiling/should_run  profinline001 (prof)
   profiling/should_run  scc001 (prof)
   profiling/should_run  scc002 (prof)
   profiling/should_run  scc003 (prof)
   stranal/should_compilenewtype (optasm)
   thTH_spliceE5_prof (normal)

Unexpected failures:
   codeGen/should_run cgrun068 [exit code non-0] (normal)
   ghci/scripts   T5979 [bad stderr] (ghci)
   perf/compiler  T1969 [stat not good enough] (normal)
   perf/haddock   haddock.Cabal [stat not good enough] (normal)
   perf/haddock   haddock.base [stat not good enough] (normal)
   typecheck/should_fail  T5300 [stderr mismatch] (normal)
   typecheck/should_fail  T5691 [stderr mismatch] (normal)

___
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc


[nightly] 04-Dec-2012 build of STABLE on x86_64-unknown-linux (cam-04-unx)

2012-12-04 Thread GHC Build Reports
Build description = STABLE on x86_64-unknown-linux (cam-04-unx)
Build location= /64playpen/simonmar/nightly/STABLE-cam-04-unx
Build config file = /home/simonmar/nightly/site/msrc/conf-STABLE-cam-04-unx

Nightly build started on cam-04-unx at Tue Dec 4 18:10:01 GMT 2012.
 checking out new source tree ... warning: Remote branch 
ghc-7.6 not found in upstream origin, using HEAD instead
ok.
 Building stage 1 compiler... ok.
GHC Version 7.6.1.20121203
 Building stage 2 compiler... ok.
 Building stage 3 compiler... ok.
 building source distribution ... ok.
 uploading source distribution... ok.
 building testsuite tools ... ok.
 running tests... ok (summary below).
 building compiler binary distribution... ok.
 uploading binary distribution... ok.
 running nofib (-rtsopts -O2) ... ok.
 running nofib (-rtsopts -O2 -fllvm)  ... ok.
 running nofib (-rtsopts -O2 -prof -auto-all -static)... ok.
 running nofib (-rtsopts -O2 -prof -auto-all -fllvm -static)... ok.
 publishing logs  ... Write failed: Broken pipe
lost connection
failed.
Logs  are at http://www.haskell.org/ghc/dist/stable/logs
Dists are at http://www.haskell.org/ghc/dist/stable/dist
Docs  are at http://www.haskell.org/ghc/dist/stable/docs
-
Respository hashes:
.|b637a24dbb471d99887e5544037a2abe10af26ee
ghc-tarballs|18e0c37f8023abf469af991e2fc2d3b024319c27
libraries/Cabal|e7e7ce1029707a67d26e6dc29de11141734898e3
libraries/Win32|e13098aecd0489399435dbf8643e1db2272e1e02
libraries/array|8dcd15240a9c2ba142fcbd31f597b51cf2f560bf
libraries/base|066fb9edecb3f293dbab36b87317100722a3c57c
libraries/binary|2d31cea238d0d08885c457475fc354dbf2b88976
libraries/bytestring|65e40bdf5b3a2484b36221a71b054e4400361a5f
libraries/containers|a9b7224068ae60f73baacd5f76d2c27624d90120
libraries/deepseq|4821349305c2a73efacdd58d2ba485b07eb84eda
libraries/directory|ef17afe1bd44ae10ef413146e5ade8867cb05625
libraries/filepath|2d60d0dd5d8fc924420bb238902266929f4e2cfb
libraries/ghc-prim|03144fbee792555bfd6de6184228ebaeffed2896
libraries/haskeline|f4040ab5831866c260e03fc8601edf7e1ed77049
libraries/haskell2010|d7e33da36585c250cd0bfb45b518c95e44197f3c
libraries/haskell98|c5a0db5eb4ce6a3736bf4f5caac3ff465b3dbaf9
libraries/hoopl|293d339303097641e7f14a1c0365a3801a87918d
libraries/hpc|c1b783dbbb0ab917208655c53a0af5c7538c2a0b
libraries/integer-gmp|2d9eca147f5c8b6f390eca15e03b315f67f2df01
libraries/integer-simple|47737f6f16d891b743a3d02b0a016100fd3a36d1
libraries/old-locale|47542432234f6fc406a9abf5d3f94e43d9bd10f6
libraries/old-time|cf225c367e5490201a5b04b1b8cb322f6e230d46
libraries/pretty|0a22cc0b3a4f8db876c4019013a30bfd1c0dd9a2
libraries/process|0ab69a65edae8c1a34ecee3a97b3839c833985f2
libraries/template-haskell|db0b4de55926b0bc98717c92ba543bcf9b89d024
libraries/terminfo|579d2c324e69856ff8d1ea8b5036e30c920e1973
libraries/transformers|a59fb93860f84ccd44178dcbbb82cfea7e02cd07
libraries/unix|b95a003b20436863ef2f5fc01e6cd77f5bef94a0
libraries/utf8-string|73ca1b9def3f350ad28e55fcba077e6be3b67e93
libraries/xhtml|fb9e0bbb69e15873682a9f25d39652099a3ccac1
nofib|f0082fddac1f13c5d032c230f8cdff94bf163ef0
testsuite|c96a151e2e48092efe58bfb2ba11aad428480b27
utils/haddock|1d480b49a2d9098993889ca29dd82ef228ae5c0d
utils/hsc2hs|67b8c663216690150b6f762e09b32ebbe6334ddd
-
All done!
Nightly build finished successfully at Wed Dec 5 01:30:42 GMT 2012

- GHC Test summary -

OVERALL SUMMARY for test run started at Tue Dec  4 21:35:43 GMT 2012
3402 total tests, which gave rise to
   16613 test cases, of which
  10 caused framework failures
3563 were skipped

   12537 expected passes
 367 had missing libraries
 131 expected failures
   0 unexpected passes
  15 unexpected failures

Unexpected failures:
   perf/compilerT6048 [stat not good enough] (optasm)
   perf/haddock haddock.Cabal [stat not good enough] (normal)
   perf/haddock haddock.base [stat not good enough] (normal)
   perf/haddock haddock.compiler [stat not good enough] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly01 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly02 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly03 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly04 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly05 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly06 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly07 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly08 [stderr mismatch] 

[nightly] 04-Dec-2012 build of HEAD on x86_64-unknown-linux (cam-04-unx)

2012-12-04 Thread GHC Build Reports
Build description = HEAD on x86_64-unknown-linux (cam-04-unx)
Build location= /64playpen/simonmar/nightly/HEAD-cam-04-unx
Build config file = /home/simonmar/nightly/site/msrc/conf-HEAD-cam-04-unx

Nightly build started on cam-04-unx at Tue Dec 4 18:00:02 GMT 2012.
 checking out new source tree ... warning: libraries/xhtml 
already present; omitting
Submodule 'libraries/Cabal' (http://darcs.haskell.org/libraries/Cabal.git/) 
registered for path 'libraries/Cabal'
Submodule 'libraries/Win32' (http://darcs.haskell.org/libraries/Win32.git/) 
registered for path 'libraries/Win32'
Submodule 'libraries/binary' (http://darcs.haskell.org/libraries/binary.git/) 
registered for path 'libraries/binary'
Submodule 'libraries/bytestring' 
(http://darcs.haskell.org/libraries/bytestring.git/) registered for path 
'libraries/bytestring'
Submodule 'libraries/containers' 
(http://darcs.haskell.org/libraries/containers.git/) registered for path 
'libraries/containers'
Submodule 'libraries/haskeline' 
(http://darcs.haskell.org/libraries/haskeline.git/) registered for path 
'libraries/haskeline'
Submodule 'libraries/pretty' (http://darcs.haskell.org/libraries/pretty.git/) 
registered for path 'libraries/pretty'
Submodule 'libraries/primitive' 
(http://darcs.haskell.org/libraries/primitive.git/) registered for path 
'libraries/primitive'
Submodule 'libraries/terminfo' 
(http://darcs.haskell.org/libraries/terminfo.git/) registered for path 
'libraries/terminfo'
Submodule 'libraries/time' (http://darcs.haskell.org/libraries/time.git/) 
registered for path 'libraries/time'
Submodule 'libraries/transformers' 
(http://darcs.haskell.org/libraries/transformers.git/) registered for path 
'libraries/transformers'
Submodule 'libraries/vector' (http://darcs.haskell.org/libraries/vector.git/) 
registered for path 'libraries/vector'
Submodule 'libraries/xhtml' (http://darcs.haskell.org/libraries/xhtml.git/) 
registered for path 'libraries/xhtml'
Cloning into 'libraries/Cabal'...
Submodule path 'libraries/Cabal': checked out 
'4b43bd95753e5f3e29d7bfbe6bba8477715ac296'
Cloning into 'libraries/Win32'...
Submodule path 'libraries/Win32': checked out 
'21335a30161c099da79ae9619c9782e5e32e4644'
Cloning into 'libraries/binary'...
Submodule path 'libraries/binary': checked out 
'2d31cea238d0d08885c457475fc354dbf2b88976'
Cloning into 'libraries/bytestring'...
Submodule path 'libraries/bytestring': checked out 
'6bd69fe27af33e878e38f4c579983f6a23120a87'
Cloning into 'libraries/containers'...
Submodule path 'libraries/containers': checked out 
'a9b7224068ae60f73baacd5f76d2c27624d90120'
Cloning into 'libraries/haskeline'...
Submodule path 'libraries/haskeline': checked out 
'6ee5fc8ccdee410486a826cadfb2a0a560d60506'
Cloning into 'libraries/pretty'...
Submodule path 'libraries/pretty': checked out 
'ab7e8d91470bb94c9e184dffbec89d0aae116f9b'
Cloning into 'libraries/primitive'...
Submodule path 'libraries/primitive': checked out 
'75c3379b6d76e914cc3c7ffd290b6b1cad7ea3e6'
Cloning into 'libraries/terminfo'...
Submodule path 'libraries/terminfo': checked out 
'579d2c324e69856ff8d1ea8b5036e30c920e1973'
Cloning into 'libraries/time'...
Submodule path 'libraries/time': checked out 
'c98806fe0c9cde7371452ec30fa2900d28d16b16'
Cloning into 'libraries/transformers'...
Submodule path 'libraries/transformers': checked out 
'a59fb93860f84ccd44178dcbbb82cfea7e02cd07'
Cloning into 'libraries/vector'...
Submodule path 'libraries/vector': checked out 
'c4c5a740ec977a4300449bc85f4707ec641be923'
Cloning into 'libraries/xhtml'...
Submodule path 'libraries/xhtml': checked out 
'fb9e0bbb69e15873682a9f25d39652099a3ccac1'
ok.
 Building stage 1 compiler... ok.
GHC Version 7.7.20121204
 Building stage 2 compiler... ok.
 Building stage 3 compiler... ok.
 building source distribution ... ok.
 uploading source distribution... ok.
 building testsuite tools ... ok.
 running tests... ok (summary below).
 building compiler binary distribution... ok.
 uploading binary distribution... ok.
 running nofib (-rtsopts -O2) ... ok.
 running nofib (-rtsopts -O2 -fllvm)  ... ok.
 running nofib (-rtsopts -O2 -prof -auto-all -static)... ok.
 running nofib (-rtsopts -O2 -prof -auto-all -fllvm -static)... ok.
 publishing logs  ... ok.
Logs  are at http://www.haskell.org/ghc/dist/current/logs
Dists are at http://www.haskell.org/ghc/dist/current/dist
Docs  are at http://www.haskell.org/ghc/dist/current/docs
-
Respository hashes:
.|e6ce335e8e3ba0718efd234910185e4257424562
ghc-tarballs|18e0c37f8023abf469af991e2fc2d3b024319c27
libraries/array|442ff7744fb51004c5358ec626e704f4536e3d6c
libraries/base|afb81977555a74a95de161b33e154f5cb61fab40

tn23 (x86 OSX HEAD), build 774, Success

2012-12-04 Thread Builder
tn23 (x86 OSX HEAD), build 774

Build succeeded
Details: http://darcs.haskell.org/ghcBuilder/builders/tn23/774.html

git clone| Success
create mk/build.mk   | Success
get subrepos | Success
repo versions| Success
touching clean-check files   | Success
setting version date | Success
booting  | Success
configuring  | Success
creating check-remove-before | Success
compiling| Success
creating check-remove-after  | Success
compiling testremove | Success
simulating clean | Success
checking clean   | Success
making bindist   | Success
testing bindist  | Success
testing  | Success
testsuite summary| Success

Build succeeded
Details: http://darcs.haskell.org/ghcBuilder/builders/tn23/774.html

File not deleted:compiler/ghc.cabal.old
File not deleted:includes/dist-derivedconstants
File not deleted:includes/dist-derivedconstants/header
File not deleted:includes/dist-derivedconstants/header/DerivedConstants.h
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellExports.hs
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellType.hs
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellWrappers.hs
File not deleted:includes/dist-derivedconstants/header/platformConstants
File not deleted:includes/dist-derivedconstants/header/tmp.c
File not deleted:includes/dist-derivedconstants/header/tmp.o
File not deleted:inplace
File not deleted:libraries/base/include/EventConfig.h
File not deleted:mk/config.mk.old
File not deleted:mk/project.mk.old
File not deleted:rts/libs.depend
File not deleted:rts/package.conf.inplace
File not deleted:rts/package.conf.inplace.raw

OVERALL SUMMARY for test run started at Wed Dec  5 03:30:01 CET 2012
3504 total tests, which gave rise to
   13901 test cases, of which
   0 caused framework failures
   10731 were skipped

3069 expected passes
  28 had missing libraries
  34 expected failures
  23 unexpected passes
  16 unexpected failures

Unexpected passes:
   codeGen/should_runT7319 (prof)
   profiling/should_compile  2410 (normal)
   profiling/should_compile  prof001 (normal)
   profiling/should_compile  prof002 (normal)
   profiling/should_run  5314 (prof)
   profiling/should_run  T2552 (prof)
   profiling/should_run  T3001 (prof_hb)
   profiling/should_run  T3001-2 (prof_hb)
   profiling/should_run  T5363 (prof)
   profiling/should_run  T5559 (prof)
   profiling/should_run  T680 (prof)
   profiling/should_run  T949 (prof)
   profiling/should_run  callstack001 (prof)
   profiling/should_run  callstack002 (prof)
   profiling/should_run  heapprof001 (prof)
   profiling/should_run  prof-doc-fib (prof)
   profiling/should_run  prof-doc-last (prof)
   profiling/should_run  profinline001 (prof)
   profiling/should_run  scc001 (prof)
   profiling/should_run  scc002 (prof)
   profiling/should_run  scc003 (prof)
   stranal/should_compilenewtype (optasm)
   thTH_spliceE5_prof (normal)

Unexpected failures:
   ../../libraries/directory/tests  T4113 [bad stdout] (normal)
   codeGen/should_run   cgrun068 [exit code non-0] (normal)
   concurrent/should_runconc070 [bad stdout or stderr] (ghci)
   dynlibs  T3807 [bad exit code] (normal)
   ghci/linking ghcilink003 [bad exit code] (normal)
   ghci/linking ghcilink006 [bad exit code] (normal)
   ghci/scripts T5979 [bad stderr] (ghci)
   ghci/should_run  3171 [bad stdout] (normal)
   perf/compilerT1969 [stat not good enough] (normal)
   perf/compilerT783 [stat not good enough] (normal)
   perf/compilerparsing001 [stat not good enough] (normal)
   perf/haddock haddock.Cabal [stat not good enough] 
(normal)
   perf/haddock haddock.base [stat not good enough] (normal)
   perf/haddock haddock.compiler [stat too good] (normal)
   typecheck/should_failT5300 [stderr mismatch] (normal)
   typecheck/should_failT5691 [stderr mismatch] (normal)

___
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc


pgj (x86 FreeBSD HEAD), build 879, Success

2012-12-04 Thread Builder
pgj (x86 FreeBSD HEAD), build 879

Build succeeded
Details: http://darcs.haskell.org/ghcBuilder/builders/pgj/879.html

git clone| Success
create mk/build.mk   | Success
get subrepos | Success
repo versions| Success
touching clean-check files   | Success
setting version date | Success
booting  | Success
configuring  | Success
creating check-remove-before | Success
compiling| Success
creating check-remove-after  | Success
compiling testremove | Success
simulating clean | Success
checking clean   | Success
making bindist   | Success
publishing bindist   | Success
testing bindist  | Success
testing  | Success
testsuite summary| Success

Build succeeded
Details: http://darcs.haskell.org/ghcBuilder/builders/pgj/879.html

File not deleted:compiler/ghc.cabal.old
File not deleted:includes/dist-derivedconstants
File not deleted:includes/dist-derivedconstants/header
File not deleted:includes/dist-derivedconstants/header/DerivedConstants.h
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellExports.hs
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellType.hs
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellWrappers.hs
File not deleted:includes/dist-derivedconstants/header/platformConstants
File not deleted:includes/dist-derivedconstants/header/tmp.c
File not deleted:includes/dist-derivedconstants/header/tmp.o
File not deleted:inplace
File not deleted:libraries/base/include/EventConfig.h
File not deleted:mk/config.mk.old
File not deleted:mk/project.mk.old
File not deleted:rts/libs.depend
File not deleted:rts/package.conf.inplace
File not deleted:rts/package.conf.inplace.raw

OVERALL SUMMARY for test run started at Wed Dec  5 04:09:38 UTC 2012
3504 total tests, which gave rise to
   11674 test cases, of which
   0 caused framework failures
8509 were skipped

2857 expected passes
  26 had missing libraries
  35 expected failures
  27 unexpected passes
 220 unexpected failures

Unexpected passes:
   ../../libraries/unix/tests  getEnvironment01 (normal)
   ../../libraries/unix/tests  getEnvironment02 (normal)
   ../../libraries/unix/tests  getGroupEntryForName (normal)
   ../../libraries/unix/tests  getUserEntryForName (normal)
   ../../libraries/unix/tests  queryfdoption01 (normal)
   codeGen/should_run  T7319 (prof)
   profiling/should_compile2410 (normal)
   profiling/should_compileprof001 (normal)
   profiling/should_compileprof002 (normal)
   profiling/should_run5314 (prof)
   profiling/should_runT2552 (prof)
   profiling/should_runT3001 (prof_hb)
   profiling/should_runT3001-2 (prof_hb)
   profiling/should_runT5363 (prof)
   profiling/should_runT5559 (prof)
   profiling/should_runT680 (prof)
   profiling/should_runT949 (prof)
   profiling/should_runcallstack001 (prof)
   profiling/should_runcallstack002 (prof)
   profiling/should_runheapprof001 (prof)
   profiling/should_runprof-doc-fib (prof)
   profiling/should_runprof-doc-last (prof)
   profiling/should_runprofinline001 (prof)
   profiling/should_runscc001 (prof)
   profiling/should_runscc002 (prof)
   profiling/should_runscc003 (prof)
   stranal/should_compile  newtype (optasm)

Unexpected failures:
   ../../libraries/base/tests/IO3307 [bad stderr] (normal)
   ../../libraries/base/tests/IOenvironment001 [bad stderr] (normal)
   ../../libraries/directory/tests  getPermissions001 [bad exit code] 
(normal)
   ../../libraries/hpc/tests/ghc_ghci   hpc_ghc_ghci [bad stderr] (normal)
   ../../libraries/process/testsprocess007 [bad stdout] (normal)
   ../../libraries/process/testsprocess009 [bad stdout] (normal)
   ../../libraries/unix/tests   fdReadBuf001 [bad exit code] (ghci)
   ../../libraries/unix/tests/libposix  posix005 [bad stdout] (normal)
   cabal1750 [bad stderr] (normal)
   cabalghcpkg01 [bad stderr] (normal)
   cabalghcpkg03 [bad stderr] (normal)
   cabalghcpkg05 [bad stderr] (normal)
   cabalghcpkg06 [bad stderr] (normal)
   cabalshadow [bad stderr] (normal)
   cabal/cabal01cabal01 [bad stderr] (normal)
   cabal/cabal04cabal04 [bad stderr] (normal)
   codeGen/should_compile   2578 [bad stderr] (normal)
   codeGen/should_run   cgrun068 [exit code non-0] (normal)
   deSugar/should_compile   T5252 

pgj2 (amd64 FreeBSD HEAD), build 882, Failure

2012-12-04 Thread Builder
pgj2 (amd64 FreeBSD HEAD), build 882

Build failed
Details: http://darcs.haskell.org/ghcBuilder/builders/pgj2/882.html

git clone| Success
create mk/build.mk   | Success
get subrepos | Success
repo versions| Success
touching clean-check files   | Success
setting version date | Success
booting  | Success
configuring  | Success
creating check-remove-before | Success
compiling| Success
creating check-remove-after  | Success
compiling testremove | Success
simulating clean | Success
checking clean   | Success
making bindist   | Success
publishing bindist   | Success
testing bindist  | Success
testing  | Failure: Just (ExitFailure 2)

Build failed
Details: http://darcs.haskell.org/ghcBuilder/builders/pgj2/882.html

+++ ./rts/T7037.run.stderr  2012-12-05 07:29:57.768756098 +
@@ -0,0 +1,2 @@
+[: /usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/lib/ghc-7.7.20121205/base-4.7.0.0: unexpected operator
+[: /usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/lib/ghc-7.7.20121205/base-4.7.0.0: unexpected operator
*** unexpected failure for T7037(normal)
= 7087(normal) 3214 of 3504 [21, 209, 0]
cd ./rts  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -o 7087 7087.hs
7087.comp.stderr 21
cd ./rts  ./7087/dev/null 7087.run.stdout 27087.run.stderr
= T7160(normal) 3215 of 3504 [21, 209, 0]
cd ./rts  
'/usr/home/ghc-builder/work/builder/tempbuild/build/bindisttest/install   
dir/bin/ghc' -fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output 
-no-user-package-db -rtsopts -fno-ghci-history -o T7160 T7160.hs
T7160.comp.stderr 21
cd ./rts  ./T7160/dev/null T7160.run.stdout 2T7160.run.stderr
Wrong exit code (expected 0 , actual 139 )
Stdout:

Stderr:
Traceback (most recent call last):
  File ../driver/runtests.py, line 264, in module
oneTest()
  File 
/usr/home/ghc-builder/work/builder/tempbuild/build/testsuite/driver/testlib.py,
 line 598, in lambda
thisTest = lambda : runTest(myTestOpts, name, func, args)
  File 
/usr/home/ghc-builder/work/builder/tempbuild/build/testsuite/driver/testlib.py,
 line 581, in runTest
test_common_work (name, opts, func, args)
  File 
/usr/home/ghc-builder/work/builder/tempbuild/build/testsuite/driver/testlib.py,
 line 730, in test_common_work
framework_fail(name, 'runTest', 'Unhandled exception: ' + str(e))
  File 
/usr/home/ghc-builder/work/builder/tempbuild/build/testsuite/driver/testlib.py,
 line 865, in framework_fail
print '*** framework failure for', full_name, reason, ':'
IOError: [Errno 32] Broken pipe
gmake[2]: *** [test] Error 1
gmake[1]: *** [fast] Broken pipe: 13
gmake: *** [test] Broken pipe: 13
File not deleted:compiler/ghc.cabal.old
File not deleted:includes/dist-derivedconstants
File not deleted:includes/dist-derivedconstants/header
File not deleted:includes/dist-derivedconstants/header/DerivedConstants.h
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellExports.hs
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellType.hs
File not deleted:
includes/dist-derivedconstants/header/GHCConstantsHaskellWrappers.hs
File not deleted:includes/dist-derivedconstants/header/platformConstants
File not deleted:includes/dist-derivedconstants/header/tmp.c
File not deleted:includes/dist-derivedconstants/header/tmp.o
File not deleted:inplace
File not deleted:libraries/base/include/EventConfig.h
File not deleted:mk/config.mk.old
File not deleted:mk/project.mk.old
File not deleted:rts/libs.depend
File not deleted:rts/package.conf.inplace
File not deleted:rts/package.conf.inplace.raw
___
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc


pgj-freebsd-i386-stable (x86 FreeBSD STABLE), build 742, Success

2012-12-04 Thread Builder
pgj-freebsd-i386-stable (x86 FreeBSD STABLE), build 742

Build succeeded
Details: 
http://darcs.haskell.org/ghcBuilder/builders/pgj-freebsd-i386-stable/742.html

git clone| Success
create mk/build.mk   | Success
get subrepos | Success
repo versions| Success
touching clean-check files   | Success
setting version date | Success
booting  | Success
configuring  | Success
creating check-remove-before | Success
compiling| Success
creating check-remove-after  | Success
compiling testremove | Success
simulating clean | Success
checking clean   | Success
making bindist   | Success
publishing bindist   | Success
testing bindist  | Success
testing  | Success
testsuite summary| Success

Build succeeded
Details: 
http://darcs.haskell.org/ghcBuilder/builders/pgj-freebsd-i386-stable/742.html

File not deleted:compiler/ghc.cabal.old
File not deleted:inplace
File not deleted:libraries/base/include/EventConfig.h
Deleted before file: libraries/time/include/HsTimeConfig.h
File not deleted:mk/config.mk.old
File not deleted:mk/project.mk.old
File not deleted:rts/libs.depend
File not deleted:rts/package.conf.inplace
File not deleted:rts/package.conf.inplace.raw

OVERALL SUMMARY for test run started at Wed Dec  5 07:02:34 UTC 2012
3402 total tests, which gave rise to
   14436 test cases, of which
  10 caused framework failures
   11364 were skipped

2957 expected passes
  48 had missing libraries
  34 expected failures
   5 unexpected passes
  28 unexpected failures

Unexpected passes:
   ../../libraries/unix/tests  getEnvironment01 (normal)
   ../../libraries/unix/tests  getEnvironment02 (normal)
   ../../libraries/unix/tests  getGroupEntryForName (normal)
   ../../libraries/unix/tests  getUserEntryForName (normal)
   ../../libraries/unix/tests  queryfdoption01 (normal)

Unexpected failures:
   ../../libraries/directory/tests  getPermissions001 [bad exit code] 
(normal)
   ../../libraries/process/testsprocess007 [bad stdout] (normal)
   ../../libraries/unix/tests/libposix  posix005 [bad stdout] (normal)
   driver   dynHelloWorld [bad exit code] (dyn)
   driver/recomp011 recomp011 [bad stdout] (normal)
   dynlibs  T3807 [bad exit code] (normal)
   dynlibs  T5373 [bad stdout] (normal)
   ghci/scripts T5979 [bad stderr] (ghci)
   perf/haddock haddock.Cabal [stat too good] (normal)
   perf/haddock haddock.base [stat too good] (normal)
   perf/haddock haddock.compiler [stat too good] 
(normal)
   plugins  plugins01 [bad exit code] (normal)
   plugins  plugins02 [stderr mismatch] (normal)
   plugins  plugins03 [stderr mismatch] (normal)
   rts  T2615 [bad stdout] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly01 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly02 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly03 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly04 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly05 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly06 [exit code non-0] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly07 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly08 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly09 [stderr mismatch] (normal)
   safeHaskell/check/pkg01  ImpSafeOnly10 [exit code non-0] (normal)
   safeHaskell/check/pkg01  safePkg01 [bad exit code] (normal)
   typecheck/should_failT5300 [stderr mismatch] (normal)
   typecheck/should_failT5691 [stderr mismatch] (normal)

___
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc