| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
TreeSitter.Ruby.AST
Documentation
debugSymbolNames :: [String] Source #
type AnonymousTilde = Token "~" 91 Source #
type AnonymousRBrace = Token "}" 6 Source #
type AnonymousPipePipeEqual = Token "||=" 57 Source #
type AnonymousPipePipe = Token "||" 71 Source #
type AnonymousPipeEqual = Token "|=" 58 Source #
type AnonymousPipe = Token "|" 14 Source #
type AnonymousLBrace = Token "{" 5 Source #
type AnonymousYield = Token "yield" 26 Source #
type AnonymousWhile = Token "while" 33 Source #
type AnonymousWhen = Token "when" 40 Source #
type AnonymousUntil = Token "until" 34 Source #
type AnonymousUnless = Token "unless" 32 Source #
data Uninterpreted a Source #
Constructors
| Uninterpreted | |
Instances
type AnonymousUndef = Token "undef" 98 Source #
Instances
| Functor True Source # | |
| Foldable True Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => True m -> m # foldMap :: Monoid m => (a -> m) -> True a -> 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 # elem :: Eq a => a -> True a -> Bool # maximum :: Ord a => True a -> a # | |
| Traversable True Source # | |
| SymbolMatching True Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal True Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (True a) | |
| Eq a => Eq (True a) Source # | |
| Ord a => Ord (True a) Source # | |
| Show a => Show (True a) Source # | |
| Generic (True a) Source # | |
| Generic1 True Source # | |
| type Rep (True a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (True a) = D1 ('MetaData "True" "TreeSitter.Ruby.AST" "tree-sitter-ruby-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 # | |
Defined in TreeSitter.Ruby.AST type Rep1 True = D1 ('MetaData "True" "TreeSitter.Ruby.AST" "tree-sitter-ruby-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))) | |
type AnonymousThen = Token "then" 43 Source #
Instances
| Functor Super Source # | |
| Foldable Super Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Super m -> m # foldMap :: Monoid m => (a -> m) -> Super a -> m # foldMap' :: Monoid m => (a -> m) -> Super a -> m # foldr :: (a -> b -> b) -> b -> Super a -> b # foldr' :: (a -> b -> b) -> b -> Super a -> b # foldl :: (b -> a -> b) -> b -> Super a -> b # foldl' :: (b -> a -> b) -> b -> Super a -> b # foldr1 :: (a -> a -> a) -> Super a -> a # foldl1 :: (a -> a -> a) -> Super a -> a # elem :: Eq a => a -> Super a -> Bool # maximum :: Ord a => Super a -> a # minimum :: Ord a => Super a -> a # | |
| Traversable Super Source # | |
| SymbolMatching Super Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Super Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Super a) | |
| Eq a => Eq (Super a) Source # | |
| Ord a => Ord (Super a) Source # | |
| Show a => Show (Super a) Source # | |
| Generic (Super a) Source # | |
| Generic1 Super Source # | |
| type Rep (Super a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Super a) = D1 ('MetaData "Super" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Super" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
| type Rep1 Super Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Super = D1 ('MetaData "Super" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Super" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
Instances
| Functor Self Source # | |
| Foldable Self Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Self m -> m # foldMap :: Monoid m => (a -> m) -> Self a -> m # foldMap' :: Monoid m => (a -> m) -> Self a -> m # foldr :: (a -> b -> b) -> b -> Self a -> b # foldr' :: (a -> b -> b) -> b -> Self a -> b # foldl :: (b -> a -> b) -> b -> Self a -> b # foldl' :: (b -> a -> b) -> b -> Self a -> b # foldr1 :: (a -> a -> a) -> Self a -> a # foldl1 :: (a -> a -> a) -> Self a -> a # elem :: Eq a => a -> Self a -> Bool # maximum :: Ord a => Self a -> a # | |
| Traversable Self Source # | |
| SymbolMatching Self Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Self Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Self a) | |
| Eq a => Eq (Self a) Source # | |
| Ord a => Ord (Self a) Source # | |
| Show a => Show (Self a) Source # | |
| Generic (Self a) Source # | |
| Generic1 Self Source # | |
| type Rep (Self a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Self a) = D1 ('MetaData "Self" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Self" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
| type Rep1 Self Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Self = D1 ('MetaData "Self" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Self" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
type AnonymousReturn = Token "return" 25 Source #
type AnonymousRetry = Token "retry" 30 Source #
type AnonymousRescue = Token "rescue" 35 Source #
type AnonymousRedo = Token "redo" 29 Source #
type AnonymousR = Token "r" 104 Source #
type AnonymousOr = Token "or" 70 Source #
type AnonymousNot = Token "not" 89 Source #
Instances
| Functor Nil Source # | |
| Foldable Nil Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Nil m -> m # foldMap :: Monoid m => (a -> m) -> Nil a -> m # foldMap' :: Monoid m => (a -> m) -> Nil a -> m # foldr :: (a -> b -> b) -> b -> Nil a -> b # foldr' :: (a -> b -> b) -> b -> Nil a -> b # foldl :: (b -> a -> b) -> b -> Nil a -> b # foldl' :: (b -> a -> b) -> b -> Nil a -> b # foldr1 :: (a -> a -> a) -> Nil a -> a # foldl1 :: (a -> a -> a) -> Nil a -> a # elem :: Eq a => a -> Nil a -> Bool # maximum :: Ord a => Nil a -> a # | |
| Traversable Nil Source # | |
| SymbolMatching Nil Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Nil Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Nil a) | |
| Eq a => Eq (Nil a) Source # | |
| Ord a => Ord (Nil a) Source # | |
| Show a => Show (Nil a) Source # | |
| Generic (Nil a) Source # | |
| Generic1 Nil Source # | |
| type Rep (Nil a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Nil a) = D1 ('MetaData "Nil" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Nil" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
| type Rep1 Nil Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Nil = D1 ('MetaData "Nil" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Nil" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
type AnonymousNext = Token "next" 28 Source #
type AnonymousModule = Token "module" 23 Source #
Instances
| Functor Integer Source # | |
| Foldable Integer Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Integer m -> m # foldMap :: Monoid m => (a -> m) -> Integer a -> m # foldMap' :: Monoid m => (a -> m) -> Integer a -> m # foldr :: (a -> b -> b) -> b -> Integer a -> b # foldr' :: (a -> b -> b) -> b -> Integer a -> b # foldl :: (b -> a -> b) -> b -> Integer a -> b # foldl' :: (b -> a -> b) -> b -> Integer a -> b # foldr1 :: (a -> a -> a) -> Integer a -> a # foldl1 :: (a -> a -> a) -> Integer a -> a # elem :: Eq a => a -> Integer a -> Bool # maximum :: Ord a => Integer a -> a # minimum :: Ord a => Integer a -> a # | |
| Traversable Integer Source # | |
| SymbolMatching Integer Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Integer Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Integer a) | |
| Eq a => Eq (Integer a) Source # | |
| Ord a => Ord (Integer a) Source # | |
| Show a => Show (Integer a) Source # | |
| Generic (Integer a) Source # | |
| Generic1 Integer Source # | |
| type Rep (Integer a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Integer a) = D1 ('MetaData "Integer" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Integer" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
| type Rep1 Integer Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Integer = D1 ('MetaData "Integer" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Integer" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
data InstanceVariable a Source #
Constructors
| InstanceVariable | |
Instances
type AnonymousIn = Token "in" 37 Source #
type AnonymousIf = Token "if" 31 Source #
data Identifier a Source #
Constructors
| Identifier | |
Instances
data HeredocEnd a Source #
Constructors
| HeredocEnd | |
Instances
data HeredocBeginning a Source #
Constructors
| HeredocBeginning | |
Instances
data GlobalVariable a Source #
Constructors
| GlobalVariable | |
Instances
type AnonymousFor = Token "for" 36 Source #
Instances
| Functor Float Source # | |
| Foldable Float Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Float m -> m # foldMap :: Monoid m => (a -> m) -> Float a -> m # foldMap' :: Monoid m => (a -> m) -> Float a -> m # foldr :: (a -> b -> b) -> b -> Float a -> b # foldr' :: (a -> b -> b) -> b -> Float a -> b # foldl :: (b -> a -> b) -> b -> Float a -> b # foldl' :: (b -> a -> b) -> b -> Float a -> b # foldr1 :: (a -> a -> a) -> Float a -> a # foldl1 :: (a -> a -> a) -> Float a -> a # elem :: Eq a => a -> Float a -> Bool # maximum :: Ord a => Float a -> a # minimum :: Ord a => Float a -> a # | |
| Traversable Float Source # | |
| SymbolMatching Float Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Float Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Float a) | |
| Eq a => Eq (Float a) Source # | |
| Ord a => Ord (Float a) Source # | |
| Show a => Show (Float a) Source # | |
| Generic (Float a) Source # | |
| Generic1 Float Source # | |
| type Rep (Float a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Float a) = D1 ('MetaData "Float" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Float" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
| type Rep1 Float Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Float = D1 ('MetaData "Float" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Float" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
Instances
| Functor False Source # | |
| Foldable False Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => False m -> m # foldMap :: Monoid m => (a -> m) -> False a -> 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 # elem :: Eq a => a -> False a -> Bool # maximum :: Ord a => False a -> a # minimum :: Ord a => False a -> a # | |
| Traversable False Source # | |
| SymbolMatching False Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal False Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (False a) | |
| Eq a => Eq (False a) Source # | |
| Ord a => Ord (False a) Source # | |
| Show a => Show (False a) Source # | |
| Generic (False a) Source # | |
| Generic1 False Source # | |
| type Rep (False a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (False a) = D1 ('MetaData "False" "TreeSitter.Ruby.AST" "tree-sitter-ruby-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 # | |
Defined in TreeSitter.Ruby.AST type Rep1 False = D1 ('MetaData "False" "TreeSitter.Ruby.AST" "tree-sitter-ruby-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 EscapeSequence a Source #
Constructors
| EscapeSequence | |
Instances
type AnonymousEnsure = Token "ensure" 45 Source #
type AnonymousEnd = Token "end" 24 Source #
type AnonymousElsif = Token "elsif" 41 Source #
type AnonymousElse = Token "else" 42 Source #
type AnonymousDo = Token "do" 38 Source #
type AnonymousDefinedQuestion = Token "defined?" 88 Source #
type AnonymousDef = Token "def" 8 Source #
Instances
Instances
| Functor Complex Source # | |
| Foldable Complex Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Complex m -> m # foldMap :: Monoid m => (a -> m) -> Complex a -> m # foldMap' :: Monoid m => (a -> m) -> Complex a -> m # foldr :: (a -> b -> b) -> b -> Complex a -> b # foldr' :: (a -> b -> b) -> b -> Complex a -> b # foldl :: (b -> a -> b) -> b -> Complex a -> b # foldl' :: (b -> a -> b) -> b -> Complex a -> b # foldr1 :: (a -> a -> a) -> Complex a -> a # foldl1 :: (a -> a -> a) -> Complex a -> a # elem :: Eq a => a -> Complex a -> Bool # maximum :: Ord a => Complex a -> a # minimum :: Ord a => Complex a -> a # | |
| Traversable Complex Source # | |
| SymbolMatching Complex Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Complex Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Complex a) | |
| Eq a => Eq (Complex a) Source # | |
| Ord a => Ord (Complex a) Source # | |
| Show a => Show (Complex a) Source # | |
| Generic (Complex a) Source # | |
| Generic1 Complex Source # | |
| type Rep (Complex a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Complex a) = D1 ('MetaData "Complex" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Complex" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
| type Rep1 Complex Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Complex = D1 ('MetaData "Complex" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Complex" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
data ClassVariable a Source #
Constructors
| ClassVariable | |
Instances
type AnonymousClass = Token "class" 21 Source #
Instances
type AnonymousCase = Token "case" 39 Source #
type AnonymousBreak = Token "break" 27 Source #
type AnonymousBegin = Token "begin" 44 Source #
type AnonymousAnd = Token "and" 69 Source #
type AnonymousAlias = Token "alias" 99 Source #
type AnonymousBacktick = Token "`" 97 Source #
type AnonymousUnderscoreENDUnderscore = Token "__END__" 2 Source #
type AnonymousCaretEqual = Token "^=" 64 Source #
type AnonymousCaret = Token "^" 78 Source #
type AnonymousRBracket = Token "]" 48 Source #
type AnonymousLBracketRBracketEqual = Token "[]=" 96 Source #
type AnonymousLBracketRBracket = Token "[]" 95 Source #
type AnonymousLBracket = Token "[" 47 Source #
type AnonymousEND = Token "END" 7 Source #
type AnonymousBEGIN = Token "BEGIN" 4 Source #
type AnonymousQuestion = Token "?" 65 Source #
type AnonymousRAngleRAngleEqual = Token ">>=" 62 Source #
type AnonymousRAngleRAngle = Token ">>" 74 Source #
type AnonymousRAngleEqual = Token ">=" 77 Source #
type AnonymousRAngle = Token ">" 76 Source #
type AnonymousEqualTilde = Token "=~" 86 Source #
type AnonymousEqualRAngle = Token "=>" 46 Source #
type AnonymousEqualEqualEqual = Token "===" 84 Source #
type AnonymousEqualEqual = Token "==" 82 Source #
type AnonymousEqual = Token "=" 20 Source #
type AnonymousLAngleEqualRAngle = Token "<=>" 85 Source #
type AnonymousLAngleEqual = Token "<=" 75 Source #
type AnonymousLAngleLAngleEqual = Token "<<=" 63 Source #
type AnonymousLAngleLAngle = Token "<<" 73 Source #
type AnonymousLAngle = Token "<" 22 Source #
type AnonymousSemicolon = Token ";" 15 Source #
type AnonymousColonColon = Token "::" 12 Source #
type AnonymousColonDQuote = Token ":\"" 123 Source #
type AnonymousColon = Token ":" 19 Source #
type AnonymousSlashEqual = Token "/=" 56 Source #
type AnonymousSlash = Token "/" 80 Source #
type AnonymousDotDotDot = Token "..." 68 Source #
type AnonymousDotDot = Token ".." 67 Source #
type AnonymousDot = Token "." 11 Source #
type AnonymousMinusAt = Token "-@" 94 Source #
type AnonymousMinusRAngle = Token "->" 119 Source #
type AnonymousMinusEqual = Token "-=" 53 Source #
type AnonymousMinus = Token "-" 92 Source #
type AnonymousComma = Token "," 13 Source #
type AnonymousPlusAt = Token "+@" 93 Source #
type AnonymousPlusEqual = Token "+=" 52 Source #
type AnonymousPlus = Token "+" 79 Source #
type AnonymousStarEqual = Token "*=" 54 Source #
type AnonymousStarStarEqual = Token "**=" 55 Source #
type AnonymousStarStar = Token "**" 17 Source #
type AnonymousStar = Token "*" 16 Source #
type AnonymousRParen = Token ")" 10 Source #
type AnonymousLParen = Token "(" 9 Source #
type AnonymousAmpersandEqual = Token "&=" 60 Source #
type AnonymousAmpersandDot = Token "&." 50 Source #
type AnonymousAmpersandAmpersandEqual = Token "&&=" 59 Source #
type AnonymousAmpersandAmpersand = Token "&&" 72 Source #
type AnonymousAmpersand = Token "&" 18 Source #
type AnonymousPercentwLParen = Token "%w(" 126 Source #
type AnonymousPercentiLParen = Token "%i(" 127 Source #
type AnonymousPercentEqual = Token "%=" 61 Source #
type AnonymousPercent = Token "%" 81 Source #
type AnonymousHashLBrace = Token "#{" 115 Source #
type AnonymousDQuote = Token "\"" 122 Source #
type AnonymousBangTilde = Token "!~" 87 Source #
type AnonymousBangEqual = Token "!=" 83 Source #
type AnonymousBang = Token "!" 90 Source #
Constructors
| Yield | |
Fields
| |
Instances
| Functor Yield Source # | |
| Foldable Yield Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Yield m -> m # foldMap :: Monoid m => (a -> m) -> Yield a -> m # foldMap' :: Monoid m => (a -> m) -> Yield a -> m # foldr :: (a -> b -> b) -> b -> Yield a -> b # foldr' :: (a -> b -> b) -> b -> Yield a -> b # foldl :: (b -> a -> b) -> b -> Yield a -> b # foldl' :: (b -> a -> b) -> b -> Yield a -> b # foldr1 :: (a -> a -> a) -> Yield a -> a # foldl1 :: (a -> a -> a) -> Yield a -> a # elem :: Eq a => a -> Yield a -> Bool # maximum :: Ord a => Yield a -> a # minimum :: Ord a => Yield a -> a # | |
| Traversable Yield Source # | |
| SymbolMatching Yield Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Yield Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Yield a) | |
| Eq a => Eq (Yield a) Source # | |
| Ord a => Ord (Yield a) Source # | |
| Show a => Show (Yield a) Source # | |
| Generic (Yield a) Source # | |
| Generic1 Yield Source # | |
| type Rep (Yield a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Yield a) = D1 ('MetaData "Yield" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Yield" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ArgumentList a))))) | |
| type Rep1 Yield Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Yield = D1 ('MetaData "Yield" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Yield" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ArgumentList))) | |
data WhileModifier a Source #
Constructors
| WhileModifier | |
Instances
Instances
Constructors
| When | |
Instances
data UntilModifier a Source #
Constructors
| UntilModifier | |
Instances
Instances
data UnlessModifier a Source #
Constructors
| UnlessModifier | |
Instances
Constructors
| Unless | |
Instances
Constructors
| Undef | |
Fields
| |
Instances
| Functor Undef Source # | |
| Foldable Undef Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Undef m -> m # foldMap :: Monoid m => (a -> m) -> Undef a -> m # foldMap' :: Monoid m => (a -> m) -> Undef a -> m # foldr :: (a -> b -> b) -> b -> Undef a -> b # foldr' :: (a -> b -> b) -> b -> Undef a -> b # foldl :: (b -> a -> b) -> b -> Undef a -> b # foldl' :: (b -> a -> b) -> b -> Undef a -> b # foldr1 :: (a -> a -> a) -> Undef a -> a # foldl1 :: (a -> a -> a) -> Undef a -> a # elem :: Eq a => a -> Undef a -> Bool # maximum :: Ord a => Undef a -> a # minimum :: Ord a => Undef a -> a # | |
| Traversable Undef Source # | |
| SymbolMatching Undef Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Undef Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Undef a) | |
| Eq a => Eq (Undef a) Source # | |
| Ord a => Ord (Undef a) Source # | |
| Show a => Show (Undef a) Source # | |
| Generic (Undef a) Source # | |
| Generic1 Undef Source # | |
| type Rep (Undef a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Undef a) = D1 ('MetaData "Undef" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Undef" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (MethodName a))))) | |
| type Rep1 Undef Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Undef = D1 ('MetaData "Undef" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Undef" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (NonEmpty :.: Rec1 MethodName))) | |
Constructors
| Unary | |
Fields
| |
Instances
| Functor Unary Source # | |
| Foldable Unary Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Unary m -> m # foldMap :: Monoid m => (a -> m) -> Unary a -> m # foldMap' :: Monoid m => (a -> m) -> Unary a -> m # foldr :: (a -> b -> b) -> b -> Unary a -> b # foldr' :: (a -> b -> b) -> b -> Unary a -> b # foldl :: (b -> a -> b) -> b -> Unary a -> b # foldl' :: (b -> a -> b) -> b -> Unary a -> b # foldr1 :: (a -> a -> a) -> Unary a -> a # foldl1 :: (a -> a -> a) -> Unary a -> a # elem :: Eq a => a -> Unary a -> Bool # maximum :: Ord a => Unary a -> a # minimum :: Ord a => Unary a -> a # | |
| Traversable Unary Source # | |
| SymbolMatching Unary Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Unary Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Unary a) | |
| Eq a => Eq (Unary a) Source # | |
| Ord a => Ord (Unary a) Source # | |
| Show a => Show (Unary a) Source # | |
| Generic (Unary a) Source # | |
| Generic1 Unary Source # | |
| type Rep (Unary a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Unary a) = D1 ('MetaData "Unary" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Unary" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (((Arg :+: Float) :+: (Integer :+: ParenthesizedStatements)) a)))) | |
| type Rep1 Unary Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Unary = D1 ('MetaData "Unary" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Unary" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 ((Arg :+: Float) :+: (Integer :+: ParenthesizedStatements))))) | |
Constructors
| Then | |
Fields
| |
Instances
| Functor Then Source # | |
| Foldable Then Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Then m -> m # foldMap :: Monoid m => (a -> m) -> Then a -> m # foldMap' :: Monoid m => (a -> m) -> Then a -> m # foldr :: (a -> b -> b) -> b -> Then a -> b # foldr' :: (a -> b -> b) -> b -> Then a -> b # foldl :: (b -> a -> b) -> b -> Then a -> b # foldl' :: (b -> a -> b) -> b -> Then a -> b # foldr1 :: (a -> a -> a) -> Then a -> a # foldl1 :: (a -> a -> a) -> Then a -> a # elem :: Eq a => a -> Then a -> Bool # maximum :: Ord a => Then a -> a # | |
| Traversable Then Source # | |
| SymbolMatching Then Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Then Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Then a) | |
| Eq a => Eq (Then a) Source # | |
| Ord a => Ord (Then a) Source # | |
| Show a => Show (Then a) Source # | |
| Generic (Then a) Source # | |
| Generic1 Then Source # | |
| type Rep (Then a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Then a) = D1 ('MetaData "Then" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Then" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Statement :+: EmptyStatement) a]))) | |
| type Rep1 Then Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Then = D1 ('MetaData "Then" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Then" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 (Statement :+: EmptyStatement)))) | |
data SymbolArray a Source #
Constructors
| SymbolArray | |
Fields
| |
Instances
Constructors
| Symbol | |
Fields
| |
Instances
| Functor Symbol Source # | |
| Foldable Symbol Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Symbol m -> m # foldMap :: Monoid m => (a -> m) -> Symbol a -> m # foldMap' :: Monoid m => (a -> m) -> Symbol a -> m # foldr :: (a -> b -> b) -> b -> Symbol a -> b # foldr' :: (a -> b -> b) -> b -> Symbol a -> b # foldl :: (b -> a -> b) -> b -> Symbol a -> b # foldl' :: (b -> a -> b) -> b -> Symbol a -> b # foldr1 :: (a -> a -> a) -> Symbol a -> a # foldl1 :: (a -> a -> a) -> Symbol a -> a # elem :: Eq a => a -> Symbol a -> Bool # maximum :: Ord a => Symbol a -> a # minimum :: Ord a => Symbol a -> a # | |
| Traversable Symbol Source # | |
| SymbolMatching Symbol Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Symbol Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Symbol a) | |
| Eq a => Eq (Symbol a) Source # | |
| Ord a => Ord (Symbol a) Source # | |
Defined in TreeSitter.Ruby.AST | |
| Show a => Show (Symbol a) Source # | |
| Generic (Symbol a) Source # | |
| Generic1 Symbol Source # | |
| type Rep (Symbol a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Symbol a) = D1 ('MetaData "Symbol" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Symbol" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(EscapeSequence :+: Interpolation) a]))) | |
| type Rep1 Symbol Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Symbol = D1 ('MetaData "Symbol" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Symbol" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 (EscapeSequence :+: Interpolation)))) | |
data Superclass a Source #
Constructors
| Superclass | |
Fields
| |
Instances
Constructors
| Subshell | |
Fields
| |
Instances
data StringArray a Source #
Constructors
| StringArray | |
Fields
| |
Instances
Constructors
| String | |
Fields
| |
Instances
| Functor String Source # | |
| Foldable String Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => String m -> m # foldMap :: Monoid m => (a -> m) -> String a -> 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 # elem :: Eq a => a -> String a -> Bool # maximum :: Ord a => String a -> a # minimum :: Ord a => String a -> a # | |
| Traversable String Source # | |
| SymbolMatching String Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal String Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (String a) | |
| Eq a => Eq (String a) Source # | |
| Ord a => Ord (String a) Source # | |
Defined in TreeSitter.Ruby.AST | |
| Show a => Show (String a) Source # | |
| Generic (String a) Source # | |
| Generic1 String Source # | |
| type Rep (String a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (String a) = D1 ('MetaData "String" "TreeSitter.Ruby.AST" "tree-sitter-ruby-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 [(EscapeSequence :+: Interpolation) a]))) | |
| type Rep1 String Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 String = D1 ('MetaData "String" "TreeSitter.Ruby.AST" "tree-sitter-ruby-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) ([] :.: Rec1 (EscapeSequence :+: Interpolation)))) | |
data SplatParameter a Source #
Constructors
| SplatParameter | |
Fields
| |
Instances
data SplatArgument a Source #
Constructors
| SplatArgument | |
Fields
| |
Instances
data SingletonMethod a Source #
Constructors
| SingletonMethod | |
Fields
| |
Instances
data SingletonClass a Source #
Constructors
| SingletonClass | |
Instances
Constructors
| Setter | |
Fields
| |
Instances
| Functor Setter Source # | |
| Foldable Setter Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Setter m -> m # foldMap :: Monoid m => (a -> m) -> Setter a -> m # foldMap' :: Monoid m => (a -> m) -> Setter a -> m # foldr :: (a -> b -> b) -> b -> Setter a -> b # foldr' :: (a -> b -> b) -> b -> Setter a -> b # foldl :: (b -> a -> b) -> b -> Setter a -> b # foldl' :: (b -> a -> b) -> b -> Setter a -> b # foldr1 :: (a -> a -> a) -> Setter a -> a # foldl1 :: (a -> a -> a) -> Setter a -> a # elem :: Eq a => a -> Setter a -> Bool # maximum :: Ord a => Setter a -> a # minimum :: Ord a => Setter a -> a # | |
| Traversable Setter Source # | |
| SymbolMatching Setter Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Setter Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Setter a) | |
| Eq a => Eq (Setter a) Source # | |
| Ord a => Ord (Setter a) Source # | |
Defined in TreeSitter.Ruby.AST | |
| Show a => Show (Setter a) Source # | |
| Generic (Setter a) Source # | |
| Generic1 Setter Source # | |
| type Rep (Setter a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Setter a) = D1 ('MetaData "Setter" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Setter" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Identifier a)))) | |
| type Rep1 Setter Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Setter = D1 ('MetaData "Setter" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Setter" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Identifier))) | |
data ScopeResolution a Source #
Constructors
| ScopeResolution | |
Instances
data RightAssignmentList a Source #
Constructors
| RightAssignmentList | |
Fields
| |
Instances
Constructors
| Return | |
Fields
| |
Instances
| Functor Return Source # | |
| Foldable Return Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Return m -> m # foldMap :: Monoid m => (a -> m) -> Return a -> m # foldMap' :: Monoid m => (a -> m) -> Return a -> m # foldr :: (a -> b -> b) -> b -> Return a -> b # foldr' :: (a -> b -> b) -> b -> Return a -> b # foldl :: (b -> a -> b) -> b -> Return a -> b # foldl' :: (b -> a -> b) -> b -> Return a -> b # foldr1 :: (a -> a -> a) -> Return a -> a # foldl1 :: (a -> a -> a) -> Return a -> a # elem :: Eq a => a -> Return a -> Bool # maximum :: Ord a => Return a -> a # minimum :: Ord a => Return a -> a # | |
| Traversable Return Source # | |
| SymbolMatching Return Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Return Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Return a) | |
| Eq a => Eq (Return a) Source # | |
| Ord a => Ord (Return a) Source # | |
Defined in TreeSitter.Ruby.AST | |
| Show a => Show (Return a) Source # | |
| Generic (Return a) Source # | |
| Generic1 Return Source # | |
| type Rep (Return a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Return a) = D1 ('MetaData "Return" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Return" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ArgumentList a))))) | |
| type Rep1 Return Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Return = D1 ('MetaData "Return" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Return" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ArgumentList))) | |
Constructors
| Retry | |
Fields
| |
Instances
| Functor Retry Source # | |
| Foldable Retry Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Retry m -> m # foldMap :: Monoid m => (a -> m) -> Retry a -> m # foldMap' :: Monoid m => (a -> m) -> Retry a -> m # foldr :: (a -> b -> b) -> b -> Retry a -> b # foldr' :: (a -> b -> b) -> b -> Retry a -> b # foldl :: (b -> a -> b) -> b -> Retry a -> b # foldl' :: (b -> a -> b) -> b -> Retry a -> b # foldr1 :: (a -> a -> a) -> Retry a -> a # foldl1 :: (a -> a -> a) -> Retry a -> a # elem :: Eq a => a -> Retry a -> Bool # maximum :: Ord a => Retry a -> a # minimum :: Ord a => Retry a -> a # | |
| Traversable Retry Source # | |
| SymbolMatching Retry Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Retry Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Retry a) | |
| Eq a => Eq (Retry a) Source # | |
| Ord a => Ord (Retry a) Source # | |
| Show a => Show (Retry a) Source # | |
| Generic (Retry a) Source # | |
| Generic1 Retry Source # | |
| type Rep (Retry a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Retry a) = D1 ('MetaData "Retry" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Retry" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ArgumentList a))))) | |
| type Rep1 Retry Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Retry = D1 ('MetaData "Retry" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Retry" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ArgumentList))) | |
data RestAssignment a Source #
Constructors
| RestAssignment | |
Fields
| |
Instances
data RescueModifier a Source #
Constructors
| RescueModifier | |
Instances
Constructors
| Rescue | |
Fields
| |
Instances
Constructors
| Regex | |
Fields
| |
Instances
| Functor Regex Source # | |
| Foldable Regex Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Regex m -> m # foldMap :: Monoid m => (a -> m) -> Regex a -> m # foldMap' :: Monoid m => (a -> m) -> Regex a -> m # foldr :: (a -> b -> b) -> b -> Regex a -> b # foldr' :: (a -> b -> b) -> b -> Regex a -> b # foldl :: (b -> a -> b) -> b -> Regex a -> b # foldl' :: (b -> a -> b) -> b -> Regex a -> b # foldr1 :: (a -> a -> a) -> Regex a -> a # foldl1 :: (a -> a -> a) -> Regex a -> a # elem :: Eq a => a -> Regex a -> Bool # maximum :: Ord a => Regex a -> a # minimum :: Ord a => Regex a -> a # | |
| Traversable Regex Source # | |
| SymbolMatching Regex Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Regex Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Regex a) | |
| Eq a => Eq (Regex a) Source # | |
| Ord a => Ord (Regex a) Source # | |
| Show a => Show (Regex a) Source # | |
| Generic (Regex a) Source # | |
| Generic1 Regex Source # | |
| type Rep (Regex a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Regex a) = D1 ('MetaData "Regex" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Regex" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(EscapeSequence :+: Interpolation) a]))) | |
| type Rep1 Regex Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Regex = D1 ('MetaData "Regex" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Regex" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 (EscapeSequence :+: Interpolation)))) | |
Constructors
| Redo | |
Fields
| |
Instances
| Functor Redo Source # | |
| Foldable Redo Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Redo m -> m # foldMap :: Monoid m => (a -> m) -> Redo a -> m # foldMap' :: Monoid m => (a -> m) -> Redo a -> m # foldr :: (a -> b -> b) -> b -> Redo a -> b # foldr' :: (a -> b -> b) -> b -> Redo a -> b # foldl :: (b -> a -> b) -> b -> Redo a -> b # foldl' :: (b -> a -> b) -> b -> Redo a -> b # foldr1 :: (a -> a -> a) -> Redo a -> a # foldl1 :: (a -> a -> a) -> Redo a -> a # elem :: Eq a => a -> Redo a -> Bool # maximum :: Ord a => Redo a -> a # | |
| Traversable Redo Source # | |
| SymbolMatching Redo Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Redo Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Redo a) | |
| Eq a => Eq (Redo a) Source # | |
| Ord a => Ord (Redo a) Source # | |
| Show a => Show (Redo a) Source # | |
| Generic (Redo a) Source # | |
| Generic1 Redo Source # | |
| type Rep (Redo a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Redo a) = D1 ('MetaData "Redo" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Redo" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ArgumentList a))))) | |
| type Rep1 Redo Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Redo = D1 ('MetaData "Redo" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Redo" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ArgumentList))) | |
Constructors
| Rational | |
Fields
| |
Instances
Constructors
| Range | |
Fields
| |
Instances
| Functor Range Source # | |
| Foldable Range Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Range m -> m # foldMap :: Monoid m => (a -> m) -> Range a -> m # foldMap' :: Monoid m => (a -> m) -> Range a -> m # foldr :: (a -> b -> b) -> b -> Range a -> b # foldr' :: (a -> b -> b) -> b -> Range a -> b # foldl :: (b -> a -> b) -> b -> Range a -> b # foldl' :: (b -> a -> b) -> b -> Range a -> b # foldr1 :: (a -> a -> a) -> Range a -> a # foldl1 :: (a -> a -> a) -> Range a -> a # elem :: Eq a => a -> Range a -> Bool # maximum :: Ord a => Range a -> a # minimum :: Ord a => Range a -> a # | |
| Traversable Range Source # | |
| SymbolMatching Range Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Range Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Range a) | |
| Eq a => Eq (Range a) Source # | |
| Ord a => Ord (Range a) Source # | |
| Show a => Show (Range a) Source # | |
| Generic (Range a) Source # | |
| Generic1 Range Source # | |
| type Rep (Range a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Range a) = D1 ('MetaData "Range" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Range" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty (Arg a))))) | |
| type Rep1 Range Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Range = D1 ('MetaData "Range" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Range" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (NonEmpty :.: Rec1 Arg))) | |
Constructors
| Program | |
Fields
| |
Instances
Constructors
| Pattern | |
Fields
| |
Instances
| Functor Pattern Source # | |
| Foldable Pattern Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Pattern m -> m # foldMap :: Monoid m => (a -> m) -> Pattern a -> m # foldMap' :: Monoid m => (a -> m) -> Pattern a -> m # foldr :: (a -> b -> b) -> b -> Pattern a -> b # foldr' :: (a -> b -> b) -> b -> Pattern a -> b # foldl :: (b -> a -> b) -> b -> Pattern a -> b # foldl' :: (b -> a -> b) -> b -> Pattern a -> b # foldr1 :: (a -> a -> a) -> Pattern a -> a # foldl1 :: (a -> a -> a) -> Pattern a -> a # elem :: Eq a => a -> Pattern a -> Bool # maximum :: Ord a => Pattern a -> a # minimum :: Ord a => Pattern a -> a # | |
| Traversable Pattern Source # | |
| SymbolMatching Pattern Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Pattern Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Pattern a) | |
| Eq a => Eq (Pattern a) Source # | |
| Ord a => Ord (Pattern a) Source # | |
| Show a => Show (Pattern a) Source # | |
| Generic (Pattern a) Source # | |
| Generic1 Pattern Source # | |
| type Rep (Pattern a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Pattern a) = D1 ('MetaData "Pattern" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Pattern" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((Arg :+: SplatArgument) a)))) | |
| type Rep1 Pattern Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Pattern = D1 ('MetaData "Pattern" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Pattern" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (Arg :+: SplatArgument)))) | |
data ParenthesizedStatements a Source #
Constructors
| ParenthesizedStatements | |
Fields
| |
Instances
Instances
data OptionalParameter a Source #
Constructors
| OptionalParameter | |
Fields
| |
Instances
data OperatorAssignment a Source #
Constructors
| OperatorAssignment | |
Instances
Instances
Constructors
| Next | |
Fields
| |
Instances
| Functor Next Source # | |
| Foldable Next Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Next m -> m # foldMap :: Monoid m => (a -> m) -> Next a -> m # foldMap' :: Monoid m => (a -> m) -> Next a -> m # foldr :: (a -> b -> b) -> b -> Next a -> b # foldr' :: (a -> b -> b) -> b -> Next a -> b # foldl :: (b -> a -> b) -> b -> Next a -> b # foldl' :: (b -> a -> b) -> b -> Next a -> b # foldr1 :: (a -> a -> a) -> Next a -> a # foldl1 :: (a -> a -> a) -> Next a -> a # elem :: Eq a => a -> Next a -> Bool # maximum :: Ord a => Next a -> a # | |
| Traversable Next Source # | |
| SymbolMatching Next Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Next Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Next a) | |
| Eq a => Eq (Next a) Source # | |
| Ord a => Ord (Next a) Source # | |
| Show a => Show (Next a) Source # | |
| Generic (Next a) Source # | |
| Generic1 Next Source # | |
| type Rep (Next a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Next a) = D1 ('MetaData "Next" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Next" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ArgumentList a))))) | |
| type Rep1 Next Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Next = D1 ('MetaData "Next" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Next" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ArgumentList))) | |
Constructors
| Module | |
Fields
| |
Instances
data MethodParameters a Source #
Constructors
| MethodParameters | |
Fields
| |
Instances
data MethodCall a Source #
Constructors
| MethodCall | |
Instances
Constructors
| Method | |
Fields
| |
Instances
data LeftAssignmentList a Source #
Constructors
| LeftAssignmentList | |
Fields
| |
Instances
data LambdaParameters a Source #
Constructors
| LambdaParameters | |
Fields
| |
Instances
Constructors
| Lambda | |
Fields
| |
Instances
data KeywordParameter a Source #
Constructors
| KeywordParameter | |
Instances
data Interpolation a Source #
Constructors
| Interpolation | |
Fields
| |
Instances
Constructors
| In | |
Fields
| |
Instances
| Functor In Source # | |
| Foldable In Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => In m -> m # foldMap :: Monoid m => (a -> m) -> In a -> m # foldMap' :: Monoid m => (a -> m) -> In a -> m # foldr :: (a -> b -> b) -> b -> In a -> b # foldr' :: (a -> b -> b) -> b -> In a -> b # foldl :: (b -> a -> b) -> b -> In a -> b # foldl' :: (b -> a -> b) -> b -> In a -> b # foldr1 :: (a -> a -> a) -> In a -> a # foldl1 :: (a -> a -> a) -> In a -> a # elem :: Eq a => a -> In a -> Bool # maximum :: Ord a => In a -> a # | |
| Traversable In Source # | |
| SymbolMatching In Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal In Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (In a) | |
| Eq a => Eq (In a) Source # | |
| Ord a => Ord (In a) Source # | |
| Show a => Show (In a) Source # | |
| Generic (In a) Source # | |
| Generic1 In Source # | |
| type Rep (In a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (In a) = D1 ('MetaData "In" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "In" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Arg a)))) | |
| type Rep1 In Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 In = D1 ('MetaData "In" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "In" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 Arg))) | |
data IfModifier a Source #
Constructors
| IfModifier | |
Instances
Constructors
| If | |
Instances
data HashSplatParameter a Source #
Constructors
| HashSplatParameter | |
Fields
| |
Instances
data HashSplatArgument a Source #
Constructors
| HashSplatArgument | |
Fields
| |
Instances
Constructors
| Hash | |
Fields
| |
Instances
| Functor Hash Source # | |
| Foldable Hash Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Hash m -> m # foldMap :: Monoid m => (a -> m) -> Hash a -> m # foldMap' :: Monoid m => (a -> m) -> Hash a -> m # foldr :: (a -> b -> b) -> b -> Hash a -> b # foldr' :: (a -> b -> b) -> b -> Hash a -> b # foldl :: (b -> a -> b) -> b -> Hash a -> b # foldl' :: (b -> a -> b) -> b -> Hash a -> b # foldr1 :: (a -> a -> a) -> Hash a -> a # foldl1 :: (a -> a -> a) -> Hash a -> a # elem :: Eq a => a -> Hash a -> Bool # maximum :: Ord a => Hash a -> a # | |
| Traversable Hash Source # | |
| SymbolMatching Hash Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Hash Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Hash a) | |
| Eq a => Eq (Hash a) Source # | |
| Ord a => Ord (Hash a) Source # | |
| Show a => Show (Hash a) Source # | |
| Generic (Hash a) Source # | |
| Generic1 Hash Source # | |
| type Rep (Hash a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Hash a) = D1 ('MetaData "Hash" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Hash" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(HashSplatArgument :+: Pair) a]))) | |
| type Rep1 Hash Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Hash = D1 ('MetaData "Hash" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Hash" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 (HashSplatArgument :+: Pair)))) | |
Constructors
| For | |
Instances
data Exceptions a Source #
Constructors
| Exceptions | |
Fields
| |
Instances
data ExceptionVariable a Source #
Constructors
| ExceptionVariable | |
Fields
| |
Instances
Constructors
| Ensure | |
Fields
| |
Instances
| Functor Ensure Source # | |
| Foldable Ensure Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Ensure m -> m # foldMap :: Monoid m => (a -> m) -> Ensure a -> m # foldMap' :: Monoid m => (a -> m) -> Ensure a -> m # foldr :: (a -> b -> b) -> b -> Ensure a -> b # foldr' :: (a -> b -> b) -> b -> Ensure a -> b # foldl :: (b -> a -> b) -> b -> Ensure a -> b # foldl' :: (b -> a -> b) -> b -> Ensure a -> b # foldr1 :: (a -> a -> a) -> Ensure a -> a # foldl1 :: (a -> a -> a) -> Ensure a -> a # elem :: Eq a => a -> Ensure a -> Bool # maximum :: Ord a => Ensure a -> a # minimum :: Ord a => Ensure a -> a # | |
| Traversable Ensure Source # | |
| SymbolMatching Ensure Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Ensure Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Ensure a) | |
| Eq a => Eq (Ensure a) Source # | |
| Ord a => Ord (Ensure a) Source # | |
Defined in TreeSitter.Ruby.AST | |
| Show a => Show (Ensure a) Source # | |
| Generic (Ensure a) Source # | |
| Generic1 Ensure Source # | |
| type Rep (Ensure a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Ensure a) = D1 ('MetaData "Ensure" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Ensure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Statement :+: EmptyStatement) a]))) | |
| type Rep1 Ensure Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Ensure = D1 ('MetaData "Ensure" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Ensure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 (Statement :+: EmptyStatement)))) | |
Constructors
| EndBlock | |
Fields
| |
Instances
data EmptyStatement a Source #
Constructors
| EmptyStatement | |
Instances
Constructors
| Elsif | |
Instances
Constructors
| Else | |
Fields
| |
Instances
data ElementReference a Source #
Constructors
| ElementReference | |
Fields
| |
Instances
Constructors
| DoBlock | |
Fields
| |
Instances
Constructors
| Do | |
Fields
| |
Instances
| Functor Do Source # | |
| Foldable Do Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Do m -> m # foldMap :: Monoid m => (a -> m) -> Do a -> m # foldMap' :: Monoid m => (a -> m) -> Do a -> m # foldr :: (a -> b -> b) -> b -> Do a -> b # foldr' :: (a -> b -> b) -> b -> Do a -> b # foldl :: (b -> a -> b) -> b -> Do a -> b # foldl' :: (b -> a -> b) -> b -> Do a -> b # foldr1 :: (a -> a -> a) -> Do a -> a # foldl1 :: (a -> a -> a) -> Do a -> a # elem :: Eq a => a -> Do a -> Bool # maximum :: Ord a => Do a -> a # | |
| Traversable Do Source # | |
| SymbolMatching Do Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Do Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Do a) | |
| Eq a => Eq (Do a) Source # | |
| Ord a => Ord (Do a) Source # | |
| Show a => Show (Do a) Source # | |
| Generic (Do a) Source # | |
| Generic1 Do Source # | |
| type Rep (Do a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Do a) = D1 ('MetaData "Do" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Do" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Statement :+: EmptyStatement) a]))) | |
| type Rep1 Do Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Do = D1 ('MetaData "Do" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Do" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 (Statement :+: EmptyStatement)))) | |
data DestructuredParameter a Source #
Constructors
| DestructuredParameter | |
Fields
| |
Instances
data DestructuredLeftAssignment a Source #
Constructors
| DestructuredLeftAssignment | |
Fields
| |
Instances
data Conditional a Source #
Constructors
| Conditional | |
Fields
| |
Instances
Constructors
| Class | |
Fields
| |
Instances
data ChainedString a Source #
Constructors
| ChainedString | |
Fields
| |
Instances
Instances
| Functor Case Source # | |
| Foldable Case Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Case m -> m # foldMap :: Monoid m => (a -> m) -> Case a -> m # foldMap' :: Monoid m => (a -> m) -> Case a -> m # foldr :: (a -> b -> b) -> b -> Case a -> b # foldr' :: (a -> b -> b) -> b -> Case a -> b # foldl :: (b -> a -> b) -> b -> Case a -> b # foldl' :: (b -> a -> b) -> b -> Case a -> b # foldr1 :: (a -> a -> a) -> Case a -> a # foldl1 :: (a -> a -> a) -> Case a -> a # elem :: Eq a => a -> Case a -> Bool # maximum :: Ord a => Case a -> a # | |
| Traversable Case Source # | |
| SymbolMatching Case Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Case Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Case a) | |
| Eq a => Eq (Case a) Source # | |
| Ord a => Ord (Case a) Source # | |
| Show a => Show (Case a) Source # | |
| Generic (Case a) Source # | |
| Generic1 Case Source # | |
| type Rep (Case a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Case a) = D1 ('MetaData "Case" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Case" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Arg a))) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Else :+: When) a])))) | |
| type Rep1 Case Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Case = D1 ('MetaData "Case" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Case" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: (S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 Arg) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 (Else :+: When))))) | |
Constructors
| Call | |
Instances
Constructors
| Break | |
Fields
| |
Instances
| Functor Break Source # | |
| Foldable Break Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Break m -> m # foldMap :: Monoid m => (a -> m) -> Break a -> m # foldMap' :: Monoid m => (a -> m) -> Break a -> m # foldr :: (a -> b -> b) -> b -> Break a -> b # foldr' :: (a -> b -> b) -> b -> Break a -> b # foldl :: (b -> a -> b) -> b -> Break a -> b # foldl' :: (b -> a -> b) -> b -> Break a -> b # foldr1 :: (a -> a -> a) -> Break a -> a # foldl1 :: (a -> a -> a) -> Break a -> a # elem :: Eq a => a -> Break a -> Bool # maximum :: Ord a => Break a -> a # minimum :: Ord a => Break a -> a # | |
| Traversable Break Source # | |
| SymbolMatching Break Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Break Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Break a) | |
| Eq a => Eq (Break a) Source # | |
| Ord a => Ord (Break a) Source # | |
| Show a => Show (Break a) Source # | |
| Generic (Break a) Source # | |
| Generic1 Break Source # | |
| type Rep (Break a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Break a) = D1 ('MetaData "Break" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Break" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ArgumentList a))))) | |
| type Rep1 Break Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Break = D1 ('MetaData "Break" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Break" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Maybe :.: Rec1 ArgumentList))) | |
data BlockParameters a Source #
Constructors
| BlockParameters | |
Fields
| |
Instances
data BlockParameter a Source #
Constructors
| BlockParameter | |
Fields
| |
Instances
data BlockArgument a Source #
Constructors
| BlockArgument | |
Fields
| |
Instances
Constructors
| Block | |
Fields
| |
Instances
| Functor Block Source # | |
| Foldable Block Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Block m -> m # foldMap :: Monoid m => (a -> m) -> Block a -> m # foldMap' :: Monoid m => (a -> m) -> Block a -> m # foldr :: (a -> b -> b) -> b -> Block a -> b # foldr' :: (a -> b -> b) -> b -> Block a -> b # foldl :: (b -> a -> b) -> b -> Block a -> b # foldl' :: (b -> a -> b) -> b -> Block a -> b # foldr1 :: (a -> a -> a) -> Block a -> a # foldl1 :: (a -> a -> a) -> Block a -> a # elem :: Eq a => a -> Block a -> Bool # maximum :: Ord a => Block a -> a # minimum :: Ord a => Block a -> a # | |
| Traversable Block Source # | |
| SymbolMatching Block Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Block Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Block a) | |
| Eq a => Eq (Block a) Source # | |
| Ord a => Ord (Block a) Source # | |
| Show a => Show (Block a) Source # | |
| Generic (Block a) Source # | |
| Generic1 Block Source # | |
| type Rep (Block a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Block a) = D1 ('MetaData "Block" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Block" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Statement :+: (BlockParameters :+: EmptyStatement)) a]))) | |
| type Rep1 Block Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Block = D1 ('MetaData "Block" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Block" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 (Statement :+: (BlockParameters :+: EmptyStatement))))) | |
Constructors
Instances
data BeginBlock a Source #
Constructors
| BeginBlock | |
Fields
| |
Instances
Constructors
| Begin | |
Instances
| Functor Begin Source # | |
| Foldable Begin Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Begin m -> m # foldMap :: Monoid m => (a -> m) -> Begin a -> m # foldMap' :: Monoid m => (a -> m) -> Begin a -> m # foldr :: (a -> b -> b) -> b -> Begin a -> b # foldr' :: (a -> b -> b) -> b -> Begin a -> b # foldl :: (b -> a -> b) -> b -> Begin a -> b # foldl' :: (b -> a -> b) -> b -> Begin a -> b # foldr1 :: (a -> a -> a) -> Begin a -> a # foldl1 :: (a -> a -> a) -> Begin a -> a # elem :: Eq a => a -> Begin a -> Bool # maximum :: Ord a => Begin a -> a # minimum :: Ord a => Begin a -> a # | |
| Traversable Begin Source # | |
| SymbolMatching Begin Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Begin Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Begin a) | |
| Eq a => Eq (Begin a) Source # | |
| Ord a => Ord (Begin a) Source # | |
| Show a => Show (Begin a) Source # | |
| Generic (Begin a) Source # | |
| Generic1 Begin Source # | |
| type Rep (Begin a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Begin a) = D1 ('MetaData "Begin" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Begin" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [((Statement :+: Else) :+: (EmptyStatement :+: (Ensure :+: Rescue))) a]))) | |
| type Rep1 Begin Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Begin = D1 ('MetaData "Begin" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Begin" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 ((Statement :+: Else) :+: (EmptyStatement :+: (Ensure :+: Rescue)))))) | |
data BareSymbol a Source #
Constructors
| BareSymbol | |
Fields
| |
Instances
data BareString a Source #
Constructors
| BareString | |
Fields
| |
Instances
data Assignment a Source #
Constructors
| Assignment | |
Instances
Constructors
| Array | |
Fields
| |
Instances
data ArgumentList a Source #
Constructors
| ArgumentList | |
Fields
| |
Instances
Constructors
| Alias | |
Fields
| |
Instances
Constructors
| Variable ((:+:) ((:+:) ClassVariable ((:+:) Constant GlobalVariable)) ((:+:) ((:+:) Identifier InstanceVariable) ((:+:) Self Super)) a) |
Instances
Constructors
| Statement ((:+:) ((:+:) ((:+:) ((:+:) Arg Alias) ((:+:) Assignment BeginBlock)) ((:+:) ((:+:) Binary Break) ((:+:) EndBlock ((:+:) IfModifier MethodCall)))) ((:+:) ((:+:) ((:+:) Next OperatorAssignment) ((:+:) RescueModifier Return)) ((:+:) ((:+:) Undef UnlessModifier) ((:+:) UntilModifier ((:+:) WhileModifier Yield)))) a) |
Instances
Constructors
| Primary ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) Lhs Array) ((:+:) Begin Break)) ((:+:) ((:+:) Case ChainedString) ((:+:) Character ((:+:) Class Complex)))) ((:+:) ((:+:) ((:+:) Float For) ((:+:) Hash HeredocBeginning)) ((:+:) ((:+:) If Integer) ((:+:) Lambda ((:+:) Method Module))))) ((:+:) ((:+:) ((:+:) ((:+:) Next ParenthesizedStatements) ((:+:) Rational Redo)) ((:+:) ((:+:) Regex Retry) ((:+:) Return ((:+:) SingletonClass SingletonMethod)))) ((:+:) ((:+:) ((:+:) String StringArray) ((:+:) Subshell ((:+:) Symbol SymbolArray))) ((:+:) ((:+:) Unary Unless) ((:+:) Until ((:+:) While Yield))))) a) |
Instances
newtype MethodName a Source #
Constructors
| MethodName ((:+:) ((:+:) ((:+:) ClassVariable Constant) ((:+:) GlobalVariable Identifier)) ((:+:) ((:+:) InstanceVariable Operator) ((:+:) Setter Symbol)) a) |
Instances
Constructors
| Lhs ((:+:) ((:+:) ((:+:) Variable Call) ((:+:) ElementReference False)) ((:+:) ((:+:) MethodCall Nil) ((:+:) ScopeResolution True)) a) |
Instances
| Functor Lhs Source # | |
| Foldable Lhs Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Lhs m -> m # foldMap :: Monoid m => (a -> m) -> Lhs a -> m # foldMap' :: Monoid m => (a -> m) -> Lhs a -> m # foldr :: (a -> b -> b) -> b -> Lhs a -> b # foldr' :: (a -> b -> b) -> b -> Lhs a -> b # foldl :: (b -> a -> b) -> b -> Lhs a -> b # foldl' :: (b -> a -> b) -> b -> Lhs a -> b # foldr1 :: (a -> a -> a) -> Lhs a -> a # foldl1 :: (a -> a -> a) -> Lhs a -> a # elem :: Eq a => a -> Lhs a -> Bool # maximum :: Ord a => Lhs a -> a # | |
| Traversable Lhs Source # | |
| SymbolMatching Lhs Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Lhs Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Lhs a) | |
| Eq a => Eq (Lhs a) Source # | |
| Ord a => Ord (Lhs a) Source # | |
| Show a => Show (Lhs a) Source # | |
| Generic (Lhs a) Source # | |
| Generic1 Lhs Source # | |
| type Rep (Lhs a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Lhs a) = D1 ('MetaData "Lhs" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'True) (C1 ('MetaCons "Lhs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((((Variable :+: Call) :+: (ElementReference :+: False)) :+: ((MethodCall :+: Nil) :+: (ScopeResolution :+: True))) a)))) | |
| type Rep1 Lhs Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Lhs = D1 ('MetaData "Lhs" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'True) (C1 ('MetaCons "Lhs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (((Variable :+: Call) :+: (ElementReference :+: False)) :+: ((MethodCall :+: Nil) :+: (ScopeResolution :+: True)))))) | |
Constructors
| Arg ((:+:) ((:+:) Primary ((:+:) Assignment Binary)) ((:+:) ((:+:) Conditional OperatorAssignment) ((:+:) Range Unary)) a) |
Instances
| Functor Arg Source # | |
| Foldable Arg Source # | |
Defined in TreeSitter.Ruby.AST Methods fold :: Monoid m => Arg m -> m # foldMap :: Monoid m => (a -> m) -> Arg a -> m # foldMap' :: Monoid m => (a -> m) -> Arg a -> m # foldr :: (a -> b -> b) -> b -> Arg a -> b # foldr' :: (a -> b -> b) -> b -> Arg a -> b # foldl :: (b -> a -> b) -> b -> Arg a -> b # foldl' :: (b -> a -> b) -> b -> Arg a -> b # foldr1 :: (a -> a -> a) -> Arg a -> a # foldl1 :: (a -> a -> a) -> Arg a -> a # elem :: Eq a => a -> Arg a -> Bool # maximum :: Ord a => Arg a -> a # | |
| Traversable Arg Source # | |
| SymbolMatching Arg Source # | |
Defined in TreeSitter.Ruby.AST | |
| Unmarshal Arg Source # | |
Defined in TreeSitter.Ruby.AST Methods 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 (Arg a) | |
| Eq a => Eq (Arg a) Source # | |
| Ord a => Ord (Arg a) Source # | |
| Show a => Show (Arg a) Source # | |
| Generic (Arg a) Source # | |
| Generic1 Arg Source # | |
| type Rep (Arg a) Source # | |
Defined in TreeSitter.Ruby.AST type Rep (Arg a) = D1 ('MetaData "Arg" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'True) (C1 ('MetaCons "Arg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (((Primary :+: (Assignment :+: Binary)) :+: ((Conditional :+: OperatorAssignment) :+: (Range :+: Unary))) a)))) | |
| type Rep1 Arg Source # | |
Defined in TreeSitter.Ruby.AST type Rep1 Arg = D1 ('MetaData "Arg" "TreeSitter.Ruby.AST" "tree-sitter-ruby-0.4.0.0-inplace" 'True) (C1 ('MetaCons "Arg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 ((Primary :+: (Assignment :+: Binary)) :+: ((Conditional :+: OperatorAssignment) :+: (Range :+: Unary)))))) | |