language-c-0.8.2: 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 #

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

type TagEntry = Either TagFwdDecl TagDef #

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

data TagFwdDecl #

Instances
CNode TagFwdDecl # 
Instance details

Defined in Language.C.Analysis.DefTable

Pretty TagFwdDecl # 
Instance details

Defined in Language.C.Analysis.Debug

HasSUERef TagFwdDecl # 
Instance details

Defined in Language.C.Analysis.DefTable

Methods

sueRef :: TagFwdDecl -> SUERef #

data DefTable #

Table holding current definitions

Constructors

DefTable 

Fields

Instances
Pretty DefTable # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: DefTable -> Doc #

prettyPrec :: Int -> DefTable -> Doc #

emptyDefTable :: DefTable #

empty definition table, with all name space maps in global scope

globalDefs :: DefTable -> GlobalDecls #

get the globally defined entries of a definition table

enterFunctionScope :: DefTable -> DefTable #

Enter function scope (AND the corresponding block scope)

leaveFunctionScope :: DefTable -> DefTable #

Leave function scope, and return the associated DefTable. Error if not in function scope.

enterBlockScope :: DefTable -> DefTable #

Enter new block scope

leaveBlockScope :: DefTable -> DefTable #

Leave innermost block scope

enterMemberDecl :: DefTable -> DefTable #

Enter new member declaration scope

leaveMemberDecl :: DefTable -> ([MemberDecl], DefTable) #

Leave innermost member declaration scope

data DeclarationStatus t #

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
Data t => Data (DeclarationStatus t) # 
Instance details

Defined in Language.C.Analysis.DefTable

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeclarationStatus t -> c (DeclarationStatus t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (DeclarationStatus t) #

toConstr :: DeclarationStatus t -> Constr #

dataTypeOf :: DeclarationStatus t -> DataType #

dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (DeclarationStatus t)) #

dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (DeclarationStatus t)) #

gmapT :: (forall b. Data b => b -> b) -> DeclarationStatus t -> DeclarationStatus t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeclarationStatus t -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeclarationStatus t -> r #

gmapQ :: (forall d. Data d => d -> u) -> DeclarationStatus t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DeclarationStatus t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeclarationStatus t -> m (DeclarationStatus t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeclarationStatus t -> m (DeclarationStatus t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeclarationStatus t -> m (DeclarationStatus t) #

defineGlobalIdent :: Ident -> IdentDecl -> DefTable -> (DeclarationStatus IdentEntry, DefTable) #

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) #

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) #

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) #

declare a tag (fwd decl in case the struct name isn't defined yet)

defineLabel :: Ident -> DefTable -> (DeclarationStatus Ident, DefTable) #

define a label Return the old label if it is already defined in this function's scope

lookupIdent :: Ident -> DefTable -> Maybe IdentEntry #

lookup identifier (object, function, typeDef, enumerator)

lookupLabel :: Ident -> DefTable -> Maybe Ident #

lookup label

lookupIdentInner :: Ident -> DefTable -> Maybe IdentEntry #

lookup an object in the innermost scope

lookupTagInner :: SUERef -> DefTable -> Maybe TagEntry #

lookup an identifier in the innermost scope

insertType :: DefTable -> Name -> Type -> DefTable #

Record the type of a node.

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

Lookup the type of a node.

mergeDefTable :: DefTable -> DefTable -> DefTable #

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