ghc-mod/GHCApi.hs

79 lines
2.5 KiB
Haskell
Raw Normal View History

2012-02-14 07:09:53 +00:00
module GHCApi where
2012-02-15 05:52:48 +00:00
import Control.Applicative
import Control.Exception
2012-02-14 07:09:53 +00:00
import CoreMonad
import DynFlags
import ErrMsg
import Exception
import GHC
import GHC.Paths (libdir)
import System.Exit
import System.IO
2012-02-14 07:09:53 +00:00
import Types
----------------------------------------------------------------
2012-02-15 05:52:48 +00:00
withGHC :: Alternative m => Ghc (m a) -> IO (m a)
2012-12-07 05:27:02 +00:00
withGHC = withGHC' "Dummy"
withGHC' :: Alternative m => FilePath -> Ghc (m a) -> IO (m a)
withGHC' file body = ghandle ignore $ runGhc (Just libdir) $ do
2012-02-14 10:14:21 +00:00
dflags <- getSessionDynFlags
defaultCleanupHandler dflags body
2012-02-14 07:09:53 +00:00
where
2012-02-15 05:52:48 +00:00
ignore :: Alternative m => SomeException -> IO (m a)
ignore e = do
2012-12-07 05:27:02 +00:00
hPutStr stderr $ file ++ ":0:0:Error:"
hPrint stderr e
2012-06-04 06:40:26 +00:00
exitSuccess
2012-02-14 07:09:53 +00:00
----------------------------------------------------------------
initSession0 :: Options -> Ghc [PackageId]
initSession0 opt = getSessionDynFlags >>=
(>>= setSessionDynFlags) . setGhcFlags opt
initSession :: Options -> [String] -> [FilePath] -> Maybe [String] -> Bool -> Ghc LogReader
initSession opt cmdOpts idirs mayPkgs logging = do
2012-02-14 07:09:53 +00:00
dflags <- getSessionDynFlags
let opts = map noLoc cmdOpts
(dflags',_,_) <- parseDynamicFlags dflags opts
(dflags'',readLog) <- liftIO . (>>= setLogger logging)
. setGhcFlags opt . setFlags opt dflags' idirs $ mayPkgs
2012-08-06 00:43:47 +00:00
_ <- setSessionDynFlags dflags''
2012-02-14 07:09:53 +00:00
return readLog
----------------------------------------------------------------
setFlags :: Options -> DynFlags -> [FilePath] -> Maybe [String] -> DynFlags
setFlags opt d idirs mayPkgs
2012-02-27 03:37:11 +00:00
| expandSplice opt = dopt_set d' Opt_D_dump_splices
| otherwise = d'
2012-02-14 07:09:53 +00:00
where
d' = maySetExpose $ d {
importPaths = idirs
2012-03-23 17:05:38 +00:00
, ghcLink = LinkInMemory
2012-02-14 07:09:53 +00:00
, hscTarget = HscInterpreted
2012-02-27 03:37:11 +00:00
, flags = flags d
2012-02-14 07:09:53 +00:00
}
-- Do hide-all only when depend packages specified
maySetExpose df = maybe df (\x -> (dopt_set df Opt_HideAllPackages) {
packageFlags = map ExposePackage x ++ packageFlags df
}) mayPkgs
2012-02-14 07:09:53 +00:00
ghcPackage :: PackageFlag
ghcPackage = ExposePackage "ghc"
setGhcFlags :: Monad m => Options -> DynFlags -> m DynFlags
setGhcFlags opt flagset =
do (flagset',_,_) <- parseDynamicFlags flagset (map noLoc (ghcOpts opt))
return flagset'
----------------------------------------------------------------
setTargetFile :: (GhcMonad m) => String -> m ()
setTargetFile file = do
target <- guessTarget file Nothing
setTargets [target]