Copyright | (c) 2008 Benedikt Huber |
---|---|
License | BSD-style |
Maintainer | benedikt.huber@gmail.com |
Stability | alpha |
Portability | ghc |
Safe Haskell | None |
Language | Haskell2010 |
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
- data TagDef
- typeOfTagDef :: TagDef -> TypeName
- class Declaration n where
- getVarDecl :: n -> VarDecl
- declIdent :: Declaration n => n -> Ident
- declName :: Declaration n => n -> VarName
- declType :: Declaration n => n -> Type
- declAttrs :: Declaration n => n -> DeclAttrs
- data IdentDecl
- objKindDescr :: IdentDecl -> String
- splitIdentDecls :: Bool -> Map Ident IdentDecl -> (Map Ident Decl, (Map Ident Enumerator, Map Ident ObjDef, Map Ident FunDef))
- data GlobalDecls = GlobalDecls {}
- emptyGlobalDecls :: GlobalDecls
- filterGlobalDecls :: (DeclEvent -> Bool) -> GlobalDecls -> GlobalDecls
- mergeGlobalDecls :: GlobalDecls -> GlobalDecls -> GlobalDecls
- data DeclEvent
- data Decl = Decl VarDecl NodeInfo
- data ObjDef = ObjDef VarDecl (Maybe Initializer) NodeInfo
- isTentative :: ObjDef -> Bool
- data FunDef = FunDef VarDecl Stmt NodeInfo
- data ParamDecl
- data MemberDecl
- = MemberDecl VarDecl (Maybe Expr) NodeInfo
- | AnonBitField Type Expr NodeInfo
- data TypeDef = TypeDef Ident Type Attributes NodeInfo
- identOfTypeDef :: TypeDef -> Ident
- data VarDecl = VarDecl VarName DeclAttrs Type
- data DeclAttrs = DeclAttrs FunctionAttrs Storage Attributes
- isExtDecl :: Declaration n => n -> Bool
- data FunctionAttrs = FunctionAttrs {
- isInline :: Bool
- isNoreturn :: Bool
- functionAttrs :: Declaration d => d -> FunctionAttrs
- noFunctionAttrs :: FunctionAttrs
- data Storage
- declStorage :: Declaration d => d -> Storage
- type ThreadLocal = Bool
- type Register = Bool
- data Linkage
- hasLinkage :: Storage -> Bool
- declLinkage :: Declaration d => d -> Linkage
- data Type
- data FunType
- = FunType Type [ParamDecl] Bool
- | FunTypeIncomplete Type
- data ArraySize
- = UnknownArraySize Bool
- | ArraySize Bool Expr
- data TypeDefRef = TypeDefRef Ident Type NodeInfo
- data TypeName
- data BuiltinType
- data IntType
- data FloatType
- class HasSUERef a where
- class HasCompTyKind a where
- compTag :: a -> CompTyKind
- data CompTypeRef = CompTypeRef SUERef CompTyKind NodeInfo
- data CompType = CompType SUERef CompTyKind [MemberDecl] Attributes NodeInfo
- typeOfCompDef :: CompType -> TypeName
- data CompTyKind
- data EnumTypeRef = EnumTypeRef SUERef NodeInfo
- data EnumType = EnumType SUERef [Enumerator] Attributes NodeInfo
- typeOfEnumDef :: EnumType -> TypeName
- data Enumerator = Enumerator Ident Expr EnumType NodeInfo
- data TypeQuals = TypeQuals {}
- noTypeQuals :: TypeQuals
- mergeTypeQuals :: TypeQuals -> TypeQuals -> TypeQuals
- data VarName
- identOfVarName :: VarName -> Ident
- isNoName :: VarName -> Bool
- type AsmName = CStrLit
- data Attr = Attr Ident [Expr] NodeInfo
- type Attributes = [Attr]
- noAttributes :: Attributes
- mergeAttributes :: Attributes -> Attributes -> Attributes
- type Stmt = CStat
- type Expr = CExpr
- type Initializer = CInit
- type AsmBlock = CStrLit
Sums of tags and identifiers
Composite type definitions (tags)
Instances
Data TagDef # | |
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 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 # | |
Pos TagDef # | |
Defined in Language.C.Analysis.SemRep | |
CNode TagDef # | |
Defined in Language.C.Analysis.SemRep | |
Pretty TagDef # | |
Defined in Language.C.Analysis.Debug | |
HasSUERef TagDef # | |
Defined in Language.C.Analysis.SemRep |
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
Declaration Enumerator # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: Enumerator -> VarDecl # | |
Declaration VarDecl # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: VarDecl -> VarDecl # | |
Declaration MemberDecl # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: MemberDecl -> VarDecl # | |
Declaration ParamDecl # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: ParamDecl -> VarDecl # | |
Declaration FunDef # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: FunDef -> VarDecl # | |
Declaration ObjDef # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: ObjDef -> VarDecl # | |
Declaration Decl # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: Decl -> VarDecl # | |
Declaration IdentDecl # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: IdentDecl -> VarDecl # | |
(Declaration a, Declaration b) => Declaration (Either a b) # | |
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
identifiers, typedefs and enumeration constants (namespace sum)
Constructors
Declaration Decl | object or function declaration |
ObjectDef ObjDef | object definition |
FunctionDef FunDef | function definition |
EnumeratorDef Enumerator | definition of an enumerator |
Instances
Data IdentDecl # | |
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 # | |
Pos IdentDecl # | |
Defined in Language.C.Analysis.SemRep | |
CNode IdentDecl # | |
Defined in Language.C.Analysis.SemRep | |
Pretty IdentDecl # | |
Defined in Language.C.Analysis.Debug | |
Declaration IdentDecl # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: IdentDecl -> VarDecl # |
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 | |
Instances
Pretty GlobalDecls # | |
Defined in Language.C.Analysis.Debug |
emptyGlobalDecls :: GlobalDecls #
empty global declaration table
filterGlobalDecls :: (DeclEvent -> Bool) -> GlobalDecls -> GlobalDecls #
filter global declarations
mergeGlobalDecls :: GlobalDecls -> GlobalDecls -> GlobalDecls #
merge global declarations
Events for visitors
Declaration events
Those events are reported to callbacks, which are executed during the traversal.
Constructors
TagEvent TagDef | file-scope struct/union/enum event |
DeclEvent IdentDecl | file-scope declaration or definition |
ParamEvent ParamDecl | parameter declaration |
LocalEvent IdentDecl | local variable declaration or definition |
TypeDefEvent TypeDef | a type definition |
AsmEvent AsmBlock | assembler block |
Declarations and definitions
Declarations, which aren't definitions
Instances
Data Decl # | |
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 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 # | |
Pos Decl # | |
Defined in Language.C.Analysis.SemRep | |
CNode Decl # | |
Defined in Language.C.Analysis.SemRep | |
Pretty Decl # | |
Defined in Language.C.Analysis.Debug | |
Declaration Decl # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: Decl -> VarDecl # |
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
Data ObjDef # | |
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 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 # | |
Pos ObjDef # | |
Defined in Language.C.Analysis.SemRep | |
CNode ObjDef # | |
Defined in Language.C.Analysis.SemRep | |
Pretty ObjDef # | |
Defined in Language.C.Analysis.Debug | |
Declaration ObjDef # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: ObjDef -> VarDecl # |
isTentative :: ObjDef -> Bool #
Returns True
if the given object definition is tentative.
Function definitions
A function definition is a declaration together with a statement (the function body).
Instances
Data FunDef # | |
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 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 # | |
Pos FunDef # | |
Defined in Language.C.Analysis.SemRep | |
CNode FunDef # | |
Defined in Language.C.Analysis.SemRep | |
Pretty FunDef # | |
Defined in Language.C.Analysis.Debug | |
Declaration FunDef # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: FunDef -> VarDecl # |
Parameter declaration
Instances
Data ParamDecl # | |
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 # | |
Pos ParamDecl # | |
Defined in Language.C.Analysis.SemRep | |
CNode ParamDecl # | |
Defined in Language.C.Analysis.SemRep | |
Pretty ParamDecl # | |
Defined in Language.C.Analysis.Debug | |
Declaration ParamDecl # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: ParamDecl -> VarDecl # |
data MemberDecl #
Struct/Union member declaration
Constructors
MemberDecl VarDecl (Maybe Expr) NodeInfo | MemberDecl vardecl bitfieldsize node |
AnonBitField Type Expr NodeInfo | AnonBitField typ size |
Instances
Data MemberDecl # | |
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 # | |
Defined in Language.C.Analysis.SemRep Methods showsPrec :: Int -> MemberDecl -> ShowS show :: MemberDecl -> String showList :: [MemberDecl] -> ShowS | |
Pos MemberDecl # | |
Defined in Language.C.Analysis.SemRep Methods posOf :: MemberDecl -> Position # | |
CNode MemberDecl # | |
Defined in Language.C.Analysis.SemRep Methods nodeInfo :: MemberDecl -> NodeInfo # | |
Pretty MemberDecl # | |
Defined in Language.C.Analysis.Debug | |
Declaration MemberDecl # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: MemberDecl -> VarDecl # |
typedef
definitions.
The identifier is a new name for the given type.
Constructors
TypeDef Ident Type Attributes NodeInfo |
Instances
Data TypeDef # | |
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 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 # | |
Pos TypeDef # | |
Defined in Language.C.Analysis.SemRep | |
CNode TypeDef # | |
Defined in Language.C.Analysis.SemRep | |
Pretty TypeDef # | |
Defined in Language.C.Analysis.Debug |
identOfTypeDef :: TypeDef -> Ident #
return the idenitifier of a typedef
Generic variable declarations
Instances
Data VarDecl # | |
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 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 # | |
Pretty VarDecl # | |
Defined in Language.C.Analysis.Debug | |
Declaration VarDecl # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: VarDecl -> VarDecl # |
Declaration attributes
Declaration attributes of the form DeclAttrs isInlineFunction storage linkage attrs
They specify the storage and linkage of a declared object.
Constructors
DeclAttrs FunctionAttrs Storage Attributes | DeclAttrs fspecs storage attrs |
Instances
Data DeclAttrs # | |
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 # | |
Pretty DeclAttrs # | |
Defined in Language.C.Analysis.Debug |
isExtDecl :: Declaration n => n -> Bool #
data FunctionAttrs #
Constructors
FunctionAttrs | |
Fields
|
Instances
Eq FunctionAttrs # | |
Defined in Language.C.Analysis.SemRep | |
Data FunctionAttrs # | |
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 # | |
Defined in Language.C.Analysis.SemRep Methods compare :: FunctionAttrs -> FunctionAttrs -> Ordering (<) :: FunctionAttrs -> FunctionAttrs -> Bool (<=) :: FunctionAttrs -> FunctionAttrs -> Bool (>) :: FunctionAttrs -> FunctionAttrs -> Bool (>=) :: FunctionAttrs -> FunctionAttrs -> Bool max :: FunctionAttrs -> FunctionAttrs -> FunctionAttrs min :: FunctionAttrs -> FunctionAttrs -> FunctionAttrs | |
Show FunctionAttrs # | |
Defined in Language.C.Analysis.SemRep Methods showsPrec :: Int -> FunctionAttrs -> ShowS show :: FunctionAttrs -> String showList :: [FunctionAttrs] -> ShowS | |
Pretty FunctionAttrs # | |
Defined in Language.C.Analysis.Debug |
functionAttrs :: Declaration d => d -> FunctionAttrs #
get the `function attributes' of a declaration
Storage duration and linkage of a variable
Constructors
NoStorage | no storage |
Auto Register | automatic storage (optional: register) |
Static Linkage ThreadLocal | static storage, linkage spec and thread local specifier (gnu c) |
FunLinkage Linkage | function, either internal or external linkage |
Instances
Eq Storage # | |
Data Storage # | |
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 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 # | |
Show Storage # | |
Pretty Storage # | |
Defined in Language.C.Analysis.Debug |
declStorage :: Declaration d => d -> Storage #
get the Storage
of a declaration
type ThreadLocal = Bool #
Linkage: Either no linkage, internal to the translation unit or external
Constructors
NoLinkage | |
InternalLinkage | |
ExternalLinkage |
Instances
Eq Linkage # | |
Data Linkage # | |
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 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 # | |
Show Linkage # | |
Pretty Linkage # | |
Defined in Language.C.Analysis.Debug |
hasLinkage :: Storage -> Bool #
return True
if the object has linkage
declLinkage :: Declaration d => d -> Linkage #
Get the linkage of a definition
Types
types of C objects
Constructors
DirectType TypeName TypeQuals Attributes | a non-derived type |
PtrType Type TypeQuals Attributes | pointer type |
ArrayType Type ArraySize TypeQuals Attributes | array type |
FunctionType FunType Attributes | function type |
TypeDefType TypeDefRef TypeQuals Attributes | a defined type |
Instances
Data Type # | |
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 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 # | |
Pretty Type # | |
Defined in Language.C.Analysis.Debug |
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
.
Constructors
FunType Type [ParamDecl] Bool | |
FunTypeIncomplete Type |
Instances
Data FunType # | |
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 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 # | |
An array type may either have unknown size or a specified array size, the latter either variable or constant.
Furthermore, when used as a function parameters, the size may be qualified as static.
In a function prototype, the size may be `Unspecified variable size' ([*]
).
Constructors
UnknownArraySize Bool | UnknownArraySize is-starred |
ArraySize Bool Expr | FixedSizeArray is-static size-expr |
Instances
Data ArraySize # | |
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 # | |
data TypeDefRef #
typdef references If the actual type is known, it is attached for convenience
Constructors
TypeDefRef Ident Type NodeInfo |
Instances
Data TypeDefRef # | |
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 # | |
Defined in Language.C.Analysis.SemRep Methods showsPrec :: Int -> TypeDefRef -> ShowS show :: TypeDefRef -> String showList :: [TypeDefRef] -> ShowS | |
Pos TypeDefRef # | |
Defined in Language.C.Analysis.SemRep Methods posOf :: TypeDefRef -> Position # | |
CNode TypeDefRef # | |
Defined in Language.C.Analysis.SemRep Methods nodeInfo :: TypeDefRef -> NodeInfo # |
normalized type representation
Constructors
TyVoid | |
TyIntegral IntType | |
TyFloating FloatType | |
TyComplex FloatType | |
TyComp CompTypeRef | |
TyEnum EnumTypeRef | |
TyBuiltin BuiltinType |
Instances
Data TypeName # | |
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 # | |
data BuiltinType #
Builtin type (va_list, anything)
Instances
Data BuiltinType # | |
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 # | |
Defined in Language.C.Analysis.SemRep Methods showsPrec :: Int -> BuiltinType -> ShowS show :: BuiltinType -> String showList :: [BuiltinType] -> ShowS |
integral types (C99 6.7.2.2)
Constructors
TyBool | |
TyChar | |
TySChar | |
TyUChar | |
TyShort | |
TyUShort | |
TyInt | |
TyUInt | |
TyInt128 | |
TyUInt128 | |
TyLong | |
TyULong | |
TyLLong | |
TyULLong |
Instances
Eq IntType # | |
Data IntType # | |
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 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 # | |
Show IntType # | |
floating point type (C99 6.7.2.2)
Instances
Eq FloatType # | |
Data FloatType # | |
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 # | |
Defined in Language.C.Analysis.SemRep | |
Show FloatType # | |
accessor class : struct/union/enum names
Instances
HasSUERef EnumType # | |
Defined in Language.C.Analysis.SemRep | |
HasSUERef CompType # | |
Defined in Language.C.Analysis.SemRep | |
HasSUERef EnumTypeRef # | |
Defined in Language.C.Analysis.SemRep Methods sueRef :: EnumTypeRef -> SUERef # | |
HasSUERef CompTypeRef # | |
Defined in Language.C.Analysis.SemRep Methods sueRef :: CompTypeRef -> SUERef # | |
HasSUERef TagDef # | |
Defined in Language.C.Analysis.SemRep | |
HasSUERef TagFwdDecl # | |
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
HasCompTyKind CompType # | |
Defined in Language.C.Analysis.SemRep Methods compTag :: CompType -> CompTyKind # | |
HasCompTyKind CompTypeRef # | |
Defined in Language.C.Analysis.SemRep Methods compTag :: CompTypeRef -> CompTyKind # |
data CompTypeRef #
composite type declarations
Constructors
CompTypeRef SUERef CompTyKind NodeInfo |
Instances
Data CompTypeRef # | |
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 # | |
Defined in Language.C.Analysis.SemRep Methods showsPrec :: Int -> CompTypeRef -> ShowS show :: CompTypeRef -> String showList :: [CompTypeRef] -> ShowS | |
Pos CompTypeRef # | |
Defined in Language.C.Analysis.SemRep Methods posOf :: CompTypeRef -> Position # | |
CNode CompTypeRef # | |
Defined in Language.C.Analysis.SemRep Methods nodeInfo :: CompTypeRef -> NodeInfo # | |
Pretty CompTypeRef # | |
Defined in Language.C.Analysis.Debug | |
HasCompTyKind CompTypeRef # | |
Defined in Language.C.Analysis.SemRep Methods compTag :: CompTypeRef -> CompTyKind # | |
HasSUERef CompTypeRef # | |
Defined in Language.C.Analysis.SemRep Methods sueRef :: CompTypeRef -> SUERef # |
Composite type (struct or union).
Constructors
CompType SUERef CompTyKind [MemberDecl] Attributes NodeInfo |
Instances
Data CompType # | |
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 # | |
Pos CompType # | |
Defined in Language.C.Analysis.SemRep | |
CNode CompType # | |
Defined in Language.C.Analysis.SemRep | |
Pretty CompType # | |
Defined in Language.C.Analysis.Debug | |
HasCompTyKind CompType # | |
Defined in Language.C.Analysis.SemRep Methods compTag :: CompType -> CompTyKind # | |
HasSUERef CompType # | |
Defined in Language.C.Analysis.SemRep |
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
.
Instances
Eq CompTyKind # | |
Defined in Language.C.Analysis.SemRep | |
Data CompTyKind # | |
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 # | |
Defined in Language.C.Analysis.SemRep Methods compare :: CompTyKind -> CompTyKind -> Ordering (<) :: CompTyKind -> CompTyKind -> Bool (<=) :: CompTyKind -> CompTyKind -> Bool (>) :: CompTyKind -> CompTyKind -> Bool (>=) :: CompTyKind -> CompTyKind -> Bool max :: CompTyKind -> CompTyKind -> CompTyKind min :: CompTyKind -> CompTyKind -> CompTyKind | |
Show CompTyKind # | |
Defined in Language.C.Analysis.SemRep Methods showsPrec :: Int -> CompTyKind -> ShowS show :: CompTyKind -> String showList :: [CompTyKind] -> ShowS | |
Pretty CompTyKind # | |
Defined in Language.C.Analysis.Debug |
data EnumTypeRef #
Constructors
EnumTypeRef SUERef NodeInfo |
Instances
Data EnumTypeRef # | |
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 # | |
Defined in Language.C.Analysis.SemRep Methods showsPrec :: Int -> EnumTypeRef -> ShowS show :: EnumTypeRef -> String showList :: [EnumTypeRef] -> ShowS | |
Pos EnumTypeRef # | |
Defined in Language.C.Analysis.SemRep Methods posOf :: EnumTypeRef -> Position # | |
CNode EnumTypeRef # | |
Defined in Language.C.Analysis.SemRep Methods nodeInfo :: EnumTypeRef -> NodeInfo # | |
Pretty EnumTypeRef # | |
Defined in Language.C.Analysis.Debug | |
HasSUERef EnumTypeRef # | |
Defined in Language.C.Analysis.SemRep Methods sueRef :: EnumTypeRef -> SUERef # |
Representation of C enumeration types
Constructors
EnumType SUERef [Enumerator] Attributes NodeInfo | EnumType name enumeration-constants attrs node |
Instances
Data EnumType # | |
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 # | |
Pos EnumType # | |
Defined in Language.C.Analysis.SemRep | |
CNode EnumType # | |
Defined in Language.C.Analysis.SemRep | |
Pretty EnumType # | |
Defined in Language.C.Analysis.Debug | |
HasSUERef EnumType # | |
Defined in Language.C.Analysis.SemRep |
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
Constructors
Enumerator Ident Expr EnumType NodeInfo |
Instances
Data Enumerator # | |
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 # | |
Defined in Language.C.Analysis.SemRep Methods showsPrec :: Int -> Enumerator -> ShowS show :: Enumerator -> String showList :: [Enumerator] -> ShowS | |
Pos Enumerator # | |
Defined in Language.C.Analysis.SemRep Methods posOf :: Enumerator -> Position # | |
CNode Enumerator # | |
Defined in Language.C.Analysis.SemRep Methods nodeInfo :: Enumerator -> NodeInfo # | |
Pretty Enumerator # | |
Defined in Language.C.Analysis.Debug | |
Declaration Enumerator # | |
Defined in Language.C.Analysis.SemRep Methods getVarDecl :: Enumerator -> VarDecl # |
Type qualifiers: constant, volatile and restrict
Constructors
TypeQuals | |
Instances
Eq TypeQuals # | |
Data TypeQuals # | |
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 # | |
Defined in Language.C.Analysis.SemRep | |
Show TypeQuals # | |
Pretty TypeQuals # | |
Defined in Language.C.Analysis.Debug |
no type qualifiers
mergeTypeQuals :: TypeQuals -> TypeQuals -> TypeQuals #
merge (&&) two type qualifier sets
Variable names
VarName name assembler-name
is a name of an declared object
Instances
Data VarName # | |
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 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 # | |
Pretty VarName # | |
Defined in Language.C.Analysis.Debug |
identOfVarName :: VarName -> Ident #
Attributes (STUB, not yet analyzed)
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
Instances
Data Attr # | |
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 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 # | |
Pos Attr # | |
Defined in Language.C.Analysis.SemRep | |
CNode Attr # | |
Defined in Language.C.Analysis.SemRep | |
Pretty Attributes # | |
Defined in Language.C.Analysis.Debug | |
Pretty Attr # | |
Defined in Language.C.Analysis.Debug |
type Attributes = [Attr] #
Empty attribute list
mergeAttributes :: Attributes -> Attributes -> Attributes #
Merge attribute lists TODO: currently does not remove duplicates
Statements and Expressions (STUB, aliases to 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