language-c-0.4.7: Analysis and generation of C code

Copyright(c) 2008 Benedikt Huber based on code from c2hs (c) [1999..2001] Manuel M. T. Chakravarty
LicenseBSD-style
Maintainerbenedikt.huber@gmail.com
Stabilityalpha
Portabilityghc
Safe HaskellNone
LanguageHaskell98

Language.C.Analysis.DefTable

Description

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.

Synopsis

Documentation

type IdentEntry = Either TypeDef IdentDecl Source

All ordinary identifiers map to IdenTyDecl: either a typedef or a object/function/enumerator

type TagEntry = Either TagFwdDecl TagDef Source

Tag names map to forward declarations or definitions of struct/union/enum types

data DefTable Source

Table holding current definitions

Constructors

DefTable 

Fields

identDecls :: NameSpaceMap Ident IdentEntry

declared `ordinary identifiers'

tagDecls :: NameSpaceMap SUERef TagEntry

declared structunionenum tags

labelDefs :: NameSpaceMap Ident Ident

defined labels

memberDecls :: NameSpaceMap Ident MemberDecl

member declarations (only local)

refTable :: IntMap Name

link names with definitions

typeTable :: IntMap Type
 

Instances

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

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

Constructors

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

Instances

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)

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

insertType :: DefTable -> Name -> Type -> DefTable Source

Record the type of a node.

lookupType :: DefTable -> Name -> Maybe Type Source

Lookup the type of a node.

mergeDefTable :: DefTable -> DefTable -> DefTable Source

Merge two DefTables. If both tables contain an entry for a given key, they must agree on its value.