Copyright | (c) 2006-2011 Harvard University (c) 2011-2013 Geoffrey Mainland (c) 2013 Manuel M T Chakravarty : (c) 2013-2016 Drexel University |
---|---|
License | BSD-style |
Maintainer | mainland@drexel.edu |
Safe Haskell | None |
Language | Haskell98 |
- data Extensions
- data Id
- data StringLit = StringLit [String] String !SrcLoc
- type Linkage = StringLit
- data Storage
- data TypeQual
- = Tconst !SrcLoc
- | Tvolatile !SrcLoc
- | EscTypeQual String !SrcLoc
- | AntiTypeQual String !SrcLoc
- | AntiTypeQuals String !SrcLoc
- | Tinline !SrcLoc
- | Trestrict !SrcLoc
- | T__restrict !SrcLoc
- | TAttr Attr
- | TCUDAdevice !SrcLoc
- | TCUDAglobal !SrcLoc
- | TCUDAhost !SrcLoc
- | TCUDAconstant !SrcLoc
- | TCUDAshared !SrcLoc
- | TCUDArestrict !SrcLoc
- | TCUDAnoinline !SrcLoc
- | TCLprivate !SrcLoc
- | TCLlocal !SrcLoc
- | TCLglobal !SrcLoc
- | TCLconstant !SrcLoc
- | TCLreadonly !SrcLoc
- | TCLwriteonly !SrcLoc
- | TCLkernel !SrcLoc
- data Sign
- data TypeSpec
- = Tvoid !SrcLoc
- | Tchar (Maybe Sign) !SrcLoc
- | Tshort (Maybe Sign) !SrcLoc
- | Tint (Maybe Sign) !SrcLoc
- | Tlong (Maybe Sign) !SrcLoc
- | Tlong_long (Maybe Sign) !SrcLoc
- | Tfloat !SrcLoc
- | Tdouble !SrcLoc
- | Tlong_double !SrcLoc
- | Tstruct (Maybe Id) (Maybe [FieldGroup]) [Attr] !SrcLoc
- | Tunion (Maybe Id) (Maybe [FieldGroup]) [Attr] !SrcLoc
- | Tenum (Maybe Id) [CEnum] [Attr] !SrcLoc
- | Tnamed Id [Id] !SrcLoc
- | T_Bool !SrcLoc
- | Tfloat_Complex !SrcLoc
- | Tdouble_Complex !SrcLoc
- | Tlong_double_Complex !SrcLoc
- | Tfloat_Imaginary !SrcLoc
- | Tdouble_Imaginary !SrcLoc
- | Tlong_double_Imaginary !SrcLoc
- | TtypeofExp Exp !SrcLoc
- | TtypeofType Type !SrcLoc
- | Tva_list !SrcLoc
- data DeclSpec
- data ArraySize
- data Decl
- data Type
- data Designator
- data Designation = Designation [Designator] !SrcLoc
- data Initializer
- type AsmLabel = StringLit
- data Init = Init Id Decl (Maybe AsmLabel) (Maybe Initializer) [Attr] !SrcLoc
- data Typedef = Typedef Id Decl [Attr] !SrcLoc
- data InitGroup
- data Field = Field (Maybe Id) (Maybe Decl) (Maybe Exp) !SrcLoc
- data FieldGroup
- = FieldGroup DeclSpec [Field] !SrcLoc
- | AntiSdecl String !SrcLoc
- | AntiSdecls String !SrcLoc
- data CEnum
- data Attr = Attr Id [Exp] !SrcLoc
- data Param
- data Params = Params [Param] Bool !SrcLoc
- data Func
- data Definition
- = FuncDef Func !SrcLoc
- | DecDef InitGroup !SrcLoc
- | EscDef String !SrcLoc
- | AntiFunc String !SrcLoc
- | AntiEsc String !SrcLoc
- | AntiEdecl String !SrcLoc
- | AntiEdecls String !SrcLoc
- | ObjCClassDec [Id] !SrcLoc
- | ObjCClassIface Id (Maybe Id) [Id] [ObjCIvarDecl] [ObjCIfaceDecl] [Attr] !SrcLoc
- | ObjCCatIface Id (Maybe Id) [Id] [ObjCIvarDecl] [ObjCIfaceDecl] !SrcLoc
- | ObjCProtDec [Id] !SrcLoc
- | ObjCProtDef Id [Id] [ObjCIfaceDecl] !SrcLoc
- | ObjCClassImpl Id (Maybe Id) [ObjCIvarDecl] [Definition] !SrcLoc
- | ObjCCatImpl Id Id [Definition] !SrcLoc
- | ObjCSynDef [(Id, Maybe Id)] !SrcLoc
- | ObjCDynDef [Id] !SrcLoc
- | ObjCMethDef ObjCMethodProto [BlockItem] !SrcLoc
- | ObjCCompAlias Id Id !SrcLoc
- | AntiObjCMeth String !SrcLoc
- | AntiObjCMeths String !SrcLoc
- data Stm
- = Label Id [Attr] Stm !SrcLoc
- | Case Exp Stm !SrcLoc
- | Default Stm !SrcLoc
- | Exp (Maybe Exp) !SrcLoc
- | Block [BlockItem] !SrcLoc
- | If Exp Stm (Maybe Stm) !SrcLoc
- | Switch Exp Stm !SrcLoc
- | While Exp Stm !SrcLoc
- | DoWhile Stm Exp !SrcLoc
- | For (Either InitGroup (Maybe Exp)) (Maybe Exp) (Maybe Exp) Stm !SrcLoc
- | Goto Id !SrcLoc
- | Continue !SrcLoc
- | Break !SrcLoc
- | Return (Maybe Exp) !SrcLoc
- | Pragma String !SrcLoc
- | Comment String Stm !SrcLoc
- | EscStm String !SrcLoc
- | AntiEscStm String !SrcLoc
- | AntiPragma String !SrcLoc
- | AntiComment String Stm !SrcLoc
- | AntiStm String !SrcLoc
- | AntiStms String !SrcLoc
- | Asm Bool [Attr] AsmTemplate [AsmOut] [AsmIn] [AsmClobber] !SrcLoc
- | AsmGoto Bool [Attr] AsmTemplate [AsmIn] [AsmClobber] [Id] !SrcLoc
- | ObjCTry [BlockItem] [ObjCCatch] (Maybe [BlockItem]) !SrcLoc
- | ObjCThrow (Maybe Exp) !SrcLoc
- | ObjCSynchronized Exp [BlockItem] !SrcLoc
- | ObjCAutoreleasepool [BlockItem] !SrcLoc
- data BlockItem
- data Signed
- data Const
- = IntConst String Signed Integer !SrcLoc
- | LongIntConst String Signed Integer !SrcLoc
- | LongLongIntConst String Signed Integer !SrcLoc
- | FloatConst String Float !SrcLoc
- | DoubleConst String Double !SrcLoc
- | LongDoubleConst String Double !SrcLoc
- | CharConst String Char !SrcLoc
- | StringConst [String] String !SrcLoc
- | AntiConst String !SrcLoc
- | AntiInt String !SrcLoc
- | AntiUInt String !SrcLoc
- | AntiLInt String !SrcLoc
- | AntiULInt String !SrcLoc
- | AntiLLInt String !SrcLoc
- | AntiULLInt String !SrcLoc
- | AntiFloat String !SrcLoc
- | AntiDouble String !SrcLoc
- | AntiLongDouble String !SrcLoc
- | AntiChar String !SrcLoc
- | AntiString String !SrcLoc
- data Exp
- = Var Id !SrcLoc
- | Const Const !SrcLoc
- | BinOp BinOp Exp Exp !SrcLoc
- | Assign Exp AssignOp Exp !SrcLoc
- | PreInc Exp !SrcLoc
- | PostInc Exp !SrcLoc
- | PreDec Exp !SrcLoc
- | PostDec Exp !SrcLoc
- | UnOp UnOp Exp !SrcLoc
- | SizeofExp Exp !SrcLoc
- | SizeofType Type !SrcLoc
- | Cast Type Exp !SrcLoc
- | Cond Exp Exp Exp !SrcLoc
- | Member Exp Id !SrcLoc
- | PtrMember Exp Id !SrcLoc
- | Index Exp Exp !SrcLoc
- | FnCall Exp [Exp] !SrcLoc
- | CudaCall Exp ExeConfig [Exp] !SrcLoc
- | Seq Exp Exp !SrcLoc
- | CompoundLit Type [(Maybe Designation, Initializer)] !SrcLoc
- | StmExpr [BlockItem] !SrcLoc
- | EscExp String !SrcLoc
- | AntiEscExp String !SrcLoc
- | AntiExp String !SrcLoc
- | AntiArgs String !SrcLoc
- | BuiltinVaArg Exp Type !SrcLoc
- | BlockLit BlockType [Attr] [BlockItem] !SrcLoc
- | ObjCMsg ObjCRecv [ObjCArg] [Exp] !SrcLoc
- | ObjCLitConst (Maybe UnOp) Const !SrcLoc
- | ObjCLitString [Const] !SrcLoc
- | ObjCLitBool Bool !SrcLoc
- | ObjCLitArray [Exp] !SrcLoc
- | ObjCLitDict [ObjCDictElem] !SrcLoc
- | ObjCLitBoxed Exp !SrcLoc
- | ObjCEncode Type !SrcLoc
- | ObjCProtocol Id !SrcLoc
- | ObjCSelector String !SrcLoc
- | Lambda LambdaIntroducer (Maybe LambdaDeclarator) [BlockItem] !SrcLoc
- data BinOp
- data AssignOp
- data UnOp
- type AsmTemplate = StringLit
- data AsmOut = AsmOut (Maybe Id) String Id
- data AsmIn = AsmIn (Maybe Id) String Exp
- type AsmClobber = String
- data BlockType
- data ObjCIvarDecl
- data ObjCVisibilitySpec
- data ObjCIfaceDecl
- data ObjCPropAttr
- = ObjCGetter Id !SrcLoc
- | ObjCSetter Id !SrcLoc
- | ObjCReadonly !SrcLoc
- | ObjCReadwrite !SrcLoc
- | ObjCAssign !SrcLoc
- | ObjCRetain !SrcLoc
- | ObjCCopy !SrcLoc
- | ObjCNonatomic !SrcLoc
- | ObjCAtomic !SrcLoc
- | ObjCStrong !SrcLoc
- | ObjCWeak !SrcLoc
- | ObjCUnsafeUnretained !SrcLoc
- | AntiObjCAttr String !SrcLoc
- | AntiObjCAttrs String !SrcLoc
- data ObjCMethodReq
- data ObjCParam
- data ObjCMethodProto
- data ObjCCatch = ObjCCatch (Maybe Param) [BlockItem] !SrcLoc
- data ObjCDictElem
- data ObjCRecv
- data ObjCArg
- data LambdaIntroducer = LambdaIntroducer [CaptureListEntry] !SrcLoc
- data LambdaDeclarator = LambdaDeclarator Params Bool (Maybe Type) !SrcLoc
- data CaptureListEntry
- data ExeConfig = ExeConfig {
- exeGridDim :: Exp
- exeBlockDim :: Exp
- exeSharedSize :: Maybe Exp
- exeStream :: Maybe Exp
- exeLoc :: !SrcLoc
- funcProto :: Func -> InitGroup
- isPtr :: Type -> Bool
- ctypedef :: Id -> Decl -> [Attr] -> Typedef
- cdeclSpec :: [Storage] -> [TypeQual] -> TypeSpec -> DeclSpec
- cinitGroup :: DeclSpec -> [Attr] -> [Init] -> InitGroup
- ctypedefGroup :: DeclSpec -> [Attr] -> [Typedef] -> InitGroup
Documentation
data Extensions Source #
Tvoid !SrcLoc | |
Tchar (Maybe Sign) !SrcLoc | |
Tshort (Maybe Sign) !SrcLoc | |
Tint (Maybe Sign) !SrcLoc | |
Tlong (Maybe Sign) !SrcLoc | |
Tlong_long (Maybe Sign) !SrcLoc | |
Tfloat !SrcLoc | |
Tdouble !SrcLoc | |
Tlong_double !SrcLoc | |
Tstruct (Maybe Id) (Maybe [FieldGroup]) [Attr] !SrcLoc | |
Tunion (Maybe Id) (Maybe [FieldGroup]) [Attr] !SrcLoc | |
Tenum (Maybe Id) [CEnum] [Attr] !SrcLoc | |
Tnamed Id [Id] !SrcLoc | |
T_Bool !SrcLoc | |
Tfloat_Complex !SrcLoc | |
Tdouble_Complex !SrcLoc | |
Tlong_double_Complex !SrcLoc | |
Tfloat_Imaginary !SrcLoc | |
Tdouble_Imaginary !SrcLoc | |
Tlong_double_Imaginary !SrcLoc | |
TtypeofExp Exp !SrcLoc | |
TtypeofType Type !SrcLoc | |
Tva_list !SrcLoc |
There are two types of declarators in C, regular declarators and abstract
declarators. The former is for declaring variables, function parameters,
typedefs, etc. and the latter for abstract types---typedef int
({*}foo)(void)
vs. tt int ({*})(void)
. The difference between the two is
just whether or not an identifier is attached to the declarator. We therefore
only define one Decl
type and use it for both cases.
data Designator Source #
data Designation Source #
data Initializer Source #
data FieldGroup Source #
data Definition Source #
FuncDef Func !SrcLoc | |
DecDef InitGroup !SrcLoc | |
EscDef String !SrcLoc | |
AntiFunc String !SrcLoc | |
AntiEsc String !SrcLoc | |
AntiEdecl String !SrcLoc | |
AntiEdecls String !SrcLoc | |
ObjCClassDec [Id] !SrcLoc | |
ObjCClassIface Id (Maybe Id) [Id] [ObjCIvarDecl] [ObjCIfaceDecl] [Attr] !SrcLoc | |
ObjCCatIface Id (Maybe Id) [Id] [ObjCIvarDecl] [ObjCIfaceDecl] !SrcLoc | |
ObjCProtDec [Id] !SrcLoc | |
ObjCProtDef Id [Id] [ObjCIfaceDecl] !SrcLoc | |
ObjCClassImpl Id (Maybe Id) [ObjCIvarDecl] [Definition] !SrcLoc | |
ObjCCatImpl Id Id [Definition] !SrcLoc | |
ObjCSynDef [(Id, Maybe Id)] !SrcLoc | |
ObjCDynDef [Id] !SrcLoc | |
ObjCMethDef ObjCMethodProto [BlockItem] !SrcLoc | |
ObjCCompAlias Id Id !SrcLoc | |
AntiObjCMeth String !SrcLoc | |
AntiObjCMeths String !SrcLoc |
Label Id [Attr] Stm !SrcLoc | |
Case Exp Stm !SrcLoc | |
Default Stm !SrcLoc | |
Exp (Maybe Exp) !SrcLoc | |
Block [BlockItem] !SrcLoc | |
If Exp Stm (Maybe Stm) !SrcLoc | |
Switch Exp Stm !SrcLoc | |
While Exp Stm !SrcLoc | |
DoWhile Stm Exp !SrcLoc | |
For (Either InitGroup (Maybe Exp)) (Maybe Exp) (Maybe Exp) Stm !SrcLoc | |
Goto Id !SrcLoc | |
Continue !SrcLoc | |
Break !SrcLoc | |
Return (Maybe Exp) !SrcLoc | |
Pragma String !SrcLoc | |
Comment String Stm !SrcLoc | |
EscStm String !SrcLoc | |
AntiEscStm String !SrcLoc | |
AntiPragma String !SrcLoc | |
AntiComment String Stm !SrcLoc | |
AntiStm String !SrcLoc | |
AntiStms String !SrcLoc | |
Asm Bool [Attr] AsmTemplate [AsmOut] [AsmIn] [AsmClobber] !SrcLoc | |
AsmGoto Bool [Attr] AsmTemplate [AsmIn] [AsmClobber] [Id] !SrcLoc | |
ObjCTry [BlockItem] [ObjCCatch] (Maybe [BlockItem]) !SrcLoc | Invariant: There is either at least one |
ObjCThrow (Maybe Exp) !SrcLoc | |
ObjCSynchronized Exp [BlockItem] !SrcLoc | |
ObjCAutoreleasepool [BlockItem] !SrcLoc |
The String
parameter to Const
data constructors is the raw string
representation of the constant as it was parsed.
type AsmTemplate = StringLit Source #
type AsmClobber = String Source #
data ObjCIvarDecl Source #
data ObjCVisibilitySpec Source #
data ObjCIfaceDecl Source #
data ObjCPropAttr Source #
data ObjCMethodReq Source #
data ObjCMethodProto Source #
data ObjCDictElem Source #
data LambdaIntroducer Source #
data LambdaDeclarator Source #
data CaptureListEntry Source #
ExeConfig | |
|