Safe Haskell | None |
---|---|
Language | Haskell98 |
- 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 Fixity = Fixity 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
- data TopLevelFlag
- isTopLevel :: TopLevelFlag -> Bool
- isNotTopLevel :: TopLevelFlag -> Bool
- data OverlapFlag
- = NoOverlap { }
- | OverlapOk { }
- | Incoherent { }
- data Boxity
- isBoxed :: Boxity -> Bool
- data TupleSort
- tupleSortBoxity :: TupleSort -> Boxity
- boxityNormalTupleSort :: 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
- 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
- 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
- newtype HValue = HValue Any
Documentation
bumpVersion :: Version -> VersionSource
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
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
data FunctionOrDataSource
data WarningTxtSource
boolToRecFlag :: Bool -> RecFlagSource
isGenerated :: Origin -> BoolSource
type RuleName = FastStringSource
isTopLevel :: TopLevelFlag -> BoolSource
data OverlapFlagSource
The semantics allowed for overlapping instances for a particular
instance. See Note [Safe Haskell isSafeOverlap] (in lhs
) for a
explanation of the isSafeOverlap
field.
NoOverlap | This instance must not overlap another |
OverlapOk | Silently ignore this instance if you find a more specific one that matches the constraint you are trying to resolve Example: constraint (Foo [Int]) instances (Foo [Int]) (Foo [a]) OverlapOk Since the second instance has the OverlapOk flag, the first instance will be chosen (otherwise its ambiguous which to choose) |
Incoherent | Silently ignore this instance if you find any other that matches the constraing you are trying to resolve, including when checking if there are instances that do not match, but unify. Example: constraint (Foo [b])
instances (Foo [Int]) Incoherent
(Foo [a])
Without the Incoherent flag, we'd complain that
instantiating |
tupleParens :: TupleSort -> SDoc -> SDocSource
The OneShotInfo type
data OneShotInfoSource
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 |
ProbOneShot | The lambda is probably applied at most once |
OneShotLam | The lambda is applied at most once. |
noOneShotInfo :: OneShotInfoSource
It is always safe to assume that an Id
has no lambda-bound variable information
Identifier occurrence information
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
type InterestingCxt = BoolSource
data ActivationSource
isActive :: CompilerPhase -> Activation -> BoolSource
isActiveIn :: PhaseNum -> Activation -> BoolSource
data RuleMatchInfoSource
isConLike :: RuleMatchInfo -> BoolSource
isFunLike :: RuleMatchInfo -> BoolSource
data InlineSpecSource
data InlinePragmaSource
succeeded :: SuccessFlag -> BoolSource
failed :: SuccessFlag -> BoolSource
successIf :: Bool -> SuccessFlagSource
data FractionalLitSource