GHC.Prim problem
Ben Sinclair
bsinclai at turing.une.edu.au
Fri May 25 11:38:25 EDT 2007
Hello, I've had a problem with GHC.Prim when compiling the darcs HEAD
lately. When I compile it in the normal way with no special options
> sh boot && ./configure && make && make install
it compiles correctly, but if I attempt to compile
> module Main where
>
> import GHC.Prim
>
> main :: IO ()
> main = return ()
then I get this output:
> $ ghc --make Main.hs -fglasgow-exts -v
> Glasgow Haskell Compiler, Version 6.7.20070524, for Haskell 98, compiled by GHC version 6.7.20070524
> Using package config file: /usr/local/lib/ghc-6.7.20070524/package.conf
> wired-in package base mapped to base-2.1
> wired-in package rts mapped to rts-1.0
> wired-in package haskell98 mapped to haskell98-1.0
> wired-in package template-haskell mapped to template-haskell-0.1
> Hsc static flags: -static
> *** Chasing dependencies:
> Chasing modules from: Main.hs
> Stable obj: []
> Stable BCO: []
> Ready for upsweep
> [NONREC
> ModSummary {
> ms_hs_date = Sat May 26 01:11:06 EST 2007
> ms_mod = main:Main,
> ms_imps = []
> ms_srcimps = []
> }]
> compile: input file Main.hs
> Created temporary directory: /tmp/ghc19188_0
> *** Checking old interface for main:Main:
> [1 of 1] Compiling Main ( Main.hs, Main.o )
> *** Parser:
> *** Renamer/typechecker:
>
> Main.hs:3:0:
> Failed to load interface for `GHC.Prim':
> locations searched:
> GHC/Prim.hs
> GHC/Prim.lhs
> *** Deleting temp files:
> Deleting: /tmp/ghc19188_0/ghc19188_0.s
> Warning: deleting non-existent /tmp/ghc19188_0/ghc19188_0.s
> Upsweep partially successful.
> *** Deleting temp files:
> Deleting:
> link(batch): upsweep (partially) failed OR
> Main.main not exported; not linking.
> *** Deleting temp files:
> Deleting:
> *** Deleting temp dirs:
> Deleting: /tmp/ghc19188_0
Is there anything I should be doing to make this work? Thanks for any
advice,
Ben
More information about the Glasgow-haskell-users
mailing list