tree-sitter-0.8.0.1: Unstable bindings for the tree-sitter parsing library.
Safe HaskellNone
LanguageHaskell2010

TreeSitter.Unmarshal

Synopsis

Documentation

data UnmarshalState Source #

Constructors

UnmarshalState 

Fields

newtype FieldName Source #

Constructors

FieldName 

Fields

Instances

Instances details
Eq FieldName Source # 
Instance details

Defined in TreeSitter.Unmarshal

Ord FieldName Source # 
Instance details

Defined in TreeSitter.Unmarshal

Show FieldName Source # 
Instance details

Defined in TreeSitter.Unmarshal

class SymbolMatching t => 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 matchers providing that they have a suitable Generic1 instance.

Minimal complete definition

Nothing

Methods

matchers' :: IntMap (Match t) Source #

matchers :: B (Int, Match t) Source #

default matchers :: (Generic1 t, GUnmarshal (Rep1 t)) => B (Int, Match t) Source #

Instances

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

Defined in TreeSitter.Unmarshal

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

Defined in TreeSitter.Unmarshal

Methods

matchers' :: IntMap (Match (Token sym n)) Source #

matchers :: B (Int, Match (Token sym n)) Source #

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

Defined in TreeSitter.Unmarshal

Methods

matchers' :: IntMap (Match (f :+: g)) Source #

matchers :: B (Int, Match (f :+: g)) 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 :: Node -> MatchM a Source #

Instances

Instances details
UnmarshalAnn () Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalAnn :: Node -> MatchM () Source #

UnmarshalAnn Text Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalAnn :: Node -> MatchM Text Source #

UnmarshalAnn Loc Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalAnn :: Node -> MatchM Loc Source #

UnmarshalAnn Range Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalAnn :: Node -> MatchM Range Source #

UnmarshalAnn Span Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalAnn :: Node -> MatchM Span Source #

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

Instance for pairs of annotations

Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalAnn :: Node -> MatchM (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 Source #

Arguments

:: (Unmarshal f, UnmarshalAnn a) 
=> String

datatype name

-> String

field name

-> [Node]

nodes

-> MatchM (t (f a)) 

Instances

Instances details
UnmarshalField [] Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalField :: (Unmarshal f, UnmarshalAnn a) => String -> String -> [Node] -> MatchM [f a] Source #

UnmarshalField Maybe Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalField :: (Unmarshal f, UnmarshalAnn a) => String -> String -> [Node] -> MatchM (Maybe (f a)) Source #

UnmarshalField NonEmpty Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

unmarshalField :: (Unmarshal f, UnmarshalAnn a) => String -> String -> [Node] -> MatchM (NonEmpty (f a)) Source #

class SymbolMatching (a :: * -> *) where Source #

Methods

matchedSymbols :: Proxy a -> [Int] Source #

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

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

Instances

Instances details
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

matchedSymbols :: Proxy (Token sym n) -> [Int] Source #

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

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

Defined in TreeSitter.Unmarshal

Methods

matchedSymbols :: Proxy (f :+: g) -> [Int] Source #

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

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

Defined in TreeSitter.Unmarshal

Methods

matchedSymbols :: Proxy (M1 i c f) -> [Int] Source #

showFailure :: Proxy (M1 i c f) -> Node -> String Source #

newtype Match t Source #

Constructors

Match 

Fields

hoist :: (forall x. t x -> t' x) -> Match t -> Match t' Source #

unmarshalNode :: forall t a. (UnmarshalAnn a, Unmarshal t) => Node -> MatchM (t a) Source #

Unmarshal a node

class GHasAnn a t where Source #

Methods

gann :: t a -> a Source #

Instances

Instances details
HasField "ann" (t a) a => GHasAnn a t Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

gann :: t a -> a Source #

(GHasAnn a l, GHasAnn a r) => GHasAnn a (l :+: r) Source # 
Instance details

Defined in TreeSitter.Unmarshal

Methods

gann :: (l :+: r) a -> a Source #

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

Defined in TreeSitter.Unmarshal

Methods

gann :: M1 i c f a -> a Source #