{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
module Development.IDE.GHC.Compat.Core (
DynFlags,
extensions,
extensionFlags,
targetPlatform,
packageFlags,
generalFlags,
warningFlags,
topDir,
hiDir,
tmpDir,
importPaths,
useColor,
canUseColor,
useUnicode,
objectDir,
flagsForCompletion,
setImportPaths,
outputFile,
pluginModNames,
refLevelHoleFits,
maxRefHoleFits,
maxValidHoleFits,
setOutputFile,
lookupType,
needWiredInHomeIface,
loadWiredInHomeIface,
readIface,
loadSysInterface,
importDecl,
CommandLineOption,
sPgm_F,
settings,
gopt,
gopt_set,
gopt_unset,
wopt,
wopt_set,
xFlags,
xopt,
xopt_unset,
xopt_set,
FlagSpec(..),
WarningFlag(..),
GeneralFlag(..),
PackageFlag,
PackageArg(..),
ModRenaming(..),
pattern ExposePackage,
parseDynamicFlagsCmdLine,
parseDynamicFilePragma,
#if !MIN_VERSION_ghc(9,3,0)
WarnReason(..),
#endif
wWarningFlags,
updOptLevel,
setUnsafeGlobalDynFlags,
scaledThing,
IfaceExport,
IfaceTyCon(..),
ModIface,
ModIface_(..),
HscSource(..),
WhereFrom(..),
loadInterface,
#if !MIN_VERSION_ghc(9,3,0)
SourceModified(..),
#endif
loadModuleInterface,
RecompileRequired(..),
mkPartialIface,
mkFullIface,
checkOldIface,
IsBootInterface(..),
LexicalFixity(..),
Fixity (..),
mi_fix,
defaultFixity,
lookupFixityRn,
ModSummary(..),
HomeModInfo(..),
ModGuts(..),
CgGuts(..),
ModDetails(..),
Type (
TyCoRep.TyVarTy,
TyCoRep.AppTy,
TyCoRep.TyConApp,
TyCoRep.ForAllTy,
TyCoRep.LitTy,
TyCoRep.CastTy,
TyCoRep.CoercionTy
),
pattern FunTy,
pattern ConPatIn,
conPatDetails,
mapConPatDetail,
mkVisFunTys,
ImpDeclSpec(..),
ImportSpec(..),
SourceText(..),
tyThingParent_maybe,
Way,
wayGeneralFlags,
wayUnsetGeneralFlags,
Avail.AvailInfo,
pattern AvailName,
pattern AvailFL,
pattern AvailTC,
Avail.availName,
Avail.availNames,
#if !MIN_VERSION_ghc(9,7,0)
Avail.availNamesWithSelectors,
#endif
Avail.availsToNameSet,
TcGblEnv(..),
HsModule(..),
GHC.ParsedSource,
GHC.RenamedSource,
HscEnv,
GHC.runGhc,
unGhc,
Session(..),
modifySession,
getSession,
GHC.setSessionDynFlags,
getSessionDynFlags,
GhcMonad,
Ghc,
runHsc,
compileFile,
Phase(..),
hscDesugar,
hscGenHardCode,
hscInteractive,
hscSimplify,
hscTypecheckRename,
Development.IDE.GHC.Compat.Core.makeSimpleDetails,
tcSplitForAllTyVars,
tcSplitForAllTyVarBinder_maybe,
typecheckIface,
Development.IDE.GHC.Compat.Core.mkIfaceTc,
Development.IDE.GHC.Compat.Core.mkBootModDetailsTc,
Development.IDE.GHC.Compat.Core.initTidyOpts,
hscUpdateHPT,
driverNoStop,
tidyProgram,
ImportedModsVal(..),
importedByUser,
GHC.TypecheckedSource,
HasSrcSpan,
SrcLoc.Located,
SrcLoc.unLoc,
getLoc,
GHC.getLocA,
GHC.locA,
GHC.noLocA,
unLocA,
LocatedAn,
GHC.LocatedA,
GHC.AnnListItem(..),
GHC.NameAnn(..),
SrcLoc.RealLocated,
SrcLoc.GenLocated(..),
SrcLoc.SrcSpan(SrcLoc.UnhelpfulSpan),
SrcLoc.RealSrcSpan,
pattern RealSrcSpan,
SrcLoc.RealSrcLoc,
pattern RealSrcLoc,
SrcLoc.SrcLoc(SrcLoc.UnhelpfulLoc),
BufSpan,
SrcSpanAnn',
GHC.SrcAnn,
SrcLoc.leftmost_smallest,
SrcLoc.containsSpan,
SrcLoc.mkGeneralSrcSpan,
SrcLoc.mkRealSrcSpan,
SrcLoc.mkRealSrcLoc,
SrcLoc.getRealSrcSpan,
SrcLoc.realSrcLocSpan,
SrcLoc.realSrcSpanStart,
SrcLoc.realSrcSpanEnd,
isSubspanOfA,
SrcLoc.isSubspanOf,
SrcLoc.wiredInSrcSpan,
SrcLoc.mkSrcSpan,
SrcLoc.srcSpanStart,
SrcLoc.srcSpanStartLine,
SrcLoc.srcSpanStartCol,
SrcLoc.srcSpanEnd,
SrcLoc.srcSpanEndLine,
SrcLoc.srcSpanEndCol,
SrcLoc.srcSpanFile,
SrcLoc.srcLocCol,
SrcLoc.srcLocFile,
SrcLoc.srcLocLine,
SrcLoc.noSrcSpan,
SrcLoc.noSrcLoc,
SrcLoc.noLoc,
mapLoc,
FindResult(..),
mkHomeModLocation,
addBootSuffixLocnOut,
findObjectLinkableMaybe,
InstalledFindResult(..),
ModuleOrigin(..),
PackageName(..),
Unlinked(..),
Linkable(..),
unload,
Hooks,
runMetaHook,
MetaHook,
MetaRequest(..),
metaRequestE,
metaRequestP,
metaRequestT,
metaRequestD,
metaRequestAW,
addToHpt,
addListToHpt,
Target(..),
TargetId(..),
mkModuleGraph,
initObjLinker,
loadDLL,
InteractiveImport(..),
GHC.getContext,
GHC.setContext,
GHC.parseImportDecl,
GHC.runDecls,
Warn(..),
GHC.ModLocation,
Module.ml_hs_file,
Module.ml_obj_file,
Module.ml_hi_file,
Module.ml_hie_file,
DataCon.dataConExTyCoVars,
Role(..),
Plain.PlainGhcException,
panic,
panicDoc,
GHC.CoreModule(..),
GHC.SafeHaskellMode(..),
pattern GRE,
gre_name,
gre_imp,
gre_lcl,
gre_par,
collectHsBindsBinders,
module GHC.Builtin.Names,
module GHC.Builtin.Types,
module GHC.Builtin.Types.Prim,
module GHC.Builtin.Utils,
module GHC.Core.Class,
module GHC.Core.Coercion,
module GHC.Core.ConLike,
module GHC.Core.DataCon,
module GHC.Core.FamInstEnv,
module GHC.Core.InstEnv,
module GHC.Types.Unique.FM,
module GHC.Core.PatSyn,
module GHC.Core.Predicate,
module GHC.Core.TyCon,
module GHC.Core.TyCo.Ppr,
module GHC.Core.Type,
module GHC.Core.Unify,
module GHC.Core.Utils,
module GHC.HsToCore.Docs,
module GHC.HsToCore.Expr,
module GHC.HsToCore.Monad,
module GHC.Iface.Syntax,
module GHC.Hs.Decls,
module GHC.Hs.Expr,
module GHC.Hs.Doc,
module GHC.Hs.Extension,
module GHC.Hs.ImpExp,
module GHC.Hs.Pat,
module GHC.Hs.Type,
module GHC.Hs.Utils,
module Language.Haskell.Syntax,
module GHC.Rename.Names,
module GHC.Rename.Splice,
module GHC.Tc.Instance.Family,
module GHC.Tc.Module,
module GHC.Tc.Types,
module GHC.Tc.Types.Evidence,
module GHC.Tc.Utils.Env,
module GHC.Tc.Utils.Monad,
module GHC.Types.Basic,
module GHC.Types.Id,
module GHC.Types.Name ,
module GHC.Types.Name.Set,
module GHC.Types.Name.Cache,
module GHC.Types.Name.Env,
module GHC.Types.Name.Reader,
module GHC.Utils.Error,
#if !MIN_VERSION_ghc(9,7,0)
module GHC.Types.Avail,
#endif
module GHC.Types.SourceFile,
module GHC.Types.SourceText,
module GHC.Types.TyThing,
module GHC.Types.TyThing.Ppr,
module GHC.Types.Unique.Supply,
module GHC.Types.Var,
module GHC.Unit.Module,
module GHC.Hs,
module GHC.Hs.Binds,
module GHC.Parser,
module GHC.Parser.Header,
module GHC.Parser.Lexer,
#if MIN_VERSION_ghc(9,3,0)
CompileReason(..),
hsc_type_env_vars,
hscUpdateHUG, hscUpdateHPT, hsc_HUG,
GhcMessage(..),
getKey,
module GHC.Driver.Env.KnotVars,
module GHC.Iface.Recomp,
module GHC.Linker.Types,
module GHC.Unit.Module.Graph,
module GHC.Types.Unique.Map,
module GHC.Utils.TmpFs,
module GHC.Utils.Panic,
module GHC.Unit.Finder.Types,
module GHC.Unit.Env,
module GHC.Driver.Phases,
#endif
# if !MIN_VERSION_ghc(9,4,0)
pattern HsFieldBind,
hfbAnn,
hfbLHS,
hfbRHS,
hfbPun,
#endif
#if !MIN_VERSION_ghc_boot_th(9,4,1)
Extension(.., NamedFieldPuns),
#else
Extension(..),
#endif
UniqFM,
mkCgInteractiveGuts,
justBytecode,
justObjects,
emptyHomeModInfoLinkable,
homeModInfoByteCode,
homeModInfoObject,
# if !MIN_VERSION_ghc(9,5,0)
field_label,
#endif
groupOrigin,
) where
import qualified GHC
import GHC.LanguageExtensions.Type hiding (Cpp)
import GHC.Hs.Binds
import GHC.Builtin.Names hiding (Unique, printName)
import GHC.Builtin.Types
import GHC.Builtin.Types.Prim
import GHC.Builtin.Utils
import GHC.Core.Class
import GHC.Core.Coercion
import GHC.Core.ConLike
import GHC.Core.DataCon hiding (dataConExTyCoVars)
import qualified GHC.Core.DataCon as DataCon
import GHC.Core.FamInstEnv hiding (pprFamInst)
import GHC.Core.InstEnv
import GHC.Types.Unique.FM
import GHC.Core.PatSyn
import GHC.Core.Predicate
import GHC.Core.TyCo.Ppr
import qualified GHC.Core.TyCo.Rep as TyCoRep
import GHC.Core.TyCon
import GHC.Core.Type
import GHC.Core.Unify
import GHC.Core.Utils
import GHC.Driver.CmdLine (Warn (..))
import GHC.Driver.Hooks
import GHC.Driver.Main as GHC
import GHC.Driver.Monad
import GHC.Driver.Phases
import GHC.Driver.Pipeline
import GHC.Driver.Plugins
import GHC.Driver.Session hiding (ExposePackage)
import qualified GHC.Driver.Session as DynFlags
import GHC.HsToCore.Docs
import GHC.HsToCore.Expr
import GHC.HsToCore.Monad
import GHC.Iface.Load
import GHC.Iface.Make as GHC
import GHC.Iface.Recomp
import GHC.Iface.Syntax
import GHC.Iface.Tidy as GHC
import GHC.IfaceToCore
import GHC.Parser
import GHC.Parser.Header hiding (getImports)
import GHC.Rename.Fixity (lookupFixityRn)
import GHC.Rename.Names
import GHC.Rename.Splice
import qualified GHC.Runtime.Interpreter as GHCi
import GHC.Tc.Instance.Family
import GHC.Tc.Module
import GHC.Tc.Types
import GHC.Tc.Types.Evidence hiding ((<.>))
import GHC.Tc.Utils.Env
import GHC.Tc.Utils.Monad hiding (Applicative (..), IORef,
MonadFix (..), MonadIO (..),
allM, anyM, concatMapM,
mapMaybeM, (<$>))
import GHC.Tc.Utils.TcType as TcType
import qualified GHC.Types.Avail as Avail
import GHC.Types.Basic
import GHC.Types.Id
import GHC.Types.Name hiding (varName)
import GHC.Types.Name.Cache
import GHC.Types.Name.Env
import GHC.Types.Name.Reader hiding (GRE, gre_name, gre_imp, gre_lcl, gre_par)
import qualified GHC.Types.Name.Reader as RdrName
import GHC.Types.SrcLoc (BufPos, BufSpan,
SrcLoc (UnhelpfulLoc),
SrcSpan (UnhelpfulSpan))
import qualified GHC.Types.SrcLoc as SrcLoc
import GHC.Types.Unique.Supply
import GHC.Types.Var (Var (varName), setTyVarUnique,
setVarUnique)
import GHC.Unit.Info (PackageName (..))
import GHC.Unit.Module hiding (ModLocation (..), UnitId,
moduleUnit,
toUnitId)
import qualified GHC.Unit.Module as Module
import GHC.Unit.State (ModuleOrigin (..))
import GHC.Utils.Error (Severity (..), emptyMessages)
import GHC.Utils.Panic hiding (try)
import qualified GHC.Utils.Panic.Plain as Plain
import Data.Foldable (toList)
import GHC.Data.Bag
import GHC.Core.Multiplicity (scaledThing)
import GHC.Driver.Env
import GHC.Hs (HsModule (..), SrcSpanAnn')
import GHC.Hs.Decls hiding (FunDep)
import GHC.Hs.Doc
import GHC.Hs.Expr
import GHC.Hs.Extension
import GHC.Hs.ImpExp
import GHC.Hs.Pat
import GHC.Hs.Type
import GHC.Hs.Utils hiding (collectHsBindsBinders)
import qualified GHC.Linker.Loader as Linker
import GHC.Linker.Types
import GHC.Parser.Lexer hiding (initParserState, getPsMessages)
import GHC.Parser.Annotation (EpAnn (..))
import GHC.Platform.Ways
import GHC.Runtime.Context (InteractiveImport (..))
#if !MIN_VERSION_ghc(9,7,0)
import GHC.Types.Avail (greNamePrintableName)
#endif
import GHC.Types.Fixity (LexicalFixity (..), Fixity (..), defaultFixity)
import GHC.Types.Meta
import GHC.Types.Name.Set
import GHC.Types.SourceFile (HscSource (..))
import GHC.Types.SourceText
import GHC.Types.Target (Target (..), TargetId (..))
import GHC.Types.TyThing
import GHC.Types.TyThing.Ppr
import GHC.Unit.Finder hiding (mkHomeModLocation)
import GHC.Unit.Home.ModInfo
import GHC.Unit.Module.Imported
import GHC.Unit.Module.ModDetails
import GHC.Unit.Module.ModGuts
import GHC.Unit.Module.ModIface (IfaceExport, ModIface (..),
ModIface_ (..), mi_fix)
import GHC.Unit.Module.ModSummary (ModSummary (..))
import Language.Haskell.Syntax hiding (FunDep)
#if !MIN_VERSION_ghc(9,3,0)
import GHC.Types.SourceFile (SourceModified(..))
import GHC.Unit.Module.Graph (mkModuleGraph)
import qualified GHC.Unit.Finder as GHC
#endif
#if MIN_VERSION_ghc(9,3,0)
import GHC.Driver.Env.KnotVars
import GHC.Unit.Module.Graph
import GHC.Driver.Errors.Types
import GHC.Types.Unique.Map
import GHC.Types.Unique
import GHC.Utils.TmpFs
import GHC.Utils.Panic
import GHC.Unit.Finder.Types
import GHC.Unit.Env
import qualified GHC.Driver.Config.Tidy as GHC
import qualified GHC.Data.Strict as Strict
import GHC.Driver.Env as GHCi
import qualified GHC.Unit.Finder as GHC
import qualified GHC.Driver.Config.Finder as GHC
#endif
mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO Module.ModLocation
#if MIN_VERSION_ghc(9,3,0)
mkHomeModLocation df mn f = pure $ GHC.mkHomeModLocation (GHC.initFinderOpts df) mn f
#else
mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO ModLocation
mkHomeModLocation = DynFlags -> ModuleName -> FilePath -> IO ModLocation
GHC.mkHomeModLocation
#endif
#if MIN_VERSION_ghc(9,3,0)
pattern RealSrcSpan :: SrcLoc.RealSrcSpan -> Maybe BufSpan -> SrcLoc.SrcSpan
#else
pattern RealSrcSpan :: SrcLoc.RealSrcSpan -> Maybe BufSpan -> SrcLoc.SrcSpan
#endif
#if MIN_VERSION_ghc(9,3,0)
pattern RealSrcSpan x y <- SrcLoc.RealSrcSpan x ((\case Strict.Nothing -> Nothing; Strict.Just a -> Just a) -> y) where
RealSrcSpan x y = SrcLoc.RealSrcSpan x (case y of Nothing -> Strict.Nothing; Just a -> Strict.Just a)
#else
pattern $bRealSrcSpan :: RealSrcSpan -> Maybe BufSpan -> SrcSpan
$mRealSrcSpan :: forall {r}.
SrcSpan -> (RealSrcSpan -> Maybe BufSpan -> r) -> ((# #) -> r) -> r
RealSrcSpan x y = SrcLoc.RealSrcSpan x y
#endif
{-# COMPLETE RealSrcSpan, UnhelpfulSpan #-}
#if MIN_VERSION_ghc(9,3,0)
pattern RealSrcLoc :: SrcLoc.RealSrcLoc -> Strict.Maybe BufPos-> SrcLoc.SrcLoc
#else
pattern RealSrcLoc :: SrcLoc.RealSrcLoc -> Maybe BufPos-> SrcLoc.SrcLoc
#endif
pattern $bRealSrcLoc :: RealSrcLoc -> Maybe BufPos -> SrcLoc
$mRealSrcLoc :: forall {r}.
SrcLoc -> (RealSrcLoc -> Maybe BufPos -> r) -> ((# #) -> r) -> r
RealSrcLoc x y = SrcLoc.RealSrcLoc x y
{-# COMPLETE RealSrcLoc, UnhelpfulLoc #-}
pattern AvailTC :: Name -> [Name] -> [FieldLabel] -> Avail.AvailInfo
#if __GLASGOW_HASKELL__ >= 907
pattern AvailTC n names pieces <- Avail.AvailTC n ((,[]) -> (names,pieces))
#else
pattern $mAvailTC :: forall {r}.
AvailInfo
-> (Name -> [Name] -> [FieldLabel] -> r) -> ((# #) -> r) -> r
AvailTC n names pieces <- Avail.AvailTC n ((\[GreName]
gres -> forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (\GreName
gre ([Name]
names, [FieldLabel]
pieces) -> case GreName
gre of
Avail.NormalGreName Name
name -> (Name
nameforall a. a -> [a] -> [a]
: [Name]
names, [FieldLabel]
pieces)
Avail.FieldGreName FieldLabel
label -> ([Name]
names, FieldLabel
labelforall a. a -> [a] -> [a]
:[FieldLabel]
pieces)) ([], []) [GreName]
gres) -> (names, pieces))
#endif
pattern AvailName :: Name -> Avail.AvailInfo
#if __GLASGOW_HASKELL__ >= 907
pattern AvailName n <- Avail.Avail n
#else
pattern $mAvailName :: forall {r}. AvailInfo -> (Name -> r) -> ((# #) -> r) -> r
AvailName n <- Avail.Avail (Avail.NormalGreName n)
#endif
pattern AvailFL :: FieldLabel -> Avail.AvailInfo
#if __GLASGOW_HASKELL__ >= 907
pattern AvailFL fl <- (const Nothing -> Just fl)
#else
pattern $mAvailFL :: forall {r}. AvailInfo -> (FieldLabel -> r) -> ((# #) -> r) -> r
AvailFL fl <- Avail.Avail (Avail.FieldGreName fl)
#endif
{-# COMPLETE AvailTC, AvailName, AvailFL #-}
setImportPaths :: [FilePath] -> DynFlags -> DynFlags
setImportPaths :: [FilePath] -> DynFlags -> DynFlags
setImportPaths [FilePath]
importPaths DynFlags
flags = DynFlags
flags { importPaths :: [FilePath]
importPaths = [FilePath]
importPaths }
pattern ExposePackage :: String -> PackageArg -> ModRenaming -> PackageFlag
#ifdef __FACEBOOK_HASKELL__
pattern ExposePackage s a mr <- DynFlags.ExposePackage s a _ mr
#else
pattern $bExposePackage :: FilePath -> PackageArg -> ModRenaming -> PackageFlag
$mExposePackage :: forall {r}.
PackageFlag
-> (FilePath -> PackageArg -> ModRenaming -> r)
-> ((# #) -> r)
-> r
ExposePackage s a mr = DynFlags.ExposePackage s a mr
#endif
pattern FunTy :: Type -> Type -> Type
pattern $mFunTy :: forall {r}. Type -> (Type -> Type -> r) -> ((# #) -> r) -> r
FunTy arg res <- TyCoRep.FunTy {ft_arg = arg, ft_res = res}
class HasSrcSpan a where
getLoc :: a -> SrcSpan
instance HasSrcSpan SrcSpan where
getLoc :: SrcSpan -> SrcSpan
getLoc = forall a. a -> a
id
instance HasSrcSpan (SrcLoc.GenLocated SrcSpan a) where
getLoc :: GenLocated SrcSpan a -> SrcSpan
getLoc = forall l e. GenLocated l e -> l
GHC.getLoc
instance HasSrcSpan (SrcSpanAnn' ann) where
getLoc :: SrcSpanAnn' ann -> SrcSpan
getLoc = forall ann. SrcSpanAnn' ann -> SrcSpan
GHC.locA
instance HasSrcSpan (SrcLoc.GenLocated (SrcSpanAnn' ann) a) where
getLoc :: GenLocated (SrcSpanAnn' ann) a -> SrcSpan
getLoc (L SrcSpan
l a
_) = SrcSpan
l
pattern L :: HasSrcSpan a => SrcSpan -> e -> SrcLoc.GenLocated a e
pattern $mL :: forall {r} {a} {e}.
HasSrcSpan a =>
GenLocated a e -> (SrcSpan -> e -> r) -> ((# #) -> r) -> r
L l a <- GHC.L (getLoc -> l) a
{-# COMPLETE L #-}
pattern ConPatIn :: SrcLoc.Located (ConLikeP GhcPs) -> HsConPatDetails GhcPs -> Pat GhcPs
pattern $bConPatIn :: Located (ConLikeP GhcPs) -> HsConPatDetails GhcPs -> Pat GhcPs
$mConPatIn :: forall {r}.
Pat GhcPs
-> (Located (ConLikeP GhcPs) -> HsConPatDetails GhcPs -> r)
-> ((# #) -> r)
-> r
ConPatIn con args <- ConPat EpAnnNotUsed (L _ (SrcLoc.noLoc -> con)) args
where
ConPatIn Located (ConLikeP GhcPs)
con HsConPatDetails GhcPs
args = forall p.
XConPat p -> XRec p (ConLikeP p) -> HsConPatDetails p -> Pat p
ConPat forall ann. EpAnn ann
EpAnnNotUsed (forall a an. a -> LocatedAn an a
GHC.noLocA forall a b. (a -> b) -> a -> b
$ forall l e. GenLocated l e -> e
SrcLoc.unLoc Located (ConLikeP GhcPs)
con) HsConPatDetails GhcPs
args
conPatDetails :: Pat p -> Maybe (HsConPatDetails p)
conPatDetails :: forall p. Pat p -> Maybe (HsConPatDetails p)
conPatDetails (ConPat XConPat p
_ XRec p (ConLikeP p)
_ HsConPatDetails p
args) = forall a. a -> Maybe a
Just HsConPatDetails p
args
conPatDetails Pat p
_ = forall a. Maybe a
Nothing
mapConPatDetail :: (HsConPatDetails p -> Maybe (HsConPatDetails p)) -> Pat p -> Maybe (Pat p)
mapConPatDetail :: forall p.
(HsConPatDetails p -> Maybe (HsConPatDetails p))
-> Pat p -> Maybe (Pat p)
mapConPatDetail HsConPatDetails p -> Maybe (HsConPatDetails p)
f pat :: Pat p
pat@(ConPat XConPat p
_ XRec p (ConLikeP p)
_ HsConPatDetails p
args) = (\HsConPatDetails p
args' -> Pat p
pat { pat_args :: HsConPatDetails p
pat_args = HsConPatDetails p
args'}) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HsConPatDetails p -> Maybe (HsConPatDetails p)
f HsConPatDetails p
args
mapConPatDetail HsConPatDetails p -> Maybe (HsConPatDetails p)
_ Pat p
_ = forall a. Maybe a
Nothing
initObjLinker :: HscEnv -> IO ()
initObjLinker :: HscEnv -> IO ()
initObjLinker HscEnv
env =
Interp -> IO ()
GHCi.initObjLinker (HscEnv -> Interp
GHCi.hscInterp HscEnv
env)
loadDLL :: HscEnv -> String -> IO (Maybe String)
loadDLL :: HscEnv -> FilePath -> IO (Maybe FilePath)
loadDLL HscEnv
env =
Interp -> FilePath -> IO (Maybe FilePath)
GHCi.loadDLL (HscEnv -> Interp
GHCi.hscInterp HscEnv
env)
unload :: HscEnv -> [Linkable] -> IO ()
unload :: HscEnv -> [Linkable] -> IO ()
unload HscEnv
hsc_env [Linkable]
linkables =
Interp -> HscEnv -> [Linkable] -> IO ()
Linker.unload
(HscEnv -> Interp
GHCi.hscInterp HscEnv
hsc_env)
HscEnv
hsc_env [Linkable]
linkables
#if !MIN_VERSION_ghc(9,3,0)
setOutputFile :: FilePath -> DynFlags -> DynFlags
setOutputFile :: FilePath -> DynFlags -> DynFlags
setOutputFile FilePath
f DynFlags
d = DynFlags
d {
outputFile_ :: Maybe FilePath
outputFile_ = forall a. a -> Maybe a
Just FilePath
f
}
#endif
isSubspanOfA :: LocatedAn la a -> LocatedAn lb b -> Bool
isSubspanOfA :: forall la a lb b. LocatedAn la a -> LocatedAn lb b -> Bool
isSubspanOfA LocatedAn la a
a LocatedAn lb b
b = SrcSpan -> SrcSpan -> Bool
SrcLoc.isSubspanOf (forall ann a. GenLocated (SrcSpanAnn' ann) a -> SrcSpan
GHC.getLocA LocatedAn la a
a) (forall ann a. GenLocated (SrcSpanAnn' ann) a -> SrcSpan
GHC.getLocA LocatedAn lb b
b)
type LocatedAn a = GHC.LocatedAn a
unLocA :: forall pass a. XRec (GhcPass pass) a -> a
unLocA :: forall (pass :: Pass) a. XRec (GhcPass pass) a -> a
unLocA = forall p a. UnXRec p => XRec p a -> a
unXRec @(GhcPass pass)
pattern GRE :: Name -> Parent -> Bool -> [ImportSpec] -> RdrName.GlobalRdrElt
{-# COMPLETE GRE #-}
pattern $mGRE :: forall {r}.
GlobalRdrElt
-> (Name -> Parent -> Bool -> [ImportSpec] -> r)
-> ((# #) -> r)
-> r
GRE{GlobalRdrElt -> Name
gre_name, GlobalRdrElt -> Parent
gre_par, GlobalRdrElt -> Bool
gre_lcl, GlobalRdrElt -> [ImportSpec]
gre_imp} <- RdrName.GRE
#if MIN_VERSION_ghc(9,7,0)
{gre_name = gre_name
#else
{gre_name = (greNamePrintableName -> gre_name)
#endif
,gre_par, gre_lcl, gre_imp = (toList -> gre_imp)}
collectHsBindsBinders :: CollectPass p => Bag (XRec p (HsBindLR p idR)) -> [IdP p]
collectHsBindsBinders :: forall p idR.
CollectPass p =>
Bag (XRec p (HsBindLR p idR)) -> [IdP p]
collectHsBindsBinders Bag (XRec p (HsBindLR p idR))
x = forall p idR.
CollectPass p =>
CollectFlag p -> LHsBindsLR p idR -> [IdP p]
GHC.collectHsBindsBinders forall p. CollectFlag p
CollNoDictBinders Bag (XRec p (HsBindLR p idR))
x
makeSimpleDetails :: HscEnv -> TcGblEnv -> IO ModDetails
makeSimpleDetails :: HscEnv -> TcGblEnv -> IO ModDetails
makeSimpleDetails HscEnv
hsc_env =
HscEnv -> TcGblEnv -> IO ModDetails
GHC.makeSimpleDetails
#if MIN_VERSION_ghc(9,3,0)
(hsc_logger hsc_env)
#else
HscEnv
hsc_env
#endif
mkIfaceTc :: HscEnv
-> SafeHaskellMode -> ModDetails -> p -> TcGblEnv -> IO ModIface
mkIfaceTc HscEnv
hsc_env SafeHaskellMode
sf ModDetails
details p
_ms TcGblEnv
tcGblEnv =
HscEnv -> SafeHaskellMode -> ModDetails -> TcGblEnv -> IO ModIface
GHC.mkIfaceTc HscEnv
hsc_env SafeHaskellMode
sf ModDetails
details
#if MIN_VERSION_ghc(9,3,0)
_ms
#endif
TcGblEnv
tcGblEnv
mkBootModDetailsTc :: HscEnv -> TcGblEnv -> IO ModDetails
mkBootModDetailsTc :: HscEnv -> TcGblEnv -> IO ModDetails
mkBootModDetailsTc HscEnv
session = HscEnv -> TcGblEnv -> IO ModDetails
GHC.mkBootModDetailsTc
#if MIN_VERSION_ghc(9,3,0)
(hsc_logger session)
#else
HscEnv
session
#endif
#if !MIN_VERSION_ghc(9,3,0)
type TidyOpts = HscEnv
#endif
initTidyOpts :: HscEnv -> IO TidyOpts
initTidyOpts :: HscEnv -> IO HscEnv
initTidyOpts =
#if MIN_VERSION_ghc(9,3,0)
GHC.initTidyOpts
#else
forall (f :: * -> *) a. Applicative f => a -> f a
pure
#endif
driverNoStop :: Phase
driverNoStop =
#if MIN_VERSION_ghc(9,3,0)
NoStop
#else
Phase
StopLn
#endif
#if !MIN_VERSION_ghc(9,3,0)
hscUpdateHPT :: (HomePackageTable -> HomePackageTable) -> HscEnv -> HscEnv
hscUpdateHPT :: (HomePackageTable -> HomePackageTable) -> HscEnv -> HscEnv
hscUpdateHPT HomePackageTable -> HomePackageTable
k HscEnv
session = HscEnv
session { hsc_HPT :: HomePackageTable
hsc_HPT = HomePackageTable -> HomePackageTable
k (HscEnv -> HomePackageTable
hsc_HPT HscEnv
session) }
#endif
#if !MIN_VERSION_ghc(9,4,0)
pattern HsFieldBind :: XHsRecField id -> id -> arg -> Bool -> HsRecField' id arg
pattern $bHsFieldBind :: forall id arg.
XHsRecField id -> id -> arg -> Bool -> HsRecField' id arg
$mHsFieldBind :: forall {r} {id} {arg}.
HsRecField' id arg
-> (XHsRecField id -> id -> arg -> Bool -> r) -> ((# #) -> r) -> r
HsFieldBind {forall id arg. HsRecField' id arg -> XHsRecField id
hfbAnn, forall id arg. HsRecField' id arg -> id
hfbLHS, forall id arg. HsRecField' id arg -> arg
hfbRHS, forall id arg. HsRecField' id arg -> Bool
hfbPun} <- HsRecField hfbAnn (SrcLoc.unLoc -> hfbLHS) hfbRHS hfbPun where
HsFieldBind XHsRecField id
ann id
lhs arg
rhs Bool
pun = forall id arg.
XHsRecField id -> Located id -> arg -> Bool -> HsRecField' id arg
HsRecField XHsRecField id
ann (forall e. e -> Located e
SrcLoc.noLoc id
lhs) arg
rhs Bool
pun
#endif
#if !MIN_VERSION_ghc_boot_th(9,4,1)
pattern NamedFieldPuns :: Extension
pattern $bNamedFieldPuns :: Extension
$mNamedFieldPuns :: forall {r}. Extension -> ((# #) -> r) -> ((# #) -> r) -> r
NamedFieldPuns = RecordPuns
#endif
#if MIN_VERSION_ghc(9,5,0)
mkVisFunTys = mkScaledFunctionTys
mapLoc :: (a -> b) -> SrcLoc.GenLocated l a -> SrcLoc.GenLocated l b
mapLoc = fmap
groupOrigin = mg_ext
#else
mapLoc :: (a -> b) -> SrcLoc.GenLocated l a -> SrcLoc.GenLocated l b
mapLoc :: forall a b l. (a -> b) -> GenLocated l a -> GenLocated l b
mapLoc = forall a b l. (a -> b) -> GenLocated l a -> GenLocated l b
SrcLoc.mapLoc
groupOrigin :: MatchGroup p body -> Origin
groupOrigin :: forall p body. MatchGroup p body -> Origin
groupOrigin = forall p body. MatchGroup p body -> Origin
mg_origin
#endif
#if !MIN_VERSION_ghc(9,5,0)
mkCgInteractiveGuts :: CgGuts -> CgGuts
mkCgInteractiveGuts :: CgGuts -> CgGuts
mkCgInteractiveGuts = forall a. a -> a
id
emptyHomeModInfoLinkable :: Maybe Linkable
emptyHomeModInfoLinkable :: Maybe Linkable
emptyHomeModInfoLinkable = forall a. Maybe a
Nothing
justBytecode :: Linkable -> Maybe Linkable
justBytecode :: Linkable -> Maybe Linkable
justBytecode = forall a. a -> Maybe a
Just
justObjects :: Linkable -> Maybe Linkable
justObjects :: Linkable -> Maybe Linkable
justObjects = forall a. a -> Maybe a
Just
homeModInfoByteCode, homeModInfoObject :: HomeModInfo -> Maybe Linkable
homeModInfoByteCode :: HomeModInfo -> Maybe Linkable
homeModInfoByteCode = HomeModInfo -> Maybe Linkable
hm_linkable
homeModInfoObject :: HomeModInfo -> Maybe Linkable
homeModInfoObject = HomeModInfo -> Maybe Linkable
hm_linkable
field_label :: a -> a
field_label :: forall a. a -> a
field_label = forall a. a -> a
id
#endif