Safe Haskell | None |
---|---|
Language | Haskell2010 |
TreeSitter.TypeScript.AST
Documentation
debugSymbolNames :: [String] Source #
type AnonymousTilde = Token "~" 88 Source #
type AnonymousRBrace = Token "}" 11 Source #
type AnonymousPipeRBrace = Token "|}" 137 Source #
type AnonymousPipePipe = Token "||" 69 Source #
type AnonymousPipeEqual = Token "|=" 61 Source #
type AnonymousPipe = Token "|" 75 Source #
type AnonymousLBracePipe = Token "{|" 136 Source #
type AnonymousLBrace = Token "{" 9 Source #
type AnonymousYield = Token "yield" 42 Source #
type AnonymousWith = Token "with" 31 Source #
type AnonymousWhile = Token "while" 28 Source #
type AnonymousVoid = Token "void" 89 Source #
type AnonymousVar = Token "var" 16 Source #
Instances
type AnonymousTypeof = Token "typeof" 13 Source #
data TypeIdentifier a Source #
Constructors
TypeIdentifier | |
Instances
type AnonymousType = Token "type" 12 Source #
type AnonymousTry = Token "try" 30 Source #
Instances
Functor True Source # | |
Foldable True Source # | |
Defined in TreeSitter.TypeScript.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.TypeScript.AST | |
Unmarshal True Source # | |
Defined in TreeSitter.TypeScript.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.TypeScript.AST type Rep (True a) = D1 ('MetaData "True" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-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.TypeScript.AST type Rep1 True = D1 ('MetaData "True" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-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 AnonymousThrow = Token "throw" 36 Source #
Instances
Functor This Source # | |
Foldable This Source # | |
Defined in TreeSitter.TypeScript.AST Methods fold :: Monoid m => This m -> m # foldMap :: Monoid m => (a -> m) -> This a -> m # foldMap' :: Monoid m => (a -> m) -> This a -> m # foldr :: (a -> b -> b) -> b -> This a -> b # foldr' :: (a -> b -> b) -> b -> This a -> b # foldl :: (b -> a -> b) -> b -> This a -> b # foldl' :: (b -> a -> b) -> b -> This a -> b # foldr1 :: (a -> a -> a) -> This a -> a # foldl1 :: (a -> a -> a) -> This a -> a # elem :: Eq a => a -> This a -> Bool # maximum :: Ord a => This a -> a # | |
Traversable This Source # | |
SymbolMatching This Source # | |
Defined in TreeSitter.TypeScript.AST | |
Unmarshal This Source # | |
Defined in TreeSitter.TypeScript.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 (This a) | |
Eq a => Eq (This a) Source # | |
Ord a => Ord (This a) Source # | |
Show a => Show (This a) Source # | |
Generic (This a) Source # | |
Generic1 This Source # | |
type Rep (This a) Source # | |
Defined in TreeSitter.TypeScript.AST type Rep (This a) = D1 ('MetaData "This" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-0.4.0.0-inplace" 'False) (C1 ('MetaCons "This" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
type Rep1 This Source # | |
Defined in TreeSitter.TypeScript.AST type Rep1 This = D1 ('MetaData "This" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-0.4.0.0-inplace" 'False) (C1 ('MetaCons "This" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
type AnonymousTarget = Token "target" 105 Source #
type AnonymousSymbol = Token "symbol" 126 Source #
type AnonymousSwitch = Token "switch" 21 Source #
Instances
Functor Super Source # | |
Foldable Super Source # | |
Defined in TreeSitter.TypeScript.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.TypeScript.AST | |
Unmarshal Super Source # | |
Defined in TreeSitter.TypeScript.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 # | |
Defined in TreeSitter.TypeScript.AST | |
Show a => Show (Super a) Source # | |
Generic (Super a) Source # | |
Generic1 Super Source # | |
type Rep (Super a) Source # | |
Defined in TreeSitter.TypeScript.AST type Rep (Super a) = D1 ('MetaData "Super" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-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.TypeScript.AST type Rep1 Super = D1 ('MetaData "Super" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-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))) |
type AnonymousString = Token "string" 125 Source #
type AnonymousStatic = Token "static" 113 Source #
data StatementIdentifier a Source #
Constructors
StatementIdentifier | |
Instances
data ShorthandPropertyIdentifier a Source #
Constructors
ShorthandPropertyIdentifier | |
Instances
type AnonymousSet = Token "set" 116 Source #
type AnonymousReturn = Token "return" 35 Source #
type AnonymousRequire = Token "require" 127 Source #
data RegexPattern a Source #
Constructors
RegexPattern | |
Instances
data RegexFlags a Source #
Constructors
RegexFlags | |
Instances
Instances
type AnonymousPublic = Token "public" 118 Source #
type AnonymousProtected = Token "protected" 120 Source #
data PropertyIdentifier a Source #
Constructors
PropertyIdentifier | |
Instances
type AnonymousPrivate = Token "private" 119 Source #
type AnonymousOf = Token "of" 27 Source #
type AnonymousNumber = Token "number" 123 Source #
Instances
Functor Number Source # | |
Foldable Number Source # | |
Defined in TreeSitter.TypeScript.AST Methods fold :: Monoid m => Number m -> m # foldMap :: Monoid m => (a -> m) -> Number a -> m # foldMap' :: Monoid m => (a -> m) -> Number a -> m # foldr :: (a -> b -> b) -> b -> Number a -> b # foldr' :: (a -> b -> b) -> b -> Number a -> b # foldl :: (b -> a -> b) -> b -> Number a -> b # foldl' :: (b -> a -> b) -> b -> Number a -> b # foldr1 :: (a -> a -> a) -> Number a -> a # foldl1 :: (a -> a -> a) -> Number a -> a # elem :: Eq a => a -> Number a -> Bool # maximum :: Ord a => Number a -> a # minimum :: Ord a => Number a -> a # | |
Traversable Number Source # | |
SymbolMatching Number Source # | |
Defined in TreeSitter.TypeScript.AST | |
Unmarshal Number Source # | |
Defined in TreeSitter.TypeScript.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 (Number a) | |
Eq a => Eq (Number a) Source # | |
Ord a => Ord (Number a) Source # | |
Defined in TreeSitter.TypeScript.AST | |
Show a => Show (Number a) Source # | |
Generic (Number a) Source # | |
Generic1 Number Source # | |
type Rep (Number a) Source # | |
Defined in TreeSitter.TypeScript.AST type Rep (Number a) = D1 ('MetaData "Number" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Number" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
type Rep1 Number Source # | |
Defined in TreeSitter.TypeScript.AST type Rep1 Number = D1 ('MetaData "Number" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Number" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
Instances
Functor Null Source # | |
Foldable Null Source # | |
Defined in TreeSitter.TypeScript.AST Methods fold :: Monoid m => Null m -> m # foldMap :: Monoid m => (a -> m) -> Null a -> m # foldMap' :: Monoid m => (a -> m) -> Null a -> m # foldr :: (a -> b -> b) -> b -> Null a -> b # foldr' :: (a -> b -> b) -> b -> Null a -> b # foldl :: (b -> a -> b) -> b -> Null a -> b # foldl' :: (b -> a -> b) -> b -> Null a -> b # foldr1 :: (a -> a -> a) -> Null a -> a # foldl1 :: (a -> a -> a) -> Null a -> a # elem :: Eq a => a -> Null a -> Bool # maximum :: Ord a => Null a -> a # | |
Traversable Null Source # | |
SymbolMatching Null Source # | |
Defined in TreeSitter.TypeScript.AST | |
Unmarshal Null Source # | |
Defined in TreeSitter.TypeScript.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 (Null a) | |
Eq a => Eq (Null a) Source # | |
Ord a => Ord (Null a) Source # | |
Show a => Show (Null a) Source # | |
Generic (Null a) Source # | |
Generic1 Null Source # | |
type Rep (Null a) Source # | |
Defined in TreeSitter.TypeScript.AST type Rep (Null a) = D1 ('MetaData "Null" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Null" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
type Rep1 Null Source # | |
Defined in TreeSitter.TypeScript.AST type Rep1 Null = D1 ('MetaData "Null" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Null" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
type AnonymousNew = Token "new" 53 Source #
type AnonymousNamespace = Token "namespace" 8 Source #
type AnonymousModule = Token "module" 121 Source #
type AnonymousLet = Token "let" 17 Source #
type AnonymousKeyof = Token "keyof" 135 Source #
Instances
Functor JsxText Source # | |
Foldable JsxText Source # | |
Defined in TreeSitter.TypeScript.AST Methods fold :: Monoid m => JsxText m -> m # foldMap :: Monoid m => (a -> m) -> JsxText a -> m # foldMap' :: Monoid m => (a -> m) -> JsxText a -> m # foldr :: (a -> b -> b) -> b -> JsxText a -> b # foldr' :: (a -> b -> b) -> b -> JsxText a -> b # foldl :: (b -> a -> b) -> b -> JsxText a -> b # foldl' :: (b -> a -> b) -> b -> JsxText a -> b # foldr1 :: (a -> a -> a) -> JsxText a -> a # foldl1 :: (a -> a -> a) -> JsxText a -> a # elem :: Eq a => a -> JsxText a -> Bool # maximum :: Ord a => JsxText a -> a # minimum :: Ord a => JsxText a -> a # | |
Traversable JsxText Source # | |
SymbolMatching JsxText Source # | |
Defined in TreeSitter.TypeScript.AST | |
Unmarshal JsxText Source # | |
Defined in TreeSitter.TypeScript.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 (JsxText a) | |
Eq a => Eq (JsxText a) Source # | |
Ord a => Ord (JsxText a) Source # | |
Show a => Show (JsxText a) Source # | |
Generic (JsxText a) Source # | |
Generic1 JsxText Source # | |
type Rep (JsxText a) Source # | |
Defined in TreeSitter.TypeScript.AST type Rep (JsxText a) = D1 ('MetaData "JsxText" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-0.4.0.0-inplace" 'False) (C1 ('MetaCons "JsxText" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
type Rep1 JsxText Source # | |
Defined in TreeSitter.TypeScript.AST type Rep1 JsxText = D1 ('MetaData "JsxText" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-0.4.0.0-inplace" 'False) (C1 ('MetaCons "JsxText" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
type AnonymousIs = Token "is" 134 Source #
type AnonymousInterface = Token "interface" 130 Source #
type AnonymousInstanceof = Token "instanceof" 86 Source #
type AnonymousIn = Token "in" 26 Source #
type AnonymousImport = Token "import" 14 Source #
type AnonymousImplements = Token "implements" 128 Source #
type AnonymousIf = Token "if" 19 Source #
data Identifier a Source #
Constructors
Identifier | |
Instances
data HashBangLine a Source #
Constructors
HashBangLine | |
Instances
type AnonymousGlobal = Token "global" 129 Source #
type AnonymousGet = Token "get" 115 Source #
type AnonymousFunction = Token "function" 51 Source #
type AnonymousFrom = Token "from" 15 Source #
type AnonymousFor = Token "for" 22 Source #
type AnonymousFinally = Token "finally" 41 Source #
Instances
Functor False Source # | |
Foldable False Source # | |
Defined in TreeSitter.TypeScript.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.TypeScript.AST | |
Unmarshal False Source # | |
Defined in TreeSitter.TypeScript.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 # | |
Defined in TreeSitter.TypeScript.AST | |
Show a => Show (False a) Source # | |
Generic (False a) Source # | |
Generic1 False Source # | |
type Rep (False a) Source # | |
Defined in TreeSitter.TypeScript.AST type Rep (False a) = D1 ('MetaData "False" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-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.TypeScript.AST type Rep1 False = D1 ('MetaData "False" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-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))) |
type AnonymousExtends = Token "extends" 131 Source #
type AnonymousExport = Token "export" 3 Source #
data EscapeSequence a Source #
Constructors
EscapeSequence | |
Instances
type AnonymousEnum = Token "enum" 132 Source #
type AnonymousElse = Token "else" 20 Source #
type AnonymousDo = Token "do" 29 Source #
type AnonymousDelete = Token "delete" 90 Source #
type AnonymousDefault = Token "default" 5 Source #
type AnonymousDeclare = Token "declare" 117 Source #
type AnonymousDebugger = Token "debugger" 34 Source #
type AnonymousContinue = Token "continue" 33 Source #
type AnonymousConst = Token "const" 18 Source #
type AnonymousClass = Token "class" 49 Source #
type AnonymousCatch = Token "catch" 40 Source #
type AnonymousCase = Token "case" 39 Source #
type AnonymousBreak = Token "break" 32 Source #
type AnonymousBoolean = Token "boolean" 124 Source #
type AnonymousAwait = Token "await" 25 Source #
type AnonymousAsync = Token "async" 50 Source #
type AnonymousAs = Token "as" 7 Source #
type AnonymousAny = Token "any" 122 Source #
type AnonymousAbstract = Token "abstract" 114 Source #
type AnonymousBacktick = Token "`" 99 Source #
type AnonymousCaretEqual = Token "^=" 59 Source #
type AnonymousCaret = Token "^" 74 Source #
type AnonymousRBracket = Token "]" 44 Source #
type AnonymousLBracket = Token "[" 43 Source #
type AnonymousAt = Token "@" 112 Source #
type AnonymousQuestion = Token "?" 67 Source #
type AnonymousRAngleRAngleRAngleEqual = Token ">>>=" 63 Source #
type AnonymousRAngleRAngleRAngle = Token ">>>" 71 Source #
type AnonymousRAngleRAngleEqual = Token ">>=" 62 Source #
type AnonymousRAngleRAngle = Token ">>" 70 Source #
type AnonymousRAngleEqual = Token ">=" 85 Source #
type AnonymousRAngle = Token ">" 46 Source #
type AnonymousEqualRAngle = Token "=>" 52 Source #
type AnonymousEqualEqualEqual = Token "===" 82 Source #
type AnonymousEqualEqual = Token "==" 81 Source #
type AnonymousEqual = Token "=" 6 Source #
type AnonymousLAngleEqual = Token "<=" 80 Source #
type AnonymousLAngleLAngleEqual = Token "<<=" 64 Source #
type AnonymousLAngleLAngle = Token "<<" 72 Source #
type AnonymousLAngle = Token "<" 45 Source #
type AnonymousSemicolon = Token ";" 37 Source #
type AnonymousColon = Token ":" 38 Source #
type AnonymousSlashEqual = Token "/=" 57 Source #
type AnonymousSlash = Token "/" 47 Source #
type AnonymousDotDotDot = Token "..." 66 Source #
type AnonymousDot = Token "." 48 Source #
type AnonymousMinusEqual = Token "-=" 55 Source #
type AnonymousMinusMinus = Token "--" 92 Source #
type AnonymousMinus = Token "-" 77 Source #
type AnonymousComma = Token "," 10 Source #
type AnonymousPlusEqual = Token "+=" 54 Source #
type AnonymousPlusPlus = Token "++" 91 Source #
type AnonymousPlus = Token "+" 76 Source #
type AnonymousStarEqual = Token "*=" 56 Source #
type AnonymousStarStarEqual = Token "**=" 65 Source #
type AnonymousStarStar = Token "**" 79 Source #
type AnonymousStar = Token "*" 4 Source #
type AnonymousRParen = Token ")" 24 Source #
type AnonymousLParen = Token "(" 23 Source #
type AnonymousSQuote = Token "'" 95 Source #
type AnonymousAmpersandEqual = Token "&=" 60 Source #
type AnonymousAmpersandAmpersand = Token "&&" 68 Source #
type AnonymousAmpersand = Token "&" 73 Source #
type AnonymousPercentEqual = Token "%=" 58 Source #
type AnonymousPercent = Token "%" 78 Source #
type AnonymousDollarLBrace = Token "${" 100 Source #
type AnonymousDQuote = Token "\"" 93 Source #
type AnonymousBangEqualEqual = Token "!==" 84 Source #
type AnonymousBangEqual = Token "!=" 83 Source #
type AnonymousBang = Token "!" 87 Source #
data YieldExpression a Source #
Constructors
YieldExpression | |
Fields
|
Instances
data WithStatement a Source #
Constructors
WithStatement | |
Fields
|
Instances
data WhileStatement a Source #
Constructors
WhileStatement | |
Fields
|
Instances
data VariableDeclarator a Source #
Constructors
VariableDeclarator | |
Fields
|
Instances
data VariableDeclaration a Source #
Constructors
VariableDeclaration | |
Fields
|
Instances
data UpdateExpression a Source #
Constructors
UpdateExpression | |
Fields
|
Instances
Constructors
UnionType | |
Fields
|
Instances
data UnaryExpression a Source #
Constructors
UnaryExpression | |
Fields
|
Instances
Constructors
TypeQuery | |
Fields
|
Instances
data TypePredicate a Source #
Constructors
TypePredicate | |
Fields
|
Instances
data TypeParameters a Source #
Constructors
TypeParameters | |
Fields
|
Instances
data TypeParameter a Source #
Constructors
TypeParameter | |
Fields
|
Instances
data TypeAssertion a Source #
Constructors
TypeAssertion | |
Fields
|
Instances
data TypeArguments a Source #
Constructors
TypeArguments | |
Fields
|
Instances
data TypeAnnotation a Source #
Constructors
TypeAnnotation | |
Fields
|
Instances
data TypeAliasDeclaration a Source #
Constructors
TypeAliasDeclaration | |
Fields
|
Instances
Constructors
TupleType | |
Fields
|
Instances
data TryStatement a Source #
Constructors
TryStatement | |
Fields
|
Instances
data ThrowStatement a Source #
Constructors
ThrowStatement | |
Fields
|
Instances
data TernaryExpression a Source #
Constructors
TernaryExpression | |
Fields
|
Instances
data TemplateSubstitution a Source #
Constructors
TemplateSubstitution | |
Fields
|
Instances
data TemplateString a Source #
Constructors
TemplateString | |
Fields
|
Instances
data SwitchStatement a Source #
Constructors
SwitchStatement | |
Fields
|
Instances
data SwitchDefault a Source #
Constructors
SwitchDefault | |
Fields
|
Instances
data SwitchCase a Source #
Constructors
SwitchCase | |
Fields
|
Instances
data SwitchBody a Source #
Constructors
SwitchBody | |
Fields
|
Instances
data SubscriptExpression a Source #
Constructors
SubscriptExpression | |
Fields
|
Instances
Constructors
String | |
Fields
|
Instances
Functor String Source # | |
Foldable String Source # | |
Defined in TreeSitter.TypeScript.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.TypeScript.AST | |
Unmarshal String Source # | |
Defined in TreeSitter.TypeScript.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.TypeScript.AST | |
Show a => Show (String a) Source # | |
Generic (String a) Source # | |
Generic1 String Source # | |
type Rep (String a) Source # | |
Defined in TreeSitter.TypeScript.AST type Rep (String a) = D1 ('MetaData "String" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-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 a]))) | |
type Rep1 String Source # | |
Defined in TreeSitter.TypeScript.AST type Rep1 String = D1 ('MetaData "String" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-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))) |
data StatementBlock a Source #
Constructors
StatementBlock | |
Fields
|
Instances
data SpreadElement a Source #
Constructors
SpreadElement | |
Fields
|
Instances
data SequenceExpression a Source #
Constructors
SequenceExpression | |
Fields
|
Instances
data ReturnStatement a Source #
Constructors
ReturnStatement | |
Fields
|
Instances
data RestParameter a Source #
Constructors
RestParameter | |
Fields
|
Instances
data RequiredParameter a Source #
Constructors
RequiredParameter | |
Fields
|
Instances
Constructors
Regex | |
Fields
|
Instances
data PublicFieldDefinition a Source #
Constructors
PublicFieldDefinition | |
Fields
|
Instances
data PropertySignature a Source #
Constructors
PropertySignature | |
Fields
|
Instances
Constructors
Program | |
Fields
|
Instances
data PredefinedType a Source #
Constructors
PredefinedType | |
Instances
data ParenthesizedType a Source #
Constructors
ParenthesizedType | |
Fields
|
Instances
data ParenthesizedExpression a Source #
Constructors
ParenthesizedExpression | |
Fields
|
Instances
Constructors
Pair | |
Fields
|
Instances
data OptionalParameter a Source #
Constructors
OptionalParameter | |
Fields
|
Instances
data ObjectType a Source #
Constructors
ObjectType | |
Fields
|
Instances
data ObjectPattern a Source #
Constructors
ObjectPattern | |
Fields
|
Instances
Constructors
Object | |
Fields
|
Instances
data NonNullExpression a Source #
Constructors
NonNullExpression | |
Fields
|
Instances
data NewExpression a Source #
Constructors
NewExpression | |
Fields
|
Instances
data NestedTypeIdentifier a Source #
Constructors
NestedTypeIdentifier | |
Fields
|
Instances
data NestedIdentifier a Source #
Constructors
NestedIdentifier | |
Fields
|
Instances
data NamespaceImport a Source #
Constructors
NamespaceImport | |
Fields
|
Instances
data NamedImports a Source #
Constructors
NamedImports | |
Fields
|
Instances
Constructors
Module | |
Fields
|
Instances
data MethodSignature a Source #
Constructors
MethodSignature | |
Fields
|
Instances
data MethodDefinition a Source #
Constructors
MethodDefinition | |
Fields
|
Instances
data MetaProperty a Source #
Constructors
MetaProperty | |
Instances
data MemberExpression a Source #
Constructors
MemberExpression | |
Fields
|
Instances
data MappedTypeClause a Source #
Constructors
MappedTypeClause | |
Fields
|
Instances
data LookupType a Source #
Constructors
LookupType | |
Fields
|
Instances
data LiteralType a Source #
Constructors
LiteralType | |
Instances
data LexicalDeclaration a Source #
Constructors
LexicalDeclaration | |
Fields
|
Instances
data LabeledStatement a Source #
Constructors
LabeledStatement | |
Fields
|
Instances
data JsxSelfClosingElement a Source #
Constructors
JsxSelfClosingElement | |
Fields
|
Instances
data JsxOpeningElement a Source #
Constructors
JsxOpeningElement | |
Fields
|
Instances
data JsxNamespaceName a Source #
Constructors
JsxNamespaceName | |
Fields
|
Instances
data JsxFragment a Source #
Constructors
JsxFragment | |
Fields
|
Instances
data JsxExpression a Source #
Constructors
JsxExpression | |
Fields
|
Instances
data JsxElement a Source #
Constructors
JsxElement | |
Fields
|
Instances
data JsxClosingElement a Source #
Constructors
JsxClosingElement | |
Fields
|
Instances
data JsxAttribute a Source #
Constructors
JsxAttribute | |
Fields
|
Instances
data IntersectionType a Source #
Constructors
IntersectionType | |
Fields
|
Instances
data InternalModule a Source #
Constructors
InternalModule | |
Fields
|
Instances
data InterfaceDeclaration a Source #
Constructors
InterfaceDeclaration | |
Fields
|
Instances
data IndexTypeQuery a Source #
Constructors
IndexTypeQuery | |
Fields
|
Instances
data IndexSignature a Source #
Constructors
IndexSignature | |
Fields
|
Instances
data ImportStatement a Source #
Constructors
ImportStatement | |
Fields
|
Instances
data ImportSpecifier a Source #
Constructors
ImportSpecifier | |
Fields
|
Instances
data ImportRequireClause a Source #
Constructors
ImportRequireClause | |
Fields
|
Instances
data ImportClause a Source #
Constructors
ImportClause | |
Fields
|
Instances
data ImportAlias a Source #
Constructors
ImportAlias | |
Fields
|
Instances
Instances
Functor Import Source # | |
Foldable Import Source # | |
Defined in TreeSitter.TypeScript.AST Methods fold :: Monoid m => Import m -> m # foldMap :: Monoid m => (a -> m) -> Import a -> m # foldMap' :: Monoid m => (a -> m) -> Import a -> m # foldr :: (a -> b -> b) -> b -> Import a -> b # foldr' :: (a -> b -> b) -> b -> Import a -> b # foldl :: (b -> a -> b) -> b -> Import a -> b # foldl' :: (b -> a -> b) -> b -> Import a -> b # foldr1 :: (a -> a -> a) -> Import a -> a # foldl1 :: (a -> a -> a) -> Import a -> a # elem :: Eq a => a -> Import a -> Bool # maximum :: Ord a => Import a -> a # minimum :: Ord a => Import a -> a # | |
Traversable Import Source # | |
SymbolMatching Import Source # | |
Defined in TreeSitter.TypeScript.AST | |
Unmarshal Import Source # | |
Defined in TreeSitter.TypeScript.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 (Import a) | |
Eq a => Eq (Import a) Source # | |
Ord a => Ord (Import a) Source # | |
Defined in TreeSitter.TypeScript.AST | |
Show a => Show (Import a) Source # | |
Generic (Import a) Source # | |
Generic1 Import Source # | |
type Rep (Import a) Source # | |
Defined in TreeSitter.TypeScript.AST type Rep (Import a) = D1 ('MetaData "Import" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Import" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
type Rep1 Import Source # | |
Defined in TreeSitter.TypeScript.AST type Rep1 Import = D1 ('MetaData "Import" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Import" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
data ImplementsClause a Source #
Constructors
ImplementsClause | |
Fields
|
Instances
data IfStatement a Source #
Constructors
IfStatement | |
Fields
|
Instances
data GenericType a Source #
Constructors
GenericType | |
Fields
|
Instances
data GeneratorFunctionDeclaration a Source #
Constructors
GeneratorFunctionDeclaration | |
Fields
|
Instances
data GeneratorFunction a Source #
Constructors
GeneratorFunction | |
Fields
|
Instances
data FunctionType a Source #
Constructors
FunctionType | |
Fields
|
Instances
data FunctionSignature a Source #
Constructors
FunctionSignature | |
Fields
|
Instances
data FunctionDeclaration a Source #
Constructors
FunctionDeclaration | |
Fields
|
Instances
Constructors
Function | |
Fields
|
Instances
data FormalParameters a Source #
Constructors
FormalParameters | |
Fields
|
Instances
data ForStatement a Source #
Constructors
ForStatement | |
Fields
|
Instances
data ForInStatement a Source #
Constructors
ForInStatement | |
Fields
|
Instances
data FlowMaybeType a Source #
Constructors
FlowMaybeType | |
Fields
|
Instances
data FinallyClause a Source #
Constructors
FinallyClause | |
Fields
|
Instances
data ExtendsClause a Source #
Constructors
ExtendsClause | |
Fields
|
Instances
data ExpressionStatement a Source #
Constructors
ExpressionStatement | |
Fields
|
Instances
data ExportStatement a Source #
Constructors
ExportStatement | |
Fields
|
Instances
data ExportSpecifier a Source #
Constructors
ExportSpecifier | |
Fields
|
Instances
data ExportClause a Source #
Constructors
ExportClause | |
Fields
|
Instances
data ExistentialType a Source #
Constructors
ExistentialType | |
Instances
data EnumDeclaration a Source #
Constructors
EnumDeclaration | |
Fields
|
Instances
Constructors
EnumBody | |
Fields
|
Instances
data EnumAssignment a Source #
Constructors
EnumAssignment | |
Fields
|
Instances
data EmptyStatement a Source #
Constructors
EmptyStatement | |
Instances
data DoStatement a Source #
Constructors
DoStatement | |
Fields
|
Instances
data DefaultType a Source #
Constructors
DefaultType | |
Fields
|
Instances
Constructors
Decorator | |
Fields
|
Instances
data DebuggerStatement a Source #
Constructors
DebuggerStatement | |
Instances
data ContinueStatement a Source #
Constructors
ContinueStatement | |
Fields
|
Instances
data ConstructorType a Source #
Constructors
ConstructorType | |
Fields
|
Instances
data ConstructSignature a Source #
Constructors
ConstructSignature | |
Fields
|
Instances
data Constraint a Source #
Constructors
Constraint | |
Fields
|
Instances
data ComputedPropertyName a Source #
Constructors
ComputedPropertyName | |
Fields
|
Instances
data ClassHeritage a Source #
Constructors
ClassHeritage | |
Fields
|
Instances
data ClassDeclaration a Source #
Constructors
ClassDeclaration | |
Fields
|
Instances
Constructors
ClassBody | |
Fields
|
Instances
Constructors
Class | |
Fields
|
Instances
data CatchClause a Source #
Constructors
CatchClause | |
Fields
|
Instances
data CallSignature a Source #
Constructors
CallSignature | |
Fields
|
Instances
data CallExpression a Source #
Constructors
CallExpression | |
Fields
|
Instances
data BreakStatement a Source #
Constructors
BreakStatement | |
Fields
|
Instances
data BinaryExpression a Source #
Constructors
Instances
data AwaitExpression a Source #
Constructors
AwaitExpression | |
Fields
|
Instances
data AugmentedAssignmentExpression a Source #
Constructors
AugmentedAssignmentExpression | |
Fields
|
Instances
data AssignmentPattern a Source #
Constructors
AssignmentPattern | |
Fields
|
Instances
data AssignmentExpression a Source #
Constructors
AssignmentExpression | |
Fields
|
Instances
data AsExpression a Source #
Constructors
AsExpression | |
Fields
|
Instances
data ArrowFunction a Source #
Constructors
ArrowFunction | |
Fields
|
Instances
Constructors
ArrayType | |
Fields
|
Instances
data ArrayPattern a Source #
Constructors
ArrayPattern | |
Fields
|
Instances
Constructors
Array | |
Fields
|
Instances
Functor Array Source # | |
Foldable Array Source # | |
Defined in TreeSitter.TypeScript.AST Methods fold :: Monoid m => Array m -> m # foldMap :: Monoid m => (a -> m) -> Array a -> m # foldMap' :: Monoid m => (a -> m) -> Array a -> m # foldr :: (a -> b -> b) -> b -> Array a -> b # foldr' :: (a -> b -> b) -> b -> Array a -> b # foldl :: (b -> a -> b) -> b -> Array a -> b # foldl' :: (b -> a -> b) -> b -> Array a -> b # foldr1 :: (a -> a -> a) -> Array a -> a # foldl1 :: (a -> a -> a) -> Array a -> a # elem :: Eq a => a -> Array a -> Bool # maximum :: Ord a => Array a -> a # minimum :: Ord a => Array a -> a # | |
Traversable Array Source # | |
SymbolMatching Array Source # | |
Defined in TreeSitter.TypeScript.AST | |
Unmarshal Array Source # | |
Defined in TreeSitter.TypeScript.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 (Array a) | |
Eq a => Eq (Array a) Source # | |
Ord a => Ord (Array a) Source # | |
Defined in TreeSitter.TypeScript.AST | |
Show a => Show (Array a) Source # | |
Generic (Array a) Source # | |
Generic1 Array Source # | |
type Rep (Array a) Source # | |
Defined in TreeSitter.TypeScript.AST type Rep (Array a) = D1 ('MetaData "Array" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Array" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Expression :+: SpreadElement) a]))) | |
type Rep1 Array Source # | |
Defined in TreeSitter.TypeScript.AST type Rep1 Array = D1 ('MetaData "Array" "TreeSitter.TypeScript.AST" "tree-sitter-typescript-0.4.0.0-inplace" 'False) (C1 ('MetaCons "Array" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "extraChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 (Expression :+: SpreadElement)))) |
Constructors
Arguments | |
Fields
|
Instances
data AmbientDeclaration a Source #
Constructors
AmbientDeclaration | |
Fields
|
Instances
data AccessibilityModifier a Source #
Constructors
AccessibilityModifier | |
Instances
data AbstractMethodSignature a Source #
Constructors
AbstractMethodSignature | |
Fields
|
Instances
data AbstractClassDeclaration a Source #
Constructors
AbstractClassDeclaration | |
Fields
|
Instances
Constructors
Instances
newtype Expression a Source #
Constructors
Instances
newtype DestructuringPattern a Source #
Constructors
DestructuringPattern ((:+:) ArrayPattern ObjectPattern a) |
Instances
newtype Declaration a Source #
Constructors