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

Safe HaskellNone
LanguageHaskell2010

TreeSitter.Unmarshal

Synopsis

Documentation

class Unmarshal t where Source #

Unmarshalling 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 Generic1 instance.

Minimal complete definition

Nothing

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (t a) Source #

unmarshalNode :: (Carrier sig m, Generic1 t, GUnmarshal (Rep1 t), Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (t a) Source #

Instances
Unmarshal t => Unmarshal (Rec1 t) Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Rec1 t a) Source #

Unmarshal (Token sym n) Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Token sym n a) Source #

(Unmarshal f, Unmarshal g, SymbolMatching f, SymbolMatching g) => Unmarshal (f :+: g) Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalNode :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m ((f :+: g) a) Source #

class UnmarshalAnn a where Source #

Unmarshal an annotation field.

Leaf nodes have Text fields, and leaves, anonymous leaves, and products all have parametric annotation fields. All of these fields are unmarshalled using the metadata of the node, e.g. its start/end bytes, without reference to any child nodes it may contain.

Methods

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

Instances
UnmarshalAnn () Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

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

UnmarshalAnn Text Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

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

UnmarshalAnn Loc Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

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

UnmarshalAnn Range Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

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

UnmarshalAnn Span Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

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

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

Instance for pairs of annotations

Instance details

Defined in TreeSitter.Unmarshal

Methods

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

class UnmarshalField t where Source #

Optional/repeated fields occurring in product datatypes are wrapped in type constructors, e.g. Maybe, '[]', or NonEmpty, and thus can unmarshal zero or more nodes for the same field name.

Methods

unmarshalField :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, Unmarshal f, UnmarshalAnn a) => [Node] -> m (t (f a)) Source #

Instances
UnmarshalField [] Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

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

UnmarshalField Maybe Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

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

UnmarshalField NonEmpty Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalField :: (Carrier sig m, Member (Reader ByteString) sig, Member (Reader (Ptr Cursor)) sig, MonadFail m, MonadIO m, Unmarshal f, UnmarshalAnn a) => [Node] -> m (NonEmpty (f a)) 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 f => SymbolMatching (Rec1 f) Source # 
Instance details

Defined in TreeSitter.Unmarshal

(KnownNat n, KnownSymbol sym) => SymbolMatching (Token sym n) Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

symbolMatch :: Proxy (Token sym n) -> Node -> Bool Source #

showFailure :: Proxy (Token sym n) -> Node -> String Source #

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

Defined in TreeSitter.Unmarshal

Methods

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

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

SymbolMatching f => SymbolMatching (M1 i c f) Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

symbolMatch :: Proxy (M1 i c f) -> Node -> Bool Source #

showFailure :: Proxy (M1 i c f) -> 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 Node Source #

Return the Node that the cursor is pointing at.

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 Fields Source #

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