Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- parseByteString :: (Unmarshal t, UnmarshalAnn a) => Ptr Language -> ByteString -> IO (Either String (t a))
- newtype FieldName = FieldName {}
- class Unmarshal t where
- unmarshalNode :: (Has (Reader ByteString) sig m, Has (Reader (Ptr Cursor)) sig m, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (t a)
- class UnmarshalAnn a where
- unmarshalAnn :: (Has (Reader ByteString) sig m, Has (Reader (Ptr Cursor)) sig m, MonadFail m, MonadIO m) => Node -> m a
- class UnmarshalField t where
- unmarshalField :: (Has (Reader ByteString) sig m, Has (Reader (Ptr Cursor)) sig m, MonadFail m, MonadIO m, Unmarshal f, UnmarshalAnn a) => [Node] -> m (t (f a))
- class SymbolMatching (a :: * -> *) where
- symbolMatch :: Proxy a -> Node -> Bool
- showFailure :: Proxy a -> Node -> String
- step :: (Has (Reader (Ptr Cursor)) sig m, MonadIO m) => m Bool
- push :: (Has (Reader (Ptr Cursor)) sig m, MonadIO m) => m a -> m (Maybe a)
- goto :: (Has (Reader (Ptr Cursor)) sig m, MonadIO m) => TSNode -> m ()
- peekNode :: (Has (Reader (Ptr Cursor)) sig m, MonadIO m) => m Node
- peekFieldName :: (Has (Reader (Ptr Cursor)) sig m, MonadIO m) => m (Maybe FieldName)
- getFields :: (Has (Reader (Ptr Cursor)) sig m, MonadIO m) => m Fields
Documentation
parseByteString :: (Unmarshal t, UnmarshalAnn a) => Ptr Language -> ByteString -> IO (Either String (t a)) Source #
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.
Nothing
unmarshalNode :: (Has (Reader ByteString) sig m, Has (Reader (Ptr Cursor)) sig m, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (t a) Source #
default unmarshalNode :: (Generic1 t, GUnmarshal (Rep1 t), Has (Reader ByteString) sig m, Has (Reader (Ptr Cursor)) sig m, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (t a) Source #
Instances
Unmarshal t => Unmarshal (Rec1 t) Source # | |
Defined in TreeSitter.Unmarshal unmarshalNode :: forall (sig :: (Type -> Type) -> Type -> Type) m a. (Has (Reader ByteString) sig m, Has (Reader (Ptr Cursor)) sig m, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Rec1 t a) Source # | |
Unmarshal (Token sym n) Source # | |
Defined in TreeSitter.Unmarshal unmarshalNode :: forall (sig :: (Type -> Type) -> Type -> Type) m a. (Has (Reader ByteString) sig m, Has (Reader (Ptr Cursor)) sig m, 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 # | |
Defined in TreeSitter.Unmarshal unmarshalNode :: forall (sig :: (Type -> Type) -> Type -> Type) m a. (Has (Reader ByteString) sig m, Has (Reader (Ptr Cursor)) sig m, 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.
unmarshalAnn :: (Has (Reader ByteString) sig m, Has (Reader (Ptr Cursor)) sig m, MonadFail m, MonadIO m) => Node -> m a Source #
Instances
UnmarshalAnn () Source # | |
Defined in TreeSitter.Unmarshal | |
UnmarshalAnn Text Source # | |
Defined in TreeSitter.Unmarshal | |
UnmarshalAnn Loc Source # | |
Defined in TreeSitter.Unmarshal | |
UnmarshalAnn Range Source # | |
Defined in TreeSitter.Unmarshal | |
UnmarshalAnn Span Source # | |
Defined in TreeSitter.Unmarshal | |
(UnmarshalAnn a, UnmarshalAnn b) => UnmarshalAnn (a, b) Source # | Instance for pairs of annotations |
Defined in TreeSitter.Unmarshal |
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.
unmarshalField :: (Has (Reader ByteString) sig m, Has (Reader (Ptr Cursor)) sig m, MonadFail m, MonadIO m, Unmarshal f, UnmarshalAnn a) => [Node] -> m (t (f a)) Source #
Instances
UnmarshalField [] Source # | |
Defined in TreeSitter.Unmarshal unmarshalField :: forall (sig :: (Type -> Type) -> Type -> Type) m f a. (Has (Reader ByteString) sig m, Has (Reader (Ptr Cursor)) sig m, MonadFail m, MonadIO m, Unmarshal f, UnmarshalAnn a) => [Node] -> m [f a] Source # | |
UnmarshalField Maybe Source # | |
Defined in TreeSitter.Unmarshal | |
UnmarshalField NonEmpty Source # | |
Defined in TreeSitter.Unmarshal |
class SymbolMatching (a :: * -> *) where Source #
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 # | |
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 |
step :: (Has (Reader (Ptr Cursor)) sig m, MonadIO m) => m Bool Source #
Advance the cursor to the next sibling of the current node.
push :: (Has (Reader (Ptr Cursor)) sig m, MonadIO m) => m a -> m (Maybe a) Source #
Run an action over the children of the current node.
goto :: (Has (Reader (Ptr Cursor)) sig m, MonadIO m) => TSNode -> m () Source #
Move the cursor to point at the passed TSNode
.
peekNode :: (Has (Reader (Ptr Cursor)) sig m, MonadIO m) => m Node Source #
Return the Node
that the cursor is pointing at.