Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type Version = Int
- bumpVersion :: Version -> Version
- initialVersion :: Version
- data LeftOrRight
- pickLR :: LeftOrRight -> (a, a) -> a
- type ConTag = Int
- type ConTagZ = Int
- fIRST_TAG :: ConTag
- type Arity = Int
- type RepArity = Int
- type JoinArity = Int
- type Alignment = Int
- data FunctionOrData
- = IsFunction
- | IsData
- data WarningTxt
- pprWarningTxtForMsg :: WarningTxt -> SDoc
- data StringLiteral = StringLiteral {
- sl_st :: SourceText
- sl_fs :: FastString
- data Fixity = Fixity SourceText Int FixityDirection
- data FixityDirection
- defaultFixity :: Fixity
- maxPrecedence :: Int
- minPrecedence :: Int
- negateFixity :: Fixity
- funTyFixity :: Fixity
- compareFixity :: Fixity -> Fixity -> (Bool, Bool)
- data LexicalFixity
- data RecFlag
- isRec :: RecFlag -> Bool
- isNonRec :: RecFlag -> Bool
- boolToRecFlag :: Bool -> RecFlag
- data Origin
- isGenerated :: Origin -> Bool
- type RuleName = FastString
- pprRuleName :: RuleName -> SDoc
- data TopLevelFlag
- isTopLevel :: TopLevelFlag -> Bool
- isNotTopLevel :: TopLevelFlag -> Bool
- data DerivStrategy
- 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 TyPrec
- maybeParen :: TyPrec -> TyPrec -> SDoc -> SDoc
- data TupleSort
- tupleSortBoxity :: TupleSort -> Boxity
- boxityTupleSort :: Boxity -> TupleSort
- tupleParens :: TupleSort -> SDoc -> SDoc
- sumParens :: SDoc -> SDoc
- pprAlternative :: (a -> SDoc) -> a -> ConTag -> Arity -> SDoc
- data OneShotInfo
- noOneShotInfo :: OneShotInfo
- hasNoOneShotInfo :: OneShotInfo -> Bool
- isOneShotInfo :: OneShotInfo -> Bool
- bestOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo
- worstOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo
- data OccInfo
- = ManyOccs {
- occ_tail :: !TailCallInfo
- | IAmDead
- | OneOcc { }
- | IAmALoopBreaker {
- occ_rules_only :: !RulesOnly
- occ_tail :: !TailCallInfo
- = ManyOccs {
- noOccInfo :: OccInfo
- seqOccInfo :: OccInfo -> ()
- zapFragileOcc :: OccInfo -> OccInfo
- isOneOcc :: OccInfo -> Bool
- isDeadOcc :: OccInfo -> Bool
- isStrongLoopBreaker :: OccInfo -> Bool
- isWeakLoopBreaker :: OccInfo -> Bool
- isManyOccs :: OccInfo -> Bool
- strongLoopBreaker :: OccInfo
- weakLoopBreaker :: OccInfo
- type InsideLam = Bool
- insideLam :: InsideLam
- notInsideLam :: InsideLam
- type OneBranch = Bool
- oneBranch :: OneBranch
- notOneBranch :: OneBranch
- type InterestingCxt = Bool
- data TailCallInfo
- tailCallInfo :: OccInfo -> TailCallInfo
- zapOccTailCallInfo :: OccInfo -> OccInfo
- isAlwaysTailCalled :: OccInfo -> Bool
- data EP a = EP {}
- data DefMethSpec ty
- data SwapFlag
- flipSwap :: SwapFlag -> SwapFlag
- unSwap :: SwapFlag -> (a -> a -> b) -> a -> a -> b
- isSwapped :: SwapFlag -> Bool
- data CompilerPhase
- type PhaseNum = Int
- data Activation
- isActive :: CompilerPhase -> Activation -> Bool
- isActiveIn :: PhaseNum -> Activation -> Bool
- competesWith :: Activation -> Activation -> Bool
- isNeverActive :: Activation -> Bool
- isAlwaysActive :: Activation -> Bool
- isEarlyActive :: Activation -> Bool
- data RuleMatchInfo
- isConLike :: RuleMatchInfo -> Bool
- isFunLike :: RuleMatchInfo -> Bool
- data InlineSpec
- isEmptyInlineSpec :: InlineSpec -> Bool
- data InlinePragma = InlinePragma {}
- defaultInlinePragma :: InlinePragma
- alwaysInlinePragma :: InlinePragma
- neverInlinePragma :: InlinePragma
- dfunInlinePragma :: InlinePragma
- isDefaultInlinePragma :: InlinePragma -> Bool
- isInlinePragma :: InlinePragma -> Bool
- isInlinablePragma :: InlinePragma -> Bool
- isAnyInlinePragma :: InlinePragma -> Bool
- inlinePragmaSpec :: InlinePragma -> InlineSpec
- inlinePragmaSat :: InlinePragma -> Maybe Arity
- inlinePragmaActivation :: InlinePragma -> Activation
- inlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo
- setInlinePragmaActivation :: InlinePragma -> Activation -> InlinePragma
- setInlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo -> InlinePragma
- pprInline :: InlinePragma -> SDoc
- pprInlineDebug :: InlinePragma -> SDoc
- data SuccessFlag
- succeeded :: SuccessFlag -> Bool
- failed :: SuccessFlag -> Bool
- successIf :: Bool -> SuccessFlag
- data FractionalLit = FL {}
- negateFractionalLit :: FractionalLit -> FractionalLit
- integralFractionalLit :: Integer -> FractionalLit
- data SourceText
- pprWithSourceText :: SourceText -> SDoc -> SDoc
- data IntWithInf
- infinity :: IntWithInf
- treatZeroAsInf :: Int -> IntWithInf
- mkIntWithInf :: Int -> IntWithInf
- intGtLimit :: Int -> IntWithInf -> Bool
- data SpliceExplicitFlag
Documentation
bumpVersion :: Version -> Version Source #
data LeftOrRight Source #
pickLR :: LeftOrRight -> (a, a) -> a Source #
Constructor Tag
Type of the tags associated with each constructor possibility or superclass selector
Tags are allocated from here for real constructors or for superclass selectors
The number of value arguments that can be applied to a value before it does "real work". So: fib 100 has arity 0 x -> fib x has arity 1 See also Note [Definition of arity] in CoreArity
The number of arguments that a join point takes. Unlike the arity of a function, this is a purely syntactic property and is fixed when the join point is created (or converted from a value). Both type and value arguments are counted.
data FunctionOrData Source #
data WarningTxt Source #
Warning Text
reason/explanation from a WARNING or DEPRECATED pragma
pprWarningTxtForMsg :: WarningTxt -> SDoc Source #
data StringLiteral Source #
A String Literal in the source, including its original raw format for use by source to source manipulation tools.
data FixityDirection Source #
maxPrecedence :: Int Source #
minPrecedence :: Int Source #
funTyFixity :: Fixity Source #
data LexicalFixity Source #
Captures the fixity of declarations as they are parsed. This is not necessarily the same as the fixity declaration, as the normal fixity may be overridden using parens or backticks.
Recursivity Flag
boolToRecFlag :: Bool -> RecFlag Source #
isGenerated :: Origin -> Bool Source #
type RuleName = FastString Source #
pprRuleName :: RuleName -> SDoc Source #
isTopLevel :: TopLevelFlag -> Bool Source #
isNotTopLevel :: TopLevelFlag -> Bool Source #
data DerivStrategy Source #
Which technique the user explicitly requested when deriving an instance.
StockStrategy | GHC's "standard" strategy, which is to implement a
custom instance for the data type. This only works
for certain types that GHC knows about (e.g., |
AnyclassStrategy | -XDeriveAnyClass |
NewtypeStrategy | -XGeneralizedNewtypeDeriving |
data OverlapFlag Source #
The semantics allowed for overlapping instances for a particular
instance. See Note [Safe Haskell isSafeOverlap] (in hs
) for a
explanation of the isSafeOverlap
field.
AnnKeywordId
:AnnOpen
'{-# OVERLAPPABLE'
or'{-# OVERLAPPING'
or'{-# OVERLAPS'
or'{-# INCOHERENT'
,AnnClose
`#-}`
,
data OverlapMode Source #
NoOverlap SourceText | This instance must not overlap another |
Overlappable SourceText | Silently ignore this instance if you find a more specific one that matches the constraint you are trying to resolve Example: constraint (Foo [Int]) instance Foo [Int] instance {--} Foo [a] Since the second instance has the Overlappable flag, the first instance will be chosen (otherwise its ambiguous which to choose) |
Overlapping SourceText | Silently ignore any more general instances that may be used to solve the constraint. Example: constraint (Foo [Int]) instance {--} Foo [Int] instance Foo [a] Since the first instance has the Overlapping flag, the second---more general---instance will be ignored (otherwise it is ambiguous which to choose) |
Overlaps SourceText | Equivalent to having both |
Incoherent SourceText | Behave like Overlappable and Overlapping, and in addition pick an an arbitrary one if there are multiple matching candidates, and don't worry about later instantiation Example: constraint (Foo [b])
instance {-# INCOHERENT -} Foo [Int]
instance Foo [a]
Without the Incoherent flag, we'd complain that
instantiating |
hasOverlappingFlag :: OverlapMode -> Bool Source #
hasIncoherentFlag :: OverlapMode -> Bool Source #
tupleSortBoxity :: TupleSort -> Boxity Source #
boxityTupleSort :: Boxity -> TupleSort Source #
:: (a -> SDoc) | The pretty printing function to use |
-> a | The things to be pretty printed |
-> ConTag | Alternative (one-based) |
-> Arity | Arity |
-> SDoc |
|
Pretty print an alternative in an unboxed sum e.g. "| a | |".
The OneShotInfo type
data OneShotInfo Source #
If the Id
is a lambda-bound variable then it may have lambda-bound
variable info. Sometimes we know whether the lambda binding this variable
is a "one-shot" lambda; that is, whether it is applied at most once.
This information may be useful in optimisation, as computations may safely be floated inside such a lambda without risk of duplicating work.
NoOneShotInfo | No information |
OneShotLam | The lambda is applied at most once. |
noOneShotInfo :: OneShotInfo Source #
It is always safe to assume that an Id
has no lambda-bound variable information
hasNoOneShotInfo :: OneShotInfo -> Bool Source #
isOneShotInfo :: OneShotInfo -> Bool Source #
bestOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo Source #
worstOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo Source #
identifier Occurrence Information
ManyOccs | There are many occurrences, or unknown occurrences |
| |
IAmDead | Marks unused variables. Sometimes useful for lambda and case-bound variables. |
OneOcc | Occurs exactly once (per branch), not inside a rule |
| |
IAmALoopBreaker | This identifier breaks a loop of mutually recursive functions. The field marks whether it is only a loop breaker due to a reference in a rule |
|
seqOccInfo :: OccInfo -> () Source #
zapFragileOcc :: OccInfo -> OccInfo Source #
isStrongLoopBreaker :: OccInfo -> Bool Source #
isWeakLoopBreaker :: OccInfo -> Bool Source #
isManyOccs :: OccInfo -> Bool Source #
type InterestingCxt = Bool Source #
Interesting Context
data TailCallInfo Source #
tailCallInfo :: OccInfo -> TailCallInfo Source #
zapOccTailCallInfo :: OccInfo -> OccInfo Source #
isAlwaysTailCalled :: OccInfo -> Bool Source #
data DefMethSpec ty Source #
Default Method Specification
Outputable (DefMethSpec ty) # | |
Binary (DefMethSpec IfaceType) # | |
data Activation Source #
isActive :: CompilerPhase -> Activation -> Bool Source #
isActiveIn :: PhaseNum -> Activation -> Bool Source #
competesWith :: Activation -> Activation -> Bool Source #
isNeverActive :: Activation -> Bool Source #
isAlwaysActive :: Activation -> Bool Source #
isEarlyActive :: Activation -> Bool Source #
data RuleMatchInfo Source #
Rule Match Information
isConLike :: RuleMatchInfo -> Bool Source #
isFunLike :: RuleMatchInfo -> Bool Source #
data InlineSpec Source #
Inline Specification
isEmptyInlineSpec :: InlineSpec -> Bool Source #
data InlinePragma Source #
InlinePragma | |
|
isInlinePragma :: InlinePragma -> Bool Source #
isInlinablePragma :: InlinePragma -> Bool Source #
isAnyInlinePragma :: InlinePragma -> Bool Source #
inlinePragmaSat :: InlinePragma -> Maybe Arity Source #
pprInline :: InlinePragma -> SDoc Source #
pprInlineDebug :: InlinePragma -> SDoc Source #
succeeded :: SuccessFlag -> Bool Source #
failed :: SuccessFlag -> Bool Source #
successIf :: Bool -> SuccessFlag Source #
data FractionalLit Source #
Fractional Literal
Used (instead of Rational) to represent exactly the floating point literal that we encountered in the user's source program. This allows us to pretty-print exactly what the user wrote, which is important e.g. for floating point numbers that can't represented as Doubles (we used to via Double for pretty-printing). See also #2245.
data SourceText Source #
SourceText String | |
NoSourceText | For when code is generated, e.g. TH, deriving. The pretty printer will then make its own representation of the item. |
pprWithSourceText :: SourceText -> SDoc -> SDoc Source #
Special combinator for showing string literals.
data IntWithInf Source #
An integer or infinity
infinity :: IntWithInf Source #
A representation of infinity
treatZeroAsInf :: Int -> IntWithInf Source #
Turn a positive number into an IntWithInf
, where 0 represents infinity
mkIntWithInf :: Int -> IntWithInf Source #
Inject any integer into an IntWithInf
intGtLimit :: Int -> IntWithInf -> Bool Source #
data SpliceExplicitFlag Source #
ExplicitSplice | = $(f x y) |
ImplicitSplice | = f x y, i.e. a naked top level expression |