mirror of
https://github.com/github/semantic.git
synced 2024-11-28 18:23:44 +03:00
Map public_field_definition to FieldDecl and fix up VarDecl and VarAssignment mappings
This commit is contained in:
parent
980565af05
commit
01a8087b0a
@ -46,7 +46,8 @@ languageForType mediaType = case mediaType of
|
||||
toVarDeclOrAssignment :: (HasField fields Category) => Term (S.Syntax Text) (Record fields) -> Term (S.Syntax Text) (Record fields)
|
||||
toVarDeclOrAssignment child = case unwrap child of
|
||||
S.Indexed [child', assignment] -> cofree $ setCategory (extract child) VarAssignment :< S.VarAssignment [child'] assignment
|
||||
S.VarDecl _ -> child
|
||||
S.Indexed [child'] -> cofree $ setCategory (extract child) VarDecl :< S.VarDecl [child']
|
||||
S.VarDecl _ -> cofree $ setCategory (extract child) VarDecl :< unwrap child
|
||||
S.VarAssignment _ _ -> child
|
||||
_ -> toVarDecl child
|
||||
|
||||
|
@ -22,17 +22,7 @@ termAssignment source category children = case (category, children) of
|
||||
(For, [rangeClause, body]) | Other "range_clause" <- Info.category (extract rangeClause) -> Just $ S.For (toList (unwrap rangeClause)) (toList (unwrap body))
|
||||
(TypeDecl, [identifier, ty]) -> Just $ S.TypeDecl identifier ty
|
||||
(StructTy, _) -> Just (S.Ty children)
|
||||
(FieldDecl, [idList])
|
||||
| [ident] <- toList (unwrap idList)
|
||||
-> Just (S.FieldDecl ident Nothing Nothing)
|
||||
(FieldDecl, [idList, ty])
|
||||
| [ident] <- toList (unwrap idList)
|
||||
-> Just $ case Info.category (extract ty) of
|
||||
StringLiteral -> S.FieldDecl ident Nothing (Just ty)
|
||||
_ -> S.FieldDecl ident (Just ty) Nothing
|
||||
(FieldDecl, [idList, ty, tag])
|
||||
| [ident] <- toList (unwrap idList)
|
||||
-> Just (S.FieldDecl ident (Just ty) (Just tag))
|
||||
(FieldDecl, _) -> Just (S.FieldDecl children)
|
||||
(ParameterDecl, param : ty) -> Just $ S.ParameterDecl (listToMaybe ty) param
|
||||
(Assignment, [identifier, expression]) -> Just $ S.VarAssignment [identifier] expression
|
||||
(Select, _) -> Just $ S.Select (children >>= toList . unwrap)
|
||||
|
@ -27,8 +27,10 @@ termAssignment _ category children =
|
||||
-> Just $ S.MethodCall target method (toList . unwrap =<< args)
|
||||
(FunctionCall, function : args) -> Just $ S.FunctionCall function (toList . unwrap =<< args)
|
||||
(Ternary, condition : cases) -> Just $ S.Ternary condition cases
|
||||
(VarDecl, _) -> Just . S.Indexed $ toVarDeclOrAssignment <$> children
|
||||
(VarAssignment, _ ) -> toPublicFieldDefinition children
|
||||
(Other "variable_declaration", _) -> Just . S.Indexed $ toVarDeclOrAssignment <$> children
|
||||
(Other "trailing_variable_declaration", _) -> Just . S.Indexed $ toVarDeclOrAssignment <$> children
|
||||
(VarAssignment, [id, assignment]) -> Just $ S.VarAssignment [id] assignment
|
||||
(FieldDecl, _) -> Just $ S.FieldDecl children
|
||||
(Object, _) -> Just . S.Object Nothing $ foldMap toTuple children
|
||||
(DoWhile, [ expr, body ]) -> Just $ S.DoWhile expr body
|
||||
(Constructor, [ expr ]) -> Just $ S.Constructor expr
|
||||
@ -113,8 +115,6 @@ categoryForTypeScriptName = \case
|
||||
"subscript_access" -> SubscriptAccess
|
||||
"regex" -> Regex
|
||||
"template_string" -> TemplateString
|
||||
"variable_declaration" -> VarDecl
|
||||
"trailing_variable_declaration" -> VarDecl
|
||||
"switch_statement" -> Switch
|
||||
"math_assignment" -> MathAssignment
|
||||
"case" -> Case
|
||||
@ -139,7 +139,7 @@ categoryForTypeScriptName = \case
|
||||
"break_statement" -> Break
|
||||
"continue_statement" -> Continue
|
||||
"yield_expression" -> Yield
|
||||
"public_field_definition" -> VarAssignment
|
||||
"public_field_definition" -> FieldDecl
|
||||
"variable_declarator" -> VarAssignment
|
||||
"type_annotation" -> Ty
|
||||
"accessibility_modifier" -> Identifier
|
||||
|
@ -149,7 +149,7 @@ syntaxToTermField syntax = case syntax of
|
||||
S.ParameterDecl ty field -> [ "type" .= ty ] <> [ "identifier" .= field ]
|
||||
S.DefaultCase c -> childrenFields c
|
||||
S.TypeDecl id ty -> [ "type" .= ty ] <> [ "identifier" .= id ]
|
||||
S.FieldDecl id ty tag -> [ "type" .= ty ] <> [ "identifier" .= id ] <> [ "tag" .= tag]
|
||||
S.FieldDecl children -> childrenFields children
|
||||
S.Ty ty -> [ "type" .= ty ]
|
||||
S.Send channel expr -> [ "channel" .= channel ] <> [ "expression" .= expr ]
|
||||
where childrenFields c = [ "children" .= c ]
|
||||
|
@ -282,7 +282,7 @@ toTermName source term = case unwrap term of
|
||||
S.Continue expr -> maybe "" toTermName' expr
|
||||
S.BlockStatement children -> termNameFromChildren term children
|
||||
S.DefaultCase children -> termNameFromChildren term children
|
||||
S.FieldDecl id expr tag -> termNameFromSource id <> maybe "" (\expr' -> " " <> termNameFromSource expr') expr <> maybe "" ((" " <>) . termNameFromSource) tag
|
||||
S.FieldDecl children -> termNameFromChildren term children
|
||||
where toTermName' = toTermName source
|
||||
termNameFromChildren term children = termNameFromRange (unionRangesFrom (range term) (range <$> children))
|
||||
termNameFromSource term = termNameFromRange (range term)
|
||||
|
@ -101,7 +101,7 @@ data Syntax a f
|
||||
-- | A type declaration has an identifier and a type.
|
||||
| TypeDecl f f
|
||||
-- | A field declaration with an optional type, and an optional tag.
|
||||
| FieldDecl f (Maybe f) (Maybe f)
|
||||
| FieldDecl [f]
|
||||
-- | A type.
|
||||
| Ty [f]
|
||||
-- | A send statement has a channel and an expression in Go.
|
||||
@ -162,7 +162,7 @@ instance Listable2 Syntax where
|
||||
\/ liftCons1 (liftTiers recur) BlockStatement
|
||||
\/ liftCons2 (liftTiers recur) recur ParameterDecl
|
||||
\/ liftCons2 recur recur TypeDecl
|
||||
\/ liftCons3 recur (liftTiers recur) (liftTiers recur) FieldDecl
|
||||
\/ liftCons1 (liftTiers recur) FieldDecl
|
||||
\/ liftCons1 (liftTiers recur) Ty
|
||||
\/ liftCons2 recur recur Send
|
||||
\/ liftCons1 (liftTiers recur) DefaultCase
|
||||
|
@ -1,5 +1,5 @@
|
||||
{+(Program
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(NumberLiteral))))+}
|
||||
|
@ -1,11 +1,9 @@
|
||||
{+(Program
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
(VarDecl
|
||||
(Other "variable_declarator"
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(Object))
|
||||
(VarDecl
|
||||
(Other "variable_declarator"
|
||||
(Identifier)))))+}
|
||||
(Identifier))))+}
|
||||
|
@ -1,5 +1,5 @@
|
||||
{-(Program
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(NumberLiteral))))-}
|
||||
|
@ -1,11 +1,9 @@
|
||||
{-(Program
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
(VarDecl
|
||||
(Other "variable_declarator"
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(Object))
|
||||
(VarDecl
|
||||
(Other "variable_declarator"
|
||||
(Identifier)))))-}
|
||||
(Identifier))))-}
|
||||
|
@ -1,14 +1,11 @@
|
||||
(Program
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
{+(VarDecl
|
||||
(Other "variable_declarator"
|
||||
(Identifier)))+}
|
||||
{+(VarAssignment
|
||||
(Identifier)
|
||||
(Object))+}
|
||||
(Identifier))+}
|
||||
(VarAssignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (NumberLiteral)
|
||||
->(Object) })
|
||||
{+(VarDecl
|
||||
(Other "variable_declarator"
|
||||
(Identifier)))+}
|
||||
{-(VarAssignment
|
||||
(Identifier)
|
||||
(NumberLiteral))-}))
|
||||
(Identifier))+}))
|
||||
|
@ -1,14 +1,12 @@
|
||||
(Program
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
{+(VarAssignment
|
||||
(Identifier)
|
||||
(NumberLiteral))+}
|
||||
{-(VarDecl
|
||||
(Other "variable_declarator"
|
||||
(Identifier)))-}
|
||||
(Identifier))-}
|
||||
{-(VarAssignment
|
||||
(Identifier)
|
||||
(Object))-}
|
||||
{-(VarDecl
|
||||
(Other "variable_declarator"
|
||||
(Identifier)))-}))
|
||||
(Identifier))-}))
|
||||
|
@ -1,5 +1,5 @@
|
||||
(Program
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(NumberLiteral))))
|
||||
|
@ -1,11 +1,9 @@
|
||||
(Program
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
(VarDecl
|
||||
(Other "variable_declarator"
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(Object))
|
||||
(VarDecl
|
||||
(Other "variable_declarator"
|
||||
(Identifier)))))
|
||||
(Identifier))))
|
||||
|
2
test/fixtures/typescript/yield.diff+A.txt
vendored
2
test/fixtures/typescript/yield.diff+A.txt
vendored
@ -3,7 +3,7 @@
|
||||
(Function
|
||||
(Identifier)
|
||||
(ExpressionStatements
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(NumberLiteral)))
|
||||
|
2
test/fixtures/typescript/yield.diff+B.txt
vendored
2
test/fixtures/typescript/yield.diff+B.txt
vendored
@ -3,7 +3,7 @@
|
||||
(Function
|
||||
(Identifier)
|
||||
(ExpressionStatements
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(NumberLiteral)))
|
||||
|
2
test/fixtures/typescript/yield.diff-A.txt
vendored
2
test/fixtures/typescript/yield.diff-A.txt
vendored
@ -3,7 +3,7 @@
|
||||
(Function
|
||||
(Identifier)
|
||||
(ExpressionStatements
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(NumberLiteral)))
|
||||
|
2
test/fixtures/typescript/yield.diff-B.txt
vendored
2
test/fixtures/typescript/yield.diff-B.txt
vendored
@ -3,7 +3,7 @@
|
||||
(Function
|
||||
(Identifier)
|
||||
(ExpressionStatements
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(NumberLiteral)))
|
||||
|
2
test/fixtures/typescript/yield.diffA-B.txt
vendored
2
test/fixtures/typescript/yield.diffA-B.txt
vendored
@ -3,7 +3,7 @@
|
||||
(Function
|
||||
(Identifier)
|
||||
(ExpressionStatements
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(NumberLiteral)))
|
||||
|
2
test/fixtures/typescript/yield.diffB-A.txt
vendored
2
test/fixtures/typescript/yield.diffB-A.txt
vendored
@ -3,7 +3,7 @@
|
||||
(Function
|
||||
(Identifier)
|
||||
(ExpressionStatements
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(NumberLiteral)))
|
||||
|
2
test/fixtures/typescript/yield.parseA.txt
vendored
2
test/fixtures/typescript/yield.parseA.txt
vendored
@ -3,7 +3,7 @@
|
||||
(Function
|
||||
(Identifier)
|
||||
(ExpressionStatements
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(NumberLiteral)))
|
||||
|
2
test/fixtures/typescript/yield.parseB.txt
vendored
2
test/fixtures/typescript/yield.parseB.txt
vendored
@ -3,7 +3,7 @@
|
||||
(Function
|
||||
(Identifier)
|
||||
(ExpressionStatements
|
||||
(VarDecl
|
||||
(Other "variable_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(NumberLiteral)))
|
||||
|
Loading…
Reference in New Issue
Block a user