language-c-0.3.1.1: Analysis and generation of C codeSource codeContentsIndex
Language.C.Analysis.SemRep
Portabilityghc
Stabilityalpha
Maintainerbenedikt.huber@gmail.com
Contents
Sums of tags and identifiers
Global definitions
Events for visitors
Declarations and definitions
Declaration attributes
Types
Variable names
Attributes (STUB, not yet analyzed)
Statements and Expressions (STUB, aliases to Syntax)
Description
This module contains definitions for representing C translation units. In contrast to Language.C.Syntax.AST, the representation tries to express the semantics of of a translation unit.
Synopsis
data TagDef
= CompDef CompType
| EnumDef EnumType
typeOfTagDef :: TagDef -> TypeName
class Declaration n where
getVarDecl :: n -> VarDecl
declIdent :: Declaration n => n -> Ident
declName :: Declaration n => n -> VarName
declType :: Declaration n => n -> Type
declAttrs :: Declaration n => n -> DeclAttrs
data IdentDecl
= Declaration Decl
| ObjectDef ObjDef
| FunctionDef FunDef
| EnumeratorDef Enumerator
objKindDescr :: IdentDecl -> String
splitIdentDecls :: Bool -> Map Ident IdentDecl -> (Map Ident Decl, (Map Ident Enumerator, Map Ident ObjDef, Map Ident FunDef))
data GlobalDecls = GlobalDecls {
gObjs :: Map Ident IdentDecl
gTags :: Map SUERef TagDef
gTypeDefs :: Map Ident TypeDef
}
emptyGlobalDecls :: GlobalDecls
filterGlobalDecls :: (DeclEvent -> Bool) -> GlobalDecls -> GlobalDecls
mergeGlobalDecls :: GlobalDecls -> GlobalDecls -> GlobalDecls
data DeclEvent
= TagEvent TagDef
| DeclEvent IdentDecl
| TypeDefEvent TypeDef
| AsmEvent AsmBlock
data Decl = Decl VarDecl NodeInfo
data ObjDef = ObjDef VarDecl (Maybe Initializer) NodeInfo
isTentative :: ObjDef -> Bool
data FunDef = FunDef VarDecl Stmt NodeInfo
data ParamDecl
= ParamDecl VarDecl NodeInfo
| AbstractParamDecl VarDecl NodeInfo
data MemberDecl
= MemberDecl VarDecl (Maybe Expr) NodeInfo
| AnonBitField Type Expr NodeInfo
data TypeDef = TypeDef Ident Type Attributes NodeInfo
identOfTypeDef :: TypeDef -> Ident
data VarDecl = VarDecl VarName DeclAttrs Type
data DeclAttrs = DeclAttrs Bool Storage Attributes
isExtDecl :: Declaration n => n -> Bool
data Storage
= NoStorage
| Auto Register
| Static Linkage ThreadLocal
| FunLinkage Linkage
declStorage :: Declaration d => d -> Storage
type ThreadLocal = Bool
type Register = Bool
data Linkage
= InternalLinkage
| ExternalLinkage
data Type
= DirectType TypeName TypeQuals
| PtrType Type TypeQuals Attributes
| ArrayType Type ArraySize TypeQuals Attributes
| FunctionType FunType
| TypeDefType TypeDefRef
| TypeOfExpr Expr
data FunType
= FunType Type [ParamDecl] Bool Attributes
| FunTypeIncomplete Type Attributes
isFunctionType :: Type -> Bool
derefTypeDef :: Type -> Type
referencedType :: Type -> Maybe Type
hasTypeOfExpr :: Type -> Bool
data ArraySize
= UnknownArraySize Bool
| ArraySize Bool Expr
data TypeDefRef = TypeDefRef Ident (Maybe Type) NodeInfo
data TypeName
= TyVoid
| TyIntegral IntType
| TyFloating FloatType
| TyComplex FloatType
| TyComp CompTypeRef
| TyEnum EnumTypeRef
| TyBuiltin BuiltinType
data BuiltinType = TyVaList
data IntType
= TyBool
| TyChar
| TySChar
| TyUChar
| TyShort
| TyUShort
| TyInt
| TyUInt
| TyLong
| TyULong
| TyLLong
| TyULLong
data FloatType
= TyFloat
| TyDouble
| TyLDouble
class HasSUERef a where
sueRef :: a -> SUERef
class HasCompTyKind a where
compTag :: a -> CompTyKind
data CompTypeRef = CompTypeRef SUERef CompTyKind NodeInfo
data CompType = CompType SUERef CompTyKind [MemberDecl] Attributes NodeInfo
typeOfCompDef :: CompType -> TypeName
data CompTyKind
= StructTag
| UnionTag
data EnumTypeRef = EnumTypeRef SUERef NodeInfo
data EnumType = EnumType SUERef [Enumerator] Attributes NodeInfo
typeOfEnumDef :: EnumType -> TypeName
data Enumerator = Enumerator Ident Expr EnumType NodeInfo
data TypeQuals = TypeQuals {
constant :: Bool
volatile :: Bool
restrict :: Bool
}
noTypeQuals :: TypeQuals
mergeTypeQuals :: TypeQuals -> TypeQuals -> TypeQuals
data VarName
= VarName Ident (Maybe AsmName)
| NoName
identOfVarName :: VarName -> Ident
type AsmName = CStrLit
data Attr = Attr Ident [Expr] NodeInfo
type Attributes = [Attr]
type Stmt = CStat
type Expr = CExpr
type Initializer = CInit
type AsmBlock = CStrLit
Sums of tags and identifiers
data TagDef Source
Composite type definitions (tags)
Constructors
CompDef CompType
EnumDef EnumType
typeOfTagDef :: TagDef -> TypeNameSource
return the type corresponding to a tag definition
class Declaration n whereSource
All datatypes aggregating a declaration are instances of Declaration
Methods
getVarDecl :: n -> VarDeclSource
get the name, type and declaration attributes of a declaration or definition
declIdent :: Declaration n => n -> IdentSource
get the variable identifier of a declaration (only safe if the the declaration is known to have a name)
declName :: Declaration n => n -> VarNameSource
get the variable name of a Declaration
declType :: Declaration n => n -> TypeSource
get the type of a Declaration
declAttrs :: Declaration n => n -> DeclAttrsSource
get the declaration attributes of a Declaration
data IdentDecl Source
identifiers, typedefs and enumeration constants (namespace sum)
Constructors
Declaration Declobject or function declaration
ObjectDef ObjDefobject definition
FunctionDef FunDeffunction definition
EnumeratorDef Enumeratordefinition of an enumerator
objKindDescr :: IdentDecl -> StringSource
textual description of the kind of an object
splitIdentDecls :: Bool -> Map Ident IdentDecl -> (Map Ident Decl, (Map Ident Enumerator, Map Ident ObjDef, Map Ident FunDef))Source
splitIdentDecls includeAllDecls splits a map of object, function and enumerator declarations and definitions into one map holding declarations, and three maps for object definitions, enumerator definitions and function definitions. If includeAllDecls is True all declarations are present in the first map, otherwise only those where no corresponding definition is available.
Global definitions
data GlobalDecls Source
global declaration/definition table returned by the analysis
Constructors
GlobalDecls
gObjs :: Map Ident IdentDecl
gTags :: Map SUERef TagDef
gTypeDefs :: Map Ident TypeDef
emptyGlobalDecls :: GlobalDeclsSource
empty global declaration table
filterGlobalDecls :: (DeclEvent -> Bool) -> GlobalDecls -> GlobalDeclsSource
filter global declarations
mergeGlobalDecls :: GlobalDecls -> GlobalDecls -> GlobalDeclsSource
merge global declarations
Events for visitors
data DeclEvent Source

Declaration events

Those events are reported to callbacks, which are executed during the traversal.

Constructors
TagEvent TagDeffile-scope struct/union/enum event
DeclEvent IdentDeclfile-scope declaration or definition
TypeDefEvent TypeDefa type definition
AsmEvent AsmBlockassembler block
Declarations and definitions
data Decl Source
Declarations, which aren't definitions
Constructors
Decl VarDecl NodeInfo
data ObjDef Source

Object Definitions

An object definition is a declaration together with an initializer.

If the initializer is missing, it is a tentative definition, i.e. a definition which might be overriden later on.

Constructors
ObjDef VarDecl (Maybe Initializer) NodeInfo
isTentative :: ObjDef -> BoolSource
Returns True if the given object definition is tentative.
data FunDef Source

Function definitions

A function definition is a declaration together with a statement (the function body).

Constructors
FunDef VarDecl Stmt NodeInfo
data ParamDecl Source
Parameter declaration
Constructors
ParamDecl VarDecl NodeInfo
AbstractParamDecl VarDecl NodeInfo
data MemberDecl Source
Struct/Union member declaration
Constructors
MemberDecl VarDecl (Maybe Expr) NodeInfo
MemberDecl vardecl bitfieldsize node
AnonBitField Type Expr NodeInfo
AnonBitField typ size
data TypeDef Source

typedef definitions.

The identifier is a new name for the given type.

Constructors
TypeDef Ident Type Attributes NodeInfo
identOfTypeDef :: TypeDef -> IdentSource
return the idenitifier of a typedef
data VarDecl Source
Generic variable declarations
Constructors
VarDecl VarName DeclAttrs Type
Declaration attributes
data DeclAttrs Source

Declaration attributes of the form DeclAttrs isInlineFunction storage linkage attrs

They specify the storage and linkage of a declared object.

Constructors
DeclAttrs Bool Storage Attributes
DeclAttrs inline storage attrs
isExtDecl :: Declaration n => n -> BoolSource
data Storage Source
Storage duration and linkage of a variable
Constructors
NoStorageno storage
Auto Registerautomatic storage (optional: register)
Static Linkage ThreadLocalstatic storage, with linkage and thread local specifier (gnu c)
FunLinkage Linkagefunction, either internal or external linkage
declStorage :: Declaration d => d -> StorageSource
get the Storage of a declaration
type ThreadLocal = BoolSource
type Register = BoolSource
data Linkage Source
Linkage: Either internal to the translation unit or external
Constructors
InternalLinkage
ExternalLinkage
Types
data Type Source
types of C objects
Constructors
DirectType TypeName TypeQualsa non-derived type
PtrType Type TypeQuals Attributespointer type
ArrayType Type ArraySize TypeQuals Attributesarray type
FunctionType FunTypefunction type
TypeDefType TypeDefRefa defined type
TypeOfExpr Expr(GNU) typeof (broken and should be removed, but we do not yet have expression type analysis)
data FunType Source

Function types are of the form FunType return-type params isVariadic attrs.

If the parameter types aren't yet known, the function has type FunTypeIncomplete type attrs.

Constructors
FunType Type [ParamDecl] Bool Attributes
FunTypeIncomplete Type Attributes
isFunctionType :: Type -> BoolSource

return True if the given type is a function type

Result is undefined in the presence of TypeOfExpr or undefined typeDefs

derefTypeDef :: Type -> TypeSource
resolve typedefs, if possible
referencedType :: Type -> Maybe TypeSource
hasTypeOfExpr :: Type -> BoolSource
data ArraySize Source
An array type may either have unknown size or a specified array size, the latter either variable or constant. Furthermore, when used as a function parameters, the size may be qualified as static. In a function prototype, the size may be `Unspecified variable size' ([*]).
Constructors
UnknownArraySize Bool
UnknownArraySize is-starred
ArraySize Bool Expr
FixedSizeArray is-static size-expr
data TypeDefRef Source
typdef references If the actual type is known, it is attached for convenience
Constructors
TypeDefRef Ident (Maybe Type) NodeInfo
data TypeName Source
normalized type representation
Constructors
TyVoid
TyIntegral IntType
TyFloating FloatType
TyComplex FloatType
TyComp CompTypeRef
TyEnum EnumTypeRef
TyBuiltin BuiltinType
data BuiltinType Source
Builtin type (va_list)
Constructors
TyVaList
data IntType Source
integral types (C99 6.7.2.2)
Constructors
TyBool
TyChar
TySChar
TyUChar
TyShort
TyUShort
TyInt
TyUInt
TyLong
TyULong
TyLLong
TyULLong
data FloatType Source
floating point type (C99 6.7.2.2)
Constructors
TyFloat
TyDouble
TyLDouble
class HasSUERef a whereSource
accessor class : struct/union/enum names
Methods
sueRef :: a -> SUERefSource
class HasCompTyKind a whereSource
accessor class : composite type tags (struct or union)
Methods
compTag :: a -> CompTyKindSource
data CompTypeRef Source
composite type declarations
Constructors
CompTypeRef SUERef CompTyKind NodeInfo
data CompType Source
Composite type (struct or union).
Constructors
CompType SUERef CompTyKind [MemberDecl] Attributes NodeInfo
typeOfCompDef :: CompType -> TypeNameSource
return the type of a composite type definition
data CompTyKind Source
a tag to determine wheter we refer to a struct or union, see CompType.
Constructors
StructTag
UnionTag
data EnumTypeRef Source
Constructors
EnumTypeRef SUERef NodeInfo
data EnumType Source
Representation of C enumeration types
Constructors
EnumType SUERef [Enumerator] Attributes NodeInfo
EnumType name enumeration-constants attrs node
typeOfEnumDef :: EnumType -> TypeNameSource
return the type of an enum definition
data Enumerator Source
An Enumerator consists of an identifier, a constant expressions and the link to its type
Constructors
Enumerator Ident Expr EnumType NodeInfo
data TypeQuals Source
Type qualifiers: constant, volatile and restrict
Constructors
TypeQuals
constant :: Bool
volatile :: Bool
restrict :: Bool
noTypeQuals :: TypeQualsSource
no type qualifiers
mergeTypeQuals :: TypeQuals -> TypeQuals -> TypeQualsSource
merge (&&) two type qualifier sets
Variable names
data VarName Source
VarName name assembler-name is a name of an declared object
Constructors
VarName Ident (Maybe AsmName)
NoName
identOfVarName :: VarName -> IdentSource
type AsmName = CStrLitSource
Assembler name (alias for CStrLit)
Attributes (STUB, not yet analyzed)
data Attr Source

__attribute__ annotations

Those are of the form Attr attribute-name attribute-parameters, and serve as generic properties of some syntax tree elements.

Some examples:

  • labels can be attributed with unused to indicate that their not used
  • struct definitions can be attributed with packed to tell the compiler to use the most compact representation
  • declarations can be attributed with deprecated
  • function declarations can be attributes with noreturn to tell the compiler that the function will never return,
  • or with const to indicate that it is a pure function

TODO: ultimatively, we want to parse attributes and represent them in a typed way

Constructors
Attr Ident [Expr] NodeInfo
type Attributes = [Attr]Source
Statements and Expressions (STUB, aliases to Syntax)
type Stmt = CStatSource
Stmt is an alias for CStat (Syntax)
type Expr = CExprSource
Expr is currently an alias for CExpr (Syntax)
type Initializer = CInitSource

Initializer is currently an alias for CInit.

We're planning a normalized representation, but this depends on the implementation of constant expression evaluation

type AsmBlock = CStrLitSource
Top level assembler block (alias for CStrLit)
Produced by Haddock version 2.6.0