Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- parseByteString :: (Unmarshal t, UnmarshalAnn a) => Ptr Language -> ByteString -> IO (Either String (t a))
- data UnmarshalState = UnmarshalState {
- source :: !ByteString
- cursor :: !(Ptr Cursor)
- newtype UnmarshalError = UnmarshalError {}
- newtype FieldName = FieldName {}
- class SymbolMatching t => Unmarshal t where
- class UnmarshalAnn a where
- unmarshalAnn :: Node -> MatchM a
- class UnmarshalField t where
- unmarshalField :: (Unmarshal f, UnmarshalAnn a) => String -> String -> [Node] -> MatchM (t (f a))
- class SymbolMatching (a :: * -> *) where
- matchedSymbols :: Proxy a -> [Int]
- showFailure :: Proxy a -> Node -> String
- newtype Match t = Match {
- runMatch :: forall a. UnmarshalAnn a => Node -> MatchM (t a)
- hoist :: (forall x. t x -> t' x) -> Match t -> Match t'
- lookupSymbol :: TSSymbol -> IntMap a -> Maybe a
- unmarshalNode :: forall t a. (UnmarshalAnn a, Unmarshal t) => Node -> MatchM (t a)
- class GHasAnn a t where
- gann :: t a -> a
Documentation
parseByteString :: (Unmarshal t, UnmarshalAnn a) => Ptr Language -> ByteString -> IO (Either String (t a)) Source #
data UnmarshalState Source #
UnmarshalState | |
|
newtype UnmarshalError Source #
Instances
Show UnmarshalError Source # | |
Defined in TreeSitter.Unmarshal showsPrec :: Int -> UnmarshalError -> ShowS # show :: UnmarshalError -> String # showList :: [UnmarshalError] -> ShowS # | |
Exception UnmarshalError Source # | |
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.
Nothing
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.
unmarshalAnn :: Node -> MatchM a Source #
Instances
UnmarshalAnn () Source # | |
Defined in TreeSitter.Unmarshal unmarshalAnn :: Node -> MatchM () Source # | |
UnmarshalAnn Text Source # | |
Defined in TreeSitter.Unmarshal unmarshalAnn :: Node -> MatchM Text Source # | |
UnmarshalAnn Loc Source # | |
Defined in TreeSitter.Unmarshal unmarshalAnn :: Node -> MatchM Loc Source # | |
UnmarshalAnn Range Source # | |
Defined in TreeSitter.Unmarshal unmarshalAnn :: Node -> MatchM Range Source # | |
UnmarshalAnn Span Source # | |
Defined in TreeSitter.Unmarshal unmarshalAnn :: Node -> MatchM Span Source # | |
(UnmarshalAnn a, UnmarshalAnn b) => UnmarshalAnn (a, b) Source # | Instance for pairs of annotations |
Defined in TreeSitter.Unmarshal 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.
:: (Unmarshal f, UnmarshalAnn a) | |
=> String | datatype name |
-> String | field name |
-> [Node] | nodes |
-> MatchM (t (f a)) |
Instances
UnmarshalField [] Source # | |
Defined in TreeSitter.Unmarshal unmarshalField :: (Unmarshal f, UnmarshalAnn a) => String -> String -> [Node] -> MatchM [f a] Source # | |
UnmarshalField Maybe Source # | |
Defined in TreeSitter.Unmarshal unmarshalField :: (Unmarshal f, UnmarshalAnn a) => String -> String -> [Node] -> MatchM (Maybe (f a)) Source # | |
UnmarshalField NonEmpty Source # | |
Defined in TreeSitter.Unmarshal unmarshalField :: (Unmarshal f, UnmarshalAnn a) => String -> String -> [Node] -> MatchM (NonEmpty (f a)) Source # |
class SymbolMatching (a :: * -> *) where Source #
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
SymbolMatching f => SymbolMatching (Rec1 f) Source # | |
Defined in TreeSitter.Unmarshal | |
(KnownNat n, KnownSymbol sym) => SymbolMatching (Token sym n) Source # | |
Defined in TreeSitter.Unmarshal | |
(SymbolMatching f, SymbolMatching g) => SymbolMatching (f :+: g) Source # | |
Defined in TreeSitter.Unmarshal | |
SymbolMatching f => SymbolMatching (M1 i c f) Source # | |
Defined in TreeSitter.Unmarshal |
unmarshalNode :: forall t a. (UnmarshalAnn a, Unmarshal t) => Node -> MatchM (t a) Source #
Unmarshal a node