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 | Safe-Inferred |
Language | Haskell2010 |
Language.C.Syntax
Description
Synopsis
- 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
- 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
- | CaseRange Exp 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 #
Instances
Instances
Data Id Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Id -> c Id Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Id Source # toConstr :: Id -> Constr Source # dataTypeOf :: Id -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Id) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Id) Source # gmapT :: (forall b. Data b => b -> b) -> Id -> Id Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Id -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Id -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Id -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Id -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Id -> m Id Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Id -> m Id Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Id -> m Id Source # | |
IsString Id Source # | |
Defined in Language.C.Syntax Methods fromString :: String -> Id Source # | |
Show Id Source # | |
Eq Id Source # | |
Ord Id Source # | |
ToIdent Id Source # | |
Pretty Id Source # | |
Located Id Source # | |
Relocatable Id Source # | |
ToIdent (SrcLoc -> Id) Source # | |
Instances
Data StringLit Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StringLit -> c StringLit Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StringLit Source # toConstr :: StringLit -> Constr Source # dataTypeOf :: StringLit -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StringLit) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StringLit) Source # gmapT :: (forall b. Data b => b -> b) -> StringLit -> StringLit Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StringLit -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StringLit -> r Source # gmapQ :: (forall d. Data d => d -> u) -> StringLit -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> StringLit -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StringLit -> m StringLit Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StringLit -> m StringLit Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StringLit -> m StringLit Source # | |
IsString StringLit Source # | |
Defined in Language.C.Syntax Methods fromString :: String -> StringLit Source # | |
Show StringLit Source # | |
Eq StringLit Source # | |
Ord StringLit Source # | |
Defined in Language.C.Syntax | |
Pretty StringLit Source # | |
Located StringLit Source # | |
Relocatable StringLit Source # | |
Constructors
Tauto !SrcLoc | |
Tregister !SrcLoc | |
Tstatic !SrcLoc | |
Textern (Maybe Linkage) !SrcLoc | |
Ttypedef !SrcLoc | |
T__block !SrcLoc | |
TObjC__weak !SrcLoc | |
TObjC__strong !SrcLoc | |
TObjC__unsafe_unretained !SrcLoc |
Instances
Data Storage Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Storage -> c Storage Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Storage Source # toConstr :: Storage -> Constr Source # dataTypeOf :: Storage -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Storage) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Storage) Source # gmapT :: (forall b. Data b => b -> b) -> Storage -> Storage Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Storage -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Storage -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Storage -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Storage -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Storage -> m Storage Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Storage -> m Storage Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Storage -> m Storage Source # | |
Show Storage Source # | |
Eq Storage Source # | |
Ord Storage Source # | |
Defined in Language.C.Syntax | |
Pretty Storage Source # | |
Located Storage Source # | |
Relocatable Storage Source # | |
Constructors
Instances
Data TypeQual Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeQual -> c TypeQual Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeQual Source # toConstr :: TypeQual -> Constr Source # dataTypeOf :: TypeQual -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeQual) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeQual) Source # gmapT :: (forall b. Data b => b -> b) -> TypeQual -> TypeQual Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeQual -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeQual -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TypeQual -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeQual -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeQual -> m TypeQual Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeQual -> m TypeQual Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeQual -> m TypeQual Source # | |
Show TypeQual Source # | |
Eq TypeQual Source # | |
Ord TypeQual Source # | |
Defined in Language.C.Syntax | |
Pretty TypeQual Source # | |
Located TypeQual Source # | |
Relocatable TypeQual Source # | |
Instances
Data Sign Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sign -> c Sign Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Sign Source # toConstr :: Sign -> Constr Source # dataTypeOf :: Sign -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Sign) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sign) Source # gmapT :: (forall b. Data b => b -> b) -> Sign -> Sign Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sign -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sign -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Sign -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sign -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sign -> m Sign Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sign -> m Sign Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sign -> m Sign Source # | |
Show Sign Source # | |
Eq Sign Source # | |
Ord Sign Source # | |
Pretty Sign Source # | |
Located Sign Source # | |
Relocatable Sign Source # | |
Constructors
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 |
Instances
Data TypeSpec Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeSpec -> c TypeSpec Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeSpec Source # toConstr :: TypeSpec -> Constr Source # dataTypeOf :: TypeSpec -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeSpec) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeSpec) Source # gmapT :: (forall b. Data b => b -> b) -> TypeSpec -> TypeSpec Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeSpec -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeSpec -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TypeSpec -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeSpec -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeSpec -> m TypeSpec Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeSpec -> m TypeSpec Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeSpec -> m TypeSpec Source # | |
Show TypeSpec Source # | |
Eq TypeSpec Source # | |
Ord TypeSpec Source # | |
Defined in Language.C.Syntax | |
Pretty TypeSpec Source # | |
Located TypeSpec Source # | |
Relocatable TypeSpec Source # | |
Constructors
DeclSpec [Storage] [TypeQual] TypeSpec !SrcLoc | |
AntiDeclSpec String !SrcLoc | |
AntiTypeDeclSpec [Storage] [TypeQual] String !SrcLoc |
Instances
Data DeclSpec Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeclSpec -> c DeclSpec Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeclSpec Source # toConstr :: DeclSpec -> Constr Source # dataTypeOf :: DeclSpec -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DeclSpec) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeclSpec) Source # gmapT :: (forall b. Data b => b -> b) -> DeclSpec -> DeclSpec Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeclSpec -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeclSpec -> r Source # gmapQ :: (forall d. Data d => d -> u) -> DeclSpec -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> DeclSpec -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeclSpec -> m DeclSpec Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeclSpec -> m DeclSpec Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeclSpec -> m DeclSpec Source # | |
Show DeclSpec Source # | |
Eq DeclSpec Source # | |
Ord DeclSpec Source # | |
Defined in Language.C.Syntax | |
Pretty DeclSpec Source # | |
Located DeclSpec Source # | |
Relocatable DeclSpec Source # | |
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.
Constructors
ArraySize Bool Exp !SrcLoc | |
VariableArraySize !SrcLoc | |
NoArraySize !SrcLoc |
Instances
Data ArraySize Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArraySize -> c ArraySize Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArraySize Source # toConstr :: ArraySize -> Constr Source # dataTypeOf :: ArraySize -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ArraySize) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArraySize) Source # gmapT :: (forall b. Data b => b -> b) -> ArraySize -> ArraySize Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArraySize -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArraySize -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ArraySize -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArraySize -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArraySize -> m ArraySize Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArraySize -> m ArraySize Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArraySize -> m ArraySize Source # | |
Show ArraySize Source # | |
Eq ArraySize Source # | |
Ord ArraySize Source # | |
Defined in Language.C.Syntax | |
Pretty ArraySize Source # | |
Located ArraySize Source # | |
Relocatable ArraySize Source # | |
Constructors
DeclRoot !SrcLoc | |
Ptr [TypeQual] Decl !SrcLoc | |
Array [TypeQual] ArraySize Decl !SrcLoc | |
Proto Decl Params !SrcLoc | |
OldProto Decl [Id] !SrcLoc | |
AntiTypeDecl String !SrcLoc | |
BlockPtr [TypeQual] Decl !SrcLoc |
Instances
Data Decl Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Decl -> c Decl Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Decl Source # toConstr :: Decl -> Constr Source # dataTypeOf :: Decl -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Decl) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Decl) Source # gmapT :: (forall b. Data b => b -> b) -> Decl -> Decl Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Decl -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Decl -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Decl -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Decl -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Decl -> m Decl Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Decl -> m Decl Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Decl -> m Decl Source # | |
Show Decl Source # | |
Eq Decl Source # | |
Ord Decl Source # | |
Located Decl Source # | |
Relocatable Decl Source # | |
Instances
Data Type Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Type -> c Type Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Type Source # toConstr :: Type -> Constr Source # dataTypeOf :: Type -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Type) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Type) Source # gmapT :: (forall b. Data b => b -> b) -> Type -> Type Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Type -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Type -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Type -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Type -> m Type Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Type -> m Type Source # | |
Show Type Source # | |
Eq Type Source # | |
Ord Type Source # | |
Pretty Type Source # | |
Located Type Source # | |
Relocatable Type Source # | |
data Designator Source #
Constructors
IndexDesignator Exp !SrcLoc | |
MemberDesignator Id !SrcLoc |
Instances
data Designation Source #
Constructors
Designation [Designator] !SrcLoc |
Instances
data Initializer Source #
Constructors
ExpInitializer Exp !SrcLoc | |
CompoundInitializer [(Maybe Designation, Initializer)] !SrcLoc | |
AntiInit String !SrcLoc | |
AntiInits String !SrcLoc |
Instances
Instances
Data Init Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Init -> c Init Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Init Source # toConstr :: Init -> Constr Source # dataTypeOf :: Init -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Init) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Init) Source # gmapT :: (forall b. Data b => b -> b) -> Init -> Init Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Init -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Init -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Init -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Init -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Init -> m Init Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Init -> m Init Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Init -> m Init Source # | |
Show Init Source # | |
Eq Init Source # | |
Ord Init Source # | |
Pretty Init Source # | |
Located Init Source # | |
Relocatable Init Source # | |
Instances
Data Typedef Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Typedef -> c Typedef Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Typedef Source # toConstr :: Typedef -> Constr Source # dataTypeOf :: Typedef -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Typedef) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Typedef) Source # gmapT :: (forall b. Data b => b -> b) -> Typedef -> Typedef Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Typedef -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Typedef -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Typedef -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Typedef -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Typedef -> m Typedef Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Typedef -> m Typedef Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Typedef -> m Typedef Source # | |
Show Typedef Source # | |
Eq Typedef Source # | |
Ord Typedef Source # | |
Defined in Language.C.Syntax | |
Pretty Typedef Source # | |
Located Typedef Source # | |
Relocatable Typedef Source # | |
Constructors
InitGroup DeclSpec [Attr] [Init] !SrcLoc | |
TypedefGroup DeclSpec [Attr] [Typedef] !SrcLoc | |
AntiDecl String !SrcLoc | |
AntiDecls String !SrcLoc |
Instances
Data InitGroup Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InitGroup -> c InitGroup Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InitGroup Source # toConstr :: InitGroup -> Constr Source # dataTypeOf :: InitGroup -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InitGroup) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InitGroup) Source # gmapT :: (forall b. Data b => b -> b) -> InitGroup -> InitGroup Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InitGroup -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InitGroup -> r Source # gmapQ :: (forall d. Data d => d -> u) -> InitGroup -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> InitGroup -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InitGroup -> m InitGroup Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InitGroup -> m InitGroup Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InitGroup -> m InitGroup Source # | |
Show InitGroup Source # | |
Eq InitGroup Source # | |
Ord InitGroup Source # | |
Defined in Language.C.Syntax | |
Pretty InitGroup Source # | |
Located InitGroup Source # | |
Relocatable InitGroup Source # | |
Instances
Data Field Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Field -> c Field Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Field Source # toConstr :: Field -> Constr Source # dataTypeOf :: Field -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Field) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Field) Source # gmapT :: (forall b. Data b => b -> b) -> Field -> Field Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Field -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Field -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Field -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Field -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Field -> m Field Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Field -> m Field Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Field -> m Field Source # | |
Show Field Source # | |
Eq Field Source # | |
Ord Field Source # | |
Defined in Language.C.Syntax | |
Pretty Field Source # | |
Located Field Source # | |
Relocatable Field Source # | |
data FieldGroup Source #
Constructors
FieldGroup DeclSpec [Field] !SrcLoc | |
AntiSdecl String !SrcLoc | |
AntiSdecls String !SrcLoc |
Instances
Instances
Data CEnum Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CEnum -> c CEnum Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CEnum Source # toConstr :: CEnum -> Constr Source # dataTypeOf :: CEnum -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CEnum) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CEnum) Source # gmapT :: (forall b. Data b => b -> b) -> CEnum -> CEnum Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CEnum -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CEnum -> r Source # gmapQ :: (forall d. Data d => d -> u) -> CEnum -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> CEnum -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CEnum -> m CEnum Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CEnum -> m CEnum Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CEnum -> m CEnum Source # | |
Show CEnum Source # | |
Eq CEnum Source # | |
Ord CEnum Source # | |
Defined in Language.C.Syntax | |
Pretty CEnum Source # | |
Located CEnum Source # | |
Relocatable CEnum Source # | |
Instances
Data Attr Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Attr -> c Attr Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Attr Source # toConstr :: Attr -> Constr Source # dataTypeOf :: Attr -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Attr) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Attr) Source # gmapT :: (forall b. Data b => b -> b) -> Attr -> Attr Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Attr -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Attr -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Attr -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Attr -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Attr -> m Attr Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Attr -> m Attr Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Attr -> m Attr Source # | |
Show Attr Source # | |
Eq Attr Source # | |
Ord Attr Source # | |
Pretty Attr Source # | |
Located Attr Source # | |
Relocatable Attr Source # | |
Constructors
Param (Maybe Id) DeclSpec Decl !SrcLoc | |
AntiParam String !SrcLoc | |
AntiParams String !SrcLoc |
Instances
Data Param Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Param -> c Param Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Param Source # toConstr :: Param -> Constr Source # dataTypeOf :: Param -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Param) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Param) Source # gmapT :: (forall b. Data b => b -> b) -> Param -> Param Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Param -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Param -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Param -> m Param Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Param -> m Param Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Param -> m Param Source # | |
Show Param Source # | |
Eq Param Source # | |
Ord Param Source # | |
Defined in Language.C.Syntax | |
Pretty Param Source # | |
Located Param Source # | |
Relocatable Param Source # | |
Instances
Data Params Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Params -> c Params Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Params Source # toConstr :: Params -> Constr Source # dataTypeOf :: Params -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Params) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Params) Source # gmapT :: (forall b. Data b => b -> b) -> Params -> Params Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Params -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Params -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Params -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Params -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Params -> m Params Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Params -> m Params Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Params -> m Params Source # | |
Show Params Source # | |
Eq Params Source # | |
Ord Params Source # | |
Pretty Params Source # | |
Located Params Source # | |
Relocatable Params Source # | |
Constructors
Func DeclSpec Id Decl Params [BlockItem] !SrcLoc | |
OldFunc DeclSpec Id Decl [Id] (Maybe [InitGroup]) [BlockItem] !SrcLoc |
Instances
Data Func Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Func -> c Func Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Func Source # toConstr :: Func -> Constr Source # dataTypeOf :: Func -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Func) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Func) Source # gmapT :: (forall b. Data b => b -> b) -> Func -> Func Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Func -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Func -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Func -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Func -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Func -> m Func Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Func -> m Func Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Func -> m Func Source # | |
Show Func Source # | |
Eq Func Source # | |
Ord Func Source # | |
Pretty Func Source # | |
Located Func Source # | |
Relocatable Func Source # | |
data Definition Source #
Constructors
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 |
Instances
Constructors
Label Id [Attr] Stm !SrcLoc | |
Case Exp Stm !SrcLoc | |
CaseRange Exp 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 |
Instances
Data Stm Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Stm -> c Stm Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Stm Source # toConstr :: Stm -> Constr Source # dataTypeOf :: Stm -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Stm) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Stm) Source # gmapT :: (forall b. Data b => b -> b) -> Stm -> Stm Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stm -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stm -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Stm -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Stm -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stm -> m Stm Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stm -> m Stm Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stm -> m Stm Source # | |
Show Stm Source # | |
Eq Stm Source # | |
Ord Stm Source # | |
Pretty Stm Source # | |
Located Stm Source # | |
Relocatable Stm Source # | |
Constructors
BlockDecl InitGroup | |
BlockStm Stm | |
AntiBlockItem String !SrcLoc | |
AntiBlockItems String !SrcLoc |
Instances
Data BlockItem Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BlockItem -> c BlockItem Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BlockItem Source # toConstr :: BlockItem -> Constr Source # dataTypeOf :: BlockItem -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BlockItem) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BlockItem) Source # gmapT :: (forall b. Data b => b -> b) -> BlockItem -> BlockItem Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BlockItem -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BlockItem -> r Source # gmapQ :: (forall d. Data d => d -> u) -> BlockItem -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> BlockItem -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BlockItem -> m BlockItem Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockItem -> m BlockItem Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockItem -> m BlockItem Source # | |
Show BlockItem Source # | |
Eq BlockItem Source # | |
Ord BlockItem Source # | |
Defined in Language.C.Syntax | |
Pretty BlockItem Source # | |
Located BlockItem Source # | |
Relocatable BlockItem Source # | |
Instances
Data Signed Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Signed -> c Signed Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Signed Source # toConstr :: Signed -> Constr Source # dataTypeOf :: Signed -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Signed) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Signed) Source # gmapT :: (forall b. Data b => b -> b) -> Signed -> Signed Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Signed -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Signed -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Signed -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Signed -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Signed -> m Signed Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Signed -> m Signed Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Signed -> m Signed Source # | |
Show Signed Source # | |
Eq Signed Source # | |
Ord Signed Source # | |
The String
parameter to Const
data constructors is the raw string
representation of the constant as it was parsed.
Constructors
Instances
Data Const Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Const -> c Const Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Const Source # toConstr :: Const -> Constr Source # dataTypeOf :: Const -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Const) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Const) Source # gmapT :: (forall b. Data b => b -> b) -> Const -> Const Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Const -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Const -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Const -> m Const Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Const -> m Const Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Const -> m Const Source # | |
Show Const Source # | |
Eq Const Source # | |
Ord Const Source # | |
Defined in Language.C.Syntax | |
ToConst Const Source # | |
Pretty Const Source # | |
Located Const Source # | |
Relocatable Const Source # | |
Constructors
Instances
Data Exp Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Exp -> c Exp Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Exp Source # toConstr :: Exp -> Constr Source # dataTypeOf :: Exp -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Exp) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp) Source # gmapT :: (forall b. Data b => b -> b) -> Exp -> Exp Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Exp -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Exp -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Exp -> m Exp Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp Source # | |
Enum Exp Source # | |
Defined in Language.C.Smart | |
Floating Exp Source # | |
Num Exp Source # | |
Fractional Exp Source # | |
Integral Exp Source # | |
Real Exp Source # | |
Defined in Language.C.Smart Methods toRational :: Exp -> Rational Source # | |
Show Exp Source # | |
Eq Exp Source # | |
Ord Exp Source # | |
ToExp Exp Source # | |
Pretty Exp Source # | |
Located Exp Source # | |
Relocatable Exp Source # | |
Instances
Data BinOp Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BinOp -> c BinOp Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BinOp Source # toConstr :: BinOp -> Constr Source # dataTypeOf :: BinOp -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BinOp) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BinOp) Source # gmapT :: (forall b. Data b => b -> b) -> BinOp -> BinOp Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BinOp -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BinOp -> r Source # gmapQ :: (forall d. Data d => d -> u) -> BinOp -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> BinOp -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp Source # | |
Show BinOp Source # | |
Eq BinOp Source # | |
Ord BinOp Source # | |
Defined in Language.C.Syntax | |
CFixity BinOp Source # | |
Pretty BinOp Source # | |
Constructors
JustAssign | |
AddAssign | |
SubAssign | |
MulAssign | |
DivAssign | |
ModAssign | |
LshAssign | |
RshAssign | |
AndAssign | |
XorAssign | |
OrAssign |
Instances
Data AssignOp Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AssignOp -> c AssignOp Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AssignOp Source # toConstr :: AssignOp -> Constr Source # dataTypeOf :: AssignOp -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AssignOp) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AssignOp) Source # gmapT :: (forall b. Data b => b -> b) -> AssignOp -> AssignOp Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AssignOp -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AssignOp -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AssignOp -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AssignOp -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AssignOp -> m AssignOp Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AssignOp -> m AssignOp Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AssignOp -> m AssignOp Source # | |
Show AssignOp Source # | |
Eq AssignOp Source # | |
Ord AssignOp Source # | |
Defined in Language.C.Syntax | |
CFixity AssignOp Source # | |
Pretty AssignOp Source # | |
Instances
Data UnOp Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnOp -> c UnOp Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnOp Source # toConstr :: UnOp -> Constr Source # dataTypeOf :: UnOp -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnOp) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnOp) Source # gmapT :: (forall b. Data b => b -> b) -> UnOp -> UnOp Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnOp -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnOp -> r Source # gmapQ :: (forall d. Data d => d -> u) -> UnOp -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> UnOp -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnOp -> m UnOp Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnOp -> m UnOp Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnOp -> m UnOp Source # | |
Show UnOp Source # | |
Eq UnOp Source # | |
Ord UnOp Source # | |
CFixity UnOp Source # | |
Pretty UnOp Source # | |
type AsmTemplate = StringLit Source #
Instances
Data AsmOut Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AsmOut -> c AsmOut Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AsmOut Source # toConstr :: AsmOut -> Constr Source # dataTypeOf :: AsmOut -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AsmOut) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AsmOut) Source # gmapT :: (forall b. Data b => b -> b) -> AsmOut -> AsmOut Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AsmOut -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AsmOut -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AsmOut -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AsmOut -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AsmOut -> m AsmOut Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AsmOut -> m AsmOut Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AsmOut -> m AsmOut Source # | |
Show AsmOut Source # | |
Eq AsmOut Source # | |
Ord AsmOut Source # | |
Pretty AsmOut Source # | |
Instances
Data AsmIn Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AsmIn -> c AsmIn Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AsmIn Source # toConstr :: AsmIn -> Constr Source # dataTypeOf :: AsmIn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AsmIn) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AsmIn) Source # gmapT :: (forall b. Data b => b -> b) -> AsmIn -> AsmIn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AsmIn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AsmIn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> AsmIn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> AsmIn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AsmIn -> m AsmIn Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AsmIn -> m AsmIn Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AsmIn -> m AsmIn Source # | |
Show AsmIn Source # | |
Eq AsmIn Source # | |
Ord AsmIn Source # | |
Defined in Language.C.Syntax | |
Pretty AsmIn Source # | |
type AsmClobber = String Source #
Instances
Data BlockType Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BlockType -> c BlockType Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BlockType Source # toConstr :: BlockType -> Constr Source # dataTypeOf :: BlockType -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BlockType) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BlockType) Source # gmapT :: (forall b. Data b => b -> b) -> BlockType -> BlockType Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BlockType -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BlockType -> r Source # gmapQ :: (forall d. Data d => d -> u) -> BlockType -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> BlockType -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BlockType -> m BlockType Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockType -> m BlockType Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockType -> m BlockType Source # | |
Show BlockType Source # | |
Eq BlockType Source # | |
Ord BlockType Source # | |
Defined in Language.C.Syntax | |
Pretty BlockType Source # | |
Located BlockType Source # | |
Relocatable BlockType Source # | |
data ObjCIvarDecl Source #
Constructors
ObjCIvarVisi ObjCVisibilitySpec !SrcLoc | |
ObjCIvarDecl FieldGroup !SrcLoc |
Instances
data ObjCVisibilitySpec Source #
Constructors
ObjCPrivate !SrcLoc | |
ObjCPublic !SrcLoc | |
ObjCProtected !SrcLoc | |
ObjCPackage !SrcLoc |
Instances
data ObjCIfaceDecl Source #
Constructors
Instances
data ObjCPropAttr Source #
Constructors
Instances
data ObjCMethodReq Source #
Constructors
ObjCRequired !SrcLoc | |
ObjCOptional !SrcLoc |
Instances
Constructors
ObjCParam (Maybe Id) (Maybe Type) [Attr] (Maybe Id) !SrcLoc | |
AntiObjCParam String !SrcLoc | |
AntiObjCParams String !SrcLoc |
Instances
Data ObjCParam Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjCParam -> c ObjCParam Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjCParam Source # toConstr :: ObjCParam -> Constr Source # dataTypeOf :: ObjCParam -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjCParam) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjCParam) Source # gmapT :: (forall b. Data b => b -> b) -> ObjCParam -> ObjCParam Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjCParam -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjCParam -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ObjCParam -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjCParam -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjCParam -> m ObjCParam Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCParam -> m ObjCParam Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCParam -> m ObjCParam Source # | |
Show ObjCParam Source # | |
Eq ObjCParam Source # | |
Ord ObjCParam Source # | |
Defined in Language.C.Syntax | |
Pretty ObjCParam Source # | |
Located ObjCParam Source # | |
Relocatable ObjCParam Source # | |
data ObjCMethodProto Source #
Constructors
ObjCMethodProto Bool (Maybe Type) [Attr] [ObjCParam] Bool [Attr] !SrcLoc | Invariant: First parameter must at least either have a selector or an identifier; all other parameters must have an identifier. |
AntiObjCMethodProto String !SrcLoc |
Instances
Instances
Data ObjCCatch Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjCCatch -> c ObjCCatch Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjCCatch Source # toConstr :: ObjCCatch -> Constr Source # dataTypeOf :: ObjCCatch -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjCCatch) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjCCatch) Source # gmapT :: (forall b. Data b => b -> b) -> ObjCCatch -> ObjCCatch Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjCCatch -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjCCatch -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ObjCCatch -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjCCatch -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjCCatch -> m ObjCCatch Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCCatch -> m ObjCCatch Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCCatch -> m ObjCCatch Source # | |
Show ObjCCatch Source # | |
Eq ObjCCatch Source # | |
Ord ObjCCatch Source # | |
Defined in Language.C.Syntax | |
Pretty ObjCCatch Source # | |
Located ObjCCatch Source # | |
Relocatable ObjCCatch Source # | |
data ObjCDictElem Source #
Constructors
ObjCDictElem Exp Exp !SrcLoc | |
AntiObjCDictElems String !SrcLoc |
Instances
Constructors
ObjCRecvSuper !SrcLoc | |
ObjCRecvExp Exp !SrcLoc | |
AntiObjCRecv String !SrcLoc |
Instances
Data ObjCRecv Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjCRecv -> c ObjCRecv Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjCRecv Source # toConstr :: ObjCRecv -> Constr Source # dataTypeOf :: ObjCRecv -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjCRecv) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjCRecv) Source # gmapT :: (forall b. Data b => b -> b) -> ObjCRecv -> ObjCRecv Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjCRecv -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjCRecv -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ObjCRecv -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjCRecv -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjCRecv -> m ObjCRecv Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCRecv -> m ObjCRecv Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCRecv -> m ObjCRecv Source # | |
Show ObjCRecv Source # | |
Eq ObjCRecv Source # | |
Ord ObjCRecv Source # | |
Defined in Language.C.Syntax | |
Pretty ObjCRecv Source # | |
Located ObjCRecv Source # | |
Relocatable ObjCRecv Source # | |
Constructors
ObjCArg (Maybe Id) (Maybe Exp) !SrcLoc | |
AntiObjCArg String !SrcLoc | |
AntiObjCArgs String !SrcLoc |
Instances
Data ObjCArg Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjCArg -> c ObjCArg Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjCArg Source # toConstr :: ObjCArg -> Constr Source # dataTypeOf :: ObjCArg -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjCArg) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjCArg) Source # gmapT :: (forall b. Data b => b -> b) -> ObjCArg -> ObjCArg Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjCArg -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjCArg -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ObjCArg -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjCArg -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjCArg -> m ObjCArg Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCArg -> m ObjCArg Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCArg -> m ObjCArg Source # | |
Show ObjCArg Source # | |
Eq ObjCArg Source # | |
Ord ObjCArg Source # | |
Defined in Language.C.Syntax | |
Located ObjCArg Source # | |
Relocatable ObjCArg Source # | |
data LambdaIntroducer Source #
Constructors
LambdaIntroducer [CaptureListEntry] !SrcLoc |
Instances
data LambdaDeclarator Source #
Instances
data CaptureListEntry Source #
Constructors
DefaultByReference | |
DefaultByValue |
Instances
Constructors
ExeConfig | |
Fields
|
Instances
Data ExeConfig Source # | |
Defined in Language.C.Syntax Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExeConfig -> c ExeConfig Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExeConfig Source # toConstr :: ExeConfig -> Constr Source # dataTypeOf :: ExeConfig -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExeConfig) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExeConfig) Source # gmapT :: (forall b. Data b => b -> b) -> ExeConfig -> ExeConfig Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExeConfig -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExeConfig -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ExeConfig -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExeConfig -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExeConfig -> m ExeConfig Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExeConfig -> m ExeConfig Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExeConfig -> m ExeConfig Source # | |
Show ExeConfig Source # | |
Eq ExeConfig Source # | |
Ord ExeConfig Source # | |
Defined in Language.C.Syntax | |
Located ExeConfig Source # | |
Relocatable ExeConfig Source # | |