{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-unused-top-binds #-}
module TreeSitter.Internal (
C.TREE_SITTER_LANGUAGE_VERSION,
C.TREE_SITTER_MIN_COMPATIBLE_LANGUAGE_VERSION,
Symbol (..),
StateId (..),
GrammarType (..),
FieldId (..),
FieldName (..),
CaptureName (..),
CaptureIndex (..),
PatternIndex (..),
Language,
Parser,
Tree,
Query,
QueryCursor,
LookaheadIterator,
InputEncoding (InputEncodingUTF8, InputEncodingUTF16),
SymbolType (SymbolTypeRegular, SymbolTypeAnonymous, SymbolTypeSupertype, SymbolTypeAuxiliary),
Point (Point, pointColumn, pointRow),
Range (Range, rangeStartPoint, rangeEndPoint, rangeStartByte, rangeEndByte),
Input,
LogType (LogTypeLex, LogTypeParse),
InputEdit (InputEdit, inputEditStartByte, inputEditOldEndByte, inputEditNewEndByte, inputEditStartPoint, inputEditOldEndPoint, inputEditNewEndPoint),
Node,
NodeId (..),
nodeId,
TreeCursor,
TreeCursorId (..),
QueryCapture,
Quantifier,
QueryMatch,
QueryPredicateStepType,
QueryPredicateStep,
QueryErrorType (QueryErrorTypeSyntax, QueryErrorTypeNodeType, QueryErrorTypeField, QueryErrorTypeCapture, QueryErrorTypeStructure, QueryErrorTypeLanguage),
QueryError (..),
parserNew,
unsafeParserDelete,
withParser,
parserSetLanguage,
parserLanguage,
parserSetIncludedRanges,
parserIncludedRanges,
parserSetLogger,
parserLogger,
parserHasLogger,
parserRemoveLogger,
parserParse,
parserParseString,
parserParseByteString,
parserParseByteStringWithEncoding,
parserReset,
Microsecond (..),
parserSetTimeoutMicros,
parserTimeoutMicros,
CancellationFlag (Cancel, Continue),
CancellationFlagRef,
getCancellationFlag,
putCancellationFlag,
parserSetCancellationFlag,
parserCancellationFlag,
parserPrintDotGraphs,
treeCopy,
unsafeTreeDelete,
treeRootNode,
treeRootNodeWithOffset,
treeLanguage,
treeIncludedRanges,
treeEdit,
treeGetChangedRanges,
treePrintDotGraph,
nodeType,
nodeTypeAsString,
nodeSymbol,
nodeLanguage,
nodeGrammarType,
nodeGrammarTypeAsString,
nodeGrammarSymbol,
nodeRange,
nodeStartByte,
nodeStartPoint,
nodeEndByte,
nodeEndPoint,
showNode,
showNodeAsString,
nodeIsNull,
nodeIsNamed,
nodeIsMissing,
nodeIsExtra,
nodeHasChanges,
nodeHasError,
nodeIsError,
nodeParseState,
nodeNextParseState,
nodeParent,
nodeChildWithDescendant,
nodeChild,
nodeFieldNameForChild,
nodeFieldNameForChildAsString,
nodeFieldNameForNamedChild,
nodeFieldNameForNamedChildAsString,
nodeChildCount,
nodeNamedChild,
nodeNamedChildCount,
nodeChildByFieldName,
nodeChildByFieldId,
nodeNextSibling,
nodePrevSibling,
nodeNextNamedSibling,
nodePrevNamedSibling,
nodeFirstChildForByte,
nodeFirstNamedChildForByte,
nodeDescendantCount,
nodeDescendantForByteRange,
nodeDescendantForPointRange,
nodeNamedDescendantForByteRange,
nodeNamedDescendantForPointRange,
nodeEdit,
nodeEq,
treeCursorNew,
unsafeTreeCursorDelete,
treeCursorReset,
treeCursorResetTo,
treeCursorCurrentNode,
treeCursorCurrentFieldName,
treeCursorCurrentFieldId,
treeCursorGotoParent,
treeCursorGotoNextSibling,
treeCursorGotoPreviousSibling,
treeCursorGotoFirstChild,
treeCursorGotoLastChild,
treeCursorGotoDescendant,
treeCursorCurrentDescendantIndex,
treeCursorCurrentDepth,
treeCursorGotoFirstChildForByte,
treeCursorGotoFirstChildForPoint,
treeCursorCopy,
queryNew,
unsafeQueryDelete,
queryPatternCount,
queryCaptureCount,
queryStringCount,
queryStartByteForPattern,
queryEndByteForPattern,
queryPredicatesForPattern,
queryIsPatternRooted,
queryIsPatternNonLocal,
queryIsPatternGuaranteedAtStep,
queryCaptureNameForIndex,
queryCaptureQuantifierForIndex,
queryStringValueForIndex,
queryDisableCapture,
queryDisablePattern,
queryCursorNew,
unsafeQueryCursorDelete,
queryCursorExec,
queryCursorDidExceedMatchLimit,
queryCursorMatchLimit,
queryCursorSetMatchLimit,
queryCursorSetTimeoutMicros,
queryCursorTimeoutMicros,
queryCursorSetByteRange,
queryCursorSetPointRange,
queryCursorNextMatch,
queryCursorRemoveMatch,
queryCursorNextCapture,
queryCursorSetMaxStartDepth,
unsafeToLanguage,
unsafeLanguageDelete,
languageCopy,
languageSymbolCount,
languageStateCount,
languageSymbolName,
languageSymbolForGrammarType,
languageFieldCount,
languageFieldNameForId,
languageFieldIdForName,
languageSymbolType,
languageVersion,
languageNextState,
withLookaheadIteratorAsTSLookaheadIteratorPtr,
lookaheadIteratorNew,
unsafeLookaheadIteratorDelete,
lookaheadIteratorResetState,
lookaheadIteratorReset,
lookaheadIteratorLanguage,
lookaheadIteratorNext,
lookaheadIteratorCurrentSymbol,
lookaheadIteratorCurrentSymbolName,
) where
import Control.Exception (Exception (..), assert, bracket, throwIO)
import Control.Monad ((<=<))
import Data.ByteString qualified as BS
import Data.ByteString.Builder qualified as BSB
import Data.ByteString.Char8 qualified as BSC
import Data.ByteString.Internal (ByteString (BS))
import Data.ByteString.Unsafe qualified as BSU
import Data.Coerce (coerce)
import Data.IORef (newIORef, writeIORef)
import Data.Maybe (isJust)
import Foreign
import Foreign.C (CBool, CInt (CInt), CSize (..))
import Foreign.C.ConstPtr.Compat (ConstPtr (..))
import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr)
import GHC.IO.FD (FD (..))
import GHC.IO.Handle.FD (handleToFd)
import System.IO (Handle)
import TreeSitter.CApi qualified as C
import TreeSitter.CApi qualified as TSNode (TSNode (..))
{-# ANN module ("HLint: ignore Redundant lambda" :: String) #-}
{-# ANN module ("HLint: ignore Foreign should be imported post-qualified or with an explicit import list" :: String) #-}
newtype CaptureIndex = WrapTSCaptureIndex {CaptureIndex -> Word32
unWrapTSCaptureIndex :: Word32}
newtype PatternIndex = WrapTSPatternIndex {PatternIndex -> Word32
unWrapTSPatternIndex :: Word32}
newtype StateId = WrapTSStateId {StateId -> TSStateId
unWrapTSStateId :: C.TSStateId}
deriving stock (Int -> StateId -> ShowS
[StateId] -> ShowS
StateId -> [Char]
(Int -> StateId -> ShowS)
-> (StateId -> [Char]) -> ([StateId] -> ShowS) -> Show StateId
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> StateId -> ShowS
showsPrec :: Int -> StateId -> ShowS
$cshow :: StateId -> [Char]
show :: StateId -> [Char]
$cshowList :: [StateId] -> ShowS
showList :: [StateId] -> ShowS
Show, ReadPrec [StateId]
ReadPrec StateId
Int -> ReadS StateId
ReadS [StateId]
(Int -> ReadS StateId)
-> ReadS [StateId]
-> ReadPrec StateId
-> ReadPrec [StateId]
-> Read StateId
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StateId
readsPrec :: Int -> ReadS StateId
$creadList :: ReadS [StateId]
readList :: ReadS [StateId]
$creadPrec :: ReadPrec StateId
readPrec :: ReadPrec StateId
$creadListPrec :: ReadPrec [StateId]
readListPrec :: ReadPrec [StateId]
Read, StateId -> StateId -> Bool
(StateId -> StateId -> Bool)
-> (StateId -> StateId -> Bool) -> Eq StateId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StateId -> StateId -> Bool
== :: StateId -> StateId -> Bool
$c/= :: StateId -> StateId -> Bool
/= :: StateId -> StateId -> Bool
Eq, Eq StateId
Eq StateId =>
(StateId -> StateId -> Ordering)
-> (StateId -> StateId -> Bool)
-> (StateId -> StateId -> Bool)
-> (StateId -> StateId -> Bool)
-> (StateId -> StateId -> Bool)
-> (StateId -> StateId -> StateId)
-> (StateId -> StateId -> StateId)
-> Ord StateId
StateId -> StateId -> Bool
StateId -> StateId -> Ordering
StateId -> StateId -> StateId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: StateId -> StateId -> Ordering
compare :: StateId -> StateId -> Ordering
$c< :: StateId -> StateId -> Bool
< :: StateId -> StateId -> Bool
$c<= :: StateId -> StateId -> Bool
<= :: StateId -> StateId -> Bool
$c> :: StateId -> StateId -> Bool
> :: StateId -> StateId -> Bool
$c>= :: StateId -> StateId -> Bool
>= :: StateId -> StateId -> Bool
$cmax :: StateId -> StateId -> StateId
max :: StateId -> StateId -> StateId
$cmin :: StateId -> StateId -> StateId
min :: StateId -> StateId -> StateId
Ord)
deriving newtype (Integer -> StateId
StateId -> StateId
StateId -> StateId -> StateId
(StateId -> StateId -> StateId)
-> (StateId -> StateId -> StateId)
-> (StateId -> StateId -> StateId)
-> (StateId -> StateId)
-> (StateId -> StateId)
-> (StateId -> StateId)
-> (Integer -> StateId)
-> Num StateId
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: StateId -> StateId -> StateId
+ :: StateId -> StateId -> StateId
$c- :: StateId -> StateId -> StateId
- :: StateId -> StateId -> StateId
$c* :: StateId -> StateId -> StateId
* :: StateId -> StateId -> StateId
$cnegate :: StateId -> StateId
negate :: StateId -> StateId
$cabs :: StateId -> StateId
abs :: StateId -> StateId
$csignum :: StateId -> StateId
signum :: StateId -> StateId
$cfromInteger :: Integer -> StateId
fromInteger :: Integer -> StateId
Num, Num StateId
Ord StateId
(Num StateId, Ord StateId) => (StateId -> Rational) -> Real StateId
StateId -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: StateId -> Rational
toRational :: StateId -> Rational
Real, Enum StateId
Real StateId
(Real StateId, Enum StateId) =>
(StateId -> StateId -> StateId)
-> (StateId -> StateId -> StateId)
-> (StateId -> StateId -> StateId)
-> (StateId -> StateId -> StateId)
-> (StateId -> StateId -> (StateId, StateId))
-> (StateId -> StateId -> (StateId, StateId))
-> (StateId -> Integer)
-> Integral StateId
StateId -> Integer
StateId -> StateId -> (StateId, StateId)
StateId -> StateId -> StateId
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: StateId -> StateId -> StateId
quot :: StateId -> StateId -> StateId
$crem :: StateId -> StateId -> StateId
rem :: StateId -> StateId -> StateId
$cdiv :: StateId -> StateId -> StateId
div :: StateId -> StateId -> StateId
$cmod :: StateId -> StateId -> StateId
mod :: StateId -> StateId -> StateId
$cquotRem :: StateId -> StateId -> (StateId, StateId)
quotRem :: StateId -> StateId -> (StateId, StateId)
$cdivMod :: StateId -> StateId -> (StateId, StateId)
divMod :: StateId -> StateId -> (StateId, StateId)
$ctoInteger :: StateId -> Integer
toInteger :: StateId -> Integer
Integral, Int -> StateId
StateId -> Int
StateId -> [StateId]
StateId -> StateId
StateId -> StateId -> [StateId]
StateId -> StateId -> StateId -> [StateId]
(StateId -> StateId)
-> (StateId -> StateId)
-> (Int -> StateId)
-> (StateId -> Int)
-> (StateId -> [StateId])
-> (StateId -> StateId -> [StateId])
-> (StateId -> StateId -> [StateId])
-> (StateId -> StateId -> StateId -> [StateId])
-> Enum StateId
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: StateId -> StateId
succ :: StateId -> StateId
$cpred :: StateId -> StateId
pred :: StateId -> StateId
$ctoEnum :: Int -> StateId
toEnum :: Int -> StateId
$cfromEnum :: StateId -> Int
fromEnum :: StateId -> Int
$cenumFrom :: StateId -> [StateId]
enumFrom :: StateId -> [StateId]
$cenumFromThen :: StateId -> StateId -> [StateId]
enumFromThen :: StateId -> StateId -> [StateId]
$cenumFromTo :: StateId -> StateId -> [StateId]
enumFromTo :: StateId -> StateId -> [StateId]
$cenumFromThenTo :: StateId -> StateId -> StateId -> [StateId]
enumFromThenTo :: StateId -> StateId -> StateId -> [StateId]
Enum)
newtype Symbol = WrapTSSymbol {Symbol -> TSSymbol
unWrapTSSymbol :: C.TSSymbol}
deriving stock (Int -> Symbol -> ShowS
[Symbol] -> ShowS
Symbol -> [Char]
(Int -> Symbol -> ShowS)
-> (Symbol -> [Char]) -> ([Symbol] -> ShowS) -> Show Symbol
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Symbol -> ShowS
showsPrec :: Int -> Symbol -> ShowS
$cshow :: Symbol -> [Char]
show :: Symbol -> [Char]
$cshowList :: [Symbol] -> ShowS
showList :: [Symbol] -> ShowS
Show, ReadPrec [Symbol]
ReadPrec Symbol
Int -> ReadS Symbol
ReadS [Symbol]
(Int -> ReadS Symbol)
-> ReadS [Symbol]
-> ReadPrec Symbol
-> ReadPrec [Symbol]
-> Read Symbol
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Symbol
readsPrec :: Int -> ReadS Symbol
$creadList :: ReadS [Symbol]
readList :: ReadS [Symbol]
$creadPrec :: ReadPrec Symbol
readPrec :: ReadPrec Symbol
$creadListPrec :: ReadPrec [Symbol]
readListPrec :: ReadPrec [Symbol]
Read, Symbol -> Symbol -> Bool
(Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Bool) -> Eq Symbol
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Symbol -> Symbol -> Bool
== :: Symbol -> Symbol -> Bool
$c/= :: Symbol -> Symbol -> Bool
/= :: Symbol -> Symbol -> Bool
Eq, Eq Symbol
Eq Symbol =>
(Symbol -> Symbol -> Ordering)
-> (Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Symbol)
-> (Symbol -> Symbol -> Symbol)
-> Ord Symbol
Symbol -> Symbol -> Bool
Symbol -> Symbol -> Ordering
Symbol -> Symbol -> Symbol
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Symbol -> Symbol -> Ordering
compare :: Symbol -> Symbol -> Ordering
$c< :: Symbol -> Symbol -> Bool
< :: Symbol -> Symbol -> Bool
$c<= :: Symbol -> Symbol -> Bool
<= :: Symbol -> Symbol -> Bool
$c> :: Symbol -> Symbol -> Bool
> :: Symbol -> Symbol -> Bool
$c>= :: Symbol -> Symbol -> Bool
>= :: Symbol -> Symbol -> Bool
$cmax :: Symbol -> Symbol -> Symbol
max :: Symbol -> Symbol -> Symbol
$cmin :: Symbol -> Symbol -> Symbol
min :: Symbol -> Symbol -> Symbol
Ord)
deriving newtype (Integer -> Symbol
Symbol -> Symbol
Symbol -> Symbol -> Symbol
(Symbol -> Symbol -> Symbol)
-> (Symbol -> Symbol -> Symbol)
-> (Symbol -> Symbol -> Symbol)
-> (Symbol -> Symbol)
-> (Symbol -> Symbol)
-> (Symbol -> Symbol)
-> (Integer -> Symbol)
-> Num Symbol
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Symbol -> Symbol -> Symbol
+ :: Symbol -> Symbol -> Symbol
$c- :: Symbol -> Symbol -> Symbol
- :: Symbol -> Symbol -> Symbol
$c* :: Symbol -> Symbol -> Symbol
* :: Symbol -> Symbol -> Symbol
$cnegate :: Symbol -> Symbol
negate :: Symbol -> Symbol
$cabs :: Symbol -> Symbol
abs :: Symbol -> Symbol
$csignum :: Symbol -> Symbol
signum :: Symbol -> Symbol
$cfromInteger :: Integer -> Symbol
fromInteger :: Integer -> Symbol
Num, Num Symbol
Ord Symbol
(Num Symbol, Ord Symbol) => (Symbol -> Rational) -> Real Symbol
Symbol -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Symbol -> Rational
toRational :: Symbol -> Rational
Real, Enum Symbol
Real Symbol
(Real Symbol, Enum Symbol) =>
(Symbol -> Symbol -> Symbol)
-> (Symbol -> Symbol -> Symbol)
-> (Symbol -> Symbol -> Symbol)
-> (Symbol -> Symbol -> Symbol)
-> (Symbol -> Symbol -> (Symbol, Symbol))
-> (Symbol -> Symbol -> (Symbol, Symbol))
-> (Symbol -> Integer)
-> Integral Symbol
Symbol -> Integer
Symbol -> Symbol -> (Symbol, Symbol)
Symbol -> Symbol -> Symbol
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Symbol -> Symbol -> Symbol
quot :: Symbol -> Symbol -> Symbol
$crem :: Symbol -> Symbol -> Symbol
rem :: Symbol -> Symbol -> Symbol
$cdiv :: Symbol -> Symbol -> Symbol
div :: Symbol -> Symbol -> Symbol
$cmod :: Symbol -> Symbol -> Symbol
mod :: Symbol -> Symbol -> Symbol
$cquotRem :: Symbol -> Symbol -> (Symbol, Symbol)
quotRem :: Symbol -> Symbol -> (Symbol, Symbol)
$cdivMod :: Symbol -> Symbol -> (Symbol, Symbol)
divMod :: Symbol -> Symbol -> (Symbol, Symbol)
$ctoInteger :: Symbol -> Integer
toInteger :: Symbol -> Integer
Integral, Int -> Symbol
Symbol -> Int
Symbol -> [Symbol]
Symbol -> Symbol
Symbol -> Symbol -> [Symbol]
Symbol -> Symbol -> Symbol -> [Symbol]
(Symbol -> Symbol)
-> (Symbol -> Symbol)
-> (Int -> Symbol)
-> (Symbol -> Int)
-> (Symbol -> [Symbol])
-> (Symbol -> Symbol -> [Symbol])
-> (Symbol -> Symbol -> [Symbol])
-> (Symbol -> Symbol -> Symbol -> [Symbol])
-> Enum Symbol
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Symbol -> Symbol
succ :: Symbol -> Symbol
$cpred :: Symbol -> Symbol
pred :: Symbol -> Symbol
$ctoEnum :: Int -> Symbol
toEnum :: Int -> Symbol
$cfromEnum :: Symbol -> Int
fromEnum :: Symbol -> Int
$cenumFrom :: Symbol -> [Symbol]
enumFrom :: Symbol -> [Symbol]
$cenumFromThen :: Symbol -> Symbol -> [Symbol]
enumFromThen :: Symbol -> Symbol -> [Symbol]
$cenumFromTo :: Symbol -> Symbol -> [Symbol]
enumFromTo :: Symbol -> Symbol -> [Symbol]
$cenumFromThenTo :: Symbol -> Symbol -> Symbol -> [Symbol]
enumFromThenTo :: Symbol -> Symbol -> Symbol -> [Symbol]
Enum)
newtype GrammarType = WrapTSGrammarType {GrammarType -> ByteString
unWrapTSGrammarType :: ByteString}
deriving stock (Int -> GrammarType -> ShowS
[GrammarType] -> ShowS
GrammarType -> [Char]
(Int -> GrammarType -> ShowS)
-> (GrammarType -> [Char])
-> ([GrammarType] -> ShowS)
-> Show GrammarType
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GrammarType -> ShowS
showsPrec :: Int -> GrammarType -> ShowS
$cshow :: GrammarType -> [Char]
show :: GrammarType -> [Char]
$cshowList :: [GrammarType] -> ShowS
showList :: [GrammarType] -> ShowS
Show, ReadPrec [GrammarType]
ReadPrec GrammarType
Int -> ReadS GrammarType
ReadS [GrammarType]
(Int -> ReadS GrammarType)
-> ReadS [GrammarType]
-> ReadPrec GrammarType
-> ReadPrec [GrammarType]
-> Read GrammarType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS GrammarType
readsPrec :: Int -> ReadS GrammarType
$creadList :: ReadS [GrammarType]
readList :: ReadS [GrammarType]
$creadPrec :: ReadPrec GrammarType
readPrec :: ReadPrec GrammarType
$creadListPrec :: ReadPrec [GrammarType]
readListPrec :: ReadPrec [GrammarType]
Read, GrammarType -> GrammarType -> Bool
(GrammarType -> GrammarType -> Bool)
-> (GrammarType -> GrammarType -> Bool) -> Eq GrammarType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GrammarType -> GrammarType -> Bool
== :: GrammarType -> GrammarType -> Bool
$c/= :: GrammarType -> GrammarType -> Bool
/= :: GrammarType -> GrammarType -> Bool
Eq, Eq GrammarType
Eq GrammarType =>
(GrammarType -> GrammarType -> Ordering)
-> (GrammarType -> GrammarType -> Bool)
-> (GrammarType -> GrammarType -> Bool)
-> (GrammarType -> GrammarType -> Bool)
-> (GrammarType -> GrammarType -> Bool)
-> (GrammarType -> GrammarType -> GrammarType)
-> (GrammarType -> GrammarType -> GrammarType)
-> Ord GrammarType
GrammarType -> GrammarType -> Bool
GrammarType -> GrammarType -> Ordering
GrammarType -> GrammarType -> GrammarType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: GrammarType -> GrammarType -> Ordering
compare :: GrammarType -> GrammarType -> Ordering
$c< :: GrammarType -> GrammarType -> Bool
< :: GrammarType -> GrammarType -> Bool
$c<= :: GrammarType -> GrammarType -> Bool
<= :: GrammarType -> GrammarType -> Bool
$c> :: GrammarType -> GrammarType -> Bool
> :: GrammarType -> GrammarType -> Bool
$c>= :: GrammarType -> GrammarType -> Bool
>= :: GrammarType -> GrammarType -> Bool
$cmax :: GrammarType -> GrammarType -> GrammarType
max :: GrammarType -> GrammarType -> GrammarType
$cmin :: GrammarType -> GrammarType -> GrammarType
min :: GrammarType -> GrammarType -> GrammarType
Ord)
newtype FieldId = WrapTSFieldId {FieldId -> TSFieldId
unWrapTSFieldId :: C.TSFieldId}
deriving stock (Int -> FieldId -> ShowS
[FieldId] -> ShowS
FieldId -> [Char]
(Int -> FieldId -> ShowS)
-> (FieldId -> [Char]) -> ([FieldId] -> ShowS) -> Show FieldId
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldId -> ShowS
showsPrec :: Int -> FieldId -> ShowS
$cshow :: FieldId -> [Char]
show :: FieldId -> [Char]
$cshowList :: [FieldId] -> ShowS
showList :: [FieldId] -> ShowS
Show, ReadPrec [FieldId]
ReadPrec FieldId
Int -> ReadS FieldId
ReadS [FieldId]
(Int -> ReadS FieldId)
-> ReadS [FieldId]
-> ReadPrec FieldId
-> ReadPrec [FieldId]
-> Read FieldId
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FieldId
readsPrec :: Int -> ReadS FieldId
$creadList :: ReadS [FieldId]
readList :: ReadS [FieldId]
$creadPrec :: ReadPrec FieldId
readPrec :: ReadPrec FieldId
$creadListPrec :: ReadPrec [FieldId]
readListPrec :: ReadPrec [FieldId]
Read, FieldId -> FieldId -> Bool
(FieldId -> FieldId -> Bool)
-> (FieldId -> FieldId -> Bool) -> Eq FieldId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldId -> FieldId -> Bool
== :: FieldId -> FieldId -> Bool
$c/= :: FieldId -> FieldId -> Bool
/= :: FieldId -> FieldId -> Bool
Eq, Eq FieldId
Eq FieldId =>
(FieldId -> FieldId -> Ordering)
-> (FieldId -> FieldId -> Bool)
-> (FieldId -> FieldId -> Bool)
-> (FieldId -> FieldId -> Bool)
-> (FieldId -> FieldId -> Bool)
-> (FieldId -> FieldId -> FieldId)
-> (FieldId -> FieldId -> FieldId)
-> Ord FieldId
FieldId -> FieldId -> Bool
FieldId -> FieldId -> Ordering
FieldId -> FieldId -> FieldId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldId -> FieldId -> Ordering
compare :: FieldId -> FieldId -> Ordering
$c< :: FieldId -> FieldId -> Bool
< :: FieldId -> FieldId -> Bool
$c<= :: FieldId -> FieldId -> Bool
<= :: FieldId -> FieldId -> Bool
$c> :: FieldId -> FieldId -> Bool
> :: FieldId -> FieldId -> Bool
$c>= :: FieldId -> FieldId -> Bool
>= :: FieldId -> FieldId -> Bool
$cmax :: FieldId -> FieldId -> FieldId
max :: FieldId -> FieldId -> FieldId
$cmin :: FieldId -> FieldId -> FieldId
min :: FieldId -> FieldId -> FieldId
Ord)
deriving newtype (Integer -> FieldId
FieldId -> FieldId
FieldId -> FieldId -> FieldId
(FieldId -> FieldId -> FieldId)
-> (FieldId -> FieldId -> FieldId)
-> (FieldId -> FieldId -> FieldId)
-> (FieldId -> FieldId)
-> (FieldId -> FieldId)
-> (FieldId -> FieldId)
-> (Integer -> FieldId)
-> Num FieldId
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: FieldId -> FieldId -> FieldId
+ :: FieldId -> FieldId -> FieldId
$c- :: FieldId -> FieldId -> FieldId
- :: FieldId -> FieldId -> FieldId
$c* :: FieldId -> FieldId -> FieldId
* :: FieldId -> FieldId -> FieldId
$cnegate :: FieldId -> FieldId
negate :: FieldId -> FieldId
$cabs :: FieldId -> FieldId
abs :: FieldId -> FieldId
$csignum :: FieldId -> FieldId
signum :: FieldId -> FieldId
$cfromInteger :: Integer -> FieldId
fromInteger :: Integer -> FieldId
Num, Num FieldId
Ord FieldId
(Num FieldId, Ord FieldId) => (FieldId -> Rational) -> Real FieldId
FieldId -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: FieldId -> Rational
toRational :: FieldId -> Rational
Real, Enum FieldId
Real FieldId
(Real FieldId, Enum FieldId) =>
(FieldId -> FieldId -> FieldId)
-> (FieldId -> FieldId -> FieldId)
-> (FieldId -> FieldId -> FieldId)
-> (FieldId -> FieldId -> FieldId)
-> (FieldId -> FieldId -> (FieldId, FieldId))
-> (FieldId -> FieldId -> (FieldId, FieldId))
-> (FieldId -> Integer)
-> Integral FieldId
FieldId -> Integer
FieldId -> FieldId -> (FieldId, FieldId)
FieldId -> FieldId -> FieldId
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: FieldId -> FieldId -> FieldId
quot :: FieldId -> FieldId -> FieldId
$crem :: FieldId -> FieldId -> FieldId
rem :: FieldId -> FieldId -> FieldId
$cdiv :: FieldId -> FieldId -> FieldId
div :: FieldId -> FieldId -> FieldId
$cmod :: FieldId -> FieldId -> FieldId
mod :: FieldId -> FieldId -> FieldId
$cquotRem :: FieldId -> FieldId -> (FieldId, FieldId)
quotRem :: FieldId -> FieldId -> (FieldId, FieldId)
$cdivMod :: FieldId -> FieldId -> (FieldId, FieldId)
divMod :: FieldId -> FieldId -> (FieldId, FieldId)
$ctoInteger :: FieldId -> Integer
toInteger :: FieldId -> Integer
Integral, Int -> FieldId
FieldId -> Int
FieldId -> [FieldId]
FieldId -> FieldId
FieldId -> FieldId -> [FieldId]
FieldId -> FieldId -> FieldId -> [FieldId]
(FieldId -> FieldId)
-> (FieldId -> FieldId)
-> (Int -> FieldId)
-> (FieldId -> Int)
-> (FieldId -> [FieldId])
-> (FieldId -> FieldId -> [FieldId])
-> (FieldId -> FieldId -> [FieldId])
-> (FieldId -> FieldId -> FieldId -> [FieldId])
-> Enum FieldId
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FieldId -> FieldId
succ :: FieldId -> FieldId
$cpred :: FieldId -> FieldId
pred :: FieldId -> FieldId
$ctoEnum :: Int -> FieldId
toEnum :: Int -> FieldId
$cfromEnum :: FieldId -> Int
fromEnum :: FieldId -> Int
$cenumFrom :: FieldId -> [FieldId]
enumFrom :: FieldId -> [FieldId]
$cenumFromThen :: FieldId -> FieldId -> [FieldId]
enumFromThen :: FieldId -> FieldId -> [FieldId]
$cenumFromTo :: FieldId -> FieldId -> [FieldId]
enumFromTo :: FieldId -> FieldId -> [FieldId]
$cenumFromThenTo :: FieldId -> FieldId -> FieldId -> [FieldId]
enumFromThenTo :: FieldId -> FieldId -> FieldId -> [FieldId]
Enum)
newtype FieldName = WrapTSFieldName {FieldName -> ByteString
unWrapTSFieldName :: ByteString}
deriving stock (Int -> FieldName -> ShowS
[FieldName] -> ShowS
FieldName -> [Char]
(Int -> FieldName -> ShowS)
-> (FieldName -> [Char])
-> ([FieldName] -> ShowS)
-> Show FieldName
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FieldName -> ShowS
showsPrec :: Int -> FieldName -> ShowS
$cshow :: FieldName -> [Char]
show :: FieldName -> [Char]
$cshowList :: [FieldName] -> ShowS
showList :: [FieldName] -> ShowS
Show, ReadPrec [FieldName]
ReadPrec FieldName
Int -> ReadS FieldName
ReadS [FieldName]
(Int -> ReadS FieldName)
-> ReadS [FieldName]
-> ReadPrec FieldName
-> ReadPrec [FieldName]
-> Read FieldName
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FieldName
readsPrec :: Int -> ReadS FieldName
$creadList :: ReadS [FieldName]
readList :: ReadS [FieldName]
$creadPrec :: ReadPrec FieldName
readPrec :: ReadPrec FieldName
$creadListPrec :: ReadPrec [FieldName]
readListPrec :: ReadPrec [FieldName]
Read, FieldName -> FieldName -> Bool
(FieldName -> FieldName -> Bool)
-> (FieldName -> FieldName -> Bool) -> Eq FieldName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldName -> FieldName -> Bool
== :: FieldName -> FieldName -> Bool
$c/= :: FieldName -> FieldName -> Bool
/= :: FieldName -> FieldName -> Bool
Eq, Eq FieldName
Eq FieldName =>
(FieldName -> FieldName -> Ordering)
-> (FieldName -> FieldName -> Bool)
-> (FieldName -> FieldName -> Bool)
-> (FieldName -> FieldName -> Bool)
-> (FieldName -> FieldName -> Bool)
-> (FieldName -> FieldName -> FieldName)
-> (FieldName -> FieldName -> FieldName)
-> Ord FieldName
FieldName -> FieldName -> Bool
FieldName -> FieldName -> Ordering
FieldName -> FieldName -> FieldName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FieldName -> FieldName -> Ordering
compare :: FieldName -> FieldName -> Ordering
$c< :: FieldName -> FieldName -> Bool
< :: FieldName -> FieldName -> Bool
$c<= :: FieldName -> FieldName -> Bool
<= :: FieldName -> FieldName -> Bool
$c> :: FieldName -> FieldName -> Bool
> :: FieldName -> FieldName -> Bool
$c>= :: FieldName -> FieldName -> Bool
>= :: FieldName -> FieldName -> Bool
$cmax :: FieldName -> FieldName -> FieldName
max :: FieldName -> FieldName -> FieldName
$cmin :: FieldName -> FieldName -> FieldName
min :: FieldName -> FieldName -> FieldName
Ord)
newtype CaptureName = WrapTSCaptureName {CaptureName -> ByteString
unWrapTSCaptureName :: ByteString}
deriving stock (Int -> CaptureName -> ShowS
[CaptureName] -> ShowS
CaptureName -> [Char]
(Int -> CaptureName -> ShowS)
-> (CaptureName -> [Char])
-> ([CaptureName] -> ShowS)
-> Show CaptureName
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CaptureName -> ShowS
showsPrec :: Int -> CaptureName -> ShowS
$cshow :: CaptureName -> [Char]
show :: CaptureName -> [Char]
$cshowList :: [CaptureName] -> ShowS
showList :: [CaptureName] -> ShowS
Show, ReadPrec [CaptureName]
ReadPrec CaptureName
Int -> ReadS CaptureName
ReadS [CaptureName]
(Int -> ReadS CaptureName)
-> ReadS [CaptureName]
-> ReadPrec CaptureName
-> ReadPrec [CaptureName]
-> Read CaptureName
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS CaptureName
readsPrec :: Int -> ReadS CaptureName
$creadList :: ReadS [CaptureName]
readList :: ReadS [CaptureName]
$creadPrec :: ReadPrec CaptureName
readPrec :: ReadPrec CaptureName
$creadListPrec :: ReadPrec [CaptureName]
readListPrec :: ReadPrec [CaptureName]
Read, CaptureName -> CaptureName -> Bool
(CaptureName -> CaptureName -> Bool)
-> (CaptureName -> CaptureName -> Bool) -> Eq CaptureName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CaptureName -> CaptureName -> Bool
== :: CaptureName -> CaptureName -> Bool
$c/= :: CaptureName -> CaptureName -> Bool
/= :: CaptureName -> CaptureName -> Bool
Eq, Eq CaptureName
Eq CaptureName =>
(CaptureName -> CaptureName -> Ordering)
-> (CaptureName -> CaptureName -> Bool)
-> (CaptureName -> CaptureName -> Bool)
-> (CaptureName -> CaptureName -> Bool)
-> (CaptureName -> CaptureName -> Bool)
-> (CaptureName -> CaptureName -> CaptureName)
-> (CaptureName -> CaptureName -> CaptureName)
-> Ord CaptureName
CaptureName -> CaptureName -> Bool
CaptureName -> CaptureName -> Ordering
CaptureName -> CaptureName -> CaptureName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: CaptureName -> CaptureName -> Ordering
compare :: CaptureName -> CaptureName -> Ordering
$c< :: CaptureName -> CaptureName -> Bool
< :: CaptureName -> CaptureName -> Bool
$c<= :: CaptureName -> CaptureName -> Bool
<= :: CaptureName -> CaptureName -> Bool
$c> :: CaptureName -> CaptureName -> Bool
> :: CaptureName -> CaptureName -> Bool
$c>= :: CaptureName -> CaptureName -> Bool
>= :: CaptureName -> CaptureName -> Bool
$cmax :: CaptureName -> CaptureName -> CaptureName
max :: CaptureName -> CaptureName -> CaptureName
$cmin :: CaptureName -> CaptureName -> CaptureName
min :: CaptureName -> CaptureName -> CaptureName
Ord)
newtype Language = WrapTSLanguage {Language -> ForeignPtr TSLanguage
unWrapTSLanguage :: ForeignPtr C.TSLanguage}
newtype Parser = WrapTSParser {Parser -> ForeignPtr TSParser
unWrapTSParser :: ForeignPtr C.TSParser}
newtype Tree = WrapTSTree {Tree -> ForeignPtr TSTree
unWrapTSTree :: ForeignPtr C.TSTree}
newtype Query = WrapTSQuery {Query -> ForeignPtr TSQuery
unWrapTSQuery :: ForeignPtr C.TSQuery}
newtype QueryCursor = WrapTSQueryCursor {QueryCursor -> ForeignPtr TSQueryCursor
unWrapTSQueryCursor :: ForeignPtr C.TSQueryCursor}
newtype LookaheadIterator = WrapTSLookaheadIterator {LookaheadIterator -> ForeignPtr TSLookaheadIterator
unWrapTSLookaheadIterator :: ForeignPtr C.TSLookaheadIterator}
newtype InputEncoding = WrapTSInputEncoding {InputEncoding -> TSInputEncoding
unWrapTSInputEncoding :: C.TSInputEncoding}
pattern InputEncodingUTF8 :: InputEncoding
pattern $mInputEncodingUTF8 :: forall {r}. InputEncoding -> ((# #) -> r) -> ((# #) -> r) -> r
$bInputEncodingUTF8 :: InputEncoding
InputEncodingUTF8 = WrapTSInputEncoding C.TSInputEncodingUTF8
pattern InputEncodingUTF16 :: InputEncoding
pattern $mInputEncodingUTF16 :: forall {r}. InputEncoding -> ((# #) -> r) -> ((# #) -> r) -> r
$bInputEncodingUTF16 :: InputEncoding
InputEncodingUTF16 = WrapTSInputEncoding C.TSInputEncodingUTF16
{-# COMPLETE InputEncodingUTF8, InputEncodingUTF16 #-}
instance Show InputEncoding where
show :: InputEncoding -> [Char]
show InputEncoding
InputEncodingUTF8 = [Char]
"InputEncodingUTF8"
show InputEncoding
InputEncodingUTF16 = [Char]
"InputEncodingUTF16"
newtype SymbolType = WrapTSSymbolType {SymbolType -> TSSymbolType
unWrapTSSymbolType :: C.TSSymbolType}
deriving stock (SymbolType -> SymbolType -> Bool
(SymbolType -> SymbolType -> Bool)
-> (SymbolType -> SymbolType -> Bool) -> Eq SymbolType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SymbolType -> SymbolType -> Bool
== :: SymbolType -> SymbolType -> Bool
$c/= :: SymbolType -> SymbolType -> Bool
/= :: SymbolType -> SymbolType -> Bool
Eq)
pattern SymbolTypeRegular :: SymbolType
pattern $mSymbolTypeRegular :: forall {r}. SymbolType -> ((# #) -> r) -> ((# #) -> r) -> r
$bSymbolTypeRegular :: SymbolType
SymbolTypeRegular = WrapTSSymbolType C.TSSymbolTypeRegular
pattern SymbolTypeAnonymous :: SymbolType
pattern $mSymbolTypeAnonymous :: forall {r}. SymbolType -> ((# #) -> r) -> ((# #) -> r) -> r
$bSymbolTypeAnonymous :: SymbolType
SymbolTypeAnonymous = WrapTSSymbolType C.TSSymbolTypeAnonymous
pattern SymbolTypeSupertype :: SymbolType
pattern $mSymbolTypeSupertype :: forall {r}. SymbolType -> ((# #) -> r) -> ((# #) -> r) -> r
$bSymbolTypeSupertype :: SymbolType
SymbolTypeSupertype = WrapTSSymbolType C.TSSymbolTypeSupertype
pattern SymbolTypeAuxiliary :: SymbolType
pattern $mSymbolTypeAuxiliary :: forall {r}. SymbolType -> ((# #) -> r) -> ((# #) -> r) -> r
$bSymbolTypeAuxiliary :: SymbolType
SymbolTypeAuxiliary = WrapTSSymbolType C.TSSymbolTypeAuxiliary
{-# COMPLETE SymbolTypeRegular, SymbolTypeAnonymous, SymbolTypeSupertype, SymbolTypeAuxiliary #-}
instance Show SymbolType where
show :: SymbolType -> [Char]
show SymbolType
SymbolTypeRegular = [Char]
"SymbolTypeRegular"
show SymbolType
SymbolTypeAnonymous = [Char]
"SymbolTypeAnonymous"
show SymbolType
SymbolTypeSupertype = [Char]
"SymbolTypeSupertype"
show SymbolType
SymbolTypeAuxiliary = [Char]
"SymbolTypeAuxiliary"
newtype Point = WrapTSPoint {Point -> TSPoint
unWrapTSPoint :: C.TSPoint}
deriving newtype (Eq Point
Eq Point =>
(Point -> Point -> Ordering)
-> (Point -> Point -> Bool)
-> (Point -> Point -> Bool)
-> (Point -> Point -> Bool)
-> (Point -> Point -> Bool)
-> (Point -> Point -> Point)
-> (Point -> Point -> Point)
-> Ord Point
Point -> Point -> Bool
Point -> Point -> Ordering
Point -> Point -> Point
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Point -> Point -> Ordering
compare :: Point -> Point -> Ordering
$c< :: Point -> Point -> Bool
< :: Point -> Point -> Bool
$c<= :: Point -> Point -> Bool
<= :: Point -> Point -> Bool
$c> :: Point -> Point -> Bool
> :: Point -> Point -> Bool
$c>= :: Point -> Point -> Bool
>= :: Point -> Point -> Bool
$cmax :: Point -> Point -> Point
max :: Point -> Point -> Point
$cmin :: Point -> Point -> Point
min :: Point -> Point -> Point
Ord, Point -> Point -> Bool
(Point -> Point -> Bool) -> (Point -> Point -> Bool) -> Eq Point
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Point -> Point -> Bool
== :: Point -> Point -> Bool
$c/= :: Point -> Point -> Bool
/= :: Point -> Point -> Bool
Eq)
pattern Point :: Word32 -> Word32 -> Point
pattern $mPoint :: forall {r}. Point -> (Word32 -> Word32 -> r) -> ((# #) -> r) -> r
$bPoint :: Word32 -> Word32 -> Point
Point
{ Point -> Word32
pointRow
, Point -> Word32
pointColumn
} =
WrapTSPoint
( C.TSPoint
pointRow
pointColumn
)
{-# COMPLETE Point #-}
instance Show Point where
showsPrec :: Int -> Point -> ShowS
showsPrec :: Int -> Point -> ShowS
showsPrec Int
p Point{Word32
pointColumn :: Point -> Word32
pointRow :: Point -> Word32
pointRow :: Word32
pointColumn :: Word32
..} =
Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
[Char] -> ShowS
showString [Char]
"Point "
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Word32
pointRow
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Word32
pointColumn
newtype Range = WrapTSRange {Range -> TSRange
unWrapTSRange :: C.TSRange}
deriving stock (Range -> Range -> Bool
(Range -> Range -> Bool) -> (Range -> Range -> Bool) -> Eq Range
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Range -> Range -> Bool
== :: Range -> Range -> Bool
$c/= :: Range -> Range -> Bool
/= :: Range -> Range -> Bool
Eq)
pattern Range :: Point -> Point -> Word32 -> Word32 -> Range
pattern $mRange :: forall {r}.
Range
-> (Point -> Point -> Word32 -> Word32 -> r) -> ((# #) -> r) -> r
$bRange :: Point -> Point -> Word32 -> Word32 -> Range
Range
{ Range -> Point
rangeStartPoint
, Range -> Point
rangeEndPoint
, Range -> Word32
rangeStartByte
, Range -> Word32
rangeEndByte
} <-
WrapTSRange
( C.TSRange
(WrapTSPoint -> rangeStartPoint)
(WrapTSPoint -> rangeEndPoint)
rangeStartByte
rangeEndByte
)
where
Range Point
startPoint Point
endPoint Word32
startByte Word32
endByte =
TSRange -> Range
WrapTSRange
( TSPoint -> TSPoint -> Word32 -> Word32 -> TSRange
C.TSRange
(Point -> TSPoint
unWrapTSPoint Point
startPoint)
(Point -> TSPoint
unWrapTSPoint Point
endPoint)
Word32
startByte
Word32
endByte
)
{-# COMPLETE Range #-}
instance Show Range where
showsPrec :: Int -> Range -> ShowS
showsPrec :: Int -> Range -> ShowS
showsPrec Int
p Range{Word32
Point
rangeStartPoint :: Range -> Point
rangeEndPoint :: Range -> Point
rangeStartByte :: Range -> Word32
rangeEndByte :: Range -> Word32
rangeStartPoint :: Point
rangeEndPoint :: Point
rangeStartByte :: Word32
rangeEndByte :: Word32
..} =
Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
[Char] -> ShowS
showString [Char]
"Range "
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Point -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Point
rangeStartPoint
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Point -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Point
rangeEndPoint
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Word32
rangeStartByte
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 Word32
rangeEndByte
newtype LogType = WrapTSLogType {LogType -> TSLogType
unWrapTSLogType :: C.TSLogType}
deriving (LogType -> LogType -> Bool
(LogType -> LogType -> Bool)
-> (LogType -> LogType -> Bool) -> Eq LogType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LogType -> LogType -> Bool
== :: LogType -> LogType -> Bool
$c/= :: LogType -> LogType -> Bool
/= :: LogType -> LogType -> Bool
Eq)
pattern LogTypeParse :: LogType
pattern $mLogTypeParse :: forall {r}. LogType -> ((# #) -> r) -> ((# #) -> r) -> r
$bLogTypeParse :: LogType
LogTypeParse = WrapTSLogType C.TSLogTypeParse
pattern LogTypeLex :: LogType
pattern $mLogTypeLex :: forall {r}. LogType -> ((# #) -> r) -> ((# #) -> r) -> r
$bLogTypeLex :: LogType
LogTypeLex = WrapTSLogType C.TSLogTypeLex
{-# COMPLETE LogTypeParse, LogTypeLex #-}
instance Show LogType where
show :: LogType -> [Char]
show LogType
LogTypeParse = [Char]
"LogTypeParse"
show LogType
LogTypeLex = [Char]
"LogTypeLex"
type Log = LogType -> ByteString -> IO ()
logToTSLog :: Log -> C.TSLog
logToTSLog :: Log -> TSLog
logToTSLog Log
logFun = \TSLogType
logType ConstPtr CChar
logMsg ->
CString -> IO ByteString
BS.packCString (ConstPtr CChar -> CString
forall a. ConstPtr a -> Ptr a
unConstPtr ConstPtr CChar
logMsg) IO ByteString -> (ByteString -> IO ()) -> IO ()
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Log
logFun (TSLogType -> LogType
forall a b. Coercible a b => a -> b
coerce TSLogType
logType)
tsLogToLog :: C.TSLog -> Log
tsLogToLog :: TSLog -> Log
tsLogToLog TSLog
logFun = \LogType
logType ByteString
logMsg ->
ByteString -> (CString -> IO ()) -> IO ()
forall a. ByteString -> (CString -> IO a) -> IO a
BS.useAsCString ByteString
logMsg ((CString -> IO ()) -> IO ()) -> (CString -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ TSLog
logFun (LogType -> TSLogType
forall a b. Coercible a b => a -> b
coerce LogType
logType) (ConstPtr CChar -> IO ())
-> (CString -> ConstPtr CChar) -> CString -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> ConstPtr CChar
forall a. Ptr a -> ConstPtr a
ConstPtr
newtype InputEdit = WrapTSInputEdit {InputEdit -> TSInputEdit
unWrapTSInputEdit :: C.TSInputEdit}
pattern InputEdit :: Word32 -> Word32 -> Word32 -> Point -> Point -> Point -> InputEdit
pattern $mInputEdit :: forall {r}.
InputEdit
-> (Word32 -> Word32 -> Word32 -> Point -> Point -> Point -> r)
-> ((# #) -> r)
-> r
$bInputEdit :: Word32 -> Word32 -> Word32 -> Point -> Point -> Point -> InputEdit
InputEdit
{ InputEdit -> Word32
inputEditStartByte
, InputEdit -> Word32
inputEditOldEndByte
, InputEdit -> Word32
inputEditNewEndByte
, InputEdit -> Point
inputEditStartPoint
, InputEdit -> Point
inputEditOldEndPoint
, InputEdit -> Point
inputEditNewEndPoint
} <-
WrapTSInputEdit
( C.TSInputEdit
inputEditStartByte
inputEditOldEndByte
inputEditNewEndByte
(WrapTSPoint -> inputEditStartPoint)
(WrapTSPoint -> inputEditOldEndPoint)
(WrapTSPoint -> inputEditNewEndPoint)
)
where
InputEdit Word32
startByte Word32
oldEndByte Word32
newEndByte Point
startPoint Point
oldEndPoint Point
newEndPoint =
TSInputEdit -> InputEdit
WrapTSInputEdit
( Word32
-> Word32 -> Word32 -> TSPoint -> TSPoint -> TSPoint -> TSInputEdit
C.TSInputEdit
Word32
startByte
Word32
oldEndByte
Word32
newEndByte
(Point -> TSPoint
unWrapTSPoint Point
startPoint)
(Point -> TSPoint
unWrapTSPoint Point
oldEndPoint)
(Point -> TSPoint
unWrapTSPoint Point
newEndPoint)
)
newtype Node = WrapTSNode {Node -> TSNode
unWrapTSNode :: C.TSNode}
newtype NodeId = WrapTSNodeId {NodeId -> Int
unWrapTSNodeId :: Int}
deriving stock (NodeId -> NodeId -> Bool
(NodeId -> NodeId -> Bool)
-> (NodeId -> NodeId -> Bool) -> Eq NodeId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NodeId -> NodeId -> Bool
== :: NodeId -> NodeId -> Bool
$c/= :: NodeId -> NodeId -> Bool
/= :: NodeId -> NodeId -> Bool
Eq, Eq NodeId
Eq NodeId =>
(NodeId -> NodeId -> Ordering)
-> (NodeId -> NodeId -> Bool)
-> (NodeId -> NodeId -> Bool)
-> (NodeId -> NodeId -> Bool)
-> (NodeId -> NodeId -> Bool)
-> (NodeId -> NodeId -> NodeId)
-> (NodeId -> NodeId -> NodeId)
-> Ord NodeId
NodeId -> NodeId -> Bool
NodeId -> NodeId -> Ordering
NodeId -> NodeId -> NodeId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: NodeId -> NodeId -> Ordering
compare :: NodeId -> NodeId -> Ordering
$c< :: NodeId -> NodeId -> Bool
< :: NodeId -> NodeId -> Bool
$c<= :: NodeId -> NodeId -> Bool
<= :: NodeId -> NodeId -> Bool
$c> :: NodeId -> NodeId -> Bool
> :: NodeId -> NodeId -> Bool
$c>= :: NodeId -> NodeId -> Bool
>= :: NodeId -> NodeId -> Bool
$cmax :: NodeId -> NodeId -> NodeId
max :: NodeId -> NodeId -> NodeId
$cmin :: NodeId -> NodeId -> NodeId
min :: NodeId -> NodeId -> NodeId
Ord)
deriving newtype (Int -> NodeId -> ShowS
[NodeId] -> ShowS
NodeId -> [Char]
(Int -> NodeId -> ShowS)
-> (NodeId -> [Char]) -> ([NodeId] -> ShowS) -> Show NodeId
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> NodeId -> ShowS
showsPrec :: Int -> NodeId -> ShowS
$cshow :: NodeId -> [Char]
show :: NodeId -> [Char]
$cshowList :: [NodeId] -> ShowS
showList :: [NodeId] -> ShowS
Show)
nodeId :: Node -> NodeId
nodeId :: Node -> NodeId
nodeId = IntPtr -> NodeId
forall a b. Coercible a b => a -> b
coerce (IntPtr -> NodeId) -> (Node -> IntPtr) -> Node -> NodeId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Any -> IntPtr
forall a. Ptr a -> IntPtr
ptrToIntPtr (Ptr Any -> IntPtr) -> (Node -> Ptr Any) -> Node -> IntPtr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstPtr Void -> Ptr Any
forall a b. Coercible a b => a -> b
coerce (ConstPtr Void -> Ptr Any)
-> (Node -> ConstPtr Void) -> Node -> Ptr Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TSNode -> ConstPtr Void
TSNode._id (TSNode -> ConstPtr Void)
-> (Node -> TSNode) -> Node -> ConstPtr Void
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> TSNode
forall a b. Coercible a b => a -> b
coerce
newtype TreeCursor = WrapTSTreeCursor {TreeCursor -> ForeignPtr TSTreeCursor
unWrapTSTreeCursor :: ForeignPtr C.TSTreeCursor}
newtype TreeCursorId = WrapTSTreeCursorId {TreeCursorId -> Word
unWrapTSTreeCursorId :: Word}
deriving (TreeCursorId -> TreeCursorId -> Bool
(TreeCursorId -> TreeCursorId -> Bool)
-> (TreeCursorId -> TreeCursorId -> Bool) -> Eq TreeCursorId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TreeCursorId -> TreeCursorId -> Bool
== :: TreeCursorId -> TreeCursorId -> Bool
$c/= :: TreeCursorId -> TreeCursorId -> Bool
/= :: TreeCursorId -> TreeCursorId -> Bool
Eq, Eq TreeCursorId
Eq TreeCursorId =>
(TreeCursorId -> TreeCursorId -> Ordering)
-> (TreeCursorId -> TreeCursorId -> Bool)
-> (TreeCursorId -> TreeCursorId -> Bool)
-> (TreeCursorId -> TreeCursorId -> Bool)
-> (TreeCursorId -> TreeCursorId -> Bool)
-> (TreeCursorId -> TreeCursorId -> TreeCursorId)
-> (TreeCursorId -> TreeCursorId -> TreeCursorId)
-> Ord TreeCursorId
TreeCursorId -> TreeCursorId -> Bool
TreeCursorId -> TreeCursorId -> Ordering
TreeCursorId -> TreeCursorId -> TreeCursorId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: TreeCursorId -> TreeCursorId -> Ordering
compare :: TreeCursorId -> TreeCursorId -> Ordering
$c< :: TreeCursorId -> TreeCursorId -> Bool
< :: TreeCursorId -> TreeCursorId -> Bool
$c<= :: TreeCursorId -> TreeCursorId -> Bool
<= :: TreeCursorId -> TreeCursorId -> Bool
$c> :: TreeCursorId -> TreeCursorId -> Bool
> :: TreeCursorId -> TreeCursorId -> Bool
$c>= :: TreeCursorId -> TreeCursorId -> Bool
>= :: TreeCursorId -> TreeCursorId -> Bool
$cmax :: TreeCursorId -> TreeCursorId -> TreeCursorId
max :: TreeCursorId -> TreeCursorId -> TreeCursorId
$cmin :: TreeCursorId -> TreeCursorId -> TreeCursorId
min :: TreeCursorId -> TreeCursorId -> TreeCursorId
Ord)
newtype QueryCapture = WrapTSQueryCapture {QueryCapture -> TSQueryCapture
unWrapTSQueryCapture :: C.TSQueryCapture}
newtype Quantifier = WrapTSQuantifier {Quantifier -> TSQuantifier
unWrapTSQuantifier :: C.TSQuantifier}
deriving stock (Quantifier -> Quantifier -> Bool
(Quantifier -> Quantifier -> Bool)
-> (Quantifier -> Quantifier -> Bool) -> Eq Quantifier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Quantifier -> Quantifier -> Bool
== :: Quantifier -> Quantifier -> Bool
$c/= :: Quantifier -> Quantifier -> Bool
/= :: Quantifier -> Quantifier -> Bool
Eq)
pattern QuantifierZero :: Quantifier
pattern $mQuantifierZero :: forall {r}. Quantifier -> ((# #) -> r) -> ((# #) -> r) -> r
$bQuantifierZero :: Quantifier
QuantifierZero = WrapTSQuantifier C.TSQuantifierZero
pattern QuantifierZeroOrOne :: Quantifier
pattern $mQuantifierZeroOrOne :: forall {r}. Quantifier -> ((# #) -> r) -> ((# #) -> r) -> r
$bQuantifierZeroOrOne :: Quantifier
QuantifierZeroOrOne = WrapTSQuantifier C.TSQuantifierZeroOrOne
pattern QuantifierZeroOrMore :: Quantifier
pattern $mQuantifierZeroOrMore :: forall {r}. Quantifier -> ((# #) -> r) -> ((# #) -> r) -> r
$bQuantifierZeroOrMore :: Quantifier
QuantifierZeroOrMore = WrapTSQuantifier C.TSQuantifierZeroOrMore
pattern QuantifierOne :: Quantifier
pattern $mQuantifierOne :: forall {r}. Quantifier -> ((# #) -> r) -> ((# #) -> r) -> r
$bQuantifierOne :: Quantifier
QuantifierOne = WrapTSQuantifier C.TSQuantifierOne
pattern QuantifierOneOrMore :: Quantifier
pattern $mQuantifierOneOrMore :: forall {r}. Quantifier -> ((# #) -> r) -> ((# #) -> r) -> r
$bQuantifierOneOrMore :: Quantifier
QuantifierOneOrMore = WrapTSQuantifier C.TSQuantifierOneOrMore
{-# COMPLETE QuantifierZero, QuantifierZeroOrOne, QuantifierZeroOrMore, QuantifierOne, QuantifierOneOrMore #-}
instance Show Quantifier where
show :: Quantifier -> [Char]
show Quantifier
QuantifierZero = [Char]
"QuantifierZero"
show Quantifier
QuantifierZeroOrOne = [Char]
"QuantifierZeroOrOne"
show Quantifier
QuantifierZeroOrMore = [Char]
"QuantifierZeroOrMore"
show Quantifier
QuantifierOne = [Char]
"QuantifierOne"
show Quantifier
QuantifierOneOrMore = [Char]
"QuantifierOneOrMore"
newtype QueryMatch = WrapTSQueryMatch {QueryMatch -> TSQueryMatch
unWrapTSQueryMatch :: C.TSQueryMatch}
newtype QueryPredicateStepType = WrapTSQueryPredicateStepType {QueryPredicateStepType -> TSQueryPredicateStepType
unWrapTSQueryPredicateStepType :: C.TSQueryPredicateStepType}
deriving stock (QueryPredicateStepType -> QueryPredicateStepType -> Bool
(QueryPredicateStepType -> QueryPredicateStepType -> Bool)
-> (QueryPredicateStepType -> QueryPredicateStepType -> Bool)
-> Eq QueryPredicateStepType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QueryPredicateStepType -> QueryPredicateStepType -> Bool
== :: QueryPredicateStepType -> QueryPredicateStepType -> Bool
$c/= :: QueryPredicateStepType -> QueryPredicateStepType -> Bool
/= :: QueryPredicateStepType -> QueryPredicateStepType -> Bool
Eq)
pattern QueryPredicateStepTypeDone :: QueryPredicateStepType
pattern $mQueryPredicateStepTypeDone :: forall {r}.
QueryPredicateStepType -> ((# #) -> r) -> ((# #) -> r) -> r
$bQueryPredicateStepTypeDone :: QueryPredicateStepType
QueryPredicateStepTypeDone = WrapTSQueryPredicateStepType C.TSQueryPredicateStepTypeDone
pattern QueryPredicateStepTypeCapture :: QueryPredicateStepType
pattern $mQueryPredicateStepTypeCapture :: forall {r}.
QueryPredicateStepType -> ((# #) -> r) -> ((# #) -> r) -> r
$bQueryPredicateStepTypeCapture :: QueryPredicateStepType
QueryPredicateStepTypeCapture = WrapTSQueryPredicateStepType C.TSQueryPredicateStepTypeCapture
pattern QueryPredicateStepTypeString :: QueryPredicateStepType
pattern $mQueryPredicateStepTypeString :: forall {r}.
QueryPredicateStepType -> ((# #) -> r) -> ((# #) -> r) -> r
$bQueryPredicateStepTypeString :: QueryPredicateStepType
QueryPredicateStepTypeString = WrapTSQueryPredicateStepType C.TSQueryPredicateStepTypeString
{-# COMPLETE QueryPredicateStepTypeDone, QueryPredicateStepTypeCapture, QueryPredicateStepTypeString #-}
instance Show QueryPredicateStepType where
show :: QueryPredicateStepType -> [Char]
show QueryPredicateStepType
QueryPredicateStepTypeDone = [Char]
"QueryPredicateStepTypeDone"
show QueryPredicateStepType
QueryPredicateStepTypeCapture = [Char]
"QueryPredicateStepTypeCapture"
show QueryPredicateStepType
QueryPredicateStepTypeString = [Char]
"QueryPredicateStepTypeString"
newtype QueryPredicateStep = WrapTSQueryPredicateStep {QueryPredicateStep -> TSQueryPredicateStep
unWrapTSQueryPredicateStep :: C.TSQueryPredicateStep}
newtype QueryErrorType = WrapTSQueryErrorType {QueryErrorType -> TSQueryError
unWrapTSQueryErrorType :: C.TSQueryError}
deriving stock (QueryErrorType -> QueryErrorType -> Bool
(QueryErrorType -> QueryErrorType -> Bool)
-> (QueryErrorType -> QueryErrorType -> Bool) -> Eq QueryErrorType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QueryErrorType -> QueryErrorType -> Bool
== :: QueryErrorType -> QueryErrorType -> Bool
$c/= :: QueryErrorType -> QueryErrorType -> Bool
/= :: QueryErrorType -> QueryErrorType -> Bool
Eq)
pattern QueryErrorTypeSyntax :: QueryErrorType
pattern $mQueryErrorTypeSyntax :: forall {r}. QueryErrorType -> ((# #) -> r) -> ((# #) -> r) -> r
$bQueryErrorTypeSyntax :: QueryErrorType
QueryErrorTypeSyntax = WrapTSQueryErrorType C.TSQueryErrorSyntax
pattern QueryErrorTypeNodeType :: QueryErrorType
pattern $mQueryErrorTypeNodeType :: forall {r}. QueryErrorType -> ((# #) -> r) -> ((# #) -> r) -> r
$bQueryErrorTypeNodeType :: QueryErrorType
QueryErrorTypeNodeType = WrapTSQueryErrorType C.TSQueryErrorNodeType
pattern QueryErrorTypeField :: QueryErrorType
pattern $mQueryErrorTypeField :: forall {r}. QueryErrorType -> ((# #) -> r) -> ((# #) -> r) -> r
$bQueryErrorTypeField :: QueryErrorType
QueryErrorTypeField = WrapTSQueryErrorType C.TSQueryErrorField
pattern QueryErrorTypeCapture :: QueryErrorType
pattern $mQueryErrorTypeCapture :: forall {r}. QueryErrorType -> ((# #) -> r) -> ((# #) -> r) -> r
$bQueryErrorTypeCapture :: QueryErrorType
QueryErrorTypeCapture = WrapTSQueryErrorType C.TSQueryErrorCapture
pattern QueryErrorTypeStructure :: QueryErrorType
pattern $mQueryErrorTypeStructure :: forall {r}. QueryErrorType -> ((# #) -> r) -> ((# #) -> r) -> r
$bQueryErrorTypeStructure :: QueryErrorType
QueryErrorTypeStructure = WrapTSQueryErrorType C.TSQueryErrorStructure
pattern QueryErrorTypeLanguage :: QueryErrorType
pattern $mQueryErrorTypeLanguage :: forall {r}. QueryErrorType -> ((# #) -> r) -> ((# #) -> r) -> r
$bQueryErrorTypeLanguage :: QueryErrorType
QueryErrorTypeLanguage = WrapTSQueryErrorType C.TSQueryErrorLanguage
{-# COMPLETE QueryErrorTypeSyntax, QueryErrorTypeNodeType, QueryErrorTypeField, QueryErrorTypeCapture, QueryErrorTypeStructure, QueryErrorTypeLanguage #-}
instance Show QueryErrorType where
show :: QueryErrorType -> [Char]
show QueryErrorType
QueryErrorTypeSyntax = [Char]
"QueryErrorTypeSyntax"
show QueryErrorType
QueryErrorTypeNodeType = [Char]
"QueryErrorTypeNodeType"
show QueryErrorType
QueryErrorTypeField = [Char]
"QueryErrorTypeField"
show QueryErrorType
QueryErrorTypeCapture = [Char]
"QueryErrorTypeCapture"
show QueryErrorType
QueryErrorTypeStructure = [Char]
"QueryErrorTypeStructure"
show QueryErrorType
QueryErrorTypeLanguage = [Char]
"QueryErrorTypeLanguage"
data QueryError = QueryError
{ QueryError -> Word32
queryErrorOffset :: !Word32
, QueryError -> Point
queryErrorPoint :: !Point
, QueryError -> [Char]
queryErrorMessage :: !String
, QueryError -> QueryErrorType
queryErrorType :: !QueryErrorType
}
deriving (Int -> QueryError -> ShowS
[QueryError] -> ShowS
QueryError -> [Char]
(Int -> QueryError -> ShowS)
-> (QueryError -> [Char])
-> ([QueryError] -> ShowS)
-> Show QueryError
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> QueryError -> ShowS
showsPrec :: Int -> QueryError -> ShowS
$cshow :: QueryError -> [Char]
show :: QueryError -> [Char]
$cshowList :: [QueryError] -> ShowS
showList :: [QueryError] -> ShowS
Show)
instance Exception QueryError where
displayException :: QueryError -> String
displayException :: QueryError -> [Char]
displayException = QueryError -> [Char]
queryErrorMessage
withParserAsTSParserPtr :: Parser -> (Ptr C.TSParser -> IO a) -> IO a
withParserAsTSParserPtr :: forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr = ForeignPtr TSParser -> (Ptr TSParser -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (ForeignPtr TSParser -> (Ptr TSParser -> IO a) -> IO a)
-> (Parser -> ForeignPtr TSParser)
-> Parser
-> (Ptr TSParser -> IO a)
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser -> ForeignPtr TSParser
forall a b. Coercible a b => a -> b
coerce
parserNew :: IO Parser
parserNew :: IO Parser
parserNew = (FinalizerPtr Any -> Ptr Any -> IO (ForeignPtr Any))
-> FunPtr (Ptr TSParser -> IO ()) -> Ptr TSParser -> IO Parser
forall a b. Coercible a b => a -> b
coerce FinalizerPtr Any -> Ptr Any -> IO (ForeignPtr Any)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FunPtr (Ptr TSParser -> IO ())
C.p_ts_parser_delete (Ptr TSParser -> IO Parser) -> IO (Ptr TSParser) -> IO Parser
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (Ptr TSParser)
C.ts_parser_new
unsafeParserDelete :: Parser -> IO ()
unsafeParserDelete :: Parser -> IO ()
unsafeParserDelete = (ForeignPtr Any -> IO ()) -> Parser -> IO ()
forall a b. Coercible a b => a -> b
coerce ForeignPtr Any -> IO ()
forall a. ForeignPtr a -> IO ()
finalizeForeignPtr
withParser :: (Parser -> IO a) -> IO a
withParser :: forall a. (Parser -> IO a) -> IO a
withParser = IO Parser -> (Parser -> IO ()) -> (Parser -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket IO Parser
parserNew Parser -> IO ()
unsafeParserDelete
parserLanguage :: Parser -> IO Language
parserLanguage :: Parser -> IO Language
parserLanguage Parser
parser =
Parser -> (Ptr TSParser -> IO Language) -> IO Language
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO Language) -> IO Language)
-> (Ptr TSParser -> IO Language) -> IO Language
forall a b. (a -> b) -> a -> b
$
ConstPtr Any -> IO Language
forall tsLanguage. ConstPtr tsLanguage -> IO Language
unsafeToLanguage (ConstPtr Any -> IO Language)
-> (Ptr TSParser -> IO (ConstPtr Any))
-> Ptr TSParser
-> IO Language
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (ConstPtr TSParser -> IO (ConstPtr TSLanguage))
-> Ptr TSParser -> IO (ConstPtr Any)
forall a b. Coercible a b => a -> b
coerce ConstPtr TSParser -> IO (ConstPtr TSLanguage)
C.ts_parser_language
parserSetLanguage :: Parser -> Language -> IO Bool
parserSetLanguage :: Parser -> Language -> IO Bool
parserSetLanguage Parser
parser Language
language =
Parser -> (Ptr TSParser -> IO Bool) -> IO Bool
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO Bool) -> IO Bool)
-> (Ptr TSParser -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr TSParser
parserPtr -> do
Language -> (ConstPtr TSLanguage -> IO Bool) -> IO Bool
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr Language
language ((ConstPtr TSLanguage -> IO Bool) -> IO Bool)
-> (ConstPtr TSLanguage -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLanguage
languagePtr -> do
CBool
success <- Ptr TSParser -> ConstPtr TSLanguage -> IO CBool
C.ts_parser_set_language Ptr TSParser
parserPtr ConstPtr TSLanguage
languagePtr
Bool -> IO Bool
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool CBool
success
parserSetIncludedRanges :: Parser -> [Range] -> IO Bool
parserSetIncludedRanges :: Parser -> [Range] -> IO Bool
parserSetIncludedRanges Parser
parser [Range]
ranges =
Parser -> (Ptr TSParser -> IO Bool) -> IO Bool
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO Bool) -> IO Bool)
-> (Ptr TSParser -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr TSParser
parserPtr -> do
let rangesLength :: Int
rangesLength = [Range] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Range]
ranges
[TSRange] -> (Ptr TSRange -> IO Bool) -> IO Bool
forall a b. Storable a => [a] -> (Ptr a -> IO b) -> IO b
withArray ([Range] -> [TSRange]
forall a b. Coercible a b => a -> b
coerce [Range]
ranges) ((Ptr TSRange -> IO Bool) -> IO Bool)
-> (Ptr TSRange -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr TSRange
rangesPtr -> do
CBool
success <-
Ptr TSParser -> ConstPtr TSRange -> Word32 -> IO CBool
C.ts_parser_set_included_ranges
Ptr TSParser
parserPtr
(Ptr TSRange -> ConstPtr TSRange
forall a. Ptr a -> ConstPtr a
ConstPtr Ptr TSRange
rangesPtr)
(Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
rangesLength)
Bool -> IO Bool
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool CBool
success
parserIncludedRanges :: Parser -> IO [Range]
parserIncludedRanges :: Parser -> IO [Range]
parserIncludedRanges Parser
parser =
Parser -> (Ptr TSParser -> IO [Range]) -> IO [Range]
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO [Range]) -> IO [Range])
-> (Ptr TSParser -> IO [Range]) -> IO [Range]
forall a b. (a -> b) -> a -> b
$ \Ptr TSParser
parserPtr -> do
(Ptr Word32 -> IO [Range]) -> IO [Range]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Word32 -> IO [Range]) -> IO [Range])
-> (Ptr Word32 -> IO [Range]) -> IO [Range]
forall a b. (a -> b) -> a -> b
$ \Ptr Word32
rangesLengthPtr -> do
ConstPtr TSRange
rangesPtr <-
ConstPtr TSParser -> Ptr Word32 -> IO (ConstPtr TSRange)
C.ts_parser_included_ranges
(Ptr TSParser -> ConstPtr TSParser
forall a. Ptr a -> ConstPtr a
ConstPtr Ptr TSParser
parserPtr)
Ptr Word32
rangesLengthPtr
Int
rangesLength <- Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> IO Word32 -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
rangesLengthPtr
IO [TSRange] -> IO [Range]
forall a b. Coercible a b => a -> b
coerce (IO [TSRange] -> IO [Range]) -> IO [TSRange] -> IO [Range]
forall a b. (a -> b) -> a -> b
$ Int -> Ptr TSRange -> IO [TSRange]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
rangesLength (ConstPtr TSRange -> Ptr TSRange
forall a. ConstPtr a -> Ptr a
unConstPtr ConstPtr TSRange
rangesPtr)
parserSetLogger :: Parser -> Log -> IO ()
parserSetLogger :: Parser -> Log -> IO ()
parserSetLogger Parser
parser Log
logFun =
Parser -> (Ptr TSParser -> IO ()) -> IO ()
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO ()) -> IO ())
-> (Ptr TSParser -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSParser
parserPtr ->
Ptr TSParser -> TSLog -> IO ()
C.ts_parser_set_logger (Ptr TSParser -> Ptr TSParser
forall a b. Coercible a b => a -> b
coerce Ptr TSParser
parserPtr) (Log -> TSLog
logToTSLog Log
logFun)
parserLogger :: Parser -> IO (Maybe Log)
parserLogger :: Parser -> IO (Maybe Log)
parserLogger Parser
parser =
Parser -> (Ptr TSParser -> IO (Maybe Log)) -> IO (Maybe Log)
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO (Maybe Log)) -> IO (Maybe Log))
-> (Ptr TSParser -> IO (Maybe Log)) -> IO (Maybe Log)
forall a b. (a -> b) -> a -> b
$
(Maybe TSLog -> Maybe Log) -> IO (Maybe TSLog) -> IO (Maybe Log)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((TSLog -> Log) -> Maybe TSLog -> Maybe Log
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TSLog -> Log
tsLogToLog) (IO (Maybe TSLog) -> IO (Maybe Log))
-> (Ptr TSParser -> IO (Maybe TSLog))
-> Ptr TSParser
-> IO (Maybe Log)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstPtr TSParser -> IO (Maybe TSLog)
C.ts_parser_logger (ConstPtr TSParser -> IO (Maybe TSLog))
-> (Ptr TSParser -> ConstPtr TSParser)
-> Ptr TSParser
-> IO (Maybe TSLog)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr TSParser -> ConstPtr TSParser
forall a b. Coercible a b => a -> b
coerce
parserHasLogger :: Parser -> IO Bool
parserHasLogger :: Parser -> IO Bool
parserHasLogger = (Maybe Log -> Bool) -> IO (Maybe Log) -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe Log -> Bool
forall a. Maybe a -> Bool
isJust (IO (Maybe Log) -> IO Bool)
-> (Parser -> IO (Maybe Log)) -> Parser -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Parser -> IO (Maybe Log)
parserLogger
parserRemoveLogger :: Parser -> IO (Maybe Log)
parserRemoveLogger :: Parser -> IO (Maybe Log)
parserRemoveLogger Parser
parser =
Parser -> (Ptr TSParser -> IO (Maybe Log)) -> IO (Maybe Log)
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO (Maybe Log)) -> IO (Maybe Log))
-> (Ptr TSParser -> IO (Maybe Log)) -> IO (Maybe Log)
forall a b. (a -> b) -> a -> b
$
(Maybe TSLog -> Maybe Log) -> IO (Maybe TSLog) -> IO (Maybe Log)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((TSLog -> Log) -> Maybe TSLog -> Maybe Log
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TSLog -> Log
tsLogToLog) (IO (Maybe TSLog) -> IO (Maybe Log))
-> (Ptr TSParser -> IO (Maybe TSLog))
-> Ptr TSParser
-> IO (Maybe Log)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr TSParser -> IO (Maybe TSLog)
C.ts_parser_remove_logger (Ptr TSParser -> IO (Maybe TSLog))
-> (Ptr TSParser -> Ptr TSParser)
-> Ptr TSParser
-> IO (Maybe TSLog)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr TSParser -> Ptr TSParser
forall a b. Coercible a b => a -> b
coerce
type Input =
Word32 ->
Point ->
IO ByteString
parserParse :: Parser -> Maybe Tree -> Input -> InputEncoding -> IO (Maybe Tree)
parserParse :: Parser -> Maybe Tree -> Input -> InputEncoding -> IO (Maybe Tree)
parserParse Parser
parser Maybe Tree
oldTree Input
input InputEncoding
encoding =
Parser -> (Ptr TSParser -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO (Maybe Tree)) -> IO (Maybe Tree))
-> (Ptr TSParser -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a b. (a -> b) -> a -> b
$ \Ptr TSParser
parserPtr ->
Maybe Tree -> (Ptr TSTree -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a. Maybe Tree -> (Ptr TSTree -> IO a) -> IO a
withMaybeTreeAsTSTreePtr Maybe Tree
oldTree ((Ptr TSTree -> IO (Maybe Tree)) -> IO (Maybe Tree))
-> (Ptr TSTree -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a b. (a -> b) -> a -> b
$ \Ptr TSTree
oldTreePtr -> do
IORef ByteString
chunkRef <- ByteString -> IO (IORef ByteString)
forall a. a -> IO (IORef a)
newIORef ByteString
BS.empty
let tsRead :: Word32 -> Ptr TSPoint -> Ptr Word32 -> IO (ConstPtr CChar)
tsRead = \Word32
byteIndex Ptr TSPoint
position_p Ptr Word32
bytesRead -> do
Point
position <- TSPoint -> Point
WrapTSPoint (TSPoint -> Point) -> IO TSPoint -> IO Point
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr TSPoint -> IO TSPoint
forall a. Storable a => Ptr a -> IO a
peek Ptr TSPoint
position_p
chunk :: ByteString
chunk@(BS ForeignPtr Word8
chunkForeignPtr Int
chunkLenInt) <- Input
input Word32
byteIndex Point
position
IORef ByteString -> ByteString -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef ByteString
chunkRef ByteString
chunk
let chunkLen :: Word32
chunkLen = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
chunkLenInt
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word32
bytesRead Word32
chunkLen
let chunkPtr :: ConstPtr CChar
chunkPtr = Ptr Word8 -> ConstPtr CChar
forall a b. Coercible a b => a -> b
coerce (ForeignPtr Word8 -> Ptr Word8
forall a. ForeignPtr a -> Ptr a
unsafeForeignPtrToPtr ForeignPtr Word8
chunkForeignPtr)
ConstPtr CChar -> IO (ConstPtr CChar)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ConstPtr CChar
chunkPtr
Ptr TSTree
newTreePtr <-
Ptr TSParser
-> ConstPtr TSTree
-> (Word32 -> Ptr TSPoint -> Ptr Word32 -> IO (ConstPtr CChar))
-> TSInputEncoding
-> IO (Ptr TSTree)
C.ts_parser_parse
Ptr TSParser
parserPtr
(Ptr TSTree -> ConstPtr TSTree
forall a. Ptr a -> ConstPtr a
ConstPtr Ptr TSTree
oldTreePtr)
Word32 -> Ptr TSPoint -> Ptr Word32 -> IO (ConstPtr CChar)
tsRead
(InputEncoding -> TSInputEncoding
forall a b. Coercible a b => a -> b
coerce InputEncoding
encoding)
Ptr TSTree -> IO (Maybe Tree)
toMaybeTree Ptr TSTree
newTreePtr
parserParseString :: Parser -> Maybe Tree -> String -> IO (Maybe Tree)
parserParseString :: Parser -> Maybe Tree -> [Char] -> IO (Maybe Tree)
parserParseString Parser
parser Maybe Tree
oldTree [Char]
string =
Parser -> Maybe Tree -> ByteString -> IO (Maybe Tree)
parserParseByteString Parser
parser Maybe Tree
oldTree ([Char] -> ByteString
BSC.pack [Char]
string)
parserParseByteString :: Parser -> Maybe Tree -> ByteString -> IO (Maybe Tree)
parserParseByteString :: Parser -> Maybe Tree -> ByteString -> IO (Maybe Tree)
parserParseByteString Parser
parser Maybe Tree
oldTree ByteString
string =
Parser -> (Ptr TSParser -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO (Maybe Tree)) -> IO (Maybe Tree))
-> (Ptr TSParser -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a b. (a -> b) -> a -> b
$ \Ptr TSParser
parserPtr ->
Maybe Tree -> (Ptr TSTree -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a. Maybe Tree -> (Ptr TSTree -> IO a) -> IO a
withMaybeTreeAsTSTreePtr Maybe Tree
oldTree ((Ptr TSTree -> IO (Maybe Tree)) -> IO (Maybe Tree))
-> (Ptr TSTree -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a b. (a -> b) -> a -> b
$ \Ptr TSTree
oldTreePtr ->
ByteString -> (CStringLen -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BSU.unsafeUseAsCStringLen ByteString
string ((CStringLen -> IO (Maybe Tree)) -> IO (Maybe Tree))
-> (CStringLen -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a b. (a -> b) -> a -> b
$ \(CString
stringPtr, Int
stringLen) -> do
Ptr TSTree
newTreePtr <-
Ptr TSParser
-> ConstPtr TSTree -> ConstPtr CChar -> Word32 -> IO (Ptr TSTree)
C.ts_parser_parse_string
Ptr TSParser
parserPtr
(Ptr TSTree -> ConstPtr TSTree
forall a. Ptr a -> ConstPtr a
ConstPtr Ptr TSTree
oldTreePtr)
(CString -> ConstPtr CChar
forall a. Ptr a -> ConstPtr a
ConstPtr CString
stringPtr)
(Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
stringLen)
Ptr TSTree -> IO (Maybe Tree)
toMaybeTree Ptr TSTree
newTreePtr
parserParseByteStringWithEncoding :: Parser -> Maybe Tree -> ByteString -> InputEncoding -> IO (Maybe Tree)
parserParseByteStringWithEncoding :: Parser
-> Maybe Tree -> ByteString -> InputEncoding -> IO (Maybe Tree)
parserParseByteStringWithEncoding Parser
parser Maybe Tree
oldTree ByteString
string InputEncoding
inputEncoding =
Parser -> (Ptr TSParser -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO (Maybe Tree)) -> IO (Maybe Tree))
-> (Ptr TSParser -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a b. (a -> b) -> a -> b
$ \Ptr TSParser
parserPtr ->
Maybe Tree -> (Ptr TSTree -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a. Maybe Tree -> (Ptr TSTree -> IO a) -> IO a
withMaybeTreeAsTSTreePtr Maybe Tree
oldTree ((Ptr TSTree -> IO (Maybe Tree)) -> IO (Maybe Tree))
-> (Ptr TSTree -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a b. (a -> b) -> a -> b
$ \Ptr TSTree
oldTreePtr ->
ByteString -> (CStringLen -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BSU.unsafeUseAsCStringLen ByteString
string ((CStringLen -> IO (Maybe Tree)) -> IO (Maybe Tree))
-> (CStringLen -> IO (Maybe Tree)) -> IO (Maybe Tree)
forall a b. (a -> b) -> a -> b
$ \(CString
stringPtr, Int
stringLen) -> do
Ptr TSTree
newTreePtr <-
Ptr TSParser
-> ConstPtr TSTree
-> ConstPtr CChar
-> Word32
-> TSInputEncoding
-> IO (Ptr TSTree)
C.ts_parser_parse_string_encoding
Ptr TSParser
parserPtr
(Ptr TSTree -> ConstPtr TSTree
forall a. Ptr a -> ConstPtr a
ConstPtr Ptr TSTree
oldTreePtr)
(CString -> ConstPtr CChar
forall a. Ptr a -> ConstPtr a
ConstPtr CString
stringPtr)
(Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
stringLen)
(InputEncoding -> TSInputEncoding
forall a b. Coercible a b => a -> b
coerce InputEncoding
inputEncoding)
Ptr TSTree -> IO (Maybe Tree)
toMaybeTree Ptr TSTree
newTreePtr
parserReset :: Parser -> IO ()
parserReset :: Parser -> IO ()
parserReset = (Parser -> (Ptr TSParser -> IO ()) -> IO ()
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
`withParserAsTSParserPtr` Ptr TSParser -> IO ()
C.ts_parser_reset)
newtype Microsecond = Microsecond {Microsecond -> Word64
unMicrosecond :: Word64}
deriving stock (Int -> Microsecond -> ShowS
[Microsecond] -> ShowS
Microsecond -> [Char]
(Int -> Microsecond -> ShowS)
-> (Microsecond -> [Char])
-> ([Microsecond] -> ShowS)
-> Show Microsecond
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Microsecond -> ShowS
showsPrec :: Int -> Microsecond -> ShowS
$cshow :: Microsecond -> [Char]
show :: Microsecond -> [Char]
$cshowList :: [Microsecond] -> ShowS
showList :: [Microsecond] -> ShowS
Show, ReadPrec [Microsecond]
ReadPrec Microsecond
Int -> ReadS Microsecond
ReadS [Microsecond]
(Int -> ReadS Microsecond)
-> ReadS [Microsecond]
-> ReadPrec Microsecond
-> ReadPrec [Microsecond]
-> Read Microsecond
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Microsecond
readsPrec :: Int -> ReadS Microsecond
$creadList :: ReadS [Microsecond]
readList :: ReadS [Microsecond]
$creadPrec :: ReadPrec Microsecond
readPrec :: ReadPrec Microsecond
$creadListPrec :: ReadPrec [Microsecond]
readListPrec :: ReadPrec [Microsecond]
Read, Microsecond -> Microsecond -> Bool
(Microsecond -> Microsecond -> Bool)
-> (Microsecond -> Microsecond -> Bool) -> Eq Microsecond
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Microsecond -> Microsecond -> Bool
== :: Microsecond -> Microsecond -> Bool
$c/= :: Microsecond -> Microsecond -> Bool
/= :: Microsecond -> Microsecond -> Bool
Eq, Eq Microsecond
Eq Microsecond =>
(Microsecond -> Microsecond -> Ordering)
-> (Microsecond -> Microsecond -> Bool)
-> (Microsecond -> Microsecond -> Bool)
-> (Microsecond -> Microsecond -> Bool)
-> (Microsecond -> Microsecond -> Bool)
-> (Microsecond -> Microsecond -> Microsecond)
-> (Microsecond -> Microsecond -> Microsecond)
-> Ord Microsecond
Microsecond -> Microsecond -> Bool
Microsecond -> Microsecond -> Ordering
Microsecond -> Microsecond -> Microsecond
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Microsecond -> Microsecond -> Ordering
compare :: Microsecond -> Microsecond -> Ordering
$c< :: Microsecond -> Microsecond -> Bool
< :: Microsecond -> Microsecond -> Bool
$c<= :: Microsecond -> Microsecond -> Bool
<= :: Microsecond -> Microsecond -> Bool
$c> :: Microsecond -> Microsecond -> Bool
> :: Microsecond -> Microsecond -> Bool
$c>= :: Microsecond -> Microsecond -> Bool
>= :: Microsecond -> Microsecond -> Bool
$cmax :: Microsecond -> Microsecond -> Microsecond
max :: Microsecond -> Microsecond -> Microsecond
$cmin :: Microsecond -> Microsecond -> Microsecond
min :: Microsecond -> Microsecond -> Microsecond
Ord)
deriving newtype (Integer -> Microsecond
Microsecond -> Microsecond
Microsecond -> Microsecond -> Microsecond
(Microsecond -> Microsecond -> Microsecond)
-> (Microsecond -> Microsecond -> Microsecond)
-> (Microsecond -> Microsecond -> Microsecond)
-> (Microsecond -> Microsecond)
-> (Microsecond -> Microsecond)
-> (Microsecond -> Microsecond)
-> (Integer -> Microsecond)
-> Num Microsecond
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Microsecond -> Microsecond -> Microsecond
+ :: Microsecond -> Microsecond -> Microsecond
$c- :: Microsecond -> Microsecond -> Microsecond
- :: Microsecond -> Microsecond -> Microsecond
$c* :: Microsecond -> Microsecond -> Microsecond
* :: Microsecond -> Microsecond -> Microsecond
$cnegate :: Microsecond -> Microsecond
negate :: Microsecond -> Microsecond
$cabs :: Microsecond -> Microsecond
abs :: Microsecond -> Microsecond
$csignum :: Microsecond -> Microsecond
signum :: Microsecond -> Microsecond
$cfromInteger :: Integer -> Microsecond
fromInteger :: Integer -> Microsecond
Num, Num Microsecond
Ord Microsecond
(Num Microsecond, Ord Microsecond) =>
(Microsecond -> Rational) -> Real Microsecond
Microsecond -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Microsecond -> Rational
toRational :: Microsecond -> Rational
Real, Enum Microsecond
Real Microsecond
(Real Microsecond, Enum Microsecond) =>
(Microsecond -> Microsecond -> Microsecond)
-> (Microsecond -> Microsecond -> Microsecond)
-> (Microsecond -> Microsecond -> Microsecond)
-> (Microsecond -> Microsecond -> Microsecond)
-> (Microsecond -> Microsecond -> (Microsecond, Microsecond))
-> (Microsecond -> Microsecond -> (Microsecond, Microsecond))
-> (Microsecond -> Integer)
-> Integral Microsecond
Microsecond -> Integer
Microsecond -> Microsecond -> (Microsecond, Microsecond)
Microsecond -> Microsecond -> Microsecond
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Microsecond -> Microsecond -> Microsecond
quot :: Microsecond -> Microsecond -> Microsecond
$crem :: Microsecond -> Microsecond -> Microsecond
rem :: Microsecond -> Microsecond -> Microsecond
$cdiv :: Microsecond -> Microsecond -> Microsecond
div :: Microsecond -> Microsecond -> Microsecond
$cmod :: Microsecond -> Microsecond -> Microsecond
mod :: Microsecond -> Microsecond -> Microsecond
$cquotRem :: Microsecond -> Microsecond -> (Microsecond, Microsecond)
quotRem :: Microsecond -> Microsecond -> (Microsecond, Microsecond)
$cdivMod :: Microsecond -> Microsecond -> (Microsecond, Microsecond)
divMod :: Microsecond -> Microsecond -> (Microsecond, Microsecond)
$ctoInteger :: Microsecond -> Integer
toInteger :: Microsecond -> Integer
Integral, Int -> Microsecond
Microsecond -> Int
Microsecond -> [Microsecond]
Microsecond -> Microsecond
Microsecond -> Microsecond -> [Microsecond]
Microsecond -> Microsecond -> Microsecond -> [Microsecond]
(Microsecond -> Microsecond)
-> (Microsecond -> Microsecond)
-> (Int -> Microsecond)
-> (Microsecond -> Int)
-> (Microsecond -> [Microsecond])
-> (Microsecond -> Microsecond -> [Microsecond])
-> (Microsecond -> Microsecond -> [Microsecond])
-> (Microsecond -> Microsecond -> Microsecond -> [Microsecond])
-> Enum Microsecond
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Microsecond -> Microsecond
succ :: Microsecond -> Microsecond
$cpred :: Microsecond -> Microsecond
pred :: Microsecond -> Microsecond
$ctoEnum :: Int -> Microsecond
toEnum :: Int -> Microsecond
$cfromEnum :: Microsecond -> Int
fromEnum :: Microsecond -> Int
$cenumFrom :: Microsecond -> [Microsecond]
enumFrom :: Microsecond -> [Microsecond]
$cenumFromThen :: Microsecond -> Microsecond -> [Microsecond]
enumFromThen :: Microsecond -> Microsecond -> [Microsecond]
$cenumFromTo :: Microsecond -> Microsecond -> [Microsecond]
enumFromTo :: Microsecond -> Microsecond -> [Microsecond]
$cenumFromThenTo :: Microsecond -> Microsecond -> Microsecond -> [Microsecond]
enumFromThenTo :: Microsecond -> Microsecond -> Microsecond -> [Microsecond]
Enum)
parserSetTimeoutMicros :: Parser -> Microsecond -> IO ()
parserSetTimeoutMicros :: Parser -> Microsecond -> IO ()
parserSetTimeoutMicros Parser
parser Microsecond
ms =
Parser -> (Ptr TSParser -> IO ()) -> IO ()
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO ()) -> IO ())
-> (Ptr TSParser -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSParser
parserPtr ->
(Ptr TSParser -> Word64 -> IO ())
-> Ptr TSParser -> Microsecond -> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr TSParser -> Word64 -> IO ()
C.ts_parser_set_timeout_micros Ptr TSParser
parserPtr Microsecond
ms
parserTimeoutMicros :: Parser -> IO Microsecond
parserTimeoutMicros :: Parser -> IO Microsecond
parserTimeoutMicros Parser
parser =
Parser -> (Ptr TSParser -> IO Microsecond) -> IO Microsecond
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO Microsecond) -> IO Microsecond)
-> (Ptr TSParser -> IO Microsecond) -> IO Microsecond
forall a b. (a -> b) -> a -> b
$
(Ptr TSParser -> IO Word64) -> Ptr TSParser -> IO Microsecond
forall a b. Coercible a b => a -> b
coerce Ptr TSParser -> IO Word64
C.ts_parser_timeout_micros
newtype CancellationFlag = WrapTSCancellationFlag {CancellationFlag -> CSize
unWrapTSCancellationFlag :: CSize}
isContinue :: CancellationFlag -> Bool
isContinue :: CancellationFlag -> Bool
isContinue = (CSize -> CSize -> Bool
forall a. Eq a => a -> a -> Bool
== CSize
0) (CSize -> Bool)
-> (CancellationFlag -> CSize) -> CancellationFlag -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CancellationFlag -> CSize
unWrapTSCancellationFlag
{-# INLINE isContinue #-}
pattern Continue :: CancellationFlag
pattern $mContinue :: forall {r}. CancellationFlag -> ((# #) -> r) -> ((# #) -> r) -> r
$bContinue :: CancellationFlag
Continue = WrapTSCancellationFlag 0
pattern Cancel :: CancellationFlag
pattern $mCancel :: forall {r}. CancellationFlag -> ((# #) -> r) -> ((# #) -> r) -> r
$bCancel :: CancellationFlag
Cancel <- (isContinue -> False)
where
Cancel = CSize -> CancellationFlag
WrapTSCancellationFlag CSize
1
{-# COMPLETE Continue, Cancel #-}
newtype CancellationFlagRef = CancellationFlagRef {CancellationFlagRef -> ConstPtr CSize
unCancellationFlagRef :: ConstPtr CSize}
putCancellationFlag :: CancellationFlagRef -> CancellationFlag -> IO ()
putCancellationFlag :: CancellationFlagRef -> CancellationFlag -> IO ()
putCancellationFlag = (Ptr CSize -> CSize -> IO ())
-> CancellationFlagRef -> CancellationFlag -> IO ()
forall a b. Coercible a b => a -> b
coerce (forall a. Storable a => Ptr a -> a -> IO ()
poke @CSize)
{-# INLINE putCancellationFlag #-}
getCancellationFlag :: CancellationFlagRef -> IO CancellationFlag
getCancellationFlag :: CancellationFlagRef -> IO CancellationFlag
getCancellationFlag = (Ptr CSize -> IO CSize)
-> CancellationFlagRef -> IO CancellationFlag
forall a b. Coercible a b => a -> b
coerce (forall a. Storable a => Ptr a -> IO a
peek @CSize)
{-# INLINE getCancellationFlag #-}
parserSetCancellationFlag :: Parser -> CancellationFlagRef -> IO ()
parserSetCancellationFlag :: Parser -> CancellationFlagRef -> IO ()
parserSetCancellationFlag Parser
parser CancellationFlagRef
cancellationFlagRef =
Parser -> (Ptr TSParser -> IO ()) -> IO ()
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO ()) -> IO ())
-> (Ptr TSParser -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSParser
parserPtr ->
(Ptr TSParser -> ConstPtr CSize -> IO ())
-> Ptr TSParser -> CancellationFlagRef -> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr TSParser -> ConstPtr CSize -> IO ()
C.ts_parser_set_cancellation_flag Ptr TSParser
parserPtr CancellationFlagRef
cancellationFlagRef
parserCancellationFlag :: Parser -> IO CancellationFlagRef
parserCancellationFlag :: Parser -> IO CancellationFlagRef
parserCancellationFlag Parser
parser =
Parser
-> (Ptr TSParser -> IO CancellationFlagRef)
-> IO CancellationFlagRef
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO CancellationFlagRef)
-> IO CancellationFlagRef)
-> (Ptr TSParser -> IO CancellationFlagRef)
-> IO CancellationFlagRef
forall a b. (a -> b) -> a -> b
$ \Ptr TSParser
parserPtr ->
(ConstPtr TSParser -> IO (ConstPtr CSize))
-> Ptr TSParser -> IO CancellationFlagRef
forall a b. Coercible a b => a -> b
coerce ConstPtr TSParser -> IO (ConstPtr CSize)
C.ts_parser_cancellation_flag Ptr TSParser
parserPtr
parserPrintDotGraphs :: Parser -> Handle -> IO ()
parserPrintDotGraphs :: Parser -> Handle -> IO ()
parserPrintDotGraphs Parser
parser Handle
handle = do
CInt
fileDescriptor <- FD -> CInt
fdFD (FD -> CInt) -> IO FD -> IO CInt
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO FD
handleToFd Handle
handle
Parser -> (Ptr TSParser -> IO ()) -> IO ()
forall a. Parser -> (Ptr TSParser -> IO a) -> IO a
withParserAsTSParserPtr Parser
parser ((Ptr TSParser -> IO ()) -> IO ())
-> (Ptr TSParser -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSParser
parserPtr ->
(Ptr TSParser -> Int32 -> IO ()) -> Ptr TSParser -> CInt -> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr TSParser -> Int32 -> IO ()
C.ts_parser_print_dot_graphs Ptr TSParser
parserPtr CInt
fileDescriptor
toTree :: Ptr C.TSTree -> IO Tree
toTree :: Ptr TSTree -> IO Tree
toTree = (FinalizerPtr Any -> Ptr Any -> IO (ForeignPtr Any))
-> FunPtr (Ptr TSTree -> IO ()) -> Ptr TSTree -> IO Tree
forall a b. Coercible a b => a -> b
coerce FinalizerPtr Any -> Ptr Any -> IO (ForeignPtr Any)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FunPtr (Ptr TSTree -> IO ())
C.p_ts_tree_delete
withTreeAsTSTreePtr :: Tree -> (Ptr C.TSTree -> IO a) -> IO a
withTreeAsTSTreePtr :: forall a. Tree -> (Ptr TSTree -> IO a) -> IO a
withTreeAsTSTreePtr = ForeignPtr TSTree -> (Ptr TSTree -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (ForeignPtr TSTree -> (Ptr TSTree -> IO a) -> IO a)
-> (Tree -> ForeignPtr TSTree)
-> Tree
-> (Ptr TSTree -> IO a)
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tree -> ForeignPtr TSTree
forall a b. Coercible a b => a -> b
coerce
toMaybeTree :: Ptr C.TSTree -> IO (Maybe Tree)
toMaybeTree :: Ptr TSTree -> IO (Maybe Tree)
toMaybeTree Ptr TSTree
treePtr
| Ptr TSTree
treePtr Ptr TSTree -> Ptr TSTree -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr TSTree
forall a. Ptr a
nullPtr = Maybe Tree -> IO (Maybe Tree)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Tree
forall a. Maybe a
Nothing
| Bool
otherwise = Tree -> Maybe Tree
forall a. a -> Maybe a
Just (Tree -> Maybe Tree) -> IO Tree -> IO (Maybe Tree)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr TSTree -> IO Tree
toTree Ptr TSTree
treePtr
withMaybeTreeAsTSTreePtr :: Maybe Tree -> (Ptr C.TSTree -> IO a) -> IO a
withMaybeTreeAsTSTreePtr :: forall a. Maybe Tree -> (Ptr TSTree -> IO a) -> IO a
withMaybeTreeAsTSTreePtr Maybe Tree
mtree Ptr TSTree -> IO a
action =
IO a -> (Tree -> IO a) -> Maybe Tree -> IO a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Ptr TSTree -> IO a
action Ptr TSTree
forall a. Ptr a
nullPtr) (Tree -> (Ptr TSTree -> IO a) -> IO a
forall a. Tree -> (Ptr TSTree -> IO a) -> IO a
`withTreeAsTSTreePtr` Ptr TSTree -> IO a
action) Maybe Tree
mtree
treeCopy :: Tree -> IO Tree
treeCopy :: Tree -> IO Tree
treeCopy Tree
tree =
Tree -> (Ptr TSTree -> IO Tree) -> IO Tree
forall a. Tree -> (Ptr TSTree -> IO a) -> IO a
withTreeAsTSTreePtr Tree
tree ((Ptr TSTree -> IO Tree) -> IO Tree)
-> (Ptr TSTree -> IO Tree) -> IO Tree
forall a b. (a -> b) -> a -> b
$
Ptr TSTree -> IO Tree
toTree (Ptr TSTree -> IO Tree)
-> (Ptr TSTree -> IO (Ptr TSTree)) -> Ptr TSTree -> IO Tree
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Ptr TSTree -> IO (Ptr TSTree)
C.ts_tree_copy
unsafeTreeDelete :: Tree -> IO ()
unsafeTreeDelete :: Tree -> IO ()
unsafeTreeDelete = (ForeignPtr Any -> IO ()) -> Tree -> IO ()
forall a b. Coercible a b => a -> b
coerce ForeignPtr Any -> IO ()
forall a. ForeignPtr a -> IO ()
finalizeForeignPtr
treeRootNode :: Tree -> IO Node
treeRootNode :: Tree -> IO Node
treeRootNode Tree
tree =
Tree -> (Ptr TSTree -> IO Node) -> IO Node
forall a. Tree -> (Ptr TSTree -> IO a) -> IO a
withTreeAsTSTreePtr Tree
tree ((Ptr TSTree -> IO Node) -> IO Node)
-> (Ptr TSTree -> IO Node) -> IO Node
forall a b. (a -> b) -> a -> b
$
(ConstPtr TSTree -> IO TSNode) -> Ptr TSTree -> IO Node
forall a b. Coercible a b => a -> b
coerce ConstPtr TSTree -> IO TSNode
C.ts_tree_root_node
treeRootNodeWithOffset :: Tree -> Word32 -> Point -> IO Node
treeRootNodeWithOffset :: Tree -> Word32 -> Point -> IO Node
treeRootNodeWithOffset Tree
tree Word32
offsetBytes Point
offsetExtent =
Tree -> (Ptr TSTree -> IO Node) -> IO Node
forall a. Tree -> (Ptr TSTree -> IO a) -> IO a
withTreeAsTSTreePtr Tree
tree ((Ptr TSTree -> IO Node) -> IO Node)
-> (Ptr TSTree -> IO Node) -> IO Node
forall a b. (a -> b) -> a -> b
$ \Ptr TSTree
treePtr ->
(ConstPtr TSTree -> Word32 -> TSPoint -> IO TSNode)
-> Ptr TSTree -> Word32 -> Point -> IO Node
forall a b. Coercible a b => a -> b
coerce ConstPtr TSTree -> Word32 -> TSPoint -> IO TSNode
C.ts_tree_root_node_with_offset Ptr TSTree
treePtr Word32
offsetBytes Point
offsetExtent
treeLanguage :: Tree -> IO Language
treeLanguage :: Tree -> IO Language
treeLanguage Tree
tree =
Tree -> (Ptr TSTree -> IO Language) -> IO Language
forall a. Tree -> (Ptr TSTree -> IO a) -> IO a
withTreeAsTSTreePtr Tree
tree ((Ptr TSTree -> IO Language) -> IO Language)
-> (Ptr TSTree -> IO Language) -> IO Language
forall a b. (a -> b) -> a -> b
$
ConstPtr TSLanguage -> IO Language
forall tsLanguage. ConstPtr tsLanguage -> IO Language
unsafeToLanguage (ConstPtr TSLanguage -> IO Language)
-> (Ptr TSTree -> IO (ConstPtr TSLanguage))
-> Ptr TSTree
-> IO Language
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Ptr TSTree -> IO (ConstPtr TSLanguage)
C.ts_tree_language
treeIncludedRanges :: Tree -> IO [Range]
treeIncludedRanges :: Tree -> IO [Range]
treeIncludedRanges Tree
tree = do
(Ptr Word32 -> IO [Range]) -> IO [Range]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Word32 -> IO [Range]) -> IO [Range])
-> (Ptr Word32 -> IO [Range]) -> IO [Range]
forall a b. (a -> b) -> a -> b
$ \Ptr Word32
rangesLengthPtr -> do
Ptr TSRange
rangesPtr <-
Tree -> (Ptr TSTree -> IO (Ptr TSRange)) -> IO (Ptr TSRange)
forall a. Tree -> (Ptr TSTree -> IO a) -> IO a
withTreeAsTSTreePtr Tree
tree ((Ptr TSTree -> IO (Ptr TSRange)) -> IO (Ptr TSRange))
-> (Ptr TSTree -> IO (Ptr TSRange)) -> IO (Ptr TSRange)
forall a b. (a -> b) -> a -> b
$ \Ptr TSTree
treePtr ->
Ptr TSTree -> Ptr Word32 -> IO (Ptr TSRange)
C.ts_tree_included_ranges Ptr TSTree
treePtr Ptr Word32
rangesLengthPtr
Int
rangesLength <- Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> IO Word32 -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
rangesLengthPtr
[TSRange] -> [Range]
forall a b. Coercible a b => a -> b
coerce ([TSRange] -> [Range]) -> IO [TSRange] -> IO [Range]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Ptr TSRange -> IO [TSRange]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
rangesLength Ptr TSRange
rangesPtr
treeEdit :: Tree -> InputEdit -> IO ()
treeEdit :: Tree -> InputEdit -> IO ()
treeEdit Tree
tree InputEdit
inputEdit =
Tree -> (Ptr TSTree -> IO ()) -> IO ()
forall a. Tree -> (Ptr TSTree -> IO a) -> IO a
withTreeAsTSTreePtr Tree
tree ((Ptr TSTree -> IO ()) -> IO ()) -> (Ptr TSTree -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSTree
treePtr ->
TSInputEdit -> (Ptr TSInputEdit -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (InputEdit -> TSInputEdit
forall a b. Coercible a b => a -> b
coerce InputEdit
inputEdit) ((Ptr TSInputEdit -> IO ()) -> IO ())
-> (Ptr TSInputEdit -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSInputEdit
inputEditPtr ->
Ptr TSTree -> Ptr TSInputEdit -> IO ()
C.ts_tree_edit Ptr TSTree
treePtr Ptr TSInputEdit
inputEditPtr
treeGetChangedRanges :: Tree -> Tree -> IO [Range]
treeGetChangedRanges :: Tree -> Tree -> IO [Range]
treeGetChangedRanges Tree
oldTree Tree
newTree =
(Ptr Word32 -> IO [Range]) -> IO [Range]
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Word32 -> IO [Range]) -> IO [Range])
-> (Ptr Word32 -> IO [Range]) -> IO [Range]
forall a b. (a -> b) -> a -> b
$ \Ptr Word32
rangesLengthPtr -> do
Ptr TSRange
rangesPtr <-
Tree -> (Ptr TSTree -> IO (Ptr TSRange)) -> IO (Ptr TSRange)
forall a. Tree -> (Ptr TSTree -> IO a) -> IO a
withTreeAsTSTreePtr Tree
oldTree ((Ptr TSTree -> IO (Ptr TSRange)) -> IO (Ptr TSRange))
-> (Ptr TSTree -> IO (Ptr TSRange)) -> IO (Ptr TSRange)
forall a b. (a -> b) -> a -> b
$ \Ptr TSTree
oldTreePtr ->
Tree -> (Ptr TSTree -> IO (Ptr TSRange)) -> IO (Ptr TSRange)
forall a. Tree -> (Ptr TSTree -> IO a) -> IO a
withTreeAsTSTreePtr Tree
newTree ((Ptr TSTree -> IO (Ptr TSRange)) -> IO (Ptr TSRange))
-> (Ptr TSTree -> IO (Ptr TSRange)) -> IO (Ptr TSRange)
forall a b. (a -> b) -> a -> b
$ \Ptr TSTree
newTreePtr ->
Ptr TSTree -> Ptr TSTree -> Ptr Word32 -> IO (Ptr TSRange)
C.ts_tree_get_changed_ranges Ptr TSTree
oldTreePtr Ptr TSTree
newTreePtr Ptr Word32
rangesLengthPtr
Int
rangesLength <- Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> IO Word32 -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
rangesLengthPtr
[TSRange] -> [Range]
forall a b. Coercible a b => a -> b
coerce ([TSRange] -> [Range]) -> IO [TSRange] -> IO [Range]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Ptr TSRange -> IO [TSRange]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
rangesLength Ptr TSRange
rangesPtr
treePrintDotGraph :: Tree -> Handle -> IO ()
treePrintDotGraph :: Tree -> Handle -> IO ()
treePrintDotGraph Tree
tree Handle
handle = do
CInt
fileDescriptor <- FD -> CInt
fdFD (FD -> CInt) -> IO FD -> IO CInt
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Handle -> IO FD
handleToFd Handle
handle
Tree -> (Ptr TSTree -> IO ()) -> IO ()
forall a. Tree -> (Ptr TSTree -> IO a) -> IO a
withTreeAsTSTreePtr Tree
tree ((Ptr TSTree -> IO ()) -> IO ()) -> (Ptr TSTree -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSTree
treePtr ->
Ptr TSTree -> Int32 -> IO ()
C.ts_tree_print_dot_graph Ptr TSTree
treePtr (CInt -> Int32
forall a b. Coercible a b => a -> b
coerce CInt
fileDescriptor)
nodeType :: Node -> IO ByteString
nodeType :: Node -> IO ByteString
nodeType =
CString -> IO ByteString
BSU.unsafePackCString (CString -> IO ByteString)
-> (Node -> IO CString) -> Node -> IO ByteString
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (TSNode -> IO (ConstPtr CChar)) -> Node -> IO CString
forall a b. Coercible a b => a -> b
coerce TSNode -> IO (ConstPtr CChar)
C.ts_node_type
{-# INLINE nodeType #-}
nodeTypeAsString :: Node -> IO String
nodeTypeAsString :: Node -> IO [Char]
nodeTypeAsString = (ByteString -> [Char]) -> IO ByteString -> IO [Char]
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> [Char]
BSC.unpack (IO ByteString -> IO [Char])
-> (Node -> IO ByteString) -> Node -> IO [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> IO ByteString
nodeType
{-# INLINE nodeTypeAsString #-}
nodeSymbol :: Node -> IO Symbol
nodeSymbol :: Node -> IO Symbol
nodeSymbol = (TSNode -> IO TSSymbol) -> Node -> IO Symbol
forall a b. Coercible a b => a -> b
coerce TSNode -> IO TSSymbol
C.ts_node_symbol
{-# INLINE nodeSymbol #-}
nodeLanguage :: Node -> IO Language
nodeLanguage :: Node -> IO Language
nodeLanguage = ConstPtr Any -> IO Language
forall tsLanguage. ConstPtr tsLanguage -> IO Language
unsafeToLanguage (ConstPtr Any -> IO Language)
-> (Node -> IO (ConstPtr Any)) -> Node -> IO Language
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (TSNode -> IO (ConstPtr TSLanguage)) -> Node -> IO (ConstPtr Any)
forall a b. Coercible a b => a -> b
coerce TSNode -> IO (ConstPtr TSLanguage)
C.ts_node_language
{-# INLINE nodeLanguage #-}
nodeGrammarType :: Node -> IO GrammarType
nodeGrammarType :: Node -> IO GrammarType
nodeGrammarType =
IO ByteString -> IO GrammarType
forall a b. Coercible a b => a -> b
coerce (IO ByteString -> IO GrammarType)
-> (CString -> IO ByteString) -> CString -> IO GrammarType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> IO ByteString
BSU.unsafePackCString (CString -> IO GrammarType)
-> (Node -> IO CString) -> Node -> IO GrammarType
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (TSNode -> IO (ConstPtr CChar)) -> Node -> IO CString
forall a b. Coercible a b => a -> b
coerce TSNode -> IO (ConstPtr CChar)
C.ts_node_grammar_type
{-# INLINE nodeGrammarType #-}
nodeGrammarTypeAsString :: Node -> IO String
nodeGrammarTypeAsString :: Node -> IO [Char]
nodeGrammarTypeAsString = (GrammarType -> [Char]) -> IO GrammarType -> IO [Char]
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ByteString -> [Char]
BSC.unpack (ByteString -> [Char])
-> (GrammarType -> ByteString) -> GrammarType -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GrammarType -> ByteString
forall a b. Coercible a b => a -> b
coerce) (IO GrammarType -> IO [Char])
-> (Node -> IO GrammarType) -> Node -> IO [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> IO GrammarType
nodeGrammarType
{-# INLINE nodeGrammarTypeAsString #-}
nodeGrammarSymbol :: Node -> IO Symbol
nodeGrammarSymbol :: Node -> IO Symbol
nodeGrammarSymbol = (TSNode -> IO TSSymbol) -> Node -> IO Symbol
forall a b. Coercible a b => a -> b
coerce TSNode -> IO TSSymbol
C.ts_node_grammar_symbol
{-# INLINE nodeGrammarSymbol #-}
nodeRange :: Node -> IO Range
nodeRange :: Node -> IO Range
nodeRange Node
node = do
Word32
rangeStartByte <- Node -> IO Word32
nodeStartByte Node
node
Word32
rangeEndByte <- Node -> IO Word32
nodeEndByte Node
node
Point
rangeStartPoint <- Node -> IO Point
nodeStartPoint Node
node
Point
rangeEndPoint <- Node -> IO Point
nodeEndPoint Node
node
Range -> IO Range
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Range{Word32
Point
rangeStartPoint :: Point
rangeEndPoint :: Point
rangeStartByte :: Word32
rangeEndByte :: Word32
rangeStartByte :: Word32
rangeEndByte :: Word32
rangeStartPoint :: Point
rangeEndPoint :: Point
..}
nodeStartByte :: Node -> IO Word32
nodeStartByte :: Node -> IO Word32
nodeStartByte = (TSNode -> IO Word32) -> Node -> IO Word32
forall a b. Coercible a b => a -> b
coerce TSNode -> IO Word32
C.ts_node_start_byte
{-# INLINE nodeStartByte #-}
nodeStartPoint :: Node -> IO Point
nodeStartPoint :: Node -> IO Point
nodeStartPoint = (TSNode -> IO TSPoint) -> Node -> IO Point
forall a b. Coercible a b => a -> b
coerce TSNode -> IO TSPoint
C.ts_node_start_point
{-# INLINE nodeStartPoint #-}
nodeEndByte :: Node -> IO Word32
nodeEndByte :: Node -> IO Word32
nodeEndByte = (TSNode -> IO Word32) -> Node -> IO Word32
forall a b. Coercible a b => a -> b
coerce TSNode -> IO Word32
C.ts_node_end_byte
{-# INLINE nodeEndByte #-}
nodeEndPoint :: Node -> IO Point
nodeEndPoint :: Node -> IO Point
nodeEndPoint = (TSNode -> IO TSPoint) -> Node -> IO Point
forall a b. Coercible a b => a -> b
coerce TSNode -> IO TSPoint
C.ts_node_end_point
{-# INLINE nodeEndPoint #-}
showNode :: Node -> IO ByteString
showNode :: Node -> IO ByteString
showNode = CString -> IO ByteString
BSU.unsafePackMallocCString (CString -> IO ByteString)
-> (Node -> IO CString) -> Node -> IO ByteString
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (TSNode -> IO CString) -> Node -> IO CString
forall a b. Coercible a b => a -> b
coerce TSNode -> IO CString
C.ts_node_string
{-# INLINE showNode #-}
showNodeAsString :: Node -> IO String
showNodeAsString :: Node -> IO [Char]
showNodeAsString = (ByteString -> [Char]) -> IO ByteString -> IO [Char]
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> [Char]
BSC.unpack (IO ByteString -> IO [Char])
-> (Node -> IO ByteString) -> Node -> IO [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> IO ByteString
showNode
{-# INLINE showNodeAsString #-}
nodeIsNull :: Node -> IO Bool
nodeIsNull :: Node -> IO Bool
nodeIsNull = (CBool -> Bool) -> IO CBool -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CBool -> IO Bool) -> (Node -> IO CBool) -> Node -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TSNode -> IO CBool
C.ts_node_is_null (TSNode -> IO CBool) -> (Node -> TSNode) -> Node -> IO CBool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> TSNode
forall a b. Coercible a b => a -> b
coerce
{-# INLINE nodeIsNull #-}
nodeIsNamed :: Node -> IO Bool
nodeIsNamed :: Node -> IO Bool
nodeIsNamed = (CBool -> Bool) -> IO CBool -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CBool -> IO Bool) -> (Node -> IO CBool) -> Node -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TSNode -> IO CBool
C.ts_node_is_named (TSNode -> IO CBool) -> (Node -> TSNode) -> Node -> IO CBool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> TSNode
forall a b. Coercible a b => a -> b
coerce
{-# INLINE nodeIsNamed #-}
nodeIsMissing :: Node -> IO Bool
nodeIsMissing :: Node -> IO Bool
nodeIsMissing = (CBool -> Bool) -> IO CBool -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CBool -> IO Bool) -> (Node -> IO CBool) -> Node -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TSNode -> IO CBool
C.ts_node_is_missing (TSNode -> IO CBool) -> (Node -> TSNode) -> Node -> IO CBool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> TSNode
forall a b. Coercible a b => a -> b
coerce
{-# INLINE nodeIsMissing #-}
nodeIsExtra :: Node -> IO Bool
= (CBool -> Bool) -> IO CBool -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CBool -> IO Bool) -> (Node -> IO CBool) -> Node -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TSNode -> IO CBool
C.ts_node_is_extra (TSNode -> IO CBool) -> (Node -> TSNode) -> Node -> IO CBool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> TSNode
forall a b. Coercible a b => a -> b
coerce
{-# INLINE nodeIsExtra #-}
nodeHasChanges :: Node -> IO Bool
nodeHasChanges :: Node -> IO Bool
nodeHasChanges = (CBool -> Bool) -> IO CBool -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CBool -> IO Bool) -> (Node -> IO CBool) -> Node -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TSNode -> IO CBool
C.ts_node_has_changes (TSNode -> IO CBool) -> (Node -> TSNode) -> Node -> IO CBool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> TSNode
forall a b. Coercible a b => a -> b
coerce
{-# INLINE nodeHasChanges #-}
nodeHasError :: Node -> IO Bool
nodeHasError :: Node -> IO Bool
nodeHasError = (CBool -> Bool) -> IO CBool -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CBool -> IO Bool) -> (Node -> IO CBool) -> Node -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TSNode -> IO CBool
C.ts_node_has_error (TSNode -> IO CBool) -> (Node -> TSNode) -> Node -> IO CBool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> TSNode
forall a b. Coercible a b => a -> b
coerce
{-# INLINE nodeHasError #-}
nodeIsError :: Node -> IO Bool
nodeIsError :: Node -> IO Bool
nodeIsError = (CBool -> Bool) -> IO CBool -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CBool -> IO Bool) -> (Node -> IO CBool) -> Node -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TSNode -> IO CBool
C.ts_node_is_error (TSNode -> IO CBool) -> (Node -> TSNode) -> Node -> IO CBool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> TSNode
forall a b. Coercible a b => a -> b
coerce
{-# INLINE nodeIsError #-}
nodeParseState :: Node -> IO StateId
nodeParseState :: Node -> IO StateId
nodeParseState = (TSNode -> IO TSStateId) -> Node -> IO StateId
forall a b. Coercible a b => a -> b
coerce TSNode -> IO TSStateId
C.ts_node_parse_state
{-# INLINE nodeParseState #-}
nodeNextParseState :: Node -> IO StateId
nodeNextParseState :: Node -> IO StateId
nodeNextParseState = (TSNode -> IO TSStateId) -> Node -> IO StateId
forall a b. Coercible a b => a -> b
coerce TSNode -> IO TSStateId
C.ts_node_next_parse_state
{-# INLINE nodeNextParseState #-}
nodeParent :: Node -> IO Node
nodeParent :: Node -> IO Node
nodeParent = (TSNode -> IO TSNode) -> Node -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> IO TSNode
C.ts_node_parent
{-# INLINE nodeParent #-}
nodeChildWithDescendant :: Node -> Node -> IO Node
nodeChildWithDescendant :: Node -> Node -> IO Node
nodeChildWithDescendant = (TSNode -> TSNode -> IO TSNode) -> Node -> Node -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> TSNode -> IO TSNode
C.ts_node_child_with_descendant
{-# INLINE nodeChildWithDescendant #-}
nodeChild :: Node -> Word32 -> IO Node
nodeChild :: Node -> Word32 -> IO Node
nodeChild = (TSNode -> Word32 -> IO TSNode) -> Node -> Word32 -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> Word32 -> IO TSNode
C.ts_node_child
{-# INLINE nodeChild #-}
nodeFieldNameForChild :: Node -> Word32 -> IO FieldName
nodeFieldNameForChild :: Node -> Word32 -> IO FieldName
nodeFieldNameForChild Node
node =
IO ByteString -> IO FieldName
forall a b. Coercible a b => a -> b
coerce (IO ByteString -> IO FieldName)
-> (CString -> IO ByteString) -> CString -> IO FieldName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> IO ByteString
BSU.unsafePackCString (CString -> IO FieldName)
-> (Word32 -> IO CString) -> Word32 -> IO FieldName
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (TSNode -> Word32 -> IO (ConstPtr CChar))
-> Node -> Word32 -> IO CString
forall a b. Coercible a b => a -> b
coerce TSNode -> Word32 -> IO (ConstPtr CChar)
C.ts_node_field_name_for_child Node
node
{-# INLINE nodeFieldNameForChild #-}
nodeFieldNameForChildAsString :: Node -> Word32 -> IO String
nodeFieldNameForChildAsString :: Node -> Word32 -> IO [Char]
nodeFieldNameForChildAsString Node
node Word32
childIndex =
ByteString -> [Char]
BSC.unpack (ByteString -> [Char])
-> (FieldName -> ByteString) -> FieldName -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldName -> ByteString
forall a b. Coercible a b => a -> b
coerce (FieldName -> [Char]) -> IO FieldName -> IO [Char]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Node -> Word32 -> IO FieldName
nodeFieldNameForChild Node
node Word32
childIndex
{-# INLINE nodeFieldNameForChildAsString #-}
nodeFieldNameForNamedChild :: Node -> Word32 -> IO FieldName
nodeFieldNameForNamedChild :: Node -> Word32 -> IO FieldName
nodeFieldNameForNamedChild Node
node =
IO ByteString -> IO FieldName
forall a b. Coercible a b => a -> b
coerce (IO ByteString -> IO FieldName)
-> (CString -> IO ByteString) -> CString -> IO FieldName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> IO ByteString
BSU.unsafePackCString (CString -> IO FieldName)
-> (Word32 -> IO CString) -> Word32 -> IO FieldName
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (TSNode -> Word32 -> IO (ConstPtr CChar))
-> Node -> Word32 -> IO CString
forall a b. Coercible a b => a -> b
coerce TSNode -> Word32 -> IO (ConstPtr CChar)
C.ts_node_field_name_for_named_child Node
node
{-# INLINE nodeFieldNameForNamedChild #-}
nodeFieldNameForNamedChildAsString :: Node -> Word32 -> IO String
nodeFieldNameForNamedChildAsString :: Node -> Word32 -> IO [Char]
nodeFieldNameForNamedChildAsString Node
node Word32
childIndex =
ByteString -> [Char]
BSC.unpack (ByteString -> [Char])
-> (FieldName -> ByteString) -> FieldName -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldName -> ByteString
forall a b. Coercible a b => a -> b
coerce (FieldName -> [Char]) -> IO FieldName -> IO [Char]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Node -> Word32 -> IO FieldName
nodeFieldNameForNamedChild Node
node Word32
childIndex
{-# INLINE nodeFieldNameForNamedChildAsString #-}
nodeChildCount :: Node -> IO Word32
nodeChildCount :: Node -> IO Word32
nodeChildCount = (TSNode -> IO Word32) -> Node -> IO Word32
forall a b. Coercible a b => a -> b
coerce TSNode -> IO Word32
C.ts_node_child_count
{-# INLINE nodeChildCount #-}
nodeNamedChild :: Node -> Word32 -> IO Node
nodeNamedChild :: Node -> Word32 -> IO Node
nodeNamedChild = (TSNode -> Word32 -> IO TSNode) -> Node -> Word32 -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> Word32 -> IO TSNode
C.ts_node_named_child
{-# INLINE nodeNamedChild #-}
nodeNamedChildCount :: Node -> IO Word32
nodeNamedChildCount :: Node -> IO Word32
nodeNamedChildCount = (TSNode -> IO Word32) -> Node -> IO Word32
forall a b. Coercible a b => a -> b
coerce TSNode -> IO Word32
C.ts_node_named_child_count
{-# INLINE nodeNamedChildCount #-}
nodeChildByFieldName :: Node -> FieldName -> IO Node
nodeChildByFieldName :: Node -> FieldName -> IO Node
nodeChildByFieldName Node
node FieldName
fieldName =
ByteString -> (CStringLen -> IO Node) -> IO Node
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BSU.unsafeUseAsCStringLen (FieldName -> ByteString
forall a b. Coercible a b => a -> b
coerce FieldName
fieldName) ((CStringLen -> IO Node) -> IO Node)
-> (CStringLen -> IO Node) -> IO Node
forall a b. (a -> b) -> a -> b
$ \(CString
stringPtr, Int
stringLen) ->
(TSNode -> ConstPtr CChar -> Word32 -> IO TSNode)
-> Node -> CString -> Word32 -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> ConstPtr CChar -> Word32 -> IO TSNode
C.ts_node_child_by_field_name Node
node CString
stringPtr (Word32 -> IO Node) -> Word32 -> IO Node
forall a b. (a -> b) -> a -> b
$
forall a b. (Integral a, Num b) => a -> b
fromIntegral @_ @Word32 Int
stringLen
{-# INLINE nodeChildByFieldName #-}
nodeChildByFieldId :: Node -> FieldId -> IO Node
nodeChildByFieldId :: Node -> FieldId -> IO Node
nodeChildByFieldId = (TSNode -> TSFieldId -> IO TSNode) -> Node -> FieldId -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> TSFieldId -> IO TSNode
C.ts_node_child_by_field_id
{-# INLINE nodeChildByFieldId #-}
nodeNextSibling :: Node -> IO Node
nodeNextSibling :: Node -> IO Node
nodeNextSibling = (TSNode -> IO TSNode) -> Node -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> IO TSNode
C.ts_node_next_sibling
{-# INLINE nodeNextSibling #-}
nodePrevSibling :: Node -> IO Node
nodePrevSibling :: Node -> IO Node
nodePrevSibling = (TSNode -> IO TSNode) -> Node -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> IO TSNode
C.ts_node_prev_sibling
{-# INLINE nodePrevSibling #-}
nodeNextNamedSibling :: Node -> IO Node
nodeNextNamedSibling :: Node -> IO Node
nodeNextNamedSibling = (TSNode -> IO TSNode) -> Node -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> IO TSNode
C.ts_node_next_named_sibling
{-# INLINE nodeNextNamedSibling #-}
nodePrevNamedSibling :: Node -> IO Node
nodePrevNamedSibling :: Node -> IO Node
nodePrevNamedSibling = (TSNode -> IO TSNode) -> Node -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> IO TSNode
C.ts_node_prev_named_sibling
{-# INLINE nodePrevNamedSibling #-}
nodeFirstChildForByte :: Node -> Word32 -> IO Node
nodeFirstChildForByte :: Node -> Word32 -> IO Node
nodeFirstChildForByte = (TSNode -> Word32 -> IO TSNode) -> Node -> Word32 -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> Word32 -> IO TSNode
C.ts_node_first_child_for_byte
{-# INLINE nodeFirstChildForByte #-}
nodeFirstNamedChildForByte :: Node -> Word32 -> IO Node
nodeFirstNamedChildForByte :: Node -> Word32 -> IO Node
nodeFirstNamedChildForByte = (TSNode -> Word32 -> IO TSNode) -> Node -> Word32 -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> Word32 -> IO TSNode
C.ts_node_first_named_child_for_byte
{-# INLINE nodeFirstNamedChildForByte #-}
nodeDescendantCount :: Node -> IO Word32
nodeDescendantCount :: Node -> IO Word32
nodeDescendantCount = (TSNode -> IO Word32) -> Node -> IO Word32
forall a b. Coercible a b => a -> b
coerce TSNode -> IO Word32
C.ts_node_descendant_count
{-# INLINE nodeDescendantCount #-}
nodeDescendantForByteRange :: Node -> Word32 -> Word32 -> IO Node
nodeDescendantForByteRange :: Node -> Word32 -> Word32 -> IO Node
nodeDescendantForByteRange = (TSNode -> Word32 -> Word32 -> IO TSNode)
-> Node -> Word32 -> Word32 -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> Word32 -> Word32 -> IO TSNode
C.ts_node_descendant_for_byte_range
{-# INLINE nodeDescendantForByteRange #-}
nodeDescendantForPointRange :: Node -> Point -> Point -> IO Node
nodeDescendantForPointRange :: Node -> Point -> Point -> IO Node
nodeDescendantForPointRange = (TSNode -> TSPoint -> TSPoint -> IO TSNode)
-> Node -> Point -> Point -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> TSPoint -> TSPoint -> IO TSNode
C.ts_node_descendant_for_point_range
{-# INLINE nodeDescendantForPointRange #-}
nodeNamedDescendantForByteRange :: Node -> Word32 -> Word32 -> IO Node
nodeNamedDescendantForByteRange :: Node -> Word32 -> Word32 -> IO Node
nodeNamedDescendantForByteRange = (TSNode -> Word32 -> Word32 -> IO TSNode)
-> Node -> Word32 -> Word32 -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> Word32 -> Word32 -> IO TSNode
C.ts_node_named_descendant_for_byte_range
{-# INLINE nodeNamedDescendantForByteRange #-}
nodeNamedDescendantForPointRange :: Node -> Point -> Point -> IO Node
nodeNamedDescendantForPointRange :: Node -> Point -> Point -> IO Node
nodeNamedDescendantForPointRange = (TSNode -> TSPoint -> TSPoint -> IO TSNode)
-> Node -> Point -> Point -> IO Node
forall a b. Coercible a b => a -> b
coerce TSNode -> TSPoint -> TSPoint -> IO TSNode
C.ts_node_named_descendant_for_point_range
{-# INLINE nodeNamedDescendantForPointRange #-}
nodeEdit :: Node -> InputEdit -> IO ()
nodeEdit :: Node -> InputEdit -> IO ()
nodeEdit Node
node InputEdit
inputEdit =
TSNode -> (Ptr TSNode -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Node -> TSNode
unWrapTSNode Node
node) ((Ptr TSNode -> IO ()) -> IO ()) -> (Ptr TSNode -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSNode
nodePtr ->
TSInputEdit -> (Ptr TSInputEdit -> IO ()) -> IO ()
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (InputEdit -> TSInputEdit
unWrapTSInputEdit InputEdit
inputEdit) ((Ptr TSInputEdit -> IO ()) -> IO ())
-> (Ptr TSInputEdit -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSInputEdit
inputEditPtr ->
(Ptr TSNode -> ConstPtr TSInputEdit -> IO ())
-> Ptr TSNode -> Ptr TSInputEdit -> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr TSNode -> ConstPtr TSInputEdit -> IO ()
C.ts_node_edit Ptr TSNode
nodePtr Ptr TSInputEdit
inputEditPtr
{-# INLINE nodeEdit #-}
nodeEq :: Node -> Node -> IO Bool
nodeEq :: Node -> Node -> IO Bool
nodeEq Node
node1 Node
node2 =
CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> TSNode -> TSNode -> IO CBool
C.ts_node_eq (Node -> TSNode
forall a b. Coercible a b => a -> b
coerce Node
node1) (Node -> TSNode
forall a b. Coercible a b => a -> b
coerce Node
node2)
{-# INLINE nodeEq #-}
withTreeCursorAsTSTreeCursorPtr :: TreeCursor -> (Ptr C.TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr :: forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr = ForeignPtr TSTreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (ForeignPtr TSTreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a)
-> (TreeCursor -> ForeignPtr TSTreeCursor)
-> TreeCursor
-> (Ptr TSTreeCursor -> IO a)
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TreeCursor -> ForeignPtr TSTreeCursor
forall a b. Coercible a b => a -> b
coerce
treeCursorNew :: Node -> IO TreeCursor
treeCursorNew :: Node -> IO TreeCursor
treeCursorNew Node
node = do
ForeignPtr TSTreeCursor
treeCursorForeignPtr <- IO (ForeignPtr TSTreeCursor)
forall a. Storable a => IO (ForeignPtr a)
mallocForeignPtr
ForeignPtr TSTreeCursor -> (Ptr TSTreeCursor -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr TSTreeCursor
treeCursorForeignPtr ((Ptr TSTreeCursor -> IO ()) -> IO ())
-> (Ptr TSTreeCursor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSTreeCursor
treeCursorPtr ->
TSNode -> Ptr TSTreeCursor -> IO ()
C.ts_tree_cursor_new_p (Node -> TSNode
forall a b. Coercible a b => a -> b
coerce Node
node) Ptr TSTreeCursor
treeCursorPtr
FinalizerPtr TSTreeCursor -> ForeignPtr TSTreeCursor -> IO ()
forall a. FinalizerPtr a -> ForeignPtr a -> IO ()
addForeignPtrFinalizer FinalizerPtr TSTreeCursor
C.p_ts_tree_cursor_delete ForeignPtr TSTreeCursor
treeCursorForeignPtr
TreeCursor -> IO TreeCursor
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TreeCursor -> IO TreeCursor) -> TreeCursor -> IO TreeCursor
forall a b. (a -> b) -> a -> b
$ ForeignPtr TSTreeCursor -> TreeCursor
WrapTSTreeCursor ForeignPtr TSTreeCursor
treeCursorForeignPtr
unsafeTreeCursorDelete :: TreeCursor -> IO ()
unsafeTreeCursorDelete :: TreeCursor -> IO ()
unsafeTreeCursorDelete = (ForeignPtr Any -> IO ()) -> TreeCursor -> IO ()
forall a b. Coercible a b => a -> b
coerce ForeignPtr Any -> IO ()
forall a. ForeignPtr a -> IO ()
finalizeForeignPtr
treeCursorReset :: TreeCursor -> Node -> IO ()
treeCursorReset :: TreeCursor -> Node -> IO ()
treeCursorReset TreeCursor
treeCursor Node
node =
TreeCursor -> (Ptr TSTreeCursor -> IO ()) -> IO ()
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO ()) -> IO ())
-> (Ptr TSTreeCursor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSTreeCursor
treeCursorPtr ->
Ptr TSTreeCursor -> TSNode -> IO ()
C.ts_tree_cursor_reset Ptr TSTreeCursor
treeCursorPtr (Node -> TSNode
forall a b. Coercible a b => a -> b
coerce Node
node)
treeCursorResetTo :: TreeCursor -> TreeCursor -> IO ()
treeCursorResetTo :: TreeCursor -> TreeCursor -> IO ()
treeCursorResetTo TreeCursor
self TreeCursor
other =
TreeCursor -> (Ptr TSTreeCursor -> IO ()) -> IO ()
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
self ((Ptr TSTreeCursor -> IO ()) -> IO ())
-> (Ptr TSTreeCursor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSTreeCursor
selfPtr ->
TreeCursor -> (Ptr TSTreeCursor -> IO ()) -> IO ()
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
other ((Ptr TSTreeCursor -> IO ()) -> IO ())
-> (Ptr TSTreeCursor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSTreeCursor
otherPtr ->
(Ptr TSTreeCursor -> ConstPtr TSTreeCursor -> IO ())
-> Ptr TSTreeCursor -> Ptr TSTreeCursor -> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr TSTreeCursor -> ConstPtr TSTreeCursor -> IO ()
C.ts_tree_cursor_reset_to Ptr TSTreeCursor
selfPtr Ptr TSTreeCursor
otherPtr
treeCursorCurrentNode :: TreeCursor -> IO Node
treeCursorCurrentNode :: TreeCursor -> IO Node
treeCursorCurrentNode TreeCursor
treeCursor =
TreeCursor -> (Ptr TSTreeCursor -> IO Node) -> IO Node
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO Node) -> IO Node)
-> (Ptr TSTreeCursor -> IO Node) -> IO Node
forall a b. (a -> b) -> a -> b
$ \Ptr TSTreeCursor
treeCursorPtr ->
(ConstPtr TSTreeCursor -> IO TSNode) -> Ptr TSTreeCursor -> IO Node
forall a b. Coercible a b => a -> b
coerce ConstPtr TSTreeCursor -> IO TSNode
C.ts_tree_cursor_current_node Ptr TSTreeCursor
treeCursorPtr
treeCursorCurrentFieldName :: TreeCursor -> IO (Maybe ByteString)
treeCursorCurrentFieldName :: TreeCursor -> IO (Maybe ByteString)
treeCursorCurrentFieldName TreeCursor
treeCursor =
TreeCursor
-> (Ptr TSTreeCursor -> IO (Maybe ByteString))
-> IO (Maybe ByteString)
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO (Maybe ByteString))
-> IO (Maybe ByteString))
-> (Ptr TSTreeCursor -> IO (Maybe ByteString))
-> IO (Maybe ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr TSTreeCursor
treeCursorPtr -> do
CString
fieldNamePtr <- (ConstPtr TSTreeCursor -> IO (ConstPtr CChar))
-> Ptr TSTreeCursor -> IO CString
forall a b. Coercible a b => a -> b
coerce ConstPtr TSTreeCursor -> IO (ConstPtr CChar)
C.ts_tree_cursor_current_field_name Ptr TSTreeCursor
treeCursorPtr
if CString
fieldNamePtr CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
== CString
forall a. Ptr a
nullPtr
then Maybe ByteString -> IO (Maybe ByteString)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe ByteString
forall a. Maybe a
Nothing
else ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> IO ByteString -> IO (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CString -> IO ByteString
BSU.unsafePackCString CString
fieldNamePtr
treeCursorCurrentFieldId :: TreeCursor -> IO (Maybe FieldId)
treeCursorCurrentFieldId :: TreeCursor -> IO (Maybe FieldId)
treeCursorCurrentFieldId TreeCursor
treeCursor =
TreeCursor
-> (Ptr TSTreeCursor -> IO (Maybe FieldId)) -> IO (Maybe FieldId)
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO (Maybe FieldId)) -> IO (Maybe FieldId))
-> (Ptr TSTreeCursor -> IO (Maybe FieldId)) -> IO (Maybe FieldId)
forall a b. (a -> b) -> a -> b
$ \Ptr TSTreeCursor
treeCursorPtr -> do
FieldId
fieldId <- (ConstPtr TSTreeCursor -> IO TSFieldId)
-> Ptr TSTreeCursor -> IO FieldId
forall a b. Coercible a b => a -> b
coerce ConstPtr TSTreeCursor -> IO TSFieldId
C.ts_tree_cursor_current_field_id Ptr TSTreeCursor
treeCursorPtr
Maybe FieldId -> IO (Maybe FieldId)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe FieldId -> IO (Maybe FieldId))
-> Maybe FieldId -> IO (Maybe FieldId)
forall a b. (a -> b) -> a -> b
$ if FieldId
fieldId FieldId -> FieldId -> Bool
forall a. Eq a => a -> a -> Bool
== FieldId
0 then Maybe FieldId
forall a. Maybe a
Nothing else FieldId -> Maybe FieldId
forall a. a -> Maybe a
Just FieldId
fieldId
treeCursorGotoParent :: TreeCursor -> IO Bool
treeCursorGotoParent :: TreeCursor -> IO Bool
treeCursorGotoParent TreeCursor
treeCursor =
TreeCursor -> (Ptr TSTreeCursor -> IO Bool) -> IO Bool
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO Bool) -> IO Bool)
-> (Ptr TSTreeCursor -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$
(CBool -> Bool) -> IO CBool -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CBool -> IO Bool)
-> (Ptr TSTreeCursor -> IO CBool) -> Ptr TSTreeCursor -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr TSTreeCursor -> IO CBool
C.ts_tree_cursor_goto_parent
treeCursorGotoNextSibling :: TreeCursor -> IO Bool
treeCursorGotoNextSibling :: TreeCursor -> IO Bool
treeCursorGotoNextSibling TreeCursor
treeCursor =
TreeCursor -> (Ptr TSTreeCursor -> IO Bool) -> IO Bool
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO Bool) -> IO Bool)
-> (Ptr TSTreeCursor -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$
(CBool -> Bool) -> IO CBool -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CBool -> IO Bool)
-> (Ptr TSTreeCursor -> IO CBool) -> Ptr TSTreeCursor -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr TSTreeCursor -> IO CBool
C.ts_tree_cursor_goto_next_sibling
treeCursorGotoPreviousSibling :: TreeCursor -> IO Bool
treeCursorGotoPreviousSibling :: TreeCursor -> IO Bool
treeCursorGotoPreviousSibling TreeCursor
treeCursor =
TreeCursor -> (Ptr TSTreeCursor -> IO Bool) -> IO Bool
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO Bool) -> IO Bool)
-> (Ptr TSTreeCursor -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$
(CBool -> Bool) -> IO CBool -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CBool -> IO Bool)
-> (Ptr TSTreeCursor -> IO CBool) -> Ptr TSTreeCursor -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr TSTreeCursor -> IO CBool
C.ts_tree_cursor_goto_previous_sibling
treeCursorGotoFirstChild :: TreeCursor -> IO Bool
treeCursorGotoFirstChild :: TreeCursor -> IO Bool
treeCursorGotoFirstChild TreeCursor
treeCursor =
TreeCursor -> (Ptr TSTreeCursor -> IO Bool) -> IO Bool
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO Bool) -> IO Bool)
-> (Ptr TSTreeCursor -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$
(CBool -> Bool) -> IO CBool -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CBool -> IO Bool)
-> (Ptr TSTreeCursor -> IO CBool) -> Ptr TSTreeCursor -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr TSTreeCursor -> IO CBool
C.ts_tree_cursor_goto_first_child
treeCursorGotoLastChild :: TreeCursor -> IO Bool
treeCursorGotoLastChild :: TreeCursor -> IO Bool
treeCursorGotoLastChild TreeCursor
treeCursor =
TreeCursor -> (Ptr TSTreeCursor -> IO Bool) -> IO Bool
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO Bool) -> IO Bool)
-> (Ptr TSTreeCursor -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$
(CBool -> Bool) -> IO CBool -> IO Bool
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (IO CBool -> IO Bool)
-> (Ptr TSTreeCursor -> IO CBool) -> Ptr TSTreeCursor -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr TSTreeCursor -> IO CBool
C.ts_tree_cursor_goto_last_child
treeCursorGotoDescendant :: TreeCursor -> Word32 -> IO ()
treeCursorGotoDescendant :: TreeCursor -> Word32 -> IO ()
treeCursorGotoDescendant TreeCursor
treeCursor Word32
descsendantIndex =
TreeCursor -> (Ptr TSTreeCursor -> IO ()) -> IO ()
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO ()) -> IO ())
-> (Ptr TSTreeCursor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSTreeCursor
treeCursorPtr ->
Ptr TSTreeCursor -> Word32 -> IO ()
C.ts_tree_cursor_goto_descendant Ptr TSTreeCursor
treeCursorPtr Word32
descsendantIndex
treeCursorCurrentDescendantIndex :: TreeCursor -> IO Word32
treeCursorCurrentDescendantIndex :: TreeCursor -> IO Word32
treeCursorCurrentDescendantIndex TreeCursor
treeCursor =
TreeCursor -> (Ptr TSTreeCursor -> IO Word32) -> IO Word32
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO Word32) -> IO Word32)
-> (Ptr TSTreeCursor -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$
ConstPtr TSTreeCursor -> IO Word32
C.ts_tree_cursor_current_descendant_index (ConstPtr TSTreeCursor -> IO Word32)
-> (Ptr TSTreeCursor -> ConstPtr TSTreeCursor)
-> Ptr TSTreeCursor
-> IO Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr TSTreeCursor -> ConstPtr TSTreeCursor
forall a b. Coercible a b => a -> b
coerce
treeCursorCurrentDepth :: TreeCursor -> IO Word32
treeCursorCurrentDepth :: TreeCursor -> IO Word32
treeCursorCurrentDepth TreeCursor
treeCursor =
TreeCursor -> (Ptr TSTreeCursor -> IO Word32) -> IO Word32
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO Word32) -> IO Word32)
-> (Ptr TSTreeCursor -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$
ConstPtr TSTreeCursor -> IO Word32
C.ts_tree_cursor_current_depth (ConstPtr TSTreeCursor -> IO Word32)
-> (Ptr TSTreeCursor -> ConstPtr TSTreeCursor)
-> Ptr TSTreeCursor
-> IO Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr TSTreeCursor -> ConstPtr TSTreeCursor
forall a b. Coercible a b => a -> b
coerce
treeCursorGotoFirstChildForByte :: TreeCursor -> Word32 -> IO Int64
treeCursorGotoFirstChildForByte :: TreeCursor -> Word32 -> IO Int64
treeCursorGotoFirstChildForByte TreeCursor
treeCursor Word32
goalByte =
TreeCursor -> (Ptr TSTreeCursor -> IO Int64) -> IO Int64
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO Int64) -> IO Int64)
-> (Ptr TSTreeCursor -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ \Ptr TSTreeCursor
treeCursorPtr ->
Ptr TSTreeCursor -> Word32 -> IO Int64
C.ts_tree_cursor_goto_first_child_for_byte Ptr TSTreeCursor
treeCursorPtr Word32
goalByte
treeCursorGotoFirstChildForPoint :: TreeCursor -> Point -> IO Int64
treeCursorGotoFirstChildForPoint :: TreeCursor -> Point -> IO Int64
treeCursorGotoFirstChildForPoint TreeCursor
treeCursor Point
point =
TreeCursor -> (Ptr TSTreeCursor -> IO Int64) -> IO Int64
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO Int64) -> IO Int64)
-> (Ptr TSTreeCursor -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ \Ptr TSTreeCursor
treeCursorPtr ->
Ptr TSTreeCursor -> TSPoint -> IO Int64
C.ts_tree_cursor_goto_first_child_for_point Ptr TSTreeCursor
treeCursorPtr (Point -> TSPoint
forall a b. Coercible a b => a -> b
coerce Point
point)
treeCursorCopy :: TreeCursor -> IO TreeCursor
treeCursorCopy :: TreeCursor -> IO TreeCursor
treeCursorCopy TreeCursor
treeCursor = do
ForeignPtr TSTreeCursor
copyOfTreeCursorForeignPtr <- IO (ForeignPtr TSTreeCursor)
forall a. Storable a => IO (ForeignPtr a)
mallocForeignPtr
ForeignPtr TSTreeCursor -> (Ptr TSTreeCursor -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr TSTreeCursor
copyOfTreeCursorForeignPtr ((Ptr TSTreeCursor -> IO ()) -> IO ())
-> (Ptr TSTreeCursor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSTreeCursor
copyOfTreeCursorPtr ->
TreeCursor -> (Ptr TSTreeCursor -> IO ()) -> IO ()
forall a. TreeCursor -> (Ptr TSTreeCursor -> IO a) -> IO a
withTreeCursorAsTSTreeCursorPtr TreeCursor
treeCursor ((Ptr TSTreeCursor -> IO ()) -> IO ())
-> (Ptr TSTreeCursor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSTreeCursor
treeCursorPtr ->
Ptr TSTreeCursor -> Ptr TSTreeCursor -> IO ()
C.ts_tree_cursor_copy_p Ptr TSTreeCursor
treeCursorPtr Ptr TSTreeCursor
copyOfTreeCursorPtr
FinalizerPtr TSTreeCursor -> ForeignPtr TSTreeCursor -> IO ()
forall a. FinalizerPtr a -> ForeignPtr a -> IO ()
addForeignPtrFinalizer FinalizerPtr TSTreeCursor
C.p_ts_tree_cursor_delete ForeignPtr TSTreeCursor
copyOfTreeCursorForeignPtr
TreeCursor -> IO TreeCursor
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TreeCursor -> IO TreeCursor) -> TreeCursor -> IO TreeCursor
forall a b. (a -> b) -> a -> b
$ ForeignPtr TSTreeCursor -> TreeCursor
WrapTSTreeCursor ForeignPtr TSTreeCursor
copyOfTreeCursorForeignPtr
withQueryAsTSQueryPtr :: Query -> (Ptr C.TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr :: forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr = ForeignPtr TSQuery -> (Ptr TSQuery -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (ForeignPtr TSQuery -> (Ptr TSQuery -> IO a) -> IO a)
-> (Query -> ForeignPtr TSQuery)
-> Query
-> (Ptr TSQuery -> IO a)
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Query -> ForeignPtr TSQuery
forall a b. Coercible a b => a -> b
coerce
queryNew :: Language -> ByteString -> IO Query
queryNew :: Language -> ByteString -> IO Query
queryNew Language
language ByteString
query =
(Ptr Word32 -> IO Query) -> IO Query
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Word32 -> IO Query) -> IO Query)
-> (Ptr Word32 -> IO Query) -> IO Query
forall a b. (a -> b) -> a -> b
$ \Ptr Word32
queryErrorOffsetPtr -> (Ptr TSQueryError -> IO Query) -> IO Query
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr TSQueryError -> IO Query) -> IO Query)
-> (Ptr TSQueryError -> IO Query) -> IO Query
forall a b. (a -> b) -> a -> b
$ \Ptr TSQueryError
queryErrorTypePtr -> do
Ptr TSQuery
queryPtr <-
Language
-> (ConstPtr TSLanguage -> IO (Ptr TSQuery)) -> IO (Ptr TSQuery)
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr Language
language ((ConstPtr TSLanguage -> IO (Ptr TSQuery)) -> IO (Ptr TSQuery))
-> (ConstPtr TSLanguage -> IO (Ptr TSQuery)) -> IO (Ptr TSQuery)
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLanguage
languagePtr ->
ByteString -> (CStringLen -> IO (Ptr TSQuery)) -> IO (Ptr TSQuery)
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BSU.unsafeUseAsCStringLen ByteString
query ((CStringLen -> IO (Ptr TSQuery)) -> IO (Ptr TSQuery))
-> (CStringLen -> IO (Ptr TSQuery)) -> IO (Ptr TSQuery)
forall a b. (a -> b) -> a -> b
$ \(CString
queryPtr, Int
queryLen) ->
(ConstPtr TSLanguage
-> ConstPtr CChar
-> Word32
-> Ptr Word32
-> Ptr TSQueryError
-> IO (Ptr TSQuery))
-> ConstPtr TSLanguage
-> CString
-> Word32
-> Ptr Word32
-> Ptr TSQueryError
-> IO (Ptr TSQuery)
forall a b. Coercible a b => a -> b
coerce ConstPtr TSLanguage
-> ConstPtr CChar
-> Word32
-> Ptr Word32
-> Ptr TSQueryError
-> IO (Ptr TSQuery)
C.ts_query_new ConstPtr TSLanguage
languagePtr CString
queryPtr (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
queryLen :: Word32) Ptr Word32
queryErrorOffsetPtr Ptr TSQueryError
queryErrorTypePtr
TSQueryError
queryErrorType' <- Ptr TSQueryError -> IO TSQueryError
forall a. Storable a => Ptr a -> IO a
peek Ptr TSQueryError
queryErrorTypePtr
if Ptr TSQuery
queryPtr Ptr TSQuery -> Ptr TSQuery -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr TSQuery
forall a. Ptr a
nullPtr
then Bool -> IO Query -> IO Query
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (TSQueryError
queryErrorType' TSQueryError -> TSQueryError -> Bool
forall a. Eq a => a -> a -> Bool
== TSQueryError
C.TSQueryErrorNone) (IO Query -> IO Query) -> IO Query -> IO Query
forall a b. (a -> b) -> a -> b
$ do
ForeignPtr TSQuery -> Query
WrapTSQuery (ForeignPtr TSQuery -> Query)
-> IO (ForeignPtr TSQuery) -> IO Query
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FinalizerPtr TSQuery -> Ptr TSQuery -> IO (ForeignPtr TSQuery)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr TSQuery
C.p_ts_query_delete Ptr TSQuery
queryPtr
else Bool -> IO Query -> IO Query
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (TSQueryError
queryErrorType' TSQueryError -> TSQueryError -> Bool
forall a. Eq a => a -> a -> Bool
/= TSQueryError
C.TSQueryErrorNone) (IO Query -> IO Query) -> IO Query -> IO Query
forall a b. (a -> b) -> a -> b
$ do
Word32
queryErrorOffset' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
queryErrorOffsetPtr
let !queryError :: QueryError
queryError = ByteString -> Word32 -> QueryErrorType -> QueryError
makeQueryError ByteString
query Word32
queryErrorOffset' (TSQueryError -> QueryErrorType
WrapTSQueryErrorType TSQueryError
queryErrorType')
QueryError -> IO Query
forall e a. Exception e => e -> IO a
throwIO QueryError
queryError
makeQueryError :: ByteString -> Word32 -> QueryErrorType -> QueryError
makeQueryError :: ByteString -> Word32 -> QueryErrorType -> QueryError
makeQueryError ByteString
query Word32
queryErrorOffset QueryErrorType
queryErrorType = QueryError{[Char]
Word32
QueryErrorType
Point
queryErrorOffset :: Word32
queryErrorPoint :: Point
queryErrorMessage :: [Char]
queryErrorType :: QueryErrorType
queryErrorOffset :: Word32
queryErrorType :: QueryErrorType
queryErrorPoint :: Point
queryErrorMessage :: [Char]
..}
where
(Point
queryErrorPoint, [Char]
queryErrorLine) = ByteString -> Word32 -> (Point, [Char])
offsetToPointAndLine ByteString
query Word32
queryErrorOffset
queryErrorMessage :: [Char]
queryErrorMessage =
ByteString -> [Char]
BSC.unpack (ByteString -> [Char])
-> ([Builder] -> ByteString) -> [Builder] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LazyByteString -> ByteString
BS.toStrict (LazyByteString -> ByteString)
-> ([Builder] -> LazyByteString) -> [Builder] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> LazyByteString
BSB.toLazyByteString (Builder -> LazyByteString)
-> ([Builder] -> Builder) -> [Builder] -> LazyByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> [Char]) -> [Builder] -> [Char]
forall a b. (a -> b) -> a -> b
$
[ [Char] -> Builder
BSB.stringUtf8 ([Char] -> Builder) -> [Char] -> Builder
forall a b. (a -> b) -> a -> b
$
case QueryErrorType
queryErrorType of
QueryErrorType
QueryErrorTypeSyntax -> [Char]
"Invalid syntax"
QueryErrorType
QueryErrorTypeNodeType -> [Char]
"Invalid node type"
QueryErrorType
QueryErrorTypeField -> [Char]
"Invalid field name"
QueryErrorType
QueryErrorTypeCapture -> [Char]
"Invalid capture name"
QueryErrorType
QueryErrorTypeStructure -> [Char]
"Impossible pattern"
QueryErrorType
QueryErrorTypeLanguage -> [Char]
"Invalid language"
, [Char] -> Builder
BSB.stringUtf8 [Char]
" at row "
, Word32 -> Builder
BSB.word32Dec (Word32 -> Builder) -> Word32 -> Builder
forall a b. (a -> b) -> a -> b
$ Point -> Word32
pointRow Point
queryErrorPoint
, [Char] -> Builder
BSB.stringUtf8 [Char]
", column "
, Word32 -> Builder
BSB.word32Dec (Word32 -> Builder) -> Word32 -> Builder
forall a b. (a -> b) -> a -> b
$ Point -> Word32
pointColumn Point
queryErrorPoint
, [Char] -> Builder
BSB.stringUtf8 [Char]
":\n\n> "
, [Char] -> Builder
BSB.stringUtf8 [Char]
queryErrorLine
, [Char] -> Builder
BSB.stringUtf8 [Char]
"\n> "
, [Char] -> Builder
BSB.stringUtf8 (Int -> Char -> [Char]
forall a. Int -> a -> [a]
replicate (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> Word32 -> Int
forall a b. (a -> b) -> a -> b
$ Point -> Word32
pointColumn Point
queryErrorPoint Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
- Word32
1) Char
' ')
, [Char] -> Builder
BSB.stringUtf8 [Char]
"^\n\n"
]
offsetToPointAndLine :: ByteString -> Word32 -> (Point, String)
offsetToPointAndLine :: ByteString -> Word32 -> (Point, [Char])
offsetToPointAndLine ByteString
str Word32
offset = (Point
point, [Char]
line)
where
(ByteString
prefix, ByteString
suffix) = Int -> ByteString -> (ByteString, ByteString)
BS.splitAt (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
offset) ByteString
str
prefixLine :: [Char]
prefixLine = ByteString -> [Char]
BSC.unpack (ByteString -> [Char]) -> ByteString -> [Char]
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> ByteString -> ByteString
BSC.takeWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\n') ByteString
prefix
suffixLine :: [Char]
suffixLine = ByteString -> [Char]
BSC.unpack (ByteString -> [Char]) -> ByteString -> [Char]
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> ByteString -> ByteString
BSC.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\n') ByteString
suffix
row :: Int
row = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Char -> ByteString -> Int
BSC.count Char
'\n' ByteString
prefix
column :: Int
column = Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [Char] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Char]
prefixLine
point :: Point
point = Point{pointRow :: Word32
pointRow = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
row, pointColumn :: Word32
pointColumn = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
column}
line :: [Char]
line = [Char]
prefixLine [Char] -> ShowS
forall a. Semigroup a => a -> a -> a
<> [Char]
suffixLine
unsafeQueryDelete :: Query -> IO ()
unsafeQueryDelete :: Query -> IO ()
unsafeQueryDelete = (ForeignPtr Any -> IO ()) -> Query -> IO ()
forall a b. Coercible a b => a -> b
coerce ForeignPtr Any -> IO ()
forall a. ForeignPtr a -> IO ()
finalizeForeignPtr
queryPatternCount :: Query -> IO Word32
queryPatternCount :: Query -> IO Word32
queryPatternCount Query
query =
Query -> (Ptr TSQuery -> IO Word32) -> IO Word32
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr Query
query ((Ptr TSQuery -> IO Word32) -> IO Word32)
-> (Ptr TSQuery -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$
(ConstPtr TSQuery -> IO Word32) -> Ptr TSQuery -> IO Word32
forall a b. Coercible a b => a -> b
coerce ConstPtr TSQuery -> IO Word32
C.ts_query_pattern_count
queryCaptureCount :: Query -> IO Word32
queryCaptureCount :: Query -> IO Word32
queryCaptureCount Query
query =
Query -> (Ptr TSQuery -> IO Word32) -> IO Word32
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr Query
query ((Ptr TSQuery -> IO Word32) -> IO Word32)
-> (Ptr TSQuery -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$
(ConstPtr TSQuery -> IO Word32) -> Ptr TSQuery -> IO Word32
forall a b. Coercible a b => a -> b
coerce ConstPtr TSQuery -> IO Word32
C.ts_query_capture_count
queryStringCount :: Query -> IO Word32
queryStringCount :: Query -> IO Word32
queryStringCount Query
query =
Query -> (Ptr TSQuery -> IO Word32) -> IO Word32
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr Query
query ((Ptr TSQuery -> IO Word32) -> IO Word32)
-> (Ptr TSQuery -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$
(ConstPtr TSQuery -> IO Word32) -> Ptr TSQuery -> IO Word32
forall a b. Coercible a b => a -> b
coerce ConstPtr TSQuery -> IO Word32
C.ts_query_string_count
queryStartByteForPattern :: Query -> PatternIndex -> IO Word32
queryStartByteForPattern :: Query -> PatternIndex -> IO Word32
queryStartByteForPattern Query
query PatternIndex
patternIndex =
Query -> (Ptr TSQuery -> IO Word32) -> IO Word32
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr Query
query ((Ptr TSQuery -> IO Word32) -> IO Word32)
-> (Ptr TSQuery -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TSQuery
queryPtr ->
(ConstPtr TSQuery -> Word32 -> IO Word32)
-> Ptr TSQuery -> PatternIndex -> IO Word32
forall a b. Coercible a b => a -> b
coerce ConstPtr TSQuery -> Word32 -> IO Word32
C.ts_query_start_byte_for_pattern Ptr TSQuery
queryPtr PatternIndex
patternIndex
queryEndByteForPattern :: Query -> PatternIndex -> IO Word32
queryEndByteForPattern :: Query -> PatternIndex -> IO Word32
queryEndByteForPattern Query
query PatternIndex
patternIndex =
Query -> (Ptr TSQuery -> IO Word32) -> IO Word32
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr Query
query ((Ptr TSQuery -> IO Word32) -> IO Word32)
-> (Ptr TSQuery -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr TSQuery
queryPtr ->
(ConstPtr TSQuery -> Word32 -> IO Word32)
-> Ptr TSQuery -> PatternIndex -> IO Word32
forall a b. Coercible a b => a -> b
coerce ConstPtr TSQuery -> Word32 -> IO Word32
C.ts_query_end_byte_for_pattern Ptr TSQuery
queryPtr PatternIndex
patternIndex
queryPredicatesForPattern :: Query -> Word32 -> IO [QueryPredicateStep]
queryPredicatesForPattern :: Query -> Word32 -> IO [QueryPredicateStep]
queryPredicatesForPattern Query
query Word32
patternIndex = do
(Ptr TSQueryPredicateStep
stepsPtr, Int
stepsLen) <-
(Ptr Word32 -> IO (Ptr TSQueryPredicateStep, Int))
-> IO (Ptr TSQueryPredicateStep, Int)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Word32 -> IO (Ptr TSQueryPredicateStep, Int))
-> IO (Ptr TSQueryPredicateStep, Int))
-> (Ptr Word32 -> IO (Ptr TSQueryPredicateStep, Int))
-> IO (Ptr TSQueryPredicateStep, Int)
forall a b. (a -> b) -> a -> b
$ \Ptr Word32
stepCountPtr -> do
ConstPtr TSQueryPredicateStep
stepsPtr <-
Query
-> (Ptr TSQuery -> IO (ConstPtr TSQueryPredicateStep))
-> IO (ConstPtr TSQueryPredicateStep)
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr Query
query ((Ptr TSQuery -> IO (ConstPtr TSQueryPredicateStep))
-> IO (ConstPtr TSQueryPredicateStep))
-> (Ptr TSQuery -> IO (ConstPtr TSQueryPredicateStep))
-> IO (ConstPtr TSQueryPredicateStep)
forall a b. (a -> b) -> a -> b
$ \Ptr TSQuery
queryPtr ->
ConstPtr TSQuery
-> Word32 -> Ptr Word32 -> IO (ConstPtr TSQueryPredicateStep)
C.ts_query_predicates_for_pattern (Ptr TSQuery -> ConstPtr TSQuery
forall a. Ptr a -> ConstPtr a
ConstPtr Ptr TSQuery
queryPtr) Word32
patternIndex Ptr Word32
stepCountPtr
Int
stepsLen <- Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> IO Word32 -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
stepCountPtr
(Ptr TSQueryPredicateStep, Int)
-> IO (Ptr TSQueryPredicateStep, Int)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ConstPtr TSQueryPredicateStep -> Ptr TSQueryPredicateStep
forall a. ConstPtr a -> Ptr a
unConstPtr ConstPtr TSQueryPredicateStep
stepsPtr, Int
stepsLen)
IO [TSQueryPredicateStep] -> IO [QueryPredicateStep]
forall a b. Coercible a b => a -> b
coerce (IO [TSQueryPredicateStep] -> IO [QueryPredicateStep])
-> IO [TSQueryPredicateStep] -> IO [QueryPredicateStep]
forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray @C.TSQueryPredicateStep Int
stepsLen Ptr TSQueryPredicateStep
stepsPtr
queryIsPatternRooted :: Query -> PatternIndex -> IO Bool
queryIsPatternRooted :: Query -> PatternIndex -> IO Bool
queryIsPatternRooted Query
query PatternIndex
patternIndex =
Query -> (Ptr TSQuery -> IO Bool) -> IO Bool
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr Query
query ((Ptr TSQuery -> IO Bool) -> IO Bool)
-> (Ptr TSQuery -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr TSQuery
queryPtr ->
forall a. (Eq a, Num a) => a -> Bool
toBool @CBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ConstPtr TSQuery -> Word32 -> IO CBool)
-> Ptr TSQuery -> PatternIndex -> IO CBool
forall a b. Coercible a b => a -> b
coerce ConstPtr TSQuery -> Word32 -> IO CBool
C.ts_query_is_pattern_rooted Ptr TSQuery
queryPtr PatternIndex
patternIndex
queryIsPatternNonLocal :: Query -> PatternIndex -> IO Bool
queryIsPatternNonLocal :: Query -> PatternIndex -> IO Bool
queryIsPatternNonLocal Query
query PatternIndex
patternIndex =
Query -> (Ptr TSQuery -> IO Bool) -> IO Bool
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr Query
query ((Ptr TSQuery -> IO Bool) -> IO Bool)
-> (Ptr TSQuery -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr TSQuery
queryPtr ->
forall a. (Eq a, Num a) => a -> Bool
toBool @CBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ConstPtr TSQuery -> Word32 -> IO CBool)
-> Ptr TSQuery -> PatternIndex -> IO CBool
forall a b. Coercible a b => a -> b
coerce ConstPtr TSQuery -> Word32 -> IO CBool
C.ts_query_is_pattern_non_local Ptr TSQuery
queryPtr PatternIndex
patternIndex
queryIsPatternGuaranteedAtStep :: Query -> Word32 -> IO Bool
queryIsPatternGuaranteedAtStep :: Query -> Word32 -> IO Bool
queryIsPatternGuaranteedAtStep Query
query Word32
byteOffset =
Query -> (Ptr TSQuery -> IO Bool) -> IO Bool
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr Query
query ((Ptr TSQuery -> IO Bool) -> IO Bool)
-> (Ptr TSQuery -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr TSQuery
queryPtr ->
CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ConstPtr TSQuery -> Word32 -> IO CBool
C.ts_query_is_pattern_guaranteed_at_step (Ptr TSQuery -> ConstPtr TSQuery
forall a. Ptr a -> ConstPtr a
ConstPtr Ptr TSQuery
queryPtr) Word32
byteOffset
queryCaptureNameForIndex :: Query -> CaptureIndex -> IO CaptureName
queryCaptureNameForIndex :: Query -> CaptureIndex -> IO CaptureName
queryCaptureNameForIndex Query
query CaptureIndex
captureIndex = do
(CString
namePtr, Int
nameLen) <-
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca @Word32 ((Ptr Word32 -> IO CStringLen) -> IO CStringLen)
-> (Ptr Word32 -> IO CStringLen) -> IO CStringLen
forall a b. (a -> b) -> a -> b
$ \Ptr Word32
nameLenPtr ->
(,)
(CString -> Int -> CStringLen)
-> IO CString -> IO (Int -> CStringLen)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> (Ptr TSQuery -> IO CString) -> IO CString
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr
Query
query
( \Ptr TSQuery
queryPtr ->
(ConstPtr TSQuery -> Word32 -> Ptr Word32 -> IO (ConstPtr CChar))
-> Ptr TSQuery -> CaptureIndex -> Ptr Word32 -> IO CString
forall a b. Coercible a b => a -> b
coerce ConstPtr TSQuery -> Word32 -> Ptr Word32 -> IO (ConstPtr CChar)
C.ts_query_capture_name_for_id Ptr TSQuery
queryPtr CaptureIndex
captureIndex Ptr Word32
nameLenPtr
)
IO (Int -> CStringLen) -> IO Int -> IO CStringLen
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> IO Word32 -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
nameLenPtr)
IO ByteString -> IO CaptureName
forall a b. Coercible a b => a -> b
coerce (IO ByteString -> IO CaptureName)
-> IO ByteString -> IO CaptureName
forall a b. (a -> b) -> a -> b
$ CStringLen -> IO ByteString
BSU.unsafePackCStringLen (CString
namePtr, Int
nameLen)
queryCaptureQuantifierForIndex :: Query -> PatternIndex -> CaptureIndex -> IO Quantifier
queryCaptureQuantifierForIndex :: Query -> PatternIndex -> CaptureIndex -> IO Quantifier
queryCaptureQuantifierForIndex Query
query PatternIndex
patternIndex CaptureIndex
captureIndex =
Query -> (Ptr TSQuery -> IO Quantifier) -> IO Quantifier
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr Query
query ((Ptr TSQuery -> IO Quantifier) -> IO Quantifier)
-> (Ptr TSQuery -> IO Quantifier) -> IO Quantifier
forall a b. (a -> b) -> a -> b
$ \Ptr TSQuery
queryPtr ->
(ConstPtr TSQuery -> Word32 -> Word32 -> IO TSQuantifier)
-> Ptr TSQuery -> PatternIndex -> CaptureIndex -> IO Quantifier
forall a b. Coercible a b => a -> b
coerce ConstPtr TSQuery -> Word32 -> Word32 -> IO TSQuantifier
C.ts_query_capture_quantifier_for_id Ptr TSQuery
queryPtr PatternIndex
patternIndex CaptureIndex
captureIndex
queryStringValueForIndex :: Query -> CaptureIndex -> IO ByteString
queryStringValueForIndex :: Query -> CaptureIndex -> IO ByteString
queryStringValueForIndex Query
query CaptureIndex
captureIndex = do
(CString
strPtr, Int
strLen) <-
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca @Word32 ((Ptr Word32 -> IO CStringLen) -> IO CStringLen)
-> (Ptr Word32 -> IO CStringLen) -> IO CStringLen
forall a b. (a -> b) -> a -> b
$ \Ptr Word32
strLenPtr ->
(,)
(CString -> Int -> CStringLen)
-> IO CString -> IO (Int -> CStringLen)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Query -> (Ptr TSQuery -> IO CString) -> IO CString
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr
Query
query
( \Ptr TSQuery
queryPtr ->
(ConstPtr TSQuery -> Word32 -> Ptr Word32 -> IO (ConstPtr CChar))
-> Ptr TSQuery -> CaptureIndex -> Ptr Word32 -> IO CString
forall a b. Coercible a b => a -> b
coerce ConstPtr TSQuery -> Word32 -> Ptr Word32 -> IO (ConstPtr CChar)
C.ts_query_string_value_for_id Ptr TSQuery
queryPtr CaptureIndex
captureIndex Ptr Word32
strLenPtr
)
IO (Int -> CStringLen) -> IO Int -> IO CStringLen
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int) -> IO Word32 -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
strLenPtr)
CStringLen -> IO ByteString
BS.packCStringLen (CString
strPtr, Int
strLen)
queryDisableCapture :: Query -> CaptureName -> IO ()
queryDisableCapture :: Query -> CaptureName -> IO ()
queryDisableCapture Query
query CaptureName
captureName =
Query -> (Ptr TSQuery -> IO ()) -> IO ()
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr Query
query ((Ptr TSQuery -> IO ()) -> IO ())
-> (Ptr TSQuery -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSQuery
queryPtr ->
ByteString -> (CStringLen -> IO ()) -> IO ()
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BSU.unsafeUseAsCStringLen (CaptureName -> ByteString
forall a b. Coercible a b => a -> b
coerce CaptureName
captureName) ((CStringLen -> IO ()) -> IO ()) -> (CStringLen -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \(CString
namePtr, Int
nameLen) ->
(Ptr TSQuery -> ConstPtr CChar -> Word32 -> IO ())
-> Ptr TSQuery -> CString -> Word32 -> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr TSQuery -> ConstPtr CChar -> Word32 -> IO ()
C.ts_query_disable_capture Ptr TSQuery
queryPtr CString
namePtr (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
nameLen :: Word32)
queryDisablePattern :: Query -> PatternIndex -> IO ()
queryDisablePattern :: Query -> PatternIndex -> IO ()
queryDisablePattern Query
query PatternIndex
patternIndex =
Query -> (Ptr TSQuery -> IO ()) -> IO ()
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr Query
query ((Ptr TSQuery -> IO ()) -> IO ())
-> (Ptr TSQuery -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSQuery
queryPtr ->
(Ptr TSQuery -> Word32 -> IO ())
-> Ptr TSQuery -> PatternIndex -> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr TSQuery -> Word32 -> IO ()
C.ts_query_disable_pattern Ptr TSQuery
queryPtr PatternIndex
patternIndex
withQueryCursorAsTSQueryCursorPtr :: QueryCursor -> (Ptr C.TSQueryCursor -> IO a) -> IO a
withQueryCursorAsTSQueryCursorPtr :: forall a. QueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a
withQueryCursorAsTSQueryCursorPtr = ForeignPtr TSQueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (ForeignPtr TSQueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a)
-> (QueryCursor -> ForeignPtr TSQueryCursor)
-> QueryCursor
-> (Ptr TSQueryCursor -> IO a)
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QueryCursor -> ForeignPtr TSQueryCursor
forall a b. Coercible a b => a -> b
coerce
queryCursorNew :: IO QueryCursor
queryCursorNew :: IO QueryCursor
queryCursorNew =
(FinalizerPtr Any -> Ptr Any -> IO (ForeignPtr Any))
-> FunPtr (Ptr TSQueryCursor -> IO ())
-> Ptr TSQueryCursor
-> IO QueryCursor
forall a b. Coercible a b => a -> b
coerce FinalizerPtr Any -> Ptr Any -> IO (ForeignPtr Any)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FunPtr (Ptr TSQueryCursor -> IO ())
C.p_ts_query_cursor_delete (Ptr TSQueryCursor -> IO QueryCursor)
-> IO (Ptr TSQueryCursor) -> IO QueryCursor
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO (Ptr TSQueryCursor)
C.ts_query_cursor_new
unsafeQueryCursorDelete :: QueryCursor -> IO ()
unsafeQueryCursorDelete :: QueryCursor -> IO ()
unsafeQueryCursorDelete = (ForeignPtr Any -> IO ()) -> QueryCursor -> IO ()
forall a b. Coercible a b => a -> b
coerce ForeignPtr Any -> IO ()
forall a. ForeignPtr a -> IO ()
finalizeForeignPtr
queryCursorExec :: QueryCursor -> Query -> Node -> IO ()
queryCursorExec :: QueryCursor -> Query -> Node -> IO ()
queryCursorExec QueryCursor
queryCursor Query
query Node
node =
QueryCursor -> (Ptr TSQueryCursor -> IO ()) -> IO ()
forall a. QueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a
withQueryCursorAsTSQueryCursorPtr QueryCursor
queryCursor ((Ptr TSQueryCursor -> IO ()) -> IO ())
-> (Ptr TSQueryCursor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSQueryCursor
queryCursorPtr ->
Query -> (Ptr TSQuery -> IO ()) -> IO ()
forall a. Query -> (Ptr TSQuery -> IO a) -> IO a
withQueryAsTSQueryPtr Query
query ((Ptr TSQuery -> IO ()) -> IO ())
-> (Ptr TSQuery -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSQuery
queryPtr ->
(Ptr TSQueryCursor -> ConstPtr TSQuery -> TSNode -> IO ())
-> Ptr TSQueryCursor -> Ptr TSQuery -> Node -> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr TSQueryCursor -> ConstPtr TSQuery -> TSNode -> IO ()
C.ts_query_cursor_exec Ptr TSQueryCursor
queryCursorPtr Ptr TSQuery
queryPtr Node
node
queryCursorDidExceedMatchLimit :: QueryCursor -> IO Bool
queryCursorDidExceedMatchLimit :: QueryCursor -> IO Bool
queryCursorDidExceedMatchLimit QueryCursor
queryCursor =
QueryCursor -> (Ptr TSQueryCursor -> IO Bool) -> IO Bool
forall a. QueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a
withQueryCursorAsTSQueryCursorPtr QueryCursor
queryCursor ((Ptr TSQueryCursor -> IO Bool) -> IO Bool)
-> (Ptr TSQueryCursor -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr TSQueryCursor
queryCursorPtr ->
forall a. (Eq a, Num a) => a -> Bool
toBool @CBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ConstPtr TSQueryCursor -> IO CBool)
-> Ptr TSQueryCursor -> IO CBool
forall a b. Coercible a b => a -> b
coerce ConstPtr TSQueryCursor -> IO CBool
C.ts_query_cursor_did_exceed_match_limit Ptr TSQueryCursor
queryCursorPtr
queryCursorMatchLimit :: QueryCursor -> IO Word32
queryCursorMatchLimit :: QueryCursor -> IO Word32
queryCursorMatchLimit QueryCursor
queryCursor =
QueryCursor -> (Ptr TSQueryCursor -> IO Word32) -> IO Word32
forall a. QueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a
withQueryCursorAsTSQueryCursorPtr QueryCursor
queryCursor ((Ptr TSQueryCursor -> IO Word32) -> IO Word32)
-> (Ptr TSQueryCursor -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$
(ConstPtr TSQueryCursor -> IO Word32)
-> Ptr TSQueryCursor -> IO Word32
forall a b. Coercible a b => a -> b
coerce ConstPtr TSQueryCursor -> IO Word32
C.ts_query_cursor_match_limit
queryCursorSetMatchLimit :: QueryCursor -> Word32 -> IO ()
queryCursorSetMatchLimit :: QueryCursor -> Word32 -> IO ()
queryCursorSetMatchLimit QueryCursor
queryCursor Word32
matchLimit =
QueryCursor -> (Ptr TSQueryCursor -> IO ()) -> IO ()
forall a. QueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a
withQueryCursorAsTSQueryCursorPtr QueryCursor
queryCursor ((Ptr TSQueryCursor -> IO ()) -> IO ())
-> (Ptr TSQueryCursor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSQueryCursor
queryCursorPtr ->
Ptr TSQueryCursor -> Word32 -> IO ()
C.ts_query_cursor_set_match_limit Ptr TSQueryCursor
queryCursorPtr Word32
matchLimit
queryCursorSetTimeoutMicros :: QueryCursor -> Microsecond -> IO ()
queryCursorSetTimeoutMicros :: QueryCursor -> Microsecond -> IO ()
queryCursorSetTimeoutMicros QueryCursor
queryCursor Microsecond
micros =
QueryCursor -> (Ptr TSQueryCursor -> IO ()) -> IO ()
forall a. QueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a
withQueryCursorAsTSQueryCursorPtr QueryCursor
queryCursor ((Ptr TSQueryCursor -> IO ()) -> IO ())
-> (Ptr TSQueryCursor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSQueryCursor
queryCursorPtr ->
(Ptr TSQueryCursor -> Word64 -> IO ())
-> Ptr TSQueryCursor -> Microsecond -> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr TSQueryCursor -> Word64 -> IO ()
C.ts_query_cursor_set_timeout_micros Ptr TSQueryCursor
queryCursorPtr Microsecond
micros
queryCursorTimeoutMicros :: QueryCursor -> IO Microsecond
queryCursorTimeoutMicros :: QueryCursor -> IO Microsecond
queryCursorTimeoutMicros QueryCursor
queryCursor =
QueryCursor
-> (Ptr TSQueryCursor -> IO Microsecond) -> IO Microsecond
forall a. QueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a
withQueryCursorAsTSQueryCursorPtr QueryCursor
queryCursor ((Ptr TSQueryCursor -> IO Microsecond) -> IO Microsecond)
-> (Ptr TSQueryCursor -> IO Microsecond) -> IO Microsecond
forall a b. (a -> b) -> a -> b
$
(ConstPtr TSQueryCursor -> IO Word64)
-> Ptr TSQueryCursor -> IO Microsecond
forall a b. Coercible a b => a -> b
coerce ConstPtr TSQueryCursor -> IO Word64
C.ts_query_cursor_timeout_micros
queryCursorSetByteRange :: QueryCursor -> Word32 -> Word32 -> IO ()
queryCursorSetByteRange :: QueryCursor -> Word32 -> Word32 -> IO ()
queryCursorSetByteRange QueryCursor
queryCursor Word32
startByte Word32
endByte =
QueryCursor -> (Ptr TSQueryCursor -> IO ()) -> IO ()
forall a. QueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a
withQueryCursorAsTSQueryCursorPtr QueryCursor
queryCursor ((Ptr TSQueryCursor -> IO ()) -> IO ())
-> (Ptr TSQueryCursor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSQueryCursor
queryCursorPtr ->
Ptr TSQueryCursor -> Word32 -> Word32 -> IO ()
C.ts_query_cursor_set_byte_range Ptr TSQueryCursor
queryCursorPtr Word32
startByte Word32
endByte
queryCursorSetPointRange :: QueryCursor -> Point -> Point -> IO ()
queryCursorSetPointRange :: QueryCursor -> Point -> Point -> IO ()
queryCursorSetPointRange QueryCursor
queryCursor Point
startPoint Point
endPoint =
QueryCursor -> (Ptr TSQueryCursor -> IO ()) -> IO ()
forall a. QueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a
withQueryCursorAsTSQueryCursorPtr QueryCursor
queryCursor ((Ptr TSQueryCursor -> IO ()) -> IO ())
-> (Ptr TSQueryCursor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSQueryCursor
queryCursorPtr ->
(Ptr TSQueryCursor -> TSPoint -> TSPoint -> IO ())
-> Ptr TSQueryCursor -> Point -> Point -> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr TSQueryCursor -> TSPoint -> TSPoint -> IO ()
C.ts_query_cursor_set_point_range Ptr TSQueryCursor
queryCursorPtr Point
startPoint Point
endPoint
queryCursorNextMatch :: QueryCursor -> IO (Maybe QueryMatch)
queryCursorNextMatch :: QueryCursor -> IO (Maybe QueryMatch)
queryCursorNextMatch QueryCursor
queryCursor =
(Ptr TSQueryMatch -> IO (Maybe QueryMatch))
-> IO (Maybe QueryMatch)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr TSQueryMatch -> IO (Maybe QueryMatch))
-> IO (Maybe QueryMatch))
-> (Ptr TSQueryMatch -> IO (Maybe QueryMatch))
-> IO (Maybe QueryMatch)
forall a b. (a -> b) -> a -> b
$ \Ptr TSQueryMatch
queryMatchPtr -> do
CBool
success <-
QueryCursor -> (Ptr TSQueryCursor -> IO CBool) -> IO CBool
forall a. QueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a
withQueryCursorAsTSQueryCursorPtr QueryCursor
queryCursor ((Ptr TSQueryCursor -> IO CBool) -> IO CBool)
-> (Ptr TSQueryCursor -> IO CBool) -> IO CBool
forall a b. (a -> b) -> a -> b
$ \Ptr TSQueryCursor
queryCursorPtr ->
Ptr TSQueryCursor -> Ptr TSQueryMatch -> IO CBool
C.ts_query_cursor_next_match Ptr TSQueryCursor
queryCursorPtr Ptr TSQueryMatch
queryMatchPtr
if CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool CBool
success
then do
TSQueryMatch
queryMatch <- Ptr TSQueryMatch -> IO TSQueryMatch
forall a. Storable a => Ptr a -> IO a
peek Ptr TSQueryMatch
queryMatchPtr
Maybe QueryMatch -> IO (Maybe QueryMatch)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe QueryMatch -> IO (Maybe QueryMatch))
-> (TSQueryMatch -> Maybe QueryMatch)
-> TSQueryMatch
-> IO (Maybe QueryMatch)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QueryMatch -> Maybe QueryMatch
forall a. a -> Maybe a
Just (QueryMatch -> Maybe QueryMatch)
-> (TSQueryMatch -> QueryMatch) -> TSQueryMatch -> Maybe QueryMatch
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TSQueryMatch -> QueryMatch
forall a b. Coercible a b => a -> b
coerce (TSQueryMatch -> IO (Maybe QueryMatch))
-> TSQueryMatch -> IO (Maybe QueryMatch)
forall a b. (a -> b) -> a -> b
$ TSQueryMatch
queryMatch
else Maybe QueryMatch -> IO (Maybe QueryMatch)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe QueryMatch
forall a. Maybe a
Nothing
queryCursorRemoveMatch :: QueryCursor -> CaptureIndex -> IO ()
queryCursorRemoveMatch :: QueryCursor -> CaptureIndex -> IO ()
queryCursorRemoveMatch QueryCursor
queryCursor CaptureIndex
captureIndex =
QueryCursor -> (Ptr TSQueryCursor -> IO ()) -> IO ()
forall a. QueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a
withQueryCursorAsTSQueryCursorPtr QueryCursor
queryCursor ((Ptr TSQueryCursor -> IO ()) -> IO ())
-> (Ptr TSQueryCursor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSQueryCursor
queryCursorPtr ->
(Ptr TSQueryCursor -> Word32 -> IO ())
-> Ptr TSQueryCursor -> CaptureIndex -> IO ()
forall a b. Coercible a b => a -> b
coerce Ptr TSQueryCursor -> Word32 -> IO ()
C.ts_query_cursor_remove_match Ptr TSQueryCursor
queryCursorPtr CaptureIndex
captureIndex
queryCursorNextCapture :: QueryCursor -> IO (Maybe (CaptureIndex, QueryMatch))
queryCursorNextCapture :: QueryCursor -> IO (Maybe (CaptureIndex, QueryMatch))
queryCursorNextCapture QueryCursor
queryCursor =
(Ptr Word32 -> IO (Maybe (CaptureIndex, QueryMatch)))
-> IO (Maybe (CaptureIndex, QueryMatch))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Word32 -> IO (Maybe (CaptureIndex, QueryMatch)))
-> IO (Maybe (CaptureIndex, QueryMatch)))
-> (Ptr Word32 -> IO (Maybe (CaptureIndex, QueryMatch)))
-> IO (Maybe (CaptureIndex, QueryMatch))
forall a b. (a -> b) -> a -> b
$ \Ptr Word32
captureIndexPtr -> (Ptr TSQueryMatch -> IO (Maybe (CaptureIndex, QueryMatch)))
-> IO (Maybe (CaptureIndex, QueryMatch))
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr TSQueryMatch -> IO (Maybe (CaptureIndex, QueryMatch)))
-> IO (Maybe (CaptureIndex, QueryMatch)))
-> (Ptr TSQueryMatch -> IO (Maybe (CaptureIndex, QueryMatch)))
-> IO (Maybe (CaptureIndex, QueryMatch))
forall a b. (a -> b) -> a -> b
$ \Ptr TSQueryMatch
queryMatchPtr -> do
CBool
success <-
QueryCursor -> (Ptr TSQueryCursor -> IO CBool) -> IO CBool
forall a. QueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a
withQueryCursorAsTSQueryCursorPtr QueryCursor
queryCursor ((Ptr TSQueryCursor -> IO CBool) -> IO CBool)
-> (Ptr TSQueryCursor -> IO CBool) -> IO CBool
forall a b. (a -> b) -> a -> b
$ \Ptr TSQueryCursor
queryCursorPtr ->
Ptr TSQueryCursor -> Ptr TSQueryMatch -> Ptr Word32 -> IO CBool
C.ts_query_cursor_next_capture Ptr TSQueryCursor
queryCursorPtr Ptr TSQueryMatch
queryMatchPtr Ptr Word32
captureIndexPtr
if CBool -> Bool
forall a. (Eq a, Num a) => a -> Bool
toBool CBool
success
then do
Word32
captureIndex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
captureIndexPtr
TSQueryMatch
queryMatch <- Ptr TSQueryMatch -> IO TSQueryMatch
forall a. Storable a => Ptr a -> IO a
peek Ptr TSQueryMatch
queryMatchPtr
Maybe (CaptureIndex, QueryMatch)
-> IO (Maybe (CaptureIndex, QueryMatch))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (CaptureIndex, QueryMatch)
-> IO (Maybe (CaptureIndex, QueryMatch)))
-> ((Word32, TSQueryMatch) -> Maybe (CaptureIndex, QueryMatch))
-> (Word32, TSQueryMatch)
-> IO (Maybe (CaptureIndex, QueryMatch))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CaptureIndex, QueryMatch) -> Maybe (CaptureIndex, QueryMatch)
forall a. a -> Maybe a
Just ((CaptureIndex, QueryMatch) -> Maybe (CaptureIndex, QueryMatch))
-> ((Word32, TSQueryMatch) -> (CaptureIndex, QueryMatch))
-> (Word32, TSQueryMatch)
-> Maybe (CaptureIndex, QueryMatch)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word32, TSQueryMatch) -> (CaptureIndex, QueryMatch)
forall a b. Coercible a b => a -> b
coerce ((Word32, TSQueryMatch) -> IO (Maybe (CaptureIndex, QueryMatch)))
-> (Word32, TSQueryMatch) -> IO (Maybe (CaptureIndex, QueryMatch))
forall a b. (a -> b) -> a -> b
$ (Word32
captureIndex, TSQueryMatch
queryMatch)
else Maybe (CaptureIndex, QueryMatch)
-> IO (Maybe (CaptureIndex, QueryMatch))
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (CaptureIndex, QueryMatch)
forall a. Maybe a
Nothing
queryCursorSetMaxStartDepth :: QueryCursor -> Word32 -> IO ()
queryCursorSetMaxStartDepth :: QueryCursor -> Word32 -> IO ()
queryCursorSetMaxStartDepth QueryCursor
queryCursor Word32
maxStartDepth =
QueryCursor -> (Ptr TSQueryCursor -> IO ()) -> IO ()
forall a. QueryCursor -> (Ptr TSQueryCursor -> IO a) -> IO a
withQueryCursorAsTSQueryCursorPtr QueryCursor
queryCursor ((Ptr TSQueryCursor -> IO ()) -> IO ())
-> (Ptr TSQueryCursor -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr TSQueryCursor
queryCursorPtr ->
Ptr TSQueryCursor -> Word32 -> IO ()
C.ts_query_cursor_set_max_start_depth Ptr TSQueryCursor
queryCursorPtr Word32
maxStartDepth
unsafeToLanguage :: ConstPtr tsLanguage -> IO Language
unsafeToLanguage :: forall tsLanguage. ConstPtr tsLanguage -> IO Language
unsafeToLanguage ConstPtr tsLanguage
languageConstPtr = do
let languagePtr :: Ptr Any
languagePtr = Ptr tsLanguage -> Ptr Any
forall a b. Ptr a -> Ptr b
castPtr (Ptr tsLanguage -> Ptr Any)
-> (ConstPtr tsLanguage -> Ptr tsLanguage)
-> ConstPtr tsLanguage
-> Ptr Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstPtr tsLanguage -> Ptr tsLanguage
forall a. ConstPtr a -> Ptr a
unConstPtr (ConstPtr tsLanguage -> Ptr Any) -> ConstPtr tsLanguage -> Ptr Any
forall a b. (a -> b) -> a -> b
$ ConstPtr tsLanguage
languageConstPtr
let languageFinalizer :: FunPtr b
languageFinalizer = FunPtr (ConstPtr TSLanguage -> IO ()) -> FunPtr b
forall a b. FunPtr a -> FunPtr b
castFunPtr FunPtr (ConstPtr TSLanguage -> IO ())
C.p_ts_language_delete
ForeignPtr Any
languageForeignPtr <- FinalizerPtr Any -> Ptr Any -> IO (ForeignPtr Any)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr Any
forall {b}. FunPtr b
languageFinalizer Ptr Any
languagePtr
Language -> IO Language
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Language -> IO Language) -> Language -> IO Language
forall a b. (a -> b) -> a -> b
$ ForeignPtr Any -> Language
forall a b. Coercible a b => a -> b
coerce ForeignPtr Any
languageForeignPtr
unsafeLanguageDelete :: Language -> IO ()
unsafeLanguageDelete :: Language -> IO ()
unsafeLanguageDelete =
ForeignPtr Any -> IO ()
forall a. ForeignPtr a -> IO ()
finalizeForeignPtr (ForeignPtr Any -> IO ())
-> (Language -> ForeignPtr Any) -> Language -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Language -> ForeignPtr Any
forall a b. Coercible a b => a -> b
coerce
withLanguageAsTSLanguagePtr :: Language -> (ConstPtr C.TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr :: forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr Language
language ConstPtr TSLanguage -> IO a
action =
ForeignPtr TSLanguage -> (Ptr TSLanguage -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (Language -> ForeignPtr TSLanguage
forall a b. Coercible a b => a -> b
coerce Language
language) (ConstPtr TSLanguage -> IO a
action (ConstPtr TSLanguage -> IO a)
-> (Ptr TSLanguage -> ConstPtr TSLanguage)
-> Ptr TSLanguage
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr TSLanguage -> ConstPtr TSLanguage
forall a. Ptr a -> ConstPtr a
ConstPtr)
languageCopy :: Language -> IO Language
languageCopy :: Language -> IO Language
languageCopy Language
language =
Language -> (ConstPtr TSLanguage -> IO Language) -> IO Language
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr Language
language ((ConstPtr TSLanguage -> IO Language) -> IO Language)
-> (ConstPtr TSLanguage -> IO Language) -> IO Language
forall a b. (a -> b) -> a -> b
$
ConstPtr TSLanguage -> IO Language
forall tsLanguage. ConstPtr tsLanguage -> IO Language
unsafeToLanguage (ConstPtr TSLanguage -> IO Language)
-> (ConstPtr TSLanguage -> IO (ConstPtr TSLanguage))
-> ConstPtr TSLanguage
-> IO Language
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< ConstPtr TSLanguage -> IO (ConstPtr TSLanguage)
C.ts_language_copy (ConstPtr TSLanguage -> IO (ConstPtr TSLanguage))
-> (ConstPtr TSLanguage -> ConstPtr TSLanguage)
-> ConstPtr TSLanguage
-> IO (ConstPtr TSLanguage)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstPtr TSLanguage -> ConstPtr TSLanguage
forall a b. Coercible a b => a -> b
coerce
languageSymbolCount :: Language -> IO Word32
languageSymbolCount :: Language -> IO Word32
languageSymbolCount Language
language =
Language -> (ConstPtr TSLanguage -> IO Word32) -> IO Word32
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr
Language
language
ConstPtr TSLanguage -> IO Word32
C.ts_language_symbol_count
languageStateCount :: Language -> IO Word32
languageStateCount :: Language -> IO Word32
languageStateCount Language
language =
Language -> (ConstPtr TSLanguage -> IO Word32) -> IO Word32
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr
Language
language
ConstPtr TSLanguage -> IO Word32
C.ts_language_state_count
languageSymbolName :: Language -> Symbol -> IO ByteString
languageSymbolName :: Language -> Symbol -> IO ByteString
languageSymbolName Language
language Symbol
symbol =
Language -> (ConstPtr TSLanguage -> IO ByteString) -> IO ByteString
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr Language
language ((ConstPtr TSLanguage -> IO ByteString) -> IO ByteString)
-> (ConstPtr TSLanguage -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLanguage
languagePtr ->
CString -> IO ByteString
BSU.unsafePackCString (CString -> IO ByteString) -> IO CString -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (ConstPtr TSLanguage -> TSSymbol -> IO (ConstPtr CChar))
-> ConstPtr TSLanguage -> Symbol -> IO CString
forall a b. Coercible a b => a -> b
coerce ConstPtr TSLanguage -> TSSymbol -> IO (ConstPtr CChar)
C.ts_language_symbol_name ConstPtr TSLanguage
languagePtr Symbol
symbol
languageSymbolForGrammarType :: Language -> ByteString -> Bool -> IO Symbol
languageSymbolForGrammarType :: Language -> ByteString -> Bool -> IO Symbol
languageSymbolForGrammarType Language
language ByteString
grammarType Bool
isNamed =
Language -> (ConstPtr TSLanguage -> IO Symbol) -> IO Symbol
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr Language
language ((ConstPtr TSLanguage -> IO Symbol) -> IO Symbol)
-> (ConstPtr TSLanguage -> IO Symbol) -> IO Symbol
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLanguage
languagePtr ->
ByteString -> (CStringLen -> IO Symbol) -> IO Symbol
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BSU.unsafeUseAsCStringLen ByteString
grammarType ((CStringLen -> IO Symbol) -> IO Symbol)
-> (CStringLen -> IO Symbol) -> IO Symbol
forall a b. (a -> b) -> a -> b
$ \(CString
grammarTypeStr, Int
grammarTypeLen) ->
(ConstPtr TSLanguage
-> ConstPtr CChar -> Word32 -> CBool -> IO TSSymbol)
-> ConstPtr TSLanguage -> CString -> Word32 -> CBool -> IO Symbol
forall a b. Coercible a b => a -> b
coerce
ConstPtr TSLanguage
-> ConstPtr CChar -> Word32 -> CBool -> IO TSSymbol
C.ts_language_symbol_for_name
ConstPtr TSLanguage
languagePtr
CString
grammarTypeStr
(Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
grammarTypeLen :: Word32)
(Bool -> CBool
forall a. Num a => Bool -> a
fromBool Bool
isNamed :: CBool)
languageFieldCount :: Language -> IO Word32
languageFieldCount :: Language -> IO Word32
languageFieldCount Language
language =
Language -> (ConstPtr TSLanguage -> IO Word32) -> IO Word32
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr Language
language ((ConstPtr TSLanguage -> IO Word32) -> IO Word32)
-> (ConstPtr TSLanguage -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLanguage
languagePtr ->
ConstPtr TSLanguage -> IO Word32
C.ts_language_field_count ConstPtr TSLanguage
languagePtr
languageFieldNameForId :: Language -> FieldId -> IO ByteString
languageFieldNameForId :: Language -> FieldId -> IO ByteString
languageFieldNameForId Language
language FieldId
fieldId =
Language -> (ConstPtr TSLanguage -> IO ByteString) -> IO ByteString
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr Language
language ((ConstPtr TSLanguage -> IO ByteString) -> IO ByteString)
-> (ConstPtr TSLanguage -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLanguage
languagePtr ->
CString -> IO ByteString
BSU.unsafePackCString (CString -> IO ByteString) -> IO CString -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (ConstPtr TSLanguage -> TSFieldId -> IO (ConstPtr CChar))
-> ConstPtr TSLanguage -> FieldId -> IO CString
forall a b. Coercible a b => a -> b
coerce ConstPtr TSLanguage -> TSFieldId -> IO (ConstPtr CChar)
C.ts_language_field_name_for_id ConstPtr TSLanguage
languagePtr FieldId
fieldId
languageFieldIdForName :: Language -> ByteString -> IO FieldId
languageFieldIdForName :: Language -> ByteString -> IO FieldId
languageFieldIdForName Language
language ByteString
fieldName =
Language -> (ConstPtr TSLanguage -> IO FieldId) -> IO FieldId
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr Language
language ((ConstPtr TSLanguage -> IO FieldId) -> IO FieldId)
-> (ConstPtr TSLanguage -> IO FieldId) -> IO FieldId
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLanguage
languagePtr ->
ByteString -> (CStringLen -> IO FieldId) -> IO FieldId
forall a. ByteString -> (CStringLen -> IO a) -> IO a
BSU.unsafeUseAsCStringLen ByteString
fieldName ((CStringLen -> IO FieldId) -> IO FieldId)
-> (CStringLen -> IO FieldId) -> IO FieldId
forall a b. (a -> b) -> a -> b
$ \(CString
fieldNameStr, Int
fieldNameLen) ->
(ConstPtr TSLanguage -> ConstPtr CChar -> Word32 -> IO TSFieldId)
-> ConstPtr TSLanguage -> CString -> Word32 -> IO FieldId
forall a b. Coercible a b => a -> b
coerce
ConstPtr TSLanguage -> ConstPtr CChar -> Word32 -> IO TSFieldId
C.ts_language_field_id_for_name
ConstPtr TSLanguage
languagePtr
CString
fieldNameStr
(Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
fieldNameLen :: Word32)
languageSymbolType :: Language -> Symbol -> IO SymbolType
languageSymbolType :: Language -> Symbol -> IO SymbolType
languageSymbolType Language
language Symbol
symbol =
Language -> (ConstPtr TSLanguage -> IO SymbolType) -> IO SymbolType
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr Language
language ((ConstPtr TSLanguage -> IO SymbolType) -> IO SymbolType)
-> (ConstPtr TSLanguage -> IO SymbolType) -> IO SymbolType
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLanguage
languagePtr ->
(ConstPtr TSLanguage -> TSSymbol -> IO TSSymbolType)
-> ConstPtr TSLanguage -> Symbol -> IO SymbolType
forall a b. Coercible a b => a -> b
coerce ConstPtr TSLanguage -> TSSymbol -> IO TSSymbolType
C.ts_language_symbol_type ConstPtr TSLanguage
languagePtr Symbol
symbol
languageVersion :: Language -> IO Word32
languageVersion :: Language -> IO Word32
languageVersion Language
language =
Language -> (ConstPtr TSLanguage -> IO Word32) -> IO Word32
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr Language
language ConstPtr TSLanguage -> IO Word32
C.ts_language_version
languageNextState :: Language -> StateId -> Symbol -> IO StateId
languageNextState :: Language -> StateId -> Symbol -> IO StateId
languageNextState Language
language StateId
stateId Symbol
symbol =
Language -> (ConstPtr TSLanguage -> IO StateId) -> IO StateId
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr Language
language ((ConstPtr TSLanguage -> IO StateId) -> IO StateId)
-> (ConstPtr TSLanguage -> IO StateId) -> IO StateId
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLanguage
languagePtr ->
(ConstPtr TSLanguage -> TSStateId -> TSSymbol -> IO TSStateId)
-> ConstPtr TSLanguage -> StateId -> Symbol -> IO StateId
forall a b. Coercible a b => a -> b
coerce ConstPtr TSLanguage -> TSStateId -> TSSymbol -> IO TSStateId
C.ts_language_next_state ConstPtr TSLanguage
languagePtr StateId
stateId Symbol
symbol
withLookaheadIteratorAsTSLookaheadIteratorPtr :: LookaheadIterator -> (ConstPtr C.TSLookaheadIterator -> IO a) -> IO a
withLookaheadIteratorAsTSLookaheadIteratorPtr :: forall a.
LookaheadIterator -> (ConstPtr TSLookaheadIterator -> IO a) -> IO a
withLookaheadIteratorAsTSLookaheadIteratorPtr LookaheadIterator
lookaheadIterator ConstPtr TSLookaheadIterator -> IO a
action =
ForeignPtr TSLookaheadIterator
-> (Ptr TSLookaheadIterator -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr (LookaheadIterator -> ForeignPtr TSLookaheadIterator
forall a b. Coercible a b => a -> b
coerce LookaheadIterator
lookaheadIterator) (ConstPtr TSLookaheadIterator -> IO a
action (ConstPtr TSLookaheadIterator -> IO a)
-> (Ptr TSLookaheadIterator -> ConstPtr TSLookaheadIterator)
-> Ptr TSLookaheadIterator
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr TSLookaheadIterator -> ConstPtr TSLookaheadIterator
forall a. Ptr a -> ConstPtr a
ConstPtr)
lookaheadIteratorNew :: Language -> StateId -> IO LookaheadIterator
lookaheadIteratorNew :: Language -> StateId -> IO LookaheadIterator
lookaheadIteratorNew Language
language StateId
stateId =
Language
-> (ConstPtr TSLanguage -> IO LookaheadIterator)
-> IO LookaheadIterator
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr Language
language ((ConstPtr TSLanguage -> IO LookaheadIterator)
-> IO LookaheadIterator)
-> (ConstPtr TSLanguage -> IO LookaheadIterator)
-> IO LookaheadIterator
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLanguage
languagePtr ->
(FinalizerPtr Any -> Ptr Any -> IO (ForeignPtr Any))
-> FunPtr (Ptr TSLookaheadIterator -> IO ())
-> Ptr TSLookaheadIterator
-> IO LookaheadIterator
forall a b. Coercible a b => a -> b
coerce FinalizerPtr Any -> Ptr Any -> IO (ForeignPtr Any)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FunPtr (Ptr TSLookaheadIterator -> IO ())
C.p_ts_lookahead_iterator_delete
(Ptr TSLookaheadIterator -> IO LookaheadIterator)
-> IO (Ptr TSLookaheadIterator) -> IO LookaheadIterator
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ConstPtr TSLanguage -> TSStateId -> IO (Ptr TSLookaheadIterator)
C.ts_lookahead_iterator_new ConstPtr TSLanguage
languagePtr (StateId -> TSStateId
forall a b. Coercible a b => a -> b
coerce StateId
stateId)
unsafeLookaheadIteratorDelete :: LookaheadIterator -> IO ()
unsafeLookaheadIteratorDelete :: LookaheadIterator -> IO ()
unsafeLookaheadIteratorDelete = (ForeignPtr Any -> IO ()) -> LookaheadIterator -> IO ()
forall a b. Coercible a b => a -> b
coerce ForeignPtr Any -> IO ()
forall a. ForeignPtr a -> IO ()
finalizeForeignPtr
lookaheadIteratorResetState :: LookaheadIterator -> StateId -> IO Bool
lookaheadIteratorResetState :: LookaheadIterator -> StateId -> IO Bool
lookaheadIteratorResetState LookaheadIterator
lookaheadIterator StateId
stateId =
LookaheadIterator
-> (ConstPtr TSLookaheadIterator -> IO Bool) -> IO Bool
forall a.
LookaheadIterator -> (ConstPtr TSLookaheadIterator -> IO a) -> IO a
withLookaheadIteratorAsTSLookaheadIteratorPtr LookaheadIterator
lookaheadIterator ((ConstPtr TSLookaheadIterator -> IO Bool) -> IO Bool)
-> (ConstPtr TSLookaheadIterator -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLookaheadIterator
lookaheadIteratorPtr -> do
forall a. (Eq a, Num a) => a -> Bool
toBool @CBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ptr TSLookaheadIterator -> TSStateId -> IO CBool)
-> ConstPtr TSLookaheadIterator -> StateId -> IO CBool
forall a b. Coercible a b => a -> b
coerce Ptr TSLookaheadIterator -> TSStateId -> IO CBool
C.ts_lookahead_iterator_reset_state ConstPtr TSLookaheadIterator
lookaheadIteratorPtr StateId
stateId
lookaheadIteratorReset :: LookaheadIterator -> Language -> StateId -> IO Bool
lookaheadIteratorReset :: LookaheadIterator -> Language -> StateId -> IO Bool
lookaheadIteratorReset LookaheadIterator
lookaheadIterator Language
language StateId
stateId = do
Language -> (ConstPtr TSLanguage -> IO Bool) -> IO Bool
forall a. Language -> (ConstPtr TSLanguage -> IO a) -> IO a
withLanguageAsTSLanguagePtr Language
language ((ConstPtr TSLanguage -> IO Bool) -> IO Bool)
-> (ConstPtr TSLanguage -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLanguage
languagePtr ->
LookaheadIterator
-> (ConstPtr TSLookaheadIterator -> IO Bool) -> IO Bool
forall a.
LookaheadIterator -> (ConstPtr TSLookaheadIterator -> IO a) -> IO a
withLookaheadIteratorAsTSLookaheadIteratorPtr LookaheadIterator
lookaheadIterator ((ConstPtr TSLookaheadIterator -> IO Bool) -> IO Bool)
-> (ConstPtr TSLookaheadIterator -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLookaheadIterator
lookaheadIteratorPtr ->
forall a. (Eq a, Num a) => a -> Bool
toBool @CBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ptr TSLookaheadIterator
-> ConstPtr TSLanguage -> TSStateId -> IO CBool)
-> ConstPtr TSLookaheadIterator
-> ConstPtr TSLanguage
-> StateId
-> IO CBool
forall a b. Coercible a b => a -> b
coerce Ptr TSLookaheadIterator
-> ConstPtr TSLanguage -> TSStateId -> IO CBool
C.ts_lookahead_iterator_reset ConstPtr TSLookaheadIterator
lookaheadIteratorPtr ConstPtr TSLanguage
languagePtr StateId
stateId
lookaheadIteratorLanguage :: LookaheadIterator -> IO Language
lookaheadIteratorLanguage :: LookaheadIterator -> IO Language
lookaheadIteratorLanguage LookaheadIterator
lookaheadIterator =
LookaheadIterator
-> (ConstPtr TSLookaheadIterator -> IO Language) -> IO Language
forall a.
LookaheadIterator -> (ConstPtr TSLookaheadIterator -> IO a) -> IO a
withLookaheadIteratorAsTSLookaheadIteratorPtr LookaheadIterator
lookaheadIterator ((ConstPtr TSLookaheadIterator -> IO Language) -> IO Language)
-> (ConstPtr TSLookaheadIterator -> IO Language) -> IO Language
forall a b. (a -> b) -> a -> b
$
ConstPtr Any -> IO Language
forall tsLanguage. ConstPtr tsLanguage -> IO Language
unsafeToLanguage (ConstPtr Any -> IO Language)
-> (ConstPtr TSLookaheadIterator -> IO (ConstPtr Any))
-> ConstPtr TSLookaheadIterator
-> IO Language
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (Ptr TSLookaheadIterator -> IO (ConstPtr TSLanguage))
-> ConstPtr TSLookaheadIterator -> IO (ConstPtr Any)
forall a b. Coercible a b => a -> b
coerce Ptr TSLookaheadIterator -> IO (ConstPtr TSLanguage)
C.ts_lookahead_iterator_language
lookaheadIteratorNext :: LookaheadIterator -> IO Bool
lookaheadIteratorNext :: LookaheadIterator -> IO Bool
lookaheadIteratorNext LookaheadIterator
lookaheadIterator =
LookaheadIterator
-> (ConstPtr TSLookaheadIterator -> IO Bool) -> IO Bool
forall a.
LookaheadIterator -> (ConstPtr TSLookaheadIterator -> IO a) -> IO a
withLookaheadIteratorAsTSLookaheadIteratorPtr LookaheadIterator
lookaheadIterator ((ConstPtr TSLookaheadIterator -> IO Bool) -> IO Bool)
-> (ConstPtr TSLookaheadIterator -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLookaheadIterator
lookaheadIteratorPtr ->
forall a. (Eq a, Num a) => a -> Bool
toBool @CBool (CBool -> Bool) -> IO CBool -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ptr TSLookaheadIterator -> IO CBool)
-> ConstPtr TSLookaheadIterator -> IO CBool
forall a b. Coercible a b => a -> b
coerce Ptr TSLookaheadIterator -> IO CBool
C.ts_lookahead_iterator_next ConstPtr TSLookaheadIterator
lookaheadIteratorPtr
lookaheadIteratorCurrentSymbol :: LookaheadIterator -> IO Symbol
lookaheadIteratorCurrentSymbol :: LookaheadIterator -> IO Symbol
lookaheadIteratorCurrentSymbol LookaheadIterator
lookaheadIterator =
LookaheadIterator
-> (ConstPtr TSLookaheadIterator -> IO Symbol) -> IO Symbol
forall a.
LookaheadIterator -> (ConstPtr TSLookaheadIterator -> IO a) -> IO a
withLookaheadIteratorAsTSLookaheadIteratorPtr LookaheadIterator
lookaheadIterator ((ConstPtr TSLookaheadIterator -> IO Symbol) -> IO Symbol)
-> (ConstPtr TSLookaheadIterator -> IO Symbol) -> IO Symbol
forall a b. (a -> b) -> a -> b
$ \ConstPtr TSLookaheadIterator
lookaheadIteratorPtr ->
(ConstPtr TSLookaheadIterator -> IO TSSymbol)
-> ConstPtr TSLookaheadIterator -> IO Symbol
forall a b. Coercible a b => a -> b
coerce ConstPtr TSLookaheadIterator -> IO TSSymbol
C.ts_lookahead_iterator_current_symbol ConstPtr TSLookaheadIterator
lookaheadIteratorPtr
lookaheadIteratorCurrentSymbolName :: LookaheadIterator -> IO ByteString
lookaheadIteratorCurrentSymbolName :: LookaheadIterator -> IO ByteString
lookaheadIteratorCurrentSymbolName LookaheadIterator
lookaheadIterator =
LookaheadIterator
-> (ConstPtr TSLookaheadIterator -> IO ByteString) -> IO ByteString
forall a.
LookaheadIterator -> (ConstPtr TSLookaheadIterator -> IO a) -> IO a
withLookaheadIteratorAsTSLookaheadIteratorPtr LookaheadIterator
lookaheadIterator ((ConstPtr TSLookaheadIterator -> IO ByteString) -> IO ByteString)
-> (ConstPtr TSLookaheadIterator -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$
CString -> IO ByteString
BSU.unsafePackCString (CString -> IO ByteString)
-> (ConstPtr TSLookaheadIterator -> IO CString)
-> ConstPtr TSLookaheadIterator
-> IO ByteString
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< (ConstPtr TSLookaheadIterator -> IO (ConstPtr CChar))
-> ConstPtr TSLookaheadIterator -> IO CString
forall a b. Coercible a b => a -> b
coerce ConstPtr TSLookaheadIterator -> IO (ConstPtr CChar)
C.ts_lookahead_iterator_current_symbol_name