retrie-1.2.3: A powerful, easy-to-use codemodding tool for Haskell.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Retrie.GHC

Synopsis

Documentation

dLPat :: LPat (GhcPass p) -> Maybe (LPat (GhcPass p)) Source #

Only returns located pat if there is a genuine location available.

dLPatUnsafe :: LPat (GhcPass p) -> LPat (GhcPass p) Source #

Will always give a location, but it may be noSrcSpan.

uniqBag :: Uniquable a => [(a, b)] -> UniqFM a [b] Source #

module GHC.Hs

showSDoc :: DynFlags -> SDoc -> String #

Show a SDoc as a String with the default user style

data Levity #

Constructors

Lifted 
Unlifted 

Instances

Instances details
Outputable Levity 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Levity -> SDoc #

Eq Levity 
Instance details

Defined in GHC.Types.Basic

Methods

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

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

data ForeignSrcLang #

Foreign formats supported by GHC via TH

Constructors

LangC

C

LangCxx

C++

LangObjc

Objective C

LangObjcxx

Objective C++

LangAsm

Assembly language (.s)

LangJs

JavaScript

RawObject

Object (.o)

Instances

Instances details
Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang :: Type -> Type #

Show ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Eq ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

type Rep ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

type Rep ForeignSrcLang = D1 ('MetaData "ForeignSrcLang" "GHC.ForeignSrcLang.Type" "ghc-boot-th-9.6.3" 'False) ((C1 ('MetaCons "LangC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LangCxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LangObjc" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LangObjcxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LangAsm" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LangJs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RawObject" 'PrefixI 'False) (U1 :: Type -> Type))))

type ConTag = Int #

A *one-index* constructor tag

Type of the tags associated with each constructor possibility or superclass selector

data Boxity #

Constructors

Boxed 
Unboxed 

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 #

data PromotionFlag #

Is a TyCon a promoted data constructor or just a normal type constructor?

Constructors

NotPromoted 
IsPromoted 

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

Specify whether to default kind variables, and type variables of kind RuntimeRepLevityMultiplicity.

Constructors

DefaultKindVars

Default kind variables:

  • default kind variables of kind Type to Type,
  • default RuntimeRepLevityMultiplicity kind variables to LiftedRepLiftedMany, respectively.

When this strategy is used, it means that we have determined that the variables we are considering defaulting are all kind variables.

Usually, we pass this option when -XNoPolyKinds is enabled.

NonStandardDefaulting NonStandardDefaultingStrategy

Default (or don't default) non-standard variables, of kinds RuntimeRep, Levity and Multiplicity.

Instances

Instances details
Outputable DefaultingStrategy 
Instance details

Defined in GHC.Types.Basic

data NonStandardDefaultingStrategy #

Specify whether to default type variables of kind RuntimeRepLevityMultiplicity.

Constructors

DefaultNonStandardTyVars

Default type variables of the given kinds:

  • default RuntimeRep variables to LiftedRep
  • default Levity variables to Lifted
  • default Multiplicity variables to Many
TryNotToDefaultNonStandardTyVars

Try not to default type variables of the kinds RuntimeRepLevityMultiplicity.

Note that these might get defaulted anyway, if they are kind variables and `-XNoPolyKinds` is enabled.

Instances

Instances details
Outputable NonStandardDefaultingStrategy 
Instance details

Defined in GHC.Types.Basic

data TypeOrConstraint #

Constructors

TypeLike 
ConstraintLike 

Instances

Instances details
Data TypeOrConstraint 
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) -> TypeOrConstraint -> c TypeOrConstraint #

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

toConstr :: TypeOrConstraint -> Constr #

dataTypeOf :: TypeOrConstraint -> DataType #

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

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

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

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

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

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

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

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

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

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

Eq TypeOrConstraint 
Instance details

Defined in GHC.Types.Basic

Ord TypeOrConstraint 
Instance details

Defined in GHC.Types.Basic

data TypeOrKind #

Flag to see whether we're type-checking terms or kind-checking types

Constructors

TypeLevel 
KindLevel 

Instances

Instances details
Outputable TypeOrKind 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: TypeOrKind -> SDoc #

Eq TypeOrKind 
Instance details

Defined in GHC.Types.Basic

data InlineSpec #

Inline Specification

Instances

Instances details
Data InlineSpec 
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) -> InlineSpec -> c InlineSpec #

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

toConstr :: InlineSpec -> Constr #

dataTypeOf :: InlineSpec -> DataType #

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

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

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

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

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

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

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

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

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

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

Show InlineSpec 
Instance details

Defined in GHC.Types.Basic

Binary InlineSpec 
Instance details

Defined in GHC.Types.Basic

Outputable InlineSpec 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: InlineSpec -> SDoc #

Eq InlineSpec 
Instance details

Defined in GHC.Types.Basic

data RuleMatchInfo #

Rule Match Information

Constructors

ConLike 
FunLike 

Instances

Instances details
Data RuleMatchInfo 
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) -> RuleMatchInfo -> c RuleMatchInfo #

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

toConstr :: RuleMatchInfo -> Constr #

dataTypeOf :: RuleMatchInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RuleMatchInfo 
Instance details

Defined in GHC.Types.Basic

Binary RuleMatchInfo 
Instance details

Defined in GHC.Types.Basic

Outputable RuleMatchInfo 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: RuleMatchInfo -> SDoc #

Eq RuleMatchInfo 
Instance details

Defined in GHC.Types.Basic

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

Instances

Instances details
Data Activation 
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) -> Activation -> c Activation #

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

toConstr :: Activation -> Constr #

dataTypeOf :: Activation -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary Activation 
Instance details

Defined in GHC.Types.Basic

Outputable Activation 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Activation -> SDoc #

Eq Activation 
Instance details

Defined in GHC.Types.Basic

data CompilerPhase #

Instances

Instances details
Outputable CompilerPhase 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: CompilerPhase -> SDoc #

Eq CompilerPhase 
Instance details

Defined in GHC.Types.Basic

type PhaseNum = Int #

Phase Number

data SuccessFlag #

Constructors

Succeeded 
Failed 

Instances

Instances details
Semigroup SuccessFlag 
Instance details

Defined in GHC.Types.Basic

Outputable SuccessFlag 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: SuccessFlag -> SDoc #

data DefMethSpec ty #

Default Method Specification

Constructors

VanillaDM 
GenericDM ty 

Instances

Instances details
Outputable (DefMethSpec ty) 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: DefMethSpec ty -> SDoc #

data TailCallInfo #

Instances

Instances details
Outputable TailCallInfo 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: TailCallInfo -> SDoc #

Eq TailCallInfo 
Instance details

Defined in GHC.Types.Basic

data InsideLam #

Inside Lambda

Constructors

IsInsideLam

Occurs inside a non-linear lambda Substituting a redex for this occurrence is dangerous because it might duplicate work.

NotInsideLam 

Instances

Instances details
Monoid InsideLam 
Instance details

Defined in GHC.Types.Basic

Semigroup InsideLam

If any occurrence of an identifier is inside a lambda, then the occurrence info of that identifier marks it as occurring inside a lambda

Instance details

Defined in GHC.Types.Basic

Eq InsideLam 
Instance details

Defined in GHC.Types.Basic

data InterestingCxt #

Interesting Context

Constructors

IsInteresting

Function: is applied Data value: scrutinised by a case with at least one non-DEFAULT branch

NotInteresting 

Instances

Instances details
Monoid InterestingCxt 
Instance details

Defined in GHC.Types.Basic

Semigroup InterestingCxt

If there is any interesting identifier occurrence, then the aggregated occurrence info of that identifier is considered interesting.

Instance details

Defined in GHC.Types.Basic

Eq InterestingCxt 
Instance details

Defined in GHC.Types.Basic

data OccInfo #

identifier Occurrence Information

Constructors

ManyOccs

There are many occurrences, or unknown occurrences

IAmDead

Marks unused variables. Sometimes useful for lambda and case-bound variables.

OneOcc

Occurs exactly once (per branch), not inside a rule

IAmALoopBreaker

This identifier breaks a loop of mutually recursive functions. The field marks whether it is only a loop breaker due to a reference in a rule

Fields

Instances

Instances details
Outputable OccInfo 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OccInfo -> SDoc #

Eq OccInfo 
Instance details

Defined in GHC.Types.Basic

Methods

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

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

data UnboxedTupleOrSum #

Are we dealing with an unboxed tuple or an unboxed sum?

Used when validity checking, see check_ubx_tuple_or_sum.

Instances

Instances details
Outputable UnboxedTupleOrSum 
Instance details

Defined in GHC.Types.Basic

Eq UnboxedTupleOrSum 
Instance details

Defined in GHC.Types.Basic

data TupleSort #

Instances

Instances details
Data TupleSort 
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) -> TupleSort -> c TupleSort #

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

toConstr :: TupleSort -> Constr #

dataTypeOf :: TupleSort -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary TupleSort 
Instance details

Defined in GHC.Types.Basic

Outputable TupleSort 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: TupleSort -> SDoc #

Eq TupleSort 
Instance details

Defined in GHC.Types.Basic

newtype PprPrec #

A general-purpose pretty-printing precedence type.

Constructors

PprPrec Int 

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

Constructors

NoOverlap SourceText

This instance must not overlap another NoOverlap instance. However, it may be overlapped by Overlapping instances, and it may overlap Overlappable instances.

Overlappable SourceText

Silently ignore this instance if you find a more specific one that matches the constraint you are trying to resolve

Example: constraint (Foo [Int]) instance Foo [Int] instance {-# OVERLAPPABLE #-} Foo [a]

Since the second instance has the Overlappable flag, the first instance will be chosen (otherwise its ambiguous which to choose)

Overlapping SourceText

Silently ignore any more general instances that may be used to solve the constraint.

Example: constraint (Foo [Int]) instance {-# OVERLAPPING #-} Foo [Int] instance Foo [a]

Since the first instance has the Overlapping flag, the second---more general---instance will be ignored (otherwise it is ambiguous which to choose)

Overlaps SourceText

Equivalent to having both Overlapping and Overlappable flags.

Incoherent SourceText

Behave like Overlappable and Overlapping, and in addition pick an arbitrary one if there are multiple matching candidates, and don't worry about later instantiation

Example: constraint (Foo [b]) instance {-# INCOHERENT -} Foo [Int] instance Foo [a] Without the Incoherent flag, we'd complain that instantiating b would change which instance was chosen. See also Note [Incoherent instances] in GHC.Core.InstEnv

Instances

Instances details
Data OverlapMode 
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) -> OverlapMode -> c OverlapMode #

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

toConstr :: OverlapMode -> Constr #

dataTypeOf :: OverlapMode -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary OverlapMode 
Instance details

Defined in GHC.Types.Basic

Outputable OverlapMode 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OverlapMode -> SDoc #

Eq OverlapMode 
Instance details

Defined in GHC.Types.Basic

ExactPrint (LocatedP OverlapMode) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.ExactPrint

type Anno OverlapMode 
Instance details

Defined in GHC.Hs.Decls

type Anno OverlapMode 
Instance details

Defined in GHC.Hs.Decls

data OverlapFlag #

The semantics allowed for overlapping instances for a particular instance. See Note [Safe Haskell isSafeOverlap] in GHC.Core.InstEnv for a explanation of the isSafeOverlap field.

Instances

Instances details
Data OverlapFlag 
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) -> OverlapFlag -> c OverlapFlag #

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

toConstr :: OverlapFlag -> Constr #

dataTypeOf :: OverlapFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary OverlapFlag 
Instance details

Defined in GHC.Types.Basic

Outputable OverlapFlag 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OverlapFlag -> SDoc #

Eq OverlapFlag 
Instance details

Defined in GHC.Types.Basic

data Origin #

Constructors

FromSource 
Generated 

Instances

Instances details
Data Origin 
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) -> Origin -> c Origin #

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

toConstr :: Origin -> Constr #

dataTypeOf :: Origin -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable Origin 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Origin -> SDoc #

Eq Origin 
Instance details

Defined in GHC.Types.Basic

Methods

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

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

data RecFlag #

Recursivity Flag

Constructors

Recursive 
NonRecursive 

Instances

Instances details
Data RecFlag 
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) -> RecFlag -> c RecFlag #

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

toConstr :: RecFlag -> Constr #

dataTypeOf :: RecFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary RecFlag 
Instance details

Defined in GHC.Types.Basic

Outputable RecFlag 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: RecFlag -> SDoc #

Eq RecFlag 
Instance details

Defined in GHC.Types.Basic

Methods

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

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

data CbvMark #

Should an argument be passed evaluated *and* tagged.

Constructors

MarkedCbv 
NotMarkedCbv 

Instances

Instances details
Binary CbvMark 
Instance details

Defined in GHC.Types.Basic

Outputable CbvMark 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: CbvMark -> SDoc #

Eq CbvMark 
Instance details

Defined in GHC.Types.Basic

Methods

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

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

data TopLevelFlag #

Constructors

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

Constructors

IsFunction 
IsData 

Instances

Instances details
Data FunctionOrData 
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) -> FunctionOrData -> c FunctionOrData #

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

toConstr :: FunctionOrData -> Constr #

dataTypeOf :: FunctionOrData -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary FunctionOrData 
Instance details

Defined in GHC.Types.Basic

Outputable FunctionOrData 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: FunctionOrData -> SDoc #

Eq FunctionOrData 
Instance details

Defined in GHC.Types.Basic

Ord FunctionOrData 
Instance details

Defined in GHC.Types.Basic

data SwapFlag #

Constructors

NotSwapped 
IsSwapped 

Instances

Instances details
Outputable SwapFlag 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: SwapFlag -> SDoc #

data OneShotInfo #

If the Id is a lambda-bound variable then it may have lambda-bound variable info. Sometimes we know whether the lambda binding this variable is a "one-shot" lambda; that is, whether it is applied at most once.

This information may be useful in optimisation, as computations may safely be floated inside such a lambda without risk of duplicating work.

See also Note [OneShotInfo overview] above.

Constructors

NoOneShotInfo

No information

OneShotLam

The lambda is applied at most once.

Instances

Instances details
Outputable OneShotInfo 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: OneShotInfo -> SDoc #

Eq OneShotInfo 
Instance details

Defined in GHC.Types.Basic

data Alignment #

A power-of-two alignment

Instances

Instances details
Outputable Alignment 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: Alignment -> SDoc #

Eq Alignment 
Instance details

Defined in GHC.Types.Basic

Ord Alignment 
Instance details

Defined in GHC.Types.Basic

OutputableP env Alignment 
Instance details

Defined in GHC.Types.Basic

Methods

pdoc :: env -> Alignment -> SDoc #

type ConTagZ = Int #

A *zero-indexed* constructor tag

type FullArgCount = Int #

FullArgCount is the number of type or value arguments in an application, or the number of type or value binders in a lambda. Note: it includes both type and value arguments!

type JoinArity = Int #

The number of arguments that a join point takes. Unlike the arity of a function, this is a purely syntactic property and is fixed when the join point is created (or converted from a value). Both type and value arguments are counted.

type RepArity = Int #

Representation Arity

The number of represented arguments that can be applied to a value before it does "real work". So: fib 100 has representation arity 0 x -> fib x has representation arity 1 (# x, y #) -> fib (x + y) has representation arity 2

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

data LeftOrRight #

Constructors

CLeft 
CRight 

Instances

Instances details
Data LeftOrRight 
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) -> LeftOrRight -> c LeftOrRight #

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

toConstr :: LeftOrRight -> Constr #

dataTypeOf :: LeftOrRight -> DataType #

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

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

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

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

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

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

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

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

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

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

Binary LeftOrRight 
Instance details

Defined in GHC.Types.Basic

Outputable LeftOrRight 
Instance details

Defined in GHC.Types.Basic

Methods

ppr :: LeftOrRight -> SDoc #

Eq LeftOrRight 
Instance details

Defined in GHC.Types.Basic

infinity :: IntWithInf #

A representation of infinity

fromEP :: EP a -> a #

toEP :: EP a -> a #

pickLR :: LeftOrRight -> (a, a) -> a #

fIRST_TAG :: ConTag #

Tags are allocated from here for real constructors or for superclass selectors

noOneShotInfo :: OneShotInfo #

It is always safe to assume that an Id has no lambda-bound variable information

unSwap :: SwapFlag -> (a -> a -> b) -> a -> a -> b #

pprAlternative #

Arguments

:: (a -> SDoc)

The pretty printing function to use

-> a

The things to be pretty printed

-> ConTag

Alternative (one-based)

-> Arity

Arity

-> SDoc

SDoc where the alternative havs been pretty printed and finally packed into a paragraph.

Pretty print an alternative in an unboxed sum e.g. "| a | |".

inlinePragmaName :: InlineSpec -> SDoc #

Outputs string for pragma name for any of INLINEINLINABLENOINLINE. This differs from the Outputable instance for the InlineSpec type where the pragma name string as well as the accompanying SourceText (if any) is printed.

pprInline :: InlinePragma -> SDoc #

Pretty-print without displaying the user-specified InlineSpec.

pprInlineDebug :: InlinePragma -> SDoc #

Pretty-print including the user-specified InlineSpec.

treatZeroAsInf :: Int -> IntWithInf #

Turn a positive number into an IntWithInf, where 0 represents infinity

mkIntWithInf :: Int -> IntWithInf #

Inject any integer into an IntWithInf

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 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 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 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 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 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 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 InteractiveImport 
Instance details

Defined in GHC.Runtime.Context

Outputable GetDocsFailure 
Instance details

Defined in GHC.Runtime.Eval

Methods

ppr :: GetDocsFailure -> 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 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 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 TouchabilityTestResult 
Instance details

Defined in GHC.Tc.Solver.Monad

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 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 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 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 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 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 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 Comment 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Methods

ppr :: Comment -> SDoc #

Outputable Ordering 
Instance details

Defined in GHC.Utils.Outputable

Methods

ppr :: Ordering -> 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 (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 (Scaled a) 
Instance details

Defined in GHC.Core.TyCo.Rep

Methods

ppr :: Scaled a -> SDoc #

Outputable a => Outputable (Bag a) 
Instance details

Defined in GHC.Data.Bag

Methods

ppr :: Bag a -> SDoc #

OutputableBndr a => Outputable (BooleanFormula a) 
Instance details

Defined in GHC.Data.BooleanFormula

Methods

ppr :: BooleanFormula 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 (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 (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 (UniqSet a) 
Instance details

Defined in GHC.Types.Unique.Set

Methods

ppr :: UniqSet a -> SDoc #

Outputable (WarningTxt pass) 
Instance details

Defined in GHC.Unit.Module.Warnings

Methods

ppr :: WarningTxt pass -> 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 (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 (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 (UniqFM key a) 
Instance details

Defined in GHC.Types.Unique.FM

Methods

ppr :: UniqFM key 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 #