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

364 lines
10 KiB
Haskell
Raw Normal View History

{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, CPP #-}
2012-02-14 07:09:53 +00:00
2013-05-17 01:00:01 +00:00
module Language.Haskell.GhcMod.Gap (
Language.Haskell.GhcMod.Gap.ClsInst
, mkTarget
2013-03-12 13:15:23 +00:00
, withStyle
, setLogAction
, supportedExtensions
2012-02-14 07:09:53 +00:00
, getSrcSpan
, getSrcFile
, setCtx
, fOptions
, toStringBuffer
, showSeverityCaption
, setCabalPkg
, addDevPkgs
, filterOutChildren
, infoThing
, pprInfo
, HasType(..)
2013-11-19 03:28:59 +00:00
, errorMsgSpan
2013-11-19 03:35:42 +00:00
, typeForUser
2013-11-19 03:54:08 +00:00
, deSugar
2012-02-14 07:09:53 +00:00
#if __GLASGOW_HASKELL__ >= 702
#else
, module Pretty
#endif
, showDocWith
2014-02-06 12:34:40 +00:00
, GapThing(..)
, fromTyThing
2014-03-27 11:54:18 +00:00
, dumpSplicesFlag
2012-02-14 07:09:53 +00:00
) where
import Control.Applicative hiding (empty)
2014-03-27 07:02:16 +00:00
import Control.Monad (filterM)
import CoreSyn (CoreExpr)
import Data.List (intersperse)
import Data.Maybe (catMaybes)
import Data.Time.Clock (UTCTime)
2014-02-06 13:09:00 +00:00
import DataCon (dataConRepType)
2013-11-19 03:54:08 +00:00
import Desugar (deSugarExpr)
2012-02-14 07:09:53 +00:00
import DynFlags
import ErrUtils
2012-02-14 07:09:53 +00:00
import FastString
2013-07-14 08:07:30 +00:00
import HscTypes
2013-05-17 01:00:01 +00:00
import Language.Haskell.GhcMod.GHCChoice
2013-07-02 09:29:08 +00:00
import Language.Haskell.GhcMod.Types hiding (convert)
2013-07-14 08:07:30 +00:00
import NameSet
2012-02-14 07:09:53 +00:00
import Outputable
2013-07-14 08:07:30 +00:00
import PprTyThing
2012-02-14 07:09:53 +00:00
import StringBuffer
import TcType
2014-02-06 13:09:00 +00:00
import Var (varType)
2012-02-14 07:09:53 +00:00
import qualified InstEnv
import qualified Pretty
import qualified StringBuffer as SB
#if __GLASGOW_HASKELL__ >= 707
import FamInstEnv
import ConLike (ConLike(..))
2014-02-06 13:12:07 +00:00
import PatSyn (patSynType)
2014-01-08 00:55:06 +00:00
#else
import TcRnTypes
#endif
#if __GLASGOW_HASKELL__ >= 706
import GHC hiding (ClsInst)
#else
import GHC hiding (Instance)
#endif
2014-03-27 06:08:07 +00:00
#if __GLASGOW_HASKELL__ < 702
2012-02-14 07:09:53 +00:00
import CoreMonad (liftIO)
import Pretty
#endif
#if __GLASGOW_HASKELL__ < 706
2013-07-02 09:29:08 +00:00
import Control.Arrow hiding ((<+>))
import Data.Convertible
#endif
----------------------------------------------------------------
----------------------------------------------------------------
--
#if __GLASGOW_HASKELL__ >= 706
type ClsInst = InstEnv.ClsInst
#else
type ClsInst = InstEnv.Instance
#endif
mkTarget :: TargetId -> Bool -> Maybe (SB.StringBuffer, UTCTime) -> Target
#if __GLASGOW_HASKELL__ >= 706
mkTarget = Target
#else
mkTarget tid allowObjCode = Target tid allowObjCode . (fmap . second) convert
#endif
----------------------------------------------------------------
----------------------------------------------------------------
2013-03-12 13:15:23 +00:00
withStyle :: DynFlags -> PprStyle -> SDoc -> Pretty.Doc
#if __GLASGOW_HASKELL__ >= 706
2013-03-12 13:15:23 +00:00
withStyle = withPprStyleDoc
#else
2013-03-12 13:15:23 +00:00
withStyle _ = withPprStyleDoc
#endif
setLogAction :: DynFlags
-> (DynFlags -> Severity -> SrcSpan -> PprStyle -> SDoc -> IO ())
-> DynFlags
setLogAction df f =
#if __GLASGOW_HASKELL__ >= 706
df { log_action = f }
#else
df { log_action = f df }
#endif
showDocWith :: DynFlags -> Pretty.Mode -> Pretty.Doc -> String
#if __GLASGOW_HASKELL__ >= 707
-- Pretty.showDocWith disappeard.
-- https://github.com/ghc/ghc/commit/08a3536e4246e323fbcd8040e0b80001950fe9bc
showDocWith dflags mode = Pretty.showDoc mode (pprCols dflags)
#else
showDocWith _ = Pretty.showDocWith
#endif
2012-02-14 07:09:53 +00:00
----------------------------------------------------------------
----------------------------------------------------------------
supportedExtensions :: [String]
#if __GLASGOW_HASKELL__ >= 700
supportedExtensions = supportedLanguagesAndExtensions
#else
supportedExtensions = supportedLanguages
#endif
----------------------------------------------------------------
----------------------------------------------------------------
getSrcSpan :: SrcSpan -> Maybe (Int,Int,Int,Int)
#if __GLASGOW_HASKELL__ >= 702
getSrcSpan (RealSrcSpan spn)
#else
getSrcSpan spn | isGoodSrcSpan spn
#endif
= Just (srcSpanStartLine spn
, srcSpanStartCol spn
, srcSpanEndLine spn
, srcSpanEndCol spn)
getSrcSpan _ = Nothing
getSrcFile :: SrcSpan -> Maybe String
#if __GLASGOW_HASKELL__ >= 702
getSrcFile (RealSrcSpan spn) = Just . unpackFS . srcSpanFile $ spn
#else
getSrcFile spn | isGoodSrcSpan spn = Just . unpackFS . srcSpanFile $ spn
#endif
getSrcFile _ = Nothing
----------------------------------------------------------------
toStringBuffer :: [String] -> Ghc StringBuffer
#if __GLASGOW_HASKELL__ >= 702
toStringBuffer = return . stringToStringBuffer . unlines
#else
toStringBuffer = liftIO . stringToStringBuffer . unlines
#endif
----------------------------------------------------------------
fOptions :: [String]
2012-06-07 06:56:55 +00:00
#if __GLASGOW_HASKELL__ >= 704
fOptions = [option | (option,_,_) <- fFlags]
++ [option | (option,_,_) <- fWarningFlags]
++ [option | (option,_,_) <- fLangFlags]
#elif __GLASGOW_HASKELL__ == 702
2012-02-14 07:09:53 +00:00
fOptions = [option | (option,_,_,_) <- fFlags]
++ [option | (option,_,_,_) <- fWarningFlags]
++ [option | (option,_,_,_) <- fLangFlags]
2012-02-14 07:09:53 +00:00
#else
fOptions = [option | (option,_,_) <- fFlags]
#endif
----------------------------------------------------------------
----------------------------------------------------------------
2014-04-11 03:56:06 +00:00
setCtx :: FilePath -> Ghc ModSummary
#if __GLASGOW_HASKELL__ >= 704
2014-04-11 03:56:06 +00:00
setCtx file = do
mss <- getModuleGraph
#if __GLASGOW_HASKELL__ >= 706
let modName = IIModule . moduleName . ms_mod
#else
let modName = IIModule . ms_mod
#endif
2014-04-11 03:41:39 +00:00
top <- map modName <$> filterM isTop mss
2012-02-14 07:09:53 +00:00
setContext top
2014-04-11 03:41:39 +00:00
let [ms] = filter (\m -> ml_hs_file (ms_location m) == Just file) mss
return ms
2012-02-14 07:09:53 +00:00
#else
2014-04-11 03:56:06 +00:00
setCtx file = do
mss <- getModuleGraph
2014-04-11 03:41:39 +00:00
top <- map ms_mod <$> filterM isTop mss
setContext top []
2014-04-11 03:41:39 +00:00
let [ms] = filter (\m -> ml_hs_file (ms_location m) == Just file) mss
return ms
2012-02-14 07:09:53 +00:00
#endif
where
2012-02-16 05:44:20 +00:00
isTop mos = lookupMod ||> returnFalse
2012-02-14 07:09:53 +00:00
where
lookupMod = lookupModule (ms_mod_name mos) Nothing >> return True
2012-02-15 05:52:48 +00:00
returnFalse = return False
showSeverityCaption :: Severity -> String
#if __GLASGOW_HASKELL__ >= 706
showSeverityCaption SevWarning = "Warning: "
showSeverityCaption _ = ""
#else
showSeverityCaption = const ""
#endif
----------------------------------------------------------------
----------------------------------------------------------------
setCabalPkg :: DynFlags -> DynFlags
#if __GLASGOW_HASKELL__ >= 707
setCabalPkg dflag = gopt_set dflag Opt_BuildingCabalPackage
#else
setCabalPkg dflag = dopt_set dflag Opt_BuildingCabalPackage
#endif
----------------------------------------------------------------
addDevPkgs :: DynFlags -> [Package] -> DynFlags
addDevPkgs df [] = df
addDevPkgs df pkgs = df''
where
#if __GLASGOW_HASKELL__ >= 707
df' = gopt_set df Opt_HideAllPackages
2013-07-14 08:07:30 +00:00
#else
df' = dopt_set df Opt_HideAllPackages
2013-07-14 08:07:30 +00:00
#endif
df'' = df' {
packageFlags = map expose pkgs ++ packageFlags df
}
expose pkg = ExposePackageId $ showPkgId pkg
----------------------------------------------------------------
----------------------------------------------------------------
class HasType a where
getType :: GhcMonad m => TypecheckedModule -> a -> m (Maybe (SrcSpan, Type))
instance HasType (LHsBind Id) where
#if __GLASGOW_HASKELL__ >= 707
getType _ (L spn FunBind{fun_matches = MG _ in_tys out_typ}) = return $ Just (spn, typ)
where typ = mkFunTys in_tys out_typ
2013-07-14 08:07:30 +00:00
#else
getType _ (L spn FunBind{fun_matches = MatchGroup _ typ}) = return $ Just (spn, typ)
2013-07-14 08:07:30 +00:00
#endif
getType _ _ = return Nothing
----------------------------------------------------------------
----------------------------------------------------------------
-- from ghc/InteractiveUI.hs
filterOutChildren :: (a -> TyThing) -> [a] -> [a]
filterOutChildren get_thing xs
= [x | x <- xs, not (getName (get_thing x) `elemNameSet` implicits)]
where
implicits = mkNameSet [getName t | x <- xs, t <- implicitTyThings (get_thing x)]
2013-07-14 08:07:30 +00:00
infoThing :: String -> Ghc SDoc
infoThing str = do
names <- parseName str
#if __GLASGOW_HASKELL__ >= 707
mb_stuffs <- mapM (getInfo False) names
let filtered = filterOutChildren (\(t,_f,_i,_fam) -> t) (catMaybes mb_stuffs)
2013-07-14 08:07:30 +00:00
#else
mb_stuffs <- mapM getInfo names
let filtered = filterOutChildren (\(t,_f,_i) -> t) (catMaybes mb_stuffs)
#endif
2013-07-14 08:07:30 +00:00
return $ vcat (intersperse (text "") $ map (pprInfo False) filtered)
#if __GLASGOW_HASKELL__ >= 707
2013-11-12 23:44:34 +00:00
pprInfo :: Bool -> (TyThing, GHC.Fixity, [ClsInst], [FamInst]) -> SDoc
pprInfo _ (thing, fixity, insts, famInsts)
= pprTyThingInContextLoc thing
$$ show_fixity fixity
$$ InstEnv.pprInstances insts
$$ pprFamInsts famInsts
where
show_fixity fx
| fx == defaultFixity = Outputable.empty
| otherwise = ppr fx <+> ppr (getName thing)
2013-07-14 08:07:30 +00:00
#else
pprInfo :: PrintExplicitForalls -> (TyThing, GHC.Fixity, [ClsInst]) -> SDoc
pprInfo pefas (thing, fixity, insts)
= pprTyThingInContextLoc pefas thing
$$ show_fixity fixity
$$ vcat (map pprInstance insts)
where
show_fixity fx
| fx == defaultFixity = Outputable.empty
| otherwise = ppr fx <+> ppr (getName thing)
#endif
2013-11-12 23:44:34 +00:00
2013-11-19 03:28:59 +00:00
----------------------------------------------------------------
----------------------------------------------------------------
errorMsgSpan :: ErrMsg -> SrcSpan
#if __GLASGOW_HASKELL__ >= 707
errorMsgSpan = errMsgSpan
#else
errorMsgSpan = head . errMsgSpans
#endif
2013-11-19 03:35:42 +00:00
typeForUser :: Type -> SDoc
#if __GLASGOW_HASKELL__ >= 707
typeForUser = pprTypeForUser
#else
typeForUser = pprTypeForUser False
#endif
2013-11-19 03:54:08 +00:00
deSugar :: TypecheckedModule -> LHsExpr Id -> HscEnv
2014-03-27 07:02:16 +00:00
-> IO (Maybe CoreExpr)
2013-11-19 03:54:08 +00:00
#if __GLASGOW_HASKELL__ >= 707
2014-01-08 00:55:06 +00:00
deSugar _ e hs_env = snd <$> deSugarExpr hs_env e
2013-11-19 03:54:08 +00:00
#else
deSugar tcm e hs_env = snd <$> deSugarExpr hs_env modu rn_env ty_env e
where
modu = ms_mod $ pm_mod_summary $ tm_parsed_module tcm
tcgEnv = fst $ tm_internals_ tcm
rn_env = tcg_rdr_env tcgEnv
ty_env = tcg_type_env tcgEnv
#endif
2014-02-06 12:34:40 +00:00
----------------------------------------------------------------
----------------------------------------------------------------
2014-02-06 13:09:00 +00:00
data GapThing = GtA Type | GtT TyCon | GtN
2014-02-06 12:34:40 +00:00
fromTyThing :: TyThing -> GapThing
2014-02-06 13:09:00 +00:00
fromTyThing (AnId i) = GtA $ varType i
#if __GLASGOW_HASKELL__ >= 707
2014-02-06 13:09:00 +00:00
fromTyThing (AConLike (RealDataCon d)) = GtA $ dataConRepType d
fromTyThing (AConLike (PatSynCon p)) = GtA $ patSynType p
#else
2014-02-06 13:09:00 +00:00
fromTyThing (ADataCon d) = GtA $ dataConRepType d
#endif
fromTyThing (ATyCon t) = GtT t
fromTyThing _ = GtN
2014-03-27 11:54:18 +00:00
----------------------------------------------------------------
#if __GLASGOW_HASKELL__ >= 707
dumpSplicesFlag :: DumpFlag
#else
dumpSplicesFlag :: DynFlag
#endif
dumpSplicesFlag = Opt_D_dump_splices