Safe Haskell | None |
---|---|
Language | GHC2021 |
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
- notSwapped :: SwapFlag -> Bool
- isSwapped :: SwapFlag -> Bool
- pickSwap :: SwapFlag -> a -> a -> a
- 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 Source #
Instances
pickLR :: LeftOrRight -> (a, a) -> a Source #
A *one-index* 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
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 Source #
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 Source #
Instances
NFData JoinPointHood Source # | |
Defined in GHC.Utils.Outputable rnf :: JoinPointHood -> () Source # | |
Binary JoinPointHood Source # | |
Defined in GHC.Utils.Binary put_ :: WriteBinHandle -> JoinPointHood -> IO () Source # put :: WriteBinHandle -> JoinPointHood -> IO (Bin JoinPointHood) Source # get :: ReadBinHandle -> IO JoinPointHood Source # | |
Outputable JoinPointHood Source # | |
Defined in GHC.Utils.Outputable ppr :: JoinPointHood -> SDoc Source # | |
Eq JoinPointHood Source # | |
Defined in GHC.Utils.Outputable (==) :: JoinPointHood -> JoinPointHood -> Bool # (/=) :: JoinPointHood -> JoinPointHood -> Bool # |
isJoinPoint :: JoinPointHood -> Bool Source #
A power-of-two alignment
mkAlignment :: Int -> Alignment Source #
alignmentOf :: Int -> Alignment Source #
alignmentBytes :: Alignment -> Int Source #
data PromotionFlag Source #
Instances
isPromoted :: PromotionFlag -> Bool Source #
data FunctionOrData Source #
Instances
Recursivity Flag
Instances
Binary RecFlag Source # | |
Outputable 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 # | |
Eq RecFlag Source # | |
boolToRecFlag :: Bool -> RecFlag Source #
Was this piece of code user-written or generated by the compiler?
See Note [Generated code and pattern-match checking].
Instances
Outputable 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 # | |
Eq Origin Source # | |
isGenerated :: Origin -> Bool Source #
Whether to run pattern-match checks in generated code.
See Note [Generated code and pattern-match checking].
Instances
Outputable DoPmc Source # | |
Data DoPmc Source # | |
Defined in GHC.Types.Basic 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 # | |
Eq DoPmc Source # | |
requiresPMC :: Origin -> Bool Source #
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
Instances
Outputable GenReason Source # | |
Data GenReason Source # | |
Defined in GHC.Types.Basic 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 # | |
Eq GenReason Source # | |
isDoExpansionGenerated :: Origin -> Bool Source #
type RuleName = FastString Source #
pprRuleName :: RuleName -> SDoc Source #
data TopLevelFlag Source #
Instances
Outputable TopLevelFlag Source # | |
Defined in GHC.Types.Basic ppr :: TopLevelFlag -> SDoc Source # | |
Data TopLevelFlag Source # | |
Defined in GHC.Types.Basic 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 # |
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.
Instances
Binary OverlapFlag Source # | |
Defined in GHC.Types.Basic put_ :: WriteBinHandle -> OverlapFlag -> IO () Source # put :: WriteBinHandle -> OverlapFlag -> IO (Bin OverlapFlag) Source # get :: ReadBinHandle -> IO OverlapFlag Source # | |
Outputable OverlapFlag Source # | |
Defined in GHC.Types.Basic ppr :: OverlapFlag -> SDoc Source # | |
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 # | |
Eq OverlapFlag Source # | |
Defined in GHC.Types.Basic (==) :: OverlapFlag -> OverlapFlag -> Bool # (/=) :: OverlapFlag -> OverlapFlag -> Bool # |
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 {-# 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
Binary OverlapMode Source # | |
Defined in GHC.Types.Basic put_ :: WriteBinHandle -> OverlapMode -> IO () Source # put :: WriteBinHandle -> OverlapMode -> IO (Bin OverlapMode) Source # get :: ReadBinHandle -> IO OverlapMode Source # | |
Outputable OverlapMode Source # | |
Defined in GHC.Types.Basic ppr :: OverlapMode -> SDoc Source # | |
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 # | |
Eq OverlapMode Source # | |
Defined in GHC.Types.Basic (==) :: OverlapMode -> OverlapMode -> Bool # (/=) :: OverlapMode -> OverlapMode -> Bool # | |
type Anno OverlapMode Source # | |
Defined in GHC.Hs.Decls |
hasOverlappingFlag :: OverlapMode -> Bool Source #
hasIncoherentFlag :: OverlapMode -> Bool Source #
Instances
Binary Boxity Source # | |
Outputable Boxity Source # | |
Data Boxity Source # | |
Defined in Language.Haskell.Syntax.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 # | |
Eq Boxity Source # | |
Should an argument be passed evaluated *and* tagged.
isMarkedCbv :: CbvMark -> Bool Source #
A general-purpose pretty-printing precedence type.
Instances
Binary TupleSort Source # | |
Outputable 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 # | |
Eq TupleSort Source # | |
Ord TupleSort Source # | |
Defined in GHC.Types.Basic |
tupleSortBoxity :: TupleSort -> Boxity Source #
boxityTupleSort :: Boxity -> TupleSort Source #
data UnboxedTupleOrSum Source #
Are we dealing with an unboxed tuple or an unboxed sum?
Used when validity checking, see check_ubx_tuple_or_sum
.
Instances
Outputable UnboxedTupleOrSum Source # | |
Defined in GHC.Types.Basic ppr :: UnboxedTupleOrSum -> SDoc Source # | |
Eq UnboxedTupleOrSum Source # | |
Defined in GHC.Types.Basic (==) :: UnboxedTupleOrSum -> UnboxedTupleOrSum -> Bool # (/=) :: UnboxedTupleOrSum -> UnboxedTupleOrSum -> Bool # |
:: (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
Outputable OneShotInfo Source # | |
Defined in GHC.Types.Basic ppr :: OneShotInfo -> SDoc Source # | |
Eq OneShotInfo Source # | |
Defined in GHC.Types.Basic (==) :: OneShotInfo -> OneShotInfo -> Bool # (/=) :: OneShotInfo -> OneShotInfo -> Bool # |
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
Monoid InterestingCxt Source # | |
Defined in GHC.Types.Basic mappend :: InterestingCxt -> InterestingCxt -> InterestingCxt # mconcat :: [InterestingCxt] -> InterestingCxt # | |
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 # | |
Eq InterestingCxt Source # | |
Defined in GHC.Types.Basic (==) :: InterestingCxt -> InterestingCxt -> Bool # (/=) :: InterestingCxt -> InterestingCxt -> Bool # |
data TailCallInfo Source #
Instances
Outputable TailCallInfo Source # | |
Defined in GHC.Types.Basic ppr :: TailCallInfo -> SDoc Source # | |
Eq TailCallInfo Source # | |
Defined in GHC.Types.Basic (==) :: TailCallInfo -> TailCallInfo -> Bool # (/=) :: TailCallInfo -> TailCallInfo -> Bool # |
tailCallInfo :: OccInfo -> TailCallInfo Source #
zapOccTailCallInfo :: OccInfo -> OccInfo Source #
isAlwaysTailCalled :: OccInfo -> Bool Source #
data DefMethSpec ty Source #
Default Method Specification
Instances
Binary (DefMethSpec IfaceType) Source # | |
Defined in GHC.Iface.Type put_ :: WriteBinHandle -> DefMethSpec IfaceType -> IO () Source # put :: WriteBinHandle -> DefMethSpec IfaceType -> IO (Bin (DefMethSpec IfaceType)) Source # get :: ReadBinHandle -> IO (DefMethSpec IfaceType) Source # | |
Outputable (DefMethSpec ty) Source # | |
Defined in GHC.Types.Basic ppr :: DefMethSpec ty -> SDoc Source # |
notSwapped :: SwapFlag -> Bool Source #
data CompilerPhase Source #
Instances
Outputable CompilerPhase Source # | |
Defined in GHC.Types.Basic ppr :: CompilerPhase -> SDoc Source # | |
Eq CompilerPhase Source # | |
Defined in GHC.Types.Basic (==) :: CompilerPhase -> CompilerPhase -> Bool # (/=) :: CompilerPhase -> CompilerPhase -> Bool # |
beginPhase :: Activation -> CompilerPhase Source #
laterPhase :: CompilerPhase -> CompilerPhase -> CompilerPhase Source #
data Activation Source #
AlwaysActive | |
ActiveBefore SourceText PhaseNum | |
ActiveAfter SourceText PhaseNum | |
FinalActive | |
NeverActive |
Instances
Binary Activation Source # | |
Defined in GHC.Types.Basic put_ :: WriteBinHandle -> Activation -> IO () Source # put :: WriteBinHandle -> Activation -> IO (Bin Activation) Source # get :: ReadBinHandle -> IO Activation Source # | |
Outputable Activation Source # | |
Defined in GHC.Types.Basic ppr :: Activation -> SDoc Source # | |
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 # | |
Eq Activation Source # | |
Defined in GHC.Types.Basic (==) :: Activation -> Activation -> Bool # (/=) :: Activation -> Activation -> Bool # |
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
noUserInlineSpec :: InlineSpec -> Bool Source #
data InlinePragma Source #
InlinePragma | |
|
Instances
isInlinePragma :: InlinePragma -> Bool Source #
isInlinablePragma :: InlinePragma -> Bool Source #
isNoInlinePragma :: InlinePragma -> Bool Source #
isOpaquePragma :: InlinePragma -> Bool Source #
isAnyInlinePragma :: InlinePragma -> Bool Source #
inlinePragmaName :: InlineSpec -> SDoc Source #
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 Source #
pprInline :: InlinePragma -> SDoc Source #
Pretty-print without displaying the user-specified InlineSpec
.
pprInlineDebug :: InlinePragma -> SDoc Source #
Pretty-print including the user-specified InlineSpec
.
data UnfoldingSource Source #
Instances
Binary UnfoldingSource Source # | |
Defined in GHC.Types.Basic put_ :: WriteBinHandle -> UnfoldingSource -> IO () Source # put :: WriteBinHandle -> UnfoldingSource -> IO (Bin UnfoldingSource) Source # get :: ReadBinHandle -> IO UnfoldingSource Source # | |
Outputable UnfoldingSource Source # | |
Defined in GHC.Types.Basic ppr :: UnfoldingSource -> SDoc Source # |
isStableSource :: UnfoldingSource -> Bool Source #
data SuccessFlag Source #
Instances
Outputable SuccessFlag Source # | |
Defined in GHC.Types.Basic ppr :: SuccessFlag -> SDoc Source # | |
Semigroup SuccessFlag Source # | |
Defined in GHC.Types.Basic (<>) :: SuccessFlag -> SuccessFlag -> SuccessFlag # sconcat :: NonEmpty SuccessFlag -> SuccessFlag # stimes :: Integral b => b -> SuccessFlag -> SuccessFlag # |
succeeded :: SuccessFlag -> Bool Source #
failed :: SuccessFlag -> Bool Source #
successIf :: Bool -> SuccessFlag Source #
data IntWithInf Source #
An integer or infinity
Instances
Outputable IntWithInf Source # | |
Defined in GHC.Types.Basic ppr :: IntWithInf -> SDoc Source # | |
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 # | |
Eq IntWithInf Source # | |
Defined in GHC.Types.Basic (==) :: IntWithInf -> IntWithInf -> Bool # (/=) :: IntWithInf -> IntWithInf -> Bool # | |
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 # |
infinity :: IntWithInf Source #
A representation of infinity
treatZeroAsInf :: Int -> IntWithInf Source #
Turn a positive number into an IntWithInf
, where 0 represents infinity
subWithInf :: IntWithInf -> Int -> IntWithInf Source #
Subtract an Int
from an IntWithInf
mkIntWithInf :: Int -> IntWithInf Source #
Inject any integer into an IntWithInf
intGtLimit :: Int -> IntWithInf -> Bool Source #
data TypeOrKind Source #
Flag to see whether we're type-checking terms or kind-checking types
Instances
Outputable TypeOrKind Source # | |
Defined in GHC.Types.Basic ppr :: TypeOrKind -> SDoc Source # | |
Eq TypeOrKind Source # | |
Defined in GHC.Types.Basic (==) :: TypeOrKind -> TypeOrKind -> Bool # (/=) :: TypeOrKind -> TypeOrKind -> Bool # |
isTypeLevel :: TypeOrKind -> Bool Source #
isKindLevel :: TypeOrKind -> Bool Source #
Instances
Binary Levity Source # | |
Outputable Levity Source # | |
Data Levity Source # | |
Defined in GHC.Types.Basic 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 Source # | |
Eq Levity Source # | |
Ord Levity Source # | |
data TypeOrConstraint Source #
Instances
data TyConFlavour tc Source #
Paints a picture of what a TyCon
represents, in broad strokes.
This is used towards more informative error messages.
Instances
Functor TyConFlavour Source # | |
Defined in GHC.Types.Basic fmap :: (a -> b) -> TyConFlavour a -> TyConFlavour b # (<$) :: a -> TyConFlavour b -> TyConFlavour a # | |
NFData tc => NFData (TyConFlavour tc) Source # | |
Defined in GHC.Types.Basic rnf :: TyConFlavour tc -> () Source # | |
Outputable (TyConFlavour tc) Source # | |
Defined in GHC.Types.Basic ppr :: TyConFlavour tc -> SDoc Source # | |
Data tc => Data (TyConFlavour tc) Source # | |
Defined in GHC.Types.Basic 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) # | |
Eq tc => Eq (TyConFlavour tc) Source # | |
Defined in GHC.Types.Basic (==) :: TyConFlavour tc -> TyConFlavour tc -> Bool # (/=) :: TyConFlavour tc -> TyConFlavour tc -> Bool # |
data TypeOrData Source #
Whether something is a type or a data declaration, e.g. a type family or a data family.
Instances
Outputable TypeOrData Source # | |
Defined in GHC.Types.Basic ppr :: TypeOrData -> SDoc Source # | |
Data TypeOrData Source # | |
Defined in GHC.Types.Basic 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 # | |
Eq TypeOrData Source # | |
Defined in GHC.Types.Basic (==) :: TypeOrData -> TypeOrData -> Bool # (/=) :: TypeOrData -> TypeOrData -> Bool # |
tyConFlavourAssoc_maybe :: TyConFlavour tc -> Maybe tc Source #
Get the enclosing class TyCon (if there is one) for the given TyConFlavour
data NonStandardDefaultingStrategy Source #
Specify whether to default type variables of kind RuntimeRep
Levity
Multiplicity
.
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
data DefaultingStrategy Source #
Specify whether to default kind variables, and type variables
of kind RuntimeRep
Levity
Multiplicity
.
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 Source # | |
Defined in GHC.Types.Basic ppr :: DefaultingStrategy -> SDoc Source # |
data ForeignSrcLang #
Instances
Orphan instances
Binary Boxity Source # | |
Binary PromotionFlag Source # | |
put_ :: WriteBinHandle -> PromotionFlag -> IO () Source # put :: WriteBinHandle -> PromotionFlag -> IO (Bin PromotionFlag) Source # get :: ReadBinHandle -> IO PromotionFlag Source # | |
Outputable Boxity Source # | |
Outputable PromotionFlag Source # | |
ppr :: PromotionFlag -> SDoc Source # |