| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GHC.Types.Basic
Contents
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
- type FullArgCount = Int
- 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
- 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
- data CbvMark
- isMarkedCbv :: CbvMark -> 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
- 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 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 SpliceExplicitFlag
- data TypeOrKind
- isTypeLevel :: TypeOrKind -> Bool
- isKindLevel :: TypeOrKind -> Bool
- data Levity
- mightBeLifted :: Maybe Levity -> Bool
- mightBeUnlifted :: Maybe Levity -> Bool
- data ExprOrPat
- data NonStandardDefaultingStrategy
- data DefaultingStrategy
- defaultNonStandardTyVars :: DefaultingStrategy -> Bool
- data ForeignSrcLang
Documentation
data LeftOrRight Source #
Instances
| Data LeftOrRight Source # | |
| 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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LeftOrRight Source # toConstr :: LeftOrRight -> Constr Source # dataTypeOf :: LeftOrRight -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LeftOrRight) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LeftOrRight) Source # gmapT :: (forall b. Data b => b -> b) -> LeftOrRight -> LeftOrRight Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LeftOrRight -> r Source # gmapQ :: (forall d. Data d => d -> u) -> LeftOrRight -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> LeftOrRight -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LeftOrRight -> m LeftOrRight Source # | |
| Binary LeftOrRight Source # | |
| Defined in GHC.Types.Basic Methods put_ :: BinHandle -> LeftOrRight -> IO () Source # put :: BinHandle -> LeftOrRight -> IO (Bin LeftOrRight) Source # | |
| Outputable LeftOrRight Source # | |
| Defined in GHC.Types.Basic Methods ppr :: LeftOrRight -> SDoc Source # | |
| Eq LeftOrRight Source # | |
| Defined in GHC.Types.Basic | |
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
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!
A power-of-two alignment
Instances
| Outputable Alignment Source # | |
| Eq Alignment Source # | |
| Ord Alignment Source # | |
| OutputableP env Alignment Source # | |
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?
Constructors
| NotPromoted | |
| IsPromoted | 
Instances
isPromoted :: PromotionFlag -> Bool Source #
data FunctionOrData Source #
Constructors
| IsFunction | |
| IsData | 
Instances
Recursivity Flag
Constructors
| Recursive | |
| NonRecursive | 
Instances
| Data RecFlag Source # | |
| 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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecFlag Source # toConstr :: RecFlag -> Constr Source # dataTypeOf :: RecFlag -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RecFlag) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecFlag) Source # gmapT :: (forall b. Data b => b -> b) -> RecFlag -> RecFlag Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecFlag -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecFlag -> r Source # gmapQ :: (forall d. Data d => d -> u) -> RecFlag -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> RecFlag -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFlag -> m RecFlag Source # | |
| Binary RecFlag Source # | |
| Outputable RecFlag Source # | |
| Eq RecFlag Source # | |
boolToRecFlag :: Bool -> RecFlag Source #
Constructors
| FromSource | |
| Generated | 
Instances
| Data Origin Source # | |
| 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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Origin Source # toConstr :: Origin -> Constr Source # dataTypeOf :: Origin -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Origin) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Origin) Source # gmapT :: (forall b. Data b => b -> b) -> Origin -> Origin Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Origin -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Origin -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Origin -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Origin -> m Origin Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Origin -> m Origin Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Origin -> m Origin Source # | |
| Outputable Origin Source # | |
| Eq Origin Source # | |
isGenerated :: Origin -> Bool Source #
type RuleName = FastString Source #
pprRuleName :: RuleName -> SDoc Source #
data TopLevelFlag Source #
Constructors
| TopLevel | |
| NotTopLevel | 
Instances
| Data TopLevelFlag Source # | |
| 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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TopLevelFlag Source # toConstr :: TopLevelFlag -> Constr Source # dataTypeOf :: TopLevelFlag -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TopLevelFlag) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TopLevelFlag) Source # gmapT :: (forall b. Data b => b -> b) -> TopLevelFlag -> TopLevelFlag Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TopLevelFlag -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TopLevelFlag -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TopLevelFlag -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TopLevelFlag -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TopLevelFlag -> m TopLevelFlag Source # | |
| Outputable TopLevelFlag Source # | |
| Defined in GHC.Types.Basic Methods ppr :: TopLevelFlag -> SDoc Source # | |
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- `#-}`,
Constructors
| OverlapFlag | |
| Fields | |
Instances
| Data OverlapFlag Source # | |
| 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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverlapFlag Source # toConstr :: OverlapFlag -> Constr Source # dataTypeOf :: OverlapFlag -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverlapFlag) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverlapFlag) Source # gmapT :: (forall b. Data b => b -> b) -> OverlapFlag -> OverlapFlag Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverlapFlag -> r Source # gmapQ :: (forall d. Data d => d -> u) -> OverlapFlag -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlapFlag -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapFlag -> m OverlapFlag Source # | |
| Binary OverlapFlag Source # | |
| Defined in GHC.Types.Basic Methods put_ :: BinHandle -> OverlapFlag -> IO () Source # put :: BinHandle -> OverlapFlag -> IO (Bin OverlapFlag) Source # | |
| Outputable OverlapFlag Source # | |
| Defined in GHC.Types.Basic Methods ppr :: OverlapFlag -> SDoc Source # | |
| Eq OverlapFlag Source # | |
| Defined in GHC.Types.Basic | |
data OverlapMode Source #
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  | 
Instances
| Data OverlapMode Source # | |
| 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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverlapMode Source # toConstr :: OverlapMode -> Constr Source # dataTypeOf :: OverlapMode -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverlapMode) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverlapMode) Source # gmapT :: (forall b. Data b => b -> b) -> OverlapMode -> OverlapMode Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverlapMode -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverlapMode -> r Source # gmapQ :: (forall d. Data d => d -> u) -> OverlapMode -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverlapMode -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverlapMode -> m OverlapMode Source # | |
| Binary OverlapMode Source # | |
| Defined in GHC.Types.Basic Methods put_ :: BinHandle -> OverlapMode -> IO () Source # put :: BinHandle -> OverlapMode -> IO (Bin OverlapMode) Source # | |
| Outputable OverlapMode Source # | |
| Defined in GHC.Types.Basic Methods ppr :: OverlapMode -> SDoc Source # | |
| Eq OverlapMode Source # | |
| Defined in GHC.Types.Basic | |
| type Anno OverlapMode Source # | |
| Defined in GHC.Hs.Decls | |
| type Anno OverlapMode Source # | |
| Defined in GHC.Hs.Decls | |
hasOverlappingFlag :: OverlapMode -> Bool Source #
hasIncoherentFlag :: OverlapMode -> Bool Source #
Instances
| Data Boxity Source # | |
| Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Boxity -> c Boxity Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Boxity Source # toConstr :: Boxity -> Constr Source # dataTypeOf :: Boxity -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Boxity) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Boxity) Source # gmapT :: (forall b. Data b => b -> b) -> Boxity -> Boxity Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Boxity -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Boxity -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Boxity -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Boxity -> m Boxity Source # | |
| Binary Boxity Source # | |
| Outputable Boxity Source # | |
| Eq Boxity Source # | |
Should an argument be passed evaluated *and* tagged.
Constructors
| MarkedCbv | |
| NotMarkedCbv | 
isMarkedCbv :: CbvMark -> Bool Source #
A general-purpose pretty-printing precedence type.
Constructors
| BoxedTuple | |
| UnboxedTuple | |
| ConstraintTuple | 
Instances
| Data TupleSort Source # | |
| 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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TupleSort Source # toConstr :: TupleSort -> Constr Source # dataTypeOf :: TupleSort -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TupleSort) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TupleSort) Source # gmapT :: (forall b. Data b => b -> b) -> TupleSort -> TupleSort Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TupleSort -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TupleSort -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TupleSort -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TupleSort -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TupleSort -> m TupleSort Source # | |
| Binary TupleSort Source # | |
| Outputable TupleSort Source # | |
| Eq TupleSort Source # | |
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.
Constructors
| UnboxedTupleType | |
| UnboxedSumType | 
Instances
| Outputable UnboxedTupleOrSum Source # | |
| Defined in GHC.Types.Basic Methods ppr :: UnboxedTupleOrSum -> SDoc Source # | |
| Eq UnboxedTupleOrSum Source # | |
| 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 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.
Constructors
| NoOneShotInfo | No information | 
| OneShotLam | The lambda is applied at most once. | 
Instances
| Outputable OneShotInfo Source # | |
| Defined in GHC.Types.Basic Methods ppr :: OneShotInfo -> SDoc Source # | |
| Eq 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
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 -> () Source #
zapFragileOcc :: OccInfo -> OccInfo Source #
isStrongLoopBreaker :: OccInfo -> Bool Source #
isWeakLoopBreaker :: OccInfo -> Bool Source #
isManyOccs :: OccInfo -> Bool Source #
isNoOccInfo :: OccInfo -> Bool Source #
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 Source #
data InterestingCxt Source #
Interesting Context
Constructors
| 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 Methods mempty :: InterestingCxt Source # mappend :: InterestingCxt -> InterestingCxt -> InterestingCxt Source # mconcat :: [InterestingCxt] -> InterestingCxt Source # | |
| Semigroup InterestingCxt Source # | If there is any  | 
| Defined in GHC.Types.Basic Methods (<>) :: InterestingCxt -> InterestingCxt -> InterestingCxt Source # sconcat :: NonEmpty InterestingCxt -> InterestingCxt Source # stimes :: Integral b => b -> InterestingCxt -> InterestingCxt Source # | |
| Eq InterestingCxt Source # | |
| Defined in GHC.Types.Basic Methods (==) :: InterestingCxt -> InterestingCxt -> Bool # (/=) :: InterestingCxt -> InterestingCxt -> Bool # | |
data TailCallInfo Source #
Constructors
| AlwaysTailCalled JoinArity | |
| NoTailCallInfo | 
Instances
| Outputable TailCallInfo Source # | |
| Defined in GHC.Types.Basic Methods ppr :: TailCallInfo -> SDoc Source # | |
| Eq 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
| Binary (DefMethSpec IfaceType) Source # | |
| Defined in GHC.Iface.Type | |
| Outputable (DefMethSpec ty) Source # | |
| Defined in GHC.Types.Basic Methods ppr :: DefMethSpec ty -> SDoc Source # | |
Constructors
| NotSwapped | |
| IsSwapped | 
Instances
data CompilerPhase Source #
Constructors
| InitialPhase | |
| Phase PhaseNum | |
| FinalPhase | 
Instances
| Outputable CompilerPhase Source # | |
| Defined in GHC.Types.Basic Methods ppr :: CompilerPhase -> SDoc Source # | |
| Eq CompilerPhase Source # | |
| Defined in GHC.Types.Basic Methods (==) :: CompilerPhase -> CompilerPhase -> Bool # (/=) :: CompilerPhase -> CompilerPhase -> Bool # | |
beginPhase :: Activation -> CompilerPhase Source #
laterPhase :: CompilerPhase -> CompilerPhase -> CompilerPhase Source #
data Activation Source #
Constructors
| AlwaysActive | |
| ActiveBefore SourceText PhaseNum | |
| ActiveAfter SourceText PhaseNum | |
| FinalActive | |
| NeverActive | 
Instances
| Data Activation Source # | |
| 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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Activation Source # toConstr :: Activation -> Constr Source # dataTypeOf :: Activation -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Activation) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Activation) Source # gmapT :: (forall b. Data b => b -> b) -> Activation -> Activation Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Activation -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Activation -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Activation -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Activation -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Activation -> m Activation Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Activation -> m Activation Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Activation -> m Activation Source # | |
| Binary Activation Source # | |
| Defined in GHC.Types.Basic Methods put_ :: BinHandle -> Activation -> IO () Source # put :: BinHandle -> Activation -> IO (Bin Activation) Source # | |
| Outputable Activation Source # | |
| Defined in GHC.Types.Basic Methods ppr :: Activation -> SDoc Source # | |
| Eq Activation Source # | |
| Defined in GHC.Types.Basic | |
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
Constructors
| Inline SourceText | |
| Inlinable SourceText | |
| NoInline SourceText | |
| Opaque SourceText | |
| NoUserInlinePrag | 
Instances
| Data InlineSpec Source # | |
| 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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InlineSpec Source # toConstr :: InlineSpec -> Constr Source # dataTypeOf :: InlineSpec -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InlineSpec) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlineSpec) Source # gmapT :: (forall b. Data b => b -> b) -> InlineSpec -> InlineSpec Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlineSpec -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlineSpec -> r Source # gmapQ :: (forall d. Data d => d -> u) -> InlineSpec -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> InlineSpec -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlineSpec -> m InlineSpec Source # | |
| Show InlineSpec Source # | |
| Defined in GHC.Types.Basic | |
| Binary InlineSpec Source # | |
| Defined in GHC.Types.Basic Methods put_ :: BinHandle -> InlineSpec -> IO () Source # put :: BinHandle -> InlineSpec -> IO (Bin InlineSpec) Source # | |
| Outputable InlineSpec Source # | |
| Defined in GHC.Types.Basic Methods ppr :: InlineSpec -> SDoc Source # | |
| Eq InlineSpec Source # | |
| Defined in GHC.Types.Basic | |
noUserInlineSpec :: InlineSpec -> Bool Source #
data InlinePragma Source #
Constructors
| InlinePragma | |
| Fields 
 | |
Instances
| Data InlinePragma Source # | |
| 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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InlinePragma Source # toConstr :: InlinePragma -> Constr Source # dataTypeOf :: InlinePragma -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InlinePragma) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InlinePragma) Source # gmapT :: (forall b. Data b => b -> b) -> InlinePragma -> InlinePragma Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InlinePragma -> r Source # gmapQ :: (forall d. Data d => d -> u) -> InlinePragma -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> InlinePragma -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InlinePragma -> m InlinePragma Source # | |
| Binary InlinePragma Source # | |
| Defined in GHC.Types.Basic Methods put_ :: BinHandle -> InlinePragma -> IO () Source # put :: BinHandle -> InlinePragma -> IO (Bin InlinePragma) Source # | |
| Outputable InlinePragma Source # | |
| Defined in GHC.Types.Basic Methods ppr :: InlinePragma -> SDoc Source # | |
| Eq InlinePragma Source # | |
| Defined in GHC.Types.Basic | |
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 #
pprInlineDebug :: InlinePragma -> SDoc Source #
data SuccessFlag Source #
Instances
| Semigroup SuccessFlag Source # | |
| Defined in GHC.Types.Basic Methods (<>) :: SuccessFlag -> SuccessFlag -> SuccessFlag Source # sconcat :: NonEmpty SuccessFlag -> SuccessFlag Source # stimes :: Integral b => b -> SuccessFlag -> SuccessFlag Source # | |
| Outputable SuccessFlag Source # | |
| Defined in GHC.Types.Basic Methods ppr :: SuccessFlag -> SDoc Source # | |
succeeded :: SuccessFlag -> Bool Source #
failed :: SuccessFlag -> Bool Source #
successIf :: Bool -> SuccessFlag Source #
data IntWithInf Source #
An integer or infinity
Instances
| Num IntWithInf Source # | |
| Defined in GHC.Types.Basic Methods (+) :: IntWithInf -> IntWithInf -> IntWithInf Source # (-) :: IntWithInf -> IntWithInf -> IntWithInf Source # (*) :: IntWithInf -> IntWithInf -> IntWithInf Source # negate :: IntWithInf -> IntWithInf Source # abs :: IntWithInf -> IntWithInf Source # signum :: IntWithInf -> IntWithInf Source # fromInteger :: Integer -> IntWithInf Source # | |
| Outputable IntWithInf Source # | |
| Defined in GHC.Types.Basic Methods ppr :: IntWithInf -> SDoc Source # | |
| Eq IntWithInf Source # | |
| Defined in GHC.Types.Basic | |
| Ord IntWithInf Source # | |
| 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 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 IntWithInf from an IntWithInf
mkIntWithInf :: Int -> IntWithInf Source #
Inject any integer into an IntWithInf
intGtLimit :: Int -> IntWithInf -> Bool Source #
data SpliceExplicitFlag Source #
Constructors
| ExplicitSplice | = $(f x y) | 
| ImplicitSplice | = f x y, i.e. a naked top level expression | 
Instances
| Data SpliceExplicitFlag Source # | |
| Defined in GHC.Types.Basic Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SpliceExplicitFlag -> c SpliceExplicitFlag Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SpliceExplicitFlag Source # toConstr :: SpliceExplicitFlag -> Constr Source # dataTypeOf :: SpliceExplicitFlag -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SpliceExplicitFlag) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SpliceExplicitFlag) Source # gmapT :: (forall b. Data b => b -> b) -> SpliceExplicitFlag -> SpliceExplicitFlag Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SpliceExplicitFlag -> r Source # gmapQ :: (forall d. Data d => d -> u) -> SpliceExplicitFlag -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> SpliceExplicitFlag -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SpliceExplicitFlag -> m SpliceExplicitFlag Source # | |
data TypeOrKind Source #
Flag to see whether we're type-checking terms or kind-checking types
Instances
| Outputable TypeOrKind Source # | |
| Defined in GHC.Types.Basic Methods ppr :: TypeOrKind -> SDoc Source # | |
| Eq TypeOrKind Source # | |
| Defined in GHC.Types.Basic | |
isTypeLevel :: TypeOrKind -> Bool Source #
isKindLevel :: TypeOrKind -> Bool Source #
Are we dealing with an expression or a pattern?
Used only for the textual output of certain error messages;
 see the FRRDataConArg constructor of FixedRuntimeRepContext.
Constructors
| Expression | |
| Pattern | 
data NonStandardDefaultingStrategy Source #
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 Source # | |
| Defined in GHC.Types.Basic Methods | |
data DefaultingStrategy Source #
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 Source # | |
| Defined in GHC.Types.Basic Methods ppr :: DefaultingStrategy -> SDoc Source # | |
data ForeignSrcLang #
Instances
| Generic ForeignSrcLang | |
| Defined in GHC.ForeignSrcLang.Type Methods from :: ForeignSrcLang -> Rep ForeignSrcLang x Source # to :: Rep ForeignSrcLang x -> ForeignSrcLang Source # | |
| Show ForeignSrcLang | |
| Defined in GHC.ForeignSrcLang.Type | |
| Eq ForeignSrcLang | |
| Defined in GHC.ForeignSrcLang.Type Methods (==) :: ForeignSrcLang -> ForeignSrcLang -> Bool # (/=) :: ForeignSrcLang -> ForeignSrcLang -> Bool # | |
| type Rep ForeignSrcLang | |
| Defined in GHC.ForeignSrcLang.Type type Rep ForeignSrcLang = D1 ('MetaData "ForeignSrcLang" "GHC.ForeignSrcLang.Type" "ghc-boot-th-9.4.8" 'False) ((C1 ('MetaCons "LangC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LangCxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LangObjc" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LangObjcxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LangAsm" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RawObject" 'PrefixI 'False) (U1 :: Type -> Type)))) | |