| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Clang
Description
LibClang is a Haskell binding to the libclang library, a compiler front-end for C-family languages. It allows you to produce and walk an AST, get a list of diagnostic warnings and errors, perform code completion, and more.
Your starting point for using LibClang should be this module, which
exports the ClangT monad and the functions you'll need to start
analyzing source code. The other modules in this library, such as
Clang.Cursor and Clang.Type, are meant to be imported
qualified, and provide the functions you'll need to get more
detailed information about the AST.
- parseSourceFile :: ClangBase m => FilePath -> [String] -> (forall s. TranslationUnit s -> ClangT s m a) -> m (Maybe a)
- type CursorList s = Vector (Cursor s)
- getChildren :: ClangBase m => Cursor s' -> ClangT s m (CursorList s)
- getDescendants :: ClangBase m => Cursor s' -> ClangT s m (CursorList s)
- getDeclarations :: ClangBase m => TranslationUnit s' -> ClangT s m (CursorList s)
- getReferences :: ClangBase m => TranslationUnit s' -> ClangT s m (CursorList s)
- getDeclarationsAndReferences :: ClangBase m => TranslationUnit s' -> ClangT s m (CursorList s, CursorList s)
- type ParentedCursorList s = Vector (ParentedCursor s)
- getParentedDescendants :: ClangBase m => Cursor s' -> ClangT s m (ParentedCursorList s)
- getParentedDeclarations :: ClangBase m => TranslationUnit s' -> ClangT s m (ParentedCursorList s)
- getParentedReferences :: ClangBase m => TranslationUnit s' -> ClangT s m (ParentedCursorList s)
- getParentedDeclarationsAndReferences :: ClangBase m => TranslationUnit s' -> ClangT s m (ParentedCursorList s, ParentedCursorList s)
- data Inclusion s = Inclusion !(File s) !(SourceLocation s) !Bool
- type InclusionList s = Vector (Inclusion s)
- getInclusions :: ClangBase m => TranslationUnit s' -> ClangT s m (InclusionList s)
- data ClangT s m a
- type Clang s a = ClangT s IO a
- type ClangBase m = MonadResourceBase m
- class ClangValue v where
- fromOuterScope :: ClangBase m => v s' -> ClangT s m (v s)
- class ClangValueList v where
- listFromOuterScope :: ClangBase m => Vector (v s') -> ClangT s m (Vector (v s))
- clangScope :: ClangBase m => (forall s. ClangT s m a) -> ClangT s' m a
- data AvailabilityKind
- data CursorKind
- = UnexposedDeclCursor
- | StructDeclCursor
- | UnionDeclCursor
- | ClassDeclCursor
- | EnumDeclCursor
- | FieldDeclCursor
- | EnumConstantDeclCursor
- | FunctionDeclCursor
- | VarDeclCursor
- | ParmDeclCursor
- | ObjCInterfaceDeclCursor
- | ObjCCategoryDeclCursor
- | ObjCProtocolDeclCursor
- | ObjCPropertyDeclCursor
- | ObjCIvarDeclCursor
- | ObjCInstanceMethodDeclCursor
- | ObjCClassMethodDeclCursor
- | ObjCImplementationDeclCursor
- | ObjCCategoryImplDeclCursor
- | TypedefDeclCursor
- | CXXMethodCursor
- | NamespaceCursor
- | LinkageSpecCursor
- | ConstructorCursor
- | DestructorCursor
- | ConversionFunctionCursor
- | TemplateTypeParameterCursor
- | NonTypeTemplateParameterCursor
- | TemplateTemplateParameterCursor
- | FunctionTemplateCursor
- | ClassTemplateCursor
- | ClassTemplatePartialSpecializationCursor
- | NamespaceAliasCursor
- | UsingDirectiveCursor
- | UsingDeclarationCursor
- | TypeAliasDeclCursor
- | ObjCSynthesizeDeclCursor
- | ObjCDynamicDeclCursor
- | CXXAccessSpecifierCursor
- | ObjCSuperClassRefCursor
- | ObjCProtocolRefCursor
- | ObjCClassRefCursor
- | TypeRefCursor
- | CXXBaseSpecifierCursor
- | TemplateRefCursor
- | NamespaceRefCursor
- | MemberRefCursor
- | LabelRefCursor
- | OverloadedDeclRefCursor
- | VariableRefCursor
- | InvalidFileCursor
- | NoDeclFoundCursor
- | NotImplementedCursor
- | InvalidCodeCursor
- | UnexposedExprCursor
- | DeclRefExprCursor
- | MemberRefExprCursor
- | CallExprCursor
- | ObjCMessageExprCursor
- | BlockExprCursor
- | IntegerLiteralCursor
- | FloatingLiteralCursor
- | ImaginaryLiteralCursor
- | StringLiteralCursor
- | CharacterLiteralCursor
- | ParenExprCursor
- | UnaryOperatorCursor
- | ArraySubscriptExprCursor
- | BinaryOperatorCursor
- | CompoundAssignOperatorCursor
- | ConditionalOperatorCursor
- | CStyleCastExprCursor
- | CompoundLiteralExprCursor
- | InitListExprCursor
- | AddrLabelExprCursor
- | StmtExprCursor
- | GenericSelectionExprCursor
- | GNUNullExprCursor
- | CXXStaticCastExprCursor
- | CXXDynamicCastExprCursor
- | CXXReinterpretCastExprCursor
- | CXXConstCastExprCursor
- | CXXFunctionalCastExprCursor
- | CXXTypeidExprCursor
- | CXXBoolLiteralExprCursor
- | CXXNullPtrLiteralExprCursor
- | CXXThisExprCursor
- | CXXThrowExprCursor
- | CXXNewExprCursor
- | CXXDeleteExprCursor
- | UnaryExprCursor
- | ObjCStringLiteralCursor
- | ObjCEncodeExprCursor
- | ObjCSelectorExprCursor
- | ObjCProtocolExprCursor
- | ObjCBridgedCastExprCursor
- | PackExpansionExprCursor
- | SizeOfPackExprCursor
- | LambdaExprCursor
- | ObjCBoolLiteralExprCursor
- | ObjCSelfExprCursor
- | UnexposedStmtCursor
- | LabelStmtCursor
- | CompoundStmtCursor
- | CaseStmtCursor
- | DefaultStmtCursor
- | IfStmtCursor
- | SwitchStmtCursor
- | WhileStmtCursor
- | DoStmtCursor
- | ForStmtCursor
- | GotoStmtCursor
- | IndirectGotoStmtCursor
- | ContinueStmtCursor
- | BreakStmtCursor
- | ReturnStmtCursor
- | AsmStmtCursor
- | ObjCAtTryStmtCursor
- | ObjCAtCatchStmtCursor
- | ObjCAtFinallyStmtCursor
- | ObjCAtThrowStmtCursor
- | ObjCAtSynchronizedStmtCursor
- | ObjCAutoreleasePoolStmtCursor
- | ObjCForCollectionStmtCursor
- | CXXCatchStmtCursor
- | CXXTryStmtCursor
- | CXXForRangeStmtCursor
- | SEHTryStmtCursor
- | SEHExceptStmtCursor
- | SEHFinallyStmtCursor
- | MSAsmStmtCursor
- | NullStmtCursor
- | DeclStmtCursor
- | OMPParallelDirectiveCursor
- | TranslationUnitCursor
- | UnexposedAttrCursor
- | IBActionAttrCursor
- | IBOutletAttrCursor
- | IBOutletCollectionAttrCursor
- | CXXFinalAttrCursor
- | CXXOverrideAttrCursor
- | AnnotateAttrCursor
- | AsmLabelAttrCursor
- | PackedAttrCursor
- | PreprocessingDirectiveCursor
- | MacroDefinitionCursor
- | MacroExpansionCursor
- | InclusionDirectiveCursor
- | ModuleImportDeclCursor
- data LinkageKind
- data LanguageKind
- data Cursor s
- data CursorSet s
- data ParentedCursor s = ParentedCursor {
- parentCursor :: !(Cursor s)
- childCursor :: !(Cursor s)
- data ObjCPropertyAttrKind
- = ObjCPropertyAttr_noattr
- | ObjCPropertyAttr_readonly
- | ObjCPropertyAttr_getter
- | ObjCPropertyAttr_assign
- | ObjCPropertyAttr_readwrite
- | ObjCPropertyAttr_retain
- | ObjCPropertyAttr_copy
- | ObjCPropertyAttr_nonatomic
- | ObjCPropertyAttr_setter
- | ObjCPropertyAttr_atomic
- | ObjCPropertyAttr_weak
- | ObjCPropertyAttr_strong
- | ObjCPropertyAttr_unsafe_unretained
- data ObjCDeclQualifierKind
- data NameRefFlags
- data Version = Version {
- majorVersion :: !Int
- minorVersion :: !Int
- subminorVersion :: !Int
- data PlatformAvailability = PlatformAvailability {}
- data PlatformAvailabilityInfo s = PlatformAvailabilityInfo {}
- data Diagnostic s
- data DiagnosticSet s
- data File s
- data Remapping s
- data SourceLocation s
- data SourceRange s
- data ClangString s
- data Token s
- data TokenKind
- data Index s
- data TranslationUnit s
- data UnsavedFile
- newtype Module s = Module {}
- data Type s
- data TypeKind
- = Type_Invalid
- | Type_Unexposed
- | Type_Void
- | Type_Bool
- | Type_Char_U
- | Type_UChar
- | Type_Char16
- | Type_Char32
- | Type_UShort
- | Type_UInt
- | Type_ULong
- | Type_ULongLong
- | Type_UInt128
- | Type_Char_S
- | Type_SChar
- | Type_WChar
- | Type_Short
- | Type_Int
- | Type_Long
- | Type_LongLong
- | Type_Int128
- | Type_Float
- | Type_Double
- | Type_LongDouble
- | Type_NullPtr
- | Type_Overload
- | Type_Dependent
- | Type_ObjCId
- | Type_ObjCClass
- | Type_ObjCSel
- | Type_Complex
- | Type_Pointer
- | Type_BlockPointer
- | Type_LValueReference
- | Type_RValueReference
- | Type_Record
- | Type_Enum
- | Type_Typedef
- | Type_ObjCInterface
- | Type_ObjCObjectPointer
- | Type_FunctionNoProto
- | Type_FunctionProto
- | Type_ConstantArray
- | Type_Vector
- | Type_IncompleteArray
- | Type_VariableArray
- | Type_DependentSizedArray
- | Type_MemberPointer
- data CallingConv
- = CallingConv_Default
- | CallingConv_C
- | CallingConv_X86StdCall
- | CallingConv_X86FastCall
- | CallingConv_X86ThisCall
- | CallingConv_X86Pascal
- | CallingConv_AAPCS
- | CallingConv_AAPCS_VFP
- | CallingConv_PnaclCall
- | CallingConv_IntelOclBic
- | CallingConv_X86_64Win64
- | CallingConv_X86_64SysV
- | CallingConv_Invalid
- | CallingConv_Unexposed
- data CXXAccessSpecifier
- data TypeLayoutError
- data RefQualifierKind
Parsing
Arguments
| :: ClangBase m | |
| => FilePath | Source filename |
| -> [String] | Clang-compatible compilation arguments |
| -> (forall s. TranslationUnit s -> ClangT s m a) | Callback |
| -> m (Maybe a) |
Parses a source file using libclang and allows you to analyze the resulting AST using a callback.
More flexible alternatives to parseSourceFile are available in
Clang.Index and Clang.TranslationUnit.
Traversing the AST
type CursorList s = Vector (Cursor s) Source
getChildren :: ClangBase m => Cursor s' -> ClangT s m (CursorList s) Source
Gets an CursorList of the children of this Cursor.
getDescendants :: ClangBase m => Cursor s' -> ClangT s m (CursorList s) Source
Gets an CursorList of all descendants of this
Cursor. If you are planning on visiting all the descendants
anyway, this is often more efficient than calling getChildren
repeatedly. The descendants are listed according to a preorder
traversal of the AST.
getDeclarations :: ClangBase m => TranslationUnit s' -> ClangT s m (CursorList s) Source
Gets an CursorList of all declarations in this TranslationUnit.
getReferences :: ClangBase m => TranslationUnit s' -> ClangT s m (CursorList s) Source
Gets an CursorList of all references in this TranslationUnit.
getDeclarationsAndReferences :: ClangBase m => TranslationUnit s' -> ClangT s m (CursorList s, CursorList s) Source
Gets two CursorLists, one containing all declarations in
this TranslationUnit, and another containing all
references. If you need both lists, this is more efficient than
calling getDeclarations and getReferences individually, as it
only traverses the AST once.
type ParentedCursorList s = Vector (ParentedCursor s) Source
getParentedDescendants :: ClangBase m => Cursor s' -> ClangT s m (ParentedCursorList s) Source
Like getDescendants, but each descendant is annotated with its
parent AST node. This provides enough information to replicate the
preorder traversal of the AST, but maintains the performance
benefits relative to getChildren.
getParentedDeclarations :: ClangBase m => TranslationUnit s' -> ClangT s m (ParentedCursorList s) Source
Like getDeclarations, but each declaration is annotated with
its parent AST node.
getParentedReferences :: ClangBase m => TranslationUnit s' -> ClangT s m (ParentedCursorList s) Source
Like getReferences, but each reference is annotated with
its parent AST node.
getParentedDeclarationsAndReferences :: ClangBase m => TranslationUnit s' -> ClangT s m (ParentedCursorList s, ParentedCursorList s) Source
Like getDeclarationsAndReferences, but each reference is annotated with
its parent AST node.
Traversing inclusions
Constructors
| Inclusion !(File s) !(SourceLocation s) !Bool |
type InclusionList s = Vector (Inclusion s) Source
getInclusions :: ClangBase m => TranslationUnit s' -> ClangT s m (InclusionList s) Source
Gets all inclusions in this TranslationUnit.
The ClangT monad
Instances
| MonadBase b m => MonadBase b (ClangT s m) Source | |
| MonadTrans (ClangT s) Source | |
| Monad m => Monad (ClangT s m) Source | |
| Functor m => Functor (ClangT s m) Source | |
| Applicative m => Applicative (ClangT s m) Source | |
| MonadIO m => MonadIO (ClangT s m) Source | |
| ClangBase m => MonadResource (ClangT s m) Source | |
| MonadThrow m => MonadThrow (ClangT s m) Source |
class ClangValue v where Source
Minimal complete definition
Nothing
Methods
fromOuterScope :: ClangBase m => v s' -> ClangT s m (v s) Source
Promotes a value from an outer scope to the current inner scope. The value's lifetime remains that of the outer scope. This is never necessary, but it may allow you to write code more naturally in some situations, since it can occasionally be inconvenient that variables from different scopes are different types.
Instances
class ClangValueList v where Source
Minimal complete definition
Nothing
Methods
listFromOuterScope :: ClangBase m => Vector (v s') -> ClangT s m (Vector (v s)) Source
Promotes a list from an outer scope to the current inner scope. The list's lifetime remains that of the outer scope. This is never necessary, but it may allow you to write code more naturally in some situations, since it can occasionally be inconvenient that variables from different scopes are different types.
clangScope :: ClangBase m => (forall s. ClangT s m a) -> ClangT s' m a Source
Runs a monadic computation with libclang and frees all the resources allocated by that computation immediately.
Clang AST types
data AvailabilityKind Source
data CursorKind Source
Constructors
data LinkageKind Source
data LanguageKind Source
Constructors
| Language_Invalid | |
| Language_C | |
| Language_ObjC | |
| Language_CPlusPlus |
data ParentedCursor s Source
Constructors
| ParentedCursor | |
Fields
| |
Instances
data ObjCPropertyAttrKind Source
Constructors
data NameRefFlags Source
Constructors
| Version | |
Fields
| |
data PlatformAvailability Source
Constructors
| PlatformAvailability | |
data PlatformAvailabilityInfo s Source
Constructors
| PlatformAvailabilityInfo | |
data Diagnostic s Source
Instances
| ClangValue Diagnostic Source | |
| Eq (Diagnostic s) Source | |
| Ord (Diagnostic s) Source |
data DiagnosticSet s Source
Instances
data SourceLocation s Source
Instances
data SourceRange s Source
Instances
| ClangValue SourceRange Source | |
| Eq (SourceRange s) Source | |
| Ord (SourceRange s) Source | |
| Storable (SourceRange s) Source |
data ClangString s Source
Instances
| ClangValue ClangString Source | |
| Eq (ClangString s) Source | |
| Ord (ClangString s) Source | |
| Storable (ClangString s) Source | |
| Hashable (ClangString s) Source |
data TranslationUnit s Source
Instances
Constructors
data CallingConv Source
Constructors
data CXXAccessSpecifier Source
Constructors
| CXXInvalidAccessSpecifier | |
| CXXPublic | |
| CXXProtected | |
| CXXPrivate |