Copyright | (c) 2008 Benedikt Huber based on code from c2hs (c) [1999..2001] Manuel M. T. Chakravarty |
---|---|
License | BSD-style |
Maintainer | benedikt.huber@gmail.com |
Stability | alpha |
Portability | ghc |
Safe Haskell | None |
Language | Haskell98 |
This module manages symbols in local and global scopes.
There are four different kind of identifiers: ordinary identifiers (henceforth
simply called identifier
), tag names (names of struct/union/enum types),
labels and structure members.
- type IdentEntry = Either TypeDef IdentDecl
- identOfTyDecl :: IdentEntry -> Ident
- type TagEntry = Either TagFwdDecl TagDef
- data TagFwdDecl
- data DefTable = DefTable {}
- emptyDefTable :: DefTable
- globalDefs :: DefTable -> GlobalDecls
- inFileScope :: DefTable -> Bool
- enterFunctionScope :: DefTable -> DefTable
- leaveFunctionScope :: DefTable -> DefTable
- enterBlockScope :: DefTable -> DefTable
- leaveBlockScope :: DefTable -> DefTable
- enterMemberDecl :: DefTable -> DefTable
- leaveMemberDecl :: DefTable -> ([MemberDecl], DefTable)
- data DeclarationStatus t
- = NewDecl
- | Redeclared t
- | KeepDef t
- | Shadowed t
- | KindMismatch t
- declStatusDescr :: DeclarationStatus t -> String
- defineTypeDef :: Ident -> TypeDef -> DefTable -> (DeclarationStatus IdentEntry, DefTable)
- defineGlobalIdent :: Ident -> IdentDecl -> DefTable -> (DeclarationStatus IdentEntry, DefTable)
- defineScopedIdent :: Ident -> IdentDecl -> DefTable -> (DeclarationStatus IdentEntry, DefTable)
- defineScopedIdentWhen :: (IdentDecl -> Bool) -> Ident -> IdentDecl -> DefTable -> (DeclarationStatus IdentEntry, DefTable)
- declareTag :: SUERef -> TagFwdDecl -> DefTable -> (DeclarationStatus TagEntry, DefTable)
- defineTag :: SUERef -> TagDef -> DefTable -> (DeclarationStatus TagEntry, DefTable)
- defineLabel :: Ident -> DefTable -> (DeclarationStatus Ident, DefTable)
- lookupIdent :: Ident -> DefTable -> Maybe IdentEntry
- lookupTag :: SUERef -> DefTable -> Maybe TagEntry
- lookupLabel :: Ident -> DefTable -> Maybe Ident
- lookupIdentInner :: Ident -> DefTable -> Maybe IdentEntry
- lookupTagInner :: SUERef -> DefTable -> Maybe TagEntry
- insertType :: DefTable -> Name -> Type -> DefTable
- lookupType :: DefTable -> Name -> Maybe Type
- mergeDefTable :: DefTable -> DefTable -> DefTable
Documentation
type IdentEntry = Either TypeDef IdentDecl Source
All ordinary identifiers map to IdenTyDecl
: either a typedef or a object/function/enumerator
identOfTyDecl :: IdentEntry -> Ident Source
type TagEntry = Either TagFwdDecl TagDef Source
Tag names map to forward declarations or definitions of struct/union/enum types
data TagFwdDecl Source
Table holding current definitions
DefTable | |
|
emptyDefTable :: DefTable Source
empty definition table, with all name space maps in global scope
globalDefs :: DefTable -> GlobalDecls Source
get the globally defined entries of a definition table
inFileScope :: DefTable -> Bool Source
enterFunctionScope :: DefTable -> DefTable Source
Enter function scope (AND the corresponding block scope)
leaveFunctionScope :: DefTable -> DefTable Source
Leave function scope, and return the associated DefTable. Error if not in function scope.
enterBlockScope :: DefTable -> DefTable Source
Enter new block scope
leaveBlockScope :: DefTable -> DefTable Source
Leave innermost block scope
enterMemberDecl :: DefTable -> DefTable Source
Enter new member declaration scope
leaveMemberDecl :: DefTable -> ([MemberDecl], DefTable) Source
Leave innermost member declaration scope
data DeclarationStatus t Source
Status of a declaration
NewDecl | new entry |
Redeclared t | old def was overwritten |
KeepDef t | new def was discarded |
Shadowed t | new def shadows one in outer scope |
KindMismatch t | kind mismatch |
Data t => Data (DeclarationStatus t) | |
Typeable (* -> *) DeclarationStatus |
declStatusDescr :: DeclarationStatus t -> String Source
defineTypeDef :: Ident -> TypeDef -> DefTable -> (DeclarationStatus IdentEntry, DefTable) Source
defineGlobalIdent :: Ident -> IdentDecl -> DefTable -> (DeclarationStatus IdentEntry, DefTable) Source
declare/define a global object/function/typeDef
returns Redeclared def
if there is already an object/function/typeDef
in global scope, or DifferentKindRedec def
if the old declaration is of a different kind.
defineScopedIdent :: Ident -> IdentDecl -> DefTable -> (DeclarationStatus IdentEntry, DefTable) Source
declare/define a object/function/typeDef with lexical scope
returns Redeclared def
or DifferentKindRedec def
if there is already an object/function/typeDef
in the same scope.
defineScopedIdentWhen :: (IdentDecl -> Bool) -> Ident -> IdentDecl -> DefTable -> (DeclarationStatus IdentEntry, DefTable) Source
declare/define a object/function/typeDef with lexical scope, if the given predicate holds on the old entry.
returns Keep old_def
if the old definition shouldn't be overwritten, and otherwise Redeclared def
or
DifferentKindRedecl def
if there is already an object/function/typeDef in the same scope.
declareTag :: SUERef -> TagFwdDecl -> DefTable -> (DeclarationStatus TagEntry, DefTable) Source
declare a tag (fwd decl in case the struct name isn't defined yet)
defineTag :: SUERef -> TagDef -> DefTable -> (DeclarationStatus TagEntry, DefTable) Source
define a tag
defineLabel :: Ident -> DefTable -> (DeclarationStatus Ident, DefTable) Source
define a label Return the old label if it is already defined in this function's scope
lookupIdent :: Ident -> DefTable -> Maybe IdentEntry Source
lookup identifier (object, function, typeDef, enumerator)
lookupIdentInner :: Ident -> DefTable -> Maybe IdentEntry Source
lookup an object in the innermost scope
lookupTagInner :: SUERef -> DefTable -> Maybe TagEntry Source
lookup an identifier in the innermost scope
mergeDefTable :: DefTable -> DefTable -> DefTable Source
Merge two DefTables. If both tables contain an entry for a given key, they must agree on its value.