ghc-6.10.2: The GHC APIContentsIndex
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 InlineSpec = Inline Activation Bool
defaultInlineSpec :: InlineSpec
alwaysInlineSpec :: InlineSpec
neverInlineSpec :: InlineSpec
data SuccessFlag
= Succeeded
| Failed
succeeded :: SuccessFlag -> Bool
failed :: SuccessFlag -> Bool
successIf :: Bool -> SuccessFlag
Documentation
type Version = Int
bumpVersion :: Version -> Version
initialVersion :: Version
type Arity = Int
data FunctionOrData
Constructors
IsFunction
IsData
show/hide Instances
data WarningTxt
Constructors
WarningTxt FastString
DeprecatedTxt FastString
show/hide Instances
data Fixity
Constructors
Fixity Int FixityDirection
show/hide Instances
data FixityDirection
Constructors
InfixL
InfixR
InfixN
show/hide Instances
defaultFixity :: Fixity
maxPrecedence :: Int
negateFixity :: Fixity
funTyFixity :: Fixity
compareFixity :: Fixity -> Fixity -> (Bool, Bool)
newtype IPName name
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 -> name
mapIPName :: (a -> b) -> IPName a -> IPName b
data RecFlag
Constructors
Recursive
NonRecursive
show/hide Instances
isRec :: RecFlag -> Bool
isNonRec :: RecFlag -> Bool
boolToRecFlag :: Bool -> RecFlag
type RuleName = FastString
data TopLevelFlag
Constructors
TopLevel
NotTopLevel
show/hide Instances
isTopLevel :: TopLevelFlag -> Bool
isNotTopLevel :: TopLevelFlag -> Bool
data OverlapFlag
Constructors
NoOverlap
OverlapOk
Incoherent
show/hide Instances
data Boxity
Constructors
Boxed
Unboxed
show/hide Instances
isBoxed :: Boxity -> Bool
data TupCon
Constructors
TupCon Boxity Arity
show/hide Instances
tupleParens :: Boxity -> SDoc -> SDoc
data OccInfo
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 -> ()
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
Constructors
EP
fromEP :: a
toEP :: a
data StrictnessMark
Constructors
MarkedStrict
MarkedUnboxed
NotMarkedStrict
show/hide Instances
isMarkedUnboxed :: StrictnessMark -> Bool
isMarkedStrict :: StrictnessMark -> Bool
type CompilerPhase = Int
data Activation
Constructors
NeverActive
AlwaysActive
ActiveBefore CompilerPhase
ActiveAfter CompilerPhase
show/hide Instances
isActive :: CompilerPhase -> Activation -> Bool
isNeverActive :: Activation -> Bool
isAlwaysActive :: Activation -> Bool
data InlineSpec
Constructors
Inline Activation Bool
show/hide Instances
defaultInlineSpec :: InlineSpec
alwaysInlineSpec :: InlineSpec
neverInlineSpec :: InlineSpec
data SuccessFlag
Constructors
Succeeded
Failed
show/hide Instances
succeeded :: SuccessFlag -> Bool
failed :: SuccessFlag -> Bool
successIf :: Bool -> SuccessFlag
Produced by Haddock version 2.4.2