ghc-8.0.1: The GHC API

Safe HaskellNone
LanguageHaskell2010

BasicTypes

Contents

Synopsis

Documentation

type ConTag = Int Source #

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

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

type RepArity = Int Source #

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

data FunctionOrData Source #

Constructors

IsFunction 
IsData 

Instances

Eq FunctionOrData # 
Data FunctionOrData # 

Methods

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

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

toConstr :: FunctionOrData -> Constr Source #

dataTypeOf :: FunctionOrData -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord FunctionOrData # 
Outputable FunctionOrData # 
Binary FunctionOrData # 

data WarningTxt Source #

Instances

Eq WarningTxt # 
Data WarningTxt # 

Methods

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

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

toConstr :: WarningTxt -> Constr Source #

dataTypeOf :: WarningTxt -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable WarningTxt # 
Binary WarningTxt # 

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

Methods

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

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

toConstr :: StringLiteral -> Constr Source #

dataTypeOf :: StringLiteral -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Binary StringLiteral # 

data Fixity Source #

Instances

Eq Fixity # 

Methods

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

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

Data Fixity # 

Methods

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

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

toConstr :: Fixity -> Constr Source #

dataTypeOf :: Fixity -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable Fixity # 
Binary Fixity # 

data FixityDirection Source #

Constructors

InfixL 
InfixR 
InfixN 

Instances

Eq FixityDirection # 
Data FixityDirection # 

Methods

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

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

toConstr :: FixityDirection -> Constr Source #

dataTypeOf :: FixityDirection -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable FixityDirection # 
Binary FixityDirection # 

data RecFlag Source #

Constructors

Recursive 
NonRecursive 

Instances

Eq RecFlag # 

Methods

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

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

Data RecFlag # 

Methods

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

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

toConstr :: RecFlag -> Constr Source #

dataTypeOf :: RecFlag -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable RecFlag # 
Binary RecFlag # 

data Origin Source #

Constructors

FromSource 
Generated 

Instances

Eq Origin # 

Methods

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

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

Data Origin # 

Methods

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

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

toConstr :: Origin -> Constr Source #

dataTypeOf :: Origin -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable Origin # 

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

Methods

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

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

toConstr :: OverlapFlag -> Constr Source #

dataTypeOf :: OverlapFlag -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable OverlapFlag # 
Binary OverlapFlag # 

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

Methods

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

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

toConstr :: OverlapMode -> Constr Source #

dataTypeOf :: OverlapMode -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable OverlapMode # 
Binary OverlapMode # 

data Boxity Source #

Constructors

Boxed 
Unboxed 

Instances

Eq Boxity # 

Methods

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

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

Data Boxity # 

Methods

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

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

toConstr :: Boxity -> Constr Source #

dataTypeOf :: Boxity -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable Boxity # 

data TupleSort Source #

Instances

Eq TupleSort # 
Data TupleSort # 

Methods

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

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

toConstr :: TupleSort -> Constr Source #

dataTypeOf :: TupleSort -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Binary TupleSort # 

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

ProbOneShot

The lambda is probably applied at most once See Note [Computing one-shot info, and ProbOneShot] in Demand

OneShotLam

The lambda is applied at most once.

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

NoOccInfo

There are many occurrences, or unknown occurrences

IAmDead

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

OneOcc !InsideLam !OneBranch !InterestingCxt

Occurs exactly once, not inside a rule

IAmALoopBreaker !RulesOnly

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

data EP a Source #

Constructors

EP 

Fields

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

data Activation Source #

Instances

Eq Activation # 
Data Activation # 

Methods

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

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

toConstr :: Activation -> Constr Source #

dataTypeOf :: Activation -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable Activation # 
Binary Activation # 

data RuleMatchInfo Source #

Constructors

ConLike 
FunLike 

Instances

Eq RuleMatchInfo # 
Data RuleMatchInfo # 

Methods

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

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

toConstr :: RuleMatchInfo -> Constr Source #

dataTypeOf :: RuleMatchInfo -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show RuleMatchInfo # 
Outputable RuleMatchInfo # 
Binary RuleMatchInfo # 

data InlineSpec Source #

Instances

Eq InlineSpec # 
Data InlineSpec # 

Methods

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

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

toConstr :: InlineSpec -> Constr Source #

dataTypeOf :: InlineSpec -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show InlineSpec # 
Outputable InlineSpec # 
Binary InlineSpec # 

data InlinePragma Source #

Instances

Eq InlinePragma # 
Data InlinePragma # 

Methods

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

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

toConstr :: InlinePragma -> Constr Source #

dataTypeOf :: InlinePragma -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Outputable InlinePragma # 
Binary InlinePragma # 

data FractionalLit Source #

Constructors

FL 

Instances

Eq FractionalLit # 
Data FractionalLit # 

Methods

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

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

toConstr :: FractionalLit -> Constr Source #

dataTypeOf :: FractionalLit -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord FractionalLit # 
Show FractionalLit # 
Outputable FractionalLit # 

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