ghc-mod/Language/Haskell/GhcMod/GHCApi.hs

264 lines
8.6 KiB
Haskell
Raw Normal View History

2014-04-23 01:41:28 +00:00
{-# LANGUAGE ScopedTypeVariables, RecordWildCards #-}
2013-04-10 06:02:49 +00:00
2013-05-17 01:00:01 +00:00
module Language.Haskell.GhcMod.GHCApi (
initializeFlagsWithCradle
, setTargetFiles
2013-03-04 04:41:56 +00:00
, getDynamicFlags
, systemLibDir
, withDynFlags
2014-05-09 14:45:34 +00:00
, withCmdFlags
2014-04-28 03:52:09 +00:00
, setNoWaringFlags
, setAllWaringFlags
, ghcPkgDb
, package
, modules
, findModule
, moduleInfo
, localModuleInfo
, bindings
2013-03-04 04:41:56 +00:00
) where
2012-02-14 07:09:53 +00:00
import Language.Haskell.GhcMod.CabalApi
import Language.Haskell.GhcMod.GHCChoice
import Language.Haskell.GhcMod.GhcPkg
import qualified Language.Haskell.GhcMod.Gap as Gap
import Language.Haskell.GhcMod.Types
import Control.Applicative ((<$>))
2014-04-26 12:59:06 +00:00
import Control.Monad (forM, void)
import Distribution.Package (InstalledPackageId(..))
2014-03-27 06:43:33 +00:00
import Data.Maybe (isJust, fromJust)
import qualified Data.Map.Strict as M
import GHC (DynFlags(..), GhcLink(..), HscTarget(..), LoadHowMuch(..))
2014-03-27 06:43:33 +00:00
import qualified GHC as G
import GhcMonad
import GHC.Paths (libdir)
import qualified Packages as G
import qualified Module as G
import qualified OccName as G
2014-04-28 03:52:09 +00:00
import System.IO.Unsafe (unsafePerformIO)
----------------------------------------------------------------
2014-03-26 03:09:02 +00:00
-- | Obtaining the directory for system libraries.
systemLibDir :: FilePath
systemLibDir = libdir
2012-02-14 07:09:53 +00:00
----------------------------------------------------------------
importDirs :: [IncludeDir]
importDirs = [".","..","../..","../../..","../../../..","../../../../.."]
data Build = CabalPkg | SingleFile deriving Eq
-- | Initialize the 'DynFlags' relating to the compilation of a single
-- file or GHC session according to the 'Cradle' and 'Options'
-- provided.
2014-04-23 01:41:28 +00:00
initializeFlagsWithCradle :: GhcMonad m
=> Options
-> Cradle
-> m ()
initializeFlagsWithCradle opt cradle
| cabal = withCabal |||> withSandbox
| otherwise = withSandbox
where
2013-09-19 07:21:48 +00:00
mCradleFile = cradleCabalFile cradle
cabal = isJust mCradleFile
ghcopts = ghcOpts opt
2013-04-10 06:02:49 +00:00
withCabal = do
2013-09-19 07:21:48 +00:00
pkgDesc <- liftIO $ parseCabalFile $ fromJust mCradleFile
compOpts <- liftIO $ getCompilerOptions ghcopts cradle pkgDesc
initSession CabalPkg opt compOpts
withSandbox = initSession SingleFile opt compOpts
2013-09-19 06:58:50 +00:00
where
pkgOpts = ghcDbStackOpts $ cradlePkgDbStack cradle
compOpts
| null pkgOpts = CompilerOptions ghcopts importDirs []
| otherwise = CompilerOptions (ghcopts ++ pkgOpts) [wdir,rdir] []
wdir = cradleCurrentDir cradle
rdir = cradleRootDir cradle
2013-03-04 04:41:56 +00:00
----------------------------------------------------------------
2014-04-23 01:41:28 +00:00
initSession :: GhcMonad m
=> Build
-> Options
2013-09-19 06:58:50 +00:00
-> CompilerOptions
-> m ()
initSession build Options {..} CompilerOptions {..} = do
2014-04-23 01:41:28 +00:00
df <- G.getSessionDynFlags
void $ G.setSessionDynFlags =<< (addCmdOpts ghcOptions
2014-04-23 01:41:28 +00:00
$ setLinkerOptions
$ setIncludeDirs includeDirs
$ setBuildEnv build
$ setEmptyLogger
2014-04-23 01:41:28 +00:00
$ Gap.addPackageFlags depPackages df)
2013-03-04 04:41:56 +00:00
setEmptyLogger :: DynFlags -> DynFlags
setEmptyLogger df = Gap.setLogAction df $ \_ _ _ _ _ -> return ()
2013-03-04 03:53:28 +00:00
2013-03-13 04:17:22 +00:00
----------------------------------------------------------------
2014-04-23 01:41:28 +00:00
-- we don't want to generate object code so we compile to bytecode
-- (HscInterpreted) which implies LinkInMemory
-- HscInterpreted
setLinkerOptions :: DynFlags -> DynFlags
setLinkerOptions df = df {
ghcLink = LinkInMemory
, hscTarget = HscInterpreted
}
setIncludeDirs :: [IncludeDir] -> DynFlags -> DynFlags
setIncludeDirs idirs df = df { importPaths = idirs }
setBuildEnv :: Build -> DynFlags -> DynFlags
setBuildEnv build = setHideAllPackages build . setCabalPackage build
-- At the moment with this option set ghc only prints different error messages,
-- suggesting the user to add a hidden package to the build-depends in his cabal
-- file for example
setCabalPackage :: Build -> DynFlags -> DynFlags
setCabalPackage CabalPkg df = Gap.setCabalPkg df
setCabalPackage _ df = df
-- | Enable hiding of all package not explicitly exposed (like Cabal does)
setHideAllPackages :: Build -> DynFlags -> DynFlags
setHideAllPackages CabalPkg df = Gap.setHideAllPackages df
setHideAllPackages _ df = df
-- | Parse command line ghc options and add them to the 'DynFlags' passed
addCmdOpts :: GhcMonad m => [GHCOption] -> DynFlags -> m DynFlags
addCmdOpts cmdOpts df =
tfst <$> G.parseDynamicFlags df (map G.noLoc cmdOpts)
2013-03-05 07:16:27 +00:00
where
tfst (a,_,_) = a
2012-02-14 07:09:53 +00:00
----------------------------------------------------------------
2014-04-28 12:51:39 +00:00
-- | Set the files as targets and load them.
2013-09-16 02:00:39 +00:00
setTargetFiles :: (GhcMonad m) => [FilePath] -> m ()
setTargetFiles files = do
2014-03-27 06:43:33 +00:00
targets <- forM files $ \file -> G.guessTarget file Nothing
2014-04-26 12:59:06 +00:00
G.setTargets targets
void $ G.load LoadAllTargets
2013-03-04 02:21:41 +00:00
----------------------------------------------------------------
2013-09-05 05:35:28 +00:00
-- | Return the 'DynFlags' currently in use in the GHC session.
2013-03-04 04:41:56 +00:00
getDynamicFlags :: IO DynFlags
getDynamicFlags = do
G.runGhc (Just systemLibDir) G.getSessionDynFlags
2014-05-14 16:05:40 +00:00
withDynFlags :: GhcMonad m
=> (DynFlags -> DynFlags)
-> m a
-> m a
withDynFlags setFlags body = G.gbracket setup teardown (\_ -> body)
where
setup = do
2014-05-14 16:05:40 +00:00
dflags <- G.getSessionDynFlags
void $ G.setSessionDynFlags (setFlags dflags)
return dflags
teardown = void . G.setSessionDynFlags
2014-04-26 13:51:29 +00:00
2014-05-14 16:05:40 +00:00
withCmdFlags :: GhcMonad m => [GHCOption] -> m a -> m a
2014-05-09 14:45:34 +00:00
withCmdFlags flags body = G.gbracket setup teardown (\_ -> body)
where
setup = do
2014-05-14 16:05:40 +00:00
dflags <- G.getSessionDynFlags >>= addCmdOpts flags
void $ G.setSessionDynFlags dflags
return dflags
2014-05-09 14:45:34 +00:00
teardown = void . G.setSessionDynFlags
2014-04-26 13:51:29 +00:00
----------------------------------------------------------------
2014-04-28 12:51:39 +00:00
-- | Set 'DynFlags' equivalent to "-w:".
2014-04-28 03:52:09 +00:00
setNoWaringFlags :: DynFlags -> DynFlags
2014-04-28 05:36:55 +00:00
setNoWaringFlags df = df { warningFlags = Gap.emptyWarnFlags}
2014-04-28 03:52:09 +00:00
2014-04-28 12:51:39 +00:00
-- | Set 'DynFlags' equivalent to "-Wall".
2014-04-28 03:52:09 +00:00
setAllWaringFlags :: DynFlags -> DynFlags
setAllWaringFlags df = df { warningFlags = allWarningFlags }
2014-04-28 05:36:55 +00:00
allWarningFlags :: Gap.WarnFlags
2014-04-28 03:52:09 +00:00
allWarningFlags = unsafePerformIO $ do
G.runGhc (Just systemLibDir) $ do
2014-04-28 03:52:09 +00:00
df <- G.getSessionDynFlags
df' <- addCmdOpts ["-Wall"] df
return $ G.warningFlags df'
----------------------------------------------------------------
-- get Packages,Modules,Bindings
ghcPkgDb :: GhcMonad m => m PkgDb
ghcPkgDb = M.fromList <$>
maybe [] (map toKv . filterInternal) <$> pkgDatabase <$> G.getSessionDynFlags
where
toKv pkg = (fromInstalledPackageId $ G.installedPackageId pkg, pkg)
filterInternal =
filter ((/= InstalledPackageId "builtin_rts") . G.installedPackageId)
package :: G.PackageConfig -> Package
package = fromInstalledPackageId . G.installedPackageId
modules :: G.PackageConfig -> [ModuleString]
modules = map G.moduleNameString . G.exposedModules
findModule :: ModuleString -> PkgDb -> [Package]
findModule m db = do
M.elems $ package `M.map` (containsModule `M.filter` db)
where
containsModule :: G.PackageConfig -> Bool
containsModule pkgConf =
G.mkModuleName m `elem` G.exposedModules pkgConf
ghcPkgId :: Package -> G.PackageId
ghcPkgId (name,_,_) =
-- TODO: Adding the package version too breaks 'findModule' for some reason
-- this isn't a big deal since in the common case where we're in a cabal
-- project we just use cabal's view of package dependencies anyways so we're
-- guaranteed to only have one version of each package exposed. However when
-- we're operating without a cabal project this will probaly cause trouble.
G.stringToPackageId name
type Binding = String
-- | @moduleInfo mpkg module@. @mpkg@ should be 'Nothing' iff. moduleInfo
-- should look for @module@ in the working directory.
--
-- To map a 'ModuleString' to a package see 'findModule'
moduleInfo :: GhcMonad m
=> Maybe Package
-> ModuleString
-> m (Maybe G.ModuleInfo)
moduleInfo mpkg mdl = do
let mdlName = G.mkModuleName mdl
mfsPkgId = G.packageIdFS . ghcPkgId <$> mpkg
loadLocalModule
G.findModule mdlName mfsPkgId >>= G.getModuleInfo
where
loadLocalModule = case mpkg of
Just _ -> return ()
Nothing -> setTargetFiles [mdl]
localModuleInfo :: GhcMonad m => ModuleString -> m (Maybe G.ModuleInfo)
localModuleInfo mdl = moduleInfo Nothing mdl
bindings :: G.ModuleInfo -> [Binding]
bindings minfo = do
map (G.occNameString . G.getOccName) $ G.modInfoExports minfo
----------------------------------------------------------------
-- for PkgDoc
-- import Distribution.InstalledPackageInfo (showInstalledPackageInfoField)
-- haddockHtml :: GhcMonad m => Package -> m String
-- haddockHtml pkg = do
-- extractField info . fromJust . lookup pkg <$> ghcPkgDb
-- where
-- extractField = fromJust $ showInstalledPackageInfoField "haddock-html"