ghc-6.12.1: The GHC APISource codeContentsIndex
BasicTypes
Synopsis
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
= InfixL
| InfixR
| InfixN
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
= Recursive
| NonRecursive
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
= Boxed
| Unboxed
isBoxed :: Boxity -> Bool
data TupCon = TupCon Boxity Arity
tupleParens :: Boxity -> SDoc -> SDoc
data OccInfo
= NoOccInfo
| IAmDead
| OneOcc !InsideLam !OneBranch !InterestingCxt
| IAmALoopBreaker !RulesOnly
seqOccInfo :: OccInfo -> ()
isFragileOcc :: OccInfo -> Bool
isOneOcc :: OccInfo -> Bool
isDeadOcc :: OccInfo -> Bool
isLoopBreaker :: OccInfo -> Bool
isNonRuleLoopBreaker :: OccInfo -> Bool
isNoOcc :: OccInfo -> Bool
type InsideLam = Bool
insideLam :: InsideLam
notInsideLam :: InsideLam
type OneBranch = Bool
oneBranch :: OneBranch
notOneBranch :: OneBranch
type InterestingCxt = Bool
data EP a = EP {
fromEP :: a
toEP :: a
}
data StrictnessMark
= MarkedStrict
| MarkedUnboxed
| NotMarkedStrict
isMarkedUnboxed :: StrictnessMark -> Bool
isMarkedStrict :: StrictnessMark -> Bool
type CompilerPhase = Int
data Activation
= NeverActive
| AlwaysActive
| ActiveBefore CompilerPhase
| ActiveAfter CompilerPhase
isActive :: CompilerPhase -> Activation -> Bool
isNeverActive :: Activation -> Bool
isAlwaysActive :: Activation -> Bool
data RuleMatchInfo
= ConLike
| FunLike
isConLike :: RuleMatchInfo -> Bool
isFunLike :: RuleMatchInfo -> Bool
data InlinePragma = InlinePragma Activation RuleMatchInfo
defaultInlinePragma :: InlinePragma
isDefaultInlinePragma :: InlinePragma -> Bool
inlinePragmaActivation :: InlinePragma -> Activation
inlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo
setInlinePragmaActivation :: InlinePragma -> Activation -> InlinePragma
setInlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo -> InlinePragma
data InlineSpec = Inline InlinePragma Bool
defaultInlineSpec :: InlineSpec
alwaysInlineSpec :: RuleMatchInfo -> InlineSpec
neverInlineSpec :: RuleMatchInfo -> InlineSpec
data SuccessFlag
= Succeeded
| Failed
succeeded :: SuccessFlag -> Bool
failed :: SuccessFlag -> Bool
successIf :: Bool -> SuccessFlag
Documentation
type Version = IntSource
bumpVersion :: Version -> VersionSource
initialVersion :: VersionSource
type Arity = IntSource
data FunctionOrData Source
Constructors
IsFunction
IsData
show/hide Instances
data WarningTxt Source
Constructors
WarningTxt [FastString]
DeprecatedTxt [FastString]
show/hide Instances
data Fixity Source
Constructors
Fixity Int FixityDirection
show/hide Instances
data FixityDirection Source
Constructors
InfixL
InfixR
InfixN
show/hide Instances
defaultFixity :: FixitySource
maxPrecedence :: IntSource
negateFixity :: FixitySource
funTyFixity :: FixitySource
compareFixity :: Fixity -> Fixity -> (Bool, Bool)Source
newtype IPName name Source
Constructors
IPName name
show/hide Instances
Eq name => Eq (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
mapIPName :: (a -> b) -> IPName a -> IPName bSource
data RecFlag Source
Constructors
Recursive
NonRecursive
show/hide Instances
isRec :: RecFlag -> BoolSource
isNonRec :: RecFlag -> BoolSource
boolToRecFlag :: Bool -> RecFlagSource
type RuleName = FastStringSource
data TopLevelFlag Source
Constructors
TopLevel
NotTopLevel
show/hide Instances
isTopLevel :: TopLevelFlag -> BoolSource
isNotTopLevel :: TopLevelFlag -> BoolSource
data OverlapFlag Source
Constructors
NoOverlap
OverlapOk
Incoherent
show/hide Instances
data Boxity Source
Constructors
Boxed
Unboxed
show/hide Instances
isBoxed :: Boxity -> BoolSource
data TupCon Source
Constructors
TupCon Boxity Arity
show/hide Instances
tupleParens :: Boxity -> SDoc -> SDocSource
data OccInfo Source
Identifier occurrence information
Constructors
NoOccInfoThere are many occurrences, or unknown occurences
IAmDeadMarks unused variables. Sometimes useful for lambda and case-bound variables.
OneOcc !InsideLam !OneBranch !InterestingCxtOccurs exactly once, not inside a rule
IAmALoopBreaker !RulesOnlyThis 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
show/hide Instances
seqOccInfo :: OccInfo -> ()Source
isFragileOcc :: OccInfo -> BoolSource
isOneOcc :: OccInfo -> BoolSource
isDeadOcc :: OccInfo -> BoolSource
isLoopBreaker :: OccInfo -> BoolSource
isNonRuleLoopBreaker :: OccInfo -> BoolSource
isNoOcc :: OccInfo -> BoolSource
type InsideLam = BoolSource
insideLam :: InsideLamSource
notInsideLam :: InsideLamSource
type OneBranch = BoolSource
oneBranch :: OneBranchSource
notOneBranch :: OneBranchSource
type InterestingCxt = BoolSource
data EP a Source
Constructors
EP
fromEP :: a
toEP :: a
data StrictnessMark Source
Constructors
MarkedStrict
MarkedUnboxed
NotMarkedStrict
show/hide Instances
isMarkedUnboxed :: StrictnessMark -> BoolSource
isMarkedStrict :: StrictnessMark -> BoolSource
type CompilerPhase = IntSource
data Activation Source
Constructors
NeverActive
AlwaysActive
ActiveBefore CompilerPhase
ActiveAfter CompilerPhase
show/hide Instances
isActive :: CompilerPhase -> Activation -> BoolSource
isNeverActive :: Activation -> BoolSource
isAlwaysActive :: Activation -> BoolSource
data RuleMatchInfo Source
Constructors
ConLike
FunLike
show/hide Instances
isConLike :: RuleMatchInfo -> BoolSource
isFunLike :: RuleMatchInfo -> BoolSource
data InlinePragma Source
Constructors
InlinePragma Activation RuleMatchInfo
show/hide Instances
defaultInlinePragma :: InlinePragmaSource
isDefaultInlinePragma :: InlinePragma -> BoolSource
inlinePragmaActivation :: InlinePragma -> ActivationSource
inlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfoSource
setInlinePragmaActivation :: InlinePragma -> Activation -> InlinePragmaSource
setInlinePragmaRuleMatchInfo :: InlinePragma -> RuleMatchInfo -> InlinePragmaSource
data InlineSpec Source
Constructors
Inline InlinePragma Bool
show/hide Instances
defaultInlineSpec :: InlineSpecSource
alwaysInlineSpec :: RuleMatchInfo -> InlineSpecSource
neverInlineSpec :: RuleMatchInfo -> InlineSpecSource
data SuccessFlag Source
Constructors
Succeeded
Failed
show/hide Instances
succeeded :: SuccessFlag -> BoolSource
failed :: SuccessFlag -> BoolSource
successIf :: Bool -> SuccessFlagSource
Produced by Haddock version 2.6.0