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

167 lines
5.3 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 Language.Haskell.GhcMod.DynFlags
import qualified Language.Haskell.GhcMod.Gap as Gap
import Language.Haskell.GhcMod.Types
import Control.Applicative ((<$>))
import Control.Monad (void)
import Distribution.Package (InstalledPackageId(..))
2014-03-27 06:43:33 +00:00
import Data.Maybe (isJust, fromJust)
import qualified Data.Map as M
import GHC (DynFlags(..))
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-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 = [".","..","../..","../../..","../../../..","../../../../.."]
-- | 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
----------------------------------------------------------------
-- 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"