ghcide-1.9.1.0: The core of an IDE
Safe HaskellSafe-Inferred
LanguageHaskell2010

Development.IDE.GHC.Compat

Description

Attempt at hiding the GHC version differences we can.

Synopsis

Documentation

newtype NameCacheUpdater #

A function that atomically updates the name cache given a modifier function. The second result of the modifier function will be the result of the IO action.

Constructors

NCU 

Fields

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 

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

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] -> DsM (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 :: NameCacheUpdater -> FilePath -> IO HieFileResult #

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

type TypeIndex = Int #

data TyVarScope #

Scope of a type variable.

This warrants a data type apart from Scope because of complexities introduced by features like -XScopedTypeVariables and -XInstanceSigs. For example, consider:

foo, bar, baz :: forall a. a -> a

Here a is in scope in all the definitions of foo, bar, and baz, so we need a list of scopes to keep track of this. Furthermore, this list cannot be computed until we resolve the binding sites of foo, bar, and baz.

Consequently, a starts with an UnresolvedScope [foo, bar, baz] Nothing which later gets resolved into a ResolvedScopes.

Constructors

ResolvedScopes [Scope] 
UnresolvedScope

Unresolved scopes should never show up in the final .hie file

Fields

  • [Name]

    names of the definitions over which the scope spans

  • (Maybe Span)

    the location of the instance/class declaration for the case where the type variable is declared in a method type signature

Instances

Instances details
Binary TyVarScope 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable TyVarScope 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: TyVarScope -> SDoc #

Eq TyVarScope 
Instance details

Defined in GHC.Iface.Ext.Types

Ord TyVarScope 
Instance details

Defined in GHC.Iface.Ext.Types

newtype SourcedNodeInfo a #

NodeInfos grouped by source

Instances

Instances details
Foldable SourcedNodeInfo 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

fold :: Monoid m => SourcedNodeInfo m -> m #

foldMap :: Monoid m => (a -> m) -> SourcedNodeInfo a -> m #

foldMap' :: Monoid m => (a -> m) -> SourcedNodeInfo a -> m #

foldr :: (a -> b -> b) -> b -> SourcedNodeInfo a -> b #

foldr' :: (a -> b -> b) -> b -> SourcedNodeInfo a -> b #

foldl :: (b -> a -> b) -> b -> SourcedNodeInfo a -> b #

foldl' :: (b -> a -> b) -> b -> SourcedNodeInfo a -> b #

foldr1 :: (a -> a -> a) -> SourcedNodeInfo a -> a #

foldl1 :: (a -> a -> a) -> SourcedNodeInfo a -> a #

toList :: SourcedNodeInfo a -> [a] #

null :: SourcedNodeInfo a -> Bool #

length :: SourcedNodeInfo a -> Int #

elem :: Eq a => a -> SourcedNodeInfo a -> Bool #

maximum :: Ord a => SourcedNodeInfo a -> a #

minimum :: Ord a => SourcedNodeInfo a -> a #

sum :: Num a => SourcedNodeInfo a -> a #

product :: Num a => SourcedNodeInfo a -> a #

Traversable SourcedNodeInfo 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

traverse :: Applicative f => (a -> f b) -> SourcedNodeInfo a -> f (SourcedNodeInfo b) #

sequenceA :: Applicative f => SourcedNodeInfo (f a) -> f (SourcedNodeInfo a) #

mapM :: Monad m => (a -> m b) -> SourcedNodeInfo a -> m (SourcedNodeInfo b) #

sequence :: Monad m => SourcedNodeInfo (m a) -> m (SourcedNodeInfo a) #

Functor SourcedNodeInfo 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Binary (SourcedNodeInfo TypeIndex) 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable a => Outputable (SourcedNodeInfo a) 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: SourcedNodeInfo a -> SDoc #

data Scope #

Instances

Instances details
Data Scope 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

toConstr :: Scope -> Constr #

dataTypeOf :: Scope -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary Scope 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

get :: BinHandle -> IO Scope #

Outputable Scope 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: Scope -> SDoc #

Eq Scope 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Ord Scope 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

compare :: Scope -> Scope -> Ordering #

(<) :: Scope -> Scope -> Bool #

(<=) :: Scope -> Scope -> Bool #

(>) :: Scope -> Scope -> Bool #

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

max :: Scope -> Scope -> Scope #

min :: Scope -> Scope -> Scope #

data RecFieldContext #

Instances

Instances details
Enum RecFieldContext 
Instance details

Defined in GHC.Iface.Ext.Types

Binary RecFieldContext 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable RecFieldContext 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: RecFieldContext -> SDoc #

Eq RecFieldContext 
Instance details

Defined in GHC.Iface.Ext.Types

Ord RecFieldContext 
Instance details

Defined in GHC.Iface.Ext.Types

data NodeInfo a #

The information stored in one AST node.

The type parameter exists to provide flexibility in representation of types (see Note [Efficient serialization of redundant type info]).

Constructors

NodeInfo (Set NodeAnnotation) [a] (NodeIdentifiers a) 

Instances

Instances details
Foldable NodeInfo 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

fold :: Monoid m => NodeInfo m -> m #

foldMap :: Monoid m => (a -> m) -> NodeInfo a -> m #

foldMap' :: Monoid m => (a -> m) -> NodeInfo a -> m #

foldr :: (a -> b -> b) -> b -> NodeInfo a -> b #

foldr' :: (a -> b -> b) -> b -> NodeInfo a -> b #

foldl :: (b -> a -> b) -> b -> NodeInfo a -> b #

foldl' :: (b -> a -> b) -> b -> NodeInfo a -> b #

foldr1 :: (a -> a -> a) -> NodeInfo a -> a #

foldl1 :: (a -> a -> a) -> NodeInfo a -> a #

toList :: NodeInfo a -> [a] #

null :: NodeInfo a -> Bool #

length :: NodeInfo a -> Int #

elem :: Eq a => a -> NodeInfo a -> Bool #

maximum :: Ord a => NodeInfo a -> a #

minimum :: Ord a => NodeInfo a -> a #

sum :: Num a => NodeInfo a -> a #

product :: Num a => NodeInfo a -> a #

Traversable NodeInfo 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

traverse :: Applicative f => (a -> f b) -> NodeInfo a -> f (NodeInfo b) #

sequenceA :: Applicative f => NodeInfo (f a) -> f (NodeInfo a) #

mapM :: Monad m => (a -> m b) -> NodeInfo a -> m (NodeInfo b) #

sequence :: Monad m => NodeInfo (m a) -> m (NodeInfo a) #

Functor NodeInfo 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Binary (NodeInfo TypeIndex) 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable a => Outputable (NodeInfo a) 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: NodeInfo a -> SDoc #

data IdentifierDetails a #

Information associated with every identifier

We need to include types with identifiers because sometimes multiple identifiers occur in the same span(Overloaded Record Fields and so on)

Instances

Instances details
Foldable IdentifierDetails 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

fold :: Monoid m => IdentifierDetails m -> m #

foldMap :: Monoid m => (a -> m) -> IdentifierDetails a -> m #

foldMap' :: Monoid m => (a -> m) -> IdentifierDetails a -> m #

foldr :: (a -> b -> b) -> b -> IdentifierDetails a -> b #

foldr' :: (a -> b -> b) -> b -> IdentifierDetails a -> b #

foldl :: (b -> a -> b) -> b -> IdentifierDetails a -> b #

foldl' :: (b -> a -> b) -> b -> IdentifierDetails a -> b #

foldr1 :: (a -> a -> a) -> IdentifierDetails a -> a #

foldl1 :: (a -> a -> a) -> IdentifierDetails a -> a #

toList :: IdentifierDetails a -> [a] #

null :: IdentifierDetails a -> Bool #

length :: IdentifierDetails a -> Int #

elem :: Eq a => a -> IdentifierDetails a -> Bool #

maximum :: Ord a => IdentifierDetails a -> a #

minimum :: Ord a => IdentifierDetails a -> a #

sum :: Num a => IdentifierDetails a -> a #

product :: Num a => IdentifierDetails a -> a #

Traversable IdentifierDetails 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

traverse :: Applicative f => (a -> f b) -> IdentifierDetails a -> f (IdentifierDetails b) #

sequenceA :: Applicative f => IdentifierDetails (f a) -> f (IdentifierDetails a) #

mapM :: Monad m => (a -> m b) -> IdentifierDetails a -> m (IdentifierDetails b) #

sequence :: Monad m => IdentifierDetails (m a) -> m (IdentifierDetails a) #

Functor IdentifierDetails 
Instance details

Defined in GHC.Iface.Ext.Types

Monoid (IdentifierDetails a) 
Instance details

Defined in GHC.Iface.Ext.Types

Semigroup (IdentifierDetails a) 
Instance details

Defined in GHC.Iface.Ext.Types

NFData a => NFData (IdentifierDetails a) Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: IdentifierDetails a -> () #

Binary (IdentifierDetails TypeIndex) 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable a => Outputable (IdentifierDetails a) 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: IdentifierDetails a -> SDoc #

Eq a => Eq (IdentifierDetails a) 
Instance details

Defined in GHC.Iface.Ext.Types

data IEType #

Types of imports and exports

Instances

Instances details
Enum IEType 
Instance details

Defined in GHC.Iface.Ext.Types

Binary IEType 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

get :: BinHandle -> IO IEType #

Outputable IEType 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: IEType -> SDoc #

Eq IEType 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Ord IEType 
Instance details

Defined in GHC.Iface.Ext.Types

newtype HieTypeFix #

Roughly isomorphic to the original core Type.

Constructors

Roll (HieType HieTypeFix) 

data HieType a #

A flattened version of Type.

See Note [Efficient serialization of redundant type info]

Constructors

HTyVarTy Name 
HAppTy a (HieArgs a) 
HTyConApp IfaceTyCon (HieArgs a) 
HForAllTy ((Name, a), ArgFlag) a 
HFunTy a a a 
HQualTy a a

type with constraint: t1 => t2 (see IfaceDFunTy)

HLitTy IfaceTyLit 
HCastTy a 
HCoercionTy 

Instances

Instances details
Foldable HieType 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

fold :: Monoid m => HieType m -> m #

foldMap :: Monoid m => (a -> m) -> HieType a -> m #

foldMap' :: Monoid m => (a -> m) -> HieType a -> m #

foldr :: (a -> b -> b) -> b -> HieType a -> b #

foldr' :: (a -> b -> b) -> b -> HieType a -> b #

foldl :: (b -> a -> b) -> b -> HieType a -> b #

foldl' :: (b -> a -> b) -> b -> HieType a -> b #

foldr1 :: (a -> a -> a) -> HieType a -> a #

foldl1 :: (a -> a -> a) -> HieType a -> a #

toList :: HieType a -> [a] #

null :: HieType a -> Bool #

length :: HieType a -> Int #

elem :: Eq a => a -> HieType a -> Bool #

maximum :: Ord a => HieType a -> a #

minimum :: Ord a => HieType a -> a #

sum :: Num a => HieType a -> a #

product :: Num a => HieType a -> a #

Traversable HieType 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

traverse :: Applicative f => (a -> f b) -> HieType a -> f (HieType b) #

sequenceA :: Applicative f => HieType (f a) -> f (HieType a) #

mapM :: Monad m => (a -> m b) -> HieType a -> m (HieType b) #

sequence :: Monad m => HieType (m a) -> m (HieType a) #

Functor HieType 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Binary (HieType TypeIndex) 
Instance details

Defined in GHC.Iface.Ext.Types

Eq a => Eq (HieType a) 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

(==) :: HieType a -> HieType a -> Bool #

(/=) :: HieType a -> HieType a -> Bool #

data HieName #

Name's get converted into HieName's before being written into .hie files. See toHieName and fromHieName for logic on how to convert between these two types.

Instances

Instances details
Outputable HieName 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: HieName -> SDoc #

Eq HieName 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Ord HieName 
Instance details

Defined in GHC.Iface.Ext.Types

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

newtype HieArgs a #

A list of type arguments along with their respective visibilities (ie. is this an argument that would return True for isVisibleArgFlag?).

Constructors

HieArgs [(Bool, a)] 

Instances

Instances details
Foldable HieArgs 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

fold :: Monoid m => HieArgs m -> m #

foldMap :: Monoid m => (a -> m) -> HieArgs a -> m #

foldMap' :: Monoid m => (a -> m) -> HieArgs a -> m #

foldr :: (a -> b -> b) -> b -> HieArgs a -> b #

foldr' :: (a -> b -> b) -> b -> HieArgs a -> b #

foldl :: (b -> a -> b) -> b -> HieArgs a -> b #

foldl' :: (b -> a -> b) -> b -> HieArgs a -> b #

foldr1 :: (a -> a -> a) -> HieArgs a -> a #

foldl1 :: (a -> a -> a) -> HieArgs a -> a #

toList :: HieArgs a -> [a] #

null :: HieArgs a -> Bool #

length :: HieArgs a -> Int #

elem :: Eq a => a -> HieArgs a -> Bool #

maximum :: Ord a => HieArgs a -> a #

minimum :: Ord a => HieArgs a -> a #

sum :: Num a => HieArgs a -> a #

product :: Num a => HieArgs a -> a #

Traversable HieArgs 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

traverse :: Applicative f => (a -> f b) -> HieArgs a -> f (HieArgs b) #

sequenceA :: Applicative f => HieArgs (f a) -> f (HieArgs a) #

mapM :: Monad m => (a -> m b) -> HieArgs a -> m (HieArgs b) #

sequence :: Monad m => HieArgs (m a) -> m (HieArgs a) #

Functor HieArgs 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Binary (HieArgs TypeIndex) 
Instance details

Defined in GHC.Iface.Ext.Types

Eq a => Eq (HieArgs a) 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

(==) :: HieArgs a -> HieArgs a -> Bool #

(/=) :: HieArgs a -> HieArgs a -> Bool #

newtype HieASTs a #

Mapping from filepaths to the corresponding AST

Constructors

HieASTs 

Fields

Instances

Instances details
Foldable HieASTs 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

fold :: Monoid m => HieASTs m -> m #

foldMap :: Monoid m => (a -> m) -> HieASTs a -> m #

foldMap' :: Monoid m => (a -> m) -> HieASTs a -> m #

foldr :: (a -> b -> b) -> b -> HieASTs a -> b #

foldr' :: (a -> b -> b) -> b -> HieASTs a -> b #

foldl :: (b -> a -> b) -> b -> HieASTs a -> b #

foldl' :: (b -> a -> b) -> b -> HieASTs a -> b #

foldr1 :: (a -> a -> a) -> HieASTs a -> a #

foldl1 :: (a -> a -> a) -> HieASTs a -> a #

toList :: HieASTs a -> [a] #

null :: HieASTs a -> Bool #

length :: HieASTs a -> Int #

elem :: Eq a => a -> HieASTs a -> Bool #

maximum :: Ord a => HieASTs a -> a #

minimum :: Ord a => HieASTs a -> a #

sum :: Num a => HieASTs a -> a #

product :: Num a => HieASTs a -> a #

Traversable HieASTs 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

traverse :: Applicative f => (a -> f b) -> HieASTs a -> f (HieASTs b) #

sequenceA :: Applicative f => HieASTs (f a) -> f (HieASTs a) #

mapM :: Monad m => (a -> m b) -> HieASTs a -> m (HieASTs b) #

sequence :: Monad m => HieASTs (m a) -> m (HieASTs a) #

Functor HieASTs 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Binary (HieASTs TypeIndex) 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable a => Outputable (HieASTs a) 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: HieASTs a -> SDoc #

data HieAST a #

Constructors

Node 

Instances

Instances details
Foldable HieAST 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

fold :: Monoid m => HieAST m -> m #

foldMap :: Monoid m => (a -> m) -> HieAST a -> m #

foldMap' :: Monoid m => (a -> m) -> HieAST a -> m #

foldr :: (a -> b -> b) -> b -> HieAST a -> b #

foldr' :: (a -> b -> b) -> b -> HieAST a -> b #

foldl :: (b -> a -> b) -> b -> HieAST a -> b #

foldl' :: (b -> a -> b) -> b -> HieAST a -> b #

foldr1 :: (a -> a -> a) -> HieAST a -> a #

foldl1 :: (a -> a -> a) -> HieAST a -> a #

toList :: HieAST a -> [a] #

null :: HieAST a -> Bool #

length :: HieAST a -> Int #

elem :: Eq a => a -> HieAST a -> Bool #

maximum :: Ord a => HieAST a -> a #

minimum :: Ord a => HieAST a -> a #

sum :: Num a => HieAST a -> a #

product :: Num a => HieAST a -> a #

Traversable HieAST 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

traverse :: Applicative f => (a -> f b) -> HieAST a -> f (HieAST b) #

sequenceA :: Applicative f => HieAST (f a) -> f (HieAST a) #

mapM :: Monad m => (a -> m b) -> HieAST a -> m (HieAST b) #

sequence :: Monad m => HieAST (m a) -> m (HieAST a) #

Functor HieAST 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Binary (HieAST TypeIndex) 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable a => Outputable (HieAST a) 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: HieAST a -> SDoc #

data EvVarSource #

Constructors

EvPatternBind

bound by a pattern match

EvSigBind

bound by a type signature

EvWrapperBind

bound by a hswrapper

EvImplicitBind

bound by an implicit variable

EvInstBind

Bound by some instance of given class

Fields

EvLetBind EvBindDeps

A direct let binding

newtype EvBindDeps #

Eq/Ord instances compare on the converted HieName, as non-exported names may have different uniques after a roundtrip

Constructors

EvBindDeps 

Fields

Instances

Instances details
Binary EvBindDeps 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable EvBindDeps 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: EvBindDeps -> SDoc #

Eq EvBindDeps 
Instance details

Defined in GHC.Iface.Ext.Types

Ord EvBindDeps 
Instance details

Defined in GHC.Iface.Ext.Types

data DeclType #

Constructors

FamDec

type or data family

SynDec

type synonym

DataDec

data declaration

ConDec

constructor declaration

PatSynDec

pattern synonym

ClassDec

class declaration

InstDec

instance declaration

Instances

Instances details
Enum DeclType 
Instance details

Defined in GHC.Iface.Ext.Types

Binary DeclType 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable DeclType 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: DeclType -> SDoc #

Eq DeclType 
Instance details

Defined in GHC.Iface.Ext.Types

Ord DeclType 
Instance details

Defined in GHC.Iface.Ext.Types

data ContextInfo #

Different contexts under which identifiers exist

Constructors

Use

regular variable

MatchBind 
IEThing IEType

import/export

TyDecl 
ValBind

Value binding

Fields

  • BindType

    whether or not the binding is in an instance

  • Scope

    scope over which the value is bound

  • (Maybe Span)

    span of entire binding

PatternBind

Pattern binding

This case is tricky because the bound identifier can be used in two distinct scopes. Consider the following example (with -XViewPatterns)

do (b, a, (a -> True)) <- bar
   foo a

The identifier a has two scopes: in the view pattern (a -> True) and in the rest of the do-block in foo a.

Fields

  • Scope

    scope in the pattern (the variable bound can be used further in the pattern)

  • Scope

    rest of the scope outside the pattern

  • (Maybe Span)

    span of entire binding

ClassTyDecl (Maybe Span) 
Decl

Declaration

Fields

TyVarBind Scope TyVarScope

Type variable

RecField RecFieldContext (Maybe Span)

Record field

EvidenceVarBind

Constraint/Dictionary evidence variable binding

Fields

EvidenceVarUse

Usage of evidence variable

data BindType #

Constructors

RegularBind 
InstanceBind 

Instances

Instances details
Enum BindType 
Instance details

Defined in GHC.Iface.Ext.Types

Binary BindType 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable BindType 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: BindType -> SDoc #

Eq BindType 
Instance details

Defined in GHC.Iface.Ext.Types

Ord BindType 
Instance details

Defined in GHC.Iface.Ext.Types

hieVersion :: Integer #

Current version of .hie files

pattern HiePath :: FastString -> HiePath #

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 #

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

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

data Dependencies #

Dependency information about ALL modules and packages below this one in the import hierarchy.

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

Invariant: none of the lists contain duplicates.

Instances

Instances details
Binary Dependencies 
Instance details

Defined in GHC.Unit.Module.Deps

Eq Dependencies 
Instance details

Defined in GHC.Unit.Module.Deps

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