ghc-8.10.2: The GHC API
Safe HaskellNone
LanguageHaskell2010

HieTypes

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 HieTypes

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 
HQualTy a a

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

HLitTy IfaceTyLit 
HCastTy a 
HCoercionTy 

Instances

Instances details
Functor HieType Source # 
Instance details

Defined in HieTypes

Methods

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

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

Foldable HieType Source # 
Instance details

Defined in HieTypes

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

Defined in HieTypes

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

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

Defined in HieTypes

Methods

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

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

Binary (HieType TypeIndex) Source # 
Instance details

Defined in HieTypes

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

Defined in HieTypes

Methods

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

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

Foldable HieArgs Source # 
Instance details

Defined in HieTypes

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

Defined in HieTypes

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

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

Defined in HieTypes

Methods

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

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

Binary (HieArgs TypeIndex) Source # 
Instance details

Defined in HieTypes

newtype HieASTs a Source #

Mapping from filepaths (represented using FastString) to the corresponding AST

Constructors

HieASTs 

Fields

Instances

Instances details
Functor HieASTs Source # 
Instance details

Defined in HieTypes

Methods

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

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

Foldable HieASTs Source # 
Instance details

Defined in HieTypes

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

Defined in HieTypes

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

Binary (HieASTs TypeIndex) Source # 
Instance details

Defined in HieTypes

data HieAST a Source #

Constructors

Node 

Instances

Instances details
Functor HieAST Source # 
Instance details

Defined in HieTypes

Methods

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

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

Foldable HieAST Source # 
Instance details

Defined in HieTypes

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

Defined in HieTypes

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

Binary (HieAST TypeIndex) Source # 
Instance details

Defined in HieTypes

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

Defined in HieTypes

Methods

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

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

Foldable NodeInfo Source # 
Instance details

Defined in HieTypes

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

Defined in HieTypes

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

Binary (NodeInfo TypeIndex) Source # 
Instance details

Defined in HieTypes

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

Defined in HieTypes

Foldable IdentifierDetails Source # 
Instance details

Defined in HieTypes

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

Defined in HieTypes

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

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

Defined in HieTypes

Semigroup (IdentifierDetails a) Source # 
Instance details

Defined in HieTypes

Monoid (IdentifierDetails a) Source # 
Instance details

Defined in HieTypes

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

Defined in HieTypes

Binary (IdentifierDetails TypeIndex) Source # 
Instance details

Defined in HieTypes

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

data IEType Source #

Types of imports and exports

Instances

Instances details
Enum IEType Source # 
Instance details

Defined in HieTypes

Eq IEType Source # 
Instance details

Defined in HieTypes

Methods

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

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

Ord IEType Source # 
Instance details

Defined in HieTypes

Show IEType Source # 
Instance details

Defined in HieTypes

Binary IEType Source # 
Instance details

Defined in HieTypes

data RecFieldContext Source #

Instances

Instances details
Enum RecFieldContext Source # 
Instance details

Defined in HieTypes

Eq RecFieldContext Source # 
Instance details

Defined in HieTypes

Ord RecFieldContext Source # 
Instance details

Defined in HieTypes

Show RecFieldContext Source # 
Instance details

Defined in HieTypes

Binary RecFieldContext Source # 
Instance details

Defined in HieTypes

data BindType Source #

Constructors

RegularBind 
InstanceBind 

Instances

Instances details
Enum BindType Source # 
Instance details

Defined in HieTypes

Eq BindType Source # 
Instance details

Defined in HieTypes

Ord BindType Source # 
Instance details

Defined in HieTypes

Show BindType Source # 
Instance details

Defined in HieTypes

Binary BindType Source # 
Instance details

Defined in HieTypes

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

Instances

Instances details
Enum DeclType Source # 
Instance details

Defined in HieTypes

Eq DeclType Source # 
Instance details

Defined in HieTypes

Ord DeclType Source # 
Instance details

Defined in HieTypes

Show DeclType Source # 
Instance details

Defined in HieTypes

Binary DeclType Source # 
Instance details

Defined in HieTypes

data Scope Source #

Instances

Instances details
Eq Scope Source # 
Instance details

Defined in HieTypes

Methods

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

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

Data Scope Source # 
Instance details

Defined in HieTypes

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 #

Ord Scope Source # 
Instance details

Defined in HieTypes

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 #

Show Scope Source # 
Instance details

Defined in HieTypes

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

Outputable Scope Source # 
Instance details

Defined in HieTypes

Binary Scope Source # 
Instance details

Defined in HieTypes

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

Instances

Instances details
Eq TyVarScope Source # 
Instance details

Defined in HieTypes

Ord TyVarScope Source # 
Instance details

Defined in HieTypes

Show TyVarScope Source # 
Instance details

Defined in HieTypes

Binary TyVarScope Source # 
Instance details

Defined in HieTypes