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 |
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 = 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 #
Instances
Instances
Eq Id Source # | |
Data Id Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Id -> c Id # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Id # dataTypeOf :: Id -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Id) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Id) # gmapT :: (forall b. Data b => b -> b) -> Id -> Id # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Id -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Id -> r # gmapQ :: (forall d. Data d => d -> u) -> Id -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Id -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Id -> m Id # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Id -> m Id # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Id -> m Id # | |
Ord Id Source # | |
Show Id Source # | |
IsString Id Source # | |
Defined in Language.C.Syntax fromString :: String -> Id # | |
Pretty Id Source # | |
Located Id Source # | |
Relocatable Id Source # | |
ToIdent Id Source # | |
ToIdent (SrcLoc -> Id) Source # | |
Instances
Eq StringLit Source # | |
Data StringLit Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StringLit -> c StringLit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StringLit # toConstr :: StringLit -> Constr # dataTypeOf :: StringLit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StringLit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StringLit) # gmapT :: (forall b. Data b => b -> b) -> StringLit -> StringLit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StringLit -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StringLit -> r # gmapQ :: (forall d. Data d => d -> u) -> StringLit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> StringLit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StringLit -> m StringLit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StringLit -> m StringLit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StringLit -> m StringLit # | |
Ord StringLit Source # | |
Defined in Language.C.Syntax | |
Show StringLit Source # | |
IsString StringLit Source # | |
Defined in Language.C.Syntax fromString :: String -> StringLit # | |
Pretty StringLit Source # | |
Located StringLit Source # | |
Relocatable StringLit Source # | |
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
Eq Storage Source # | |
Data Storage Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Storage -> c Storage # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Storage # toConstr :: Storage -> Constr # dataTypeOf :: Storage -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Storage) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Storage) # gmapT :: (forall b. Data b => b -> b) -> Storage -> Storage # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Storage -> r # gmapQr :: (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 Source # | |
Show Storage Source # | |
Pretty Storage Source # | |
Located Storage Source # | |
Relocatable Storage Source # | |
Instances
Eq TypeQual Source # | |
Data TypeQual Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeQual -> c TypeQual # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeQual # toConstr :: TypeQual -> Constr # dataTypeOf :: TypeQual -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeQual) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeQual) # gmapT :: (forall b. Data b => b -> b) -> TypeQual -> TypeQual # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeQual -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeQual -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeQual -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeQual -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeQual -> m TypeQual # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeQual -> m TypeQual # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeQual -> m TypeQual # | |
Ord TypeQual Source # | |
Defined in Language.C.Syntax | |
Show TypeQual Source # | |
Pretty TypeQual Source # | |
Located TypeQual Source # | |
Relocatable TypeQual Source # | |
Instances
Eq Sign Source # | |
Data Sign Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sign -> c Sign # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Sign # dataTypeOf :: Sign -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Sign) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sign) # gmapT :: (forall b. Data b => b -> b) -> Sign -> Sign # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sign -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sign -> r # gmapQ :: (forall d. Data d => d -> u) -> Sign -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sign -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sign -> m Sign # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sign -> m Sign # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sign -> m Sign # | |
Ord Sign Source # | |
Show Sign Source # | |
Pretty Sign Source # | |
Located Sign Source # | |
Relocatable Sign 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 |
Instances
Eq TypeSpec Source # | |
Data TypeSpec Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeSpec -> c TypeSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeSpec # toConstr :: TypeSpec -> Constr # dataTypeOf :: TypeSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeSpec) # gmapT :: (forall b. Data b => b -> b) -> TypeSpec -> TypeSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeSpec -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> TypeSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeSpec -> m TypeSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeSpec -> m TypeSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeSpec -> m TypeSpec # | |
Ord TypeSpec Source # | |
Defined in Language.C.Syntax | |
Show TypeSpec Source # | |
Pretty TypeSpec Source # | |
Located TypeSpec Source # | |
Relocatable TypeSpec Source # | |
DeclSpec [Storage] [TypeQual] TypeSpec !SrcLoc | |
AntiDeclSpec String !SrcLoc | |
AntiTypeDeclSpec [Storage] [TypeQual] String !SrcLoc |
Instances
Eq DeclSpec Source # | |
Data DeclSpec Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeclSpec -> c DeclSpec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeclSpec # toConstr :: DeclSpec -> Constr # dataTypeOf :: DeclSpec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DeclSpec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeclSpec) # gmapT :: (forall b. Data b => b -> b) -> DeclSpec -> DeclSpec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeclSpec -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeclSpec -> r # gmapQ :: (forall d. Data d => d -> u) -> DeclSpec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DeclSpec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeclSpec -> m DeclSpec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeclSpec -> m DeclSpec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeclSpec -> m DeclSpec # | |
Ord DeclSpec Source # | |
Defined in Language.C.Syntax | |
Show DeclSpec Source # | |
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.
Instances
Eq ArraySize Source # | |
Data ArraySize Source # | |
Defined in Language.C.Syntax 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 :: (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 # | |
Ord ArraySize Source # | |
Defined in Language.C.Syntax | |
Show ArraySize Source # | |
Pretty ArraySize Source # | |
Located ArraySize Source # | |
Relocatable ArraySize Source # | |
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
Eq Decl Source # | |
Data Decl Source # | |
Defined in Language.C.Syntax 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 :: (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 # | |
Ord Decl Source # | |
Show Decl Source # | |
Located Decl Source # | |
Relocatable Decl Source # | |
Instances
Eq Type Source # | |
Data Type Source # | |
Defined in Language.C.Syntax 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 :: (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 # | |
Ord Type Source # | |
Show Type Source # | |
Pretty Type Source # | |
Located Type Source # | |
Relocatable Type Source # | |
data Designator Source #
Instances
data Designation Source #
Instances
data Initializer Source #
ExpInitializer Exp !SrcLoc | |
CompoundInitializer [(Maybe Designation, Initializer)] !SrcLoc | |
AntiInit String !SrcLoc | |
AntiInits String !SrcLoc |
Instances
Instances
Eq Init Source # | |
Data Init Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Init -> c Init # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Init # dataTypeOf :: Init -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Init) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Init) # gmapT :: (forall b. Data b => b -> b) -> Init -> Init # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Init -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Init -> r # gmapQ :: (forall d. Data d => d -> u) -> Init -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Init -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Init -> m Init # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Init -> m Init # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Init -> m Init # | |
Ord Init Source # | |
Show Init Source # | |
Pretty Init Source # | |
Located Init Source # | |
Relocatable Init Source # | |
Instances
Eq Typedef Source # | |
Data Typedef Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Typedef -> c Typedef # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Typedef # toConstr :: Typedef -> Constr # dataTypeOf :: Typedef -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Typedef) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Typedef) # gmapT :: (forall b. Data b => b -> b) -> Typedef -> Typedef # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Typedef -> r # gmapQr :: (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 # | |
Ord Typedef Source # | |
Show Typedef Source # | |
Pretty Typedef Source # | |
Located Typedef Source # | |
Relocatable Typedef Source # | |
InitGroup DeclSpec [Attr] [Init] !SrcLoc | |
TypedefGroup DeclSpec [Attr] [Typedef] !SrcLoc | |
AntiDecl String !SrcLoc | |
AntiDecls String !SrcLoc |
Instances
Eq InitGroup Source # | |
Data InitGroup Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InitGroup -> c InitGroup # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InitGroup # toConstr :: InitGroup -> Constr # dataTypeOf :: InitGroup -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InitGroup) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InitGroup) # gmapT :: (forall b. Data b => b -> b) -> InitGroup -> InitGroup # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InitGroup -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InitGroup -> r # gmapQ :: (forall d. Data d => d -> u) -> InitGroup -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> InitGroup -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InitGroup -> m InitGroup # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InitGroup -> m InitGroup # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InitGroup -> m InitGroup # | |
Ord InitGroup Source # | |
Defined in Language.C.Syntax | |
Show InitGroup Source # | |
Pretty InitGroup Source # | |
Located InitGroup Source # | |
Relocatable InitGroup Source # | |
Instances
Eq Field Source # | |
Data Field Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Field -> c Field # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Field # dataTypeOf :: Field -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Field) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Field) # gmapT :: (forall b. Data b => b -> b) -> Field -> Field # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Field -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Field -> r # gmapQ :: (forall d. Data d => d -> u) -> Field -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Field -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Field -> m Field # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Field -> m Field # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Field -> m Field # | |
Ord Field Source # | |
Show Field Source # | |
Pretty Field Source # | |
Located Field Source # | |
Relocatable Field Source # | |
data FieldGroup Source #
Instances
Instances
Eq CEnum Source # | |
Data CEnum Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CEnum -> c CEnum # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CEnum # dataTypeOf :: CEnum -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CEnum) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CEnum) # gmapT :: (forall b. Data b => b -> b) -> CEnum -> CEnum # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CEnum -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CEnum -> r # gmapQ :: (forall d. Data d => d -> u) -> CEnum -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CEnum -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CEnum -> m CEnum # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CEnum -> m CEnum # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CEnum -> m CEnum # | |
Ord CEnum Source # | |
Show CEnum Source # | |
Pretty CEnum Source # | |
Located CEnum Source # | |
Relocatable CEnum Source # | |
Instances
Eq Attr Source # | |
Data Attr Source # | |
Defined in Language.C.Syntax 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 :: (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 # | |
Ord Attr Source # | |
Show Attr Source # | |
Pretty Attr Source # | |
Located Attr Source # | |
Relocatable Attr Source # | |
Instances
Eq Param Source # | |
Data Param Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Param -> c Param # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Param # dataTypeOf :: Param -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Param) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Param) # gmapT :: (forall b. Data b => b -> b) -> Param -> Param # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Param -> r # gmapQ :: (forall d. Data d => d -> u) -> Param -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Param -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Param -> m Param # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Param -> m Param # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Param -> m Param # | |
Ord Param Source # | |
Show Param Source # | |
Pretty Param Source # | |
Located Param Source # | |
Relocatable Param Source # | |
Instances
Eq Params Source # | |
Data Params Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Params -> c Params # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Params # toConstr :: Params -> Constr # dataTypeOf :: Params -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Params) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Params) # gmapT :: (forall b. Data b => b -> b) -> Params -> Params # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Params -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Params -> r # gmapQ :: (forall d. Data d => d -> u) -> Params -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Params -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Params -> m Params # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Params -> m Params # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Params -> m Params # | |
Ord Params Source # | |
Show Params Source # | |
Pretty Params Source # | |
Located Params Source # | |
Relocatable Params Source # | |
Func DeclSpec Id Decl Params [BlockItem] !SrcLoc | |
OldFunc DeclSpec Id Decl [Id] (Maybe [InitGroup]) [BlockItem] !SrcLoc |
Instances
Eq Func Source # | |
Data Func Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Func -> c Func # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Func # dataTypeOf :: Func -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Func) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Func) # gmapT :: (forall b. Data b => b -> b) -> Func -> Func # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Func -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Func -> r # gmapQ :: (forall d. Data d => d -> u) -> Func -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Func -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Func -> m Func # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Func -> m Func # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Func -> m Func # | |
Ord Func Source # | |
Show Func Source # | |
Pretty Func Source # | |
Located Func Source # | |
Relocatable Func 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 |
Instances
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 |
Instances
Eq Stm Source # | |
Data Stm Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Stm -> c Stm # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Stm # dataTypeOf :: Stm -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Stm) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Stm) # gmapT :: (forall b. Data b => b -> b) -> Stm -> Stm # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stm -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stm -> r # gmapQ :: (forall d. Data d => d -> u) -> Stm -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Stm -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stm -> m Stm # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stm -> m Stm # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stm -> m Stm # | |
Ord Stm Source # | |
Show Stm Source # | |
Pretty Stm Source # | |
Located Stm Source # | |
Relocatable Stm Source # | |
Instances
Eq BlockItem Source # | |
Data BlockItem Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BlockItem -> c BlockItem # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BlockItem # toConstr :: BlockItem -> Constr # dataTypeOf :: BlockItem -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BlockItem) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BlockItem) # gmapT :: (forall b. Data b => b -> b) -> BlockItem -> BlockItem # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BlockItem -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BlockItem -> r # gmapQ :: (forall d. Data d => d -> u) -> BlockItem -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BlockItem -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BlockItem -> m BlockItem # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockItem -> m BlockItem # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockItem -> m BlockItem # | |
Ord BlockItem Source # | |
Defined in Language.C.Syntax | |
Show BlockItem Source # | |
Pretty BlockItem Source # | |
Located BlockItem Source # | |
Relocatable BlockItem Source # | |
Instances
Eq Signed Source # | |
Data Signed Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Signed -> c Signed # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Signed # toConstr :: Signed -> Constr # dataTypeOf :: Signed -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Signed) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Signed) # gmapT :: (forall b. Data b => b -> b) -> Signed -> Signed # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Signed -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Signed -> r # gmapQ :: (forall d. Data d => d -> u) -> Signed -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Signed -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Signed -> m Signed # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Signed -> m Signed # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Signed -> m Signed # | |
Ord Signed Source # | |
Show Signed Source # | |
The String
parameter to Const
data constructors is the raw string
representation of the constant as it was parsed.
Instances
Eq Const Source # | |
Data Const Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Const -> c Const # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Const # dataTypeOf :: Const -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Const) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Const) # gmapT :: (forall b. Data b => b -> b) -> Const -> Const # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Const -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Const -> r # gmapQ :: (forall d. Data d => d -> u) -> Const -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Const -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Const -> m Const # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Const -> m Const # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Const -> m Const # | |
Ord Const Source # | |
Show Const Source # | |
Pretty Const Source # | |
Located Const Source # | |
Relocatable Const Source # | |
ToConst Const Source # | |
Instances
Enum Exp Source # | |
Eq Exp Source # | |
Floating Exp Source # | |
Fractional Exp Source # | |
Integral Exp Source # | |
Data Exp Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Exp -> c Exp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Exp # dataTypeOf :: Exp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Exp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp) # gmapT :: (forall b. Data b => b -> b) -> Exp -> Exp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r # gmapQ :: (forall d. Data d => d -> u) -> Exp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Exp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Exp -> m Exp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp # | |
Num Exp Source # | |
Ord Exp Source # | |
Real Exp Source # | |
Defined in Language.C.Smart toRational :: Exp -> Rational # | |
Show Exp Source # | |
Pretty Exp Source # | |
Located Exp Source # | |
Relocatable Exp Source # | |
ToExp Exp Source # | |
Instances
Eq BinOp Source # | |
Data BinOp Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BinOp -> c BinOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BinOp # dataTypeOf :: BinOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BinOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BinOp) # gmapT :: (forall b. Data b => b -> b) -> BinOp -> BinOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BinOp -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BinOp -> r # gmapQ :: (forall d. Data d => d -> u) -> BinOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BinOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp # | |
Ord BinOp Source # | |
Show BinOp Source # | |
Pretty BinOp Source # | |
CFixity BinOp Source # | |
JustAssign | |
AddAssign | |
SubAssign | |
MulAssign | |
DivAssign | |
ModAssign | |
LshAssign | |
RshAssign | |
AndAssign | |
XorAssign | |
OrAssign |
Instances
Eq AssignOp Source # | |
Data AssignOp Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AssignOp -> c AssignOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AssignOp # toConstr :: AssignOp -> Constr # dataTypeOf :: AssignOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AssignOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AssignOp) # gmapT :: (forall b. Data b => b -> b) -> AssignOp -> AssignOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AssignOp -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AssignOp -> r # gmapQ :: (forall d. Data d => d -> u) -> AssignOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AssignOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AssignOp -> m AssignOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AssignOp -> m AssignOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AssignOp -> m AssignOp # | |
Ord AssignOp Source # | |
Defined in Language.C.Syntax | |
Show AssignOp Source # | |
Pretty AssignOp Source # | |
CFixity AssignOp Source # | |
Instances
Eq UnOp Source # | |
Data UnOp Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnOp -> c UnOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnOp # dataTypeOf :: UnOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnOp) # gmapT :: (forall b. Data b => b -> b) -> UnOp -> UnOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnOp -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnOp -> r # gmapQ :: (forall d. Data d => d -> u) -> UnOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UnOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnOp -> m UnOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnOp -> m UnOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnOp -> m UnOp # | |
Ord UnOp Source # | |
Show UnOp Source # | |
Pretty UnOp Source # | |
CFixity UnOp Source # | |
type AsmTemplate = StringLit Source #
Instances
Eq AsmOut Source # | |
Data AsmOut Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AsmOut -> c AsmOut # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AsmOut # toConstr :: AsmOut -> Constr # dataTypeOf :: AsmOut -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AsmOut) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AsmOut) # gmapT :: (forall b. Data b => b -> b) -> AsmOut -> AsmOut # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AsmOut -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AsmOut -> r # gmapQ :: (forall d. Data d => d -> u) -> AsmOut -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AsmOut -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AsmOut -> m AsmOut # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AsmOut -> m AsmOut # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AsmOut -> m AsmOut # | |
Ord AsmOut Source # | |
Show AsmOut Source # | |
Pretty AsmOut Source # | |
Instances
Eq AsmIn Source # | |
Data AsmIn Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AsmIn -> c AsmIn # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AsmIn # dataTypeOf :: AsmIn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AsmIn) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AsmIn) # gmapT :: (forall b. Data b => b -> b) -> AsmIn -> AsmIn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AsmIn -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AsmIn -> r # gmapQ :: (forall d. Data d => d -> u) -> AsmIn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AsmIn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AsmIn -> m AsmIn # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AsmIn -> m AsmIn # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AsmIn -> m AsmIn # | |
Ord AsmIn Source # | |
Show AsmIn Source # | |
Pretty AsmIn Source # | |
type AsmClobber = String Source #
Instances
Eq BlockType Source # | |
Data BlockType Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BlockType -> c BlockType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BlockType # toConstr :: BlockType -> Constr # dataTypeOf :: BlockType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BlockType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BlockType) # gmapT :: (forall b. Data b => b -> b) -> BlockType -> BlockType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BlockType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BlockType -> r # gmapQ :: (forall d. Data d => d -> u) -> BlockType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BlockType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BlockType -> m BlockType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockType -> m BlockType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BlockType -> m BlockType # | |
Ord BlockType Source # | |
Defined in Language.C.Syntax | |
Show BlockType Source # | |
Pretty BlockType Source # | |
Located BlockType Source # | |
Relocatable BlockType Source # | |
data ObjCIvarDecl Source #
Instances
data ObjCVisibilitySpec Source #
Instances
data ObjCIfaceDecl Source #
Instances
data ObjCPropAttr Source #
Instances
data ObjCMethodReq Source #
Instances
ObjCParam (Maybe Id) (Maybe Type) [Attr] (Maybe Id) !SrcLoc | |
AntiObjCParam String !SrcLoc | |
AntiObjCParams String !SrcLoc |
Instances
Eq ObjCParam Source # | |
Data ObjCParam Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjCParam -> c ObjCParam # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjCParam # toConstr :: ObjCParam -> Constr # dataTypeOf :: ObjCParam -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjCParam) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjCParam) # gmapT :: (forall b. Data b => b -> b) -> ObjCParam -> ObjCParam # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjCParam -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjCParam -> r # gmapQ :: (forall d. Data d => d -> u) -> ObjCParam -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjCParam -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjCParam -> m ObjCParam # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCParam -> m ObjCParam # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCParam -> m ObjCParam # | |
Ord ObjCParam Source # | |
Defined in Language.C.Syntax | |
Show ObjCParam Source # | |
Pretty ObjCParam Source # | |
Located ObjCParam Source # | |
Relocatable ObjCParam Source # | |
data ObjCMethodProto Source #
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
Eq ObjCCatch Source # | |
Data ObjCCatch Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjCCatch -> c ObjCCatch # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjCCatch # toConstr :: ObjCCatch -> Constr # dataTypeOf :: ObjCCatch -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjCCatch) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjCCatch) # gmapT :: (forall b. Data b => b -> b) -> ObjCCatch -> ObjCCatch # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjCCatch -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjCCatch -> r # gmapQ :: (forall d. Data d => d -> u) -> ObjCCatch -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjCCatch -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjCCatch -> m ObjCCatch # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCCatch -> m ObjCCatch # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCCatch -> m ObjCCatch # | |
Ord ObjCCatch Source # | |
Defined in Language.C.Syntax | |
Show ObjCCatch Source # | |
Pretty ObjCCatch Source # | |
Located ObjCCatch Source # | |
Relocatable ObjCCatch Source # | |
data ObjCDictElem Source #
Instances
Instances
Eq ObjCRecv Source # | |
Data ObjCRecv Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjCRecv -> c ObjCRecv # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjCRecv # toConstr :: ObjCRecv -> Constr # dataTypeOf :: ObjCRecv -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjCRecv) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjCRecv) # gmapT :: (forall b. Data b => b -> b) -> ObjCRecv -> ObjCRecv # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjCRecv -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjCRecv -> r # gmapQ :: (forall d. Data d => d -> u) -> ObjCRecv -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjCRecv -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjCRecv -> m ObjCRecv # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCRecv -> m ObjCRecv # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCRecv -> m ObjCRecv # | |
Ord ObjCRecv Source # | |
Defined in Language.C.Syntax | |
Show ObjCRecv Source # | |
Pretty ObjCRecv Source # | |
Located ObjCRecv Source # | |
Relocatable ObjCRecv Source # | |
Instances
Eq ObjCArg Source # | |
Data ObjCArg Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ObjCArg -> c ObjCArg # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ObjCArg # toConstr :: ObjCArg -> Constr # dataTypeOf :: ObjCArg -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ObjCArg) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ObjCArg) # gmapT :: (forall b. Data b => b -> b) -> ObjCArg -> ObjCArg # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ObjCArg -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ObjCArg -> r # gmapQ :: (forall d. Data d => d -> u) -> ObjCArg -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ObjCArg -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ObjCArg -> m ObjCArg # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCArg -> m ObjCArg # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ObjCArg -> m ObjCArg # | |
Ord ObjCArg Source # | |
Show ObjCArg Source # | |
Located ObjCArg Source # | |
Relocatable ObjCArg Source # | |
data LambdaIntroducer Source #
Instances
data LambdaDeclarator Source #
Instances
data CaptureListEntry Source #
Instances
ExeConfig | |
|
Instances
Eq ExeConfig Source # | |
Data ExeConfig Source # | |
Defined in Language.C.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExeConfig -> c ExeConfig # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExeConfig # toConstr :: ExeConfig -> Constr # dataTypeOf :: ExeConfig -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExeConfig) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExeConfig) # gmapT :: (forall b. Data b => b -> b) -> ExeConfig -> ExeConfig # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExeConfig -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExeConfig -> r # gmapQ :: (forall d. Data d => d -> u) -> ExeConfig -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExeConfig -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExeConfig -> m ExeConfig # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExeConfig -> m ExeConfig # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExeConfig -> m ExeConfig # | |
Ord ExeConfig Source # | |
Defined in Language.C.Syntax | |
Show ExeConfig Source # | |
Located ExeConfig Source # | |
Relocatable ExeConfig Source # | |