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 # | |
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.1.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.1.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
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 # | |
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.1.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.1.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 # | |
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.1.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.1.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
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
Instances
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
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
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
Constructors
Unary | |
Fields
|
Instances
Constructors
Then | |
Fields
|
Instances
data SymbolArray a Source #
Constructors
SymbolArray | |
Fields
|
Instances
Constructors
Symbol | |
Fields
|
Instances
data Superclass a Source #
Constructors
Superclass | |
Fields
|
Instances
Constructors
Subshell | |
Fields
|
Instances
data StringArray a Source #
Constructors
StringArray | |
Fields
|
Instances
Constructors
String | |
Fields
|
Instances
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
data ScopeResolution a Source #
Constructors
ScopeResolution | |
Instances
data RightAssignmentList a Source #
Constructors
RightAssignmentList | |
Fields
|
Instances
Constructors
Return | |
Fields
|
Instances
Constructors
Retry | |
Fields
|
Instances
data RestAssignment a Source #
Constructors
RestAssignment | |
Fields
|
Instances
data RescueModifier a Source #
Constructors
RescueModifier | |
Instances
Constructors
Rescue | |
Fields
|
Instances
Constructors
Regex | |
Fields
|
Instances
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 # | |
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.1.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.1.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
Constructors
Program | |
Fields
|
Instances
Constructors
Pattern | |
Fields
|
Instances
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 # | |
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.1.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.1.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 # | |
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.1.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.1.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
Constructors
For | |
Instances
data Exceptions a Source #
Constructors
Exceptions | |
Fields
|
Instances
data ExceptionVariable a Source #
Constructors
ExceptionVariable | |
Fields
|
Instances
Constructors
Ensure | |
Fields
|
Instances
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 # | |
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.1.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.1.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
Constructors
Call | |
Instances
Constructors
Break | |
Fields
|
Instances
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
Constructors
Instances
data BeginBlock a Source #
Constructors
BeginBlock | |
Fields
|
Instances
Constructors
Begin | |
Instances
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 | |
Fields
|
Instances
Constructors
Statement | |
Fields
|
Instances
Constructors
Primary | |
Fields
|
Instances
newtype MethodName a Source #
Constructors
MethodName | |
Fields
|
Instances
Constructors
Lhs | |
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 # | |
HasField "ann" (Lhs a) a Source # | |
Defined in TreeSitter.Ruby.AST | |
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.1.0-inplace" 'True) (C1 ('MetaCons "Lhs" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLhs") '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.1.0-inplace" 'True) (C1 ('MetaCons "Lhs" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLhs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (((Variable :+: Call) :+: (ElementReference :+: False)) :+: ((MethodCall :+: Nil) :+: (ScopeResolution :+: True)))))) |
Constructors
Arg | |
Fields
|
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 # | |
HasField "ann" (Arg a) a Source # | |
Defined in TreeSitter.Ruby.AST | |
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.1.0-inplace" 'True) (C1 ('MetaCons "Arg" 'PrefixI 'True) (S1 ('MetaSel ('Just "getArg") '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.1.0-inplace" 'True) (C1 ('MetaCons "Arg" 'PrefixI 'True) (S1 ('MetaSel ('Just "getArg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 ((Primary :+: (Assignment :+: Binary)) :+: ((Conditional :+: OperatorAssignment) :+: (Range :+: Unary)))))) |