liquidhaskell-boot-0.9.6.3: Liquid Types for Haskell
Safe HaskellSafe-Inferred
LanguageHaskell98

Liquid.GHC.API

Description

This module re-exports all identifiers that LH needs from the GHC API.

The intended use of this module is to provide a quick look of what GHC API features LH depends upon.

The transitive dependencies of this module shouldn't contain modules from Language.Haskell.Liquid.* or other non-boot libraries. This makes it easy to discover breaking changes in the GHC API.

Synopsis

Documentation

data Type #

Constructors

TyVarTy Var

Vanilla type or kind variable (*never* a coercion variable)

AppTy Type Type

Type application to something other than a TyCon. Parameters:

1) Function: must not be a TyConApp or CastTy, must be another AppTy, or TyVarTy See Note [Respecting definitional equality] (EQ1) about the no CastTy requirement

2) Argument type

TyConApp TyCon [KindOrType]

Application of a TyCon, including newtypes and synonyms. Invariant: saturated applications of FunTyCon must use FunTy and saturated synonyms must use their own constructors. However, unsaturated FunTyCons do appear as TyConApps. Parameters:

1) Type constructor being applied to.

2) Type arguments. Might not have enough type arguments here to saturate the constructor. Even type synonyms are not necessarily saturated; for example unsaturated type synonyms can appear as the right hand side of a type synonym.

ForAllTy !ForAllTyBinder Type

A Π type. Note [When we quantify over a coercion variable] INVARIANT: If the binder is a coercion variable, it must be mentioned in the Type. See Note [Unused coercion variable in ForAllTy]

FunTy FunTyFlag Mult Type Type

FUN m t1 t2 Very common, so an important special case See Note [Function types]

LitTy TyLit

Type literals are similar to type constructors.

CastTy Type KindCoercion

A kind cast. The coercion is always nominal. INVARIANT: The cast is never reflexive (EQ2) INVARIANT: The Type is not a CastTy (use TransCo instead) (EQ3) INVARIANT: The Type is not a ForAllTy over a tyvar (EQ4) See Note [Respecting definitional equality]

CoercionTy Coercion

Injection of a Coercion into a type This should only ever be used in the RHS of an AppTy, in the list of a TyConApp, when applying a promoted GADT data constructor

Instances

Instances details
Data Type 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

NFData Type Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

rnf :: Type -> () #

Outputable Type 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Type -> SDoc #

Eq Type Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.TypeRep

Methods

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

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

Fixpoint Type Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

toFix :: Type -> Doc #

simplify :: Type -> Type #

PPrint Type Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.PrettyPrint

Methods

pprintTidy :: Tidy -> Type -> Doc #

pprintPrec :: Int -> Tidy -> Type -> Doc #

Subable Type Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Play

SubsTy TyVar Type SpecType Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.RefType

Methods

subt :: (TyVar, Type) -> SpecType -> SpecType Source #

Eq (DeBruijn Type) 
Instance details

Defined in GHC.Core.Map.Type

Show (Axiom Var Type CoreExpr) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

data GhcMode #

The GhcMode tells us whether we're doing multi-module compilation (controlled via the GHC API) or one-shot (single-module) compilation. This makes a difference primarily to the GHC.Unit.Finder: in one-shot mode we look for interface files for imported modules, but in multi-module mode we look for source files in order to check whether they need to be recompiled.

Constructors

CompManager

--make, GHCi, etc.

Instances

Instances details
Outputable GhcMode 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: GhcMode -> SDoc #

Eq GhcMode 
Instance details

Defined in GHC.Driver.Session

Methods

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

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

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 #

Show Name Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

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 #

Symbolic Name Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

symbol :: Name -> Symbol #

Fixpoint Name Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

toFix :: Name -> Doc #

simplify :: Name -> Name #

PPrint Name Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.PrettyPrint

Methods

pprintTidy :: Tidy -> Name -> Doc #

pprintPrec :: Int -> Tidy -> Name -> Doc #

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

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

Instances

Instances details
Data ModuleName 
Instance details

Defined in Language.Haskell.Syntax.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 Language.Haskell.Syntax.Module.Name

NFData ModuleName 
Instance details

Defined in Language.Haskell.Syntax.Module.Name

Methods

rnf :: ModuleName -> () #

Uniquable ModuleName 
Instance details

Defined in GHC.Types.Unique

Outputable ModuleName 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: ModuleName -> SDoc #

Eq ModuleName 
Instance details

Defined in Language.Haskell.Syntax.Module.Name

Ord ModuleName 
Instance details

Defined in Language.Haskell.Syntax.Module.Name

Hashable ModuleName Source # 
Instance details

Defined in Liquid.GHC.API.StableModule

Symbolic ModuleName Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

Methods

symbol :: ModuleName -> Symbol #

type Anno ModuleName 
Instance details

Defined in GHC.Hs

type Anno ModuleName 
Instance details

Defined in GHC.Hs.ImpExp

data UnitId #

A UnitId identifies a built library in a database and is used to generate unique symbols, etc. It's usually of the form:

pkgname-1.2:libname+hash

These UnitId are provided to us via the -this-unit-id flag.

The library in question may be definite or indefinite; if it is indefinite, none of the holes have been filled (we never install partially instantiated libraries as we can cheaply instantiate them on-the-fly, cf VirtUnit). Put another way, an installed unit id is either fully instantiated, or not instantiated at all.

Instances

Instances details
Data Unit 
Instance details

Defined in GHC.Unit.Types

Methods

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

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

toConstr :: Unit -> Constr #

dataTypeOf :: Unit -> DataType #

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

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

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

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

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

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

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

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

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

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

Data UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

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

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

toConstr :: UnitId -> Constr #

dataTypeOf :: UnitId -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Unit 
Instance details

Defined in GHC.Unit.Types

Methods

showsPrec :: Int -> Unit -> ShowS #

show :: Unit -> String #

showList :: [Unit] -> ShowS #

NFData Unit 
Instance details

Defined in GHC.Unit.Types

Methods

rnf :: Unit -> () #

Uniquable Module 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Module -> Unique #

Uniquable UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: UnitId -> Unique #

IsUnitId UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: UnitId -> FastString #

Binary InstantiatedUnit 
Instance details

Defined in GHC.Unit.Types

Binary Unit 
Instance details

Defined in GHC.Unit.Types

Methods

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

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

get :: BinHandle -> IO Unit #

Binary UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

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

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

get :: BinHandle -> IO UnitId #

Outputable InstalledModule 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: InstalledModule -> SDoc #

Outputable InstantiatedModule 
Instance details

Defined in GHC.Unit.Types

Outputable InstantiatedUnit 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: InstantiatedUnit -> SDoc #

Outputable Module 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Module -> SDoc #

Outputable Unit 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Unit -> SDoc #

Outputable UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: UnitId -> SDoc #

Eq UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

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

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

Ord Unit 
Instance details

Defined in GHC.Unit.Types

Methods

compare :: Unit -> Unit -> Ordering #

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

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

(>) :: Unit -> Unit -> Bool #

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

max :: Unit -> Unit -> Unit #

min :: Unit -> Unit -> Unit #

Ord UnitId 
Instance details

Defined in GHC.Unit.Types

type Module = GenModule Unit #

A Module is a pair of a Unit and a ModuleName.

data SrcLoc #

Source Location

Instances

Instances details
Show SrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Outputable SrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcLoc -> SDoc #

Eq SrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

data TyCon #

TyCons represent type constructors. Type constructors are introduced by things such as:

1) Data declarations: data Foo = ... creates the Foo type constructor of kind *

2) Type synonyms: type Foo = ... creates the Foo type constructor

3) Newtypes: newtype Foo a = MkFoo ... creates the Foo type constructor of kind * -> *

4) Class declarations: class Foo where creates the Foo type constructor of kind *

This data type also encodes a number of primitive, built in type constructors such as those for function and tuple types.

If you edit this type, you may need to update the GHC formalism See Note [GHC Formalism] in GHC.Core.Lint

Instances

Instances details
Data TyCon 
Instance details

Defined in GHC.Core.TyCon

Methods

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

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

toConstr :: TyCon -> Constr #

dataTypeOf :: TyCon -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TyCon Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

showsPrec :: Int -> TyCon -> ShowS #

show :: TyCon -> String #

showList :: [TyCon] -> ShowS #

NFData TyCon Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

rnf :: TyCon -> () #

NamedThing TyCon 
Instance details

Defined in GHC.Core.TyCon

Uniquable TyCon 
Instance details

Defined in GHC.Core.TyCon

Methods

getUnique :: TyCon -> Unique #

Outputable TyCon 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: TyCon -> SDoc #

Outputable OccurrenceMap Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Play

Methods

ppr :: OccurrenceMap -> SDoc #

Eq TyCon 
Instance details

Defined in GHC.Core.TyCon

Methods

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

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

Ord TyCon Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

Methods

compare :: TyCon -> TyCon -> Ordering #

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

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

(>) :: TyCon -> TyCon -> Bool #

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

max :: TyCon -> TyCon -> TyCon #

min :: TyCon -> TyCon -> TyCon #

Hashable TyCon Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

hashWithSalt :: Int -> TyCon -> Int #

hash :: TyCon -> Int #

Symbolic TyCon Source #

Symbol Instances

Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

symbol :: TyCon -> Symbol #

PPrint TyCon Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.PrettyPrint

Methods

pprintTidy :: Tidy -> TyCon -> Doc #

pprintPrec :: Int -> Tidy -> TyCon -> Doc #

ResolveSym TyCon Source # 
Instance details

Defined in Language.Haskell.Liquid.Bare.Resolve

TyConable TyCon Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

data Var #

Variable

Essentially a typed Name, that may also contain some additional information about the Var and its use sites.

Instances

Instances details
Data Var 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: Var -> Constr #

dataTypeOf :: Var -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CoreExpr Source # 
Instance details

Defined in Language.Haskell.Liquid.Transforms.CoreToLogic

Show Var Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

NFData Var Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

rnf :: Var -> () #

NamedThing Var 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: Var -> OccName #

getName :: Var -> Name #

HasOccName Var 
Instance details

Defined in GHC.Types.Var

Methods

occName :: Var -> OccName #

Uniquable Var 
Instance details

Defined in GHC.Types.Var

Methods

getUnique :: Var -> Unique #

Outputable Var 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: Var -> SDoc #

Eq Var 
Instance details

Defined in GHC.Types.Var

Methods

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

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

Ord Var 
Instance details

Defined in GHC.Types.Var

Methods

compare :: Var -> Var -> Ordering #

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

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

(>) :: Var -> Var -> Bool #

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

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Hashable Var Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

hashWithSalt :: Int -> Var -> Int #

hash :: Var -> Int #

Symbolic Var Source #
NOTE:REFLECT-IMPORTS
we **eschew** the unique suffix for exported vars, to make it possible to lookup names from symbols _across_ modules; anyways exported names are top-level and you shouldn't have local binders that shadow them. However, we **keep** the unique suffix for local variables, as otherwise there are spurious, but extremely problematic, name collisions in the fixpoint environment.
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

symbol :: Var -> Symbol #

Fixpoint Var Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

toFix :: Var -> Doc #

simplify :: Var -> Var #

PPrint Var Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.PrettyPrint

Methods

pprintTidy :: Tidy -> Var -> Doc #

pprintPrec :: Int -> Tidy -> Var -> Doc #

Expression Var Source #

Converting to Fixpoint ----------------------------------------------------

Instance details

Defined in Language.Haskell.Liquid.Types.RefType

Methods

expr :: Var -> Expr #

Loc Var Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

srcSpan :: Var -> SrcSpan #

ResolveSym Var Source # 
Instance details

Defined in Language.Haskell.Liquid.Bare.Resolve

Subable CoreExpr Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Play

Subable Var Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Play

CBVisitable CoreBind Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Visitors

SubsTy TyVar Type SpecType Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.RefType

Methods

subt :: (TyVar, Type) -> SpecType -> SpecType Source #

Eq (DeBruijn Var) 
Instance details

Defined in GHC.Core.Map.Type

PPrint (Bind Var) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.PrettyPrint

Methods

pprintTidy :: Tidy -> Bind Var -> Doc #

pprintPrec :: Int -> Tidy -> Bind Var -> Doc #

PPrint (Expr Var) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.PrettyPrint

Methods

pprintTidy :: Tidy -> Expr Var -> Doc #

pprintPrec :: Int -> Tidy -> Expr Var -> Doc #

Subable (Alt Var) Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Play

Subable (Bind Var) Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Play

CBVisitable (Alt Var) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Visitors

CBVisitable (Expr Var) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Visitors

CBVisitable [CoreBind] Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Visitors

OutputableBndr (Id, TagSig) 
Instance details

Defined in GHC.Stg.InferTags.TagSig

Show (Axiom Var Type CoreExpr) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

type Anno Id 
Instance details

Defined in GHC.Hs.Extension

type Anno (LocatedN Id) 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] 
Instance details

Defined in GHC.Hs.Binds

data Pair a #

Constructors

Pair a a 

Instances

Instances details
Foldable Pair 
Instance details

Defined in GHC.Data.Pair

Methods

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

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

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

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

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

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

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

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

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

toList :: Pair a -> [a] #

null :: Pair a -> Bool #

length :: Pair a -> Int #

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

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

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

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

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

Traversable Pair 
Instance details

Defined in GHC.Data.Pair

Methods

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

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

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

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

Applicative Pair 
Instance details

Defined in GHC.Data.Pair

Methods

pure :: a -> Pair a #

(<*>) :: Pair (a -> b) -> Pair a -> Pair b #

liftA2 :: (a -> b -> c) -> Pair a -> Pair b -> Pair c #

(*>) :: Pair a -> Pair b -> Pair b #

(<*) :: Pair a -> Pair b -> Pair a #

Functor Pair 
Instance details

Defined in GHC.Data.Pair

Methods

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

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

(Semigroup a, Monoid a) => Monoid (Pair a) 
Instance details

Defined in GHC.Data.Pair

Methods

mempty :: Pair a #

mappend :: Pair a -> Pair a -> Pair a #

mconcat :: [Pair a] -> Pair a #

Semigroup a => Semigroup (Pair a) 
Instance details

Defined in GHC.Data.Pair

Methods

(<>) :: Pair a -> Pair a -> Pair a #

sconcat :: NonEmpty (Pair a) -> Pair a #

stimes :: Integral b => b -> Pair a -> Pair a #

Outputable a => Outputable (Pair a) 
Instance details

Defined in GHC.Data.Pair

Methods

ppr :: Pair a -> SDoc #

type Arity = Int #

The number of value arguments that can be applied to a value before it does "real work". So: fib 100 has arity 0 x -> fib x has arity 1 See also Note [Definition of arity] in GHC.Core.Opt.Arity

type Kind = Type #

The key type representing kinds in the compiler.

data ConLike #

A constructor-like thing

Constructors

RealDataCon DataCon 

Instances

Instances details
Data ConLike 
Instance details

Defined in GHC.Core.ConLike

Methods

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

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

toConstr :: ConLike -> Constr #

dataTypeOf :: ConLike -> DataType #

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

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

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

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

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

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

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

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

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

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

NamedThing ConLike 
Instance details

Defined in GHC.Core.ConLike

Uniquable ConLike 
Instance details

Defined in GHC.Core.ConLike

Methods

getUnique :: ConLike -> Unique #

Outputable ConLike 
Instance details

Defined in GHC.Core.ConLike

Methods

ppr :: ConLike -> SDoc #

OutputableBndr ConLike 
Instance details

Defined in GHC.Core.ConLike

Eq ConLike 
Instance details

Defined in GHC.Core.ConLike

Methods

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

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

type Anno ConLike 
Instance details

Defined in GHC.Hs.Pat

data Coercion #

A Coercion is concrete evidence of the equality/convertibility of two types.

Instances

Instances details
Data Coercion 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: Coercion -> Constr #

dataTypeOf :: Coercion -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable Coercion 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Coercion -> SDoc #

Eq Coercion Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.TypeRep

Subable Coercion Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Play

Eq (DeBruijn Coercion) 
Instance details

Defined in GHC.Core.Map.Type

data Fixity #

Instances

Instances details
Data Fixity 
Instance details

Defined in GHC.Types.Fixity

Methods

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

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

toConstr :: Fixity -> Constr #

dataTypeOf :: Fixity -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary Fixity 
Instance details

Defined in GHC.Types.Fixity

Methods

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

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

get :: BinHandle -> IO Fixity #

Outputable Fixity 
Instance details

Defined in GHC.Types.Fixity

Methods

ppr :: Fixity -> SDoc #

Eq Fixity 
Instance details

Defined in GHC.Types.Fixity

Methods

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

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

data Alt b #

A case split alternative. Consists of the constructor leading to the alternative, the variables bound from the constructor, and the expression to be executed given that binding. The default alternative is (DEFAULT, [], rhs)

Constructors

Alt AltCon [b] (Expr b) 

Instances

Instances details
Data b => Data (Alt b) 
Instance details

Defined in GHC.Core

Methods

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

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

toConstr :: Alt b -> Constr #

dataTypeOf :: Alt b -> DataType #

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

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

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

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

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

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

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

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

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

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

Subable (Alt Var) Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Play

CBVisitable (Alt Var) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Visitors

data CostCentre #

A Cost Centre is a single {-# SCC #-} annotation.

Instances

Instances details
Data CostCentre 
Instance details

Defined in GHC.Types.CostCentre

Methods

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

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

toConstr :: CostCentre -> Constr #

dataTypeOf :: CostCentre -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary CostCentre 
Instance details

Defined in GHC.Types.CostCentre

Outputable CostCentre 
Instance details

Defined in GHC.Types.CostCentre

Methods

ppr :: CostCentre -> SDoc #

Eq CostCentre 
Instance details

Defined in GHC.Types.CostCentre

Ord CostCentre 
Instance details

Defined in GHC.Types.CostCentre

data Unique #

Unique identifier.

The type of unique identifiers that are used in many places in GHC for fast ordering and equality tests. You should generate these with the functions from the UniqSupply module

These are sometimes also referred to as "keys" in comments in GHC.

Instances

Instances details
Show Unique 
Instance details

Defined in GHC.Types.Unique

Uniquable Unique 
Instance details

Defined in GHC.Types.Unique

Methods

getUnique :: Unique -> Unique #

Outputable Unique 
Instance details

Defined in GHC.Types.Unique

Methods

ppr :: Unique -> SDoc #

Eq Unique 
Instance details

Defined in GHC.Types.Unique

Methods

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

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

type Arg b = Expr b #

Type synonym for expressions that occur in function argument positions. Only Arg should contain a Type at top level, general Expr should not

class (IsOutput doc, IsLine (Line doc)) => IsDoc doc where #

A class of types that represent a multiline document, with support for vertical composition.

See Note [HLine versus HDoc] and Note [The outputable class hierarchy] for more details.

Minimal complete definition

line, ($$), dualDoc

Associated Types

type Line doc = (r :: Type) | r -> doc #

Methods

line :: Line doc -> doc #

($$) :: doc -> doc -> doc #

Join two docs together vertically. If there is no vertical overlap it "dovetails" the two onto one line.

lines_ :: [Line doc] -> doc #

vcat :: [doc] -> doc #

Concatenate docs vertically with dovetailing.

dualDoc :: SDoc -> HDoc -> doc #

Prints as either the given SDoc or the given HDoc, depending on which type the result is instantiated to. This should generally be avoided; see Note [dualLine and dualDoc] for details.

Instances

Instances details
IsDoc HDoc 
Instance details

Defined in GHC.Utils.Outputable

Associated Types

type Line HDoc = (r :: Type) #

Methods

line :: Line HDoc -> HDoc #

($$) :: HDoc -> HDoc -> HDoc #

lines_ :: [Line HDoc] -> HDoc #

vcat :: [HDoc] -> HDoc #

dualDoc :: SDoc -> HDoc -> HDoc #

IsDoc SDoc 
Instance details

Defined in GHC.Utils.Outputable

Associated Types

type Line SDoc = (r :: Type) #

Methods

line :: Line SDoc -> SDoc #

($$) :: SDoc -> SDoc -> SDoc #

lines_ :: [Line SDoc] -> SDoc #

vcat :: [SDoc] -> SDoc #

dualDoc :: SDoc -> HDoc -> SDoc #

type family Line doc = (r :: Type) | r -> doc #

Instances

Instances details
type Line HDoc 
Instance details

Defined in GHC.Utils.Outputable

type Line HDoc = HLine
type Line SDoc 
Instance details

Defined in GHC.Utils.Outputable

type Line SDoc = SDoc

data Env gbl lcl #

Instances

Instances details
ContainsHooks (Env gbl lcl) 
Instance details

Defined in GHC.Tc.Types

Methods

extractHooks :: Env gbl lcl -> Hooks #

ContainsDynFlags (Env gbl lcl) 
Instance details

Defined in GHC.Tc.Types

Methods

extractDynFlags :: Env gbl lcl -> DynFlags #

ContainsModule gbl => ContainsModule (Env gbl lcl) 
Instance details

Defined in GHC.Tc.Types

Methods

extractModule :: Env gbl lcl -> Module #

ContainsLogger (Env gbl lcl) 
Instance details

Defined in GHC.Tc.Types

Methods

extractLogger :: Env gbl lcl -> Logger #

class Outputable a where #

Class designating that some type has an SDoc representation

Methods

ppr :: a -> SDoc #

Instances

Instances details
Outputable Fingerprint 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Fingerprint -> SDoc #

Outputable Int16 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Int16 -> SDoc #

Outputable Int32 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Int32 -> SDoc #

Outputable Int64 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Int64 -> SDoc #

Outputable Int8 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Int8 -> SDoc #

Outputable Word16 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Word16 -> SDoc #

Outputable Word32 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Word32 -> SDoc #

Outputable Word64 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Word64 -> SDoc #

Outputable Word8 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Word8 -> SDoc #

Outputable IntSet 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: IntSet -> SDoc #

Outputable CoreModule 
Instance details

Defined in GHC

Methods

ppr :: CoreModule -> SDoc #

Outputable ByteOff 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: ByteOff -> SDoc #

Outputable CgBreakInfo 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: CgBreakInfo -> SDoc #

Outputable CompiledByteCode 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: CompiledByteCode -> SDoc #

Outputable NativeCallInfo 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: NativeCallInfo -> SDoc #

Outputable RegBitmap 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: RegBitmap -> SDoc #

Outputable UnlinkedBCO 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: UnlinkedBCO -> SDoc #

Outputable WordOff 
Instance details

Defined in GHC.ByteCode.Types

Methods

ppr :: WordOff -> SDoc #

Outputable Label 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

ppr :: Label -> SDoc #

Outputable LabelSet 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

ppr :: LabelSet -> SDoc #

Outputable AltCon 
Instance details

Defined in GHC.Core

Methods

ppr :: AltCon -> SDoc #

Outputable Class 
Instance details

Defined in GHC.Core.Class

Methods

ppr :: Class -> SDoc #

Outputable LiftingContext 
Instance details

Defined in GHC.Core.Coercion

Methods

ppr :: LiftingContext -> SDoc #

Outputable CoAxBranch 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: CoAxBranch -> SDoc #

Outputable CoAxiomRule 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: CoAxiomRule -> SDoc #

Outputable ConLike 
Instance details

Defined in GHC.Core.ConLike

Methods

ppr :: ConLike -> SDoc #

Outputable DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: DataCon -> SDoc #

Outputable EqSpec 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: EqSpec -> SDoc #

Outputable HsImplBang 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: HsImplBang -> SDoc #

Outputable HsSrcBang 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: HsSrcBang -> SDoc #

Outputable StrictnessMark 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: StrictnessMark -> SDoc #

Outputable FamInst 
Instance details

Defined in GHC.Core.FamInstEnv

Methods

ppr :: FamInst -> SDoc #

Outputable FamInstEnv 
Instance details

Defined in GHC.Core.FamInstEnv

Methods

ppr :: FamInstEnv -> SDoc #

Outputable FamInstMatch 
Instance details

Defined in GHC.Core.FamInstEnv

Methods

ppr :: FamInstMatch -> SDoc #

Outputable ClsInst 
Instance details

Defined in GHC.Core.InstEnv

Methods

ppr :: ClsInst -> SDoc #

Outputable InstEnv 
Instance details

Defined in GHC.Core.InstEnv

Methods

ppr :: InstEnv -> SDoc #

Outputable InstMatches 
Instance details

Defined in GHC.Core.InstEnv

Methods

ppr :: InstMatches -> SDoc #

Outputable PotentialUnifiers 
Instance details

Defined in GHC.Core.InstEnv

Outputable FloatBind 
Instance details

Defined in GHC.Core.Make

Methods

ppr :: FloatBind -> SDoc #

Outputable CallerCcFilter 
Instance details

Defined in GHC.Core.Opt.CallerCC

Methods

ppr :: CallerCcFilter -> SDoc #

Outputable NamePattern 
Instance details

Defined in GHC.Core.Opt.CallerCC

Methods

ppr :: NamePattern -> SDoc #

Outputable FloatOutSwitches 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

ppr :: FloatOutSwitches -> SDoc #

Outputable Details 
Instance details

Defined in GHC.Core.Opt.OccurAnal

Methods

ppr :: Details -> SDoc #

Outputable OccEncl 
Instance details

Defined in GHC.Core.Opt.OccurAnal

Methods

ppr :: OccEncl -> SDoc #

Outputable UsageDetails 
Instance details

Defined in GHC.Core.Opt.OccurAnal

Methods

ppr :: UsageDetails -> SDoc #

Outputable CoreToDo 
Instance details

Defined in GHC.Core.Opt.Pipeline.Types

Methods

ppr :: CoreToDo -> SDoc #

Outputable PatSyn 
Instance details

Defined in GHC.Core.PatSyn

Methods

ppr :: PatSyn -> SDoc #

Outputable EqRel 
Instance details

Defined in GHC.Core.Predicate

Methods

ppr :: EqRel -> SDoc #

Outputable Reduction 
Instance details

Defined in GHC.Core.Reduction

Methods

ppr :: Reduction -> SDoc #

Outputable RoughMatchLookupTc 
Instance details

Defined in GHC.Core.RoughMap

Outputable RoughMatchTc 
Instance details

Defined in GHC.Core.RoughMap

Methods

ppr :: RoughMatchTc -> SDoc #

Outputable CoSel 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: CoSel -> SDoc #

Outputable Coercion 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Coercion -> SDoc #

Outputable CoercionHole 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: CoercionHole -> SDoc #

Outputable FunSel 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: FunSel -> SDoc #

Outputable MCoercion 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: MCoercion -> SDoc #

Outputable TyLit 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: TyLit -> SDoc #

Outputable Type 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Type -> SDoc #

Outputable UnivCoProvenance 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: UnivCoProvenance -> SDoc #

Outputable Subst 
Instance details

Defined in GHC.Core.TyCo.Subst

Methods

ppr :: Subst -> SDoc #

Outputable AlgTyConFlav 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: AlgTyConFlav -> SDoc #

Outputable FamTyConFlav 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: FamTyConFlav -> SDoc #

Outputable PrimElemRep 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: PrimElemRep -> SDoc #

Outputable PrimRep 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: PrimRep -> SDoc #

Outputable TyCon 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: TyCon -> SDoc #

Outputable TyConBndrVis 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: TyConBndrVis -> SDoc #

Outputable TyConFlavour 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: TyConFlavour -> SDoc #

Outputable ArgSummary 
Instance details

Defined in GHC.Core.Unfold

Methods

ppr :: ArgSummary -> SDoc #

Outputable CallCtxt 
Instance details

Defined in GHC.Core.Unfold

Methods

ppr :: CallCtxt -> SDoc #

Outputable ExprSize 
Instance details

Defined in GHC.Core.Unfold

Methods

ppr :: ExprSize -> SDoc #

Outputable MaybeApartReason 
Instance details

Defined in GHC.Core.Unify

Methods

ppr :: MaybeApartReason -> SDoc #

Outputable FastString 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: FastString -> SDoc #

Outputable LexicalFastString 
Instance details

Defined in GHC.Utils.Outputable

Outputable NonDetFastString 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: NonDetFastString -> SDoc #

Outputable Language 
Instance details

Defined in GHC.Driver.Flags

Methods

ppr :: Language -> SDoc #

Outputable BuildPlan 
Instance details

Defined in GHC.Driver.Make

Methods

ppr :: BuildPlan -> SDoc #

Outputable CachedIface 
Instance details

Defined in GHC.Driver.Make

Methods

ppr :: CachedIface -> SDoc #

Outputable CodeGenEnable 
Instance details

Defined in GHC.Driver.Make

Methods

ppr :: CodeGenEnable -> SDoc #

Outputable ModuleGraphNodeWithBootFile 
Instance details

Defined in GHC.Driver.Make

Methods

ppr :: ModuleGraphNodeWithBootFile -> SDoc #

Outputable Phase 
Instance details

Defined in GHC.Driver.Phases

Methods

ppr :: Phase -> SDoc #

Outputable PluginRecompile 
Instance details

Defined in GHC.Driver.Plugins

Methods

ppr :: PluginRecompile -> SDoc #

Outputable GhcMode 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: GhcMode -> SDoc #

Outputable ModRenaming 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: ModRenaming -> SDoc #

Outputable PackageArg 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: PackageArg -> SDoc #

Outputable PackageFlag 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: PackageFlag -> SDoc #

Outputable ABExport 
Instance details

Defined in GHC.Hs.Binds

Methods

ppr :: ABExport -> SDoc #

Outputable TcSpecPrag 
Instance details

Defined in GHC.Hs.Binds

Methods

ppr :: TcSpecPrag -> SDoc #

Outputable XViaStrategyPs 
Instance details

Defined in GHC.Hs.Decls

Methods

ppr :: XViaStrategyPs -> SDoc #

Outputable DocStructureItem 
Instance details

Defined in GHC.Hs.Doc

Methods

ppr :: DocStructureItem -> SDoc #

Outputable Docs 
Instance details

Defined in GHC.Hs.Doc

Methods

ppr :: Docs -> SDoc #

Outputable HsDocString 
Instance details

Defined in GHC.Hs.DocString

Methods

ppr :: HsDocString -> SDoc #

Outputable HsDocStringChunk 
Instance details

Defined in GHC.Hs.DocString

Methods

ppr :: HsDocStringChunk -> SDoc #

Outputable HsDocStringDecorator 
Instance details

Defined in GHC.Hs.DocString

Outputable GrhsAnn 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: GrhsAnn -> SDoc #

Outputable PendingRnSplice 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: PendingRnSplice -> SDoc #

Outputable PendingTcSplice 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: PendingTcSplice -> SDoc #

Outputable SyntaxExprRn 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: SyntaxExprRn -> SDoc #

Outputable SyntaxExprTc 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: SyntaxExprTc -> SDoc #

Outputable XXExprGhcTc 
Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: XXExprGhcTc -> SDoc #

Outputable DsMatchContext 
Instance details

Defined in GHC.HsToCore.Monad

Methods

ppr :: DsMatchContext -> SDoc #

Outputable EquationInfo 
Instance details

Defined in GHC.HsToCore.Monad

Methods

ppr :: EquationInfo -> SDoc #

Outputable BotInfo 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: BotInfo -> SDoc #

Outputable Nabla 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: Nabla -> SDoc #

Outputable Nablas 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: Nablas -> SDoc #

Outputable PmAltCon 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmAltCon -> SDoc #

Outputable PmAltConApp 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmAltConApp -> SDoc #

Outputable PmAltConSet 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmAltConSet -> SDoc #

Outputable PmEquality 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmEquality -> SDoc #

Outputable PmLit 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmLit -> SDoc #

Outputable PmLitValue 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: PmLitValue -> SDoc #

Outputable ResidualCompleteMatches 
Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Outputable TmState

Not user-facing.

Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: TmState -> SDoc #

Outputable TyState

Not user-facing.

Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: TyState -> SDoc #

Outputable VarInfo

Not user-facing.

Instance details

Defined in GHC.HsToCore.Pmc.Solver.Types

Methods

ppr :: VarInfo -> SDoc #

Outputable IfGuidance 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfGuidance -> SDoc #

Outputable IfaceAT 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceAT -> SDoc #

Outputable IfaceAnnotation 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceAnnotation -> SDoc #

Outputable IfaceClassOp 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceClassOp -> SDoc #

Outputable IfaceClsInst 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceClsInst -> SDoc #

Outputable IfaceCompleteMatch 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceConAlt 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceConAlt -> SDoc #

Outputable IfaceDecl 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceDecl -> SDoc #

Outputable IfaceExpr 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceExpr -> SDoc #

Outputable IfaceFamInst 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceFamInst -> SDoc #

Outputable IfaceIdDetails 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceIdDetails -> SDoc #

Outputable IfaceInfoItem 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceInfoItem -> SDoc #

Outputable IfaceJoinInfo 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceJoinInfo -> SDoc #

Outputable IfaceLFInfo 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceLFInfo -> SDoc #

Outputable IfaceMaybeRhs 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceMaybeRhs -> SDoc #

Outputable IfaceRule 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceRule -> SDoc #

Outputable IfaceTopBndrInfo 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceTopBndrInfo -> SDoc #

Outputable IfaceTyConParent 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceTyConParent -> SDoc #

Outputable IfaceUnfolding 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceUnfolding -> SDoc #

Outputable ShowHowMuch 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: ShowHowMuch -> SDoc #

Outputable LibrarySpec 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: LibrarySpec -> SDoc #

Outputable Linkable 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: Linkable -> SDoc #

Outputable LoadedPkgInfo 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: LoadedPkgInfo -> SDoc #

Outputable SptEntry 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: SptEntry -> SDoc #

Outputable Unlinked 
Instance details

Defined in GHC.Linker.Types

Methods

ppr :: Unlinked -> SDoc #

Outputable AddEpAnn 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AddEpAnn -> SDoc #

Outputable Anchor 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: Anchor -> SDoc #

Outputable AnchorOperation 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnchorOperation -> SDoc #

Outputable AnnContext 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnContext -> SDoc #

Outputable AnnKeywordId 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnKeywordId -> SDoc #

Outputable AnnList 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnList -> SDoc #

Outputable AnnListItem 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnListItem -> SDoc #

Outputable AnnPragma 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnPragma -> SDoc #

Outputable AnnSortKey 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: AnnSortKey -> SDoc #

Outputable DeltaPos 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: DeltaPos -> SDoc #

Outputable EpAnnComments 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpAnnComments -> SDoc #

Outputable EpaComment 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpaComment -> SDoc #

Outputable EpaLocation 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpaLocation -> SDoc #

Outputable IsUnicodeSyntax 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: IsUnicodeSyntax -> SDoc #

Outputable NameAdornment 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: NameAdornment -> SDoc #

Outputable NameAnn 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: NameAnn -> SDoc #

Outputable NoEpAnns 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: NoEpAnns -> SDoc #

Outputable TrailingAnn 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: TrailingAnn -> SDoc #

Outputable Token 
Instance details

Defined in GHC.Parser.Lexer

Methods

ppr :: Token -> SDoc #

Outputable DataConBuilder 
Instance details

Defined in GHC.Parser.Types

Methods

ppr :: DataConBuilder -> SDoc #

Outputable MonadNames 
Instance details

Defined in GHC.Rename.Expr

Methods

ppr :: MonadNames -> SDoc #

Outputable InteractiveImport 
Instance details

Defined in GHC.Runtime.Context

Outputable GetDocsFailure 
Instance details

Defined in GHC.Runtime.Eval

Methods

ppr :: GetDocsFailure -> SDoc #

Outputable TagInfo 
Instance details

Defined in GHC.Stg.InferTags.TagSig

Methods

ppr :: TagInfo -> SDoc #

Outputable TagSig 
Instance details

Defined in GHC.Stg.InferTags.TagSig

Methods

ppr :: TagSig -> SDoc #

Outputable BinderInfo 
Instance details

Defined in GHC.Stg.Lift.Analysis

Methods

ppr :: BinderInfo -> SDoc #

Outputable Skeleton 
Instance details

Defined in GHC.Stg.Lift.Analysis

Methods

ppr :: Skeleton -> SDoc #

Outputable AltType 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: AltType -> SDoc #

Outputable ConstructorNumber 
Instance details

Defined in GHC.Stg.Syntax

Outputable NoExtFieldSilent 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: NoExtFieldSilent -> SDoc #

Outputable StgArg 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: StgArg -> SDoc #

Outputable StgOp 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: StgOp -> SDoc #

Outputable UpdateFlag 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: UpdateFlag -> SDoc #

Outputable LambdaFormInfo 
Instance details

Defined in GHC.StgToCmm.Types

Methods

ppr :: LambdaFormInfo -> SDoc #

Outputable StandardFormInfo 
Instance details

Defined in GHC.StgToCmm.Types

Methods

ppr :: StandardFormInfo -> SDoc #

Outputable Deps 
Instance details

Defined in GHC.StgToJS.Object

Methods

ppr :: Deps -> SDoc #

Outputable DepsLocation 
Instance details

Defined in GHC.StgToJS.Object

Methods

ppr :: DepsLocation -> SDoc #

Outputable ExportedFun 
Instance details

Defined in GHC.StgToJS.Object

Methods

ppr :: ExportedFun -> SDoc #

Outputable StaticArg 
Instance details

Defined in GHC.StgToJS.Types

Methods

ppr :: StaticArg -> SDoc #

Outputable StaticLit 
Instance details

Defined in GHC.StgToJS.Types

Methods

ppr :: StaticLit -> SDoc #

Outputable TypedExpr 
Instance details

Defined in GHC.StgToJS.Types

Methods

ppr :: TypedExpr -> SDoc #

Outputable HoleFit 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Methods

ppr :: HoleFit -> SDoc #

Outputable HoleFitCandidate 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Methods

ppr :: HoleFitCandidate -> SDoc #

Outputable TypedHole 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

Methods

ppr :: TypedHole -> SDoc #

Outputable ErrorItem 
Instance details

Defined in GHC.Tc.Errors.Types

Methods

ppr :: ErrorItem -> SDoc #

Outputable Exported 
Instance details

Defined in GHC.Tc.Errors.Types

Methods

ppr :: Exported -> SDoc #

Outputable PromotionErr 
Instance details

Defined in GHC.Tc.Errors.Types

Methods

ppr :: PromotionErr -> SDoc #

Outputable TypeDataForbids 
Instance details

Defined in GHC.Tc.Errors.Types

Methods

ppr :: TypeDataForbids -> SDoc #

Outputable GeneralisationPlan 
Instance details

Defined in GHC.Tc.Gen.Bind

Methods

ppr :: GeneralisationPlan -> SDoc #

Outputable InferMode 
Instance details

Defined in GHC.Tc.Solver

Methods

ppr :: InferMode -> SDoc #

Outputable TouchabilityTestResult 
Instance details

Defined in GHC.Tc.Solver.Monad

Outputable DefaultingProposal 
Instance details

Defined in GHC.Tc.Types

Outputable IdBindingInfo 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: IdBindingInfo -> SDoc #

Outputable TcBinder 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcBinder -> SDoc #

Outputable TcIdSigInfo 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcIdSigInfo -> SDoc #

Outputable TcIdSigInst 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcIdSigInst -> SDoc #

Outputable TcPatSynInfo 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcPatSynInfo -> SDoc #

Outputable TcSigInfo 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcSigInfo -> SDoc #

Outputable TcTyThing 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: TcTyThing -> SDoc #

Outputable ThStage 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: ThStage -> SDoc #

Outputable WhereFrom 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: WhereFrom -> SDoc #

Outputable CanEqLHS 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: CanEqLHS -> SDoc #

Outputable CheckTyEqResult 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: CheckTyEqResult -> SDoc #

Outputable Ct 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: Ct -> SDoc #

Outputable CtEvidence 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: CtEvidence -> SDoc #

Outputable CtFlavour 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: CtFlavour -> SDoc #

Outputable CtIrredReason 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: CtIrredReason -> SDoc #

Outputable DelayedError 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: DelayedError -> SDoc #

Outputable HasGivenEqs 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: HasGivenEqs -> SDoc #

Outputable Hole 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: Hole -> SDoc #

Outputable HoleSort 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: HoleSort -> SDoc #

Outputable ImplicStatus 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: ImplicStatus -> SDoc #

Outputable Implication 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: Implication -> SDoc #

Outputable NotConcreteError 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: NotConcreteError -> SDoc #

Outputable QCInst 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: QCInst -> SDoc #

Outputable RewriterSet 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: RewriterSet -> SDoc #

Outputable SubGoalDepth 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: SubGoalDepth -> SDoc #

Outputable TcEvDest 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: TcEvDest -> SDoc #

Outputable WantedConstraints 
Instance details

Defined in GHC.Tc.Types.Constraint

Outputable EvBind 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBind -> SDoc #

Outputable EvBindMap 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBindMap -> SDoc #

Outputable EvBindsVar 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvBindsVar -> SDoc #

Outputable EvCallStack 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvCallStack -> SDoc #

Outputable EvTerm 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvTerm -> SDoc #

Outputable EvTypeable 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: EvTypeable -> SDoc #

Outputable HoleExprRef 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: HoleExprRef -> SDoc #

Outputable HsWrapper 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: HsWrapper -> SDoc #

Outputable TcEvBinds 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: TcEvBinds -> SDoc #

Outputable CtOrigin 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: CtOrigin -> SDoc #

Outputable FRRArrowContext 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: FRRArrowContext -> SDoc #

Outputable FixedRuntimeRepContext 
Instance details

Defined in GHC.Tc.Types.Origin

Outputable NakedScFlag 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: NakedScFlag -> SDoc #

Outputable RepPolyFun 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: RepPolyFun -> SDoc #

Outputable SkolemInfo 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: SkolemInfo -> SDoc #

Outputable SkolemInfoAnon 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: SkolemInfoAnon -> SDoc #

Outputable StmtOrigin 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: StmtOrigin -> SDoc #

Outputable TyVarBndrs 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: TyVarBndrs -> SDoc #

Outputable TypedThing 
Instance details

Defined in GHC.Tc.Types.Origin

Methods

ppr :: TypedThing -> SDoc #

Outputable Rank 
Instance details

Defined in GHC.Tc.Types.Rank

Methods

ppr :: Rank -> SDoc #

Outputable IsExtraConstraint 
Instance details

Defined in GHC.Tc.Utils.Monad

Outputable ExpType 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: ExpType -> SDoc #

Outputable InferResult 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: InferResult -> SDoc #

Outputable MetaDetails 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: MetaDetails -> SDoc #

Outputable MetaInfo 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: MetaInfo -> SDoc #

Outputable PatersonSize 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: PatersonSize -> SDoc #

Outputable TcLevel 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: TcLevel -> SDoc #

Outputable TcTyVarDetails 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: TcTyVarDetails -> SDoc #

Outputable ZonkEnv 
Instance details

Defined in GHC.Tc.Utils.Zonk

Methods

ppr :: ZonkEnv -> SDoc #

Outputable Annotation 
Instance details

Defined in GHC.Types.Annotations

Methods

ppr :: Annotation -> SDoc #

Outputable AvailInfo 
Instance details

Defined in GHC.Types.Avail

Methods

ppr :: AvailInfo -> SDoc #

Outputable GreName 
Instance details

Defined in GHC.Types.Avail

Methods

ppr :: GreName -> SDoc #

Outputable Activation 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Activation -> SDoc #

Outputable Alignment 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Alignment -> SDoc #

Outputable CbvMark 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: CbvMark -> SDoc #

Outputable CompilerPhase 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: CompilerPhase -> SDoc #

Outputable DefaultingStrategy 
Instance details

Defined in GHC.Types.Basic

Outputable FunctionOrData 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: FunctionOrData -> SDoc #

Outputable InlinePragma 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: InlinePragma -> SDoc #

Outputable InlineSpec 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: InlineSpec -> SDoc #

Outputable IntWithInf 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: IntWithInf -> SDoc #

Outputable LeftOrRight 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: LeftOrRight -> SDoc #

Outputable Levity 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Levity -> SDoc #

Outputable NonStandardDefaultingStrategy 
Instance details

Defined in GHC.Types.Basic

Outputable OccInfo 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OccInfo -> SDoc #

Outputable OneShotInfo 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OneShotInfo -> SDoc #

Outputable Origin 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Origin -> SDoc #

Outputable OverlapFlag 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OverlapFlag -> SDoc #

Outputable OverlapMode 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OverlapMode -> SDoc #

Outputable RecFlag 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: RecFlag -> SDoc #

Outputable RuleMatchInfo 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: RuleMatchInfo -> SDoc #

Outputable SuccessFlag 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: SuccessFlag -> SDoc #

Outputable SwapFlag 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: SwapFlag -> SDoc #

Outputable TailCallInfo 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: TailCallInfo -> SDoc #

Outputable TopLevelFlag 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: TopLevelFlag -> SDoc #

Outputable TupleSort 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: TupleSort -> SDoc #

Outputable TypeOrKind 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: TypeOrKind -> SDoc #

Outputable UnboxedTupleOrSum 
Instance details

Defined in GHC.Types.Basic

Outputable UnfoldingSource 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: UnfoldingSource -> SDoc #

Outputable CompleteMatch 
Instance details

Defined in GHC.Types.CompleteMatch

Methods

ppr :: CompleteMatch -> SDoc #

Outputable CostCentre 
Instance details

Defined in GHC.Types.CostCentre

Methods

ppr :: CostCentre -> SDoc #

Outputable CostCentreStack 
Instance details

Defined in GHC.Types.CostCentre

Methods

ppr :: CostCentreStack -> SDoc #

Outputable Cpr

BNF:

cpr ::= ''                               -- TopCpr
     |  n                                -- FlatConCpr n
     |  n '(' cpr1 ',' cpr2 ',' ... ')'  -- ConCpr n [cpr1,cpr2,...]
     |  'b'                              -- BotCpr

Examples: * `f x = f x` has result CPR b * `1(1,)` is a valid (nested) Cpr denotation for `(I# 42#, f 42)`.

Instance details

Defined in GHC.Types.Cpr

Methods

ppr :: Cpr -> SDoc #

Outputable CprSig

Only print the CPR result

Instance details

Defined in GHC.Types.Cpr

Methods

ppr :: CprSig -> SDoc #

Outputable CprType

BNF:

cpr_ty ::= cpr               -- short form if arty == 0
        |  '\' arty '.' cpr  -- if arty > 0

Examples: * `f x y z = f x y z` has denotation `3.b` * `g !x = (x+1, x+2)` has denotation `1.1(1,1)`.

Instance details

Defined in GHC.Types.Cpr

Methods

ppr :: CprType -> SDoc #

Outputable Card

See Note [Demand notation] Current syntax was discussed in #19016.

Instance details

Defined in GHC.Types.Demand

Methods

ppr :: Card -> SDoc #

Outputable Demand

See Note [Demand notation]

Instance details

Defined in GHC.Types.Demand

Methods

ppr :: Demand -> SDoc #

Outputable Divergence 
Instance details

Defined in GHC.Types.Demand

Methods

ppr :: Divergence -> SDoc #

Outputable DmdEnv 
Instance details

Defined in GHC.Types.Demand

Methods

ppr :: DmdEnv -> SDoc #

Outputable DmdSig 
Instance details

Defined in GHC.Types.Demand

Methods

ppr :: DmdSig -> SDoc #

Outputable DmdType 
Instance details

Defined in GHC.Types.Demand

Methods

ppr :: DmdType -> SDoc #

Outputable SubDemand

See Note [Demand notation]

Instance details

Defined in GHC.Types.Demand

Methods

ppr :: SubDemand -> SDoc #

Outputable TypeShape 
Instance details

Defined in GHC.Types.Demand

Methods

ppr :: TypeShape -> SDoc #

Outputable DiagnosticCode 
Instance details

Defined in GHC.Types.Error

Methods

ppr :: DiagnosticCode -> SDoc #

Outputable DiagnosticHint 
Instance details

Defined in GHC.Types.Error

Methods

ppr :: DiagnosticHint -> SDoc #

Outputable DiagnosticReason 
Instance details

Defined in GHC.Types.Error

Methods

ppr :: DiagnosticReason -> SDoc #

Outputable Severity 
Instance details

Defined in GHC.Types.Error

Methods

ppr :: Severity -> SDoc #

Outputable DuplicateRecordFields 
Instance details

Defined in GHC.Types.FieldLabel

Outputable FieldLabel 
Instance details

Defined in GHC.Types.FieldLabel

Methods

ppr :: FieldLabel -> SDoc #

Outputable FieldSelectors 
Instance details

Defined in GHC.Types.FieldLabel

Methods

ppr :: FieldSelectors -> SDoc #

Outputable Fixity 
Instance details

Defined in GHC.Types.Fixity

Methods

ppr :: Fixity -> SDoc #

Outputable FixityDirection 
Instance details

Defined in GHC.Types.Fixity

Methods

ppr :: FixityDirection -> SDoc #

Outputable LexicalFixity 
Instance details

Defined in GHC.Types.Fixity

Methods

ppr :: LexicalFixity -> SDoc #

Outputable FixItem 
Instance details

Defined in GHC.Types.Fixity.Env

Methods

ppr :: FixItem -> SDoc #

Outputable CCallConv 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: CCallConv -> SDoc #

Outputable CCallSpec 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: CCallSpec -> SDoc #

Outputable CExportSpec 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: CExportSpec -> SDoc #

Outputable CType 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: CType -> SDoc #

Outputable ForeignCall 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: ForeignCall -> SDoc #

Outputable Header 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: Header -> SDoc #

Outputable Safety 
Instance details

Defined in GHC.Types.ForeignCall

Methods

ppr :: Safety -> SDoc #

Outputable CafInfo 
Instance details

Defined in GHC.Types.Id.Info

Methods

ppr :: CafInfo -> SDoc #

Outputable IdDetails 
Instance details

Defined in GHC.Types.Id.Info

Methods

ppr :: IdDetails -> SDoc #

Outputable RecSelParent 
Instance details

Defined in GHC.Types.Id.Info

Methods

ppr :: RecSelParent -> SDoc #

Outputable TickBoxOp 
Instance details

Defined in GHC.Types.Id.Info

Methods

ppr :: TickBoxOp -> SDoc #

Outputable Literal 
Instance details

Defined in GHC.Types.Literal

Methods

ppr :: Literal -> SDoc #

Outputable Name 
Instance details

Defined in GHC.Types.Name

Methods

ppr :: Name -> SDoc #

Outputable NameSort 
Instance details

Defined in GHC.Types.Name

Methods

ppr :: NameSort -> SDoc #

Outputable OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccName -> SDoc #

Outputable GlobalRdrElt 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: GlobalRdrElt -> SDoc #

Outputable ImportSpec 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: ImportSpec -> SDoc #

Outputable LocalRdrEnv 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: LocalRdrEnv -> SDoc #

Outputable Parent 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: Parent -> SDoc #

Outputable RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: RdrName -> SDoc #

Outputable PkgQual 
Instance details

Defined in GHC.Types.PkgQual

Methods

ppr :: PkgQual -> SDoc #

Outputable RawPkgQual 
Instance details

Defined in GHC.Types.PkgQual

Methods

ppr :: RawPkgQual -> SDoc #

Outputable IfaceTrustInfo 
Instance details

Defined in GHC.Types.SafeHaskell

Methods

ppr :: IfaceTrustInfo -> SDoc #

Outputable SafeHaskellMode 
Instance details

Defined in GHC.Types.SafeHaskell

Methods

ppr :: SafeHaskellMode -> SDoc #

Outputable FractionalLit 
Instance details

Defined in GHC.Types.SourceText

Methods

ppr :: FractionalLit -> SDoc #

Outputable IntegralLit 
Instance details

Defined in GHC.Types.SourceText

Methods

ppr :: IntegralLit -> SDoc #

Outputable SourceText 
Instance details

Defined in GHC.Types.SourceText

Methods

ppr :: SourceText -> SDoc #

Outputable StringLiteral 
Instance details

Defined in GHC.Types.SourceText

Methods

ppr :: StringLiteral -> SDoc #

Outputable RealSrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcLoc -> SDoc #

Outputable RealSrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: RealSrcSpan -> SDoc #

Outputable SrcLoc 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcLoc -> SDoc #

Outputable SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcSpan -> SDoc #

Outputable UnhelpfulSpanReason 
Instance details

Defined in GHC.Types.SrcLoc

Outputable Target 
Instance details

Defined in GHC.Types.Target

Methods

ppr :: Target -> SDoc #

Outputable TargetId 
Instance details

Defined in GHC.Types.Target

Methods

ppr :: TargetId -> SDoc #

Outputable TickishPlacement 
Instance details

Defined in GHC.Types.Tickish

Methods

ppr :: TickishPlacement -> SDoc #

Outputable TyThing 
Instance details

Defined in GHC.Types.TyThing

Methods

ppr :: TyThing -> SDoc #

Outputable Unique 
Instance details

Defined in GHC.Types.Unique

Methods

ppr :: Unique -> SDoc #

Outputable ForAllTyFlag 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: ForAllTyFlag -> SDoc #

Outputable FunTyFlag 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: FunTyFlag -> SDoc #

Outputable PiTyBinder 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: PiTyBinder -> SDoc #

Outputable Var 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: Var -> SDoc #

Outputable InScopeSet 
Instance details

Defined in GHC.Types.Var.Env

Methods

ppr :: InScopeSet -> SDoc #

Outputable HomeUnitEnv 
Instance details

Defined in GHC.Unit.Env

Methods

ppr :: HomeUnitEnv -> SDoc #

Outputable HomeModLinkable 
Instance details

Defined in GHC.Unit.Home.ModInfo

Methods

ppr :: HomeModLinkable -> SDoc #

Outputable PackageId 
Instance details

Defined in GHC.Unit.Info

Methods

ppr :: PackageId -> SDoc #

Outputable PackageName 
Instance details

Defined in GHC.Unit.Info

Methods

ppr :: PackageName -> SDoc #

Outputable NDModule 
Instance details

Defined in GHC.Unit.Module.Env

Methods

ppr :: NDModule -> SDoc #

Outputable ModNodeKeyWithUid 
Instance details

Defined in GHC.Unit.Module.Graph

Outputable ModuleGraphNode 
Instance details

Defined in GHC.Unit.Module.Graph

Methods

ppr :: ModuleGraphNode -> SDoc #

Outputable NodeKey 
Instance details

Defined in GHC.Unit.Module.Graph

Methods

ppr :: NodeKey -> SDoc #

Outputable ModLocation 
Instance details

Defined in GHC.Unit.Module.Location

Methods

ppr :: ModLocation -> SDoc #

Outputable ModSummary 
Instance details

Defined in GHC.Unit.Module.ModSummary

Methods

ppr :: ModSummary -> SDoc #

Outputable HscBackendAction 
Instance details

Defined in GHC.Unit.Module.Status

Methods

ppr :: HscBackendAction -> SDoc #

Outputable ModuleOrigin 
Instance details

Defined in GHC.Unit.State

Methods

ppr :: ModuleOrigin -> SDoc #

Outputable UnitErr 
Instance details

Defined in GHC.Unit.State

Methods

ppr :: UnitErr -> SDoc #

Outputable UnitVisibility 
Instance details

Defined in GHC.Unit.State

Methods

ppr :: UnitVisibility -> SDoc #

Outputable UnusableUnitReason 
Instance details

Defined in GHC.Unit.State

Outputable InstalledModule 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: InstalledModule -> SDoc #

Outputable InstantiatedModule 
Instance details

Defined in GHC.Unit.Types

Outputable InstantiatedUnit 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: InstantiatedUnit -> SDoc #

Outputable Module 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Module -> SDoc #

Outputable Unit 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Unit -> SDoc #

Outputable UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: UnitId -> SDoc #

Outputable PprStyle 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: PprStyle -> SDoc #

Outputable QualifyName 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: QualifyName -> SDoc #

Outputable SDoc 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: SDoc -> SDoc #

Outputable ModuleName 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: ModuleName -> SDoc #

Outputable Serialized 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Serialized -> SDoc #

Outputable Extension 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Extension -> SDoc #

Outputable Ordering 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Ordering -> SDoc #

Outputable HashableType Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

ppr :: HashableType -> SDoc #

Outputable OccurrenceMap Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Play

Methods

ppr :: OccurrenceMap -> SDoc #

Outputable TyConOccurrence Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Play

Methods

ppr :: TyConOccurrence -> SDoc #

Outputable UTCTime 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: UTCTime -> SDoc #

Outputable Integer 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Integer -> SDoc #

Outputable () 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: () -> SDoc #

Outputable Bool 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Bool -> SDoc #

Outputable Double 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Double -> SDoc #

Outputable Float 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Float -> SDoc #

Outputable Int 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Int -> SDoc #

Outputable Word 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Word -> SDoc #

Outputable a => Outputable (NonEmpty a) 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: NonEmpty a -> SDoc #

Outputable a => Outputable (SCC a) 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: SCC a -> SDoc #

Outputable elt => Outputable (IntMap elt) 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: IntMap elt -> SDoc #

Outputable a => Outputable (Set a) 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Set a -> SDoc #

Outputable a => Outputable (LabelMap a) 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

ppr :: LabelMap a -> SDoc #

Outputable b => Outputable (TaggedBndr b) 
Instance details

Defined in GHC.Core

Methods

ppr :: TaggedBndr b -> SDoc #

Outputable ev => Outputable (NormaliseStepResult ev) 
Instance details

Defined in GHC.Core.Coercion

Methods

ppr :: NormaliseStepResult ev -> SDoc #

Outputable (CoAxiom br) 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: CoAxiom br -> SDoc #

Outputable a => Outputable (CoreMap a) 
Instance details

Defined in GHC.Core.Map.Expr

Methods

ppr :: CoreMap a -> SDoc #

Outputable a => Outputable (TypeMapG a) 
Instance details

Defined in GHC.Core.Map.Type

Methods

ppr :: TypeMapG a -> SDoc #

Outputable a => Outputable (RoughMap a) 
Instance details

Defined in GHC.Core.RoughMap

Methods

ppr :: RoughMap a -> SDoc #

Outputable a => Outputable (Scaled a) 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Scaled a -> SDoc #

Outputable a => Outputable (UnifyResultM a) 
Instance details

Defined in GHC.Core.Unify

Methods

ppr :: UnifyResultM a -> SDoc #

Outputable a => Outputable (Bag a) 
Instance details

Defined in GHC.Data.Bag

Methods

ppr :: Bag a -> SDoc #

Outputable a => Outputable (OrdList a) 
Instance details

Defined in GHC.Data.OrdList

Methods

ppr :: OrdList a -> SDoc #

Outputable a => Outputable (Pair a) 
Instance details

Defined in GHC.Data.Pair

Methods

ppr :: Pair a -> SDoc #

Outputable (KnotVars a) 
Instance details

Defined in GHC.Driver.Env.KnotVars

Methods

ppr :: KnotVars a -> SDoc #

Outputable a => Outputable (OnOff a) 
Instance details

Defined in GHC.Driver.Session

Methods

ppr :: OnOff a -> SDoc #

Outputable a => Outputable (EpAnn a) 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: EpAnn a -> SDoc #

Outputable a => Outputable (SrcSpanAnn' a) 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: SrcSpanAnn' a -> SDoc #

Outputable (PatBuilder GhcPs) 
Instance details

Defined in GHC.Parser.Types

Methods

ppr :: PatBuilder GhcPs -> SDoc #

Outputable a => Outputable (StmtTree a) 
Instance details

Defined in GHC.Rename.Expr

Methods

ppr :: StmtTree a -> SDoc #

Outputable (TagEnv p) 
Instance details

Defined in GHC.Stg.InferTags.Types

Methods

ppr :: TagEnv p -> SDoc #

OutputablePass pass => Outputable (GenStgBinding pass) 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: GenStgBinding pass -> SDoc #

OutputablePass pass => Outputable (GenStgExpr pass) 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: GenStgExpr pass -> SDoc #

OutputablePass pass => Outputable (GenStgRhs pass) 
Instance details

Defined in GHC.Stg.Syntax

Methods

ppr :: GenStgRhs pass -> SDoc #

OutputableBndrId a => Outputable (InstInfo (GhcPass a)) 
Instance details

Defined in GHC.Tc.Utils.Env

Methods

ppr :: InstInfo (GhcPass a) -> SDoc #

Outputable name => Outputable (AnnTarget name) 
Instance details

Defined in GHC.Types.Annotations

Methods

ppr :: AnnTarget name -> SDoc #

Outputable (DefMethSpec ty) 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: DefMethSpec ty -> SDoc #

Diagnostic e => Outputable (Messages e) 
Instance details

Defined in GHC.Types.Error

Methods

ppr :: Messages e -> SDoc #

Outputable a => Outputable (OccEnv a) 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccEnv a -> SDoc #

Outputable e => Outputable (Located e) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: Located e -> SDoc #

Outputable a => Outputable (UniqDSet a) 
Instance details

Defined in GHC.Types.Unique.DSet

Methods

ppr :: UniqDSet a -> SDoc #

Outputable a => Outputable (UniqSet a) 
Instance details

Defined in GHC.Types.Unique.Set

Methods

ppr :: UniqSet a -> SDoc #

Outputable (UnitEnvGraph HomeUnitEnv) 
Instance details

Defined in GHC.Unit.Env

Outputable elt => Outputable (InstalledModuleEnv elt) 
Instance details

Defined in GHC.Unit.Module.Env

Methods

ppr :: InstalledModuleEnv elt -> SDoc #

Outputable a => Outputable (ModuleEnv a) 
Instance details

Defined in GHC.Unit.Module.Env

Methods

ppr :: ModuleEnv a -> SDoc #

Outputable (WarningTxt pass) 
Instance details

Defined in GHC.Unit.Module.Warnings

Methods

ppr :: WarningTxt pass -> SDoc #

Outputable u => Outputable (UnitDatabase u) 
Instance details

Defined in GHC.Unit.State

Methods

ppr :: UnitDatabase u -> SDoc #

Outputable unit => Outputable (Definite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Definite unit -> SDoc #

Outputable a => Outputable (GenWithIsBoot a) 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: GenWithIsBoot a -> SDoc #

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

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

ppr :: HashSet a -> SDoc #

Outputable a => Outputable (Maybe a) 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Maybe a -> SDoc #

Outputable a => Outputable [a] 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: [a] -> SDoc #

(Outputable a, Outputable b) => Outputable (Either a b) 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Either a b -> SDoc #

(Outputable key, Outputable elt) => Outputable (Map key elt) 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Map key elt -> SDoc #

(Outputable a, Outputable (m a)) => Outputable (GenMap m a) 
Instance details

Defined in GHC.Data.TrieMap

Methods

ppr :: GenMap m a -> SDoc #

(TrieMap m, Outputable a) => Outputable (ListMap m a) 
Instance details

Defined in GHC.Data.TrieMap

Methods

ppr :: ListMap m a -> SDoc #

Outputable a => Outputable (WithHsDocIdentifiers a pass)

For compatibility with the existing @-ddump-parsed' output, we only show the docstring.

Use pprHsDoc to show HsDoc's internals.

Instance details

Defined in GHC.Hs.Doc

Methods

ppr :: WithHsDocIdentifiers a pass -> SDoc #

(Outputable a, Outputable b) => Outputable (HsExpansion a b)

Just print the original expression (the a).

Instance details

Defined in GHC.Hs.Expr

Methods

ppr :: HsExpansion a b -> SDoc #

(Outputable a, Outputable b) => Outputable (HsPatExpansion a b) 
Instance details

Defined in GHC.Hs.Pat

Methods

ppr :: HsPatExpansion a b -> SDoc #

(Outputable r, Outputable b) => Outputable (IfaceBindingX r b) 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceBindingX r b -> SDoc #

Outputable (GenLocated Anchor EpaComment) 
Instance details

Defined in GHC.Parser.Annotation

(Outputable a, Outputable e) => Outputable (GenLocated (SrcSpanAnn' a) e) 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: GenLocated (SrcSpanAnn' a) e -> SDoc #

Outputable a => Outputable (GenLocated TokenLocation a) 
Instance details

Defined in GHC.Parser.Annotation

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

Defined in GHC.Types.SrcLoc

Outputable a => Outputable (UniqDFM key a) 
Instance details

Defined in GHC.Types.Unique.DFM

Methods

ppr :: UniqDFM key a -> SDoc #

Outputable a => Outputable (UniqFM key a) 
Instance details

Defined in GHC.Types.Unique.FM

Methods

ppr :: UniqFM key a -> SDoc #

(Outputable k, Outputable a) => Outputable (UniqMap k a) 
Instance details

Defined in GHC.Types.Unique.Map

Methods

ppr :: UniqMap k a -> SDoc #

OutputableBndr tv => Outputable (VarBndr tv TyConBndrVis) 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: VarBndr tv TyConBndrVis -> SDoc #

Outputable tv => Outputable (VarBndr tv ForAllTyFlag) 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: VarBndr tv ForAllTyFlag -> SDoc #

Outputable tv => Outputable (VarBndr tv Specificity) 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: VarBndr tv Specificity -> SDoc #

(Outputable a, Outputable b) => Outputable (a, b) 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: (a, b) -> SDoc #

(Outputable a, Outputable b, Outputable c) => Outputable (a, b, c) 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: (a, b, c) -> SDoc #

(Outputable a, Outputable b, Outputable c, Outputable d) => Outputable (a, b, c, d) 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: (a, b, c, d) -> SDoc #

(Outputable a, Outputable b, Outputable c, Outputable d, Outputable e) => Outputable (a, b, c, d, e) 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: (a, b, c, d, e) -> SDoc #

(Outputable a, Outputable b, Outputable c, Outputable d, Outputable e, Outputable f) => Outputable (a, b, c, d, e, f) 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: (a, b, c, d, e, f) -> SDoc #

(Outputable a, Outputable b, Outputable c, Outputable d, Outputable e, Outputable f, Outputable g) => Outputable (a, b, c, d, e, f, g) 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: (a, b, c, d, e, f, g) -> SDoc #

data GhcException #

GHC's own exception type error messages all take the form:

     <location>: <error>
 

If the location is on the command line, or in GHC itself, then <location>="ghc". All of the error types below correspond to a <location> of "ghc", except for ProgramError (where the string is assumed to contain a location already, so we don't print one).

Constructors

CmdLineError String

A problem with the command line arguments, but don't print usage.

ProgramError String

An error in the user's code, probably.

data SDoc #

Represents a pretty-printable document.

To display an SDoc, use printSDoc, printSDocLn, bufLeftRenderSDoc, or renderWithContext. Avoid calling runSDoc directly as it breaks the abstraction layer.

Instances

Instances details
IsString SDoc 
Instance details

Defined in GHC.Utils.Outputable

Methods

fromString :: String -> SDoc #

IsDoc SDoc 
Instance details

Defined in GHC.Utils.Outputable

Associated Types

type Line SDoc = (r :: Type) #

Methods

line :: Line SDoc -> SDoc #

($$) :: SDoc -> SDoc -> SDoc #

lines_ :: [Line SDoc] -> SDoc #

vcat :: [SDoc] -> SDoc #

dualDoc :: SDoc -> HDoc -> SDoc #

IsLine SDoc 
Instance details

Defined in GHC.Utils.Outputable

Methods

char :: Char -> SDoc #

text :: String -> SDoc #

ftext :: FastString -> SDoc #

ztext :: FastZString -> SDoc #

(<>) :: SDoc -> SDoc -> SDoc #

(<+>) :: SDoc -> SDoc -> SDoc #

sep :: [SDoc] -> SDoc #

fsep :: [SDoc] -> SDoc #

hcat :: [SDoc] -> SDoc #

hsep :: [SDoc] -> SDoc #

dualLine :: SDoc -> HLine -> SDoc #

IsOutput SDoc 
Instance details

Defined in GHC.Utils.Outputable

Outputable SDoc 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: SDoc -> SDoc #

OutputableP env SDoc 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> SDoc -> SDoc #

type Line SDoc 
Instance details

Defined in GHC.Utils.Outputable

type Line SDoc = SDoc

data Annotation #

Represents an annotation after it has been sufficiently desugared from it's initial form of AnnDecl

Constructors

Annotation 

Fields

Instances

Instances details
Outputable Annotation 
Instance details

Defined in GHC.Types.Annotations

Methods

ppr :: Annotation -> SDoc #

data HsExpr p #

A Haskell expression.

Constructors

HsVar (XVar p) (LIdP p)

Variable See Note [Located RdrNames]

HsOverLit (XOverLitE p) (HsOverLit p)

Overloaded literals

ExprWithTySig (XExprWithTySig p) (LHsExpr p) (LHsSigWcType (NoGhcTc p))

Expression with an explicit type signature. e :: type

Instances

Instances details
DisambECP (HsExpr GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

Associated Types

type Body (HsExpr GhcPs) :: Type -> Type #

type InfixOp (HsExpr GhcPs) #

type FunArg (HsExpr GhcPs) #

Methods

ecpFromCmd' :: LHsCmd GhcPs -> PV (LocatedA (HsExpr GhcPs)) #

ecpFromExp' :: LHsExpr GhcPs -> PV (LocatedA (HsExpr GhcPs)) #

mkHsProjUpdatePV :: SrcSpan -> Located [LocatedAn NoEpAnns (DotFieldOcc GhcPs)] -> LocatedA (HsExpr GhcPs) -> Bool -> [AddEpAnn] -> PV (LHsRecProj GhcPs (LocatedA (HsExpr GhcPs))) #

mkHsLamPV :: SrcSpan -> (EpAnnComments -> MatchGroup GhcPs (LocatedA (HsExpr GhcPs))) -> PV (LocatedA (HsExpr GhcPs)) #

mkHsLetPV :: SrcSpan -> LHsToken "let" GhcPs -> HsLocalBinds GhcPs -> LHsToken "in" GhcPs -> LocatedA (HsExpr GhcPs) -> PV (LocatedA (HsExpr GhcPs)) #

superInfixOp :: (DisambInfixOp (InfixOp (HsExpr GhcPs)) => PV (LocatedA (HsExpr GhcPs))) -> PV (LocatedA (HsExpr GhcPs)) #

mkHsOpAppPV :: SrcSpan -> LocatedA (HsExpr GhcPs) -> LocatedN (InfixOp (HsExpr GhcPs)) -> LocatedA (HsExpr GhcPs) -> PV (LocatedA (HsExpr GhcPs)) #

mkHsCasePV :: SrcSpan -> LHsExpr GhcPs -> LocatedL [LMatch GhcPs (LocatedA (HsExpr GhcPs))] -> EpAnnHsCase -> PV (LocatedA (HsExpr GhcPs)) #

mkHsLamCasePV :: SrcSpan -> LamCaseVariant -> LocatedL [LMatch GhcPs (LocatedA (HsExpr GhcPs))] -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

superFunArg :: (DisambECP (FunArg (HsExpr GhcPs)) => PV (LocatedA (HsExpr GhcPs))) -> PV (LocatedA (HsExpr GhcPs)) #

mkHsAppPV :: SrcSpanAnnA -> LocatedA (HsExpr GhcPs) -> LocatedA (FunArg (HsExpr GhcPs)) -> PV (LocatedA (HsExpr GhcPs)) #

mkHsAppTypePV :: SrcSpanAnnA -> LocatedA (HsExpr GhcPs) -> LHsToken "@" GhcPs -> LHsType GhcPs -> PV (LocatedA (HsExpr GhcPs)) #

mkHsIfPV :: SrcSpan -> LHsExpr GhcPs -> Bool -> LocatedA (HsExpr GhcPs) -> Bool -> LocatedA (HsExpr GhcPs) -> AnnsIf -> PV (LocatedA (HsExpr GhcPs)) #

mkHsDoPV :: SrcSpan -> Maybe ModuleName -> LocatedL [LStmt GhcPs (LocatedA (HsExpr GhcPs))] -> AnnList -> PV (LocatedA (HsExpr GhcPs)) #

mkHsParPV :: SrcSpan -> LHsToken "(" GhcPs -> LocatedA (HsExpr GhcPs) -> LHsToken ")" GhcPs -> PV (LocatedA (HsExpr GhcPs)) #

mkHsVarPV :: LocatedN RdrName -> PV (LocatedA (HsExpr GhcPs)) #

mkHsLitPV :: Located (HsLit GhcPs) -> PV (Located (HsExpr GhcPs)) #

mkHsOverLitPV :: LocatedAn a (HsOverLit GhcPs) -> PV (LocatedAn a (HsExpr GhcPs)) #

mkHsWildCardPV :: SrcSpan -> PV (Located (HsExpr GhcPs)) #

mkHsTySigPV :: SrcSpanAnnA -> LocatedA (HsExpr GhcPs) -> LHsType GhcPs -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

mkHsExplicitListPV :: SrcSpan -> [LocatedA (HsExpr GhcPs)] -> AnnList -> PV (LocatedA (HsExpr GhcPs)) #

mkHsSplicePV :: Located (HsUntypedSplice GhcPs) -> PV (Located (HsExpr GhcPs)) #

mkHsRecordPV :: Bool -> SrcSpan -> SrcSpan -> LocatedA (HsExpr GhcPs) -> ([Fbind (HsExpr GhcPs)], Maybe SrcSpan) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

mkHsNegAppPV :: SrcSpan -> LocatedA (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

mkHsSectionR_PV :: SrcSpan -> LocatedA (InfixOp (HsExpr GhcPs)) -> LocatedA (HsExpr GhcPs) -> PV (Located (HsExpr GhcPs)) #

mkHsViewPatPV :: SrcSpan -> LHsExpr GhcPs -> LocatedA (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

mkHsAsPatPV :: SrcSpan -> LocatedN RdrName -> LHsToken "@" GhcPs -> LocatedA (HsExpr GhcPs) -> PV (LocatedA (HsExpr GhcPs)) #

mkHsLazyPatPV :: SrcSpan -> LocatedA (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

mkHsBangPatPV :: SrcSpan -> LocatedA (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

mkSumOrTuplePV :: SrcSpanAnnA -> Boxity -> SumOrTuple (HsExpr GhcPs) -> [AddEpAnn] -> PV (LocatedA (HsExpr GhcPs)) #

rejectPragmaPV :: LocatedA (HsExpr GhcPs) -> PV () #

DisambInfixOp (HsExpr GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type Body (HsExpr GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type FunArg (HsExpr GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type InfixOp (HsExpr GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (HsExpr (GhcPass p)) 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

data RdrName #

Reader Name

Do not use the data constructors of RdrName directly: prefer the family of functions that creates them, such as mkRdrUnqual

  • Note: A Located RdrName will only have API Annotations if it is a compound one, e.g.
`bar`
( ~ )

Instances

Instances details
Data RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

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

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

toConstr :: RdrName -> Constr #

dataTypeOf :: RdrName -> DataType #

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

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

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

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

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

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

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

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

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

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

DisambInfixOp RdrName 
Instance details

Defined in GHC.Parser.PostProcess

HasOccName RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

occName :: RdrName -> OccName #

Outputable RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: RdrName -> SDoc #

OutputableBndr RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Eq RdrName 
Instance details

Defined in GHC.Types.Name.Reader

Methods

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

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

Ord RdrName 
Instance details

Defined in GHC.Types.Name.Reader

type Anno RdrName 
Instance details

Defined in GHC.Hs.Extension

type Anno (LocatedN RdrName) 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] 
Instance details

Defined in GHC.Hs.Binds

type Id = Var #

Identifier

data TcGblEnv #

TcGblEnv describes the top-level of the module at the point at which the typechecker is finished work. It is this structure that is handed on to the desugarer For state that needs to be updated during the typechecking phase and returned at end, use a TcRef (= IORef).

Instances

Instances details
ContainsModule TcGblEnv 
Instance details

Defined in GHC.Tc.Types

data DynFlags #

Contains not only a collection of GeneralFlags but also a plethora of information relating to the compilation of a single file or GHC session

data SourceError #

A source error is an error that is caused by one or more errors in the source code. A SourceError is thrown by many functions in the compilation pipeline. Inside GHC these errors are merely printed via log_action, but API clients may treat them differently, for example, insert them into a list box. If you want the default behaviour, use the idiom:

handleSourceError printExceptionAndWarnings $ do
  ... api calls that may fail ...

The SourceErrors error messages can be accessed via srcErrorMessages. This list may be empty if the compiler failed due to -Werror (Opt_WarnIsError).

See printExceptionAndWarnings for more information on what to take care of when writing a custom error handler.

Instances

Instances details
Exception SourceError 
Instance details

Defined in GHC.Types.SourceError

Show SourceError 
Instance details

Defined in GHC.Types.SourceError

PPrint SourceError Source #

A whole bunch of PPrint instances follow ----------------------------------

Instance details

Defined in Language.Haskell.Liquid.Types.PrettyPrint

Result SourceError Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Interface

data Plugin #

Plugin is the compiler plugin data type. Try to avoid constructing one of these directly, and just modify some fields of defaultPlugin instead: this is to try and preserve source-code compatibility when we add fields to this.

Nonetheless, this API is preliminary and highly likely to change in the future.

Constructors

Plugin 

Fields

data FastString #

A FastString is a UTF-8 encoded string together with a unique ID. All FastStrings are stored in a global hashtable to support fast O(1) comparison.

It is also associated with a lazy reference to the Z-encoding of this string which is used by the compiler internally.

Instances

Instances details
Data FastString 
Instance details

Defined in GHC.Data.FastString

Methods

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

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

toConstr :: FastString -> Constr #

dataTypeOf :: FastString -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString FastString 
Instance details

Defined in GHC.Data.FastString

Monoid FastString 
Instance details

Defined in GHC.Data.FastString

Semigroup FastString 
Instance details

Defined in GHC.Data.FastString

Show FastString 
Instance details

Defined in GHC.Data.FastString

NFData FastString 
Instance details

Defined in GHC.Data.FastString

Methods

rnf :: FastString -> () #

ToJExpr FastString 
Instance details

Defined in GHC.JS.Make

Uniquable FastString 
Instance details

Defined in GHC.Types.Unique

Outputable FastString 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: FastString -> SDoc #

Eq FastString 
Instance details

Defined in GHC.Data.FastString

Symbolic FastString Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

symbol :: FastString -> Symbol #

ToJExpr a => ToJExpr (UniqMap FastString a) 
Instance details

Defined in GHC.JS.Make

type Anno FastString 
Instance details

Defined in GHC.Hs.Expr

type Anno (SourceText, RuleName) 
Instance details

Defined in GHC.Hs.Decls

data Role #

See Note [Roles] in GHC.Core.Coercion

Order of constructors matters: the Ord instance coincides with the *super*typing relation on roles.

Instances

Instances details
Data Role 
Instance details

Defined in Language.Haskell.Syntax.Basic

Methods

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

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

toConstr :: Role -> Constr #

dataTypeOf :: Role -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq Role 
Instance details

Defined in Language.Haskell.Syntax.Basic

Methods

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

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

Ord Role 
Instance details

Defined in Language.Haskell.Syntax.Basic

Methods

compare :: Role -> Role -> Ordering #

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

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

(>) :: Role -> Role -> Bool #

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

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

type Anno (Maybe Role) 
Instance details

Defined in GHC.Hs.Decls

type Anno (Maybe Role) 
Instance details

Defined in GHC.Hs.Decls

data Boxity #

Constructors

Boxed 

Instances

Instances details
Data Boxity 
Instance details

Defined in Language.Haskell.Syntax.Basic

Methods

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

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

toConstr :: Boxity -> Constr #

dataTypeOf :: Boxity -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq Boxity 
Instance details

Defined in Language.Haskell.Syntax.Basic

Methods

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

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

type family IdP p #

Maps the "normal" id type for a given pass

Instances

Instances details
type IdP (GhcPass p) 
Instance details

Defined in GHC.Hs.Extension

type IdP (GhcPass p) = IdGhcP p

data OccName #

Occurrence Name

In this context that means: "classified (i.e. as a type name, value name, etc) but not qualified and not yet resolved"

Instances

Instances details
Data OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

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

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

toConstr :: OccName -> Constr #

dataTypeOf :: OccName -> DataType #

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

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

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

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

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

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

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

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

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

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

NFData OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

rnf :: OccName -> () #

HasOccName OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

occName :: OccName -> OccName #

Uniquable OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

getUnique :: OccName -> Unique #

Binary OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Outputable OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

ppr :: OccName -> SDoc #

OutputableBndr OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Eq OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

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

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

Ord OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

data IsBootInterface #

Indicates whether a module name is referring to a boot interface (hs-boot file) or regular module (hs file). We need to treat boot modules specially when building compilation graphs, since they break cycles. Regular source files and signature files are treated equivalently.

Constructors

NotBoot 
IsBoot 

Instances

Instances details
Data IsBootInterface 
Instance details

Defined in Language.Haskell.Syntax.ImpExp

Methods

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

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

toConstr :: IsBootInterface -> Constr #

dataTypeOf :: IsBootInterface -> DataType #

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

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

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

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

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

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

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

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

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

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

Show IsBootInterface 
Instance details

Defined in Language.Haskell.Syntax.ImpExp

Eq IsBootInterface 
Instance details

Defined in Language.Haskell.Syntax.ImpExp

Ord IsBootInterface 
Instance details

Defined in Language.Haskell.Syntax.ImpExp

class IsOutput doc => IsLine doc where #

A class of types that represent a single logical line of text, with support for horizontal composition.

See Note [HLine versus HDoc] and Note [The outputable class hierarchy] for more details.

Minimal complete definition

char, text, ftext, ztext, (<>), (<+>), sep, fsep, dualLine

Methods

char :: Char -> doc #

text :: String -> doc #

ftext :: FastString -> doc #

ztext :: FastZString -> doc #

(<+>) :: doc -> doc -> doc #

Join two docs together horizontally with a gap between them.

sep :: [doc] -> doc #

Separate: is either like hsep or like vcat, depending on what fits.

fsep :: [doc] -> doc #

A paragraph-fill combinator. It's much like sep, only it keeps fitting things on one line until it can't fit any more.

hcat :: [doc] -> doc #

Concatenate docs horizontally without gaps.

hsep :: [doc] -> doc #

Concatenate docs horizontally with a space between each one.

dualLine :: SDoc -> HLine -> doc #

Prints as either the given SDoc or the given HLine, depending on which type the result is instantiated to. This should generally be avoided; see Note [dualLine and dualDoc] for details.

Instances

Instances details
IsLine HLine 
Instance details

Defined in GHC.Utils.Outputable

IsLine SDoc 
Instance details

Defined in GHC.Utils.Outputable

Methods

char :: Char -> SDoc #

text :: String -> SDoc #

ftext :: FastString -> SDoc #

ztext :: FastZString -> SDoc #

(<>) :: SDoc -> SDoc -> SDoc #

(<+>) :: SDoc -> SDoc -> SDoc #

sep :: [SDoc] -> SDoc #

fsep :: [SDoc] -> SDoc #

hcat :: [SDoc] -> SDoc #

hsep :: [SDoc] -> SDoc #

dualLine :: SDoc -> HLine -> SDoc #

class IsOutput doc where #

A superclass for IsLine and IsDoc that provides an identity, empty, as well as access to the shared SDocContext.

See Note [The outputable class hierarchy] for more details.

Methods

empty :: doc #

docWithContext :: (SDocContext -> doc) -> doc #

Instances

Instances details
IsOutput HDoc 
Instance details

Defined in GHC.Utils.Outputable

IsOutput HLine 
Instance details

Defined in GHC.Utils.Outputable

IsOutput SDoc 
Instance details

Defined in GHC.Utils.Outputable

data HDoc #

Represents a (possibly empty) sequence of lines that can be efficiently printed directly to a Handle (actually a BufHandle). See Note [SDoc versus HDoc] and Note [HLine versus HDoc] for more details.

Instances

Instances details
IsDoc HDoc 
Instance details

Defined in GHC.Utils.Outputable

Associated Types

type Line HDoc = (r :: Type) #

Methods

line :: Line HDoc -> HDoc #

($$) :: HDoc -> HDoc -> HDoc #

lines_ :: [Line HDoc] -> HDoc #

vcat :: [HDoc] -> HDoc #

dualDoc :: SDoc -> HDoc -> HDoc #

IsOutput HDoc 
Instance details

Defined in GHC.Utils.Outputable

type Line HDoc 
Instance details

Defined in GHC.Utils.Outputable

type Line HDoc = HLine

data HLine #

Represents a single line of output that can be efficiently printed directly to a Handle (actually a BufHandle). See Note [SDoc versus HDoc] and Note [HLine versus HDoc] for more details.

Instances

Instances details
IsLine HLine 
Instance details

Defined in GHC.Utils.Outputable

IsOutput HLine 
Instance details

Defined in GHC.Utils.Outputable

class Outputable a => OutputableBndr a where #

When we print a binder, we often want to print its type too. The OutputableBndr class encapsulates this idea.

Minimal complete definition

pprPrefixOcc, pprInfixOcc

Instances

Instances details
OutputableBndr ConLike 
Instance details

Defined in GHC.Core.ConLike

OutputableBndr DataCon 
Instance details

Defined in GHC.Core.DataCon

OutputableBndr PatSyn 
Instance details

Defined in GHC.Core.PatSyn

OutputableBndr BinderInfo 
Instance details

Defined in GHC.Stg.Lift.Analysis

OutputableBndr Name 
Instance details

Defined in GHC.Types.Name

OutputableBndr OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

OutputableBndr RdrName 
Instance details

Defined in GHC.Types.Name.Reader

(Outputable a, OutputableBndr e) => OutputableBndr (GenLocated (SrcSpanAnn' a) e) 
Instance details

Defined in GHC.Parser.Annotation

OutputableBndr (Id, TagSig) 
Instance details

Defined in GHC.Stg.InferTags.TagSig

data BindingSite #

BindingSite is used to tell the thing that prints binder what language construct is binding the identifier. This can be used to decide how much info to print. Also see Note [Binding-site specific printing] in GHC.Core.Ppr

Constructors

LambdaBind

The x in (x. e)

CaseBind

The x in case scrut of x { (y,z) -> ... }

CasePatBind

The y,z in case scrut of x { (y,z) -> ... }

LetBind

The x in (let x = rhs in e)

Instances

Instances details
Eq BindingSite 
Instance details

Defined in GHC.Utils.Outputable

newtype PDoc a #

Wrapper for types having a Outputable instance when an OutputableP instance is required.

Constructors

PDoc a 

Instances

Instances details
Outputable a => OutputableP env (PDoc a) 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> PDoc a -> SDoc #

class OutputableP env a where #

Outputable class with an additional environment value

See Note [The OutputableP class]

Methods

pdoc :: env -> a -> SDoc #

Instances

Instances details
OutputableP env Void 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> Void -> SDoc #

OutputableP env Label 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

pdoc :: env -> Label -> SDoc #

OutputableP env Alignment 
Instance details

Defined in GHC.Types.Basic

Methods

pdoc :: env -> Alignment -> SDoc #

OutputableP env SDoc 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> SDoc -> SDoc #

OutputableP env a => OutputableP env (SCC a) 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> SCC a -> SDoc #

OutputableP env a => OutputableP env (Set a) 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> Set a -> SDoc #

OutputableP env a => OutputableP env (LabelMap a) 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

pdoc :: env -> LabelMap a -> SDoc #

Outputable a => OutputableP env (PDoc a) 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> PDoc a -> SDoc #

OutputableP env a => OutputableP env (Maybe a) 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> Maybe a -> SDoc #

OutputableP env a => OutputableP env [a] 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> [a] -> SDoc #

(OutputableP env key, OutputableP env elt) => OutputableP env (Map key elt) 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> Map key elt -> SDoc #

(OutputableP env a, OutputableP env b) => OutputableP env (a, b) 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> (a, b) -> SDoc #

(OutputableP env a, OutputableP env b, OutputableP env c) => OutputableP env (a, b, c) 
Instance details

Defined in GHC.Utils.Outputable

Methods

pdoc :: env -> (a, b, c) -> SDoc #

data SDocContext #

Constructors

SDC 

Fields

data QualifyName #

Instances

Instances details
Outputable QualifyName 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: QualifyName -> SDoc #

data PromotionTickContext #

Flags that affect whether a promotion tick is printed.

type QueryPromotionTick = PromotedItem -> Bool #

Given a promoted data constructor, decide whether to print a tick to disambiguate the namespace.

type QueryQualifyPackage = Unit -> Bool #

For a given package, we need to know whether to print it with the component id to disambiguate it.

type QueryQualifyModule = Module -> Bool #

For a given module, we need to know whether to print it with a package name to disambiguate it.

type QueryQualifyName = Module -> OccName -> QualifyName #

Given a Name's Module and OccName, decide whether and how to qualify it.

data NamePprCtx #

When printing code that contains original names, we need to map the original names back to something the user understands. This is the purpose of the triple of functions that gets passed around when rendering SDoc.

data Depth #

Constructors

AllTheWay 
PartWay Int

0 => stop

DefaultDepth

Use sdocDefaultDepth field as depth

data PprStyle #

Constructors

PprUser NamePprCtx Depth Coloured 
PprDump NamePprCtx 
PprCode

Print code; either C or assembler

Instances

Instances details
Outputable PprStyle 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: PprStyle -> SDoc #

data IdDetails #

Identifier Details

The IdDetails of an Id give stable, and necessary, information about the Id.

Constructors

VanillaId 
RecSelId RecSelParent Bool

The Id for a record selector

DataConWorkId DataCon

The Id is for a data constructor worker

DataConWrapId DataCon

The Id is for a data constructor wrapper

Instances

Instances details
Outputable IdDetails 
Instance details

Defined in GHC.Types.Id.Info

Methods

ppr :: IdDetails -> SDoc #

data IdInfo #

Identifier Information

An IdInfo gives optional information about an Id. If present it never lies, but it may not be present, in which case there is always a conservative assumption which can be made.

Two Ids may have different info even though they have the same Unique (and are hence the same Id); for example, one might lack the properties attached to the other.

Most of the IdInfo gives information about the value, or definition, of the Id, independent of its usage. Exceptions to this are demandInfo, occInfo, oneShotInfo and callArityInfo.

Performance note: when we update IdInfo, we have to reallocate this entire record, so it is a good idea not to let this data structure get too big.

class Uniquable a where #

Class of things that we can obtain a Unique from

Methods

getUnique :: a -> Unique #

Instances

Instances details
Uniquable Label 
Instance details

Defined in GHC.Cmm.Dataflow.Label

Methods

getUnique :: Label -> Unique #

Uniquable Class 
Instance details

Defined in GHC.Core.Class

Methods

getUnique :: Class -> Unique #

Uniquable CoAxiomRule 
Instance details

Defined in GHC.Core.Coercion.Axiom

Uniquable ConLike 
Instance details

Defined in GHC.Core.ConLike

Methods

getUnique :: ConLike -> Unique #

Uniquable DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

getUnique :: DataCon -> Unique #

Uniquable PatSyn 
Instance details

Defined in GHC.Core.PatSyn

Methods

getUnique :: PatSyn -> Unique #

Uniquable CoercionHole 
Instance details

Defined in GHC.Core.TyCo.Rep

Uniquable TyCon 
Instance details

Defined in GHC.Core.TyCon

Methods

getUnique :: TyCon -> Unique #

Uniquable FastString 
Instance details

Defined in GHC.Types.Unique

Uniquable Ident 
Instance details

Defined in GHC.JS.Syntax

Methods

getUnique :: Ident -> Unique #

Uniquable EvBindsVar 
Instance details

Defined in GHC.Tc.Types.Evidence

Uniquable SkolemInfo 
Instance details

Defined in GHC.Tc.Types.Origin

Uniquable Name 
Instance details

Defined in GHC.Types.Name

Methods

getUnique :: Name -> Unique #

Uniquable OccName 
Instance details

Defined in GHC.Types.Name.Occurrence

Methods

getUnique :: OccName -> Unique #

Uniquable Unique 
Instance details

Defined in GHC.Types.Unique

Methods

getUnique :: Unique -> Unique #

Uniquable Var 
Instance details

Defined in GHC.Types.Var

Methods

getUnique :: Var -> Unique #

Uniquable PackageId 
Instance details

Defined in GHC.Unit.Info

Uniquable PackageName 
Instance details

Defined in GHC.Unit.Info

Uniquable Module 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Module -> Unique #

Uniquable UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: UnitId -> Unique #

Uniquable ModuleName 
Instance details

Defined in GHC.Types.Unique

Uniquable Int 
Instance details

Defined in GHC.Types.Unique

Methods

getUnique :: Int -> Unique #

Uniquable (CoAxiom br) 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

getUnique :: CoAxiom br -> Unique #

Uniquable unit => Uniquable (Definite unit) 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Definite unit -> Unique #

IsUnitId u => Uniquable (GenUnit u) 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: GenUnit u -> Unique #

class NamedThing a where #

A class allowing convenient access to the Name of various datatypes

Minimal complete definition

getName

Methods

getOccName :: a -> OccName #

getName :: a -> Name #

Instances

Instances details
NamedThing Class 
Instance details

Defined in GHC.Core.Class

NamedThing ConLike 
Instance details

Defined in GHC.Core.ConLike

NamedThing DataCon 
Instance details

Defined in GHC.Core.DataCon

NamedThing FamInst 
Instance details

Defined in GHC.Core.FamInstEnv

NamedThing ClsInst 
Instance details

Defined in GHC.Core.InstEnv

NamedThing PatSyn 
Instance details

Defined in GHC.Core.PatSyn

NamedThing TyCon 
Instance details

Defined in GHC.Core.TyCon

NamedThing IfaceClassOp 
Instance details

Defined in GHC.Iface.Syntax

NamedThing IfaceConDecl 
Instance details

Defined in GHC.Iface.Syntax

NamedThing IfaceDecl 
Instance details

Defined in GHC.Iface.Syntax

NamedThing HoleFitCandidate 
Instance details

Defined in GHC.Tc.Errors.Hole.FitTypes

NamedThing Name 
Instance details

Defined in GHC.Types.Name

NamedThing TyThing 
Instance details

Defined in GHC.Types.TyThing

NamedThing Var 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: Var -> OccName #

getName :: Var -> Name #

NamedThing (CoAxiom br) 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

getOccName :: CoAxiom br -> OccName #

getName :: CoAxiom br -> Name #

NamedThing e => NamedThing (Located e) 
Instance details

Defined in GHC.Types.Name

NamedThing (Located a) => NamedThing (LocatedAn an a) 
Instance details

Defined in GHC.Parser.Annotation

Methods

getOccName :: LocatedAn an a -> OccName #

getName :: LocatedAn an a -> Name #

NamedThing tv => NamedThing (VarBndr tv flag) 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: VarBndr tv flag -> OccName #

getName :: VarBndr tv flag -> Name #

type TyVar = Var #

Type or kind Variable

data Specificity #

Whether an Invisible argument may appear in source Haskell.

Constructors

SpecifiedSpec

the argument may appear in source Haskell, but isn't required.

Instances

Instances details
Data Specificity 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: Specificity -> Constr #

dataTypeOf :: Specificity -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary Specificity 
Instance details

Defined in GHC.Types.Var

Eq Specificity 
Instance details

Defined in GHC.Types.Var

Ord Specificity 
Instance details

Defined in GHC.Types.Var

OutputableBndrFlag Specificity p 
Instance details

Defined in GHC.Hs.Type

Outputable tv => Outputable (VarBndr tv Specificity) 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: VarBndr tv Specificity -> SDoc #

data VarBndr var argf #

Constructors

Bndr var argf 

Instances

Instances details
(Data var, Data argf) => Data (VarBndr var argf) 
Instance details

Defined in GHC.Types.Var

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VarBndr var argf -> c (VarBndr var argf) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (VarBndr var argf) #

toConstr :: VarBndr var argf -> Constr #

dataTypeOf :: VarBndr var argf -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> VarBndr var argf -> VarBndr var argf #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VarBndr var argf -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VarBndr var argf -> r #

gmapQ :: (forall d. Data d => d -> u) -> VarBndr var argf -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VarBndr var argf -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VarBndr var argf -> m (VarBndr var argf) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VarBndr var argf -> m (VarBndr var argf) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VarBndr var argf -> m (VarBndr var argf) #

NamedThing tv => NamedThing (VarBndr tv flag) 
Instance details

Defined in GHC.Types.Var

Methods

getOccName :: VarBndr tv flag -> OccName #

getName :: VarBndr tv flag -> Name #

(Binary tv, Binary vis) => Binary (VarBndr tv vis) 
Instance details

Defined in GHC.Types.Var

Methods

put_ :: BinHandle -> VarBndr tv vis -> IO () #

put :: BinHandle -> VarBndr tv vis -> IO (Bin (VarBndr tv vis)) #

get :: BinHandle -> IO (VarBndr tv vis) #

OutputableBndr tv => Outputable (VarBndr tv TyConBndrVis) 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: VarBndr tv TyConBndrVis -> SDoc #

Outputable tv => Outputable (VarBndr tv ForAllTyFlag) 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: VarBndr tv ForAllTyFlag -> SDoc #

Outputable tv => Outputable (VarBndr tv Specificity) 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: VarBndr tv Specificity -> SDoc #

(Eq tyvar, Eq argf) => Eq (VarBndr tyvar argf) Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.TypeRep

Methods

(==) :: VarBndr tyvar argf -> VarBndr tyvar argf -> Bool #

(/=) :: VarBndr tyvar argf -> VarBndr tyvar argf -> Bool #

data FunTyFlag #

The non-dependent version of ForAllTyFlag. See Note [FunTyFlag] Appears here partly so that it's together with its friends ForAllTyFlag and ForallVisFlag, but also because it is used in IfaceType, rather early in the compilation chain

Constructors

FTF_T_T 

Instances

Instances details
Data FunTyFlag 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: FunTyFlag -> Constr #

dataTypeOf :: FunTyFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary FunTyFlag 
Instance details

Defined in GHC.Types.Var

Outputable FunTyFlag 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: FunTyFlag -> SDoc #

Eq FunTyFlag 
Instance details

Defined in GHC.Types.Var

Ord FunTyFlag 
Instance details

Defined in GHC.Types.Var

data ForAllTyFlag #

ForAllTyFlag

Is something required to appear in source Haskell (Required), permitted by request (Specified) (visible type application), or prohibited entirely from appearing in source Haskell (Inferred)? See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in GHC.Core.TyCo.Rep

Constructors

Required 

Instances

Instances details
Data ForAllTyFlag 
Instance details

Defined in GHC.Types.Var

Methods

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

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

toConstr :: ForAllTyFlag -> Constr #

dataTypeOf :: ForAllTyFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary ForAllTyFlag 
Instance details

Defined in GHC.Types.Var

Outputable ForAllTyFlag 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: ForAllTyFlag -> SDoc #

Eq ForAllTyFlag 
Instance details

Defined in GHC.Types.Var

Ord ForAllTyFlag 
Instance details

Defined in GHC.Types.Var

Outputable tv => Outputable (VarBndr tv ForAllTyFlag) 
Instance details

Defined in GHC.Types.Var

Methods

ppr :: VarBndr tv ForAllTyFlag -> SDoc #

type CoreExpr = Expr CoreBndr #

Expressions where binders are CoreBndrs

type CoreBndr = Var #

The common case for the type of binders and variables when we are manipulating the Core language within GHC

data Expr b #

This is the data type that represents GHCs core intermediate language. Currently GHC uses System FC https://www.microsoft.com/en-us/research/publication/system-f-with-type-equality-coercions/ for this purpose, which is closely related to the simpler and better known System F http://en.wikipedia.org/wiki/System_F.

We get from Haskell source to this Core language in a number of stages:

  1. The source code is parsed into an abstract syntax tree, which is represented by the data type HsExpr with the names being RdrNames
  2. This syntax tree is renamed, which attaches a Unique to every RdrName (yielding a Name) to disambiguate identifiers which are lexically identical. For example, this program:
     f x = let f x = x + 1
           in f (x - 2)

Would be renamed by having Uniques attached so it looked something like this:

     f_1 x_2 = let f_3 x_4 = x_4 + 1
               in f_3 (x_2 - 2)

But see Note [Shadowing] below.

  1. The resulting syntax tree undergoes type checking (which also deals with instantiating type class arguments) to yield a HsExpr type that has Id as it's names.
  2. Finally the syntax tree is desugared from the expressive HsExpr type into this Expr type, which has far fewer constructors and hence is easier to perform optimization, analysis and code generation on.

The type parameter b is for the type of binders in the expression tree.

The language consists of the following elements:

  • Variables See Note [Variable occurrences in Core]
  • Primitive literals
  • Applications: note that the argument may be a Type. See Note [Representation polymorphism invariants]
  • Lambda abstraction See Note [Representation polymorphism invariants]
  • Recursive and non recursive lets. Operationally this corresponds to allocating a thunk for the things bound and then executing the sub-expression.

See Note [Core letrec invariant] See Note [Core let-can-float invariant] See Note [Representation polymorphism invariants] See Note [Core type and coercion invariant]

  • Case expression. Operationally this corresponds to evaluating the scrutinee (expression examined) to weak head normal form and then examining at most one level of resulting constructor (i.e. you cannot do nested pattern matching directly with this).

The binder gets bound to the value of the scrutinee, and the Type must be that of all the case alternatives

IMPORTANT: see Note [Case expression invariants]

  • Cast an expression to a particular type. This is used to implement newtypes (a newtype constructor or destructor just becomes a Cast in Core) and GADTs.
  • Ticks. These are used to represent all the source annotation we support: profiling SCCs, HPC ticks, and GHCi breakpoints.
  • A type: this should only show up at the top level of an Arg
  • A coercion

Constructors

Var Id 
Lit Literal 
App (Expr b) (Arg b) infixl 4 
Lam b (Expr b) 
Let (Bind b) (Expr b) 
Case (Expr b) b Type [Alt b] 
Cast (Expr b) CoercionR 
Tick CoreTickish (Expr b) 
Type Type 
Coercion Coercion 

Instances

Instances details
Show CoreExpr Source # 
Instance details

Defined in Language.Haskell.Liquid.Transforms.CoreToLogic

Subable CoreExpr Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Play

Data b => Data (Expr b) 
Instance details

Defined in GHC.Core

Methods

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

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

toConstr :: Expr b -> Constr #

dataTypeOf :: Expr b -> DataType #

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

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

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

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

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

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

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

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

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

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

PPrint (Expr Var) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.PrettyPrint

Methods

pprintTidy :: Tidy -> Expr Var -> Doc #

pprintPrec :: Int -> Tidy -> Expr Var -> Doc #

CBVisitable (Expr Var) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Visitors

Show (Axiom Var Type CoreExpr) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

data TyThing #

A global typecheckable-thing, essentially anything that has a name. Not to be confused with a TcTyThing, which is also a typecheckable thing but in the *local* context. See GHC.Tc.Utils.Env for how to retrieve a TyThing given a Name.

Instances

Instances details
NamedThing TyThing 
Instance details

Defined in GHC.Types.TyThing

Outputable TyThing 
Instance details

Defined in GHC.Types.TyThing

Methods

ppr :: TyThing -> SDoc #

PPrint TyThing Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

Methods

pprintTidy :: Tidy -> TyThing -> Doc #

pprintPrec :: Int -> Tidy -> TyThing -> Doc #

type PredType = Type #

A type of the form p of constraint kind represents a value whose type is the Haskell predicate p, where a predicate is what occurs before the => in a Haskell type.

We use PredType as documentation to mark those types that we guarantee to have this kind.

It can be expanded into its representation, but:

  • The type checker must treat it as opaque
  • The rest of the compiler treats it as transparent

Consider these examples:

f :: (Eq a) => a -> Int
g :: (?x :: Int -> Int) => a -> Int
h :: (r\l) => {r} => {l::Int | r}

Here the Eq a and ?x :: Int -> Int and rl are all called "predicates"

data TyLit #

Instances

Instances details
Data TyLit 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: TyLit -> Constr #

dataTypeOf :: TyLit -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable TyLit 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: TyLit -> SDoc #

Eq TyLit 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

data UnivCoProvenance #

For simplicity, we have just one UnivCo that represents a coercion from some type to some other type, with (in general) no restrictions on the type. The UnivCoProvenance specifies more exactly what the coercion really is and why a program should (or shouldn't!) trust the coercion. It is reasonable to consider each constructor of UnivCoProvenance as a totally independent coercion form; their only commonality is that they don't tell you what types they coercion between. (That info is in the UnivCo constructor of Coercion.

Constructors

PhantomProv KindCoercion

See Note [Phantom coercions]. Only in Phantom roled coercions

ProofIrrelProv KindCoercion

From the fact that any two coercions are considered equivalent. See Note [ProofIrrelProv]. Can be used in Nominal or Representational coercions

Instances

Instances details
Data UnivCoProvenance 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

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

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

toConstr :: UnivCoProvenance -> Constr #

dataTypeOf :: UnivCoProvenance -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable UnivCoProvenance 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: UnivCoProvenance -> SDoc #

class Monad m => MonadUnique (m :: Type -> Type) where #

A monad for generating unique identifiers

Minimal complete definition

getUniqueSupplyM

Methods

getUniqueM :: m Unique #

Get a new unique identifier

data GenLocated l e #

We attach SrcSpans to lots of things, so let's have a datatype for it.

Constructors

L l e 

Instances

Instances details
Foldable (GenLocated l) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

fold :: Monoid m => GenLocated l m -> m #

foldMap :: Monoid m => (a -> m) -> GenLocated l a -> m #

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

foldr :: (a -> b -> b) -> b -> GenLocated l a -> b #

foldr' :: (a -> b -> b) -> b -> GenLocated l a -> b #

foldl :: (b -> a -> b) -> b -> GenLocated l a -> b #

foldl' :: (b -> a -> b) -> b -> GenLocated l a -> b #

foldr1 :: (a -> a -> a) -> GenLocated l a -> a #

foldl1 :: (a -> a -> a) -> GenLocated l a -> a #

toList :: GenLocated l a -> [a] #

null :: GenLocated l a -> Bool #

length :: GenLocated l a -> Int #

elem :: Eq a => a -> GenLocated l a -> Bool #

maximum :: Ord a => GenLocated l a -> a #

minimum :: Ord a => GenLocated l a -> a #

sum :: Num a => GenLocated l a -> a #

product :: Num a => GenLocated l a -> a #

Traversable (GenLocated l) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

sequenceA :: Applicative f => GenLocated l (f a) -> f (GenLocated l a) #

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

sequence :: Monad m => GenLocated l (m a) -> m (GenLocated l a) #

Functor (GenLocated l) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

fmap :: (a -> b) -> GenLocated l a -> GenLocated l b #

(<$) :: a -> GenLocated l b -> GenLocated l a #

NamedThing e => NamedThing (Located e) 
Instance details

Defined in GHC.Types.Name

Outputable e => Outputable (Located e) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: Located e -> SDoc #

(Data l, Data e) => Data (GenLocated l e) 
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) -> GenLocated l e -> c (GenLocated l e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenLocated l e) #

toConstr :: GenLocated l e -> Constr #

dataTypeOf :: GenLocated l e -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> GenLocated l e -> GenLocated l e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenLocated l e -> r #

gmapQ :: (forall d. Data d => d -> u) -> GenLocated l e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenLocated l e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenLocated l e -> m (GenLocated l e) #

(Show l, Show e) => Show (GenLocated l e) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

showsPrec :: Int -> GenLocated l e -> ShowS #

show :: GenLocated l e -> String #

showList :: [GenLocated l e] -> ShowS #

(NFData l, NFData e) => NFData (GenLocated l e) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

rnf :: GenLocated l e -> () #

NamedThing (Located a) => NamedThing (LocatedAn an a) 
Instance details

Defined in GHC.Parser.Annotation

Methods

getOccName :: LocatedAn an a -> OccName #

getName :: LocatedAn an a -> Name #

Outputable (GenLocated Anchor EpaComment) 
Instance details

Defined in GHC.Parser.Annotation

(Outputable a, Outputable e) => Outputable (GenLocated (SrcSpanAnn' a) e) 
Instance details

Defined in GHC.Parser.Annotation

Methods

ppr :: GenLocated (SrcSpanAnn' a) e -> SDoc #

Outputable a => Outputable (GenLocated TokenLocation a) 
Instance details

Defined in GHC.Parser.Annotation

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

Defined in GHC.Types.SrcLoc

(Outputable a, OutputableBndr e) => OutputableBndr (GenLocated (SrcSpanAnn' a) e) 
Instance details

Defined in GHC.Parser.Annotation

(Eq l, Eq e) => Eq (GenLocated l e) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

(==) :: GenLocated l e -> GenLocated l e -> Bool #

(/=) :: GenLocated l e -> GenLocated l e -> Bool #

(Ord l, Ord e) => Ord (GenLocated l e) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

compare :: GenLocated l e -> GenLocated l e -> Ordering #

(<) :: GenLocated l e -> GenLocated l e -> Bool #

(<=) :: GenLocated l e -> GenLocated l e -> Bool #

(>) :: GenLocated l e -> GenLocated l e -> Bool #

(>=) :: GenLocated l e -> GenLocated l e -> Bool #

max :: GenLocated l e -> GenLocated l e -> GenLocated l e #

min :: GenLocated l e -> GenLocated l e -> GenLocated l e #

type Anno (LocatedA (IE (GhcPass p))) 
Instance details

Defined in GHC.Hs.ImpExp

type Anno (LocatedN Name) 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN RdrName) 
Instance details

Defined in GHC.Hs.Binds

type Anno (LocatedN Id) 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (Match GhcPs (LocatedA (PatBuilder GhcPs)))] 
Instance details

Defined in GHC.Parser.PostProcess

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] = SrcSpanAnnL
type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] 
Instance details

Defined in GHC.Hs.Expr

type Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr))))] = SrcSpanAnnL
type Anno [LocatedA (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs)))] 
Instance details

Defined in GHC.Parser.Types

type Anno [LocatedA (IE (GhcPass p))] 
Instance details

Defined in GHC.Hs.ImpExp

type Anno [LocatedA (ConDeclField (GhcPass _1))] 
Instance details

Defined in GHC.Hs.Decls

type Anno [LocatedA (HsType (GhcPass p))] 
Instance details

Defined in GHC.Hs.Type

type Anno [LocatedN Name] 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN RdrName] 
Instance details

Defined in GHC.Hs.Binds

type Anno [LocatedN Id] 
Instance details

Defined in GHC.Hs.Binds

type Anno (FamEqn p (LocatedA (HsType p))) 
Instance details

Defined in GHC.Hs.Decls

type Anno (GRHS (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (GRHS GhcPs (LocatedA (PatBuilder GhcPs))) 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (Match (GhcPass p) (LocatedA (HsCmd (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match (GhcPass p) (LocatedA (HsExpr (GhcPass p)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (Match GhcPs (LocatedA (PatBuilder GhcPs))) 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr)))) 
Instance details

Defined in GHC.Hs.Expr

type Anno (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (body (GhcPass pr)))) = SrcSpanAnnA
type Anno (StmtLR GhcPs GhcPs (LocatedA (PatBuilder GhcPs))) 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (StmtLR GhcRn GhcRn (LocatedA (body GhcRn))) 
Instance details

Defined in GHC.Hs.Expr

data SrcSpan #

Source Span

A SrcSpan identifies either a specific portion of a text file or a human-readable description of a location.

Instances

Instances details
FromJSON SrcSpan Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Errors

FromJSONKey SrcSpan Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Errors

ToJSON SrcSpan Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Errors

ToJSONKey SrcSpan Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Errors

Data SrcSpan 
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) -> SrcSpan -> c SrcSpan #

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

toConstr :: SrcSpan -> Constr #

dataTypeOf :: SrcSpan -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

NFData SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

rnf :: SrcSpan -> () #

ToJson SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

json :: SrcSpan -> JsonDoc #

Outputable SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: SrcSpan -> SDoc #

Eq SrcSpan 
Instance details

Defined in GHC.Types.SrcLoc

Methods

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

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

Hashable SrcSpan Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

hashWithSalt :: Int -> SrcSpan -> Int #

hash :: SrcSpan -> Int #

PPrint SrcSpan Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Errors

Methods

pprintTidy :: Tidy -> SrcSpan -> Doc #

pprintPrec :: Int -> Tidy -> SrcSpan -> Doc #

NamedThing e => NamedThing (Located e) 
Instance details

Defined in GHC.Types.Name

Outputable e => Outputable (Located e) 
Instance details

Defined in GHC.Types.SrcLoc

Methods

ppr :: Located e -> SDoc #

data RealSrcSpan #

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

Defined in Language.Haskell.Liquid.Types.Errors

ToJSON RealSrcSpan Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Errors

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

Constructors

SourceText String 
NoSourceText

For when code is generated, e.g. TH, deriving. The pretty printer will then make its own representation of the item.

Instances

Instances details
Data SourceText 
Instance details

Defined in GHC.Types.SourceText

Methods

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

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

toConstr :: SourceText -> Constr #

dataTypeOf :: SourceText -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SourceText 
Instance details

Defined in GHC.Types.SourceText

Binary SourceText 
Instance details

Defined in GHC.Types.SourceText

Outputable SourceText 
Instance details

Defined in GHC.Types.SourceText

Methods

ppr :: SourceText -> SDoc #

Eq SourceText 
Instance details

Defined in GHC.Types.SourceText

type Anno (SourceText, RuleName) 
Instance details

Defined in GHC.Hs.Decls

data FieldLabel #

Fields in an algebraic record type; see Note [FieldLabel].

Instances

Instances details
Data FieldLabel 
Instance details

Defined in GHC.Types.FieldLabel

Methods

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

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

toConstr :: FieldLabel -> Constr #

dataTypeOf :: FieldLabel -> DataType #

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

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

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

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

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

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

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

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

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

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

NFData FieldLabel 
Instance details

Defined in GHC.Types.FieldLabel

Methods

rnf :: FieldLabel -> () #

HasOccName FieldLabel 
Instance details

Defined in GHC.Types.FieldLabel

Binary Name => Binary FieldLabel

We need the Binary Name constraint here even though there is an instance defined in GHC.Types.Name, because the we have a SOURCE import, so the instance is not in scope. And the instance cannot be added to Name.hs-boot because GHC.Utils.Binary itself depends on GHC.Types.Name.

Instance details

Defined in GHC.Types.FieldLabel

Outputable FieldLabel 
Instance details

Defined in GHC.Types.FieldLabel

Methods

ppr :: FieldLabel -> SDoc #

Eq FieldLabel 
Instance details

Defined in GHC.Types.FieldLabel

data Bag a #

Instances

Instances details
Foldable Bag 
Instance details

Defined in GHC.Data.Bag

Methods

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

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

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

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

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

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

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

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

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

toList :: Bag a -> [a] #

null :: Bag a -> Bool #

length :: Bag a -> Int #

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

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

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

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

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

Traversable Bag 
Instance details

Defined in GHC.Data.Bag

Methods

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

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

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

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

Functor Bag 
Instance details

Defined in GHC.Data.Bag

Methods

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

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

Data a => Data (Bag a) 
Instance details

Defined in GHC.Data.Bag

Methods

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

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

toConstr :: Bag a -> Constr #

dataTypeOf :: Bag a -> DataType #

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

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

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

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

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

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

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

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

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

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

Monoid (Bag a) 
Instance details

Defined in GHC.Data.Bag

Methods

mempty :: Bag a #

mappend :: Bag a -> Bag a -> Bag a #

mconcat :: [Bag a] -> Bag a #

Semigroup (Bag a) 
Instance details

Defined in GHC.Data.Bag

Methods

(<>) :: Bag a -> Bag a -> Bag a #

sconcat :: NonEmpty (Bag a) -> Bag a #

stimes :: Integral b => b -> Bag a -> Bag a #

IsList (Bag a) 
Instance details

Defined in GHC.Data.Bag

Associated Types

type Item (Bag a) #

Methods

fromList :: [Item (Bag a)] -> Bag a #

fromListN :: Int -> [Item (Bag a)] -> Bag a #

toList :: Bag a -> [Item (Bag a)] #

Outputable a => Outputable (Bag a) 
Instance details

Defined in GHC.Data.Bag

Methods

ppr :: Bag a -> SDoc #

type Item (Bag a) 
Instance details

Defined in GHC.Data.Bag

type Item (Bag a) = a

data LexicalFixity #

Captures the fixity of declarations as they are parsed. This is not necessarily the same as the fixity declaration, as the normal fixity may be overridden using parens or backticks.

Constructors

Prefix 

Instances

Instances details
Data LexicalFixity 
Instance details

Defined in GHC.Types.Fixity

Methods

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

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

toConstr :: LexicalFixity -> Constr #

dataTypeOf :: LexicalFixity -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable LexicalFixity 
Instance details

Defined in GHC.Types.Fixity

Methods

ppr :: LexicalFixity -> SDoc #

Eq LexicalFixity 
Instance details

Defined in GHC.Types.Fixity

data FixityDirection #

Constructors

InfixR 
InfixN 

Instances

Instances details
Data FixityDirection 
Instance details

Defined in GHC.Types.Fixity

Methods

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

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

toConstr :: FixityDirection -> Constr #

dataTypeOf :: FixityDirection -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary FixityDirection 
Instance details

Defined in GHC.Types.Fixity

Outputable FixityDirection 
Instance details

Defined in GHC.Types.Fixity

Methods

ppr :: FixityDirection -> SDoc #

Eq FixityDirection 
Instance details

Defined in GHC.Types.Fixity

data GenWithIsBoot mod #

This data type just pairs a value mod with an IsBootInterface flag. In practice, mod is usually a Module or ModuleName'.

Instances

Instances details
Foldable GenWithIsBoot 
Instance details

Defined in GHC.Unit.Types

Methods

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

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

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

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

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

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

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

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

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

toList :: GenWithIsBoot a -> [a] #

null :: GenWithIsBoot a -> Bool #

length :: GenWithIsBoot a -> Int #

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

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

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

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

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

Traversable GenWithIsBoot 
Instance details

Defined in GHC.Unit.Types

Methods

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

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

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

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

Functor GenWithIsBoot 
Instance details

Defined in GHC.Unit.Types

Methods

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

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

Show mod => Show (GenWithIsBoot mod) 
Instance details

Defined in GHC.Unit.Types

Binary a => Binary (GenWithIsBoot a) 
Instance details

Defined in GHC.Unit.Types

Outputable a => Outputable (GenWithIsBoot a) 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: GenWithIsBoot a -> SDoc #

Eq mod => Eq (GenWithIsBoot mod) 
Instance details

Defined in GHC.Unit.Types

Methods

(==) :: GenWithIsBoot mod -> GenWithIsBoot mod -> Bool #

(/=) :: GenWithIsBoot mod -> GenWithIsBoot mod -> Bool #

Ord mod => Ord (GenWithIsBoot mod) 
Instance details

Defined in GHC.Unit.Types

data ModLocation #

Module Location

Where a module lives on the file system: the actual locations of the .hs, .hi, .dyn_hi, .o, .dyn_o and .hie files, if we have them.

For a module in another unit, the ml_hs_file and ml_obj_file components of ModLocation are undefined.

The locations specified by a ModLocation may or may not correspond to actual files yet: for example, even if the object file doesn't exist, the ModLocation still contains the path to where the object file will reside if/when it is created.

The paths of anything which can affect recompilation should be placed inside ModLocation.

When a ModLocation is created none of the filepaths will have -boot suffixes. This is because in --make mode the ModLocation is put in the finder cache which is indexed by ModuleName, when a ModLocation is retrieved from the FinderCache the boot suffixes are appended. The other case is in -c mode, there the ModLocation immediately gets given the boot suffixes in mkOneShotModLocation.

Instances

Instances details
Show ModLocation 
Instance details

Defined in GHC.Unit.Module.Location

Outputable ModLocation 
Instance details

Defined in GHC.Unit.Module.Location

Methods

ppr :: ModLocation -> SDoc #

data PkgQual #

Package-qualifier after renaming

Renaming detects if "this" or the unit-id of the home-unit was used as a package qualifier.

Constructors

NoPkgQual

No package qualifier

Instances

Instances details
Data PkgQual 
Instance details

Defined in GHC.Types.PkgQual

Methods

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

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

toConstr :: PkgQual -> Constr #

dataTypeOf :: PkgQual -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable PkgQual 
Instance details

Defined in GHC.Types.PkgQual

Methods

ppr :: PkgQual -> SDoc #

Eq PkgQual 
Instance details

Defined in GHC.Types.PkgQual

Methods

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

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

Ord PkgQual 
Instance details

Defined in GHC.Types.PkgQual

type LHsExpr p #

Arguments

 = XRec p (HsExpr p)

May have AnnKeywordId : AnnComma when in a list

Located Haskell Expression

data PromotionFlag #

Is a TyCon a promoted data constructor or just a normal type constructor?

Constructors

NotPromoted 

Instances

Instances details
Data PromotionFlag 
Instance details

Defined in Language.Haskell.Syntax.Type

Methods

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

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

toConstr :: PromotionFlag -> Constr #

dataTypeOf :: PromotionFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq PromotionFlag 
Instance details

Defined in Language.Haskell.Syntax.Type

data InlinePragma #

Instances

Instances details
Data InlinePragma 
Instance details

Defined in GHC.Types.Basic

Methods

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

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

toConstr :: InlinePragma -> Constr #

dataTypeOf :: InlinePragma -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary InlinePragma 
Instance details

Defined in GHC.Types.Basic

Outputable InlinePragma 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: InlinePragma -> SDoc #

Eq InlinePragma 
Instance details

Defined in GHC.Types.Basic

data Phase #

Untyped Phase description

Constructors

StopLn 

Instances

Instances details
Show Phase 
Instance details

Defined in GHC.Driver.Phases

Methods

showsPrec :: Int -> Phase -> ShowS #

show :: Phase -> String #

showList :: [Phase] -> ShowS #

Outputable Phase 
Instance details

Defined in GHC.Driver.Phases

Methods

ppr :: Phase -> SDoc #

Eq Phase 
Instance details

Defined in GHC.Driver.Phases

Methods

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

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

data PprPrec #

A general-purpose pretty-printing precedence type.

Instances

Instances details
Show PprPrec 
Instance details

Defined in GHC.Types.Basic

Eq PprPrec 
Instance details

Defined in GHC.Types.Basic

Methods

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

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

Ord PprPrec 
Instance details

Defined in GHC.Types.Basic

data TopLevelFlag #

Constructors

NotTopLevel 

Instances

Instances details
Data TopLevelFlag 
Instance details

Defined in GHC.Types.Basic

Methods

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

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

toConstr :: TopLevelFlag -> Constr #

dataTypeOf :: TopLevelFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable TopLevelFlag 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: TopLevelFlag -> SDoc #

data DataCon #

A data constructor

Instances

Instances details
Data DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

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

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

toConstr :: DataCon -> Constr #

dataTypeOf :: DataCon -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DataCon Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

NamedThing DataCon 
Instance details

Defined in GHC.Core.DataCon

Uniquable DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

getUnique :: DataCon -> Unique #

Outputable DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: DataCon -> SDoc #

Outputable OccurrenceMap Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Play

Methods

ppr :: OccurrenceMap -> SDoc #

OutputableBndr DataCon 
Instance details

Defined in GHC.Core.DataCon

Eq DataCon 
Instance details

Defined in GHC.Core.DataCon

Methods

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

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

Ord DataCon Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

Hashable DataCon Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

hashWithSalt :: Int -> DataCon -> Int #

hash :: DataCon -> Int #

Symbolic DataCon Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

Methods

symbol :: DataCon -> Symbol #

PPrint DataCon Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Types

Methods

pprintTidy :: Tidy -> DataCon -> Doc #

pprintPrec :: Int -> Tidy -> DataCon -> Doc #

ResolveSym DataCon Source # 
Instance details

Defined in Language.Haskell.Liquid.Bare.Resolve

Qualify (Measure SpecType DataCon) Source # 
Instance details

Defined in Language.Haskell.Liquid.Bare.Resolve

type DFunId = Id #

Dictionary Function Identifier

type VarSet = UniqSet Var #

A non-deterministic Variable Set

A non-deterministic set of variables. See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM for explanation why it's not deterministic and why it matters. Use DVarSet if the set eventually gets converted into a list or folded over in a way where the order changes the generated code, for example when abstracting variables.

data AvailInfo #

Records what things are "available", i.e. in scope

Constructors

Avail GreName

An ordinary identifier in scope, or a field label without a parent type (see Note [Representing pattern synonym fields in AvailInfo]).

AvailTC

A type or class in scope

The AvailTC Invariant: If the type or class is itself to be in scope, it must be first in this list. Thus, typically:

AvailTC Eq [Eq, ==, \/=]

Fields

  • Name

    The name of the type or class

  • [GreName]

    The available pieces of type or class (see Note [Representing fields in AvailInfo]).

Instances

Instances details
Data AvailInfo 
Instance details

Defined in GHC.Types.Avail

Methods

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

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

toConstr :: AvailInfo -> Constr #

dataTypeOf :: AvailInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

NFData AvailInfo 
Instance details

Defined in GHC.Types.Avail

Methods

rnf :: AvailInfo -> () #

Binary AvailInfo 
Instance details

Defined in GHC.Types.Avail

Outputable AvailInfo 
Instance details

Defined in GHC.Types.Avail

Methods

ppr :: AvailInfo -> SDoc #

Eq AvailInfo

Used when deciding if the interface has changed

Instance details

Defined in GHC.Types.Avail

data ImpItemSpec #

Import Item Specification

Describes import info a particular Name

Constructors

ImpAll

The import had no import list, or had a hiding list

Instances

Instances details
Data ImpItemSpec 
Instance details

Defined in GHC.Types.Name.Reader

Methods

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

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

toConstr :: ImpItemSpec -> Constr #

dataTypeOf :: ImpItemSpec -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq ImpItemSpec 
Instance details

Defined in GHC.Types.Name.Reader

data ImpDeclSpec #

Import Declaration Specification

Describes a particular import declaration and is shared among all the Provenances for that decl

Constructors

ImpDeclSpec 

Fields

  • is_mod :: ModuleName

    Module imported, e.g. import Muggle Note the Muggle may well not be the defining module for this thing!

  • is_as :: ModuleName

    Import alias, e.g. from as M (or Muggle if there is no as clause)

  • is_qual :: Bool

    Was this import qualified?

  • is_dloc :: SrcSpan

    The location of the entire import declaration

Instances

Instances details
Data ImpDeclSpec 
Instance details

Defined in GHC.Types.Name.Reader

Methods

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

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

toConstr :: ImpDeclSpec -> Constr #

dataTypeOf :: ImpDeclSpec -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq ImpDeclSpec 
Instance details

Defined in GHC.Types.Name.Reader

data ImportSpec #

Import Specification

The ImportSpec of something says how it came to be imported It's quite elaborate so that we can give accurate unused-name warnings.

Instances

Instances details
Data ImportSpec 
Instance details

Defined in GHC.Types.Name.Reader

Methods

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

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

toConstr :: ImportSpec -> Constr #

dataTypeOf :: ImportSpec -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable ImportSpec 
Instance details

Defined in GHC.Types.Name.Reader

Methods

ppr :: ImportSpec -> SDoc #

Eq ImportSpec 
Instance details

Defined in GHC.Types.Name.Reader

type LImportDecl pass #

Arguments

 = XRec pass (ImportDecl pass)

When in a list this may have

Located Import Declaration

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 #

type AnnPayload #

Arguments

 = Serialized

The "payload" of an annotation allows recovery of its value at a given type, and can be persisted to an interface file

data CoAxiomRule #

For now, we work only with nominal equality.

Instances

Instances details
Data CoAxiomRule 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

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

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

toConstr :: CoAxiomRule -> Constr #

dataTypeOf :: CoAxiomRule -> DataType #

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

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

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

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

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

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

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

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

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

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

Uniquable CoAxiomRule 
Instance details

Defined in GHC.Core.Coercion.Axiom

Outputable CoAxiomRule 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: CoAxiomRule -> SDoc #

Eq CoAxiomRule 
Instance details

Defined in GHC.Core.Coercion.Axiom

Ord CoAxiomRule 
Instance details

Defined in GHC.Core.Coercion.Axiom

data CoAxiom (br :: BranchFlag) #

A CoAxiom is a "coercion constructor", i.e. a named equality axiom.

Instances

Instances details
Typeable br => Data (CoAxiom br) 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

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

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

toConstr :: CoAxiom br -> Constr #

dataTypeOf :: CoAxiom br -> DataType #

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

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

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

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

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

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

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

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

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

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

NamedThing (CoAxiom br) 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

getOccName :: CoAxiom br -> OccName #

getName :: CoAxiom br -> Name #

Uniquable (CoAxiom br) 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

getUnique :: CoAxiom br -> Unique #

Outputable (CoAxiom br) 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

ppr :: CoAxiom br -> SDoc #

Eq (CoAxiom br) 
Instance details

Defined in GHC.Core.Coercion.Axiom

Methods

(==) :: CoAxiom br -> CoAxiom br -> Bool #

(/=) :: CoAxiom br -> CoAxiom br -> Bool #

type Branched = 'Branched #

data Class #

Instances

Instances details
Data Class 
Instance details

Defined in GHC.Core.Class

Methods

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

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

toConstr :: Class -> Constr #

dataTypeOf :: Class -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Class Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

showsPrec :: Int -> Class -> ShowS #

show :: Class -> String #

showList :: [Class] -> ShowS #

NFData Class Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

rnf :: Class -> () #

NamedThing Class 
Instance details

Defined in GHC.Core.Class

Uniquable Class 
Instance details

Defined in GHC.Core.Class

Methods

getUnique :: Class -> Unique #

Outputable Class 
Instance details

Defined in GHC.Core.Class

Methods

ppr :: Class -> SDoc #

Eq Class 
Instance details

Defined in GHC.Core.Class

Methods

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

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

Hashable Class Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

hashWithSalt :: Int -> Class -> Int #

hash :: Class -> Int #

Symbolic Class Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Misc

Methods

symbol :: Class -> Symbol #

Fixpoint Class Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.RefType

Methods

toFix :: Class -> Doc #

simplify :: Class -> Class #

PPrint Class Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.PrettyPrint

Methods

pprintTidy :: Tidy -> Class -> Doc #

pprintPrec :: Int -> Tidy -> Class -> Doc #

data TyConBndrVis #

Constructors

AnonTCB FunTyFlag 

Instances

Instances details
Binary TyConBndrVis 
Instance details

Defined in GHC.Core.TyCon

Outputable TyConBndrVis 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: TyConBndrVis -> SDoc #

OutputableBndr tv => Outputable (VarBndr tv TyConBndrVis) 
Instance details

Defined in GHC.Core.TyCon

Methods

ppr :: VarBndr tv TyConBndrVis -> SDoc #

data GenTickish (pass :: TickishPass) #

Constructors

ProfNote

An {-# SCC #-} profiling annotation, either automatically added by the desugarer as a result of -auto-all, or added by the user.

Fields

HpcTick

A "tick" used by HPC to track the execution of each subexpression in the original source code.

Fields

Breakpoint

A breakpoint for the GHCi debugger. This behaves like an HPC tick, but has a list of free variables which will be available for inspection in GHCi when the program stops at the breakpoint.

NB. we must take account of these Ids when (a) counting free variables, and (b) substituting (don't substitute for them)

Fields

SourceNote

A source note.

Source notes are pure annotations: Their presence should neither influence compilation nor execution. The semantics are given by causality: The presence of a source note means that a local change in the referenced source code span will possibly provoke the generated code to change. On the flip-side, the functionality of annotated code *must* be invariant against changes to all source code *except* the spans referenced in the source notes (see "Causality of optimized Haskell" paper for details).

Therefore extending the scope of any given source note is always valid. Note that it is still undesirable though, as this reduces their usefulness for debugging and profiling. Therefore we will generally try only to make use of this property where it is necessary to enable optimizations.

Fields

Instances

Instances details
Data (GenTickish 'TickishPassCmm) 
Instance details

Defined in GHC.Types.Tickish

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenTickish 'TickishPassCmm -> c (GenTickish 'TickishPassCmm) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenTickish 'TickishPassCmm) #

toConstr :: GenTickish 'TickishPassCmm -> Constr #

dataTypeOf :: GenTickish 'TickishPassCmm -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> GenTickish 'TickishPassCmm -> GenTickish 'TickishPassCmm #

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

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

gmapQ :: (forall d. Data d => d -> u) -> GenTickish 'TickishPassCmm -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenTickish 'TickishPassCmm -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenTickish 'TickishPassCmm -> m (GenTickish 'TickishPassCmm) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenTickish 'TickishPassCmm -> m (GenTickish 'TickishPassCmm) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenTickish 'TickishPassCmm -> m (GenTickish 'TickishPassCmm) #

Data (GenTickish 'TickishPassCore) 
Instance details

Defined in GHC.Types.Tickish

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenTickish 'TickishPassCore -> c (GenTickish 'TickishPassCore) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenTickish 'TickishPassCore) #

toConstr :: GenTickish 'TickishPassCore -> Constr #

dataTypeOf :: GenTickish 'TickishPassCore -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> GenTickish 'TickishPassCore -> GenTickish 'TickishPassCore #

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

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

gmapQ :: (forall d. Data d => d -> u) -> GenTickish 'TickishPassCore -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenTickish 'TickishPassCore -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenTickish 'TickishPassCore -> m (GenTickish 'TickishPassCore) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenTickish 'TickishPassCore -> m (GenTickish 'TickishPassCore) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenTickish 'TickishPassCore -> m (GenTickish 'TickishPassCore) #

Data (GenTickish 'TickishPassStg) 
Instance details

Defined in GHC.Types.Tickish

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenTickish 'TickishPassStg -> c (GenTickish 'TickishPassStg) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (GenTickish 'TickishPassStg) #

toConstr :: GenTickish 'TickishPassStg -> Constr #

dataTypeOf :: GenTickish 'TickishPassStg -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> GenTickish 'TickishPassStg -> GenTickish 'TickishPassStg #

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

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

gmapQ :: (forall d. Data d => d -> u) -> GenTickish 'TickishPassStg -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenTickish 'TickishPassStg -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenTickish 'TickishPassStg -> m (GenTickish 'TickishPassStg) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenTickish 'TickishPassStg -> m (GenTickish 'TickishPassStg) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenTickish 'TickishPassStg -> m (GenTickish 'TickishPassStg) #

Eq (GenTickish 'TickishPassCmm) 
Instance details

Defined in GHC.Types.Tickish

Methods

(==) :: GenTickish 'TickishPassCmm -> GenTickish 'TickishPassCmm -> Bool #

(/=) :: GenTickish 'TickishPassCmm -> GenTickish 'TickishPassCmm -> Bool #

Eq (GenTickish 'TickishPassCore) 
Instance details

Defined in GHC.Types.Tickish

Methods

(==) :: GenTickish 'TickishPassCore -> GenTickish 'TickishPassCore -> Bool #

(/=) :: GenTickish 'TickishPassCore -> GenTickish 'TickishPassCore -> Bool #

Ord (GenTickish 'TickishPassCmm) 
Instance details

Defined in GHC.Types.Tickish

Methods

compare :: GenTickish 'TickishPassCmm -> GenTickish 'TickishPassCmm -> Ordering #

(<) :: GenTickish 'TickishPassCmm -> GenTickish 'TickishPassCmm -> Bool #

(<=) :: GenTickish 'TickishPassCmm -> GenTickish 'TickishPassCmm -> Bool #

(>) :: GenTickish 'TickishPassCmm -> GenTickish 'TickishPassCmm -> Bool #

(>=) :: GenTickish 'TickishPassCmm -> GenTickish 'TickishPassCmm -> Bool #

max :: GenTickish 'TickishPassCmm -> GenTickish 'TickishPassCmm -> GenTickish 'TickishPassCmm #

min :: GenTickish 'TickishPassCmm -> GenTickish 'TickishPassCmm -> GenTickish 'TickishPassCmm #

Ord (GenTickish 'TickishPassCore) 
Instance details

Defined in GHC.Types.Tickish

Methods

compare :: GenTickish 'TickishPassCore -> GenTickish 'TickishPassCore -> Ordering #

(<) :: GenTickish 'TickishPassCore -> GenTickish 'TickishPassCore -> Bool #

(<=) :: GenTickish 'TickishPassCore -> GenTickish 'TickishPassCore -> Bool #

(>) :: GenTickish 'TickishPassCore -> GenTickish 'TickishPassCore -> Bool #

(>=) :: GenTickish 'TickishPassCore -> GenTickish 'TickishPassCore -> Bool #

max :: GenTickish 'TickishPassCore -> GenTickish 'TickishPassCore -> GenTickish 'TickishPassCore #

min :: GenTickish 'TickishPassCore -> GenTickish 'TickishPassCore -> GenTickish 'TickishPassCore #

type CoreTickish = GenTickish 'TickishPassCore #

data LitNumType #

Numeric literal type

Constructors

LitNumInt

Int# - according to target machine

Instances

Instances details
Data LitNumType 
Instance details

Defined in GHC.Types.Literal

Methods

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

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

toConstr :: LitNumType -> Constr #

dataTypeOf :: LitNumType -> DataType #

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

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

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

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

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

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

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

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

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

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

Enum LitNumType 
Instance details

Defined in GHC.Types.Literal

Binary LitNumType 
Instance details

Defined in GHC.Types.Literal

Eq LitNumType 
Instance details

Defined in GHC.Types.Literal

Ord LitNumType 
Instance details

Defined in GHC.Types.Literal

data Literal #

So-called Literals are one of:

  • An unboxed numeric literal or floating-point literal which is presumed to be surrounded by appropriate constructors (Int#, etc.), so that the overall thing makes sense.

We maintain the invariant that the Integer in the LitNumber constructor is actually in the (possibly target-dependent) range. The mkLit{Int,Word}*Wrap smart constructors ensure this by applying the target machine's wrapping semantics. Use these in situations where you know the wrapping semantics are correct.

  • The literal derived from the label mentioned in a "foreign label" declaration (LitLabel)
  • A LitRubbish to be used in place of values that are never used.
  • A character
  • A string
  • The NULL pointer

Constructors

LitChar Char

Char# - at least 31 bits. Create with mkLitChar

LitNumber !LitNumType !Integer

Any numeric literal that can be internally represented with an Integer.

LitString !ByteString

A string-literal: stored and emitted UTF-8 encoded, we'll arrange to decode it at runtime. Also emitted with a '\0' terminator. Create with mkLitString

LitFloat Rational

Float#. Create with mkLitFloat

LitDouble Rational

Double#. Create with mkLitDouble

Instances

Instances details
Data Literal 
Instance details

Defined in GHC.Types.Literal

Methods

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

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

toConstr :: Literal -> Constr #

dataTypeOf :: Literal -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary Literal 
Instance details

Defined in GHC.Types.Literal

Outputable Literal 
Instance details

Defined in GHC.Types.Literal

Methods

ppr :: Literal -> SDoc #

Eq Literal 
Instance details

Defined in GHC.Types.Literal

Methods

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

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

Ord Literal

Needed for the Ord instance of AltCon, which in turn is needed in CoreMap.

Instance details

Defined in GHC.Types.Literal

data Severity #

Used to describe warnings and errors o The message has a file/line/column heading, plus "warning:" or "error:", added by mkLocMessage o With SevIgnore the message is suppressed o Output is intended for end users

Constructors

SevWarning 

Instances

Instances details
Show Severity 
Instance details

Defined in GHC.Types.Error

ToJson Severity 
Instance details

Defined in GHC.Types.Error

Methods

json :: Severity -> JsonDoc #

Outputable Severity 
Instance details

Defined in GHC.Types.Error

Methods

ppr :: Severity -> SDoc #

Eq Severity 
Instance details

Defined in GHC.Types.Error

data MessageClass #

The class for a diagnostic message. The main purpose is to classify a message within GHC, to distinguish it from a debug/dump message vs a proper diagnostic, for which we include a DiagnosticReason.

Constructors

MCDiagnostic Severity DiagnosticReason (Maybe DiagnosticCode)

Diagnostics from the compiler. This constructor is very powerful as it allows the construction of a MessageClass with a completely arbitrary permutation of Severity and DiagnosticReason. As such, users are encouraged to use the mkMCDiagnostic smart constructor instead. Use this constructor directly only if you need to construct and manipulate diagnostic messages directly, for example inside Error. In all the other circumstances, especially when emitting compiler diagnostics, use the smart constructor.

The Maybe DiagnosticCode field carries a code (if available) for this diagnostic. If you are creating a message not tied to any error-message type, then use Nothing. In the long run, this really should always have a DiagnosticCode. See Note [Diagnostic codes].

Instances

Instances details
ToJson MessageClass 
Instance details

Defined in GHC.Types.Error

Methods

json :: MessageClass -> JsonDoc #

data MsgEnvelope e #

An envelope for GHC's facts about a running program, parameterised over the domain-specific (i.e. parsing, typecheck-renaming, etc) diagnostics.

To say things differently, GHC emits diagnostics about the running program, each of which is wrapped into a MsgEnvelope that carries specific information like where the error happened, etc. Finally, multiple MsgEnvelopes are aggregated into Messages that are returned to the user.

Instances

Instances details
Foldable MsgEnvelope 
Instance details

Defined in GHC.Types.Error

Methods

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

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

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

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

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

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

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

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

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

toList :: MsgEnvelope a -> [a] #

null :: MsgEnvelope a -> Bool #

length :: MsgEnvelope a -> Int #

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

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

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

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

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

Traversable MsgEnvelope 
Instance details

Defined in GHC.Types.Error

Methods

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

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

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

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

Functor MsgEnvelope 
Instance details

Defined in GHC.Types.Error

Methods

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

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

Show (MsgEnvelope DiagnosticMessage) 
Instance details

Defined in GHC.Types.Error

data DiagnosticReason #

The reason why a Diagnostic was emitted in the first place. Diagnostic messages are born within GHC with a very precise reason, which can be completely statically-computed (i.e. this is an error or a warning no matter what), or influenced by the specific state of the DynFlags at the moment of the creation of a new Diagnostic. For example, a parsing error is always going to be an error, whereas a 'WarningWithoutFlag Opt_WarnUnusedImports' might turn into an error due to '-Werror' or '-Werror=warn-unused-imports'. Interpreting a DiagnosticReason together with its associated Severity gives us the full picture.

Constructors

WarningWithoutFlag

Born as a warning.

Instances

Instances details
Show DiagnosticReason 
Instance details

Defined in GHC.Types.Error

Outputable DiagnosticReason 
Instance details

Defined in GHC.Types.Error

Methods

ppr :: DiagnosticReason -> SDoc #

Eq DiagnosticReason 
Instance details

Defined in GHC.Types.Error

class Diagnostic a where #

A class identifying a diagnostic. Dictionary.com defines a diagnostic as:

"a message output by a computer diagnosing an error in a computer program, computer system, or component device".

A Diagnostic carries the actual description of the message (which, in GHC's case, it can be an error or a warning) and the reason why such message was generated in the first place.

data Messages e #

A collection of messages emitted by GHC during error reporting. A diagnostic message is typically a warning or an error. See Note [Messages].

INVARIANT: All the messages in this collection must be relevant, i.e. their Severity should not be SevIgnore. The smart constructor mkMessages will filter out any message which Severity is SevIgnore.

Instances

Instances details
Foldable Messages 
Instance details

Defined in GHC.Types.Error

Methods

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

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

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

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

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

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

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

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

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

toList :: Messages a -> [a] #

null :: Messages a -> Bool #

length :: Messages a -> Int #

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

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

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

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

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

Traversable Messages 
Instance details

Defined in GHC.Types.Error

Methods

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

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

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

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

Functor Messages 
Instance details

Defined in GHC.Types.Error

Methods

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

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

Monoid (Messages e) 
Instance details

Defined in GHC.Types.Error

Methods

mempty :: Messages e #

mappend :: Messages e -> Messages e -> Messages e #

mconcat :: [Messages e] -> Messages e #

Semigroup (Messages e) 
Instance details

Defined in GHC.Types.Error

Methods

(<>) :: Messages e -> Messages e -> Messages e #

sconcat :: NonEmpty (Messages e) -> Messages e #

stimes :: Integral b => b -> Messages e -> Messages e #

Diagnostic e => Outputable (Messages e) 
Instance details

Defined in GHC.Types.Error

Methods

ppr :: Messages e -> SDoc #

data Logger #

data StrictnessMark #

Instances

Instances details
Binary StrictnessMark 
Instance details

Defined in GHC.Core.DataCon

Outputable StrictnessMark 
Instance details

Defined in GHC.Core.DataCon

Methods

ppr :: StrictnessMark -> SDoc #

Eq StrictnessMark 
Instance details

Defined in GHC.Core.DataCon

data HsArg tm ty #

Arguments in an expression/type after splitting

Constructors

HsValArg tm 

data HsType pass #

Haskell Type

Constructors

HsForAllTy (XForAllTy pass) (HsForAllTelescope pass) (LHsType pass)
HsQualTy (XQualTy pass) (LHsContext pass) (LHsType pass) 
HsTyVar (XTyVar pass) PromotionFlag (LIdP pass)
HsAppTy (XAppTy pass) (LHsType pass) (LHsType pass)
HsWildCardTy (XWildCardTy pass)

Instances

Instances details
DisambTD (HsType GhcPs) 
Instance details

Defined in GHC.Parser.PostProcess

type Anno (BangType (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsKind (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsType (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

type Anno [LocatedA (HsType (GhcPass p))] 
Instance details

Defined in GHC.Hs.Type

type Anno (FamEqn p (LocatedA (HsType p))) 
Instance details

Defined in GHC.Hs.Decls

data HsTyVarBndr flag pass #

Haskell Type Variable Binder The flag annotates the binder. It is Specificity in places where explicit specificity is allowed (e.g. x :: forall {a} b. ...) or () in other places.

Constructors

UserTyVar (XUserTyVar pass) flag (LIdP pass) 

Instances

Instances details
type Anno (HsTyVarBndr _flag (GhcPass _1)) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag (GhcPass _1)) = SrcSpanAnnA
type Anno (HsTyVarBndr _flag GhcPs) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag GhcRn) 
Instance details

Defined in GHC.Hs.Type

type Anno (HsTyVarBndr _flag GhcTc) 
Instance details

Defined in GHC.Hs.Type

data HsSigType pass #

A type signature that obeys the forall-or-nothing rule. In other words, an LHsType that uses an HsOuterSigTyVarBndrs to represent its outermost type variable quantification. See Note [Representing type signatures].

Constructors

HsSig (XHsSig pass) (HsOuterSigTyVarBndrs pass) (LHsType pass) 

Instances

Instances details
type Anno (HsSigType (GhcPass p)) 
Instance details

Defined in GHC.Hs.Type

data HsWildCardBndrs pass thing #

Haskell Wildcard Binders

Constructors

HsWC (XHsWC pass thing) thing 

data HsOuterTyVarBndrs flag pass #

The outermost type variables in a type that obeys the forall-or-nothing rule. See Note [forall-or-nothing rule].

Constructors

HsOuterImplicit (XHsOuterImplicit pass)

Implicit forall, e.g., f :: a -> b -> b

Instances

Instances details
type Anno (HsOuterTyVarBndrs _1 (GhcPass _2)) 
Instance details

Defined in GHC.Hs.Type

type LHsType pass #

Arguments

 = XRec pass (HsType pass)

May have AnnKeywordId : AnnComma when in a list

Located Haskell Type

data FixitySig pass #

Fixity Signature

Constructors

FixitySig (XFixitySig pass) [LIdP pass] Fixity 

Instances

Instances details
type Anno (FixitySig (GhcPass p)) 
Instance details

Defined in GHC.Hs.Binds

data Sig pass #

Signatures and pragmas

Constructors

TypeSig (XTypeSig pass) [LIdP pass] (LHsSigWcType pass)

An ordinary type signature

f :: Num a => a -> a

After renaming, this list of Names contains the named wildcards brought into scope by this signature. For a signature _ -> _a -> Bool, the renamer will leave the unnamed wildcard _ untouched, and the named wildcard _a is then replaced with fresh meta vars in the type. Their names are stored in the type signature that brought them into scope, in this third field to be more specific.

FixSig (XFixSig pass) (FixitySig pass)

An ordinary fixity declaration

    infixl 8 ***
InlineSig (XInlineSig pass) (LIdP pass) InlinePragma

An inline pragma

{#- INLINE f #-}

Instances

Instances details
type Anno (Sig (GhcPass p)) 
Instance details

Defined in GHC.Hs.Binds

data HsDecl p #

A Haskell Declaration

Constructors

SigD (XSigD p) (Sig p)

Signature declaration

Instances

Instances details
type Anno (HsDecl (GhcPass _1)) 
Instance details

Defined in GHC.Hs.Decls

type LHsDecl p #

Arguments

 = XRec p (HsDecl p)

When in a list this may have

data HsModule p #

Haskell Module

All we actually declare here is the top-level structure for a module.

type CoreAlt = Alt CoreBndr #

Case alternatives where binders are CoreBndrs

type CoreBind = Bind CoreBndr #

Binding groups where binders are CoreBndrs

type CoreArg = Arg CoreBndr #

Argument expressions where binders are CoreBndrs

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

DFunUnfolding [Var] DataCon [CoreExpr] 
CoreUnfolding CoreExpr UnfoldingSource Bool UnfoldingCache UnfoldingGuidance

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

data Bind b #

Binding, used for top level bindings in a module and local bindings in a let.

Constructors

NonRec b (Expr b) 
Rec [(b, Expr b)] 

Instances

Instances details
CBVisitable CoreBind Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Visitors

Data b => Data (Bind b) 
Instance details

Defined in GHC.Core

Methods

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

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

toConstr :: Bind b -> Constr #

dataTypeOf :: Bind b -> DataType #

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

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

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

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

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

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

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

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

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

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

PPrint (Bind Var) Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.PrettyPrint

Methods

pprintTidy :: Tidy -> Bind Var -> Doc #

pprintPrec :: Int -> Tidy -> Bind Var -> Doc #

Subable (Bind Var) Source # 
Instance details

Defined in Language.Haskell.Liquid.GHC.Play

CBVisitable [CoreBind] Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Visitors

data AltCon #

A case alternative constructor (i.e. pattern match)

Constructors

DataAlt DataCon 
LitAlt Literal

A literal: case e of { 1 -> ... } Invariant: always an *unlifted* literal See Note [Literal alternatives]

DEFAULT

Trivial alternative: case e of { _ -> ... }

Instances

Instances details
Data AltCon 
Instance details

Defined in GHC.Core

Methods

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

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

toConstr :: AltCon -> Constr #

dataTypeOf :: AltCon -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable AltCon 
Instance details

Defined in GHC.Core

Methods

ppr :: AltCon -> SDoc #

Eq AltCon 
Instance details

Defined in GHC.Core

Methods

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

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

Ord AltCon 
Instance details

Defined in GHC.Core

CBVisitable AltCon Source # 
Instance details

Defined in Language.Haskell.Liquid.Types.Visitors

data Reduction #

A Reduction is the result of an operation that rewrites a type ty_in. The Reduction includes the rewritten type ty_out and a Coercion co such that co :: ty_in ~ ty_out, where the role of the coercion is determined by the context. That is, the LHS type of the coercion is the original type ty_in, while its RHS type is the rewritten type ty_out.

A Reduction is always homogeneous, unless it is wrapped inside a HetReduction, which separately stores the kind coercion.

See Note [The Reduction type].

Constructors

Reduction Coercion !Type 

Instances

Instances details
Outputable Reduction 
Instance details

Defined in GHC.Core.Reduction

Methods

ppr :: Reduction -> SDoc #

data CafInfo #

Constant applicative form Information

Records whether an Id makes Constant Applicative Form references

Constructors

NoCafRefs

A function or static constructor that refers to no CAFs.

Instances

Instances details
Outputable CafInfo 
Instance details

Defined in GHC.Types.Id.Info

Methods

ppr :: CafInfo -> SDoc #

Eq CafInfo 
Instance details

Defined in GHC.Types.Id.Info

Methods

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

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

Ord CafInfo 
Instance details

Defined in GHC.Types.Id.Info

data FamInstEnv #

Instances

Instances details
Outputable FamInstEnv 
Instance details

Defined in GHC.Core.FamInstEnv

Methods

ppr :: FamInstEnv -> SDoc #

data FamFlavor #

Constructors

DataFamilyInst TyCon 

data FamInst #

Instances

Instances details
NamedThing FamInst 
Instance details

Defined in GHC.Core.FamInstEnv

Outputable FamInst 
Instance details

Defined in GHC.Core.FamInstEnv

Methods

ppr :: FamInst -> SDoc #

data IfaceAnnotation #

Instances

Instances details
NFData IfaceAnnotation 
Instance details

Defined in GHC.Iface.Syntax

Methods

rnf :: IfaceAnnotation -> () #

Binary IfaceAnnotation 
Instance details

Defined in GHC.Iface.Syntax

Outputable IfaceAnnotation 
Instance details

Defined in GHC.Iface.Syntax

Methods

ppr :: IfaceAnnotation -> SDoc #

data GhcLink #

What to do in the link step, if there is one.

Constructors

LinkInMemory

Use the in-memory dynamic linker (works for both bytecode and object code).

Instances

data TcEvBinds #

Constructors

EvBinds (Bag EvBind) 

Instances

Instances details
Data TcEvBinds 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

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

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

toConstr :: TcEvBinds -> Constr #

dataTypeOf :: TcEvBinds -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable TcEvBinds 
Instance details

Defined in GHC.Tc.Types.Evidence

Methods

ppr :: TcEvBinds -> SDoc #

data ClsInst #

A type-class instance. Note that there is some tricky laziness at work here. See Note [ClsInst laziness and the rough-match fields] for more details.

Instances

Instances details
Data ClsInst 
Instance details

Defined in GHC.Core.InstEnv

Methods

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

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

toConstr :: ClsInst -> Constr #

dataTypeOf :: ClsInst -> DataType #

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

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

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

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

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

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

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

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

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

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

NamedThing ClsInst 
Instance details

Defined in GHC.Core.InstEnv

Outputable ClsInst 
Instance details

Defined in GHC.Core.InstEnv

Methods

ppr :: ClsInst -> SDoc #

data FindResult #

The result of searching for an imported module.

NB: FindResult manages both user source-import lookups (which can result in GenModule) as well as direct imports for interfaces (which always result in InstalledModule).

Constructors

Found ModLocation Module

The module was found

NoPackage Unit

The requested unit was not found

FoundMultiple [(Module, ModuleOrigin)]

_Error_: both in multiple packages

NotFound [FilePath] (Maybe Unit) [Unit] [Unit] [(Unit, UnusableUnitReason)] [ModuleSuggestion]

Not found

data ModGuts #

A ModGuts is carried through the compiler, accumulating stuff as it goes There is only one ModGuts at any time, the one for the module being compiled right now. Once it is compiled, a ModIface and ModDetails are extracted and the ModGuts is discarded.

data ModIface_ (phase :: ModIfacePhase) #

A ModIface plus a ModDetails summarises everything we know about a compiled module. The ModIface is the stuff *before* linking, and can be written out to an interface file. The 'ModDetails is after linking and can be completely recovered from just the ModIface.

When we read an interface file, we also construct a ModIface from it, except that we explicitly make the mi_decls and a few other fields empty; as when reading we consolidate the declarations etc. into a number of indexed maps and environments in the ExternalPackageState.

See Note [Strictness in ModIface] to learn about why some fields are strict and others are not.

Instances

Instances details
Binary ModIface 
Instance details

Defined in GHC.Unit.Module.ModIface

(NFData (IfaceBackendExts phase), NFData (IfaceDeclExts phase)) => NFData (ModIface_ phase) 
Instance details

Defined in GHC.Unit.Module.ModIface

Methods

rnf :: ModIface_ phase -> () #

data ExternalPackageState #

Information about other packages that we have slurped in by reading their interface files

data ExternalUnitCache #

Information about the currently loaded external packages. This is mutable because packages will be demand-loaded during a compilation run as required.

type HomePackageTable = DModuleNameEnv HomeModInfo #

Helps us find information about modules in the home package

data HomeModInfo #

Information about modules in the package being compiled

data UnitEnv #

data ModSummary #

Data for a module node in a ModuleGraph. Module nodes of the module graph are one of:

  • A regular Haskell source module
  • A hi-boot source module

Instances

Instances details
Outputable ModSummary 
Instance details

Defined in GHC.Unit.Module.ModSummary

Methods

ppr :: ModSummary -> SDoc #

data HscEnv #

HscEnv is like Session, except that some of the fields are immutable. An HscEnv is used to compile a single module from plain Haskell source code (after preprocessing) to either C, assembly or C--. It's also used to store the dynamic linker state to allow for multiple linkers in the same address space. Things like the module graph don't change during a single compilation.

Historical note: "hsc" used to be the name of the compiler binary, when there was a separate driver and compiler. To compile a single module, the driver would invoke hsc on the source code... so nowadays we think of hsc as the layer of the compiler that deals with compiling a single module.

Instances

Instances details
ContainsDynFlags HscEnv 
Instance details

Defined in GHC.Driver.Env.Types

data Ghc a #

A minimal implementation of a GhcMonad. If you need a custom monad, e.g., to maintain additional state consider wrapping this monad or using GhcT.

Instances

Instances details
MonadFail Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

fail :: String -> Ghc a #

MonadFix Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

mfix :: (a -> Ghc a) -> Ghc a #

MonadIO Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

liftIO :: IO a -> Ghc a #

Applicative Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

pure :: a -> Ghc a #

(<*>) :: Ghc (a -> b) -> Ghc a -> Ghc b #

liftA2 :: (a -> b -> c) -> Ghc a -> Ghc b -> Ghc c #

(*>) :: Ghc a -> Ghc b -> Ghc b #

(<*) :: Ghc a -> Ghc b -> Ghc a #

Functor Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

Monad Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

(>>=) :: Ghc a -> (a -> Ghc b) -> Ghc b #

(>>) :: Ghc a -> Ghc b -> Ghc b #

return :: a -> Ghc a #

MonadCatch Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

catch :: (HasCallStack, Exception e) => Ghc a -> (e -> Ghc a) -> Ghc a #

MonadMask Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

mask :: HasCallStack => ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b #

uninterruptibleMask :: HasCallStack => ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b #

generalBracket :: HasCallStack => Ghc a -> (a -> ExitCase b -> Ghc c) -> (a -> Ghc b) -> Ghc (b, c) #

MonadThrow Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

throwM :: (HasCallStack, Exception e) => e -> Ghc a #

GhcMonad Ghc 
Instance details

Defined in GHC.Driver.Monad

HasDynFlags Ghc 
Instance details

Defined in GHC.Driver.Monad

HasLogger Ghc 
Instance details

Defined in GHC.Driver.Monad

Methods

getLogger :: Ghc Logger #

data WhereFrom #

Constructors

ImportBySystem 

Instances

Instances details
Outputable WhereFrom 
Instance details

Defined in GHC.Tc.Types

Methods

ppr :: WhereFrom -> SDoc #

type TcM = TcRn #

Historical "type-checking monad" (now it's just TcRn).

type CommandLineOption = String #

Command line options gathered from the -PModule.Name:stuff syntax are given to you as this type

type DsM = TcRnIf DsGblEnv DsLclEnv #

Desugaring monad. See also TcM.

data InferMode #

How should we choose which constraints to quantify over?

Constructors

NoRestrictions

Quantify over any constraint that satisfies pickQuantifiablePreds

Instances

Instances details
Outputable InferMode 
Instance details

Defined in GHC.Tc.Solver

Methods

ppr :: InferMode -> SDoc #

data DesugaredModule #

The result of successful desugaring (i.e., translation to core). Also contains all the information of a typechecked module.

data TypecheckedModule #

The result of successful typechecking. It also contains the parser result.

data ParsedModule #

The result of successful parsing.

Instances

Instances details
ParsedMod ParsedModule 
Instance details

Defined in GHC

data StableModule Source #

A newtype wrapper around a Module which:

  • Allows a Module to be serialised (i.e. it has a Binary instance)
  • It tries to use stable comparison and equality under the hood.

Instances

Instances details
Generic StableModule Source # 
Instance details

Defined in Liquid.GHC.API.StableModule

Associated Types

type Rep StableModule :: Type -> Type #

Show StableModule Source # 
Instance details

Defined in Liquid.GHC.API.StableModule

Binary StableModule Source # 
Instance details

Defined in Liquid.GHC.API.StableModule

Eq StableModule Source # 
Instance details

Defined in Liquid.GHC.API.StableModule

Ord StableModule Source # 
Instance details

Defined in Liquid.GHC.API.StableModule

Hashable StableModule Source # 
Instance details

Defined in Liquid.GHC.API.StableModule

type Rep StableModule Source # 
Instance details

Defined in Liquid.GHC.API.StableModule

type Rep StableModule = D1 ('MetaData "StableModule" "Liquid.GHC.API.StableModule" "liquidhaskell-boot-0.9.6.3-9A5uxmIRMTwLbbjDHLeYgP" 'True) (C1 ('MetaCons "StableModule" 'PrefixI 'True) (S1 ('MetaSel ('Just "unStableModule") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Module)))

data ApiComment Source #

Abstraction of EpaComment.

Instances

Instances details
Show ApiComment Source # 
Instance details

Defined in Liquid.GHC.API.Extra

Eq ApiComment Source # 
Instance details

Defined in Liquid.GHC.API.Extra

pattern ManyTy :: Mult #

space :: IsLine doc => doc #

comma :: IsLine doc => doc #

colon :: IsLine doc => doc #

int :: IsLine doc => Int -> doc #

integer :: IsLine doc => Integer -> doc #

float :: IsLine doc => Float -> doc #

double :: IsLine doc => Double -> doc #

isTyVar :: Var -> Bool #

Is this a type-level (i.e., computationally irrelevant, thus erasable) variable? Satisfies isTyVar = not . isId.

liftIO :: MonadIO m => IO a -> m a #

Lift a computation from the IO monad. This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations (i.e. IO is the base monad for the stack).

Example

Expand
import Control.Monad.Trans.State -- from the "transformers" library

printState :: Show s => StateT s IO ()
printState = do
  state <- get
  liftIO $ print state

Had we omitted liftIO, we would have ended up with this error:

• Couldn't match type ‘IO’ with ‘StateT s IO’
 Expected type: StateT s IO ()
   Actual type: IO ()

The important part here is the mismatch between StateT s IO () and IO ().

Luckily, we know of a function that takes an IO a and returns an (m a): liftIO, enabling us to run the program and see the expected results:

> evalStateT printState "hello"
"hello"

> evalStateT printState 3
3

getEnv :: IOEnv env env #

srcLocFile :: RealSrcLoc -> FastString #

Gives the filename of the RealSrcLoc

parens :: IsLine doc => doc -> doc #

moduleName :: GenModule unit -> ModuleName #

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

moduleUnit :: GenModule unit -> unit #

Unit the module belongs to

mkFunTy :: HasDebugCallStack => FunTyFlag -> Mult -> Type -> Type -> Type infixr 3 #

splitTyConApp :: Type -> (TyCon, [Type]) #

Attempts to tease a type apart into a type constructor and the application of a number of arguments to that constructor. Panics if that is not possible. See also splitTyConApp_maybe

mkCoreApps infixl 4 #

Arguments

:: CoreExpr

function

-> [CoreExpr]

arguments

-> CoreExpr 

Construct an expression which represents the application of a number of expressions to another. The leftmost expression in the list is applied first

mkCoreConApps :: DataCon -> [CoreExpr] -> CoreExpr #

Construct an expression which represents the application of a number of expressions to that of a data constructor expression. The leftmost expression in the list is applied first

mkCoreLams :: [CoreBndr] -> CoreExpr -> CoreExpr #

Create a lambda where the given expression has a number of variables bound over it. The leftmost binder is that bound by the outermost lambda in the result

mkCoreLets :: [CoreBind] -> CoreExpr -> CoreExpr #

Bind a list of binding groups over an expression. The leftmost binding group becomes the outermost group in the resulting expression

expandTypeSynonyms :: Type -> Type #

Expand out all type synonyms. Actually, it'd suffice to expand out just the ones that discard type variables (e.g. type Funny a = Int) But we don't know which those are currently, so we just expand all.

expandTypeSynonyms only expands out type synonyms mentioned in the type, not in the kinds of any TyCon or TyVar mentioned in the type.

Keep this synchronized with synonymTyConsOfType

panic :: HasCallStack => String -> a #

Panics and asserts.

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

mkFastString :: String -> FastString #

Creates a UTF-8 encoded FastString from a String

unpackFS :: FastString -> String #

Lazily unpacks and decodes the FastString

mkPtrString# :: Addr# -> PtrString #

Wrap an unboxed address into a PtrString.

semi :: IsLine doc => doc #

equals :: IsLine doc => doc #

lparen :: IsLine doc => doc #

rparen :: IsLine doc => doc #

lbrack :: IsLine doc => doc #

rbrack :: IsLine doc => doc #

lbrace :: IsLine doc => doc #

rbrace :: IsLine doc => doc #

doubleQuotes :: IsLine doc => doc -> doc #

brackets :: IsLine doc => doc -> doc #

braces :: IsLine doc => doc -> doc #

nest :: Int -> SDoc -> SDoc #

Indent SDoc some specified amount

hang #

Arguments

:: SDoc

The header

-> Int

Amount to indent the hung body

-> SDoc

The hung body, indented and placed below the header

-> SDoc 

hangNotEmpty :: SDoc -> Int -> SDoc -> SDoc #

This behaves like hang, but does not indent the second document when the header is empty.

punctuate #

Arguments

:: IsLine doc 
=> doc

The punctuation

-> [doc]

The list that will have punctuation added between every adjacent pair of elements

-> [doc]

Punctuated list

($+$) :: SDoc -> SDoc -> SDoc #

Join two SDoc together vertically

cat :: [SDoc] -> SDoc #

A paragraph-fill combinator. It's much like sep, only it keeps fitting things on one line until it can't fit any more.

fcat :: [SDoc] -> SDoc #

This behaves like fsep, but it uses <> for horizontal composition rather than <+>

noExtField :: NoExtField #

Used when constructing a term with an unused extension point.

alwaysQualifyNames :: QueryQualifyName #

NB: This won't ever show package IDs

defaultErrStyle :: PprStyle #

Default style for error messages, when we don't know NamePprCtx It's a bit of a hack because it doesn't take into account what's in scope Only used for desugarer warnings, and typechecker errors in interface sigs

mkErrStyle :: NamePprCtx -> PprStyle #

Style for printing error messages

defaultSDocContext :: SDocContext #

Default pretty-printing options

pprDeeperList :: ([SDoc] -> SDoc) -> [SDoc] -> SDoc #

Truncate a list that is longer than the current depth.

sdocOption :: (SDocContext -> a) -> (a -> SDoc) -> SDoc #

getPprDebug :: IsOutput doc => (Bool -> doc) -> doc #

Indicate if -dppr-debug mode is enabled

ifPprDebug :: IsOutput doc => doc -> doc -> doc #

Says what to do with and without -dppr-debug

whenPprDebug :: IsOutput doc => doc -> doc #

Says what to do with -dppr-debug; without, return empty

printSDoc :: SDocContext -> Mode -> Handle -> SDoc -> IO () #

The analog of printDoc_ for SDoc, which tries to make sure the terminal doesn't get screwed up by the ANSI color codes if an exception is thrown during pretty-printing.

printSDocLn :: SDocContext -> Mode -> Handle -> SDoc -> IO () #

Like printSDoc but appends an extra newline.

bufLeftRenderSDoc :: SDocContext -> BufHandle -> SDoc -> IO () #

An efficient variant of printSDoc specialized for LeftMode that outputs to a BufHandle.

pprDebugAndThen :: SDocContext -> (String -> a) -> SDoc -> SDoc -> a #

doublePrec :: Int -> Double -> SDoc #

doublePrec p n shows a floating point number n with p digits of precision after the decimal point.

angleBrackets :: IsLine doc => doc -> doc #

cparen :: Bool -> SDoc -> SDoc #

underscore :: IsLine doc => doc #

dot :: IsLine doc => doc #

vbar :: IsLine doc => doc #

ppWhen :: IsOutput doc => Bool -> doc -> doc #

ppUnless :: IsOutput doc => Bool -> doc -> doc #

ppUnlessOption :: IsLine doc => (SDocContext -> Bool) -> doc -> doc #

coloured :: PprColour -> SDoc -> SDoc #

Apply the given colour/style for the argument.

Only takes effect if colours are enabled.

pprModuleName :: IsLine doc => ModuleName -> doc #

pprHsChar :: Char -> SDoc #

Special combinator for showing character literals.

pprHsString :: FastString -> SDoc #

Special combinator for showing string literals.

pprHsBytes :: ByteString -> SDoc #

Special combinator for showing bytestring literals.

pprPrimChar :: Char -> SDoc #

Special combinator for showing unboxed literals.

pprFilePathString :: IsLine doc => FilePath -> doc #

Normalise, escape and render a string representing a path

e.g. "c:\whatever"

pprWithCommas #

Arguments

:: (a -> SDoc)

The pretty printing function to use

-> [a]

The things to be pretty printed

-> SDoc

SDoc where the things have been pretty printed, comma-separated and finally packed into a paragraph.

pprWithBars #

Arguments

:: (a -> SDoc)

The pretty printing function to use

-> [a]

The things to be pretty printed

-> SDoc

SDoc where the things have been pretty printed, bar-separated and finally packed into a paragraph.

interppSP :: Outputable a => [a] -> SDoc #

Returns the separated concatenation of the pretty printed things.

interpp'SP :: Outputable a => [a] -> SDoc #

Returns the comma-separated concatenation of the pretty printed things.

interpp'SP' :: (a -> SDoc) -> [a] -> SDoc #

pprQuotedList :: Outputable a => [a] -> SDoc #

Returns the comma-separated concatenation of the quoted pretty printed things.

[x,y,z]  ==>  `x', `y', `z'

speakNth :: Int -> SDoc #

Converts an integer to a verbal index:

speakNth 1 = text "first"
speakNth 5 = text "fifth"
speakNth 21 = text "21st"

speakN :: Int -> SDoc #

Converts an integer to a verbal multiplicity:

speakN 0 = text "none"
speakN 5 = text "five"
speakN 10 = text "10"

speakNOf :: Int -> SDoc -> SDoc #

Converts an integer and object description to a statement about the multiplicity of those objects:

speakNOf 0 (text "melon") = text "no melons"
speakNOf 1 (text "melon") = text "one melon"
speakNOf 3 (text "melon") = text "three melons"

plural :: [a] -> SDoc #

Determines the pluralisation suffix appropriate for the length of a list:

plural [] = char 's'
plural ["Hello"] = empty
plural ["Hello", "World"] = char 's'

singular :: [a] -> SDoc #

Determines the singular verb suffix appropriate for the length of a list:

singular [] = empty
singular["Hello"] = char 's'
singular ["Hello", "World"] = empty

isOrAre :: [a] -> SDoc #

Determines the form of to be appropriate for the length of a list:

isOrAre [] = text "are"
isOrAre ["Hello"] = text "is"
isOrAre ["Hello", "World"] = text "are"

doOrDoes :: [a] -> SDoc #

Determines the form of to do appropriate for the length of a list:

doOrDoes [] = text "do"
doOrDoes ["Hello"] = text "does"
doOrDoes ["Hello", "World"] = text "do"

itsOrTheir :: [a] -> SDoc #

Determines the form of possessive appropriate for the length of a list:

itsOrTheir [x]   = text "its"
itsOrTheir [x,y] = text "their"
itsOrTheir []    = text "their"  -- probably avoid this

thisOrThese :: [a] -> SDoc #

Determines the form of subject appropriate for the length of a list:

thisOrThese [x]   = text "This"
thisOrThese [x,y] = text "These"
thisOrThese []    = text "These"  -- probably avoid this

hasOrHave :: [a] -> SDoc #

"has" or "have" depending on the length of a list.

vanillaIdInfo :: IdInfo #

Basic IdInfo that carries no useful information whatsoever

hasKey :: Uniquable a => a -> Unique -> Bool #

isTupleTyCon :: TyCon -> Bool #

Does this TyCon represent a tuple?

NB: when compiling Data.Tuple, the tycons won't reply True to isTupleTyCon, because they are built as AlgTyCons. However they get spat into the interface file as tuple tycons, so I don't think it matters.

srcLocLine :: RealSrcLoc -> Int #

Raises an error when used on a "bad" RealSrcLoc

srcLocCol :: RealSrcLoc -> Int #

Raises an error when used on a "bad" RealSrcLoc

noSrcSpan :: SrcSpan #

Built-in "bad" SrcSpans for common sources of location uncertainty

mkGeneralSrcSpan :: FastString -> SrcSpan #

Create a "bad" SrcSpan that has not location information

mkRealSrcSpan :: RealSrcLoc -> RealSrcLoc -> RealSrcSpan #

Create a SrcSpan between two points in a file

mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan #

Create a SrcSpan between two points in a file

combineSrcSpans :: SrcSpan -> SrcSpan -> SrcSpan #

Combines two SrcSpan into one that spans at least all the characters within both spans. Returns UnhelpfulSpan if the files differ.

isGoodSrcSpan :: SrcSpan -> Bool #

Test if a SrcSpan is "good", i.e. has precise location information

srcSpanFileName_maybe :: SrcSpan -> Maybe FastString #

Obtains the filename for a SrcSpan if it is "good"

unLoc :: GenLocated l e -> e #

mkUniqSet :: Uniquable a => [a] -> UniqSet a #

bagToList :: Bag a -> [a] #

fsToUnit :: FastString -> Unit #

Create a new simple unit identifier from a FastString. Internally, this is primarily used to specify wired-in unit identifiers.

toUnitId :: Unit -> UnitId #

Return the UnitId of the Unit. For on-the-fly instantiated units, return the UnitId of the indefinite unit this unit is an instance of.

moduleStableString :: Module -> String #

Get a string representation of a GenModule that's unique and stable across recompilations. eg. "$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal"

dataConWrapId :: DataCon -> Id #

Returns an Id which looks like the Haskell-source constructor by using the wrapper if it exists (see dataConWrapId_maybe) and failing over to the worker (see dataConWorkId)

dataConFullSig :: DataCon -> ([TyVar], [TyCoVar], [EqSpec], ThetaType, [Scaled Type], Type) #

The "full signature" of the DataCon returns, in order:

1) The result of dataConUnivTyVars

2) The result of dataConExTyCoVars

3) The non-dependent GADT equalities. Dependent GADT equalities are implied by coercion variables in return value (2).

4) The other constraints of the data constructor type, excluding GADT equalities

5) The original argument types to the DataCon (i.e. before any change of the representation of the type) with linearity annotations

6) The original result type of the DataCon

dataConFieldLabels :: DataCon -> [FieldLabel] #

The labels for the fields of this particular DataCon

dataConExTyCoVars :: DataCon -> [TyCoVar] #

The existentially-quantified type/coercion variables of the constructor including dependent (kind-) GADT equalities

dataConTyCon :: DataCon -> TyCon #

The type constructor that we are building via this data constructor

dataConWorkId :: DataCon -> Id #

Get the Id of the DataCon worker: a function that is the "actual" constructor and has no top level binding in the program. The type may be different from the obvious one written in the source program. Panics if there is no such Id for this DataCon

dataConName :: DataCon -> Name #

The Name of the DataCon, giving it a unique, rooted identification

mkInternalName :: Unique -> OccName -> SrcSpan -> Name #

Create a name which is (for now at least) local to the current module and hence does not need a GenModule to disambiguate it from other Names

mkSystemName :: Unique -> OccName -> Name #

Create a name brought into being by the compiler

stableNameCmp :: Name -> Name -> Ordering #

Compare Names lexicographically This only works for Names that originate in the source code or have been tidied.

nameStableString :: Name -> String #

Get a string representation of a Name that's unique and stable across recompilations. Used for deterministic generation of binds for derived instances. eg. "$aeson_70dylHtv1FFGeai1IoxcQr$Data.Aeson.Types.Internal$String"

binderVar :: VarBndr tv argf -> tv #

isId :: Var -> Bool #

Is this a value-level (i.e., computationally relevant) Varentifier? Satisfies isId = not . isTyVar.

isCoVar :: Var -> Bool #

Is this a coercion variable? Satisfies isId v ==> isCoVar v == not (isNonCoVarId v).

tyConAppTyCon_maybe :: Type -> Maybe TyCon #

The same as fst . splitTyConApp We can short-cut the FunTy case

splitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type]) #

Attempts to tease a type apart into a type constructor and the application of a number of arguments to that constructor

mkTyConApp :: TyCon -> [Type] -> Type #

A key function: builds a TyConApp or FunTy as appropriate to its arguments. Applies its arguments to the constructor from left to right.

availNames :: AvailInfo -> [Name] #

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

greNameMangledName :: GreName -> Name #

A Name for internal use, but not for output to the user. For fields, the OccName will be the selector. See Note [GreNames] in GHC.Types.Name.Reader.

mkQual :: NameSpace -> (FastString, FastString) -> RdrName #

Make a qualified RdrName in the given namespace and where the ModuleName and the OccName are taken from the first and second elements of the tuple respectively

getRdrName :: NamedThing thing => thing -> RdrName #

gresFromAvails :: Maybe ImportSpec -> [AvailInfo] -> [GlobalRdrElt] #

make a GlobalRdrEnv where all the elements point to the same Provenance (useful for "hiding" imports, or imports with no details).

greMangledName :: GlobalRdrElt -> Name #

A Name for the GRE for internal use. Careful: the OccName of this Name is not necessarily the same as the greOccName (see Note [GreNames]).

lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt] #

Look for this RdrName in the global environment. Omits record fields without selector functions (see Note [NoFieldSelectors] in GHC.Rename.Env).

noLocA :: a -> LocatedAn an a #

noAnn :: EpAnn a #

Short form for EpAnnNotUsed

ideclName :: ImportDecl pass -> XRec pass ModuleName #

Module name.

ideclAs :: ImportDecl pass -> Maybe (XRec pass ModuleName) #

as Module

findAnns :: Typeable a => ([Word8] -> a) -> AnnEnv -> CoreAnnTarget -> [a] #

Find the annotations attached to the given target as Typeable values of your choice. If no deserializer is specified, only transient annotations will be returned.

coAxiomTyCon :: forall (br :: BranchFlag). CoAxiom br -> TyCon #

coercionKind :: Coercion -> Pair Type #

If it is the case that

c :: (t1 ~ t2)

i.e. the kind of c relates t1 and t2, then coercionKind c = Pair t1 t2.

mkPrimTyCon #

Arguments

:: Name 
-> [TyConBinder] 
-> Kind

result kind Must answer True to isFixedRuntimeRepKind (i.e., no representation polymorphism). (If you need a representation-polymorphic PrimTyCon, change tcHasFixedRuntimeRep, marshalablePrimTyCon, reifyTyCon for PrimTyCons.)

-> [Role] 
-> TyCon 

Create an primitive TyCon, such as Int#, Type or RealWorld# Primitive TyCons are marshalable iff not lifted. If you'd like to change this, modify marshalablePrimTyCon.

isPrimTyCon :: TyCon -> Bool #

Does this TyCon represent something that cannot be defined in Haskell?

isAlgTyCon :: TyCon -> Bool #

Returns True if the supplied TyCon resulted from either a data or newtype declaration

isVanillaAlgTyCon :: TyCon -> Bool #

Returns True for vanilla AlgTyCons -- that is, those created with a data or newtype declaration.

isNewTyCon :: TyCon -> Bool #

Is this TyCon that for a newtype

isTypeSynonymTyCon :: TyCon -> Bool #

Is this a TyCon representing a regular H98 type synonym (type)?

isGadtSyntaxTyCon :: TyCon -> Bool #

Is this an algebraic TyCon declared with the GADT syntax?

isFamilyTyCon :: TyCon -> Bool #

Is this a TyCon, synonym or otherwise, that defines a family?

isBoxedTupleTyCon :: TyCon -> Bool #

Is this the TyCon for a boxed tuple?

isPromotedDataCon :: TyCon -> Bool #

Is this a PromotedDataCon?

tyConDataCons :: TyCon -> [DataCon] #

As tyConDataCons_maybe, but returns the empty list of constructors if no constructors could be found

tyConDataCons_maybe :: TyCon -> Maybe [DataCon] #

Determine the DataCons originating from the given TyCon, if the TyCon is the sort that can have any constructors (note: this does not include abstract algebraic types)

tyConSingleDataCon_maybe :: TyCon -> Maybe DataCon #

If the given TyCon has a single data constructor, i.e. it is a data type with one alternative, a tuple type or a newtype then that constructor is returned. If the TyCon has more than one constructor, or represents a primitive or function type constructor then Nothing is returned.

newTyConRhs :: TyCon -> ([TyVar], Type) #

Extract the bound type variables and type expansion of a type synonym TyCon. Panics if the TyCon is not a synonym

synTyConDefn_maybe :: TyCon -> Maybe ([TyVar], Type) #

Extract the TyVars bound by a vanilla type synonym and the corresponding (unsubstituted) right hand side.

synTyConRhs_maybe :: TyCon -> Maybe Type #

Extract the information pertaining to the right hand side of a type synonym (type) declaration.

isClassTyCon :: TyCon -> Bool #

Is this TyCon that for a class instance?

tyConClass_maybe :: TyCon -> Maybe Class #

If this TyCon is that for a class instance, return the class it is for. Otherwise returns Nothing

isFamInstTyCon :: TyCon -> Bool #

Is this TyCon that for a data family instance?

tyConFamInst_maybe :: TyCon -> Maybe (TyCon, [Type]) #

If this TyCon is that of a data family instance, return the family in question and the instance types. Otherwise, return Nothing

mkForAllTys :: [ForAllTyBinder] -> Type -> Type #

Wraps foralls over the type using the provided TyCoVars from left to right

extendCvSubst :: Subst -> CoVar -> Coercion -> Subst #

Add a substitution from a CoVar to a Coercion to the Subst: you must ensure that the in-scope set satisfies Note [The substitution invariant] after extending the substitution like this

mkTvSubstPrs :: [(TyVar, Type)] -> Subst #

Generates the in-scope set for the TCvSubst from the types in the incoming environment. No CoVars, please! The InScopeSet is just a thunk so with a bit of luck it'll never be evaluated

substTyWith :: HasDebugCallStack => [TyVar] -> [Type] -> Type -> Type #

Type substitution, see zipTvSubst

substTy :: HasDebugCallStack => Subst -> Type -> Type #

Substitute within a Type The substitution has to satisfy the invariants described in Note [The substitution invariant].

splitAppTys :: Type -> (Type, [Type]) #

Recursively splits a type as far as is possible, leaving a residual type being applied to and the type arguments applied to it. Never fails, even if that means returning an empty list of type applications.

splitFunTy_maybe :: Type -> Maybe (FunTyFlag, Mult, Type, Type) #

Attempts to extract the multiplicity, argument and result types from a type

piResultTys :: HasDebugCallStack => Type -> [Type] -> Type #

(piResultTys f_ty [ty1, .., tyn]) gives the type of (f ty1 .. tyn) where f :: f_ty piResultTys is interesting because: 1. f_ty may have more for-alls than there are args 2. Less obviously, it may have fewer for-alls For case 2. think of: piResultTys (forall a.a) [forall b.b, Int] This really can happen, but only (I think) in situations involving undefined. For example: undefined :: forall a. a Term: undefined (forall b. b->b) Int This term should have type (Int -> Int), but notice that there are more type args than foralls in undefineds type.

tyConAppArgs_maybe :: Type -> Maybe [Type] #

The same as snd . splitTyConApp

newTyConInstRhs :: TyCon -> [Type] -> Type #

Unwrap one layer of newtype on a type constructor and its arguments, using an eta-reduced version of the newtype if possible. This requires tys to have at least newTyConInstArity tycon elements.

splitForAllTyCoVars :: Type -> ([TyCoVar], Type) #

Take a ForAllTy apart, returning the list of tycovars and the result type. This always succeeds, even if it returns only an empty list. Note that the result type returned may have free variables that were bound by a forall.

isFunTy :: Type -> Bool #

Is this a function?

dropForAlls :: Type -> Type #

Drops all ForAllTys

isTYPEorCONSTRAINT :: Kind -> Bool #

Does this classify a type allowed to have values? Responds True to things like *, TYPE Lifted, TYPE IntRep, TYPE v, Constraint.

True of a kind `TYPE _` or `CONSTRAINT _`

eqType :: Type -> Type -> Bool #

Type equality on source types. Does not look through newtypes, PredTypes or type families, but it does look through type synonyms. This first checks that the kinds of the types are equal and then checks whether the types are equal, ignoring casts and coercions. (The kind check is a recursive call, but since all kinds have type Type, there is no need to check the types of kinds.) See also Note [Non-trivial definitional equality] in GHC.Core.TyCo.Rep.

literalType :: Literal -> Type #

Find the Haskell Type the literal occupies

mkRepReflCo :: Type -> Coercion #

Make a representational reflexive coercion

mkPlainError :: [GhcHint] -> SDoc -> DiagnosticMessage #

Create an error DiagnosticMessage holding just a single SDoc

errorsOrFatalWarningsFound :: Messages e -> Bool #

Are there any errors or -Werror warnings here?

putLogMsg :: Logger -> LogAction #

Log something

withTiming #

Arguments

:: MonadIO m 
=> Logger 
-> SDoc

The name of the phase

-> (a -> ())

A function to force the result (often either const () or rnf)

-> m a

The body of the phase to be timed

-> m a 

Time a compilation phase.

When timings are enabled (e.g. with the -v2 flag), the allocations and CPU time used by the phase will be reported to stderr. Consider a typical usage: withTiming getDynFlags (text "simplify") force PrintTimings pass. When timings are enabled the following costs are included in the produced accounting,

  • The cost of executing pass to a result r in WHNF
  • The cost of evaluating force r to WHNF (e.g. ())

The choice of the force function depends upon the amount of forcing desired; the goal here is to ensure that the cost of evaluating the result is, to the greatest extent possible, included in the accounting provided by withTiming. Often the pass already sufficiently forces its result during construction; in this case const () is a reasonable choice. In other cases, it is necessary to evaluate the result to normal form, in which case something like Control.DeepSeq.rnf is appropriate.

To avoid adversely affecting compiler performance when timings are not requested, the result is only forced when timings are enabled.

See Note [withTiming] for more.

interpreterBackend :: Backend #

The ByteCode interpreter.

Produce ByteCode objects (BCO, see GHC.ByteCode) that can be interpreted. It is used by GHCi.

Currently some extensions are not supported (foreign primops).

See GHC.StgToByteCode

ruleMatchTyKiX #

Arguments

:: TyCoVarSet

template variables

-> RnEnv2 
-> TvSubstEnv

type substitution to extend

-> Type

Template

-> Type

Target

-> Maybe TvSubstEnv 

This one is called from the expression matcher, which already has a MatchEnv in hand

tcUnifyTy :: Type -> Type -> Maybe Subst #

Simple unification of two types; all type variables are bindable Precondition: the kinds are already equal

dataConRepType :: DataCon -> Type #

The representation type of the data constructor, i.e. the sort type that will represent values of this type at runtime

dataConUnivTyVars :: DataCon -> [TyVar] #

The universally-quantified type variables of the constructor

dataConTheta :: DataCon -> ThetaType #

The *full* constraints on the constructor type, including dependent GADT equalities.

dataConWrapId_maybe :: DataCon -> Maybe Id #

Get the Id of the DataCon wrapper: a function that wraps the "actual" constructor so it has the type visible in the source program: c.f. dataConWorkId. Returns Nothing if there is no wrapper, which occurs for an algebraic data constructor and also for a newtype (whose constructor is inlined compulsorily)

dataConImplicitTyThings :: DataCon -> [TyThing] #

Find all the Ids implicitly brought into scope by the data constructor. Currently, the union of the dataConWorkId and the dataConWrapId

dataConRepStrictness :: DataCon -> [StrictnessMark] #

Give the demands on the arguments of a Core constructor application (Con dc args)

dataConWrapperType :: DataCon -> Type #

The user-declared type of the data constructor in the nice-to-read form:

T :: forall a b. a -> b -> T [a]

rather than:

T :: forall a c. forall b. (c~[a]) => a -> b -> T c

The type variables are quantified in the order that the user wrote them. See Note [DataCon user type variable binders].

NB: If the constructor is part of a data instance, the result type mentions the family tycon, not the internal one.

dataConInstArgTys #

Arguments

:: DataCon

A datacon with no existentials or equality constraints However, it can have a dcTheta (notably it can be a class dictionary, with superclasses)

-> [Type]

Instantiated at these types

-> [Scaled Type] 

Finds the instantiated types of the arguments required to construct a DataCon representation NB: these INCLUDE any dictionary args but EXCLUDE the data-declaration context, which is discarded It's all post-flattening etc; this is a representation type

dataConOrigArgTys :: DataCon -> [Scaled Type] #

Returns the argument types of the wrapper, excluding all dictionary arguments and without substituting for any type variables

dataConRepArgTys :: DataCon -> [Scaled Type] #

Returns the arg types of the worker, including *all* non-dependent evidence, after any flattening has been done and without substituting for any type variables

isVanillaDataCon :: DataCon -> Bool #

Vanilla DataCons are those that are nice boring Haskell 98 constructors

maybeUnfoldingTemplate :: Unfolding -> Maybe CoreExpr #

Retrieves the template of an unfolding if possible maybeUnfoldingTemplate is used mainly when specialising, and we do want to specialise DFuns, so it's important to return a template for DFunUnfoldings

cmpAlt :: Alt a -> Alt a -> Ordering #

mkApps :: Expr b -> [Arg b] -> Expr b infixl 4 #

Apply a list of argument expressions to a function expression in a nested fashion. Prefer to use mkCoreApps if possible

mkTyApps :: Expr b -> [Type] -> Expr b infixl 4 #

Apply a list of type argument expressions to a function expression in a nested fashion

mkTyArg :: Type -> Expr b #

mkLams :: [b] -> Expr b -> Expr b #

Bind all supplied binders over an expression in a nested lambda expression. Prefer to use mkCoreLams if possible

bindersOf :: Bind b -> [b] #

Extract every variable by this group

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

collectBinders :: Expr b -> ([b], Expr b) #

We often want to strip off leading lambdas before getting down to business. Variants are collectTyBinders, collectValBinders, and collectTyAndValBinders

collectArgs :: Expr b -> (Expr b, [Arg b]) #

Takes a nested application expression and returns the function being applied and the arguments to which it is applied

isTypeArg :: Expr b -> Bool #

Returns True iff the expression is a Type expression at its top level. Note this does NOT include Coercions.

cafInfo :: IdInfo -> CafInfo #

Id CAF info

setOccInfo :: IdInfo -> OccInfo -> IdInfo infixl 1 #

setCafInfo :: IdInfo -> CafInfo -> IdInfo infixl 1 #

idType :: Id -> Kind #

mkExportedLocalId :: IdDetails -> Name -> Type -> Id #

Create a local Id that is marked as exported. This prevents things attached to it from being removed as dead code. See Note [Exported LocalIds]

mkUserLocal :: OccName -> Unique -> Mult -> Type -> SrcSpan -> Id #

Create a user local Id. These are local Ids (see GHC.Types.Var) with a name and location that the user might recognize

idDataCon :: Id -> DataCon #

Get from either the worker or the wrapper Id to the DataCon. Currently used only in the desugarer.

INVARIANT: idDataCon (dataConWrapId d) = d: remember, dataConWrapId can return either the wrapper or the worker

realIdUnfolding :: Id -> Unfolding #

Expose the unfolding if there is one, including for loop breakers

exprFreeVarsList :: CoreExpr -> [Var] #

Find all locally-defined free Ids or type variables in an expression returning a deterministically ordered list.

topNormaliseType_maybe :: FamInstEnvs -> Type -> Maybe Reduction #

Get rid of *outermost* (or toplevel) * type function redex * data family redex * newtypes returning an appropriate Representational coercion. Specifically, if topNormaliseType_maybe env ty = Just (co, ty') then (a) co :: ty ~R ty' (b) ty' is not a newtype, and is not a type-family or data-family redex

However, ty' can be something like (Maybe (F ty)), where (F ty) is a redex.

Always operates homogeneously: the returned type has the same kind as the original type, and the returned coercion is always homogeneous.

exprType :: HasDebugCallStack => CoreExpr -> Type #

Recover the type of a well-typed Core expression. Fails when applied to the actual Type expression as it cannot really be said to have a type

extendIdSubst :: Subst -> Id -> CoreExpr -> Subst #

Add a substitution for an Id to the Subst: you must ensure that the in-scope set is such that TyCoSubst Note [The substitution invariant] holds after extending the substitution like this

substExpr :: HasDebugCallStack => Subst -> CoreExpr -> CoreExpr #

substExpr applies a substitution to an entire CoreExpr. Remember, you may only apply the substitution once: See Note [Substitutions apply only once] in GHC.Core.TyCo.Subst

Do *not* attempt to short-cut in the case of an empty substitution! See Note [Extending the IdSubstEnv]

gopt :: GeneralFlag -> DynFlags -> Bool #

Test whether a GeneralFlag is set

Note that dynamicNow (i.e., dynamic objects built with `-dynamic-too`) always implicitly enables Opt_PIC, Opt_ExternalDynamicRefs, and disables Opt_SplitSections.

updOptLevel :: Int -> DynFlags -> DynFlags #

Sets the DynFlags to be appropriate to the optimisation level

showSDoc :: DynFlags -> SDoc -> String #

Show a SDoc as a String with the default user style

failM :: IOEnv env a #

mkHsApp :: forall (id :: Pass). LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) -> LHsExpr (GhcPass id) #

mkHsLam :: forall (p :: Pass). (IsPass p, XMG (GhcPass p) (LHsExpr (GhcPass p)) ~ Origin) => [LPat (GhcPass p)] -> LHsExpr (GhcPass p) -> LHsExpr (GhcPass p) #

nlHsVar :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> LHsExpr (GhcPass p) #

nlVarPat :: forall (p :: Pass) a. IsSrcSpanAnn p a => IdP (GhcPass p) -> LPat (GhcPass p) #

nlHsAppTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #

nlHsTyVar :: forall (p :: Pass) a. IsSrcSpanAnn p a => PromotionFlag -> IdP (GhcPass p) -> LHsType (GhcPass p) #

nlHsFunTy :: forall (p :: Pass). LHsType (GhcPass p) -> LHsType (GhcPass p) -> LHsType (GhcPass p) #

nlHsTyConApp :: forall (p :: Pass) a. IsSrcSpanAnn p a => PromotionFlag -> LexicalFixity -> IdP (GhcPass p) -> [LHsTypeArg (GhcPass p)] -> LHsType (GhcPass p) #

lexprCtOrigin :: LHsExpr GhcRn -> CtOrigin #

Extract a suitable CtOrigin from a HsExpr

initDiagOpts :: DynFlags -> DiagOpts #

Initialise the general configuration for printing diagnostic messages For example, this configuration controls things like whether warnings are treated like errors.

withSession :: GhcMonad m => (HscEnv -> m a) -> m a #

Call the argument with the current session.

defaultPlugin :: Plugin #

Default plugin: does nothing at all, except for marking that safe inference has failed unless -fplugin-trustworthy is passed. For compatibility reason you should base all your plugin definitions on this default value.

findImportedModule :: HscEnv -> ModuleName -> PkgQual -> IO FindResult #

Locate a module that was imported by the user. We have the module's name, and possibly a package name. Without a package name, this function will use the search path and the known exposed packages to find the module, if a package is specified then only that package is searched for the module.

discardConstraints :: TcM a -> TcM a #

Throw out any constraints emitted by the thing_inside

initIfaceTcRn :: IfG a -> TcRn a #

Run an IfG (top-level interface monad) computation inside an existing TcRn (typecheck-renaming monad) computation by initializing an IfGblEnv based on TcGblEnv.

initDsTc :: DsM a -> TcM (Messages DsMessage, Maybe a) #

Run a DsM action inside the TcM monad.

initDsWithModGuts :: HscEnv -> ModGuts -> DsM a -> IO (Messages DsMessage, Maybe a) #

Run a DsM action in the context of an existing ModGuts

dsLExpr :: LHsExpr GhcTc -> DsM CoreExpr #

Replace the body of the function with this block to test the hsExprType function in GHC.Tc.Utils.Zonk: putSrcSpanDs loc $ do { core_expr <- dsExpr e ; massertPpr (exprType core_expr eqType hsExprType e) (ppr e + dcolon + ppr (hsExprType e) $$ ppr core_expr + dcolon + ppr (exprType core_expr)) ; return core_expr }

renamePkgQual :: UnitEnv -> ModuleName -> Maybe FastString -> PkgQual #

Rename raw package imports

tcValBinds :: TopLevelFlag -> [(RecFlag, LHsBinds GhcRn)] -> [LSig GhcRn] -> TcM thing -> TcM ([(RecFlag, LHsBinds GhcTc)], thing) #

getModuleInterface :: HscEnv -> Module -> IO (Messages TcRnMessage, Maybe ModIface) #

ASSUMES that the module is either in the HomePackageTable or is a package module with an interface on disk. If neither of these is true, then the result will be an error indicating the interface could not be found.

hscDesugar :: HscEnv -> ModSummary -> TcGblEnv -> IO ModGuts #

Convert a typechecked module to Core

toSerialized :: Typeable a => (a -> [Word8]) -> a -> Serialized #

Put a Typeable value that we are able to actually turn into bytes into a Serialized value ready for deserialization later

fromSerialized :: Typeable a => ([Word8] -> a) -> Serialized -> Maybe a #

If the Serialized value contains something of the given type, then use the specified deserializer to return Just that. Otherwise return Nothing.

deserializeWithData :: Data a => [Word8] -> a #

Use a Data instance to implement a deserialization scheme dual to that of serializeWithData

apiComments :: ParsedModule -> [Located ApiComment] Source #

Extract top-level comments from a module.

desugarModuleIO :: HscEnv -> ModSummary -> TypecheckedModuleLH -> IO ModGuts Source #

Desugar a typechecked module.

isPatErrorAlt :: CoreAlt -> Bool Source #

Tells if a case alternative calls to patError

modInfoLookupNameIO :: HscEnv -> ModuleInfoLH -> Name -> IO (Maybe TyThing) Source #

moduleInfoTc :: HscEnv -> TcGblEnv -> IO ModuleInfoLH Source #

relevantModules :: ModuleGraph -> ModGuts -> Set Module Source #

The collection of dependencies and usages modules which are relevant for liquidHaskell

typecheckModuleIO :: HscEnv -> ParsedModule -> IO TypecheckedModuleLH Source #

mkStableModule :: UnitId -> ModuleName -> StableModule Source #

Creates a new StableModule out of a ModuleName and a UnitId.

toStableModule :: Module -> StableModule Source #

Converts a Module into a StableModule.