Copyright | (c) 2008 Benedikt Huber |
---|---|
License | BSD-style |
Maintainer | benedikt.huber@gmail.com |
Stability | alpha |
Portability | ghc |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module performs the analysis of declarations and the translation of type specifications in the AST.
Synopsis
- analyseTypeDecl :: MonadTrav m => CDecl -> m Type
- tType :: MonadTrav m => Bool -> NodeInfo -> [CTypeQual] -> TypeSpecAnalysis -> [CDerivedDeclr] -> [CDecl] -> m Type
- tDirectType :: MonadTrav m => Bool -> NodeInfo -> [CTypeQual] -> TypeSpecAnalysis -> m Type
- tNumType :: MonadCError m => NumTypeSpec -> m (Either (FloatType, Bool) IntType)
- tArraySize :: MonadTrav m => CArrSize -> m ArraySize
- tTypeQuals :: MonadTrav m => [CTypeQual] -> m (TypeQuals, Attributes)
- mergeOldStyle :: MonadCError m => NodeInfo -> [CDecl] -> [CDerivedDeclr] -> m [CDerivedDeclr]
- canonicalTypeSpec :: MonadTrav m => [CTypeSpec] -> m TypeSpecAnalysis
- data NumBaseType
- data SignSpec
- = NoSignSpec
- | Signed
- | Unsigned
- data SizeMod
- data NumTypeSpec = NumTypeSpec {}
- data TypeSpecAnalysis
- canonicalStorageSpec :: MonadCError m => [CStorageSpec] -> m StorageSpec
- data StorageSpec
- hasThreadLocalSpec :: StorageSpec -> Bool
- hasClKernelSpec :: StorageSpec -> Bool
- isTypeDef :: [CDeclSpec] -> Bool
- data VarDeclInfo = VarDeclInfo VarName FunctionAttrs StorageSpec Attributes Type NodeInfo
- tAttr :: (MonadCError m, MonadSymtab m) => CAttr -> m Attr
- mkVarName :: (MonadCError m, MonadSymtab m) => NodeInfo -> Maybe Ident -> Maybe AsmName -> m VarName
- getOnlyDeclr :: MonadCError m => CDecl -> m CDeclr
- nameOfDecl :: MonadCError m => CDecl -> m Ident
- analyseVarDecl :: MonadTrav m => Bool -> [CStorageSpec] -> [CAttr] -> [CTypeQual] -> TypeSpecAnalysis -> [CFunSpec] -> CDeclr -> [CDecl] -> Maybe CInit -> m VarDeclInfo
- analyseVarDecl' :: MonadTrav m => Bool -> [CDeclSpec] -> CDeclr -> [CDecl] -> Maybe CInit -> m VarDeclInfo
Translating types
analyseTypeDecl :: MonadTrav m => CDecl -> m Type Source #
get the type of a type declaration
A type declaration T
may appear in thre forms:
typeof(T)
- as abstract declarator in a function prototype, as in
f(int)
- in a declaration without declarators, as in
struct x { int a } ;
Currently, analyseTypeDecl
is exlusively used for analysing types for GNU's typeof(T)
.
We move attributes to the type, as they have no meaning for the abstract declarator
tType :: MonadTrav m => Bool -> NodeInfo -> [CTypeQual] -> TypeSpecAnalysis -> [CDerivedDeclr] -> [CDecl] -> m Type Source #
translate a type
tDirectType :: MonadTrav m => Bool -> NodeInfo -> [CTypeQual] -> TypeSpecAnalysis -> m Type Source #
translate a type without (syntactic) indirections
Due to the GNU typeof
extension and typeDefs, this can be an arbitrary type
tNumType :: MonadCError m => NumTypeSpec -> m (Either (FloatType, Bool) IntType) Source #
Mapping from num type specs to C types (C99 6.7.2-2), ignoring the complex qualifier.
tTypeQuals :: MonadTrav m => [CTypeQual] -> m (TypeQuals, Attributes) Source #
mergeOldStyle :: MonadCError m => NodeInfo -> [CDecl] -> [CDerivedDeclr] -> m [CDerivedDeclr] Source #
convert old style parameters
This requires matching parameter names and declarations, as in the following example:
int f(d,c,a,b) char a,*b; int c; { }
is converted to
int f(int d, int c, char a, char* b)
TODO: This could be moved to syntax, as it operates on the AST only
Dissecting type specs
canonicalTypeSpec :: MonadTrav m => [CTypeSpec] -> m TypeSpecAnalysis Source #
data NumBaseType Source #
Instances
Eq NumBaseType Source # | |
Defined in Language.C.Analysis.DeclAnalysis (==) :: NumBaseType -> NumBaseType -> Bool # (/=) :: NumBaseType -> NumBaseType -> Bool # | |
Ord NumBaseType Source # | |
Defined in Language.C.Analysis.DeclAnalysis compare :: NumBaseType -> NumBaseType -> Ordering # (<) :: NumBaseType -> NumBaseType -> Bool # (<=) :: NumBaseType -> NumBaseType -> Bool # (>) :: NumBaseType -> NumBaseType -> Bool # (>=) :: NumBaseType -> NumBaseType -> Bool # max :: NumBaseType -> NumBaseType -> NumBaseType # min :: NumBaseType -> NumBaseType -> NumBaseType # |
data TypeSpecAnalysis Source #
canonicalStorageSpec :: MonadCError m => [CStorageSpec] -> m StorageSpec Source #
data StorageSpec Source #
NoStorageSpec | |
AutoSpec | |
RegSpec | |
ThreadSpec | |
StaticSpec Bool | |
ExternSpec Bool | |
ClKernelSpec | |
ClGlobalSpec | |
ClLocalSpec |
Instances
Read StorageSpec Source # | |
Defined in Language.C.Analysis.DeclAnalysis readsPrec :: Int -> ReadS StorageSpec # readList :: ReadS [StorageSpec] # readPrec :: ReadPrec StorageSpec # readListPrec :: ReadPrec [StorageSpec] # | |
Show StorageSpec Source # | |
Defined in Language.C.Analysis.DeclAnalysis showsPrec :: Int -> StorageSpec -> ShowS # show :: StorageSpec -> String # showList :: [StorageSpec] -> ShowS # | |
Eq StorageSpec Source # | |
Defined in Language.C.Analysis.DeclAnalysis (==) :: StorageSpec -> StorageSpec -> Bool # (/=) :: StorageSpec -> StorageSpec -> Bool # | |
Ord StorageSpec Source # | |
Defined in Language.C.Analysis.DeclAnalysis compare :: StorageSpec -> StorageSpec -> Ordering # (<) :: StorageSpec -> StorageSpec -> Bool # (<=) :: StorageSpec -> StorageSpec -> Bool # (>) :: StorageSpec -> StorageSpec -> Bool # (>=) :: StorageSpec -> StorageSpec -> Bool # max :: StorageSpec -> StorageSpec -> StorageSpec # min :: StorageSpec -> StorageSpec -> StorageSpec # |
hasThreadLocalSpec :: StorageSpec -> Bool Source #
hasClKernelSpec :: StorageSpec -> Bool Source #
Helpers
tAttr :: (MonadCError m, MonadSymtab m) => CAttr -> m Attr Source #
translate attribute
annotations
TODO: This is a unwrap and wrap stub
mkVarName :: (MonadCError m, MonadSymtab m) => NodeInfo -> Maybe Ident -> Maybe AsmName -> m VarName Source #
construct a name for a variable TODO: more or less bogus
getOnlyDeclr :: MonadCError m => CDecl -> m CDeclr Source #
nameOfDecl :: MonadCError m => CDecl -> m Ident Source #
analyseVarDecl :: MonadTrav m => Bool -> [CStorageSpec] -> [CAttr] -> [CTypeQual] -> TypeSpecAnalysis -> [CFunSpec] -> CDeclr -> [CDecl] -> Maybe CInit -> m VarDeclInfo Source #
analyse declarators