- type Version = Int
- bumpVersion :: Version -> Version
- initialVersion :: Version
- type Arity = Int
- data FunctionOrData
- = IsFunction
- | IsData
- data WarningTxt
- = WarningTxt [FastString]
- | DeprecatedTxt [FastString]
- data Fixity = Fixity Int FixityDirection
- data FixityDirection
- defaultFixity :: Fixity
- maxPrecedence :: Int
- negateFixity :: Fixity
- funTyFixity :: Fixity
- compareFixity :: Fixity -> Fixity -> (Bool, Bool)
- newtype IPName name = IPName name
- ipNameName :: IPName name -> name
- mapIPName :: (a -> b) -> IPName a -> IPName b
- data RecFlag
- isRec :: RecFlag -> Bool
- isNonRec :: RecFlag -> Bool
- boolToRecFlag :: Bool -> RecFlag
- type RuleName = FastString
- data TopLevelFlag
- = TopLevel
- | NotTopLevel
- isTopLevel :: TopLevelFlag -> Bool
- isNotTopLevel :: TopLevelFlag -> Bool
- data OverlapFlag
- = NoOverlap
- | OverlapOk
- | Incoherent
- data Boxity
- isBoxed :: Boxity -> Bool
- data TupCon = TupCon Boxity Arity
- tupleParens :: Boxity -> SDoc -> SDoc
- data OccInfo
- = NoOccInfo
- | IAmDead
- | OneOcc !InsideLam !OneBranch !InterestingCxt
- | IAmALoopBreaker !RulesOnly
- seqOccInfo :: OccInfo -> ()
- zapFragileOcc :: OccInfo -> OccInfo
- isOneOcc :: OccInfo -> Bool
- isDeadOcc :: OccInfo -> Bool
- isLoopBreaker :: OccInfo -> Bool
- isNonRuleLoopBreaker :: OccInfo -> Bool
- isNoOcc :: OccInfo -> Bool
- nonRuleLoopBreaker :: OccInfo
- type InsideLam = Bool
- insideLam :: InsideLam
- notInsideLam :: InsideLam
- type OneBranch = Bool
- oneBranch :: OneBranch
- notOneBranch :: OneBranch
- type InterestingCxt = Bool
- data EP a = EP {}
- data HsBang
- = HsNoBang
- | HsStrict
- | HsUnpack
- | HsUnpackFailed
- isBanged :: HsBang -> Bool
- isMarkedUnboxed :: HsBang -> Bool
- data StrictnessMark
- isMarkedStrict :: StrictnessMark -> Bool
- data DefMethSpec
- 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
- = Inline
- | Inlinable
- | NoInline
- | EmptyInlineSpec
- 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
Documentation
bumpVersion :: Version -> VersionSource
data FunctionOrData Source
data WarningTxt Source
data FixityDirection Source
IPName name |
Typeable1 IPName | |
Eq name => Eq (IPName name) | |
Data name => Data (IPName name) | |
Ord name => Ord (IPName name) | |
Outputable name => OutputableBndr (IPName name) | |
Outputable name => Outputable (IPName name) | |
Binary name => Binary (IPName name) |
ipNameName :: IPName name -> nameSource
boolToRecFlag :: Bool -> RecFlagSource
type RuleName = FastStringSource
isTopLevel :: TopLevelFlag -> BoolSource
data OverlapFlag Source
tupleParens :: Boxity -> SDoc -> SDocSource
Identifier occurrence information
NoOccInfo | There are many occurrences, or unknown occurences |
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
isLoopBreaker :: OccInfo -> BoolSource
type InterestingCxt = BoolSource
isMarkedUnboxed :: HsBang -> BoolSource
data Activation Source
isActive :: CompilerPhase -> Activation -> BoolSource
isActiveIn :: PhaseNum -> Activation -> BoolSource
data RuleMatchInfo Source
isConLike :: RuleMatchInfo -> BoolSource
isFunLike :: RuleMatchInfo -> BoolSource
data InlineSpec Source
data InlinePragma Source
succeeded :: SuccessFlag -> BoolSource
failed :: SuccessFlag -> BoolSource
successIf :: Bool -> SuccessFlagSource