On Sun, Oct 12, 2008 at 06:03:30PM -0700, Devin Mullins wrote:
> I'm trying to build 6.8.3 on Linux PowerPC, based on an old binary of
> 6.4 (latest build for this arch that I found). stage1 seems to have
> built, but from there, building libraries almost immediately fails:
> 
> > Configuring base-3.0.2.0...
> > Setup: ghc version >=6.2 is required but the version of 
> > ../../compiler/stage1/ghc-inplace could not be determined.

Okay, for those of you keeping score, here's an update. It looks like
Distribution.Simple.Program.findProgramVersion is swallowing the
exception that Distribution.Simple.Utils.rawSystemStdout is throwing,
leading to the null string in the verbose log. Here's a simple test
program:

> module Main where
> 
> import Prelude hiding (catch)
> import Control.Exception (catch)
> import Distribution.Simple.Utils (rawSystemStdout)
> import Distribution.Verbosity (deafening)
> 
> main :: IO ()
> main = putStrLn =<< rawSystemStdout deafening "/bin/ls" [] `catch` (return . 
> show)

And the output (as compiled by ghc-6.4):
$ ./Main
("/bin/ls",[])
/dev/null: openFile: invalid argument (Invalid argument)

Whuh?

Perhaps I should try bootstrapping 6.6 first...
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to