Skip to content

Commit

Permalink
Found some interesting GHC API calls
Browse files Browse the repository at this point in the history
  • Loading branch information
jacobstanley committed Sep 25, 2011
1 parent 3282092 commit 84519a3
Show file tree
Hide file tree
Showing 3 changed files with 44 additions and 1 deletion.
6 changes: 6 additions & 0 deletions examples/A.hs
@@ -0,0 +1,6 @@
module A where

f :: Int -> Int -> Int
f x y = x + y

data SomeData = NotReally | JustOne Int | JustTwo Int Double
2 changes: 2 additions & 0 deletions quick-version.cabal
Expand Up @@ -19,4 +19,6 @@ executable quickver

build-depends:
base == 4.*
, ghc == 7.2.*
, ghc-paths == 0.1.*
, QuickCheck == 2.4.*
37 changes: 36 additions & 1 deletion src/Main.hs
@@ -1,4 +1,39 @@
module Main (main) where

import qualified DynFlags as G
import Data.Maybe (catMaybes)
import qualified DataCon as G
import qualified GHC as G
import GHC.Paths (libdir)
import qualified Outputable as G
import qualified TyCon as G
import qualified Var as G

main :: IO ()
main = putStrLn "Quick Version 0.1"
main = do
res <- example
mapM_ (putStrLn . G.showSDoc . G.ppr) res

example :: IO [G.Type]
example =
G.defaultErrorHandler G.defaultLogAction $ do
G.runGhc (Just libdir) $ do
dflags <- G.getSessionDynFlags
G.setSessionDynFlags dflags
target <- G.guessTarget "examples/A.hs" Nothing
G.setTargets [target]
G.load G.LoadAllTargets

m <- G.findModule (G.mkModuleName "A") Nothing
(Just info) <- G.getModuleInfo m

exports <- mapM (G.lookupName) (G.modInfoExports info)

return $ map extractType $ catMaybes exports

extractType :: G.TyThing -> G.Type
extractType (G.AnId var) = G.varType var
extractType (G.ATyCon tycon) = G.tyConKind tycon
extractType (G.ADataCon dcon) = G.dataConRepType dcon
extractType (G.ACoAxiom _) = error "extractType: ACoAxiom"
extractType (G.AClass _) = error "extractType: AClass"

0 comments on commit 84519a3

Please sign in to comment.