tree-sitter-0.2.1.0: Unstable bindings for the tree-sitter parsing library.

Safe HaskellNone
LanguageHaskell2010

TreeSitter.Unmarshal

Synopsis

Documentation

class Unmarshal a where Source #

Unmarshal is the process of iterating over tree-sitter’s parse trees using its tree cursor API and producing Haskell ASTs for the relevant nodes.

Datatypes which can be constructed from tree-sitter parse trees may use the default definition of unmarshalNode providing that they have a suitable Generic instance.

Minimal complete definition

Nothing

Methods

unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m a Source #

unmarshalNodes :: (MonadFail m, Carrier sig m, GUnmarshal (Rep a), Generic a, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m a Source #

Instances
Unmarshal () Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m () Source #

Unmarshal Text Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Text Source #

Unmarshal Range Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Range Source #

Unmarshal Span Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m Span Source #

Unmarshal a => Unmarshal [a] Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m [a] Source #

Unmarshal a => Unmarshal (Maybe a) Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m (Maybe a) Source #

Unmarshal a => Unmarshal (NonEmpty a) Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m (NonEmpty a) Source #

(Unmarshal a, Unmarshal b, SymbolMatching a, SymbolMatching b) => Unmarshal (Either a b) Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m (Either a b) Source #

(Unmarshal a, Unmarshal b) => Unmarshal (a, b) Source #

Instance for pairs of annotations

Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalNodes :: (MonadFail m, Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadIO m) => [Node] -> m (a, b) Source #

class SymbolMatching a where Source #

Methods

symbolMatch :: Proxy a -> Node -> Bool Source #

showFailure :: Proxy a -> Node -> String Source #

Provide error message describing the node symbol vs. the symbols this can match

Instances
SymbolMatching a => SymbolMatching ([a] :: Type) Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

symbolMatch :: Proxy [a] -> Node -> Bool Source #

showFailure :: Proxy [a] -> Node -> String Source #

SymbolMatching a => SymbolMatching (Maybe a :: Type) Source # 
Instance details

Defined in TreeSitter.Unmarshal

(SymbolMatching a, SymbolMatching b) => SymbolMatching (Either a b :: Type) Source # 
Instance details

Defined in TreeSitter.Unmarshal

(SymbolMatching f, SymbolMatching g) => SymbolMatching (f :+: g :: k -> Type) Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

symbolMatch :: Proxy (f :+: g) -> Node -> Bool Source #

showFailure :: Proxy (f :+: g) -> Node -> String Source #

SymbolMatching k2 => SymbolMatching (M1 C c (M1 S s (K1 i k2 :: k1 -> Type)) :: k1 -> Type) Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

symbolMatch :: Proxy (M1 C c (M1 S s (K1 i k2))) -> Node -> Bool Source #

showFailure :: Proxy (M1 C c (M1 S s (K1 i k2))) -> Node -> String Source #

step :: (Carrier sig m, Member (Reader (Ptr Cursor)) sig, MonadIO m) => m Bool Source #

Advance the cursor to the next sibling of the current node.

push :: (Carrier sig m, Member (Reader (Ptr Cursor)) sig, MonadIO m) => m a -> m (Maybe a) Source #

Run an action over the children of the current node.

goto :: (Carrier sig m, Member (Reader (Ptr Cursor)) sig, MonadIO m) => TSNode -> m () Source #

Move the cursor to point at the passed TSNode.

peekNode :: (Carrier sig m, Member (Reader (Ptr Cursor)) sig, MonadIO m) => m (Maybe Node) Source #

Return the Node that the cursor is pointing at (if any), or Nothing otherwise.

peekFieldName :: (Carrier sig m, Member (Reader (Ptr Cursor)) sig, MonadIO m) => m (Maybe FieldName) Source #

Return the field name (if any) for the node that the cursor is pointing at (if any), or Nothing otherwise.

getFields :: (Carrier sig m, Member (Reader (Ptr Cursor)) sig, MonadIO m) => m (Map FieldName [Node]) Source #

Return the fields remaining in the current branch, represented as Map of FieldNames to their corresponding Nodes.