Safe Haskell | None |
---|---|
Language | Haskell2010 |
- 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 = OverlapFlag {}
- data OverlapMode
- setOverlapModeMaybe :: OverlapFlag -> Maybe OverlapMode -> OverlapFlag
- hasOverlappingFlag :: OverlapMode -> Bool
- hasOverlappableFlag :: OverlapMode -> Bool
- 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
- type SourceText = String
Documentation
bumpVersion :: Version -> Version Source
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
data WarningTxt Source
data FixityDirection Source
boolToRecFlag :: Bool -> RecFlag Source
isGenerated :: Origin -> Bool Source
type RuleName = FastString 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 lhs
) 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 |
tupleSortBoxity :: TupleSort -> Boxity Source
tupleParens :: TupleSort -> SDoc -> SDoc 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.
NoOneShotInfo | No information |
ProbOneShot | The lambda is probably applied at most once See Note [Computing one-shot info, and ProbOneShot] in OccurAnl |
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
isOneShotInfo :: OneShotInfo -> Bool Source
bestOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo Source
worstOneShot :: OneShotInfo -> OneShotInfo -> OneShotInfo Source
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
zapFragileOcc :: OccInfo -> OccInfo Source
isStrongLoopBreaker :: OccInfo -> Bool Source
isWeakLoopBreaker :: OccInfo -> Bool Source
type InterestingCxt = Bool Source
data DefMethSpec Source
data Activation Source
isActive :: CompilerPhase -> Activation -> Bool Source
isActiveIn :: PhaseNum -> Activation -> Bool Source
isNeverActive :: Activation -> Bool Source
isAlwaysActive :: Activation -> Bool Source
isEarlyActive :: Activation -> Bool Source
data RuleMatchInfo Source
isConLike :: RuleMatchInfo -> Bool Source
isFunLike :: RuleMatchInfo -> Bool Source
data InlineSpec Source
data InlinePragma Source
InlinePragma | |
|
isInlinePragma :: InlinePragma -> Bool Source
succeeded :: SuccessFlag -> Bool Source
failed :: SuccessFlag -> Bool Source
successIf :: Bool -> SuccessFlag Source
data FractionalLit Source
type SourceText = String Source