ghc-9.2.1: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Iface.Ext.Types

Synopsis

Documentation

hieVersion :: Integer Source #

Current version of .hie files

data HieFile Source #

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
Binary HieFile Source # 
Instance details

Defined in GHC.Iface.Ext.Types

data HieType a Source #

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 Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

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

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

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

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

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

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

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

toList :: HieType a -> [a] Source #

null :: HieType a -> Bool Source #

length :: HieType a -> Int Source #

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

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

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

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

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

Traversable HieType Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

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

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

Functor HieType Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Binary (HieType TypeIndex) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Eq a => Eq (HieType a) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

newtype HieTypeFix Source #

Roughly isomorphic to the original core Type.

Constructors

Roll (HieType HieTypeFix) 

newtype HieArgs a Source #

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 Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

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

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

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

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

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

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

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

toList :: HieArgs a -> [a] Source #

null :: HieArgs a -> Bool Source #

length :: HieArgs a -> Int Source #

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

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

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

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

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

Traversable HieArgs Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

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

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

Functor HieArgs Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Binary (HieArgs TypeIndex) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Eq a => Eq (HieArgs a) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

newtype HieASTs a Source #

Mapping from filepaths to the corresponding AST

Constructors

HieASTs 

Fields

Instances

Instances details
Foldable HieASTs Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

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

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

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

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

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

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

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

toList :: HieASTs a -> [a] Source #

null :: HieASTs a -> Bool Source #

length :: HieASTs a -> Int Source #

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

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

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

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

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

Traversable HieASTs Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

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

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

Functor HieASTs Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Binary (HieASTs TypeIndex) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable a => Outputable (HieASTs a) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: HieASTs a -> SDoc Source #

data HieAST a Source #

Constructors

Node 

Instances

Instances details
Foldable HieAST Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

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

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

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

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

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

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

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

toList :: HieAST a -> [a] Source #

null :: HieAST a -> Bool Source #

length :: HieAST a -> Int Source #

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

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

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

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

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

Traversable HieAST Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

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

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

Functor HieAST Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Binary (HieAST TypeIndex) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable a => Outputable (HieAST a) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: HieAST a -> SDoc Source #

newtype SourcedNodeInfo a Source #

NodeInfos grouped by source

Instances

Instances details
Foldable SourcedNodeInfo Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

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

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

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

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

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

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

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

toList :: SourcedNodeInfo a -> [a] Source #

null :: SourcedNodeInfo a -> Bool Source #

length :: SourcedNodeInfo a -> Int Source #

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

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

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

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

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

Traversable SourcedNodeInfo Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Functor SourcedNodeInfo Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary (SourcedNodeInfo TypeIndex) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable a => Outputable (SourcedNodeInfo a) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

data NodeOrigin Source #

Source of node info

Constructors

SourceInfo 
GeneratedInfo 

data NodeInfo a Source #

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 

Fields

Instances

Instances details
Foldable NodeInfo Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

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

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

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

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

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

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

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

toList :: NodeInfo a -> [a] Source #

null :: NodeInfo a -> Bool Source #

length :: NodeInfo a -> Int Source #

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

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

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

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

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

Traversable NodeInfo Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

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

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

Functor NodeInfo Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Binary (NodeInfo TypeIndex) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable a => Outputable (NodeInfo a) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: NodeInfo a -> SDoc Source #

data IdentifierDetails a Source #

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 Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

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

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

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

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

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

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

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

toList :: IdentifierDetails a -> [a] Source #

null :: IdentifierDetails a -> Bool Source #

length :: IdentifierDetails a -> Int Source #

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

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

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

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

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

Traversable IdentifierDetails Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Functor IdentifierDetails Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Monoid (IdentifierDetails a) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Semigroup (IdentifierDetails a) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary (IdentifierDetails TypeIndex) Source # 
Instance details

Defined in GHC.Iface.Ext.Types

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

Defined in GHC.Iface.Ext.Types

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

Defined in GHC.Iface.Ext.Types

data ContextInfo Source #

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 EvVarSource Source #

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 Source #

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

Constructors

EvBindDeps 

Fields

data IEType Source #

Types of imports and exports

Instances

Instances details
Enum IEType Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary IEType Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable IEType Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: IEType -> SDoc Source #

Eq IEType Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Ord IEType Source # 
Instance details

Defined in GHC.Iface.Ext.Types

data RecFieldContext Source #

Instances

Instances details
Enum RecFieldContext Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Binary RecFieldContext Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable RecFieldContext Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Eq RecFieldContext Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Ord RecFieldContext Source # 
Instance details

Defined in GHC.Iface.Ext.Types

data DeclType Source #

Constructors

FamDec

type or data family

SynDec

type synonym

DataDec

data declaration

ConDec

constructor declaration

PatSynDec

pattern synonym

ClassDec

class declaration

InstDec

instance declaration

data Scope Source #

Instances

Instances details
Data Scope Source # 
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 Source #

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

toConstr :: Scope -> Constr Source #

dataTypeOf :: Scope -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Binary Scope Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Outputable Scope Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: Scope -> SDoc Source #

Eq Scope Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Ord Scope Source # 
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 TyVarScope Source #

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

data HieName Source #

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 Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

ppr :: HieName -> SDoc Source #

Eq HieName Source # 
Instance details

Defined in GHC.Iface.Ext.Types

Methods

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

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

Ord HieName Source # 
Instance details

Defined in GHC.Iface.Ext.Types