Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- 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
- starPrec :: 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
- isNoOccInfo :: OccInfo -> Bool
- strongLoopBreaker :: OccInfo
- weakLoopBreaker :: OccInfo
- data InsideLam
- type BranchCount = Int
- oneBranch :: BranchCount
- data InterestingCxt
- 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
- competesWith :: Activation -> Activation -> Bool
- isNeverActive :: Activation -> Bool
- isAlwaysActive :: Activation -> Bool
- activeInFinalPhase :: Activation -> Bool
- activateAfterInitial :: Activation
- activateDuringFinal :: 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
data LeftOrRight Source #
Instances
Eq LeftOrRight Source # | |
Defined in GHC.Types.Basic (==) :: LeftOrRight -> LeftOrRight -> Bool # (/=) :: LeftOrRight -> LeftOrRight -> Bool # | |
Data LeftOrRight Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LeftOrRight # toConstr :: LeftOrRight -> Constr # dataTypeOf :: LeftOrRight -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LeftOrRight) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LeftOrRight) # gmapT :: (forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r # gmapQ :: (forall d. Data d => d -> u) -> LeftOrRight -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # | |
Outputable LeftOrRight Source # | |
Defined in GHC.Types.Basic | |
Binary LeftOrRight Source # | |
Defined in GHC.Utils.Binary put_ :: BinHandle -> LeftOrRight -> IO () Source # put :: BinHandle -> LeftOrRight -> IO (Bin LeftOrRight) Source # |
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 GHC.Core.Opt.Arity
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
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 Source # | |
Defined in GHC.Types.Basic (==) :: PromotionFlag -> PromotionFlag -> Bool # (/=) :: PromotionFlag -> PromotionFlag -> Bool # | |
Data PromotionFlag Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PromotionFlag # toConstr :: PromotionFlag -> Constr # dataTypeOf :: PromotionFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PromotionFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PromotionFlag) # gmapT :: (forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> PromotionFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PromotionFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # | |
Outputable PromotionFlag Source # | |
Defined in GHC.Types.Basic | |
Binary PromotionFlag Source # | |
Defined in GHC.Utils.Binary put_ :: BinHandle -> PromotionFlag -> IO () Source # put :: BinHandle -> PromotionFlag -> IO (Bin PromotionFlag) Source # |
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 Source # | |
Defined in GHC.Types.Basic (==) :: WarningTxt -> WarningTxt -> Bool # (/=) :: WarningTxt -> WarningTxt -> Bool # | |
Data WarningTxt Source # | |
Defined in GHC.Types.Basic 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 :: forall r r'. (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 # | |
Defined in GHC.Types.Basic | |
Binary WarningTxt Source # | |
Defined in GHC.Utils.Binary put_ :: BinHandle -> WarningTxt -> IO () Source # put :: BinHandle -> WarningTxt -> IO (Bin WarningTxt) Source # |
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 Source # | |
Defined in GHC.Types.Basic (==) :: StringLiteral -> StringLiteral -> Bool # (/=) :: StringLiteral -> StringLiteral -> Bool # | |
Data StringLiteral Source # | |
Defined in GHC.Types.Basic 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 :: forall r r'. (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 # | |
Defined in GHC.Types.Basic | |
Binary StringLiteral Source # | |
Defined in GHC.Utils.Binary put_ :: BinHandle -> StringLiteral -> IO () Source # put :: BinHandle -> StringLiteral -> IO (Bin StringLiteral) Source # |
Instances
Eq Fixity Source # | |
Data Fixity Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixity -> c Fixity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Fixity # toConstr :: Fixity -> Constr # dataTypeOf :: Fixity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Fixity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixity) # gmapT :: (forall b. Data b => b -> b) -> Fixity -> Fixity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r # gmapQ :: (forall d. Data d => d -> u) -> Fixity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity # | |
Outputable Fixity Source # | |
Binary Fixity Source # | |
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 Source # | |
Defined in GHC.Types.Basic (==) :: LexicalFixity -> LexicalFixity -> Bool # (/=) :: LexicalFixity -> LexicalFixity -> Bool # | |
Data LexicalFixity Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LexicalFixity -> c LexicalFixity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LexicalFixity # toConstr :: LexicalFixity -> Constr # dataTypeOf :: LexicalFixity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LexicalFixity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LexicalFixity) # gmapT :: (forall b. Data b => b -> b) -> LexicalFixity -> LexicalFixity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LexicalFixity -> r # gmapQ :: (forall d. Data d => d -> u) -> LexicalFixity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LexicalFixity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LexicalFixity -> m LexicalFixity # | |
Outputable LexicalFixity Source # | |
Defined in GHC.Types.Basic |
Recursivity Flag
Instances
Eq RecFlag Source # | |
Data RecFlag Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecFlag -> c RecFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecFlag # toConstr :: RecFlag -> Constr # dataTypeOf :: RecFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RecFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecFlag) # gmapT :: (forall b. Data b => b -> b) -> RecFlag -> RecFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> RecFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RecFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag # | |
Outputable RecFlag Source # | |
Binary RecFlag Source # | |
boolToRecFlag :: Bool -> RecFlag Source #
Instances
Eq Origin Source # | |
Data Origin Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Origin -> c Origin # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Origin # toConstr :: Origin -> Constr # dataTypeOf :: Origin -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Origin) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Origin) # gmapT :: (forall b. Data b => b -> b) -> Origin -> Origin # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r # gmapQ :: (forall d. Data d => d -> u) -> Origin -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Origin -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Origin -> m Origin # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Origin -> m Origin # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Origin -> m Origin # | |
Outputable Origin Source # | |
isGenerated :: Origin -> Bool Source #
type RuleName = FastString Source #
pprRuleName :: RuleName -> SDoc Source #
data TopLevelFlag Source #
Instances
Outputable TopLevelFlag Source # | |
Defined in GHC.Types.Basic |
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 GHC.Core.InstEnv) for a
explanation of the isSafeOverlap
field.
AnnKeywordId
:AnnOpen
'{-# OVERLAPPABLE'
or'{-# OVERLAPPING'
or'{-# OVERLAPS'
or'{-# INCOHERENT'
,AnnClose
`#-}`
,
Instances
Eq OverlapFlag Source # | |
Defined in GHC.Types.Basic (==) :: OverlapFlag -> OverlapFlag -> Bool # (/=) :: OverlapFlag -> OverlapFlag -> Bool # | |
Data OverlapFlag Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverlapFlag -> c OverlapFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverlapFlag # toConstr :: OverlapFlag -> Constr # dataTypeOf :: OverlapFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverlapFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverlapFlag) # gmapT :: (forall b. Data b => b -> b) -> OverlapFlag -> OverlapFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> OverlapFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlapFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # | |
Outputable OverlapFlag Source # | |
Defined in GHC.Types.Basic | |
Binary OverlapFlag Source # | |
Defined in GHC.Utils.Binary put_ :: BinHandle -> OverlapFlag -> IO () Source # put :: BinHandle -> OverlapFlag -> IO (Bin OverlapFlag) Source # |
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 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 Source # | |
Defined in GHC.Types.Basic (==) :: OverlapMode -> OverlapMode -> Bool # (/=) :: OverlapMode -> OverlapMode -> Bool # | |
Data OverlapMode Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverlapMode -> c OverlapMode # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverlapMode # toConstr :: OverlapMode -> Constr # dataTypeOf :: OverlapMode -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverlapMode) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverlapMode) # gmapT :: (forall b. Data b => b -> b) -> OverlapMode -> OverlapMode # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverlapMode -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverlapMode -> r # gmapQ :: (forall d. Data d => d -> u) -> OverlapMode -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlapMode -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # | |
Outputable OverlapMode Source # | |
Defined in GHC.Types.Basic | |
Binary OverlapMode Source # | |
Defined in GHC.Utils.Binary put_ :: BinHandle -> OverlapMode -> IO () Source # put :: BinHandle -> OverlapMode -> IO (Bin OverlapMode) Source # |
hasOverlappingFlag :: OverlapMode -> Bool Source #
hasIncoherentFlag :: OverlapMode -> Bool Source #
Instances
Eq Boxity Source # | |
Data Boxity Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Boxity -> c Boxity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Boxity # toConstr :: Boxity -> Constr # dataTypeOf :: Boxity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Boxity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Boxity) # gmapT :: (forall b. Data b => b -> b) -> Boxity -> Boxity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r # gmapQ :: (forall d. Data d => d -> u) -> Boxity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Boxity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity # | |
Outputable Boxity Source # | |
A general-purpose pretty-printing precedence type.
Instances
Eq TupleSort Source # | |
Data TupleSort Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TupleSort -> c TupleSort # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TupleSort # toConstr :: TupleSort -> Constr # dataTypeOf :: TupleSort -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TupleSort) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TupleSort) # gmapT :: (forall b. Data b => b -> b) -> TupleSort -> TupleSort # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TupleSort -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TupleSort -> r # gmapQ :: (forall d. Data d => d -> u) -> TupleSort -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TupleSort -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # | |
Outputable TupleSort Source # | |
Binary TupleSort Source # | |
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.
See also Note [OneShotInfo overview] above.
NoOneShotInfo | No information |
OneShotLam | The lambda is applied at most once. |
Instances
Eq OneShotInfo Source # | |
Defined in GHC.Types.Basic (==) :: OneShotInfo -> OneShotInfo -> Bool # (/=) :: OneShotInfo -> OneShotInfo -> Bool # | |
Outputable OneShotInfo Source # | |
Defined in GHC.Types.Basic |
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 #
isNoOccInfo :: OccInfo -> Bool Source #
Inside Lambda
IsInsideLam | Occurs inside a non-linear lambda Substituting a redex for this occurrence is dangerous because it might duplicate work. |
NotInsideLam |
type BranchCount = Int Source #
data InterestingCxt Source #
Interesting Context
IsInteresting | Function: is applied Data value: scrutinised by a case with at least one non-DEFAULT branch |
NotInteresting |
Instances
Eq InterestingCxt Source # | |
Defined in GHC.Types.Basic (==) :: InterestingCxt -> InterestingCxt -> Bool # (/=) :: InterestingCxt -> InterestingCxt -> Bool # | |
Semigroup InterestingCxt Source # | If there is any |
Defined in GHC.Types.Basic (<>) :: InterestingCxt -> InterestingCxt -> InterestingCxt # sconcat :: NonEmpty InterestingCxt -> InterestingCxt # stimes :: Integral b => b -> InterestingCxt -> InterestingCxt # | |
Monoid InterestingCxt Source # | |
Defined in GHC.Types.Basic mappend :: InterestingCxt -> InterestingCxt -> InterestingCxt # mconcat :: [InterestingCxt] -> InterestingCxt # |
data TailCallInfo Source #
Instances
Eq TailCallInfo Source # | |
Defined in GHC.Types.Basic (==) :: TailCallInfo -> TailCallInfo -> Bool # (/=) :: TailCallInfo -> TailCallInfo -> Bool # | |
Outputable TailCallInfo Source # | |
Defined in GHC.Types.Basic |
tailCallInfo :: OccInfo -> TailCallInfo Source #
zapOccTailCallInfo :: OccInfo -> OccInfo Source #
isAlwaysTailCalled :: OccInfo -> Bool Source #
data DefMethSpec ty Source #
Default Method Specification
Instances
Outputable (DefMethSpec ty) Source # | |
Defined in GHC.Types.Basic | |
Binary (DefMethSpec IfaceType) Source # | |
Defined in GHC.Iface.Type |
data CompilerPhase Source #
Instances
Eq CompilerPhase Source # | |
Defined in GHC.Types.Basic (==) :: CompilerPhase -> CompilerPhase -> Bool # (/=) :: CompilerPhase -> CompilerPhase -> Bool # | |
Outputable CompilerPhase Source # | |
Defined in GHC.Types.Basic |
data Activation Source #
AlwaysActive | |
ActiveBefore SourceText PhaseNum | |
ActiveAfter SourceText PhaseNum | |
FinalActive | |
NeverActive |
Instances
Eq Activation Source # | |
Defined in GHC.Types.Basic (==) :: Activation -> Activation -> Bool # (/=) :: Activation -> Activation -> Bool # | |
Data Activation Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Activation -> c Activation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Activation # toConstr :: Activation -> Constr # dataTypeOf :: Activation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Activation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Activation) # gmapT :: (forall b. Data b => b -> b) -> Activation -> Activation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Activation -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Activation -> r # gmapQ :: (forall d. Data d => d -> u) -> Activation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Activation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Activation -> m Activation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Activation -> m Activation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Activation -> m Activation # | |
Outputable Activation Source # | |
Defined in GHC.Types.Basic | |
Binary Activation Source # | |
Defined in GHC.Utils.Binary put_ :: BinHandle -> Activation -> IO () Source # put :: BinHandle -> Activation -> IO (Bin Activation) Source # |
isActive :: CompilerPhase -> Activation -> Bool Source #
competesWith :: Activation -> Activation -> Bool Source #
isNeverActive :: Activation -> Bool Source #
isAlwaysActive :: Activation -> Bool Source #
activeInFinalPhase :: Activation -> Bool Source #
data RuleMatchInfo Source #
Rule Match Information
Instances
isConLike :: RuleMatchInfo -> Bool Source #
isFunLike :: RuleMatchInfo -> Bool Source #
data InlineSpec Source #
Inline Specification
Instances
Eq InlineSpec Source # | |
Defined in GHC.Types.Basic (==) :: InlineSpec -> InlineSpec -> Bool # (/=) :: InlineSpec -> InlineSpec -> Bool # | |
Data InlineSpec Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InlineSpec -> c InlineSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InlineSpec # toConstr :: InlineSpec -> Constr # dataTypeOf :: InlineSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InlineSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlineSpec) # gmapT :: (forall b. Data b => b -> b) -> InlineSpec -> InlineSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlineSpec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlineSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> InlineSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InlineSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec # | |
Show InlineSpec Source # | |
Defined in GHC.Types.Basic showsPrec :: Int -> InlineSpec -> ShowS # show :: InlineSpec -> String # showList :: [InlineSpec] -> ShowS # | |
Outputable InlineSpec Source # | |
Defined in GHC.Types.Basic | |
Binary InlineSpec Source # | |
Defined in GHC.Utils.Binary put_ :: BinHandle -> InlineSpec -> IO () Source # put :: BinHandle -> InlineSpec -> IO (Bin InlineSpec) Source # |
noUserInlineSpec :: InlineSpec -> Bool Source #
data InlinePragma Source #
InlinePragma | |
|
Instances
Eq InlinePragma Source # | |
Defined in GHC.Types.Basic (==) :: InlinePragma -> InlinePragma -> Bool # (/=) :: InlinePragma -> InlinePragma -> Bool # | |
Data InlinePragma Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InlinePragma -> c InlinePragma # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InlinePragma # toConstr :: InlinePragma -> Constr # dataTypeOf :: InlinePragma -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InlinePragma) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlinePragma) # gmapT :: (forall b. Data b => b -> b) -> InlinePragma -> InlinePragma # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma -> r # gmapQ :: (forall d. Data d => d -> u) -> InlinePragma -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InlinePragma -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma # | |
Outputable InlinePragma Source # | |
Defined in GHC.Types.Basic | |
Binary InlinePragma Source # | |
Defined in GHC.Utils.Binary put_ :: BinHandle -> InlinePragma -> IO () Source # put :: BinHandle -> InlinePragma -> IO (Bin InlinePragma) Source # |
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 Source # | |
Defined in GHC.Types.Basic |
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 Source # | |
Defined in GHC.Types.Basic (==) :: SourceText -> SourceText -> Bool # (/=) :: SourceText -> SourceText -> Bool # | |
Data SourceText Source # | |
Defined in GHC.Types.Basic gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceText -> c SourceText # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceText # toConstr :: SourceText -> Constr # dataTypeOf :: SourceText -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SourceText) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceText) # gmapT :: (forall b. Data b => b -> b) -> SourceText -> SourceText # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceText -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceText -> r # gmapQ :: (forall d. Data d => d -> u) -> SourceText -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceText -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceText -> m SourceText # | |
Show SourceText Source # | |
Defined in GHC.Types.Basic showsPrec :: Int -> SourceText -> ShowS # show :: SourceText -> String # showList :: [SourceText] -> ShowS # | |
Outputable SourceText Source # | |
Defined in GHC.Types.Basic | |
Binary SourceText Source # | |
Defined in GHC.Utils.Binary put_ :: BinHandle -> SourceText -> IO () Source # put :: BinHandle -> SourceText -> IO (Bin SourceText) Source # |
pprWithSourceText :: SourceText -> SDoc -> SDoc Source #
Special combinator for showing string literals.
data IntWithInf Source #
An integer or infinity
Instances
Eq IntWithInf Source # | |
Defined in GHC.Types.Basic (==) :: IntWithInf -> IntWithInf -> Bool # (/=) :: IntWithInf -> IntWithInf -> Bool # | |
Num IntWithInf Source # | |
Defined in GHC.Types.Basic (+) :: IntWithInf -> IntWithInf -> IntWithInf # (-) :: IntWithInf -> IntWithInf -> IntWithInf # (*) :: IntWithInf -> IntWithInf -> IntWithInf # negate :: IntWithInf -> IntWithInf # abs :: IntWithInf -> IntWithInf # signum :: IntWithInf -> IntWithInf # fromInteger :: Integer -> IntWithInf # | |
Ord IntWithInf Source # | |
Defined in GHC.Types.Basic 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 Source # | |
Defined in GHC.Types.Basic |
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 Source # | |
Defined in GHC.Types.Basic 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 :: forall r r'. (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
Instances
Eq TypeOrKind Source # | |
Defined in GHC.Types.Basic (==) :: TypeOrKind -> TypeOrKind -> Bool # (/=) :: TypeOrKind -> TypeOrKind -> Bool # | |
Outputable TypeOrKind Source # | |
Defined in GHC.Types.Basic |
isTypeLevel :: TypeOrKind -> Bool Source #
isKindLevel :: TypeOrKind -> Bool Source #