Safe Haskell | None |
---|---|
Language | Haskell2010 |
BasicTypes
Contents
- type Version = Int
- bumpVersion :: Version -> Version
- initialVersion :: Version
- type ConTag = Int
- fIRST_TAG :: ConTag
- type Arity = Int
- type RepArity = Int
- type Alignment = Int
- data FunctionOrData
- = IsFunction
- | IsData
- data WarningTxt
- 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 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
- data Boxity
- isBoxed :: Boxity -> Bool
- data TupleSort
- tupleSortBoxity :: TupleSort -> Boxity
- boxityTupleSort :: Boxity -> TupleSort
- tupleParens :: TupleSort -> SDoc -> SDoc
- data OneShotInfo
- noOneShotInfo :: OneShotInfo
- hasNoOneShotInfo :: OneShotInfo -> Bool
- isOneShotInfo :: OneShotInfo -> Bool
- bestOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo
- worstOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo
- data OccInfo
- = NoOccInfo
- | IAmDead
- | OneOcc !InsideLam !OneBranch !InterestingCxt
- | IAmALoopBreaker !RulesOnly
- seqOccInfo :: OccInfo -> ()
- zapFragileOcc :: OccInfo -> OccInfo
- isOneOcc :: OccInfo -> Bool
- isDeadOcc :: OccInfo -> Bool
- isStrongLoopBreaker :: OccInfo -> Bool
- isWeakLoopBreaker :: OccInfo -> Bool
- isNoOcc :: OccInfo -> Bool
- strongLoopBreaker :: OccInfo
- weakLoopBreaker :: OccInfo
- type InsideLam = Bool
- insideLam :: InsideLam
- notInsideLam :: InsideLam
- type OneBranch = Bool
- oneBranch :: OneBranch
- notOneBranch :: OneBranch
- type InterestingCxt = 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
- data SuccessFlag
- succeeded :: SuccessFlag -> Bool
- failed :: SuccessFlag -> Bool
- successIf :: Bool -> SuccessFlag
- data FractionalLit = FL {}
- negateFractionalLit :: FractionalLit -> FractionalLit
- integralFractionalLit :: Integer -> FractionalLit
- type SourceText = String
- data IntWithInf
- infinity :: IntWithInf
- treatZeroAsInf :: Int -> IntWithInf
- mkIntWithInf :: Int -> IntWithInf
- intGtLimit :: Int -> IntWithInf -> Bool
Documentation
bumpVersion :: Version -> Version Source #
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
data FunctionOrData Source #
Constructors
IsFunction | |
IsData |
data WarningTxt Source #
Constructors
WarningTxt (Located SourceText) [Located StringLiteral] | |
DeprecatedTxt (Located SourceText) [Located StringLiteral] |
Instances
data StringLiteral Source #
A String Literal in the source, including its original raw format for use by source to source manipulation tools.
Constructors
StringLiteral | |
Fields
|
Instances
Constructors
Fixity SourceText Int FixityDirection |
data FixityDirection Source #
maxPrecedence :: Int Source #
minPrecedence :: Int Source #
funTyFixity :: Fixity Source #
Constructors
Recursive | |
NonRecursive |
boolToRecFlag :: Bool -> RecFlag Source #
Constructors
FromSource | |
Generated |
isGenerated :: Origin -> Bool Source #
type RuleName = FastString Source #
pprRuleName :: RuleName -> 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 hs
) for a
explanation of the isSafeOverlap
field.
AnnKeywordId
:AnnOpen
'{-# OVERLAPPABLE'
or'{-# OVERLAPPING'
or'{-# OVERLAPS'
or'{-# INCOHERENT'
,AnnClose
`#-}`
,
Constructors
OverlapFlag | |
Fields |
Instances
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 {--} 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 |
Instances
hasOverlappingFlag :: OverlapMode -> Bool Source #
Constructors
BoxedTuple | |
UnboxedTuple | |
ConstraintTuple |
tupleSortBoxity :: TupleSort -> Boxity Source #
boxityTupleSort :: Boxity -> TupleSort Source #
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.
Constructors
NoOneShotInfo | No information |
ProbOneShot | The lambda is probably applied at most once See Note [Computing one-shot info, and ProbOneShot] in Demand |
OneShotLam | The lambda is applied at most once. |
Instances
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
NoOccInfo | There are many occurrences, or unknown occurrences |
IAmDead | Marks unused variables. Sometimes useful for lambda and case-bound variables. |
OneOcc !InsideLam !OneBranch !InterestingCxt | Occurs exactly once, not inside a rule |
IAmALoopBreaker !RulesOnly | 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 #
type InterestingCxt = Bool Source #
data DefMethSpec ty Source #
Instances
Outputable (DefMethSpec ty) # | |
Binary (DefMethSpec IfaceType) # | |
data Activation Source #
Constructors
NeverActive | |
AlwaysActive | |
ActiveBefore SourceText PhaseNum | |
ActiveAfter SourceText PhaseNum |
Instances
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 #
Instances
isConLike :: RuleMatchInfo -> Bool Source #
isFunLike :: RuleMatchInfo -> Bool Source #
isEmptyInlineSpec :: InlineSpec -> Bool Source #
data InlinePragma Source #
Constructors
InlinePragma | |
Fields
|
Instances
isInlinePragma :: InlinePragma -> Bool Source #
isInlinablePragma :: InlinePragma -> Bool Source #
isAnyInlinePragma :: InlinePragma -> Bool Source #
inlinePragmaSat :: InlinePragma -> Maybe Arity Source #
succeeded :: SuccessFlag -> Bool Source #
failed :: SuccessFlag -> Bool Source #
successIf :: Bool -> SuccessFlag Source #
data FractionalLit Source #
Instances
type SourceText = String Source #
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 #