clang-pure-0.2.0.3: Pure C++ code analysis with libclang

Copyright(C) 2016 Patrick Chilton
Safe HaskellNone
LanguageHaskell2010

Language.C.Clang.Cursor.Typed

Description

This module contains a typed version of Language.C.Clang.Cursor. Here, we keep track of CursorKinds at type-level, which means that you don't need to check whether a Cursor has a given property at runtime.

Synopsis

Documentation

data Cursor Source #

Instances

Clang Cursor Source # 

Methods

deref :: Cursor -> (Ptr (RefOf Cursor) -> IO a) -> IO a

unsafeToPtr :: Cursor -> Ptr (RefOf Cursor)

data CursorK (kind :: CursorKind) Source #

A Cursor with a statically known CursorKind.

Instances

Eq (CursorK kind) Source # 

Methods

(==) :: CursorK kind -> CursorK kind -> Bool #

(/=) :: CursorK kind -> CursorK kind -> Bool #

Show (CursorK kind) Source # 

Methods

showsPrec :: Int -> CursorK kind -> ShowS #

show :: CursorK kind -> String #

showList :: [CursorK kind] -> ShowS #

Clang (CursorK kind) Source # 

Methods

deref :: CursorK kind -> (Ptr (RefOf (CursorK kind)) -> IO a) -> IO a

unsafeToPtr :: CursorK kind -> Ptr (RefOf (CursorK kind))

matchKind :: forall kind. SingI kind => Cursor -> Maybe (CursorK kind) Source #

Match a Cursor as a particular CursorKind. You can use the TypeApplications extension to easily specify the CursorKind you want: matchKind @'StructDecl.

cursorType :: HasType kind => CursorK kind -> Type Source #

cursorDescendantsF :: HasChildren kind => Fold (CursorK kind) Cursor Source #

Fold over a CursorK and all of its descendants recursively.

cursorDescendants :: HasChildren kind => CursorK kind -> [Cursor] Source #

List a CursorK and all of its descendants recursively.

class HasType (kind :: CursorKind) Source #

Instances

HasType StructDecl Source # 
HasType UnionDecl Source # 
HasType ClassDecl Source # 
HasType EnumDecl Source # 
HasType FieldDecl Source # 
HasType EnumConstantDecl Source # 
HasType FunctionDecl Source # 
HasType VarDecl Source # 
HasType ParmDecl Source # 
HasType TypedefDecl Source # 
HasType CXXMethod Source # 
HasType Constructor Source # 
HasType Destructor Source # 
HasType ConversionFunction Source # 
HasType TemplateTypeParameter Source # 
HasType NonTypeTemplateParameter Source # 
HasType FunctionTemplate Source # 
HasType ClassTemplatePartialSpecialization Source # 
HasType TypeRef Source # 
HasType CXXBaseSpecifier Source # 
HasType MemberRef Source # 
HasType DeclRefExpr Source # 
HasType MemberRefExpr Source # 
HasType CallExpr Source # 
HasType IntegerLiteral Source # 
HasType FloatingLiteral Source # 
HasType StringLiteral Source # 
HasType CharacterLiteral Source # 
HasType ParenExpr Source # 
HasType UnaryOperator Source # 
HasType ArraySubscriptExpr Source # 
HasType BinaryOperator Source # 
HasType CompoundAssignOperator Source # 
HasType ConditionalOperator Source # 
HasType CStyleCastExpr Source # 
HasType InitListExpr Source # 
HasType GNUNullExpr Source # 
HasType CXXStaticCastExpr Source # 
HasType CXXDynamicCastExpr Source # 
HasType CXXReinterpretCastExpr Source # 
HasType CXXConstCastExpr Source # 
HasType CXXFunctionalCastExpr Source # 
HasType CXXBoolLiteralExpr Source # 
HasType CXXThisExpr Source # 
HasType CXXThrowExpr Source # 
HasType CXXNewExpr Source # 
HasType CXXDeleteExpr Source # 

class HasChildren (kind :: CursorKind) Source #

Instances

HasChildren UnexposedDecl Source # 
HasChildren StructDecl Source # 
HasChildren UnionDecl Source # 
HasChildren ClassDecl Source # 
HasChildren EnumDecl Source # 
HasChildren FieldDecl Source # 
HasChildren EnumConstantDecl Source # 
HasChildren FunctionDecl Source # 
HasChildren VarDecl Source # 
HasChildren ParmDecl Source # 
HasChildren TypedefDecl Source # 
HasChildren CXXMethod Source # 
HasChildren Namespace Source # 
HasChildren Constructor Source # 
HasChildren Destructor Source # 
HasChildren ConversionFunction Source # 
HasChildren TemplateTypeParameter Source # 
HasChildren NonTypeTemplateParameter Source # 
HasChildren FunctionTemplate Source # 
HasChildren ClassTemplate Source # 
HasChildren ClassTemplatePartialSpecialization Source # 
HasChildren UsingDirective Source # 
HasChildren UsingDeclaration Source # 
HasChildren CXXBaseSpecifier Source # 
HasChildren FirstExpr Source # 
HasChildren DeclRefExpr Source # 
HasChildren MemberRefExpr Source # 
HasChildren CallExpr Source # 
HasChildren ParenExpr Source # 
HasChildren UnaryOperator Source # 
HasChildren ArraySubscriptExpr Source # 
HasChildren BinaryOperator Source # 
HasChildren CompoundAssignOperator Source # 
HasChildren ConditionalOperator Source # 
HasChildren CStyleCastExpr Source # 
HasChildren InitListExpr Source # 
HasChildren CXXStaticCastExpr Source # 
HasChildren CXXDynamicCastExpr Source # 
HasChildren CXXReinterpretCastExpr Source # 
HasChildren CXXConstCastExpr Source # 
HasChildren CXXFunctionalCastExpr Source # 
HasChildren CXXNewExpr Source # 
HasChildren CXXDeleteExpr Source # 
HasChildren CompoundStmt Source # 
HasChildren CaseStmt Source # 
HasChildren DefaultStmt Source # 
HasChildren IfStmt Source # 
HasChildren SwitchStmt Source # 
HasChildren WhileStmt Source # 
HasChildren DoStmt Source # 
HasChildren ForStmt Source # 
HasChildren ReturnStmt Source # 
HasChildren CXXCatchStmt Source # 
HasChildren CXXTryStmt Source # 
HasChildren DeclStmt Source # 
HasChildren TranslationUnit Source # 

class HasExtent (kind :: CursorKind) Source #

Instances

HasExtent StructDecl Source # 
HasExtent UnionDecl Source # 
HasExtent ClassDecl Source # 
HasExtent EnumDecl Source # 
HasExtent EnumConstantDecl Source # 
HasExtent FunctionDecl Source # 
HasExtent TypedefDecl Source # 
HasExtent CXXMethod Source # 
HasExtent Namespace Source # 
HasExtent Constructor Source # 
HasExtent Destructor Source # 
HasExtent ConversionFunction Source # 
HasExtent TemplateTypeParameter Source # 
HasExtent NonTypeTemplateParameter Source # 
HasExtent FunctionTemplate Source # 
HasExtent ClassTemplate Source # 
HasExtent ClassTemplatePartialSpecialization Source # 
HasExtent UsingDirective Source # 
HasExtent UsingDeclaration Source # 
HasExtent CXXAccessSpecifier Source # 
HasExtent TypeRef Source # 
HasExtent CXXBaseSpecifier Source # 
HasExtent TemplateRef Source # 
HasExtent NamespaceRef Source # 
HasExtent MemberRef Source # 
HasExtent OverloadedDeclRef Source # 
HasExtent DeclRefExpr Source # 
HasExtent MemberRefExpr Source # 
HasExtent CallExpr Source # 
HasExtent FloatingLiteral Source # 
HasExtent StringLiteral Source # 
HasExtent CharacterLiteral Source # 
HasExtent ParenExpr Source # 
HasExtent UnaryOperator Source # 
HasExtent ArraySubscriptExpr Source # 
HasExtent BinaryOperator Source # 
HasExtent CompoundAssignOperator Source # 
HasExtent ConditionalOperator Source # 
HasExtent CStyleCastExpr Source # 
HasExtent InitListExpr Source # 
HasExtent GNUNullExpr Source # 
HasExtent CXXStaticCastExpr Source # 
HasExtent CXXDynamicCastExpr Source # 
HasExtent CXXReinterpretCastExpr Source # 
HasExtent CXXConstCastExpr Source # 
HasExtent CXXFunctionalCastExpr Source # 
HasExtent CXXBoolLiteralExpr Source # 
HasExtent CXXThisExpr Source # 
HasExtent CXXThrowExpr Source # 
HasExtent CXXNewExpr Source # 
HasExtent CXXDeleteExpr Source # 
HasExtent CompoundStmt Source # 
HasExtent CaseStmt Source # 
HasExtent DefaultStmt Source # 
HasExtent IfStmt Source # 
HasExtent SwitchStmt Source # 
HasExtent WhileStmt Source # 
HasExtent DoStmt Source # 
HasExtent ForStmt Source # 
HasExtent ContinueStmt Source # 
HasExtent BreakStmt Source # 
HasExtent ReturnStmt Source # 
HasExtent CXXCatchStmt Source # 
HasExtent CXXTryStmt Source # 
HasExtent NullStmt Source # 
HasExtent DeclStmt Source # 
HasExtent TranslationUnit Source # 
HasExtent AsmLabelAttr Source # 
HasExtent PureAttr Source # 
HasExtent ConstAttr Source # 

data CursorKind Source #

Constructors

UnexposedDecl 
StructDecl 
UnionDecl 
ClassDecl 
EnumDecl 
FieldDecl 
EnumConstantDecl 
FunctionDecl 
VarDecl 
ParmDecl 
ObjCInterfaceDecl 
ObjCCategoryDecl 
ObjCProtocolDecl 
ObjCPropertyDecl 
ObjCIvarDecl 
ObjCInstanceMethodDecl 
ObjCClassMethodDecl 
ObjCImplementationDecl 
ObjCCategoryImplDecl 
TypedefDecl 
CXXMethod 
Namespace 
LinkageSpec 
Constructor 
Destructor 
ConversionFunction 
TemplateTypeParameter 
NonTypeTemplateParameter 
TemplateTemplateParameter 
FunctionTemplate 
ClassTemplate 
ClassTemplatePartialSpecialization 
NamespaceAlias 
UsingDirective 
UsingDeclaration 
TypeAliasDecl 
ObjCSynthesizeDecl 
ObjCDynamicDecl 
CXXAccessSpecifier 
FirstDecl 
LastDecl 
FirstRef 
ObjCSuperClassRef 
ObjCProtocolRef 
ObjCClassRef 
TypeRef 
CXXBaseSpecifier 
TemplateRef 
NamespaceRef 
MemberRef 
LabelRef 
OverloadedDeclRef 
VariableRef 
LastRef 
FirstInvalid 
InvalidFile 
NoDeclFound 
NotImplemented 
InvalidCode 
LastInvalid 
FirstExpr 
UnexposedExpr 
DeclRefExpr 
MemberRefExpr 
CallExpr 
ObjCMessageExpr 
BlockExpr 
IntegerLiteral 
FloatingLiteral 
ImaginaryLiteral 
StringLiteral 
CharacterLiteral 
ParenExpr 
UnaryOperator 
ArraySubscriptExpr 
BinaryOperator 
CompoundAssignOperator 
ConditionalOperator 
CStyleCastExpr 
CompoundLiteralExpr 
InitListExpr 
AddrLabelExpr 
StmtExpr 
GenericSelectionExpr 
GNUNullExpr 
CXXStaticCastExpr 
CXXDynamicCastExpr 
CXXReinterpretCastExpr 
CXXConstCastExpr 
CXXFunctionalCastExpr 
CXXTypeidExpr 
CXXBoolLiteralExpr 
CXXNullPtrLiteralExpr 
CXXThisExpr 
CXXThrowExpr 
CXXNewExpr 
CXXDeleteExpr 
UnaryExpr 
ObjCStringLiteral 
ObjCEncodeExpr 
ObjCSelectorExpr 
ObjCProtocolExpr 
ObjCBridgedCastExpr 
PackExpansionExpr 
SizeOfPackExpr 
LambdaExpr 
ObjCBoolLiteralExpr 
ObjCSelfExpr 
LastExpr 
FirstStmt 
UnexposedStmt 
LabelStmt 
CompoundStmt 
CaseStmt 
DefaultStmt 
IfStmt 
SwitchStmt 
WhileStmt 
DoStmt 
ForStmt 
GotoStmt 
IndirectGotoStmt 
ContinueStmt 
BreakStmt 
ReturnStmt 
GCCAsmStmt 
AsmStmt 
ObjCAtTryStmt 
ObjCAtCatchStmt 
ObjCAtFinallyStmt 
ObjCAtThrowStmt 
ObjCAtSynchronizedStmt 
ObjCAutoreleasePoolStmt 
ObjCForCollectionStmt 
CXXCatchStmt 
CXXTryStmt 
CXXForRangeStmt 
SEHTryStmt 
SEHExceptStmt 
SEHFinallyStmt 
MSAsmStmt 
NullStmt 
DeclStmt 
OMPParallelDirective 
OMPSimdDirective 
OMPForDirective 
OMPSectionsDirective 
OMPSectionDirective 
OMPSingleDirective 
OMPParallelForDirective 
OMPParallelSectionsDirective 
OMPTaskDirective 
OMPMasterDirective 
OMPCriticalDirective 
OMPTaskyieldDirective 
OMPBarrierDirective 
OMPTaskwaitDirective 
OMPFlushDirective 
SEHLeaveStmt 
LastStmt 
TranslationUnit 
FirstAttr 
UnexposedAttr 
IBActionAttr 
IBOutletAttr 
IBOutletCollectionAttr 
CXXFinalAttr 
CXXOverrideAttr 
AnnotateAttr 
AsmLabelAttr 
PackedAttr 
PureAttr 
ConstAttr 
NoDuplicateAttr 
CUDAConstantAttr 
CUDADeviceAttr 
CUDAGlobalAttr 
CUDAHostAttr 
LastAttr 
PreprocessingDirective 
MacroDefinition 
MacroExpansion 
MacroInstantiation 
InclusionDirective 
FirstPreprocessing 
LastPreprocessing 
ModuleImportDecl 
FirstExtraDecl 
LastExtraDecl 

Instances

Eq CursorKind Source # 
Ord CursorKind Source # 
Show CursorKind Source # 
SingKind CursorKind Source # 
SingI CursorKind UnexposedDecl Source # 

Methods

sing :: Sing UnexposedDecl a #

SingI CursorKind StructDecl Source # 

Methods

sing :: Sing StructDecl a #

SingI CursorKind UnionDecl Source # 

Methods

sing :: Sing UnionDecl a #

SingI CursorKind ClassDecl Source # 

Methods

sing :: Sing ClassDecl a #

SingI CursorKind EnumDecl Source # 

Methods

sing :: Sing EnumDecl a #

SingI CursorKind FieldDecl Source # 

Methods

sing :: Sing FieldDecl a #

SingI CursorKind EnumConstantDecl Source # 
SingI CursorKind FunctionDecl Source # 

Methods

sing :: Sing FunctionDecl a #

SingI CursorKind VarDecl Source # 

Methods

sing :: Sing VarDecl a #

SingI CursorKind ParmDecl Source # 

Methods

sing :: Sing ParmDecl a #

SingI CursorKind ObjCInterfaceDecl Source # 
SingI CursorKind ObjCCategoryDecl Source # 
SingI CursorKind ObjCProtocolDecl Source # 
SingI CursorKind ObjCPropertyDecl Source # 
SingI CursorKind ObjCIvarDecl Source # 

Methods

sing :: Sing ObjCIvarDecl a #

SingI CursorKind ObjCInstanceMethodDecl Source # 
SingI CursorKind ObjCClassMethodDecl Source # 
SingI CursorKind ObjCImplementationDecl Source # 
SingI CursorKind ObjCCategoryImplDecl Source # 
SingI CursorKind TypedefDecl Source # 

Methods

sing :: Sing TypedefDecl a #

SingI CursorKind CXXMethod Source # 

Methods

sing :: Sing CXXMethod a #

SingI CursorKind Namespace Source # 

Methods

sing :: Sing Namespace a #

SingI CursorKind LinkageSpec Source # 

Methods

sing :: Sing LinkageSpec a #

SingI CursorKind Constructor Source # 

Methods

sing :: Sing Constructor a #

SingI CursorKind Destructor Source # 

Methods

sing :: Sing Destructor a #

SingI CursorKind ConversionFunction Source # 
SingI CursorKind TemplateTypeParameter Source # 
SingI CursorKind NonTypeTemplateParameter Source # 
SingI CursorKind TemplateTemplateParameter Source # 
SingI CursorKind FunctionTemplate Source # 
SingI CursorKind ClassTemplate Source # 

Methods

sing :: Sing ClassTemplate a #

SingI CursorKind ClassTemplatePartialSpecialization Source # 
SingI CursorKind NamespaceAlias Source # 
SingI CursorKind UsingDirective Source # 
SingI CursorKind UsingDeclaration Source # 
SingI CursorKind TypeAliasDecl Source # 

Methods

sing :: Sing TypeAliasDecl a #

SingI CursorKind ObjCSynthesizeDecl Source # 
SingI CursorKind ObjCDynamicDecl Source # 
SingI CursorKind CXXAccessSpecifier Source # 
SingI CursorKind FirstDecl Source # 

Methods

sing :: Sing FirstDecl a #

SingI CursorKind LastDecl Source # 

Methods

sing :: Sing LastDecl a #

SingI CursorKind FirstRef Source # 

Methods

sing :: Sing FirstRef a #

SingI CursorKind ObjCSuperClassRef Source # 
SingI CursorKind ObjCProtocolRef Source # 
SingI CursorKind ObjCClassRef Source # 

Methods

sing :: Sing ObjCClassRef a #

SingI CursorKind TypeRef Source # 

Methods

sing :: Sing TypeRef a #

SingI CursorKind CXXBaseSpecifier Source # 
SingI CursorKind TemplateRef Source # 

Methods

sing :: Sing TemplateRef a #

SingI CursorKind NamespaceRef Source # 

Methods

sing :: Sing NamespaceRef a #

SingI CursorKind MemberRef Source # 

Methods

sing :: Sing MemberRef a #

SingI CursorKind LabelRef Source # 

Methods

sing :: Sing LabelRef a #

SingI CursorKind OverloadedDeclRef Source # 
SingI CursorKind VariableRef Source # 

Methods

sing :: Sing VariableRef a #

SingI CursorKind LastRef Source # 

Methods

sing :: Sing LastRef a #

SingI CursorKind FirstInvalid Source # 

Methods

sing :: Sing FirstInvalid a #

SingI CursorKind InvalidFile Source # 

Methods

sing :: Sing InvalidFile a #

SingI CursorKind NoDeclFound Source # 

Methods

sing :: Sing NoDeclFound a #

SingI CursorKind NotImplemented Source # 
SingI CursorKind InvalidCode Source # 

Methods

sing :: Sing InvalidCode a #

SingI CursorKind LastInvalid Source # 

Methods

sing :: Sing LastInvalid a #

SingI CursorKind FirstExpr Source # 

Methods

sing :: Sing FirstExpr a #

SingI CursorKind UnexposedExpr Source # 

Methods

sing :: Sing UnexposedExpr a #

SingI CursorKind DeclRefExpr Source # 

Methods

sing :: Sing DeclRefExpr a #

SingI CursorKind MemberRefExpr Source # 

Methods

sing :: Sing MemberRefExpr a #

SingI CursorKind CallExpr Source # 

Methods

sing :: Sing CallExpr a #

SingI CursorKind ObjCMessageExpr Source # 
SingI CursorKind BlockExpr Source # 

Methods

sing :: Sing BlockExpr a #

SingI CursorKind IntegerLiteral Source # 
SingI CursorKind FloatingLiteral Source # 
SingI CursorKind ImaginaryLiteral Source # 
SingI CursorKind StringLiteral Source # 

Methods

sing :: Sing StringLiteral a #

SingI CursorKind CharacterLiteral Source # 
SingI CursorKind ParenExpr Source # 

Methods

sing :: Sing ParenExpr a #

SingI CursorKind UnaryOperator Source # 

Methods

sing :: Sing UnaryOperator a #

SingI CursorKind ArraySubscriptExpr Source # 
SingI CursorKind BinaryOperator Source # 
SingI CursorKind CompoundAssignOperator Source # 
SingI CursorKind ConditionalOperator Source # 
SingI CursorKind CStyleCastExpr Source # 
SingI CursorKind CompoundLiteralExpr Source # 
SingI CursorKind InitListExpr Source # 

Methods

sing :: Sing InitListExpr a #

SingI CursorKind AddrLabelExpr Source # 

Methods

sing :: Sing AddrLabelExpr a #

SingI CursorKind StmtExpr Source # 

Methods

sing :: Sing StmtExpr a #

SingI CursorKind GenericSelectionExpr Source # 
SingI CursorKind GNUNullExpr Source # 

Methods

sing :: Sing GNUNullExpr a #

SingI CursorKind CXXStaticCastExpr Source # 
SingI CursorKind CXXDynamicCastExpr Source # 
SingI CursorKind CXXReinterpretCastExpr Source # 
SingI CursorKind CXXConstCastExpr Source # 
SingI CursorKind CXXFunctionalCastExpr Source # 
SingI CursorKind CXXTypeidExpr Source # 

Methods

sing :: Sing CXXTypeidExpr a #

SingI CursorKind CXXBoolLiteralExpr Source # 
SingI CursorKind CXXNullPtrLiteralExpr Source # 
SingI CursorKind CXXThisExpr Source # 

Methods

sing :: Sing CXXThisExpr a #

SingI CursorKind CXXThrowExpr Source # 

Methods

sing :: Sing CXXThrowExpr a #

SingI CursorKind CXXNewExpr Source # 

Methods

sing :: Sing CXXNewExpr a #

SingI CursorKind CXXDeleteExpr Source # 

Methods

sing :: Sing CXXDeleteExpr a #

SingI CursorKind UnaryExpr Source # 

Methods

sing :: Sing UnaryExpr a #

SingI CursorKind ObjCStringLiteral Source # 
SingI CursorKind ObjCEncodeExpr Source # 
SingI CursorKind ObjCSelectorExpr Source # 
SingI CursorKind ObjCProtocolExpr Source # 
SingI CursorKind ObjCBridgedCastExpr Source # 
SingI CursorKind PackExpansionExpr Source # 
SingI CursorKind SizeOfPackExpr Source # 
SingI CursorKind LambdaExpr Source # 

Methods

sing :: Sing LambdaExpr a #

SingI CursorKind ObjCBoolLiteralExpr Source # 
SingI CursorKind ObjCSelfExpr Source # 

Methods

sing :: Sing ObjCSelfExpr a #

SingI CursorKind LastExpr Source # 

Methods

sing :: Sing LastExpr a #

SingI CursorKind FirstStmt Source # 

Methods

sing :: Sing FirstStmt a #

SingI CursorKind UnexposedStmt Source # 

Methods

sing :: Sing UnexposedStmt a #

SingI CursorKind LabelStmt Source # 

Methods

sing :: Sing LabelStmt a #

SingI CursorKind CompoundStmt Source # 

Methods

sing :: Sing CompoundStmt a #

SingI CursorKind CaseStmt Source # 

Methods

sing :: Sing CaseStmt a #

SingI CursorKind DefaultStmt Source # 

Methods

sing :: Sing DefaultStmt a #

SingI CursorKind IfStmt Source # 

Methods

sing :: Sing IfStmt a #

SingI CursorKind SwitchStmt Source # 

Methods

sing :: Sing SwitchStmt a #

SingI CursorKind WhileStmt Source # 

Methods

sing :: Sing WhileStmt a #

SingI CursorKind DoStmt Source # 

Methods

sing :: Sing DoStmt a #

SingI CursorKind ForStmt Source # 

Methods

sing :: Sing ForStmt a #

SingI CursorKind GotoStmt Source # 

Methods

sing :: Sing GotoStmt a #

SingI CursorKind IndirectGotoStmt Source # 
SingI CursorKind ContinueStmt Source # 

Methods

sing :: Sing ContinueStmt a #

SingI CursorKind BreakStmt Source # 

Methods

sing :: Sing BreakStmt a #

SingI CursorKind ReturnStmt Source # 

Methods

sing :: Sing ReturnStmt a #

SingI CursorKind GCCAsmStmt Source # 

Methods

sing :: Sing GCCAsmStmt a #

SingI CursorKind AsmStmt Source # 

Methods

sing :: Sing AsmStmt a #

SingI CursorKind ObjCAtTryStmt Source # 

Methods

sing :: Sing ObjCAtTryStmt a #

SingI CursorKind ObjCAtCatchStmt Source # 
SingI CursorKind ObjCAtFinallyStmt Source # 
SingI CursorKind ObjCAtThrowStmt Source # 
SingI CursorKind ObjCAtSynchronizedStmt Source # 
SingI CursorKind ObjCAutoreleasePoolStmt Source # 
SingI CursorKind ObjCForCollectionStmt Source # 
SingI CursorKind CXXCatchStmt Source # 

Methods

sing :: Sing CXXCatchStmt a #

SingI CursorKind CXXTryStmt Source # 

Methods

sing :: Sing CXXTryStmt a #

SingI CursorKind CXXForRangeStmt Source # 
SingI CursorKind SEHTryStmt Source # 

Methods

sing :: Sing SEHTryStmt a #

SingI CursorKind SEHExceptStmt Source # 

Methods

sing :: Sing SEHExceptStmt a #

SingI CursorKind SEHFinallyStmt Source # 
SingI CursorKind MSAsmStmt Source # 

Methods

sing :: Sing MSAsmStmt a #

SingI CursorKind NullStmt Source # 

Methods

sing :: Sing NullStmt a #

SingI CursorKind DeclStmt Source # 

Methods

sing :: Sing DeclStmt a #

SingI CursorKind OMPParallelDirective Source # 
SingI CursorKind OMPSimdDirective Source # 
SingI CursorKind OMPForDirective Source # 
SingI CursorKind OMPSectionsDirective Source # 
SingI CursorKind OMPSectionDirective Source # 
SingI CursorKind OMPSingleDirective Source # 
SingI CursorKind OMPParallelForDirective Source # 
SingI CursorKind OMPParallelSectionsDirective Source # 
SingI CursorKind OMPTaskDirective Source # 
SingI CursorKind OMPMasterDirective Source # 
SingI CursorKind OMPCriticalDirective Source # 
SingI CursorKind OMPTaskyieldDirective Source # 
SingI CursorKind OMPBarrierDirective Source # 
SingI CursorKind OMPTaskwaitDirective Source # 
SingI CursorKind OMPFlushDirective Source # 
SingI CursorKind SEHLeaveStmt Source # 

Methods

sing :: Sing SEHLeaveStmt a #

SingI CursorKind LastStmt Source # 

Methods

sing :: Sing LastStmt a #

SingI CursorKind TranslationUnit Source # 
SingI CursorKind FirstAttr Source # 

Methods

sing :: Sing FirstAttr a #

SingI CursorKind UnexposedAttr Source # 

Methods

sing :: Sing UnexposedAttr a #

SingI CursorKind IBActionAttr Source # 

Methods

sing :: Sing IBActionAttr a #

SingI CursorKind IBOutletAttr Source # 

Methods

sing :: Sing IBOutletAttr a #

SingI CursorKind IBOutletCollectionAttr Source # 
SingI CursorKind CXXFinalAttr Source # 

Methods

sing :: Sing CXXFinalAttr a #

SingI CursorKind CXXOverrideAttr Source # 
SingI CursorKind AnnotateAttr Source # 

Methods

sing :: Sing AnnotateAttr a #

SingI CursorKind AsmLabelAttr Source # 

Methods

sing :: Sing AsmLabelAttr a #

SingI CursorKind PackedAttr Source # 

Methods

sing :: Sing PackedAttr a #

SingI CursorKind PureAttr Source # 

Methods

sing :: Sing PureAttr a #

SingI CursorKind ConstAttr Source # 

Methods

sing :: Sing ConstAttr a #

SingI CursorKind NoDuplicateAttr Source # 
SingI CursorKind CUDAConstantAttr Source # 
SingI CursorKind CUDADeviceAttr Source # 
SingI CursorKind CUDAGlobalAttr Source # 
SingI CursorKind CUDAHostAttr Source # 

Methods

sing :: Sing CUDAHostAttr a #

SingI CursorKind LastAttr Source # 

Methods

sing :: Sing LastAttr a #

SingI CursorKind PreprocessingDirective Source # 
SingI CursorKind MacroDefinition Source # 
SingI CursorKind MacroExpansion Source # 
SingI CursorKind MacroInstantiation Source # 
SingI CursorKind InclusionDirective Source # 
SingI CursorKind FirstPreprocessing Source # 
SingI CursorKind LastPreprocessing Source # 
SingI CursorKind ModuleImportDecl Source # 
SingI CursorKind FirstExtraDecl Source # 
SingI CursorKind LastExtraDecl Source # 

Methods

sing :: Sing LastExtraDecl a #

data Sing CursorKind Source # 
data Sing CursorKind where
type Demote CursorKind Source #