mirror of
https://github.com/github/semantic.git
synced 2024-11-29 02:44:36 +03:00
Relax VarDecl and VarAssignment constraints
This commit is contained in:
parent
48d46489d1
commit
d05e297084
@ -228,6 +228,8 @@ data Category
|
||||
| Modifier Category
|
||||
-- | A singleton method declaration, e.g. `def self.foo;end` in Ruby
|
||||
| SingletonMethod
|
||||
-- | An arbitrary type annotation.
|
||||
| Ty
|
||||
deriving (Eq, Generic, Ord, Show, NFData)
|
||||
|
||||
{-# DEPRECATED RescueModifier "Deprecated; use Modifier Rescue instead." #-}
|
||||
|
@ -6,6 +6,7 @@ import Info
|
||||
import Prologue
|
||||
import qualified Syntax as S
|
||||
import Term
|
||||
import Data.List (partition)
|
||||
|
||||
-- | A programming language.
|
||||
data Language =
|
||||
@ -44,11 +45,11 @@ 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.Indexed [child', assignment] -> cofree $ setCategory (extract child) VarAssignment :< S.VarAssignment [child'] assignment
|
||||
_ -> toVarDecl child
|
||||
|
||||
toVarDecl :: (HasField fields Category) => Term (S.Syntax Text) (Record fields) -> Term (S.Syntax Text) (Record fields)
|
||||
toVarDecl child = cofree $ setCategory (extract child) VarDecl :< S.VarDecl child Nothing
|
||||
toVarDecl child = cofree $ setCategory (extract child) VarDecl :< S.VarDecl [child]
|
||||
|
||||
toTuple :: Term (S.Syntax Text) (Record fields) -> [Term (S.Syntax Text) (Record fields)]
|
||||
toTuple child | S.Indexed [key,value] <- unwrap child = [cofree (extract child :< S.Pair key value)]
|
||||
@ -57,8 +58,8 @@ toTuple child | S.Leaf c <- unwrap child = [cofree (extract child :< S.Comment c
|
||||
toTuple child = pure child
|
||||
|
||||
toPublicFieldDefinition :: (HasField fields Category) => [SyntaxTerm Text fields] -> Maybe (S.Syntax Text (SyntaxTerm Text fields))
|
||||
toPublicFieldDefinition = \case
|
||||
[child, assignment] -> Just $ S.VarAssignment child assignment
|
||||
[child] -> Just $ S.VarDecl child Nothing
|
||||
toPublicFieldDefinition children = case partition (\x -> category (extract x) == Identifier) children of
|
||||
(prev, [identifier, assignment]) -> Just $ S.VarAssignment (prev ++ [identifier]) assignment
|
||||
(prev, [identifier]) -> Just $ S.VarDecl children
|
||||
_ -> Nothing
|
||||
|
||||
|
@ -34,7 +34,7 @@ termAssignment source category children = case (category, children) of
|
||||
| [ident] <- toList (unwrap idList)
|
||||
-> Just (S.FieldDecl ident (Just ty) (Just tag))
|
||||
(ParameterDecl, param : ty) -> Just $ S.ParameterDecl (listToMaybe ty) param
|
||||
(Assignment, [identifier, expression]) -> Just $ S.VarAssignment identifier expression
|
||||
(Assignment, [identifier, expression]) -> Just $ S.VarAssignment [identifier] expression
|
||||
(Select, _) -> Just $ S.Select (children >>= toList . unwrap)
|
||||
(Go, [expr]) -> Just $ S.Go expr
|
||||
(Defer, [expr]) -> Just $ S.Defer expr
|
||||
@ -54,8 +54,8 @@ termAssignment source category children = case (category, children) of
|
||||
(TypeAssertion, [a, b]) -> Just $ S.TypeAssertion a b
|
||||
(TypeConversion, [a, b]) -> Just $ S.TypeConversion a b
|
||||
-- TODO: Handle multiple var specs
|
||||
(VarAssignment, [identifier, expression]) -> Just $ S.VarAssignment identifier expression
|
||||
(VarDecl, [idList, ty]) | Identifier <- Info.category (extract ty) -> Just $ S.VarDecl idList (Just ty)
|
||||
(VarAssignment, [identifier, expression]) -> Just $ S.VarAssignment [identifier] expression
|
||||
(VarDecl, children) -> Just $ S.VarDecl children
|
||||
(FunctionCall, id : rest) -> Just $ S.FunctionCall id rest
|
||||
(AnonymousFunction, [params, _, body])
|
||||
| [params'] <- toList (unwrap params)
|
||||
|
@ -61,6 +61,7 @@ termAssignment _ category children =
|
||||
(Function, [ body ]) -> Just $ S.AnonymousFunction [] [body]
|
||||
(Function, [ params, body ]) -> Just $ S.AnonymousFunction (toList (unwrap params)) [body]
|
||||
(Function, [ id, params, body ]) -> Just $ S.Function id (toList (unwrap params)) Nothing [body]
|
||||
(Ty, children) -> Just $ S.Ty children
|
||||
_ -> Nothing
|
||||
|
||||
categoryForTypeScriptName :: Text -> Category
|
||||
@ -139,4 +140,5 @@ categoryForTypeScriptName = \case
|
||||
"continue_statement" -> Continue
|
||||
"yield_expression" -> Yield
|
||||
"public_field_definition" -> VarAssignment
|
||||
"type_annotation" -> Ty
|
||||
name -> Other name
|
||||
|
@ -110,7 +110,7 @@ syntaxToTermField syntax = case syntax of
|
||||
S.MemberAccess identifier value -> [ "identifier" .= identifier ] <> [ "value" .= value ]
|
||||
S.MethodCall identifier methodIdentifier parameters -> [ "identifier" .= identifier ] <> [ "methodIdentifier" .= methodIdentifier ] <> [ "parameters" .= parameters ]
|
||||
S.Operator syntaxes -> [ "operatorSyntaxes" .= syntaxes ]
|
||||
S.VarDecl declaration ty -> [ "declaration" .= declaration ] <> [ "type" .= ty]
|
||||
S.VarDecl children -> childrenFields children
|
||||
S.VarAssignment identifier value -> [ "identifier" .= identifier ] <> [ "value" .= value ]
|
||||
S.SubscriptAccess identifier property -> [ "identifier" .= identifier ] <> [ "property" .= property ]
|
||||
S.Switch expression cases -> [ "expression" .= expression ] <> [ "cases" .= cases ]
|
||||
|
@ -149,6 +149,7 @@ styleName category = "category-" <> case category of
|
||||
C.FieldDeclarations -> "field_declarations"
|
||||
C.RuneLiteral -> "rune_literal"
|
||||
C.Modifier c -> styleName c <> "_modifier"
|
||||
C.Ty -> "type"
|
||||
|
||||
-- | Pick the class name for a split patch.
|
||||
splitPatchToClassName :: SplitPatch a -> AttributeValue
|
||||
|
@ -241,8 +241,8 @@ toTermName source term = case unwrap term of
|
||||
SliceTy -> termNameFromSource base <> toTermName' element
|
||||
_ -> toTermName' base <> "[" <> toTermName' element <> "]"
|
||||
(_, _) -> toTermName' base <> "[" <> toTermName' element <> "]"
|
||||
S.VarAssignment varId _ -> toTermName' varId
|
||||
S.VarDecl decl _ -> toTermName' decl
|
||||
S.VarAssignment varId _ -> termNameFromChildren term varId
|
||||
S.VarDecl _ -> termNameFromSource term
|
||||
-- TODO: We should remove Case from Syntax since I don't think we should ever
|
||||
-- evaluate Case as a single toTermName Text - joshvera
|
||||
S.Case expr _ -> termNameFromSource expr
|
||||
@ -381,6 +381,7 @@ instance HasCategory Text where
|
||||
|
||||
instance HasCategory Category where
|
||||
toCategoryName = \case
|
||||
C.Ty -> "type"
|
||||
ArrayLiteral -> "array"
|
||||
BooleanOperator -> "boolean operator"
|
||||
MathOperator -> "math operator"
|
||||
|
@ -27,7 +27,7 @@ data Syntax a f
|
||||
-- | An anonymous function has a list of expressions and params.
|
||||
| AnonymousFunction { params :: [f], expressions :: [f] }
|
||||
-- | A function has a list of expressions.
|
||||
| Function { id :: f, params :: [f], ty :: (Maybe f), expressions :: [f] }
|
||||
| Function { id :: f, params :: [f], ty :: Maybe f, expressions :: [f] }
|
||||
-- | An assignment has an identifier where f can be a member access, and the value is another syntax element (function call, leaf, etc.)
|
||||
| Assignment { assignmentId :: f, value :: f }
|
||||
-- | An operator assignment represents expressions with operators like math (e.g x += 1) or conditional (e.g. x ||= 1) assignment.
|
||||
@ -41,9 +41,9 @@ data Syntax a f
|
||||
-- | An operator can be applied to a list of syntaxes.
|
||||
| Operator [f]
|
||||
-- | A variable declaration. e.g. var foo;
|
||||
| VarDecl f (Maybe f)
|
||||
| VarDecl [f]
|
||||
-- | A variable assignment in a variable declaration. var foo = bar;
|
||||
| VarAssignment { varId :: f, varValue :: f }
|
||||
| VarAssignment { varId :: [f], varValue :: f }
|
||||
-- | A subscript access contains a syntax, and another syntax that indefies a property or value in the first syntax.
|
||||
-- | e.g. in Javascript x["y"] represents a subscript access syntax.
|
||||
| SubscriptAccess { subscriptId :: f, subscriptElement :: f }
|
||||
@ -125,8 +125,8 @@ instance Listable2 Syntax where
|
||||
\/ liftCons2 recur recur MemberAccess
|
||||
\/ liftCons3 recur recur (liftTiers recur) MethodCall
|
||||
\/ liftCons1 (liftTiers recur) Operator
|
||||
\/ liftCons2 recur (liftTiers recur) VarDecl
|
||||
\/ liftCons2 recur recur VarAssignment
|
||||
\/ liftCons1 (liftTiers recur) VarDecl
|
||||
\/ liftCons2 (liftTiers recur) recur VarAssignment
|
||||
\/ liftCons2 recur recur SubscriptAccess
|
||||
\/ liftCons2 (liftTiers recur) (liftTiers recur) Switch
|
||||
\/ liftCons2 recur (liftTiers recur) Case
|
||||
|
Loading…
Reference in New Issue
Block a user