{-# LANGUAGE RoleAnnotations #-}
module TreeSitter.Internal.ST (
FieldId (..),
FieldName (..),
GrammarType (..),
InputEdit (..),
Point (..),
StateId (..),
Symbol (..),
SymbolType (..),
Language,
Node,
TreeCursor,
treeRootNode,
treeRootNodeWithOffset,
nodeType,
nodeTypeAsString,
nodeSymbol,
nodeLanguage,
nodeGrammarType,
nodeGrammarTypeAsString,
nodeGrammarSymbol,
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,
treeCursorReset,
treeCursorResetTo,
treeCursorCurrentNode,
treeCursorCurrentFieldName,
treeCursorCurrentFieldId,
treeCursorGotoParent,
treeCursorGotoNextSibling,
treeCursorGotoPreviousSibling,
treeCursorGotoFirstChild,
treeCursorGotoLastChild,
treeCursorGotoDescendant,
treeCursorCurrentDescendantIndex,
treeCursorCurrentDepth,
treeCursorGotoFirstChildForByte,
treeCursorGotoFirstChildForPoint,
treeCursorCopy,
languageCopy,
languageSymbolCount,
languageStateCount,
languageSymbolName,
languageSymbolForGrammarType,
languageFieldCount,
languageFieldNameForId,
languageFieldIdForName,
languageSymbolType,
languageVersion,
languageNextState,
) where
import Control.Monad.ST (ST)
import Control.Monad.ST.Unsafe (unsafeIOToST)
import Data.ByteString (ByteString)
import Data.Coerce (coerce)
import Data.Int (Int64)
import Data.Word (Word32)
import TreeSitter.Internal (
FieldId (..),
FieldName (..),
GrammarType (..),
InputEdit (..),
Point (..),
StateId (..),
Symbol (..),
SymbolType (..),
)
import TreeSitter.Internal qualified as TSIO
{-# ANN module ("HLint: ignore Redundant lambda" :: String) #-}
newtype Language s = WrapIOLanguage TSIO.Language
type role Language nominal
newtype Node s = WrapIONode TSIO.Node
type role Node nominal
newtype TreeCursor s = WrapIOTreeCursor TSIO.TreeCursor
type role TreeCursor nominal
treeRootNode :: TSIO.Tree -> ST s (Node s)
treeRootNode :: forall s. Tree -> ST s (Node s)
treeRootNode = IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Tree -> IO (Node s)) -> Tree -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO Node -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce (IO Node -> IO (Node s))
-> (Tree -> IO Node) -> Tree -> IO (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tree -> IO Node
TSIO.treeRootNode
{-# INLINE treeRootNode #-}
treeRootNodeWithOffset :: TSIO.Tree -> Word32 -> TSIO.Point -> ST s (Node s)
treeRootNodeWithOffset :: forall s. Tree -> Word32 -> Point -> ST s (Node s)
treeRootNodeWithOffset = ((IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Point -> IO (Node s)) -> Point -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Point -> IO (Node s)) -> Point -> ST s (Node s))
-> (Word32 -> Point -> IO (Node s))
-> Word32
-> Point
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> Point -> IO (Node s))
-> Word32 -> Point -> ST s (Node s))
-> (Tree -> Word32 -> Point -> IO (Node s))
-> Tree
-> Word32
-> Point
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Tree -> Word32 -> Point -> IO Node)
-> Tree -> Word32 -> Point -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Tree -> Word32 -> Point -> IO Node
TSIO.treeRootNodeWithOffset
{-# INLINE treeRootNodeWithOffset #-}
nodeType :: Node s -> ST s ByteString
nodeType :: forall s. Node s -> ST s ByteString
nodeType = IO ByteString -> ST s ByteString
forall a s. IO a -> ST s a
unsafeIOToST (IO ByteString -> ST s ByteString)
-> (Node s -> IO ByteString) -> Node s -> ST s ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO ByteString) -> Node s -> IO ByteString
forall a b. Coercible a b => a -> b
coerce Node -> IO ByteString
TSIO.nodeType
{-# INLINE nodeType #-}
nodeTypeAsString :: Node s -> ST s String
nodeTypeAsString :: forall s. Node s -> ST s String
nodeTypeAsString = IO String -> ST s String
forall a s. IO a -> ST s a
unsafeIOToST (IO String -> ST s String)
-> (Node s -> IO String) -> Node s -> ST s String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO String) -> Node s -> IO String
forall a b. Coercible a b => a -> b
coerce Node -> IO String
TSIO.nodeTypeAsString
{-# INLINE nodeTypeAsString #-}
nodeSymbol :: Node s -> ST s TSIO.Symbol
nodeSymbol :: forall s. Node s -> ST s Symbol
nodeSymbol = IO Symbol -> ST s Symbol
forall a s. IO a -> ST s a
unsafeIOToST (IO Symbol -> ST s Symbol)
-> (Node s -> IO Symbol) -> Node s -> ST s Symbol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Symbol) -> Node s -> IO Symbol
forall a b. Coercible a b => a -> b
coerce Node -> IO Symbol
TSIO.nodeSymbol
{-# INLINE nodeSymbol #-}
nodeLanguage :: Node s -> ST s TSIO.Language
nodeLanguage :: forall s. Node s -> ST s Language
nodeLanguage = IO Language -> ST s Language
forall a s. IO a -> ST s a
unsafeIOToST (IO Language -> ST s Language)
-> (Node s -> IO Language) -> Node s -> ST s Language
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Language) -> Node s -> IO Language
forall a b. Coercible a b => a -> b
coerce Node -> IO Language
TSIO.nodeLanguage
{-# INLINE nodeLanguage #-}
nodeGrammarType :: Node s -> ST s GrammarType
nodeGrammarType :: forall s. Node s -> ST s GrammarType
nodeGrammarType = IO GrammarType -> ST s GrammarType
forall a s. IO a -> ST s a
unsafeIOToST (IO GrammarType -> ST s GrammarType)
-> (Node s -> IO GrammarType) -> Node s -> ST s GrammarType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO GrammarType) -> Node s -> IO GrammarType
forall a b. Coercible a b => a -> b
coerce Node -> IO GrammarType
TSIO.nodeGrammarType
{-# INLINE nodeGrammarType #-}
nodeGrammarTypeAsString :: Node s -> ST s String
nodeGrammarTypeAsString :: forall s. Node s -> ST s String
nodeGrammarTypeAsString = IO String -> ST s String
forall a s. IO a -> ST s a
unsafeIOToST (IO String -> ST s String)
-> (Node s -> IO String) -> Node s -> ST s String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO String) -> Node s -> IO String
forall a b. Coercible a b => a -> b
coerce Node -> IO String
TSIO.nodeGrammarTypeAsString
{-# INLINE nodeGrammarTypeAsString #-}
nodeGrammarSymbol :: Node s -> ST s Symbol
nodeGrammarSymbol :: forall s. Node s -> ST s Symbol
nodeGrammarSymbol = IO Symbol -> ST s Symbol
forall a s. IO a -> ST s a
unsafeIOToST (IO Symbol -> ST s Symbol)
-> (Node s -> IO Symbol) -> Node s -> ST s Symbol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Symbol) -> Node s -> IO Symbol
forall a b. Coercible a b => a -> b
coerce Node -> IO Symbol
TSIO.nodeGrammarSymbol
{-# INLINE nodeGrammarSymbol #-}
nodeStartByte :: Node s -> ST s Word32
nodeStartByte :: forall s. Node s -> ST s Word32
nodeStartByte = IO Word32 -> ST s Word32
forall a s. IO a -> ST s a
unsafeIOToST (IO Word32 -> ST s Word32)
-> (Node s -> IO Word32) -> Node s -> ST s Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Word32) -> Node s -> IO Word32
forall a b. Coercible a b => a -> b
coerce Node -> IO Word32
TSIO.nodeStartByte
{-# INLINE nodeStartByte #-}
nodeStartPoint :: Node s -> ST s Point
nodeStartPoint :: forall s. Node s -> ST s Point
nodeStartPoint = IO Point -> ST s Point
forall a s. IO a -> ST s a
unsafeIOToST (IO Point -> ST s Point)
-> (Node s -> IO Point) -> Node s -> ST s Point
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Point) -> Node s -> IO Point
forall a b. Coercible a b => a -> b
coerce Node -> IO Point
TSIO.nodeStartPoint
{-# INLINE nodeStartPoint #-}
nodeEndByte :: Node s -> ST s Word32
nodeEndByte :: forall s. Node s -> ST s Word32
nodeEndByte = IO Word32 -> ST s Word32
forall a s. IO a -> ST s a
unsafeIOToST (IO Word32 -> ST s Word32)
-> (Node s -> IO Word32) -> Node s -> ST s Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Word32) -> Node s -> IO Word32
forall a b. Coercible a b => a -> b
coerce Node -> IO Word32
TSIO.nodeEndByte
{-# INLINE nodeEndByte #-}
nodeEndPoint :: Node s -> ST s Point
nodeEndPoint :: forall s. Node s -> ST s Point
nodeEndPoint = IO Point -> ST s Point
forall a s. IO a -> ST s a
unsafeIOToST (IO Point -> ST s Point)
-> (Node s -> IO Point) -> Node s -> ST s Point
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Point) -> Node s -> IO Point
forall a b. Coercible a b => a -> b
coerce Node -> IO Point
TSIO.nodeEndPoint
{-# INLINE nodeEndPoint #-}
showNode :: Node s -> ST s ByteString
showNode :: forall s. Node s -> ST s ByteString
showNode = IO ByteString -> ST s ByteString
forall a s. IO a -> ST s a
unsafeIOToST (IO ByteString -> ST s ByteString)
-> (Node s -> IO ByteString) -> Node s -> ST s ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO ByteString) -> Node s -> IO ByteString
forall a b. Coercible a b => a -> b
coerce Node -> IO ByteString
TSIO.showNode
{-# INLINE showNode #-}
showNodeAsString :: Node s -> ST s String
showNodeAsString :: forall s. Node s -> ST s String
showNodeAsString = IO String -> ST s String
forall a s. IO a -> ST s a
unsafeIOToST (IO String -> ST s String)
-> (Node s -> IO String) -> Node s -> ST s String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO String) -> Node s -> IO String
forall a b. Coercible a b => a -> b
coerce Node -> IO String
TSIO.showNodeAsString
{-# INLINE showNodeAsString #-}
nodeIsNull :: Node s -> ST s Bool
nodeIsNull :: forall s. Node s -> ST s Bool
nodeIsNull = IO Bool -> ST s Bool
forall a s. IO a -> ST s a
unsafeIOToST (IO Bool -> ST s Bool)
-> (Node s -> IO Bool) -> Node s -> ST s Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Bool) -> Node s -> IO Bool
forall a b. Coercible a b => a -> b
coerce Node -> IO Bool
TSIO.nodeIsNull
{-# INLINE nodeIsNull #-}
nodeIsNamed :: Node s -> ST s Bool
nodeIsNamed :: forall s. Node s -> ST s Bool
nodeIsNamed = IO Bool -> ST s Bool
forall a s. IO a -> ST s a
unsafeIOToST (IO Bool -> ST s Bool)
-> (Node s -> IO Bool) -> Node s -> ST s Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Bool) -> Node s -> IO Bool
forall a b. Coercible a b => a -> b
coerce Node -> IO Bool
TSIO.nodeIsNamed
{-# INLINE nodeIsNamed #-}
nodeIsMissing :: Node s -> ST s Bool
nodeIsMissing :: forall s. Node s -> ST s Bool
nodeIsMissing = IO Bool -> ST s Bool
forall a s. IO a -> ST s a
unsafeIOToST (IO Bool -> ST s Bool)
-> (Node s -> IO Bool) -> Node s -> ST s Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Bool) -> Node s -> IO Bool
forall a b. Coercible a b => a -> b
coerce Node -> IO Bool
TSIO.nodeIsMissing
{-# INLINE nodeIsMissing #-}
nodeIsExtra :: Node s -> ST s Bool
= IO Bool -> ST s Bool
forall a s. IO a -> ST s a
unsafeIOToST (IO Bool -> ST s Bool)
-> (Node s -> IO Bool) -> Node s -> ST s Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Bool) -> Node s -> IO Bool
forall a b. Coercible a b => a -> b
coerce Node -> IO Bool
TSIO.nodeIsExtra
{-# INLINE nodeIsExtra #-}
nodeHasChanges :: Node s -> ST s Bool
nodeHasChanges :: forall s. Node s -> ST s Bool
nodeHasChanges = IO Bool -> ST s Bool
forall a s. IO a -> ST s a
unsafeIOToST (IO Bool -> ST s Bool)
-> (Node s -> IO Bool) -> Node s -> ST s Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Bool) -> Node s -> IO Bool
forall a b. Coercible a b => a -> b
coerce Node -> IO Bool
TSIO.nodeHasChanges
{-# INLINE nodeHasChanges #-}
nodeHasError :: Node s -> ST s Bool
nodeHasError :: forall s. Node s -> ST s Bool
nodeHasError = IO Bool -> ST s Bool
forall a s. IO a -> ST s a
unsafeIOToST (IO Bool -> ST s Bool)
-> (Node s -> IO Bool) -> Node s -> ST s Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Bool) -> Node s -> IO Bool
forall a b. Coercible a b => a -> b
coerce Node -> IO Bool
TSIO.nodeHasError
{-# INLINE nodeHasError #-}
nodeIsError :: Node s -> ST s Bool
nodeIsError :: forall s. Node s -> ST s Bool
nodeIsError = IO Bool -> ST s Bool
forall a s. IO a -> ST s a
unsafeIOToST (IO Bool -> ST s Bool)
-> (Node s -> IO Bool) -> Node s -> ST s Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Bool) -> Node s -> IO Bool
forall a b. Coercible a b => a -> b
coerce Node -> IO Bool
TSIO.nodeIsError
{-# INLINE nodeIsError #-}
nodeParseState :: Node s -> ST s StateId
nodeParseState :: forall s. Node s -> ST s StateId
nodeParseState = IO StateId -> ST s StateId
forall a s. IO a -> ST s a
unsafeIOToST (IO StateId -> ST s StateId)
-> (Node s -> IO StateId) -> Node s -> ST s StateId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO StateId) -> Node s -> IO StateId
forall a b. Coercible a b => a -> b
coerce Node -> IO StateId
TSIO.nodeParseState
{-# INLINE nodeParseState #-}
nodeNextParseState :: Node s -> ST s StateId
nodeNextParseState :: forall s. Node s -> ST s StateId
nodeNextParseState = IO StateId -> ST s StateId
forall a s. IO a -> ST s a
unsafeIOToST (IO StateId -> ST s StateId)
-> (Node s -> IO StateId) -> Node s -> ST s StateId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO StateId) -> Node s -> IO StateId
forall a b. Coercible a b => a -> b
coerce Node -> IO StateId
TSIO.nodeNextParseState
{-# INLINE nodeNextParseState #-}
nodeParent :: Node s -> ST s (Node s)
nodeParent :: forall s. Node s -> ST s (Node s)
nodeParent = IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Node s -> IO (Node s)) -> Node s -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Node) -> Node s -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> IO Node
TSIO.nodeParent
{-# INLINE nodeParent #-}
nodeChildWithDescendant :: Node s -> Node s -> ST s (Node s)
nodeChildWithDescendant :: forall s. Node s -> Node s -> ST s (Node s)
nodeChildWithDescendant = (IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Node s -> IO (Node s)) -> Node s -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Node s -> IO (Node s)) -> Node s -> ST s (Node s))
-> (Node s -> Node s -> IO (Node s))
-> Node s
-> Node s
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> Node -> IO Node) -> Node s -> Node s -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> Node -> IO Node
TSIO.nodeChildWithDescendant
{-# INLINE nodeChildWithDescendant #-}
nodeChild :: Node s -> Word32 -> ST s (Node s)
nodeChild :: forall s. Node s -> Word32 -> ST s (Node s)
nodeChild = (IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Word32 -> IO (Node s)) -> Word32 -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> IO (Node s)) -> Word32 -> ST s (Node s))
-> (Node s -> Word32 -> IO (Node s))
-> Node s
-> Word32
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> Word32 -> IO Node) -> Node s -> Word32 -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> Word32 -> IO Node
TSIO.nodeChild
{-# INLINE nodeChild #-}
nodeFieldNameForChild :: Node s -> Word32 -> ST s FieldName
nodeFieldNameForChild :: forall s. Node s -> Word32 -> ST s FieldName
nodeFieldNameForChild = (IO FieldName -> ST s FieldName
forall a s. IO a -> ST s a
unsafeIOToST (IO FieldName -> ST s FieldName)
-> (Word32 -> IO FieldName) -> Word32 -> ST s FieldName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> IO FieldName) -> Word32 -> ST s FieldName)
-> (Node s -> Word32 -> IO FieldName)
-> Node s
-> Word32
-> ST s FieldName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> Word32 -> IO FieldName)
-> Node s -> Word32 -> IO FieldName
forall a b. Coercible a b => a -> b
coerce Node -> Word32 -> IO FieldName
TSIO.nodeFieldNameForChild
{-# INLINE nodeFieldNameForChild #-}
nodeFieldNameForChildAsString :: Node s -> Word32 -> ST s String
nodeFieldNameForChildAsString :: forall s. Node s -> Word32 -> ST s String
nodeFieldNameForChildAsString = (IO String -> ST s String
forall a s. IO a -> ST s a
unsafeIOToST (IO String -> ST s String)
-> (Word32 -> IO String) -> Word32 -> ST s String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> IO String) -> Word32 -> ST s String)
-> (Node s -> Word32 -> IO String)
-> Node s
-> Word32
-> ST s String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> Word32 -> IO String) -> Node s -> Word32 -> IO String
forall a b. Coercible a b => a -> b
coerce Node -> Word32 -> IO String
TSIO.nodeFieldNameForChildAsString
{-# INLINE nodeFieldNameForChildAsString #-}
nodeFieldNameForNamedChild :: Node s -> Word32 -> ST s FieldName
nodeFieldNameForNamedChild :: forall s. Node s -> Word32 -> ST s FieldName
nodeFieldNameForNamedChild = (IO FieldName -> ST s FieldName
forall a s. IO a -> ST s a
unsafeIOToST (IO FieldName -> ST s FieldName)
-> (Word32 -> IO FieldName) -> Word32 -> ST s FieldName
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> IO FieldName) -> Word32 -> ST s FieldName)
-> (Node s -> Word32 -> IO FieldName)
-> Node s
-> Word32
-> ST s FieldName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> Word32 -> IO FieldName)
-> Node s -> Word32 -> IO FieldName
forall a b. Coercible a b => a -> b
coerce Node -> Word32 -> IO FieldName
TSIO.nodeFieldNameForNamedChild
{-# INLINE nodeFieldNameForNamedChild #-}
nodeFieldNameForNamedChildAsString :: Node s -> Word32 -> ST s String
nodeFieldNameForNamedChildAsString :: forall s. Node s -> Word32 -> ST s String
nodeFieldNameForNamedChildAsString = (IO String -> ST s String
forall a s. IO a -> ST s a
unsafeIOToST (IO String -> ST s String)
-> (Word32 -> IO String) -> Word32 -> ST s String
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> IO String) -> Word32 -> ST s String)
-> (Node s -> Word32 -> IO String)
-> Node s
-> Word32
-> ST s String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> Word32 -> IO String) -> Node s -> Word32 -> IO String
forall a b. Coercible a b => a -> b
coerce Node -> Word32 -> IO String
TSIO.nodeFieldNameForNamedChildAsString
{-# INLINE nodeFieldNameForNamedChildAsString #-}
nodeChildCount :: Node s -> ST s Word32
nodeChildCount :: forall s. Node s -> ST s Word32
nodeChildCount = IO Word32 -> ST s Word32
forall a s. IO a -> ST s a
unsafeIOToST (IO Word32 -> ST s Word32)
-> (Node s -> IO Word32) -> Node s -> ST s Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Word32) -> Node s -> IO Word32
forall a b. Coercible a b => a -> b
coerce Node -> IO Word32
TSIO.nodeChildCount
{-# INLINE nodeChildCount #-}
nodeNamedChild :: Node s -> Word32 -> ST s (Node s)
nodeNamedChild :: forall s. Node s -> Word32 -> ST s (Node s)
nodeNamedChild = (IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Word32 -> IO (Node s)) -> Word32 -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> IO (Node s)) -> Word32 -> ST s (Node s))
-> (Node s -> Word32 -> IO (Node s))
-> Node s
-> Word32
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> Word32 -> IO Node) -> Node s -> Word32 -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> Word32 -> IO Node
TSIO.nodeNamedChild
{-# INLINE nodeNamedChild #-}
nodeNamedChildCount :: Node s -> ST s Word32
nodeNamedChildCount :: forall s. Node s -> ST s Word32
nodeNamedChildCount = IO Word32 -> ST s Word32
forall a s. IO a -> ST s a
unsafeIOToST (IO Word32 -> ST s Word32)
-> (Node s -> IO Word32) -> Node s -> ST s Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Word32) -> Node s -> IO Word32
forall a b. Coercible a b => a -> b
coerce Node -> IO Word32
TSIO.nodeNamedChildCount
{-# INLINE nodeNamedChildCount #-}
nodeChildByFieldName :: Node s -> FieldName -> ST s (Node s)
nodeChildByFieldName :: forall s. Node s -> FieldName -> ST s (Node s)
nodeChildByFieldName = (IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (FieldName -> IO (Node s)) -> FieldName -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((FieldName -> IO (Node s)) -> FieldName -> ST s (Node s))
-> (Node s -> FieldName -> IO (Node s))
-> Node s
-> FieldName
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> FieldName -> IO Node)
-> Node s -> FieldName -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> FieldName -> IO Node
TSIO.nodeChildByFieldName
{-# INLINE nodeChildByFieldName #-}
nodeChildByFieldId :: Node s -> FieldId -> ST s (Node s)
nodeChildByFieldId :: forall s. Node s -> FieldId -> ST s (Node s)
nodeChildByFieldId = (IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (FieldId -> IO (Node s)) -> FieldId -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((FieldId -> IO (Node s)) -> FieldId -> ST s (Node s))
-> (Node s -> FieldId -> IO (Node s))
-> Node s
-> FieldId
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> FieldId -> IO Node) -> Node s -> FieldId -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> FieldId -> IO Node
TSIO.nodeChildByFieldId
{-# INLINE nodeChildByFieldId #-}
nodeNextSibling :: Node s -> ST s (Node s)
nodeNextSibling :: forall s. Node s -> ST s (Node s)
nodeNextSibling = IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Node s -> IO (Node s)) -> Node s -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Node) -> Node s -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> IO Node
TSIO.nodeNextSibling
{-# INLINE nodeNextSibling #-}
nodePrevSibling :: Node s -> ST s (Node s)
nodePrevSibling :: forall s. Node s -> ST s (Node s)
nodePrevSibling = IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Node s -> IO (Node s)) -> Node s -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Node) -> Node s -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> IO Node
TSIO.nodePrevSibling
{-# INLINE nodePrevSibling #-}
nodeNextNamedSibling :: Node s -> ST s (Node s)
nodeNextNamedSibling :: forall s. Node s -> ST s (Node s)
nodeNextNamedSibling = IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Node s -> IO (Node s)) -> Node s -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Node) -> Node s -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> IO Node
TSIO.nodeNextNamedSibling
{-# INLINE nodeNextNamedSibling #-}
nodePrevNamedSibling :: Node s -> ST s (Node s)
nodePrevNamedSibling :: forall s. Node s -> ST s (Node s)
nodePrevNamedSibling = IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Node s -> IO (Node s)) -> Node s -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Node) -> Node s -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> IO Node
TSIO.nodePrevNamedSibling
{-# INLINE nodePrevNamedSibling #-}
nodeFirstChildForByte :: Node s -> Word32 -> ST s (Node s)
nodeFirstChildForByte :: forall s. Node s -> Word32 -> ST s (Node s)
nodeFirstChildForByte = (IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Word32 -> IO (Node s)) -> Word32 -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> IO (Node s)) -> Word32 -> ST s (Node s))
-> (Node s -> Word32 -> IO (Node s))
-> Node s
-> Word32
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> Word32 -> IO Node) -> Node s -> Word32 -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> Word32 -> IO Node
TSIO.nodeFirstChildForByte
{-# INLINE nodeFirstChildForByte #-}
nodeFirstNamedChildForByte :: Node s -> Word32 -> ST s (Node s)
nodeFirstNamedChildForByte :: forall s. Node s -> Word32 -> ST s (Node s)
nodeFirstNamedChildForByte = (IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Word32 -> IO (Node s)) -> Word32 -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> IO (Node s)) -> Word32 -> ST s (Node s))
-> (Node s -> Word32 -> IO (Node s))
-> Node s
-> Word32
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> Word32 -> IO Node) -> Node s -> Word32 -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> Word32 -> IO Node
TSIO.nodeFirstNamedChildForByte
{-# INLINE nodeFirstNamedChildForByte #-}
nodeDescendantCount :: Node s -> ST s Word32
nodeDescendantCount :: forall s. Node s -> ST s Word32
nodeDescendantCount = IO Word32 -> ST s Word32
forall a s. IO a -> ST s a
unsafeIOToST (IO Word32 -> ST s Word32)
-> (Node s -> IO Word32) -> Node s -> ST s Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO Word32) -> Node s -> IO Word32
forall a b. Coercible a b => a -> b
coerce Node -> IO Word32
TSIO.nodeDescendantCount
{-# INLINE nodeDescendantCount #-}
nodeDescendantForByteRange :: Node s -> Word32 -> Word32 -> ST s (Node s)
nodeDescendantForByteRange :: forall s. Node s -> Word32 -> Word32 -> ST s (Node s)
nodeDescendantForByteRange = ((IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Word32 -> IO (Node s)) -> Word32 -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> IO (Node s)) -> Word32 -> ST s (Node s))
-> (Word32 -> Word32 -> IO (Node s))
-> Word32
-> Word32
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> Word32 -> IO (Node s))
-> Word32 -> Word32 -> ST s (Node s))
-> (Node s -> Word32 -> Word32 -> IO (Node s))
-> Node s
-> Word32
-> Word32
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> Word32 -> Word32 -> IO Node)
-> Node s -> Word32 -> Word32 -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> Word32 -> Word32 -> IO Node
TSIO.nodeDescendantForByteRange
{-# INLINE nodeDescendantForByteRange #-}
nodeDescendantForPointRange :: Node s -> Point -> Point -> ST s (Node s)
nodeDescendantForPointRange :: forall s. Node s -> Point -> Point -> ST s (Node s)
nodeDescendantForPointRange = ((IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Point -> IO (Node s)) -> Point -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Point -> IO (Node s)) -> Point -> ST s (Node s))
-> (Point -> Point -> IO (Node s))
-> Point
-> Point
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Point -> Point -> IO (Node s))
-> Point -> Point -> ST s (Node s))
-> (Node s -> Point -> Point -> IO (Node s))
-> Node s
-> Point
-> Point
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> Point -> Point -> IO Node)
-> Node s -> Point -> Point -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> Point -> Point -> IO Node
TSIO.nodeDescendantForPointRange
{-# INLINE nodeDescendantForPointRange #-}
nodeNamedDescendantForByteRange :: Node s -> Word32 -> Word32 -> ST s (Node s)
nodeNamedDescendantForByteRange :: forall s. Node s -> Word32 -> Word32 -> ST s (Node s)
nodeNamedDescendantForByteRange = ((IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Word32 -> IO (Node s)) -> Word32 -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> IO (Node s)) -> Word32 -> ST s (Node s))
-> (Word32 -> Word32 -> IO (Node s))
-> Word32
-> Word32
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> Word32 -> IO (Node s))
-> Word32 -> Word32 -> ST s (Node s))
-> (Node s -> Word32 -> Word32 -> IO (Node s))
-> Node s
-> Word32
-> Word32
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> Word32 -> Word32 -> IO Node)
-> Node s -> Word32 -> Word32 -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> Word32 -> Word32 -> IO Node
TSIO.nodeNamedDescendantForByteRange
{-# INLINE nodeNamedDescendantForByteRange #-}
nodeNamedDescendantForPointRange :: Node s -> Point -> Point -> ST s (Node s)
nodeNamedDescendantForPointRange :: forall s. Node s -> Point -> Point -> ST s (Node s)
nodeNamedDescendantForPointRange = ((IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (Point -> IO (Node s)) -> Point -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Point -> IO (Node s)) -> Point -> ST s (Node s))
-> (Point -> Point -> IO (Node s))
-> Point
-> Point
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Point -> Point -> IO (Node s))
-> Point -> Point -> ST s (Node s))
-> (Node s -> Point -> Point -> IO (Node s))
-> Node s
-> Point
-> Point
-> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> Point -> Point -> IO Node)
-> Node s -> Point -> Point -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce Node -> Point -> Point -> IO Node
TSIO.nodeNamedDescendantForPointRange
{-# INLINE nodeNamedDescendantForPointRange #-}
nodeEdit :: Node s -> InputEdit -> ST s ()
nodeEdit :: forall s. Node s -> InputEdit -> ST s ()
nodeEdit = (IO () -> ST s ()
forall a s. IO a -> ST s a
unsafeIOToST (IO () -> ST s ()) -> (InputEdit -> IO ()) -> InputEdit -> ST s ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((InputEdit -> IO ()) -> InputEdit -> ST s ())
-> (Node s -> InputEdit -> IO ()) -> Node s -> InputEdit -> ST s ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> InputEdit -> IO ()) -> Node s -> InputEdit -> IO ()
forall a b. Coercible a b => a -> b
coerce Node -> InputEdit -> IO ()
TSIO.nodeEdit
{-# INLINE nodeEdit #-}
nodeEq :: Node s -> Node s -> ST s Bool
nodeEq :: forall s. Node s -> Node s -> ST s Bool
nodeEq = (IO Bool -> ST s Bool
forall a s. IO a -> ST s a
unsafeIOToST (IO Bool -> ST s Bool)
-> (Node s -> IO Bool) -> Node s -> ST s Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Node s -> IO Bool) -> Node s -> ST s Bool)
-> (Node s -> Node s -> IO Bool) -> Node s -> Node s -> ST s Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> Node -> IO Bool) -> Node s -> Node s -> IO Bool
forall a b. Coercible a b => a -> b
coerce Node -> Node -> IO Bool
TSIO.nodeEq
{-# INLINE nodeEq #-}
treeCursorNew :: Node s -> ST s (TreeCursor s)
treeCursorNew :: forall s. Node s -> ST s (TreeCursor s)
treeCursorNew = IO (TreeCursor s) -> ST s (TreeCursor s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (TreeCursor s) -> ST s (TreeCursor s))
-> (Node s -> IO (TreeCursor s)) -> Node s -> ST s (TreeCursor s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node -> IO TreeCursor) -> Node s -> IO (TreeCursor s)
forall a b. Coercible a b => a -> b
coerce Node -> IO TreeCursor
TSIO.treeCursorNew
treeCursorReset :: TreeCursor s -> Node s -> ST s ()
treeCursorReset :: forall s. TreeCursor s -> Node s -> ST s ()
treeCursorReset = (IO () -> ST s ()
forall a s. IO a -> ST s a
unsafeIOToST (IO () -> ST s ()) -> (Node s -> IO ()) -> Node s -> ST s ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Node s -> IO ()) -> Node s -> ST s ())
-> (TreeCursor s -> Node s -> IO ())
-> TreeCursor s
-> Node s
-> ST s ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> Node -> IO ()) -> TreeCursor s -> Node s -> IO ()
forall a b. Coercible a b => a -> b
coerce TreeCursor -> Node -> IO ()
TSIO.treeCursorReset
treeCursorResetTo :: TreeCursor s -> TreeCursor s -> ST s ()
treeCursorResetTo :: forall s. TreeCursor s -> TreeCursor s -> ST s ()
treeCursorResetTo = (IO () -> ST s ()
forall a s. IO a -> ST s a
unsafeIOToST (IO () -> ST s ())
-> (TreeCursor s -> IO ()) -> TreeCursor s -> ST s ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((TreeCursor s -> IO ()) -> TreeCursor s -> ST s ())
-> (TreeCursor s -> TreeCursor s -> IO ())
-> TreeCursor s
-> TreeCursor s
-> ST s ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> TreeCursor -> IO ())
-> TreeCursor s -> TreeCursor s -> IO ()
forall a b. Coercible a b => a -> b
coerce TreeCursor -> TreeCursor -> IO ()
TSIO.treeCursorResetTo
treeCursorCurrentNode :: TreeCursor s -> ST s (Node s)
treeCursorCurrentNode :: forall s. TreeCursor s -> ST s (Node s)
treeCursorCurrentNode = IO (Node s) -> ST s (Node s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Node s) -> ST s (Node s))
-> (TreeCursor s -> IO (Node s)) -> TreeCursor s -> ST s (Node s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> IO Node) -> TreeCursor s -> IO (Node s)
forall a b. Coercible a b => a -> b
coerce TreeCursor -> IO Node
TSIO.treeCursorCurrentNode
treeCursorCurrentFieldName :: TreeCursor s -> ST s (Maybe FieldName)
treeCursorCurrentFieldName :: forall s. TreeCursor s -> ST s (Maybe FieldName)
treeCursorCurrentFieldName = IO (Maybe FieldName) -> ST s (Maybe FieldName)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Maybe FieldName) -> ST s (Maybe FieldName))
-> (TreeCursor s -> IO (Maybe FieldName))
-> TreeCursor s
-> ST s (Maybe FieldName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> IO (Maybe ByteString))
-> TreeCursor s -> IO (Maybe FieldName)
forall a b. Coercible a b => a -> b
coerce TreeCursor -> IO (Maybe ByteString)
TSIO.treeCursorCurrentFieldName
treeCursorCurrentFieldId :: TreeCursor s -> ST s (Maybe FieldId)
treeCursorCurrentFieldId :: forall s. TreeCursor s -> ST s (Maybe FieldId)
treeCursorCurrentFieldId = IO (Maybe FieldId) -> ST s (Maybe FieldId)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Maybe FieldId) -> ST s (Maybe FieldId))
-> (TreeCursor s -> IO (Maybe FieldId))
-> TreeCursor s
-> ST s (Maybe FieldId)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> IO (Maybe FieldId))
-> TreeCursor s -> IO (Maybe FieldId)
forall a b. Coercible a b => a -> b
coerce TreeCursor -> IO (Maybe FieldId)
TSIO.treeCursorCurrentFieldId
treeCursorGotoParent :: TreeCursor s -> ST s Bool
treeCursorGotoParent :: forall s. TreeCursor s -> ST s Bool
treeCursorGotoParent = IO Bool -> ST s Bool
forall a s. IO a -> ST s a
unsafeIOToST (IO Bool -> ST s Bool)
-> (TreeCursor s -> IO Bool) -> TreeCursor s -> ST s Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> IO Bool) -> TreeCursor s -> IO Bool
forall a b. Coercible a b => a -> b
coerce TreeCursor -> IO Bool
TSIO.treeCursorGotoParent
treeCursorGotoNextSibling :: TreeCursor s -> ST s Bool
treeCursorGotoNextSibling :: forall s. TreeCursor s -> ST s Bool
treeCursorGotoNextSibling = IO Bool -> ST s Bool
forall a s. IO a -> ST s a
unsafeIOToST (IO Bool -> ST s Bool)
-> (TreeCursor s -> IO Bool) -> TreeCursor s -> ST s Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> IO Bool) -> TreeCursor s -> IO Bool
forall a b. Coercible a b => a -> b
coerce TreeCursor -> IO Bool
TSIO.treeCursorGotoNextSibling
treeCursorGotoPreviousSibling :: TreeCursor s -> ST s Bool
treeCursorGotoPreviousSibling :: forall s. TreeCursor s -> ST s Bool
treeCursorGotoPreviousSibling = IO Bool -> ST s Bool
forall a s. IO a -> ST s a
unsafeIOToST (IO Bool -> ST s Bool)
-> (TreeCursor s -> IO Bool) -> TreeCursor s -> ST s Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> IO Bool) -> TreeCursor s -> IO Bool
forall a b. Coercible a b => a -> b
coerce TreeCursor -> IO Bool
TSIO.treeCursorGotoPreviousSibling
treeCursorGotoFirstChild :: TreeCursor s -> ST s Bool
treeCursorGotoFirstChild :: forall s. TreeCursor s -> ST s Bool
treeCursorGotoFirstChild = IO Bool -> ST s Bool
forall a s. IO a -> ST s a
unsafeIOToST (IO Bool -> ST s Bool)
-> (TreeCursor s -> IO Bool) -> TreeCursor s -> ST s Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> IO Bool) -> TreeCursor s -> IO Bool
forall a b. Coercible a b => a -> b
coerce TreeCursor -> IO Bool
TSIO.treeCursorGotoFirstChild
treeCursorGotoLastChild :: TreeCursor s -> ST s Bool
treeCursorGotoLastChild :: forall s. TreeCursor s -> ST s Bool
treeCursorGotoLastChild = IO Bool -> ST s Bool
forall a s. IO a -> ST s a
unsafeIOToST (IO Bool -> ST s Bool)
-> (TreeCursor s -> IO Bool) -> TreeCursor s -> ST s Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> IO Bool) -> TreeCursor s -> IO Bool
forall a b. Coercible a b => a -> b
coerce TreeCursor -> IO Bool
TSIO.treeCursorGotoLastChild
treeCursorGotoDescendant :: TreeCursor s -> Word32 -> ST s ()
treeCursorGotoDescendant :: forall s. TreeCursor s -> Word32 -> ST s ()
treeCursorGotoDescendant = (IO () -> ST s ()
forall a s. IO a -> ST s a
unsafeIOToST (IO () -> ST s ()) -> (Word32 -> IO ()) -> Word32 -> ST s ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> IO ()) -> Word32 -> ST s ())
-> (TreeCursor s -> Word32 -> IO ())
-> TreeCursor s
-> Word32
-> ST s ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> Word32 -> IO ()) -> TreeCursor s -> Word32 -> IO ()
forall a b. Coercible a b => a -> b
coerce TreeCursor -> Word32 -> IO ()
TSIO.treeCursorGotoDescendant
treeCursorCurrentDescendantIndex :: TreeCursor s -> ST s Word32
treeCursorCurrentDescendantIndex :: forall s. TreeCursor s -> ST s Word32
treeCursorCurrentDescendantIndex = IO Word32 -> ST s Word32
forall a s. IO a -> ST s a
unsafeIOToST (IO Word32 -> ST s Word32)
-> (TreeCursor s -> IO Word32) -> TreeCursor s -> ST s Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> IO Word32) -> TreeCursor s -> IO Word32
forall a b. Coercible a b => a -> b
coerce TreeCursor -> IO Word32
TSIO.treeCursorCurrentDescendantIndex
treeCursorCurrentDepth :: TreeCursor s -> ST s Word32
treeCursorCurrentDepth :: forall s. TreeCursor s -> ST s Word32
treeCursorCurrentDepth = IO Word32 -> ST s Word32
forall a s. IO a -> ST s a
unsafeIOToST (IO Word32 -> ST s Word32)
-> (TreeCursor s -> IO Word32) -> TreeCursor s -> ST s Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> IO Word32) -> TreeCursor s -> IO Word32
forall a b. Coercible a b => a -> b
coerce TreeCursor -> IO Word32
TSIO.treeCursorCurrentDepth
treeCursorGotoFirstChildForByte :: TreeCursor s -> Word32 -> ST s Int64
treeCursorGotoFirstChildForByte :: forall s. TreeCursor s -> Word32 -> ST s Int64
treeCursorGotoFirstChildForByte = (IO Int64 -> ST s Int64
forall a s. IO a -> ST s a
unsafeIOToST (IO Int64 -> ST s Int64)
-> (Word32 -> IO Int64) -> Word32 -> ST s Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Word32 -> IO Int64) -> Word32 -> ST s Int64)
-> (TreeCursor s -> Word32 -> IO Int64)
-> TreeCursor s
-> Word32
-> ST s Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> Word32 -> IO Int64)
-> TreeCursor s -> Word32 -> IO Int64
forall a b. Coercible a b => a -> b
coerce TreeCursor -> Word32 -> IO Int64
TSIO.treeCursorGotoFirstChildForByte
treeCursorGotoFirstChildForPoint :: TreeCursor s -> Point -> ST s Int64
treeCursorGotoFirstChildForPoint :: forall s. TreeCursor s -> Point -> ST s Int64
treeCursorGotoFirstChildForPoint = (IO Int64 -> ST s Int64
forall a s. IO a -> ST s a
unsafeIOToST (IO Int64 -> ST s Int64)
-> (Point -> IO Int64) -> Point -> ST s Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Point -> IO Int64) -> Point -> ST s Int64)
-> (TreeCursor s -> Point -> IO Int64)
-> TreeCursor s
-> Point
-> ST s Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> Point -> IO Int64)
-> TreeCursor s -> Point -> IO Int64
forall a b. Coercible a b => a -> b
coerce TreeCursor -> Point -> IO Int64
TSIO.treeCursorGotoFirstChildForPoint
treeCursorCopy :: TreeCursor s -> ST s (TreeCursor s)
treeCursorCopy :: forall s. TreeCursor s -> ST s (TreeCursor s)
treeCursorCopy = IO (TreeCursor s) -> ST s (TreeCursor s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (TreeCursor s) -> ST s (TreeCursor s))
-> (TreeCursor s -> IO (TreeCursor s))
-> TreeCursor s
-> ST s (TreeCursor s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TreeCursor -> IO TreeCursor) -> TreeCursor s -> IO (TreeCursor s)
forall a b. Coercible a b => a -> b
coerce TreeCursor -> IO TreeCursor
TSIO.treeCursorCopy
languageCopy :: Language s -> ST s (Language s)
languageCopy :: forall s. Language s -> ST s (Language s)
languageCopy = IO (Language s) -> ST s (Language s)
forall a s. IO a -> ST s a
unsafeIOToST (IO (Language s) -> ST s (Language s))
-> (Language s -> IO (Language s))
-> Language s
-> ST s (Language s)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Language -> IO Language) -> Language s -> IO (Language s)
forall a b. Coercible a b => a -> b
coerce Language -> IO Language
TSIO.languageCopy
languageSymbolCount :: Language s -> ST s Word32
languageSymbolCount :: forall s. Language s -> ST s Word32
languageSymbolCount = IO Word32 -> ST s Word32
forall a s. IO a -> ST s a
unsafeIOToST (IO Word32 -> ST s Word32)
-> (Language s -> IO Word32) -> Language s -> ST s Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Language -> IO Word32) -> Language s -> IO Word32
forall a b. Coercible a b => a -> b
coerce Language -> IO Word32
TSIO.languageSymbolCount
languageStateCount :: Language s -> ST s Word32
languageStateCount :: forall s. Language s -> ST s Word32
languageStateCount = IO Word32 -> ST s Word32
forall a s. IO a -> ST s a
unsafeIOToST (IO Word32 -> ST s Word32)
-> (Language s -> IO Word32) -> Language s -> ST s Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Language -> IO Word32) -> Language s -> IO Word32
forall a b. Coercible a b => a -> b
coerce Language -> IO Word32
TSIO.languageStateCount
languageSymbolName :: Language s -> Symbol -> ST s ByteString
languageSymbolName :: forall s. Language s -> Symbol -> ST s ByteString
languageSymbolName = (IO ByteString -> ST s ByteString
forall a s. IO a -> ST s a
unsafeIOToST (IO ByteString -> ST s ByteString)
-> (Symbol -> IO ByteString) -> Symbol -> ST s ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Symbol -> IO ByteString) -> Symbol -> ST s ByteString)
-> (Language s -> Symbol -> IO ByteString)
-> Language s
-> Symbol
-> ST s ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Language -> Symbol -> IO ByteString)
-> Language s -> Symbol -> IO ByteString
forall a b. Coercible a b => a -> b
coerce Language -> Symbol -> IO ByteString
TSIO.languageSymbolName
languageSymbolForGrammarType :: Language s -> ByteString -> Bool -> ST s Symbol
languageSymbolForGrammarType :: forall s. Language s -> ByteString -> Bool -> ST s Symbol
languageSymbolForGrammarType = ((IO Symbol -> ST s Symbol
forall a s. IO a -> ST s a
unsafeIOToST (IO Symbol -> ST s Symbol)
-> (Bool -> IO Symbol) -> Bool -> ST s Symbol
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Bool -> IO Symbol) -> Bool -> ST s Symbol)
-> (ByteString -> Bool -> IO Symbol)
-> ByteString
-> Bool
-> ST s Symbol
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((ByteString -> Bool -> IO Symbol)
-> ByteString -> Bool -> ST s Symbol)
-> (Language s -> ByteString -> Bool -> IO Symbol)
-> Language s
-> ByteString
-> Bool
-> ST s Symbol
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Language -> ByteString -> Bool -> IO Symbol)
-> Language s -> ByteString -> Bool -> IO Symbol
forall a b. Coercible a b => a -> b
coerce Language -> ByteString -> Bool -> IO Symbol
TSIO.languageSymbolForGrammarType
languageFieldCount :: Language s -> ST s Word32
languageFieldCount :: forall s. Language s -> ST s Word32
languageFieldCount = IO Word32 -> ST s Word32
forall a s. IO a -> ST s a
unsafeIOToST (IO Word32 -> ST s Word32)
-> (Language s -> IO Word32) -> Language s -> ST s Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Language -> IO Word32) -> Language s -> IO Word32
forall a b. Coercible a b => a -> b
coerce Language -> IO Word32
TSIO.languageFieldCount
languageFieldNameForId :: Language s -> FieldId -> ST s ByteString
languageFieldNameForId :: forall s. Language s -> FieldId -> ST s ByteString
languageFieldNameForId = (IO ByteString -> ST s ByteString
forall a s. IO a -> ST s a
unsafeIOToST (IO ByteString -> ST s ByteString)
-> (FieldId -> IO ByteString) -> FieldId -> ST s ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((FieldId -> IO ByteString) -> FieldId -> ST s ByteString)
-> (Language s -> FieldId -> IO ByteString)
-> Language s
-> FieldId
-> ST s ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Language -> FieldId -> IO ByteString)
-> Language s -> FieldId -> IO ByteString
forall a b. Coercible a b => a -> b
coerce Language -> FieldId -> IO ByteString
TSIO.languageFieldNameForId
languageFieldIdForName :: Language s -> ByteString -> ST s FieldId
languageFieldIdForName :: forall s. Language s -> ByteString -> ST s FieldId
languageFieldIdForName = (IO FieldId -> ST s FieldId
forall a s. IO a -> ST s a
unsafeIOToST (IO FieldId -> ST s FieldId)
-> (ByteString -> IO FieldId) -> ByteString -> ST s FieldId
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((ByteString -> IO FieldId) -> ByteString -> ST s FieldId)
-> (Language s -> ByteString -> IO FieldId)
-> Language s
-> ByteString
-> ST s FieldId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Language -> ByteString -> IO FieldId)
-> Language s -> ByteString -> IO FieldId
forall a b. Coercible a b => a -> b
coerce Language -> ByteString -> IO FieldId
TSIO.languageFieldIdForName
languageSymbolType :: Language s -> Symbol -> ST s SymbolType
languageSymbolType :: forall s. Language s -> Symbol -> ST s SymbolType
languageSymbolType = (IO SymbolType -> ST s SymbolType
forall a s. IO a -> ST s a
unsafeIOToST (IO SymbolType -> ST s SymbolType)
-> (Symbol -> IO SymbolType) -> Symbol -> ST s SymbolType
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Symbol -> IO SymbolType) -> Symbol -> ST s SymbolType)
-> (Language s -> Symbol -> IO SymbolType)
-> Language s
-> Symbol
-> ST s SymbolType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Language -> Symbol -> IO SymbolType)
-> Language s -> Symbol -> IO SymbolType
forall a b. Coercible a b => a -> b
coerce Language -> Symbol -> IO SymbolType
TSIO.languageSymbolType
languageVersion :: Language s -> ST s Word32
languageVersion :: forall s. Language s -> ST s Word32
languageVersion = IO Word32 -> ST s Word32
forall a s. IO a -> ST s a
unsafeIOToST (IO Word32 -> ST s Word32)
-> (Language s -> IO Word32) -> Language s -> ST s Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Language -> IO Word32) -> Language s -> IO Word32
forall a b. Coercible a b => a -> b
coerce Language -> IO Word32
TSIO.languageVersion
languageNextState :: Language s -> StateId -> Symbol -> ST s StateId
languageNextState :: forall s. Language s -> StateId -> Symbol -> ST s StateId
languageNextState = ((IO StateId -> ST s StateId
forall a s. IO a -> ST s a
unsafeIOToST (IO StateId -> ST s StateId)
-> (Symbol -> IO StateId) -> Symbol -> ST s StateId
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((Symbol -> IO StateId) -> Symbol -> ST s StateId)
-> (StateId -> Symbol -> IO StateId)
-> StateId
-> Symbol
-> ST s StateId
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((StateId -> Symbol -> IO StateId)
-> StateId -> Symbol -> ST s StateId)
-> (Language s -> StateId -> Symbol -> IO StateId)
-> Language s
-> StateId
-> Symbol
-> ST s StateId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Language -> StateId -> Symbol -> IO StateId)
-> Language s -> StateId -> Symbol -> IO StateId
forall a b. Coercible a b => a -> b
coerce Language -> StateId -> Symbol -> IO StateId
TSIO.languageNextState