Safe Haskell | None |
---|
BasicTypes
- type Version = Int
- bumpVersion :: Version -> Version
- initialVersion :: Version
- type Arity = Int
- type Alignment = 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 TupleSort
- tupleSortBoxity :: TupleSort -> Boxity
- boxityNormalTupleSort :: Boxity -> TupleSort
- tupleParens :: TupleSort -> SDoc -> SDoc
- 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 HsBang
- = HsNoBang
- | HsStrict
- | HsUnpack
- | HsUnpackFailed
- | HsNoUnpack
- 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
- data FractionalLit = FL {}
- negateFractionalLit :: FractionalLit -> FractionalLit
- integralFractionalLit :: Integer -> FractionalLit
Documentation
bumpVersion :: Version -> VersionSource
data FunctionOrData Source
Constructors
IsFunction | |
IsData |
data WarningTxt Source
Constructors
WarningTxt [FastString] | |
DeprecatedTxt [FastString] |
Constructors
Fixity Int FixityDirection |
data FixityDirection Source
Constructors
IPName name |
ipNameName :: IPName name -> nameSource
Constructors
Recursive | |
NonRecursive |
boolToRecFlag :: Bool -> RecFlagSource
type RuleName = FastStringSource
isTopLevel :: TopLevelFlag -> BoolSource
data OverlapFlag Source
Constructors
NoOverlap | This instance must not overlap another |
Fields | |
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) |
Fields | |
Incoherent | Like OverlapOk, but also ignore this instance if it doesn't match the constraint you are trying to resolve, but could match if the type variables in the constraint were instantiated Example: constraint (Foo [b])
instances (Foo [Int]) Incoherent
(Foo [a])
Without the Incoherent flag, we'd complain that
instantiating |
Fields |
Constructors
BoxedTuple | |
UnboxedTuple | |
ConstraintTuple |
tupleParens :: TupleSort -> SDoc -> SDocSource
Identifier occurrence information
Constructors
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 |
Instances
seqOccInfo :: OccInfo -> ()Source
type InterestingCxt = BoolSource
Constructors
HsNoBang | |
HsStrict | |
HsUnpack | |
HsUnpackFailed | |
HsNoUnpack |
isMarkedUnboxed :: HsBang -> BoolSource
data DefMethSpec Source
Instances
data Activation Source
Constructors
NeverActive | |
AlwaysActive | |
ActiveBefore PhaseNum | |
ActiveAfter PhaseNum |
isActive :: CompilerPhase -> Activation -> BoolSource
isActiveIn :: PhaseNum -> Activation -> BoolSource
data RuleMatchInfo Source
isConLike :: RuleMatchInfo -> BoolSource
isFunLike :: RuleMatchInfo -> BoolSource
data InlineSpec Source
Constructors
Inline | |
Inlinable | |
NoInline | |
EmptyInlineSpec |
data InlinePragma Source
Constructors
InlinePragma | |
Fields
|
succeeded :: SuccessFlag -> BoolSource
failed :: SuccessFlag -> BoolSource
successIf :: Bool -> SuccessFlagSource
data FractionalLit Source