language-c-0.9.0.2: Analysis and generation of C code
Copyright(c) 2008 Benedikt Huber
LicenseBSD-style
Maintainerbenedikt.huber@gmail.com
Stabilityalpha
Portabilityghc
Safe HaskellNone
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 #

Composite type definitions (tags)

Instances

Instances details
Data TagDef # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> TagDef -> ShowS

show :: TagDef -> String

showList :: [TagDef] -> ShowS

Pos TagDef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: TagDef -> Position #

CNode TagDef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

nodeInfo :: TagDef -> NodeInfo #

Pretty TagDef # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: TagDef -> Doc #

prettyPrec :: Int -> TagDef -> Doc #

HasSUERef TagDef # 
Instance details

Defined in Language.C.Analysis.SemRep

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

Methods

getVarDecl :: n -> VarDecl #

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

Instances

Instances details
Declaration Enumerator # 
Instance details

Defined in Language.C.Analysis.SemRep

Declaration VarDecl # 
Instance details

Defined in Language.C.Analysis.SemRep

Declaration MemberDecl # 
Instance details

Defined in Language.C.Analysis.SemRep

Declaration ParamDecl # 
Instance details

Defined in Language.C.Analysis.SemRep

Declaration FunDef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

getVarDecl :: FunDef -> VarDecl #

Declaration ObjDef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

getVarDecl :: ObjDef -> VarDecl #

Declaration Decl # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

getVarDecl :: Decl -> VarDecl #

Declaration IdentDecl # 
Instance details

Defined in Language.C.Analysis.SemRep

(Declaration a, Declaration b) => Declaration (Either a b) # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

getVarDecl :: Either a b -> VarDecl #

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

Instances details
Data IdentDecl # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> IdentDecl -> ShowS

show :: IdentDecl -> String

showList :: [IdentDecl] -> ShowS

Pos IdentDecl # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: IdentDecl -> Position #

CNode IdentDecl # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty IdentDecl # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: IdentDecl -> Doc #

prettyPrec :: Int -> IdentDecl -> Doc #

Declaration IdentDecl # 
Instance details

Defined in Language.C.Analysis.SemRep

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

Constructors

GlobalDecls 

Fields

Instances

Instances details
Pretty GlobalDecls # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: GlobalDecls -> Doc #

prettyPrec :: Int -> GlobalDecls -> Doc #

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

Instances

Instances details
Pos DeclEvent # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: DeclEvent -> Position #

CNode DeclEvent # 
Instance details

Defined in Language.C.Analysis.SemRep

Declarations and definitions

data Decl #

Declarations, which aren't definitions

Constructors

Decl VarDecl NodeInfo 

Instances

Instances details
Data Decl # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> Decl -> ShowS

show :: Decl -> String

showList :: [Decl] -> ShowS

Pos Decl # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: Decl -> Position #

CNode Decl # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

nodeInfo :: Decl -> NodeInfo #

Pretty Decl # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: Decl -> Doc #

prettyPrec :: Int -> Decl -> Doc #

Declaration Decl # 
Instance details

Defined in Language.C.Analysis.SemRep

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.

Constructors

ObjDef VarDecl (Maybe Initializer) NodeInfo 

Instances

Instances details
Data ObjDef # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> ObjDef -> ShowS

show :: ObjDef -> String

showList :: [ObjDef] -> ShowS

Pos ObjDef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: ObjDef -> Position #

CNode ObjDef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

nodeInfo :: ObjDef -> NodeInfo #

Pretty ObjDef # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: ObjDef -> Doc #

prettyPrec :: Int -> ObjDef -> Doc #

Declaration ObjDef # 
Instance details

Defined in Language.C.Analysis.SemRep

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

Instances details
Data FunDef # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> FunDef -> ShowS

show :: FunDef -> String

showList :: [FunDef] -> ShowS

Pos FunDef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: FunDef -> Position #

CNode FunDef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

nodeInfo :: FunDef -> NodeInfo #

Pretty FunDef # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: FunDef -> Doc #

prettyPrec :: Int -> FunDef -> Doc #

Declaration FunDef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

getVarDecl :: FunDef -> VarDecl #

data ParamDecl #

Parameter declaration

Instances

Instances details
Data ParamDecl # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> ParamDecl -> ShowS

show :: ParamDecl -> String

showList :: [ParamDecl] -> ShowS

Pos ParamDecl # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: ParamDecl -> Position #

CNode ParamDecl # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty ParamDecl # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: ParamDecl -> Doc #

prettyPrec :: Int -> ParamDecl -> Doc #

Declaration ParamDecl # 
Instance details

Defined in Language.C.Analysis.SemRep

data MemberDecl #

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 # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> MemberDecl -> ShowS

show :: MemberDecl -> String

showList :: [MemberDecl] -> ShowS

Pos MemberDecl # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: MemberDecl -> Position #

CNode MemberDecl # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty MemberDecl # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: MemberDecl -> Doc #

prettyPrec :: Int -> MemberDecl -> Doc #

Declaration MemberDecl # 
Instance details

Defined in Language.C.Analysis.SemRep

data TypeDef #

typedef definitions.

The identifier is a new name for the given type.

Instances

Instances details
Data TypeDef # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> TypeDef -> ShowS

show :: TypeDef -> String

showList :: [TypeDef] -> ShowS

Pos TypeDef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: TypeDef -> Position #

CNode TypeDef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

nodeInfo :: TypeDef -> NodeInfo #

Pretty TypeDef # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: TypeDef -> Doc #

prettyPrec :: Int -> TypeDef -> Doc #

identOfTypeDef :: TypeDef -> Ident #

return the idenitifier of a typedef

data VarDecl #

Generic variable declarations

Instances

Instances details
Data VarDecl # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> VarDecl -> ShowS

show :: VarDecl -> String

showList :: [VarDecl] -> ShowS

Pretty VarDecl # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: VarDecl -> Doc #

prettyPrec :: Int -> VarDecl -> Doc #

Declaration VarDecl # 
Instance details

Defined in Language.C.Analysis.SemRep

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

Instances details
Data DeclAttrs # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> DeclAttrs -> ShowS

show :: DeclAttrs -> String

showList :: [DeclAttrs] -> ShowS

Pretty DeclAttrs # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: DeclAttrs -> Doc #

prettyPrec :: Int -> DeclAttrs -> Doc #

isExtDecl :: Declaration n => n -> Bool #

data FunctionAttrs #

Constructors

FunctionAttrs 

Fields

Instances

Instances details
Eq FunctionAttrs # 
Instance details

Defined in Language.C.Analysis.SemRep

Data FunctionAttrs # 
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

Ord FunctionAttrs # 
Instance details

Defined in Language.C.Analysis.SemRep

Show FunctionAttrs # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> FunctionAttrs -> ShowS

show :: FunctionAttrs -> String

showList :: [FunctionAttrs] -> ShowS

Pretty FunctionAttrs # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: FunctionAttrs -> Doc #

prettyPrec :: Int -> FunctionAttrs -> Doc #

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

Instances details
Eq Storage # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

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

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

Data Storage # 
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

Ord Storage # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

compare :: Storage -> Storage -> Ordering

(<) :: Storage -> Storage -> Bool

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

(>) :: Storage -> Storage -> Bool

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

max :: Storage -> Storage -> Storage

min :: Storage -> Storage -> Storage

Show Storage # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> Storage -> ShowS

show :: Storage -> String

showList :: [Storage] -> ShowS

Pretty Storage # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: Storage -> Doc #

prettyPrec :: Int -> Storage -> Doc #

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

get the Storage of a declaration

type ThreadLocal = Bool #

type Register = Bool #

data Linkage #

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

Instances

Instances details
Eq Linkage # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

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

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

Data Linkage # 
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

Ord Linkage # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

compare :: Linkage -> Linkage -> Ordering

(<) :: Linkage -> Linkage -> Bool

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

(>) :: Linkage -> Linkage -> Bool

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

max :: Linkage -> Linkage -> Linkage

min :: Linkage -> Linkage -> Linkage

Show Linkage # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> Linkage -> ShowS

show :: Linkage -> String

showList :: [Linkage] -> ShowS

Pretty Linkage # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: Linkage -> Doc #

prettyPrec :: Int -> Linkage -> Doc #

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

Instances details
Data Type # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> Type -> ShowS

show :: Type -> String

showList :: [Type] -> ShowS

Pretty Type # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: Type -> Doc #

prettyPrec :: Int -> Type -> Doc #

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

Instances details
Data FunType # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> FunType -> ShowS

show :: FunType -> String

showList :: [FunType] -> ShowS

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

Instances details
Data ArraySize # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> ArraySize -> ShowS

show :: ArraySize -> String

showList :: [ArraySize] -> ShowS

data TypeDefRef #

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

Instances

Instances details
Data TypeDefRef # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> TypeDefRef -> ShowS

show :: TypeDefRef -> String

showList :: [TypeDefRef] -> ShowS

Pos TypeDefRef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: TypeDefRef -> Position #

CNode TypeDefRef # 
Instance details

Defined in Language.C.Analysis.SemRep

data TypeName #

normalized type representation

Instances

Instances details
Data TypeName # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> TypeName -> ShowS

show :: TypeName -> String

showList :: [TypeName] -> ShowS

data BuiltinType #

Builtin type (va_list, anything)

Constructors

TyVaList 
TyAny 

Instances

Instances details
Data BuiltinType # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> BuiltinType -> ShowS

show :: BuiltinType -> String

showList :: [BuiltinType] -> ShowS

data IntType #

integral types (C99 6.7.2.2)

Instances

Instances details
Eq IntType # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

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

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

Data IntType # 
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

Ord IntType # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

compare :: IntType -> IntType -> Ordering

(<) :: IntType -> IntType -> Bool

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

(>) :: IntType -> IntType -> Bool

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

max :: IntType -> IntType -> IntType

min :: IntType -> IntType -> IntType

Show IntType # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> IntType -> ShowS

show :: IntType -> String

showList :: [IntType] -> ShowS

data FloatType #

floating point type (C99 6.7.2.2)

Constructors

TyFloat 
TyDouble 
TyLDouble 
TyFloatN Int Bool 

Instances

Instances details
Eq FloatType # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

(==) :: FloatType -> FloatType -> Bool

(/=) :: FloatType -> FloatType -> Bool

Data FloatType # 
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

Ord FloatType # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

compare :: FloatType -> FloatType -> Ordering

(<) :: FloatType -> FloatType -> Bool

(<=) :: FloatType -> FloatType -> Bool

(>) :: FloatType -> FloatType -> Bool

(>=) :: FloatType -> FloatType -> Bool

max :: FloatType -> FloatType -> FloatType

min :: FloatType -> FloatType -> FloatType

Show FloatType # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> FloatType -> ShowS

show :: FloatType -> String

showList :: [FloatType] -> ShowS

class HasSUERef a where #

accessor class : struct/union/enum names

Methods

sueRef :: a -> SUERef #

Instances

Instances details
HasSUERef EnumType # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

sueRef :: EnumType -> SUERef #

HasSUERef CompType # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

sueRef :: CompType -> SUERef #

HasSUERef EnumTypeRef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

sueRef :: EnumTypeRef -> SUERef #

HasSUERef CompTypeRef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

sueRef :: CompTypeRef -> SUERef #

HasSUERef TagDef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

sueRef :: TagDef -> SUERef #

HasSUERef TagFwdDecl # 
Instance details

Defined in Language.C.Analysis.DefTable

Methods

sueRef :: TagFwdDecl -> SUERef #

class HasCompTyKind a where #

accessor class : composite type tags (struct or union)

Methods

compTag :: a -> CompTyKind #

Instances

Instances details
HasCompTyKind CompType # 
Instance details

Defined in Language.C.Analysis.SemRep

HasCompTyKind CompTypeRef # 
Instance details

Defined in Language.C.Analysis.SemRep

data CompTypeRef #

composite type declarations

Instances

Instances details
Data CompTypeRef # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> CompTypeRef -> ShowS

show :: CompTypeRef -> String

showList :: [CompTypeRef] -> ShowS

Pos CompTypeRef # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode CompTypeRef # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty CompTypeRef # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: CompTypeRef -> Doc #

prettyPrec :: Int -> CompTypeRef -> Doc #

HasCompTyKind CompTypeRef # 
Instance details

Defined in Language.C.Analysis.SemRep

HasSUERef CompTypeRef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

sueRef :: CompTypeRef -> SUERef #

data CompType #

Composite type (struct or union).

Instances

Instances details
Data CompType # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> CompType -> ShowS

show :: CompType -> String

showList :: [CompType] -> ShowS

Pos CompType # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: CompType -> Position #

CNode CompType # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty CompType # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: CompType -> Doc #

prettyPrec :: Int -> CompType -> Doc #

HasCompTyKind CompType # 
Instance details

Defined in Language.C.Analysis.SemRep

HasSUERef CompType # 
Instance details

Defined in Language.C.Analysis.SemRep

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

Instances details
Eq CompTyKind # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

(==) :: CompTyKind -> CompTyKind -> Bool

(/=) :: CompTyKind -> CompTyKind -> Bool

Data CompTyKind # 
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

Ord CompTyKind # 
Instance details

Defined in Language.C.Analysis.SemRep

Show CompTyKind # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> CompTyKind -> ShowS

show :: CompTyKind -> String

showList :: [CompTyKind] -> ShowS

Pretty CompTyKind # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: CompTyKind -> Doc #

prettyPrec :: Int -> CompTyKind -> Doc #

data EnumTypeRef #

Instances

Instances details
Data EnumTypeRef # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> EnumTypeRef -> ShowS

show :: EnumTypeRef -> String

showList :: [EnumTypeRef] -> ShowS

Pos EnumTypeRef # 
Instance details

Defined in Language.C.Analysis.SemRep

CNode EnumTypeRef # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty EnumTypeRef # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: EnumTypeRef -> Doc #

prettyPrec :: Int -> EnumTypeRef -> Doc #

HasSUERef EnumTypeRef # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

sueRef :: EnumTypeRef -> SUERef #

data EnumType #

Representation of C enumeration types

Constructors

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

Instances

Instances details
Data EnumType # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> EnumType -> ShowS

show :: EnumType -> String

showList :: [EnumType] -> ShowS

Pos EnumType # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: EnumType -> Position #

CNode EnumType # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty EnumType # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: EnumType -> Doc #

prettyPrec :: Int -> EnumType -> Doc #

HasSUERef EnumType # 
Instance details

Defined in Language.C.Analysis.SemRep

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

Instances details
Data Enumerator # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> Enumerator -> ShowS

show :: Enumerator -> String

showList :: [Enumerator] -> ShowS

Pos Enumerator # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: Enumerator -> Position #

CNode Enumerator # 
Instance details

Defined in Language.C.Analysis.SemRep

Pretty Enumerator # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: Enumerator -> Doc #

prettyPrec :: Int -> Enumerator -> Doc #

Declaration Enumerator # 
Instance details

Defined in Language.C.Analysis.SemRep

data TypeQuals #

Type qualifiers: constant, volatile and restrict

Constructors

TypeQuals 

Fields

Instances

Instances details
Eq TypeQuals # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

(==) :: TypeQuals -> TypeQuals -> Bool

(/=) :: TypeQuals -> TypeQuals -> Bool

Data TypeQuals # 
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

Ord TypeQuals # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

compare :: TypeQuals -> TypeQuals -> Ordering

(<) :: TypeQuals -> TypeQuals -> Bool

(<=) :: TypeQuals -> TypeQuals -> Bool

(>) :: TypeQuals -> TypeQuals -> Bool

(>=) :: TypeQuals -> TypeQuals -> Bool

max :: TypeQuals -> TypeQuals -> TypeQuals

min :: TypeQuals -> TypeQuals -> TypeQuals

Show TypeQuals # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> TypeQuals -> ShowS

show :: TypeQuals -> String

showList :: [TypeQuals] -> ShowS

Pretty TypeQuals # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: TypeQuals -> Doc #

prettyPrec :: Int -> TypeQuals -> Doc #

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

Instances details
Data VarName # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> VarName -> ShowS

show :: VarName -> String

showList :: [VarName] -> ShowS

Pretty VarName # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: VarName -> Doc #

prettyPrec :: Int -> VarName -> Doc #

isNoName :: VarName -> Bool #

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

Instances details
Data Attr # 
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 # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

showsPrec :: Int -> Attr -> ShowS

show :: Attr -> String

showList :: [Attr] -> ShowS

Pos Attr # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

posOf :: Attr -> Position #

CNode Attr # 
Instance details

Defined in Language.C.Analysis.SemRep

Methods

nodeInfo :: Attr -> NodeInfo #

Pretty Attributes # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: Attributes -> Doc #

prettyPrec :: Int -> Attributes -> Doc #

Pretty Attr # 
Instance details

Defined in Language.C.Analysis.Debug

Methods

pretty :: Attr -> Doc #

prettyPrec :: Int -> Attr -> Doc #

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)