GHC/As a library: Difference between revisions
mNo edit summary |
m (update links for ghc/ghc-paths packages) |
||
(30 intermediate revisions by 17 users not shown) | |||
Line 7: | Line 7: | ||
GHC's functionality can be useful for more things than just compiling Haskell programs. Important use cases are programs that analyse (and perhaps transform) Haskell code. Others include loading Haskell code dynamically in a GHCi-like manner. For this reason, a lot of GHC's features can be accessed by programs which import the <tt>ghc</tt> package. | GHC's functionality can be useful for more things than just compiling Haskell programs. Important use cases are programs that analyse (and perhaps transform) Haskell code. Others include loading Haskell code dynamically in a GHCi-like manner. For this reason, a lot of GHC's features can be accessed by programs which import the <tt>ghc</tt> package. | ||
The instructions on this page concern the API of GHC 6.10.1 and above. Please | The instructions on this page concern the API of GHC 6.10.1 and above. Please note that the GHC API is still in flux and may change quite significantly between major releases while we (the GHC team) provide new features or simplify certain aspects. | ||
== Getting Started == | == Getting Started == | ||
To use the GHC API you need GHC 6.10.1 or above and import the <tt>ghc</tt> package. | To use the GHC API you need GHC 6.10.1 or above and import the [https://hackage.haskell.org/package/ghc <tt>ghc</tt> package]. | ||
<pre> | <pre> | ||
ghc -package ghc my_program.hs | ghc -package ghc my_program.hs | ||
</pre> | </pre> | ||
In most cases you probably also want to use the [http://hackage.haskell.org | In most cases you probably also want to use the [http://hackage.haskell.org/package/ghc-paths <tt>ghc-paths</tt> package]. | ||
Most of the common functionality is provided by the <tt>GHC</tt> module, but occasionally you may have to import other modules. See the GHC's haddock documentation for a list of these modules. | Most of the common functionality is provided by the <tt>GHC</tt> module, but occasionally you may have to import other modules. See the GHC's [https://downloads.haskell.org/~ghc/latest/docs/html/libraries/ haddock documentation] for a list of these modules. One good entry point into the docs is [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/GHC.html GHC]. | ||
== A Simple Example == | == A Simple Example == | ||
Line 27: | Line 25: | ||
<haskell> | <haskell> | ||
{-# LANGUAGE CPP #-} | |||
import GHC | import GHC | ||
import GHC.Paths ( libdir ) | import GHC.Paths ( libdir ) | ||
import DynFlags | import DynFlags | ||
main = | main = | ||
defaultErrorHandler | #if __GLASGOW_HASKELL__ > 704 | ||
defaultErrorHandler defaultFatalMessager defaultFlushOut $ do | |||
#else | |||
defaultErrorHandler defaultLogAction $ do | |||
#endif | |||
runGhc (Just libdir) $ do | runGhc (Just libdir) $ do | ||
dflags <- getSessionDynFlags | dflags <- getSessionDynFlags | ||
setSessionDynFlags dflags | setSessionDynFlags dflags | ||
target <- guessTarget "test_main.hs" Nothing | target <- guessTarget "test_main.hs" Nothing | ||
setTargets [target] | |||
load LoadAllTargets | load LoadAllTargets | ||
</haskell> | </haskell> | ||
The outermost function, < | The outermost function, <tt>defaultErrorHandler</tt>, sets up proper exception handlers and prints an error message and exits with exit code 1 if it encounters one of these exceptions. | ||
Most of GHC's high-level API requires access to a current session. Therefore, these functions require to be called inside a monad that is an instance of the <tt>GhcMonad</tt> typeclass. Two default implementations of this typeclass are <tt>Ghc</tt> and <tt>GhcT</tt>. In the above example we used the <tt>Ghc</tt> monad since we don't need to track any extra state. | Most of GHC's high-level API requires access to a current session. Therefore, these functions require to be called inside a monad that is an instance of the <tt>GhcMonad</tt> typeclass. Two default implementations of this typeclass are <tt>Ghc</tt> and <tt>GhcT</tt>. In the above example we used the <tt>Ghc</tt> monad since we don't need to track any extra state. | ||
The argument to <tt>runGhc</tt> is a bit tricky. GHC needs this to find its libraries, so the argument must refer to the directory that is printed by <tt>ghc --print-libdir</tt> for the ''same'' version of GHC that the program is being compiled with. Above we therefore use the <tt>ghc-paths</tt> package which provides this for us. | The argument to <tt>runGhc</tt> is a bit tricky. GHC needs this to find its libraries, so the argument must refer to the directory that is printed by <tt>ghc --print-libdir</tt> for the ''same'' version of GHC that the program is being compiled with. Above we therefore use the <tt>ghc-paths</tt> package which provides this for us. | ||
== Another example == | |||
Here we demonstrate calling [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/GHC.html#v:parseModule parseModule], [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/GHC.html#v:typecheckModule typecheckModule], [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/GHC.html#v:desugarModule desugarModule], [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/GHC.html#v:getNamesInScope getNamesInScope], and [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/GHC.html#v:getModuleGraph getModuleGraph]. This works for haskell-platform, ghc-7.0.3 to ghc-7.6.x. It also demonstrates how to enable some extensions. | |||
<haskell> | |||
--A.hs | |||
--invoke: ghci -package ghc A.hs | |||
{-# LANGUAGE CPP #-} | |||
import GHC | |||
import Outputable | |||
import GHC.Paths ( libdir ) | |||
--GHC.Paths is available via cabal install ghc-paths | |||
import DynFlags | |||
targetFile = "B.hs" | |||
main :: IO () | |||
main = do | |||
res <- example | |||
#if __GLASGOW_HASKELL__ > 704 | |||
str <- runGhc (Just libdir) $ do | |||
dflags <- getSessionDynFlags | |||
return $ showSDoc dflags $ ppr res | |||
putStrLn str | |||
#else | |||
putStrLn $ showSDoc ( ppr res ) | |||
#endif | |||
example = | |||
#if __GLASGOW_HASKELL__ > 704 | |||
defaultErrorHandler defaultFatalMessager defaultFlushOut $ do | |||
#else | |||
defaultErrorHandler defaultLogAction $ do | |||
#endif | |||
runGhc (Just libdir) $ do | |||
dflags <- getSessionDynFlags | |||
let dflags' = foldl xopt_set dflags | |||
[Opt_Cpp, Opt_ImplicitPrelude, Opt_MagicHash] | |||
setSessionDynFlags dflags' | |||
target <- guessTarget targetFile Nothing | |||
setTargets [target] | |||
load LoadAllTargets | |||
modSum <- getModSummary $ mkModuleName "B" | |||
p <- parseModule modSum | |||
t <- typecheckModule p | |||
d <- desugarModule t | |||
l <- loadModule d | |||
n <- getNamesInScope | |||
c <- return $ coreModule d | |||
g <- getModuleGraph | |||
mapM showModule g | |||
return $ (parsedSource d,"/n-----/n", typecheckedSource d) | |||
</haskell> | |||
<haskell> | |||
--B.hs | |||
module B where | |||
main = print "Hello, World!" | |||
</haskell> | |||
== Running interactive statements == | |||
Once you've loaded your module, you can run statements in that context, much as GHCi does, using the [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/GHC.html#v:runStmt runStmt] function. | |||
Given the modSum ModSummary obtained earlier, you can dump the results of your statement, if the result type is a Show instance: | |||
<haskell> | |||
run :: GhcMonad m => ModSummary -> String -> m () | |||
run modSum expr = do | |||
#if __GLASGOW_HASKELL__ < 704 | |||
setContext [ms_mod modSum] [] | |||
#else | |||
#if __GLASGOW_HASKELL__ < 706 | |||
setContext [IIModule $ ms_mod modSum] | |||
#else | |||
setContext [IIModule $ moduleName $ ms_mod modSum] | |||
#endif | |||
#endif | |||
rr<- runStmt expr RunToCompletion | |||
case rr of | |||
RunOk ns-> | |||
do | |||
let q=(qualName &&& qualModule) defaultUserStyle | |||
mapM_ (\n -> do | |||
mty <- lookupName n | |||
case mty of | |||
Just (AnId aid) -> do | |||
df <- getSessionDynFlags | |||
t <- gtry $ obtainTermFromId maxBound True aid | |||
evalDoc <- case t of | |||
Right term -> showTerm term | |||
Left exn -> return (text "*** Exception:" <+> | |||
text (show (exn :: SomeException))) | |||
liftIO $ putStrLn $ showSDocForUser df q evalDoc | |||
return () | |||
_ -> return () | |||
) ns | |||
RunException e -> liftIO $ print e | |||
_ -> return () | |||
</haskell> | |||
Note the call to [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/GHC.html#v:setContext setContext]. Basically then runStmt return the names bound by the statement, which you then lookup via [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/GHC.html#v:lookupName lookupName] and [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/GHC.html#v:obtainTermFromId obtainTermFromId] and print via [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/Debugger.html#v:showTerm showTerm]. | |||
=== Session parameters for interactive evaluation === | |||
The [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/GHC.html#t:DynFlags DynFlags] contain different flags that may be useful when working with the API, mainly to avoid generating the linker output. You need to be careful when you set them, though, since they can have long ranging effects. A common setting would be: | |||
<haskell> | |||
setSessionDynFlags oldFlgs {hscTarget = HscInterpreted, ghcLink = LinkInMemory , ghcMode = CompManager } | |||
</haskell> | |||
* '''HscInterpreted''' means you can still get TemplateHaskell support but you're not generating output code | |||
* '''LinkInMemory''' is required to be able to reload modules properly. Using '''NoLink''' will break that: reloading a module won't allow allow to run interactive statements on the new version of the module | |||
* '''CompManager''' ensures dependent modules are built and loaded if needed. | |||
== Libraries == | |||
* [https://hackage.haskell.org/package/plugins plugins], dynamic linking and runtime evaluation of Haskell, and C, including dependency chasing and package resolution. The current version (2017-01-26, version 1.5.5.0) is not compilable on Windows systems, or with GHC >= 8 | |||
* [https://hackage.haskell.org/package/hint hint], this library defines an Interpreter monad. It allows to load Haskell modules, browse them, type-check and evaluate strings with Haskell expressions and even coerce them into values. | |||
== Further reading == | |||
* [https://downloads.haskell.org/~ghc/latest/docs/html/ GHC API documentation] (click on the GHC API link on that page.) | |||
* Blog posts from "(parentheses)": [http://parenz.wordpress.com/2013/08/17/ghc-api-interpreted-compiled-and-package-modules/ GHC API: Interpreted, compiled and package modules], [http://parenz.wordpress.com/2013/07/29/ghc-packagedb/ Adding a package database to the GHC API session], [http://parenz.wordpress.com/2013/07/23/on-custom-error-handlers-for-ghc-api/ On custom error handlers for the GHC API]. | |||
* [http://mistuke.wordpress.com/category/vsx/ Great blog post] about using the GHC API to get "QuickInfo" in a Visual Studio binding for Haskell. |
Latest revision as of 15:40, 22 December 2017
For instructions on the GHC API with GHC 6.8 or older please refer to GHC/As a library (up to 6.8)
Introduction
GHC's functionality can be useful for more things than just compiling Haskell programs. Important use cases are programs that analyse (and perhaps transform) Haskell code. Others include loading Haskell code dynamically in a GHCi-like manner. For this reason, a lot of GHC's features can be accessed by programs which import the ghc package.
The instructions on this page concern the API of GHC 6.10.1 and above. Please note that the GHC API is still in flux and may change quite significantly between major releases while we (the GHC team) provide new features or simplify certain aspects.
Getting Started
To use the GHC API you need GHC 6.10.1 or above and import the ghc package.
ghc -package ghc my_program.hs
In most cases you probably also want to use the ghc-paths package.
Most of the common functionality is provided by the GHC module, but occasionally you may have to import other modules. See the GHC's haddock documentation for a list of these modules. One good entry point into the docs is GHC.
A Simple Example
The following little program essentially does what ghc --make does.
{-# LANGUAGE CPP #-}
import GHC
import GHC.Paths ( libdir )
import DynFlags
main =
#if __GLASGOW_HASKELL__ > 704
defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
#else
defaultErrorHandler defaultLogAction $ do
#endif
runGhc (Just libdir) $ do
dflags <- getSessionDynFlags
setSessionDynFlags dflags
target <- guessTarget "test_main.hs" Nothing
setTargets [target]
load LoadAllTargets
The outermost function, defaultErrorHandler, sets up proper exception handlers and prints an error message and exits with exit code 1 if it encounters one of these exceptions.
Most of GHC's high-level API requires access to a current session. Therefore, these functions require to be called inside a monad that is an instance of the GhcMonad typeclass. Two default implementations of this typeclass are Ghc and GhcT. In the above example we used the Ghc monad since we don't need to track any extra state.
The argument to runGhc is a bit tricky. GHC needs this to find its libraries, so the argument must refer to the directory that is printed by ghc --print-libdir for the same version of GHC that the program is being compiled with. Above we therefore use the ghc-paths package which provides this for us.
Another example
Here we demonstrate calling parseModule, typecheckModule, desugarModule, getNamesInScope, and getModuleGraph. This works for haskell-platform, ghc-7.0.3 to ghc-7.6.x. It also demonstrates how to enable some extensions.
--A.hs
--invoke: ghci -package ghc A.hs
{-# LANGUAGE CPP #-}
import GHC
import Outputable
import GHC.Paths ( libdir )
--GHC.Paths is available via cabal install ghc-paths
import DynFlags
targetFile = "B.hs"
main :: IO ()
main = do
res <- example
#if __GLASGOW_HASKELL__ > 704
str <- runGhc (Just libdir) $ do
dflags <- getSessionDynFlags
return $ showSDoc dflags $ ppr res
putStrLn str
#else
putStrLn $ showSDoc ( ppr res )
#endif
example =
#if __GLASGOW_HASKELL__ > 704
defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
#else
defaultErrorHandler defaultLogAction $ do
#endif
runGhc (Just libdir) $ do
dflags <- getSessionDynFlags
let dflags' = foldl xopt_set dflags
[Opt_Cpp, Opt_ImplicitPrelude, Opt_MagicHash]
setSessionDynFlags dflags'
target <- guessTarget targetFile Nothing
setTargets [target]
load LoadAllTargets
modSum <- getModSummary $ mkModuleName "B"
p <- parseModule modSum
t <- typecheckModule p
d <- desugarModule t
l <- loadModule d
n <- getNamesInScope
c <- return $ coreModule d
g <- getModuleGraph
mapM showModule g
return $ (parsedSource d,"/n-----/n", typecheckedSource d)
--B.hs
module B where
main = print "Hello, World!"
Running interactive statements
Once you've loaded your module, you can run statements in that context, much as GHCi does, using the runStmt function.
Given the modSum ModSummary obtained earlier, you can dump the results of your statement, if the result type is a Show instance:
run :: GhcMonad m => ModSummary -> String -> m ()
run modSum expr = do
#if __GLASGOW_HASKELL__ < 704
setContext [ms_mod modSum] []
#else
#if __GLASGOW_HASKELL__ < 706
setContext [IIModule $ ms_mod modSum]
#else
setContext [IIModule $ moduleName $ ms_mod modSum]
#endif
#endif
rr<- runStmt expr RunToCompletion
case rr of
RunOk ns->
do
let q=(qualName &&& qualModule) defaultUserStyle
mapM_ (\n -> do
mty <- lookupName n
case mty of
Just (AnId aid) -> do
df <- getSessionDynFlags
t <- gtry $ obtainTermFromId maxBound True aid
evalDoc <- case t of
Right term -> showTerm term
Left exn -> return (text "*** Exception:" <+>
text (show (exn :: SomeException)))
liftIO $ putStrLn $ showSDocForUser df q evalDoc
return ()
_ -> return ()
) ns
RunException e -> liftIO $ print e
_ -> return ()
Note the call to setContext. Basically then runStmt return the names bound by the statement, which you then lookup via lookupName and obtainTermFromId and print via showTerm.
Session parameters for interactive evaluation
The DynFlags contain different flags that may be useful when working with the API, mainly to avoid generating the linker output. You need to be careful when you set them, though, since they can have long ranging effects. A common setting would be:
setSessionDynFlags oldFlgs {hscTarget = HscInterpreted, ghcLink = LinkInMemory , ghcMode = CompManager }
- HscInterpreted means you can still get TemplateHaskell support but you're not generating output code
- LinkInMemory is required to be able to reload modules properly. Using NoLink will break that: reloading a module won't allow allow to run interactive statements on the new version of the module
- CompManager ensures dependent modules are built and loaded if needed.
Libraries
- plugins, dynamic linking and runtime evaluation of Haskell, and C, including dependency chasing and package resolution. The current version (2017-01-26, version 1.5.5.0) is not compilable on Windows systems, or with GHC >= 8
- hint, this library defines an Interpreter monad. It allows to load Haskell modules, browse them, type-check and evaluate strings with Haskell expressions and even coerce them into values.
Further reading
- GHC API documentation (click on the GHC API link on that page.)
- Blog posts from "(parentheses)": GHC API: Interpreted, compiled and package modules, Adding a package database to the GHC API session, On custom error handlers for the GHC API.
- Great blog post about using the GHC API to get "QuickInfo" in a Visual Studio binding for Haskell.