Difference between revisions of "GHC/As a library"

From HaskellWiki
< GHC
Jump to navigation Jump to search
m
(Undo revision 56433 by DaniilFrumin (talk))
(19 intermediate revisions by 13 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 not 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.
+
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.
   
   
Line 18: Line 18:
 
In most cases you probably also want to use the [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ghc-paths ghc-paths package].
 
In most cases you probably also want to use the [http://hackage.haskell.org/cgi-bin/hackage-scripts/package/ghc-paths ghc-paths 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 [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/index.html 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].
 
''FIXME: link to haddock docs''
 
 
 
== A Simple Example ==
 
== A Simple Example ==
   
Line 27: Line 24:
   
 
<haskell>
 
<haskell>
  +
{-# LANGUAGE CPP #-}
 
import GHC
 
import GHC
 
import GHC.Paths ( libdir )
 
import GHC.Paths ( libdir )
import DynFlags ( defaultDynFlags )
+
import DynFlags
  +
 
 
main =
 
main =
  +
#if __GLASGOW_HASKELL__ > 704
defaultErrorHandler defaultDynFlags $ do
 
  +
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
setTarget [target]
+
setTargets [target]
 
load LoadAllTargets
 
load LoadAllTargets
 
</haskell>
 
</haskell>
   
The outermost function, <haskell>defaultErrorHandler</haskell>, sets up proper exception handlers and prints an error message and exits with exit code 1 if it encounters one of these exceptions.
+
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 = do
  +
res <- example
  +
#if __GLASGOW_HASKELL__ > 704
  +
putStrLn $ showSDoc tracingDynFlags ( ppr res )
  +
#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>
  +
  +
== Links ==
  +
  +
* [http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/index.html GHC API haddock]
  +
* [http://mistuke.wordpress.com/category/vsx/ Great blog post] about using the GHC API to get "QuickInfo" in a Visual Studio binding for Haskell.

Revision as of 20:37, 22 July 2013

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 = do
   res <- example
#if __GLASGOW_HASKELL__ > 704
   putStrLn $ showSDoc tracingDynFlags ( ppr res )
#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!"

Links