tree-sitter-json-0.4.0.0: Tree-sitter grammar/parser for JSON

Safe HaskellNone
LanguageHaskell2010

TreeSitter.JSON.AST

Synopsis

Documentation

data StringContent a Source #

The content of a string literal.

This is defined rather than being derived from the grammar to represent it as just the textual content, without explicit representation of escape sequences.

Constructors

StringContent 

Fields

Instances
Functor StringContent Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fmap :: (a -> b) -> StringContent a -> StringContent b #

(<$) :: a -> StringContent b -> StringContent a #

Foldable StringContent Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fold :: Monoid m => StringContent m -> m #

foldMap :: Monoid m => (a -> m) -> StringContent a -> m #

foldr :: (a -> b -> b) -> b -> StringContent a -> b #

foldr' :: (a -> b -> b) -> b -> StringContent a -> b #

foldl :: (b -> a -> b) -> b -> StringContent a -> b #

foldl' :: (b -> a -> b) -> b -> StringContent a -> b #

foldr1 :: (a -> a -> a) -> StringContent a -> a #

foldl1 :: (a -> a -> a) -> StringContent a -> a #

toList :: StringContent a -> [a] #

null :: StringContent a -> Bool #

length :: StringContent a -> Int #

elem :: Eq a => a -> StringContent a -> Bool #

maximum :: Ord a => StringContent a -> a #

minimum :: Ord a => StringContent a -> a #

sum :: Num a => StringContent a -> a #

product :: Num a => StringContent a -> a #

Traversable StringContent Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

traverse :: Applicative f => (a -> f b) -> StringContent a -> f (StringContent b) #

sequenceA :: Applicative f => StringContent (f a) -> f (StringContent a) #

mapM :: Monad m => (a -> m b) -> StringContent a -> m (StringContent b) #

sequence :: Monad m => StringContent (m a) -> m (StringContent a) #

Unmarshal StringContent Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

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

Eq a => Eq (StringContent a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Ord a => Ord (StringContent a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Show a => Show (StringContent a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Generic (StringContent a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep (StringContent a) :: Type -> Type #

Generic1 StringContent Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep1 StringContent :: k -> Type #

type Rep (StringContent a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep (StringContent a) = D1 (MetaData "StringContent" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "StringContent" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))
type Rep1 StringContent Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep1 StringContent = D1 (MetaData "StringContent" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "StringContent" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Null a Source #

Constructors

Null 

Fields

Instances
Functor Null Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fmap :: (a -> b) -> Null a -> Null b #

(<$) :: a -> Null b -> Null a #

Foldable Null Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fold :: Monoid m => Null m -> m #

foldMap :: Monoid m => (a -> m) -> Null a -> m #

foldr :: (a -> b -> b) -> b -> Null a -> b #

foldr' :: (a -> b -> b) -> b -> Null a -> b #

foldl :: (b -> a -> b) -> b -> Null a -> b #

foldl' :: (b -> a -> b) -> b -> Null a -> b #

foldr1 :: (a -> a -> a) -> Null a -> a #

foldl1 :: (a -> a -> a) -> Null a -> a #

toList :: Null a -> [a] #

null :: Null a -> Bool #

length :: Null a -> Int #

elem :: Eq a => a -> Null a -> Bool #

maximum :: Ord a => Null a -> a #

minimum :: Ord a => Null a -> a #

sum :: Num a => Null a -> a #

product :: Num a => Null a -> a #

Traversable Null Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

traverse :: Applicative f => (a -> f b) -> Null a -> f (Null b) #

sequenceA :: Applicative f => Null (f a) -> f (Null a) #

mapM :: Monad m => (a -> m b) -> Null a -> m (Null b) #

sequence :: Monad m => Null (m a) -> m (Null a) #

SymbolMatching Null Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

symbolMatch :: Proxy Null -> Node -> Bool

showFailure :: Proxy Null -> Node -> String

Unmarshal Null Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

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

Eq a => Eq (Null a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

(==) :: Null a -> Null a -> Bool #

(/=) :: Null a -> Null a -> Bool #

Ord a => Ord (Null a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

compare :: Null a -> Null a -> Ordering #

(<) :: Null a -> Null a -> Bool #

(<=) :: Null a -> Null a -> Bool #

(>) :: Null a -> Null a -> Bool #

(>=) :: Null a -> Null a -> Bool #

max :: Null a -> Null a -> Null a #

min :: Null a -> Null a -> Null a #

Show a => Show (Null a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

showsPrec :: Int -> Null a -> ShowS #

show :: Null a -> String #

showList :: [Null a] -> ShowS #

Generic (Null a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep (Null a) :: Type -> Type #

Methods

from :: Null a -> Rep (Null a) x #

to :: Rep (Null a) x -> Null a #

Generic1 Null Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep1 Null :: k -> Type #

Methods

from1 :: Null a -> Rep1 Null a #

to1 :: Rep1 Null a -> Null a #

type Rep (Null a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep (Null a) = D1 (MetaData "Null" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "Null" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))
type Rep1 Null Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep1 Null = D1 (MetaData "Null" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "Null" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data False a Source #

Constructors

False 

Fields

Instances
Functor False Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fmap :: (a -> b) -> False a -> False b #

(<$) :: a -> False b -> False a #

Foldable False Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fold :: Monoid m => False m -> m #

foldMap :: Monoid m => (a -> m) -> False a -> m #

foldr :: (a -> b -> b) -> b -> False a -> b #

foldr' :: (a -> b -> b) -> b -> False a -> b #

foldl :: (b -> a -> b) -> b -> False a -> b #

foldl' :: (b -> a -> b) -> b -> False a -> b #

foldr1 :: (a -> a -> a) -> False a -> a #

foldl1 :: (a -> a -> a) -> False a -> a #

toList :: False a -> [a] #

null :: False a -> Bool #

length :: False a -> Int #

elem :: Eq a => a -> False a -> Bool #

maximum :: Ord a => False a -> a #

minimum :: Ord a => False a -> a #

sum :: Num a => False a -> a #

product :: Num a => False a -> a #

Traversable False Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

traverse :: Applicative f => (a -> f b) -> False a -> f (False b) #

sequenceA :: Applicative f => False (f a) -> f (False a) #

mapM :: Monad m => (a -> m b) -> False a -> m (False b) #

sequence :: Monad m => False (m a) -> m (False a) #

SymbolMatching False Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

symbolMatch :: Proxy False -> Node -> Bool

showFailure :: Proxy False -> Node -> String

Unmarshal False Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

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

Eq a => Eq (False a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

(==) :: False a -> False a -> Bool #

(/=) :: False a -> False a -> Bool #

Ord a => Ord (False a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

compare :: False a -> False a -> Ordering #

(<) :: False a -> False a -> Bool #

(<=) :: False a -> False a -> Bool #

(>) :: False a -> False a -> Bool #

(>=) :: False a -> False a -> Bool #

max :: False a -> False a -> False a #

min :: False a -> False a -> False a #

Show a => Show (False a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

showsPrec :: Int -> False a -> ShowS #

show :: False a -> String #

showList :: [False a] -> ShowS #

Generic (False a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep (False a) :: Type -> Type #

Methods

from :: False a -> Rep (False a) x #

to :: Rep (False a) x -> False a #

Generic1 False Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep1 False :: k -> Type #

Methods

from1 :: False a -> Rep1 False a #

to1 :: Rep1 False a -> False a #

type Rep (False a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep (False a) = D1 (MetaData "False" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "False" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))
type Rep1 False Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep1 False = D1 (MetaData "False" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "False" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data True a Source #

Constructors

True 

Fields

Instances
Functor True Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fmap :: (a -> b) -> True a -> True b #

(<$) :: a -> True b -> True a #

Foldable True Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fold :: Monoid m => True m -> m #

foldMap :: Monoid m => (a -> m) -> True a -> m #

foldr :: (a -> b -> b) -> b -> True a -> b #

foldr' :: (a -> b -> b) -> b -> True a -> b #

foldl :: (b -> a -> b) -> b -> True a -> b #

foldl' :: (b -> a -> b) -> b -> True a -> b #

foldr1 :: (a -> a -> a) -> True a -> a #

foldl1 :: (a -> a -> a) -> True a -> a #

toList :: True a -> [a] #

null :: True a -> Bool #

length :: True a -> Int #

elem :: Eq a => a -> True a -> Bool #

maximum :: Ord a => True a -> a #

minimum :: Ord a => True a -> a #

sum :: Num a => True a -> a #

product :: Num a => True a -> a #

Traversable True Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

traverse :: Applicative f => (a -> f b) -> True a -> f (True b) #

sequenceA :: Applicative f => True (f a) -> f (True a) #

mapM :: Monad m => (a -> m b) -> True a -> m (True b) #

sequence :: Monad m => True (m a) -> m (True a) #

SymbolMatching True Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

symbolMatch :: Proxy True -> Node -> Bool

showFailure :: Proxy True -> Node -> String

Unmarshal True Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

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

Eq a => Eq (True a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

(==) :: True a -> True a -> Bool #

(/=) :: True a -> True a -> Bool #

Ord a => Ord (True a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

compare :: True a -> True a -> Ordering #

(<) :: True a -> True a -> Bool #

(<=) :: True a -> True a -> Bool #

(>) :: True a -> True a -> Bool #

(>=) :: True a -> True a -> Bool #

max :: True a -> True a -> True a #

min :: True a -> True a -> True a #

Show a => Show (True a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

showsPrec :: Int -> True a -> ShowS #

show :: True a -> String #

showList :: [True a] -> ShowS #

Generic (True a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep (True a) :: Type -> Type #

Methods

from :: True a -> Rep (True a) x #

to :: Rep (True a) x -> True a #

Generic1 True Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep1 True :: k -> Type #

Methods

from1 :: True a -> Rep1 True a #

to1 :: Rep1 True a -> True a #

type Rep (True a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep (True a) = D1 (MetaData "True" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "True" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))
type Rep1 True Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep1 True = D1 (MetaData "True" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "True" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Number a Source #

Constructors

Number 

Fields

Instances
Functor Number Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fmap :: (a -> b) -> Number a -> Number b #

(<$) :: a -> Number b -> Number a #

Foldable Number Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fold :: Monoid m => Number m -> m #

foldMap :: Monoid m => (a -> m) -> Number a -> m #

foldr :: (a -> b -> b) -> b -> Number a -> b #

foldr' :: (a -> b -> b) -> b -> Number a -> b #

foldl :: (b -> a -> b) -> b -> Number a -> b #

foldl' :: (b -> a -> b) -> b -> Number a -> b #

foldr1 :: (a -> a -> a) -> Number a -> a #

foldl1 :: (a -> a -> a) -> Number a -> a #

toList :: Number a -> [a] #

null :: Number a -> Bool #

length :: Number a -> Int #

elem :: Eq a => a -> Number a -> Bool #

maximum :: Ord a => Number a -> a #

minimum :: Ord a => Number a -> a #

sum :: Num a => Number a -> a #

product :: Num a => Number a -> a #

Traversable Number Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

traverse :: Applicative f => (a -> f b) -> Number a -> f (Number b) #

sequenceA :: Applicative f => Number (f a) -> f (Number a) #

mapM :: Monad m => (a -> m b) -> Number a -> m (Number b) #

sequence :: Monad m => Number (m a) -> m (Number a) #

SymbolMatching Number Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

symbolMatch :: Proxy Number -> Node -> Bool

showFailure :: Proxy Number -> Node -> String

Unmarshal Number Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

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

Eq a => Eq (Number a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

(==) :: Number a -> Number a -> Bool #

(/=) :: Number a -> Number a -> Bool #

Ord a => Ord (Number a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

compare :: Number a -> Number a -> Ordering #

(<) :: Number a -> Number a -> Bool #

(<=) :: Number a -> Number a -> Bool #

(>) :: Number a -> Number a -> Bool #

(>=) :: Number a -> Number a -> Bool #

max :: Number a -> Number a -> Number a #

min :: Number a -> Number a -> Number a #

Show a => Show (Number a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

showsPrec :: Int -> Number a -> ShowS #

show :: Number a -> String #

showList :: [Number a] -> ShowS #

Generic (Number a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep (Number a) :: Type -> Type #

Methods

from :: Number a -> Rep (Number a) x #

to :: Rep (Number a) x -> Number a #

Generic1 Number Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep1 Number :: k -> Type #

Methods

from1 :: Number a -> Rep1 Number a #

to1 :: Rep1 Number a -> Number a #

type Rep (Number a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep (Number a) = D1 (MetaData "Number" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "Number" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))
type Rep1 Number Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep1 Number = D1 (MetaData "Number" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "Number" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data EscapeSequence a Source #

Constructors

EscapeSequence 

Fields

Instances
Functor EscapeSequence Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fmap :: (a -> b) -> EscapeSequence a -> EscapeSequence b #

(<$) :: a -> EscapeSequence b -> EscapeSequence a #

Foldable EscapeSequence Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fold :: Monoid m => EscapeSequence m -> m #

foldMap :: Monoid m => (a -> m) -> EscapeSequence a -> m #

foldr :: (a -> b -> b) -> b -> EscapeSequence a -> b #

foldr' :: (a -> b -> b) -> b -> EscapeSequence a -> b #

foldl :: (b -> a -> b) -> b -> EscapeSequence a -> b #

foldl' :: (b -> a -> b) -> b -> EscapeSequence a -> b #

foldr1 :: (a -> a -> a) -> EscapeSequence a -> a #

foldl1 :: (a -> a -> a) -> EscapeSequence a -> a #

toList :: EscapeSequence a -> [a] #

null :: EscapeSequence a -> Bool #

length :: EscapeSequence a -> Int #

elem :: Eq a => a -> EscapeSequence a -> Bool #

maximum :: Ord a => EscapeSequence a -> a #

minimum :: Ord a => EscapeSequence a -> a #

sum :: Num a => EscapeSequence a -> a #

product :: Num a => EscapeSequence a -> a #

Traversable EscapeSequence Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

traverse :: Applicative f => (a -> f b) -> EscapeSequence a -> f (EscapeSequence b) #

sequenceA :: Applicative f => EscapeSequence (f a) -> f (EscapeSequence a) #

mapM :: Monad m => (a -> m b) -> EscapeSequence a -> m (EscapeSequence b) #

sequence :: Monad m => EscapeSequence (m a) -> m (EscapeSequence a) #

SymbolMatching EscapeSequence Source # 
Instance details

Defined in TreeSitter.JSON.AST

Unmarshal EscapeSequence Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

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

Eq a => Eq (EscapeSequence a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Ord a => Ord (EscapeSequence a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Show a => Show (EscapeSequence a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Generic (EscapeSequence a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep (EscapeSequence a) :: Type -> Type #

Generic1 EscapeSequence Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep1 EscapeSequence :: k -> Type #

type Rep (EscapeSequence a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep (EscapeSequence a) = D1 (MetaData "EscapeSequence" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "EscapeSequence" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))
type Rep1 EscapeSequence Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep1 EscapeSequence = D1 (MetaData "EscapeSequence" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "EscapeSequence" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

type AnonymousDQuote = Token "\"" 7 Source #

type AnonymousRBracket = Token "]" 6 Source #

type AnonymousLBracket = Token "[" 5 Source #

type AnonymousColon = Token ":" 4 Source #

type AnonymousRBrace = Token "}" 3 Source #

type AnonymousComma = Token "," 2 Source #

type AnonymousLBrace = Token "{" 1 Source #

data String a Source #

Constructors

String 

Fields

Instances
Functor String Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fmap :: (a -> b) -> String a -> String b #

(<$) :: a -> String b -> String a #

Foldable String Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fold :: Monoid m => String m -> m #

foldMap :: Monoid m => (a -> m) -> String a -> m #

foldr :: (a -> b -> b) -> b -> String a -> b #

foldr' :: (a -> b -> b) -> b -> String a -> b #

foldl :: (b -> a -> b) -> b -> String a -> b #

foldl' :: (b -> a -> b) -> b -> String a -> b #

foldr1 :: (a -> a -> a) -> String a -> a #

foldl1 :: (a -> a -> a) -> String a -> a #

toList :: String a -> [a] #

null :: String a -> Bool #

length :: String a -> Int #

elem :: Eq a => a -> String a -> Bool #

maximum :: Ord a => String a -> a #

minimum :: Ord a => String a -> a #

sum :: Num a => String a -> a #

product :: Num a => String a -> a #

Traversable String Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

traverse :: Applicative f => (a -> f b) -> String a -> f (String b) #

sequenceA :: Applicative f => String (f a) -> f (String a) #

mapM :: Monad m => (a -> m b) -> String a -> m (String b) #

sequence :: Monad m => String (m a) -> m (String a) #

SymbolMatching String Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

symbolMatch :: Proxy String -> Node -> Bool

showFailure :: Proxy String -> Node -> String0

Unmarshal String Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

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

Eq a => Eq (String a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

(==) :: String a -> String a -> Bool #

(/=) :: String a -> String a -> Bool #

Ord a => Ord (String a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

compare :: String a -> String a -> Ordering #

(<) :: String a -> String a -> Bool #

(<=) :: String a -> String a -> Bool #

(>) :: String a -> String a -> Bool #

(>=) :: String a -> String a -> Bool #

max :: String a -> String a -> String a #

min :: String a -> String a -> String a #

Show a => Show (String a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

showsPrec :: Int -> String a -> ShowS #

show :: String a -> String0 #

showList :: [String a] -> ShowS #

Generic (String a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep (String a) :: Type -> Type #

Methods

from :: String a -> Rep (String a) x #

to :: Rep (String a) x -> String a #

Generic1 String Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep1 String :: k -> Type #

Methods

from1 :: String a -> Rep1 String a #

to1 :: Rep1 String a -> String a #

type Rep (String a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep (String a) = D1 (MetaData "String" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "String" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (StringContent a)))))
type Rep1 String Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep1 String = D1 (MetaData "String" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "String" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Maybe :.: Rec1 StringContent)))

data Pair a Source #

Constructors

Pair 

Fields

Instances
Functor Pair Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fmap :: (a -> b) -> Pair a -> Pair b #

(<$) :: a -> Pair b -> Pair a #

Foldable Pair Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fold :: Monoid m => Pair m -> m #

foldMap :: Monoid m => (a -> m) -> Pair a -> m #

foldr :: (a -> b -> b) -> b -> Pair a -> b #

foldr' :: (a -> b -> b) -> b -> Pair a -> b #

foldl :: (b -> a -> b) -> b -> Pair a -> b #

foldl' :: (b -> a -> b) -> b -> Pair a -> b #

foldr1 :: (a -> a -> a) -> Pair a -> a #

foldl1 :: (a -> a -> a) -> Pair a -> a #

toList :: Pair a -> [a] #

null :: Pair a -> Bool #

length :: Pair a -> Int #

elem :: Eq a => a -> Pair a -> Bool #

maximum :: Ord a => Pair a -> a #

minimum :: Ord a => Pair a -> a #

sum :: Num a => Pair a -> a #

product :: Num a => Pair a -> a #

Traversable Pair Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

traverse :: Applicative f => (a -> f b) -> Pair a -> f (Pair b) #

sequenceA :: Applicative f => Pair (f a) -> f (Pair a) #

mapM :: Monad m => (a -> m b) -> Pair a -> m (Pair b) #

sequence :: Monad m => Pair (m a) -> m (Pair a) #

SymbolMatching Pair Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

symbolMatch :: Proxy Pair -> Node -> Bool

showFailure :: Proxy Pair -> Node -> String

Unmarshal Pair Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

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

Eq a => Eq (Pair a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

(==) :: Pair a -> Pair a -> Bool #

(/=) :: Pair a -> Pair a -> Bool #

Ord a => Ord (Pair a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

compare :: Pair a -> Pair a -> Ordering #

(<) :: Pair a -> Pair a -> Bool #

(<=) :: Pair a -> Pair a -> Bool #

(>) :: Pair a -> Pair a -> Bool #

(>=) :: Pair a -> Pair a -> Bool #

max :: Pair a -> Pair a -> Pair a #

min :: Pair a -> Pair a -> Pair a #

Show a => Show (Pair a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

showsPrec :: Int -> Pair a -> ShowS #

show :: Pair a -> String #

showList :: [Pair a] -> ShowS #

Generic (Pair a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep (Pair a) :: Type -> Type #

Methods

from :: Pair a -> Rep (Pair a) x #

to :: Rep (Pair a) x -> Pair a #

Generic1 Pair Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep1 Pair :: k -> Type #

Methods

from1 :: Pair a -> Rep1 Pair a #

to1 :: Rep1 Pair a -> Pair a #

type Rep (Pair a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep1 Pair Source # 
Instance details

Defined in TreeSitter.JSON.AST

data Object a Source #

Constructors

Object 

Fields

Instances
Functor Object Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fmap :: (a -> b) -> Object a -> Object b #

(<$) :: a -> Object b -> Object a #

Foldable Object Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fold :: Monoid m => Object m -> m #

foldMap :: Monoid m => (a -> m) -> Object a -> m #

foldr :: (a -> b -> b) -> b -> Object a -> b #

foldr' :: (a -> b -> b) -> b -> Object a -> b #

foldl :: (b -> a -> b) -> b -> Object a -> b #

foldl' :: (b -> a -> b) -> b -> Object a -> b #

foldr1 :: (a -> a -> a) -> Object a -> a #

foldl1 :: (a -> a -> a) -> Object a -> a #

toList :: Object a -> [a] #

null :: Object a -> Bool #

length :: Object a -> Int #

elem :: Eq a => a -> Object a -> Bool #

maximum :: Ord a => Object a -> a #

minimum :: Ord a => Object a -> a #

sum :: Num a => Object a -> a #

product :: Num a => Object a -> a #

Traversable Object Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

traverse :: Applicative f => (a -> f b) -> Object a -> f (Object b) #

sequenceA :: Applicative f => Object (f a) -> f (Object a) #

mapM :: Monad m => (a -> m b) -> Object a -> m (Object b) #

sequence :: Monad m => Object (m a) -> m (Object a) #

SymbolMatching Object Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

symbolMatch :: Proxy Object -> Node -> Bool

showFailure :: Proxy Object -> Node -> String

Unmarshal Object Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

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

Eq a => Eq (Object a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

(==) :: Object a -> Object a -> Bool #

(/=) :: Object a -> Object a -> Bool #

Ord a => Ord (Object a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

compare :: Object a -> Object a -> Ordering #

(<) :: Object a -> Object a -> Bool #

(<=) :: Object a -> Object a -> Bool #

(>) :: Object a -> Object a -> Bool #

(>=) :: Object a -> Object a -> Bool #

max :: Object a -> Object a -> Object a #

min :: Object a -> Object a -> Object a #

Show a => Show (Object a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

showsPrec :: Int -> Object a -> ShowS #

show :: Object a -> String #

showList :: [Object a] -> ShowS #

Generic (Object a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep (Object a) :: Type -> Type #

Methods

from :: Object a -> Rep (Object a) x #

to :: Rep (Object a) x -> Object a #

Generic1 Object Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep1 Object :: k -> Type #

Methods

from1 :: Object a -> Rep1 Object a #

to1 :: Rep1 Object a -> Object a #

type Rep (Object a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep (Object a) = D1 (MetaData "Object" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "Object" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Pair a])))
type Rep1 Object Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep1 Object = D1 (MetaData "Object" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "Object" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 Pair)))

data Document a Source #

Constructors

Document 

Fields

Instances
Functor Document Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fmap :: (a -> b) -> Document a -> Document b #

(<$) :: a -> Document b -> Document a #

Foldable Document Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fold :: Monoid m => Document m -> m #

foldMap :: Monoid m => (a -> m) -> Document a -> m #

foldr :: (a -> b -> b) -> b -> Document a -> b #

foldr' :: (a -> b -> b) -> b -> Document a -> b #

foldl :: (b -> a -> b) -> b -> Document a -> b #

foldl' :: (b -> a -> b) -> b -> Document a -> b #

foldr1 :: (a -> a -> a) -> Document a -> a #

foldl1 :: (a -> a -> a) -> Document a -> a #

toList :: Document a -> [a] #

null :: Document a -> Bool #

length :: Document a -> Int #

elem :: Eq a => a -> Document a -> Bool #

maximum :: Ord a => Document a -> a #

minimum :: Ord a => Document a -> a #

sum :: Num a => Document a -> a #

product :: Num a => Document a -> a #

Traversable Document Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

traverse :: Applicative f => (a -> f b) -> Document a -> f (Document b) #

sequenceA :: Applicative f => Document (f a) -> f (Document a) #

mapM :: Monad m => (a -> m b) -> Document a -> m (Document b) #

sequence :: Monad m => Document (m a) -> m (Document a) #

SymbolMatching Document Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

symbolMatch :: Proxy Document -> Node -> Bool

showFailure :: Proxy Document -> Node -> String

Unmarshal Document Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

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

Eq a => Eq (Document a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

(==) :: Document a -> Document a -> Bool #

(/=) :: Document a -> Document a -> Bool #

Ord a => Ord (Document a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

compare :: Document a -> Document a -> Ordering #

(<) :: Document a -> Document a -> Bool #

(<=) :: Document a -> Document a -> Bool #

(>) :: Document a -> Document a -> Bool #

(>=) :: Document a -> Document a -> Bool #

max :: Document a -> Document a -> Document a #

min :: Document a -> Document a -> Document a #

Show a => Show (Document a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

showsPrec :: Int -> Document a -> ShowS #

show :: Document a -> String #

showList :: [Document a] -> ShowS #

Generic (Document a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep (Document a) :: Type -> Type #

Methods

from :: Document a -> Rep (Document a) x #

to :: Rep (Document a) x -> Document a #

Generic1 Document Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep1 Document :: k -> Type #

Methods

from1 :: Document a -> Rep1 Document a #

to1 :: Rep1 Document a -> Document a #

type Rep (Document a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep (Document a) = D1 (MetaData "Document" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "Document" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value a))))
type Rep1 Document Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep1 Document = D1 (MetaData "Document" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "Document" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 Value)))

data Array a Source #

Constructors

Array 

Fields

Instances
Functor Array Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fmap :: (a -> b) -> Array a -> Array b #

(<$) :: a -> Array b -> Array a #

Foldable Array Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fold :: Monoid m => Array m -> m #

foldMap :: Monoid m => (a -> m) -> Array a -> m #

foldr :: (a -> b -> b) -> b -> Array a -> b #

foldr' :: (a -> b -> b) -> b -> Array a -> b #

foldl :: (b -> a -> b) -> b -> Array a -> b #

foldl' :: (b -> a -> b) -> b -> Array a -> b #

foldr1 :: (a -> a -> a) -> Array a -> a #

foldl1 :: (a -> a -> a) -> Array a -> a #

toList :: Array a -> [a] #

null :: Array a -> Bool #

length :: Array a -> Int #

elem :: Eq a => a -> Array a -> Bool #

maximum :: Ord a => Array a -> a #

minimum :: Ord a => Array a -> a #

sum :: Num a => Array a -> a #

product :: Num a => Array a -> a #

Traversable Array Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

traverse :: Applicative f => (a -> f b) -> Array a -> f (Array b) #

sequenceA :: Applicative f => Array (f a) -> f (Array a) #

mapM :: Monad m => (a -> m b) -> Array a -> m (Array b) #

sequence :: Monad m => Array (m a) -> m (Array a) #

SymbolMatching Array Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

symbolMatch :: Proxy Array -> Node -> Bool

showFailure :: Proxy Array -> Node -> String

Unmarshal Array Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

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

Eq a => Eq (Array a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

(==) :: Array a -> Array a -> Bool #

(/=) :: Array a -> Array a -> Bool #

Ord a => Ord (Array a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

compare :: Array a -> Array a -> Ordering #

(<) :: Array a -> Array a -> Bool #

(<=) :: Array a -> Array a -> Bool #

(>) :: Array a -> Array a -> Bool #

(>=) :: Array a -> Array a -> Bool #

max :: Array a -> Array a -> Array a #

min :: Array a -> Array a -> Array a #

Show a => Show (Array a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

Generic (Array a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep (Array a) :: Type -> Type #

Methods

from :: Array a -> Rep (Array a) x #

to :: Rep (Array a) x -> Array a #

Generic1 Array Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep1 Array :: k -> Type #

Methods

from1 :: Array a -> Rep1 Array a #

to1 :: Rep1 Array a -> Array a #

type Rep (Array a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep (Array a) = D1 (MetaData "Array" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "Array" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Value a])))
type Rep1 Array Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep1 Array = D1 (MetaData "Array" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" False) (C1 (MetaCons "Array" PrefixI True) (S1 (MetaSel (Just "ann") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "extraChildren") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 Value)))

newtype Value a Source #

Instances
Functor Value Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fmap :: (a -> b) -> Value a -> Value b #

(<$) :: a -> Value b -> Value a #

Foldable Value Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

fold :: Monoid m => Value m -> m #

foldMap :: Monoid m => (a -> m) -> Value a -> m #

foldr :: (a -> b -> b) -> b -> Value a -> b #

foldr' :: (a -> b -> b) -> b -> Value a -> b #

foldl :: (b -> a -> b) -> b -> Value a -> b #

foldl' :: (b -> a -> b) -> b -> Value a -> b #

foldr1 :: (a -> a -> a) -> Value a -> a #

foldl1 :: (a -> a -> a) -> Value a -> a #

toList :: Value a -> [a] #

null :: Value a -> Bool #

length :: Value a -> Int #

elem :: Eq a => a -> Value a -> Bool #

maximum :: Ord a => Value a -> a #

minimum :: Ord a => Value a -> a #

sum :: Num a => Value a -> a #

product :: Num a => Value a -> a #

Traversable Value Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

traverse :: Applicative f => (a -> f b) -> Value a -> f (Value b) #

sequenceA :: Applicative f => Value (f a) -> f (Value a) #

mapM :: Monad m => (a -> m b) -> Value a -> m (Value b) #

sequence :: Monad m => Value (m a) -> m (Value a) #

SymbolMatching Value Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

symbolMatch :: Proxy Value -> Node -> Bool

showFailure :: Proxy Value -> Node -> String

Unmarshal Value Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

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

Eq a => Eq (Value a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

(==) :: Value a -> Value a -> Bool #

(/=) :: Value a -> Value a -> Bool #

Ord a => Ord (Value a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

compare :: Value a -> Value a -> Ordering #

(<) :: Value a -> Value a -> Bool #

(<=) :: Value a -> Value a -> Bool #

(>) :: Value a -> Value a -> Bool #

(>=) :: Value a -> Value a -> Bool #

max :: Value a -> Value a -> Value a #

min :: Value a -> Value a -> Value a #

Show a => Show (Value a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Methods

showsPrec :: Int -> Value a -> ShowS #

show :: Value a -> String #

showList :: [Value a] -> ShowS #

Generic (Value a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep (Value a) :: Type -> Type #

Methods

from :: Value a -> Rep (Value a) x #

to :: Rep (Value a) x -> Value a #

Generic1 Value Source # 
Instance details

Defined in TreeSitter.JSON.AST

Associated Types

type Rep1 Value :: k -> Type #

Methods

from1 :: Value a -> Rep1 Value a #

to1 :: Rep1 Value a -> Value a #

type Rep (Value a) Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep (Value a) = D1 (MetaData "Value" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" True) (C1 (MetaCons "Value" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (((Array :+: (False :+: Null)) :+: ((Number :+: Object) :+: (String :+: True))) a))))
type Rep1 Value Source # 
Instance details

Defined in TreeSitter.JSON.AST

type Rep1 Value = D1 (MetaData "Value" "TreeSitter.JSON.AST" "tree-sitter-json-0.4.0.0-inplace" True) (C1 (MetaCons "Value" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 ((Array :+: (False :+: Null)) :+: ((Number :+: Object) :+: (String :+: True))))))

data ((f :: k -> Type) :+: (g :: k -> Type)) (p :: k) :: forall k. (k -> Type) -> (k -> Type) -> k -> Type infixr 5 #

Sums: encode choice between constructors

Constructors

L1 (f p) 
R1 (g p) 
Instances
(GEffect m m' l l', GEffect m m' r r') => GEffect m m' (l :+: r) (l' :+: r') 
Instance details

Defined in Control.Effect.Carrier

Methods

ghandle :: (Functor f, Monad m) => f () -> (forall x. f (m x) -> m' (f x)) -> (l :+: r) a -> (l' :+: r') (f a)

(GHFunctor m m' l l', GHFunctor m m' r r') => GHFunctor m m' (l :+: r) (l' :+: r') 
Instance details

Defined in Control.Effect.Carrier

Methods

ghmap :: Functor m => (forall x. m x -> m' x) -> (l :+: r) a -> (l' :+: r') a

Generic1 (f :+: g :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (f :+: g) :: k -> Type #

Methods

from1 :: (f :+: g) a -> Rep1 (f :+: g) a #

to1 :: Rep1 (f :+: g) a -> (f :+: g) a #

(GSum arity a, GSum arity b) => GSum arity (a :+: b) 
Instance details

Defined in Data.Hashable.Generic.Instances

Methods

hashSum :: HashArgs arity a0 -> Int -> Int -> (a :+: b) a0 -> Int

(Functor f, Functor g) => Functor (f :+: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> (f :+: g) a -> (f :+: g) b #

(<$) :: a -> (f :+: g) b -> (f :+: g) a #

(Foldable f, Foldable g) => Foldable (f :+: g)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => (f :+: g) m -> m #

foldMap :: Monoid m => (a -> m) -> (f :+: g) a -> m #

foldr :: (a -> b -> b) -> b -> (f :+: g) a -> b #

foldr' :: (a -> b -> b) -> b -> (f :+: g) a -> b #

foldl :: (b -> a -> b) -> b -> (f :+: g) a -> b #

foldl' :: (b -> a -> b) -> b -> (f :+: g) a -> b #

foldr1 :: (a -> a -> a) -> (f :+: g) a -> a #

foldl1 :: (a -> a -> a) -> (f :+: g) a -> a #

toList :: (f :+: g) a -> [a] #

null :: (f :+: g) a -> Bool #

length :: (f :+: g) a -> Int #

elem :: Eq a => a -> (f :+: g) a -> Bool #

maximum :: Ord a => (f :+: g) a -> a #

minimum :: Ord a => (f :+: g) a -> a #

sum :: Num a => (f :+: g) a -> a #

product :: Num a => (f :+: g) a -> a #

(Traversable f, Traversable g) => Traversable (f :+: g)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> (f :+: g) a -> f0 ((f :+: g) b) #

sequenceA :: Applicative f0 => (f :+: g) (f0 a) -> f0 ((f :+: g) a) #

mapM :: Monad m => (a -> m b) -> (f :+: g) a -> m ((f :+: g) b) #

sequence :: Monad m => (f :+: g) (m a) -> m ((f :+: g) a) #

(SumSize a, SumSize b) => SumSize (a :+: b) 
Instance details

Defined in Data.Hashable.Generic.Instances

Methods

sumSize :: Tagged (a :+: b)

(GSumGet a, GSumGet b) => GSumGet (a :+: b) 
Instance details

Defined in Data.Binary.Generic

Methods

getSum :: (Ord word, Num word, Bits word) => word -> word -> Get ((a :+: b) a0)

(SumSize a, SumSize b) => SumSize (a :+: b) 
Instance details

Defined in Data.Binary.Generic

Methods

sumSize :: Tagged (a :+: b) Word64

(GSumPut a, GSumPut b) => GSumPut (a :+: b) 
Instance details

Defined in Data.Binary.Generic

Methods

putSum :: (Num w, Bits w, Binary w) => w -> w -> (a :+: b) a0 -> Put

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

Defined in TreeSitter.Unmarshal

Methods

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

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

(Unmarshal f, Unmarshal g, SymbolMatching f, SymbolMatching g) => Unmarshal (f :+: g) 
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)

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

Defined in TreeSitter.Unmarshal

Methods

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

(Eq (f p), Eq (g p)) => Eq ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: (f :+: g) p -> (f :+: g) p -> Bool #

(/=) :: (f :+: g) p -> (f :+: g) p -> Bool #

(Ord (f p), Ord (g p)) => Ord ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: (f :+: g) p -> (f :+: g) p -> Ordering #

(<) :: (f :+: g) p -> (f :+: g) p -> Bool #

(<=) :: (f :+: g) p -> (f :+: g) p -> Bool #

(>) :: (f :+: g) p -> (f :+: g) p -> Bool #

(>=) :: (f :+: g) p -> (f :+: g) p -> Bool #

max :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p #

min :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p #

(Read (f p), Read (g p)) => Read ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

readsPrec :: Int -> ReadS ((f :+: g) p) #

readList :: ReadS [(f :+: g) p] #

readPrec :: ReadPrec ((f :+: g) p) #

readListPrec :: ReadPrec [(f :+: g) p] #

(Show (f p), Show (g p)) => Show ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :+: g) p -> ShowS #

show :: (f :+: g) p -> String #

showList :: [(f :+: g) p] -> ShowS #

Generic ((f :+: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :+: g) p) :: Type -> Type #

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x #

to :: Rep ((f :+: g) p) x -> (f :+: g) p #

type Rep1 (f :+: g :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics