Remove withGhc and withGhc', they're not used anymore.

This commit is contained in:
Daniel Gröber 2014-07-11 10:40:09 +02:00
parent 9f94bc863c
commit 73bf4cbc4e
2 changed files with 3 additions and 27 deletions

View File

@ -1,9 +1,7 @@
{-# LANGUAGE ScopedTypeVariables, RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables, RecordWildCards #-}
module Language.Haskell.GhcMod.GHCApi ( module Language.Haskell.GhcMod.GHCApi (
withGHC initializeFlagsWithCradle
, withGHC'
, initializeFlagsWithCradle
, setTargetFiles , setTargetFiles
, getDynamicFlags , getDynamicFlags
, systemLibDir , systemLibDir
@ -39,26 +37,6 @@ systemLibDir = libdir
---------------------------------------------------------------- ----------------------------------------------------------------
-- | Converting the 'Ghc' monad to the 'IO' monad.
withGHC :: FilePath -- ^ A target file displayed in an error message.
-> Ghc a -- ^ 'Ghc' actions created by the Ghc utilities.
-> IO a
withGHC file body = ghandle ignore $ withGHC' body
where
ignore :: SomeException -> IO a
ignore e = do
hPutStr stderr $ file ++ ":0:0:Error:"
hPrint stderr e
exitSuccess
withGHC' :: Ghc a -> IO a
withGHC' body = do
G.runGhc (Just systemLibDir) $ do
dflags <- G.getSessionDynFlags
G.defaultCleanupHandler dflags body
----------------------------------------------------------------
importDirs :: [IncludeDir] importDirs :: [IncludeDir]
importDirs = [".","..","../..","../../..","../../../..","../../../../.."] importDirs = [".","..","../..","../../..","../../../..","../../../../.."]
@ -107,6 +85,7 @@ initSession build Options {..} CompilerOptions {..} = do
$ setEmptyLogger $ setEmptyLogger
$ Gap.addPackageFlags depPackages df) $ Gap.addPackageFlags depPackages df)
setEmptyLogger :: DynFlags -> DynFlags setEmptyLogger :: DynFlags -> DynFlags
setEmptyLogger df = Gap.setLogAction df $ \_ _ _ _ _ -> return () setEmptyLogger df = Gap.setLogAction df $ \_ _ _ _ _ -> return ()

View File

@ -1,9 +1,6 @@
module Language.Haskell.GhcMod.Ghc ( module Language.Haskell.GhcMod.Ghc (
-- * Converting the 'Ghc' monad to the 'IO' monad
withGHC
, withGHC'
-- * 'SymMdlDb' -- * 'SymMdlDb'
, Symbol Symbol
, SymMdlDb , SymMdlDb
, getSymMdlDb , getSymMdlDb
, lookupSym , lookupSym