YhcSource codeContentsIndex
Info
Description
Central data structures of the symbol table
Synopsis
data IE
= IEnone
| IEsel
| IEsome
| IEabs
| IEall
isExported :: IE -> Bool
combIE :: IE -> IE -> IE
patchIE :: IE -> IE
data DataKind
= DataTypeSynonym Bool Int
| DataNewType Bool [Id]
| Data Bool [Id]
| DataPrimitive Int
data Info
= InfoClear
| InfoUsed Id [(IdKind, TokenId, PackedString, Pos)]
| InfoUsedClass Id [(IdKind, TokenId, PackedString, Pos)] (Map Id (PackedString, [Id], [(Id, Id)]))
| InfoData Id TokenId IE NewType DataKind
| InfoClass Id TokenId IE NewType [Id] [Id] (Map Id (PackedString, [Id], [(Id, Id)]))
| InfoVar Id TokenId IE (InfixClass TokenId, Int) NewType (Maybe Int)
| InfoConstr Id TokenId IE (InfixClass TokenId, Int) NewType [Maybe Id] Id
| InfoField Id TokenId IE [(Id, Int)] Id Id
| InfoMethod Id TokenId IE (InfixClass TokenId, Int) NewType (Maybe Int) Id
| InfoIMethod Id TokenId NewType (Maybe Int) Id
| InfoDMethod Id TokenId NewType (Maybe Int) Id
| InfoInstance Id PackedString NewType Id
| InfoName Id TokenId Int TokenId Bool
clearI :: a -> Info
isMethod :: Info -> Bool
isData :: Info -> Bool
isRealData :: Info -> Bool
isRenamingFor :: Map Id Info -> Info -> NewType
isDataUnBoxed :: Info -> Bool
isField :: Info -> Bool
isClass :: Info -> Bool
isUsedClass :: Info -> Bool
isConstr :: Info -> Bool
depthI :: Info -> Maybe Int
typeSynonymBodyI :: Info -> Maybe NewType
updTypeSynonym :: Bool -> Int -> Info -> Info
updNewType :: Bool -> Info -> Info
newNT :: NewType -> Info -> Info
ntI :: Info -> NewType
maybeNtI :: Info -> Maybe NewType
strictI :: Info -> [Bool]
qDefI :: Info -> Bool
uniqueI :: Info -> Id
descI :: Info -> String
tidI :: Info -> TokenId
cmpTid :: TokenId -> Info -> Bool
methodsI :: Info -> [(Id, Id)]
instancesI :: Info -> Map Id (PackedString, [Id], [(Id, Id)])
superclassesI :: Info -> [Id]
addInstanceI :: Id -> PackedString -> [Id] -> [(Id, Id)] -> Info -> Info
joinInsts :: Map Id a -> Map Id a -> Map Id a
constrsI :: Info -> [Id]
updConstrsI :: Info -> [Id] -> Info
fieldsI :: Info -> [Maybe Id]
combInfo :: Info -> Info -> Info
expI :: Info -> IE
arityVI :: Info -> Int
arityI :: Info -> Int
arityIM :: Info -> Int
fixityI :: Info -> (InfixClass TokenId, Int)
belongstoI :: Info -> Id
profI :: Info -> TokenId
module Id
data IdKind
data TokenId
data NewType
data InfixClass a
= InfixDef
| InfixL
| InfixR
| Infix
| InfixPre a
data Pos
Documentation
data IE

This is Interface Exports

   defined in a lattice   IEall
                         /     \
                        |     IEsome
                      IEsel     |
                        |     IEabs
                         \     /
                          IEnone
  IEall  -> exported (with all constructors/fields/methods)
  IEsome -> exported with selected constructors/fields/methods
  IEabs  -> exported abstractly (without constructors/fields/methods)
  IEnone -> not exported
  IEsel  -> selected constructors/fields/methods
                      (is exported, despite defn below!)
Constructors
IEnone
IEsel
IEsome
IEabs
IEall
show/hide Instances
Eq IE
Show IE
isExported :: IE -> Bool
combIE :: IE -> IE -> IE
patchIE :: IE -> IE
Patch newtype for exports (Its constructor must always be in the interface file, even if not visible in the importing module.)
data DataKind
Constructors
DataTypeSynonym Bool Int
DataNewType Bool [Id]
Data Bool [Id]
DataPrimitive Int
show/hide Instances
data Info
Given all the selector functions below, shouldn't these constructors be record constructors? -SamB
Constructors
InfoClear
InfoUsed Id [(IdKind, TokenId, PackedString, Pos)]
InfoUsedClass Id [(IdKind, TokenId, PackedString, Pos)] (Map Id (PackedString, [Id], [(Id, Id)]))
InfoData Id TokenId IE NewType DataKind
InfoClass Id TokenId IE NewType [Id] [Id] (Map Id (PackedString, [Id], [(Id, Id)]))
InfoVar Id TokenId IE (InfixClass TokenId, Int) NewType (Maybe Int)
InfoConstr Id TokenId IE (InfixClass TokenId, Int) NewType [Maybe Id] Id
InfoField Id TokenId IE [(Id, Int)] Id Id
InfoMethod Id TokenId IE (InfixClass TokenId, Int) NewType (Maybe Int) Id
InfoIMethod Id TokenId NewType (Maybe Int) Id
InfoDMethod Id TokenId NewType (Maybe Int) Id
InfoInstance Id PackedString NewType IdOnly used in Export
InfoName Id TokenId Int TokenId Bool
show/hide Instances
Show Info
clearI :: a -> Info
isMethod :: Info -> Bool
isData :: Info -> Bool
isRealData :: Info -> Bool
isRenamingFor :: Map Id Info -> Info -> NewType
isDataUnBoxed :: Info -> Bool
isField :: Info -> Bool
isClass :: Info -> Bool
isUsedClass :: Info -> Bool
isConstr :: Info -> Bool
depthI :: Info -> Maybe Int
typeSynonymBodyI :: Info -> Maybe NewType
updTypeSynonym :: Bool -> Int -> Info -> Info
updNewType :: Bool -> Info -> Info
Sets the unboxedness information in newtype info as given.
newNT :: NewType -> Info -> Info
Sets the type information in variable info as given. Is only applied to identifiers without types,i.e. never methods of any kind!
ntI :: Info -> NewType
maybeNtI :: Info -> Maybe NewType
strictI :: Info -> [Bool]
qDefI :: Info -> Bool
uniqueI :: Info -> Id
descI :: Info -> String
tidI :: Info -> TokenId
cmpTid :: TokenId -> Info -> Bool
methodsI :: Info -> [(Id, Id)]
instancesI :: Info -> Map Id (PackedString, [Id], [(Id, Id)])
superclassesI :: Info -> [Id]
Return identifiers of all superclasses of the class which is described by given info.
addInstanceI :: Id -> PackedString -> [Id] -> [(Id, Id)] -> Info -> Info

Add information about an instance to info of a class. If information about this instance exists already in info, then info left unchanged.

type constructor -> free type variables -> context -> class info -> class info

joinInsts :: Map Id a -> Map Id a -> Map Id a
In joining two trees for describing instances the second one gets precedence in case of conflict.
constrsI :: Info -> [Id]
Determine constructors of a type from the info of the type
updConstrsI :: Info -> [Id] -> Info
fieldsI :: Info -> [Maybe Id]
combInfo :: Info -> Info -> Info
expI :: Info -> IE
arityVI :: Info -> Int
arity without context (Visible)
arityI :: Info -> Int
arity with context
arityIM :: Info -> Int
fixityI :: Info -> (InfixClass TokenId, Int)
belongstoI :: Info -> Id
profI :: Info -> TokenId
module Id
data IdKind
show/hide Instances
Eq IdKind
Ord IdKind
Show IdKind
data TokenId
show/hide Instances
data NewType
Perhaps NewType is a type schema? It quantifies variables over an arrow of NTs.
show/hide Instances
data InfixClass a
Constructors
InfixDef
InfixL
InfixR
Infix
InfixPre a
show/hide Instances
Eq (InfixClass a)
Show a => Show (InfixClass a)
data Pos
abstract type for storing the position of a syntactic construct in a file, that is, line and column number of both start and end positions.
show/hide Instances
Eq Pos
Ord Pos
Show Pos
Produced by Haddock version 0.8