ghc-lib-parser-0.20200102: The GHC API, decoupled from GHC versions

Safe HaskellNone
LanguageHaskell2010

BasicTypes

Contents

Synopsis

Documentation

data LeftOrRight Source #

Constructors

CLeft 
CRight 
Instances
Eq LeftOrRight Source # 
Instance details

Defined in BasicTypes

Data LeftOrRight Source # 
Instance details

Defined in BasicTypes

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

Outputable LeftOrRight Source # 
Instance details

Defined in BasicTypes

Binary LeftOrRight Source # 
Instance details

Defined in Binary

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

type ConTag = Int Source #

Constructor Tag

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

type ConTagZ = Int Source #

A *zero-indexed* constructor tag

fIRST_TAG :: ConTag Source #

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

type Arity = Int Source #

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 CoreArity

type RepArity = Int Source #

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 () -> fib (x + y) has representation arity 2

type JoinArity = Int Source #

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.

data Alignment Source #

A power-of-two alignment

Instances
Eq Alignment Source # 
Instance details

Defined in BasicTypes

Ord Alignment Source # 
Instance details

Defined in BasicTypes

Outputable Alignment Source # 
Instance details

Defined in BasicTypes

data PromotionFlag Source #

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

Constructors

NotPromoted 
IsPromoted 
Instances
Eq PromotionFlag Source # 
Instance details

Defined in BasicTypes

Data PromotionFlag Source # 
Instance details

Defined in BasicTypes

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

Binary PromotionFlag Source # 
Instance details

Defined in Binary

data FunctionOrData Source #

Constructors

IsFunction 
IsData 
Instances
Eq FunctionOrData Source # 
Instance details

Defined in BasicTypes

Data FunctionOrData Source # 
Instance details

Defined in BasicTypes

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

Ord FunctionOrData Source # 
Instance details

Defined in BasicTypes

Outputable FunctionOrData Source # 
Instance details

Defined in BasicTypes

Binary FunctionOrData Source # 
Instance details

Defined in Binary

data WarningTxt Source #

Warning Text

reason/explanation from a WARNING or DEPRECATED pragma

Instances
Eq WarningTxt Source # 
Instance details

Defined in BasicTypes

Data WarningTxt Source # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: WarningTxt -> Constr #

dataTypeOf :: WarningTxt -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable WarningTxt Source # 
Instance details

Defined in BasicTypes

Binary WarningTxt Source # 
Instance details

Defined in Binary

data StringLiteral Source #

A String Literal in the source, including its original raw format for use by source to source manipulation tools.

Constructors

StringLiteral 
Instances
Eq StringLiteral Source # 
Instance details

Defined in BasicTypes

Data StringLiteral Source # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: StringLiteral -> Constr #

dataTypeOf :: StringLiteral -> DataType #

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

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

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

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

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

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

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

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

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

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

Outputable StringLiteral Source # 
Instance details

Defined in BasicTypes

Binary StringLiteral Source # 
Instance details

Defined in Binary

data Fixity Source #

Instances
Eq Fixity Source # 
Instance details

Defined in BasicTypes

Methods

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

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

Data Fixity Source # 
Instance details

Defined in BasicTypes

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

Outputable Fixity Source # 
Instance details

Defined in BasicTypes

Binary Fixity Source # 
Instance details

Defined in Binary

data FixityDirection Source #

Constructors

InfixL 
InfixR 
InfixN 
Instances
Eq FixityDirection Source # 
Instance details

Defined in BasicTypes

Data FixityDirection Source # 
Instance details

Defined in BasicTypes

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

Outputable FixityDirection Source # 
Instance details

Defined in BasicTypes

Binary FixityDirection Source # 
Instance details

Defined in Binary

data LexicalFixity Source #

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 
Infix 
Instances
Eq LexicalFixity Source # 
Instance details

Defined in BasicTypes

Data LexicalFixity Source # 
Instance details

Defined in BasicTypes

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

Defined in BasicTypes

data RecFlag Source #

Recursivity Flag

Constructors

Recursive 
NonRecursive 
Instances
Eq RecFlag Source # 
Instance details

Defined in BasicTypes

Methods

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

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

Data RecFlag Source # 
Instance details

Defined in BasicTypes

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

Outputable RecFlag Source # 
Instance details

Defined in BasicTypes

Binary RecFlag Source # 
Instance details

Defined in Binary

data Origin Source #

Constructors

FromSource 
Generated 
Instances
Eq Origin Source # 
Instance details

Defined in BasicTypes

Methods

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

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

Data Origin Source # 
Instance details

Defined in BasicTypes

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

Defined in BasicTypes

data TopLevelFlag Source #

Constructors

TopLevel 
NotTopLevel 
Instances
Outputable TopLevelFlag Source # 
Instance details

Defined in BasicTypes

data OverlapFlag Source #

The semantics allowed for overlapping instances for a particular instance. See Note [Safe Haskell isSafeOverlap] (in hs) for a explanation of the isSafeOverlap field.

Instances
Eq OverlapFlag Source # 
Instance details

Defined in BasicTypes

Data OverlapFlag Source # 
Instance details

Defined in BasicTypes

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

Outputable OverlapFlag Source # 
Instance details

Defined in BasicTypes

Binary OverlapFlag Source # 
Instance details

Defined in Binary

data OverlapMode Source #

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 {--} 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 {--} 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 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 InstEnv

Instances
Eq OverlapMode Source # 
Instance details

Defined in BasicTypes

Data OverlapMode Source # 
Instance details

Defined in BasicTypes

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

Outputable OverlapMode Source # 
Instance details

Defined in BasicTypes

Binary OverlapMode Source # 
Instance details

Defined in Binary

data Boxity Source #

Constructors

Boxed 
Unboxed 
Instances
Eq Boxity Source # 
Instance details

Defined in BasicTypes

Methods

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

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

Data Boxity Source # 
Instance details

Defined in BasicTypes

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

Outputable Boxity Source # 
Instance details

Defined in BasicTypes

newtype PprPrec Source #

A general-purpose pretty-printing precedence type.

Constructors

PprPrec Int 
Instances
Eq PprPrec Source # 
Instance details

Defined in BasicTypes

Methods

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

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

Ord PprPrec Source # 
Instance details

Defined in BasicTypes

Show PprPrec Source # 
Instance details

Defined in BasicTypes

data TupleSort Source #

Instances
Eq TupleSort Source # 
Instance details

Defined in BasicTypes

Data TupleSort Source # 
Instance details

Defined in BasicTypes

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

Outputable TupleSort Source # 
Instance details

Defined in BasicTypes

Binary TupleSort Source # 
Instance details

Defined in Binary

pprAlternative Source #

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

The OneShotInfo type

data OneShotInfo Source #

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.

Constructors

NoOneShotInfo

No information

OneShotLam

The lambda is applied at most once.

Instances
Eq OneShotInfo Source # 
Instance details

Defined in BasicTypes

Outputable OneShotInfo Source # 
Instance details

Defined in BasicTypes

noOneShotInfo :: OneShotInfo Source #

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

data OccInfo Source #

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

Defined in BasicTypes

Methods

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

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

Outputable OccInfo Source # 
Instance details

Defined in BasicTypes

data InsideLam Source #

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

Defined in BasicTypes

Semigroup InsideLam Source #

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

Instance details

Defined in BasicTypes

Monoid InsideLam Source # 
Instance details

Defined in BasicTypes

data OneBranch Source #

Constructors

InOneBranch

One syntactic occurance: Occurs in only one case branch so no code-duplication issue to worry about

MultipleBranches 
Instances
Eq OneBranch Source # 
Instance details

Defined in BasicTypes

data InterestingCxt Source #

Interesting Context

Constructors

IsInteresting

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

NotInteresting 
Instances
Eq InterestingCxt Source # 
Instance details

Defined in BasicTypes

Semigroup InterestingCxt Source #

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

Instance details

Defined in BasicTypes

Monoid InterestingCxt Source # 
Instance details

Defined in BasicTypes

data EP a Source #

Embedding Projection pair

Constructors

EP 

Fields

data DefMethSpec ty Source #

Default Method Specification

Constructors

VanillaDM 
GenericDM ty 

data SwapFlag Source #

Constructors

NotSwapped 
IsSwapped 
Instances
Outputable SwapFlag Source # 
Instance details

Defined in BasicTypes

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

type PhaseNum = Int Source #

Phase Number

data Activation Source #

Instances
Eq Activation Source # 
Instance details

Defined in BasicTypes

Data Activation Source # 
Instance details

Defined in BasicTypes

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

Outputable Activation Source # 
Instance details

Defined in BasicTypes

Binary Activation Source # 
Instance details

Defined in Binary

data RuleMatchInfo Source #

Rule Match Information

Constructors

ConLike 
FunLike 
Instances
Eq RuleMatchInfo Source # 
Instance details

Defined in BasicTypes

Data RuleMatchInfo Source # 
Instance details

Defined in BasicTypes

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

Defined in BasicTypes

Outputable RuleMatchInfo Source # 
Instance details

Defined in BasicTypes

Binary RuleMatchInfo Source # 
Instance details

Defined in Binary

data InlineSpec Source #

Inline Specification

Instances
Eq InlineSpec Source # 
Instance details

Defined in BasicTypes

Data InlineSpec Source # 
Instance details

Defined in BasicTypes

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

Defined in BasicTypes

Outputable InlineSpec Source # 
Instance details

Defined in BasicTypes

Binary InlineSpec Source # 
Instance details

Defined in Binary

data InlinePragma Source #

Instances
Eq InlinePragma Source # 
Instance details

Defined in BasicTypes

Data InlinePragma Source # 
Instance details

Defined in BasicTypes

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

Outputable InlinePragma Source # 
Instance details

Defined in BasicTypes

Binary InlinePragma Source # 
Instance details

Defined in Binary

data SuccessFlag Source #

Constructors

Succeeded 
Failed 
Instances
Outputable SuccessFlag Source # 
Instance details

Defined in BasicTypes

data IntegralLit Source #

Integral Literal

Used (instead of Integer) to represent negative zegative zero which is required for NegativeLiterals extension to correctly parse `-0::Double` as negative zero. See also #13211.

Constructors

IL 
Instances
Eq IntegralLit Source # 
Instance details

Defined in BasicTypes

Data IntegralLit Source # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: IntegralLit -> Constr #

dataTypeOf :: IntegralLit -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord IntegralLit Source # 
Instance details

Defined in BasicTypes

Show IntegralLit Source # 
Instance details

Defined in BasicTypes

Outputable IntegralLit Source # 
Instance details

Defined in BasicTypes

data FractionalLit Source #

Fractional Literal

Used (instead of Rational) to represent exactly the floating point literal that we encountered in the user's source program. This allows us to pretty-print exactly what the user wrote, which is important e.g. for floating point numbers that can't represented as Doubles (we used to via Double for pretty-printing). See also #2245.

Constructors

FL 
Instances
Eq FractionalLit Source # 
Instance details

Defined in BasicTypes

Data FractionalLit Source # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: FractionalLit -> Constr #

dataTypeOf :: FractionalLit -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FractionalLit Source # 
Instance details

Defined in BasicTypes

Show FractionalLit Source # 
Instance details

Defined in BasicTypes

Outputable FractionalLit Source # 
Instance details

Defined in BasicTypes

data SourceText Source #

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

Defined in BasicTypes

Data SourceText Source # 
Instance details

Defined in BasicTypes

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

Defined in BasicTypes

Outputable SourceText Source # 
Instance details

Defined in BasicTypes

Binary SourceText Source # 
Instance details

Defined in Binary

pprWithSourceText :: SourceText -> SDoc -> SDoc Source #

Special combinator for showing string literals.

infinity :: IntWithInf Source #

A representation of infinity

treatZeroAsInf :: Int -> IntWithInf Source #

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

mkIntWithInf :: Int -> IntWithInf Source #

Inject any integer into an IntWithInf

data SpliceExplicitFlag Source #

Constructors

ExplicitSplice

= $(f x y)

ImplicitSplice

= f x y, i.e. a naked top level expression

Instances
Data SpliceExplicitFlag Source # 
Instance details

Defined in BasicTypes

Methods

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

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

toConstr :: SpliceExplicitFlag -> Constr #

dataTypeOf :: SpliceExplicitFlag -> DataType #

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

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

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

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

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

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

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

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

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

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

data TypeOrKind Source #

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

Constructors

TypeLevel 
KindLevel 
Instances
Eq TypeOrKind Source # 
Instance details

Defined in BasicTypes

Outputable TypeOrKind Source # 
Instance details

Defined in BasicTypes