Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
debugSymbolNames :: [String] Source #
type AnonymousRBrace = Token "}" 22 Source #
type AnonymousPipePipe = Token "||" 77 Source #
type AnonymousPipeEqual = Token "|=" 39 Source #
type AnonymousPipe = Token "|" 69 Source #
type AnonymousLBrace = Token "{" 21 Source #
type AnonymousVar = Token "var" 13 Source #
data TypeIdentifier a Source #
Instances
type AnonymousType = Token "type" 16 Source #
Instances
Functor True Source # | |
Foldable True Source # | |
Defined in TreeSitter.Go.AST 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.Go.AST symbolMatch :: Proxy True -> Node -> Bool showFailure :: Proxy True -> Node -> String | |
Unmarshal True Source # | |
Defined in TreeSitter.Go.AST 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.Go.AST type Rep (True a) = D1 ('MetaData "True" "TreeSitter.Go.AST" "tree-sitter-go-0.3.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.Go.AST type Rep1 True = D1 ('MetaData "True" "TreeSitter.Go.AST" "tree-sitter-go-0.3.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 AnonymousSwitch = Token "switch" 53 Source #
type AnonymousStruct = Token "struct" 20 Source #
type AnonymousSelect = Token "select" 56 Source #
data RuneLiteral a Source #
Instances
type AnonymousReturn = Token "return" 46 Source #
data RawStringLiteral a Source #
Instances
type AnonymousRange = Token "range" 52 Source #
data PackageIdentifier a Source #
Instances
type AnonymousPackage = Token "package" 4 Source #
Instances
Functor Nil Source # | |
Foldable Nil Source # | |
Defined in TreeSitter.Go.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.Go.AST symbolMatch :: Proxy Nil -> Node -> Bool showFailure :: Proxy Nil -> Node -> String | |
Unmarshal Nil Source # | |
Defined in TreeSitter.Go.AST 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.Go.AST type Rep (Nil a) = D1 ('MetaData "Nil" "TreeSitter.Go.AST" "tree-sitter-go-0.3.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.Go.AST type Rep1 Nil = D1 ('MetaData "Nil" "TreeSitter.Go.AST" "tree-sitter-go-0.3.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 AnonymousMap = Token "map" 24 Source #
Instances
type AnonymousInterface = Token "interface" 23 Source #
data IntLiteral a Source #
Instances
type AnonymousImport = Token "import" 5 Source #
data ImaginaryLiteral a Source #
Instances
type AnonymousIf = Token "if" 49 Source #
data Identifier a Source #
Instances
type AnonymousGoto = Token "goto" 45 Source #
type AnonymousGo = Token "go" 47 Source #
type AnonymousFunc = Token "func" 14 Source #
type AnonymousFor = Token "for" 51 Source #
data FloatLiteral a Source #
Instances
data FieldIdentifier a Source #
Instances
Instances
Functor False Source # | |
Foldable False Source # | |
Defined in TreeSitter.Go.AST 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.Go.AST symbolMatch :: Proxy False -> Node -> Bool showFailure :: Proxy False -> Node -> String | |
Unmarshal False Source # | |
Defined in TreeSitter.Go.AST 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.Go.AST type Rep (False a) = D1 ('MetaData "False" "TreeSitter.Go.AST" "tree-sitter-go-0.3.1.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.Go.AST type Rep1 False = D1 ('MetaData "False" "TreeSitter.Go.AST" "tree-sitter-go-0.3.1.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 AnonymousFallthrough = Token "fallthrough" 42 Source #
data EscapeSequence a Source #
Instances
type AnonymousElse = Token "else" 50 Source #
type AnonymousDefer = Token "defer" 48 Source #
type AnonymousDefault = Token "default" 55 Source #
type AnonymousContinue = Token "continue" 44 Source #
type AnonymousConst = Token "const" 10 Source #
type AnonymousChan = Token "chan" 25 Source #
type AnonymousCase = Token "case" 54 Source #
type AnonymousBreak = Token "break" 43 Source #
data BlankIdentifier a Source #
Instances
type AnonymousCaretEqual = Token "^=" 40 Source #
type AnonymousCaret = Token "^" 62 Source #
type AnonymousRBracket = Token "]" 19 Source #
type AnonymousLBracket = Token "[" 18 Source #
type AnonymousRAngleRAngleEqual = Token ">>=" 34 Source #
type AnonymousRAngleRAngle = Token ">>" 67 Source #
type AnonymousRAngleEqual = Token ">=" 75 Source #
type AnonymousRAngle = Token ">" 74 Source #
type AnonymousEqualEqual = Token "==" 70 Source #
type AnonymousEqual = Token "=" 12 Source #
type AnonymousLAngleEqual = Token "<=" 73 Source #
type AnonymousLAngleLAngleEqual = Token "<<=" 33 Source #
type AnonymousLAngleLAngle = Token "<<" 66 Source #
type AnonymousLAngleMinus = Token "<-" 26 Source #
type AnonymousLAngle = Token "<" 72 Source #
type AnonymousSemicolon = Token ";" 3 Source #
type AnonymousColonEqual = Token ":=" 27 Source #
type AnonymousColon = Token ":" 41 Source #
type AnonymousSlashEqual = Token "/=" 31 Source #
type AnonymousSlash = Token "/" 64 Source #
type AnonymousDotDotDot = Token "..." 15 Source #
type AnonymousDot = Token "." 6 Source #
type AnonymousMinusEqual = Token "-=" 38 Source #
type AnonymousMinusMinus = Token "--" 29 Source #
type AnonymousMinus = Token "-" 60 Source #
type AnonymousComma = Token "," 11 Source #
type AnonymousPlusEqual = Token "+=" 37 Source #
type AnonymousPlusPlus = Token "++" 28 Source #
type AnonymousPlus = Token "+" 59 Source #
type AnonymousStarEqual = Token "*=" 30 Source #
type AnonymousStar = Token "*" 17 Source #
type AnonymousRParen = Token ")" 9 Source #
type AnonymousLParen = Token "(" 8 Source #
type AnonymousAmpersandCaretEqual = Token "&^=" 36 Source #
type AnonymousAmpersandCaret = Token "&^" 68 Source #
type AnonymousAmpersandEqual = Token "&=" 35 Source #
type AnonymousAmpersandAmpersand = Token "&&" 76 Source #
type AnonymousAmpersand = Token "&" 63 Source #
type AnonymousPercentEqual = Token "%=" 32 Source #
type AnonymousPercent = Token "%" 65 Source #
type AnonymousDQuote = Token "\"" 79 Source #
type AnonymousBangEqual = Token "!=" 71 Source #
type AnonymousBang = Token "!" 61 Source #
type AnonymousLF = Token "\n" 2 Source #
data VariadicParameterDeclaration a Source #
Instances
data VariadicArgument a Source #
VariadicArgument | |
|
Instances
VarSpec | |
|
Instances
data VarDeclaration a Source #
VarDeclaration | |
|
Instances
data UnaryExpression a Source #
UnaryExpression | |
|
Instances
data TypeSwitchStatement a Source #
TypeSwitchStatement | |
|
Instances
Instances
data TypeDeclaration a Source #
TypeDeclaration | |
|
Instances
data TypeConversionExpression a Source #
TypeConversionExpression | |
|
Instances
TypeCase | |
|
Instances
data TypeAssertionExpression a Source #
TypeAssertionExpression | |
|
Instances
Instances
data StructType a Source #
StructType | |
|
Instances
data SourceFile a Source #
SourceFile | |
|
Instances
Instances
data SliceExpression a Source #
SliceExpression | |
|
Instances
data ShortVarDeclaration a Source #
ShortVarDeclaration | |
|
Instances
data SendStatement a Source #
SendStatement | |
|
Instances
data SelectorExpression a Source #
SelectorExpression | |
|
Instances
data SelectStatement a Source #
SelectStatement | |
|
Instances
data ReturnStatement a Source #
ReturnStatement | |
|
Instances
data ReceiveStatement a Source #
ReceiveStatement | |
|
Instances
data RangeClause a Source #
RangeClause | |
|
Instances
data QualifiedType a Source #
QualifiedType | |
|
Instances
data PointerType a Source #
PointerType | |
|
Instances
data ParenthesizedType a Source #
ParenthesizedType | |
|
Instances
data ParenthesizedExpression a Source #
ParenthesizedExpression | |
|
Instances
data ParameterList a Source #
ParameterList | |
|
Instances
data ParameterDeclaration a Source #
ParameterDeclaration | |
|
Instances
data PackageClause a Source #
PackageClause | |
|
Instances
data MethodSpecList a Source #
MethodSpecList | |
|
Instances
data MethodSpec a Source #
MethodSpec | |
|
Instances
data MethodDeclaration a Source #
MethodDeclaration | |
|
Instances
Instances
data LiteralValue a Source #
LiteralValue | |
|
Instances
data LabeledStatement a Source #
Instances
data KeyedElement a Source #
KeyedElement | |
|
Instances
data InterpretedStringLiteral a Source #
InterpretedStringLiteral | |
|
Instances
data InterfaceType a Source #
InterfaceType | |
|
Instances
data IndexExpression a Source #
IndexExpression | |
|
Instances
data IncStatement a Source #
IncStatement | |
|
Instances
data ImportSpecList a Source #
ImportSpecList | |
|
Instances
data ImportSpec a Source #
ImportSpec | |
|
Instances
data ImportDeclaration a Source #
ImportDeclaration | |
|
Instances
data ImplicitLengthArrayType a Source #
Instances
data IfStatement a Source #
IfStatement | |
|
Instances
data GotoStatement a Source #
GotoStatement | |
|
Instances
data GoStatement a Source #
GoStatement | |
|
Instances
data FunctionType a Source #
FunctionType | |
|
Instances
data FunctionDeclaration a Source #
FunctionDeclaration | |
|
Instances
data FuncLiteral a Source #
FuncLiteral | |
|
Instances
data ForStatement a Source #
ForStatement | |
|
Instances
ForClause | |
|
Instances
data FieldDeclarationList a Source #
FieldDeclarationList | |
|
Instances
data FieldDeclaration a Source #
FieldDeclaration | |
|
Instances
data FallthroughStatement a Source #
Instances
data ExpressionSwitchStatement a Source #
ExpressionSwitchStatement | |
|
Instances
data ExpressionList a Source #
ExpressionList | |
|
Instances
data ExpressionCase a Source #
ExpressionCase | |
|
Instances
data EmptyStatement a Source #
Instances
Element | |
|
Instances
Instances
Functor Dot Source # | |
Foldable Dot Source # | |
Defined in TreeSitter.Go.AST fold :: Monoid m => Dot m -> m # foldMap :: Monoid m => (a -> m) -> Dot a -> m # foldMap' :: Monoid m => (a -> m) -> Dot a -> m # foldr :: (a -> b -> b) -> b -> Dot a -> b # foldr' :: (a -> b -> b) -> b -> Dot a -> b # foldl :: (b -> a -> b) -> b -> Dot a -> b # foldl' :: (b -> a -> b) -> b -> Dot a -> b # foldr1 :: (a -> a -> a) -> Dot a -> a # foldl1 :: (a -> a -> a) -> Dot a -> a # elem :: Eq a => a -> Dot a -> Bool # maximum :: Ord a => Dot a -> a # | |
Traversable Dot Source # | |
SymbolMatching Dot Source # | |
Defined in TreeSitter.Go.AST symbolMatch :: Proxy Dot -> Node -> Bool showFailure :: Proxy Dot -> Node -> String | |
Unmarshal Dot Source # | |
Defined in TreeSitter.Go.AST 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 (Dot a) | |
Eq a => Eq (Dot a) Source # | |
Ord a => Ord (Dot a) Source # | |
Show a => Show (Dot a) Source # | |
Generic (Dot a) Source # | |
Generic1 Dot Source # | |
type Rep (Dot a) Source # | |
Defined in TreeSitter.Go.AST type Rep (Dot a) = D1 ('MetaData "Dot" "TreeSitter.Go.AST" "tree-sitter-go-0.3.1.0-inplace" 'False) (C1 ('MetaCons "Dot" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
type Rep1 Dot Source # | |
Defined in TreeSitter.Go.AST type Rep1 Dot = D1 ('MetaData "Dot" "TreeSitter.Go.AST" "tree-sitter-go-0.3.1.0-inplace" 'False) (C1 ('MetaCons "Dot" 'PrefixI 'True) (S1 ('MetaSel ('Just "ann") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
data DeferStatement a Source #
DeferStatement | |
|
Instances
data DefaultCase a Source #
DefaultCase | |
|
Instances
data DecStatement a Source #
DecStatement | |
|
Instances
data ContinueStatement a Source #
ContinueStatement | |
|
Instances
ConstSpec | |
|
Instances
data ConstDeclaration a Source #
ConstDeclaration | |
|
Instances
data CompositeLiteral a Source #
CompositeLiteral | |
|
Instances
data CommunicationCase a Source #
CommunicationCase | |
|
Instances
data ChannelType a Source #
Instances
data CallExpression a Source #
CallExpression | |
|
Instances
data BreakStatement a Source #
BreakStatement | |
|
Instances
Block | |
|
Instances
Functor Block Source # | |
Foldable Block Source # | |
Defined in TreeSitter.Go.AST 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.Go.AST symbolMatch :: Proxy Block -> Node -> Bool showFailure :: Proxy Block -> Node -> String | |
Unmarshal Block Source # | |
Defined in TreeSitter.Go.AST 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.Go.AST type Rep (Block a) = D1 ('MetaData "Block" "TreeSitter.Go.AST" "tree-sitter-go-0.3.1.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 a]))) | |
type Rep1 Block Source # | |
Defined in TreeSitter.Go.AST type Rep1 Block = D1 ('MetaData "Block" "TreeSitter.Go.AST" "tree-sitter-go-0.3.1.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))) |
data BinaryExpression a Source #
Instances
data AssignmentStatement a Source #
Instances
Instances
data ArgumentList a Source #
ArgumentList | |
|
Instances
Instances
Functor Type Source # | |
Foldable Type Source # | |
Defined in TreeSitter.Go.AST fold :: Monoid m => Type m -> m # foldMap :: Monoid m => (a -> m) -> Type a -> m # foldMap' :: Monoid m => (a -> m) -> Type a -> m # foldr :: (a -> b -> b) -> b -> Type a -> b # foldr' :: (a -> b -> b) -> b -> Type a -> b # foldl :: (b -> a -> b) -> b -> Type a -> b # foldl' :: (b -> a -> b) -> b -> Type a -> b # foldr1 :: (a -> a -> a) -> Type a -> a # foldl1 :: (a -> a -> a) -> Type a -> a # elem :: Eq a => a -> Type a -> Bool # maximum :: Ord a => Type a -> a # | |
Traversable Type Source # | |
SymbolMatching Type Source # | |
Defined in TreeSitter.Go.AST symbolMatch :: Proxy Type -> Node -> Bool showFailure :: Proxy Type -> Node -> String | |
Unmarshal Type Source # | |
Defined in TreeSitter.Go.AST unmarshalNode :: forall (sig :: (Type0 -> Type0) -> Type0 -> Type0) m a. (Has (Reader ByteString) sig m, Has (Reader (Ptr Cursor)) sig m, MonadFail m, MonadIO m, UnmarshalAnn a) => Node -> m (Type a) | |
Eq a => Eq (Type a) Source # | |
Ord a => Ord (Type a) Source # | |
Show a => Show (Type a) Source # | |
Generic (Type a) Source # | |
Generic1 Type Source # | |
type Rep (Type a) Source # | |
Defined in TreeSitter.Go.AST type Rep (Type a) = D1 ('MetaData "Type" "TreeSitter.Go.AST" "tree-sitter-go-0.3.1.0-inplace" 'True) (C1 ('MetaCons "Type" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((SimpleType :+: ParenthesizedType) a)))) | |
type Rep1 Type Source # | |
Defined in TreeSitter.Go.AST type Rep1 Type = D1 ('MetaData "Type" "TreeSitter.Go.AST" "tree-sitter-go-0.3.1.0-inplace" 'True) (C1 ('MetaCons "Type" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (SimpleType :+: ParenthesizedType)))) |
Instances
newtype SimpleType a Source #
Instances
newtype SimpleStatement a Source #
SimpleStatement ((:+:) ((:+:) Expression ((:+:) AssignmentStatement DecStatement)) ((:+:) IncStatement ((:+:) SendStatement ShortVarDeclaration)) a) |
Instances
newtype Expression a Source #