mirror of
https://github.com/github/semantic.git
synced 2024-11-24 08:54:07 +03:00
🔥 monolithic TypeScript assignment.
This commit is contained in:
parent
a53d9b5e46
commit
4916ccde2f
@ -57,7 +57,6 @@ library
|
|||||||
, Language.JSON.Assignment
|
, Language.JSON.Assignment
|
||||||
, Language.Ruby.Grammar
|
, Language.Ruby.Grammar
|
||||||
, Language.Ruby.Assignment
|
, Language.Ruby.Assignment
|
||||||
, Language.TypeScript
|
|
||||||
, Language.TypeScript.Assignment
|
, Language.TypeScript.Assignment
|
||||||
, Language.TypeScript.Grammar
|
, Language.TypeScript.Grammar
|
||||||
, Language.TypeScript.Syntax
|
, Language.TypeScript.Syntax
|
||||||
|
@ -1,183 +0,0 @@
|
|||||||
{-# LANGUAGE DataKinds #-}
|
|
||||||
module Language.TypeScript where
|
|
||||||
|
|
||||||
import Control.Comonad (extract)
|
|
||||||
import Control.Comonad.Cofree (unwrap)
|
|
||||||
import Data.Foldable (toList)
|
|
||||||
import Data.Record
|
|
||||||
import Data.Source
|
|
||||||
import Data.Term
|
|
||||||
import Data.Text (Text)
|
|
||||||
import Info
|
|
||||||
import Language
|
|
||||||
import qualified Syntax as S
|
|
||||||
|
|
||||||
termAssignment
|
|
||||||
:: Source -- ^ The source of the term.
|
|
||||||
-> Category -- ^ The category for the term.
|
|
||||||
-> [ Term S.Syntax (Record DefaultFields) ] -- ^ The child nodes of the term.
|
|
||||||
-> Maybe (S.Syntax (Term S.Syntax (Record DefaultFields))) -- ^ The resulting term, in Maybe.
|
|
||||||
termAssignment _ category children =
|
|
||||||
case (category, children) of
|
|
||||||
(Assignment, [ identifier, value ]) -> Just $ S.Assignment identifier value
|
|
||||||
(MathAssignment, [ identifier, value ]) -> Just $ S.OperatorAssignment identifier value
|
|
||||||
(MemberAccess, [ base, property ]) -> Just $ S.MemberAccess base property
|
|
||||||
(SubscriptAccess, [ base, element ]) -> Just $ S.SubscriptAccess base element
|
|
||||||
(CommaOperator, [ a, b ])
|
|
||||||
| S.Indexed rest <- unwrap b
|
|
||||||
-> Just $ S.Indexed $ a : rest
|
|
||||||
(FunctionCall, id : rest) -> case break ((== Args) . Info.category . extract) rest of
|
|
||||||
(typeArgs, [ args ]) -> let flatArgs = toList (unwrap args) in
|
|
||||||
Just $ case unwrap id of
|
|
||||||
S.MemberAccess target method -> S.MethodCall target method typeArgs flatArgs
|
|
||||||
_ -> S.FunctionCall id typeArgs flatArgs
|
|
||||||
_ -> Nothing
|
|
||||||
(Ternary, condition : cases) -> Just $ S.Ternary condition cases
|
|
||||||
(Other "variable_declaration", _) -> Just . S.Indexed $ toVarDeclOrAssignment <$> children
|
|
||||||
(Other "trailing_variable_declaration", _) -> Just . S.Indexed $ toVarDeclOrAssignment <$> children
|
|
||||||
(Other "lexical_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
|
|
||||||
(Try, [ body ]) -> Just $ S.Try [body] [] Nothing Nothing
|
|
||||||
(Try, [ body, catch ])
|
|
||||||
| Catch <- Info.category (extract catch)
|
|
||||||
-> Just $ S.Try [body] [catch] Nothing Nothing
|
|
||||||
(Try, [ body, finally ])
|
|
||||||
| Finally <- Info.category (extract finally)
|
|
||||||
-> Just $ S.Try [body] [] Nothing (Just finally)
|
|
||||||
(Try, [ body, catch, finally ])
|
|
||||||
| Catch <- Info.category (extract catch)
|
|
||||||
, Finally <- Info.category (extract finally)
|
|
||||||
-> Just $ S.Try [body] [catch] Nothing (Just finally)
|
|
||||||
(ArrayLiteral, _) -> Just $ S.Array Nothing children
|
|
||||||
(Method, children) -> case break ((== ExpressionStatements) . Info.category . extract) children of
|
|
||||||
(prev, [body]) -> case break ((== Identifier) . Info.category . extract) prev of
|
|
||||||
(prev, [id, callSignature]) -> Just $ S.Method prev id Nothing (toList (unwrap callSignature)) (toList (unwrap body))
|
|
||||||
_ -> Nothing -- No identifier found or callSignature found.
|
|
||||||
_ -> Nothing -- No body found.``
|
|
||||||
(Class, identifier : rest) -> case break ((== Other "class_body") . Info.category . extract) rest of
|
|
||||||
(clauses, [ definitions ]) -> Just $ S.Class identifier clauses (toList (unwrap definitions))
|
|
||||||
_ -> Nothing
|
|
||||||
(Module, [ identifier, definitions ]) -> Just $ S.Module identifier (toList (unwrap definitions))
|
|
||||||
(Namespace, [ identifier, definitions ]) -> Just $ S.Namespace identifier (toList (unwrap definitions))
|
|
||||||
(Import, [ statements, identifier ] ) -> Just $ S.Import identifier (toList (unwrap statements))
|
|
||||||
(Import, [ identifier ] ) -> Just $ S.Import identifier []
|
|
||||||
(Export, [ statements, identifier] ) -> Just $ S.Export (Just identifier) (toList (unwrap statements))
|
|
||||||
(Export, [ statements ] )
|
|
||||||
| S.Indexed _ <- unwrap statements
|
|
||||||
-> Just $ S.Export Nothing (toList (unwrap statements))
|
|
||||||
| otherwise -> Just $ S.Export (Just statements) []
|
|
||||||
(For, _:_) -> Just $ S.For (init children >>= flattenExpressionStatements) [last children]
|
|
||||||
(Function, children) -> case break ((== ExpressionStatements) . Info.category . extract) children of
|
|
||||||
(inits, [body]) -> case inits of
|
|
||||||
[id, callSignature] -> Just $ S.Function id (toList (unwrap callSignature)) (toList (unwrap body))
|
|
||||||
[callSignature] -> Just $ S.AnonymousFunction (toList (unwrap callSignature)) (toList (unwrap body))
|
|
||||||
_ -> Nothing -- More than 1 identifier found or no call signature found
|
|
||||||
_ -> Nothing -- No body found.
|
|
||||||
(Ty, children) -> Just $ S.Ty children
|
|
||||||
(Interface, children) -> toInterface children
|
|
||||||
_ -> Nothing
|
|
||||||
where flattenExpressionStatements term
|
|
||||||
| Info.category (extract term) `elem` [ExpressionStatements, CommaOperator] = toList (unwrap term) >>= flattenExpressionStatements
|
|
||||||
| otherwise = [term]
|
|
||||||
|
|
||||||
categoryForTypeScriptName :: Text -> Category
|
|
||||||
categoryForTypeScriptName category = case category of
|
|
||||||
"object" -> Object
|
|
||||||
"expression_statement" -> ExpressionStatements
|
|
||||||
"trailing_expression_statement" -> ExpressionStatements
|
|
||||||
"this_expression" -> Identifier
|
|
||||||
"null" -> Identifier
|
|
||||||
"undefined" -> Identifier
|
|
||||||
"type_identifier" -> Identifier
|
|
||||||
"property_identifier" -> Identifier
|
|
||||||
"shorthand_property_identifier" -> Identifier
|
|
||||||
"nested_identifier" -> Identifier
|
|
||||||
"arrow_function" -> Function
|
|
||||||
"generator_function" -> Function
|
|
||||||
"math_op" -> MathOperator -- math operator, e.g. +, -, *, /.
|
|
||||||
"update_expression" -> MathOperator -- math operator, e.g. ++, --
|
|
||||||
"bool_op" -> BooleanOperator -- boolean operator, e.g. ||, &&.
|
|
||||||
"comma_op" -> CommaOperator -- comma operator, e.g. expr1, expr2.
|
|
||||||
"sequence_expression" -> CommaOperator -- comma operator, e.g. expr1, expr2.
|
|
||||||
"delete_op" -> Operator -- delete operator, e.g. delete x[2].
|
|
||||||
"type_op" -> Operator -- type operator, e.g. typeof Object.
|
|
||||||
"void_op" -> Operator -- void operator, e.g. void 2.
|
|
||||||
"for_statement" -> For
|
|
||||||
"trailing_for_statement" -> For
|
|
||||||
"for_in_statement" -> For
|
|
||||||
"trailing_for_in_statement" -> For
|
|
||||||
"for_of_statement" -> For
|
|
||||||
"trailing_for_of_statement" -> For
|
|
||||||
"new_expression" -> Constructor
|
|
||||||
"class" -> Class
|
|
||||||
"catch" -> Catch
|
|
||||||
"catch_clause" -> Catch
|
|
||||||
"finally" -> Finally
|
|
||||||
"finally_clause" -> Finally
|
|
||||||
"if_statement" -> If
|
|
||||||
"trailing_if_statement" -> If
|
|
||||||
"empty_statement" -> Empty
|
|
||||||
"program" -> Program
|
|
||||||
"function_call" -> FunctionCall
|
|
||||||
"call_expression" -> FunctionCall
|
|
||||||
"pair" -> Pair
|
|
||||||
"string" -> StringLiteral
|
|
||||||
"integer" -> IntegerLiteral
|
|
||||||
"number" -> NumberLiteral
|
|
||||||
"float" -> FloatLiteral
|
|
||||||
"symbol" -> SymbolLiteral
|
|
||||||
"array" -> ArrayLiteral
|
|
||||||
"function" -> Function
|
|
||||||
"identifier" -> Identifier
|
|
||||||
"formal_parameters" -> Params
|
|
||||||
"arguments" -> Args
|
|
||||||
"statement_block" -> ExpressionStatements
|
|
||||||
"assignment" -> Assignment
|
|
||||||
"assignment_expression" -> Assignment
|
|
||||||
"member_access" -> MemberAccess
|
|
||||||
"member_expression" -> MemberAccess
|
|
||||||
"op" -> Operator
|
|
||||||
"subscript_access" -> SubscriptAccess
|
|
||||||
"subscript_expression" -> SubscriptAccess
|
|
||||||
"regex" -> Regex
|
|
||||||
"template_string" -> TemplateString
|
|
||||||
"switch_statement" -> Switch
|
|
||||||
"math_assignment" -> MathAssignment
|
|
||||||
"augmented_assignment_expression" -> MathAssignment
|
|
||||||
"case" -> Case
|
|
||||||
"switch_case" -> Case
|
|
||||||
"true" -> Boolean
|
|
||||||
"false" -> Boolean
|
|
||||||
"ternary" -> Ternary
|
|
||||||
"ternary_expression" -> Ternary
|
|
||||||
"while_statement" -> While
|
|
||||||
"trailing_while_statement" -> While
|
|
||||||
"do_statement" -> DoWhile
|
|
||||||
"trailing_do_statement" -> DoWhile
|
|
||||||
"return_statement" -> Return
|
|
||||||
"trailing_return_statement" -> Return
|
|
||||||
"throw_statement" -> Throw
|
|
||||||
"trailing_throw_statement" -> Throw
|
|
||||||
"try_statement" -> Try
|
|
||||||
"method_definition" -> Method
|
|
||||||
"comment" -> Comment
|
|
||||||
"bitwise_op" -> BitwiseOperator
|
|
||||||
"rel_op" -> RelationalOperator
|
|
||||||
"import_statement" -> Import
|
|
||||||
"export_statement" -> Export
|
|
||||||
"break_statement" -> Break
|
|
||||||
"continue_statement" -> Continue
|
|
||||||
"yield_expression" -> Yield
|
|
||||||
"public_field_definition" -> FieldDecl
|
|
||||||
"variable_declarator" -> VarAssignment
|
|
||||||
"type_annotation" -> Ty
|
|
||||||
"template_chars" -> TemplateString
|
|
||||||
"module" -> Module
|
|
||||||
"internal_module" -> Namespace
|
|
||||||
"interface_declaration" -> Interface
|
|
||||||
"parenthesized_expression" -> ParenthesizedExpression
|
|
||||||
name -> Other name
|
|
Loading…
Reference in New Issue
Block a user