ghcide-2.13.0.0: The core of an IDE
Safe HaskellNone
LanguageGHC2021

Development.IDE.GHC.Compat

Description

Attempt at hiding the GHC version differences we can.

Synopsis

Documentation

reLoc :: LocatedAn a e -> Located e #

reLocA :: Located e -> LocatedAn ann e #

data Usage #

Records modules for which changes may force recompilation of this module See wiki: https://gitlab.haskell.org/ghc/ghc/wikis/commentary/compiler/recompilation-avoidance

This differs from Dependencies. A module X may be in the dep_mods of this module (via an import chain) but if we don't use anything from X it won't appear in our Usage

Constructors

UsagePackageModule

Module from another package

Fields

UsageHomeModule

Module from the current package

Fields

UsageFile

A file upon which the module depends, e.g. a CPP #include, or using TH's addDependentFile

Fields

UsageHomeModuleInterface 

Fields

UsageMergedRequirement

A requirement which was merged into this one.

Fields

Instances

Instances details
Binary Usage 
Instance details

Defined in GHC.Unit.Module.Deps

Methods

put_ :: BinHandle -> Usage -> IO () #

put :: BinHandle -> Usage -> IO (Bin Usage) #

get :: BinHandle -> IO Usage #

Eq Usage 
Instance details

Defined in GHC.Unit.Module.Deps

Methods

(==) :: Usage -> Usage -> Bool #

(/=) :: Usage -> Usage -> Bool #

bytesFS :: FastString -> ByteString #

Gives the Modified UTF-8 encoded bytes corresponding to a FastString

mkFastStringByteString :: ByteString -> FastString #

Create a FastString by copying an existing ByteString

getSourceNodeIds :: HieAST a -> Map Identifier (IdentifierDetails a) Source #

Like getNodeIds but with generated node removed

combineRealSrcSpans :: RealSrcSpan -> RealSrcSpan -> RealSrcSpan #

Combines two SrcSpan into one that spans at least all the characters within both spans. Assumes the "file" part is the same in both inputs

HIE Compat

data HieFile #

GHC builds up a wealth of information about Haskell source as it compiles it. .hie files are a way of persisting some of this information to disk so that external tools that need to work with haskell source don't need to parse, typecheck, and rename all over again. These files contain:

  • a simplified AST

    • nodes are annotated with source positions and types
    • identifiers are annotated with scope information
  • the raw bytes of the initial Haskell source

Besides saving compilation cycles, .hie files also offer a more stable interface than the GHC API.

Constructors

HieFile 

Fields

Instances

Instances details
Show HieFile Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData HieFile Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: HieFile -> () #

Binary HieFile 
Instance details

Defined in GHC.Iface.Ext.Types

enrichHie :: TypecheckedSource -> RenamedSource -> Bag EvBind -> [ClsInst] -> [TyCon] -> HieASTs Type #

writeHieFile :: FilePath -> HieFile -> IO () #

Write a HieFile to the given FilePath, with a proper header and symbol tables for Names and FastStrings

readHieFile :: NameCache -> FilePath -> IO HieFileResult #

Read a HieFile from a FilePath. Can use an existing NameCache.

Compat modules

Extras that rely on compat modules

SysTools

data Option #

When invoking external tools as part of the compilation pipeline, we pass these a sequence of options on the command-line. Rather than just using a list of Strings, we use a type that allows us to distinguish between filepaths and 'other stuff'. The reason for this is that this type gives us a handle on transforming filenames, and filenames only, to whatever format they're expected to be on a particular platform.

Instances

Instances details
Eq Option 
Instance details

Defined in GHC.Utils.CliOption

Methods

(==) :: Option -> Option -> Bool #

(/=) :: Option -> Option -> Bool #

runUnlit :: Logger -> DynFlags -> [Option] -> IO () #

runPp :: Logger -> DynFlags -> [Option] -> IO () #

Recompilation avoidance

type CoreExpr = Expr CoreBndr #

Expressions where binders are CoreBndrs

lintInteractiveExpr #

Arguments

:: SDoc

The source of the linted expression

-> HscEnv 
-> CoreExpr 
-> IO () 

type HomePackageTable = DModuleNameEnv HomeModInfo #

Helps us find information about modules in the home package

loadModulesHome :: [HomeModInfo] -> HscEnv -> HscEnv Source #

Load modules, quickly. Input doesn't need to be desugared. A module must be loaded before dependent modules can be typechecked. This variant of loadModuleHome will *never* cause recompilation, it just modifies the session. The order modules are loaded is important when there are hs-boot files. In particular you should make sure to load the .hs version of a file after the .hs-boot version.

bcoFreeNames :: UnlinkedBCO -> UniqDSet Name #

Finds external references. Remember to remove the names defined by this group of BCOs themselves

data AnnTarget name #

An annotation target

Constructors

ModuleTarget Module

We are annotating a particular module

Instances

Instances details
Functor AnnTarget 
Instance details

Defined in GHC.Types.Annotations

Methods

fmap :: (a -> b) -> AnnTarget a -> AnnTarget b #

(<$) :: a -> AnnTarget b -> AnnTarget a #

Binary name => Binary (AnnTarget name) 
Instance details

Defined in GHC.Types.Annotations

Methods

put_ :: BinHandle -> AnnTarget name -> IO () #

put :: BinHandle -> AnnTarget name -> IO (Bin (AnnTarget name)) #

get :: BinHandle -> IO (AnnTarget name) #

Outputable name => Outputable (AnnTarget name) 
Instance details

Defined in GHC.Types.Annotations

Methods

ppr :: AnnTarget name -> SDoc #

extendAnnEnvList :: AnnEnv -> [Annotation] -> AnnEnv #

Add the given annotation to the environment.

flattenBinds :: [Bind b] -> [(b, Expr b)] #

Collapse all the bindings in the supplied groups into a single list of lhs/rhs pairs suitable for binding in a Rec binding group

data Unfolding #

Records the unfolding of an identifier, which is approximately the form the identifier would have if we substituted its definition in for the identifier. This type should be treated as abstract everywhere except in GHC.Core.Unfold

Constructors

NoUnfolding

We have no information about the unfolding.

BootUnfolding

We have no information about the unfolding, because this Id came from an hi-boot file. See Note [Inlining and hs-boot files] in GHC.CoreToIface for what this is used for.

OtherCon [AltCon]

It ain't one of these constructors. OtherCon xs also indicates that something has been evaluated and hence there's no point in re-evaluating it. OtherCon [] is used even for non-data-type values to indicated evaluated-ness. Notably:

data C = C !(Int -> Int)
case x of { C f -> ... }

Here, f gets an OtherCon [] unfolding.

DFunUnfolding 

Fields

CoreUnfolding

An unfolding with redundant cached information. Parameters:

uf_tmpl: Template used to perform unfolding; NB: Occurrence info is guaranteed correct: see Note [OccInfo in unfoldings and rules]

uf_is_top: Is this a top level binding?

uf_is_value: exprIsHNF template (cached); it is ok to discard a seq on this variable

uf_is_work_free: Does this waste only a little work if we expand it inside an inlining? Basically this is a cached version of exprIsWorkFree

uf_guidance: Tells us about the size of the unfolding template

noUnfolding :: Unfolding #

There is no known Unfolding

loadExpr :: Interp -> HscEnv -> SrcSpan -> UnlinkedBCO -> IO ForeignHValue #

Load a single expression, including first loading packages and modules that this expression depends on.

Raises an IO exception (ProgramError) if it can't find a compiled version of the dependents to load.

hscInterp :: HscEnv -> Interp #

Retrieve the target code interpreter

Fails if no target code interpreter is available

recDotDot :: forall (p :: Pass) arg. HsRecFields (GhcPass p) arg -> Maybe Int Source #

data Dependencies #

Dependency information about ALL modules and packages below this one in the import hierarchy. This is the serialisable version of ImportAvails.

Invariant: the dependencies of a module M never includes M.

Invariant: none of the lists contain duplicates.

Invariant: lists are ordered canonically (e.g. using stableModuleCmp)

See Note [Transitive Information in Dependencies]

Instances

Instances details
Binary Dependencies 
Instance details

Defined in GHC.Unit.Module.Deps

Eq Dependencies 
Instance details

Defined in GHC.Unit.Module.Deps

data XModulePs #

Haskell Module extension point: GHC specific

Constructors

XModulePs 

Fields

Instances

Instances details
Data XModulePs 
Instance details

Defined in GHC.Hs

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XModulePs -> c XModulePs #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XModulePs #

toConstr :: XModulePs -> Constr #

dataTypeOf :: XModulePs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c XModulePs) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XModulePs) #

gmapT :: (forall b. Data b => b -> b) -> XModulePs -> XModulePs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XModulePs -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XModulePs -> r #

gmapQ :: (forall d. Data d => d -> u) -> XModulePs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> XModulePs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> XModulePs -> m XModulePs #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XModulePs -> m XModulePs #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XModulePs -> m XModulePs #