Using GHC-as-a-library
Mathew Mills
mathewmills at mac.com
Thu Oct 5 11:29:48 EDT 2006
check out main/SysTools.lhs.
Looks like it uses some heuristic to decide whether GHC is
"installed" or not. I suspect your test app is running from a
location it considers to be part of the build-tree.
Look at initSysTools and findTopDir.
On Oct 5, 2006, at 4:43 AM, Martin Grabmueller wrote:
> Hello all,
>
> I've been playing around with GHC-as-a-library a bit now, and using
> yesterday's snapshot of GHC (ghc-6.5.20061004, compiled from source),
> I ran into the following problem:
>
> When using the Haskell program at the end of this mail, it compiles
> fine (after exposing the ghc package with ghc-pkg), but when running
> it complains:
>
> Main: Can't find package.conf as /usr/local/ghc/lib/
> ghc-6.5.20061004/driver/package.conf.inplace
>
> So it seems to search for a package.conf file in the build tree
> instead
> of an installed one. Passing in the path to the build tree
> (commented out
> in the program) to GHC.newSession works.
>
> Has anyone else encountered this problem? There is probably only a
> small
> fix necessary, but I have not yet been able to figure it out by
> myself.
>
> Thanks,
> Martin
>
> module Main where
>
> import qualified GHC
> import DynFlags (defaultDynFlags)
> import Outputable (ppr, showSDoc, text, (<+>), ($$), empty)
> import BasicTypes
>
> import Data.List
>
> -- This should work, but compiler complains:
> -- Main: Can't find package.conf as
> -- /usr/local/ghc/lib/ghc-6.5.20061004/driver/package.conf.inplace
> my_ghc_root = "/usr/local/ghc/lib/ghc-6.5.20061004"
>
> -- This does work:
> --my_ghc_root = "/home/misc/src/ghc-6.5.20061004"
>
> main = GHC.defaultErrorHandler defaultDynFlags $ do
> let ghcMode = GHC.JustTypecheck
>
> -- Create GHC session, passing GHC installation directory
> session <- GHC.newSession ghcMode (Just my_ghc_root)
> dflags0 <- GHC.getSessionDynFlags session
> GHC.defaultCleanupHandler dflags0 $ do
> GHC.setSessionDynFlags session dflags0
> putStrLn "New session defined"
> let testModule = (GHC.mkModuleName "Test")
> t <- GHC.guessTarget "Test.hs" Nothing
> GHC.setTargets session [t]
> ok <- GHC.load session GHC.LoadAllTargets
> if failed ok
> then putStrLn "Loading failed!"
> else putStrLn "Loading OK!"
> checked <- GHC.checkModule session testModule
> case checked of
> Nothing -> putStrLn "Couldn't check"
> Just (GHC.CheckedModule parsed renamed typechecked info) ->
> do putStrLn (showSDoc (ppr parsed))
> putStrLn (showSDoc (ppr renamed))
> putStrLn (showSDoc (ppr typechecked))
> putStrLn (showSDoc
> (case info of
> Just cm | Just scope <- GHC.modInfoTopLevelScope cm ->
> let
> (local,global) = partition ((== testModule) .
> GHC.moduleName . GHC.nameModule) scope
> in
> (text "global names: " <+> ppr global) $$
> (text "local names: " <+> ppr local)
> _ -> empty))
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
More information about the Glasgow-haskell-users
mailing list