Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Version = Int
- bumpVersion :: Version -> Version
- initialVersion :: Version
- data LeftOrRight
- pickLR :: LeftOrRight -> (a, a) -> a
- type ConTag = Int
- type ConTagZ = Int
- fIRST_TAG :: ConTag
- type Arity = Int
- type RepArity = Int
- type JoinArity = Int
- data Alignment
- mkAlignment :: Int -> Alignment
- alignmentOf :: Int -> Alignment
- alignmentBytes :: Alignment -> Int
- data PromotionFlag
- isPromoted :: PromotionFlag -> Bool
- data FunctionOrData
- = IsFunction
- | IsData
- data WarningTxt
- pprWarningTxtForMsg :: WarningTxt -> SDoc
- data StringLiteral = StringLiteral {
- sl_st :: SourceText
- sl_fs :: FastString
- data Fixity = Fixity SourceText Int FixityDirection
- data FixityDirection
- defaultFixity :: Fixity
- maxPrecedence :: Int
- minPrecedence :: Int
- negateFixity :: Fixity
- funTyFixity :: Fixity
- compareFixity :: Fixity -> Fixity -> (Bool, Bool)
- data LexicalFixity
- data RecFlag
- isRec :: RecFlag -> Bool
- isNonRec :: RecFlag -> Bool
- boolToRecFlag :: Bool -> RecFlag
- data Origin
- isGenerated :: Origin -> Bool
- type RuleName = FastString
- pprRuleName :: RuleName -> SDoc
- data TopLevelFlag
- isTopLevel :: TopLevelFlag -> Bool
- isNotTopLevel :: TopLevelFlag -> Bool
- data OverlapFlag = OverlapFlag {}
- data OverlapMode
- setOverlapModeMaybe :: OverlapFlag -> Maybe OverlapMode -> OverlapFlag
- hasOverlappingFlag :: OverlapMode -> Bool
- hasOverlappableFlag :: OverlapMode -> Bool
- hasIncoherentFlag :: OverlapMode -> Bool
- data Boxity
- isBoxed :: Boxity -> Bool
- newtype PprPrec = PprPrec Int
- topPrec :: PprPrec
- sigPrec :: PprPrec
- opPrec :: PprPrec
- funPrec :: PprPrec
- appPrec :: PprPrec
- maybeParen :: PprPrec -> PprPrec -> SDoc -> SDoc
- data TupleSort
- tupleSortBoxity :: TupleSort -> Boxity
- boxityTupleSort :: Boxity -> TupleSort
- tupleParens :: TupleSort -> SDoc -> SDoc
- sumParens :: SDoc -> SDoc
- pprAlternative :: (a -> SDoc) -> a -> ConTag -> Arity -> SDoc
- data OneShotInfo
- noOneShotInfo :: OneShotInfo
- hasNoOneShotInfo :: OneShotInfo -> Bool
- isOneShotInfo :: OneShotInfo -> Bool
- bestOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo
- worstOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo
- data OccInfo
- = ManyOccs {
- occ_tail :: !TailCallInfo
- | IAmDead
- | OneOcc { }
- | IAmALoopBreaker {
- occ_rules_only :: !RulesOnly
- occ_tail :: !TailCallInfo
- = ManyOccs {
- noOccInfo :: OccInfo
- seqOccInfo :: OccInfo -> ()
- zapFragileOcc :: OccInfo -> OccInfo
- isOneOcc :: OccInfo -> Bool
- isDeadOcc :: OccInfo -> Bool
- isStrongLoopBreaker :: OccInfo -> Bool
- isWeakLoopBreaker :: OccInfo -> Bool
- isManyOccs :: OccInfo -> Bool
- strongLoopBreaker :: OccInfo
- weakLoopBreaker :: OccInfo
- type InsideLam = Bool
- insideLam :: InsideLam
- notInsideLam :: InsideLam
- type OneBranch = Bool
- oneBranch :: OneBranch
- notOneBranch :: OneBranch
- type InterestingCxt = Bool
- data TailCallInfo
- tailCallInfo :: OccInfo -> TailCallInfo
- zapOccTailCallInfo :: OccInfo -> OccInfo
- isAlwaysTailCalled :: OccInfo -> Bool
- data EP a = EP {}
- data DefMethSpec ty
- data SwapFlag
- flipSwap :: SwapFlag -> SwapFlag
- unSwap :: SwapFlag -> (a -> a -> b) -> a -> a -> b
- isSwapped :: SwapFlag -> Bool
- data CompilerPhase
- type PhaseNum = Int
- data Activation
- isActive :: CompilerPhase -> Activation -> Bool
- isActiveIn :: PhaseNum -> Activation -> Bool
- competesWith :: Activation -> Activation -> Bool
- isNeverActive :: Activation -> Bool
- isAlwaysActive :: Activation -> Bool
- isEarlyActive :: Activation -> Bool
- activeAfterInitial :: Activation
- activeDuringFinal :: Activation
- data RuleMatchInfo
- isConLike :: RuleMatchInfo -> Bool
- isFunLike :: RuleMatchInfo -> Bool
- data InlineSpec
- noUserInlineSpec :: InlineSpec -> Bool
- data InlinePragma = InlinePragma {}
- defaultInlinePragma :: InlinePragma
- alwaysInlinePragma :: InlinePragma
- neverInlinePragma :: InlinePragma
- dfunInlinePragma :: InlinePragma
- isDefaultInlinePragma :: InlinePragma -> Bool
- isInlinePragma :: InlinePragma -> Bool
- isInlinablePragma :: InlinePragma -> Bool
- isAnyInlinePragma :: InlinePragma -> Bool
- inlinePragmaSpec :: InlinePragma -> InlineSpec
- inlinePragmaSat :: InlinePragma -> Maybe Arity
- inlinePragmaActivation :: InlinePragma -> Activation
- inlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo
- setInlinePragmaActivation :: InlinePragma -> Activation -> InlinePragma
- setInlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo -> InlinePragma
- pprInline :: InlinePragma -> SDoc
- pprInlineDebug :: InlinePragma -> SDoc
- data SuccessFlag
- succeeded :: SuccessFlag -> Bool
- failed :: SuccessFlag -> Bool
- successIf :: Bool -> SuccessFlag
- data IntegralLit = IL {}
- data FractionalLit = FL {}
- negateIntegralLit :: IntegralLit -> IntegralLit
- negateFractionalLit :: FractionalLit -> FractionalLit
- mkIntegralLit :: Integral a => a -> IntegralLit
- mkFractionalLit :: Real a => a -> FractionalLit
- integralFractionalLit :: Bool -> Integer -> FractionalLit
- data SourceText
- pprWithSourceText :: SourceText -> SDoc -> SDoc
- data IntWithInf
- infinity :: IntWithInf
- treatZeroAsInf :: Int -> IntWithInf
- mkIntWithInf :: Int -> IntWithInf
- intGtLimit :: Int -> IntWithInf -> Bool
- data SpliceExplicitFlag
- data TypeOrKind
- isTypeLevel :: TypeOrKind -> Bool
- isKindLevel :: TypeOrKind -> Bool
Documentation
bumpVersion :: Version -> Version Source #
data LeftOrRight Source #
Instances
Eq LeftOrRight # | |
Defined in BasicTypes (==) :: LeftOrRight -> LeftOrRight -> Bool # (/=) :: LeftOrRight -> LeftOrRight -> Bool # | |
Data LeftOrRight # | |
Defined in BasicTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LeftOrRight Source # toConstr :: LeftOrRight -> Constr Source # dataTypeOf :: LeftOrRight -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LeftOrRight) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LeftOrRight) Source # gmapT :: (forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r Source # gmapQ :: (forall d. Data d => d -> u) -> LeftOrRight -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight Source # | |
Outputable LeftOrRight # | |
Defined in BasicTypes | |
Binary LeftOrRight # | |
pickLR :: LeftOrRight -> (a, a) -> a Source #
Constructor Tag
Type of the tags associated with each constructor possibility or superclass selector
Tags are allocated from here for real constructors or for superclass selectors
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
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.
A power-of-two alignment
Instances
Eq Alignment # | |
Ord Alignment # | |
Defined in BasicTypes | |
Outputable Alignment # | |
mkAlignment :: Int -> Alignment Source #
alignmentOf :: Int -> Alignment Source #
alignmentBytes :: Alignment -> Int Source #
data PromotionFlag Source #
Is a TyCon a promoted data constructor or just a normal type constructor?
Instances
Eq PromotionFlag # | |
Defined in BasicTypes (==) :: PromotionFlag -> PromotionFlag -> Bool # (/=) :: PromotionFlag -> PromotionFlag -> Bool # | |
Data PromotionFlag # | |
Defined in BasicTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PromotionFlag Source # toConstr :: PromotionFlag -> Constr Source # dataTypeOf :: PromotionFlag -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PromotionFlag) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PromotionFlag) Source # gmapT :: (forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r Source # gmapQ :: (forall d. Data d => d -> u) -> PromotionFlag -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> PromotionFlag -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag Source # | |
Binary PromotionFlag # | |
isPromoted :: PromotionFlag -> Bool Source #
data FunctionOrData Source #
Instances
data WarningTxt Source #
Warning Text
reason/explanation from a WARNING or DEPRECATED pragma
WarningTxt (Located SourceText) [Located StringLiteral] | |
DeprecatedTxt (Located SourceText) [Located StringLiteral] |
Instances
Eq WarningTxt # | |
Defined in BasicTypes (==) :: WarningTxt -> WarningTxt -> Bool # (/=) :: WarningTxt -> WarningTxt -> Bool # | |
Data WarningTxt # | |
Defined in BasicTypes 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 :: forall r r'. (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 # | |
Defined in BasicTypes | |
Binary WarningTxt # | |
pprWarningTxtForMsg :: WarningTxt -> SDoc Source #
data StringLiteral Source #
A String Literal in the source, including its original raw format for use by source to source manipulation tools.
Instances
Eq StringLiteral # | |
Defined in BasicTypes (==) :: StringLiteral -> StringLiteral -> Bool # (/=) :: StringLiteral -> StringLiteral -> Bool # | |
Data StringLiteral # | |
Defined in BasicTypes 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 :: forall r r'. (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 # | |
Outputable StringLiteral # | |
Defined in BasicTypes | |
Binary StringLiteral # | |
Instances
Eq Fixity # | |
Data Fixity # | |
Defined in BasicTypes 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 :: forall r r'. (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 #
Instances
maxPrecedence :: Int Source #
minPrecedence :: Int Source #
funTyFixity :: Fixity Source #
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.
Instances
Eq LexicalFixity # | |
Defined in BasicTypes (==) :: LexicalFixity -> LexicalFixity -> Bool # (/=) :: LexicalFixity -> LexicalFixity -> Bool # | |
Data LexicalFixity # | |
Defined in BasicTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LexicalFixity -> c LexicalFixity Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LexicalFixity Source # toConstr :: LexicalFixity -> Constr Source # dataTypeOf :: LexicalFixity -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LexicalFixity) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LexicalFixity) Source # gmapT :: (forall b. Data b => b -> b) -> LexicalFixity -> LexicalFixity Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r Source # gmapQ :: (forall d. Data d => d -> u) -> LexicalFixity -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> LexicalFixity -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity Source # | |
Outputable LexicalFixity # | |
Defined in BasicTypes |
Recursivity Flag
Instances
Eq RecFlag # | |
Data RecFlag # | |
Defined in BasicTypes 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 :: forall r r'. (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 # | |
boolToRecFlag :: Bool -> RecFlag Source #
Instances
Eq Origin # | |
Data Origin # | |
Defined in BasicTypes 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 :: forall r r'. (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 # | |
isGenerated :: Origin -> Bool Source #
type RuleName = FastString Source #
pprRuleName :: RuleName -> SDoc Source #
data TopLevelFlag Source #
Instances
Outputable TopLevelFlag # | |
Defined in BasicTypes |
isTopLevel :: TopLevelFlag -> Bool Source #
isNotTopLevel :: TopLevelFlag -> Bool Source #
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.
AnnKeywordId
:AnnOpen
'{-# OVERLAPPABLE'
or'{-# OVERLAPPING'
or'{-# OVERLAPS'
or'{-# INCOHERENT'
,AnnClose
`#-}`
,
Instances
Eq OverlapFlag # | |
Defined in BasicTypes (==) :: OverlapFlag -> OverlapFlag -> Bool # (/=) :: OverlapFlag -> OverlapFlag -> Bool # | |
Data OverlapFlag # | |
Defined in BasicTypes 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 :: forall r r'. (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 # | |
Defined in BasicTypes | |
Binary OverlapFlag # | |
data OverlapMode Source #
NoOverlap SourceText | This instance must not overlap another |
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 |
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 |
Instances
Eq OverlapMode # | |
Defined in BasicTypes (==) :: OverlapMode -> OverlapMode -> Bool # (/=) :: OverlapMode -> OverlapMode -> Bool # | |
Data OverlapMode # | |
Defined in BasicTypes 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 :: forall r r'. (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 # | |
Defined in BasicTypes | |
Binary OverlapMode # | |
hasOverlappingFlag :: OverlapMode -> Bool Source #
hasIncoherentFlag :: OverlapMode -> Bool Source #
Instances
Eq Boxity # | |
Data Boxity # | |
Defined in BasicTypes 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 :: forall r r'. (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 # | |
A general-purpose pretty-printing precedence type.
Instances
Eq TupleSort # | |
Data TupleSort # | |
Defined in BasicTypes 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 :: forall r r'. (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 # | |
Outputable TupleSort # | |
Binary TupleSort # | |
tupleSortBoxity :: TupleSort -> Boxity Source #
boxityTupleSort :: Boxity -> TupleSort Source #
:: (a -> SDoc) | The pretty printing function to use |
-> a | The things to be pretty printed |
-> ConTag | Alternative (one-based) |
-> Arity | Arity |
-> SDoc |
|
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.
NoOneShotInfo | No information |
OneShotLam | The lambda is applied at most once. |
Instances
Eq OneShotInfo # | |
Defined in BasicTypes (==) :: OneShotInfo -> OneShotInfo -> Bool # (/=) :: OneShotInfo -> OneShotInfo -> Bool # | |
Outputable OneShotInfo # | |
Defined in BasicTypes |
noOneShotInfo :: OneShotInfo Source #
It is always safe to assume that an Id
has no lambda-bound variable information
hasNoOneShotInfo :: OneShotInfo -> Bool Source #
isOneShotInfo :: OneShotInfo -> Bool Source #
bestOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo Source #
worstOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo Source #
identifier Occurrence Information
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 |
|
seqOccInfo :: OccInfo -> () Source #
zapFragileOcc :: OccInfo -> OccInfo Source #
isStrongLoopBreaker :: OccInfo -> Bool Source #
isWeakLoopBreaker :: OccInfo -> Bool Source #
isManyOccs :: OccInfo -> Bool Source #
type InterestingCxt = Bool Source #
Interesting Context
data TailCallInfo Source #
Instances
Eq TailCallInfo # | |
Defined in BasicTypes (==) :: TailCallInfo -> TailCallInfo -> Bool # (/=) :: TailCallInfo -> TailCallInfo -> Bool # | |
Outputable TailCallInfo # | |
Defined in BasicTypes |
tailCallInfo :: OccInfo -> TailCallInfo Source #
zapOccTailCallInfo :: OccInfo -> OccInfo Source #
isAlwaysTailCalled :: OccInfo -> Bool Source #
data DefMethSpec ty Source #
Default Method Specification
Instances
Outputable (DefMethSpec ty) # | |
Defined in BasicTypes | |
Binary (DefMethSpec IfaceType) # | |
data CompilerPhase Source #
Instances
Outputable CompilerPhase # | |
Defined in BasicTypes |
data Activation Source #
Instances
Eq Activation # | |
Defined in BasicTypes (==) :: Activation -> Activation -> Bool # (/=) :: Activation -> Activation -> Bool # | |
Data Activation # | |
Defined in BasicTypes 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 :: forall r r'. (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 # | |
Defined in BasicTypes | |
Binary Activation # | |
isActive :: CompilerPhase -> Activation -> Bool Source #
isActiveIn :: PhaseNum -> Activation -> Bool Source #
competesWith :: Activation -> Activation -> Bool Source #
isNeverActive :: Activation -> Bool Source #
isAlwaysActive :: Activation -> Bool Source #
isEarlyActive :: Activation -> Bool Source #
data RuleMatchInfo Source #
Rule Match Information
Instances
Eq RuleMatchInfo # | |
Defined in BasicTypes (==) :: RuleMatchInfo -> RuleMatchInfo -> Bool # (/=) :: RuleMatchInfo -> RuleMatchInfo -> Bool # | |
Data RuleMatchInfo # | |
Defined in BasicTypes 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 :: forall r r'. (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 # | |
Defined in BasicTypes | |
Outputable RuleMatchInfo # | |
Defined in BasicTypes | |
Binary RuleMatchInfo # | |
isConLike :: RuleMatchInfo -> Bool Source #
isFunLike :: RuleMatchInfo -> Bool Source #
data InlineSpec Source #
Inline Specification
Instances
Eq InlineSpec # | |
Defined in BasicTypes (==) :: InlineSpec -> InlineSpec -> Bool # (/=) :: InlineSpec -> InlineSpec -> Bool # | |
Data InlineSpec # | |
Defined in BasicTypes 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 :: forall r r'. (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 # | |
Defined in BasicTypes | |
Outputable InlineSpec # | |
Defined in BasicTypes | |
Binary InlineSpec # | |
noUserInlineSpec :: InlineSpec -> Bool Source #
data InlinePragma Source #
InlinePragma | |
|
Instances
Eq InlinePragma # | |
Defined in BasicTypes (==) :: InlinePragma -> InlinePragma -> Bool # (/=) :: InlinePragma -> InlinePragma -> Bool # | |
Data InlinePragma # | |
Defined in BasicTypes 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 :: forall r r'. (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 # | |
Defined in BasicTypes | |
Binary InlinePragma # | |
isInlinePragma :: InlinePragma -> Bool Source #
isInlinablePragma :: InlinePragma -> Bool Source #
isAnyInlinePragma :: InlinePragma -> Bool Source #
inlinePragmaSat :: InlinePragma -> Maybe Arity Source #
pprInline :: InlinePragma -> SDoc Source #
pprInlineDebug :: InlinePragma -> SDoc Source #
data SuccessFlag Source #
Instances
Outputable SuccessFlag # | |
Defined in BasicTypes |
succeeded :: SuccessFlag -> Bool Source #
failed :: SuccessFlag -> Bool Source #
successIf :: Bool -> SuccessFlag Source #
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.
Instances
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.
Instances
mkIntegralLit :: Integral a => a -> IntegralLit Source #
mkFractionalLit :: Real a => a -> FractionalLit Source #
integralFractionalLit :: Bool -> Integer -> FractionalLit Source #
data SourceText Source #
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 # | |
Defined in BasicTypes (==) :: SourceText -> SourceText -> Bool # (/=) :: SourceText -> SourceText -> Bool # | |
Data SourceText # | |
Defined in BasicTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceText -> c SourceText Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceText Source # toConstr :: SourceText -> Constr Source # dataTypeOf :: SourceText -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceText) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceText) Source # gmapT :: (forall b. Data b => b -> b) -> SourceText -> SourceText Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceText -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceText -> r Source # gmapQ :: (forall d. Data d => d -> u) -> SourceText -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceText -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText Source # | |
Show SourceText # | |
Defined in BasicTypes | |
Outputable SourceText # | |
Defined in BasicTypes | |
Binary SourceText # | |
pprWithSourceText :: SourceText -> SDoc -> SDoc Source #
Special combinator for showing string literals.
data IntWithInf Source #
An integer or infinity
Instances
Eq IntWithInf # | |
Defined in BasicTypes (==) :: IntWithInf -> IntWithInf -> Bool # (/=) :: IntWithInf -> IntWithInf -> Bool # | |
Num IntWithInf # | |
Defined in BasicTypes (+) :: IntWithInf -> IntWithInf -> IntWithInf Source # (-) :: IntWithInf -> IntWithInf -> IntWithInf Source # (*) :: IntWithInf -> IntWithInf -> IntWithInf Source # negate :: IntWithInf -> IntWithInf Source # abs :: IntWithInf -> IntWithInf Source # signum :: IntWithInf -> IntWithInf Source # fromInteger :: Integer -> IntWithInf Source # | |
Ord IntWithInf # | |
Defined in BasicTypes compare :: IntWithInf -> IntWithInf -> Ordering # (<) :: IntWithInf -> IntWithInf -> Bool # (<=) :: IntWithInf -> IntWithInf -> Bool # (>) :: IntWithInf -> IntWithInf -> Bool # (>=) :: IntWithInf -> IntWithInf -> Bool # max :: IntWithInf -> IntWithInf -> IntWithInf # min :: IntWithInf -> IntWithInf -> IntWithInf # | |
Outputable IntWithInf # | |
Defined in BasicTypes |
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
intGtLimit :: Int -> IntWithInf -> Bool Source #
data SpliceExplicitFlag Source #
ExplicitSplice | = $(f x y) |
ImplicitSplice | = f x y, i.e. a naked top level expression |
Instances
Data SpliceExplicitFlag # | |
Defined in BasicTypes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpliceExplicitFlag -> c SpliceExplicitFlag Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SpliceExplicitFlag Source # toConstr :: SpliceExplicitFlag -> Constr Source # dataTypeOf :: SpliceExplicitFlag -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SpliceExplicitFlag) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SpliceExplicitFlag) Source # gmapT :: (forall b. Data b => b -> b) -> SpliceExplicitFlag -> SpliceExplicitFlag Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r Source # gmapQ :: (forall d. Data d => d -> u) -> SpliceExplicitFlag -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceExplicitFlag -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag Source # |
data TypeOrKind Source #
Flag to see whether we're type-checking terms or kind-checking types
Instances
Eq TypeOrKind # | |
Defined in BasicTypes (==) :: TypeOrKind -> TypeOrKind -> Bool # (/=) :: TypeOrKind -> TypeOrKind -> Bool # | |
Outputable TypeOrKind # | |
Defined in BasicTypes |
isTypeLevel :: TypeOrKind -> Bool Source #
isKindLevel :: TypeOrKind -> Bool Source #