Difference between revisions of "GHC/As a library (up to 6.8)"

From HaskellWiki
< GHC
Jump to navigation Jump to search
(remove a misleading phrase)
(major major major addition, edition, and a bit of deletion)
Line 10: Line 10:
   
 
== Getting started ==
 
== Getting started ==
You'll need to get a version of GHC that supports the GHC API. Either download ghc from [http://www.haskell.org/ghc/docs/latest/html/building/sec-cvs.html CVS] or use darcs: <tt>darcs get --partial http://darcs.haskell.org/ghc</tt>. There are also [http://www.haskell.org/ghc/dist/current/dist nightly snapshot distributions] available.
+
You'll need a version of GHC (at least 6.5) that supports the GHC API. The [http://www.haskell.org/ghc/download.html GHC download page] offers stable releases and development versions; you can also use CVS ([http://www.haskell.org/ghc/docs/latest/html/building/sec-cvs.html instructions]) or darcs (e.g., <tt>darcs get --partial http://darcs.haskell.org/ghc</tt>).
   
To use the GHC API you say simply
+
To use the GHC API you say
<pre>
+
<haskell>
import GHC
+
import GHC
</pre>
+
</haskell>
Doing this imports the module <tt>GHC</tt> from the package <tt>ghc</tt>, which comes with GHC 6.5 and subsequent. The module GHC exports the "GHC API", which is still in a state of flux. Currently it's not even Haddock-documented. You can see the source code (which is somewhat documented) here
+
Doing this imports the module <tt>GHC</tt> from the package <tt>ghc</tt>. This module exports the "GHC API", which is still in a state of flux. Currently it's not even Haddock-documented. You can see the [http://darcs.haskell.org/ghc/compiler/main/GHC.hs source code] (somewhat documented). There are also other modules of interest as you do more special things.
http://darcs.haskell.org/ghc/compiler/main/GHC.hs
 
   
Here's an example main program that does it [[Media:Main.hs]] (good for GHC 6.6). You need to manually change the value of <hask>myGhcRoot</hask> to point to your GHC directory.
+
Here's an example main program that does it [[Media:Main.hs]] (good for GHC 6.6). You need to manually change the value of <tt>myGhcRoot</tt> to point to your GHC directory.
   
 
To compile [[Media:Main.hs]], you have to turn on the flag "-package ghc", e.g.
 
To compile [[Media:Main.hs]], you have to turn on the flag "-package ghc", e.g.
Line 26: Line 25:
 
</pre>
 
</pre>
   
== Using the GHC library from inside GHCi ==
+
== Common use cases and functions ==
   
  +
'''Assumes GHC 6.6.'''
This works, to some extent. However, beware about loading object code, because there is only a single linker symbol table in the runtime, so GHCi will be sharing the symbol table with the new GHC session.
 
   
  +
=== Default exception and cleanup handling ===
<pre>
 
  +
<!-- todo -->
Prelude> :m + GHC Module Packages PackageConfig
 
  +
TODO
Prelude GHC> session <- newSession Interactive (Just "/usr/local/lib/ghc-6.6")
 
Prelude GHC> (\(f,_) -> setSessionDynFlags session f) =<< initPackages =<< getSessionDynFlags session
 
Prelude GHC> setContext session [] [mkModule (stringToPackageId "base") (mkModuleName "Prelude")]
 
Prelude GHC> runStmt session "let add1 x = x + 1"
 
Prelude GHC> runStmt session "add1 2"
 
3
 
Prelude GHC> :q
 
Leaving GHCi.
 
</pre>
 
   
== Relevant information ==
+
=== Initialization ===
 
'''As of GHC 6.6.'''
 
   
 
First create a session:
 
First create a session:
  +
<haskell>
<pre>GHC.newSession :: DynFlags.GhcMode -> Maybe FilePath -> IO Session</pre>
 
  +
newSession :: GhcMode -- BatchCompile | Interactive | MkDepend | ...
The path should be the GHC installation directory, e.g., /usr/local/lib/ghc-6.6
 
  +
-> Maybe FilePath -- GHC installation directory
  +
-> IO Session -- your seesion; you will need it
  +
</haskell>
  +
The path to your GHC installation directory (e.g., /usr/local/lib/ghc-6.6) is in practice mandatory, even though in theory marked as optional.
   
  +
The session is configurable by dynamic flags (GHC dynamic flags plus session state; think <tt>-O2</tt>, <tt>-fvia-C</tt>, <tt>-fglasgow-exts</tt>, <tt>-package</tt>). This can be done with:
Load Module
 
<pre>
+
<haskell>
  +
getSessionDynFlags :: Session -> IO DynFlags
HscTypes.TargetId = TargetModule ModuleName | TargetFile FilePath (Maybe Phase)
 
  +
setSessionDynFlags :: Session
</pre>
 
  +
-> DynFlags
The Phase determines which phase to start from (preprocessing)
 
  +
-> IO [PackageId] -- important iff dynamic-linking
  +
parseDynamicFlags :: DynFlags -- old flags
  +
-> [String] -- e.g., all or part of getArgs
  +
-> IO (DynFlags, [String]) -- new flags, unknown args
  +
</haskell>
  +
The <hask>DynFlags</hask> record has a gazillion fields; ask ghci to show all of them. You can change them by hand, or use the parser (which implements the GHC command line format and does the Right Thing). But there is one you must note:
  +
<haskell>
  +
data DynFlags = DynFlags { ...,
  +
hscTarget :: HscTarget } -- HscC | HscAsm | HscInterpreted | ...
  +
</haskell>
  +
This corresponds to <tt>-fvia-C</tt>, <tt>-fasm</tt>, or interpreting. When the session needs to re-compile a module, this field controls how. The default is <hask>HscAsm</hask>, ''even in the interactive mode'', meaning the interactive mode may produce .hi and .o files too. If you want to follow GHCi in not doing that, you must set this field to <hask>HscInterpreted</hask> yourself. (On the other hand, it is fun to contemplate an interactive session that generates machine code upon your command.)
   
  +
<hask>setSessionDynFlags</hask> also sets up your session's awareness of the package database (without which you can't even use the Prelude), so even if you like the defaults, you should still call it. (Older code called <hask>PackageConfig.initPackages</hask> for this.)
Enter Expressions/Run Statements
 
<pre>GHC.runStmt :: Session -> String -> IO RunResult
 
data GHC.RunResult
 
= RunOk [Name]
 
| RunFailed
 
| RunException GHC.IOBase.Exception -- that's Control.Exception.Exception
 
</pre>
 
Example:
 
<pre>runStmt session "let n = 2 + 2"</pre>
 
The RunResult of this is RunOk [n] where n is bound to 4. So if we subsequently enter <pre>runStmt session "n"</pre> we get 4.
 
   
  +
Examples:
CompileExpr, DynCompileExpr
 
  +
* vanilla compiler, use all defaults (rare but good start)
  +
<haskell>
  +
session <- newSession BatchCompile (Just "/usr/local/lib/ghc-6.6")
  +
getSessionDynFlags session >>= setSessionDynFlags session
  +
</haskell>
  +
* compiler with custom flags, easy with parser
  +
<haskell>
  +
session <- newSession BatchCompile (Just "/usr/local/lib/ghc-6.6")
  +
f0 <- getSessionDynFlags session
  +
(f1,b) <- parseDynamicFlags f0 ["-fglasgow-exts", "-O", "-package", "ghc", "-package Cabal",
  +
"foo", "-v", "bar"]
  +
-- b = ["foo", "bar"]; the other args are recognized
  +
-- in GHC 6.6 "-O" implies "-fvia-C", that kind of thing is automatic here too
  +
setSessionDynFlags session f1
  +
</haskell>
  +
* interactive session with interpreter
  +
<haskell>
  +
session <- newSession Interactive (Just "/usr/local/lib/ghc-6.6")
  +
f0 <- getSessionDynFlags session
  +
setSessionDynFlags session f0{hscTarget = HscInterpreted}
  +
</haskell>
   
  +
=== Load or compile modules ===
Get module dependency graph
 
<pre>GHC.getModuleGraph :: Session -> IO ModuleGraph</pre>
 
Get bindings
 
<pre>GHC.getBindings :: Session -> IO [TyThing]</pre>
 
   
  +
To compile code or load modules, first set one or more targets, then call the <hask>load</hask> function.
Error messages can be routed through a callback mechanism using
 
  +
<haskell>
<pre>setSessionDynFlags :: Session -> DynFlags -> IO [PackageId]</pre>
 
  +
guessTarget :: String -- "filename.hs" or "filename.lhs" or "MyModule"
where <code>DynFlags</code> is a record with many fields, one of which is
 
  +
-> Maybe Phase -- if not Nothing, specifies starting phase
<pre>
 
  +
-> IO Target
log_action :: Severity -> SrcLoc.SrcSpan -> Outputable.PprStyle -> ErrUtils.Message
 
-> IO ()}
+
addTarget :: Session -> Target -> IO ()
  +
setTargets :: Session -> [Target] -> IO ()
</pre>
 
  +
getTargets :: Session -> IO [Target]
and you can set it to your action, like
 
  +
removeTarget :: Session -> TargetId -> IO ()
<pre>
 
  +
load :: Session -> LoadHowMuch -> IO SuccessFlag
f <- getSessionDynFlags session
 
  +
data LoadHowMuch
setSessionDynFlags session f{log_action = my_action}
 
  +
= LoadAllTargets
</pre>
 
  +
| LoadUpTo ModuleName
  +
| LoadDependenciesOf ModuleName
  +
</haskell>
  +
  +
Example:
  +
<haskell>
  +
t <- guessTarget "Main.hs" Nothing
  +
addTarget session t -- setTargets session [t] is also good
  +
sf <- load session LoadAllTargets
  +
case sf of Succeeded -> ...
  +
Failed -> ...
  +
</haskell>
  +
Dependencies are processed automatically (and silently).
  +
  +
Modules are compiled as per the <hask>hscTarget</hask> flag (<tt>-fasm</tt>, <tt>-fvia-C</tt>, or interpreter) in <hask>DynFlags</hask>, ''independent of GHC mode''.
  +
  +
=== Interactive evaluation ===
  +
  +
Interactive evaluation ala GHCi is done by <hask>runStmt</hask>. But first, this is always done under a current context, i.e., which modules are in scope. Most probably you want to have at least the Prelude and those you loaded in the previous section. How to manipulate the context:
  +
<haskell>
  +
setContext :: Session
  +
-> [Module] -- their top levels will be visible
  +
-> [Module] -- their exports will be visible
  +
-> IO ()
  +
getContext :: Session -> IO ([Module], [Module])
  +
findModule :: Session -> ModuleName -> Maybe PackageId -> IO Module
  +
mkModule :: PackageId -> ModuleName -> Module
  +
mkModuleName :: String -> ModuleName
  +
PackageConfig.stringToPackageId :: String -> PackageId
  +
</haskell>
  +
Every module given to <hask>setContext</hask> must be either in a package known to the session or has been loaded as per the previous subsection. Example:
  +
<haskell>
  +
-- equivalent to GHCi's :m Prelude Control.Monad *Main
  +
prelude <- findModule session (mkModuleName "Prelude") Nothing
  +
monad <- findModule session (mkModuleName "Control.Monad") Nothing
  +
usermod <- findModule session (mkModuleName "Main") Nothing -- we have loaded this
  +
setContext session [usermod] [prelude,monad]
  +
</haskell>
  +
You can also be specific about packages. You can also use <hask>mkModule</hask> instead of <hask>findModule</hask>, or even some module query functions in the next subsection.
  +
  +
Having set a useful context, we're now ready to evaluate.
  +
<haskell>
  +
runStmt :: Session -> String -> IO RunResult
  +
data RunResult
  +
= RunOk [Name] -- names bound by the expression
  +
| RunFailed
  +
| RunException GHC.IOBase.Exception -- that's Control.Exception.Exception
  +
</haskell>
  +
Example:
  +
<haskell>
  +
runStmt session "let n = 2 + 2" -- n is bound
  +
runStmt session "n" -- 4 is printed (note "it" is bound)
  +
</haskell>
  +
  +
(Interactive evaluation works in BatchCompile mode too! There are still other subtle differences, so this is not recommended.)
  +
  +
=== Queries ===
  +
  +
<haskell>
  +
-- Get module dependency graph
  +
getModuleGraph :: Session -> IO ModuleGraph -- ModuleGraph = [ModSummary]
  +
-- Get bindings
  +
getBindings :: Session -> IO [TyThing]
  +
</haskell>
  +
  +
=== Error handling ===
  +
  +
(This refers to compiler-reported errors such as syntax and type errors in source code.)
  +
  +
Error messages can be routed through a callback mechanism. This is a field in <hask>DynFlags</hask>:
  +
<haskell>
  +
data DynFlags = DynFlags { ...,
  +
log_action :: Severity -> SrcLoc.SrcSpan -> Outputable.PprStyle -> ErrUtils.Message -> IO () }
  +
</haskell>
  +
You can set it to your action, like
  +
<haskell>
  +
f <- getSessionDynFlags session
  +
setSessionDynFlags session f{log_action = my_action}
  +
</haskell>
   
 
== Interactive mode example ==
 
== Interactive mode example ==
   
 
The file [[Media:Interactive.hs]] (also requires [[Media:MyPrelude.hs]]) serves as an example for using GHC as a library in interactive mode. It also shows how to replace some of the standard prelude functions with modified versions. See the comments in the code for further information.
 
The file [[Media:Interactive.hs]] (also requires [[Media:MyPrelude.hs]]) serves as an example for using GHC as a library in interactive mode. It also shows how to replace some of the standard prelude functions with modified versions. See the comments in the code for further information.
  +
----
 
  +
== Using the GHC library from inside GHCi ==
  +
  +
This works, to some extent. However, beware about loading object code, because there is only a single linker symbol table in the runtime, so GHCi will be sharing the symbol table with the new GHC session.
  +
  +
<pre>
  +
$ ghci -package ghc
  +
Prelude> :m + GHC PackageConfig
  +
Prelude GHC> session <- newSession Interactive (Just "/usr/local/lib/ghc-6.6")
  +
Prelude GHC> setSessionDynFlags session =<< getSessionDynFlags session
  +
Prelude GHC> setContext session [] [mkModule (stringToPackageId "base") (mkModuleName "Prelude")]
  +
Prelude GHC> runStmt session "let add1 x = x + 1"
  +
Prelude GHC> runStmt session "add1 2"
  +
3
  +
</pre>

Revision as of 06:22, 8 January 2007

Using GHC as a library

In GHC 6.5 and subsequently you can import GHC as a Haskell library, which lets you write a Haskell program that has access to all of GHC.

This page is a place for everyone to add

  • Notes about how to get it working
  • Comments about the API
  • Suggestions for improvement

and so on.

Getting started

You'll need a version of GHC (at least 6.5) that supports the GHC API. The GHC download page offers stable releases and development versions; you can also use CVS (instructions) or darcs (e.g., darcs get --partial http://darcs.haskell.org/ghc).

To use the GHC API you say

import GHC

Doing this imports the module GHC from the package ghc. This module exports the "GHC API", which is still in a state of flux. Currently it's not even Haddock-documented. You can see the source code (somewhat documented). There are also other modules of interest as you do more special things.

Here's an example main program that does it Media:Main.hs (good for GHC 6.6). You need to manually change the value of myGhcRoot to point to your GHC directory.

To compile Media:Main.hs, you have to turn on the flag "-package ghc", e.g.

  ghc -package ghc Main.hs

Common use cases and functions

Assumes GHC 6.6.

Default exception and cleanup handling

TODO

Initialization

First create a session:

newSession :: GhcMode         -- BatchCompile | Interactive | MkDepend | ...
           -> Maybe FilePath  -- GHC installation directory
           -> IO Session      -- your seesion; you will need it

The path to your GHC installation directory (e.g., /usr/local/lib/ghc-6.6) is in practice mandatory, even though in theory marked as optional.

The session is configurable by dynamic flags (GHC dynamic flags plus session state; think -O2, -fvia-C, -fglasgow-exts, -package). This can be done with:

getSessionDynFlags :: Session -> IO DynFlags
setSessionDynFlags :: Session
                   -> DynFlags
                   -> IO [PackageId]  -- important iff dynamic-linking
parseDynamicFlags :: DynFlags  -- old flags
                  -> [String]  -- e.g., all or part of getArgs
                  -> IO (DynFlags, [String])  -- new flags, unknown args

The DynFlags record has a gazillion fields; ask ghci to show all of them. You can change them by hand, or use the parser (which implements the GHC command line format and does the Right Thing). But there is one you must note:

data DynFlags = DynFlags { ...,
    hscTarget :: HscTarget }    -- HscC | HscAsm | HscInterpreted | ...

This corresponds to -fvia-C, -fasm, or interpreting. When the session needs to re-compile a module, this field controls how. The default is HscAsm, even in the interactive mode, meaning the interactive mode may produce .hi and .o files too. If you want to follow GHCi in not doing that, you must set this field to HscInterpreted yourself. (On the other hand, it is fun to contemplate an interactive session that generates machine code upon your command.)

setSessionDynFlags also sets up your session's awareness of the package database (without which you can't even use the Prelude), so even if you like the defaults, you should still call it. (Older code called PackageConfig.initPackages for this.)

Examples:

  • vanilla compiler, use all defaults (rare but good start)
session <- newSession BatchCompile (Just "/usr/local/lib/ghc-6.6")
getSessionDynFlags session >>= setSessionDynFlags session
  • compiler with custom flags, easy with parser
session <- newSession BatchCompile (Just "/usr/local/lib/ghc-6.6")
f0 <- getSessionDynFlags session
(f1,b) <- parseDynamicFlags f0 ["-fglasgow-exts", "-O", "-package", "ghc", "-package Cabal",
                                "foo", "-v", "bar"]
-- b = ["foo", "bar"]; the other args are recognized
-- in GHC 6.6 "-O" implies "-fvia-C", that kind of thing is automatic here too
setSessionDynFlags session f1
  • interactive session with interpreter
session <- newSession Interactive (Just "/usr/local/lib/ghc-6.6")
f0 <- getSessionDynFlags session
setSessionDynFlags session f0{hscTarget = HscInterpreted}

Load or compile modules

To compile code or load modules, first set one or more targets, then call the load function.

guessTarget :: String       -- "filename.hs" or "filename.lhs" or "MyModule"
            -> Maybe Phase  -- if not Nothing, specifies starting phase
            -> IO Target
addTarget :: Session -> Target -> IO ()
setTargets :: Session -> [Target] -> IO ()
getTargets :: Session -> IO [Target]
removeTarget :: Session -> TargetId -> IO ()
load :: Session -> LoadHowMuch -> IO SuccessFlag
data LoadHowMuch
  = LoadAllTargets
  | LoadUpTo ModuleName
  | LoadDependenciesOf ModuleName

Example:

t <- guessTarget "Main.hs" Nothing
addTarget session t    -- setTargets session [t] is also good
sf <- load session LoadAllTargets
case sf of Succeeded -> ...
           Failed -> ...

Dependencies are processed automatically (and silently).

Modules are compiled as per the hscTarget flag (-fasm, -fvia-C, or interpreter) in DynFlags, independent of GHC mode.

Interactive evaluation

Interactive evaluation ala GHCi is done by runStmt. But first, this is always done under a current context, i.e., which modules are in scope. Most probably you want to have at least the Prelude and those you loaded in the previous section. How to manipulate the context:

setContext :: Session
           -> [Module]    -- their top levels will be visible
           -> [Module]    -- their exports will be visible
           -> IO ()
getContext :: Session -> IO ([Module], [Module])
findModule :: Session -> ModuleName -> Maybe PackageId -> IO Module
mkModule :: PackageId -> ModuleName -> Module
mkModuleName :: String -> ModuleName
PackageConfig.stringToPackageId :: String -> PackageId

Every module given to setContext must be either in a package known to the session or has been loaded as per the previous subsection. Example:

-- equivalent to GHCi's :m Prelude Control.Monad *Main
prelude <- findModule session (mkModuleName "Prelude") Nothing
monad <- findModule session (mkModuleName "Control.Monad") Nothing
usermod <- findModule session (mkModuleName "Main") Nothing  -- we have loaded this
setContext session [usermod] [prelude,monad]

You can also be specific about packages. You can also use mkModule instead of findModule, or even some module query functions in the next subsection.

Having set a useful context, we're now ready to evaluate.

runStmt :: Session -> String -> IO RunResult
data RunResult
    = RunOk [Name]    -- names bound by the expression
    | RunFailed
    | RunException GHC.IOBase.Exception  -- that's Control.Exception.Exception

Example:

runStmt session "let n = 2 + 2"  -- n is bound
runStmt session "n"              -- 4 is printed (note "it" is bound)

(Interactive evaluation works in BatchCompile mode too! There are still other subtle differences, so this is not recommended.)

Queries

-- Get module dependency graph
getModuleGraph :: Session -> IO ModuleGraph    -- ModuleGraph = [ModSummary]
-- Get bindings
getBindings :: Session -> IO [TyThing]

Error handling

(This refers to compiler-reported errors such as syntax and type errors in source code.)

Error messages can be routed through a callback mechanism. This is a field in DynFlags:

data DynFlags = DynFlags { ...,
    log_action :: Severity -> SrcLoc.SrcSpan -> Outputable.PprStyle -> ErrUtils.Message -> IO () }

You can set it to your action, like

f <- getSessionDynFlags session
setSessionDynFlags session f{log_action = my_action}

Interactive mode example

The file Media:Interactive.hs (also requires Media:MyPrelude.hs) serves as an example for using GHC as a library in interactive mode. It also shows how to replace some of the standard prelude functions with modified versions. See the comments in the code for further information.

Using the GHC library from inside GHCi

This works, to some extent. However, beware about loading object code, because there is only a single linker symbol table in the runtime, so GHCi will be sharing the symbol table with the new GHC session.

$ ghci -package ghc
Prelude> :m + GHC PackageConfig
Prelude GHC> session <- newSession Interactive (Just "/usr/local/lib/ghc-6.6")
Prelude GHC> setSessionDynFlags session =<< getSessionDynFlags session
Prelude GHC> setContext session [] [mkModule (stringToPackageId "base") (mkModuleName "Prelude")]
Prelude GHC> runStmt session "let add1 x = x + 1"
Prelude GHC> runStmt session "add1 2"
3