From abd9bd9e1f26b841cd4d7a9a1b6a3b63692b140d Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Mon, 29 Jan 2018 10:55:52 -0800 Subject: [PATCH 01/68] create ideas directory with one seed idea --- vendor/freer-cofreer | 2 +- vendor/haskell-tree-sitter | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/vendor/freer-cofreer b/vendor/freer-cofreer index 22164cdeb..f18b72357 160000 --- a/vendor/freer-cofreer +++ b/vendor/freer-cofreer @@ -1 +1 @@ -Subproject commit 22164cdebd939dc9b4a21b41a5e4968f991435d1 +Subproject commit f18b723579f700674dda90ed1519f6e7298e2117 diff --git a/vendor/haskell-tree-sitter b/vendor/haskell-tree-sitter index 79271a537..1baeb2f3e 160000 --- a/vendor/haskell-tree-sitter +++ b/vendor/haskell-tree-sitter @@ -1 +1 @@ -Subproject commit 79271a537b78377baa5dcad37effa363b59c77b6 +Subproject commit 1baeb2f3eaa29457de0ce343ce579f7405731c24 From f39413ec7ad6c305dd023946d313297a4b5c5c75 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Thu, 15 Mar 2018 14:57:06 -0700 Subject: [PATCH 02/68] stub out java assignment --- semantic-diff.cabal | 3 +++ 1 file changed, 3 insertions(+) diff --git a/semantic-diff.cabal b/semantic-diff.cabal index 7322c4a3b..292cfc398 100644 --- a/semantic-diff.cabal +++ b/semantic-diff.cabal @@ -101,6 +101,9 @@ library , Language.Python.Assignment , Language.Python.Grammar , Language.Python.Syntax + , Language.Java.Assignment + , Language.Java.Grammar + , Language.Java.Syntax -- Parser glue , Parsing.CMark , Parsing.Parser From 60dcba72742aaafb472915c404805d01ed35325a Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Thu, 15 Mar 2018 15:38:39 -0700 Subject: [PATCH 03/68] Bump tree-sitter --- vendor/haskell-tree-sitter | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vendor/haskell-tree-sitter b/vendor/haskell-tree-sitter index 1baeb2f3e..e98d82687 160000 --- a/vendor/haskell-tree-sitter +++ b/vendor/haskell-tree-sitter @@ -1 +1 @@ -Subproject commit 1baeb2f3eaa29457de0ce343ce579f7405731c24 +Subproject commit e98d8268797b39231b6c3cc46864f6ab9c37e83d From d1bf498f8853030c48e0fe8e2b9dd5236c75fa17 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Thu, 15 Mar 2018 15:39:04 -0700 Subject: [PATCH 04/68] Stub files --- src/Language/Java/Assignment.hs | 1 + src/Language/Java/Grammar.hs | 1 + src/Language/Java/Syntax.hs | 1 + 3 files changed, 3 insertions(+) create mode 100644 src/Language/Java/Assignment.hs create mode 100644 src/Language/Java/Grammar.hs create mode 100644 src/Language/Java/Syntax.hs diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs new file mode 100644 index 000000000..68cf224d6 --- /dev/null +++ b/src/Language/Java/Assignment.hs @@ -0,0 +1 @@ +module Language.Java.Assignment where diff --git a/src/Language/Java/Grammar.hs b/src/Language/Java/Grammar.hs new file mode 100644 index 000000000..3acf36228 --- /dev/null +++ b/src/Language/Java/Grammar.hs @@ -0,0 +1 @@ +module Language.Java.Grammar where diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs new file mode 100644 index 000000000..89c3a73af --- /dev/null +++ b/src/Language/Java/Syntax.hs @@ -0,0 +1 @@ +module Language.Java.Syntax where From 8ccfecade0190867f805c8dbf78160b9e44ab270 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Thu, 15 Mar 2018 15:53:55 -0700 Subject: [PATCH 05/68] tree-sitter-java updates --- semantic-diff.cabal | 1 + src/Language/Java/Grammar.hs | 11 +++++++++++ 2 files changed, 12 insertions(+) diff --git a/semantic-diff.cabal b/semantic-diff.cabal index 292cfc398..1331b7865 100644 --- a/semantic-diff.cabal +++ b/semantic-diff.cabal @@ -168,6 +168,7 @@ library , tree-sitter-python , tree-sitter-ruby , tree-sitter-typescript + , tree-sitter-java default-language: Haskell2010 default-extensions: DeriveFunctor, DeriveFoldable, DeriveTraversable, DeriveGeneric, FlexibleContexts, FlexibleInstances, OverloadedStrings, RecordWildCards, StrictData ghc-options: -Wall -fno-warn-name-shadowing -O -j diff --git a/src/Language/Java/Grammar.hs b/src/Language/Java/Grammar.hs index 3acf36228..8d49da5e0 100644 --- a/src/Language/Java/Grammar.hs +++ b/src/Language/Java/Grammar.hs @@ -1 +1,12 @@ +{-# LANGUAGE TemplateHaskell #-} module Language.Java.Grammar where + +import Language.Haskell.TH +import TreeSitter.Language +import TreeSitter.Java + +-- Regenerate template haskell code when these files change: +addDependentFileRelative "../../../vendor/haskell-tree-sitter/languages/java/vendor/tree-sitter-java/src/parser.c" + +-- | Statically-known rules corresponding to symbols in the grammar. +mkSymbolDatatype (mkName "Grammar") tree_sitter_java From e497f463fa7bda4ebd07ccf5bab89e0580ee89f9 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 16 Mar 2018 11:47:21 -0700 Subject: [PATCH 06/68] update submodule --- vendor/haskell-tree-sitter | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vendor/haskell-tree-sitter b/vendor/haskell-tree-sitter index e98d82687..271296cad 160000 --- a/vendor/haskell-tree-sitter +++ b/vendor/haskell-tree-sitter @@ -1 +1 @@ -Subproject commit e98d8268797b39231b6c3cc46864f6ab9c37e83d +Subproject commit 271296cad95e7f6531b9a7524b100d0f8751bf80 From a20b660940359dc1e9d5162fa44bb04974b87969 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 16 Mar 2018 11:49:06 -0700 Subject: [PATCH 07/68] checkout haskell-tree-sitter java --- vendor/haskell-tree-sitter | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vendor/haskell-tree-sitter b/vendor/haskell-tree-sitter index 271296cad..e98d82687 160000 --- a/vendor/haskell-tree-sitter +++ b/vendor/haskell-tree-sitter @@ -1 +1 @@ -Subproject commit 271296cad95e7f6531b9a7524b100d0f8751bf80 +Subproject commit e98d8268797b39231b6c3cc46864f6ab9c37e83d From 0ba92894f3eee0d599d3fe3df03b39d6664a3785 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 16 Mar 2018 13:57:50 -0700 Subject: [PATCH 08/68] get tree-sitter-java updates --- vendor/haskell-tree-sitter | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vendor/haskell-tree-sitter b/vendor/haskell-tree-sitter index e98d82687..f80fbc335 160000 --- a/vendor/haskell-tree-sitter +++ b/vendor/haskell-tree-sitter @@ -1 +1 @@ -Subproject commit e98d8268797b39231b6c3cc46864f6ab9c37e83d +Subproject commit f80fbc335403a8b93e07e02698c72ce4f4eb97f0 From 691da412b5ea3161a7d5c7067e57b52b1baae85c Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 16 Mar 2018 14:42:25 -0700 Subject: [PATCH 09/68] update haskell-tree-sitter with removed scanner.cc --- vendor/haskell-tree-sitter | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vendor/haskell-tree-sitter b/vendor/haskell-tree-sitter index f80fbc335..c1f988d8b 160000 --- a/vendor/haskell-tree-sitter +++ b/vendor/haskell-tree-sitter @@ -1 +1 @@ -Subproject commit f80fbc335403a8b93e07e02698c72ce4f4eb97f0 +Subproject commit c1f988d8b211c24bf7b22c19084a1df47dfe9b7a From 17aee28de02ff59211def9753baadd137d27c04d Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 16 Mar 2018 14:58:09 -0700 Subject: [PATCH 10/68] Update submodules --- vendor/effects | 2 +- vendor/freer-cofreer | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/vendor/effects b/vendor/effects index 7b905b290..51f0f85dd 160000 --- a/vendor/effects +++ b/vendor/effects @@ -1 +1 @@ -Subproject commit 7b905b290f746c07f6a5486afd9fd881cfd30caf +Subproject commit 51f0f85dd85a09c8cfeab08b2d2703bb70fc5491 diff --git a/vendor/freer-cofreer b/vendor/freer-cofreer index f18b72357..22164cdeb 160000 --- a/vendor/freer-cofreer +++ b/vendor/freer-cofreer @@ -1 +1 @@ -Subproject commit f18b723579f700674dda90ed1519f6e7298e2117 +Subproject commit 22164cdebd939dc9b4a21b41a5e4968f991435d1 From a0d880f1fa565344d6b69b90af2ad2d0ea418e6f Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 16 Mar 2018 16:58:23 -0700 Subject: [PATCH 11/68] add java and php to assignment macro in .ghci --- .ghci | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.ghci b/.ghci index d8fd64b8d..8b4e37a65 100644 --- a/.ghci +++ b/.ghci @@ -24,6 +24,8 @@ assignmentExample lang = case lang of "Haskell" -> mk "hs" "haskell" "Markdown" -> mk "md" "markdown" "JSON" -> mk "json" "json" + "Java" -> mk "java" "java" + "PHP" -> mk "php" "php" _ -> mk "" "" where mk fileExtension parser = putStrLn ("example: fmap (() <$) . runTask . parse " ++ parser ++ "Parser =<< Semantic.Util.file \"example." ++ fileExtension ++ "\"") >> return ("import Parsing.Parser\nimport Semantic.Task\nimport Semantic.Util") :} From 4280b9a300d2dcc5caba41682d51c2242143feec Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 16 Mar 2018 17:00:11 -0700 Subject: [PATCH 12/68] add Java data constructor to language type constructor --- src/Data/Language.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Data/Language.hs b/src/Data/Language.hs index de7c6abd1..66ded44d7 100644 --- a/src/Data/Language.hs +++ b/src/Data/Language.hs @@ -7,6 +7,7 @@ import Data.Aeson -- | A programming language. data Language = Go + | Java | JavaScript | JSON | JSX @@ -20,6 +21,7 @@ data Language -- | Returns a Language based on the file extension (including the "."). languageForType :: String -> Maybe Language languageForType mediaType = case mediaType of + ".java" -> Just Java ".json" -> Just JSON ".md" -> Just Markdown ".rb" -> Just Ruby From 06475e0304ad5503a2ccf80ffaba6d7b40cb16f1 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 16 Mar 2018 17:00:43 -0700 Subject: [PATCH 13/68] wiring up parser for Java --- src/Parsing/Parser.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/src/Parsing/Parser.hs b/src/Parsing/Parser.hs index 91471222f..e56e4c6df 100644 --- a/src/Parsing/Parser.hs +++ b/src/Parsing/Parser.hs @@ -6,6 +6,7 @@ module Parsing.Parser , ApplyAll -- À la carte parsers , goParser +, javaParser , jsonParser , markdownParser , pythonParser @@ -25,6 +26,7 @@ import qualified Data.Syntax as Syntax import Data.Term import Foreign.Ptr import qualified Language.Go.Assignment as Go +import qualified Language.Java.Assignment as Java import qualified Language.JSON.Assignment as JSON import qualified Language.Markdown.Assignment as Markdown import qualified Language.Python.Assignment as Python @@ -34,6 +36,7 @@ import qualified Language.PHP.Assignment as PHP import qualified TreeSitter.Language as TS (Language, Symbol) import TreeSitter.Go import TreeSitter.JSON +import TreeSitter.Java import TreeSitter.PHP import TreeSitter.Python import TreeSitter.Ruby @@ -68,6 +71,7 @@ data SomeParser typeclasses ann where -- -- > case someParser (Proxy :: Proxy '[Show1]) <$> blobLanguage language of { Just (SomeParser parser) -> runTask (parse parser blob) >>= putStrLn . show ; _ -> return () } someParser :: ( ApplyAll typeclasses (Union Go.Syntax) + , ApplyAll typeclasses (Union Java.Syntax) , ApplyAll typeclasses (Union JSON.Syntax) , ApplyAll typeclasses (Union Markdown.Syntax) , ApplyAll typeclasses (Union Python.Syntax) @@ -80,6 +84,7 @@ someParser :: ( ApplyAll typeclasses (Union Go.Syntax) -> SomeParser typeclasses (Record Location) -- ^ A 'SomeParser' abstracting the syntax type to be produced. someParser _ Go = SomeParser goParser someParser _ JavaScript = SomeParser typescriptParser +someParser _ Java = SomeParser javaParser someParser _ JSON = SomeParser jsonParser someParser _ JSX = SomeParser typescriptParser someParser _ Markdown = SomeParser markdownParser @@ -101,6 +106,9 @@ phpParser = AssignmentParser (ASTParser tree_sitter_php) PHP.assignment pythonParser :: Parser Python.Term pythonParser = AssignmentParser (ASTParser tree_sitter_python) Python.assignment +javaParser :: Parser Java.Term +javaParser = AssignmentParser (ASTParser tree_sitter_java) Java.assignment + jsonParser :: Parser JSON.Term jsonParser = AssignmentParser (ASTParser tree_sitter_json) JSON.assignment From df7daebe973eee9e963ccc9947a03afad5515ed0 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 16 Mar 2018 17:20:32 -0700 Subject: [PATCH 14/68] assignment for string and integer literal --- src/Language/Java/Assignment.hs | 79 ++++++++++++++++++++++++++++++++- 1 file changed, 78 insertions(+), 1 deletion(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 68cf224d6..596666e78 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -1 +1,78 @@ -module Language.Java.Assignment where +{-# LANGUAGE DataKinds, RankNTypes, TypeOperators #-} +module Language.Java.Assignment +( assignment +, Syntax +, Grammar +, Term +) where + +import Assigning.Assignment hiding (Assignment, Error) +import Data.Abstract.FreeVariables +import Data.Functor (void) +import Data.List.NonEmpty (some1) +import Data.Record +import Data.Semigroup +import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError, postContextualize) +import Data.Union +import GHC.Stack +import Language.Java.Grammar as Grammar +import Language.Java.Syntax as Syntax +import qualified Assigning.Assignment as Assignment +import qualified Data.Syntax as Syntax +import qualified Data.Syntax.Comment as Comment +import qualified Data.Syntax.Declaration as Declaration +import qualified Data.Syntax.Expression as Expression +import qualified Data.Syntax.Literal as Literal +import qualified Data.Syntax.Statement as Statement +import qualified Data.Syntax.Type as Type +import qualified Data.Term as Term + +-- ' - lift into datakind +type Syntax = + '[ Comment.Comment + , Literal.Integer + , Literal.String + , Literal.TextElement + , Syntax.Context + , Syntax.Empty + , Syntax.Error + , Syntax.Program + , [] + ] + +type Term = Term.Term (Union Syntax) (Record Location) +type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term + +-- | Assignment from AST in Python's grammar onto a program in Python's syntax. +assignment :: Assignment +assignment = handleError $ makeTerm <$> symbol Grammar.Program <*> children (Syntax.Program <$> manyTerm expression) <|> parseError + +-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present. +manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] +manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) + +someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] +someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) + +term :: Assignment -> Assignment +term term = contextualize comment (postContextualize comment term) + +expression :: Assignment +expression = handleError (choice expressionChoices) + +expressionChoices :: [Assignment.Assignment [] Grammar Term] +expressionChoices = + -- Long-term, can we de/serialize assignments and avoid paying the cost of construction altogether? + [ + integer + , string + ] + +comment :: Assignment +comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) + +integer :: Assignment +integer = makeTerm <$> symbol IntegerLiteral <*> children (symbol DecimalIntegerLiteral >> Literal.Integer <$> source) + +string :: Assignment +string = makeTerm <$> symbol StringLiteral <*> (Literal.TextElement <$> source) From dea1234009eec3a8d02e29dd71a3a245984ec2db Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 16 Mar 2018 17:21:39 -0700 Subject: [PATCH 15/68] clean comments --- src/Language/Java/Assignment.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 596666e78..7527927d4 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -27,7 +27,6 @@ import qualified Data.Syntax.Statement as Statement import qualified Data.Syntax.Type as Type import qualified Data.Term as Term --- ' - lift into datakind type Syntax = '[ Comment.Comment , Literal.Integer @@ -43,7 +42,7 @@ type Syntax = type Term = Term.Term (Union Syntax) (Record Location) type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term --- | Assignment from AST in Python's grammar onto a program in Python's syntax. +-- | Assignment from AST in Java's grammar onto a program in Java's syntax. assignment :: Assignment assignment = handleError $ makeTerm <$> symbol Grammar.Program <*> children (Syntax.Program <$> manyTerm expression) <|> parseError @@ -62,7 +61,6 @@ expression = handleError (choice expressionChoices) expressionChoices :: [Assignment.Assignment [] Grammar Term] expressionChoices = - -- Long-term, can we de/serialize assignments and avoid paying the cost of construction altogether? [ integer , string From 2e55f09082cb9d75d000bf083cb63975e8c5d938 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Mon, 9 Apr 2018 11:02:27 -0700 Subject: [PATCH 16/68] introduce assignments for identifier, method, return and type --- src/Data/Syntax/Type.hs | 33 +++++++++++++++++++++++++++ src/Language/Java/Assignment.hs | 37 +++++++++++++++++++++++++++++-- src/Language/Python/Assignment.hs | 2 +- src/Language/Ruby/Assignment.hs | 2 +- 4 files changed, 70 insertions(+), 4 deletions(-) diff --git a/src/Data/Syntax/Type.hs b/src/Data/Syntax/Type.hs index 364ebd607..f25ff7017 100644 --- a/src/Data/Syntax/Type.hs +++ b/src/Data/Syntax/Type.hs @@ -3,6 +3,7 @@ module Data.Syntax.Type where import Data.Abstract.Evaluatable import Diffing.Algorithm +import Prelude hiding (Int, Float) import Prologue hiding (Map) data Array a = Array { arraySize :: Maybe a, arrayElementType :: a } @@ -126,3 +127,35 @@ instance Show1 TypeParameters where liftShowsPrec = genericLiftShowsPrec -- TODO: Implement Eval instance for TypeParameters instance Evaluatable TypeParameters + +-- data instead of newtype because no payload +data Void a = Void + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 Void where liftEq = genericLiftEq +instance Ord1 Void where liftCompare = genericLiftCompare +instance Show1 Void where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for Void +instance Evaluatable Void + +-- data instead of newtype because no payload +data Int a = Int + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 Int where liftEq = genericLiftEq +instance Ord1 Int where liftCompare = genericLiftCompare +instance Show1 Int where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for Int +instance Evaluatable Int + +data Float a = Float | Double + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 Float where liftEq = genericLiftEq +instance Ord1 Float where liftCompare = genericLiftCompare +instance Show1 Float where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for Float +instance Evaluatable Float diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 7527927d4..4ace5460d 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -8,7 +8,7 @@ module Language.Java.Assignment import Assigning.Assignment hiding (Assignment, Error) import Data.Abstract.FreeVariables -import Data.Functor (void) +import Data.Functor (void, ($>)) import Data.List.NonEmpty (some1) import Data.Record import Data.Semigroup @@ -29,13 +29,21 @@ import qualified Data.Term as Term type Syntax = '[ Comment.Comment + , Declaration.Class + , Declaration.Method , Literal.Integer , Literal.String , Literal.TextElement , Syntax.Context , Syntax.Empty , Syntax.Error + , Syntax.Identifier , Syntax.Program + , Type.Int + , Type.Void + , Type.Float + , Type.Annotation + , Statement.Return , [] ] @@ -62,7 +70,11 @@ expression = handleError (choice expressionChoices) expressionChoices :: [Assignment.Assignment [] Grammar Term] expressionChoices = [ - integer + class' + , identifier + , integer + , method + , return' , string ] @@ -74,3 +86,24 @@ integer = makeTerm <$> symbol IntegerLiteral <*> children (symbol DecimalInteger string :: Assignment string = makeTerm <$> symbol StringLiteral <*> (Literal.TextElement <$> source) + +class' :: Assignment +class' = makeTerm <$> symbol ClassDeclaration <*> children (Declaration.Class [] <$> term identifier <*> pure [] <*> classBody) + where classBody = makeTerm <$> symbol ClassBody <*> children (manyTerm expression) + +identifier :: Assignment +identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier <$> (name <$> source)) + +method :: Assignment +method = makeTerm <$> symbol MethodDeclaration <*> children ((method <$ symbol MethodHeader <*> emptyTerm <*> children ((,) <$> type' <* symbol MethodDeclarator <*> children ( (,) <$> identifier <*> manyTerm parameter)) ) <* symbol MethodBody <*> children (makeTerm <$> symbol Block <*> children (manyTerm expression))) + where method receiver (returnType, (name, params)) body = Declaration.Method [returnType] receiver name params body + parameter = makeTerm <$> symbol FormalParameter <*> children (flip Type.Annotation <$> type' <* symbol VariableDeclaratorId <*> children identifier) +-- TODO: re-introduce makeTerm later; matching types as part of the type rule for now + +return' :: Assignment +return' = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> expression) + +type' :: Assignment +type' = makeTerm <$> token VoidType <*> pure Type.Void + <|> makeTerm <$> token IntegralType <*> pure Type.Int + <|> makeTerm <$> symbol FloatingPointType <*> children (token AnonFloat $> Type.Float <|> token AnonDouble $> Type.Double) diff --git a/src/Language/Python/Assignment.hs b/src/Language/Python/Assignment.hs index d6268087a..ebe7ab433 100644 --- a/src/Language/Python/Assignment.hs +++ b/src/Language/Python/Assignment.hs @@ -255,7 +255,7 @@ async' :: Assignment async' = makeTerm <$> symbol AnonAsync <*> (Syntax.Identifier <$> (name <$> source)) classDefinition :: Assignment -classDefinition = makeTerm <$> symbol ClassDefinition <*> children (Declaration.Class <$> pure [] <*> term expression <*> argumentList <*> expressions) +classDefinition = makeTerm <$> symbol ClassDefinition <*> children (Declaration.Class [] <$> term expression <*> argumentList <*> expressions) where argumentList = symbol ArgumentList *> children (manyTerm expression) <|> pure [] diff --git a/src/Language/Ruby/Assignment.hs b/src/Language/Ruby/Assignment.hs index 8157e9262..f59103f6c 100644 --- a/src/Language/Ruby/Assignment.hs +++ b/src/Language/Ruby/Assignment.hs @@ -223,7 +223,7 @@ parameter = where mk s = makeTerm <$> symbol s <*> (Syntax.Identifier <$> (name <$> source)) method :: Assignment -method = makeTerm <$> symbol Method <*> children (Declaration.Method <$> pure [] <*> emptyTerm <*> expression <*> params <*> expressions') +method = makeTerm <$> symbol Method <*> children (Declaration.Method [] <$> emptyTerm <*> expression <*> params <*> expressions') where params = symbol MethodParameters *> children (many parameter) <|> pure [] expressions' = makeTerm <$> location <*> many expression From dde7369479087746737019567ffa5ec0550133c9 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 10 Apr 2018 14:04:46 -0700 Subject: [PATCH 17/68] bump haskell tree-sitter --- vendor/haskell-tree-sitter | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vendor/haskell-tree-sitter b/vendor/haskell-tree-sitter index c1f988d8b..9df64df87 160000 --- a/vendor/haskell-tree-sitter +++ b/vendor/haskell-tree-sitter @@ -1 +1 @@ -Subproject commit c1f988d8b211c24bf7b22c19084a1df47dfe9b7a +Subproject commit 9df64df8764060cb09daad1460da0094d30727a0 From 372e1aef8cabf5db8afc4dab15fd39f57d1e849e Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 10 Apr 2018 14:05:24 -0700 Subject: [PATCH 18/68] WIP variable declarations --- src/Language/Java/Assignment.hs | 62 ++++++++++++++++++++++++++++----- src/Language/Java/Syntax.hs | 15 ++++++++ 2 files changed, 69 insertions(+), 8 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 4ace5460d..786c951c7 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -16,7 +16,7 @@ import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTer import Data.Union import GHC.Stack import Language.Java.Grammar as Grammar -import Language.Java.Syntax as Syntax +import Language.Java.Syntax as Java.Syntax import qualified Assigning.Assignment as Assignment import qualified Data.Syntax as Syntax import qualified Data.Syntax.Comment as Comment @@ -31,13 +31,18 @@ type Syntax = '[ Comment.Comment , Declaration.Class , Declaration.Method + , Declaration.VariableDeclaration + , Java.Syntax.ArrayType + , Literal.Array , Literal.Integer , Literal.String , Literal.TextElement + , Statement.Assignment , Syntax.Context , Syntax.Empty , Syntax.Error , Syntax.Identifier + , Syntax.AccessibilityModifier , Syntax.Program , Type.Int , Type.Void @@ -70,40 +75,81 @@ expression = handleError (choice expressionChoices) expressionChoices :: [Assignment.Assignment [] Grammar Term] expressionChoices = [ - class' + array_initializer + , char + , class' + , constantDeclaration , identifier , integer , method , return' , string + , local_variable_declaration_statement ] +modifier :: Assignment +modifier = makeTerm <$> symbol Modifier <*> (Syntax.AccessibilityModifier <$> source) + +array_initializer :: Assignment +array_initializer = makeTerm <$> symbol ArrayInitializer <*> (Literal.Array <$> many expression) + comment :: Assignment comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) +-- constantDeclaration :: Assignment +-- constantDeclaration = makeTerm <$> symbol ConstantDeclaration <*> + +-- TODO: Rename these to be conventionally namned functions (camelCase ) +local_variable_declaration :: Assignment +local_variable_declaration = makeDecl <$> symbol LocalVariableDeclaration <*> many type' <*> children (Declaration.VariableDeclaration <$> vDeclList) + where + makeSingleDecl loc types (target, value) = makeTerm loc (Statement.Assignment types target value) + makeDecl loc types decls = fmap (makeSingleDecl loc types) decls + vDeclList = symbol VariableDeclaratorList *> children (many variableDeclarator) + variableDeclarator = makeTerm <$> symbol VariableDeclarator <*> ((,) <*> variable_declarator_id <*> expression) + +local_variable_declaration_statement :: Assignment +local_variable_declaration_statement = makeTerm <$> symbol LocalVariableDeclarationStatement <*> children (many local_variable_declaration) + +unannotated_type :: Assignment +unannotated_type = makeTerm <$> symbol Grammar.ArrayType <*> (Java.Syntax.ArrayType <$> source) + +variable_declarator_id :: Assignment +variable_declarator_id = makeTerm <$> symbol VariableDeclaratorId <*> (Syntax.Identifier <$> (name <$> source)) + + + integer :: Assignment integer = makeTerm <$> symbol IntegerLiteral <*> children (symbol DecimalIntegerLiteral >> Literal.Integer <$> source) string :: Assignment string = makeTerm <$> symbol StringLiteral <*> (Literal.TextElement <$> source) +char :: Assignment +char = makeTerm <$> symbol CharacterLiteral <*> (Literal.TextElement <$> source) + class' :: Assignment -class' = makeTerm <$> symbol ClassDeclaration <*> children (Declaration.Class [] <$> term identifier <*> pure [] <*> classBody) +class' = makeTerm <$> symbol ClassDeclaration <*> children (Declaration.Class <$> many modifier <*> term identifier <*> pure [] <*> classBody) where classBody = makeTerm <$> symbol ClassBody <*> children (manyTerm expression) identifier :: Assignment identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier <$> (name <$> source)) method :: Assignment -method = makeTerm <$> symbol MethodDeclaration <*> children ((method <$ symbol MethodHeader <*> emptyTerm <*> children ((,) <$> type' <* symbol MethodDeclarator <*> children ( (,) <$> identifier <*> manyTerm parameter)) ) <* symbol MethodBody <*> children (makeTerm <$> symbol Block <*> children (manyTerm expression))) - where method receiver (returnType, (name, params)) body = Declaration.Method [returnType] receiver name params body +method = makeTerm <$> symbol MethodDeclaration <*> children ( + (makeMethod <$> many modifier <* symbol MethodHeader <*> emptyTerm <*> children ((,) <$> type' <* symbol MethodDeclarator <*> children ( (,) <$> identifier <*> manyTerm parameter)) ) + <* symbol MethodBody <*> children (makeTerm <$> symbol Block <*> children (manyTerm expression)) + ) + where makeMethod modifiers receiver (returnType, (name, params)) body = Declaration.Method (returnType : modifiers) receiver name params body parameter = makeTerm <$> symbol FormalParameter <*> children (flip Type.Annotation <$> type' <* symbol VariableDeclaratorId <*> children identifier) + -- TODO: re-introduce makeTerm later; matching types as part of the type rule for now return' :: Assignment return' = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> expression) type' :: Assignment -type' = makeTerm <$> token VoidType <*> pure Type.Void - <|> makeTerm <$> token IntegralType <*> pure Type.Int - <|> makeTerm <$> symbol FloatingPointType <*> children (token AnonFloat $> Type.Float <|> token AnonDouble $> Type.Double) +type' = makeTerm <$> token VoidType <*> pure Type.Void + <|> makeTerm <$> token IntegralType <*> pure Type.Int + <|> makeTerm <$> token FloatingPointType <*> pure Type.Float + -- <|> makeTerm <$> symbol FloatingPointType <*> children (token AnonFloat $> Type.Float <|> token AnonDouble $> Type.Double) diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index 89c3a73af..ab927d675 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -1 +1,16 @@ +{-# LANGUAGE DeriveAnyClass #-} module Language.Java.Syntax where + +import Data.Abstract.Evaluatable hiding (Label) +import Diffing.Algorithm +import Prologue + +newtype ArrayType a = ArrayType ByteString + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + +instance Eq1 ArrayType where liftEq = genericLiftEq +instance Ord1 ArrayType where liftCompare = genericLiftCompare +instance Show1 ArrayType where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for ArrayType +instance Evaluatable ArrayType From 6fa9b185af05539239620df4c856ecb9e1a09d9c Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 10 Apr 2018 14:52:27 -0700 Subject: [PATCH 19/68] add assignment for variableDeclarator --- src/Language/Java/Assignment.hs | 21 ++++++++++++++------- 1 file changed, 14 insertions(+), 7 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 786c951c7..b24e925a4 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -35,6 +35,7 @@ type Syntax = , Java.Syntax.ArrayType , Literal.Array , Literal.Integer + , Literal.Float , Literal.String , Literal.TextElement , Statement.Assignment @@ -78,9 +79,10 @@ expressionChoices = array_initializer , char , class' - , constantDeclaration + -- , constantDeclaration , identifier , integer + , float , method , return' , string @@ -101,27 +103,32 @@ comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) -- TODO: Rename these to be conventionally namned functions (camelCase ) local_variable_declaration :: Assignment -local_variable_declaration = makeDecl <$> symbol LocalVariableDeclaration <*> many type' <*> children (Declaration.VariableDeclaration <$> vDeclList) +local_variable_declaration = makeDecl <$> symbol LocalVariableDeclaration <*> children ((,) <$> some type' <*> vDeclList) where makeSingleDecl loc types (target, value) = makeTerm loc (Statement.Assignment types target value) - makeDecl loc types decls = fmap (makeSingleDecl loc types) decls - vDeclList = symbol VariableDeclaratorList *> children (many variableDeclarator) - variableDeclarator = makeTerm <$> symbol VariableDeclarator <*> ((,) <*> variable_declarator_id <*> expression) + makeDecl loc (types, decls) = makeTerm loc $ fmap (makeSingleDecl loc types) decls + -- makeImportTerm loc ([x], from) = makeImportTerm1 loc from x + -- makeImportTerm loc (xs, from) = makeTerm loc $ fmap (makeImportTerm1 loc from) xs + vDeclList = symbol VariableDeclaratorList *> children (some variableDeclarator) + variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variable_declarator_id <*> expression) local_variable_declaration_statement :: Assignment -local_variable_declaration_statement = makeTerm <$> symbol LocalVariableDeclarationStatement <*> children (many local_variable_declaration) +local_variable_declaration_statement = symbol LocalVariableDeclarationStatement *> children local_variable_declaration unannotated_type :: Assignment unannotated_type = makeTerm <$> symbol Grammar.ArrayType <*> (Java.Syntax.ArrayType <$> source) variable_declarator_id :: Assignment -variable_declarator_id = makeTerm <$> symbol VariableDeclaratorId <*> (Syntax.Identifier <$> (name <$> source)) +variable_declarator_id = symbol VariableDeclaratorId *> children identifier integer :: Assignment integer = makeTerm <$> symbol IntegerLiteral <*> children (symbol DecimalIntegerLiteral >> Literal.Integer <$> source) +float :: Assignment +float = makeTerm <$> symbol FloatingPointLiteral <*> (Literal.Float <$> source) + string :: Assignment string = makeTerm <$> symbol StringLiteral <*> (Literal.TextElement <$> source) From 9026c1d9f31136bab1b3ed39cd42ca5688e0395c Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Thu, 12 Apr 2018 11:47:56 -0700 Subject: [PATCH 20/68] add null literal --- src/Data/Syntax/Type.hs | 11 +++++++++-- src/Language/Java/Assignment.hs | 18 ++++++++++++++++-- 2 files changed, 25 insertions(+), 4 deletions(-) diff --git a/src/Data/Syntax/Type.hs b/src/Data/Syntax/Type.hs index f25ff7017..8430e4e10 100644 --- a/src/Data/Syntax/Type.hs +++ b/src/Data/Syntax/Type.hs @@ -3,7 +3,7 @@ module Data.Syntax.Type where import Data.Abstract.Evaluatable import Diffing.Algorithm -import Prelude hiding (Int, Float) +import Prelude hiding (Int, Float, Bool) import Prologue hiding (Map) data Array a = Array { arraySize :: Maybe a, arrayElementType :: a } @@ -157,5 +157,12 @@ instance Eq1 Float where liftEq = genericLiftEq instance Ord1 Float where liftCompare = genericLiftCompare instance Show1 Float where liftShowsPrec = genericLiftShowsPrec +data Bool a = Bool + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 Bool where liftEq = genericLiftEq +instance Ord1 Bool where liftCompare = genericLiftCompare +instance Show1 Bool where liftShowsPrec = genericLiftShowsPrec + -- TODO: Implement Eval instance for Float -instance Evaluatable Float +instance Evaluatable Bool diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index b24e925a4..0fc7cebea 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -34,8 +34,10 @@ type Syntax = , Declaration.VariableDeclaration , Java.Syntax.ArrayType , Literal.Array + , Literal.Boolean , Literal.Integer , Literal.Float + , Literal.Null , Literal.String , Literal.TextElement , Statement.Assignment @@ -45,6 +47,7 @@ type Syntax = , Syntax.Identifier , Syntax.AccessibilityModifier , Syntax.Program + , Type.Bool , Type.Int , Type.Void , Type.Float @@ -84,6 +87,7 @@ expressionChoices = , integer , float , method + , null' , return' , string , local_variable_declaration_statement @@ -107,8 +111,6 @@ local_variable_declaration = makeDecl <$> symbol LocalVariableDeclaration <*> ch where makeSingleDecl loc types (target, value) = makeTerm loc (Statement.Assignment types target value) makeDecl loc (types, decls) = makeTerm loc $ fmap (makeSingleDecl loc types) decls - -- makeImportTerm loc ([x], from) = makeImportTerm1 loc from x - -- makeImportTerm loc (xs, from) = makeTerm loc $ fmap (makeImportTerm1 loc from) xs vDeclList = symbol VariableDeclaratorList *> children (some variableDeclarator) variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variable_declarator_id <*> expression) @@ -121,7 +123,18 @@ unannotated_type = makeTerm <$> symbol Grammar.ArrayType <*> (Java.Syntax.ArrayT variable_declarator_id :: Assignment variable_declarator_id = symbol VariableDeclaratorId *> children identifier +-- Literals +-- TODO: Need to disaggregate true/false in +boolean :: Assignment +boolean = makeTerm <$> token BooleanLiteral <*> pure Literal.true + +null' :: Assignment +null' = makeTerm <$> symbol NullLiteral <*> (Literal.Null <$ source) +-- +-- boolean :: Assignment +-- boolean = makeTerm <$> token Grammar.True <*> pure Literal.true +-- <|> makeTerm <$> token Grammar.False <*> pure Literal.false integer :: Assignment integer = makeTerm <$> symbol IntegerLiteral <*> children (symbol DecimalIntegerLiteral >> Literal.Integer <$> source) @@ -159,4 +172,5 @@ type' :: Assignment type' = makeTerm <$> token VoidType <*> pure Type.Void <|> makeTerm <$> token IntegralType <*> pure Type.Int <|> makeTerm <$> token FloatingPointType <*> pure Type.Float + <|> makeTerm <$> token BooleanType <*> pure Type.Bool -- <|> makeTerm <$> symbol FloatingPointType <*> children (token AnonFloat $> Type.Float <|> token AnonDouble $> Type.Double) From 527f334ebf2e2010f64e68f22eafe4c24c8d2e54 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Thu, 12 Apr 2018 15:55:42 -0700 Subject: [PATCH 21/68] add assignment for module --- src/Data/Syntax/Literal.hs | 2 -- src/Language/Java/Assignment.hs | 53 ++++++++++++++++++++++----------- src/Language/Java/Syntax.hs | 13 ++++++++ 3 files changed, 49 insertions(+), 19 deletions(-) diff --git a/src/Data/Syntax/Literal.hs b/src/Data/Syntax/Literal.hs index 73b2fdab7..17ff579b7 100644 --- a/src/Data/Syntax/Literal.hs +++ b/src/Data/Syntax/Literal.hs @@ -44,9 +44,7 @@ instance Evaluatable Data.Syntax.Literal.Integer where -- TODO: This instance probably shouldn't have readInteger? eval (Data.Syntax.Literal.Integer x) = integer (maybe 0 fst (readInteger x)) - -- TODO: Should IntegerLiteral hold an Integer instead of a ByteString? --- TODO: Do we care about differentiating between hex/octal/decimal/binary integer literals? -- TODO: Consider a Numeric datatype with FloatingPoint/Integral/etc constructors. -- | A literal float of unspecified width. diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 0fc7cebea..dcd3eb66b 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -33,6 +33,7 @@ type Syntax = , Declaration.Method , Declaration.VariableDeclaration , Java.Syntax.ArrayType + , Java.Syntax.Module , Literal.Array , Literal.Boolean , Literal.Integer @@ -79,25 +80,28 @@ expression = handleError (choice expressionChoices) expressionChoices :: [Assignment.Assignment [] Grammar Term] expressionChoices = [ - array_initializer + arrayInitializer , char , class' -- , constantDeclaration + , float + -- , hexadecimal , identifier , integer - , float , method + , module' , null' , return' , string - , local_variable_declaration_statement + , localVariableDeclaration + , localVariableDeclarationStatement ] modifier :: Assignment modifier = makeTerm <$> symbol Modifier <*> (Syntax.AccessibilityModifier <$> source) -array_initializer :: Assignment -array_initializer = makeTerm <$> symbol ArrayInitializer <*> (Literal.Array <$> many expression) +arrayInitializer :: Assignment +arrayInitializer = makeTerm <$> symbol ArrayInitializer <*> (Literal.Array <$> many expression) comment :: Assignment comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) @@ -105,20 +109,20 @@ comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) -- constantDeclaration :: Assignment -- constantDeclaration = makeTerm <$> symbol ConstantDeclaration <*> --- TODO: Rename these to be conventionally namned functions (camelCase ) -local_variable_declaration :: Assignment -local_variable_declaration = makeDecl <$> symbol LocalVariableDeclaration <*> children ((,) <$> some type' <*> vDeclList) +localVariableDeclaration :: Assignment +localVariableDeclaration = makeDecl <$> symbol LocalVariableDeclaration <*> children ((,) <$> some type' <*> vDeclList) where makeSingleDecl loc types (target, value) = makeTerm loc (Statement.Assignment types target value) makeDecl loc (types, decls) = makeTerm loc $ fmap (makeSingleDecl loc types) decls vDeclList = symbol VariableDeclaratorList *> children (some variableDeclarator) variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variable_declarator_id <*> expression) -local_variable_declaration_statement :: Assignment -local_variable_declaration_statement = symbol LocalVariableDeclarationStatement *> children local_variable_declaration +localVariableDeclarationStatement :: Assignment +localVariableDeclarationStatement = symbol LocalVariableDeclarationStatement *> children localVariableDeclaration -unannotated_type :: Assignment -unannotated_type = makeTerm <$> symbol Grammar.ArrayType <*> (Java.Syntax.ArrayType <$> source) +-- so it's legit to have +unannotatedType :: Assignment +unannotatedType = makeTerm <$> symbol Grammar.ArrayType <*> (Java.Syntax.ArrayType <$> source) variable_declarator_id :: Assignment variable_declarator_id = symbol VariableDeclaratorId *> children identifier @@ -129,19 +133,29 @@ variable_declarator_id = symbol VariableDeclaratorId *> children identifier boolean :: Assignment boolean = makeTerm <$> token BooleanLiteral <*> pure Literal.true -null' :: Assignment -null' = makeTerm <$> symbol NullLiteral <*> (Literal.Null <$ source) --- -- boolean :: Assignment -- boolean = makeTerm <$> token Grammar.True <*> pure Literal.true -- <|> makeTerm <$> token Grammar.False <*> pure Literal.false +null' :: Assignment +null' = makeTerm <$> symbol NullLiteral <*> (Literal.Null <$ source) +-- why is this <$? + integer :: Assignment integer = makeTerm <$> symbol IntegerLiteral <*> children (symbol DecimalIntegerLiteral >> Literal.Integer <$> source) float :: Assignment float = makeTerm <$> symbol FloatingPointLiteral <*> (Literal.Float <$> source) +-- hexadecimalInt :: Assignment +-- hexadecimalInt = makeTerm <$> symbol HexIntegerLiteral <*> (Literal.Integer <$> source) +-- +-- hexadecimalFloat :: Assignment +-- hexadecimalFloat = makeTerm <$> symbol HexFloatingPointLiteral <*> (Literal.Float <$> source) +-- +-- octalInt :: Assignment +-- hexadecimalInt = makeTerm <$> symbol OctalIntegerLiteral <*> (Literal.Integer <$> source) + string :: Assignment string = makeTerm <$> symbol StringLiteral <*> (Literal.TextElement <$> source) @@ -152,8 +166,9 @@ class' :: Assignment class' = makeTerm <$> symbol ClassDeclaration <*> children (Declaration.Class <$> many modifier <*> term identifier <*> pure [] <*> classBody) where classBody = makeTerm <$> symbol ClassBody <*> children (manyTerm expression) +-- consolidated with scopedIdentifier identifier :: Assignment -identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier <$> (name <$> source)) +identifier = makeTerm <$> (symbol Identifier <|> symbol ScopedIdentifier) <*> (Syntax.Identifier . name <$> source) method :: Assignment method = makeTerm <$> symbol MethodDeclaration <*> children ( @@ -162,9 +177,13 @@ method = makeTerm <$> symbol MethodDeclaration <*> children ( ) where makeMethod modifiers receiver (returnType, (name, params)) body = Declaration.Method (returnType : modifiers) receiver name params body parameter = makeTerm <$> symbol FormalParameter <*> children (flip Type.Annotation <$> type' <* symbol VariableDeclaratorId <*> children identifier) - -- TODO: re-introduce makeTerm later; matching types as part of the type rule for now +module' :: Assignment +module' = makeTerm <$> symbol ModuleDeclaration <*> children (Java.Syntax.Module <$> expression <*> many expression) + +importStatement = makeTerm <$> symbol + return' :: Assignment return' = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> expression) diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index ab927d675..170d741f5 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -14,3 +14,16 @@ instance Show1 ArrayType where liftShowsPrec = genericLiftShowsPrec -- TODO: Implement Eval instance for ArrayType instance Evaluatable ArrayType + +data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] } + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 Module where liftEq = genericLiftEq +instance Ord1 Module where liftCompare = genericLiftCompare +instance Show1 Module where liftShowsPrec = genericLiftShowsPrec + +instance Evaluatable Module where + eval (Module iden xs) = do + name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden) + letrec' name $ \addr -> + eval xs <* makeNamespace name addr [] From 07c3f4b4b561a283148db150c85dce934583282e Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Thu, 12 Apr 2018 16:17:54 -0700 Subject: [PATCH 22/68] add assignment for import declarations --- src/Language/Java/Assignment.hs | 5 ++++- src/Language/Java/Syntax.hs | 10 ++++++++++ 2 files changed, 14 insertions(+), 1 deletion(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index dcd3eb66b..12f099946 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -33,6 +33,7 @@ type Syntax = , Declaration.Method , Declaration.VariableDeclaration , Java.Syntax.ArrayType + , Java.Syntax.Import , Java.Syntax.Module , Literal.Array , Literal.Boolean @@ -87,6 +88,7 @@ expressionChoices = , float -- , hexadecimal , identifier + , import' , integer , method , module' @@ -182,7 +184,8 @@ method = makeTerm <$> symbol MethodDeclaration <*> children ( module' :: Assignment module' = makeTerm <$> symbol ModuleDeclaration <*> children (Java.Syntax.Module <$> expression <*> many expression) -importStatement = makeTerm <$> symbol +import' :: Assignment +import' = makeTerm <$> symbol ImportDeclaration <*> children (Java.Syntax.Import <$> some identifier) return' :: Assignment return' = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> expression) diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index 170d741f5..2983d11f5 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -15,6 +15,16 @@ instance Show1 ArrayType where liftShowsPrec = genericLiftShowsPrec -- TODO: Implement Eval instance for ArrayType instance Evaluatable ArrayType +newtype Import a = Import [a] + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + +instance Eq1 Import where liftEq = genericLiftEq +instance Ord1 Import where liftCompare = genericLiftCompare +instance Show1 Import where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for ArrayType +instance Evaluatable Import + data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] } deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) From 8a3f3d4decc5bb0ff181eabf557aeacbad1f9ad5 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Thu, 12 Apr 2018 17:34:04 -0700 Subject: [PATCH 23/68] stub out literals and interface declarations --- src/Language/Java/Assignment.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 12f099946..7616f5151 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -30,6 +30,7 @@ import qualified Data.Term as Term type Syntax = '[ Comment.Comment , Declaration.Class + -- , Declaration.InterfaceDeclaration , Declaration.Method , Declaration.VariableDeclaration , Java.Syntax.ArrayType @@ -87,6 +88,7 @@ expressionChoices = -- , constantDeclaration , float -- , hexadecimal + -- , interface , identifier , import' , integer @@ -122,7 +124,6 @@ localVariableDeclaration = makeDecl <$> symbol LocalVariableDeclaration <*> chil localVariableDeclarationStatement :: Assignment localVariableDeclarationStatement = symbol LocalVariableDeclarationStatement *> children localVariableDeclaration --- so it's legit to have unannotatedType :: Assignment unannotatedType = makeTerm <$> symbol Grammar.ArrayType <*> (Java.Syntax.ArrayType <$> source) @@ -185,7 +186,10 @@ module' :: Assignment module' = makeTerm <$> symbol ModuleDeclaration <*> children (Java.Syntax.Module <$> expression <*> many expression) import' :: Assignment -import' = makeTerm <$> symbol ImportDeclaration <*> children (Java.Syntax.Import <$> some identifier) +import' = makeTerm <$> symbol ImportDeclaration <*> children (Java.Syntax.Import <$> some identifier) + +-- interface :: Assignment +-- interface = makeTerm <$> symbol InterfaceDeclaration <*> (Declaration.InterfaceDeclaration <$> source) return' :: Assignment return' = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> expression) From eb180275474653fc20971a0864c9f7b288d88311 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 13 Apr 2018 16:57:57 -0700 Subject: [PATCH 24/68] assignments for interfaces, packages and hex, binary, octal literals and floats --- src/Language/Java/Assignment.hs | 72 +++++++++++++++++++++++++-------- src/Language/Java/Syntax.hs | 10 +++++ src/Language/Ruby/Assignment.hs | 1 - 3 files changed, 65 insertions(+), 18 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 7616f5151..7869c3a5c 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -30,12 +30,13 @@ import qualified Data.Term as Term type Syntax = '[ Comment.Comment , Declaration.Class - -- , Declaration.InterfaceDeclaration + , Declaration.InterfaceDeclaration , Declaration.Method , Declaration.VariableDeclaration , Java.Syntax.ArrayType , Java.Syntax.Import , Java.Syntax.Module + , Java.Syntax.Package , Literal.Array , Literal.Boolean , Literal.Integer @@ -79,6 +80,9 @@ term term = contextualize comment (postContextualize comment term) expression :: Assignment expression = handleError (choice expressionChoices) +expressions :: Assignment +expressions = makeTerm'' <$> location <*> many expression + expressionChoices :: [Assignment.Assignment [] Grammar Term] expressionChoices = [ @@ -88,13 +92,14 @@ expressionChoices = -- , constantDeclaration , float -- , hexadecimal - -- , interface + , interface , identifier , import' , integer , method , module' , null' + , package , return' , string , localVariableDeclaration @@ -132,7 +137,7 @@ variable_declarator_id = symbol VariableDeclaratorId *> children identifier -- Literals --- TODO: Need to disaggregate true/false in +-- TODO: Need to disaggregate true/false in treesitter boolean :: Assignment boolean = makeTerm <$> token BooleanLiteral <*> pure Literal.true @@ -144,20 +149,12 @@ null' :: Assignment null' = makeTerm <$> symbol NullLiteral <*> (Literal.Null <$ source) -- why is this <$? +-- Supports all integer and floating point literals (hex, octal, binary) integer :: Assignment -integer = makeTerm <$> symbol IntegerLiteral <*> children (symbol DecimalIntegerLiteral >> Literal.Integer <$> source) +integer = makeTerm <$> symbol IntegerLiteral <*> children (Literal.Integer <$> source) float :: Assignment -float = makeTerm <$> symbol FloatingPointLiteral <*> (Literal.Float <$> source) - --- hexadecimalInt :: Assignment --- hexadecimalInt = makeTerm <$> symbol HexIntegerLiteral <*> (Literal.Integer <$> source) --- --- hexadecimalFloat :: Assignment --- hexadecimalFloat = makeTerm <$> symbol HexFloatingPointLiteral <*> (Literal.Float <$> source) --- --- octalInt :: Assignment --- hexadecimalInt = makeTerm <$> symbol OctalIntegerLiteral <*> (Literal.Integer <$> source) +float = makeTerm <$> symbol FloatingPointLiteral <*> children (Literal.Float <$> source) string :: Assignment string = makeTerm <$> symbol StringLiteral <*> (Literal.TextElement <$> source) @@ -180,7 +177,7 @@ method = makeTerm <$> symbol MethodDeclaration <*> children ( ) where makeMethod modifiers receiver (returnType, (name, params)) body = Declaration.Method (returnType : modifiers) receiver name params body parameter = makeTerm <$> symbol FormalParameter <*> children (flip Type.Annotation <$> type' <* symbol VariableDeclaratorId <*> children identifier) --- TODO: re-introduce makeTerm later; matching types as part of the type rule for now +-- TODO: re-introduce makeTerm later; matching types as part of the type rule for now. module' :: Assignment module' = makeTerm <$> symbol ModuleDeclaration <*> children (Java.Syntax.Module <$> expression <*> many expression) @@ -188,8 +185,16 @@ module' = makeTerm <$> symbol ModuleDeclaration <*> children (Java.Syntax.Module import' :: Assignment import' = makeTerm <$> symbol ImportDeclaration <*> children (Java.Syntax.Import <$> some identifier) --- interface :: Assignment --- interface = makeTerm <$> symbol InterfaceDeclaration <*> (Declaration.InterfaceDeclaration <$> source) +interface :: Assignment +interface = makeTerm <$> symbol InterfaceDeclaration <*> children (normal <|> annotationType) + where + interfaceBody = makeTerm <$> symbol InterfaceBody <*> children (many expression) + normal = symbol NormalInterfaceDeclaration *> children (Declaration.InterfaceDeclaration [] <$> identifier <*> interfaceBody) + annotationType = symbol AnnotationTypeDeclaration *> children (Declaration.InterfaceDeclaration [] <$> identifier <*> annotationTypeBody) + annotationTypeBody = makeTerm <$> symbol AnnotationTypeBody <*> children (many expression) + +package :: Assignment +package = makeTerm <$> symbol PackageDeclaration <*> children (Java.Syntax.Package <$> some identifier) return' :: Assignment return' = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> expression) @@ -200,3 +205,36 @@ type' = makeTerm <$> token VoidType <*> pure Type.Void <|> makeTerm <$> token FloatingPointType <*> pure Type.Float <|> makeTerm <$> token BooleanType <*> pure Type.Bool -- <|> makeTerm <$> symbol FloatingPointType <*> children (token AnonFloat $> Type.Float <|> token AnonDouble $> Type.Double) + +-- method expressions + +-- TODO: consolidate ifthen and ifthenelse in grammar +-- if' :: Assignment +-- if' = makeTerm <$> symbol Conditional <*> children (Statement.If <$> expression <*> expression <*> expression) +-- +-- if' :: Assignment +-- if' = makeTerm <$> symbol IfThenStatement <*> children (Statement.If <$> expression <*> expression <*> (else' <|> emptyTerm)) +-- <|> makeTerm +-- +-- else' :: Assignment +-- else' = makeTerm <$> symbol IfThenElseStatement <*> children + +-- from Ruby +-- if' :: Assignment +-- if' = ifElsif If +-- <|> makeTerm <$> symbol IfModifier <*> children (flip Statement.If <$> expression <*> expression <*> emptyTerm) +-- where +-- ifElsif s = makeTerm <$> symbol s <*> children (Statement.If <$> expression <*> expressions' <*> (elsif' <|> else' <|> emptyTerm)) +-- expressions' = makeTerm <$> location <*> manyTermsTill expression (void (symbol Else) <|> void (symbol Elsif) <|> eof) +-- elsif' = postContextualize comment (ifElsif Elsif) +-- else' = postContextualize comment (symbol Else *> children expressions) +-- +-- for :: Assignment +-- for = makeTerm <$> symbol For <*> children (Statement.ForEach <$> (makeTerm <$> location <*> manyTermsTill expression (symbol In)) <*> inClause <*> expressions) +-- where inClause = symbol In *> children expression + +-- expression + +-- infix operators +-- binary :: Assignment +-- binary = makeTerm diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index 2983d11f5..a34ab1d8c 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -37,3 +37,13 @@ instance Evaluatable Module where name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden) letrec' name $ \addr -> eval xs <* makeNamespace name addr [] + +newtype Package a = Package [a] + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + +instance Eq1 Package where liftEq = genericLiftEq +instance Ord1 Package where liftCompare = genericLiftCompare +instance Show1 Package where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for ArrayType +instance Evaluatable Package diff --git a/src/Language/Ruby/Assignment.hs b/src/Language/Ruby/Assignment.hs index ee8455094..ecffacf32 100644 --- a/src/Language/Ruby/Assignment.hs +++ b/src/Language/Ruby/Assignment.hs @@ -417,7 +417,6 @@ conditional = makeTerm <$> symbol Conditional <*> children (Statement.If <$> exp emptyStatement :: Assignment emptyStatement = makeTerm <$> symbol EmptyStatement <*> (Syntax.Empty <$ source <|> pure Syntax.Empty) - -- Helper functions invert :: Assignment -> Assignment From 759181c3a76d7c00a76e5806c8ffd5a34a8fa353 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 17 Apr 2018 16:45:51 -0700 Subject: [PATCH 25/68] assignments for enum, if, block, while, doWhile, switch, break, continue, throw, try-catch --- src/Language/Java/Assignment.hs | 139 +++++++++++++++++++++++++------- src/Language/Java/Syntax.hs | 8 ++ vendor/haskell-tree-sitter | 2 +- 3 files changed, 117 insertions(+), 32 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 7869c3a5c..ea6763585 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -6,7 +6,7 @@ module Language.Java.Assignment , Term ) where -import Assigning.Assignment hiding (Assignment, Error) +import Assigning.Assignment hiding (Assignment, Error, while, try) import Data.Abstract.FreeVariables import Data.Functor (void, ($>)) import Data.List.NonEmpty (some1) @@ -26,6 +26,7 @@ import qualified Data.Syntax.Literal as Literal import qualified Data.Syntax.Statement as Statement import qualified Data.Syntax.Type as Type import qualified Data.Term as Term +import Prelude hiding (break) type Syntax = '[ Comment.Comment @@ -34,6 +35,7 @@ type Syntax = , Declaration.Method , Declaration.VariableDeclaration , Java.Syntax.ArrayType + , Java.Syntax.EnumDeclaration , Java.Syntax.Import , Java.Syntax.Module , Java.Syntax.Package @@ -45,6 +47,17 @@ type Syntax = , Literal.String , Literal.TextElement , Statement.Assignment + , Statement.Break + , Statement.Catch + , Statement.Continue + , Statement.DoWhile + , Statement.Finally + , Statement.If + , Statement.Match + , Statement.Pattern + , Statement.While + , Statement.Throw + , Statement.Try , Syntax.Context , Syntax.Empty , Syntax.Error @@ -76,9 +89,12 @@ someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Conte term :: Assignment -> Assignment term term = contextualize comment (postContextualize comment term) +-- matches comments before and after the node expression :: Assignment expression = handleError (choice expressionChoices) +-- "expression" +-- choice walks the expressionChoices and inserts <|> (notionally but not really lol) expressions :: Assignment expressions = makeTerm'' <$> location <*> many expression @@ -87,11 +103,18 @@ expressionChoices :: [Assignment.Assignment [] Grammar Term] expressionChoices = [ arrayInitializer + , block + , boolean + , break , char , class' + , continue -- , constantDeclaration + , doWhile , float + , enum -- , hexadecimal + , if' , interface , identifier , import' @@ -102,9 +125,15 @@ expressionChoices = , package , return' , string + , switch + , throw + , try , localVariableDeclaration , localVariableDeclarationStatement + , while ] + -- adding something to expressionChoices list is useful because expression (above) uses expressionChoices, and so + -- it is available to form assignments when we encounter any of those terms modifier :: Assignment modifier = makeTerm <$> symbol Modifier <*> (Syntax.AccessibilityModifier <$> source) @@ -139,11 +168,11 @@ variable_declarator_id = symbol VariableDeclaratorId *> children identifier -- TODO: Need to disaggregate true/false in treesitter boolean :: Assignment -boolean = makeTerm <$> token BooleanLiteral <*> pure Literal.true +boolean = makeTerm <$> symbol BooleanLiteral <*> children + (token Grammar.True $> Literal.true + <|> token Grammar.False $> Literal.false) --- boolean :: Assignment --- boolean = makeTerm <$> token Grammar.True <*> pure Literal.true --- <|> makeTerm <$> token Grammar.False <*> pure Literal.false +-- *> pure = $> null' :: Assignment null' = makeTerm <$> symbol NullLiteral <*> (Literal.Null <$ source) @@ -168,7 +197,7 @@ class' = makeTerm <$> symbol ClassDeclaration <*> children (Declaration.Class <$ -- consolidated with scopedIdentifier identifier :: Assignment -identifier = makeTerm <$> (symbol Identifier <|> symbol ScopedIdentifier) <*> (Syntax.Identifier . name <$> source) +identifier = makeTerm <$> (symbol Identifier <|> symbol ScopedIdentifier <|> symbol TypeIdentifier) <*> (Syntax.Identifier . name <$> source) method :: Assignment method = makeTerm <$> symbol MethodDeclaration <*> children ( @@ -196,39 +225,87 @@ interface = makeTerm <$> symbol InterfaceDeclaration <*> children (normal <|> an package :: Assignment package = makeTerm <$> symbol PackageDeclaration <*> children (Java.Syntax.Package <$> some identifier) +enum :: Assignment +enum = makeTerm <$> symbol Grammar.EnumDeclaration <*> children (Java.Syntax.EnumDeclaration <$> term identifier <*> manyTerm enumConstant) + where enumConstant = symbol EnumConstant *> children (term identifier) +-- list of 0 or more +-- Java.Syntax.EnumDeclaration is taking something that has been matched and applying a function over it +-- makeTerm (a function) is not matching, but rather mapping over a matched term +-- makeTerm is lifted into the <$> functor, which is applied to the result of its child assignments +-- <*> apply is used when you've got a function built up on the LHS +-- we don't have a makeTerm, so we don't have a function on the LHS to apply <*>, hence we just match on the symbol EnumConstant, and use it as a marker to descend into children +-- we want the effect, not the result, of symbol because we want to match the EnumConstant node without caring about its range or span +-- we don't care about the range and span because the identifier rule produces a term which already has a range and span +-- show only has one argument, so we don't need to <*> because when we fmap it over a list, it's fully applied +-- term = also accounts for preceding comments +-- (+) <$> [1,2,3] :: Num a => [a -> a] -- it is a function that takes one number and returns another number of the same type + return' :: Assignment -return' = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> expression) +return' = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children (expression)) +-- can move the children into or out of the fmap rule because the children expression returns the result of a child +-- so if you fmap over the result of RHS it's equivalent +-- if you f <$> (g <$> a) == f . g <$> a (fusion law) +-- if you have two nested fmaps, same as composing type' :: Assignment -type' = makeTerm <$> token VoidType <*> pure Type.Void - <|> makeTerm <$> token IntegralType <*> pure Type.Int - <|> makeTerm <$> token FloatingPointType <*> pure Type.Float - <|> makeTerm <$> token BooleanType <*> pure Type.Bool +type' = choice [ + makeTerm <$> token VoidType <*> pure Type.Void + , makeTerm <$> token IntegralType <*> pure Type.Int + , makeTerm <$> token FloatingPointType <*> pure Type.Float + , makeTerm <$> token BooleanType <*> pure Type.Bool + , symbol CatchType *> children (term type') + , identifier + ] -- <|> makeTerm <$> symbol FloatingPointType <*> children (token AnonFloat $> Type.Float <|> token AnonDouble $> Type.Double) + -- we had to say token with the first 4 because pure don't advance past the first nodes; implies no effect, just produces value + -- if we want to match a node and consume that node (which we have to do) we need to use token because it has that behavior -- method expressions --- TODO: consolidate ifthen and ifthenelse in grammar --- if' :: Assignment --- if' = makeTerm <$> symbol Conditional <*> children (Statement.If <$> expression <*> expression <*> expression) --- --- if' :: Assignment --- if' = makeTerm <$> symbol IfThenStatement <*> children (Statement.If <$> expression <*> expression <*> (else' <|> emptyTerm)) --- <|> makeTerm --- --- else' :: Assignment --- else' = makeTerm <$> symbol IfThenElseStatement <*> children +if' :: Assignment +if' = makeTerm <$> symbol IfThenElseStatement <*> children (Statement.If <$> term expression <*> term expression <*> (term expression <|> emptyTerm)) + +block :: Assignment +block = makeTerm <$> symbol Block <*> children (manyTerm expression) + +while :: Assignment +while = makeTerm <$> symbol WhileStatement <*> children (Statement.While <$> term expression <*> term expression) + +doWhile :: Assignment +doWhile = makeTerm <$> symbol DoStatement <*> children (flip Statement.DoWhile <$> term expression <*> term expression) +-- flipping so when we match body it goes into second field and when we match condition it goes into the first field + +switch :: Assignment +switch = makeTerm <$> symbol SwitchStatement <*> children (Statement.Match <$> term expression <*> switchBlock) + where + switchBlock = makeTerm <$> symbol SwitchBlock <*> children (manyTerm switchLabel) + switchLabel = makeTerm <$> symbol SwitchLabel <*> (Statement.Pattern <$> children (term expression <|> emptyTerm) <*> expressions) +-- not identifier, expression + +break :: Assignment +break = makeTerm <$> symbol BreakStatement <*> children (Statement.Break <$> (term expression <|> emptyTerm)) +-- manyTerm matches 0 or more and also produces a list +-- term expression <|> emptyTerm accounts for an expression or nothing at all + +continue :: Assignment +continue = makeTerm <$> symbol ContinueStatement <*> children (Statement.Continue <$> (term expression <|> emptyTerm)) + +throw :: Assignment +throw = makeTerm <$> symbol ThrowStatement <*> children (Statement.Throw <$> term expression) + +try :: Assignment +try = makeTerm <$> symbol TryStatement <*> children (Statement.Try <$> term expression <*> (append <$> optional catches <*> optional finally)) + where + catches = symbol Catches *> children (manyTerm catch) + catch = makeTerm <$> symbol CatchClause <*> children (Statement.Catch <$> catchFormalParameter <*> term expression) + catchFormalParameter = makeTerm <$> symbol CatchFormalParameter <*> children (flip Type.Annotation <$> type' <* symbol VariableDeclaratorId <*> children identifier) + finally = makeTerm <$> symbol Finally <*> children (Statement.Finally <$> term expression) + -- append catches finally = + append Nothing Nothing = [] + append Nothing (Just a) = [a] + append (Just a) Nothing = a + append (Just a) (Just b) = a <> [b] --- from Ruby --- if' :: Assignment --- if' = ifElsif If --- <|> makeTerm <$> symbol IfModifier <*> children (flip Statement.If <$> expression <*> expression <*> emptyTerm) --- where --- ifElsif s = makeTerm <$> symbol s <*> children (Statement.If <$> expression <*> expressions' <*> (elsif' <|> else' <|> emptyTerm)) --- expressions' = makeTerm <$> location <*> manyTermsTill expression (void (symbol Else) <|> void (symbol Elsif) <|> eof) --- elsif' = postContextualize comment (ifElsif Elsif) --- else' = postContextualize comment (symbol Else *> children expressions) --- -- for :: Assignment -- for = makeTerm <$> symbol For <*> children (Statement.ForEach <$> (makeTerm <$> location <*> manyTermsTill expression (symbol In)) <*> inClause <*> expressions) -- where inClause = symbol In *> children expression diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index a34ab1d8c..e8053ff88 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -47,3 +47,11 @@ instance Show1 Package where liftShowsPrec = genericLiftShowsPrec -- TODO: Implement Eval instance for ArrayType instance Evaluatable Package + +data EnumDeclaration a = EnumDeclaration { _enumDeclarationIdentifier :: !a, _enumDeclarationBody :: ![a] } + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 EnumDeclaration where liftEq = genericLiftEq +instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare +instance Show1 EnumDeclaration where liftShowsPrec = genericLiftShowsPrec +instance Evaluatable EnumDeclaration diff --git a/vendor/haskell-tree-sitter b/vendor/haskell-tree-sitter index 9df64df87..ab0654689 160000 --- a/vendor/haskell-tree-sitter +++ b/vendor/haskell-tree-sitter @@ -1 +1 @@ -Subproject commit 9df64df8764060cb09daad1460da0094d30727a0 +Subproject commit ab06546890d140fd8fd725e3536d0e9d434226a0 From 4c90a412de0d090fa981f8f9925181eddbc1c3e7 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Wed, 18 Apr 2018 13:16:56 -0700 Subject: [PATCH 26/68] terrifying magic to finally get for statement assignments --- src/Language/Java/Assignment.hs | 36 ++++++++++++++++++++++++++------- src/Language/Java/Syntax.hs | 11 ++++++++++ src/Language/Ruby/Assignment.hs | 1 + 3 files changed, 41 insertions(+), 7 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index ea6763585..2f9b68f66 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -39,6 +39,7 @@ type Syntax = , Java.Syntax.Import , Java.Syntax.Module , Java.Syntax.Package + , Java.Syntax.Variable , Literal.Array , Literal.Boolean , Literal.Integer @@ -52,6 +53,7 @@ type Syntax = , Statement.Continue , Statement.DoWhile , Statement.Finally + , Statement.For , Statement.If , Statement.Match , Statement.Pattern @@ -84,6 +86,13 @@ assignment = handleError $ makeTerm <$> symbol Grammar.Program <*> children (Syn manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) +-- | Match a series of terms or comments until a delimiter is matched +manyTermsTill :: Assignment.Assignment [] Grammar Term + -> Assignment.Assignment [] Grammar b + -> Assignment.Assignment [] Grammar [Term] +manyTermsTill step end = manyTill (step <|> comment) end +-- used in cases where the rules overlap, ie., step <|> comment and end can overlap + someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) @@ -112,6 +121,7 @@ expressionChoices = -- , constantDeclaration , doWhile , float + , for , enum -- , hexadecimal , if' @@ -148,12 +158,14 @@ comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) -- constantDeclaration = makeTerm <$> symbol ConstantDeclaration <*> localVariableDeclaration :: Assignment -localVariableDeclaration = makeDecl <$> symbol LocalVariableDeclaration <*> children ((,) <$> some type' <*> vDeclList) +localVariableDeclaration = makeDecl <$> symbol LocalVariableDeclaration <*> children ((,) <$> type' <*> vDeclList) where - makeSingleDecl loc types (target, value) = makeTerm loc (Statement.Assignment types target value) - makeDecl loc (types, decls) = makeTerm loc $ fmap (makeSingleDecl loc types) decls + makeSingleDecl type' (target, Nothing) = makeTerm1 (Java.Syntax.Variable target type') + makeSingleDecl type' (target, Just value) = makeTerm1 (Statement.Assignment [] (makeTerm1 (Java.Syntax.Variable target type')) value) + makeDecl loc (type', decls) = makeTerm'' loc $ fmap (makeSingleDecl type') decls -- we need loc here because it's the outermost node that comprises the list of all things vDeclList = symbol VariableDeclaratorList *> children (some variableDeclarator) - variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variable_declarator_id <*> expression) + variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variable_declarator_id <*> optional expression) +-- function arg localVariableDeclarationStatement :: Assignment localVariableDeclarationStatement = symbol LocalVariableDeclarationStatement *> children localVariableDeclaration @@ -306,9 +318,19 @@ try = makeTerm <$> symbol TryStatement <*> children (Statement.Try <$> term expr append (Just a) Nothing = a append (Just a) (Just b) = a <> [b] --- for :: Assignment --- for = makeTerm <$> symbol For <*> children (Statement.ForEach <$> (makeTerm <$> location <*> manyTermsTill expression (symbol In)) <*> inClause <*> expressions) --- where inClause = symbol In *> children expression +for :: Assignment +for = makeTerm <$> symbol ForStatement <*> children (Statement.For <$ token AnonFor <* token AnonLParen <*> (token AnonSemicolon *> emptyTerm <|> forInit <* token AnonSemicolon) <*> (token AnonSemicolon *> emptyTerm <|> term expression <* token AnonSemicolon) <*> forStep <*> term expression) + where + forInit = symbol ForInit *> children (term expression) + forStep = makeTerm <$> location <*> manyTermsTill expression (token AnonRParen) +-- don't have symbol to match against for forStep because we don't know what that would be, but we need to still provide an annotation and location +-- location rule = for when you need to provide a location without matching any nodes +-- don't need to make a term here because term sion already produces a term +-- makeTerm is used when the data constructor (syntax) field has an element, not a list +-- Statement.For = data constructor that takes three statements and produces a piece of syntax +-- don't need to produce syntax with term expression (already produces a term) so don't need to makeTerm +-- dont wanna do manyTerm because it'll greedily match any of the expressions it can which means it'll match the for loop body, which would fail... +-- because it would've already matched it and consumed it and the whole rule would fail because it wouldn't be available -- expression diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index e8053ff88..8fb112eef 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -55,3 +55,14 @@ instance Eq1 EnumDeclaration where liftEq = genericLiftEq instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare instance Show1 EnumDeclaration where liftShowsPrec = genericLiftShowsPrec instance Evaluatable EnumDeclaration + + +data Variable a = Variable { variableName :: !a, variableType :: !a} + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 Variable where liftEq = genericLiftEq +instance Ord1 Variable where liftCompare = genericLiftCompare +instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for Variable +instance Evaluatable Variable diff --git a/src/Language/Ruby/Assignment.hs b/src/Language/Ruby/Assignment.hs index ecffacf32..ee8455094 100644 --- a/src/Language/Ruby/Assignment.hs +++ b/src/Language/Ruby/Assignment.hs @@ -417,6 +417,7 @@ conditional = makeTerm <$> symbol Conditional <*> children (Statement.If <$> exp emptyStatement :: Assignment emptyStatement = makeTerm <$> symbol EmptyStatement <*> (Syntax.Empty <$ source <|> pure Syntax.Empty) + -- Helper functions invert :: Assignment -> Assignment From 0cb73439b79c48e122c428d2bc0833c9d5719d8b Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Thu, 19 Apr 2018 15:26:17 -0700 Subject: [PATCH 27/68] enhancedFor, basicFor, binary, unary, update and assignment operators --- src/Data/Syntax/Statement.hs | 23 ++++++ src/Language/Java/Assignment.hs | 124 +++++++++++++++++++++++++++++--- src/Language/Java/Syntax.hs | 2 +- src/Language/Ruby/Assignment.hs | 2 +- 4 files changed, 140 insertions(+), 11 deletions(-) diff --git a/src/Data/Syntax/Statement.hs b/src/Data/Syntax/Statement.hs index 6400c1c50..c9b7ac720 100644 --- a/src/Data/Syntax/Statement.hs +++ b/src/Data/Syntax/Statement.hs @@ -122,6 +122,29 @@ instance Show1 PostDecrement where liftShowsPrec = genericLiftShowsPrec -- TODO: Implement Eval instance for PostDecrement instance Evaluatable PostDecrement +-- | Pre increment operator (e.g. ++1 in C or Java). +newtype PreIncrement a = PreIncrement a + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 PreIncrement where liftEq = genericLiftEq +instance Ord1 PreIncrement where liftCompare = genericLiftCompare +instance Show1 PreIncrement where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for PreIncrement +instance Evaluatable PreIncrement + + +-- | Pre decrement operator (e.g. --1 in C or Java). +newtype PreDecrement a = PreDecrement a + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 PreDecrement where liftEq = genericLiftEq +instance Ord1 PreDecrement where liftCompare = genericLiftCompare +instance Show1 PreDecrement where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for PreDecrement +instance Evaluatable PreDecrement + -- Returns diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 2f9b68f66..be0a8d259 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -34,6 +34,10 @@ type Syntax = , Declaration.InterfaceDeclaration , Declaration.Method , Declaration.VariableDeclaration + , Expression.Arithmetic + , Expression.Comparison + , Expression.Bitwise + , Expression.Boolean , Java.Syntax.ArrayType , Java.Syntax.EnumDeclaration , Java.Syntax.Import @@ -54,9 +58,14 @@ type Syntax = , Statement.DoWhile , Statement.Finally , Statement.For + , Statement.ForEach , Statement.If , Statement.Match , Statement.Pattern + , Statement.PostIncrement + , Statement.PostDecrement + , Statement.PreIncrement + , Statement.PreDecrement , Statement.While , Statement.Throw , Statement.Try @@ -112,7 +121,9 @@ expressionChoices :: [Assignment.Assignment [] Grammar Term] expressionChoices = [ arrayInitializer + , assignment' , block + , binary , boolean , break , char @@ -138,6 +149,8 @@ expressionChoices = , switch , throw , try + , unary + , update , localVariableDeclaration , localVariableDeclarationStatement , while @@ -158,13 +171,13 @@ comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) -- constantDeclaration = makeTerm <$> symbol ConstantDeclaration <*> localVariableDeclaration :: Assignment -localVariableDeclaration = makeDecl <$> symbol LocalVariableDeclaration <*> children ((,) <$> type' <*> vDeclList) +localVariableDeclaration = makeDecl <$> symbol LocalVariableDeclaration <*> children ((,,) <$> manyTerm modifier <*> type' <*> vDeclList) where - makeSingleDecl type' (target, Nothing) = makeTerm1 (Java.Syntax.Variable target type') - makeSingleDecl type' (target, Just value) = makeTerm1 (Statement.Assignment [] (makeTerm1 (Java.Syntax.Variable target type')) value) - makeDecl loc (type', decls) = makeTerm'' loc $ fmap (makeSingleDecl type') decls -- we need loc here because it's the outermost node that comprises the list of all things + makeSingleDecl modifiers type' (target, Nothing) = makeTerm1 (Java.Syntax.Variable modifiers type' target) + makeSingleDecl modifiers type' (target, Just value) = makeTerm1 (Statement.Assignment [] (makeTerm1 (Java.Syntax.Variable modifiers type' target)) value) + makeDecl loc (modifiers, type', decls) = makeTerm'' loc $ fmap (makeSingleDecl modifiers type') decls -- we need loc here because it's the outermost node that comprises the list of all things vDeclList = symbol VariableDeclaratorList *> children (some variableDeclarator) - variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variable_declarator_id <*> optional expression) + variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variableDeclaratorId <*> optional expression) -- function arg localVariableDeclarationStatement :: Assignment @@ -173,8 +186,8 @@ localVariableDeclarationStatement = symbol LocalVariableDeclarationStatement *> unannotatedType :: Assignment unannotatedType = makeTerm <$> symbol Grammar.ArrayType <*> (Java.Syntax.ArrayType <$> source) -variable_declarator_id :: Assignment -variable_declarator_id = symbol VariableDeclaratorId *> children identifier +variableDeclaratorId :: Assignment +variableDeclaratorId = symbol VariableDeclaratorId *> children identifier -- Literals @@ -319,7 +332,11 @@ try = makeTerm <$> symbol TryStatement <*> children (Statement.Try <$> term expr append (Just a) (Just b) = a <> [b] for :: Assignment -for = makeTerm <$> symbol ForStatement <*> children (Statement.For <$ token AnonFor <* token AnonLParen <*> (token AnonSemicolon *> emptyTerm <|> forInit <* token AnonSemicolon) <*> (token AnonSemicolon *> emptyTerm <|> term expression <* token AnonSemicolon) <*> forStep <*> term expression) +for = symbol ForStatement *> children (basicFor <|> enhancedFor) +-- dropping so *> + +basicFor :: Assignment +basicFor = makeTerm <$> symbol BasicForStatement <*> children (Statement.For <$ token AnonFor <* token AnonLParen <*> (token AnonSemicolon *> emptyTerm <|> forInit <* token AnonSemicolon) <*> (token AnonSemicolon *> emptyTerm <|> term expression <* token AnonSemicolon) <*> forStep <*> term expression) where forInit = symbol ForInit *> children (term expression) forStep = makeTerm <$> location <*> manyTermsTill expression (token AnonRParen) @@ -332,7 +349,96 @@ for = makeTerm <$> symbol ForStatement <*> children (Statement.For <$ token Anon -- dont wanna do manyTerm because it'll greedily match any of the expressions it can which means it'll match the for loop body, which would fail... -- because it would've already matched it and consumed it and the whole rule would fail because it wouldn't be available --- expression +enhancedFor :: Assignment +enhancedFor = makeTerm <$> symbol EnhancedForStatement <*> children (Statement.ForEach <$> (variable <$> manyTerm modifier <*> type' <*> variableDeclaratorId) <*> term expression <*> term expression) + where variable modifiers type' variableDeclaratorId = makeTerm1 (Java.Syntax.Variable modifiers type' variableDeclaratorId) +-- variableDeclaratorId takes name and then type' so that's the order we give it, but variable takes type' first and variableDeclaratorId +-- going to populate binding field with a new term which should be a variable +-- binding = variable +-- subject = thing being iterated over +-- body + +-- TODO: instanceOf +binary :: Assignment +binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expression expression + [ (inj .) . Expression.LessThan <$ symbol AnonLAngle + , (inj .) . Expression.GreaterThan <$ symbol AnonRAngle + , (inj .) . Expression.Equal <$ symbol AnonEqualEqual + , (inj .) . Expression.GreaterThanEqual <$ symbol AnonRAngleEqual + , (inj .) . Expression.LessThanEqual <$ symbol AnonLAngleEqual + , (inj .) . invert Expression.Equal <$ symbol AnonBangEqual + , (inj .) . Expression.And <$ symbol AnonAmpersandAmpersand + , (inj .) . Expression.Or <$ symbol AnonPipePipe + , (inj .) . Expression.BAnd <$ symbol AnonAmpersand + , (inj .) . Expression.BOr <$ symbol AnonPipe + , (inj .) . Expression.BXOr <$ symbol AnonCaret + , (inj .) . Expression.Modulo <$ symbol AnonPercent + , (inj .) . Expression.LShift <$ symbol AnonLAngleLAngle + , (inj .) . Expression.RShift <$ symbol AnonRAngleRAngle + , (inj .) . Expression.UnsignedRShift <$ symbol AnonRAngleRAngleRAngle + , (inj .) . Expression.Plus <$ symbol AnonPlus + , (inj .) . Expression.Minus <$ symbol AnonMinus + , (inj .) . Expression.Times <$ symbol AnonStar + , (inj .) . Expression.DividedBy <$ symbol AnonSlash + ]) + where invert cons a b = Expression.Not (makeTerm1 (cons a b)) + +-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand. +infixTerm :: HasCallStack + => Assignment + -> Assignment + -> [Assignment.Assignment [] Grammar (Term -> Term -> Union Syntax Term)] + -> Assignment.Assignment [] Grammar (Union Syntax Term) +infixTerm = infixContext comment + +assignment' :: Assignment +assignment' = makeTerm' <$> symbol AssignmentExpression <*> children (infixTerm lhs expression + [ (inj .) . Statement.Assignment [] <$ symbol AnonEqual + , assign Expression.Plus <$ symbol AnonPlusEqual + , assign Expression.Minus <$ symbol AnonMinusEqual + , assign Expression.Times <$ symbol AnonStarEqual + , assign Expression.DividedBy <$ symbol AnonSlashEqual + , assign Expression.BOr <$ symbol AnonPipeEqual + , assign Expression.BAnd <$ symbol AnonAmpersandEqual + , assign Expression.Modulo <$ symbol AnonPercentEqual + , assign Expression.RShift <$ symbol AnonRAngleRAngleEqual + , assign Expression.UnsignedRShift <$ symbol AnonRAngleRAngleRAngleEqual + , assign Expression.LShift <$ symbol AnonLAngleLAngleEqual + , assign Expression.BXOr <$ symbol AnonCaretEqual + ]) + where + assign :: (f :< Syntax) => (Term -> Term -> f Term) -> Term -> Term -> Union Syntax Term + assign c l r = inj (Statement.Assignment [] l (makeTerm1 (c l r))) + lhs = symbol Lhs *> children (term expression) + +data UnaryType + = UPlus + | UMinus + | UBang + | UTilde + +unary :: Assignment +unary = make <$> symbol UnaryExpression <*> children ((,) <$> operator <*> term expression) + where + make _ (UPlus, operand) = operand + make loc (UMinus, operand) = makeTerm loc (Expression.Negate operand) + make loc (UBang, operand) = makeTerm loc (Expression.Not operand) + make loc (UTilde, operand) = makeTerm loc (Expression.Complement operand) + operator = token AnonPlus $> UPlus + <|> token AnonMinus $> UMinus + <|> token AnonBang $> UBang + <|> token AnonTilde $> UTilde + -- had to use make because we didn't always make a term + +update :: Assignment +update = makeTerm' <$> symbol UpdateExpression <*> children ( + inj . Statement.PreIncrement <$ token AnonPlusPlus <*> term expression + <|> inj . Statement.PreDecrement <$ token AnonMinusMinus <*> term expression + <|> inj . Statement.PostIncrement <$> term expression <* token AnonPlusPlus + <|> inj . Statement.PostDecrement <$> term expression <* token AnonMinusMinus) +-- makterm' so need inj . +-- tries them in order; true of alternations, order matters; (if-else) +-- but choice doesn't have this property (order doesn't matter) because it constructs a jump table (switch) -- infix operators -- binary :: Assignment diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index 8fb112eef..a0beca040 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -57,7 +57,7 @@ instance Show1 EnumDeclaration where liftShowsPrec = genericLiftShowsPrec instance Evaluatable EnumDeclaration -data Variable a = Variable { variableName :: !a, variableType :: !a} +data Variable a = Variable { variableModifiers :: ![a], variableType :: !a, variableName :: !a} deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) instance Eq1 Variable where liftEq = genericLiftEq diff --git a/src/Language/Ruby/Assignment.hs b/src/Language/Ruby/Assignment.hs index ee8455094..76955de9e 100644 --- a/src/Language/Ruby/Assignment.hs +++ b/src/Language/Ruby/Assignment.hs @@ -353,7 +353,7 @@ assignment' = makeTerm <$> symbol Assignment <*> children (Statement.As , assign Expression.Times <$ symbol AnonStarEqual , assign Expression.Power <$ symbol AnonStarStarEqual , assign Expression.DividedBy <$ symbol AnonSlashEqual - , assign Expression.And <$ symbol AnonPipePipeEqual + , assign Expression.Or <$ symbol AnonPipePipeEqual , assign Expression.BOr <$ symbol AnonPipeEqual , assign Expression.And <$ symbol AnonAmpersandAmpersandEqual , assign Expression.BAnd <$ symbol AnonAmpersandEqual From bef61d68804b18460035c8fdbb8ac504e8763fed Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 20 Apr 2018 10:17:47 -0700 Subject: [PATCH 28/68] ternary expressions --- src/Language/Java/Assignment.hs | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index be0a8d259..7d2f34f72 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -147,6 +147,7 @@ expressionChoices = , return' , string , switch + , ternary , throw , try , unary @@ -440,6 +441,12 @@ update = makeTerm' <$> symbol UpdateExpression <*> children ( -- tries them in order; true of alternations, order matters; (if-else) -- but choice doesn't have this property (order doesn't matter) because it constructs a jump table (switch) +ternary :: Assignment +ternary = makeTerm <$> symbol TernaryExpression <*> children (Statement.If <$> term expression <*> term expression <*> term expression) + +-- delimiter, if optional, need +-- token vs. symbol -- whether we want to skip past the node or not; token skips past the node; symbol does not +-- need token or symbol to mention any token/symbol because they take a token and produce a grammar rule -- infix operators -- binary :: Assignment -- binary = makeTerm From 653bbce7af84fcb8f96456adf22c1b9057c743a8 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 20 Apr 2018 11:03:23 -0700 Subject: [PATCH 29/68] add termToTree to output a prettier tree --- src/Data/AST.hs | 9 +++++++++ 1 file changed, 9 insertions(+) diff --git a/src/Data/AST.hs b/src/Data/AST.hs index a050ce764..5c6f97b2c 100644 --- a/src/Data/AST.hs +++ b/src/Data/AST.hs @@ -5,6 +5,7 @@ import Data.Range import Data.Record import Data.Span import Data.Term +import Prologue -- | An AST node labelled with symbols and source location. type AST syntax grammar = Term syntax (Node grammar) @@ -21,3 +22,11 @@ type Location = '[Range, Span] nodeLocation :: Node grammar -> Record Location nodeLocation Node{..} = nodeByteRange :. nodeSpan :. Nil + +newtype Tree (syntax) = Tree (syntax (Tree syntax)) + +instance (Show1 syntax) => Show (Tree syntax) where + showsPrec precedence (Tree syntax) = showsPrec1 precedence syntax + +termToTree :: Functor syntax => Term syntax annotation -> Tree syntax +termToTree = cata (\ (In _ syntax) -> Tree syntax) From 297ae73cc179fb7b4705d8c67197b87626487174 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 20 Apr 2018 11:51:35 -0700 Subject: [PATCH 30/68] assignments for synchronized statement and array types --- src/Language/Java/Assignment.hs | 15 +++++++++++---- src/Language/Java/Syntax.hs | 20 ++++++++++---------- 2 files changed, 21 insertions(+), 14 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 7d2f34f72..0b0435093 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -38,11 +38,11 @@ type Syntax = , Expression.Comparison , Expression.Bitwise , Expression.Boolean - , Java.Syntax.ArrayType , Java.Syntax.EnumDeclaration , Java.Syntax.Import , Java.Syntax.Module , Java.Syntax.Package + , Java.Syntax.Synchronized , Java.Syntax.Variable , Literal.Array , Literal.Boolean @@ -75,6 +75,7 @@ type Syntax = , Syntax.Identifier , Syntax.AccessibilityModifier , Syntax.Program + , Type.Array , Type.Bool , Type.Int , Type.Void @@ -147,6 +148,7 @@ expressionChoices = , return' , string , switch + , synchronized , ternary , throw , try @@ -184,9 +186,6 @@ localVariableDeclaration = makeDecl <$> symbol LocalVariableDeclaration <*> chil localVariableDeclarationStatement :: Assignment localVariableDeclarationStatement = symbol LocalVariableDeclarationStatement *> children localVariableDeclaration -unannotatedType :: Assignment -unannotatedType = makeTerm <$> symbol Grammar.ArrayType <*> (Java.Syntax.ArrayType <$> source) - variableDeclaratorId :: Assignment variableDeclaratorId = symbol VariableDeclaratorId *> children identifier @@ -273,15 +272,20 @@ return' = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children -- if you f <$> (g <$> a) == f . g <$> a (fusion law) -- if you have two nested fmaps, same as composing +dims :: Assignment.Assignment [] Grammar [Term] +dims = symbol Dims *> children (many (emptyTerm <* token AnonLBracket <* token AnonRBracket)) + type' :: Assignment type' = choice [ makeTerm <$> token VoidType <*> pure Type.Void , makeTerm <$> token IntegralType <*> pure Type.Int , makeTerm <$> token FloatingPointType <*> pure Type.Float , makeTerm <$> token BooleanType <*> pure Type.Bool + , symbol ArrayType *> children (array <$> type' <*> dims) , symbol CatchType *> children (term type') , identifier ] + where array type' = foldl (\into each -> makeTerm1 (Type.Array (Just each) into)) type' -- <|> makeTerm <$> symbol FloatingPointType <*> children (token AnonFloat $> Type.Float <|> token AnonDouble $> Type.Double) -- we had to say token with the first 4 because pure don't advance past the first nodes; implies no effect, just produces value -- if we want to match a node and consume that node (which we have to do) we need to use token because it has that behavior @@ -450,3 +454,6 @@ ternary = makeTerm <$> symbol TernaryExpression <*> children (Statement.If <$> t -- infix operators -- binary :: Assignment -- binary = makeTerm + +synchronized :: Assignment +synchronized = makeTerm <$> symbol SynchronizedStatement <*> children (Java.Syntax.Synchronized <$> term expression <*> term expression) diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index a0beca040..8bc3f8eb7 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -5,16 +5,6 @@ import Data.Abstract.Evaluatable hiding (Label) import Diffing.Algorithm import Prologue -newtype ArrayType a = ArrayType ByteString - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) - -instance Eq1 ArrayType where liftEq = genericLiftEq -instance Ord1 ArrayType where liftCompare = genericLiftCompare -instance Show1 ArrayType where liftShowsPrec = genericLiftShowsPrec - --- TODO: Implement Eval instance for ArrayType -instance Evaluatable ArrayType - newtype Import a = Import [a] deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) @@ -66,3 +56,13 @@ instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec -- TODO: Implement Eval instance for Variable instance Evaluatable Variable + +data Synchronized a = Synchronized { synchronizedSubject :: !a, synchronizedBody :: !a} + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 Synchronized where liftEq = genericLiftEq +instance Ord1 Synchronized where liftCompare = genericLiftCompare +instance Show1 Synchronized where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for Synchronized +instance Evaluatable Synchronized From 07b835147cb385eaeae2cd3aa3c404686f57357b Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 20 Apr 2018 16:06:08 -0700 Subject: [PATCH 31/68] assign classInstance, argumentList, super, this, constructorDeclaration, typeParameters, throws, formalParameters --- example.java | 5 +++ src/Data/Syntax/Expression.hs | 17 +++++++- src/Language/Java/Assignment.hs | 77 +++++++++++++++++++++++++++++---- src/Language/Java/Syntax.hs | 33 +++++++++++++- 4 files changed, 121 insertions(+), 11 deletions(-) create mode 100644 example.java diff --git a/example.java b/example.java new file mode 100644 index 000000000..826709bf4 --- /dev/null +++ b/example.java @@ -0,0 +1,5 @@ +public final class Exceptions { + private Exceptions() { + throw new IllegalStateException("No instances!"); + } +} diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index 8af42a5f3..61013bac4 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -281,7 +281,6 @@ instance Show1 New where liftShowsPrec = genericLiftShowsPrec -- TODO: Implement Eval instance for New instance Evaluatable New - -- | A cast expression to a specified type. data Cast a = Cast { castSubject :: !a, castType :: !a } deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) @@ -292,3 +291,19 @@ instance Show1 Cast where liftShowsPrec = genericLiftShowsPrec -- TODO: Implement Eval instance for Cast instance Evaluatable Cast + +data Super a = Super + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 Super where liftEq = genericLiftEq +instance Ord1 Super where liftCompare = genericLiftCompare +instance Show1 Super where liftShowsPrec = genericLiftShowsPrec +instance Evaluatable Super + +data This a = This + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 This where liftEq = genericLiftEq +instance Ord1 This where liftCompare = genericLiftCompare +instance Show1 This where liftShowsPrec = genericLiftShowsPrec +instance Evaluatable This diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 0b0435093..a7a15bf70 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -8,7 +8,7 @@ module Language.Java.Assignment import Assigning.Assignment hiding (Assignment, Error, while, try) import Data.Abstract.FreeVariables -import Data.Functor (void, ($>)) +import Data.Functor (($>)) import Data.List.NonEmpty (some1) import Data.Record import Data.Semigroup @@ -35,12 +35,20 @@ type Syntax = , Declaration.Method , Declaration.VariableDeclaration , Expression.Arithmetic + , Expression.Call , Expression.Comparison , Expression.Bitwise , Expression.Boolean + , Expression.InstanceOf + , Expression.MemberAccess + , Expression.Super + , Expression.This + , Java.Syntax.Asterisk + , Java.Syntax.Constructor , Java.Syntax.EnumDeclaration , Java.Syntax.Import , Java.Syntax.Module + , Java.Syntax.New , Java.Syntax.Package , Java.Syntax.Synchronized , Java.Syntax.Variable @@ -129,7 +137,9 @@ expressionChoices = , break , char , class' + , classInstance , continue + , constructorDeclaration -- , constantDeclaration , doWhile , float @@ -142,14 +152,18 @@ expressionChoices = , import' , integer , method + , methodInvocation , module' , null' , package , return' + , scopedIdentifier , string + , super , switch , synchronized , ternary + , this , throw , try , unary @@ -222,22 +236,32 @@ class' = makeTerm <$> symbol ClassDeclaration <*> children (Declaration.Class <$ -- consolidated with scopedIdentifier identifier :: Assignment -identifier = makeTerm <$> (symbol Identifier <|> symbol ScopedIdentifier <|> symbol TypeIdentifier) <*> (Syntax.Identifier . name <$> source) +identifier = makeTerm <$> (symbol Identifier <|> symbol TypeIdentifier) <*> (Syntax.Identifier . name <$> source) + +scopedIdentifier :: Assignment +scopedIdentifier = makeTerm <$> symbol ScopedIdentifier <*> children (Expression.MemberAccess <$> term expression <*> term expression) method :: Assignment method = makeTerm <$> symbol MethodDeclaration <*> children ( - (makeMethod <$> many modifier <* symbol MethodHeader <*> emptyTerm <*> children ((,) <$> type' <* symbol MethodDeclarator <*> children ( (,) <$> identifier <*> manyTerm parameter)) ) + (makeMethod <$> many modifier <* symbol MethodHeader <*> emptyTerm <*> children ((,) <$> type' <* symbol MethodDeclarator <*> children ( (,) <$> identifier <*> formalParameters)) ) <* symbol MethodBody <*> children (makeTerm <$> symbol Block <*> children (manyTerm expression)) ) where makeMethod modifiers receiver (returnType, (name, params)) body = Declaration.Method (returnType : modifiers) receiver name params body - parameter = makeTerm <$> symbol FormalParameter <*> children (flip Type.Annotation <$> type' <* symbol VariableDeclaratorId <*> children identifier) + -- TODO: re-introduce makeTerm later; matching types as part of the type rule for now. +methodInvocation :: Assignment +methodInvocation = makeTerm <$> symbol MethodInvocation <*> children (Expression.Call [] <$> (callFunction <$> term expression <*> optional (token AnonDot *> term expression)) <*> argumentList <*> emptyTerm) + where + callFunction a (Just b) = makeTerm1 (Expression.MemberAccess a b) + callFunction a Nothing = a + module' :: Assignment module' = makeTerm <$> symbol ModuleDeclaration <*> children (Java.Syntax.Module <$> expression <*> many expression) import' :: Assignment -import' = makeTerm <$> symbol ImportDeclaration <*> children (Java.Syntax.Import <$> some identifier) +import' = makeTerm <$> symbol ImportDeclaration <*> children (Java.Syntax.Import <$> someTerm (expression <|> asterisk)) + where asterisk = makeTerm <$> token Grammar.Asterisk <*> pure Java.Syntax.Asterisk interface :: Assignment interface = makeTerm <$> symbol InterfaceDeclaration <*> children (normal <|> annotationType) @@ -248,7 +272,7 @@ interface = makeTerm <$> symbol InterfaceDeclaration <*> children (normal <|> an annotationTypeBody = makeTerm <$> symbol AnnotationTypeBody <*> children (many expression) package :: Assignment -package = makeTerm <$> symbol PackageDeclaration <*> children (Java.Syntax.Package <$> some identifier) +package = makeTerm <$> symbol PackageDeclaration <*> children (Java.Syntax.Package <$> someTerm expression) enum :: Assignment enum = makeTerm <$> symbol Grammar.EnumDeclaration <*> children (Java.Syntax.EnumDeclaration <$> term identifier <*> manyTerm enumConstant) @@ -385,6 +409,7 @@ binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expressio , (inj .) . Expression.Minus <$ symbol AnonMinus , (inj .) . Expression.Times <$ symbol AnonStar , (inj .) . Expression.DividedBy <$ symbol AnonSlash + , (inj .) . Expression.InstanceOf <$ symbol AnonInstanceof ]) where invert cons a b = Expression.Not (makeTerm1 (cons a b)) @@ -447,13 +472,47 @@ update = makeTerm' <$> symbol UpdateExpression <*> children ( ternary :: Assignment ternary = makeTerm <$> symbol TernaryExpression <*> children (Statement.If <$> term expression <*> term expression <*> term expression) - -- delimiter, if optional, need -- token vs. symbol -- whether we want to skip past the node or not; token skips past the node; symbol does not -- need token or symbol to mention any token/symbol because they take a token and produce a grammar rule -- infix operators --- binary :: Assignment --- binary = makeTerm synchronized :: Assignment synchronized = makeTerm <$> symbol SynchronizedStatement <*> children (Java.Syntax.Synchronized <$> term expression <*> term expression) + +classInstance :: Assignment +classInstance = makeTerm <$> symbol ClassInstanceCreationExpression <*> children unqualified + where + unqualified = symbol UnqualifiedClassInstanceCreationExpression *> children (Java.Syntax.New <$> type' <*> (argumentList <|> pure [])) + +argumentList :: Assignment.Assignment [] Grammar [Term] +argumentList = symbol ArgumentList *> children (manyTerm expression) + +super :: Assignment +super = makeTerm <$> token Super <*> pure Expression.Super +-- not a rule so using pure to lift value into an assignment + +this :: Assignment +this = makeTerm <$> token This <*> pure Expression.This + +constructorDeclaration :: Assignment +constructorDeclaration = makeTerm <$> symbol ConstructorDeclaration <*> children ( + constructor <$> manyTerm modifier <*> constructorDeclarator <*> (throws <|> pure []) <*> constructorBody) + where + constructorDeclarator = symbol ConstructorDeclarator *> children ((,,) <$> (typeParameters <|> pure []) <*> term identifier <*> formalParameters) + constructorBody = makeTerm <$> symbol ConstructorBody <*> children (manyTerm expression) -- wrapping list of terms up in single node + constructor modifiers (typeParameters, identifier, formalParameters) = Java.Syntax.Constructor modifiers typeParameters identifier formalParameters -- let partial application do its thing + +typeParameters :: Assignment.Assignment [] Grammar [Term] +typeParameters = symbol TypeParameters *> children (pure []) +-- stubbing in so deals with empty list +-- come back and populate this + +throws :: Assignment.Assignment [] Grammar [Term] +throws = symbol Throws *> children (pure []) +-- TODO: come back and assign + +formalParameters :: Assignment.Assignment [] Grammar [Term] +formalParameters = manyTerm parameter + where + parameter = makeTerm <$> symbol FormalParameter <*> children (flip Type.Annotation <$> type' <* symbol VariableDeclaratorId <*> children identifier) diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index 8bc3f8eb7..1cad56517 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -3,7 +3,7 @@ module Language.Java.Syntax where import Data.Abstract.Evaluatable hiding (Label) import Diffing.Algorithm -import Prologue +import Prologue hiding (Constructor) newtype Import a = Import [a] deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) @@ -66,3 +66,34 @@ instance Show1 Synchronized where liftShowsPrec = genericLiftShowsPrec -- TODO: Implement Eval instance for Synchronized instance Evaluatable Synchronized + +data New a = New { newType :: !a, newArgs :: ![a] } + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 New where liftEq = genericLiftEq +instance Ord1 New where liftCompare = genericLiftCompare +instance Show1 New where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for New +instance Evaluatable New + +data Asterisk a = Asterisk + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 Asterisk where liftEq = genericLiftEq +instance Ord1 Asterisk where liftCompare = genericLiftCompare +instance Show1 Asterisk where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for New +instance Evaluatable Asterisk + + +data Constructor a = Constructor { constructorModifiers :: ![a], constructorTypeParams :: ![a], constructorIdentifier :: !a, constructorParams :: ![a], constructorThrows :: ![a], constructorBody :: a} + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 Constructor where liftEq = genericLiftEq +instance Ord1 Constructor where liftCompare = genericLiftCompare +instance Show1 Constructor where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for Constructor +instance Evaluatable Constructor From fef6471e37d9d6b0e31b70d2e1da298733a90ee8 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Mon, 23 Apr 2018 18:21:48 -0700 Subject: [PATCH 32/68] typeParameters, throws and modifier assignments --- example.java | 7 ++-- src/Language/Java/Assignment.hs | 62 +++++++++++++++++++++++++++++---- src/Language/Java/Syntax.hs | 30 ++++++++++++++++ 3 files changed, 89 insertions(+), 10 deletions(-) diff --git a/example.java b/example.java index 826709bf4..71a48a009 100644 --- a/example.java +++ b/example.java @@ -1,5 +1,6 @@ -public final class Exceptions { - private Exceptions() { - throw new IllegalStateException("No instances!"); +@Override +class Quack { + <@Hello(foo = "hi") T>Bird() { + } } diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index a7a15bf70..2d5c854f0 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -43,6 +43,8 @@ type Syntax = , Expression.MemberAccess , Expression.Super , Expression.This + , Java.Syntax.Annotation + , Java.Syntax.AnnotationField , Java.Syntax.Asterisk , Java.Syntax.Constructor , Java.Syntax.EnumDeclaration @@ -51,6 +53,7 @@ type Syntax = , Java.Syntax.New , Java.Syntax.Package , Java.Syntax.Synchronized + , Java.Syntax.TypeParameter , Java.Syntax.Variable , Literal.Array , Literal.Boolean @@ -172,11 +175,38 @@ expressionChoices = , localVariableDeclarationStatement , while ] - -- adding something to expressionChoices list is useful because expression (above) uses expressionChoices, and so - -- it is available to form assignments when we encounter any of those terms modifier :: Assignment -modifier = makeTerm <$> symbol Modifier <*> (Syntax.AccessibilityModifier <$> source) +modifier = make <$> symbol Modifier <*> children(Left <$> annotation <|> Right . Syntax.AccessibilityModifier <$> source) + where + make loc (Right modifier) = makeTerm loc modifier + make _ (Left annotation) = annotation +-- if we don't match the annotation we will match the token +-- don't do this if you have more than one word possible +-- left fmap +-- right - composing the right function after wrapping the bytestring of source in the accessibilityModifier syntax, then compose that with right function +-- this enables us to have the same type in both places (either term (syntax.accessibilityModifier term)) +-- whack error∷/Users/aymannadeem/github/semantic-diff/src/Language/Java/Assignment.hs:180:69: error: +-- • Couldn't match type ‘Syntax.AccessibilityModifier a0’ +-- with ‘Term.Term (Union Syntax) (Record Location)’ +-- Expected type: Control.Monad.Free.Freer.Freer +-- (Assigning.Assignment.Tracing +-- (Assigning.Assignment.AssignmentF [] Grammar)) +-- Term +-- Actual type: Control.Monad.Free.Freer.Freer +-- (Assigning.Assignment.Tracing +-- (Assigning.Assignment.AssignmentF [] Grammar)) +-- (Syntax.AccessibilityModifier a0) +-- • In the second argument of ‘(<|>)’, namely +-- ‘Syntax.AccessibilityModifier <$> source’ +-- In the first argument of ‘children’, namely +-- ‘(annotation <|> Syntax.AccessibilityModifier <$> source)’ +-- In the second argument of ‘(<*>)’, namely +-- ‘children (annotation <|> Syntax.AccessibilityModifier <$> source)’ +-- | +-- 180 | modifier = makeTerm <$> symbol Modifier <*> children(annotation <|> Syntax.AccessibilityModifier <$> source) +-- | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ +-- Failed, 118 modules loaded. arrayInitializer :: Assignment arrayInitializer = makeTerm <$> symbol ArrayInitializer <*> (Literal.Array <$> many expression) @@ -195,7 +225,6 @@ localVariableDeclaration = makeDecl <$> symbol LocalVariableDeclaration <*> chil makeDecl loc (modifiers, type', decls) = makeTerm'' loc $ fmap (makeSingleDecl modifiers type') decls -- we need loc here because it's the outermost node that comprises the list of all things vDeclList = symbol VariableDeclaratorList *> children (some variableDeclarator) variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variableDeclaratorId <*> optional expression) --- function arg localVariableDeclarationStatement :: Assignment localVariableDeclarationStatement = symbol LocalVariableDeclarationStatement *> children localVariableDeclaration @@ -307,6 +336,7 @@ type' = choice [ , makeTerm <$> token BooleanType <*> pure Type.Bool , symbol ArrayType *> children (array <$> type' <*> dims) , symbol CatchType *> children (term type') + , symbol ExceptionType *> children (term type') , identifier ] where array type' = foldl (\into each -> makeTerm1 (Type.Array (Just each) into)) type' @@ -504,13 +534,31 @@ constructorDeclaration = makeTerm <$> symbol ConstructorDeclaration <*> children constructor modifiers (typeParameters, identifier, formalParameters) = Java.Syntax.Constructor modifiers typeParameters identifier formalParameters -- let partial application do its thing typeParameters :: Assignment.Assignment [] Grammar [Term] -typeParameters = symbol TypeParameters *> children (pure []) +typeParameters = symbol TypeParameters *> children (manyTerm typeParam) -- this produces a list, which is what we need to return given by the type definition + where + typeParam = makeTerm <$> symbol Grammar.TypeParameter <*> children (Java.Syntax.TypeParameter <$> manyTerm annotation <*> term identifier <*> (typeBound <|> pure [])) -- wrapping up all three of those fields so we need to makeTerm (producing a term here) + typeBound = symbol TypeBound *> children (manyTerm type') -- stubbing in so deals with empty list -- come back and populate this +-- optional combinator produces type Maybe +-- instead of optional and maybe, we have that arg as a list now and we say we either produce the list or an empty list via pure [] + +annotation :: Assignment +annotation = makeTerm <$> symbol NormalAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> (elementValuePairList <|> pure [])) + <|> makeTerm <$> symbol MarkerAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> pure []) + <|> makeTerm <$> symbol SingleElementAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> (pure <$> term elementValue)) + where + elementValuePairList = symbol ElementValuePairList *> children (manyTerm elementValuePair) + elementValuePair = makeTerm <$> symbol ElementValuePair <*> children (Java.Syntax.AnnotationField <$> term expression <*> term elementValue) + elementValue = symbol ElementValue *> children (term expression) +-- pure over lists can produce single element lists; wrapping the expression in a list +-- elementValue, we don't have syntax to construct; we only construct syntax when we're making a node throws :: Assignment.Assignment [] Grammar [Term] -throws = symbol Throws *> children (pure []) --- TODO: come back and assign +throws = symbol Throws *> children (symbol ExceptionTypeList *> children(manyTerm type')) +-- discard the symbol and get the result of rule +-- match a throws node, and apply the rest of the to its children +-- we are matching the structure in the grammar formalParameters :: Assignment.Assignment [] Grammar [Term] formalParameters = manyTerm parameter diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index 1cad56517..f3bb795b4 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -97,3 +97,33 @@ instance Show1 Constructor where liftShowsPrec = genericLiftShowsPrec -- TODO: Implement Eval instance for Constructor instance Evaluatable Constructor + +data TypeParameter a = TypeParameter { typeParamAnnotation :: ![a], typeParamIdentifier :: !a, typeParamTypeBound :: ![a]} + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 TypeParameter where liftEq = genericLiftEq +instance Ord1 TypeParameter where liftCompare = genericLiftCompare +instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for TypeParameter +instance Evaluatable TypeParameter + +data Annotation a = Annotation { annotationName :: !a, annotationField :: [a]} + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 Annotation where liftEq = genericLiftEq +instance Ord1 Annotation where liftCompare = genericLiftCompare +instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for Annotation +instance Evaluatable Annotation + +data AnnotationField a = AnnotationField { annotationFieldName :: a, annotationFieldValue :: a } + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 AnnotationField where liftEq = genericLiftEq +instance Ord1 AnnotationField where liftCompare = genericLiftCompare +instance Show1 AnnotationField where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for AnnotationField +instance Evaluatable AnnotationField From 914a0ec3f24be18e1e72937ed8dbf45b0040a8cb Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 24 Apr 2018 10:51:34 -0700 Subject: [PATCH 33/68] refactor method declaration --- example.java | 5 ++--- src/Language/Java/Assignment.hs | 22 +++++++++++++++++----- 2 files changed, 19 insertions(+), 8 deletions(-) diff --git a/example.java b/example.java index 71a48a009..4190a9b9e 100644 --- a/example.java +++ b/example.java @@ -1,6 +1,5 @@ -@Override class Quack { - <@Hello(foo = "hi") T>Bird() { - + void hello() { + "woooo"; } } diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 2d5c854f0..2aafa3dec 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -270,14 +270,26 @@ identifier = makeTerm <$> (symbol Identifier <|> symbol TypeIdentifier) <*> (Syn scopedIdentifier :: Assignment scopedIdentifier = makeTerm <$> symbol ScopedIdentifier <*> children (Expression.MemberAccess <$> term expression <*> term expression) +-- refactor method declaration to have clearly understandable top-level rule + sub-rules broken out in the where so it's easier to reason about method :: Assignment method = makeTerm <$> symbol MethodDeclaration <*> children ( - (makeMethod <$> many modifier <* symbol MethodHeader <*> emptyTerm <*> children ((,) <$> type' <* symbol MethodDeclarator <*> children ( (,) <$> identifier <*> formalParameters)) ) - <* symbol MethodBody <*> children (makeTerm <$> symbol Block <*> children (manyTerm expression)) - ) - where makeMethod modifiers receiver (returnType, (name, params)) body = Declaration.Method (returnType : modifiers) receiver name params body - + makeMethod <$> many modifier <*> emptyTerm <*> methodHeader <*> methodBody) + where + methodBody = symbol MethodBody *> children (term expression) + methodDeclarator = symbol MethodDeclarator *> children ( (,) <$> identifier <*> formalParameters) + methodHeader = symbol MethodHeader *> children ((,) <$> type' <*> methodDeclarator) + makeMethod modifiers receiver (returnType, (name, params)) body = Declaration.Method (returnType : modifiers) receiver name params body +-- emptyTerm can be inserted at any position; if you have an optional term, you can use a maybe, but if you have for ex. an else statement, +-- where we wanna assume the else position always exists, emptyTerm allows us to keep the semantics for if-else really simple because we can +-- just provide it emptyTerm +-- emptyTerm just pattern matches; always produces a term. +-- current location will be the methodHeader node. -- TODO: re-introduce makeTerm later; matching types as part of the type rule for now. +-- full apply vs. half, what we want to retain +-- before we had a left-associative chain where we were discarding the +-- ((a + b) + c) +-- a + bc +-- bc = (b + c) methodInvocation :: Assignment methodInvocation = makeTerm <$> symbol MethodInvocation <*> children (Expression.Call [] <$> (callFunction <$> term expression <*> optional (token AnonDot *> term expression)) <*> argumentList <*> emptyTerm) From ab3bb2a944d6ecdaf79d94dae40ae5605dfd7324 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 24 Apr 2018 11:57:37 -0700 Subject: [PATCH 34/68] add type params to classes --- example.java | 5 ++--- src/Language/Java/Assignment.hs | 18 ++++++++++++------ 2 files changed, 14 insertions(+), 9 deletions(-) diff --git a/example.java b/example.java index 4190a9b9e..b4da52ef6 100644 --- a/example.java +++ b/example.java @@ -1,5 +1,4 @@ -class Quack { - void hello() { - "woooo"; +class someClass { + public static void anotherMethod(S arg) { } } diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 2aafa3dec..93b16cafd 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -260,8 +260,12 @@ char :: Assignment char = makeTerm <$> symbol CharacterLiteral <*> (Literal.TextElement <$> source) class' :: Assignment -class' = makeTerm <$> symbol ClassDeclaration <*> children (Declaration.Class <$> many modifier <*> term identifier <*> pure [] <*> classBody) - where classBody = makeTerm <$> symbol ClassBody <*> children (manyTerm expression) +class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many modifier <*> term identifier <*> (typeParameters <|> pure []) <*> emptyTerm <*> classBody) + where + makeClass modifiers identifier typeParams superClass classBody = Declaration.Class (modifiers ++ typeParams) identifier [superClass] classBody -- not doing an assignment, just straight up function + classBody = makeTerm <$> symbol ClassBody <*> children (manyTerm expression) +-- might wanna come back and change to maybe superClass +-- TODO: superclass -- need to match the superclass node when it exists (which will be a rule, similar to how the type params rule matches the typeparams node when it exists) -- consolidated with scopedIdentifier identifier :: Assignment @@ -272,13 +276,13 @@ scopedIdentifier = makeTerm <$> symbol ScopedIdentifier <*> children (Expression -- refactor method declaration to have clearly understandable top-level rule + sub-rules broken out in the where so it's easier to reason about method :: Assignment -method = makeTerm <$> symbol MethodDeclaration <*> children ( - makeMethod <$> many modifier <*> emptyTerm <*> methodHeader <*> methodBody) +method = makeTerm <$> symbol MethodDeclaration <*> children (makeMethod <$> many modifier <*> emptyTerm <*> methodHeader <*> methodBody) +-- makeMethod is a wrapper that takes the arguments in the structure they occur in the grammar and rearranges them to satisfy the structure required for our syntax types where methodBody = symbol MethodBody *> children (term expression) methodDeclarator = symbol MethodDeclarator *> children ( (,) <$> identifier <*> formalParameters) - methodHeader = symbol MethodHeader *> children ((,) <$> type' <*> methodDeclarator) - makeMethod modifiers receiver (returnType, (name, params)) body = Declaration.Method (returnType : modifiers) receiver name params body + methodHeader = symbol MethodHeader *> children ((,,,,) <$> (typeParameters <|> pure []) <*> manyTerm annotation <*> type' <*> methodDeclarator <*> (throws <|> pure [])) + makeMethod modifiers receiver (typeParams, annotations, returnType, (name, params), throws) body = Declaration.Method (returnType : modifiers ++ typeParams ++ annotations ++ throws) receiver name params body -- emptyTerm can be inserted at any position; if you have an optional term, you can use a maybe, but if you have for ex. an else statement, -- where we wanna assume the else position always exists, emptyTerm allows us to keep the semantics for if-else really simple because we can -- just provide it emptyTerm @@ -291,6 +295,8 @@ method = makeTerm <$> symbol MethodDeclaration <*> children ( -- a + bc -- bc = (b + c) +-- TODO: add genericType + methodInvocation :: Assignment methodInvocation = makeTerm <$> symbol MethodInvocation <*> children (Expression.Call [] <$> (callFunction <$> term expression <*> optional (token AnonDot *> term expression)) <*> argumentList <*> emptyTerm) where From a8543461e4338feb1af83525218542d3abcb248c Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 24 Apr 2018 16:34:49 -0700 Subject: [PATCH 35/68] remove comments --- src/Language/Java/Assignment.hs | 125 ++++---------------------------- 1 file changed, 13 insertions(+), 112 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 93b16cafd..c9dcabc1a 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -107,24 +107,22 @@ assignment = handleError $ makeTerm <$> symbol Grammar.Program <*> children (Syn manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) --- | Match a series of terms or comments until a delimiter is matched +-- | Match a series of terms or comments until a delimiter is matched. manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term] manyTermsTill step end = manyTill (step <|> comment) end --- used in cases where the rules overlap, ie., step <|> comment and end can overlap someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) +-- | Match comments before and after the node. term :: Assignment -> Assignment term term = contextualize comment (postContextualize comment term) --- matches comments before and after the node +-- | Match expression :: Assignment expression = handleError (choice expressionChoices) --- "expression" --- choice walks the expressionChoices and inserts <|> (notionally but not really lol) expressions :: Assignment expressions = makeTerm'' <$> location <*> many expression @@ -181,32 +179,6 @@ modifier = make <$> symbol Modifier <*> children(Left <$> annotation <|> Right . where make loc (Right modifier) = makeTerm loc modifier make _ (Left annotation) = annotation --- if we don't match the annotation we will match the token --- don't do this if you have more than one word possible --- left fmap --- right - composing the right function after wrapping the bytestring of source in the accessibilityModifier syntax, then compose that with right function --- this enables us to have the same type in both places (either term (syntax.accessibilityModifier term)) --- whack error∷/Users/aymannadeem/github/semantic-diff/src/Language/Java/Assignment.hs:180:69: error: --- • Couldn't match type ‘Syntax.AccessibilityModifier a0’ --- with ‘Term.Term (Union Syntax) (Record Location)’ --- Expected type: Control.Monad.Free.Freer.Freer --- (Assigning.Assignment.Tracing --- (Assigning.Assignment.AssignmentF [] Grammar)) --- Term --- Actual type: Control.Monad.Free.Freer.Freer --- (Assigning.Assignment.Tracing --- (Assigning.Assignment.AssignmentF [] Grammar)) --- (Syntax.AccessibilityModifier a0) --- • In the second argument of ‘(<|>)’, namely --- ‘Syntax.AccessibilityModifier <$> source’ --- In the first argument of ‘children’, namely --- ‘(annotation <|> Syntax.AccessibilityModifier <$> source)’ --- In the second argument of ‘(<*>)’, namely --- ‘children (annotation <|> Syntax.AccessibilityModifier <$> source)’ --- | --- 180 | modifier = makeTerm <$> symbol Modifier <*> children(annotation <|> Syntax.AccessibilityModifier <$> source) --- | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ --- Failed, 118 modules loaded. arrayInitializer :: Assignment arrayInitializer = makeTerm <$> symbol ArrayInitializer <*> (Literal.Array <$> many expression) @@ -233,20 +205,15 @@ variableDeclaratorId :: Assignment variableDeclaratorId = symbol VariableDeclaratorId *> children identifier -- Literals - --- TODO: Need to disaggregate true/false in treesitter boolean :: Assignment boolean = makeTerm <$> symbol BooleanLiteral <*> children (token Grammar.True $> Literal.true <|> token Grammar.False $> Literal.false) --- *> pure = $> - null' :: Assignment null' = makeTerm <$> symbol NullLiteral <*> (Literal.Null <$ source) --- why is this <$? --- Supports all integer and floating point literals (hex, octal, binary) +-- Integer supports all integer and floating point literals (hex, octal, binary) integer :: Assignment integer = makeTerm <$> symbol IntegerLiteral <*> children (Literal.Integer <$> source) @@ -259,6 +226,14 @@ string = makeTerm <$> symbol StringLiteral <*> (Literal.TextElement <$> source) char :: Assignment char = makeTerm <$> symbol CharacterLiteral <*> (Literal.TextElement <$> source) +-- Identifiers +identifier :: Assignment +identifier = makeTerm <$> (symbol Identifier <|> symbol TypeIdentifier) <*> (Syntax.Identifier . name <$> source) + +scopedIdentifier :: Assignment +scopedIdentifier = makeTerm <$> symbol ScopedIdentifier <*> children (Expression.MemberAccess <$> term expression <*> term expression) + +-- Declarations class' :: Assignment class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many modifier <*> term identifier <*> (typeParameters <|> pure []) <*> emptyTerm <*> classBody) where @@ -267,33 +242,13 @@ class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many m -- might wanna come back and change to maybe superClass -- TODO: superclass -- need to match the superclass node when it exists (which will be a rule, similar to how the type params rule matches the typeparams node when it exists) --- consolidated with scopedIdentifier -identifier :: Assignment -identifier = makeTerm <$> (symbol Identifier <|> symbol TypeIdentifier) <*> (Syntax.Identifier . name <$> source) - -scopedIdentifier :: Assignment -scopedIdentifier = makeTerm <$> symbol ScopedIdentifier <*> children (Expression.MemberAccess <$> term expression <*> term expression) - --- refactor method declaration to have clearly understandable top-level rule + sub-rules broken out in the where so it's easier to reason about method :: Assignment method = makeTerm <$> symbol MethodDeclaration <*> children (makeMethod <$> many modifier <*> emptyTerm <*> methodHeader <*> methodBody) --- makeMethod is a wrapper that takes the arguments in the structure they occur in the grammar and rearranges them to satisfy the structure required for our syntax types where methodBody = symbol MethodBody *> children (term expression) methodDeclarator = symbol MethodDeclarator *> children ( (,) <$> identifier <*> formalParameters) methodHeader = symbol MethodHeader *> children ((,,,,) <$> (typeParameters <|> pure []) <*> manyTerm annotation <*> type' <*> methodDeclarator <*> (throws <|> pure [])) makeMethod modifiers receiver (typeParams, annotations, returnType, (name, params), throws) body = Declaration.Method (returnType : modifiers ++ typeParams ++ annotations ++ throws) receiver name params body --- emptyTerm can be inserted at any position; if you have an optional term, you can use a maybe, but if you have for ex. an else statement, --- where we wanna assume the else position always exists, emptyTerm allows us to keep the semantics for if-else really simple because we can --- just provide it emptyTerm --- emptyTerm just pattern matches; always produces a term. --- current location will be the methodHeader node. --- TODO: re-introduce makeTerm later; matching types as part of the type rule for now. --- full apply vs. half, what we want to retain --- before we had a left-associative chain where we were discarding the --- ((a + b) + c) --- a + bc --- bc = (b + c) -- TODO: add genericType @@ -324,25 +279,11 @@ package = makeTerm <$> symbol PackageDeclaration <*> children (Java.Syntax.Packa enum :: Assignment enum = makeTerm <$> symbol Grammar.EnumDeclaration <*> children (Java.Syntax.EnumDeclaration <$> term identifier <*> manyTerm enumConstant) where enumConstant = symbol EnumConstant *> children (term identifier) --- list of 0 or more --- Java.Syntax.EnumDeclaration is taking something that has been matched and applying a function over it --- makeTerm (a function) is not matching, but rather mapping over a matched term --- makeTerm is lifted into the <$> functor, which is applied to the result of its child assignments --- <*> apply is used when you've got a function built up on the LHS --- we don't have a makeTerm, so we don't have a function on the LHS to apply <*>, hence we just match on the symbol EnumConstant, and use it as a marker to descend into children --- we want the effect, not the result, of symbol because we want to match the EnumConstant node without caring about its range or span --- we don't care about the range and span because the identifier rule produces a term which already has a range and span --- show only has one argument, so we don't need to <*> because when we fmap it over a list, it's fully applied --- term = also accounts for preceding comments --- (+) <$> [1,2,3] :: Num a => [a -> a] -- it is a function that takes one number and returns another number of the same type return' :: Assignment return' = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children (expression)) --- can move the children into or out of the fmap rule because the children expression returns the result of a child --- so if you fmap over the result of RHS it's equivalent --- if you f <$> (g <$> a) == f . g <$> a (fusion law) --- if you have two nested fmaps, same as composing +-- method expressions dims :: Assignment.Assignment [] Grammar [Term] dims = symbol Dims *> children (many (emptyTerm <* token AnonLBracket <* token AnonRBracket)) @@ -358,11 +299,6 @@ type' = choice [ , identifier ] where array type' = foldl (\into each -> makeTerm1 (Type.Array (Just each) into)) type' - -- <|> makeTerm <$> symbol FloatingPointType <*> children (token AnonFloat $> Type.Float <|> token AnonDouble $> Type.Double) - -- we had to say token with the first 4 because pure don't advance past the first nodes; implies no effect, just produces value - -- if we want to match a node and consume that node (which we have to do) we need to use token because it has that behavior - --- method expressions if' :: Assignment if' = makeTerm <$> symbol IfThenElseStatement <*> children (Statement.If <$> term expression <*> term expression <*> (term expression <|> emptyTerm)) @@ -375,19 +311,15 @@ while = makeTerm <$> symbol WhileStatement <*> children (Statement.While <$> ter doWhile :: Assignment doWhile = makeTerm <$> symbol DoStatement <*> children (flip Statement.DoWhile <$> term expression <*> term expression) --- flipping so when we match body it goes into second field and when we match condition it goes into the first field switch :: Assignment switch = makeTerm <$> symbol SwitchStatement <*> children (Statement.Match <$> term expression <*> switchBlock) where switchBlock = makeTerm <$> symbol SwitchBlock <*> children (manyTerm switchLabel) switchLabel = makeTerm <$> symbol SwitchLabel <*> (Statement.Pattern <$> children (term expression <|> emptyTerm) <*> expressions) --- not identifier, expression break :: Assignment break = makeTerm <$> symbol BreakStatement <*> children (Statement.Break <$> (term expression <|> emptyTerm)) --- manyTerm matches 0 or more and also produces a list --- term expression <|> emptyTerm accounts for an expression or nothing at all continue :: Assignment continue = makeTerm <$> symbol ContinueStatement <*> children (Statement.Continue <$> (term expression <|> emptyTerm)) @@ -410,30 +342,16 @@ try = makeTerm <$> symbol TryStatement <*> children (Statement.Try <$> term expr for :: Assignment for = symbol ForStatement *> children (basicFor <|> enhancedFor) --- dropping so *> basicFor :: Assignment basicFor = makeTerm <$> symbol BasicForStatement <*> children (Statement.For <$ token AnonFor <* token AnonLParen <*> (token AnonSemicolon *> emptyTerm <|> forInit <* token AnonSemicolon) <*> (token AnonSemicolon *> emptyTerm <|> term expression <* token AnonSemicolon) <*> forStep <*> term expression) where forInit = symbol ForInit *> children (term expression) forStep = makeTerm <$> location <*> manyTermsTill expression (token AnonRParen) --- don't have symbol to match against for forStep because we don't know what that would be, but we need to still provide an annotation and location --- location rule = for when you need to provide a location without matching any nodes --- don't need to make a term here because term sion already produces a term --- makeTerm is used when the data constructor (syntax) field has an element, not a list --- Statement.For = data constructor that takes three statements and produces a piece of syntax --- don't need to produce syntax with term expression (already produces a term) so don't need to makeTerm --- dont wanna do manyTerm because it'll greedily match any of the expressions it can which means it'll match the for loop body, which would fail... --- because it would've already matched it and consumed it and the whole rule would fail because it wouldn't be available enhancedFor :: Assignment enhancedFor = makeTerm <$> symbol EnhancedForStatement <*> children (Statement.ForEach <$> (variable <$> manyTerm modifier <*> type' <*> variableDeclaratorId) <*> term expression <*> term expression) where variable modifiers type' variableDeclaratorId = makeTerm1 (Java.Syntax.Variable modifiers type' variableDeclaratorId) --- variableDeclaratorId takes name and then type' so that's the order we give it, but variable takes type' first and variableDeclaratorId --- going to populate binding field with a new term which should be a variable --- binding = variable --- subject = thing being iterated over --- body -- TODO: instanceOf binary :: Assignment @@ -514,16 +432,9 @@ update = makeTerm' <$> symbol UpdateExpression <*> children ( <|> inj . Statement.PreDecrement <$ token AnonMinusMinus <*> term expression <|> inj . Statement.PostIncrement <$> term expression <* token AnonPlusPlus <|> inj . Statement.PostDecrement <$> term expression <* token AnonMinusMinus) --- makterm' so need inj . --- tries them in order; true of alternations, order matters; (if-else) --- but choice doesn't have this property (order doesn't matter) because it constructs a jump table (switch) ternary :: Assignment ternary = makeTerm <$> symbol TernaryExpression <*> children (Statement.If <$> term expression <*> term expression <*> term expression) --- delimiter, if optional, need --- token vs. symbol -- whether we want to skip past the node or not; token skips past the node; symbol does not --- need token or symbol to mention any token/symbol because they take a token and produce a grammar rule --- infix operators synchronized :: Assignment synchronized = makeTerm <$> symbol SynchronizedStatement <*> children (Java.Syntax.Synchronized <$> term expression <*> term expression) @@ -538,7 +449,6 @@ argumentList = symbol ArgumentList *> children (manyTerm expression) super :: Assignment super = makeTerm <$> token Super <*> pure Expression.Super --- not a rule so using pure to lift value into an assignment this :: Assignment this = makeTerm <$> token This <*> pure Expression.This @@ -556,10 +466,6 @@ typeParameters = symbol TypeParameters *> children (manyTerm typeParam) -- this where typeParam = makeTerm <$> symbol Grammar.TypeParameter <*> children (Java.Syntax.TypeParameter <$> manyTerm annotation <*> term identifier <*> (typeBound <|> pure [])) -- wrapping up all three of those fields so we need to makeTerm (producing a term here) typeBound = symbol TypeBound *> children (manyTerm type') --- stubbing in so deals with empty list --- come back and populate this --- optional combinator produces type Maybe --- instead of optional and maybe, we have that arg as a list now and we say we either produce the list or an empty list via pure [] annotation :: Assignment annotation = makeTerm <$> symbol NormalAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> (elementValuePairList <|> pure [])) @@ -569,14 +475,9 @@ annotation = makeTerm <$> symbol NormalAnnotation <*> children (Java.Syntax.Anno elementValuePairList = symbol ElementValuePairList *> children (manyTerm elementValuePair) elementValuePair = makeTerm <$> symbol ElementValuePair <*> children (Java.Syntax.AnnotationField <$> term expression <*> term elementValue) elementValue = symbol ElementValue *> children (term expression) --- pure over lists can produce single element lists; wrapping the expression in a list --- elementValue, we don't have syntax to construct; we only construct syntax when we're making a node throws :: Assignment.Assignment [] Grammar [Term] throws = symbol Throws *> children (symbol ExceptionTypeList *> children(manyTerm type')) --- discard the symbol and get the result of rule --- match a throws node, and apply the rest of the to its children --- we are matching the structure in the grammar formalParameters :: Assignment.Assignment [] Grammar [Term] formalParameters = manyTerm parameter From f0189229117362e499d682bca72cbf7745e229b1 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 27 Apr 2018 15:50:39 -0700 Subject: [PATCH 36/68] add tests --- example.java | 6 ++-- src/Language/Java/Assignment.hs | 2 +- test/fixtures/java/binary.java | 19 +++++++++++++ test/fixtures/java/boolean.java | 5 ++++ test/fixtures/java/char.java | 5 ++++ test/fixtures/java/comment.java | 5 ++++ test/fixtures/java/continue.java | 14 ++++++++++ test/fixtures/java/dims.java | 4 +++ test/fixtures/java/do-while.java | 9 ++++++ test/fixtures/java/enum.java | 3 ++ test/fixtures/java/float.java | 5 ++++ test/fixtures/java/for.java | 7 +++++ test/fixtures/java/if.java | 2 ++ test/fixtures/java/import.java | 1 + test/fixtures/java/int.java | 5 ++++ test/fixtures/java/interface.java | 2 ++ test/fixtures/java/modifier-abstract.java | 3 ++ test/fixtures/java/modifier-private.java | 1 + test/fixtures/java/modifier-protected.java | 3 ++ test/fixtures/java/modifier-public.java | 3 ++ test/fixtures/java/modifier-static.java | 3 ++ test/fixtures/java/null.java | 5 ++++ test/fixtures/java/package.java | 1 + test/fixtures/java/return.java | 5 ++++ test/fixtures/java/string.java | 5 ++++ test/fixtures/java/switch.java | 29 ++++++++++++++++++++ test/fixtures/java/throws.java | 5 ++++ test/fixtures/java/try-catches.java | 19 +++++++++++++ test/fixtures/java/update.java | 4 +++ test/fixtures/java/variable-declaration.java | 1 + test/fixtures/java/while.java | 9 ++++++ 31 files changed, 187 insertions(+), 3 deletions(-) create mode 100644 test/fixtures/java/binary.java create mode 100644 test/fixtures/java/boolean.java create mode 100644 test/fixtures/java/char.java create mode 100644 test/fixtures/java/comment.java create mode 100644 test/fixtures/java/continue.java create mode 100644 test/fixtures/java/dims.java create mode 100644 test/fixtures/java/do-while.java create mode 100644 test/fixtures/java/enum.java create mode 100644 test/fixtures/java/float.java create mode 100644 test/fixtures/java/for.java create mode 100644 test/fixtures/java/if.java create mode 100644 test/fixtures/java/import.java create mode 100644 test/fixtures/java/int.java create mode 100644 test/fixtures/java/interface.java create mode 100644 test/fixtures/java/modifier-abstract.java create mode 100644 test/fixtures/java/modifier-private.java create mode 100644 test/fixtures/java/modifier-protected.java create mode 100644 test/fixtures/java/modifier-public.java create mode 100644 test/fixtures/java/modifier-static.java create mode 100644 test/fixtures/java/null.java create mode 100644 test/fixtures/java/package.java create mode 100644 test/fixtures/java/return.java create mode 100644 test/fixtures/java/string.java create mode 100644 test/fixtures/java/switch.java create mode 100644 test/fixtures/java/throws.java create mode 100644 test/fixtures/java/try-catches.java create mode 100644 test/fixtures/java/update.java create mode 100644 test/fixtures/java/variable-declaration.java create mode 100644 test/fixtures/java/while.java diff --git a/example.java b/example.java index b4da52ef6..272fff7f4 100644 --- a/example.java +++ b/example.java @@ -1,4 +1,6 @@ -class someClass { - public static void anotherMethod(S arg) { +class Hello { + class someClass extends Hello { + public static void anotherMethod(S arg) { + } } } diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index c9dcabc1a..69733392d 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -239,6 +239,7 @@ class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many m where makeClass modifiers identifier typeParams superClass classBody = Declaration.Class (modifiers ++ typeParams) identifier [superClass] classBody -- not doing an assignment, just straight up function classBody = makeTerm <$> symbol ClassBody <*> children (manyTerm expression) + -- superClass = makeTerm <$> symbol SuperClass <*> -- might wanna come back and change to maybe superClass -- TODO: superclass -- need to match the superclass node when it exists (which will be a rule, similar to how the type params rule matches the typeparams node when it exists) @@ -424,7 +425,6 @@ unary = make <$> symbol UnaryExpression <*> children ((,) <$> operator <*> term <|> token AnonMinus $> UMinus <|> token AnonBang $> UBang <|> token AnonTilde $> UTilde - -- had to use make because we didn't always make a term update :: Assignment update = makeTerm' <$> symbol UpdateExpression <*> children ( diff --git a/test/fixtures/java/binary.java b/test/fixtures/java/binary.java new file mode 100644 index 000000000..9315e2959 --- /dev/null +++ b/test/fixtures/java/binary.java @@ -0,0 +1,19 @@ +a > b; +a < b; +a == b; +a >= b; +a <= b; +a != b; +a && b; +a || b; +a & b; +a | b; +a ^ b; +a % b; +a << b; +a >> b; +a >>> b; +3 + 2; +3 - 2; +3 * 2; +9 / 3; diff --git a/test/fixtures/java/boolean.java b/test/fixtures/java/boolean.java new file mode 100644 index 000000000..fb41c1f1e --- /dev/null +++ b/test/fixtures/java/boolean.java @@ -0,0 +1,5 @@ +public class Point { + void dinosaur() { + Boolean x = true; + } +} diff --git a/test/fixtures/java/char.java b/test/fixtures/java/char.java new file mode 100644 index 000000000..4e598bff0 --- /dev/null +++ b/test/fixtures/java/char.java @@ -0,0 +1,5 @@ +public class Point { + void dinosaur() { + Char a = 'a'; + } +} diff --git a/test/fixtures/java/comment.java b/test/fixtures/java/comment.java new file mode 100644 index 000000000..8e4e9fc62 --- /dev/null +++ b/test/fixtures/java/comment.java @@ -0,0 +1,5 @@ +// This is a single-line comment. + +/* This is +a multi-line +comment */ diff --git a/test/fixtures/java/continue.java b/test/fixtures/java/continue.java new file mode 100644 index 000000000..7703f1651 --- /dev/null +++ b/test/fixtures/java/continue.java @@ -0,0 +1,14 @@ +public class Test { + + public static void main(String args[]) { + int [] numbers = {10, 20, 30, 40, 50}; + + for(int x : numbers ) { + if( x == 30 ) { + continue; + } + System.out.print( x ); + System.out.print("\n"); + } + } +} diff --git a/test/fixtures/java/dims.java b/test/fixtures/java/dims.java new file mode 100644 index 000000000..832f32599 --- /dev/null +++ b/test/fixtures/java/dims.java @@ -0,0 +1,4 @@ +class ForDemo { + void main(String[] args){ + } +} diff --git a/test/fixtures/java/do-while.java b/test/fixtures/java/do-while.java new file mode 100644 index 000000000..d344f8b93 --- /dev/null +++ b/test/fixtures/java/do-while.java @@ -0,0 +1,9 @@ +class WhileDemo { + public static void main(String[] args){ + do { + System.out.print("Guess my name: "); + guess = scanner.nextLine(); + } + while (!"Daffy Duck".equals(guess)); + } +} diff --git a/test/fixtures/java/enum.java b/test/fixtures/java/enum.java new file mode 100644 index 000000000..6b7dc1194 --- /dev/null +++ b/test/fixtures/java/enum.java @@ -0,0 +1,3 @@ +enum HandSign { + SCISSOR, PAPER, STONE +} diff --git a/test/fixtures/java/float.java b/test/fixtures/java/float.java new file mode 100644 index 000000000..93141266e --- /dev/null +++ b/test/fixtures/java/float.java @@ -0,0 +1,5 @@ +public class Point { + void dinosaur() { + Float x = 10.0; + } +} diff --git a/test/fixtures/java/for.java b/test/fixtures/java/for.java new file mode 100644 index 000000000..0a6f0f757 --- /dev/null +++ b/test/fixtures/java/for.java @@ -0,0 +1,7 @@ +class ForDemo { + public static void main(String[] args){ + for(int i=1; i<11; i++){ + System.out.println("Count is: " + i); + } + } +} diff --git a/test/fixtures/java/if.java b/test/fixtures/java/if.java new file mode 100644 index 000000000..a00e30c3b --- /dev/null +++ b/test/fixtures/java/if.java @@ -0,0 +1,2 @@ +if (x) + y; diff --git a/test/fixtures/java/import.java b/test/fixtures/java/import.java new file mode 100644 index 000000000..e2574c845 --- /dev/null +++ b/test/fixtures/java/import.java @@ -0,0 +1 @@ +import javax.swing.JOptionPane; diff --git a/test/fixtures/java/int.java b/test/fixtures/java/int.java new file mode 100644 index 000000000..ac5ce9267 --- /dev/null +++ b/test/fixtures/java/int.java @@ -0,0 +1,5 @@ +public class Point { + void dinosaur() { + Int x = 1; + } +} diff --git a/test/fixtures/java/interface.java b/test/fixtures/java/interface.java new file mode 100644 index 000000000..432a2c27e --- /dev/null +++ b/test/fixtures/java/interface.java @@ -0,0 +1,2 @@ +interface Top { +} diff --git a/test/fixtures/java/modifier-abstract.java b/test/fixtures/java/modifier-abstract.java new file mode 100644 index 000000000..67415f10b --- /dev/null +++ b/test/fixtures/java/modifier-abstract.java @@ -0,0 +1,3 @@ +abstract class Point { + +} diff --git a/test/fixtures/java/modifier-private.java b/test/fixtures/java/modifier-private.java new file mode 100644 index 000000000..8b1378917 --- /dev/null +++ b/test/fixtures/java/modifier-private.java @@ -0,0 +1 @@ + diff --git a/test/fixtures/java/modifier-protected.java b/test/fixtures/java/modifier-protected.java new file mode 100644 index 000000000..22ffbbd51 --- /dev/null +++ b/test/fixtures/java/modifier-protected.java @@ -0,0 +1,3 @@ +protected class Point { + +} diff --git a/test/fixtures/java/modifier-public.java b/test/fixtures/java/modifier-public.java new file mode 100644 index 000000000..c3915b5ff --- /dev/null +++ b/test/fixtures/java/modifier-public.java @@ -0,0 +1,3 @@ +public class Point { + +} diff --git a/test/fixtures/java/modifier-static.java b/test/fixtures/java/modifier-static.java new file mode 100644 index 000000000..faa2ea4a5 --- /dev/null +++ b/test/fixtures/java/modifier-static.java @@ -0,0 +1,3 @@ +public static class Point { + +} diff --git a/test/fixtures/java/null.java b/test/fixtures/java/null.java new file mode 100644 index 000000000..8bfa02284 --- /dev/null +++ b/test/fixtures/java/null.java @@ -0,0 +1,5 @@ +public class Point { + void dinosaur() { + String str = null; + } +} diff --git a/test/fixtures/java/package.java b/test/fixtures/java/package.java new file mode 100644 index 000000000..0f6c010ba --- /dev/null +++ b/test/fixtures/java/package.java @@ -0,0 +1 @@ +package myVector; diff --git a/test/fixtures/java/return.java b/test/fixtures/java/return.java new file mode 100644 index 000000000..40f8dc870 --- /dev/null +++ b/test/fixtures/java/return.java @@ -0,0 +1,5 @@ +public class Point { + void dinosaur() { + return x; + } +} diff --git a/test/fixtures/java/string.java b/test/fixtures/java/string.java new file mode 100644 index 000000000..e59d3a44a --- /dev/null +++ b/test/fixtures/java/string.java @@ -0,0 +1,5 @@ +public class Point { + void dinosaur() { + String str = "yo wassup"; + } +} diff --git a/test/fixtures/java/switch.java b/test/fixtures/java/switch.java new file mode 100644 index 000000000..4a88ab728 --- /dev/null +++ b/test/fixtures/java/switch.java @@ -0,0 +1,29 @@ +public class Test +{ + public static void main(String[] args) + { + int day = 5; + String dayString; + + switch (day) + { + case 1: dayString = "Monday"; + break; + case 2: dayString = "Tuesday"; + break; + case 3: dayString = "Wednesday"; + break; + case 4: dayString = "Thursday"; + break; + case 5: dayString = "Friday"; + break; + case 6: dayString = "Saturday"; + break; + case 7: dayString = "Sunday"; + break; + default: dayString = "Invalid day"; + break; + } + System.out.println(dayString); + } +} diff --git a/test/fixtures/java/throws.java b/test/fixtures/java/throws.java new file mode 100644 index 000000000..09c46ce9f --- /dev/null +++ b/test/fixtures/java/throws.java @@ -0,0 +1,5 @@ +class Beyonce { + BufferedReader newReader() throws FileNotFoundException { + new BufferedReader(new InputStreamReader(new FileInputStream(file), charset)); + } +} diff --git a/test/fixtures/java/try-catches.java b/test/fixtures/java/try-catches.java new file mode 100644 index 000000000..6989bfc22 --- /dev/null +++ b/test/fixtures/java/try-catches.java @@ -0,0 +1,19 @@ +class Example2{ + public static void main(String args[]){ + try{ + int a[]=new int[7]; + a[4]=30/0; + System.out.println("First print statement in try block"); + } + catch(ArithmeticException e){ + System.out.println("Warning: ArithmeticException"); + } + catch(ArrayIndexOutOfBoundsException e){ + System.out.println("Warning: ArrayIndexOutOfBoundsException"); + } + catch(Exception e){ + System.out.println("Warning: Some Other exception"); + } + System.out.println("Out of try-catch block..."); + } +} diff --git a/test/fixtures/java/update.java b/test/fixtures/java/update.java new file mode 100644 index 000000000..9d356b0b2 --- /dev/null +++ b/test/fixtures/java/update.java @@ -0,0 +1,4 @@ +foo++; +++bar; +baz--; +--boo; diff --git a/test/fixtures/java/variable-declaration.java b/test/fixtures/java/variable-declaration.java new file mode 100644 index 000000000..3694828b8 --- /dev/null +++ b/test/fixtures/java/variable-declaration.java @@ -0,0 +1 @@ +int x = 3; diff --git a/test/fixtures/java/while.java b/test/fixtures/java/while.java new file mode 100644 index 000000000..b84737254 --- /dev/null +++ b/test/fixtures/java/while.java @@ -0,0 +1,9 @@ +class WhileDemo { + public static void main(String[] args){ + int count = 1; + while (count < 11) { + System.out.println("Count is: " + count); + count++; + } + } +} From 64620484e19507f97c53a2c51f82a7ee639691da Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 1 May 2018 10:44:15 -0700 Subject: [PATCH 37/68] assigning generic and superclass --- example.java | 6 +----- src/Language/Java/Assignment.hs | 28 +++++++++++++++++++++++----- src/Language/Java/Syntax.hs | 10 ++++++++++ 3 files changed, 34 insertions(+), 10 deletions(-) diff --git a/example.java b/example.java index 272fff7f4..fbe40be7a 100644 --- a/example.java +++ b/example.java @@ -1,6 +1,2 @@ -class Hello { - class someClass extends Hello { - public static void anotherMethod(S arg) { - } - } +class Hello extends someClass <> { } diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 69733392d..eb9f561a4 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -27,6 +27,7 @@ import qualified Data.Syntax.Statement as Statement import qualified Data.Syntax.Type as Type import qualified Data.Term as Term import Prelude hiding (break) +import Prologue hiding (for, try, This) type Syntax = '[ Comment.Comment @@ -48,6 +49,7 @@ type Syntax = , Java.Syntax.Asterisk , Java.Syntax.Constructor , Java.Syntax.EnumDeclaration + , Java.Syntax.GenericType , Java.Syntax.Import , Java.Syntax.Module , Java.Syntax.New @@ -235,12 +237,18 @@ scopedIdentifier = makeTerm <$> symbol ScopedIdentifier <*> children (Expression -- Declarations class' :: Assignment -class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many modifier <*> term identifier <*> (typeParameters <|> pure []) <*> emptyTerm <*> classBody) +class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many modifier <*> term identifier <*> (typeParameters <|> pure []) <*> optional superClass <*> classBody) where - makeClass modifiers identifier typeParams superClass classBody = Declaration.Class (modifiers ++ typeParams) identifier [superClass] classBody -- not doing an assignment, just straight up function + makeClass modifiers identifier typeParams superClass classBody = Declaration.Class (modifiers ++ typeParams) identifier (maybeToList superClass) classBody -- not doing an assignment, just straight up function classBody = makeTerm <$> symbol ClassBody <*> children (manyTerm expression) - -- superClass = makeTerm <$> symbol SuperClass <*> --- might wanna come back and change to maybe superClass + superClass = symbol Superclass *> children type' + -- matching term expression won't work since there is no node for that; it's AnonExtends + -- superClass = makeTerm <$> symbol SuperClass <*> children (Java.Syntax.SuperClass <$> term expression <*> type') + -- We'd still like to match the SuperClass node, but we don't need to create a syntax to make a term + -- Do you lose info by omitting the superclass term? No... + -- Don't need to make a term since we're not using syntax + -- what's the difference between using tokens: AnonExtends GenericType? + -- optional: when something can or can't exist and you want to produce a Maybe -- TODO: superclass -- need to match the superclass node when it exists (which will be a rule, similar to how the type params rule matches the typeparams node when it exists) method :: Assignment @@ -252,6 +260,13 @@ method = makeTerm <$> symbol MethodDeclaration <*> children (makeMethod <$> many makeMethod modifiers receiver (typeParams, annotations, returnType, (name, params), throws) body = Declaration.Method (returnType : modifiers ++ typeParams ++ annotations ++ throws) receiver name params body -- TODO: add genericType +-- Question: should this genericType be part of type or not? Its own type because it's different structurally + +generic :: Assignment +generic = makeTerm <$> symbol Grammar.GenericType <*> children(Java.Syntax.GenericType <$> term type' <*> manyTerm type') +-- when do we make a term again? - if we want to wrap something in a syntax constructor, because each piece of syntax +-- will be populated by further terms inside it. in this case, we wrap two terms in a piece of syntax. +-- Q to help decide: do we lose anything by omitting the term? methodInvocation :: Assignment methodInvocation = makeTerm <$> symbol MethodInvocation <*> children (Expression.Call [] <$> (callFunction <$> term expression <*> optional (token AnonDot *> term expression)) <*> argumentList <*> emptyTerm) @@ -294,10 +309,13 @@ type' = choice [ , makeTerm <$> token IntegralType <*> pure Type.Int , makeTerm <$> token FloatingPointType <*> pure Type.Float , makeTerm <$> token BooleanType <*> pure Type.Bool - , symbol ArrayType *> children (array <$> type' <*> dims) + , symbol ArrayType *> children (array <$> type' <*> dims) -- type rule recurs into itself , symbol CatchType *> children (term type') , symbol ExceptionType *> children (term type') + , symbol TypeArgument *> children (term type') + -- , symbol WildCard *> children (term type') , identifier + , generic ] where array type' = foldl (\into each -> makeTerm1 (Type.Array (Just each) into)) type' diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index f3bb795b4..e1d3ec812 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -127,3 +127,13 @@ instance Show1 AnnotationField where liftShowsPrec = genericLiftShowsPrec -- TODO: Implement Eval instance for AnnotationField instance Evaluatable AnnotationField + +data GenericType a = GenericType { genericTypeIdentifier :: a, genericTypeArguments :: [a] } + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + +instance Eq1 GenericType where liftEq = genericLiftEq +instance Ord1 GenericType where liftCompare = genericLiftCompare +instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for GenericType +instance Evaluatable GenericType From 662e6b5bba4757192f66837d6e77937ae334acc3 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 1 May 2018 10:45:20 -0700 Subject: [PATCH 38/68] bump tree-sitter-java --- vendor/haskell-tree-sitter | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vendor/haskell-tree-sitter b/vendor/haskell-tree-sitter index ab0654689..07ea0c53d 160000 --- a/vendor/haskell-tree-sitter +++ b/vendor/haskell-tree-sitter @@ -1 +1 @@ -Subproject commit ab06546890d140fd8fd725e3536d0e9d434226a0 +Subproject commit 07ea0c53d6e4c910fef7a97d4356e74644cab7ff From 829b0d44e07118ece2bc9825deeb1f49ec7f5615 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 1 May 2018 16:22:34 -0700 Subject: [PATCH 39/68] add Declarations1 typeclass to syntax data types --- src/Data/Syntax/Expression.hs | 4 ++-- src/Data/Syntax/Statement.hs | 4 ++-- src/Data/Syntax/Type.hs | 11 +++++++---- src/Language/Java/Syntax.hs | 32 ++++++++++++++------------------ 4 files changed, 25 insertions(+), 26 deletions(-) diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index fa45794db..ac29e17f7 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -295,7 +295,7 @@ instance Show1 Cast where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Cast data Super a = Super - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Super where liftEq = genericLiftEq instance Ord1 Super where liftCompare = genericLiftCompare @@ -303,7 +303,7 @@ instance Show1 Super where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Super data This a = This - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 This where liftEq = genericLiftEq instance Ord1 This where liftCompare = genericLiftCompare diff --git a/src/Data/Syntax/Statement.hs b/src/Data/Syntax/Statement.hs index dcd99a4e9..2a1a2eb95 100644 --- a/src/Data/Syntax/Statement.hs +++ b/src/Data/Syntax/Statement.hs @@ -129,7 +129,7 @@ instance Evaluatable PostDecrement -- | Pre increment operator (e.g. ++1 in C or Java). newtype PreIncrement a = PreIncrement a - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 PreIncrement where liftEq = genericLiftEq instance Ord1 PreIncrement where liftCompare = genericLiftCompare @@ -141,7 +141,7 @@ instance Evaluatable PreIncrement -- | Pre decrement operator (e.g. --1 in C or Java). newtype PreDecrement a = PreDecrement a - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 PreDecrement where liftEq = genericLiftEq instance Ord1 PreDecrement where liftCompare = genericLiftCompare diff --git a/src/Data/Syntax/Type.hs b/src/Data/Syntax/Type.hs index b86039c27..6d271a144 100644 --- a/src/Data/Syntax/Type.hs +++ b/src/Data/Syntax/Type.hs @@ -130,7 +130,7 @@ instance Evaluatable TypeParameters -- data instead of newtype because no payload data Void a = Void - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Void where liftEq = genericLiftEq instance Ord1 Void where liftCompare = genericLiftCompare @@ -141,7 +141,7 @@ instance Evaluatable Void -- data instead of newtype because no payload data Int a = Int - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Int where liftEq = genericLiftEq instance Ord1 Int where liftCompare = genericLiftCompare @@ -151,14 +151,17 @@ instance Show1 Int where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Int data Float a = Float | Double - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Float where liftEq = genericLiftEq instance Ord1 Float where liftCompare = genericLiftCompare instance Show1 Float where liftShowsPrec = genericLiftShowsPrec +-- TODO: Implement Eval instance for Float +instance Evaluatable Float + data Bool a = Bool - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Bool where liftEq = genericLiftEq instance Ord1 Bool where liftCompare = genericLiftCompare diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index e1d3ec812..382aa355c 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -6,7 +6,7 @@ import Diffing.Algorithm import Prologue hiding (Constructor) newtype Import a = Import [a] - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1) instance Eq1 Import where liftEq = genericLiftEq instance Ord1 Import where liftCompare = genericLiftCompare @@ -16,20 +16,16 @@ instance Show1 Import where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Import data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Module where liftEq = genericLiftEq instance Ord1 Module where liftCompare = genericLiftCompare instance Show1 Module where liftShowsPrec = genericLiftShowsPrec -instance Evaluatable Module where - eval (Module iden xs) = do - name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden) - letrec' name $ \addr -> - eval xs <* makeNamespace name addr [] +instance Evaluatable Module newtype Package a = Package [a] - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1) instance Eq1 Package where liftEq = genericLiftEq instance Ord1 Package where liftCompare = genericLiftCompare @@ -39,7 +35,7 @@ instance Show1 Package where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Package data EnumDeclaration a = EnumDeclaration { _enumDeclarationIdentifier :: !a, _enumDeclarationBody :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 EnumDeclaration where liftEq = genericLiftEq instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare @@ -48,7 +44,7 @@ instance Evaluatable EnumDeclaration data Variable a = Variable { variableModifiers :: ![a], variableType :: !a, variableName :: !a} - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Variable where liftEq = genericLiftEq instance Ord1 Variable where liftCompare = genericLiftCompare @@ -58,7 +54,7 @@ instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Variable data Synchronized a = Synchronized { synchronizedSubject :: !a, synchronizedBody :: !a} - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Synchronized where liftEq = genericLiftEq instance Ord1 Synchronized where liftCompare = genericLiftCompare @@ -68,7 +64,7 @@ instance Show1 Synchronized where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Synchronized data New a = New { newType :: !a, newArgs :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 New where liftEq = genericLiftEq instance Ord1 New where liftCompare = genericLiftCompare @@ -78,7 +74,7 @@ instance Show1 New where liftShowsPrec = genericLiftShowsPrec instance Evaluatable New data Asterisk a = Asterisk - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Asterisk where liftEq = genericLiftEq instance Ord1 Asterisk where liftCompare = genericLiftCompare @@ -89,7 +85,7 @@ instance Evaluatable Asterisk data Constructor a = Constructor { constructorModifiers :: ![a], constructorTypeParams :: ![a], constructorIdentifier :: !a, constructorParams :: ![a], constructorThrows :: ![a], constructorBody :: a} - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Constructor where liftEq = genericLiftEq instance Ord1 Constructor where liftCompare = genericLiftCompare @@ -99,7 +95,7 @@ instance Show1 Constructor where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Constructor data TypeParameter a = TypeParameter { typeParamAnnotation :: ![a], typeParamIdentifier :: !a, typeParamTypeBound :: ![a]} - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 TypeParameter where liftEq = genericLiftEq instance Ord1 TypeParameter where liftCompare = genericLiftCompare @@ -109,7 +105,7 @@ instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec instance Evaluatable TypeParameter data Annotation a = Annotation { annotationName :: !a, annotationField :: [a]} - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Annotation where liftEq = genericLiftEq instance Ord1 Annotation where liftCompare = genericLiftCompare @@ -119,7 +115,7 @@ instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Annotation data AnnotationField a = AnnotationField { annotationFieldName :: a, annotationFieldValue :: a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 AnnotationField where liftEq = genericLiftEq instance Ord1 AnnotationField where liftCompare = genericLiftCompare @@ -129,7 +125,7 @@ instance Show1 AnnotationField where liftShowsPrec = genericLiftShowsPrec instance Evaluatable AnnotationField data GenericType a = GenericType { genericTypeIdentifier :: a, genericTypeArguments :: [a] } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 GenericType where liftEq = genericLiftEq instance Ord1 GenericType where liftCompare = genericLiftCompare From 759e520eef973e329c44ef4663e92eee1ed6290b Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 1 May 2018 16:24:04 -0700 Subject: [PATCH 40/68] add TypeWithModifiers syntax to allow formal params to match on type modifiers --- src/Language/Java/Assignment.hs | 9 ++++++++- src/Language/Java/Syntax.hs | 10 ++++++++++ 2 files changed, 18 insertions(+), 1 deletion(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index eb9f561a4..722925755 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -56,6 +56,7 @@ type Syntax = , Java.Syntax.Package , Java.Syntax.Synchronized , Java.Syntax.TypeParameter + , Java.Syntax.TypeWithModifiers , Java.Syntax.Variable , Literal.Array , Literal.Boolean @@ -500,4 +501,10 @@ throws = symbol Throws *> children (symbol ExceptionTypeList *> children(manyTer formalParameters :: Assignment.Assignment [] Grammar [Term] formalParameters = manyTerm parameter where - parameter = makeTerm <$> symbol FormalParameter <*> children (flip Type.Annotation <$> type' <* symbol VariableDeclaratorId <*> children identifier) + parameter = makeTerm <$> symbol FormalParameter <*> children (makeAnnotation <$> manyTerm modifier <*> type' <* symbol VariableDeclaratorId <*> children identifier) + makeAnnotation [] type' variableName = Type.Annotation variableName type' + makeAnnotation modifiers type' variableName = Type.Annotation variableName (makeTerm1 (Java.Syntax.TypeWithModifiers modifiers type')) +-- know when we are in a functor context and fmap is all gravy +-- we're just wrapping stuff up in data, we aren't building a pattern (assignment) so we aren't in an applicative context +-- when in an applicative context, we're also in a functor context (ie., defining how fmap will work over it) +-- sometimes it is nice to be able to say you're in an applicative context without refering to any particular applicative instance diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index 382aa355c..5e6dddd38 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -133,3 +133,13 @@ instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec -- TODO: Implement Eval instance for GenericType instance Evaluatable GenericType + +data TypeWithModifiers a = TypeWithModifiers [a] a + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + +instance Eq1 TypeWithModifiers where liftEq = genericLiftEq +instance Ord1 TypeWithModifiers where liftCompare = genericLiftCompare +instance Show1 TypeWithModifiers where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Implement Eval instance for TypeWithModifiers +instance Evaluatable TypeWithModifiers From 678122c8c30dfb92eb0bce3af66da475f0bd008d Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 1 May 2018 16:25:36 -0700 Subject: [PATCH 41/68] extract variableDeclaratorList into top-level rule to be used in field declaration --- src/Language/Java/Assignment.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 722925755..c515e7fed 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -146,6 +146,7 @@ expressionChoices = , constructorDeclaration -- , constantDeclaration , doWhile + , fieldDeclaration , float , for , enum @@ -193,13 +194,15 @@ comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) -- constantDeclaration = makeTerm <$> symbol ConstantDeclaration <*> localVariableDeclaration :: Assignment -localVariableDeclaration = makeDecl <$> symbol LocalVariableDeclaration <*> children ((,,) <$> manyTerm modifier <*> type' <*> vDeclList) +localVariableDeclaration = makeTerm <$> symbol LocalVariableDeclaration <*> children ((,) <$> manyTerm modifier <*> type' <**> variableDeclaratorList) + +variableDeclaratorList :: Assignment.Assignment [] Grammar (([Term], Term) -> [Term]) +variableDeclaratorList = symbol VariableDeclaratorList *> children (makeDecl <$> some variableDeclarator) where + variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variableDeclaratorId <*> optional expression) + makeDecl decls (modifiers, type') = map (makeSingleDecl modifiers type') decls makeSingleDecl modifiers type' (target, Nothing) = makeTerm1 (Java.Syntax.Variable modifiers type' target) makeSingleDecl modifiers type' (target, Just value) = makeTerm1 (Statement.Assignment [] (makeTerm1 (Java.Syntax.Variable modifiers type' target)) value) - makeDecl loc (modifiers, type', decls) = makeTerm'' loc $ fmap (makeSingleDecl modifiers type') decls -- we need loc here because it's the outermost node that comprises the list of all things - vDeclList = symbol VariableDeclaratorList *> children (some variableDeclarator) - variableDeclarator = symbol VariableDeclarator *> children ((,) <$> variableDeclaratorId <*> optional expression) localVariableDeclarationStatement :: Assignment localVariableDeclarationStatement = symbol LocalVariableDeclarationStatement *> children localVariableDeclaration From 09d7e2c5daf03f45cc1daf1e9f3b30a08a4d506c Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 1 May 2018 16:28:09 -0700 Subject: [PATCH 42/68] add superClass, superInterfaces and genericTypes and modify class declaration --- src/Language/Java/Assignment.hs | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index c515e7fed..b42184185 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -239,11 +239,14 @@ identifier = makeTerm <$> (symbol Identifier <|> symbol TypeIdentifier) <*> (Syn scopedIdentifier :: Assignment scopedIdentifier = makeTerm <$> symbol ScopedIdentifier <*> children (Expression.MemberAccess <$> term expression <*> term expression) +superInterfaces :: Assignment.Assignment [] Grammar [Term] +superInterfaces = symbol SuperInterfaces *> children (symbol InterfaceTypeList *> children(manyTerm type')) + -- Declarations class' :: Assignment -class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many modifier <*> term identifier <*> (typeParameters <|> pure []) <*> optional superClass <*> classBody) +class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many modifier <*> term identifier <*> (typeParameters <|> pure []) <*> optional superClass <*> (superInterfaces <|> pure []) <*> classBody) where - makeClass modifiers identifier typeParams superClass classBody = Declaration.Class (modifiers ++ typeParams) identifier (maybeToList superClass) classBody -- not doing an assignment, just straight up function + makeClass modifiers identifier typeParams superClass superInterfaces classBody = Declaration.Class (modifiers ++ typeParams) identifier (maybeToList superClass ++ superInterfaces) classBody -- not doing an assignment, just straight up function classBody = makeTerm <$> symbol ClassBody <*> children (manyTerm expression) superClass = symbol Superclass *> children type' -- matching term expression won't work since there is no node for that; it's AnonExtends @@ -488,6 +491,8 @@ typeParameters = symbol TypeParameters *> children (manyTerm typeParam) -- this where typeParam = makeTerm <$> symbol Grammar.TypeParameter <*> children (Java.Syntax.TypeParameter <$> manyTerm annotation <*> term identifier <*> (typeBound <|> pure [])) -- wrapping up all three of those fields so we need to makeTerm (producing a term here) typeBound = symbol TypeBound *> children (manyTerm type') + -- manyTerm typeParam made sense because each type Parameter was wrapped up into a Grammar.TypeParameter node, dissimilar + -- to superInterfaces annotation :: Assignment annotation = makeTerm <$> symbol NormalAnnotation <*> children (Java.Syntax.Annotation <$> term expression <*> (elementValuePairList <|> pure [])) From a53b43fb50c097d78933a05364b20cbb08e7b5f2 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 1 May 2018 16:29:57 -0700 Subject: [PATCH 43/68] modify methodBody so it is valid without a block --- src/Language/Java/Assignment.hs | 10 +++++++++- vendor/haskell-tree-sitter | 2 +- 2 files changed, 10 insertions(+), 2 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index b42184185..fd784eb9b 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -257,11 +257,19 @@ class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many m -- what's the difference between using tokens: AnonExtends GenericType? -- optional: when something can or can't exist and you want to produce a Maybe -- TODO: superclass -- need to match the superclass node when it exists (which will be a rule, similar to how the type params rule matches the typeparams node when it exists) +-- optional, when we have a single term +-- superInterfaces is also optional but since it produces a list, lists already have an empty value so we don't need to wrap it up in a maybe to get an empty value + +-- define this at the top level, we may change TS grammar so that if someone wants to write a Java snippet we could assign +-- it correctly; fieldDeclaration is standalone (compared to a type, which doesn't say anything by itself) +fieldDeclaration :: Assignment +fieldDeclaration = makeTerm <$> symbol FieldDeclaration <*> children ((,) <$> manyTerm modifier <*> type' <**> variableDeclaratorList) + method :: Assignment method = makeTerm <$> symbol MethodDeclaration <*> children (makeMethod <$> many modifier <*> emptyTerm <*> methodHeader <*> methodBody) where - methodBody = symbol MethodBody *> children (term expression) + methodBody = symbol MethodBody *> children (term expression <|> emptyTerm) methodDeclarator = symbol MethodDeclarator *> children ( (,) <$> identifier <*> formalParameters) methodHeader = symbol MethodHeader *> children ((,,,,) <$> (typeParameters <|> pure []) <*> manyTerm annotation <*> type' <*> methodDeclarator <*> (throws <|> pure [])) makeMethod modifiers receiver (typeParams, annotations, returnType, (name, params), throws) body = Declaration.Method (returnType : modifiers ++ typeParams ++ annotations ++ throws) receiver name params body diff --git a/vendor/haskell-tree-sitter b/vendor/haskell-tree-sitter index 4e947ff88..cc23c63ff 160000 --- a/vendor/haskell-tree-sitter +++ b/vendor/haskell-tree-sitter @@ -1 +1 @@ -Subproject commit 4e947ff88ab3b8bab9835027d88b625a10e41b60 +Subproject commit cc23c63ffd9e7017d3fbf9677bf37600dbcd0ad0 From afdd350e5fea60ca059d53d6c8bf5d083333e71c Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Tue, 1 May 2018 16:30:37 -0700 Subject: [PATCH 44/68] modify interfaceBody to match on NormalInterfaceDeclaration node --- src/Language/Java/Assignment.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index fd784eb9b..ccedc59a3 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -299,10 +299,13 @@ import' = makeTerm <$> symbol ImportDeclaration <*> children (Java.Syntax.Import interface :: Assignment interface = makeTerm <$> symbol InterfaceDeclaration <*> children (normal <|> annotationType) where - interfaceBody = makeTerm <$> symbol InterfaceBody <*> children (many expression) - normal = symbol NormalInterfaceDeclaration *> children (Declaration.InterfaceDeclaration [] <$> identifier <*> interfaceBody) + interfaceBody = makeTerm <$> symbol InterfaceBody <*> children (manyTerm interfaceMemberDeclaration) + normal = symbol NormalInterfaceDeclaration *> children (makeInterface <$> manyTerm modifier <*> identifier <*> (typeParameters <|> pure []) <*> interfaceBody) + makeInterface modifiers identifier typeParams interfaceBody = Declaration.InterfaceDeclaration (modifiers ++ typeParams) identifier interfaceBody annotationType = symbol AnnotationTypeDeclaration *> children (Declaration.InterfaceDeclaration [] <$> identifier <*> annotationTypeBody) annotationTypeBody = makeTerm <$> symbol AnnotationTypeBody <*> children (many expression) + interfaceMemberDeclaration = symbol InterfaceMemberDeclaration *> children (term expression) + -- we won't make a term because we have a choice of a bunch of things package :: Assignment package = makeTerm <$> symbol PackageDeclaration <*> children (Java.Syntax.Package <$> someTerm expression) From 6a889388b091f6a957631d2a5fea232b2acb75ae Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Wed, 9 May 2018 13:36:55 -0700 Subject: [PATCH 45/68] remove constantDeclaration comment messiness --- src/Language/Java/Assignment.hs | 57 +++++++++++++++++++++++++++++++-- 1 file changed, 54 insertions(+), 3 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index ccedc59a3..2127043e5 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -29,6 +29,24 @@ import qualified Data.Term as Term import Prelude hiding (break) import Prologue hiding (for, try, This) +-- [1,2,3::Int] +-- We have types and values -- two worlds that don't really intersect, they're not compatible +-- We have a way to blur these distinctions +-- We can take these values and put them into their type signatures +-- data Vec a (len :: Nat) -- this is a type level natural number, which allows us to track the length of vectors +-- "promote to the kind level" - taking something we usually think about as a value and putting into the world of types +-- '[] - type-level list, if we didn't do this it would be a value list of types, which wouldn't make sense +-- This is not like casting; it's not doing any computation at runtime, just at compile time. +-- ':k' - what the type of this type is +-- `:k Int` is * (fully saturated) +-- maybe takes an arg on type level whereas int takes an argument on val level +-- :k can only be applied to Monad (typeclasses) +-- :k type-level lists +-- '[]' - you can give it a list of statements as a valid syntax terms +-- `[]` - is treated as an imperative sequence of statements +-- In JSON there's no notion of `[]` because there's no notion of imperative computation +-- Taking this out `[]` makes a lot of stuff fail like block + type Syntax = '[ Comment.Comment , Declaration.Class @@ -190,9 +208,6 @@ arrayInitializer = makeTerm <$> symbol ArrayInitializer <*> (Literal.Array <$> m comment :: Assignment comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) --- constantDeclaration :: Assignment --- constantDeclaration = makeTerm <$> symbol ConstantDeclaration <*> - localVariableDeclaration :: Assignment localVariableDeclaration = makeTerm <$> symbol LocalVariableDeclaration <*> children ((,) <$> manyTerm modifier <*> type' <**> variableDeclaratorList) @@ -216,6 +231,26 @@ boolean = makeTerm <$> symbol BooleanLiteral <*> children (token Grammar.True $> Literal.true <|> token Grammar.False $> Literal.false) + + +-- ($>) +-- (<$) +-- value <$ action +-- 'q' <$ getLine +-- `q` is pure value, getLine is an impure action +-- we want to run the source action because it updates our location info, but source returns a bytestring, which isn't interesting because we +-- already know we're in a true case, so we return Literal.True +-- if we're looking for a float, we need a bytestring +-- but in this context, since we're looking at something that's true, we know source is going to return the literal string true +-- <$ is not half fmap, it just means evaluate the RHS for its side-effects and return the LHS without +-- source is being thrown away, but we need to evaluate it for its side-effect because it'll advance where we are in the location +-- but to have <$ you need a functor context +-- for string or whatever you need source, but null or true or false you can throw it away +-- <$ - not function, just value +-- can implement monad and apply +-- `ap` function +-- `ap` and <*> are the same, but `ap` is expressed in terms of the same capabilities of the monad + null' :: Assignment null' = makeTerm <$> symbol NullLiteral <*> (Literal.Null <$ source) @@ -241,6 +276,17 @@ scopedIdentifier = makeTerm <$> symbol ScopedIdentifier <*> children (Expression superInterfaces :: Assignment.Assignment [] Grammar [Term] superInterfaces = symbol SuperInterfaces *> children (symbol InterfaceTypeList *> children(manyTerm type')) +-- a *> b +-- both of these are impure +-- getLine *> getLine +-- in half apply, they're both monadic impure actions +-- :t (<$) +-- :t (*>) + +-- what does it mean to say monadic action? more precise term: sequence-able +-- a sequence of applicative actions can be executed left to right +-- applicative computations can't do branch and control flow; applicative computations can only compute in a direct line, monadic can compute arbitrary branches + -- Declarations class' :: Assignment @@ -497,6 +543,8 @@ constructorDeclaration = makeTerm <$> symbol ConstructorDeclaration <*> children constructorBody = makeTerm <$> symbol ConstructorBody <*> children (manyTerm expression) -- wrapping list of terms up in single node constructor modifiers (typeParameters, identifier, formalParameters) = Java.Syntax.Constructor modifiers typeParameters identifier formalParameters -- let partial application do its thing +-- when we wrap a list of values in a term, the list nature disappears +-- but in this case, our assignment ensures we return something that's explicitly a list typeParameters :: Assignment.Assignment [] Grammar [Term] typeParameters = symbol TypeParameters *> children (manyTerm typeParam) -- this produces a list, which is what we need to return given by the type definition where @@ -527,3 +575,6 @@ formalParameters = manyTerm parameter -- we're just wrapping stuff up in data, we aren't building a pattern (assignment) so we aren't in an applicative context -- when in an applicative context, we're also in a functor context (ie., defining how fmap will work over it) -- sometimes it is nice to be able to say you're in an applicative context without refering to any particular applicative instance + +-- constantDeclaration :: Assignment +-- constantDeclaration = makeTerm <$> symbol ConstantDeclaration <*> From ce28656e6e9381c9c69a632c90ad6eaac37dce39 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Thu, 17 May 2018 10:33:14 -0700 Subject: [PATCH 46/68] remove comments --- src/Language/Java/Assignment.hs | 44 +++------------------------------ 1 file changed, 3 insertions(+), 41 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 2127043e5..3ed5bab29 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DataKinds, RankNTypes, TypeOperators #-} +{-# LANGUAGE DataKinds, RankNTypes, TypeOperators, KindSignatures #-} module Language.Java.Assignment ( assignment , Syntax @@ -28,24 +28,9 @@ import qualified Data.Syntax.Type as Type import qualified Data.Term as Term import Prelude hiding (break) import Prologue hiding (for, try, This) +import GHC.TypeLits -- this is just to make sense of the Data kind (len :: Nat) example --- [1,2,3::Int] --- We have types and values -- two worlds that don't really intersect, they're not compatible --- We have a way to blur these distinctions --- We can take these values and put them into their type signatures --- data Vec a (len :: Nat) -- this is a type level natural number, which allows us to track the length of vectors --- "promote to the kind level" - taking something we usually think about as a value and putting into the world of types --- '[] - type-level list, if we didn't do this it would be a value list of types, which wouldn't make sense --- This is not like casting; it's not doing any computation at runtime, just at compile time. --- ':k' - what the type of this type is --- `:k Int` is * (fully saturated) --- maybe takes an arg on type level whereas int takes an argument on val level --- :k can only be applied to Monad (typeclasses) --- :k type-level lists --- '[]' - you can give it a list of statements as a valid syntax terms --- `[]` - is treated as an imperative sequence of statements --- In JSON there's no notion of `[]` because there's no notion of imperative computation --- Taking this out `[]` makes a lot of stuff fail like block +-- data Vec a (len :: Nat) type Syntax = '[ Comment.Comment @@ -231,26 +216,6 @@ boolean = makeTerm <$> symbol BooleanLiteral <*> children (token Grammar.True $> Literal.true <|> token Grammar.False $> Literal.false) - - --- ($>) --- (<$) --- value <$ action --- 'q' <$ getLine --- `q` is pure value, getLine is an impure action --- we want to run the source action because it updates our location info, but source returns a bytestring, which isn't interesting because we --- already know we're in a true case, so we return Literal.True --- if we're looking for a float, we need a bytestring --- but in this context, since we're looking at something that's true, we know source is going to return the literal string true --- <$ is not half fmap, it just means evaluate the RHS for its side-effects and return the LHS without --- source is being thrown away, but we need to evaluate it for its side-effect because it'll advance where we are in the location --- but to have <$ you need a functor context --- for string or whatever you need source, but null or true or false you can throw it away --- <$ - not function, just value --- can implement monad and apply --- `ap` function --- `ap` and <*> are the same, but `ap` is expressed in terms of the same capabilities of the monad - null' :: Assignment null' = makeTerm <$> symbol NullLiteral <*> (Literal.Null <$ source) @@ -287,7 +252,6 @@ superInterfaces = symbol SuperInterfaces *> children (symbol InterfaceTypeList * -- a sequence of applicative actions can be executed left to right -- applicative computations can't do branch and control flow; applicative computations can only compute in a direct line, monadic can compute arbitrary branches - -- Declarations class' :: Assignment class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many modifier <*> term identifier <*> (typeParameters <|> pure []) <*> optional superClass <*> (superInterfaces <|> pure []) <*> classBody) @@ -543,8 +507,6 @@ constructorDeclaration = makeTerm <$> symbol ConstructorDeclaration <*> children constructorBody = makeTerm <$> symbol ConstructorBody <*> children (manyTerm expression) -- wrapping list of terms up in single node constructor modifiers (typeParameters, identifier, formalParameters) = Java.Syntax.Constructor modifiers typeParameters identifier formalParameters -- let partial application do its thing --- when we wrap a list of values in a term, the list nature disappears --- but in this case, our assignment ensures we return something that's explicitly a list typeParameters :: Assignment.Assignment [] Grammar [Term] typeParameters = symbol TypeParameters *> children (manyTerm typeParam) -- this produces a list, which is what we need to return given by the type definition where From 9bd78b41232e807c6787003238a19c1539011599 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Thu, 17 May 2018 11:08:37 -0700 Subject: [PATCH 47/68] add typeclasses to deal with recent merge --- src/Data/Syntax/Expression.hs | 4 +-- src/Data/Syntax/Statement.hs | 4 +-- src/Data/Syntax/Type.hs | 8 ++--- src/Language/Java/Assignment.hs | 63 ++++++++++++++++----------------- src/Language/Java/Syntax.hs | 29 +++++++-------- src/Parsing/Parser.hs | 2 +- 6 files changed, 55 insertions(+), 55 deletions(-) diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index d671035b2..6821dc3b6 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -340,7 +340,7 @@ instance ToJSONFields1 Cast instance Evaluatable Cast data Super a = Super - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Super where liftEq = genericLiftEq instance Ord1 Super where liftCompare = genericLiftCompare @@ -348,7 +348,7 @@ instance Show1 Super where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Super data This a = This - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 This where liftEq = genericLiftEq instance Ord1 This where liftCompare = genericLiftCompare diff --git a/src/Data/Syntax/Statement.hs b/src/Data/Syntax/Statement.hs index c627369a3..16c8bd34b 100644 --- a/src/Data/Syntax/Statement.hs +++ b/src/Data/Syntax/Statement.hs @@ -159,7 +159,7 @@ instance Evaluatable PostDecrement -- | Pre increment operator (e.g. ++1 in C or Java). newtype PreIncrement a = PreIncrement a - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 PreIncrement where liftEq = genericLiftEq instance Ord1 PreIncrement where liftCompare = genericLiftCompare @@ -171,7 +171,7 @@ instance Evaluatable PreIncrement -- | Pre decrement operator (e.g. --1 in C or Java). newtype PreDecrement a = PreDecrement a - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 PreDecrement where liftEq = genericLiftEq instance Ord1 PreDecrement where liftCompare = genericLiftCompare diff --git a/src/Data/Syntax/Type.hs b/src/Data/Syntax/Type.hs index 742f5c315..a405f5e78 100644 --- a/src/Data/Syntax/Type.hs +++ b/src/Data/Syntax/Type.hs @@ -153,7 +153,7 @@ instance Evaluatable TypeParameters -- data instead of newtype because no payload data Void a = Void - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Void where liftEq = genericLiftEq instance Ord1 Void where liftCompare = genericLiftCompare @@ -164,7 +164,7 @@ instance Evaluatable Void -- data instead of newtype because no payload data Int a = Int - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Int where liftEq = genericLiftEq instance Ord1 Int where liftCompare = genericLiftCompare @@ -174,7 +174,7 @@ instance Show1 Int where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Int data Float a = Float | Double - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Float where liftEq = genericLiftEq instance Ord1 Float where liftCompare = genericLiftCompare @@ -184,7 +184,7 @@ instance Show1 Float where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Float data Bool a = Bool - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Bool where liftEq = genericLiftEq instance Ord1 Bool where liftCompare = genericLiftCompare diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 3ed5bab29..a6c630678 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -11,9 +11,8 @@ import Data.Abstract.FreeVariables import Data.Functor (($>)) import Data.List.NonEmpty (some1) import Data.Record -import Data.Semigroup import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError, postContextualize) -import Data.Union +import Data.Sum import GHC.Stack import Language.Java.Grammar as Grammar import Language.Java.Syntax as Java.Syntax @@ -102,7 +101,7 @@ type Syntax = , [] ] -type Term = Term.Term (Union Syntax) (Record Location) +type Term = Term.Term (Sum Syntax) (Record Location) type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term -- | Assignment from AST in Java's grammar onto a program in Java's syntax. @@ -403,26 +402,26 @@ enhancedFor = makeTerm <$> symbol EnhancedForStatement <*> children (Statement.F -- TODO: instanceOf binary :: Assignment binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expression expression - [ (inj .) . Expression.LessThan <$ symbol AnonLAngle - , (inj .) . Expression.GreaterThan <$ symbol AnonRAngle - , (inj .) . Expression.Equal <$ symbol AnonEqualEqual - , (inj .) . Expression.GreaterThanEqual <$ symbol AnonRAngleEqual - , (inj .) . Expression.LessThanEqual <$ symbol AnonLAngleEqual - , (inj .) . invert Expression.Equal <$ symbol AnonBangEqual - , (inj .) . Expression.And <$ symbol AnonAmpersandAmpersand - , (inj .) . Expression.Or <$ symbol AnonPipePipe - , (inj .) . Expression.BAnd <$ symbol AnonAmpersand - , (inj .) . Expression.BOr <$ symbol AnonPipe - , (inj .) . Expression.BXOr <$ symbol AnonCaret - , (inj .) . Expression.Modulo <$ symbol AnonPercent - , (inj .) . Expression.LShift <$ symbol AnonLAngleLAngle - , (inj .) . Expression.RShift <$ symbol AnonRAngleRAngle - , (inj .) . Expression.UnsignedRShift <$ symbol AnonRAngleRAngleRAngle - , (inj .) . Expression.Plus <$ symbol AnonPlus - , (inj .) . Expression.Minus <$ symbol AnonMinus - , (inj .) . Expression.Times <$ symbol AnonStar - , (inj .) . Expression.DividedBy <$ symbol AnonSlash - , (inj .) . Expression.InstanceOf <$ symbol AnonInstanceof + [ (injectSum .) . Expression.LessThan <$ symbol AnonLAngle + , (injectSum .) . Expression.GreaterThan <$ symbol AnonRAngle + , (injectSum .) . Expression.Equal <$ symbol AnonEqualEqual + , (injectSum .) . Expression.GreaterThanEqual <$ symbol AnonRAngleEqual + , (injectSum .) . Expression.LessThanEqual <$ symbol AnonLAngleEqual + , (injectSum .) . invert Expression.Equal <$ symbol AnonBangEqual + , (injectSum .) . Expression.And <$ symbol AnonAmpersandAmpersand + , (injectSum .) . Expression.Or <$ symbol AnonPipePipe + , (injectSum .) . Expression.BAnd <$ symbol AnonAmpersand + , (injectSum .) . Expression.BOr <$ symbol AnonPipe + , (injectSum .) . Expression.BXOr <$ symbol AnonCaret + , (injectSum .) . Expression.Modulo <$ symbol AnonPercent + , (injectSum .) . Expression.LShift <$ symbol AnonLAngleLAngle + , (injectSum .) . Expression.RShift <$ symbol AnonRAngleRAngle + , (injectSum .) . Expression.UnsignedRShift <$ symbol AnonRAngleRAngleRAngle + , (injectSum .) . Expression.Plus <$ symbol AnonPlus + , (injectSum .) . Expression.Minus <$ symbol AnonMinus + , (injectSum .) . Expression.Times <$ symbol AnonStar + , (injectSum .) . Expression.DividedBy <$ symbol AnonSlash + , (injectSum .) . Expression.InstanceOf <$ symbol AnonInstanceof ]) where invert cons a b = Expression.Not (makeTerm1 (cons a b)) @@ -430,13 +429,13 @@ binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expressio infixTerm :: HasCallStack => Assignment -> Assignment - -> [Assignment.Assignment [] Grammar (Term -> Term -> Union Syntax Term)] - -> Assignment.Assignment [] Grammar (Union Syntax Term) + -> [Assignment.Assignment [] Grammar (Term -> Term -> Sum Syntax Term)] + -> Assignment.Assignment [] Grammar (Sum Syntax Term) infixTerm = infixContext comment assignment' :: Assignment assignment' = makeTerm' <$> symbol AssignmentExpression <*> children (infixTerm lhs expression - [ (inj .) . Statement.Assignment [] <$ symbol AnonEqual + [ (injectSum .) . Statement.Assignment [] <$ symbol AnonEqual , assign Expression.Plus <$ symbol AnonPlusEqual , assign Expression.Minus <$ symbol AnonMinusEqual , assign Expression.Times <$ symbol AnonStarEqual @@ -450,8 +449,8 @@ assignment' = makeTerm' <$> symbol AssignmentExpression <*> children (infixTerm , assign Expression.BXOr <$ symbol AnonCaretEqual ]) where - assign :: (f :< Syntax) => (Term -> Term -> f Term) -> Term -> Term -> Union Syntax Term - assign c l r = inj (Statement.Assignment [] l (makeTerm1 (c l r))) + assign :: (f :< Syntax) => (Term -> Term -> f Term) -> Term -> Term -> Sum Syntax Term + assign c l r = injectSum (Statement.Assignment [] l (makeTerm1 (c l r))) lhs = symbol Lhs *> children (term expression) data UnaryType @@ -474,10 +473,10 @@ unary = make <$> symbol UnaryExpression <*> children ((,) <$> operator <*> term update :: Assignment update = makeTerm' <$> symbol UpdateExpression <*> children ( - inj . Statement.PreIncrement <$ token AnonPlusPlus <*> term expression - <|> inj . Statement.PreDecrement <$ token AnonMinusMinus <*> term expression - <|> inj . Statement.PostIncrement <$> term expression <* token AnonPlusPlus - <|> inj . Statement.PostDecrement <$> term expression <* token AnonMinusMinus) + injectSum . Statement.PreIncrement <$ token AnonPlusPlus <*> term expression + <|> injectSum . Statement.PreDecrement <$ token AnonMinusMinus <*> term expression + <|> injectSum . Statement.PostIncrement <$> term expression <* token AnonPlusPlus + <|> injectSum . Statement.PostDecrement <$> term expression <* token AnonMinusMinus) ternary :: Assignment ternary = makeTerm <$> symbol TernaryExpression <*> children (Statement.If <$> term expression <*> term expression <*> term expression) diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index 5e6dddd38..e3ac8a41f 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -4,9 +4,10 @@ module Language.Java.Syntax where import Data.Abstract.Evaluatable hiding (Label) import Diffing.Algorithm import Prologue hiding (Constructor) +import Data.JSON.Fields newtype Import a = Import [a] - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Import where liftEq = genericLiftEq instance Ord1 Import where liftCompare = genericLiftCompare @@ -16,7 +17,7 @@ instance Show1 Import where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Import data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Module where liftEq = genericLiftEq instance Ord1 Module where liftCompare = genericLiftCompare @@ -25,7 +26,7 @@ instance Show1 Module where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Module newtype Package a = Package [a] - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Package where liftEq = genericLiftEq instance Ord1 Package where liftCompare = genericLiftCompare @@ -35,7 +36,7 @@ instance Show1 Package where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Package data EnumDeclaration a = EnumDeclaration { _enumDeclarationIdentifier :: !a, _enumDeclarationBody :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 EnumDeclaration where liftEq = genericLiftEq instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare @@ -44,7 +45,7 @@ instance Evaluatable EnumDeclaration data Variable a = Variable { variableModifiers :: ![a], variableType :: !a, variableName :: !a} - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Variable where liftEq = genericLiftEq instance Ord1 Variable where liftCompare = genericLiftCompare @@ -54,7 +55,7 @@ instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Variable data Synchronized a = Synchronized { synchronizedSubject :: !a, synchronizedBody :: !a} - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Synchronized where liftEq = genericLiftEq instance Ord1 Synchronized where liftCompare = genericLiftCompare @@ -64,7 +65,7 @@ instance Show1 Synchronized where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Synchronized data New a = New { newType :: !a, newArgs :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 New where liftEq = genericLiftEq instance Ord1 New where liftCompare = genericLiftCompare @@ -74,7 +75,7 @@ instance Show1 New where liftShowsPrec = genericLiftShowsPrec instance Evaluatable New data Asterisk a = Asterisk - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Asterisk where liftEq = genericLiftEq instance Ord1 Asterisk where liftCompare = genericLiftCompare @@ -85,7 +86,7 @@ instance Evaluatable Asterisk data Constructor a = Constructor { constructorModifiers :: ![a], constructorTypeParams :: ![a], constructorIdentifier :: !a, constructorParams :: ![a], constructorThrows :: ![a], constructorBody :: a} - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Constructor where liftEq = genericLiftEq instance Ord1 Constructor where liftCompare = genericLiftCompare @@ -95,7 +96,7 @@ instance Show1 Constructor where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Constructor data TypeParameter a = TypeParameter { typeParamAnnotation :: ![a], typeParamIdentifier :: !a, typeParamTypeBound :: ![a]} - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 TypeParameter where liftEq = genericLiftEq instance Ord1 TypeParameter where liftCompare = genericLiftCompare @@ -105,7 +106,7 @@ instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec instance Evaluatable TypeParameter data Annotation a = Annotation { annotationName :: !a, annotationField :: [a]} - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Annotation where liftEq = genericLiftEq instance Ord1 Annotation where liftCompare = genericLiftCompare @@ -115,7 +116,7 @@ instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Annotation data AnnotationField a = AnnotationField { annotationFieldName :: a, annotationFieldValue :: a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 AnnotationField where liftEq = genericLiftEq instance Ord1 AnnotationField where liftCompare = genericLiftCompare @@ -125,7 +126,7 @@ instance Show1 AnnotationField where liftShowsPrec = genericLiftShowsPrec instance Evaluatable AnnotationField data GenericType a = GenericType { genericTypeIdentifier :: a, genericTypeArguments :: [a] } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 GenericType where liftEq = genericLiftEq instance Ord1 GenericType where liftCompare = genericLiftCompare @@ -135,7 +136,7 @@ instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable GenericType data TypeWithModifiers a = TypeWithModifiers [a] a - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 TypeWithModifiers where liftEq = genericLiftEq instance Ord1 TypeWithModifiers where liftCompare = genericLiftCompare diff --git a/src/Parsing/Parser.hs b/src/Parsing/Parser.hs index c4e89f0c0..f96b59c78 100644 --- a/src/Parsing/Parser.hs +++ b/src/Parsing/Parser.hs @@ -111,7 +111,7 @@ type family ApplyAll (typeclasses :: [(* -> *) -> Constraint]) (syntax :: * -> * -- -- > runTask (parse (someParser @'[Show1] language) blob) >>= putStrLn . withSomeTerm show someParser :: ( ApplyAll typeclasses (Sum Go.Syntax) - , ApplyAll typeclasses (Union Java.Syntax) + , ApplyAll typeclasses (Sum Java.Syntax) , ApplyAll typeclasses (Sum JSON.Syntax) , ApplyAll typeclasses (Sum Markdown.Syntax) , ApplyAll typeclasses (Sum Python.Syntax) From 09b1851aee4d22cc77c934faee13088e27d5332b Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Thu, 17 May 2018 11:29:08 -0700 Subject: [PATCH 48/68] create castExpression assignment --- example.java | 7 ++++++- src/Language/Java/Assignment.hs | 5 +++++ 2 files changed, 11 insertions(+), 1 deletion(-) diff --git a/example.java b/example.java index fbe40be7a..3be01cb2b 100644 --- a/example.java +++ b/example.java @@ -1,2 +1,7 @@ -class Hello extends someClass <> { +if (t instanceof VirtualMachineError) { + throw (VirtualMachineError) t; +} else if (t instanceof ThreadDeath) { + throw (ThreadDeath) t; +} else if (t instanceof LinkageError) { + throw (LinkageError) t; } diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index a6c630678..bda8dc97e 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -141,6 +141,7 @@ expressionChoices = , binary , boolean , break + , castExpression , char , class' , classInstance @@ -539,3 +540,7 @@ formalParameters = manyTerm parameter -- constantDeclaration :: Assignment -- constantDeclaration = makeTerm <$> symbol ConstantDeclaration <*> + +castExpression :: Assignment +castExpression = makeTerm <$> symbol CastExpression <*> children (flip Type.Annotation <$> type' <*> term expression) +-- term expression, because we can deal with comments From c57b8051c46445394e14bd7770e28f65d0bd5f06 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Thu, 17 May 2018 11:54:29 -0700 Subject: [PATCH 49/68] add explicitConstructorInvocation --- src/Language/Java/Assignment.hs | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index bda8dc97e..55335ec2c 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -147,6 +147,7 @@ expressionChoices = , classInstance , continue , constructorDeclaration + , explicitConstructorInvocation -- , constantDeclaration , doWhile , fieldDeclaration @@ -299,6 +300,12 @@ methodInvocation = makeTerm <$> symbol MethodInvocation <*> children (Expression callFunction a (Just b) = makeTerm1 (Expression.MemberAccess a b) callFunction a Nothing = a +explicitConstructorInvocation :: Assignment +explicitConstructorInvocation = makeTerm <$> symbol ExplicitConstructorInvocation <*> children (Expression.Call [] <$> (callFunction <$> term expression <*> optional (token AnonDot *> term expression)) <*> argumentList <*> emptyTerm) + where + callFunction a (Just b) = makeTerm1 (Expression.MemberAccess a b) + callFunction a Nothing = a + module' :: Assignment module' = makeTerm <$> symbol ModuleDeclaration <*> children (Java.Syntax.Module <$> expression <*> many expression) From 2684b34bcbf0ad277c547e95d69b2ff0180c118e Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Thu, 31 May 2018 14:49:22 -0700 Subject: [PATCH 50/68] allow method invocation to have empty argument lists --- example.java | 7 +------ src/Language/Java/Assignment.hs | 12 ++++++++++-- 2 files changed, 11 insertions(+), 8 deletions(-) diff --git a/example.java b/example.java index 3be01cb2b..eb60a2a92 100644 --- a/example.java +++ b/example.java @@ -1,7 +1,2 @@ -if (t instanceof VirtualMachineError) { - throw (VirtualMachineError) t; -} else if (t instanceof ThreadDeath) { - throw (ThreadDeath) t; -} else if (t instanceof LinkageError) { - throw (LinkageError) t; +public abstract class ConnectableFlowable extends Flowable { } diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 55335ec2c..1f2e7ba06 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -295,7 +295,7 @@ generic = makeTerm <$> symbol Grammar.GenericType <*> children(Java.Syntax.Gener -- Q to help decide: do we lose anything by omitting the term? methodInvocation :: Assignment -methodInvocation = makeTerm <$> symbol MethodInvocation <*> children (Expression.Call [] <$> (callFunction <$> term expression <*> optional (token AnonDot *> term expression)) <*> argumentList <*> emptyTerm) +methodInvocation = makeTerm <$> symbol MethodInvocation <*> children (Expression.Call [] <$> (callFunction <$> expression <*> optional (token AnonDot *> expression)) <*> (argumentList <|> pure []) <*> emptyTerm) where callFunction a (Just b) = makeTerm1 (Expression.MemberAccess a b) callFunction a Nothing = a @@ -325,7 +325,15 @@ interface = makeTerm <$> symbol InterfaceDeclaration <*> children (normal <|> an -- we won't make a term because we have a choice of a bunch of things package :: Assignment -package = makeTerm <$> symbol PackageDeclaration <*> children (Java.Syntax.Package <$> someTerm expression) +-- package = makeTerm <$> symbol PackageDeclaration <*> children (Java.Syntax.Package <$> someTerm expression) +package = do + loc <- symbol PackageDeclaration -- location which is calling the symbol API + c <- children $ do + expressions <- someTerm expression + pure (Java.Syntax.Package expressions) + pure (makeTerm loc c) -- pure is re-wrapping it back into the outer context, which in this case is Assignment (ie., the return type of the function) + + enum :: Assignment enum = makeTerm <$> symbol Grammar.EnumDeclaration <*> children (Java.Syntax.EnumDeclaration <$> term identifier <*> manyTerm enumConstant) From 57c5bef02a63aa14c8d9cc101c3fcbf1cf450427 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 09:47:59 -0700 Subject: [PATCH 51/68] bumped haskell-tree-sitter --- vendor/haskell-tree-sitter | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vendor/haskell-tree-sitter b/vendor/haskell-tree-sitter index fd77e6ed7..128a1c100 160000 --- a/vendor/haskell-tree-sitter +++ b/vendor/haskell-tree-sitter @@ -1 +1 @@ -Subproject commit fd77e6ed70ea92d68f221e01f358904c94a31bfa +Subproject commit 128a1c1007a1df9f7111a328919da728803c4e3b From 4641bf38a817ecc0e2c7573917eafd0e4c3c5b63 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 10:14:07 -0700 Subject: [PATCH 52/68] set back to master --- vendor/effects | 2 +- vendor/fastsum | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/vendor/effects b/vendor/effects index 4b4f2956d..adec65af3 160000 --- a/vendor/effects +++ b/vendor/effects @@ -1 +1 @@ -Subproject commit 4b4f2956d8a4d5542990431a1d0a5735f48f917e +Subproject commit adec65af304cc31681ce02111985aa73e1f11cf5 diff --git a/vendor/fastsum b/vendor/fastsum index 4a8f13592..dbeff0af5 160000 --- a/vendor/fastsum +++ b/vendor/fastsum @@ -1 +1 @@ -Subproject commit 4a8f1359233bbb2bea7a0eee478c28d0184ebe6d +Subproject commit dbeff0af57fcea85bca07ff5a8149301dd3b084c From 18a5a8482bcffd6af6db1f3a14875c6976317efe Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 10:14:54 -0700 Subject: [PATCH 53/68] set back to master --- vendor/effects | 2 +- vendor/fastsum | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/vendor/effects b/vendor/effects index adec65af3..4b4f2956d 160000 --- a/vendor/effects +++ b/vendor/effects @@ -1 +1 @@ -Subproject commit adec65af304cc31681ce02111985aa73e1f11cf5 +Subproject commit 4b4f2956d8a4d5542990431a1d0a5735f48f917e diff --git a/vendor/fastsum b/vendor/fastsum index dbeff0af5..4a8f13592 160000 --- a/vendor/fastsum +++ b/vendor/fastsum @@ -1 +1 @@ -Subproject commit dbeff0af57fcea85bca07ff5a8149301dd3b084c +Subproject commit 4a8f1359233bbb2bea7a0eee478c28d0184ebe6d From 5d484b9ed6f042c59be98b828f7215b2dfdf83d0 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 10:20:32 -0700 Subject: [PATCH 54/68] back to master for vendor/effect (2) --- vendor/effects | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vendor/effects b/vendor/effects index 4b4f2956d..adec65af3 160000 --- a/vendor/effects +++ b/vendor/effects @@ -1 +1 @@ -Subproject commit 4b4f2956d8a4d5542990431a1d0a5735f48f917e +Subproject commit adec65af304cc31681ce02111985aa73e1f11cf5 From 83a6616e9afb15e6af00938ee6f619393e45f74e Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 10:22:08 -0700 Subject: [PATCH 55/68] back to master for vendor/fastsum --- vendor/fastsum | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vendor/fastsum b/vendor/fastsum index 4a8f13592..dbeff0af5 160000 --- a/vendor/fastsum +++ b/vendor/fastsum @@ -1 +1 @@ -Subproject commit 4a8f1359233bbb2bea7a0eee478c28d0184ebe6d +Subproject commit dbeff0af57fcea85bca07ff5a8149301dd3b084c From fe066369fcf5ed4f1c0c8c629ec7fdea6a46eb1c Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 10:24:21 -0700 Subject: [PATCH 56/68] Rename to test.java --- example.java | 2 -- 1 file changed, 2 deletions(-) delete mode 100644 example.java diff --git a/example.java b/example.java deleted file mode 100644 index eb60a2a92..000000000 --- a/example.java +++ /dev/null @@ -1,2 +0,0 @@ -public abstract class ConnectableFlowable extends Flowable { -} From 9df44787519809a52d2c3875cb766f1b61fb74aa Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 10:25:33 -0700 Subject: [PATCH 57/68] Use version of this on master --- src/Data/AST.hs | 9 --------- 1 file changed, 9 deletions(-) diff --git a/src/Data/AST.hs b/src/Data/AST.hs index a76647eeb..16a90a7f0 100644 --- a/src/Data/AST.hs +++ b/src/Data/AST.hs @@ -5,7 +5,6 @@ import Data.Range import Data.Record import Data.Span import Data.Term -import Prologue import Data.Aeson import Data.ByteString.Char8 (pack) @@ -33,11 +32,3 @@ type Location = '[Range, Span] nodeLocation :: Node grammar -> Record Location nodeLocation Node{..} = nodeByteRange :. nodeSpan :. Nil - -newtype Tree (syntax) = Tree (syntax (Tree syntax)) - -instance (Show1 syntax) => Show (Tree syntax) where - showsPrec precedence (Tree syntax) = showsPrec1 precedence syntax - -termToTree :: Functor syntax => Term syntax annotation -> Tree syntax -termToTree = cata (\ (In _ syntax) -> Tree syntax) From 7c1e4ad388341c98665e6d77b6da4a272adf7c02 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 10:28:53 -0700 Subject: [PATCH 58/68] GAlign is not a thing anymore --- src/Data/Syntax/Expression.hs | 4 ++-- src/Data/Syntax/Statement.hs | 4 ++-- src/Data/Syntax/Type.hs | 8 ++++---- src/Language/Java/Syntax.hs | 28 ++++++++++++++-------------- 4 files changed, 22 insertions(+), 22 deletions(-) diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index 3ef7c6e4d..6e1573be8 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -344,7 +344,7 @@ instance ToJSONFields1 Cast instance Evaluatable Cast data Super a = Super - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Super where liftEq = genericLiftEq instance Ord1 Super where liftCompare = genericLiftCompare @@ -352,7 +352,7 @@ instance Show1 Super where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Super data This a = This - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 This where liftEq = genericLiftEq instance Ord1 This where liftCompare = genericLiftCompare diff --git a/src/Data/Syntax/Statement.hs b/src/Data/Syntax/Statement.hs index 2290bee98..4cc88c5ef 100644 --- a/src/Data/Syntax/Statement.hs +++ b/src/Data/Syntax/Statement.hs @@ -157,7 +157,7 @@ instance Evaluatable PostDecrement -- | Pre increment operator (e.g. ++1 in C or Java). newtype PreIncrement a = PreIncrement a - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 PreIncrement where liftEq = genericLiftEq instance Ord1 PreIncrement where liftCompare = genericLiftCompare @@ -169,7 +169,7 @@ instance Evaluatable PreIncrement -- | Pre decrement operator (e.g. --1 in C or Java). newtype PreDecrement a = PreDecrement a - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 PreDecrement where liftEq = genericLiftEq instance Ord1 PreDecrement where liftCompare = genericLiftCompare diff --git a/src/Data/Syntax/Type.hs b/src/Data/Syntax/Type.hs index a6a2bd587..6fa0ea0c9 100644 --- a/src/Data/Syntax/Type.hs +++ b/src/Data/Syntax/Type.hs @@ -153,7 +153,7 @@ instance Evaluatable TypeParameters -- data instead of newtype because no payload data Void a = Void - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Void where liftEq = genericLiftEq instance Ord1 Void where liftCompare = genericLiftCompare @@ -164,7 +164,7 @@ instance Evaluatable Void -- data instead of newtype because no payload data Int a = Int - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Int where liftEq = genericLiftEq instance Ord1 Int where liftCompare = genericLiftCompare @@ -174,7 +174,7 @@ instance Show1 Int where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Int data Float a = Float | Double - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Float where liftEq = genericLiftEq instance Ord1 Float where liftCompare = genericLiftCompare @@ -184,7 +184,7 @@ instance Show1 Float where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Float data Bool a = Bool - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Bool where liftEq = genericLiftEq instance Ord1 Bool where liftCompare = genericLiftCompare diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index e3ac8a41f..9857152aa 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -7,7 +7,7 @@ import Prologue hiding (Constructor) import Data.JSON.Fields newtype Import a = Import [a] - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Import where liftEq = genericLiftEq instance Ord1 Import where liftCompare = genericLiftCompare @@ -17,7 +17,7 @@ instance Show1 Import where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Import data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] } - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Module where liftEq = genericLiftEq instance Ord1 Module where liftCompare = genericLiftCompare @@ -26,7 +26,7 @@ instance Show1 Module where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Module newtype Package a = Package [a] - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Package where liftEq = genericLiftEq instance Ord1 Package where liftCompare = genericLiftCompare @@ -36,7 +36,7 @@ instance Show1 Package where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Package data EnumDeclaration a = EnumDeclaration { _enumDeclarationIdentifier :: !a, _enumDeclarationBody :: ![a] } - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 EnumDeclaration where liftEq = genericLiftEq instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare @@ -45,7 +45,7 @@ instance Evaluatable EnumDeclaration data Variable a = Variable { variableModifiers :: ![a], variableType :: !a, variableName :: !a} - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Variable where liftEq = genericLiftEq instance Ord1 Variable where liftCompare = genericLiftCompare @@ -55,7 +55,7 @@ instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Variable data Synchronized a = Synchronized { synchronizedSubject :: !a, synchronizedBody :: !a} - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Synchronized where liftEq = genericLiftEq instance Ord1 Synchronized where liftCompare = genericLiftCompare @@ -65,7 +65,7 @@ instance Show1 Synchronized where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Synchronized data New a = New { newType :: !a, newArgs :: ![a] } - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 New where liftEq = genericLiftEq instance Ord1 New where liftCompare = genericLiftCompare @@ -75,7 +75,7 @@ instance Show1 New where liftShowsPrec = genericLiftShowsPrec instance Evaluatable New data Asterisk a = Asterisk - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Asterisk where liftEq = genericLiftEq instance Ord1 Asterisk where liftCompare = genericLiftCompare @@ -86,7 +86,7 @@ instance Evaluatable Asterisk data Constructor a = Constructor { constructorModifiers :: ![a], constructorTypeParams :: ![a], constructorIdentifier :: !a, constructorParams :: ![a], constructorThrows :: ![a], constructorBody :: a} - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Constructor where liftEq = genericLiftEq instance Ord1 Constructor where liftCompare = genericLiftCompare @@ -96,7 +96,7 @@ instance Show1 Constructor where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Constructor data TypeParameter a = TypeParameter { typeParamAnnotation :: ![a], typeParamIdentifier :: !a, typeParamTypeBound :: ![a]} - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 TypeParameter where liftEq = genericLiftEq instance Ord1 TypeParameter where liftCompare = genericLiftCompare @@ -106,7 +106,7 @@ instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec instance Evaluatable TypeParameter data Annotation a = Annotation { annotationName :: !a, annotationField :: [a]} - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 Annotation where liftEq = genericLiftEq instance Ord1 Annotation where liftCompare = genericLiftCompare @@ -116,7 +116,7 @@ instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Annotation data AnnotationField a = AnnotationField { annotationFieldName :: a, annotationFieldValue :: a } - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 AnnotationField where liftEq = genericLiftEq instance Ord1 AnnotationField where liftCompare = genericLiftCompare @@ -126,7 +126,7 @@ instance Show1 AnnotationField where liftShowsPrec = genericLiftShowsPrec instance Evaluatable AnnotationField data GenericType a = GenericType { genericTypeIdentifier :: a, genericTypeArguments :: [a] } - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 GenericType where liftEq = genericLiftEq instance Ord1 GenericType where liftCompare = genericLiftCompare @@ -136,7 +136,7 @@ instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable GenericType data TypeWithModifiers a = TypeWithModifiers [a] a - deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) + deriving (Diffable, Eq, FreeVariables1, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, Declarations1, ToJSONFields1, Hashable1) instance Eq1 TypeWithModifiers where liftEq = genericLiftEq instance Ord1 TypeWithModifiers where liftCompare = genericLiftCompare From ff049a5dd2b10163909f087f516090d096ce235d Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 10:36:45 -0700 Subject: [PATCH 59/68] ++haskell-tree-sitter for new tree-sitter-java --- vendor/haskell-tree-sitter | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vendor/haskell-tree-sitter b/vendor/haskell-tree-sitter index 128a1c100..2df318536 160000 --- a/vendor/haskell-tree-sitter +++ b/vendor/haskell-tree-sitter @@ -1 +1 @@ -Subproject commit 128a1c1007a1df9f7111a328919da728803c4e3b +Subproject commit 2df318536681fcb4a3a6fb11b4bc03709bf80343 From ffec14d5f8474117a55c24a297adb942ebb57ff9 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 10:38:13 -0700 Subject: [PATCH 60/68] Remove extraneous imports --- src/Language/Java/Assignment.hs | 53 +++++++++++++++++---------------- 1 file changed, 27 insertions(+), 26 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 1f2e7ba06..8d945ca4e 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -8,6 +8,7 @@ module Language.Java.Assignment import Assigning.Assignment hiding (Assignment, Error, while, try) import Data.Abstract.FreeVariables +import Data.Abstract.Name import Data.Functor (($>)) import Data.List.NonEmpty (some1) import Data.Record @@ -418,26 +419,26 @@ enhancedFor = makeTerm <$> symbol EnhancedForStatement <*> children (Statement.F -- TODO: instanceOf binary :: Assignment binary = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expression expression - [ (injectSum .) . Expression.LessThan <$ symbol AnonLAngle - , (injectSum .) . Expression.GreaterThan <$ symbol AnonRAngle - , (injectSum .) . Expression.Equal <$ symbol AnonEqualEqual - , (injectSum .) . Expression.GreaterThanEqual <$ symbol AnonRAngleEqual - , (injectSum .) . Expression.LessThanEqual <$ symbol AnonLAngleEqual - , (injectSum .) . invert Expression.Equal <$ symbol AnonBangEqual - , (injectSum .) . Expression.And <$ symbol AnonAmpersandAmpersand - , (injectSum .) . Expression.Or <$ symbol AnonPipePipe - , (injectSum .) . Expression.BAnd <$ symbol AnonAmpersand - , (injectSum .) . Expression.BOr <$ symbol AnonPipe - , (injectSum .) . Expression.BXOr <$ symbol AnonCaret - , (injectSum .) . Expression.Modulo <$ symbol AnonPercent - , (injectSum .) . Expression.LShift <$ symbol AnonLAngleLAngle - , (injectSum .) . Expression.RShift <$ symbol AnonRAngleRAngle - , (injectSum .) . Expression.UnsignedRShift <$ symbol AnonRAngleRAngleRAngle - , (injectSum .) . Expression.Plus <$ symbol AnonPlus - , (injectSum .) . Expression.Minus <$ symbol AnonMinus - , (injectSum .) . Expression.Times <$ symbol AnonStar - , (injectSum .) . Expression.DividedBy <$ symbol AnonSlash - , (injectSum .) . Expression.InstanceOf <$ symbol AnonInstanceof + [ (inject .) . Expression.LessThan <$ symbol AnonLAngle + , (inject .) . Expression.GreaterThan <$ symbol AnonRAngle + , (inject .) . Expression.Equal <$ symbol AnonEqualEqual + , (inject .) . Expression.GreaterThanEqual <$ symbol AnonRAngleEqual + , (inject .) . Expression.LessThanEqual <$ symbol AnonLAngleEqual + , (inject .) . invert Expression.Equal <$ symbol AnonBangEqual + , (inject .) . Expression.And <$ symbol AnonAmpersandAmpersand + , (inject .) . Expression.Or <$ symbol AnonPipePipe + , (inject .) . Expression.BAnd <$ symbol AnonAmpersand + , (inject .) . Expression.BOr <$ symbol AnonPipe + , (inject .) . Expression.BXOr <$ symbol AnonCaret + , (inject .) . Expression.Modulo <$ symbol AnonPercent + , (inject .) . Expression.LShift <$ symbol AnonLAngleLAngle + , (inject .) . Expression.RShift <$ symbol AnonRAngleRAngle + , (inject .) . Expression.UnsignedRShift <$ symbol AnonRAngleRAngleRAngle + , (inject .) . Expression.Plus <$ symbol AnonPlus + , (inject .) . Expression.Minus <$ symbol AnonMinus + , (inject .) . Expression.Times <$ symbol AnonStar + , (inject .) . Expression.DividedBy <$ symbol AnonSlash + , (inject .) . Expression.InstanceOf <$ symbol AnonInstanceof ]) where invert cons a b = Expression.Not (makeTerm1 (cons a b)) @@ -451,7 +452,7 @@ infixTerm = infixContext comment assignment' :: Assignment assignment' = makeTerm' <$> symbol AssignmentExpression <*> children (infixTerm lhs expression - [ (injectSum .) . Statement.Assignment [] <$ symbol AnonEqual + [ (inject .) . Statement.Assignment [] <$ symbol AnonEqual , assign Expression.Plus <$ symbol AnonPlusEqual , assign Expression.Minus <$ symbol AnonMinusEqual , assign Expression.Times <$ symbol AnonStarEqual @@ -466,7 +467,7 @@ assignment' = makeTerm' <$> symbol AssignmentExpression <*> children (infixTerm ]) where assign :: (f :< Syntax) => (Term -> Term -> f Term) -> Term -> Term -> Sum Syntax Term - assign c l r = injectSum (Statement.Assignment [] l (makeTerm1 (c l r))) + assign c l r = inject (Statement.Assignment [] l (makeTerm1 (c l r))) lhs = symbol Lhs *> children (term expression) data UnaryType @@ -489,10 +490,10 @@ unary = make <$> symbol UnaryExpression <*> children ((,) <$> operator <*> term update :: Assignment update = makeTerm' <$> symbol UpdateExpression <*> children ( - injectSum . Statement.PreIncrement <$ token AnonPlusPlus <*> term expression - <|> injectSum . Statement.PreDecrement <$ token AnonMinusMinus <*> term expression - <|> injectSum . Statement.PostIncrement <$> term expression <* token AnonPlusPlus - <|> injectSum . Statement.PostDecrement <$> term expression <* token AnonMinusMinus) + inject . Statement.PreIncrement <$ token AnonPlusPlus <*> term expression + <|> inject . Statement.PreDecrement <$ token AnonMinusMinus <*> term expression + <|> inject . Statement.PostIncrement <$> term expression <* token AnonPlusPlus + <|> inject . Statement.PostDecrement <$> term expression <* token AnonMinusMinus) ternary :: Assignment ternary = makeTerm <$> symbol TernaryExpression <*> children (Statement.If <$> term expression <*> term expression <*> term expression) From 324ebce70942d01094cb44aa566a6891265a3909 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 11:13:50 -0700 Subject: [PATCH 61/68] remove KindSignatures --- src/Language/Java/Assignment.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 8d945ca4e..caa1c7449 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DataKinds, RankNTypes, TypeOperators, KindSignatures #-} +{-# LANGUAGE DataKinds, RankNTypes, TypeOperators #-} module Language.Java.Assignment ( assignment , Syntax From aef3e7dc73bc873af8ac083a6d7fed1f1c718212 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 11:15:15 -0700 Subject: [PATCH 62/68] remove unnecessary or incorrect imports --- src/Language/Java/Assignment.hs | 4 ---- src/Language/Java/Syntax.hs | 2 +- 2 files changed, 1 insertion(+), 5 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index caa1c7449..92415da2b 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -7,7 +7,6 @@ module Language.Java.Assignment ) where import Assigning.Assignment hiding (Assignment, Error, while, try) -import Data.Abstract.FreeVariables import Data.Abstract.Name import Data.Functor (($>)) import Data.List.NonEmpty (some1) @@ -28,9 +27,6 @@ import qualified Data.Syntax.Type as Type import qualified Data.Term as Term import Prelude hiding (break) import Prologue hiding (for, try, This) -import GHC.TypeLits -- this is just to make sense of the Data kind (len :: Nat) example - --- data Vec a (len :: Nat) type Syntax = '[ Comment.Comment diff --git a/src/Language/Java/Syntax.hs b/src/Language/Java/Syntax.hs index 9857152aa..e9f08ce85 100644 --- a/src/Language/Java/Syntax.hs +++ b/src/Language/Java/Syntax.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveAnyClass #-} module Language.Java.Syntax where -import Data.Abstract.Evaluatable hiding (Label) +import Data.Abstract.Evaluatable import Diffing.Algorithm import Prologue hiding (Constructor) import Data.JSON.Fields From 1808d53a3b1c7085582d28838b91072aec080580 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 11:16:00 -0700 Subject: [PATCH 63/68] correct text fixtures according to and/or ruby bug fix --- .../ruby/corpus/conditional-assignment.diffA-B.txt | 10 ++++++---- .../ruby/corpus/conditional-assignment.diffB-A.txt | 10 ++++++---- .../ruby/corpus/conditional-assignment.parseA.txt | 2 +- 3 files changed, 13 insertions(+), 9 deletions(-) diff --git a/test/fixtures/ruby/corpus/conditional-assignment.diffA-B.txt b/test/fixtures/ruby/corpus/conditional-assignment.diffA-B.txt index e89045c82..7dac9f474 100644 --- a/test/fixtures/ruby/corpus/conditional-assignment.diffA-B.txt +++ b/test/fixtures/ruby/corpus/conditional-assignment.diffA-B.txt @@ -1,7 +1,9 @@ (Program (Assignment (Identifier) - (And - (Identifier) - { (Integer) - ->(Integer) }))) + { (Or + {-(Identifier)-} + {-(Integer)-}) + ->(And + {+(Identifier)+} + {+(Integer)+}) })) diff --git a/test/fixtures/ruby/corpus/conditional-assignment.diffB-A.txt b/test/fixtures/ruby/corpus/conditional-assignment.diffB-A.txt index e89045c82..2c90524bf 100644 --- a/test/fixtures/ruby/corpus/conditional-assignment.diffB-A.txt +++ b/test/fixtures/ruby/corpus/conditional-assignment.diffB-A.txt @@ -1,7 +1,9 @@ (Program (Assignment (Identifier) - (And - (Identifier) - { (Integer) - ->(Integer) }))) + { (And + {-(Identifier)-} + {-(Integer)-}) + ->(Or + {+(Identifier)+} + {+(Integer)+}) })) diff --git a/test/fixtures/ruby/corpus/conditional-assignment.parseA.txt b/test/fixtures/ruby/corpus/conditional-assignment.parseA.txt index 2263a1b1f..fdfdc8028 100644 --- a/test/fixtures/ruby/corpus/conditional-assignment.parseA.txt +++ b/test/fixtures/ruby/corpus/conditional-assignment.parseA.txt @@ -1,6 +1,6 @@ (Program (Assignment (Identifier) - (And + (Or (Identifier) (Integer)))) From 86d7ccd461acc14bd62baf2564fb6877006cfae8 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 11:28:39 -0700 Subject: [PATCH 64/68] apparently remove classBody in response to this lint error --- src/Language/Java/Assignment.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 92415da2b..49291736f 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -113,7 +113,7 @@ manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Conte manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term] -manyTermsTill step end = manyTill (step <|> comment) end +manyTermsTill step = manyTill (step <|> comment) someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) @@ -254,7 +254,7 @@ superInterfaces = symbol SuperInterfaces *> children (symbol InterfaceTypeList * class' :: Assignment class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many modifier <*> term identifier <*> (typeParameters <|> pure []) <*> optional superClass <*> (superInterfaces <|> pure []) <*> classBody) where - makeClass modifiers identifier typeParams superClass superInterfaces classBody = Declaration.Class (modifiers ++ typeParams) identifier (maybeToList superClass ++ superInterfaces) classBody -- not doing an assignment, just straight up function + makeClass modifiers identifier typeParams superClass superInterfaces = Declaration.Class (modifiers ++ typeParams) identifier (maybeToList superClass ++ superInterfaces) -- not doing an assignment, just straight up function classBody = makeTerm <$> symbol ClassBody <*> children (manyTerm expression) superClass = symbol Superclass *> children type' -- matching term expression won't work since there is no node for that; it's AnonExtends @@ -273,7 +273,6 @@ class' = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> many m fieldDeclaration :: Assignment fieldDeclaration = makeTerm <$> symbol FieldDeclaration <*> children ((,) <$> manyTerm modifier <*> type' <**> variableDeclaratorList) - method :: Assignment method = makeTerm <$> symbol MethodDeclaration <*> children (makeMethod <$> many modifier <*> emptyTerm <*> methodHeader <*> methodBody) where From fc0cb9828f3e040899c2f10ffe1262cffcd4c02b Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 11:30:27 -0700 Subject: [PATCH 65/68] get rid of body from Method to address linter --- src/Language/Java/Assignment.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 49291736f..0215d88cb 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -279,7 +279,7 @@ method = makeTerm <$> symbol MethodDeclaration <*> children (makeMethod <$> many methodBody = symbol MethodBody *> children (term expression <|> emptyTerm) methodDeclarator = symbol MethodDeclarator *> children ( (,) <$> identifier <*> formalParameters) methodHeader = symbol MethodHeader *> children ((,,,,) <$> (typeParameters <|> pure []) <*> manyTerm annotation <*> type' <*> methodDeclarator <*> (throws <|> pure [])) - makeMethod modifiers receiver (typeParams, annotations, returnType, (name, params), throws) body = Declaration.Method (returnType : modifiers ++ typeParams ++ annotations ++ throws) receiver name params body + makeMethod modifiers receiver (typeParams, annotations, returnType, (name, params), throws) = Declaration.Method (returnType : modifiers ++ typeParams ++ annotations ++ throws) receiver name params -- TODO: add genericType -- Question: should this genericType be part of type or not? Its own type because it's different structurally From eb4c38c8c0316bcb6ba8f708f9c00fe7554c0464 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 11:35:43 -0700 Subject: [PATCH 66/68] blindly address linter error on package and potentially break other stuff --- src/Language/Java/Assignment.hs | 8 ++------ 1 file changed, 2 insertions(+), 6 deletions(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 0215d88cb..db7e37df0 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -314,7 +314,7 @@ interface = makeTerm <$> symbol InterfaceDeclaration <*> children (normal <|> an where interfaceBody = makeTerm <$> symbol InterfaceBody <*> children (manyTerm interfaceMemberDeclaration) normal = symbol NormalInterfaceDeclaration *> children (makeInterface <$> manyTerm modifier <*> identifier <*> (typeParameters <|> pure []) <*> interfaceBody) - makeInterface modifiers identifier typeParams interfaceBody = Declaration.InterfaceDeclaration (modifiers ++ typeParams) identifier interfaceBody + makeInterface modifiers identifier typeParams = Declaration.InterfaceDeclaration (modifiers ++ typeParams) identifier annotationType = symbol AnnotationTypeDeclaration *> children (Declaration.InterfaceDeclaration [] <$> identifier <*> annotationTypeBody) annotationTypeBody = makeTerm <$> symbol AnnotationTypeBody <*> children (many expression) interfaceMemberDeclaration = symbol InterfaceMemberDeclaration *> children (term expression) @@ -324,13 +324,9 @@ package :: Assignment -- package = makeTerm <$> symbol PackageDeclaration <*> children (Java.Syntax.Package <$> someTerm expression) package = do loc <- symbol PackageDeclaration -- location which is calling the symbol API - c <- children $ do - expressions <- someTerm expression - pure (Java.Syntax.Package expressions) + c <- children $ do Java.Syntax.Package <$> someTerm expression pure (makeTerm loc c) -- pure is re-wrapping it back into the outer context, which in this case is Assignment (ie., the return type of the function) - - enum :: Assignment enum = makeTerm <$> symbol Grammar.EnumDeclaration <*> children (Java.Syntax.EnumDeclaration <$> term identifier <*> manyTerm enumConstant) where enumConstant = symbol EnumConstant *> children (term identifier) From ef4bf8a0cda82eaa592c56761fbcfa147e90f4d8 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 11:38:18 -0700 Subject: [PATCH 67/68] remove params --- src/Language/Java/Assignment.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index db7e37df0..497c00724 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -332,7 +332,7 @@ enum = makeTerm <$> symbol Grammar.EnumDeclaration <*> children (Java.Syntax.Enu where enumConstant = symbol EnumConstant *> children (term identifier) return' :: Assignment -return' = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children (expression)) +return' = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children expression) -- method expressions dims :: Assignment.Assignment [] Grammar [Term] From d7798d5fc816095b0bf32693989064008314f6a9 Mon Sep 17 00:00:00 2001 From: Ayman Nadeem Date: Fri, 1 Jun 2018 11:39:09 -0700 Subject: [PATCH 68/68] remove type' for now --- src/Language/Java/Assignment.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Language/Java/Assignment.hs b/src/Language/Java/Assignment.hs index 497c00724..4853112d1 100644 --- a/src/Language/Java/Assignment.hs +++ b/src/Language/Java/Assignment.hs @@ -352,7 +352,7 @@ type' = choice [ , identifier , generic ] - where array type' = foldl (\into each -> makeTerm1 (Type.Array (Just each) into)) type' + where array = foldl (\into each -> makeTerm1 (Type.Array (Just each) into)) if' :: Assignment if' = makeTerm <$> symbol IfThenElseStatement <*> children (Statement.If <$> term expression <*> term expression <*> (term expression <|> emptyTerm))