Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 #
Instances
type AnonymousUndef = Token "undef" 98 Source #
Instances
type AnonymousThen = Token "then" 43 Source #
Instances
Instances
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 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 matchedSymbols :: Proxy Nil -> [Int] showFailure :: Proxy Nil -> Node -> String | |
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 #
Instances
type AnonymousIn = Token "in" 37 Source #
type AnonymousIf = Token "if" 31 Source #
data Identifier a Source #
Instances
data HeredocEnd a Source #
Instances
data HeredocBeginning a Source #
Instances
data GlobalVariable a Source #
Instances
type AnonymousFor = Token "for" 36 Source #
Instances
Instances
data EscapeSequence a Source #
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 #
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 #
Yield | |
|
Instances
data WhileModifier a Source #
Instances
Instances
Instances
data UntilModifier a Source #
Instances
Instances
data UnlessModifier a Source #
Instances
Instances
Undef | |
|
Instances
Unary | |
|
Instances
Then | |
|
Instances
data SymbolArray a Source #
SymbolArray | |
|
Instances
Symbol | |
|
Instances
data Superclass a Source #
Superclass | |
|
Instances
Subshell | |
|
Instances
data StringArray a Source #
StringArray | |
|
Instances
String | |
|
Instances
data SplatParameter a Source #
SplatParameter | |
|
Instances
data SplatArgument a Source #
SplatArgument | |
|
Instances
data SingletonMethod a Source #
SingletonMethod | |
|
Instances
data SingletonClass a Source #
Instances
Setter | |
|
Instances
data ScopeResolution a Source #
Instances
data RightAssignmentList a Source #
RightAssignmentList | |
|
Instances
Return | |
|
Instances
Retry | |
|
Instances
data RestAssignment a Source #
RestAssignment | |
|
Instances
data RescueModifier a Source #
Instances
Rescue | |
|
Instances
Regex | |
|
Instances
Redo | |
|
Instances
Rational | |
|
Instances
Range | |
|
Instances
Program | |
|
Instances
Pattern | |
|
Instances
data ParenthesizedStatements a Source #
ParenthesizedStatements | |
|
Instances
Instances
data OptionalParameter a Source #
OptionalParameter | |
|
Instances
data OperatorAssignment a Source #
Instances
Instances
Next | |
|
Instances
Module | |
|
Instances
data MethodParameters a Source #
Instances
data MethodCall a Source #
Instances
Method | |
|
Instances
data LeftAssignmentList a Source #
LeftAssignmentList | |
|
Instances
data LambdaParameters a Source #
Instances
Lambda | |
|
Instances
data KeywordParameter a Source #
Instances
data Interpolation a Source #
Interpolation | |
|
Instances
In | |
|
Instances
Functor In Source # | |
Foldable In Source # | |
Defined in TreeSitter.Ruby.AST 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 matchedSymbols :: Proxy In -> [Int] showFailure :: Proxy In -> Node -> String | |
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 #
Instances
Instances
data HashSplatParameter a Source #
HashSplatParameter | |
|
Instances
data HashSplatArgument a Source #
HashSplatArgument | |
|
Instances
Hash | |
|
Instances
Instances
data Exceptions a Source #
Exceptions | |
|
Instances
data ExceptionVariable a Source #
ExceptionVariable | |
|
Instances
Ensure | |
|
Instances
EndBlock | |
|
Instances
data EmptyStatement a Source #
Instances
Instances
Else | |
|
Instances
data ElementReference a Source #
ElementReference | |
|
Instances
DoBlock | |
|
Instances
Do | |
|
Instances
Functor Do Source # | |
Foldable Do Source # | |
Defined in TreeSitter.Ruby.AST 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 matchedSymbols :: Proxy Do -> [Int] showFailure :: Proxy Do -> Node -> String | |
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 #
Instances
data DestructuredLeftAssignment a Source #
DestructuredLeftAssignment | |
|
Instances
data Conditional a Source #
Conditional | |
|
Instances
Class | |
|
Instances
data ChainedString a Source #
ChainedString | |
|
Instances
Instances
Instances
Break | |
|
Instances
data BlockParameters a Source #
Instances
data BlockParameter a Source #
BlockParameter | |
|
Instances
data BlockArgument a Source #
BlockArgument | |
|
Instances
Block | |
|
Instances
Instances
data BeginBlock a Source #
BeginBlock | |
|
Instances
Instances
data BareSymbol a Source #
BareSymbol | |
|
Instances
data BareString a Source #
BareString | |
|
Instances
data Assignment a Source #
Instances
Array | |
|
Instances
data ArgumentList a Source #
ArgumentList | |
|
Instances
Alias | |
|
Instances
Variable | |
|
Instances
Statement | |
|
Instances
Primary | |
|
Instances
newtype MethodName a Source #
MethodName | |
|
Instances
Instances
Arg | |
|