Compiling base with custom compilation script
Simon Marlow
marlowsd at gmail.com
Mon Sep 6 08:43:29 EDT 2010
On 01/09/2010 12:08, Victor Nazarov wrote:
> I have some custom compilation script that uses GHC API
> The aim is to extract some info from every module in dependency graph
> and to write this information to the file lying near module-file.
> Script goes like this:
>
> main :: IO ()
> main =
> do args<- getArgs
> defaultErrorHandler defaultDynFlags $ runGhc (Just libdir) $
> do sdflags<- getSessionDynFlags
> (dflags, fileargs', _)<- parseDynamicFlags sdflags (map noLoc args)
> when (null fileargs') $ ghcError (UsageError "No input files.")
> _<- setSessionDynFlags dflags
> let fileargs = map unLoc fileargs'
> targets<- mapM (\x -> guessTarget x Nothing) fileargs
> setTargets targets
> mgraph<- depanal [] False
> let files = filter (not . isSuffixOf "boot")
> . map (extractPath . ms_location) $ mgraph
> extractPath l = fromMaybe (ml_hi_file l) (ml_hs_file l)
> setTargets []
> flip mapM_ files $ \file ->
> do core<- compileToCoreSimplified file
> HscTypes.liftIO $
> let info = show (generateInfo core)
> fp = replaceExtension file ".info"
> putStrLn $ "Writing " ++ fp
> writeFile fp program
>
> The problem is processing base-4 package. I'd like to run something like:
>
> $ cd base-4.2.0.1
> $ compiler -fglasgow-exts -cpp -package-name base -I./include Prelude.hs
>
> and to receive Prelude.info and .info files for every other modules
> that prelude depends on.
>
> At first I've got errors like missing .h file. I've downloaded GHC
> source distribution and get
> missing headers from GHC.
>
> But now I get errors like "trying to load Prelude module which is not
> loadable". I don't remember the exact text
> and I have no access to my developing-machine. I think it's caused by
> circular dependencies between modules.
> And I think my compilation script is not quite correct for this case.
> What do you think?
There are some problems with compiling the base package independently of
a GHC build, for some details see here:
http://hackage.haskell.org/trac/ghc/ticket/3103
in general, though, you should check what flags Cabal is passing to GHC
to see how to compile a package. Try "cabal build -v" and grab the GHC
command line.
Cheers,
Simon
More information about the Glasgow-haskell-users
mailing list