Move lots of stuff to GhcMod

- Generalize many signatures to GhcMonad m
This commit is contained in:
Alejandro Serrano
2014-06-28 21:43:51 +02:00
parent 871f72fca4
commit 1b66f65b48
9 changed files with 83 additions and 78 deletions

View File

@@ -10,12 +10,13 @@ import Data.Function (on)
import Data.List (sortBy)
import Data.Maybe (catMaybes)
import Exception (ghandle, SomeException(..))
import GHC (Ghc, LHsBind, LHsExpr, LPat, Id, TypecheckedModule(..), SrcSpan, Type)
import GHC (GhcMonad, LHsBind, LHsExpr, LPat, Id, TypecheckedModule(..), SrcSpan, Type)
import qualified GHC as G
import Language.Haskell.GhcMod.Doc (showPage)
import Language.Haskell.GhcMod.GHCApi
import Language.Haskell.GhcMod.Gap (HasType(..))
import qualified Language.Haskell.GhcMod.Gap as Gap
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.SrcUtils
import Language.Haskell.GhcMod.Types
import Language.Haskell.GhcMod.Convert
@@ -28,16 +29,17 @@ infoExpr :: Options
-> FilePath -- ^ A target file.
-> Expression -- ^ A Haskell expression.
-> IO String
infoExpr opt cradle file expr = withGHC' $ do
infoExpr opt cradle file expr = runGhcMod opt $ do
initializeFlagsWithCradle opt cradle
info opt file expr
info file expr
-- | Obtaining information of a target expression. (GHCi's info:)
info :: Options
-> FilePath -- ^ A target file.
info :: FilePath -- ^ A target file.
-> Expression -- ^ A Haskell expression.
-> Ghc String
info opt file expr = convert opt <$> ghandle handler body
-> GhcMod String
info file expr = do
opt <- options
convert opt <$> ghandle handler body
where
body = inModuleContext file $ \dflag style -> do
sdoc <- Gap.infoThing expr
@@ -53,17 +55,18 @@ typeExpr :: Options
-> Int -- ^ Line number.
-> Int -- ^ Column number.
-> IO String
typeExpr opt cradle file lineNo colNo = withGHC' $ do
typeExpr opt cradle file lineNo colNo = runGhcMod opt $ do
initializeFlagsWithCradle opt cradle
types opt file lineNo colNo
types file lineNo colNo
-- | Obtaining type of a target expression. (GHCi's type:)
types :: Options
-> FilePath -- ^ A target file.
types :: FilePath -- ^ A target file.
-> Int -- ^ Line number.
-> Int -- ^ Column number.
-> Ghc String
types opt file lineNo colNo = convert opt <$> ghandle handler body
-> GhcMod String
types file lineNo colNo = do
opt <- options
convert opt <$> ghandle handler body
where
body = inModuleContext file $ \dflag style -> do
modSum <- Gap.fileModSummary file
@@ -71,7 +74,7 @@ types opt file lineNo colNo = convert opt <$> ghandle handler body
return $ map (toTup dflag style) $ sortBy (cmp `on` fst) srcSpanTypes
handler (SomeException _) = return []
getSrcSpanType :: G.ModSummary -> Int -> Int -> Ghc [(SrcSpan, Type)]
getSrcSpanType :: GhcMonad m => G.ModSummary -> Int -> Int -> m [(SrcSpan, Type)]
getSrcSpanType modSum lineNo colNo = do
p <- G.parseModule modSum
tcm@TypecheckedModule{tm_typechecked_source = tcs} <- G.typecheckModule p