| Safe Haskell | Ignore |
|---|---|
| Language | GHC2021 |
GHC.Types.Basic
Synopsis
- data LeftOrRight
- pickLR :: LeftOrRight -> (a, a) -> a
- type ConTag = Int
- type ConTagZ = Int
- fIRST_TAG :: ConTag
- type Arity = Int
- type VisArity = Int
- type RepArity = Int
- type JoinArity = Int
- type FullArgCount = Int
- data JoinPointHood
- = JoinPoint !Int
- | NotJoinPoint
- isJoinPoint :: JoinPointHood -> Bool
- data Alignment
- mkAlignment :: Int -> Alignment
- alignmentOf :: Int -> Alignment
- alignmentBytes :: Alignment -> Int
- data PromotionFlag
- isPromoted :: PromotionFlag -> Bool
- data FunctionOrData
- = IsFunction
- | IsData
- data RecFlag
- isRec :: RecFlag -> Bool
- isNonRec :: RecFlag -> Bool
- boolToRecFlag :: Bool -> RecFlag
- data Origin
- isGenerated :: Origin -> Bool
- data DoPmc
- requiresPMC :: Origin -> Bool
- data GenReason
- isDoExpansionGenerated :: Origin -> Bool
- doExpansionFlavour :: Origin -> Maybe HsDoFlavour
- doExpansionOrigin :: HsDoFlavour -> Origin
- 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
- hasNonCanonicalFlag :: OverlapMode -> Bool
- data Boxity
- isBoxed :: Boxity -> Bool
- data CbvMark
- isMarkedCbv :: CbvMark -> Bool
- newtype PprPrec = PprPrec Int
- topPrec :: PprPrec
- sigPrec :: PprPrec
- opPrec :: PprPrec
- funPrec :: PprPrec
- starPrec :: PprPrec
- appPrec :: PprPrec
- maxPrec :: PprPrec
- maybeParen :: PprPrec -> PprPrec -> SDoc -> SDoc
- data TupleSort
- tupleSortBoxity :: TupleSort -> Boxity
- boxityTupleSort :: Boxity -> TupleSort
- tupleParens :: TupleSort -> SDoc -> SDoc
- data UnboxedTupleOrSum
- unboxedTupleOrSumExtension :: UnboxedTupleOrSum -> Extension
- 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
- beginPhase :: Activation -> CompilerPhase
- nextPhase :: CompilerPhase -> CompilerPhase
- laterPhase :: CompilerPhase -> CompilerPhase -> CompilerPhase
- data Activation
- isActive :: CompilerPhase -> Activation -> Bool
- competesWith :: Activation -> Activation -> Bool
- isNeverActive :: Activation -> Bool
- isAlwaysActive :: Activation -> Bool
- activeInFinalPhase :: Activation -> Bool
- activateAfterInitial :: Activation
- activateDuringFinal :: Activation
- activeAfter :: CompilerPhase -> 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
- isNoInlinePragma :: InlinePragma -> Bool
- isOpaquePragma :: InlinePragma -> Bool
- isAnyInlinePragma :: InlinePragma -> Bool
- alwaysInlineConLikePragma :: InlinePragma
- inlinePragmaSource :: InlinePragma -> SourceText
- inlinePragmaName :: InlineSpec -> SDoc
- inlineSpecSource :: InlineSpec -> SourceText
- 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 UnfoldingSource
- isStableSource :: UnfoldingSource -> Bool
- isStableUserSource :: UnfoldingSource -> Bool
- isStableSystemSource :: UnfoldingSource -> Bool
- isCompulsorySource :: UnfoldingSource -> Bool
- data SuccessFlag
- succeeded :: SuccessFlag -> Bool
- failed :: SuccessFlag -> Bool
- successIf :: Bool -> SuccessFlag
- data IntWithInf
- infinity :: IntWithInf
- treatZeroAsInf :: Int -> IntWithInf
- subWithInf :: IntWithInf -> Int -> IntWithInf
- mkIntWithInf :: Int -> IntWithInf
- intGtLimit :: Int -> IntWithInf -> Bool
- data TypeOrKind
- isTypeLevel :: TypeOrKind -> Bool
- isKindLevel :: TypeOrKind -> Bool
- data Levity
- mightBeLifted :: Maybe Levity -> Bool
- mightBeUnlifted :: Maybe Levity -> Bool
- data TypeOrConstraint
- data TyConFlavour tc
- data TypeOrData
- tyConFlavourAssoc_maybe :: TyConFlavour tc -> Maybe tc
- data NonStandardDefaultingStrategy
- data DefaultingStrategy
- defaultNonStandardTyVars :: DefaultingStrategy -> Bool
- data ForeignSrcLang
Documentation
data LeftOrRight #
Instances
| Data LeftOrRight # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LeftOrRight -> c LeftOrRight # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LeftOrRight # toConstr :: LeftOrRight -> Constr # dataTypeOf :: LeftOrRight -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LeftOrRight) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LeftOrRight) # gmapT :: (forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r # gmapQ :: (forall d. Data d => d -> u) -> LeftOrRight -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight # | |
| Binary LeftOrRight # | |
Defined in GHC.Types.Basic Methods put_ :: BinHandle -> LeftOrRight -> IO () # put :: BinHandle -> LeftOrRight -> IO (Bin LeftOrRight) # get :: BinHandle -> IO LeftOrRight # | |
| Outputable LeftOrRight # | |
Defined in GHC.Types.Basic Methods ppr :: LeftOrRight -> SDoc # | |
| Eq LeftOrRight # | |
Defined in GHC.Types.Basic | |
pickLR :: LeftOrRight -> (a, a) -> a #
A *one-index* constructor tag
Type of the tags associated with each constructor possibility or superclass selector
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
Syntactic (visibility) arity, i.e. the number of visible arguments. See Note [Visibility and arity]
Representation Arity
The number of represented arguments that can be applied to a value before it does "real work". So: fib 100 has representation arity 0 x -> fib x has representation arity 1 (# x, y #) -> fib (x + y) has representation arity 2
The number of arguments that a join point takes. Unlike the arity of a function, this is a purely syntactic property and is fixed when the join point is created (or converted from a value). Both type and value arguments are counted.
type FullArgCount = Int #
FullArgCount is the number of type or value arguments in an application, or the number of type or value binders in a lambda. Note: it includes both type and value arguments!
data JoinPointHood #
Constructors
| JoinPoint !Int | |
| NotJoinPoint |
Instances
| NFData JoinPointHood # | |
Defined in GHC.Utils.Outputable Methods rnf :: JoinPointHood -> () # | |
| Binary JoinPointHood # | |
Defined in GHC.Utils.Binary Methods put_ :: BinHandle -> JoinPointHood -> IO () # put :: BinHandle -> JoinPointHood -> IO (Bin JoinPointHood) # get :: BinHandle -> IO JoinPointHood # | |
| Outputable JoinPointHood # | |
Defined in GHC.Utils.Outputable Methods ppr :: JoinPointHood -> SDoc # | |
| Eq JoinPointHood # | |
Defined in GHC.Utils.Outputable Methods (==) :: JoinPointHood -> JoinPointHood -> Bool # (/=) :: JoinPointHood -> JoinPointHood -> Bool # | |
isJoinPoint :: JoinPointHood -> Bool #
A power-of-two alignment
Instances
| Outputable Alignment # | |
Defined in GHC.Types.Basic | |
| Eq Alignment # | |
| Ord Alignment # | |
| OutputableP env Alignment # | |
Defined in GHC.Types.Basic | |
mkAlignment :: Int -> Alignment #
alignmentOf :: Int -> Alignment #
alignmentBytes :: Alignment -> Int #
data PromotionFlag #
Constructors
| NotPromoted | |
| IsPromoted |
Instances
| Data PromotionFlag # | |
Defined in Language.Haskell.Syntax.Type Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PromotionFlag -> c PromotionFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PromotionFlag # toConstr :: PromotionFlag -> Constr # dataTypeOf :: PromotionFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PromotionFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PromotionFlag) # gmapT :: (forall b. Data b => b -> b) -> PromotionFlag -> PromotionFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PromotionFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> PromotionFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PromotionFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PromotionFlag -> m PromotionFlag # | |
| Binary PromotionFlag # | |
Defined in GHC.Types.Basic Methods put_ :: BinHandle -> PromotionFlag -> IO () # put :: BinHandle -> PromotionFlag -> IO (Bin PromotionFlag) # get :: BinHandle -> IO PromotionFlag # | |
| Outputable PromotionFlag # | |
Defined in GHC.Types.Basic Methods ppr :: PromotionFlag -> SDoc # | |
| Eq PromotionFlag # | |
Defined in Language.Haskell.Syntax.Type Methods (==) :: PromotionFlag -> PromotionFlag -> Bool # (/=) :: PromotionFlag -> PromotionFlag -> Bool # | |
isPromoted :: PromotionFlag -> Bool #
data FunctionOrData #
Constructors
| IsFunction | |
| IsData |
Instances
Recursivity Flag
Constructors
| Recursive | |
| NonRecursive |
Instances
| Data RecFlag # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecFlag -> c RecFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecFlag # toConstr :: RecFlag -> Constr # dataTypeOf :: RecFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RecFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecFlag) # gmapT :: (forall b. Data b => b -> b) -> RecFlag -> RecFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> RecFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RecFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag # | |
| Binary RecFlag # | |
| Outputable RecFlag # | |
Defined in GHC.Types.Basic | |
| Eq RecFlag # | |
boolToRecFlag :: Bool -> RecFlag #
Was this piece of code user-written or generated by the compiler?
See Note [Generated code and pattern-match checking].
Constructors
| FromSource | |
| Generated GenReason DoPmc |
Instances
| Data Origin # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Origin -> c Origin # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Origin # toConstr :: Origin -> Constr # dataTypeOf :: Origin -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Origin) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Origin) # gmapT :: (forall b. Data b => b -> b) -> Origin -> Origin # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r # gmapQ :: (forall d. Data d => d -> u) -> Origin -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Origin -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Origin -> m Origin # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Origin -> m Origin # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Origin -> m Origin # | |
| Outputable Origin # | |
Defined in GHC.Types.Basic | |
| Eq Origin # | |
isGenerated :: Origin -> Bool #
Whether to run pattern-match checks in generated code.
See Note [Generated code and pattern-match checking].
Instances
| Data DoPmc # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DoPmc -> c DoPmc # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DoPmc # dataTypeOf :: DoPmc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DoPmc) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DoPmc) # gmapT :: (forall b. Data b => b -> b) -> DoPmc -> DoPmc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DoPmc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DoPmc -> r # gmapQ :: (forall d. Data d => d -> u) -> DoPmc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DoPmc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DoPmc -> m DoPmc # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DoPmc -> m DoPmc # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DoPmc -> m DoPmc # | |
| Outputable DoPmc # | |
Defined in GHC.Types.Basic | |
| Eq DoPmc # | |
requiresPMC :: Origin -> Bool #
Does this Origin require us to run pattern-match checking,
or should we skip these checks?
See Note [Generated code and pattern-match checking].
This metadata stores the information as to why was the piece of code generated
It is useful for generating the right error context
See Part 3 in Note [Expanding HsDo with XXExprGhcRn] in Do
Constructors
| DoExpansion HsDoFlavour | |
| OtherExpansion |
Instances
| Data GenReason # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenReason -> c GenReason # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GenReason # toConstr :: GenReason -> Constr # dataTypeOf :: GenReason -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GenReason) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GenReason) # gmapT :: (forall b. Data b => b -> b) -> GenReason -> GenReason # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenReason -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenReason -> r # gmapQ :: (forall d. Data d => d -> u) -> GenReason -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> GenReason -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenReason -> m GenReason # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenReason -> m GenReason # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenReason -> m GenReason # | |
| Outputable GenReason # | |
Defined in GHC.Types.Basic | |
| Eq GenReason # | |
isDoExpansionGenerated :: Origin -> Bool #
doExpansionOrigin :: HsDoFlavour -> Origin #
type RuleName = FastString #
pprRuleName :: RuleName -> SDoc #
data TopLevelFlag #
Constructors
| TopLevel | |
| NotTopLevel |
Instances
| Data TopLevelFlag # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TopLevelFlag -> c TopLevelFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TopLevelFlag # toConstr :: TopLevelFlag -> Constr # dataTypeOf :: TopLevelFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TopLevelFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TopLevelFlag) # gmapT :: (forall b. Data b => b -> b) -> TopLevelFlag -> TopLevelFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TopLevelFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TopLevelFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> TopLevelFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TopLevelFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag # | |
| Outputable TopLevelFlag # | |
Defined in GHC.Types.Basic Methods ppr :: TopLevelFlag -> SDoc # | |
isTopLevel :: TopLevelFlag -> Bool #
isNotTopLevel :: TopLevelFlag -> Bool #
data OverlapFlag #
The semantics allowed for overlapping instances for a particular
instance. See Note [Safe Haskell isSafeOverlap] in GHC.Core.InstEnv for a
explanation of the isSafeOverlap field.
AnnKeywordId:AnnOpen'{-# OVERLAPPABLE'or'{-# OVERLAPPING'or'{-# OVERLAPS'or'{-# INCOHERENT',AnnClose`#-}`,
Constructors
| OverlapFlag | |
Fields | |
Instances
| Data OverlapFlag # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverlapFlag -> c OverlapFlag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverlapFlag # toConstr :: OverlapFlag -> Constr # dataTypeOf :: OverlapFlag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverlapFlag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverlapFlag) # gmapT :: (forall b. Data b => b -> b) -> OverlapFlag -> OverlapFlag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r # gmapQ :: (forall d. Data d => d -> u) -> OverlapFlag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlapFlag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag # | |
| Binary OverlapFlag # | |
Defined in GHC.Types.Basic Methods put_ :: BinHandle -> OverlapFlag -> IO () # put :: BinHandle -> OverlapFlag -> IO (Bin OverlapFlag) # get :: BinHandle -> IO OverlapFlag # | |
| Outputable OverlapFlag # | |
Defined in GHC.Types.Basic Methods ppr :: OverlapFlag -> SDoc # | |
| Eq OverlapFlag # | |
Defined in GHC.Types.Basic | |
data OverlapMode #
Constructors
| 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 {-# OVERLAPPABLE #-} Foo [a] Since the second instance has the Overlappable flag, the first instance will be chosen (otherwise its ambiguous which to choose) |
| Overlapping SourceText | Silently ignore any more general instances that may be used to solve the constraint. Example: constraint (Foo [Int]) instance {-# OVERLAPPING #-} Foo [Int] instance Foo [a] Since the first instance has the Overlapping flag, the second---more general---instance will be ignored (otherwise it is ambiguous which to choose) |
| Overlaps SourceText | Equivalent to having both |
| 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 |
| NonCanonical SourceText | Behave like Incoherent, but the instance choice is observable by the program behaviour. See Note [Coherence and specialisation: overview]. We don't have surface syntax for the distinction between
Incoherent and NonCanonical instances; instead, the flag
`-f{no-}specialise-incoherents` (on by default) controls
whether |
Instances
| Data OverlapMode # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverlapMode -> c OverlapMode # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverlapMode # toConstr :: OverlapMode -> Constr # dataTypeOf :: OverlapMode -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverlapMode) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverlapMode) # gmapT :: (forall b. Data b => b -> b) -> OverlapMode -> OverlapMode # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverlapMode -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverlapMode -> r # gmapQ :: (forall d. Data d => d -> u) -> OverlapMode -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlapMode -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode # | |
| Binary OverlapMode # | |
Defined in GHC.Types.Basic Methods put_ :: BinHandle -> OverlapMode -> IO () # put :: BinHandle -> OverlapMode -> IO (Bin OverlapMode) # get :: BinHandle -> IO OverlapMode # | |
| Outputable OverlapMode # | |
Defined in GHC.Types.Basic Methods ppr :: OverlapMode -> SDoc # | |
| Eq OverlapMode # | |
Defined in GHC.Types.Basic | |
| type Anno OverlapMode # | |
Defined in GHC.Hs.Decls | |
| type Anno OverlapMode # | |
Defined in GHC.Hs.Decls | |
hasOverlappingFlag :: OverlapMode -> Bool #
hasOverlappableFlag :: OverlapMode -> Bool #
hasIncoherentFlag :: OverlapMode -> Bool #
hasNonCanonicalFlag :: OverlapMode -> Bool #
Instances
| Data Boxity # | |
Defined in Language.Haskell.Syntax.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Boxity -> c Boxity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Boxity # toConstr :: Boxity -> Constr # dataTypeOf :: Boxity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Boxity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Boxity) # gmapT :: (forall b. Data b => b -> b) -> Boxity -> Boxity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r # gmapQ :: (forall d. Data d => d -> u) -> Boxity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Boxity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity # | |
| Binary Boxity # | |
| Outputable Boxity # | |
Defined in GHC.Types.Basic | |
| Eq Boxity # | |
Should an argument be passed evaluated *and* tagged.
Constructors
| MarkedCbv | |
| NotMarkedCbv |
Instances
| Binary CbvMark # | |
| Outputable CbvMark # | |
Defined in GHC.Types.Basic | |
| Eq CbvMark # | |
isMarkedCbv :: CbvMark -> Bool #
A general-purpose pretty-printing precedence type.
Constructors
| BoxedTuple | |
| UnboxedTuple | |
| ConstraintTuple |
Instances
| Data TupleSort # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TupleSort -> c TupleSort # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TupleSort # toConstr :: TupleSort -> Constr # dataTypeOf :: TupleSort -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TupleSort) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TupleSort) # gmapT :: (forall b. Data b => b -> b) -> TupleSort -> TupleSort # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TupleSort -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TupleSort -> r # gmapQ :: (forall d. Data d => d -> u) -> TupleSort -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TupleSort -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort # | |
| Binary TupleSort # | |
| Outputable TupleSort # | |
Defined in GHC.Types.Basic | |
| Eq TupleSort # | |
tupleSortBoxity :: TupleSort -> Boxity #
boxityTupleSort :: Boxity -> TupleSort #
tupleParens :: TupleSort -> SDoc -> SDoc #
data UnboxedTupleOrSum #
Are we dealing with an unboxed tuple or an unboxed sum?
Used when validity checking, see check_ubx_tuple_or_sum.
Constructors
| UnboxedTupleType | |
| UnboxedSumType |
Instances
| Outputable UnboxedTupleOrSum # | |
Defined in GHC.Types.Basic Methods ppr :: UnboxedTupleOrSum -> SDoc # | |
| Eq UnboxedTupleOrSum # | |
Defined in GHC.Types.Basic Methods (==) :: UnboxedTupleOrSum -> UnboxedTupleOrSum -> Bool # (/=) :: UnboxedTupleOrSum -> UnboxedTupleOrSum -> Bool # | |
Arguments
| :: (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 #
If the Id is a lambda-bound variable then it may have lambda-bound
variable info. Sometimes we know whether the lambda binding this variable
is a "one-shot" lambda; that is, whether it is applied at most once.
This information may be useful in optimisation, as computations may safely be floated inside such a lambda without risk of duplicating work.
See also Note [OneShotInfo overview] above.
Constructors
| NoOneShotInfo | No information |
| OneShotLam | The lambda is applied at most once. |
Instances
| Outputable OneShotInfo # | |
Defined in GHC.Types.Basic Methods ppr :: OneShotInfo -> SDoc # | |
| Eq OneShotInfo # | |
Defined in GHC.Types.Basic | |
noOneShotInfo :: OneShotInfo #
It is always safe to assume that an Id has no lambda-bound variable information
hasNoOneShotInfo :: OneShotInfo -> Bool #
isOneShotInfo :: OneShotInfo -> Bool #
bestOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo #
worstOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo #
identifier Occurrence Information
Constructors
| ManyOccs | There are many occurrences, or unknown occurrences |
Fields
| |
| IAmDead | Marks unused variables. Sometimes useful for lambda and case-bound variables. |
| OneOcc | Occurs exactly once (per branch), not inside a rule |
Fields
| |
| IAmALoopBreaker | This identifier breaks a loop of mutually recursive functions. The field marks whether it is only a loop breaker due to a reference in a rule |
Fields
| |
seqOccInfo :: OccInfo -> () #
zapFragileOcc :: OccInfo -> OccInfo #
isStrongLoopBreaker :: OccInfo -> Bool #
isWeakLoopBreaker :: OccInfo -> Bool #
isManyOccs :: OccInfo -> Bool #
isNoOccInfo :: OccInfo -> Bool #
Inside Lambda
Constructors
| IsInsideLam | Occurs inside a non-linear lambda Substituting a redex for this occurrence is dangerous because it might duplicate work. |
| NotInsideLam |
type BranchCount = Int #
data InterestingCxt #
Interesting Context
Constructors
| IsInteresting | Function: is applied Data value: scrutinised by a case with at least one non-DEFAULT branch |
| NotInteresting |
Instances
| Monoid InterestingCxt # | |
Defined in GHC.Types.Basic Methods mappend :: InterestingCxt -> InterestingCxt -> InterestingCxt # mconcat :: [InterestingCxt] -> InterestingCxt # | |
| Semigroup InterestingCxt # | If there is any |
Defined in GHC.Types.Basic Methods (<>) :: InterestingCxt -> InterestingCxt -> InterestingCxt # sconcat :: NonEmpty InterestingCxt -> InterestingCxt # stimes :: Integral b => b -> InterestingCxt -> InterestingCxt # | |
| Eq InterestingCxt # | |
Defined in GHC.Types.Basic Methods (==) :: InterestingCxt -> InterestingCxt -> Bool # (/=) :: InterestingCxt -> InterestingCxt -> Bool # | |
data TailCallInfo #
Constructors
| AlwaysTailCalled !JoinArity | |
| NoTailCallInfo |
Instances
| Outputable TailCallInfo # | |
Defined in GHC.Types.Basic Methods ppr :: TailCallInfo -> SDoc # | |
| Eq TailCallInfo # | |
Defined in GHC.Types.Basic | |
tailCallInfo :: OccInfo -> TailCallInfo #
zapOccTailCallInfo :: OccInfo -> OccInfo #
isAlwaysTailCalled :: OccInfo -> Bool #
data DefMethSpec ty #
Default Method Specification
Instances
| Binary (DefMethSpec IfaceType) # | |
Defined in GHC.Iface.Type | |
| Outputable (DefMethSpec ty) # | |
Defined in GHC.Types.Basic Methods ppr :: DefMethSpec ty -> SDoc # | |
Constructors
| NotSwapped | |
| IsSwapped |
Instances
| Outputable SwapFlag # | |
Defined in GHC.Types.Basic | |
data CompilerPhase #
Constructors
| InitialPhase | |
| Phase PhaseNum | |
| FinalPhase |
Instances
| Outputable CompilerPhase # | |
Defined in GHC.Types.Basic Methods ppr :: CompilerPhase -> SDoc # | |
| Eq CompilerPhase # | |
Defined in GHC.Types.Basic Methods (==) :: CompilerPhase -> CompilerPhase -> Bool # (/=) :: CompilerPhase -> CompilerPhase -> Bool # | |
beginPhase :: Activation -> CompilerPhase #
nextPhase :: CompilerPhase -> CompilerPhase #
laterPhase :: CompilerPhase -> CompilerPhase -> CompilerPhase #
data Activation #
Constructors
| AlwaysActive | |
| ActiveBefore SourceText PhaseNum | |
| ActiveAfter SourceText PhaseNum | |
| FinalActive | |
| NeverActive |
Instances
| Data Activation # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Activation -> c Activation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Activation # toConstr :: Activation -> Constr # dataTypeOf :: Activation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Activation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Activation) # gmapT :: (forall b. Data b => b -> b) -> Activation -> Activation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Activation -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Activation -> r # gmapQ :: (forall d. Data d => d -> u) -> Activation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Activation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Activation -> m Activation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Activation -> m Activation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Activation -> m Activation # | |
| Binary Activation # | |
Defined in GHC.Types.Basic Methods put_ :: BinHandle -> Activation -> IO () # put :: BinHandle -> Activation -> IO (Bin Activation) # get :: BinHandle -> IO Activation # | |
| Outputable Activation # | |
Defined in GHC.Types.Basic Methods ppr :: Activation -> SDoc # | |
| Eq Activation # | |
Defined in GHC.Types.Basic | |
isActive :: CompilerPhase -> Activation -> Bool #
competesWith :: Activation -> Activation -> Bool #
isNeverActive :: Activation -> Bool #
isAlwaysActive :: Activation -> Bool #
activeInFinalPhase :: Activation -> Bool #
activeAfter :: CompilerPhase -> Activation #
data RuleMatchInfo #
Rule Match Information
Instances
isConLike :: RuleMatchInfo -> Bool #
isFunLike :: RuleMatchInfo -> Bool #
data InlineSpec #
Inline Specification
Constructors
| Inline SourceText | |
| Inlinable SourceText | |
| NoInline SourceText | |
| Opaque SourceText | |
| NoUserInlinePrag |
Instances
| Data InlineSpec # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InlineSpec -> c InlineSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InlineSpec # toConstr :: InlineSpec -> Constr # dataTypeOf :: InlineSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InlineSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlineSpec) # gmapT :: (forall b. Data b => b -> b) -> InlineSpec -> InlineSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlineSpec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlineSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> InlineSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InlineSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec # | |
| Show InlineSpec # | |
Defined in GHC.Types.Basic Methods showsPrec :: Int -> InlineSpec -> ShowS # show :: InlineSpec -> String # showList :: [InlineSpec] -> ShowS # | |
| Binary InlineSpec # | |
Defined in GHC.Types.Basic Methods put_ :: BinHandle -> InlineSpec -> IO () # put :: BinHandle -> InlineSpec -> IO (Bin InlineSpec) # get :: BinHandle -> IO InlineSpec # | |
| Outputable InlineSpec # | |
Defined in GHC.Types.Basic Methods ppr :: InlineSpec -> SDoc # | |
| Eq InlineSpec # | |
Defined in GHC.Types.Basic | |
noUserInlineSpec :: InlineSpec -> Bool #
data InlinePragma #
Constructors
| InlinePragma | |
Fields
| |
Instances
| Data InlinePragma # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InlinePragma -> c InlinePragma # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InlinePragma # toConstr :: InlinePragma -> Constr # dataTypeOf :: InlinePragma -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InlinePragma) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlinePragma) # gmapT :: (forall b. Data b => b -> b) -> InlinePragma -> InlinePragma # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma -> r # gmapQ :: (forall d. Data d => d -> u) -> InlinePragma -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InlinePragma -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma # | |
| Binary InlinePragma # | |
Defined in GHC.Types.Basic Methods put_ :: BinHandle -> InlinePragma -> IO () # put :: BinHandle -> InlinePragma -> IO (Bin InlinePragma) # get :: BinHandle -> IO InlinePragma # | |
| Outputable InlinePragma # | |
Defined in GHC.Types.Basic Methods ppr :: InlinePragma -> SDoc # | |
| Eq InlinePragma # | |
Defined in GHC.Types.Basic | |
isInlinePragma :: InlinePragma -> Bool #
isInlinablePragma :: InlinePragma -> Bool #
isNoInlinePragma :: InlinePragma -> Bool #
isOpaquePragma :: InlinePragma -> Bool #
isAnyInlinePragma :: InlinePragma -> Bool #
inlinePragmaName :: InlineSpec -> SDoc #
Outputs string for pragma name for any of INLINEINLINABLENOINLINE. This differs from the Outputable instance for the InlineSpec type where the pragma name string as well as the accompanying SourceText (if any) is printed.
inlinePragmaSat :: InlinePragma -> Maybe Arity #
pprInline :: InlinePragma -> SDoc #
Pretty-print without displaying the user-specified InlineSpec.
pprInlineDebug :: InlinePragma -> SDoc #
Pretty-print including the user-specified InlineSpec.
data UnfoldingSource #
Constructors
| VanillaSrc | |
| StableUserSrc | |
| StableSystemSrc | |
| CompulsorySrc |
Instances
| Binary UnfoldingSource # | |
Defined in GHC.Types.Basic Methods put_ :: BinHandle -> UnfoldingSource -> IO () # put :: BinHandle -> UnfoldingSource -> IO (Bin UnfoldingSource) # get :: BinHandle -> IO UnfoldingSource # | |
| Outputable UnfoldingSource # | |
Defined in GHC.Types.Basic Methods ppr :: UnfoldingSource -> SDoc # | |
isStableSource :: UnfoldingSource -> Bool #
data SuccessFlag #
Instances
| Semigroup SuccessFlag # | |
Defined in GHC.Types.Basic Methods (<>) :: SuccessFlag -> SuccessFlag -> SuccessFlag # sconcat :: NonEmpty SuccessFlag -> SuccessFlag # stimes :: Integral b => b -> SuccessFlag -> SuccessFlag # | |
| Outputable SuccessFlag # | |
Defined in GHC.Types.Basic Methods ppr :: SuccessFlag -> SDoc # | |
succeeded :: SuccessFlag -> Bool #
failed :: SuccessFlag -> Bool #
successIf :: Bool -> SuccessFlag #
data IntWithInf #
An integer or infinity
Instances
| Num IntWithInf # | |
Defined in GHC.Types.Basic Methods (+) :: IntWithInf -> IntWithInf -> IntWithInf # (-) :: IntWithInf -> IntWithInf -> IntWithInf # (*) :: IntWithInf -> IntWithInf -> IntWithInf # negate :: IntWithInf -> IntWithInf # abs :: IntWithInf -> IntWithInf # signum :: IntWithInf -> IntWithInf # fromInteger :: Integer -> IntWithInf # | |
| Outputable IntWithInf # | |
Defined in GHC.Types.Basic Methods ppr :: IntWithInf -> SDoc # | |
| Eq IntWithInf # | |
Defined in GHC.Types.Basic | |
| Ord IntWithInf # | |
Defined in GHC.Types.Basic Methods compare :: IntWithInf -> IntWithInf -> Ordering # (<) :: IntWithInf -> IntWithInf -> Bool # (<=) :: IntWithInf -> IntWithInf -> Bool # (>) :: IntWithInf -> IntWithInf -> Bool # (>=) :: IntWithInf -> IntWithInf -> Bool # max :: IntWithInf -> IntWithInf -> IntWithInf # min :: IntWithInf -> IntWithInf -> IntWithInf # | |
infinity :: IntWithInf #
A representation of infinity
treatZeroAsInf :: Int -> IntWithInf #
Turn a positive number into an IntWithInf, where 0 represents infinity
subWithInf :: IntWithInf -> Int -> IntWithInf #
Subtract an Int from an IntWithInf
mkIntWithInf :: Int -> IntWithInf #
Inject any integer into an IntWithInf
intGtLimit :: Int -> IntWithInf -> Bool #
data TypeOrKind #
Flag to see whether we're type-checking terms or kind-checking types
Instances
| Outputable TypeOrKind # | |
Defined in GHC.Types.Basic Methods ppr :: TypeOrKind -> SDoc # | |
| Eq TypeOrKind # | |
Defined in GHC.Types.Basic | |
isTypeLevel :: TypeOrKind -> Bool #
isKindLevel :: TypeOrKind -> Bool #
Instances
| Data Levity # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Levity -> c Levity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Levity # toConstr :: Levity -> Constr # dataTypeOf :: Levity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Levity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Levity) # gmapT :: (forall b. Data b => b -> b) -> Levity -> Levity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Levity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Levity -> r # gmapQ :: (forall d. Data d => d -> u) -> Levity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Levity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Levity -> m Levity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Levity -> m Levity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Levity -> m Levity # | |
| Show Levity # | |
| Binary Levity # | |
| Outputable Levity # | |
Defined in GHC.Types.Basic | |
| Eq Levity # | |
| Ord Levity # | |
mightBeLifted :: Maybe Levity -> Bool #
mightBeUnlifted :: Maybe Levity -> Bool #
data TypeOrConstraint #
Constructors
| TypeLike | |
| ConstraintLike |
Instances
data TyConFlavour tc #
Paints a picture of what a TyCon represents, in broad strokes.
This is used towards more informative error messages.
Constructors
Instances
| Functor TyConFlavour # | |
Defined in GHC.Types.Basic Methods fmap :: (a -> b) -> TyConFlavour a -> TyConFlavour b # (<$) :: a -> TyConFlavour b -> TyConFlavour a # | |
| NFData tc => NFData (TyConFlavour tc) # | |
Defined in GHC.Types.Basic Methods rnf :: TyConFlavour tc -> () # | |
| Data tc => Data (TyConFlavour tc) # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyConFlavour tc -> c (TyConFlavour tc) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TyConFlavour tc) # toConstr :: TyConFlavour tc -> Constr # dataTypeOf :: TyConFlavour tc -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TyConFlavour tc)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TyConFlavour tc)) # gmapT :: (forall b. Data b => b -> b) -> TyConFlavour tc -> TyConFlavour tc # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyConFlavour tc -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyConFlavour tc -> r # gmapQ :: (forall d. Data d => d -> u) -> TyConFlavour tc -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TyConFlavour tc -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyConFlavour tc -> m (TyConFlavour tc) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyConFlavour tc -> m (TyConFlavour tc) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyConFlavour tc -> m (TyConFlavour tc) # | |
| Outputable (TyConFlavour tc) # | |
Defined in GHC.Types.Basic Methods ppr :: TyConFlavour tc -> SDoc # | |
| Eq tc => Eq (TyConFlavour tc) # | |
Defined in GHC.Types.Basic Methods (==) :: TyConFlavour tc -> TyConFlavour tc -> Bool # (/=) :: TyConFlavour tc -> TyConFlavour tc -> Bool # | |
data TypeOrData #
Whether something is a type or a data declaration, e.g. a type family or a data family.
Instances
| Data TypeOrData # | |
Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeOrData -> c TypeOrData # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeOrData # toConstr :: TypeOrData -> Constr # dataTypeOf :: TypeOrData -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeOrData) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeOrData) # gmapT :: (forall b. Data b => b -> b) -> TypeOrData -> TypeOrData # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeOrData -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeOrData -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeOrData -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeOrData -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeOrData -> m TypeOrData # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeOrData -> m TypeOrData # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeOrData -> m TypeOrData # | |
| Outputable TypeOrData # | |
Defined in GHC.Types.Basic Methods ppr :: TypeOrData -> SDoc # | |
| Eq TypeOrData # | |
Defined in GHC.Types.Basic | |
tyConFlavourAssoc_maybe :: TyConFlavour tc -> Maybe tc #
Get the enclosing class TyCon (if there is one) for the given TyConFlavour
data NonStandardDefaultingStrategy #
Specify whether to default type variables of kind RuntimeRepLevityMultiplicity.
Constructors
| DefaultNonStandardTyVars | Default type variables of the given kinds: |
| TryNotToDefaultNonStandardTyVars | Try not to default type variables of the kinds Note that these might get defaulted anyway, if they are kind variables and `-XNoPolyKinds` is enabled. |
Instances
| Outputable NonStandardDefaultingStrategy # | |
Defined in GHC.Types.Basic Methods | |
data DefaultingStrategy #
Specify whether to default kind variables, and type variables
of kind RuntimeRepLevityMultiplicity.
Constructors
| DefaultKindVars | Default kind variables:
When this strategy is used, it means that we have determined that the variables we are considering defaulting are all kind variables. Usually, we pass this option when -XNoPolyKinds is enabled. |
| NonStandardDefaulting NonStandardDefaultingStrategy | Default (or don't default) non-standard variables, of kinds
|
Instances
| Outputable DefaultingStrategy # | |
Defined in GHC.Types.Basic Methods ppr :: DefaultingStrategy -> SDoc # | |
data ForeignSrcLang #
Foreign formats supported by GHC via TH
Constructors
| LangC | C |
| LangCxx | C++ |
| LangObjc | Objective C |
| LangObjcxx | Objective C++ |
| LangAsm | Assembly language (.s) |
| LangJs | JavaScript |
| RawObject | Object (.o) |
Instances
Orphan instances
| Binary Boxity # | |
| Binary PromotionFlag # | |
Methods put_ :: BinHandle -> PromotionFlag -> IO () # put :: BinHandle -> PromotionFlag -> IO (Bin PromotionFlag) # get :: BinHandle -> IO PromotionFlag # | |
| Outputable Boxity # | |
| Outputable PromotionFlag # | |
Methods ppr :: PromotionFlag -> SDoc # | |