Safe Haskell | None |
---|---|
Language | Haskell2010 |
TreeSitter.CApi
Synopsis
- type TREE_SITTER_LANGUAGE_VERSION = 14
- type TREE_SITTER_MIN_COMPATIBLE_LANGUAGE_VERSION = 13
- newtype TSStateId = TSStateId Word16
- newtype TSSymbol = TSSymbol Word16
- newtype TSFieldId = TSFieldId Word16
- data TSLanguage
- data TSParser
- data TSTree
- data TSQuery
- data TSQueryCursor
- data TSLookaheadIterator
- newtype TSInputEncoding where
- TSInputEncoding { }
- pattern TSInputEncodingUTF8 :: TSInputEncoding
- pattern TSInputEncodingUTF16 :: TSInputEncoding
- newtype TSSymbolType where
- TSSymbolType { }
- pattern TSSymbolTypeRegular :: TSSymbolType
- pattern TSSymbolTypeAnonymous :: TSSymbolType
- pattern TSSymbolTypeSupertype :: TSSymbolType
- pattern TSSymbolTypeAuxiliary :: TSSymbolType
- data TSPoint = TSPoint {}
- data TSRange = TSRange {
- start_point :: !TSPoint
- end_point :: !TSPoint
- start_byte :: !Word32
- end_byte :: !Word32
- data TSInput
- type TSRead = Word32 -> Ptr TSPoint -> Ptr Word32 -> IO (ConstPtr CChar)
- newtype TSLogType where
- TSLogType { }
- pattern TSLogTypeParse :: TSLogType
- pattern TSLogTypeLex :: TSLogType
- data TSLogger
- type TSLog = TSLogType -> ConstPtr CChar -> IO ()
- data TSInputEdit = TSInputEdit {
- start_byte :: !Word32
- old_end_byte :: !Word32
- new_end_byte :: !Word32
- start_point :: !TSPoint
- old_end_point :: !TSPoint
- new_end_point :: !TSPoint
- data TSNode = TSNode {}
- data TSNodeContext = TSNodeContext !Word32 !Word32 !Word32 !Word32
- data TSTreeCursor = TSTreeCursor {}
- data TSTreeCursorContext = TSTreeCursorContext !Word32 !Word32 !Word32
- data TSQueryCapture = TSQueryCapture {}
- newtype TSQuantifier where
- TSQuantifier { }
- pattern TSQuantifierZero :: TSQuantifier
- pattern TSQuantifierZeroOrOne :: TSQuantifier
- pattern TSQuantifierZeroOrMore :: TSQuantifier
- pattern TSQuantifierOne :: TSQuantifier
- pattern TSQuantifierOneOrMore :: TSQuantifier
- data TSQueryMatch = TSQueryMatch {
- _id :: !Word32
- _pattern_index :: !Word16
- _captures :: ![TSQueryCapture]
- newtype TSQueryPredicateStepType where
- data TSQueryPredicateStep = TSQueryPredicateStep {}
- newtype TSQueryError where
- TSQueryError { }
- pattern TSQueryErrorNone :: TSQueryError
- pattern TSQueryErrorSyntax :: TSQueryError
- pattern TSQueryErrorNodeType :: TSQueryError
- pattern TSQueryErrorField :: TSQueryError
- pattern TSQueryErrorCapture :: TSQueryError
- pattern TSQueryErrorStructure :: TSQueryError
- pattern TSQueryErrorLanguage :: TSQueryError
- ts_parser_new :: IO (Ptr TSParser)
- ts_parser_delete :: Ptr TSParser -> IO ()
- p_ts_parser_delete :: FunPtr (Ptr TSParser -> IO ())
- ts_parser_language :: ConstPtr TSParser -> IO (ConstPtr TSLanguage)
- ts_parser_set_language :: Ptr TSParser -> ConstPtr TSLanguage -> IO CBool
- ts_parser_set_included_ranges :: Ptr TSParser -> ConstPtr TSRange -> Word32 -> IO CBool
- ts_parser_included_ranges :: ConstPtr TSParser -> Ptr Word32 -> IO (ConstPtr TSRange)
- ts_parser_set_logger :: Ptr TSParser -> TSLog -> IO ()
- ts_parser_logger :: ConstPtr TSParser -> IO (Maybe TSLog)
- ts_parser_remove_logger :: Ptr TSParser -> IO (Maybe TSLog)
- ts_parser_parse :: Ptr TSParser -> ConstPtr TSTree -> TSRead -> TSInputEncoding -> IO (Ptr TSTree)
- ts_parser_parse_string :: Ptr TSParser -> ConstPtr TSTree -> ConstPtr CChar -> Word32 -> IO (Ptr TSTree)
- ts_parser_parse_string_encoding :: Ptr TSParser -> ConstPtr TSTree -> ConstPtr CChar -> Word32 -> TSInputEncoding -> IO (Ptr TSTree)
- ts_parser_reset :: Ptr TSParser -> IO ()
- ts_parser_set_timeout_micros :: Ptr TSParser -> Word64 -> IO ()
- ts_parser_timeout_micros :: Ptr TSParser -> IO Word64
- ts_parser_set_cancellation_flag :: Ptr TSParser -> ConstPtr CSize -> IO ()
- ts_parser_cancellation_flag :: ConstPtr TSParser -> IO (ConstPtr CSize)
- ts_parser_print_dot_graphs :: Ptr TSParser -> Int32 -> IO ()
- ts_tree_copy :: Ptr TSTree -> IO (Ptr TSTree)
- ts_tree_delete :: Ptr TSTree -> IO ()
- p_ts_tree_delete :: FunPtr (Ptr TSTree -> IO ())
- ts_tree_language :: Ptr TSTree -> IO (ConstPtr TSLanguage)
- ts_tree_included_ranges :: Ptr TSTree -> Ptr Word32 -> IO (Ptr TSRange)
- ts_tree_edit :: Ptr TSTree -> Ptr TSInputEdit -> IO ()
- ts_tree_get_changed_ranges :: Ptr TSTree -> Ptr TSTree -> Ptr Word32 -> IO (Ptr TSRange)
- ts_tree_print_dot_graph :: Ptr TSTree -> Int32 -> IO ()
- ts_tree_root_node :: ConstPtr TSTree -> IO TSNode
- ts_tree_root_node_with_offset :: ConstPtr TSTree -> Word32 -> TSPoint -> IO TSNode
- ts_node_type :: TSNode -> IO (ConstPtr CChar)
- ts_node_symbol :: TSNode -> IO TSSymbol
- ts_node_language :: TSNode -> IO (ConstPtr TSLanguage)
- ts_node_grammar_type :: TSNode -> IO (ConstPtr CChar)
- ts_node_grammar_symbol :: TSNode -> IO TSSymbol
- ts_node_start_byte :: TSNode -> IO Word32
- ts_node_start_point :: TSNode -> IO TSPoint
- ts_node_end_byte :: TSNode -> IO Word32
- ts_node_end_point :: TSNode -> IO TSPoint
- ts_node_string :: TSNode -> IO (Ptr CChar)
- ts_node_is_null :: TSNode -> IO CBool
- ts_node_is_named :: TSNode -> IO CBool
- ts_node_is_missing :: TSNode -> IO CBool
- ts_node_is_extra :: TSNode -> IO CBool
- ts_node_has_changes :: TSNode -> IO CBool
- ts_node_has_error :: TSNode -> IO CBool
- ts_node_is_error :: TSNode -> IO CBool
- ts_node_parse_state :: TSNode -> IO TSStateId
- ts_node_next_parse_state :: TSNode -> IO TSStateId
- ts_node_parent :: TSNode -> IO TSNode
- ts_node_child_with_descendant :: TSNode -> TSNode -> IO TSNode
- ts_node_child :: TSNode -> Word32 -> IO TSNode
- ts_node_field_name_for_child :: TSNode -> Word32 -> IO (ConstPtr CChar)
- ts_node_field_name_for_named_child :: TSNode -> Word32 -> IO (ConstPtr CChar)
- ts_node_child_count :: TSNode -> IO Word32
- ts_node_named_child :: TSNode -> Word32 -> IO TSNode
- ts_node_named_child_count :: TSNode -> IO Word32
- ts_node_child_by_field_name :: TSNode -> ConstPtr CChar -> Word32 -> IO TSNode
- ts_node_child_by_field_id :: TSNode -> TSFieldId -> IO TSNode
- ts_node_next_sibling :: TSNode -> IO TSNode
- ts_node_prev_sibling :: TSNode -> IO TSNode
- ts_node_next_named_sibling :: TSNode -> IO TSNode
- ts_node_prev_named_sibling :: TSNode -> IO TSNode
- ts_node_first_child_for_byte :: TSNode -> Word32 -> IO TSNode
- ts_node_first_named_child_for_byte :: TSNode -> Word32 -> IO TSNode
- ts_node_descendant_count :: TSNode -> IO Word32
- ts_node_descendant_for_byte_range :: TSNode -> Word32 -> Word32 -> IO TSNode
- ts_node_descendant_for_point_range :: TSNode -> TSPoint -> TSPoint -> IO TSNode
- ts_node_named_descendant_for_byte_range :: TSNode -> Word32 -> Word32 -> IO TSNode
- ts_node_named_descendant_for_point_range :: TSNode -> TSPoint -> TSPoint -> IO TSNode
- ts_node_edit :: Ptr TSNode -> ConstPtr TSInputEdit -> IO ()
- ts_node_eq :: TSNode -> TSNode -> IO CBool
- ts_tree_cursor_new :: TSNode -> IO TSTreeCursor
- ts_tree_cursor_new_p :: TSNode -> Ptr TSTreeCursor -> IO ()
- ts_tree_cursor_delete :: Ptr TSTreeCursor -> IO ()
- p_ts_tree_cursor_delete :: FunPtr (Ptr TSTreeCursor -> IO ())
- ts_tree_cursor_reset :: Ptr TSTreeCursor -> TSNode -> IO ()
- ts_tree_cursor_reset_to :: Ptr TSTreeCursor -> ConstPtr TSTreeCursor -> IO ()
- ts_tree_cursor_current_node :: ConstPtr TSTreeCursor -> IO TSNode
- ts_tree_cursor_current_field_name :: ConstPtr TSTreeCursor -> IO (ConstPtr CChar)
- ts_tree_cursor_current_field_id :: ConstPtr TSTreeCursor -> IO TSFieldId
- ts_tree_cursor_goto_parent :: Ptr TSTreeCursor -> IO CBool
- ts_tree_cursor_goto_next_sibling :: Ptr TSTreeCursor -> IO CBool
- ts_tree_cursor_goto_previous_sibling :: Ptr TSTreeCursor -> IO CBool
- ts_tree_cursor_goto_first_child :: Ptr TSTreeCursor -> IO CBool
- ts_tree_cursor_goto_last_child :: Ptr TSTreeCursor -> IO CBool
- ts_tree_cursor_goto_descendant :: Ptr TSTreeCursor -> Word32 -> IO ()
- ts_tree_cursor_current_descendant_index :: ConstPtr TSTreeCursor -> IO Word32
- ts_tree_cursor_current_depth :: ConstPtr TSTreeCursor -> IO Word32
- ts_tree_cursor_goto_first_child_for_byte :: Ptr TSTreeCursor -> Word32 -> IO Int64
- ts_tree_cursor_goto_first_child_for_point :: Ptr TSTreeCursor -> TSPoint -> IO Int64
- ts_tree_cursor_copy :: Ptr TSTreeCursor -> IO TSTreeCursor
- ts_tree_cursor_copy_p :: Ptr TSTreeCursor -> Ptr TSTreeCursor -> IO ()
- ts_query_new :: ConstPtr TSLanguage -> ConstPtr CChar -> Word32 -> Ptr Word32 -> Ptr TSQueryError -> IO (Ptr TSQuery)
- ts_query_delete :: Ptr TSQuery -> IO ()
- p_ts_query_delete :: FunPtr (Ptr TSQuery -> IO ())
- ts_query_pattern_count :: ConstPtr TSQuery -> IO Word32
- ts_query_capture_count :: ConstPtr TSQuery -> IO Word32
- ts_query_string_count :: ConstPtr TSQuery -> IO Word32
- ts_query_start_byte_for_pattern :: ConstPtr TSQuery -> Word32 -> IO Word32
- ts_query_end_byte_for_pattern :: ConstPtr TSQuery -> Word32 -> IO Word32
- ts_query_predicates_for_pattern :: ConstPtr TSQuery -> Word32 -> Ptr Word32 -> IO (ConstPtr TSQueryPredicateStep)
- ts_query_is_pattern_rooted :: ConstPtr TSQuery -> Word32 -> IO CBool
- ts_query_is_pattern_non_local :: ConstPtr TSQuery -> Word32 -> IO CBool
- ts_query_is_pattern_guaranteed_at_step :: ConstPtr TSQuery -> Word32 -> IO CBool
- ts_query_capture_name_for_id :: ConstPtr TSQuery -> Word32 -> Ptr Word32 -> IO (ConstPtr CChar)
- ts_query_capture_quantifier_for_id :: ConstPtr TSQuery -> Word32 -> Word32 -> IO TSQuantifier
- ts_query_string_value_for_id :: ConstPtr TSQuery -> Word32 -> Ptr Word32 -> IO (ConstPtr CChar)
- ts_query_disable_capture :: Ptr TSQuery -> ConstPtr CChar -> Word32 -> IO ()
- ts_query_disable_pattern :: Ptr TSQuery -> Word32 -> IO ()
- ts_query_cursor_new :: IO (Ptr TSQueryCursor)
- ts_query_cursor_delete :: Ptr TSQueryCursor -> IO ()
- p_ts_query_cursor_delete :: FunPtr (Ptr TSQueryCursor -> IO ())
- ts_query_cursor_exec :: Ptr TSQueryCursor -> ConstPtr TSQuery -> TSNode -> IO ()
- ts_query_cursor_did_exceed_match_limit :: ConstPtr TSQueryCursor -> IO CBool
- ts_query_cursor_match_limit :: ConstPtr TSQueryCursor -> IO Word32
- ts_query_cursor_set_match_limit :: Ptr TSQueryCursor -> Word32 -> IO ()
- ts_query_cursor_set_timeout_micros :: Ptr TSQueryCursor -> Word64 -> IO ()
- ts_query_cursor_timeout_micros :: ConstPtr TSQueryCursor -> IO Word64
- ts_query_cursor_set_byte_range :: Ptr TSQueryCursor -> Word32 -> Word32 -> IO ()
- ts_query_cursor_set_point_range :: Ptr TSQueryCursor -> TSPoint -> TSPoint -> IO ()
- ts_query_cursor_next_match :: Ptr TSQueryCursor -> Ptr TSQueryMatch -> IO CBool
- ts_query_cursor_remove_match :: Ptr TSQueryCursor -> Word32 -> IO ()
- ts_query_cursor_next_capture :: Ptr TSQueryCursor -> Ptr TSQueryMatch -> Ptr Word32 -> IO CBool
- ts_query_cursor_set_max_start_depth :: Ptr TSQueryCursor -> Word32 -> IO ()
- ts_language_copy :: ConstPtr TSLanguage -> IO (ConstPtr TSLanguage)
- ts_language_delete :: ConstPtr TSLanguage -> IO ()
- p_ts_language_delete :: FunPtr (ConstPtr TSLanguage -> IO ())
- ts_language_symbol_count :: ConstPtr TSLanguage -> IO Word32
- ts_language_state_count :: ConstPtr TSLanguage -> IO Word32
- ts_language_symbol_name :: ConstPtr TSLanguage -> TSSymbol -> IO (ConstPtr CChar)
- ts_language_symbol_for_name :: ConstPtr TSLanguage -> ConstPtr CChar -> Word32 -> CBool -> IO TSSymbol
- ts_language_field_count :: ConstPtr TSLanguage -> IO Word32
- ts_language_field_name_for_id :: ConstPtr TSLanguage -> TSFieldId -> IO (ConstPtr CChar)
- ts_language_field_id_for_name :: ConstPtr TSLanguage -> ConstPtr CChar -> Word32 -> IO TSFieldId
- ts_language_symbol_type :: ConstPtr TSLanguage -> TSSymbol -> IO TSSymbolType
- ts_language_version :: ConstPtr TSLanguage -> IO Word32
- ts_language_next_state :: ConstPtr TSLanguage -> TSStateId -> TSSymbol -> IO TSStateId
- ts_lookahead_iterator_new :: ConstPtr TSLanguage -> TSStateId -> IO (Ptr TSLookaheadIterator)
- ts_lookahead_iterator_delete :: Ptr TSLookaheadIterator -> IO ()
- p_ts_lookahead_iterator_delete :: FunPtr (Ptr TSLookaheadIterator -> IO ())
- ts_lookahead_iterator_reset_state :: Ptr TSLookaheadIterator -> TSStateId -> IO CBool
- ts_lookahead_iterator_reset :: Ptr TSLookaheadIterator -> ConstPtr TSLanguage -> TSStateId -> IO CBool
- ts_lookahead_iterator_language :: Ptr TSLookaheadIterator -> IO (ConstPtr TSLanguage)
- ts_lookahead_iterator_next :: Ptr TSLookaheadIterator -> IO CBool
- ts_lookahead_iterator_current_symbol :: ConstPtr TSLookaheadIterator -> IO TSSymbol
- ts_lookahead_iterator_current_symbol_name :: ConstPtr TSLookaheadIterator -> IO (ConstPtr CChar)
- ts_set_allocator :: FunPtr (CSize -> IO ()) -> FunPtr (CSize -> CSize -> IO ()) -> FunPtr (Ptr a -> CSize -> IO ()) -> FunPtr (Ptr a -> IO ()) -> IO ()
ABI Versioning
type TREE_SITTER_LANGUAGE_VERSION = 14 Source #
The latest ABI version that is supported by the current version of the library. When Languages are generated by the Tree-sitter CLI, they are assigned an ABI version number that corresponds to the current CLI version. The Tree-sitter library is generally backwards-compatible with languages generated using older CLI versions, but is not forwards-compatible.
#define TREE_SITTER_LANGUAGE_VERSION 14
type TREE_SITTER_MIN_COMPATIBLE_LANGUAGE_VERSION = 13 Source #
The earliest ABI version that is supported by the current version of the library.
#define TREE_SITTER_MIN_COMPATIBLE_LANGUAGE_VERSION 13
Types
typedef uint16_t TSStateId;
Instances
Enum TSStateId Source # | |
Defined in TreeSitter.CApi Methods succ :: TSStateId -> TSStateId # pred :: TSStateId -> TSStateId # fromEnum :: TSStateId -> Int # enumFrom :: TSStateId -> [TSStateId] # enumFromThen :: TSStateId -> TSStateId -> [TSStateId] # enumFromTo :: TSStateId -> TSStateId -> [TSStateId] # enumFromThenTo :: TSStateId -> TSStateId -> TSStateId -> [TSStateId] # | |
Num TSStateId Source # | |
Defined in TreeSitter.CApi | |
Read TSStateId Source # | |
Integral TSStateId Source # | |
Defined in TreeSitter.CApi Methods quot :: TSStateId -> TSStateId -> TSStateId # rem :: TSStateId -> TSStateId -> TSStateId # div :: TSStateId -> TSStateId -> TSStateId # mod :: TSStateId -> TSStateId -> TSStateId # quotRem :: TSStateId -> TSStateId -> (TSStateId, TSStateId) # divMod :: TSStateId -> TSStateId -> (TSStateId, TSStateId) # | |
Real TSStateId Source # | |
Defined in TreeSitter.CApi Methods toRational :: TSStateId -> Rational # | |
Show TSStateId Source # | |
Eq TSStateId Source # | |
Ord TSStateId Source # | |
typedef uint16_t TSSymbol;
Instances
Enum TSSymbol Source # | |
Num TSSymbol Source # | |
Read TSSymbol Source # | |
Integral TSSymbol Source # | |
Defined in TreeSitter.CApi | |
Real TSSymbol Source # | |
Defined in TreeSitter.CApi Methods toRational :: TSSymbol -> Rational # | |
Show TSSymbol Source # | |
Eq TSSymbol Source # | |
Ord TSSymbol Source # | |
Defined in TreeSitter.CApi |
typedef uint16_t TSFieldId;
Instances
Enum TSFieldId Source # | |
Defined in TreeSitter.CApi Methods succ :: TSFieldId -> TSFieldId # pred :: TSFieldId -> TSFieldId # fromEnum :: TSFieldId -> Int # enumFrom :: TSFieldId -> [TSFieldId] # enumFromThen :: TSFieldId -> TSFieldId -> [TSFieldId] # enumFromTo :: TSFieldId -> TSFieldId -> [TSFieldId] # enumFromThenTo :: TSFieldId -> TSFieldId -> TSFieldId -> [TSFieldId] # | |
Num TSFieldId Source # | |
Defined in TreeSitter.CApi | |
Read TSFieldId Source # | |
Integral TSFieldId Source # | |
Defined in TreeSitter.CApi Methods quot :: TSFieldId -> TSFieldId -> TSFieldId # rem :: TSFieldId -> TSFieldId -> TSFieldId # div :: TSFieldId -> TSFieldId -> TSFieldId # mod :: TSFieldId -> TSFieldId -> TSFieldId # quotRem :: TSFieldId -> TSFieldId -> (TSFieldId, TSFieldId) # divMod :: TSFieldId -> TSFieldId -> (TSFieldId, TSFieldId) # | |
Real TSFieldId Source # | |
Defined in TreeSitter.CApi Methods toRational :: TSFieldId -> Rational # | |
Show TSFieldId Source # | |
Eq TSFieldId Source # | |
Ord TSFieldId Source # | |
data TSLanguage Source #
typedef struct TSLanguage TSLanguage;
data TSQueryCursor Source #
typedef struct TSQueryCursor TSQueryCursor;
data TSLookaheadIterator Source #
typedef struct TSLookaheadIterator TSLookaheadIterator;
newtype TSInputEncoding Source #
typedef enum TSInputEncoding { TSInputEncodingUTF8, TSInputEncodingUTF16, } TSInputEncoding;
Constructors
TSInputEncoding | |
Fields |
Bundled Patterns
pattern TSInputEncodingUTF8 :: TSInputEncoding | |
pattern TSInputEncodingUTF16 :: TSInputEncoding |
Instances
Storable TSInputEncoding Source # | |
Defined in TreeSitter.CApi Methods sizeOf :: TSInputEncoding -> Int # alignment :: TSInputEncoding -> Int # peekElemOff :: Ptr TSInputEncoding -> Int -> IO TSInputEncoding # pokeElemOff :: Ptr TSInputEncoding -> Int -> TSInputEncoding -> IO () # peekByteOff :: Ptr b -> Int -> IO TSInputEncoding # pokeByteOff :: Ptr b -> Int -> TSInputEncoding -> IO () # peek :: Ptr TSInputEncoding -> IO TSInputEncoding # poke :: Ptr TSInputEncoding -> TSInputEncoding -> IO () # | |
Show TSInputEncoding Source # | |
Defined in TreeSitter.CApi Methods showsPrec :: Int -> TSInputEncoding -> ShowS # show :: TSInputEncoding -> String # showList :: [TSInputEncoding] -> ShowS # | |
Eq TSInputEncoding Source # | |
Defined in TreeSitter.CApi Methods (==) :: TSInputEncoding -> TSInputEncoding -> Bool # (/=) :: TSInputEncoding -> TSInputEncoding -> Bool # |
newtype TSSymbolType Source #
typedef enum TSSymbolType { TSSymbolTypeRegular, TSSymbolTypeAnonymous, TSSymbolTypeSupertype, TSSymbolTypeAuxiliary, } TSSymbolType;
Constructors
TSSymbolType | |
Fields |
Bundled Patterns
pattern TSSymbolTypeRegular :: TSSymbolType | |
pattern TSSymbolTypeAnonymous :: TSSymbolType | |
pattern TSSymbolTypeSupertype :: TSSymbolType | |
pattern TSSymbolTypeAuxiliary :: TSSymbolType |
Instances
Show TSSymbolType Source # | |
Defined in TreeSitter.CApi Methods showsPrec :: Int -> TSSymbolType -> ShowS # show :: TSSymbolType -> String # showList :: [TSSymbolType] -> ShowS # | |
Eq TSSymbolType Source # | |
Defined in TreeSitter.CApi |
typedef struct TSPoint { uint32_t row; uint32_t column; } TSPoint;
Instances
Storable TSPoint Source # | |
Show TSPoint Source # | |
Eq TSPoint Source # | |
Ord TSPoint Source # | |
typedef struct TSRange { TSPoint start_point; TSPoint end_point; uint32_t start_byte; uint32_t end_byte; } TSRange;
Constructors
TSRange | |
Fields
|
Instances
Storable TSRange Source # | |
Show TSRange Source # | |
Eq TSRange Source # | |
typedef struct TSInput { void *payload; const char *(*read)( void *payload, uint32_t byte_index, TSPoint position, uint32_t *bytes_read ); TSInputEncoding encoding; } TSInput;
type TSRead = Word32 -> Ptr TSPoint -> Ptr Word32 -> IO (ConstPtr CChar) Source #
The type of the
argument of the read
function._wrap_ts_input_new
typedef const char *(*TSRead)( uint32_t byte_index, TSPoint *position, uint32_t *bytes_read );
typedef enum TSLogType { TSLogTypeParse, TSLogTypeLex, } TSLogType;
Constructors
TSLogType | |
Fields |
Bundled Patterns
pattern TSLogTypeParse :: TSLogType | |
pattern TSLogTypeLex :: TSLogType |
Instances
typedef struct TSLogger { void *payload; void (*log)(void *payload, TSLogType log_type, const char *buffer); } TSLogger;
type TSLog = TSLogType -> ConstPtr CChar -> IO () Source #
The type of the
argument of the log
function._wrap_ts_logger_new
void (*log)(TSLogType log_type, const char *buffer);
data TSInputEdit Source #
typedef struct TSInputEdit { uint32_t start_byte; uint32_t old_end_byte; uint32_t new_end_byte; TSPoint start_point; TSPoint old_end_point; TSPoint new_end_point; } TSInputEdit;
Constructors
TSInputEdit | |
Fields
|
Instances
Storable TSInputEdit Source # | |
Defined in TreeSitter.CApi Methods sizeOf :: TSInputEdit -> Int # alignment :: TSInputEdit -> Int # peekElemOff :: Ptr TSInputEdit -> Int -> IO TSInputEdit # pokeElemOff :: Ptr TSInputEdit -> Int -> TSInputEdit -> IO () # peekByteOff :: Ptr b -> Int -> IO TSInputEdit # pokeByteOff :: Ptr b -> Int -> TSInputEdit -> IO () # peek :: Ptr TSInputEdit -> IO TSInputEdit # poke :: Ptr TSInputEdit -> TSInputEdit -> IO () # | |
Show TSInputEdit Source # | |
Defined in TreeSitter.CApi Methods showsPrec :: Int -> TSInputEdit -> ShowS # show :: TSInputEdit -> String # showList :: [TSInputEdit] -> ShowS # | |
Eq TSInputEdit Source # | |
Defined in TreeSitter.CApi |
typedef struct TSNode { uint32_t context[4]; const void *id; const TSTree *tree; } TSNode;
Constructors
TSNode | |
data TSNodeContext Source #
Constructors
TSNodeContext !Word32 !Word32 !Word32 !Word32 |
data TSTreeCursor Source #
typedef struct TSTreeCursor { const void *tree; const void *id; uint32_t context[3]; } TSTreeCursor;
Constructors
TSTreeCursor | |
Instances
Storable TSTreeCursor Source # | |
Defined in TreeSitter.CApi Methods sizeOf :: TSTreeCursor -> Int # alignment :: TSTreeCursor -> Int # peekElemOff :: Ptr TSTreeCursor -> Int -> IO TSTreeCursor # pokeElemOff :: Ptr TSTreeCursor -> Int -> TSTreeCursor -> IO () # peekByteOff :: Ptr b -> Int -> IO TSTreeCursor # pokeByteOff :: Ptr b -> Int -> TSTreeCursor -> IO () # peek :: Ptr TSTreeCursor -> IO TSTreeCursor # poke :: Ptr TSTreeCursor -> TSTreeCursor -> IO () # |
data TSTreeCursorContext Source #
The type of the
field of a _context
struct.TSTreeCursor
uint32_t context[3];
Constructors
TSTreeCursorContext !Word32 !Word32 !Word32 |
data TSQueryCapture Source #
typedef struct TSQueryCapture { TSNode node; uint32_t index; } TSQueryCapture;
Constructors
TSQueryCapture | |
Instances
Storable TSQueryCapture Source # | |
Defined in TreeSitter.CApi Methods sizeOf :: TSQueryCapture -> Int # alignment :: TSQueryCapture -> Int # peekElemOff :: Ptr TSQueryCapture -> Int -> IO TSQueryCapture # pokeElemOff :: Ptr TSQueryCapture -> Int -> TSQueryCapture -> IO () # peekByteOff :: Ptr b -> Int -> IO TSQueryCapture # pokeByteOff :: Ptr b -> Int -> TSQueryCapture -> IO () # peek :: Ptr TSQueryCapture -> IO TSQueryCapture # poke :: Ptr TSQueryCapture -> TSQueryCapture -> IO () # |
newtype TSQuantifier Source #
typedef enum TSQuantifier { TSQuantifierZero = 0, // must match the array initialization value TSQuantifierZeroOrOne, TSQuantifierZeroOrMore, TSQuantifierOne, TSQuantifierOneOrMore, } TSQuantifier;
Constructors
TSQuantifier | |
Fields |
Bundled Patterns
pattern TSQuantifierZero :: TSQuantifier | |
pattern TSQuantifierZeroOrOne :: TSQuantifier | |
pattern TSQuantifierZeroOrMore :: TSQuantifier | |
pattern TSQuantifierOne :: TSQuantifier | |
pattern TSQuantifierOneOrMore :: TSQuantifier |
Instances
Storable TSQuantifier Source # | |
Defined in TreeSitter.CApi Methods sizeOf :: TSQuantifier -> Int # alignment :: TSQuantifier -> Int # peekElemOff :: Ptr TSQuantifier -> Int -> IO TSQuantifier # pokeElemOff :: Ptr TSQuantifier -> Int -> TSQuantifier -> IO () # peekByteOff :: Ptr b -> Int -> IO TSQuantifier # pokeByteOff :: Ptr b -> Int -> TSQuantifier -> IO () # peek :: Ptr TSQuantifier -> IO TSQuantifier # poke :: Ptr TSQuantifier -> TSQuantifier -> IO () # | |
Show TSQuantifier Source # | |
Defined in TreeSitter.CApi Methods showsPrec :: Int -> TSQuantifier -> ShowS # show :: TSQuantifier -> String # showList :: [TSQuantifier] -> ShowS # | |
Eq TSQuantifier Source # | |
Defined in TreeSitter.CApi |
data TSQueryMatch Source #
typedef struct TSQueryMatch { uint32_t id; uint16_t pattern_index; uint16_t capture_count; const TSQueryCapture *captures; } TSQueryMatch;
Constructors
TSQueryMatch | |
Fields
|
Instances
Storable TSQueryMatch Source # | |
Defined in TreeSitter.CApi Methods sizeOf :: TSQueryMatch -> Int # alignment :: TSQueryMatch -> Int # peekElemOff :: Ptr TSQueryMatch -> Int -> IO TSQueryMatch # pokeElemOff :: Ptr TSQueryMatch -> Int -> TSQueryMatch -> IO () # peekByteOff :: Ptr b -> Int -> IO TSQueryMatch # pokeByteOff :: Ptr b -> Int -> TSQueryMatch -> IO () # peek :: Ptr TSQueryMatch -> IO TSQueryMatch # poke :: Ptr TSQueryMatch -> TSQueryMatch -> IO () # |
newtype TSQueryPredicateStepType Source #
typedef enum TSQueryPredicateStepType { TSQueryPredicateStepTypeDone, TSQueryPredicateStepTypeCapture, TSQueryPredicateStepTypeString, } TSQueryPredicateStepType;
Constructors
TSQueryPredicateStepType | |
Fields |
Bundled Patterns
pattern TSQueryPredicateStepTypeDone :: TSQueryPredicateStepType | |
pattern TSQueryPredicateStepTypeCapture :: TSQueryPredicateStepType | |
pattern TSQueryPredicateStepTypeString :: TSQueryPredicateStepType |
Instances
data TSQueryPredicateStep Source #
typedef struct TSQueryPredicateStep { TSQueryPredicateStepType type; uint32_t value_id; } TSQueryPredicateStep;
Constructors
TSQueryPredicateStep | |
Fields
|
Instances
Storable TSQueryPredicateStep Source # | |
Defined in TreeSitter.CApi Methods sizeOf :: TSQueryPredicateStep -> Int # alignment :: TSQueryPredicateStep -> Int # peekElemOff :: Ptr TSQueryPredicateStep -> Int -> IO TSQueryPredicateStep # pokeElemOff :: Ptr TSQueryPredicateStep -> Int -> TSQueryPredicateStep -> IO () # peekByteOff :: Ptr b -> Int -> IO TSQueryPredicateStep # pokeByteOff :: Ptr b -> Int -> TSQueryPredicateStep -> IO () # peek :: Ptr TSQueryPredicateStep -> IO TSQueryPredicateStep # poke :: Ptr TSQueryPredicateStep -> TSQueryPredicateStep -> IO () # |
newtype TSQueryError Source #
typedef enum TSQueryError { TSQueryErrorNone = 0, TSQueryErrorSyntax, TSQueryErrorNodeType, TSQueryErrorField, TSQueryErrorCapture, TSQueryErrorStructure, TSQueryErrorLanguage, } TSQueryError;
Constructors
TSQueryError | |
Fields |
Bundled Patterns
pattern TSQueryErrorNone :: TSQueryError | |
pattern TSQueryErrorSyntax :: TSQueryError | |
pattern TSQueryErrorNodeType :: TSQueryError | |
pattern TSQueryErrorField :: TSQueryError | |
pattern TSQueryErrorCapture :: TSQueryError | |
pattern TSQueryErrorStructure :: TSQueryError | |
pattern TSQueryErrorLanguage :: TSQueryError |
Instances
Storable TSQueryError Source # | |
Defined in TreeSitter.CApi Methods sizeOf :: TSQueryError -> Int # alignment :: TSQueryError -> Int # peekElemOff :: Ptr TSQueryError -> Int -> IO TSQueryError # pokeElemOff :: Ptr TSQueryError -> Int -> TSQueryError -> IO () # peekByteOff :: Ptr b -> Int -> IO TSQueryError # pokeByteOff :: Ptr b -> Int -> TSQueryError -> IO () # peek :: Ptr TSQueryError -> IO TSQueryError # poke :: Ptr TSQueryError -> TSQueryError -> IO () # | |
Show TSQueryError Source # | |
Defined in TreeSitter.CApi Methods showsPrec :: Int -> TSQueryError -> ShowS # show :: TSQueryError -> String # showList :: [TSQueryError] -> ShowS # | |
Eq TSQueryError Source # | |
Defined in TreeSitter.CApi |
Parser
ts_parser_delete :: Ptr TSParser -> IO () Source #
Delete the parser, freeing all of the memory that it used.
void ts_parser_delete(TSParser *self);
p_ts_parser_delete :: FunPtr (Ptr TSParser -> IO ()) Source #
C function pointer to
.ts_parser_delete
ts_parser_language :: ConstPtr TSParser -> IO (ConstPtr TSLanguage) Source #
Get the parser's current language.
const TSLanguage *ts_parser_language(const TSParser *self);
ts_parser_set_language :: Ptr TSParser -> ConstPtr TSLanguage -> IO CBool Source #
Set the language that the parser should use for parsing.
Returns a boolean indicating whether or not the language was successfully
assigned. True means assignment succeeded. False means there was a version
mismatch: the language was generated with an incompatible version of the
Tree-sitter CLI. Check the language's version using
and compare it to this library's ts_language_version
and
TREE_SITTER_LANGUAGE_VERSION
constants.TREE_SITTER_MIN_COMPATIBLE_LANGUAGE_VERSION
bool ts_parser_set_language(TSParser *self, const TSLanguage *language);
ts_parser_set_included_ranges :: Ptr TSParser -> ConstPtr TSRange -> Word32 -> IO CBool Source #
Set the ranges of text that the parser should include when parsing.
By default, the parser will always include entire documents. This function allows you to parse only a *portion* of a document but still return a syntax tree whose ranges match up with the document as a whole. You can also pass multiple disjoint ranges.
The second and third parameters specify the location and length of an array of ranges. The parser does *not* take ownership of these ranges; it copies the data, so it doesn't matter how these ranges are allocated.
If count
is zero, then the entire document will be parsed. Otherwise,
the given ranges must be ordered from earliest to latest in the document,
and they must not overlap. That is, the following must hold for all:
i < count - 1: ranges[i].end_byte <= ranges[i + 1].start_byte
If this requirement is not satisfied, the operation will fail, the ranges
will not be assigned, and this function will return
. On success,
this function returns False
.True
bool ts_parser_set_included_ranges( TSParser *self, const TSRange *ranges, uint32_t count );
ts_parser_included_ranges :: ConstPtr TSParser -> Ptr Word32 -> IO (ConstPtr TSRange) Source #
Get the ranges of text that the parser will include when parsing.
The returned pointer is owned by the parser. The caller should not free it
or write to it. The length of the array will be written to the given
count
pointer.
const TSRange *ts_parser_included_ranges( const TSParser *self, uint32_t *count );
ts_parser_set_logger :: Ptr TSParser -> TSLog -> IO () Source #
Set the logger that a parser should use during parsing.
The parser does not take ownership over the logger payload. If a logger was previously assigned, the caller is responsible for releasing any memory owned by the previous logger.
void ts_parser_set_logger(TSParser *self, TSLogger logger);
ts_parser_logger :: ConstPtr TSParser -> IO (Maybe TSLog) Source #
Get the parser's current logger.
TSLogger ts_parser_logger(const TSParser *self);
ts_parser_remove_logger :: Ptr TSParser -> IO (Maybe TSLog) Source #
Remove the parser's current logger.
ts_parser_parse :: Ptr TSParser -> ConstPtr TSTree -> TSRead -> TSInputEncoding -> IO (Ptr TSTree) Source #
Use the parser to parse some source code and create a syntax tree.
If you are parsing this document for the first time, pass NULL
for the
old_tree
parameter. Otherwise, if you have already parsed an earlier
version of this document and the document has since been edited, pass the
previous syntax tree so that the unchanged parts of it can be reused.
This will save time and memory. For this to work correctly, you must have
already edited the old syntax tree using the
function in a
way that exactly matches the source code changes.ts_tree_edit
The
parameter lets you specify how to read the text. It has the
following three fields:TSInput
read
: A function to retrieve a chunk of text at a given byte offset and (row, column) position. The function should return a pointer to the text and write its length to thebytes_read
pointer. The parser does not take ownership of this buffer; it just borrows it until it has finished reading it. The function should write a zero value to thebytes_read
pointer to indicate the end of the document.payload
: An arbitrary pointer that will be passed to each invocation of theread
function.encoding
: An indication of how the text is encoded. EitherTSInputEncodingUTF8
orTSInputEncodingUTF16
.
This function returns a syntax tree on success, and NULL
on failure. There
are three possible reasons for failure:
- The parser does not have a language assigned. Check for this using the
function.ts_parser_language
- Parsing was cancelled due to a timeout that was set by an earlier call to
the
function. You can resume parsing from where the parser left out by callingts_parser_set_timeout_micros
again with the same arguments. Or you can start parsing from scratch by first callingts_parser_parse
.ts_parser_reset
- Parsing was cancelled using a cancellation flag that was set by an
earlier call to
. You can resume parsing from where the parser left out by callingts_parser_set_cancellation_flag
again with the same arguments.ts_parser_parse
TSTree *ts_parser_parse( TSParser *self, const TSTree *old_tree, TSInput input );
ts_parser_parse_string :: Ptr TSParser -> ConstPtr TSTree -> ConstPtr CChar -> Word32 -> IO (Ptr TSTree) Source #
Use the parser to parse some source code stored in one contiguous buffer.
The first two parameters are the same as in the
function
above. The second two parameters indicate the location of the buffer and its
length in bytes.ts_parser_parse
TSTree *ts_parser_parse_string( TSParser *self, const TSTree *old_tree, const char *string, uint32_t length );
ts_parser_parse_string_encoding :: Ptr TSParser -> ConstPtr TSTree -> ConstPtr CChar -> Word32 -> TSInputEncoding -> IO (Ptr TSTree) Source #
Use the parser to parse some source code stored in one contiguous buffer with
a given encoding. The first four parameters work the same as in the
method above. The final parameter indicates whether
the text is encoded as UTF8 or UTF16.ts_parser_parse_string
TSTree *ts_parser_parse_string_encoding( TSParser *self, const TSTree *old_tree, const char *string, uint32_t length, TSInputEncoding encoding );
ts_parser_reset :: Ptr TSParser -> IO () Source #
Instruct the parser to start the next parse from the beginning.
If the parser previously failed because of a timeout or a cancellation, then
by default, it will resume where it left off on the next call to
or other parsing functions. If you don't want to resume,
and instead intend to use this parser to parse some other document, you must
call ts_parser_parse
first.ts_parser_reset
void ts_parser_reset(TSParser *self);
ts_parser_set_timeout_micros :: Ptr TSParser -> Word64 -> IO () Source #
Set the maximum duration in microseconds that parsing should be allowed to take before halting.
If parsing takes longer than this, it will halt early, returning NULL
.
See
for more information.ts_parser_parse
void ts_parser_set_timeout_micros(TSParser *self, uint64_t timeout_micros);
ts_parser_timeout_micros :: Ptr TSParser -> IO Word64 Source #
Get the duration in microseconds that parsing is allowed to take.
uint64_t ts_parser_timeout_micros(const TSParser *self);
ts_parser_set_cancellation_flag :: Ptr TSParser -> ConstPtr CSize -> IO () Source #
Set the parser's current cancellation flag pointer.
If a non-null pointer is assigned, then the parser will periodically read
from this pointer during parsing. If it reads a non-zero value, it will
halt early, returning NULL
. See
for more information.ts_parser_parse
void ts_parser_set_cancellation_flag(TSParser *self, const size_t *flag);
ts_parser_cancellation_flag :: ConstPtr TSParser -> IO (ConstPtr CSize) Source #
Get the parser's current cancellation flag pointer.
const size_t *ts_parser_cancellation_flag(const TSParser *self);
ts_parser_print_dot_graphs :: Ptr TSParser -> Int32 -> IO () Source #
Set the file descriptor to which the parser should write debugging graphs during parsing. The graphs are formatted in the DOT language. You may want to pipe these graphs directly to a `dot(1)` process in order to generate SVG output. You can turn off this logging by passing a negative number.
void ts_parser_print_dot_graphs(TSParser *self, int fd);
Tree
ts_tree_copy :: Ptr TSTree -> IO (Ptr TSTree) Source #
Create a shallow copy of the syntax tree. This is very fast.
You need to copy a syntax tree in order to use it on more than one thread at a time, as syntax trees are not thread safe.
TSTree *ts_tree_copy(const TSTree *self);
ts_tree_delete :: Ptr TSTree -> IO () Source #
Delete the syntax tree, freeing all of the memory that it used.
void ts_tree_delete(TSTree *self);
p_ts_tree_delete :: FunPtr (Ptr TSTree -> IO ()) Source #
C function pointer to
.ts_tree_delete
ts_tree_language :: Ptr TSTree -> IO (ConstPtr TSLanguage) Source #
Get the language that was used to parse the syntax tree.
const TSLanguage *ts_tree_language(const TSTree *self);
ts_tree_included_ranges :: Ptr TSTree -> Ptr Word32 -> IO (Ptr TSRange) Source #
Get the array of included ranges that was used to parse the syntax tree.
The returned pointer must be freed by the caller.
TSRange *ts_tree_included_ranges(const TSTree *self, uint32_t *length);
ts_tree_edit :: Ptr TSTree -> Ptr TSInputEdit -> IO () Source #
Edit the syntax tree to keep it in sync with source code that has been edited.
You must describe the edit both in terms of byte offsets and in terms of (row, column) coordinates.
void ts_tree_edit(TSTree *self, const TSInputEdit *edit);
ts_tree_get_changed_ranges :: Ptr TSTree -> Ptr TSTree -> Ptr Word32 -> IO (Ptr TSRange) Source #
Compare an old edited syntax tree to a new syntax tree representing the same document, returning an array of ranges whose syntactic structure has changed.
For this to work correctly, the old syntax tree must have been edited such
that its ranges match up to the new tree. Generally, you'll want to call
this function right after calling one of the
functions.
You need to pass the old tree that was passed to parse, as well as the new
tree that was returned from that function.ts_parser_parse
The returned array is allocated using malloc
and the caller is responsible
for freeing it using free
. The length of the array will be written to the
given length
pointer.
TSRange *ts_tree_get_changed_ranges( const TSTree *old_tree, const TSTree *new_tree, uint32_t *length );
ts_tree_print_dot_graph :: Ptr TSTree -> Int32 -> IO () Source #
Write a DOT graph describing the syntax tree to the given file.
void ts_tree_print_dot_graph(const TSTree *self, int file_descriptor);
ts_tree_root_node :: ConstPtr TSTree -> IO TSNode Source #
Get the root node of the syntax tree.
TSNode ts_tree_root_node(const TSTree *self);
ts_tree_root_node_with_offset :: ConstPtr TSTree -> Word32 -> TSPoint -> IO TSNode Source #
Get the root node of the syntax tree, but with its position shifted forward by the given offset.
TSNode ts_tree_root_node_with_offset( const TSTree *self, uint32_t offset_bytes, TSPoint offset_extent );
Node
ts_node_type :: TSNode -> IO (ConstPtr CChar) Source #
Get the node's type as a null-terminated string.
const char *ts_node_type(TSNode self);
ts_node_symbol :: TSNode -> IO TSSymbol Source #
Get the node's type as a numerical id.
TSSymbol ts_node_symbol(TSNode self);
ts_node_language :: TSNode -> IO (ConstPtr TSLanguage) Source #
Get the node's language.
const TSLanguage *ts_node_language(TSNode self);
ts_node_grammar_type :: TSNode -> IO (ConstPtr CChar) Source #
Get the node's type as it appears in the grammar ignoring aliases as a null-terminated string.
const char *ts_node_grammar_type(TSNode self);
ts_node_grammar_symbol :: TSNode -> IO TSSymbol Source #
Get the node's type as a numerical id as it appears in the grammar ignoring
aliases. This should be used in
instead of
ts_language_next_state
.ts_node_symbol
TSSymbol ts_node_grammar_symbol(TSNode self);
ts_node_start_byte :: TSNode -> IO Word32 Source #
Get the node's start byte.
uint32_t ts_node_start_byte(TSNode self);
ts_node_start_point :: TSNode -> IO TSPoint Source #
Get the node's start position in terms of rows and columns.
TSPoint ts_node_start_point(TSNode self);
ts_node_end_byte :: TSNode -> IO Word32 Source #
Get the node's end byte.
uint32_t ts_node_end_byte(TSNode self);
ts_node_end_point :: TSNode -> IO TSPoint Source #
Get the node's end position in terms of rows and columns.
TSPoint ts_node_end_point(TSNode self);
ts_node_string :: TSNode -> IO (Ptr CChar) Source #
Get an S-expression representing the node as a string.
This string is allocated with malloc
and the caller is responsible for
freeing it using free
.
char *ts_node_string(TSNode self);
ts_node_is_null :: TSNode -> IO CBool Source #
Check if the node is null. Functions like
and
ts_node_child
will return a null node to indicate that no such node
was found.ts_node_next_sibling
bool ts_node_is_null(TSNode self);
ts_node_is_named :: TSNode -> IO CBool Source #
Check if the node is *named*. Named nodes correspond to named rules in the grammar, whereas *anonymous* nodes correspond to string literals in the grammar.
bool ts_node_is_named(TSNode self);
ts_node_is_missing :: TSNode -> IO CBool Source #
Check if the node is *missing*. Missing nodes are inserted by the parser in order to recover from certain kinds of syntax errors.
bool ts_node_is_missing(TSNode self);
ts_node_is_extra :: TSNode -> IO CBool Source #
Check if the node is *extra*. Extra nodes represent things like comments, which are not required the grammar, but can appear anywhere.
bool ts_node_is_extra(TSNode self);
ts_node_has_changes :: TSNode -> IO CBool Source #
Check if a syntax node has been edited.
bool ts_node_has_changes(TSNode self);
ts_node_has_error :: TSNode -> IO CBool Source #
Check if the node is a syntax error or contains any syntax errors.
bool ts_node_has_error(TSNode self);
ts_node_is_error :: TSNode -> IO CBool Source #
Check if the node is a syntax error.
bool ts_node_is_error (TSNode self)
ts_node_parse_state :: TSNode -> IO TSStateId Source #
Get this node's parse state.
TSStateId ts_node_parse_state (TSNode self)
ts_node_next_parse_state :: TSNode -> IO TSStateId Source #
Get the parse state after this node.
TSStateId ts_node_next_parse_state (TSNode self)
ts_node_parent :: TSNode -> IO TSNode Source #
Get the node's immediate parent.
TSNode ts_node_parent(TSNode self);
ts_node_child_with_descendant :: TSNode -> TSNode -> IO TSNode Source #
Get the node that contains descendant
.
Note that this can return descendant
itself.
TSNode ts_node_child_with_descendant(TSNode self, TSNode descendant);
ts_node_child :: TSNode -> Word32 -> IO TSNode Source #
Get the node's child at the given index, where zero represents the first child.
TSNode ts_node_child(TSNode self, uint32_t child_index);
ts_node_field_name_for_child :: TSNode -> Word32 -> IO (ConstPtr CChar) Source #
Get the field name for node's child at the given index, where zero represents
the first child. Returns NULL
if no field is found.
const char *ts_node_field_name_for_child(TSNode self, uint32_t child_index);
ts_node_field_name_for_named_child :: TSNode -> Word32 -> IO (ConstPtr CChar) Source #
Get the field name for node's named child at the given index, where zero
represents the first named child. Returns NULL
, if no field is found.
const char *ts_node_field_name_for_named_child(TSNode self, uint32_t named_child_index);
ts_node_child_count :: TSNode -> IO Word32 Source #
Get the node's number of children.
uint32_t ts_node_child_count(TSNode self);
ts_node_named_child :: TSNode -> Word32 -> IO TSNode Source #
Get the node's *named* child at the given index.
See also
.ts_node_is_named
TSNode ts_node_named_child(TSNode self, uint32_t child_index);
ts_node_named_child_count :: TSNode -> IO Word32 Source #
Get the node's number of *named* children.
See also
.ts_node_is_named
uint32_t ts_node_named_child_count(TSNode self);
ts_node_child_by_field_name :: TSNode -> ConstPtr CChar -> Word32 -> IO TSNode Source #
Get the node's child with the given field name.
TSNode ts_node_child_by_field_name( TSNode self, const char *name, uint32_t name_length );
ts_node_child_by_field_id :: TSNode -> TSFieldId -> IO TSNode Source #
Get the node's child with the given numerical field id.
You can convert a field name to an id using the
function.ts_language_field_id_for_name
TSNode ts_node_child_by_field_id(TSNode self, TSFieldId field_id);
ts_node_next_sibling :: TSNode -> IO TSNode Source #
Get the node's next sibling.
TSNode ts_node_next_sibling(TSNode self);
ts_node_prev_sibling :: TSNode -> IO TSNode Source #
Get the node's previous sibling.
TSNode ts_node_prev_sibling(TSNode self);
ts_node_next_named_sibling :: TSNode -> IO TSNode Source #
Get the node's next *named* sibling.
TSNode ts_node_next_named_sibling(TSNode self);
ts_node_prev_named_sibling :: TSNode -> IO TSNode Source #
Get the node's previous *named* sibling.
TSNode ts_node_prev_named_sibling(TSNode self);
ts_node_first_child_for_byte :: TSNode -> Word32 -> IO TSNode Source #
Get the node's first child that extends beyond the given byte offset.
TSNode ts_node_first_child_for_byte(TSNode self, uint32_t byte);
ts_node_first_named_child_for_byte :: TSNode -> Word32 -> IO TSNode Source #
Get the node's first named child that extends beyond the given byte offset.
TSNode ts_node_first_named_child_for_byte(TSNode self, uint32_t byte);
ts_node_descendant_count :: TSNode -> IO Word32 Source #
Get the node's number of descendants, including one for the node itself.
uint32_t ts_node_descendant_count(TSNode self);
ts_node_descendant_for_byte_range :: TSNode -> Word32 -> Word32 -> IO TSNode Source #
Get the smallest node within this node that spans the given range of bytes.
TSNode ts_node_descendant_for_byte_range(TSNode self, uint32_t start, uint32_t end);
ts_node_descendant_for_point_range :: TSNode -> TSPoint -> TSPoint -> IO TSNode Source #
Get the smallest node within this node that spans the given range of positions.
TSNode ts_node_descendant_for_point_range(TSNode self, TSPoint start, TSPoint end);
ts_node_named_descendant_for_byte_range :: TSNode -> Word32 -> Word32 -> IO TSNode Source #
Get the smallest named node within this node that spans the given range of bytes.
TSNode ts_node_named_descendant_for_byte_range(TSNode self, uint32_t start, uint32_t end);
ts_node_named_descendant_for_point_range :: TSNode -> TSPoint -> TSPoint -> IO TSNode Source #
Get the smallest named node within this node that spans the given range of positions.
TSNode ts_node_named_descendant_for_point_range(TSNode self, TSPoint start, TSPoint end);
ts_node_edit :: Ptr TSNode -> ConstPtr TSInputEdit -> IO () Source #
Edit the node to keep it in-sync with source code that has been edited.
This function is only rarely needed. When you edit a syntax tree with the
function, all of the nodes that you retrieve from the tree
afterward will already reflect the edit. You only need to use ts_tree_edit
when you have a ts_node_edit
instance that you want to keep and continue to use
after an edit.TSNode
void ts_node_edit(TSNode *self, const TSInputEdit *edit);
ts_node_eq :: TSNode -> TSNode -> IO CBool Source #
Check if two nodes are identical.
bool ts_node_eq(TSNode self, TSNode other);
TreeCursor
ts_tree_cursor_new :: TSNode -> IO TSTreeCursor Source #
Create a new tree cursor starting from the given node.
A tree cursor allows you to walk a syntax tree more efficiently than is
possible using the
functions. It is a mutable object that is always
on a certain syntax node, and can be moved imperatively to different nodes.TSNode
TSTreeCursor ts_tree_cursor_new(TSNode node);
Arguments
:: TSNode | |
-> Ptr TSTreeCursor | Output pointer for the new tree cursor. |
-> IO () |
Create a new tree cursor starting from the given node.
Variant of ts_tree_cursor_new
that writes the tree cursor to the provided pointer.
ts_tree_cursor_delete :: Ptr TSTreeCursor -> IO () Source #
Delete a tree cursor, freeing all of the memory that it used.
void ts_tree_cursor_delete(TSTreeCursor *self);
p_ts_tree_cursor_delete :: FunPtr (Ptr TSTreeCursor -> IO ()) Source #
C function pointer to
.ts_tree_cursor_delete
ts_tree_cursor_reset :: Ptr TSTreeCursor -> TSNode -> IO () Source #
Re-initialize a tree cursor to start at the original node that the cursor was constructed with.
void ts_tree_cursor_reset(TSTreeCursor *self, TSNode node);
ts_tree_cursor_reset_to :: Ptr TSTreeCursor -> ConstPtr TSTreeCursor -> IO () Source #
Re-initialize a tree cursor to the same position as another cursor.
Unlike
, this will not lose parent information and
allows reusing already created cursors.ts_tree_cursor_reset
void ts_tree_cursor_reset_to(TSTreeCursor *dst, const TSTreeCursor *src);
ts_tree_cursor_current_node :: ConstPtr TSTreeCursor -> IO TSNode Source #
Get the tree cursor's current node.
TSNode ts_tree_cursor_current_node(const TSTreeCursor *self);
ts_tree_cursor_current_field_name :: ConstPtr TSTreeCursor -> IO (ConstPtr CChar) Source #
Get the field name of the tree cursor's current node.
This returns NULL
if the current node doesn't have a field.
See also
.ts_node_child_by_field_name
const char *ts_tree_cursor_current_field_name(const TSTreeCursor *self);
ts_tree_cursor_current_field_id :: ConstPtr TSTreeCursor -> IO TSFieldId Source #
Get the field id of the tree cursor's current node.
This returns zero if the current node doesn't have a field.
See also
, ts_node_child_by_field_id
.ts_language_field_id_for_name
TSFieldId ts_tree_cursor_current_field_id(const TSTreeCursor *self);
ts_tree_cursor_goto_parent :: Ptr TSTreeCursor -> IO CBool Source #
Move the cursor to the parent of its current node.
This returns true
if the cursor successfully moved, and returns false
if there was no parent node (the cursor was already on the root node).
bool ts_tree_cursor_goto_parent(TSTreeCursor *self);
ts_tree_cursor_goto_next_sibling :: Ptr TSTreeCursor -> IO CBool Source #
Move the cursor to the next sibling of its current node.
This returns true
if the cursor successfully moved, and returns false
if there was no next sibling node.
bool ts_tree_cursor_goto_next_sibling(TSTreeCursor *self);
ts_tree_cursor_goto_previous_sibling :: Ptr TSTreeCursor -> IO CBool Source #
Move the cursor to the previous sibling of its current node.
This returns true
if the cursor successfully moved, and returns false
if
there was no previous sibling node.
Note, that this function may be slower than
due to how node positions are stored. In
the worst case, this will need to iterate through all the children upto the
previous sibling node to recalculate its position.ts_tree_cursor_goto_next_sibling
bool ts_tree_cursor_goto_previous_sibling(TSTreeCursor *self);
ts_tree_cursor_goto_first_child :: Ptr TSTreeCursor -> IO CBool Source #
Move the cursor to the first child of its current node.
This returns true
if the cursor successfully moved, and returns false
if there were no children.
bool ts_tree_cursor_goto_first_child(TSTreeCursor *self);
ts_tree_cursor_goto_last_child :: Ptr TSTreeCursor -> IO CBool Source #
Move the cursor to the last child of its current node.
This returns true
if the cursor successfully moved, and returns false
if
there were no children.
Note that this function may be slower than
because it needs to iterate through all the children to compute the child's
position.ts_tree_cursor_goto_first_child
bool ts_tree_cursor_goto_last_child(TSTreeCursor *self);
ts_tree_cursor_goto_descendant :: Ptr TSTreeCursor -> Word32 -> IO () Source #
Move the cursor to the node that is the nth descendant of the original node that the cursor was constructed with, where zero represents the original node itself.
void ts_tree_cursor_goto_descendant(TSTreeCursor *self, uint32_t goal_descendant_index);
ts_tree_cursor_current_descendant_index :: ConstPtr TSTreeCursor -> IO Word32 Source #
Get the index of the cursor's current node out of all of the descendants of the original node that the cursor was constructed with.
uint32_t ts_tree_cursor_current_descendant_index(const TSTreeCursor *self);
ts_tree_cursor_current_depth :: ConstPtr TSTreeCursor -> IO Word32 Source #
Get the depth of the cursor's current node relative to the original node that the cursor was constructed with.
uint32_t ts_tree_cursor_current_depth(const TSTreeCursor *self);
ts_tree_cursor_goto_first_child_for_byte :: Ptr TSTreeCursor -> Word32 -> IO Int64 Source #
Move the cursor to the first child of its current node that extends beyond the given byte offset.
This returns the index of the child node if one was found, and returns -1 if no such child was found.
int64_t ts_tree_cursor_goto_first_child_for_byte(TSTreeCursor *self, uint32_t goal_byte);
ts_tree_cursor_goto_first_child_for_point :: Ptr TSTreeCursor -> TSPoint -> IO Int64 Source #
Move the cursor to the first child of its current node that extends beyond the given byte point.
This returns the index of the child node if one was found, and returns -1 if no such child was found.
int64_t ts_tree_cursor_goto_first_child_for_point(TSTreeCursor *self, TSPoint goal_point);
ts_tree_cursor_copy :: Ptr TSTreeCursor -> IO TSTreeCursor Source #
TSTreeCursor ts_tree_cursor_copy(const TSTreeCursor *cursor);
ts_tree_cursor_copy_p Source #
Arguments
:: Ptr TSTreeCursor | |
-> Ptr TSTreeCursor | Output pointer for the new tree cursor. |
-> IO () |
Copy a tree cursor.
Variant of ts_tree_cursor_copy
that writes the tree cursor to the provided pointer.
Query
ts_query_new :: ConstPtr TSLanguage -> ConstPtr CChar -> Word32 -> Ptr Word32 -> Ptr TSQueryError -> IO (Ptr TSQuery) Source #
Create a new query from a string containing one or more S-expression patterns. The query is associated with a particular language, and can only be run on syntax nodes parsed with that language.
If all of the given patterns are valid, this returns a
.
If a pattern is invalid, this returns TSQuery
NULL
, and provides two pieces
of information about the problem:
1. The byte offset of the error is written to the error_offset
parameter.
2. The type of error is written to the error_type
parameter.
TSQuery *ts_query_new( const TSLanguage *language, const char *source, uint32_t source_len, uint32_t *error_offset, TSQueryError *error_type );
ts_query_delete :: Ptr TSQuery -> IO () Source #
Delete a query, freeing all of the memory that it used.
void ts_query_delete(TSQuery *self);
p_ts_query_delete :: FunPtr (Ptr TSQuery -> IO ()) Source #
C function pointer to
.ts_query_delete
ts_query_pattern_count :: ConstPtr TSQuery -> IO Word32 Source #
Get the number of patterns in the query.
uint32_t ts_query_pattern_count(const TSQuery *self);
ts_query_capture_count :: ConstPtr TSQuery -> IO Word32 Source #
Get the number of captures in the query.
uint32_t ts_query_capture_count(const TSQuery *self);
ts_query_string_count :: ConstPtr TSQuery -> IO Word32 Source #
Get the number of string literals in the query.
uint32_t ts_query_string_count(const TSQuery *self);
ts_query_start_byte_for_pattern :: ConstPtr TSQuery -> Word32 -> IO Word32 Source #
Get the byte offset where the given pattern starts in the query's source.
This can be useful when combining queries by concatenating their source code strings.
uint32_t ts_query_start_byte_for_pattern(const TSQuery *self, uint32_t pattern_index);
ts_query_end_byte_for_pattern :: ConstPtr TSQuery -> Word32 -> IO Word32 Source #
Get the byte offset where the given pattern ends in the query's source.
This can be useful when combining queries by concatenating their source code strings.
uint32_t ts_query_end_byte_for_pattern(const TSQuery *self, uint32_t pattern_index);
ts_query_predicates_for_pattern :: ConstPtr TSQuery -> Word32 -> Ptr Word32 -> IO (ConstPtr TSQueryPredicateStep) Source #
Get all of the predicates for the given pattern in the query.
The predicates are represented as a single array of steps. There are three
types of steps in this array, which correspond to the three legal values for
the `type` field:
-
- Steps with this type represent names
of captures. Their TSQueryPredicateStepTypeCapture
value_id
can be used with the
function to obtain the name of the capture.
- ts_query_capture_name_for_id
- Steps with this type represent literal
strings. Their TSQueryPredicateStepTypeString
value_id
can be used with the
function to obtain their string value.
- ts_query_string_value_for_id
- Steps with this type are *sentinels*
that represent the end of an individual predicate. If a pattern has two
predicates, then there will be two steps with this `type` in the array.TSQueryPredicateStepTypeDone
const TSQueryPredicateStep *ts_query_predicates_for_pattern( const TSQuery *self, uint32_t pattern_index, uint32_t *step_count );
ts_query_is_pattern_rooted :: ConstPtr TSQuery -> Word32 -> IO CBool Source #
Check if the given pattern in the query has a single root node.
bool ts_query_is_pattern_rooted(const TSQuery *self, uint32_t pattern_index);
ts_query_is_pattern_non_local :: ConstPtr TSQuery -> Word32 -> IO CBool Source #
Check if the given pattern in the query is non-local.
A non-local pattern has multiple root nodes and can match within a repeating sequence of nodes, as specified by the grammar. Non-local patterns disable certain optimizations that would otherwise be possible when executing a query on a specific range of a syntax tree.
bool ts_query_is_pattern_non_local(const TSQuery *self, uint32_t pattern_index);
ts_query_is_pattern_guaranteed_at_step :: ConstPtr TSQuery -> Word32 -> IO CBool Source #
Check if a given pattern is guaranteed to match once a given step is reached. The step is specified by its byte offset in the query's source code.
bool ts_query_is_pattern_guaranteed_at_step(const TSQuery *self, uint32_t byte_offset);
ts_query_capture_name_for_id :: ConstPtr TSQuery -> Word32 -> Ptr Word32 -> IO (ConstPtr CChar) Source #
Get the name and length of one of the query's captures, or one of the query's string literals. Each capture and string is associated with a numeric id based on the order that it appeared in the query's source.
const char *ts_query_capture_name_for_id( const TSQuery *self, uint32_t index, uint32_t *length );
ts_query_capture_quantifier_for_id :: ConstPtr TSQuery -> Word32 -> Word32 -> IO TSQuantifier Source #
Get the quantifier of the query's captures. Each capture is * associated with a numeric id based on the order that it appeared in the query's source.
TSQuantifier ts_query_capture_quantifier_for_id( const TSQuery *self, uint32_t pattern_index, uint32_t capture_index );
ts_query_string_value_for_id :: ConstPtr TSQuery -> Word32 -> Ptr Word32 -> IO (ConstPtr CChar) Source #
const char *ts_query_string_value_for_id( const TSQuery *self, uint32_t index, uint32_t *length );
ts_query_disable_capture :: Ptr TSQuery -> ConstPtr CChar -> Word32 -> IO () Source #
Disable a certain capture within a query.
This prevents the capture from being returned in matches, and also avoids any resource usage associated with recording the capture. Currently, there is no way to undo this.
void ts_query_disable_capture(TSQuery *self, const char *name, uint32_t length);
ts_query_disable_pattern :: Ptr TSQuery -> Word32 -> IO () Source #
Disable a certain pattern within a query.
This prevents the pattern from matching and removes most of the overhead associated with the pattern. Currently, there is no way to undo this.
void ts_query_disable_pattern(TSQuery *self, uint32_t pattern_index);
ts_query_cursor_new :: IO (Ptr TSQueryCursor) Source #
Create a new cursor for executing a given query.
The cursor stores the state that is needed to iteratively search
for matches. To use the query cursor, first call
to start running a given query on a given syntax node. Then, there are
two options for consuming the results of the query:
1. Repeatedly call ts_query_cursor_exec
to iterate over all of the
*matches* in the order that they were found. Each match contains the
index of the pattern that matched, and an array of captures. Because
multiple patterns can match the same set of nodes, one match may contain
captures that appear *before* some of the captures from a previous match.
2. Repeatedly call ts_query_cursor_next_match
to iterate over all of the
individual *captures* in the order that they appear. This is useful if
don't care about which pattern matched, and just want a single ordered
sequence of captures.ts_query_cursor_next_capture
If you don't care about consuming all of the results, you can stop calling
or ts_query_cursor_next_match
at any point.
You can then start executing another query on another node by calling
ts_query_cursor_next_capture
again.ts_query_cursor_exec
TSQueryCursor *ts_query_cursor_new(void);
ts_query_cursor_delete :: Ptr TSQueryCursor -> IO () Source #
Delete a query cursor, freeing all of the memory that it used.
void ts_query_cursor_delete(TSQueryCursor *self);
p_ts_query_cursor_delete :: FunPtr (Ptr TSQueryCursor -> IO ()) Source #
C function pointer to
.ts_query_cursor_delete
ts_query_cursor_exec :: Ptr TSQueryCursor -> ConstPtr TSQuery -> TSNode -> IO () Source #
Start running a given query on a given node.
void ts_query_cursor_exec(TSQueryCursor *self, const TSQuery *query, TSNode node);
ts_query_cursor_did_exceed_match_limit :: ConstPtr TSQueryCursor -> IO CBool Source #
Check whether the maximum number of in-progress matches allowed by this query cursor was exceeded.
Query cursors have an optional maximum capacity for storing lists of in-progress captures. If this capacity is exceeded, then the earliest-starting match will silently be dropped to make room for further matches. This maximum capacity is optional — by default, query cursors allow any number of pending matches, dynamically allocating new space for them as needed as the query is executed.
bool ts_query_cursor_did_exceed_match_limit(const TSQueryCursor *self);
ts_query_cursor_match_limit :: ConstPtr TSQueryCursor -> IO Word32 Source #
Get the maximum number of in-progress matches allowed by this query cursor.
uint32_t ts_query_cursor_match_limit(const TSQueryCursor *self);
ts_query_cursor_set_match_limit :: Ptr TSQueryCursor -> Word32 -> IO () Source #
Set the maximum number of in-progress matches allowed by this query cursor.
void ts_query_cursor_set_match_limit(TSQueryCursor *self, uint32_t limit);
ts_query_cursor_set_timeout_micros :: Ptr TSQueryCursor -> Word64 -> IO () Source #
Set the maximum duration in microseconds that query execution should be allowed to take before halting.
If query execution takes longer than this, it will halt early, returning NULL
.
See
or ts_query_cursor_next_match
for more information.ts_query_cursor_next_capture
void ts_query_cursor_set_timeout_micros(TSQueryCursor *self, uint64_t timeout_micros);
ts_query_cursor_timeout_micros :: ConstPtr TSQueryCursor -> IO Word64 Source #
Get the duration in microseconds that query execution is allowed to take.
This is set via
.ts_query_cursor_set_timeout_micros
uint64_t ts_query_cursor_timeout_micros(const TSQueryCursor *self);
ts_query_cursor_set_byte_range :: Ptr TSQueryCursor -> Word32 -> Word32 -> IO () Source #
Set the range of bytes in which the query will be executed.
void ts_query_cursor_set_byte_range(TSQueryCursor *self, uint32_t start_byte, uint32_t end_byte);
ts_query_cursor_set_point_range :: Ptr TSQueryCursor -> TSPoint -> TSPoint -> IO () Source #
Set the range of positions in which the query will be executed.
void ts_query_cursor_set_point_range(TSQueryCursor *self, TSPoint start_point, TSPoint end_point);
ts_query_cursor_next_match :: Ptr TSQueryCursor -> Ptr TSQueryMatch -> IO CBool Source #
Advance to the next match of the currently running query.
If there is a match, write it to `*match` and return true
.
Otherwise, return false
.
bool ts_query_cursor_next_match(TSQueryCursor *self, TSQueryMatch *match);
ts_query_cursor_remove_match :: Ptr TSQueryCursor -> Word32 -> IO () Source #
Remove a match of the currently running query.
void ts_query_cursor_remove_match(TSQueryCursor *self, uint32_t match_id);
ts_query_cursor_next_capture :: Ptr TSQueryCursor -> Ptr TSQueryMatch -> Ptr Word32 -> IO CBool Source #
Advance to the next capture of the currently running query.
If there is a capture, write its match to `*match` and its index within
the matche's capture list to `*capture_index`. Otherwise, return false
.
bool ts_query_cursor_next_capture( TSQueryCursor *self, TSQueryMatch *match, uint32_t *capture_index );
ts_query_cursor_set_max_start_depth :: Ptr TSQueryCursor -> Word32 -> IO () Source #
Set the maximum start depth for a query cursor.
This prevents cursors from exploring children nodes at a certain depth. Note if a pattern includes many children, then they will still be checked.
The zero max start depth value can be used as a special behavior and it helps to destructure a subtree by staying on a node and using captures for interested parts. Note that the zero max start depth only limit a search depth for a pattern's root node but other nodes that are parts of the pattern may be searched at any depth what defined by the pattern structure.
Set to UINT32_MAX
to remove the maximum start depth.
void ts_query_cursor_set_max_start_depth(TSQueryCursor *self, uint32_t max_start_depth);
Language
ts_language_copy :: ConstPtr TSLanguage -> IO (ConstPtr TSLanguage) Source #
Get another reference to the given language.
const TSLanguage *ts_language_copy(const TSLanguage *self);
ts_language_delete :: ConstPtr TSLanguage -> IO () Source #
Free any dynamically-allocated resources for this language, if this is the last reference.
void ts_language_delete(const TSLanguage *self);
p_ts_language_delete :: FunPtr (ConstPtr TSLanguage -> IO ()) Source #
C function pointer to
.ts_language_delete
ts_language_symbol_count :: ConstPtr TSLanguage -> IO Word32 Source #
Get the number of distinct node types in the language.
uint32_t ts_language_symbol_count(const TSLanguage *self);
ts_language_state_count :: ConstPtr TSLanguage -> IO Word32 Source #
Get the number of valid states in this language.
uint32_t ts_language_state_count(const TSLanguage *self);
ts_language_symbol_name :: ConstPtr TSLanguage -> TSSymbol -> IO (ConstPtr CChar) Source #
Get a node type string for the given numerical id.
const char *ts_language_symbol_name(const TSLanguage *self, TSSymbol symbol);
ts_language_symbol_for_name :: ConstPtr TSLanguage -> ConstPtr CChar -> Word32 -> CBool -> IO TSSymbol Source #
Get the numerical id for the given node type string.
TSSymbol ts_language_symbol_for_name( const TSLanguage *self, const char *string, uint32_t length, bool is_named );
ts_language_field_count :: ConstPtr TSLanguage -> IO Word32 Source #
Get the number of distinct field names in the language.
uint32_t ts_language_field_count(const TSLanguage *self);
ts_language_field_name_for_id :: ConstPtr TSLanguage -> TSFieldId -> IO (ConstPtr CChar) Source #
Get the field name string for the given numerical id.
const char *ts_language_field_name_for_id(const TSLanguage *self, TSFieldId id);
ts_language_field_id_for_name :: ConstPtr TSLanguage -> ConstPtr CChar -> Word32 -> IO TSFieldId Source #
Get the numerical id for the given field name string.
TSFieldId ts_language_field_id_for_name(const TSLanguage *self, const char *name, uint32_t name_length);
ts_language_symbol_type :: ConstPtr TSLanguage -> TSSymbol -> IO TSSymbolType Source #
Check whether the given node type id belongs to named nodes, anonymous nodes, or a hidden nodes.
See also
. Hidden nodes are never returned from the API.ts_node_is_named
TSSymbolType ts_language_symbol_type(const TSLanguage *self, TSSymbol symbol);
ts_language_version :: ConstPtr TSLanguage -> IO Word32 Source #
Get the ABI version number for this language. This version number is used to ensure that languages were generated by a compatible version of Tree-sitter.
See also
.ts_parser_set_language
uint32_t ts_language_version(const TSLanguage *self);
ts_language_next_state :: ConstPtr TSLanguage -> TSStateId -> TSSymbol -> IO TSStateId Source #
Get the next parse state. Combine this with lookahead iterators to generate
completion suggestions or valid symbols in error nodes. Use
for valid symbols.ts_node_grammar_symbol
TSStateId ts_language_next_state(const TSLanguage *self, TSStateId state, TSSymbol symbol);
Lookahead Iterator
ts_lookahead_iterator_new :: ConstPtr TSLanguage -> TSStateId -> IO (Ptr TSLookaheadIterator) Source #
Create a new lookahead iterator for the given language and parse state.
This returns NULL
if state is invalid for the language.
Repeatedly using
and
ts_lookahead_iterator_next
will generate valid symbols in the
given parse state. Newly created lookahead iterators will contain the ts_lookahead_iterator_current_symbol
ERROR
symbol.
Lookahead iterators can be useful to generate suggestions and improve syntax
error diagnostics. To get symbols valid in an ERROR node, use the lookahead
iterator on its first leaf node state. For MISSING
nodes, a lookahead
iterator created on the previous non-extra leaf node may be appropriate.
TSLookaheadIterator *ts_lookahead_iterator_new(const TSLanguage *self, TSStateId state);
ts_lookahead_iterator_delete :: Ptr TSLookaheadIterator -> IO () Source #
Delete a lookahead iterator freeing all the memory used.
void ts_lookahead_iterator_delete(TSLookaheadIterator *self);
p_ts_lookahead_iterator_delete :: FunPtr (Ptr TSLookaheadIterator -> IO ()) Source #
C function pointer to
.ts_lookahead_iterator_delete
ts_lookahead_iterator_reset_state :: Ptr TSLookaheadIterator -> TSStateId -> IO CBool Source #
Reset the lookahead iterator to another state.
This returns true
if the iterator was reset to the given state and false
otherwise.
bool ts_lookahead_iterator_reset_state(TSLookaheadIterator *self, TSStateId state);
ts_lookahead_iterator_reset :: Ptr TSLookaheadIterator -> ConstPtr TSLanguage -> TSStateId -> IO CBool Source #
Reset the lookahead iterator.
This returns true
if the language was set successfully and false
otherwise.
bool ts_lookahead_iterator_reset(TSLookaheadIterator *self, const TSLanguage *language, TSStateId state);
ts_lookahead_iterator_language :: Ptr TSLookaheadIterator -> IO (ConstPtr TSLanguage) Source #
Get the current language of the lookahead iterator.
const TSLanguage *ts_lookahead_iterator_language(const TSLookaheadIterator *self);
ts_lookahead_iterator_next :: Ptr TSLookaheadIterator -> IO CBool Source #
Advance the lookahead iterator to the next symbol.
This returns true
if there is a new symbol and false
otherwise.
bool ts_lookahead_iterator_next(TSLookaheadIterator *self);
ts_lookahead_iterator_current_symbol :: ConstPtr TSLookaheadIterator -> IO TSSymbol Source #
Get the current symbol of the lookahead iterator;
TSSymbol ts_lookahead_iterator_current_symbol(const TSLookaheadIterator *self);
ts_lookahead_iterator_current_symbol_name :: ConstPtr TSLookaheadIterator -> IO (ConstPtr CChar) Source #
Get the current symbol type of the lookahead iterator as a null terminated string.
const char *ts_lookahead_iterator_current_symbol_name(const TSLookaheadIterator *self);
Global Configuration
ts_set_allocator :: FunPtr (CSize -> IO ()) -> FunPtr (CSize -> CSize -> IO ()) -> FunPtr (Ptr a -> CSize -> IO ()) -> FunPtr (Ptr a -> IO ()) -> IO () Source #
Set the allocation functions used by the library.
By default, Tree-sitter uses the standard libc allocation functions, but aborts the process when an allocation fails. This function lets you supply alternative allocation functions at runtime.
If you pass NULL
for any parameter, Tree-sitter will switch back to
its default implementation of that function.
If you call this function after the library has already been used, then you must ensure that either:
- All the existing objects have been freed.
- The new allocator shares its state with the old one, so it is capable of freeing memory that was allocated by the old allocator.
void ts_set_allocator( void *(*new_malloc)(size_t), void *(*new_calloc)(size_t, size_t), void *(*new_realloc)(void *, size_t), void (*new_free)(void *) );