language-c-0.9.3: Analysis and generation of C code
Copyright(c) 2008 Benedikt Huber
LicenseBSD-style
Maintainerbenedikt.huber@gmail.com
Stabilityalpha
Portabilityghc
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.C.Analysis.SemRep

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

Composite type definitions (tags)

Instances

Instances details
Data TagDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show TagDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

HasSUERef TagDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

sueRef :: TagDef -> SUERef Source #

CNode TagDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos TagDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty TagDef Source # 
Instance details

Defined in Language.C.Analysis.Debug

typeOfTagDef :: TagDef -> TypeName Source #

return the type corresponding to a tag definition

class Declaration n where Source #

All datatypes aggregating a declaration are instances of Declaration

Methods

getVarDecl :: n -> VarDecl Source #

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

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

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

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

get the variable name of a Declaration

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

get the type of a Declaration

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

get the declaration attributes of a Declaration

data IdentDecl Source #

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

Instances details
Data IdentDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show IdentDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Declaration IdentDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode IdentDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos IdentDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty IdentDecl Source # 
Instance details

Defined in Language.C.Analysis.Debug

objKindDescr :: IdentDecl -> String Source #

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

Instances

Instances details
Pretty GlobalDecls Source # 
Instance details

Defined in Language.C.Analysis.Debug

emptyGlobalDecls :: GlobalDecls Source #

empty global declaration table

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

filter global declarations

mergeGlobalDecls :: GlobalDecls -> GlobalDecls -> GlobalDecls Source #

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

Instances

Instances details
CNode DeclEvent Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos DeclEvent Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Declarations and definitions

data Decl Source #

Declarations, which aren't definitions

Constructors

Decl VarDecl NodeInfo 

Instances

Instances details
Data Decl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show Decl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> Decl -> ShowS #

show :: Decl -> String #

showList :: [Decl] -> ShowS #

Declaration Decl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode Decl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos Decl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: Decl -> Position Source #

Pretty Decl Source # 
Instance details

Defined in Language.C.Analysis.Debug

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.

Instances

Instances details
Data ObjDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show ObjDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Declaration ObjDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode ObjDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos ObjDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty ObjDef Source # 
Instance details

Defined in Language.C.Analysis.Debug

isTentative :: ObjDef -> Bool Source #

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 

Instances

Instances details
Data FunDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show FunDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Declaration FunDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode FunDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos FunDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty FunDef Source # 
Instance details

Defined in Language.C.Analysis.Debug

data ParamDecl Source #

Parameter declaration

Instances

Instances details
Data ParamDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show ParamDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Declaration ParamDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode ParamDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos ParamDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty ParamDecl Source # 
Instance details

Defined in Language.C.Analysis.Debug

data MemberDecl Source #

Struct/Union member declaration

Constructors

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

Instances

Instances details
Data MemberDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show MemberDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Declaration MemberDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode MemberDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos MemberDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty MemberDecl Source # 
Instance details

Defined in Language.C.Analysis.Debug

data TypeDef Source #

typedef definitions.

The identifier is a new name for the given type.

Instances

Instances details
Data TypeDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show TypeDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode TypeDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos TypeDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty TypeDef Source # 
Instance details

Defined in Language.C.Analysis.Debug

identOfTypeDef :: TypeDef -> Ident Source #

return the idenitifier of a typedef

data VarDecl Source #

Generic variable declarations

Instances

Instances details
Data VarDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show VarDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Declaration VarDecl Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty VarDecl Source # 
Instance details

Defined in Language.C.Analysis.Debug

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 FunctionAttrs Storage Attributes
DeclAttrs fspecs storage attrs

Instances

Instances details
Data DeclAttrs Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show DeclAttrs Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty DeclAttrs Source # 
Instance details

Defined in Language.C.Analysis.Debug

data FunctionAttrs Source #

Constructors

FunctionAttrs 

Fields

Instances

Instances details
Data FunctionAttrs Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show FunctionAttrs Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Eq FunctionAttrs Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Ord FunctionAttrs Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty FunctionAttrs Source # 
Instance details

Defined in Language.C.Analysis.Debug

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

get the `function attributes' of a declaration

data Storage Source #

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

Instances details
Data Storage Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show Storage Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Eq Storage Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

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

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

Ord Storage Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty Storage Source # 
Instance details

Defined in Language.C.Analysis.Debug

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

get the Storage of a declaration

data Linkage Source #

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

Instances

Instances details
Data Linkage Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show Linkage Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Eq Linkage Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

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

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

Ord Linkage Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty Linkage Source # 
Instance details

Defined in Language.C.Analysis.Debug

hasLinkage :: Storage -> Bool Source #

return True if the object has linkage

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

Get the linkage of a definition

Types

data Type Source #

types of C objects

Instances

Instances details
Data Type Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show Type Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Pretty Type Source # 
Instance details

Defined in Language.C.Analysis.Debug

data FunType Source #

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

Instances details
Data FunType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show FunType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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

Instances

Instances details
Data ArraySize Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show ArraySize Source # 
Instance details

Defined in Language.C.Analysis.SemRep

data TypeDefRef Source #

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

Instances

Instances details
Data TypeDefRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show TypeDefRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode TypeDefRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos TypeDefRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

data TypeName Source #

normalized type representation

Instances

Instances details
Data TypeName Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show TypeName Source # 
Instance details

Defined in Language.C.Analysis.SemRep

data BuiltinType Source #

Builtin type (va_list, anything)

Constructors

TyVaList 
TyAny 

Instances

Instances details
Data BuiltinType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show BuiltinType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

data IntType Source #

integral types (C99 6.7.2.2)

Instances

Instances details
Data IntType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show IntType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Eq IntType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

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

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

Ord IntType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

data FloatType Source #

floating point type (C99 6.7.2.2)

Instances

Instances details
Data FloatType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show FloatType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Eq FloatType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Ord FloatType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

class HasSUERef a where Source #

accessor class : struct/union/enum names

Methods

sueRef :: a -> SUERef Source #

Instances

Instances details
HasSUERef TagFwdDecl Source # 
Instance details

Defined in Language.C.Analysis.DefTable

HasSUERef CompType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

HasSUERef CompTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

HasSUERef EnumType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

HasSUERef EnumTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

HasSUERef TagDef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

sueRef :: TagDef -> SUERef Source #

class HasCompTyKind a where Source #

accessor class : composite type tags (struct or union)

Methods

compTag :: a -> CompTyKind Source #

Instances

Instances details
HasCompTyKind CompType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

HasCompTyKind CompTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

data CompTypeRef Source #

composite type declarations

Instances

Instances details
Data CompTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show CompTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

HasCompTyKind CompTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

HasSUERef CompTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode CompTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos CompTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty CompTypeRef Source # 
Instance details

Defined in Language.C.Analysis.Debug

data CompType Source #

Composite type (struct or union).

Instances

Instances details
Data CompType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show CompType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

HasCompTyKind CompType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

HasSUERef CompType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode CompType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos CompType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty CompType Source # 
Instance details

Defined in Language.C.Analysis.Debug

typeOfCompDef :: CompType -> TypeName Source #

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 

Instances

Instances details
Data CompTyKind Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show CompTyKind Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Eq CompTyKind Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Ord CompTyKind Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty CompTyKind Source # 
Instance details

Defined in Language.C.Analysis.Debug

data EnumTypeRef Source #

Instances

Instances details
Data EnumTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show EnumTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

HasSUERef EnumTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode EnumTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos EnumTypeRef Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty EnumTypeRef Source # 
Instance details

Defined in Language.C.Analysis.Debug

data EnumType Source #

Representation of C enumeration types

Constructors

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

Instances

Instances details
Data EnumType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show EnumType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

HasSUERef EnumType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode EnumType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos EnumType Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty EnumType Source # 
Instance details

Defined in Language.C.Analysis.Debug

typeOfEnumDef :: EnumType -> TypeName Source #

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

Instances

Instances details
Data Enumerator Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show Enumerator Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Declaration Enumerator Source # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode Enumerator Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos Enumerator Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty Enumerator Source # 
Instance details

Defined in Language.C.Analysis.Debug

data TypeQuals Source #

Type qualifiers: constant, volatile and restrict

Constructors

TypeQuals 

Instances

Instances details
Data TypeQuals Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show TypeQuals Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Eq TypeQuals Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Ord TypeQuals Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty TypeQuals Source # 
Instance details

Defined in Language.C.Analysis.Debug

noTypeQuals :: TypeQuals Source #

no type qualifiers

mergeTypeQuals :: TypeQuals -> TypeQuals -> TypeQuals Source #

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 

Instances

Instances details
Data VarName Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show VarName Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty VarName Source # 
Instance details

Defined in Language.C.Analysis.Debug

type AsmName = CStrLit Source #

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 

Instances

Instances details
Data Attr Source # 
Instance details

Defined in Language.C.Analysis.SemRep

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 :: forall r r'. (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 #

Show Attr Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> Attr -> ShowS #

show :: Attr -> String #

showList :: [Attr] -> ShowS #

CNode Attr Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Pos Attr Source # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: Attr -> Position Source #

Pretty Attr Source # 
Instance details

Defined in Language.C.Analysis.Debug

Pretty Attributes Source # 
Instance details

Defined in Language.C.Analysis.Debug

noAttributes :: Attributes Source #

Empty attribute list

mergeAttributes :: Attributes -> Attributes -> Attributes Source #

Merge attribute lists TODO: currently does not remove duplicates

Statements and Expressions (STUB, aliases to Syntax)

type Stmt = CStat Source #

Stmt is an alias for CStat (Syntax)

type Expr = CExpr Source #

Expr is currently an alias for CStatement (Syntax)

type Initializer = CInit Source #

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

Top level assembler block (alias for CStrLit)