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

Copyright(c) 2008 Benedikt Huber
LicenseBSD-style
Maintainerbenedikt.huber@gmail.com
Stabilityalpha
Portabilityghc
Safe HaskellNone
LanguageHaskell98

Language.C.Analysis.SemRep

Contents

Description

This module contains definitions for representing C translation units. In contrast to AST, the representation tries to express the semantics of of a translation unit.

Synopsis

Sums of tags and identifiers

data TagDef #

Composite type definitions (tags)

Instances

Data TagDef # 

Methods

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

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

toConstr :: TagDef -> Constr #

dataTypeOf :: TagDef -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos TagDef # 

Methods

posOf :: TagDef -> Position #

CNode TagDef # 

Methods

nodeInfo :: TagDef -> NodeInfo #

HasSUERef TagDef # 

Methods

sueRef :: TagDef -> SUERef #

typeOfTagDef :: TagDef -> TypeName #

return the type corresponding to a tag definition

class Declaration n where #

All datatypes aggregating a declaration are instances of Declaration

Minimal complete definition

getVarDecl

Methods

getVarDecl :: n -> VarDecl #

get the name, type and declaration attributes of a declaration or definition

declIdent :: Declaration n => n -> Ident #

get the variable identifier of a declaration (only safe if the the declaration is known to have a name)

declName :: Declaration n => n -> VarName #

get the variable name of a Declaration

declType :: Declaration n => n -> Type #

get the type of a Declaration

declAttrs :: Declaration n => n -> DeclAttrs #

get the declaration attributes of a Declaration

data IdentDecl #

identifiers, typedefs and enumeration constants (namespace sum)

Constructors

Declaration Decl

object or function declaration

ObjectDef ObjDef

object definition

FunctionDef FunDef

function definition

EnumeratorDef Enumerator

definition of an enumerator

Instances

Data IdentDecl # 

Methods

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

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

toConstr :: IdentDecl -> Constr #

dataTypeOf :: IdentDecl -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos IdentDecl # 

Methods

posOf :: IdentDecl -> Position #

CNode IdentDecl # 
Declaration IdentDecl # 

objKindDescr :: IdentDecl -> String #

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

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 #

global declaration/definition table returned by the analysis

emptyGlobalDecls :: GlobalDecls #

empty global declaration table

filterGlobalDecls :: (DeclEvent -> Bool) -> GlobalDecls -> GlobalDecls #

filter global declarations

mergeGlobalDecls :: GlobalDecls -> GlobalDecls -> GlobalDecls #

merge global declarations

Events for visitors

data DeclEvent #

Declaration events

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

Constructors

TagEvent TagDef

file-scope struct/union/enum event

DeclEvent IdentDecl

file-scope declaration or definition

ParamEvent ParamDecl

parameter declaration

LocalEvent IdentDecl

local variable declaration or definition

TypeDefEvent TypeDef

a type definition

AsmEvent AsmBlock

assembler block

Declarations and definitions

data Decl #

Declarations, which aren't definitions

Constructors

Decl VarDecl NodeInfo 

Instances

Data Decl # 

Methods

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

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

toConstr :: Decl -> Constr #

dataTypeOf :: Decl -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos Decl # 

Methods

posOf :: Decl -> Position #

CNode Decl # 

Methods

nodeInfo :: Decl -> NodeInfo #

Declaration Decl # 

Methods

getVarDecl :: Decl -> VarDecl #

data ObjDef #

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.

Instances

Data ObjDef # 

Methods

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

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

toConstr :: ObjDef -> Constr #

dataTypeOf :: ObjDef -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos ObjDef # 

Methods

posOf :: ObjDef -> Position #

CNode ObjDef # 

Methods

nodeInfo :: ObjDef -> NodeInfo #

Declaration ObjDef # 

Methods

getVarDecl :: ObjDef -> VarDecl #

isTentative :: ObjDef -> Bool #

Returns True if the given object definition is tentative.

data FunDef #

Function definitions

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

Constructors

FunDef VarDecl Stmt NodeInfo 

Instances

Data FunDef # 

Methods

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

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

toConstr :: FunDef -> Constr #

dataTypeOf :: FunDef -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos FunDef # 

Methods

posOf :: FunDef -> Position #

CNode FunDef # 

Methods

nodeInfo :: FunDef -> NodeInfo #

Declaration FunDef # 

Methods

getVarDecl :: FunDef -> VarDecl #

data ParamDecl #

Parameter declaration

Instances

Data ParamDecl # 

Methods

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

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

toConstr :: ParamDecl -> Constr #

dataTypeOf :: ParamDecl -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos ParamDecl # 

Methods

posOf :: ParamDecl -> Position #

CNode ParamDecl # 
Declaration ParamDecl # 

data MemberDecl #

Struct/Union member declaration

Constructors

MemberDecl VarDecl (Maybe Expr) NodeInfo
MemberDecl vardecl bitfieldsize node
AnonBitField Type Expr NodeInfo
AnonBitField typ size

Instances

Data MemberDecl # 

Methods

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

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

toConstr :: MemberDecl -> Constr #

dataTypeOf :: MemberDecl -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos MemberDecl # 

Methods

posOf :: MemberDecl -> Position #

CNode MemberDecl # 
Declaration MemberDecl # 

data TypeDef #

typedef definitions.

The identifier is a new name for the given type.

Instances

Data TypeDef # 

Methods

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

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

toConstr :: TypeDef -> Constr #

dataTypeOf :: TypeDef -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos TypeDef # 

Methods

posOf :: TypeDef -> Position #

CNode TypeDef # 

Methods

nodeInfo :: TypeDef -> NodeInfo #

identOfTypeDef :: TypeDef -> Ident #

return the idenitifier of a typedef

data VarDecl #

Generic variable declarations

Instances

Data VarDecl # 

Methods

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

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

toConstr :: VarDecl -> Constr #

dataTypeOf :: VarDecl -> DataType #

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

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

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

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

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

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

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

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

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

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

Declaration VarDecl # 

Declaration attributes

data DeclAttrs #

Declaration attributes of the form DeclAttrs isInlineFunction storage linkage attrs

They specify the storage and linkage of a declared object.

Constructors

DeclAttrs FunctionAttrs Storage Attributes
DeclAttrs fspecs storage attrs

Instances

Data DeclAttrs # 

Methods

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

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

toConstr :: DeclAttrs -> Constr #

dataTypeOf :: DeclAttrs -> DataType #

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

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

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

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

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

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

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

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

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

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

data FunctionAttrs #

Constructors

FunctionAttrs 

Fields

Instances

Eq FunctionAttrs # 
Data FunctionAttrs # 

Methods

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

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

toConstr :: FunctionAttrs -> Constr #

dataTypeOf :: FunctionAttrs -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FunctionAttrs # 

functionAttrs :: Declaration d => d -> FunctionAttrs #

get the `function attributes' of a declaration

data Storage #

Storage duration and linkage of a variable

Constructors

NoStorage

no storage

Auto Register

automatic storage (optional: register)

Static Linkage ThreadLocal

static storage, linkage spec and thread local specifier (gnu c)

FunLinkage Linkage

function, either internal or external linkage

Instances

Eq Storage # 

Methods

(==) :: Storage -> Storage -> Bool #

(/=) :: Storage -> Storage -> Bool #

Data Storage # 

Methods

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

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

toConstr :: Storage -> Constr #

dataTypeOf :: Storage -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Storage # 
Show Storage # 

declStorage :: Declaration d => d -> Storage #

get the Storage of a declaration

type Register = Bool #

data Linkage #

Linkage: Either no linkage, internal to the translation unit or external

Instances

Eq Linkage # 

Methods

(==) :: Linkage -> Linkage -> Bool #

(/=) :: Linkage -> Linkage -> Bool #

Data Linkage # 

Methods

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

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

toConstr :: Linkage -> Constr #

dataTypeOf :: Linkage -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Linkage # 
Show Linkage # 

hasLinkage :: Storage -> Bool #

return True if the object has linkage

declLinkage :: Declaration d => d -> Linkage #

Get the linkage of a definition

Types

data Type #

types of C objects

Instances

Data Type # 

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

data FunType #

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

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

Instances

Data FunType # 

Methods

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

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

toConstr :: FunType -> Constr #

dataTypeOf :: FunType -> DataType #

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

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

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

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

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

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

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

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

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

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

data ArraySize #

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

Instances

Data ArraySize # 

Methods

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

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

toConstr :: ArraySize -> Constr #

dataTypeOf :: ArraySize -> DataType #

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

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

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

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

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

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

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

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

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

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

data TypeDefRef #

typdef references If the actual type is known, it is attached for convenience

Instances

Data TypeDefRef # 

Methods

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

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

toConstr :: TypeDefRef -> Constr #

dataTypeOf :: TypeDefRef -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos TypeDefRef # 

Methods

posOf :: TypeDefRef -> Position #

CNode TypeDefRef # 

data TypeName #

normalized type representation

Instances

Data TypeName # 

Methods

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

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

toConstr :: TypeName -> Constr #

dataTypeOf :: TypeName -> DataType #

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

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

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

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

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

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

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

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

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

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

data BuiltinType #

Builtin type (va_list, anything)

Constructors

TyVaList 
TyAny 

Instances

Data BuiltinType # 

Methods

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

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

toConstr :: BuiltinType -> Constr #

dataTypeOf :: BuiltinType -> DataType #

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

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

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

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

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

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

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

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

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

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

data IntType #

integral types (C99 6.7.2.2)

Instances

Eq IntType # 

Methods

(==) :: IntType -> IntType -> Bool #

(/=) :: IntType -> IntType -> Bool #

Data IntType # 

Methods

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

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

toConstr :: IntType -> Constr #

dataTypeOf :: IntType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord IntType # 
Show IntType # 

data FloatType #

floating point type (C99 6.7.2.2)

Constructors

TyFloat 
TyDouble 
TyLDouble 

Instances

Eq FloatType # 
Data FloatType # 

Methods

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

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

toConstr :: FloatType -> Constr #

dataTypeOf :: FloatType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FloatType # 
Show FloatType # 

class HasSUERef a where #

accessor class : struct/union/enum names

Minimal complete definition

sueRef

Methods

sueRef :: a -> SUERef #

class HasCompTyKind a where #

accessor class : composite type tags (struct or union)

Minimal complete definition

compTag

Methods

compTag :: a -> CompTyKind #

data CompTypeRef #

composite type declarations

Instances

Data CompTypeRef # 

Methods

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

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

toConstr :: CompTypeRef -> Constr #

dataTypeOf :: CompTypeRef -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos CompTypeRef # 
CNode CompTypeRef # 
HasCompTyKind CompTypeRef # 
HasSUERef CompTypeRef # 

Methods

sueRef :: CompTypeRef -> SUERef #

data CompType #

Composite type (struct or union).

Instances

Data CompType # 

Methods

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

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

toConstr :: CompType -> Constr #

dataTypeOf :: CompType -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos CompType # 

Methods

posOf :: CompType -> Position #

CNode CompType # 
HasCompTyKind CompType # 
HasSUERef CompType # 

Methods

sueRef :: CompType -> SUERef #

typeOfCompDef :: CompType -> TypeName #

return the type of a composite type definition

data CompTyKind #

a tag to determine wheter we refer to a struct or union, see CompType.

Constructors

StructTag 
UnionTag 

Instances

Eq CompTyKind # 
Data CompTyKind # 

Methods

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

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

toConstr :: CompTyKind -> Constr #

dataTypeOf :: CompTyKind -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CompTyKind # 
Show CompTyKind # 

data EnumTypeRef #

Instances

Data EnumTypeRef # 

Methods

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

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

toConstr :: EnumTypeRef -> Constr #

dataTypeOf :: EnumTypeRef -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos EnumTypeRef # 
CNode EnumTypeRef # 
HasSUERef EnumTypeRef # 

Methods

sueRef :: EnumTypeRef -> SUERef #

data EnumType #

Representation of C enumeration types

Constructors

EnumType SUERef [Enumerator] Attributes NodeInfo
EnumType name enumeration-constants attrs node

Instances

Data EnumType # 

Methods

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

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

toConstr :: EnumType -> Constr #

dataTypeOf :: EnumType -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos EnumType # 

Methods

posOf :: EnumType -> Position #

CNode EnumType # 
HasSUERef EnumType # 

Methods

sueRef :: EnumType -> SUERef #

typeOfEnumDef :: EnumType -> TypeName #

return the type of an enum definition

data Enumerator #

An Enumerator consists of an identifier, a constant expressions and the link to its type

Instances

Data Enumerator # 

Methods

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

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

toConstr :: Enumerator -> Constr #

dataTypeOf :: Enumerator -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos Enumerator # 

Methods

posOf :: Enumerator -> Position #

CNode Enumerator # 
Declaration Enumerator # 

data TypeQuals #

Type qualifiers: constant, volatile and restrict

Constructors

TypeQuals 

Instances

Eq TypeQuals # 
Data TypeQuals # 

Methods

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

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

toConstr :: TypeQuals -> Constr #

dataTypeOf :: TypeQuals -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TypeQuals # 

noTypeQuals :: TypeQuals #

no type qualifiers

mergeTypeQuals :: TypeQuals -> TypeQuals -> TypeQuals #

merge (&&) two type qualifier sets

Variable names

data VarName #

VarName name assembler-name is a name of an declared object

Constructors

VarName Ident (Maybe AsmName) 
NoName 

Instances

Data VarName # 

Methods

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

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

toConstr :: VarName -> Constr #

dataTypeOf :: VarName -> DataType #

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

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

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

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

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

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

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

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

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

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

type AsmName = CStrLit #

Assembler name (alias for CStrLit)

Attributes (STUB, not yet analyzed)

data Attr #

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 

Instances

Data Attr # 

Methods

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

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

toConstr :: Attr -> Constr #

dataTypeOf :: Attr -> DataType #

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

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

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

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

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

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

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

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

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

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

Pos Attr # 

Methods

posOf :: Attr -> Position #

CNode Attr # 

Methods

nodeInfo :: Attr -> NodeInfo #

type Attributes = [Attr] #

noAttributes :: Attributes #

Empty attribute list

mergeAttributes :: Attributes -> Attributes -> Attributes #

Merge attribute lists TODO: currently does not remove duplicates

Statements and Expressions (STUB, aliases to Syntax)

type Stmt = CStat #

Stmt is an alias for CStat (Syntax)

type Expr = CExpr #

Expr is currently an alias for CExpr (Syntax)

type Initializer = CInit #

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 = CStrLit #

Top level assembler block (alias for CStrLit)