calligraphy-0.1.6: HIE-based Haskell call graph and source code visualizer
Safe HaskellSafe-Inferred
LanguageHaskell2010

Calligraphy.Compat.GHC

Description

Thin compatability layer that re-exports things from GHC.

Synopsis

Documentation

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

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

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

Defined in GHC.Iface.Ext.Types

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

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

Instances

Instances details
NFData IfaceTyCon 
Instance details

Defined in GHC.Iface.Type

Methods

rnf :: IfaceTyCon -> () #

Binary IfaceTyCon 
Instance details

Defined in GHC.Iface.Type

Outputable IfaceTyCon 
Instance details

Defined in GHC.Iface.Type

Methods

ppr :: IfaceTyCon -> SDoc #

Eq IfaceTyCon 
Instance details

Defined in GHC.Iface.Type

data ModuleName #

A ModuleName is essentially a simple string, e.g. Data.List.

Instances

Instances details
Data ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Methods

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

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

toConstr :: ModuleName -> Constr #

dataTypeOf :: ModuleName -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

NFData ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Methods

rnf :: ModuleName -> () #

Uniquable ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Binary ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Outputable ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Methods

ppr :: ModuleName -> SDoc #

Eq ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

Ord ModuleName 
Instance details

Defined in GHC.Unit.Module.Name

type Anno ModuleName 
Instance details

Defined in GHC.Hs.ImpExp

data Name #

A unique, unambiguous name for something, containing information about where that thing originated.

Instances

Instances details
Data Name 
Instance details

Defined in GHC.Types.Name

Methods

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

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

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

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

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

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

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

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

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

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

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

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

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

NFData Name 
Instance details

Defined in GHC.Types.Name

Methods

rnf :: Name -> () #

NamedThing Name 
Instance details

Defined in GHC.Types.Name

HasOccName Name 
Instance details

Defined in GHC.Types.Name

Methods

occName :: Name -> OccName #

Uniquable Name 
Instance details

Defined in GHC.Types.Name

Methods

getUnique :: Name -> Unique #

Binary Name

Assumes that the Name is a non-binding one. See putIfaceTopBndr and getIfaceTopBndr for serializing binding Names. See UserData for the rationale for this distinction.

Instance details

Defined in GHC.Types.Name

Methods

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

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

get :: BinHandle -> IO Name #

Outputable Name 
Instance details

Defined in GHC.Types.Name

Methods

ppr :: Name -> SDoc #

OutputableBndr Name 
Instance details

Defined in GHC.Types.Name

Eq Name

The same comments as for Name's Ord instance apply.

Instance details

Defined in GHC.Types.Name

Methods

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

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

Ord Name

Caution: This instance is implemented via nonDetCmpUnique, which means that the ordering is not stable across deserialization or rebuilds.

See nonDetCmpUnique for further information, and trac #15240 for a bug caused by improper use of this instance.

Instance details

Defined in GHC.Types.Name

Methods

compare :: Name -> Name -> Ordering #

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

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

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

type Anno Name 
Instance details

Defined in GHC.Hs.Extension

type Anno (LocatedN Name) 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Name] 
Instance details

Defined in GHC.Hs.Binds

data NameCache #

The NameCache makes sure that there is just one Unique assigned for each original name; i.e. (module-name, occ-name) pair and provides something of a lookup mechanism for those names.

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 

Fields

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

Real Source Location

Represents a single point within a file

Instances

Instances details
Show RealSrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Outputable RealSrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcLoc -> SDoc #

Eq RealSrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Ord RealSrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

data RealSrcSpan #

A SrcSpan delimits a portion of a text file. It could be represented by a pair of (line,column) coordinates, but in fact we optimise slightly by using more compact representations for single-line and zero-length spans, both of which are quite common.

The end position is defined to be the column after the end of the span. That is, a span of (1,1)-(1,2) is one character long, and a span of (1,1)-(1,1) is zero characters long.

Real Source Span

Instances

Instances details
Data RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

toConstr :: RealSrcSpan -> Constr #

dataTypeOf :: RealSrcSpan -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

ToJson RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

json :: RealSrcSpan -> JsonDoc #

Outputable RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcSpan -> SDoc #

Eq RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Ord RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Outputable e => Outputable (GenLocated RealSrcSpan e) 
Instance details

Defined in GHC.Types.SrcLoc

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

type TypeIndex = Int #

availNames :: AvailInfo -> [Name] #

All names made available by the availability information (excluding overloaded selectors)

hieVersion :: Integer #

Current version of .hie files

initNameCache :: UniqSupply -> [Name] -> NameCache #

Return a function to atomically update the name cache.

mkSplitUniqSupply :: Char -> IO UniqSupply #

Create a unique supply out of thin air. The "mask" (Char) supplied is purely cosmetic, making it easier to figure out where a Unique was born. See Note [Uniques and masks].

The payload part of the Uniques allocated from this UniqSupply are guaranteed distinct wrt all other supplies, regardless of their "mask". This is achieved by allocating the payload part from a single source of Uniques, namely genSym, shared across all UniqSupply's.

moduleName :: GenModule unit -> ModuleName #

Module name (e.g. A.B.C)

srcLocCol :: RealSrcLoc -> Int #

Raises an error when used on a "bad" SrcLoc

srcLocLine :: RealSrcLoc -> Int #

Raises an error when used on a "bad" SrcLoc