From 9aa5ba6f1830265a8fb35faf7ec72c5a926ab794 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Tue, 30 May 2017 16:54:08 -0700 Subject: [PATCH 01/89] :fire: identifier from expression --- src/Data/Syntax/Expression.hs | 8 + src/Language/Python/Syntax.hs | 2 +- src/TreeSitter.hs | 2 +- symbols.txt | 413 ++++++++++++++++++++++++++++++++++ 4 files changed, 423 insertions(+), 2 deletions(-) create mode 100644 symbols.txt diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index 5ae264f03..acfb13815 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -50,3 +50,11 @@ data Bitwise a instance Eq1 Bitwise where liftEq = genericLiftEq instance Show1 Bitwise where liftShowsPrec = genericLiftShowsPrec + +-- | Member Access +data MemberAccess a + = MemberAccess a a + deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) + +instance Eq1 MemberAccess where liftEq = genericLiftEq +instance Show1 MemberAccess where liftShowsPrec = genericLiftShowsPrec diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 0f47369ac..9fd4edf66 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -79,7 +79,7 @@ tuple :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) tuple = makeTerm <$> symbol Tuple <*> children (Literal.Tuple <$> (many expression)) expression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -expression = identifier <|> statement <|> unaryOperator <|> binaryOperator <|> booleanOperator <|> tuple <|> literal +expression = statement <|> unaryOperator <|> binaryOperator <|> booleanOperator <|> tuple <|> literal -- TODO: Consider flattening single element lists expressionList :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) diff --git a/src/TreeSitter.hs b/src/TreeSitter.hs index fc6d63d21..88a584280 100644 --- a/src/TreeSitter.hs +++ b/src/TreeSitter.hs @@ -30,6 +30,7 @@ import qualified Text.Parser.TreeSitter as TS import SourceSpan import Info + -- | Returns a TreeSitter parser for the given language and TreeSitter grammar. treeSitterParser :: Language -> Ptr TS.Language -> Source -> IO (Term (Syntax.Syntax Text) (Record DefaultFields)) treeSitterParser language grammar source = bracket ts_document_new ts_document_free $ \ document -> do @@ -40,7 +41,6 @@ treeSitterParser language grammar source = bracket ts_document_new ts_document_f term <- documentToTerm language document source pure term - -- | Parse 'Source' with the given 'TS.Language' and return its AST. parseToAST :: (Bounded grammar, Enum grammar) => Ptr TS.Language -> Source -> IO (A.AST grammar) parseToAST language source = bracket ts_document_new ts_document_free $ \ document -> do diff --git a/symbols.txt b/symbols.txt new file mode 100644 index 000000000..e51d3f7e5 --- /dev/null +++ b/symbols.txt @@ -0,0 +1,413 @@ +src/Language/Python/Syntax.hs:17:1-54: Splicing declarations + mkSymbolDatatype (mkName "Grammar") tree_sitter_python + ======> + data Grammar + = END | + HiddenNewline | + HiddenIndent | + HiddenDedent | + AnonPrint | + AnonExec | + AnonImport | + AnonFrom | + AnonDot | + AnonLParen | + AnonRParen | + AnonComma | + AnonAs | + AnonStar | + AnonRAngleRAngle | + AnonAssert | + AnonReturn | + AnonDel | + AnonRaise | + PassStatement | + BreakStatement | + ContinueStatement | + AnonIf | + AnonColon | + AnonElif | + AnonElse | + AnonFor | + AnonIn | + AnonWhile | + AnonTry | + AnonExcept | + AnonFinally | + AnonWith | + AnonAsync | + AnonDef | + AnonMinusRAngle | + AnonEqual | + AnonGlobal | + AnonNonlocal | + AnonClass | + AnonAt | + AnonNot | + AnonAnd | + AnonOr | + AnonPlus | + AnonMinus | + AnonSlash | + AnonPercent | + AnonSlashSlash | + AnonStarStar | + AnonPipe | + AnonAmpersand | + AnonCaret | + AnonLAngleLAngle | + AnonTilde | + AnonLAngle | + AnonLAngleEqual | + AnonEqualEqual | + AnonBangEqual | + AnonRAngleEqual | + AnonRAngle | + AnonLAngleRAngle | + AnonIs | + AnonLambda | + AnonPlusEqual | + AnonMinusEqual | + AnonStarEqual | + AnonSlashEqual | + AnonSlashSlashEqual | + AnonPercentEqual | + AnonStarStarEqual | + AnonRAngleRAngleEqual | + AnonLAngleLAngleEqual | + AnonAmpersandEqual | + AnonCaretEqual | + AnonPipeEqual | + AnonYield | + AnonLBracket | + AnonRBracket | + Ellipsis | + AnonLBrace | + AnonRBrace | + String | + Integer | + Float | + Identifier | + True | + False | + None | + AnonAwait | + Comment | + HiddenSemicolon | + Module | + HiddenStatement | + HiddenSimpleStatement | + KeywordIdentifier | + ImportStatement | + ImportFromStatement | + HiddenImportList | + AliasedImport | + WildcardImport | + PrintStatement | + Chevron | + AssertStatement | + ExpressionStatement | + ReturnStatement | + DeleteStatement | + RaiseStatement | + HiddenCompoundStatement | + IfStatement | + ElifClause | + ElseClause | + ForStatement | + WhileStatement | + TryStatement | + ExceptClause | + FinallyClause | + WithStatement | + WithItem | + AsyncFunctionDefinition | + FunctionDefinition | + HiddenFunctionDefinition | + Parameters | + HiddenParameters | + DefaultParameter | + TypedDefaultParameter | + ListSplatParameter | + DictionarySplatParameter | + GlobalStatement | + NonlocalStatement | + ExecStatement | + ClassDefinition | + ArgumentList | + DecoratedDefinition | + Decorator | + HiddenSuite | + Variables | + ExpressionList | + DottedName | + HiddenExpression | + HiddenPrimaryExpression | + NotOperator | + BooleanOperator | + BinaryOperator | + UnaryOperator | + ComparisonOperator | + Lambda | + Assignment | + AugmentedAssignment | + HiddenRightHandSide | + Yield | + Attribute | + Subscript | + Slice | + Call | + TypedParameter | + Type | + KeywordArgument | + ListSplatArgument | + DictionarySplatArgument | + List | + ListComprehension | + HiddenListComprehension | + Dictionary | + DictionaryComprehension | + Pair | + HiddenDictionaryComprehension | + Set | + SetComprehension | + HiddenSetComprehension | + Tuple | + GeneratorExpression | + HiddenGeneratorExpression | + ConditionalExpression | + ConcatenatedString | + Await | + AuxModuleRepeat1 | + AuxHiddenStatementRepeat1 | + AuxHiddenStatementRepeat2 | + AuxImportFromStatementRepeat1 | + AuxHiddenImportListRepeat1 | + AuxPrintStatementRepeat1 | + AuxIfStatementRepeat1 | + AuxTryStatementRepeat1 | + AuxWithStatementRepeat1 | + AuxHiddenParametersRepeat1 | + AuxGlobalStatementRepeat1 | + AuxArgumentListRepeat1 | + AuxDecoratedDefinitionRepeat1 | + AuxVariablesRepeat1 | + AuxDottedNameRepeat1 | + AuxComparisonOperatorRepeat1 | + AuxSubscriptRepeat1 | + AuxDictionaryRepeat1 | + AuxConcatenatedStringRepeat1 + deriving (Show, Eq, Enum, Ord) + instance Symbol Grammar where + symbolType Language.Python.Syntax.END = Regular + symbolType Language.Python.Syntax.HiddenNewline = Regular + symbolType Language.Python.Syntax.HiddenIndent = Regular + symbolType Language.Python.Syntax.HiddenDedent = Regular + symbolType Language.Python.Syntax.AnonPrint = Anonymous + symbolType Language.Python.Syntax.AnonExec = Anonymous + symbolType Language.Python.Syntax.AnonImport = Anonymous + symbolType Language.Python.Syntax.AnonFrom = Anonymous + symbolType Language.Python.Syntax.AnonDot = Anonymous + symbolType Language.Python.Syntax.AnonLParen = Anonymous + symbolType Language.Python.Syntax.AnonRParen = Anonymous + symbolType Language.Python.Syntax.AnonComma = Anonymous + symbolType Language.Python.Syntax.AnonAs = Anonymous + symbolType Language.Python.Syntax.AnonStar = Anonymous + symbolType Language.Python.Syntax.AnonRAngleRAngle = Anonymous + symbolType Language.Python.Syntax.AnonAssert = Anonymous + symbolType Language.Python.Syntax.AnonReturn = Anonymous + symbolType Language.Python.Syntax.AnonDel = Anonymous + symbolType Language.Python.Syntax.AnonRaise = Anonymous + symbolType Language.Python.Syntax.PassStatement = Regular + symbolType Language.Python.Syntax.BreakStatement = Regular + symbolType Language.Python.Syntax.ContinueStatement = Regular + symbolType Language.Python.Syntax.AnonIf = Anonymous + symbolType Language.Python.Syntax.AnonColon = Anonymous + symbolType Language.Python.Syntax.AnonElif = Anonymous + symbolType Language.Python.Syntax.AnonElse = Anonymous + symbolType Language.Python.Syntax.AnonFor = Anonymous + symbolType Language.Python.Syntax.AnonIn = Anonymous + symbolType Language.Python.Syntax.AnonWhile = Anonymous + symbolType Language.Python.Syntax.AnonTry = Anonymous + symbolType Language.Python.Syntax.AnonExcept = Anonymous + symbolType Language.Python.Syntax.AnonFinally = Anonymous + symbolType Language.Python.Syntax.AnonWith = Anonymous + symbolType Language.Python.Syntax.AnonAsync = Anonymous + symbolType Language.Python.Syntax.AnonDef = Anonymous + symbolType Language.Python.Syntax.AnonMinusRAngle = Anonymous + symbolType Language.Python.Syntax.AnonEqual = Anonymous + symbolType Language.Python.Syntax.AnonGlobal = Anonymous + symbolType Language.Python.Syntax.AnonNonlocal = Anonymous + symbolType Language.Python.Syntax.AnonClass = Anonymous + symbolType Language.Python.Syntax.AnonAt = Anonymous + symbolType Language.Python.Syntax.AnonNot = Anonymous + symbolType Language.Python.Syntax.AnonAnd = Anonymous + symbolType Language.Python.Syntax.AnonOr = Anonymous + symbolType Language.Python.Syntax.AnonPlus = Anonymous + symbolType Language.Python.Syntax.AnonMinus = Anonymous + symbolType Language.Python.Syntax.AnonSlash = Anonymous + symbolType Language.Python.Syntax.AnonPercent = Anonymous + symbolType Language.Python.Syntax.AnonSlashSlash = Anonymous + symbolType Language.Python.Syntax.AnonStarStar = Anonymous + symbolType Language.Python.Syntax.AnonPipe = Anonymous + symbolType Language.Python.Syntax.AnonAmpersand = Anonymous + symbolType Language.Python.Syntax.AnonCaret = Anonymous + symbolType Language.Python.Syntax.AnonLAngleLAngle = Anonymous + symbolType Language.Python.Syntax.AnonTilde = Anonymous + symbolType Language.Python.Syntax.AnonLAngle = Anonymous + symbolType Language.Python.Syntax.AnonLAngleEqual = Anonymous + symbolType Language.Python.Syntax.AnonEqualEqual = Anonymous + symbolType Language.Python.Syntax.AnonBangEqual = Anonymous + symbolType Language.Python.Syntax.AnonRAngleEqual = Anonymous + symbolType Language.Python.Syntax.AnonRAngle = Anonymous + symbolType Language.Python.Syntax.AnonLAngleRAngle = Anonymous + symbolType Language.Python.Syntax.AnonIs = Anonymous + symbolType Language.Python.Syntax.AnonLambda = Anonymous + symbolType Language.Python.Syntax.AnonPlusEqual = Anonymous + symbolType Language.Python.Syntax.AnonMinusEqual = Anonymous + symbolType Language.Python.Syntax.AnonStarEqual = Anonymous + symbolType Language.Python.Syntax.AnonSlashEqual = Anonymous + symbolType Language.Python.Syntax.AnonSlashSlashEqual = Anonymous + symbolType Language.Python.Syntax.AnonPercentEqual = Anonymous + symbolType Language.Python.Syntax.AnonStarStarEqual = Anonymous + symbolType Language.Python.Syntax.AnonRAngleRAngleEqual = Anonymous + symbolType Language.Python.Syntax.AnonLAngleLAngleEqual = Anonymous + symbolType Language.Python.Syntax.AnonAmpersandEqual = Anonymous + symbolType Language.Python.Syntax.AnonCaretEqual = Anonymous + symbolType Language.Python.Syntax.AnonPipeEqual = Anonymous + symbolType Language.Python.Syntax.AnonYield = Anonymous + symbolType Language.Python.Syntax.AnonLBracket = Anonymous + symbolType Language.Python.Syntax.AnonRBracket = Anonymous + symbolType Language.Python.Syntax.Ellipsis = Regular + symbolType Language.Python.Syntax.AnonLBrace = Anonymous + symbolType Language.Python.Syntax.AnonRBrace = Anonymous + symbolType Language.Python.Syntax.String = Regular + symbolType Language.Python.Syntax.Integer = Regular + symbolType Language.Python.Syntax.Float = Regular + symbolType Language.Python.Syntax.Identifier = Regular + symbolType Language.Python.Syntax.True = Regular + symbolType Language.Python.Syntax.False = Regular + symbolType Language.Python.Syntax.None = Regular + symbolType Language.Python.Syntax.AnonAwait = Anonymous + symbolType Language.Python.Syntax.Comment = Regular + symbolType Language.Python.Syntax.HiddenSemicolon = Regular + symbolType Language.Python.Syntax.Module = Regular + symbolType Language.Python.Syntax.HiddenStatement = Regular + symbolType Language.Python.Syntax.HiddenSimpleStatement = Regular + symbolType Language.Python.Syntax.KeywordIdentifier = Regular + symbolType Language.Python.Syntax.ImportStatement = Regular + symbolType Language.Python.Syntax.ImportFromStatement = Regular + symbolType Language.Python.Syntax.HiddenImportList = Regular + symbolType Language.Python.Syntax.AliasedImport = Regular + symbolType Language.Python.Syntax.WildcardImport = Regular + symbolType Language.Python.Syntax.PrintStatement = Regular + symbolType Language.Python.Syntax.Chevron = Regular + symbolType Language.Python.Syntax.AssertStatement = Regular + symbolType Language.Python.Syntax.ExpressionStatement = Regular + symbolType Language.Python.Syntax.ReturnStatement = Regular + symbolType Language.Python.Syntax.DeleteStatement = Regular + symbolType Language.Python.Syntax.RaiseStatement = Regular + symbolType Language.Python.Syntax.HiddenCompoundStatement = Regular + symbolType Language.Python.Syntax.IfStatement = Regular + symbolType Language.Python.Syntax.ElifClause = Regular + symbolType Language.Python.Syntax.ElseClause = Regular + symbolType Language.Python.Syntax.ForStatement = Regular + symbolType Language.Python.Syntax.WhileStatement = Regular + symbolType Language.Python.Syntax.TryStatement = Regular + symbolType Language.Python.Syntax.ExceptClause = Regular + symbolType Language.Python.Syntax.FinallyClause = Regular + symbolType Language.Python.Syntax.WithStatement = Regular + symbolType Language.Python.Syntax.WithItem = Regular + symbolType Language.Python.Syntax.AsyncFunctionDefinition = Regular + symbolType Language.Python.Syntax.FunctionDefinition = Regular + symbolType Language.Python.Syntax.HiddenFunctionDefinition + = Regular + symbolType Language.Python.Syntax.Parameters = Regular + symbolType Language.Python.Syntax.HiddenParameters = Regular + symbolType Language.Python.Syntax.DefaultParameter = Regular + symbolType Language.Python.Syntax.TypedDefaultParameter = Regular + symbolType Language.Python.Syntax.ListSplatParameter = Regular + symbolType Language.Python.Syntax.DictionarySplatParameter + = Regular + symbolType Language.Python.Syntax.GlobalStatement = Regular + symbolType Language.Python.Syntax.NonlocalStatement = Regular + symbolType Language.Python.Syntax.ExecStatement = Regular + symbolType Language.Python.Syntax.ClassDefinition = Regular + symbolType Language.Python.Syntax.ArgumentList = Regular + symbolType Language.Python.Syntax.DecoratedDefinition = Regular + symbolType Language.Python.Syntax.Decorator = Regular + symbolType Language.Python.Syntax.HiddenSuite = Regular + symbolType Language.Python.Syntax.Variables = Regular + symbolType Language.Python.Syntax.ExpressionList = Regular + symbolType Language.Python.Syntax.DottedName = Regular + symbolType Language.Python.Syntax.HiddenExpression = Regular + symbolType Language.Python.Syntax.HiddenPrimaryExpression = Regular + symbolType Language.Python.Syntax.NotOperator = Regular + symbolType Language.Python.Syntax.BooleanOperator = Regular + symbolType Language.Python.Syntax.BinaryOperator = Regular + symbolType Language.Python.Syntax.UnaryOperator = Regular + symbolType Language.Python.Syntax.ComparisonOperator = Regular + symbolType Language.Python.Syntax.Lambda = Regular + symbolType Language.Python.Syntax.Assignment = Regular + symbolType Language.Python.Syntax.AugmentedAssignment = Regular + symbolType Language.Python.Syntax.HiddenRightHandSide = Regular + symbolType Language.Python.Syntax.Yield = Regular + symbolType Language.Python.Syntax.Attribute = Regular + symbolType Language.Python.Syntax.Subscript = Regular + symbolType Language.Python.Syntax.Slice = Regular + symbolType Language.Python.Syntax.Call = Regular + symbolType Language.Python.Syntax.TypedParameter = Regular + symbolType Language.Python.Syntax.Type = Regular + symbolType Language.Python.Syntax.KeywordArgument = Regular + symbolType Language.Python.Syntax.ListSplatArgument = Regular + symbolType Language.Python.Syntax.DictionarySplatArgument = Regular + symbolType Language.Python.Syntax.List = Regular + symbolType Language.Python.Syntax.ListComprehension = Regular + symbolType Language.Python.Syntax.HiddenListComprehension = Regular + symbolType Language.Python.Syntax.Dictionary = Regular + symbolType Language.Python.Syntax.DictionaryComprehension = Regular + symbolType Language.Python.Syntax.Pair = Regular + symbolType Language.Python.Syntax.HiddenDictionaryComprehension + = Regular + symbolType Language.Python.Syntax.Set = Regular + symbolType Language.Python.Syntax.SetComprehension = Regular + symbolType Language.Python.Syntax.HiddenSetComprehension = Regular + symbolType Language.Python.Syntax.Tuple = Regular + symbolType Language.Python.Syntax.GeneratorExpression = Regular + symbolType Language.Python.Syntax.HiddenGeneratorExpression + = Regular + symbolType Language.Python.Syntax.ConditionalExpression = Regular + symbolType Language.Python.Syntax.ConcatenatedString = Regular + symbolType Language.Python.Syntax.Await = Regular + symbolType Language.Python.Syntax.AuxModuleRepeat1 = Auxiliary + symbolType Language.Python.Syntax.AuxHiddenStatementRepeat1 + = Auxiliary + symbolType Language.Python.Syntax.AuxHiddenStatementRepeat2 + = Auxiliary + symbolType Language.Python.Syntax.AuxImportFromStatementRepeat1 + = Auxiliary + symbolType Language.Python.Syntax.AuxHiddenImportListRepeat1 + = Auxiliary + symbolType Language.Python.Syntax.AuxPrintStatementRepeat1 + = Auxiliary + symbolType Language.Python.Syntax.AuxIfStatementRepeat1 = Auxiliary + symbolType Language.Python.Syntax.AuxTryStatementRepeat1 + = Auxiliary + symbolType Language.Python.Syntax.AuxWithStatementRepeat1 + = Auxiliary + symbolType Language.Python.Syntax.AuxHiddenParametersRepeat1 + = Auxiliary + symbolType Language.Python.Syntax.AuxGlobalStatementRepeat1 + = Auxiliary + symbolType Language.Python.Syntax.AuxArgumentListRepeat1 + = Auxiliary + symbolType Language.Python.Syntax.AuxDecoratedDefinitionRepeat1 + = Auxiliary + symbolType Language.Python.Syntax.AuxVariablesRepeat1 = Auxiliary + symbolType Language.Python.Syntax.AuxDottedNameRepeat1 = Auxiliary + symbolType Language.Python.Syntax.AuxComparisonOperatorRepeat1 + = Auxiliary + symbolType Language.Python.Syntax.AuxSubscriptRepeat1 = Auxiliary + symbolType Language.Python.Syntax.AuxDictionaryRepeat1 = Auxiliary + symbolType Language.Python.Syntax.AuxConcatenatedStringRepeat1 + = Auxiliary From aad7f36902836ef86e0f4286bd97c6dbe05d420a Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Tue, 30 May 2017 16:54:52 -0700 Subject: [PATCH 02/89] Assing simple member access --- src/Language/Python/Syntax.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 9fd4edf66..3e30d219a 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -32,6 +32,7 @@ type Syntax' = , Expression.Boolean , Expression.Bitwise , Expression.Call + , Expression.MemberAccess , Literal.Boolean , Literal.Float , Literal.Integer @@ -163,7 +164,7 @@ comment :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) expressionStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -expressionStatement = symbol ExpressionStatement *> children (statement <|> literal <|> expression) +expressionStatement = symbol ExpressionStatement *> children (statement <|> literal <|> expression <|> memberAccess) -- TODO Possibly match against children for dotted name and identifiers @@ -216,3 +217,6 @@ makeTerm a f = cofree (a :< inj f) emptyTerm :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) emptyTerm = makeTerm <$> location <*> pure Syntax.Empty + +memberAccess :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +memberAccess = makeTerm <$> symbol Attribute <*> children (expression >>= (\lhs -> (Expression.MemberAccess lhs) <$> identifier)) From 393c481f83f85a03b01b27b4a28397f942e72a40 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Tue, 30 May 2017 16:58:30 -0700 Subject: [PATCH 03/89] Expand If assignment --- src/Language/Python/Syntax.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 3e30d219a..4ceeae2b8 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -197,9 +197,9 @@ returnStatement = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> ifStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> condition <*> statement <*> (flip (foldr makeElif) <$> many elifClause <*> optionalElse)) +ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> expression <*> statement <*> (flip (foldr makeElif) <$> many elifClause <*> optionalElse)) where elseClause = symbol ElseClause *> children statement - elifClause = (,) <$ symbol ElifClause <*> location <*> children (Statement.If <$> condition <*> statement) + elifClause = (,) <$ symbol ElifClause <*> location <*> children (Statement.If <$> expression <*> statement) condition = boolean optionalElse = fromMaybe <$> emptyTerm <*> optional elseClause makeElif (loc, makeIf) rest = makeTerm loc (makeIf rest) From a842539c84fc1f04e7a9b562b62e13e817479cbf Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Tue, 30 May 2017 17:01:05 -0700 Subject: [PATCH 04/89] :fire: condition --- src/Language/Python/Syntax.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 4ceeae2b8..6496db0bd 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -200,7 +200,6 @@ ifStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> expression <*> statement <*> (flip (foldr makeElif) <$> many elifClause <*> optionalElse)) where elseClause = symbol ElseClause *> children statement elifClause = (,) <$ symbol ElifClause <*> location <*> children (Statement.If <$> expression <*> statement) - condition = boolean optionalElse = fromMaybe <$> emptyTerm <*> optional elseClause makeElif (loc, makeIf) rest = makeTerm loc (makeIf rest) From d5f0db7986d5ff6ceb537d0e0d30073a299f05db Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 10:49:14 -0700 Subject: [PATCH 05/89] Assign nested Attribute expressions --- src/Language/Python/Syntax.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 6496db0bd..7cf697311 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -80,7 +80,7 @@ tuple :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) tuple = makeTerm <$> symbol Tuple <*> children (Literal.Tuple <$> (many expression)) expression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -expression = statement <|> unaryOperator <|> binaryOperator <|> booleanOperator <|> tuple <|> literal +expression = statement <|> unaryOperator <|> binaryOperator <|> booleanOperator <|> tuple <|> literal <|> memberAccess -- TODO: Consider flattening single element lists expressionList :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) @@ -203,6 +203,10 @@ ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> exp optionalElse = fromMaybe <$> emptyTerm <*> optional elseClause makeElif (loc, makeIf) rest = makeTerm loc (makeIf rest) +memberAccess :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +memberAccess = makeTerm <$> symbol Attribute <*> children (Expression.MemberAccess <$> (flip (foldr makeMemberAccess) <$> many nestedAttribute <*> expression) <*> expression) + where makeMemberAccess (loc, makeRest) rest = makeTerm loc (makeRest rest) + nestedAttribute = (,) <$ symbol Attribute <*> location <*> children (Expression.MemberAccess <$> expression) boolean :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) boolean = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source) @@ -216,6 +220,3 @@ makeTerm a f = cofree (a :< inj f) emptyTerm :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) emptyTerm = makeTerm <$> location <*> pure Syntax.Empty - -memberAccess :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -memberAccess = makeTerm <$> symbol Attribute <*> children (expression >>= (\lhs -> (Expression.MemberAccess lhs) <$> identifier)) From b34aa617f057c5cfb9c3bee1c418ce8bfccc7e98 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 11:13:19 -0700 Subject: [PATCH 06/89] :memo: Member Access example --- src/Data/Syntax/Expression.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index acfb13815..59f62eca3 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -51,7 +51,7 @@ data Bitwise a instance Eq1 Bitwise where liftEq = genericLiftEq instance Show1 Bitwise where liftShowsPrec = genericLiftShowsPrec --- | Member Access +-- | Member Access (e.g. a.b) data MemberAccess a = MemberAccess a a deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) From 55b0ccdd8d7ac68fe197e1dd4e9ce25c305c01b5 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 11:13:46 -0700 Subject: [PATCH 07/89] Simplify expression statement --- src/Language/Python/Syntax.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 7cf697311..5ffa8cfec 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -79,6 +79,9 @@ statement = expressionStatement tuple :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) tuple = makeTerm <$> symbol Tuple <*> children (Literal.Tuple <$> (many expression)) +expressionStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +expressionStatement = symbol ExpressionStatement *> children expression + expression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) expression = statement <|> unaryOperator <|> binaryOperator <|> booleanOperator <|> tuple <|> literal <|> memberAccess @@ -163,8 +166,6 @@ integer = makeTerm <$> symbol Integer <*> (Literal.Integer <$> source) comment :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) -expressionStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -expressionStatement = symbol ExpressionStatement *> children (statement <|> literal <|> expression <|> memberAccess) -- TODO Possibly match against children for dotted name and identifiers From 375e1d6a017ac3d925a710e8172df8f68b3a13e0 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 11:14:03 -0700 Subject: [PATCH 08/89] Assign Subscript expressions --- src/Data/Syntax/Expression.hs | 9 +++++++++ src/Language/Python/Syntax.hs | 6 +++++- 2 files changed, 14 insertions(+), 1 deletion(-) diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index 59f62eca3..947122438 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -58,3 +58,12 @@ data MemberAccess a instance Eq1 MemberAccess where liftEq = genericLiftEq instance Show1 MemberAccess where liftShowsPrec = genericLiftShowsPrec + +-- | Subscript (e.g a[1]) +data Subscript a + = Subscript a [a] + deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) + +instance Eq1 Subscript where liftEq = genericLiftEq +instance Show1 Subscript where liftShowsPrec = genericLiftShowsPrec + diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 5ffa8cfec..0c0ccf461 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -33,6 +33,7 @@ type Syntax' = , Expression.Bitwise , Expression.Call , Expression.MemberAccess + , Expression.Subscript , Literal.Boolean , Literal.Float , Literal.Integer @@ -83,7 +84,7 @@ expressionStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Lo expressionStatement = symbol ExpressionStatement *> children expression expression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -expression = statement <|> unaryOperator <|> binaryOperator <|> booleanOperator <|> tuple <|> literal <|> memberAccess +expression = statement <|> unaryOperator <|> binaryOperator <|> booleanOperator <|> tuple <|> literal <|> memberAccess <|> subscript -- TODO: Consider flattening single element lists expressionList :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) @@ -209,6 +210,9 @@ memberAccess = makeTerm <$> symbol Attribute <*> children (Expression.MemberAcce where makeMemberAccess (loc, makeRest) rest = makeTerm loc (makeRest rest) nestedAttribute = (,) <$ symbol Attribute <*> location <*> children (Expression.MemberAccess <$> expression) +subscript :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +subscript = makeTerm <$> symbol Subscript <*> children (Expression.Subscript <$> expression <*> many expression) + boolean :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) boolean = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source) <|> makeTerm <$> symbol Grammar.False <*> (Literal.false <$ source) From 359e28d2dde562842b615534aad0f10531e95ecb Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 11:17:16 -0700 Subject: [PATCH 09/89] Flow alternative choices over multiple lines --- src/Language/Python/Syntax.hs | 17 +++++++++++------ 1 file changed, 11 insertions(+), 6 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 0c0ccf461..cfbc7bdb8 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -61,11 +61,9 @@ instance Show1 Redirect where liftShowsPrec = genericLiftShowsPrec assignment :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) assignment = makeTerm <$> symbol Module <*> children (many declaration) - declaration :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) declaration = comment <|> literal <|> statement <|> import' <|> importFrom - statement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) statement = expressionStatement <|> ifStatement @@ -77,14 +75,21 @@ statement = expressionStatement <|> assertStatement <|> globalStatement -tuple :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -tuple = makeTerm <$> symbol Tuple <*> children (Literal.Tuple <$> (many expression)) - expressionStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) expressionStatement = symbol ExpressionStatement *> children expression expression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -expression = statement <|> unaryOperator <|> binaryOperator <|> booleanOperator <|> tuple <|> literal <|> memberAccess <|> subscript +expression = statement + <|> unaryOperator + <|> binaryOperator + <|> booleanOperator + <|> tuple + <|> literal + <|> memberAccess + <|> subscript + +tuple :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +tuple = makeTerm <$> symbol Tuple <*> children (Literal.Tuple <$> (many expression)) -- TODO: Consider flattening single element lists expressionList :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) From 7297c1d8dddbbd5e51a4fe93ad34d02a2903b7ec Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 14:05:48 -0700 Subject: [PATCH 10/89] Assign Call expressions --- src/Language/Python/Syntax.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index cfbc7bdb8..681b29486 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -87,6 +87,7 @@ expression = statement <|> literal <|> memberAccess <|> subscript + <|> call tuple :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) tuple = makeTerm <$> symbol Tuple <*> children (Literal.Tuple <$> (many expression)) @@ -218,6 +219,9 @@ memberAccess = makeTerm <$> symbol Attribute <*> children (Expression.MemberAcce subscript :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) subscript = makeTerm <$> symbol Subscript <*> children (Expression.Subscript <$> expression <*> many expression) +call :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +call = makeTerm <$> symbol Call <*> children (Expression.Call <$> identifier <* symbol ArgumentList <*> children (many expression)) + boolean :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) boolean = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source) <|> makeTerm <$> symbol Grammar.False <*> (Literal.false <$ source) From 0754da600d354e61c1c7309cd02efe5554b539fb Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 14:06:02 -0700 Subject: [PATCH 11/89] Assing Lists --- src/Data/Syntax/Literal.hs | 2 +- src/Language/Python/Syntax.hs | 6 +++++- 2 files changed, 6 insertions(+), 2 deletions(-) diff --git a/src/Data/Syntax/Literal.hs b/src/Data/Syntax/Literal.hs index 03479b444..dc56e038f 100644 --- a/src/Data/Syntax/Literal.hs +++ b/src/Data/Syntax/Literal.hs @@ -97,7 +97,7 @@ instance Show1 Symbol where liftShowsPrec = genericLiftShowsPrec -- Collections -newtype Array a = Array { arrayElements :: [Union '[Identity, Comment] a] } +newtype Array a = Array { arrayElements :: [a] } deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Array where liftEq = genericLiftEq diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 681b29486..3ff3aef45 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -34,6 +34,7 @@ type Syntax' = , Expression.Call , Expression.MemberAccess , Expression.Subscript + , Literal.Array , Literal.Boolean , Literal.Float , Literal.Integer @@ -155,7 +156,10 @@ identifier :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier <$> source) literal :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -literal = string <|> integer <|> float <|> boolean <|> none <|> concatenatedString +literal = string <|> integer <|> float <|> boolean <|> none <|> concatenatedString <|> list' + +list' :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +list' = makeTerm <$> symbol List <*> children (Literal.Array <$> many expression) -- TODO: Wrap `Literal.TextElement` with a `Literal.String` string :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) From 54ef7af75dd1a97d0104000ac21157c9e02b9f46 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 14:15:05 -0700 Subject: [PATCH 12/89] Assign dictionary literals --- src/Data/Syntax/Literal.hs | 2 +- src/Language/Python/Syntax.hs | 8 +++++++- 2 files changed, 8 insertions(+), 2 deletions(-) diff --git a/src/Data/Syntax/Literal.hs b/src/Data/Syntax/Literal.hs index dc56e038f..dd1eb45f6 100644 --- a/src/Data/Syntax/Literal.hs +++ b/src/Data/Syntax/Literal.hs @@ -104,7 +104,7 @@ instance Eq1 Array where liftEq = genericLiftEq instance Show1 Array where liftShowsPrec = genericLiftShowsPrec -newtype Hash a = Hash { hashElements :: [Union '[KeyValue, Comment] a] } +newtype Hash a = Hash { hashElements :: [a] } deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Hash where liftEq = genericLiftEq diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 3ff3aef45..2a750c78f 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -37,7 +37,9 @@ type Syntax' = , Literal.Array , Literal.Boolean , Literal.Float + , Literal.Hash , Literal.Integer + , Literal.KeyValue , Literal.Null , Literal.String , Literal.TextElement @@ -156,7 +158,11 @@ identifier :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier <$> source) literal :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -literal = string <|> integer <|> float <|> boolean <|> none <|> concatenatedString <|> list' +literal = string <|> integer <|> float <|> boolean <|> none <|> concatenatedString <|> list' <|> dictionary + +dictionary :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +dictionary = makeTerm <$> symbol Dictionary <*> children (Literal.Hash <$> many pairs) + where pairs = makeTerm <$> symbol Pair <*> children (Literal.KeyValue <$> expression <*> expression) list' :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) list' = makeTerm <$> symbol List <*> children (Literal.Array <$> many expression) From 622a278e969efaebf004b14e8c57215ff8982abb Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 14:19:40 -0700 Subject: [PATCH 13/89] Ass sets --- src/Data/Syntax/Literal.hs | 9 ++++++++- src/Language/Python/Syntax.hs | 6 +++++- 2 files changed, 13 insertions(+), 2 deletions(-) diff --git a/src/Data/Syntax/Literal.hs b/src/Data/Syntax/Literal.hs index dd1eb45f6..629200739 100644 --- a/src/Data/Syntax/Literal.hs +++ b/src/Data/Syntax/Literal.hs @@ -7,7 +7,7 @@ import Data.Functor.Classes.Show.Generic import Data.Syntax.Comment import Data.Functor.Union import GHC.Generics -import Prologue +import Prologue hiding (Set) -- Boolean @@ -117,6 +117,7 @@ data KeyValue a = KeyValue { key :: !a, value :: !a } instance Eq1 KeyValue where liftEq = genericLiftEq instance Show1 KeyValue where liftShowsPrec = genericLiftShowsPrec + data Tuple a = Tuple { tupleContents :: ![a]} deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) @@ -126,3 +127,9 @@ instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec -- TODO: Object literals as distinct from hash literals? Or coalesce object/hash literals into “key-value literals”? -- TODO: Function literals (lambdas, procs, anonymous functions, what have you). -- TODO: Regexp literals. + +data Set a = Set { setElements :: [a] } + deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) + +instance Eq1 Set where liftEq = genericLiftEq +instance Show1 Set where liftShowsPrec = genericLiftShowsPrec diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 2a750c78f..3318ab4a2 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -41,6 +41,7 @@ type Syntax' = , Literal.Integer , Literal.KeyValue , Literal.Null + , Literal.Set , Literal.String , Literal.TextElement , Literal.Tuple @@ -158,7 +159,10 @@ identifier :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier <$> source) literal :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -literal = string <|> integer <|> float <|> boolean <|> none <|> concatenatedString <|> list' <|> dictionary +literal = string <|> integer <|> float <|> boolean <|> none <|> concatenatedString <|> list' <|> dictionary <|> set + +set :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +set = makeTerm <$> symbol Set <*> children (Literal.Set <$> many expression) dictionary :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) dictionary = makeTerm <$> symbol Dictionary <*> children (Literal.Hash <$> many pairs) From d93cc6eb3c857a3bb353e3e15667ccce385b49ae Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 14:23:00 -0700 Subject: [PATCH 14/89] Assign keyword identifiers --- src/Language/Python/Syntax.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 3318ab4a2..6acf23587 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -92,6 +92,10 @@ expression = statement <|> memberAccess <|> subscript <|> call + <|> keywordIdentifier + +keywordIdentifier :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +keywordIdentifier = makeTerm <$> symbol KeywordIdentifier <*> children (Syntax.Identifier <$> source) tuple :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) tuple = makeTerm <$> symbol Tuple <*> children (Literal.Tuple <$> (many expression)) From cbea157c48496e42f9bc32ce229e055da4d1f04b Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 14:29:42 -0700 Subject: [PATCH 15/89] Assing not operator --- src/Language/Python/Syntax.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 6acf23587..3879e7c5b 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -93,6 +93,10 @@ expression = statement <|> subscript <|> call <|> keywordIdentifier + <|> notOperator + +notOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +notOperator = makeTerm <$> symbol NotOperator <*> children (Expression.Not <$> expression) keywordIdentifier :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) keywordIdentifier = makeTerm <$> symbol KeywordIdentifier <*> children (Syntax.Identifier <$> source) From 7e8b3d5d51198f5751f358b266a889642b29d859 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 16:03:56 -0700 Subject: [PATCH 16/89] Assign comparison operator expressions --- src/Data/Syntax/Expression.hs | 19 ++++++++++++++++++- src/Language/Python/Syntax.hs | 16 ++++++++++++++++ 2 files changed, 34 insertions(+), 1 deletion(-) diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index 947122438..667623a60 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -14,6 +14,24 @@ data Call a = Call { callFunction :: a, callParams :: [a] } instance Eq1 Call where liftEq = genericLiftEq instance Show1 Call where liftShowsPrec = genericLiftShowsPrec + +data Comparison a + = LessThan a a + | LessThanEqual a a + | GreaterThan a a + | GreaterThanEqual a a + | Equal a a + | NotEqual a a + | In a a + | NotIn a a + | Is a a + | IsNot a a + deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) + +instance Eq1 Comparison where liftEq = genericLiftEq +instance Show1 Comparison where liftShowsPrec = genericLiftShowsPrec + + -- | Binary arithmetic operators. data Arithmetic a = Plus a a @@ -66,4 +84,3 @@ data Subscript a instance Eq1 Subscript where liftEq = genericLiftEq instance Show1 Subscript where liftShowsPrec = genericLiftShowsPrec - diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 3879e7c5b..6a3aac87a 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -32,6 +32,7 @@ type Syntax' = , Expression.Boolean , Expression.Bitwise , Expression.Call + , Expression.Comparison , Expression.MemberAccess , Expression.Subscript , Literal.Array @@ -87,6 +88,7 @@ expression = statement <|> unaryOperator <|> binaryOperator <|> booleanOperator + <|> comparisonOperator <|> tuple <|> literal <|> memberAccess @@ -95,6 +97,20 @@ expression = statement <|> keywordIdentifier <|> notOperator +comparisonOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +comparisonOperator = symbol ComparisonOperator >>= \ location -> children (expression >>= \ lexpression -> makeTerm location <$> makeComparison lexpression) + where + makeComparison lexpression = symbol AnonLAngle *> (Expression.LessThan lexpression <$> expression) + <|> symbol AnonLAngleEqual *> (Expression.LessThanEqual lexpression <$> expression) + <|> symbol AnonRAngle *> (Expression.GreaterThan lexpression <$> expression) + <|> symbol AnonRAngleEqual *> (Expression.GreaterThanEqual lexpression <$> expression) + <|> symbol AnonEqualEqual *> (Expression.Equal lexpression <$> expression) + <|> symbol AnonBangEqual *> (Expression.NotEqual lexpression <$> expression) + <|> symbol AnonIn *> (Expression.In lexpression <$> expression) + <|> symbol AnonNot *> (Expression.NotIn lexpression <$> expression) + <|> symbol AnonIs *> (Expression.Is lexpression <$> expression) + -- TODO Add AnonIsNot and AnonNotIn + notOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) notOperator = makeTerm <$> symbol NotOperator <*> children (Expression.Not <$> expression) From b86bad4b75f21ce6de993edc0bedf51996e0ecbd Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 16:15:49 -0700 Subject: [PATCH 17/89] Assign ellipsis --- src/Data/Syntax.hs | 8 ++++++++ src/Language/Python/Syntax.hs | 5 +++++ 2 files changed, 13 insertions(+) diff --git a/src/Data/Syntax.hs b/src/Data/Syntax.hs index 995e44d2f..8f158cea6 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -50,3 +50,11 @@ data Error error a = Error error instance Eq error => GAlign (Error error) instance Eq error => Eq1 (Error error) where liftEq = genericLiftEq instance Show error => Show1 (Error error) where liftShowsPrec = genericLiftShowsPrec + + +-- | Ellipsis +data Ellipsis a = Ellipsis ByteString + deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) + +instance Eq1 Ellipsis where liftEq = genericLiftEq +instance Show1 Ellipsis where liftShowsPrec = genericLiftShowsPrec diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 6a3aac87a..2905577bd 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -51,6 +51,7 @@ type Syntax' = , Statement.If , Statement.Return , Statement.Yield + , Syntax.Ellipsis , Syntax.Empty , Syntax.Identifier , [] @@ -96,6 +97,10 @@ expression = statement <|> call <|> keywordIdentifier <|> notOperator + <|> ellipsis + +ellipsis :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +ellipsis = makeTerm <$> symbol Ellipsis <*> (Syntax.Ellipsis <$> source) comparisonOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) comparisonOperator = symbol ComparisonOperator >>= \ location -> children (expression >>= \ lexpression -> makeTerm location <$> makeComparison lexpression) From 868051264c91603f85066cd2d20f5a2693585e01 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 16:44:54 -0700 Subject: [PATCH 18/89] Assign dotted name --- src/Data/Syntax/Expression.hs | 8 ++++++++ src/Language/Python/Syntax.hs | 9 +++++++-- 2 files changed, 15 insertions(+), 2 deletions(-) diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index 667623a60..6e3d9641a 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -84,3 +84,11 @@ data Subscript a instance Eq1 Subscript where liftEq = genericLiftEq instance Show1 Subscript where liftShowsPrec = genericLiftShowsPrec + +-- | Dotted Name (e.g. a.b in Python) +data DottedName a + = DottedName ![a] + deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) + +instance Eq1 DottedName where liftEq = genericLiftEq +instance Show1 DottedName where liftShowsPrec = genericLiftShowsPrec diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 2905577bd..5007f586b 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -33,6 +33,7 @@ type Syntax' = , Expression.Bitwise , Expression.Call , Expression.Comparison + , Expression.DottedName , Expression.MemberAccess , Expression.Subscript , Literal.Array @@ -98,6 +99,10 @@ expression = statement <|> keywordIdentifier <|> notOperator <|> ellipsis + <|> dottedName + +dottedName :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +dottedName = makeTerm <$> symbol DottedName <*> children (Expression.DottedName <$> many expression) ellipsis :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) ellipsis = makeTerm <$> symbol Ellipsis <*> (Syntax.Ellipsis <$> source) @@ -220,11 +225,11 @@ comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) -- TODO Possibly match against children for dotted name and identifiers import' :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -import' = makeTerm <$> symbol ImportStatement <*> (Declaration.Import <$> source) +import' = makeTerm <$> symbol ImportStatement <*> children (Declaration.Import <$> many expression) -- TODO Possibly match against children nodes importFrom :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -importFrom = makeTerm <$> symbol ImportFromStatement <*> (Declaration.Import <$> source) +importFrom = makeTerm <$> symbol ImportFromStatement <*> children (Declaration.Import <$> many expression) assertStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) assertStatement = makeTerm <$ symbol AssertStatement <*> location <*> children (Expression.Call <$> (makeTerm <$> symbol AnonAssert <*> (Syntax.Identifier <$> source)) <*> many expression) From abcba70d730fd484e7d5f95c8bd8085e06ba262f Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 16:45:20 -0700 Subject: [PATCH 19/89] Make expression constructor values strict --- src/Data/Syntax/Expression.hs | 56 +++++++++++++++++------------------ 1 file changed, 28 insertions(+), 28 deletions(-) diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index 6e3d9641a..c3e07f15c 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -8,7 +8,7 @@ import GHC.Generics import Prologue -- | Typical prefix function application, like `f(x)` in many languages, or `f x` in Haskell. -data Call a = Call { callFunction :: a, callParams :: [a] } +data Call a = Call { callFunction :: !a, callParams :: ![a] } deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Call where liftEq = genericLiftEq @@ -16,16 +16,16 @@ instance Show1 Call where liftShowsPrec = genericLiftShowsPrec data Comparison a - = LessThan a a - | LessThanEqual a a - | GreaterThan a a - | GreaterThanEqual a a - | Equal a a - | NotEqual a a - | In a a - | NotIn a a - | Is a a - | IsNot a a + = LessThan !a !a + | LessThanEqual !a !a + | GreaterThan !a !a + | GreaterThanEqual !a !a + | Equal !a !a + | NotEqual !a !a + | In !a !a + | NotIn !a !a + | Is !a !a + | IsNot !a !a deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Comparison where liftEq = genericLiftEq @@ -34,13 +34,13 @@ instance Show1 Comparison where liftShowsPrec = genericLiftShowsPrec -- | Binary arithmetic operators. data Arithmetic a - = Plus a a - | Minus a a - | Times a a - | DividedBy a a - | Modulo a a - | Power a a - | Negate a + = Plus !a !a + | Minus !a !a + | Times !a !a + | DividedBy !a !a + | Modulo !a !a + | Power !a !a + | Negate !a deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Arithmetic where liftEq = genericLiftEq @@ -48,9 +48,9 @@ instance Show1 Arithmetic where liftShowsPrec = genericLiftShowsPrec -- | Boolean operators. data Boolean a - = Or a a - | And a a - | Not a + = Or !a !a + | And !a !a + | Not !a deriving (Eq, Foldable, Functor, Generic1, Show, Traversable) instance Eq1 Boolean where liftEq = genericLiftEq @@ -58,11 +58,11 @@ instance Show1 Boolean where liftShowsPrec = genericLiftShowsPrec -- | Bitwise operators. data Bitwise a - = BOr a a - | BAnd a a - | BXOr a a - | LShift a a - | RShift a a + = BOr !a !a + | BAnd !a !a + | BXOr !a !a + | LShift !a !a + | RShift !a !a | Complement a deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) @@ -71,7 +71,7 @@ instance Show1 Bitwise where liftShowsPrec = genericLiftShowsPrec -- | Member Access (e.g. a.b) data MemberAccess a - = MemberAccess a a + = MemberAccess !a !a deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 MemberAccess where liftEq = genericLiftEq @@ -79,7 +79,7 @@ instance Show1 MemberAccess where liftShowsPrec = genericLiftShowsPrec -- | Subscript (e.g a[1]) data Subscript a - = Subscript a [a] + = Subscript !a ![a] deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Subscript where liftEq = genericLiftEq From aca71e9c78bd9287c5ff4c33615d06b465bc2a61 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 16:45:35 -0700 Subject: [PATCH 20/89] Make import values strict --- src/Data/Syntax/Declaration.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Syntax/Declaration.hs b/src/Data/Syntax/Declaration.hs index 65278fc43..dcf9ee427 100644 --- a/src/Data/Syntax/Declaration.hs +++ b/src/Data/Syntax/Declaration.hs @@ -56,7 +56,7 @@ instance Show1 Data.Syntax.Declaration.Constructor where liftShowsPrec = generic -- | Import declarations. -data Import a = Import { importContent :: ByteString } +data Import a = Import { importContent :: ![a] } deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Import where liftEq = genericLiftEq From 22bc0738a88af5bb8f2fe88071169952cfede5e8 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 16:45:46 -0700 Subject: [PATCH 21/89] Move comments --- src/Data/Syntax/Literal.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Data/Syntax/Literal.hs b/src/Data/Syntax/Literal.hs index 629200739..f76884249 100644 --- a/src/Data/Syntax/Literal.hs +++ b/src/Data/Syntax/Literal.hs @@ -45,7 +45,6 @@ instance Eq1 Data.Syntax.Literal.Float where liftEq = genericLiftEq instance Show1 Data.Syntax.Literal.Float where liftShowsPrec = genericLiftShowsPrec - data Range a = Range { rangeStart :: a, rangeEnd :: a } deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) @@ -124,12 +123,14 @@ data Tuple a = Tuple { tupleContents :: ![a]} instance Eq1 Tuple where liftEq = genericLiftEq instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec --- TODO: Object literals as distinct from hash literals? Or coalesce object/hash literals into “key-value literals”? --- TODO: Function literals (lambdas, procs, anonymous functions, what have you). --- TODO: Regexp literals. data Set a = Set { setElements :: [a] } deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Set where liftEq = genericLiftEq instance Show1 Set where liftShowsPrec = genericLiftShowsPrec + +-- TODO: Object literals as distinct from hash literals? Or coalesce object/hash literals into “key-value literals”? +-- TODO: Function literals (lambdas, procs, anonymous functions, what have you). +-- TODO: Regexp literals. + From 8d117b5769ff482cafc051b4129f9694025e817f Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 16:48:51 -0700 Subject: [PATCH 22/89] :fire: redundant import --- src/Data/Syntax/Literal.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Data/Syntax/Literal.hs b/src/Data/Syntax/Literal.hs index f76884249..00a9f055e 100644 --- a/src/Data/Syntax/Literal.hs +++ b/src/Data/Syntax/Literal.hs @@ -4,7 +4,6 @@ module Data.Syntax.Literal where import Data.Align.Generic import Data.Functor.Classes.Eq.Generic import Data.Functor.Classes.Show.Generic -import Data.Syntax.Comment import Data.Functor.Union import GHC.Generics import Prologue hiding (Set) From 092ea75681a54544b03a0c9771d65eefc8542a3b Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Wed, 31 May 2017 16:48:59 -0700 Subject: [PATCH 23/89] :fire: whitespace --- src/Language/Python/Syntax.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 5007f586b..e042d1a3c 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -221,8 +221,6 @@ integer = makeTerm <$> symbol Integer <*> (Literal.Integer <$> source) comment :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) - - -- TODO Possibly match against children for dotted name and identifiers import' :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) import' = makeTerm <$> symbol ImportStatement <*> children (Declaration.Import <$> many expression) From b0263ffc713ac6f29d560adb1fa906046d7f707a Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 10:27:50 -0700 Subject: [PATCH 24/89] Assign await statements --- src/Language/Python/Syntax.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index e042d1a3c..24c6969a4 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -100,6 +100,7 @@ expression = statement <|> notOperator <|> ellipsis <|> dottedName + <|> await dottedName :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) dottedName = makeTerm <$> symbol DottedName <*> children (Expression.DottedName <$> many expression) @@ -246,6 +247,9 @@ printStatement = do globalStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) globalStatement = makeTerm <$> symbol GlobalStatement <*> children (Expression.Call <$> (makeTerm <$> symbol AnonGlobal <*> (Syntax.Identifier <$> source)) <*> many identifier) +await :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +await = makeTerm <$> symbol Await <*> children (Expression.Call <$> (makeTerm <$> symbol AnonAwait <*> (Syntax.Identifier <$> source)) <*> many expression) + returnStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) returnStatement = makeTerm <$> symbol ReturnStatement <*> (Statement.Return <$> children expressionList) From 5792d92b8a796a01c949f8bd56301f079713b1b3 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 11:38:42 -0700 Subject: [PATCH 25/89] Rename DottedName -> ScopeResolution --- src/Data/Syntax/Expression.hs | 10 +++++----- src/Language/Python/Syntax.hs | 4 ++-- 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index c3e07f15c..5c980bf85 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -85,10 +85,10 @@ data Subscript a instance Eq1 Subscript where liftEq = genericLiftEq instance Show1 Subscript where liftShowsPrec = genericLiftShowsPrec --- | Dotted Name (e.g. a.b in Python) -data DottedName a - = DottedName ![a] +-- | ScopeResolution (e.g. import a.b in Python or a::b in C++) +data ScopeResolution a + = ScopeResolution ![a] deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) -instance Eq1 DottedName where liftEq = genericLiftEq -instance Show1 DottedName where liftShowsPrec = genericLiftShowsPrec +instance Eq1 ScopeResolution where liftEq = genericLiftEq +instance Show1 ScopeResolution where liftShowsPrec = genericLiftShowsPrec diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 24c6969a4..673f21b16 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -33,7 +33,7 @@ type Syntax' = , Expression.Bitwise , Expression.Call , Expression.Comparison - , Expression.DottedName + , Expression.ScopeResolution , Expression.MemberAccess , Expression.Subscript , Literal.Array @@ -103,7 +103,7 @@ expression = statement <|> await dottedName :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -dottedName = makeTerm <$> symbol DottedName <*> children (Expression.DottedName <$> many expression) +dottedName = makeTerm <$> symbol DottedName <*> children (Expression.ScopeResolution <$> many expression) ellipsis :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) ellipsis = makeTerm <$> symbol Ellipsis <*> (Syntax.Ellipsis <$> source) From ea6d5eba8868c8d2e483b6d89a483c1660a2cd0e Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 11:39:23 -0700 Subject: [PATCH 26/89] Assign is not comparison operator expressions --- src/Language/Python/Syntax.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 673f21b16..a8be7fdba 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -117,10 +117,10 @@ comparisonOperator = symbol ComparisonOperator >>= \ location -> children (expre <|> symbol AnonRAngleEqual *> (Expression.GreaterThanEqual lexpression <$> expression) <|> symbol AnonEqualEqual *> (Expression.Equal lexpression <$> expression) <|> symbol AnonBangEqual *> (Expression.NotEqual lexpression <$> expression) - <|> symbol AnonIn *> (Expression.In lexpression <$> expression) <|> symbol AnonNot *> (Expression.NotIn lexpression <$> expression) - <|> symbol AnonIs *> (Expression.Is lexpression <$> expression) - -- TODO Add AnonIsNot and AnonNotIn + <|> symbol AnonIn *> (Expression.In lexpression <$> expression) + <|> symbol AnonIs *> (Expression.IsNot lexpression <$ symbol AnonNot <*> expression + <|> Expression.Is lexpression <$> expression) notOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) notOperator = makeTerm <$> symbol NotOperator <*> children (Expression.Not <$> expression) From 33f71c839ba94bb1d25b3ab14d9d1a87cedbfb12 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 12:05:45 -0700 Subject: [PATCH 27/89] Assign lambda expressions --- src/Language/Python/Syntax.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index a8be7fdba..c99b776e2 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -26,6 +26,7 @@ import Term type Syntax = Union Syntax' type Syntax' = '[ Comment.Comment + , Declaration.Function , Declaration.Import , Declaration.Variable , Expression.Arithmetic @@ -101,6 +102,7 @@ expression = statement <|> ellipsis <|> dottedName <|> await + <|> lambda dottedName :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) dottedName = makeTerm <$> symbol DottedName <*> children (Expression.ScopeResolution <$> many expression) @@ -279,6 +281,9 @@ boolean = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source) none :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) none = makeTerm <$> symbol None <*> (Literal.Null <$ source) +lambda :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +lambda = makeTerm <$> symbol Lambda <*> children (Declaration.Function <$> (makeTerm <$> symbol AnonLambda <*> (Syntax.Identifier <$> source)) <*> many identifier <*> expression) + makeTerm :: HasCallStack => InUnion Syntax' f => a -> f (Term Syntax a) -> Term Syntax a makeTerm a f = cofree (a :< inj f) From 26f1e200c93decc2f22dd7180a28810acb15a32b Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 12:07:47 -0700 Subject: [PATCH 28/89] Revise lambda assignment --- src/Language/Python/Syntax.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index c99b776e2..c3d1e2e20 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -282,7 +282,10 @@ none :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) none = makeTerm <$> symbol None <*> (Literal.Null <$ source) lambda :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -lambda = makeTerm <$> symbol Lambda <*> children (Declaration.Function <$> (makeTerm <$> symbol AnonLambda <*> (Syntax.Identifier <$> source)) <*> many identifier <*> expression) +lambda = makeTerm <$> symbol Lambda <*> children (Declaration.Function <$> lambdaIdentifier <*> lambdaParameters <*> lambdaBody) + where lambdaIdentifier = makeTerm <$> symbol AnonLambda <*> (Syntax.Identifier <$> source) + lambdaParameters = many identifier + lambdaBody = expression makeTerm :: HasCallStack => InUnion Syntax' f => a -> f (Term Syntax a) -> Term Syntax a makeTerm a f = cofree (a :< inj f) From 0d7719432dfc84a0324c47101ba26e63ce0da9de Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 12:56:01 -0700 Subject: [PATCH 29/89] Add Comprehension declaration --- src/Data/Syntax/Declaration.hs | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/src/Data/Syntax/Declaration.hs b/src/Data/Syntax/Declaration.hs index dcf9ee427..a9eb2d742 100644 --- a/src/Data/Syntax/Declaration.hs +++ b/src/Data/Syntax/Declaration.hs @@ -55,6 +55,14 @@ instance Eq1 Data.Syntax.Declaration.Constructor where liftEq = genericLiftEq instance Show1 Data.Syntax.Declaration.Constructor where liftShowsPrec = genericLiftShowsPrec +-- | Comprehension (e.g. ((a for b in c) in Python) +data Comprehension a = Comprehension { result :: !a, intermediate :: ![a], base :: !a } + deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) + +instance Eq1 Comprehension where liftEq = genericLiftEq +instance Show1 Comprehension where liftShowsPrec = genericLiftShowsPrec + + -- | Import declarations. data Import a = Import { importContent :: ![a] } deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) From 4b64206feb1c2b6bafcddf08c56ce7c092ba8505 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 12:56:56 -0700 Subject: [PATCH 30/89] Assign generator expressions --- src/Language/Python/Syntax.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index c3d1e2e20..6e908c96b 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -26,6 +26,7 @@ import Term type Syntax = Union Syntax' type Syntax' = '[ Comment.Comment + , Declaration.Comprehension , Declaration.Function , Declaration.Import , Declaration.Variable @@ -103,6 +104,7 @@ expression = statement <|> dottedName <|> await <|> lambda + <|> generatorExpression dottedName :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) dottedName = makeTerm <$> symbol DottedName <*> children (Expression.ScopeResolution <$> many expression) @@ -287,6 +289,9 @@ lambda = makeTerm <$> symbol Lambda <*> children (Declaration.Function <$> lambd lambdaParameters = many identifier lambdaBody = expression +generatorExpression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +generatorExpression = makeTerm <$> symbol GeneratorExpression <*> children (Declaration.Comprehension <$> expression <* symbol AnonFor <* symbol Variables <*> children (many expression) <* symbol AnonIn <*> expression) + makeTerm :: HasCallStack => InUnion Syntax' f => a -> f (Term Syntax a) -> Term Syntax a makeTerm a f = cofree (a :< inj f) From 3f665e47d46ba34745e1d7f9c13ec1a53f543ee8 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 13:04:40 -0700 Subject: [PATCH 31/89] Assign generator expressions as a function call parameter --- src/Language/Python/Syntax.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 6e908c96b..e3d5fe4a7 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -274,7 +274,8 @@ subscript :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) subscript = makeTerm <$> symbol Subscript <*> children (Expression.Subscript <$> expression <*> many expression) call :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -call = makeTerm <$> symbol Call <*> children (Expression.Call <$> identifier <* symbol ArgumentList <*> children (many expression)) +call = makeTerm <$> symbol Call <*> children (Expression.Call <$> identifier <*> (many generatorExpression + <|> symbol ArgumentList *> children (many expression))) boolean :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) boolean = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source) From e793effa9da8c2b582c8c24cafb678c583f19cca Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 14:15:04 -0700 Subject: [PATCH 32/89] Assign arbitrarily nested generator expressions --- src/Language/Python/Syntax.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index e3d5fe4a7..5e4602b38 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -291,7 +291,9 @@ lambda = makeTerm <$> symbol Lambda <*> children (Declaration.Function <$> lambd lambdaBody = expression generatorExpression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -generatorExpression = makeTerm <$> symbol GeneratorExpression <*> children (Declaration.Comprehension <$> expression <* symbol AnonFor <* symbol Variables <*> children (many expression) <* symbol AnonIn <*> expression) +generatorExpression = makeTerm <$> symbol GeneratorExpression <*> children (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression) <*> (flip (foldr makeGeneratorExpression) <$> many nestedGeneratorExpression <*> expression)) + where makeGeneratorExpression (loc, makeRest) rest = makeTerm loc (makeRest rest) + nestedGeneratorExpression = (,) <$> location <*> (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression)) makeTerm :: HasCallStack => InUnion Syntax' f => a -> f (Term Syntax a) -> Term Syntax a makeTerm a f = cofree (a :< inj f) From 0423559efc39d1ee85663999b411427fa333b507 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 14:18:36 -0700 Subject: [PATCH 33/89] Simplify memberAccess assignment --- src/Language/Python/Syntax.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 5e4602b38..5fe6b4ffb 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -266,9 +266,7 @@ ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> exp makeElif (loc, makeIf) rest = makeTerm loc (makeIf rest) memberAccess :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -memberAccess = makeTerm <$> symbol Attribute <*> children (Expression.MemberAccess <$> (flip (foldr makeMemberAccess) <$> many nestedAttribute <*> expression) <*> expression) - where makeMemberAccess (loc, makeRest) rest = makeTerm loc (makeRest rest) - nestedAttribute = (,) <$ symbol Attribute <*> location <*> children (Expression.MemberAccess <$> expression) +memberAccess = makeTerm <$> symbol Attribute <*> children (Expression.MemberAccess <$> expression <*> expression) subscript :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) subscript = makeTerm <$> symbol Subscript <*> children (Expression.Subscript <$> expression <*> many expression) From 44ab33ee29147cf420c5103a2282e4b8526746bd Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 14:27:21 -0700 Subject: [PATCH 34/89] Assign list comprehensions --- src/Language/Python/Syntax.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 5fe6b4ffb..1449ab742 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -105,6 +105,7 @@ expression = statement <|> await <|> lambda <|> generatorExpression + <|> listComprehension dottedName :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) dottedName = makeTerm <$> symbol DottedName <*> children (Expression.ScopeResolution <$> many expression) @@ -293,6 +294,11 @@ generatorExpression = makeTerm <$> symbol GeneratorExpression <*> children (Decl where makeGeneratorExpression (loc, makeRest) rest = makeTerm loc (makeRest rest) nestedGeneratorExpression = (,) <$> location <*> (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression)) +listComprehension :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +listComprehension = makeTerm <$> symbol ListComprehension <*> children (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression) <*> (flip (foldr makeListComprehension) <$> many nestedListComprehension <*> expression)) + where makeListComprehension (loc, makeRest) rest = makeTerm loc (makeRest rest) + nestedListComprehension = (,) <$> location <*> (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression)) + makeTerm :: HasCallStack => InUnion Syntax' f => a -> f (Term Syntax a) -> Term Syntax a makeTerm a f = cofree (a :< inj f) From 3a37e1e8fdb2dd54115a406844ef2df230dfafb4 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 15:40:06 -0700 Subject: [PATCH 35/89] Assign Set comprehension; condense comprehension assignments to a single assignment --- src/Language/Python/Syntax.hs | 21 ++++++++++----------- 1 file changed, 10 insertions(+), 11 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 1449ab742..5182c02b6 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -104,8 +104,7 @@ expression = statement <|> dottedName <|> await <|> lambda - <|> generatorExpression - <|> listComprehension + <|> comprehension dottedName :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) dottedName = makeTerm <$> symbol DottedName <*> children (Expression.ScopeResolution <$> many expression) @@ -289,15 +288,15 @@ lambda = makeTerm <$> symbol Lambda <*> children (Declaration.Function <$> lambd lambdaParameters = many identifier lambdaBody = expression -generatorExpression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -generatorExpression = makeTerm <$> symbol GeneratorExpression <*> children (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression) <*> (flip (foldr makeGeneratorExpression) <$> many nestedGeneratorExpression <*> expression)) - where makeGeneratorExpression (loc, makeRest) rest = makeTerm loc (makeRest rest) - nestedGeneratorExpression = (,) <$> location <*> (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression)) - -listComprehension :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -listComprehension = makeTerm <$> symbol ListComprehension <*> children (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression) <*> (flip (foldr makeListComprehension) <$> many nestedListComprehension <*> expression)) - where makeListComprehension (loc, makeRest) rest = makeTerm loc (makeRest rest) - nestedListComprehension = (,) <$> location <*> (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression)) +comprehension :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +comprehension = makeTerm <$> symbol GeneratorExpression <*> children (comprehensionSyntax constructor expression) + <|> makeTerm <$> symbol ListComprehension <*> children (comprehensionSyntax constructor expression) + <|> makeTerm <$> symbol SetComprehension <*> children (comprehensionSyntax constructor expression) + where + constructor = Declaration.Comprehension + comprehensionSyntax constructor preceeding = constructor <$> preceeding <* symbol Variables <*> children (many expression) <*> (flip (foldr makeComprehension) <$> many nestedComprehension <*> expression) + makeComprehension (loc, makeRest) rest = makeTerm loc (makeRest rest) + nestedComprehension = (,) <$> location <*> (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression)) makeTerm :: HasCallStack => InUnion Syntax' f => a -> f (Term Syntax a) -> Term Syntax a makeTerm a f = cofree (a :< inj f) From 897c76c6b22941c237ece3279ed2068a33d4d385 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 15:40:32 -0700 Subject: [PATCH 36/89] Relax call assignment to include comprehension rather than generatorExpression assignment --- src/Language/Python/Syntax.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 5182c02b6..a9d9f276e 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -272,7 +272,7 @@ subscript :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) subscript = makeTerm <$> symbol Subscript <*> children (Expression.Subscript <$> expression <*> many expression) call :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -call = makeTerm <$> symbol Call <*> children (Expression.Call <$> identifier <*> (many generatorExpression +call = makeTerm <$> symbol Call <*> children (Expression.Call <$> identifier <*> (many comprehension <|> symbol ArgumentList *> children (many expression))) boolean :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) From 93f78e504a8983465cc7cfcfff40af6e1999e0ce Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 15:40:43 -0700 Subject: [PATCH 37/89] Assign dictionary comprehension --- src/Language/Python/Syntax.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index a9d9f276e..cdd59a871 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -292,8 +292,10 @@ comprehension :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location comprehension = makeTerm <$> symbol GeneratorExpression <*> children (comprehensionSyntax constructor expression) <|> makeTerm <$> symbol ListComprehension <*> children (comprehensionSyntax constructor expression) <|> makeTerm <$> symbol SetComprehension <*> children (comprehensionSyntax constructor expression) + <|> makeTerm <$> symbol DictionaryComprehension <*> children (comprehensionSyntax constructor keyValue) where constructor = Declaration.Comprehension + keyValue = makeTerm <$> location <*> (Literal.KeyValue <$> expression <*> expression) comprehensionSyntax constructor preceeding = constructor <$> preceeding <* symbol Variables <*> children (many expression) <*> (flip (foldr makeComprehension) <$> many nestedComprehension <*> expression) makeComprehension (loc, makeRest) rest = makeTerm loc (makeRest rest) nestedComprehension = (,) <$> location <*> (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression)) From 0ffd452efdf72d61a6de2bc3d5c89258f1f3b85d Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Thu, 1 Jun 2017 19:44:27 -0700 Subject: [PATCH 38/89] :fire: symbols.txt --- symbols.txt | 413 ---------------------------------------------------- 1 file changed, 413 deletions(-) delete mode 100644 symbols.txt diff --git a/symbols.txt b/symbols.txt deleted file mode 100644 index e51d3f7e5..000000000 --- a/symbols.txt +++ /dev/null @@ -1,413 +0,0 @@ -src/Language/Python/Syntax.hs:17:1-54: Splicing declarations - mkSymbolDatatype (mkName "Grammar") tree_sitter_python - ======> - data Grammar - = END | - HiddenNewline | - HiddenIndent | - HiddenDedent | - AnonPrint | - AnonExec | - AnonImport | - AnonFrom | - AnonDot | - AnonLParen | - AnonRParen | - AnonComma | - AnonAs | - AnonStar | - AnonRAngleRAngle | - AnonAssert | - AnonReturn | - AnonDel | - AnonRaise | - PassStatement | - BreakStatement | - ContinueStatement | - AnonIf | - AnonColon | - AnonElif | - AnonElse | - AnonFor | - AnonIn | - AnonWhile | - AnonTry | - AnonExcept | - AnonFinally | - AnonWith | - AnonAsync | - AnonDef | - AnonMinusRAngle | - AnonEqual | - AnonGlobal | - AnonNonlocal | - AnonClass | - AnonAt | - AnonNot | - AnonAnd | - AnonOr | - AnonPlus | - AnonMinus | - AnonSlash | - AnonPercent | - AnonSlashSlash | - AnonStarStar | - AnonPipe | - AnonAmpersand | - AnonCaret | - AnonLAngleLAngle | - AnonTilde | - AnonLAngle | - AnonLAngleEqual | - AnonEqualEqual | - AnonBangEqual | - AnonRAngleEqual | - AnonRAngle | - AnonLAngleRAngle | - AnonIs | - AnonLambda | - AnonPlusEqual | - AnonMinusEqual | - AnonStarEqual | - AnonSlashEqual | - AnonSlashSlashEqual | - AnonPercentEqual | - AnonStarStarEqual | - AnonRAngleRAngleEqual | - AnonLAngleLAngleEqual | - AnonAmpersandEqual | - AnonCaretEqual | - AnonPipeEqual | - AnonYield | - AnonLBracket | - AnonRBracket | - Ellipsis | - AnonLBrace | - AnonRBrace | - String | - Integer | - Float | - Identifier | - True | - False | - None | - AnonAwait | - Comment | - HiddenSemicolon | - Module | - HiddenStatement | - HiddenSimpleStatement | - KeywordIdentifier | - ImportStatement | - ImportFromStatement | - HiddenImportList | - AliasedImport | - WildcardImport | - PrintStatement | - Chevron | - AssertStatement | - ExpressionStatement | - ReturnStatement | - DeleteStatement | - RaiseStatement | - HiddenCompoundStatement | - IfStatement | - ElifClause | - ElseClause | - ForStatement | - WhileStatement | - TryStatement | - ExceptClause | - FinallyClause | - WithStatement | - WithItem | - AsyncFunctionDefinition | - FunctionDefinition | - HiddenFunctionDefinition | - Parameters | - HiddenParameters | - DefaultParameter | - TypedDefaultParameter | - ListSplatParameter | - DictionarySplatParameter | - GlobalStatement | - NonlocalStatement | - ExecStatement | - ClassDefinition | - ArgumentList | - DecoratedDefinition | - Decorator | - HiddenSuite | - Variables | - ExpressionList | - DottedName | - HiddenExpression | - HiddenPrimaryExpression | - NotOperator | - BooleanOperator | - BinaryOperator | - UnaryOperator | - ComparisonOperator | - Lambda | - Assignment | - AugmentedAssignment | - HiddenRightHandSide | - Yield | - Attribute | - Subscript | - Slice | - Call | - TypedParameter | - Type | - KeywordArgument | - ListSplatArgument | - DictionarySplatArgument | - List | - ListComprehension | - HiddenListComprehension | - Dictionary | - DictionaryComprehension | - Pair | - HiddenDictionaryComprehension | - Set | - SetComprehension | - HiddenSetComprehension | - Tuple | - GeneratorExpression | - HiddenGeneratorExpression | - ConditionalExpression | - ConcatenatedString | - Await | - AuxModuleRepeat1 | - AuxHiddenStatementRepeat1 | - AuxHiddenStatementRepeat2 | - AuxImportFromStatementRepeat1 | - AuxHiddenImportListRepeat1 | - AuxPrintStatementRepeat1 | - AuxIfStatementRepeat1 | - AuxTryStatementRepeat1 | - AuxWithStatementRepeat1 | - AuxHiddenParametersRepeat1 | - AuxGlobalStatementRepeat1 | - AuxArgumentListRepeat1 | - AuxDecoratedDefinitionRepeat1 | - AuxVariablesRepeat1 | - AuxDottedNameRepeat1 | - AuxComparisonOperatorRepeat1 | - AuxSubscriptRepeat1 | - AuxDictionaryRepeat1 | - AuxConcatenatedStringRepeat1 - deriving (Show, Eq, Enum, Ord) - instance Symbol Grammar where - symbolType Language.Python.Syntax.END = Regular - symbolType Language.Python.Syntax.HiddenNewline = Regular - symbolType Language.Python.Syntax.HiddenIndent = Regular - symbolType Language.Python.Syntax.HiddenDedent = Regular - symbolType Language.Python.Syntax.AnonPrint = Anonymous - symbolType Language.Python.Syntax.AnonExec = Anonymous - symbolType Language.Python.Syntax.AnonImport = Anonymous - symbolType Language.Python.Syntax.AnonFrom = Anonymous - symbolType Language.Python.Syntax.AnonDot = Anonymous - symbolType Language.Python.Syntax.AnonLParen = Anonymous - symbolType Language.Python.Syntax.AnonRParen = Anonymous - symbolType Language.Python.Syntax.AnonComma = Anonymous - symbolType Language.Python.Syntax.AnonAs = Anonymous - symbolType Language.Python.Syntax.AnonStar = Anonymous - symbolType Language.Python.Syntax.AnonRAngleRAngle = Anonymous - symbolType Language.Python.Syntax.AnonAssert = Anonymous - symbolType Language.Python.Syntax.AnonReturn = Anonymous - symbolType Language.Python.Syntax.AnonDel = Anonymous - symbolType Language.Python.Syntax.AnonRaise = Anonymous - symbolType Language.Python.Syntax.PassStatement = Regular - symbolType Language.Python.Syntax.BreakStatement = Regular - symbolType Language.Python.Syntax.ContinueStatement = Regular - symbolType Language.Python.Syntax.AnonIf = Anonymous - symbolType Language.Python.Syntax.AnonColon = Anonymous - symbolType Language.Python.Syntax.AnonElif = Anonymous - symbolType Language.Python.Syntax.AnonElse = Anonymous - symbolType Language.Python.Syntax.AnonFor = Anonymous - symbolType Language.Python.Syntax.AnonIn = Anonymous - symbolType Language.Python.Syntax.AnonWhile = Anonymous - symbolType Language.Python.Syntax.AnonTry = Anonymous - symbolType Language.Python.Syntax.AnonExcept = Anonymous - symbolType Language.Python.Syntax.AnonFinally = Anonymous - symbolType Language.Python.Syntax.AnonWith = Anonymous - symbolType Language.Python.Syntax.AnonAsync = Anonymous - symbolType Language.Python.Syntax.AnonDef = Anonymous - symbolType Language.Python.Syntax.AnonMinusRAngle = Anonymous - symbolType Language.Python.Syntax.AnonEqual = Anonymous - symbolType Language.Python.Syntax.AnonGlobal = Anonymous - symbolType Language.Python.Syntax.AnonNonlocal = Anonymous - symbolType Language.Python.Syntax.AnonClass = Anonymous - symbolType Language.Python.Syntax.AnonAt = Anonymous - symbolType Language.Python.Syntax.AnonNot = Anonymous - symbolType Language.Python.Syntax.AnonAnd = Anonymous - symbolType Language.Python.Syntax.AnonOr = Anonymous - symbolType Language.Python.Syntax.AnonPlus = Anonymous - symbolType Language.Python.Syntax.AnonMinus = Anonymous - symbolType Language.Python.Syntax.AnonSlash = Anonymous - symbolType Language.Python.Syntax.AnonPercent = Anonymous - symbolType Language.Python.Syntax.AnonSlashSlash = Anonymous - symbolType Language.Python.Syntax.AnonStarStar = Anonymous - symbolType Language.Python.Syntax.AnonPipe = Anonymous - symbolType Language.Python.Syntax.AnonAmpersand = Anonymous - symbolType Language.Python.Syntax.AnonCaret = Anonymous - symbolType Language.Python.Syntax.AnonLAngleLAngle = Anonymous - symbolType Language.Python.Syntax.AnonTilde = Anonymous - symbolType Language.Python.Syntax.AnonLAngle = Anonymous - symbolType Language.Python.Syntax.AnonLAngleEqual = Anonymous - symbolType Language.Python.Syntax.AnonEqualEqual = Anonymous - symbolType Language.Python.Syntax.AnonBangEqual = Anonymous - symbolType Language.Python.Syntax.AnonRAngleEqual = Anonymous - symbolType Language.Python.Syntax.AnonRAngle = Anonymous - symbolType Language.Python.Syntax.AnonLAngleRAngle = Anonymous - symbolType Language.Python.Syntax.AnonIs = Anonymous - symbolType Language.Python.Syntax.AnonLambda = Anonymous - symbolType Language.Python.Syntax.AnonPlusEqual = Anonymous - symbolType Language.Python.Syntax.AnonMinusEqual = Anonymous - symbolType Language.Python.Syntax.AnonStarEqual = Anonymous - symbolType Language.Python.Syntax.AnonSlashEqual = Anonymous - symbolType Language.Python.Syntax.AnonSlashSlashEqual = Anonymous - symbolType Language.Python.Syntax.AnonPercentEqual = Anonymous - symbolType Language.Python.Syntax.AnonStarStarEqual = Anonymous - symbolType Language.Python.Syntax.AnonRAngleRAngleEqual = Anonymous - symbolType Language.Python.Syntax.AnonLAngleLAngleEqual = Anonymous - symbolType Language.Python.Syntax.AnonAmpersandEqual = Anonymous - symbolType Language.Python.Syntax.AnonCaretEqual = Anonymous - symbolType Language.Python.Syntax.AnonPipeEqual = Anonymous - symbolType Language.Python.Syntax.AnonYield = Anonymous - symbolType Language.Python.Syntax.AnonLBracket = Anonymous - symbolType Language.Python.Syntax.AnonRBracket = Anonymous - symbolType Language.Python.Syntax.Ellipsis = Regular - symbolType Language.Python.Syntax.AnonLBrace = Anonymous - symbolType Language.Python.Syntax.AnonRBrace = Anonymous - symbolType Language.Python.Syntax.String = Regular - symbolType Language.Python.Syntax.Integer = Regular - symbolType Language.Python.Syntax.Float = Regular - symbolType Language.Python.Syntax.Identifier = Regular - symbolType Language.Python.Syntax.True = Regular - symbolType Language.Python.Syntax.False = Regular - symbolType Language.Python.Syntax.None = Regular - symbolType Language.Python.Syntax.AnonAwait = Anonymous - symbolType Language.Python.Syntax.Comment = Regular - symbolType Language.Python.Syntax.HiddenSemicolon = Regular - symbolType Language.Python.Syntax.Module = Regular - symbolType Language.Python.Syntax.HiddenStatement = Regular - symbolType Language.Python.Syntax.HiddenSimpleStatement = Regular - symbolType Language.Python.Syntax.KeywordIdentifier = Regular - symbolType Language.Python.Syntax.ImportStatement = Regular - symbolType Language.Python.Syntax.ImportFromStatement = Regular - symbolType Language.Python.Syntax.HiddenImportList = Regular - symbolType Language.Python.Syntax.AliasedImport = Regular - symbolType Language.Python.Syntax.WildcardImport = Regular - symbolType Language.Python.Syntax.PrintStatement = Regular - symbolType Language.Python.Syntax.Chevron = Regular - symbolType Language.Python.Syntax.AssertStatement = Regular - symbolType Language.Python.Syntax.ExpressionStatement = Regular - symbolType Language.Python.Syntax.ReturnStatement = Regular - symbolType Language.Python.Syntax.DeleteStatement = Regular - symbolType Language.Python.Syntax.RaiseStatement = Regular - symbolType Language.Python.Syntax.HiddenCompoundStatement = Regular - symbolType Language.Python.Syntax.IfStatement = Regular - symbolType Language.Python.Syntax.ElifClause = Regular - symbolType Language.Python.Syntax.ElseClause = Regular - symbolType Language.Python.Syntax.ForStatement = Regular - symbolType Language.Python.Syntax.WhileStatement = Regular - symbolType Language.Python.Syntax.TryStatement = Regular - symbolType Language.Python.Syntax.ExceptClause = Regular - symbolType Language.Python.Syntax.FinallyClause = Regular - symbolType Language.Python.Syntax.WithStatement = Regular - symbolType Language.Python.Syntax.WithItem = Regular - symbolType Language.Python.Syntax.AsyncFunctionDefinition = Regular - symbolType Language.Python.Syntax.FunctionDefinition = Regular - symbolType Language.Python.Syntax.HiddenFunctionDefinition - = Regular - symbolType Language.Python.Syntax.Parameters = Regular - symbolType Language.Python.Syntax.HiddenParameters = Regular - symbolType Language.Python.Syntax.DefaultParameter = Regular - symbolType Language.Python.Syntax.TypedDefaultParameter = Regular - symbolType Language.Python.Syntax.ListSplatParameter = Regular - symbolType Language.Python.Syntax.DictionarySplatParameter - = Regular - symbolType Language.Python.Syntax.GlobalStatement = Regular - symbolType Language.Python.Syntax.NonlocalStatement = Regular - symbolType Language.Python.Syntax.ExecStatement = Regular - symbolType Language.Python.Syntax.ClassDefinition = Regular - symbolType Language.Python.Syntax.ArgumentList = Regular - symbolType Language.Python.Syntax.DecoratedDefinition = Regular - symbolType Language.Python.Syntax.Decorator = Regular - symbolType Language.Python.Syntax.HiddenSuite = Regular - symbolType Language.Python.Syntax.Variables = Regular - symbolType Language.Python.Syntax.ExpressionList = Regular - symbolType Language.Python.Syntax.DottedName = Regular - symbolType Language.Python.Syntax.HiddenExpression = Regular - symbolType Language.Python.Syntax.HiddenPrimaryExpression = Regular - symbolType Language.Python.Syntax.NotOperator = Regular - symbolType Language.Python.Syntax.BooleanOperator = Regular - symbolType Language.Python.Syntax.BinaryOperator = Regular - symbolType Language.Python.Syntax.UnaryOperator = Regular - symbolType Language.Python.Syntax.ComparisonOperator = Regular - symbolType Language.Python.Syntax.Lambda = Regular - symbolType Language.Python.Syntax.Assignment = Regular - symbolType Language.Python.Syntax.AugmentedAssignment = Regular - symbolType Language.Python.Syntax.HiddenRightHandSide = Regular - symbolType Language.Python.Syntax.Yield = Regular - symbolType Language.Python.Syntax.Attribute = Regular - symbolType Language.Python.Syntax.Subscript = Regular - symbolType Language.Python.Syntax.Slice = Regular - symbolType Language.Python.Syntax.Call = Regular - symbolType Language.Python.Syntax.TypedParameter = Regular - symbolType Language.Python.Syntax.Type = Regular - symbolType Language.Python.Syntax.KeywordArgument = Regular - symbolType Language.Python.Syntax.ListSplatArgument = Regular - symbolType Language.Python.Syntax.DictionarySplatArgument = Regular - symbolType Language.Python.Syntax.List = Regular - symbolType Language.Python.Syntax.ListComprehension = Regular - symbolType Language.Python.Syntax.HiddenListComprehension = Regular - symbolType Language.Python.Syntax.Dictionary = Regular - symbolType Language.Python.Syntax.DictionaryComprehension = Regular - symbolType Language.Python.Syntax.Pair = Regular - symbolType Language.Python.Syntax.HiddenDictionaryComprehension - = Regular - symbolType Language.Python.Syntax.Set = Regular - symbolType Language.Python.Syntax.SetComprehension = Regular - symbolType Language.Python.Syntax.HiddenSetComprehension = Regular - symbolType Language.Python.Syntax.Tuple = Regular - symbolType Language.Python.Syntax.GeneratorExpression = Regular - symbolType Language.Python.Syntax.HiddenGeneratorExpression - = Regular - symbolType Language.Python.Syntax.ConditionalExpression = Regular - symbolType Language.Python.Syntax.ConcatenatedString = Regular - symbolType Language.Python.Syntax.Await = Regular - symbolType Language.Python.Syntax.AuxModuleRepeat1 = Auxiliary - symbolType Language.Python.Syntax.AuxHiddenStatementRepeat1 - = Auxiliary - symbolType Language.Python.Syntax.AuxHiddenStatementRepeat2 - = Auxiliary - symbolType Language.Python.Syntax.AuxImportFromStatementRepeat1 - = Auxiliary - symbolType Language.Python.Syntax.AuxHiddenImportListRepeat1 - = Auxiliary - symbolType Language.Python.Syntax.AuxPrintStatementRepeat1 - = Auxiliary - symbolType Language.Python.Syntax.AuxIfStatementRepeat1 = Auxiliary - symbolType Language.Python.Syntax.AuxTryStatementRepeat1 - = Auxiliary - symbolType Language.Python.Syntax.AuxWithStatementRepeat1 - = Auxiliary - symbolType Language.Python.Syntax.AuxHiddenParametersRepeat1 - = Auxiliary - symbolType Language.Python.Syntax.AuxGlobalStatementRepeat1 - = Auxiliary - symbolType Language.Python.Syntax.AuxArgumentListRepeat1 - = Auxiliary - symbolType Language.Python.Syntax.AuxDecoratedDefinitionRepeat1 - = Auxiliary - symbolType Language.Python.Syntax.AuxVariablesRepeat1 = Auxiliary - symbolType Language.Python.Syntax.AuxDottedNameRepeat1 = Auxiliary - symbolType Language.Python.Syntax.AuxComparisonOperatorRepeat1 - = Auxiliary - symbolType Language.Python.Syntax.AuxSubscriptRepeat1 = Auxiliary - symbolType Language.Python.Syntax.AuxDictionaryRepeat1 = Auxiliary - symbolType Language.Python.Syntax.AuxConcatenatedStringRepeat1 - = Auxiliary From c83a8c2c9c83e86d45ffc7f761e3ca4bae5fbf1b Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Fri, 2 Jun 2017 10:26:18 -0700 Subject: [PATCH 39/89] :fire: constructor parameter --- src/Language/Python/Syntax.hs | 11 +++++------ 1 file changed, 5 insertions(+), 6 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index cdd59a871..89148871a 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -289,14 +289,13 @@ lambda = makeTerm <$> symbol Lambda <*> children (Declaration.Function <$> lambd lambdaBody = expression comprehension :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -comprehension = makeTerm <$> symbol GeneratorExpression <*> children (comprehensionSyntax constructor expression) - <|> makeTerm <$> symbol ListComprehension <*> children (comprehensionSyntax constructor expression) - <|> makeTerm <$> symbol SetComprehension <*> children (comprehensionSyntax constructor expression) - <|> makeTerm <$> symbol DictionaryComprehension <*> children (comprehensionSyntax constructor keyValue) +comprehension = makeTerm <$> symbol GeneratorExpression <*> children (comprehensionDeclaration expression) + <|> makeTerm <$> symbol ListComprehension <*> children (comprehensionDeclaration expression) + <|> makeTerm <$> symbol SetComprehension <*> children (comprehensionDeclaration expression) + <|> makeTerm <$> symbol DictionaryComprehension <*> children (comprehensionDeclaration keyValue) where - constructor = Declaration.Comprehension keyValue = makeTerm <$> location <*> (Literal.KeyValue <$> expression <*> expression) - comprehensionSyntax constructor preceeding = constructor <$> preceeding <* symbol Variables <*> children (many expression) <*> (flip (foldr makeComprehension) <$> many nestedComprehension <*> expression) + comprehensionDeclaration preceeding = Declaration.Comprehension <$> preceeding <* symbol Variables <*> children (many expression) <*> (flip (foldr makeComprehension) <$> many nestedComprehension <*> expression) makeComprehension (loc, makeRest) rest = makeTerm loc (makeRest rest) nestedComprehension = (,) <$> location <*> (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression)) From 74ab219a0e0848725760465a1a68576cc8d3e427 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Fri, 2 Jun 2017 12:10:54 -0700 Subject: [PATCH 40/89] Move uncommited choice to last position in <|> for call --- src/Language/Python/Syntax.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 89148871a..1e342adc7 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -272,8 +272,8 @@ subscript :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) subscript = makeTerm <$> symbol Subscript <*> children (Expression.Subscript <$> expression <*> many expression) call :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -call = makeTerm <$> symbol Call <*> children (Expression.Call <$> identifier <*> (many comprehension - <|> symbol ArgumentList *> children (many expression))) +call = makeTerm <$> symbol Call <*> children (Expression.Call <$> identifier <*> (symbol ArgumentList *> children (many expression) + <|> some comprehension)) boolean :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) boolean = makeTerm <$> symbol Grammar.True <*> (Literal.true <$ source) From a3e53c872cfabf685680800bc0d7d95c2b780b2e Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Fri, 2 Jun 2017 12:11:54 -0700 Subject: [PATCH 41/89] Assign call conditional expressions --- src/Language/Python/Syntax.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 1e342adc7..63f0c1a4a 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -105,6 +105,7 @@ expression = statement <|> await <|> lambda <|> comprehension + <|> conditionalExpression dottedName :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) dottedName = makeTerm <$> symbol DottedName <*> children (Expression.ScopeResolution <$> many expression) @@ -299,6 +300,9 @@ comprehension = makeTerm <$> symbol GeneratorExpression <*> children (comprehen makeComprehension (loc, makeRest) rest = makeTerm loc (makeRest rest) nestedComprehension = (,) <$> location <*> (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression)) +conditionalExpression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) +conditionalExpression = symbol ConditionalExpression >>= \ loc -> children (call >>= \ thenBranch -> identifier >>= \ conditional -> makeTerm loc <$> (Statement.If conditional thenBranch <$> emptyTerm)) + makeTerm :: HasCallStack => InUnion Syntax' f => a -> f (Term Syntax a) -> Term Syntax a makeTerm a f = cofree (a :< inj f) From 21716c93eb92290bb0a9d32cfd0e515dbdb7b9db Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Fri, 2 Jun 2017 12:13:03 -0700 Subject: [PATCH 42/89] :fire: unnecessary bind --- src/Language/Python/Syntax.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 63f0c1a4a..a70f828c9 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -301,7 +301,7 @@ comprehension = makeTerm <$> symbol GeneratorExpression <*> children (comprehen nestedComprehension = (,) <$> location <*> (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression)) conditionalExpression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -conditionalExpression = symbol ConditionalExpression >>= \ loc -> children (call >>= \ thenBranch -> identifier >>= \ conditional -> makeTerm loc <$> (Statement.If conditional thenBranch <$> emptyTerm)) +conditionalExpression = makeTerm <$> symbol ConditionalExpression <*> children (expression >>= \ thenBranch -> expression >>= \ conditional -> Statement.If conditional thenBranch <$> emptyTerm) makeTerm :: HasCallStack => InUnion Syntax' f => a -> f (Term Syntax a) -> Term Syntax a makeTerm a f = cofree (a :< inj f) From b8670c80fb3b5e2cb3e2ecac4e41f513b68a2f88 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Fri, 2 Jun 2017 12:15:13 -0700 Subject: [PATCH 43/89] Assign assignment conditional exprssions --- src/Language/Python/Syntax.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index a70f828c9..fe2ed77a8 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -301,7 +301,7 @@ comprehension = makeTerm <$> symbol GeneratorExpression <*> children (comprehen nestedComprehension = (,) <$> location <*> (Declaration.Comprehension <$> expression <* symbol Variables <*> children (many expression)) conditionalExpression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -conditionalExpression = makeTerm <$> symbol ConditionalExpression <*> children (expression >>= \ thenBranch -> expression >>= \ conditional -> Statement.If conditional thenBranch <$> emptyTerm) +conditionalExpression = makeTerm <$> symbol ConditionalExpression <*> children (expression >>= \ thenBranch -> expression >>= \ conditional -> Statement.If conditional thenBranch <$> (expression <|> emptyTerm)) makeTerm :: HasCallStack => InUnion Syntax' f => a -> f (Term Syntax a) -> Term Syntax a makeTerm a f = cofree (a :< inj f) From 3fcba7c613b59a670a17032a8389bef5ce44e461 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Fri, 2 Jun 2017 12:23:23 -0700 Subject: [PATCH 44/89] :fire: retaining bytestring for Ellipsis --- src/Data/Syntax.hs | 2 +- src/Language/Python/Syntax.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Data/Syntax.hs b/src/Data/Syntax.hs index 8f158cea6..97b5e4c0c 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -53,7 +53,7 @@ instance Show error => Show1 (Error error) where liftShowsPrec = genericLiftShow -- | Ellipsis -data Ellipsis a = Ellipsis ByteString +data Ellipsis a = Ellipsis deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Ellipsis where liftEq = genericLiftEq diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index fe2ed77a8..b7c96c60c 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -111,7 +111,7 @@ dottedName :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) dottedName = makeTerm <$> symbol DottedName <*> children (Expression.ScopeResolution <$> many expression) ellipsis :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -ellipsis = makeTerm <$> symbol Ellipsis <*> (Syntax.Ellipsis <$> source) +ellipsis = makeTerm <$> symbol Ellipsis <*> (Syntax.Ellipsis <$ source) comparisonOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) comparisonOperator = symbol ComparisonOperator >>= \ location -> children (expression >>= \ lexpression -> makeTerm location <$> makeComparison lexpression) From 882749be06be5175161db0bd01dcb332b3fad82e Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Fri, 2 Jun 2017 12:23:43 -0700 Subject: [PATCH 45/89] Simplify declaration assignment --- src/Language/Python/Syntax.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index b7c96c60c..f44ae6008 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -71,7 +71,7 @@ assignment :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) assignment = makeTerm <$> symbol Module <*> children (many declaration) declaration :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -declaration = comment <|> literal <|> statement <|> import' <|> importFrom +declaration = comment <|> statement <|> expression statement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) statement = expressionStatement @@ -83,6 +83,8 @@ statement = expressionStatement <|> printStatement <|> assertStatement <|> globalStatement + <|> import' + <|> importFrom expressionStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) expressionStatement = symbol ExpressionStatement *> children expression From 2e601e34d527d8aa7661b3717a36c2302219b7aa Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Fri, 2 Jun 2017 16:04:29 -0700 Subject: [PATCH 46/89] Fix problem with `is not` comparison operator expressions --- src/Language/Python/Syntax.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index f44ae6008..8dfc54594 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -116,9 +116,9 @@ ellipsis :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) ellipsis = makeTerm <$> symbol Ellipsis <*> (Syntax.Ellipsis <$ source) comparisonOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -comparisonOperator = symbol ComparisonOperator >>= \ location -> children (expression >>= \ lexpression -> makeTerm location <$> makeComparison lexpression) +comparisonOperator = makeTerm <$> symbol ComparisonOperator <*> children (expression >>= \ lexpression -> makeComparison lexpression) where - makeComparison lexpression = symbol AnonLAngle *> (Expression.LessThan lexpression <$> expression) + makeComparison lexpression = symbol AnonLAngle *> (Expression.LessThan lexpression <$> expression) <|> symbol AnonLAngleEqual *> (Expression.LessThanEqual lexpression <$> expression) <|> symbol AnonRAngle *> (Expression.GreaterThan lexpression <$> expression) <|> symbol AnonRAngleEqual *> (Expression.GreaterThanEqual lexpression <$> expression) @@ -126,8 +126,8 @@ comparisonOperator = symbol ComparisonOperator >>= \ location -> children (expre <|> symbol AnonBangEqual *> (Expression.NotEqual lexpression <$> expression) <|> symbol AnonNot *> (Expression.NotIn lexpression <$> expression) <|> symbol AnonIn *> (Expression.In lexpression <$> expression) - <|> symbol AnonIs *> (Expression.IsNot lexpression <$ symbol AnonNot <*> expression - <|> Expression.Is lexpression <$> expression) + <|> symbol AnonIs *> (source *> symbol AnonNot *> (Expression.IsNot lexpression <$> expression) + <|> (Expression.Is lexpression <$> expression)) notOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) notOperator = makeTerm <$> symbol NotOperator <*> children (Expression.Not <$> expression) From 5682f8e2374d222c3f10ca447f75aefd301cf793 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Fri, 2 Jun 2017 16:14:36 -0700 Subject: [PATCH 47/89] :fire: Is and IsNot constructors --- src/Data/Syntax/Expression.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index 5c980bf85..d07e20eef 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -24,8 +24,6 @@ data Comparison a | NotEqual !a !a | In !a !a | NotIn !a !a - | Is !a !a - | IsNot !a !a deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Comparison where liftEq = genericLiftEq From 671b77d342ddbcfa0a72dee5c9e3b40090594e4c Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Fri, 2 Jun 2017 16:14:52 -0700 Subject: [PATCH 48/89] Rename In and NotIn -> Member and NotMember --- src/Data/Syntax/Expression.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index d07e20eef..694e78ec2 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -22,8 +22,8 @@ data Comparison a | GreaterThanEqual !a !a | Equal !a !a | NotEqual !a !a - | In !a !a - | NotIn !a !a + | Member !a !a + | NotMember !a !a deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Comparison where liftEq = genericLiftEq From 79d9cae8199962e3cbf76e45987d4cdd4a6bdde4 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Fri, 2 Jun 2017 16:15:06 -0700 Subject: [PATCH 49/89] Update comparison operator assignments --- src/Language/Python/Syntax.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 8dfc54594..9c7b0d5a2 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -124,10 +124,11 @@ comparisonOperator = makeTerm <$> symbol ComparisonOperator <*> children (expres <|> symbol AnonRAngleEqual *> (Expression.GreaterThanEqual lexpression <$> expression) <|> symbol AnonEqualEqual *> (Expression.Equal lexpression <$> expression) <|> symbol AnonBangEqual *> (Expression.NotEqual lexpression <$> expression) - <|> symbol AnonNot *> (Expression.NotIn lexpression <$> expression) - <|> symbol AnonIn *> (Expression.In lexpression <$> expression) - <|> symbol AnonIs *> (source *> symbol AnonNot *> (Expression.IsNot lexpression <$> expression) - <|> (Expression.Is lexpression <$> expression)) + <|> symbol AnonNot *> (Expression.NotMember lexpression <$> expression) + <|> symbol AnonIn *> (Expression.Member lexpression <$> expression) + -- source is used here to push the cursor to the next node to enable matching against `AnonNot` + <|> symbol AnonIs *> (source *> symbol AnonNot *> (Expression.NotEqual lexpression <$> expression) + <|> (Expression.Equal lexpression <$> expression)) notOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) notOperator = makeTerm <$> symbol NotOperator <*> children (Expression.Not <$> expression) From 42ac463f5a942e8b5d3612adb4ba953ee5e4e848 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Fri, 2 Jun 2017 16:31:24 -0700 Subject: [PATCH 50/89] Update Range record fields to be strict --- src/Data/Syntax/Literal.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Syntax/Literal.hs b/src/Data/Syntax/Literal.hs index 00a9f055e..604e42dae 100644 --- a/src/Data/Syntax/Literal.hs +++ b/src/Data/Syntax/Literal.hs @@ -44,7 +44,7 @@ instance Eq1 Data.Syntax.Literal.Float where liftEq = genericLiftEq instance Show1 Data.Syntax.Literal.Float where liftShowsPrec = genericLiftShowsPrec -data Range a = Range { rangeStart :: a, rangeEnd :: a } +data Range a = Range { rangeStart :: !a, rangeEnd :: !a } deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Range where liftEq = genericLiftEq From 7f2a8539fd874f8537dccce2e1fd940a65c02b74 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Fri, 2 Jun 2017 16:31:37 -0700 Subject: [PATCH 51/89] Update Tuple and Set to be newtypes --- src/Data/Syntax/Literal.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Data/Syntax/Literal.hs b/src/Data/Syntax/Literal.hs index 604e42dae..cabbde891 100644 --- a/src/Data/Syntax/Literal.hs +++ b/src/Data/Syntax/Literal.hs @@ -116,14 +116,14 @@ instance Eq1 KeyValue where liftEq = genericLiftEq instance Show1 KeyValue where liftShowsPrec = genericLiftShowsPrec -data Tuple a = Tuple { tupleContents :: ![a]} +newtype Tuple a = Tuple { tupleContents :: [a]} deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Tuple where liftEq = genericLiftEq instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec -data Set a = Set { setElements :: [a] } +newtype Set a = Set { setElements :: [a] } deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Set where liftEq = genericLiftEq From 727edb5db61b3c1c0552459988abe01cf5875422 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 10:44:09 -0400 Subject: [PATCH 52/89] Rename declarationAlgebra to syntaxDeclarationAlgebra --- src/Renderer.hs | 2 +- src/Renderer/TOC.hs | 8 ++++---- src/Semantic.hs | 4 ++-- 3 files changed, 7 insertions(+), 7 deletions(-) diff --git a/src/Renderer.hs b/src/Renderer.hs index e91e7351e..0bc306a1f 100644 --- a/src/Renderer.hs +++ b/src/Renderer.hs @@ -8,7 +8,7 @@ module Renderer , renderJSONDiff , renderJSONTerm , renderToC -, declarationAlgebra +, syntaxDeclarationAlgebra , identifierAlgebra , Summaries(..) , File(..) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index 4aaf17433..a7079584e 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -8,7 +8,7 @@ module Renderer.TOC , isValidSummary , Declaration(..) , declaration -, declarationAlgebra +, syntaxDeclarationAlgebra , Entry(..) , tableOfContentsBy , dedupe @@ -83,9 +83,9 @@ declaration (annotation :< syntax) | otherwise = annotation <$ (getField annotation :: Maybe Declaration) --- | Compute 'Declaration's for methods and functions. -declarationAlgebra :: HasField fields Range => Source -> TermF (Syntax Text) (Record fields) (Term (Syntax Text) (Record fields), Maybe Declaration) -> Maybe Declaration -declarationAlgebra source r = case tailF r of +-- | Compute 'Declaration's for methods and functions in 'Syntax'. +syntaxDeclarationAlgebra :: HasField fields Range => Source -> TermF (Syntax Text) (Record fields) (Term (Syntax Text) (Record fields), Maybe Declaration) -> Maybe Declaration +syntaxDeclarationAlgebra source r = case tailF r of S.Function (identifier, _) _ _ -> Just $ FunctionDeclaration (getSource identifier) S.Method _ (identifier, _) Nothing _ _ -> Just $ MethodDeclaration (getSource identifier) S.Method _ (identifier, _) (Just (receiver, _)) _ _ diff --git a/src/Semantic.hs b/src/Semantic.hs index cf566a775..92ff5a384 100644 --- a/src/Semantic.hs +++ b/src/Semantic.hs @@ -55,14 +55,14 @@ diffBlobPairs renderer = fmap toS . distributeFoldMap (diffBlobPair renderer) . -- | A task to parse a pair of 'SourceBlob's, diff them, and render the 'Diff'. diffBlobPair :: DiffRenderer output -> Both SourceBlob -> Task output diffBlobPair renderer blobs = case (renderer, effectiveLanguage) of - (ToCDiffRenderer, _) -> run (\ source -> parse syntaxParser source >>= decorate (declarationAlgebra source)) diffTerms (renderToC blobs) + (ToCDiffRenderer, _) -> run (\ source -> parse syntaxParser source >>= decorate (syntaxDeclarationAlgebra source)) diffTerms (renderToC blobs) (JSONDiffRenderer, Just Language.Python) -> run (parse pythonParser) diffLinearly (renderJSONDiff blobs) (JSONDiffRenderer, _) -> run (decorate identifierAlgebra <=< parse syntaxParser) diffTerms (renderJSONDiff blobs) (PatchDiffRenderer, Just Language.Python) -> run (parse pythonParser) diffLinearly (renderPatch blobs) (PatchDiffRenderer, _) -> run (parse syntaxParser) diffTerms (renderPatch blobs) (SExpressionDiffRenderer, Just Language.Python) -> run (decorate (Literally . constructorLabel) <=< parse pythonParser) diffLinearly (renderSExpressionDiff . mapAnnotations ((:. Nil) . rhead)) (SExpressionDiffRenderer, _) -> run (parse syntaxParser) diffTerms (renderSExpressionDiff . mapAnnotations ((:. Nil) . category)) - (IdentityDiffRenderer, _) -> run (\ source -> parse syntaxParser source >>= decorate (declarationAlgebra source)) diffTerms Just + (IdentityDiffRenderer, _) -> run (\ source -> parse syntaxParser source >>= decorate (syntaxDeclarationAlgebra source)) diffTerms Just where effectiveLanguage = runBothWith (<|>) (blobLanguage <$> blobs) syntaxParser = parserForLanguage effectiveLanguage From 2086a8a0a28e0e340a3abfc3c53884b2886972ba Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 10:51:31 -0400 Subject: [PATCH 53/89] Avoid rewriting categories. --- src/Renderer/TOC.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index a7079584e..06b446595 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -77,10 +77,8 @@ data Declaration deriving (Eq, Generic, NFData, Show) -- | Produce the annotations of nodes representing declarations. -declaration :: (HasField fields (Maybe Declaration), HasField fields Category) => TermF (Syntax Text) (Record fields) a -> Maybe (Record fields) -declaration (annotation :< syntax) - | S.ParseError{} <- syntax = Just (setCategory annotation C.ParseError) - | otherwise = annotation <$ (getField annotation :: Maybe Declaration) +declaration :: (HasField fields (Maybe Declaration), HasField fields Category) => TermF f (Record fields) a -> Maybe (Record fields) +declaration (annotation :< _) = annotation <$ (getField annotation :: Maybe Declaration) -- | Compute 'Declaration's for methods and functions in 'Syntax'. From 28c34635a8794b3a1cd2595bf4c545a9f743c8f1 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 10:55:45 -0400 Subject: [PATCH 54/89] Extract showExpectation. --- src/Data/Syntax/Assignment.hs | 18 ++++++++++-------- 1 file changed, 10 insertions(+), 8 deletions(-) diff --git a/src/Data/Syntax/Assignment.hs b/src/Data/Syntax/Assignment.hs index c2008acb8..06689a978 100644 --- a/src/Data/Syntax/Assignment.hs +++ b/src/Data/Syntax/Assignment.hs @@ -166,22 +166,24 @@ data ErrorCause symbol -- | Pretty-print an Error with reference to the source where it occurred. showError :: Show symbol => Source.Source -> Error symbol -> ShowS -showError source Error{..} - = withSGRCode [SetConsoleIntensity BoldIntensity] (showSourcePos Nothing errorPos) . showString ": " . withSGRCode [SetColor Foreground Vivid Red] (showString "error") . showString ": " . showExpectation . showChar '\n' +showError source error@Error{..} + = withSGRCode [SetConsoleIntensity BoldIntensity] (showSourcePos Nothing errorPos) . showString ": " . withSGRCode [SetColor Foreground Vivid Red] (showString "error") . showString ": " . showExpectation error . showChar '\n' . showString context -- actualLines results include line endings, so no newline here . showString (replicate (succ (Info.column errorPos + lineNumberDigits)) ' ') . withSGRCode [SetColor Foreground Vivid Green] (showChar '^') . showChar '\n' . showString (prettyCallStack callStack) . showChar '\n' - where showExpectation = case errorCause of - UnexpectedEndOfInput [] -> showString "no rule to match at end of input nodes" - UnexpectedEndOfInput symbols -> showString "expected " . showSymbols symbols . showString " at end of input nodes" - UnexpectedSymbol symbols a -> showString "expected " . showSymbols symbols . showString ", but got " . shows a - ParseError symbols -> showString "expected " . showSymbols symbols . showString ", but got parse error" - context = maybe "\n" (toS . Source.sourceText . sconcat) (nonEmpty [ Source.Source (toS (showLineNumber i)) <> Source.Source ": " <> l | (i, l) <- zip [1..] (Source.actualLines source), inRange (Info.line errorPos - 2, Info.line errorPos) i ]) + where context = maybe "\n" (toS . Source.sourceText . sconcat) (nonEmpty [ Source.Source (toS (showLineNumber i)) <> Source.Source ": " <> l | (i, l) <- zip [1..] (Source.actualLines source), inRange (Info.line errorPos - 2, Info.line errorPos) i ]) showLineNumber n = let s = show n in replicate (lineNumberDigits - length s) ' ' <> s lineNumberDigits = succ (floor (logBase 10 (fromIntegral (Info.line errorPos) :: Double))) showSGRCode = showString . setSGRCode withSGRCode code s = showSGRCode code . s . showSGRCode [] +showExpectation :: Show symbol => Error symbol -> ShowS +showExpectation Error{..} = case errorCause of + UnexpectedEndOfInput [] -> showString "no rule to match at end of input nodes" + UnexpectedEndOfInput symbols -> showString "expected " . showSymbols symbols . showString " at end of input nodes" + UnexpectedSymbol symbols a -> showString "expected " . showSymbols symbols . showString ", but got " . shows a + ParseError symbols -> showString "expected " . showSymbols symbols . showString ", but got parse error" + showSymbols :: Show symbol => [symbol] -> ShowS showSymbols [] = showString "end of input nodes" showSymbols [symbol] = shows symbol From d8eeb1c40edfe113ba5d759d37803082cdc660bf Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 10:56:06 -0400 Subject: [PATCH 55/89] Export showExpectation. --- src/Data/Syntax/Assignment.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Data/Syntax/Assignment.hs b/src/Data/Syntax/Assignment.hs index 06689a978..1ad633072 100644 --- a/src/Data/Syntax/Assignment.hs +++ b/src/Data/Syntax/Assignment.hs @@ -74,6 +74,7 @@ module Data.Syntax.Assignment , Error(..) , ErrorCause(..) , showError +, showExpectation , assign , runAssignment , AssignmentState(..) From 31921d7dacfe3088fb7b145e4e1ff95c50f237f7 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 10:58:15 -0400 Subject: [PATCH 56/89] Generalize diffTOC and renderToC to arbitrary Traversable functors. --- src/Renderer/TOC.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index 06b446595..c363bb6c4 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -146,7 +146,7 @@ entrySummary entry = case entry of | C.ParseError <- category record = const (ErrorSummary (maybe "" declarationIdentifier (getField record :: Maybe Declaration)) (sourceSpan record)) | otherwise = JSONSummary . Summarizable (category record) (maybe "" declarationIdentifier (getField record :: Maybe Declaration)) (sourceSpan record) -renderToC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan) => Both SourceBlob -> Diff (Syntax Text) (Record fields) -> Summaries +renderToC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan, Traversable f) => Both SourceBlob -> Diff f (Record fields) -> Summaries renderToC blobs = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . diffTOC where toMap [] = mempty toMap as = Map.singleton summaryKey (toJSON <$> as) @@ -156,7 +156,7 @@ renderToC blobs = uncurry Summaries . bimap toMap toMap . List.partition isValid | before == after -> after | otherwise -> before <> " -> " <> after -diffTOC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan) => Diff (Syntax Text) (Record fields) -> [JSONSummary] +diffTOC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan, Traversable f) => Diff f (Record fields) -> [JSONSummary] diffTOC = mapMaybe entrySummary . dedupe . tableOfContentsBy declaration -- The user-facing category name From 64d19d2a5c3c569bf0a9ad0d0e32c32870473c8f Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 10:59:22 -0400 Subject: [PATCH 57/89] =?UTF-8?q?Define=20a=20declarationAlgebra=20over=20?= =?UTF-8?q?=C3=A0=20la=20carte=20syntax.?= MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit --- src/Renderer.hs | 1 + src/Renderer/TOC.hs | 18 ++++++++++++++++++ 2 files changed, 19 insertions(+) diff --git a/src/Renderer.hs b/src/Renderer.hs index 0bc306a1f..57809aed3 100644 --- a/src/Renderer.hs +++ b/src/Renderer.hs @@ -8,6 +8,7 @@ module Renderer , renderJSONDiff , renderJSONTerm , renderToC +, declarationAlgebra , syntaxDeclarationAlgebra , identifierAlgebra , Summaries(..) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index c363bb6c4..f213825d1 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -8,6 +8,7 @@ module Renderer.TOC , isValidSummary , Declaration(..) , declaration +, declarationAlgebra , syntaxDeclarationAlgebra , Entry(..) , tableOfContentsBy @@ -21,6 +22,8 @@ import Data.Align (crosswalk) import Data.Functor.Both hiding (fst, snd) import qualified Data.Functor.Both as Both import Data.Functor.Listable +import Data.Functor.Union +import Data.Proxy import Data.Text (toLower) import Data.Text.Listable import Data.These @@ -33,6 +36,8 @@ import qualified Data.List as List import qualified Data.Map as Map hiding (null) import Source hiding (null) import Syntax as S +import qualified Data.Syntax as Syntax +import qualified Data.Syntax.Declaration as Declaration import Term data Summaries = Summaries { changes, errors :: !(Map Text [Value]) } @@ -94,6 +99,19 @@ syntaxDeclarationAlgebra source r = case tailF r of _ -> Nothing where getSource = toText . flip Source.slice source . byteRange . extract +-- | Compute 'Declaration's for methods and functions. +declarationAlgebra :: (InUnion fs Declaration.Function, InUnion fs Declaration.Method, InUnion fs (Syntax.Error error), Show error, Functor (Union fs), HasField fields Range) + => Proxy error + -> Source + -> TermF (Union fs) (Record fields) (Term (Union fs) (Record fields), Maybe Declaration) + -> Maybe Declaration +declarationAlgebra proxy source r + | Just (Declaration.Function (identifier, _) _ _) <- prj (tailF r) = Just $ FunctionDeclaration (getSource identifier) + | Just (Declaration.Method (identifier, _) _ _) <- prj (tailF r) = Just $ MethodDeclaration (getSource identifier) + | Just (Syntax.Error err) <- prj (tailF r) = Just $ ErrorDeclaration (show (err `asProxyTypeOf` proxy)) + | otherwise = Nothing + where getSource = toText . flip Source.slice source . byteRange . extract + -- | An entry in a table of contents. data Entry a From 30fd038730551c262c67df2759ce718305041461 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 11:04:52 -0400 Subject: [PATCH 58/89] Define the declaration algebras with the RAlgebra type synonym. --- src/Renderer/TOC.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index f213825d1..d3dbd8c52 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -36,6 +36,7 @@ import qualified Data.List as List import qualified Data.Map as Map hiding (null) import Source hiding (null) import Syntax as S +import Data.Syntax.Algebra (RAlgebra) import qualified Data.Syntax as Syntax import qualified Data.Syntax.Declaration as Declaration import Term @@ -87,7 +88,7 @@ declaration (annotation :< _) = annotation <$ (getField annotation :: Maybe Decl -- | Compute 'Declaration's for methods and functions in 'Syntax'. -syntaxDeclarationAlgebra :: HasField fields Range => Source -> TermF (Syntax Text) (Record fields) (Term (Syntax Text) (Record fields), Maybe Declaration) -> Maybe Declaration +syntaxDeclarationAlgebra :: HasField fields Range => Source -> RAlgebra (SyntaxTermF Text fields) (SyntaxTerm Text fields) (Maybe Declaration) syntaxDeclarationAlgebra source r = case tailF r of S.Function (identifier, _) _ _ -> Just $ FunctionDeclaration (getSource identifier) S.Method _ (identifier, _) Nothing _ _ -> Just $ MethodDeclaration (getSource identifier) @@ -103,8 +104,7 @@ syntaxDeclarationAlgebra source r = case tailF r of declarationAlgebra :: (InUnion fs Declaration.Function, InUnion fs Declaration.Method, InUnion fs (Syntax.Error error), Show error, Functor (Union fs), HasField fields Range) => Proxy error -> Source - -> TermF (Union fs) (Record fields) (Term (Union fs) (Record fields), Maybe Declaration) - -> Maybe Declaration + -> RAlgebra (TermF (Union fs) (Record fields)) (Term (Union fs) (Record fields)) (Maybe Declaration) declarationAlgebra proxy source r | Just (Declaration.Function (identifier, _) _ _) <- prj (tailF r) = Just $ FunctionDeclaration (getSource identifier) | Just (Declaration.Method (identifier, _) _ _) <- prj (tailF r) = Just $ MethodDeclaration (getSource identifier) From 200c85f4803e897ec68c36ee4e5e66aa4276f555 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 11:28:30 -0400 Subject: [PATCH 59/89] Reformat JSONSummary. --- src/Renderer/TOC.hs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index d3dbd8c52..cad2fecbf 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -54,9 +54,10 @@ instance StringConv Summaries ByteString where instance ToJSON Summaries where toJSON Summaries{..} = object [ "changes" .= changes, "errors" .= errors ] -data JSONSummary = JSONSummary { info :: Summarizable } - | ErrorSummary { error :: Text, errorSpan :: SourceSpan } - deriving (Generic, Eq, Show) +data JSONSummary + = JSONSummary { info :: Summarizable } + | ErrorSummary { error :: Text, errorSpan :: SourceSpan } + deriving (Generic, Eq, Show) instance ToJSON JSONSummary where toJSON (JSONSummary Summarizable{..}) = object [ "changeType" .= summarizableChangeType, "category" .= toCategoryName summarizableCategory, "term" .= summarizableTermName, "span" .= summarizableSourceSpan ] From 5fecc683243f3335155b936945ebd120df6ff30d Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 11:31:37 -0400 Subject: [PATCH 60/89] :fire: Summarizable. --- src/Renderer/TOC.hs | 21 ++++++++------------- test/TOCSpec.hs | 20 ++++++++++---------- 2 files changed, 18 insertions(+), 23 deletions(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index cad2fecbf..7bc34a54c 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -4,7 +4,6 @@ module Renderer.TOC , diffTOC , Summaries(..) , JSONSummary(..) -, Summarizable(..) , isValidSummary , Declaration(..) , declaration @@ -55,27 +54,23 @@ instance ToJSON Summaries where toJSON Summaries{..} = object [ "changes" .= changes, "errors" .= errors ] data JSONSummary - = JSONSummary { info :: Summarizable } + = JSONSummary + { summaryCategory :: Category + , summaryTermName :: Text + , summarySourceSpan :: SourceSpan + , summaryChangeType :: Text + } | ErrorSummary { error :: Text, errorSpan :: SourceSpan } deriving (Generic, Eq, Show) instance ToJSON JSONSummary where - toJSON (JSONSummary Summarizable{..}) = object [ "changeType" .= summarizableChangeType, "category" .= toCategoryName summarizableCategory, "term" .= summarizableTermName, "span" .= summarizableSourceSpan ] + toJSON JSONSummary{..} = object [ "changeType" .= summaryChangeType, "category" .= toCategoryName summaryCategory, "term" .= summaryTermName, "span" .= summarySourceSpan ] toJSON ErrorSummary{..} = object [ "error" .= error, "span" .= errorSpan ] isValidSummary :: JSONSummary -> Bool isValidSummary ErrorSummary{} = False isValidSummary _ = True -data Summarizable - = Summarizable - { summarizableCategory :: Category - , summarizableTermName :: Text - , summarizableSourceSpan :: SourceSpan - , summarizableChangeType :: Text - } - deriving (Eq, Show) - -- | A declaration’s identifier and type. data Declaration = MethodDeclaration { declarationIdentifier :: Text } @@ -163,7 +158,7 @@ entrySummary entry = case entry of Replaced a -> Just (recordSummary a "modified") where recordSummary record | C.ParseError <- category record = const (ErrorSummary (maybe "" declarationIdentifier (getField record :: Maybe Declaration)) (sourceSpan record)) - | otherwise = JSONSummary . Summarizable (category record) (maybe "" declarationIdentifier (getField record :: Maybe Declaration)) (sourceSpan record) + | otherwise = JSONSummary (category record) (maybe "" declarationIdentifier (getField record :: Maybe Declaration)) (sourceSpan record) renderToC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan, Traversable f) => Both SourceBlob -> Diff f (Record fields) -> Summaries renderToC blobs = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . diffTOC diff --git a/test/TOCSpec.hs b/test/TOCSpec.hs index 29d2475fe..ed6958c56 100644 --- a/test/TOCSpec.hs +++ b/test/TOCSpec.hs @@ -60,39 +60,39 @@ spec = parallel $ do sourceBlobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.B.rb") Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs) diffTOC diff `shouldBe` - [ JSONSummary $ Summarizable C.SingletonMethod "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added" - , JSONSummary $ Summarizable C.Method "bar" (sourceSpanBetween (4, 1) (6, 4)) "modified" - , JSONSummary $ Summarizable C.Method "baz" (sourceSpanBetween (4, 1) (5, 4)) "removed" ] + [ JSONSummary C.SingletonMethod "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added" + , JSONSummary C.Method "bar" (sourceSpanBetween (4, 1) (6, 4)) "modified" + , JSONSummary C.Method "baz" (sourceSpanBetween (4, 1) (5, 4)) "removed" ] it "dedupes changes in same parent method" $ do sourceBlobs <- blobsForPaths (both "javascript/duplicate-parent.A.js" "javascript/duplicate-parent.B.js") Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs) diffTOC diff `shouldBe` - [ JSONSummary $ Summarizable C.Function "myFunction" (sourceSpanBetween (1, 1) (6, 2)) "modified" ] + [ JSONSummary C.Function "myFunction" (sourceSpanBetween (1, 1) (6, 2)) "modified" ] it "dedupes similar methods" $ do sourceBlobs <- blobsForPaths (both "javascript/erroneous-duplicate-method.A.js" "javascript/erroneous-duplicate-method.B.js") Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs) diffTOC diff `shouldBe` - [ JSONSummary $ Summarizable C.Function "performHealthCheck" (sourceSpanBetween (8, 1) (29, 2)) "modified" ] + [ JSONSummary C.Function "performHealthCheck" (sourceSpanBetween (8, 1) (29, 2)) "modified" ] it "summarizes Go methods with receivers with special formatting" $ do sourceBlobs <- blobsForPaths (both "go/method-with-receiver.A.go" "go/method-with-receiver.B.go") Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs) diffTOC diff `shouldBe` - [ JSONSummary $ Summarizable C.Method "(*apiClient) CheckAuth" (sourceSpanBetween (3,1) (3,101)) "added" ] + [ JSONSummary C.Method "(*apiClient) CheckAuth" (sourceSpanBetween (3,1) (3,101)) "added" ] it "summarizes Ruby methods that start with two identifiers" $ do sourceBlobs <- blobsForPaths (both "ruby/method-starts-with-two-identifiers.A.rb" "ruby/method-starts-with-two-identifiers.B.rb") Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs) diffTOC diff `shouldBe` - [ JSONSummary $ Summarizable C.Method "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified" ] + [ JSONSummary C.Method "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified" ] it "handles unicode characters in file" $ do sourceBlobs <- blobsForPaths (both "ruby/unicode.A.rb" "ruby/unicode.B.rb") Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs) diffTOC diff `shouldBe` - [ JSONSummary $ Summarizable C.Method "foo" (sourceSpanBetween (6, 1) (7, 4)) "added" ] + [ JSONSummary C.Method "foo" (sourceSpanBetween (6, 1) (7, 4)) "added" ] prop "inserts of methods and functions are summarized" $ \name body -> @@ -125,11 +125,11 @@ spec = parallel $ do describe "JSONSummary" $ do it "encodes InSummarizable to JSON" $ do - let summary = JSONSummary $ Summarizable C.Method "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified" + let summary = JSONSummary C.Method "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified" encode summary `shouldBe` "{\"span\":{\"start\":[1,1],\"end\":[4,4]},\"category\":\"Method\",\"term\":\"foo\",\"changeType\":\"modified\"}" it "encodes Summarizable to JSON" $ do - let summary = JSONSummary $ Summarizable C.SingletonMethod "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added" + let summary = JSONSummary C.SingletonMethod "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added" encode summary `shouldBe` "{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"added\"}" describe "diff with ToCDiffRenderer" $ do From 977d4599956f6216925233461afa8b9b6172ceea Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 11:32:18 -0400 Subject: [PATCH 61/89] Rename a couple of tests. --- test/TOCSpec.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/test/TOCSpec.hs b/test/TOCSpec.hs index ed6958c56..a10268ef1 100644 --- a/test/TOCSpec.hs +++ b/test/TOCSpec.hs @@ -124,11 +124,11 @@ spec = parallel $ do diffTOC (diffTerms (pure term)) `shouldBe` [] describe "JSONSummary" $ do - it "encodes InSummarizable to JSON" $ do + it "encodes modified summaries to JSON" $ do let summary = JSONSummary C.Method "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified" encode summary `shouldBe` "{\"span\":{\"start\":[1,1],\"end\":[4,4]},\"category\":\"Method\",\"term\":\"foo\",\"changeType\":\"modified\"}" - it "encodes Summarizable to JSON" $ do + it "encodes added summaries to JSON" $ do let summary = JSONSummary C.SingletonMethod "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added" encode summary `shouldBe` "{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"added\"}" From 41e6180e7b720162be4a483f0fa8111090b61372 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 11:53:49 -0400 Subject: [PATCH 62/89] Extract the declaration getter to the top level. --- src/Renderer/TOC.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index 7bc34a54c..3ede9f8b9 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -78,6 +78,9 @@ data Declaration | ErrorDeclaration { declarationIdentifier :: Text } deriving (Eq, Generic, NFData, Show) +getDeclaration :: HasField fields (Maybe Declaration) => Record fields -> Maybe Declaration +getDeclaration = getField + -- | Produce the annotations of nodes representing declarations. declaration :: (HasField fields (Maybe Declaration), HasField fields Category) => TermF f (Record fields) a -> Maybe (Record fields) declaration (annotation :< _) = annotation <$ (getField annotation :: Maybe Declaration) @@ -145,8 +148,6 @@ dedupe = foldl' go [] similarMatch a b = sameCategory a b && similarDeclaration a b sameCategory = (==) `on` category similarDeclaration = (==) `on` fmap (toLower . declarationIdentifier) . getDeclaration - getDeclaration :: HasField fields (Maybe Declaration) => Record fields -> Maybe Declaration - getDeclaration = getField -- | Construct a 'JSONSummary' from an 'Entry'. Returns 'Nothing' for 'Unchanged' patches. entrySummary :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan) => Entry (Record fields) -> Maybe JSONSummary From 020e4d20666697661e5dba0fb96d1ec2e7fccba5 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 11:54:20 -0400 Subject: [PATCH 63/89] Indicate errors solely with ErrorDeclaration. --- src/Renderer/TOC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index 3ede9f8b9..67965dd5a 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -158,7 +158,7 @@ entrySummary entry = case entry of Inserted a -> Just (recordSummary a "added") Replaced a -> Just (recordSummary a "modified") where recordSummary record - | C.ParseError <- category record = const (ErrorSummary (maybe "" declarationIdentifier (getField record :: Maybe Declaration)) (sourceSpan record)) + | Just (ErrorDeclaration text) <- getDeclaration record = const (ErrorSummary text (sourceSpan record)) | otherwise = JSONSummary (category record) (maybe "" declarationIdentifier (getField record :: Maybe Declaration)) (sourceSpan record) renderToC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan, Traversable f) => Both SourceBlob -> Diff f (Record fields) -> Summaries From 99197b96d9772019481cc9aa751cfbb8403b5e7b Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 12:45:18 -0400 Subject: [PATCH 64/89] JSONSummary holds Text rather than a Category. --- src/Renderer/TOC.hs | 6 +++--- test/TOCSpec.hs | 20 ++++++++++---------- 2 files changed, 13 insertions(+), 13 deletions(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index 67965dd5a..d4c5eedad 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -55,7 +55,7 @@ instance ToJSON Summaries where data JSONSummary = JSONSummary - { summaryCategory :: Category + { summaryCategoryName :: Text , summaryTermName :: Text , summarySourceSpan :: SourceSpan , summaryChangeType :: Text @@ -64,7 +64,7 @@ data JSONSummary deriving (Generic, Eq, Show) instance ToJSON JSONSummary where - toJSON JSONSummary{..} = object [ "changeType" .= summaryChangeType, "category" .= toCategoryName summaryCategory, "term" .= summaryTermName, "span" .= summarySourceSpan ] + toJSON JSONSummary{..} = object [ "changeType" .= summaryChangeType, "category" .= summaryCategoryName, "term" .= summaryTermName, "span" .= summarySourceSpan ] toJSON ErrorSummary{..} = object [ "error" .= error, "span" .= errorSpan ] isValidSummary :: JSONSummary -> Bool @@ -159,7 +159,7 @@ entrySummary entry = case entry of Replaced a -> Just (recordSummary a "modified") where recordSummary record | Just (ErrorDeclaration text) <- getDeclaration record = const (ErrorSummary text (sourceSpan record)) - | otherwise = JSONSummary (category record) (maybe "" declarationIdentifier (getField record :: Maybe Declaration)) (sourceSpan record) + | otherwise = JSONSummary (toCategoryName (category record)) (maybe "" declarationIdentifier (getField record :: Maybe Declaration)) (sourceSpan record) renderToC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan, Traversable f) => Both SourceBlob -> Diff f (Record fields) -> Summaries renderToC blobs = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . diffTOC diff --git a/test/TOCSpec.hs b/test/TOCSpec.hs index a10268ef1..0578f7613 100644 --- a/test/TOCSpec.hs +++ b/test/TOCSpec.hs @@ -60,39 +60,39 @@ spec = parallel $ do sourceBlobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.B.rb") Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs) diffTOC diff `shouldBe` - [ JSONSummary C.SingletonMethod "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added" - , JSONSummary C.Method "bar" (sourceSpanBetween (4, 1) (6, 4)) "modified" - , JSONSummary C.Method "baz" (sourceSpanBetween (4, 1) (5, 4)) "removed" ] + [ JSONSummary "Method" "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added" + , JSONSummary "Method" "bar" (sourceSpanBetween (4, 1) (6, 4)) "modified" + , JSONSummary "Method" "baz" (sourceSpanBetween (4, 1) (5, 4)) "removed" ] it "dedupes changes in same parent method" $ do sourceBlobs <- blobsForPaths (both "javascript/duplicate-parent.A.js" "javascript/duplicate-parent.B.js") Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs) diffTOC diff `shouldBe` - [ JSONSummary C.Function "myFunction" (sourceSpanBetween (1, 1) (6, 2)) "modified" ] + [ JSONSummary "Function" "myFunction" (sourceSpanBetween (1, 1) (6, 2)) "modified" ] it "dedupes similar methods" $ do sourceBlobs <- blobsForPaths (both "javascript/erroneous-duplicate-method.A.js" "javascript/erroneous-duplicate-method.B.js") Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs) diffTOC diff `shouldBe` - [ JSONSummary C.Function "performHealthCheck" (sourceSpanBetween (8, 1) (29, 2)) "modified" ] + [ JSONSummary "Function" "performHealthCheck" (sourceSpanBetween (8, 1) (29, 2)) "modified" ] it "summarizes Go methods with receivers with special formatting" $ do sourceBlobs <- blobsForPaths (both "go/method-with-receiver.A.go" "go/method-with-receiver.B.go") Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs) diffTOC diff `shouldBe` - [ JSONSummary C.Method "(*apiClient) CheckAuth" (sourceSpanBetween (3,1) (3,101)) "added" ] + [ JSONSummary "Method" "(*apiClient) CheckAuth" (sourceSpanBetween (3,1) (3,101)) "added" ] it "summarizes Ruby methods that start with two identifiers" $ do sourceBlobs <- blobsForPaths (both "ruby/method-starts-with-two-identifiers.A.rb" "ruby/method-starts-with-two-identifiers.B.rb") Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs) diffTOC diff `shouldBe` - [ JSONSummary C.Method "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified" ] + [ JSONSummary "Method" "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified" ] it "handles unicode characters in file" $ do sourceBlobs <- blobsForPaths (both "ruby/unicode.A.rb" "ruby/unicode.B.rb") Just diff <- runTask (diffBlobPair IdentityDiffRenderer sourceBlobs) diffTOC diff `shouldBe` - [ JSONSummary C.Method "foo" (sourceSpanBetween (6, 1) (7, 4)) "added" ] + [ JSONSummary "Method" "foo" (sourceSpanBetween (6, 1) (7, 4)) "added" ] prop "inserts of methods and functions are summarized" $ \name body -> @@ -125,11 +125,11 @@ spec = parallel $ do describe "JSONSummary" $ do it "encodes modified summaries to JSON" $ do - let summary = JSONSummary C.Method "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified" + let summary = JSONSummary "Method" "foo" (sourceSpanBetween (1, 1) (4, 4)) "modified" encode summary `shouldBe` "{\"span\":{\"start\":[1,1],\"end\":[4,4]},\"category\":\"Method\",\"term\":\"foo\",\"changeType\":\"modified\"}" it "encodes added summaries to JSON" $ do - let summary = JSONSummary C.SingletonMethod "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added" + let summary = JSONSummary "Method" "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added" encode summary `shouldBe` "{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"added\"}" describe "diff with ToCDiffRenderer" $ do From 58c1afebe581909a01d9c310957bef1eb9713c75 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 15:47:55 -0400 Subject: [PATCH 65/89] Define & export Python and Ruby Error types. --- src/Language/Python/Syntax.hs | 8 ++++++-- src/Language/Ruby/Syntax.hs | 8 ++++++-- 2 files changed, 12 insertions(+), 4 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 12d1fae7e..f7fb15a5e 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -4,6 +4,7 @@ module Language.Python.Syntax , Syntax , Syntax' , Grammar +, Error ) where import Data.Align.Generic @@ -11,7 +12,8 @@ import Data.Functor.Classes.Eq.Generic import Data.Functor.Classes.Show.Generic import Data.Functor.Union import qualified Data.Syntax as Syntax -import Data.Syntax.Assignment +import Data.Syntax.Assignment hiding (Error) +import qualified Data.Syntax.Assignment as Assignment import qualified Data.Syntax.Comment as Comment import qualified Data.Syntax.Declaration as Declaration import qualified Data.Syntax.Expression as Expression @@ -45,11 +47,13 @@ type Syntax' = , Statement.Return , Statement.Yield , Syntax.Empty - , Syntax.Error [Error Grammar] + , Syntax.Error [Error] , Syntax.Identifier , [] ] +type Error = Assignment.Error Grammar + data Redirect a = Redirect !a !a deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) diff --git a/src/Language/Ruby/Syntax.hs b/src/Language/Ruby/Syntax.hs index 194820a0a..5a5078f4d 100644 --- a/src/Language/Ruby/Syntax.hs +++ b/src/Language/Ruby/Syntax.hs @@ -4,11 +4,13 @@ module Language.Ruby.Syntax , Syntax , Syntax' , Grammar +, Error ) where import Data.Functor.Union import qualified Data.Syntax as Syntax -import Data.Syntax.Assignment +import Data.Syntax.Assignment hiding (Error) +import qualified Data.Syntax.Assignment as Assignment import qualified Data.Syntax.Comment as Comment import qualified Data.Syntax.Declaration as Declaration import qualified Data.Syntax.Expression as Expression @@ -46,11 +48,13 @@ type Syntax' = , Statement.While , Statement.Yield , Syntax.Empty - , Syntax.Error [Error Grammar] + , Syntax.Error [Error] , Syntax.Identifier , [] ] +type Error = Assignment.Error Grammar + -- | Assignment from AST in Ruby’s grammar onto a program in Ruby’s syntax. assignment :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) From cab4a790898d225888d33f5547830174484bc87c Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 15:56:51 -0400 Subject: [PATCH 66/89] Error nodes represent exactly one error. --- src/Language/Python/Syntax.hs | 2 +- src/Language/Ruby/Syntax.hs | 4 ++-- src/Parser.hs | 4 ++-- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index f7fb15a5e..9dd9ef51f 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -47,7 +47,7 @@ type Syntax' = , Statement.Return , Statement.Yield , Syntax.Empty - , Syntax.Error [Error] + , Syntax.Error Error , Syntax.Identifier , [] ] diff --git a/src/Language/Ruby/Syntax.hs b/src/Language/Ruby/Syntax.hs index 5a5078f4d..a03c3fb14 100644 --- a/src/Language/Ruby/Syntax.hs +++ b/src/Language/Ruby/Syntax.hs @@ -48,7 +48,7 @@ type Syntax' = , Statement.While , Statement.Yield , Syntax.Empty - , Syntax.Error [Error] + , Syntax.Error Error , Syntax.Identifier , [] ] @@ -161,4 +161,4 @@ emptyTerm = makeTerm <$> location <*> pure Syntax.Empty handleError :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -> Assignment (Node Grammar) (Term Syntax Location) handleError = flip catchError $ \ error -> case errorCause error of UnexpectedEndOfInput _ -> throwError error - _ -> makeTerm <$> location <*> (Syntax.Error [error] <$ source) + _ -> makeTerm <$> location <*> (Syntax.Error error <$ source) diff --git a/src/Parser.hs b/src/Parser.hs index 95d7fa539..31e860bcd 100644 --- a/src/Parser.hs +++ b/src/Parser.hs @@ -30,7 +30,7 @@ data Parser term where -- | A parser producing 'AST' using a 'TS.Language'. ASTParser :: (Bounded grammar, Enum grammar) => Ptr TS.Language -> Parser (AST grammar) -- | A parser producing an à la carte term given an 'AST'-producing parser and an 'Assignment' onto 'Term's in some syntax type. Assignment errors will result in a top-level 'Syntax.Error' node. - AssignmentParser :: (Bounded grammar, Enum grammar, Eq grammar, Show grammar, Symbol grammar, InUnion fs (Syntax.Error [Error grammar])) + AssignmentParser :: (Bounded grammar, Enum grammar, Eq grammar, Show grammar, Symbol grammar, InUnion fs (Syntax.Error (Error grammar))) => Parser (AST grammar) -- ^ A parser producing 'AST'. -> Assignment (Node grammar) (Term (Union fs) Location) -- ^ An assignment from 'AST' onto 'Term's. -> Parser (Term (Union fs) Location) -- ^ A parser of 'Term's. @@ -65,7 +65,7 @@ runParser parser = case parser of ast <- runParser parser source let Result errors term = assign assignment source ast traverse_ (putStr . ($ "") . showError source) errors - pure (fromMaybe (cofree ((totalRange source :. totalSpan source :. Nil) :< inj (Syntax.Error errors))) term) + pure (fromMaybe (cofree ((totalRange source :. totalSpan source :. Nil) :< inj (Syntax.Error (fromMaybe (Error (SourcePos 0 0) (UnexpectedEndOfInput [])) (head errors))))) term) TreeSitterParser language tslanguage -> treeSitterParser language tslanguage MarkdownParser -> cmarkParser LineByLineParser -> lineByLineParser From 2d6bd0f9e8009d150c680413b9a9cc4abf36a08b Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 15:57:32 -0400 Subject: [PATCH 67/89] Assignment results have at most one error. --- src/Data/Syntax/Assignment.hs | 34 ++++++++++++++++------------------ src/Parser.hs | 6 +++--- 2 files changed, 19 insertions(+), 21 deletions(-) diff --git a/src/Data/Syntax/Assignment.hs b/src/Data/Syntax/Assignment.hs index 228559b9b..3a387ea88 100644 --- a/src/Data/Syntax/Assignment.hs +++ b/src/Data/Syntax/Assignment.hs @@ -148,7 +148,7 @@ type AST grammar = Rose (Node grammar) -- | The result of assignment, possibly containing an error. -data Result symbol a = Result { resultErrors :: [Error symbol], resultValue :: Maybe a } +data Result symbol a = Result { resultErrors :: Maybe (Error symbol), resultValue :: Maybe a } deriving (Eq, Foldable, Functor, Traversable) data Error symbol where @@ -203,15 +203,15 @@ assign assignment source = fmap snd . assignAllFrom assignment . makeState sourc assignAllFrom :: (Symbol grammar, Enum grammar, Eq grammar, HasCallStack) => Assignment (Node grammar) a -> AssignmentState grammar -> Result grammar (AssignmentState grammar, a) assignAllFrom assignment state = case runAssignment assignment state of - Result es (Just (state, a)) -> case stateNodes (dropAnonymous state) of - [] -> Result [] (Just (state, a)) - Rose (Just s :. _) _ :_ -> Result (if null es then [ Error (statePos state) (UnexpectedSymbol [] s) ] else es) Nothing - Rose (Nothing :. _) _ :_ -> Result (if null es then [ Error (statePos state) (ParseError []) ] else es) Nothing + Result err (Just (state, a)) -> case stateNodes (dropAnonymous state) of + [] -> Result Nothing (Just (state, a)) + Rose (Just s :. _) _ :_ -> Result (err <|> Just (Error (statePos state) (UnexpectedSymbol [] s))) Nothing + Rose (Nothing :. _) _ :_ -> Result (err <|> Just (Error (statePos state) (ParseError []))) Nothing r -> r -- | Run an assignment of nodes in a grammar onto terms in a syntax. runAssignment :: forall grammar a. (Symbol grammar, Enum grammar, Eq grammar, HasCallStack) => Assignment (Node grammar) a -> AssignmentState grammar -> Result grammar (AssignmentState grammar, a) -runAssignment = iterFreer run . fmap (\ a state -> Result [] (Just (state, a))) +runAssignment = iterFreer run . fmap (\ a state -> pure (state, a)) where run :: AssignmentF (Node grammar) x -> (x -> AssignmentState grammar -> Result grammar (AssignmentState grammar, a)) -> AssignmentState grammar -> Result grammar (AssignmentState grammar, a) run assignment yield initialState = case (assignment, stateNodes) of (Location, Rose (_ :. location) _ : _) -> yield location state @@ -219,18 +219,16 @@ runAssignment = iterFreer run . fmap (\ a state -> Result [] (Just (state, a))) (Source, Rose (_ :. range :. _) _ : _) -> yield (Source.sourceText (Source.slice (offsetRange range (negate stateOffset)) stateSource)) (advanceState state) (Children childAssignment, Rose _ children : _) -> case assignAllFrom childAssignment state { stateNodes = children } of Result _ (Just (state', a)) -> yield a (advanceState state' { stateNodes = stateNodes }) - Result es Nothing -> Result es Nothing + Result err Nothing -> Result err Nothing (Choose choices, Rose (Just symbol :. _) _ : _) | Just a <- IntMap.lookup (fromEnum symbol) choices -> yield a state -- Nullability: some rules, e.g. 'pure a' and 'many a', should match at the end of input. Either side of an alternation may be nullable, ergo Alt can match at the end of input. (Alt a b, _) -> yield a state <|> yield b state - (Throw e, _) -> Result [ e ] Nothing + (Throw e, _) -> Result (Just e) Nothing (Catch during handler, _) -> case yield during state of - Result _ (Just (state', a)) -> Result [] (Just (state', a)) - Result (e:_) Nothing -> yield (handler e) state - Result [] Nothing -> Result [] Nothing - (_, []) -> Result [ Error statePos (UnexpectedEndOfInput expectedSymbols) ] Nothing - (_, Rose (Just symbol :. _ :. nodeSpan :. Nil) _:_) -> Result [ Error (Info.spanStart nodeSpan) (UnexpectedSymbol expectedSymbols symbol) ] Nothing - (_, Rose (Nothing :. _ :. nodeSpan :. Nil) _ : _) -> Result [ Error (Info.spanStart nodeSpan) (ParseError expectedSymbols) ] Nothing + Result _ (Just (state', a)) -> Result Nothing (Just (state', a)) + Result err Nothing -> maybe (Result Nothing Nothing) (flip yield state . handler) err + (_, []) -> Result (Just (Error statePos (UnexpectedEndOfInput expectedSymbols))) Nothing + (_, Rose (symbol :. _ :. nodeSpan :. Nil) _:_) -> Result (Just (maybe (Error (Info.spanStart nodeSpan) (ParseError expectedSymbols)) (Error (Info.spanStart nodeSpan) . UnexpectedSymbol expectedSymbols) symbol)) Nothing where state@AssignmentState{..} = case assignment of Choose choices | all ((== Regular) . symbolType) (choiceSymbols choices) -> dropAnonymous initialState _ -> initialState @@ -308,13 +306,13 @@ instance Show1 ErrorCause where ParseError expected -> showsUnaryWith (liftShowsPrec sp sl) "ParseError" d expected instance Applicative (Result symbol) where - pure = Result [] . Just - Result e1 f <*> Result e2 a = Result (e1 <> e2) (f <*> a) + pure = Result Nothing . Just + Result e1 f <*> Result e2 a = Result (e1 <|> e2) (f <*> a) instance Alternative (Result symbol) where - empty = Result [] Nothing + empty = Result Nothing Nothing Result e (Just a) <|> _ = Result e (Just a) - Result e1 Nothing <|> Result e2 b = Result (e1 <> e2) b + Result e1 Nothing <|> Result e2 b = Result (e1 <|> e2) b instance MonadError (Error symbol) (Assignment (Node symbol)) where throwError :: HasCallStack => Error symbol -> Assignment (Node symbol) a diff --git a/src/Parser.hs b/src/Parser.hs index 31e860bcd..d455ef05f 100644 --- a/src/Parser.hs +++ b/src/Parser.hs @@ -63,9 +63,9 @@ runParser parser = case parser of ASTParser language -> parseToAST language AssignmentParser parser assignment -> \ source -> do ast <- runParser parser source - let Result errors term = assign assignment source ast - traverse_ (putStr . ($ "") . showError source) errors - pure (fromMaybe (cofree ((totalRange source :. totalSpan source :. Nil) :< inj (Syntax.Error (fromMaybe (Error (SourcePos 0 0) (UnexpectedEndOfInput [])) (head errors))))) term) + let Result err term = assign assignment source ast + traverse_ (putStr . ($ "") . showError source) err + pure (fromMaybe (cofree ((totalRange source :. totalSpan source :. Nil) :< inj (Syntax.Error (fromMaybe (Error (SourcePos 0 0) (UnexpectedEndOfInput [])) err)))) term) TreeSitterParser language tslanguage -> treeSitterParser language tslanguage MarkdownParser -> cmarkParser LineByLineParser -> lineByLineParser From 195aeb14f57d1c7cd2dc391c5d2b0c0ca6dfd5f6 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Mon, 5 Jun 2017 13:23:21 -0700 Subject: [PATCH 68/89] :fire: NotEqual --- src/Data/Syntax/Expression.hs | 1 - src/Language/Python/Syntax.hs | 24 ++++++++++++------------ 2 files changed, 12 insertions(+), 13 deletions(-) diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index 454a9c5bd..a1008975c 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -21,7 +21,6 @@ data Comparison a | GreaterThan !a !a | GreaterThanEqual !a !a | Equal !a !a - | NotEqual !a !a | Member !a !a | NotMember !a !a deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 631fadb47..a06794e01 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -117,19 +117,19 @@ ellipsis :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) ellipsis = makeTerm <$> symbol Ellipsis <*> (Syntax.Ellipsis <$ source) comparisonOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -comparisonOperator = makeTerm <$> symbol ComparisonOperator <*> children (expression >>= \ lexpression -> makeComparison lexpression) +comparisonOperator = symbol ComparisonOperator >>= \ loc -> children (expression >>= \ lexpression -> makeComparison loc lexpression) where - makeComparison lexpression = symbol AnonLAngle *> (Expression.LessThan lexpression <$> expression) - <|> symbol AnonLAngleEqual *> (Expression.LessThanEqual lexpression <$> expression) - <|> symbol AnonRAngle *> (Expression.GreaterThan lexpression <$> expression) - <|> symbol AnonRAngleEqual *> (Expression.GreaterThanEqual lexpression <$> expression) - <|> symbol AnonEqualEqual *> (Expression.Equal lexpression <$> expression) - <|> symbol AnonBangEqual *> (Expression.NotEqual lexpression <$> expression) - <|> symbol AnonNot *> (Expression.NotMember lexpression <$> expression) - <|> symbol AnonIn *> (Expression.Member lexpression <$> expression) - -- source is used here to push the cursor to the next node to enable matching against `AnonNot` - <|> symbol AnonIs *> (source *> symbol AnonNot *> (Expression.NotEqual lexpression <$> expression) - <|> (Expression.Equal lexpression <$> expression)) + makeComparison loc lexpression = makeTerm loc <$ symbol AnonLAngle <*> (Expression.LessThan lexpression <$> expression) + <|> makeTerm loc <$ symbol AnonLAngleEqual <*> (Expression.LessThanEqual lexpression <$> expression) + <|> makeTerm loc <$ symbol AnonRAngle <*> (Expression.GreaterThan lexpression <$> expression) + <|> makeTerm loc <$ symbol AnonRAngleEqual <*> (Expression.GreaterThanEqual lexpression <$> expression) + <|> makeTerm loc <$ symbol AnonEqualEqual <*> (Expression.Equal lexpression <$> expression) + <|> makeTerm loc <$ symbol AnonBangEqual <*> (Expression.Not <$> (makeTerm <$> location <*> (Expression.Equal lexpression <$> expression))) + <|> makeTerm loc <$ symbol AnonNot <*> (Expression.NotMember lexpression <$> expression) + <|> makeTerm loc <$ symbol AnonIn <*> (Expression.Member lexpression <$> expression) + -- source is used here to push the cursor to the next node to enable matching against `AnonNot` + <|> makeTerm loc <$ symbol AnonIs <*> (source *> symbol AnonNot *> (Expression.NotEqual lexpression <$> expression) + <|> (Expression.Equal lexpression <$> expression)) notOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) notOperator = makeTerm <$> symbol NotOperator <*> children (Expression.Not <$> expression) From e9f20b6b5788c20bbf6a1fe2d26414d8de408635 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Mon, 5 Jun 2017 13:37:51 -0700 Subject: [PATCH 69/89] Make Member a constructor of Subscript; :fire: NotMember --- src/Data/Syntax/Expression.hs | 3 +-- src/Language/Python/Syntax.hs | 8 ++++---- 2 files changed, 5 insertions(+), 6 deletions(-) diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index a1008975c..6ecea473e 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -21,8 +21,6 @@ data Comparison a | GreaterThan !a !a | GreaterThanEqual !a !a | Equal !a !a - | Member !a !a - | NotMember !a !a deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Comparison where liftEq = genericLiftEq @@ -77,6 +75,7 @@ instance Show1 MemberAccess where liftShowsPrec = genericLiftShowsPrec -- | Subscript (e.g a[1]) data Subscript a = Subscript !a ![a] + | Member !a !a deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Subscript where liftEq = genericLiftEq diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index a06794e01..f600da4ba 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -125,11 +125,11 @@ comparisonOperator = symbol ComparisonOperator >>= \ loc -> children (expression <|> makeTerm loc <$ symbol AnonRAngleEqual <*> (Expression.GreaterThanEqual lexpression <$> expression) <|> makeTerm loc <$ symbol AnonEqualEqual <*> (Expression.Equal lexpression <$> expression) <|> makeTerm loc <$ symbol AnonBangEqual <*> (Expression.Not <$> (makeTerm <$> location <*> (Expression.Equal lexpression <$> expression))) - <|> makeTerm loc <$ symbol AnonNot <*> (Expression.NotMember lexpression <$> expression) + <|> makeTerm loc <$ symbol AnonNot <*> (Expression.Not <$> (makeTerm <$> location <*> (Expression.Member lexpression <$> expression))) <|> makeTerm loc <$ symbol AnonIn <*> (Expression.Member lexpression <$> expression) - -- source is used here to push the cursor to the next node to enable matching against `AnonNot` - <|> makeTerm loc <$ symbol AnonIs <*> (source *> symbol AnonNot *> (Expression.NotEqual lexpression <$> expression) - <|> (Expression.Equal lexpression <$> expression)) + -- source is used here to push the cursor to the next node to enable matching against `AnonNot` + <|> symbol AnonIs *> source *> (symbol AnonNot *> (makeTerm loc <$> Expression.Not <$> (makeTerm <$> location <*> (Expression.Equal lexpression <$> expression))) + <|> (makeTerm loc <$> Expression.Equal lexpression <$> expression)) notOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) notOperator = makeTerm <$> symbol NotOperator <*> children (Expression.Not <$> expression) From 8ad6dcb958818ee6453afb2ff4d0c46d54a8db55 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Mon, 5 Jun 2017 13:41:10 -0700 Subject: [PATCH 70/89] Update Comprehension field names --- src/Data/Syntax/Declaration.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Syntax/Declaration.hs b/src/Data/Syntax/Declaration.hs index a9eb2d742..37c38daa6 100644 --- a/src/Data/Syntax/Declaration.hs +++ b/src/Data/Syntax/Declaration.hs @@ -56,7 +56,7 @@ instance Show1 Data.Syntax.Declaration.Constructor where liftShowsPrec = generic -- | Comprehension (e.g. ((a for b in c) in Python) -data Comprehension a = Comprehension { result :: !a, intermediate :: ![a], base :: !a } +data Comprehension a = Comprehension { comprehensionMap :: !a, comprehensionBindings :: ![a], comprehensionContext :: !a } deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) instance Eq1 Comprehension where liftEq = genericLiftEq From 83d3e3f77d3c0a0736e611ab63ae04564b98b5bb Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Mon, 5 Jun 2017 13:41:22 -0700 Subject: [PATCH 71/89] Undo whitespace changes --- src/TreeSitter.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/TreeSitter.hs b/src/TreeSitter.hs index 88a584280..fc6d63d21 100644 --- a/src/TreeSitter.hs +++ b/src/TreeSitter.hs @@ -30,7 +30,6 @@ import qualified Text.Parser.TreeSitter as TS import SourceSpan import Info - -- | Returns a TreeSitter parser for the given language and TreeSitter grammar. treeSitterParser :: Language -> Ptr TS.Language -> Source -> IO (Term (Syntax.Syntax Text) (Record DefaultFields)) treeSitterParser language grammar source = bracket ts_document_new ts_document_free $ \ document -> do @@ -41,6 +40,7 @@ treeSitterParser language grammar source = bracket ts_document_new ts_document_f term <- documentToTerm language document source pure term + -- | Parse 'Source' with the given 'TS.Language' and return its AST. parseToAST :: (Bounded grammar, Enum grammar) => Ptr TS.Language -> Source -> IO (A.AST grammar) parseToAST language source = bracket ts_document_new ts_document_free $ \ document -> do From cff0571b37738cd9f568ffb5bb55bb60b4eaf7d3 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 16:46:32 -0400 Subject: [PATCH 72/89] Use getDeclaration in entrySummary. --- src/Renderer/TOC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index d4c5eedad..0eb202179 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -159,7 +159,7 @@ entrySummary entry = case entry of Replaced a -> Just (recordSummary a "modified") where recordSummary record | Just (ErrorDeclaration text) <- getDeclaration record = const (ErrorSummary text (sourceSpan record)) - | otherwise = JSONSummary (toCategoryName (category record)) (maybe "" declarationIdentifier (getField record :: Maybe Declaration)) (sourceSpan record) + | otherwise = JSONSummary (toCategoryName (category record)) (maybe "" declarationIdentifier (getDeclaration record)) (sourceSpan record) renderToC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan, Traversable f) => Both SourceBlob -> Diff f (Record fields) -> Summaries renderToC blobs = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . diffTOC From 663bb5beb39671fef2ab644899e0b837315e7282 Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Mon, 5 Jun 2017 13:52:04 -0700 Subject: [PATCH 73/89] Move Ellipsis to Python.Syntax --- src/Data/Syntax.hs | 6 ------ src/Language/Python/Syntax.hs | 12 ++++++++++-- 2 files changed, 10 insertions(+), 8 deletions(-) diff --git a/src/Data/Syntax.hs b/src/Data/Syntax.hs index 97b5e4c0c..e59cbe245 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -52,9 +52,3 @@ instance Eq error => Eq1 (Error error) where liftEq = genericLiftEq instance Show error => Show1 (Error error) where liftShowsPrec = genericLiftShowsPrec --- | Ellipsis -data Ellipsis a = Ellipsis - deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) - -instance Eq1 Ellipsis where liftEq = genericLiftEq -instance Show1 Ellipsis where liftShowsPrec = genericLiftShowsPrec diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index f600da4ba..f77b796e0 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -54,13 +54,21 @@ type Syntax' = , Statement.If , Statement.Return , Statement.Yield - , Syntax.Ellipsis + , Language.Python.Syntax.Ellipsis , Syntax.Empty , Syntax.Error [Error Grammar] , Syntax.Identifier , [] ] +-- | Ellipsis (used in splice expressions and alternatively can be used as a fill in expression, like `undefined` in Haskell) +data Ellipsis a = Ellipsis + deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) + +instance Eq1 Ellipsis where liftEq = genericLiftEq +instance Show1 Ellipsis where liftShowsPrec = genericLiftShowsPrec + + data Redirect a = Redirect !a !a deriving (Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable) @@ -114,7 +122,7 @@ dottedName :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) dottedName = makeTerm <$> symbol DottedName <*> children (Expression.ScopeResolution <$> many expression) ellipsis :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -ellipsis = makeTerm <$> symbol Ellipsis <*> (Syntax.Ellipsis <$ source) +ellipsis = makeTerm <$> symbol Grammar.Ellipsis <*> (Language.Python.Syntax.Ellipsis <$ source) comparisonOperator :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) comparisonOperator = symbol ComparisonOperator >>= \ loc -> children (expression >>= \ lexpression -> makeComparison loc lexpression) From af841480a71cf779cdd3dd94143ce0148715ed39 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 16:52:14 -0400 Subject: [PATCH 74/89] Pattern match on the declaration directly. --- src/Renderer/TOC.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index 0eb202179..e5997ab26 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -157,9 +157,9 @@ entrySummary entry = case entry of Deleted a -> Just (recordSummary a "removed") Inserted a -> Just (recordSummary a "added") Replaced a -> Just (recordSummary a "modified") - where recordSummary record - | Just (ErrorDeclaration text) <- getDeclaration record = const (ErrorSummary text (sourceSpan record)) - | otherwise = JSONSummary (toCategoryName (category record)) (maybe "" declarationIdentifier (getDeclaration record)) (sourceSpan record) + where recordSummary record = case getDeclaration record of + Just (ErrorDeclaration text) -> const (ErrorSummary text (sourceSpan record)) + declaration -> JSONSummary (toCategoryName (category record)) (maybe "" declarationIdentifier declaration) (sourceSpan record) renderToC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan, Traversable f) => Both SourceBlob -> Diff f (Record fields) -> Summaries renderToC blobs = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . diffTOC From 95047d10a2a9b3705e19003bd943cdf5dd0d72e0 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 16:53:20 -0400 Subject: [PATCH 75/89] Factor the Just construction into recordSummary. --- src/Renderer/TOC.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index e5997ab26..d6ce78d18 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -153,13 +153,13 @@ dedupe = foldl' go [] entrySummary :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan) => Entry (Record fields) -> Maybe JSONSummary entrySummary entry = case entry of Unchanged _ -> Nothing - Changed a -> Just (recordSummary a "modified") - Deleted a -> Just (recordSummary a "removed") - Inserted a -> Just (recordSummary a "added") - Replaced a -> Just (recordSummary a "modified") + Changed a -> recordSummary a "modified" + Deleted a -> recordSummary a "removed" + Inserted a -> recordSummary a "added" + Replaced a -> recordSummary a "modified" where recordSummary record = case getDeclaration record of - Just (ErrorDeclaration text) -> const (ErrorSummary text (sourceSpan record)) - declaration -> JSONSummary (toCategoryName (category record)) (maybe "" declarationIdentifier declaration) (sourceSpan record) + Just (ErrorDeclaration text) -> Just . const (ErrorSummary text (sourceSpan record)) + declaration -> Just . JSONSummary (toCategoryName (category record)) (maybe "" declarationIdentifier declaration) (sourceSpan record) renderToC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan, Traversable f) => Both SourceBlob -> Diff f (Record fields) -> Summaries renderToC blobs = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . diffTOC From a8538e228788a0aab0753a63efc8856a856dcd64 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 16:54:32 -0400 Subject: [PATCH 76/89] Drop values missing declarations. --- src/Renderer/TOC.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index d6ce78d18..2fb3d9761 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -159,7 +159,8 @@ entrySummary entry = case entry of Replaced a -> recordSummary a "modified" where recordSummary record = case getDeclaration record of Just (ErrorDeclaration text) -> Just . const (ErrorSummary text (sourceSpan record)) - declaration -> Just . JSONSummary (toCategoryName (category record)) (maybe "" declarationIdentifier declaration) (sourceSpan record) + Just declaration -> Just . JSONSummary (toCategoryName (category record)) (declarationIdentifier declaration) (sourceSpan record) + Nothing -> const Nothing renderToC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan, Traversable f) => Both SourceBlob -> Diff f (Record fields) -> Summaries renderToC blobs = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . diffTOC From 26c59dc7cb8c0c4628071c96c341e54e131353cd Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 16:56:45 -0400 Subject: [PATCH 77/89] Pick the category name based on the declaration. --- src/Renderer/TOC.hs | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index 2fb3d9761..adfd55074 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -159,7 +159,7 @@ entrySummary entry = case entry of Replaced a -> recordSummary a "modified" where recordSummary record = case getDeclaration record of Just (ErrorDeclaration text) -> Just . const (ErrorSummary text (sourceSpan record)) - Just declaration -> Just . JSONSummary (toCategoryName (category record)) (declarationIdentifier declaration) (sourceSpan record) + Just declaration -> Just . JSONSummary (toCategoryName declaration) (declarationIdentifier declaration) (sourceSpan record) Nothing -> const Nothing renderToC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan, Traversable f) => Both SourceBlob -> Diff f (Record fields) -> Summaries @@ -176,10 +176,11 @@ diffTOC :: (HasField fields Category, HasField fields (Maybe Declaration), HasFi diffTOC = mapMaybe entrySummary . dedupe . tableOfContentsBy declaration -- The user-facing category name -toCategoryName :: Category -> Text -toCategoryName category = case category of - C.SingletonMethod -> "Method" - c -> show c +toCategoryName :: Declaration -> Text +toCategoryName declaration = case declaration of + FunctionDeclaration _ -> "Function" + MethodDeclaration _ -> "Method" + ErrorDeclaration _ -> "ParseError" instance Listable Declaration where tiers From d3edae8671b6002668c5c3b55006938145a9dec3 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 16:57:42 -0400 Subject: [PATCH 78/89] =?UTF-8?q?:fire:=20entrySummary=E2=80=99s=20depende?= =?UTF-8?q?ncy=20on=20Category.?= MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit --- src/Renderer/TOC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index adfd55074..94b4de15e 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -150,7 +150,7 @@ dedupe = foldl' go [] similarDeclaration = (==) `on` fmap (toLower . declarationIdentifier) . getDeclaration -- | Construct a 'JSONSummary' from an 'Entry'. Returns 'Nothing' for 'Unchanged' patches. -entrySummary :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan) => Entry (Record fields) -> Maybe JSONSummary +entrySummary :: (HasField fields (Maybe Declaration), HasField fields SourceSpan) => Entry (Record fields) -> Maybe JSONSummary entrySummary entry = case entry of Unchanged _ -> Nothing Changed a -> recordSummary a "modified" From ff7234074db1ceab25f1fb90d2e7ff0fc7c03eb6 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 16:59:36 -0400 Subject: [PATCH 79/89] Define sameCategory in terms of the toCategoryName computation. --- src/Renderer/TOC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index 94b4de15e..cf57c145d 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -146,7 +146,7 @@ dedupe = foldl' go [] find p x = List.break (p x) exactMatch = (==) `on` getDeclaration similarMatch a b = sameCategory a b && similarDeclaration a b - sameCategory = (==) `on` category + sameCategory = (==) `on` fmap toCategoryName . getDeclaration similarDeclaration = (==) `on` fmap (toLower . declarationIdentifier) . getDeclaration -- | Construct a 'JSONSummary' from an 'Entry'. Returns 'Nothing' for 'Unchanged' patches. From 7a753baf78ed79f5dbebddee3c1b9f220d2dca22 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 17:02:39 -0400 Subject: [PATCH 80/89] =?UTF-8?q?:fire:=20declaration=E2=80=99s=20dependen?= =?UTF-8?q?ce=20on=20Category.?= MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit --- src/Renderer/TOC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index cf57c145d..52f4d95d0 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -82,7 +82,7 @@ getDeclaration :: HasField fields (Maybe Declaration) => Record fields -> Maybe getDeclaration = getField -- | Produce the annotations of nodes representing declarations. -declaration :: (HasField fields (Maybe Declaration), HasField fields Category) => TermF f (Record fields) a -> Maybe (Record fields) +declaration :: HasField fields (Maybe Declaration) => TermF f (Record fields) a -> Maybe (Record fields) declaration (annotation :< _) = annotation <$ (getField annotation :: Maybe Declaration) From bda8746224ef898297d3e3947a979ced035c03ed Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 17:02:50 -0400 Subject: [PATCH 81/89] =?UTF-8?q?:fire:=20dedupe=E2=80=99s=20dependence=20?= =?UTF-8?q?on=20Category.?= MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit --- src/Renderer/TOC.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index 52f4d95d0..a41468dfe 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -136,7 +136,7 @@ tableOfContentsBy selector = fromMaybe [] . iter diffAlgebra . fmap (Just . fmap | otherwise = fold r patchEntry = these Deleted Inserted (const Replaced) . unPatch -dedupe :: (HasField fields Category, HasField fields (Maybe Declaration)) => [Entry (Record fields)] -> [Entry (Record fields)] +dedupe :: HasField fields (Maybe Declaration) => [Entry (Record fields)] -> [Entry (Record fields)] dedupe = foldl' go [] where go xs x | (_, _:_) <- find (exactMatch `on` entryPayload) x xs = xs | (front, similar : back) <- find (similarMatch `on` entryPayload) x xs = From 18db448df2fba3d7ecdf0ebf2a3f42fe16cc3811 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 17:03:00 -0400 Subject: [PATCH 82/89] =?UTF-8?q?:fire:=20ToC=E2=80=99s=20dependence=20on?= =?UTF-8?q?=20Category.?= MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit --- src/Renderer/TOC.hs | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/Renderer/TOC.hs b/src/Renderer/TOC.hs index a41468dfe..e88e09746 100644 --- a/src/Renderer/TOC.hs +++ b/src/Renderer/TOC.hs @@ -15,7 +15,6 @@ module Renderer.TOC , entrySummary ) where -import Category as C import Data.Aeson import Data.Align (crosswalk) import Data.Functor.Both hiding (fst, snd) @@ -162,7 +161,7 @@ entrySummary entry = case entry of Just declaration -> Just . JSONSummary (toCategoryName declaration) (declarationIdentifier declaration) (sourceSpan record) Nothing -> const Nothing -renderToC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan, Traversable f) => Both SourceBlob -> Diff f (Record fields) -> Summaries +renderToC :: (HasField fields (Maybe Declaration), HasField fields SourceSpan, Traversable f) => Both SourceBlob -> Diff f (Record fields) -> Summaries renderToC blobs = uncurry Summaries . bimap toMap toMap . List.partition isValidSummary . diffTOC where toMap [] = mempty toMap as = Map.singleton summaryKey (toJSON <$> as) @@ -172,7 +171,7 @@ renderToC blobs = uncurry Summaries . bimap toMap toMap . List.partition isValid | before == after -> after | otherwise -> before <> " -> " <> after -diffTOC :: (HasField fields Category, HasField fields (Maybe Declaration), HasField fields SourceSpan, Traversable f) => Diff f (Record fields) -> [JSONSummary] +diffTOC :: (HasField fields (Maybe Declaration), HasField fields SourceSpan, Traversable f) => Diff f (Record fields) -> [JSONSummary] diffTOC = mapMaybe entrySummary . dedupe . tableOfContentsBy declaration -- The user-facing category name From c82487688f2c20442de30a4df73d004593cb82dd Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Mon, 5 Jun 2017 17:03:54 -0400 Subject: [PATCH 83/89] Implement the ToC path for Python :tada: --- src/Semantic.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Semantic.hs b/src/Semantic.hs index 98979fc18..78204d5ba 100644 --- a/src/Semantic.hs +++ b/src/Semantic.hs @@ -11,11 +11,15 @@ import Algorithm hiding (diff) import Data.Align.Generic (GAlign) import Data.Functor.Both as Both import Data.Functor.Classes (Eq1, Show1) +import Data.Functor.Union +import Data.Proxy import Data.Record +import qualified Data.Syntax.Declaration as Declaration import Diff import Info import Interpreter import qualified Language +import qualified Language.Python.Syntax as Python import Patch import Parser import Prologue @@ -55,6 +59,7 @@ diffBlobPairs renderer = fmap toS . distributeFoldMap (diffBlobPair renderer) . -- | A task to parse a pair of 'SourceBlob's, diff them, and render the 'Diff'. diffBlobPair :: DiffRenderer output -> Both SourceBlob -> Task output diffBlobPair renderer blobs = case (renderer, effectiveLanguage) of + (ToCDiffRenderer, Just Language.Python) -> run (\ source -> parse pythonParser source >>= decorate (declarationAlgebra (Proxy :: Proxy Python.Error) source) . hoistCofree (weaken . weaken :: Union fs a -> Union (Declaration.Function ': Declaration.Method ': fs) a)) diffLinearly (renderToC blobs) (ToCDiffRenderer, _) -> run (\ source -> parse syntaxParser source >>= decorate (syntaxDeclarationAlgebra source)) diffTerms (renderToC blobs) (JSONDiffRenderer, Just Language.Python) -> run (parse pythonParser) diffLinearly (renderJSONDiff blobs) (JSONDiffRenderer, _) -> run (decorate identifierAlgebra <=< parse syntaxParser) diffTerms (renderJSONDiff blobs) From 0aea9280e1292acf61b73b1da1ab0ebcc9ca404d Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Mon, 5 Jun 2017 14:09:13 -0700 Subject: [PATCH 84/89] :abc: alternative order --- src/Language/Python/Syntax.hs | 38 +++++++++++++++++------------------ 1 file changed, 19 insertions(+), 19 deletions(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index f77b796e0..08ec4a838 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -83,40 +83,40 @@ declaration :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) declaration = comment <|> statement <|> expression statement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -statement = expressionStatement - <|> ifStatement - <|> returnStatement - <|> identifier +statement = assertStatement <|> assignment' <|> augmentedAssignment - <|> printStatement - <|> assertStatement + <|> expressionStatement <|> globalStatement + <|> ifStatement + <|> identifier <|> import' <|> importFrom + <|> printStatement + <|> returnStatement expressionStatement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) expressionStatement = symbol ExpressionStatement *> children expression expression :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -expression = statement - <|> unaryOperator +expression = await <|> binaryOperator <|> booleanOperator - <|> comparisonOperator - <|> tuple - <|> literal - <|> memberAccess - <|> subscript <|> call - <|> keywordIdentifier - <|> notOperator - <|> ellipsis - <|> dottedName - <|> await - <|> lambda + <|> comparisonOperator <|> comprehension <|> conditionalExpression + <|> dottedName + <|> ellipsis + <|> lambda + <|> keywordIdentifier + <|> literal + <|> memberAccess + <|> notOperator + <|> subscript + <|> statement + <|> tuple + <|> unaryOperator dottedName :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) dottedName = makeTerm <$> symbol DottedName <*> children (Expression.ScopeResolution <$> many expression) From 56992513bb2d57b8f5b4001e3e86476bbe37269b Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Mon, 5 Jun 2017 14:09:23 -0700 Subject: [PATCH 85/89] Add error handling --- src/Language/Python/Syntax.hs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 08ec4a838..92f487a57 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -80,7 +80,7 @@ assignment :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) assignment = makeTerm <$> symbol Module <*> children (many declaration) declaration :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -declaration = comment <|> statement <|> expression +declaration = handleError $ comment <|> statement <|> expression statement :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) statement = assertStatement @@ -320,3 +320,8 @@ makeTerm a f = cofree (a :< inj f) emptyTerm :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) emptyTerm = makeTerm <$> location <*> pure Syntax.Empty + +handleError :: HasCallStack => Assignment (Node Grammar) (Term Syntax Location) -> Assignment (Node Grammar) (Term Syntax Location) +handleError = flip catchError $ \ error -> case errorCause error of + UnexpectedEndOfInput _ -> throwError error + _ -> makeTerm <$> location <*> (Syntax.Error [error] <$ source) From 5ef141a3d3078f61a6af27cc7489759d4bdb04aa Mon Sep 17 00:00:00 2001 From: Rick Winfrey Date: Mon, 5 Jun 2017 14:24:27 -0700 Subject: [PATCH 86/89] :fire: whitespace --- src/Data/Syntax.hs | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/Data/Syntax.hs b/src/Data/Syntax.hs index e59cbe245..995e44d2f 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -50,5 +50,3 @@ data Error error a = Error error instance Eq error => GAlign (Error error) instance Eq error => Eq1 (Error error) where liftEq = genericLiftEq instance Show error => Show1 (Error error) where liftShowsPrec = genericLiftShowsPrec - - From 46b098e3127146e18dd45eb21bdcfb852f0a7d0a Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 6 Jun 2017 08:44:25 -0400 Subject: [PATCH 87/89] Rename resultErrors to resultError. --- src/Data/Syntax/Assignment.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Syntax/Assignment.hs b/src/Data/Syntax/Assignment.hs index 3a387ea88..b68944390 100644 --- a/src/Data/Syntax/Assignment.hs +++ b/src/Data/Syntax/Assignment.hs @@ -148,7 +148,7 @@ type AST grammar = Rose (Node grammar) -- | The result of assignment, possibly containing an error. -data Result symbol a = Result { resultErrors :: Maybe (Error symbol), resultValue :: Maybe a } +data Result symbol a = Result { resultError :: Maybe (Error symbol), resultValue :: Maybe a } deriving (Eq, Foldable, Functor, Traversable) data Error symbol where From 51fcf532a832a3f082fbc66e455ee882a3bc3fc9 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 6 Jun 2017 08:47:17 -0400 Subject: [PATCH 88/89] Correct the spec. --- test/Data/Syntax/Assignment/Spec.hs | 28 ++++++++++++++-------------- 1 file changed, 14 insertions(+), 14 deletions(-) diff --git a/test/Data/Syntax/Assignment/Spec.hs b/test/Data/Syntax/Assignment/Spec.hs index 511a8a861..0c9af36bf 100644 --- a/test/Data/Syntax/Assignment/Spec.hs +++ b/test/Data/Syntax/Assignment/Spec.hs @@ -14,11 +14,11 @@ spec :: Spec spec = do describe "Applicative" $ it "matches in sequence" $ - runAssignment ((,) <$> red <*> red) (makeState "helloworld" [Rose (rec Red 0 5) [], Rose (rec Red 5 10) []]) `shouldBe` Result [] (Just (AssignmentState 10 (Info.SourcePos 1 11) "" [], (Out "hello", Out "world"))) + runAssignment ((,) <$> red <*> red) (makeState "helloworld" [Rose (rec Red 0 5) [], Rose (rec Red 5 10) []]) `shouldBe` Result Nothing (Just (AssignmentState 10 (Info.SourcePos 1 11) "" [], (Out "hello", Out "world"))) describe "Alternative" $ do it "attempts multiple alternatives" $ - runAssignment (green <|> red) (makeState "hello" [Rose (rec Red 0 5) []]) `shouldBe` Result [] (Just (AssignmentState 5 (Info.SourcePos 1 6) "" [], Out "hello")) + runAssignment (green <|> red) (makeState "hello" [Rose (rec Red 0 5) []]) `shouldBe` Result Nothing (Just (AssignmentState 5 (Info.SourcePos 1 6) "" [], Out "hello")) it "matches repetitions" $ let s = "colourless green ideas sleep furiously" @@ -31,35 +31,35 @@ spec = do describe "symbol" $ do it "matches nodes with the same symbol" $ - snd <$> runAssignment red (makeState "hello" [Rose (rec Red 0 5) []]) `shouldBe` Result [] (Just (Out "hello")) + snd <$> runAssignment red (makeState "hello" [Rose (rec Red 0 5) []]) `shouldBe` Result Nothing (Just (Out "hello")) it "does not advance past the current node" $ let initialState = makeState "hi" [ Rose (rec Red 0 2) [] ] in - fst <$> runAssignment (symbol Red) initialState `shouldBe` Result [] (Just initialState) + fst <$> runAssignment (symbol Red) initialState `shouldBe` Result Nothing (Just initialState) describe "source" $ do it "produces the node’s source" $ - assign source "hi" (Rose (rec Red 0 2) []) `shouldBe` Result [] (Just "hi") + assign source "hi" (Rose (rec Red 0 2) []) `shouldBe` Result Nothing (Just "hi") it "advances past the current node" $ - fst <$> runAssignment source (makeState "hi" [ Rose (rec Red 0 2) [] ]) `shouldBe` Result [] (Just (AssignmentState 2 (Info.SourcePos 1 3) "" [])) + fst <$> runAssignment source (makeState "hi" [ Rose (rec Red 0 2) [] ]) `shouldBe` Result Nothing (Just (AssignmentState 2 (Info.SourcePos 1 3) "" [])) describe "children" $ do it "advances past the current node" $ - fst <$> runAssignment (children (pure (Out ""))) (makeState "a" [Rose (rec Red 0 1) []]) `shouldBe` Result [] (Just (AssignmentState 1 (Info.SourcePos 1 2) "" [])) + fst <$> runAssignment (children (pure (Out ""))) (makeState "a" [Rose (rec Red 0 1) []]) `shouldBe` Result Nothing (Just (AssignmentState 1 (Info.SourcePos 1 2) "" [])) it "matches if its subrule matches" $ - () <$ runAssignment (children red) (makeState "a" [Rose (rec Blue 0 1) [Rose (rec Red 0 1) []]]) `shouldBe` Result [] (Just ()) + () <$ runAssignment (children red) (makeState "a" [Rose (rec Blue 0 1) [Rose (rec Red 0 1) []]]) `shouldBe` Result Nothing (Just ()) it "does not match if its subrule does not match" $ - (runAssignment (children red) (makeState "a" [Rose (rec Blue 0 1) [Rose (rec Green 0 1) []]])) `shouldBe` Result [ Error (Info.SourcePos 1 1) (UnexpectedSymbol [Red] Green) ] Nothing + (runAssignment (children red) (makeState "a" [Rose (rec Blue 0 1) [Rose (rec Green 0 1) []]])) `shouldBe` Result (Just (Error (Info.SourcePos 1 1) (UnexpectedSymbol [Red] Green))) Nothing it "matches nested children" $ runAssignment (symbol Red *> children (symbol Green *> children (symbol Blue *> source))) (makeState "1" [ Rose (rec Red 0 1) [ Rose (rec Green 0 1) [ Rose (rec Blue 0 1) [] ] ] ]) `shouldBe` - Result [] (Just (AssignmentState 1 (Info.SourcePos 1 2) "" [], "1")) + Result Nothing (Just (AssignmentState 1 (Info.SourcePos 1 2) "" [], "1")) it "continues after children" $ resultValue (runAssignment @@ -76,17 +76,17 @@ spec = do (makeState "12" [ Rose (rec Red 0 2) [ Rose (rec Green 0 1) [ Rose (rec Blue 0 1) [] ] , Rose (rec Green 1 2) [ Rose (rec Blue 1 2) [] ] ] ]) `shouldBe` - Result [] (Just (AssignmentState 2 (Info.SourcePos 1 3) "" [], ["1", "2"])) + Result Nothing (Just (AssignmentState 2 (Info.SourcePos 1 3) "" [], ["1", "2"])) describe "runAssignment" $ do it "drops anonymous nodes before matching symbols" $ - runAssignment red (makeState "magenta red" [Rose (rec Magenta 0 7) [], Rose (rec Red 8 11) []]) `shouldBe` Result [] (Just (AssignmentState 11 (Info.SourcePos 1 12) "" [], Out "red")) + runAssignment red (makeState "magenta red" [Rose (rec Magenta 0 7) [], Rose (rec Red 8 11) []]) `shouldBe` Result Nothing (Just (AssignmentState 11 (Info.SourcePos 1 12) "" [], Out "red")) it "does not drop anonymous nodes after matching" $ - runAssignment red (makeState "red magenta" [Rose (rec Red 0 3) [], Rose (rec Magenta 4 11) []]) `shouldBe` Result [] (Just (AssignmentState 3 (Info.SourcePos 1 4) " magenta" [Rose (rec Magenta 4 11) []], Out "red")) + runAssignment red (makeState "red magenta" [Rose (rec Red 0 3) [], Rose (rec Magenta 4 11) []]) `shouldBe` Result Nothing (Just (AssignmentState 3 (Info.SourcePos 1 4) " magenta" [Rose (rec Magenta 4 11) []], Out "red")) it "does not drop anonymous nodes when requested" $ - runAssignment ((,) <$> magenta <*> red) (makeState "magenta red" [Rose (rec Magenta 0 7) [], Rose (rec Red 8 11) []]) `shouldBe` Result [] (Just (AssignmentState 11 (Info.SourcePos 1 12) "" [], (Out "magenta", Out "red"))) + runAssignment ((,) <$> magenta <*> red) (makeState "magenta red" [Rose (rec Magenta 0 7) [], Rose (rec Red 8 11) []]) `shouldBe` Result Nothing (Just (AssignmentState 11 (Info.SourcePos 1 12) "" [], (Out "magenta", Out "red"))) rec :: symbol -> Int -> Int -> Record '[Maybe symbol, Range, SourceSpan] rec symbol start end = Just symbol :. Range start end :. Info.SourceSpan (Info.SourcePos 1 (succ start)) (Info.SourcePos 1 (succ end)) :. Nil From 7fcb2c75aa680e708389e49ce32a16bfe52121fe Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 6 Jun 2017 09:06:31 -0400 Subject: [PATCH 89/89] Remove the weakening performed for functions. --- src/Semantic.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Semantic.hs b/src/Semantic.hs index 78204d5ba..984563354 100644 --- a/src/Semantic.hs +++ b/src/Semantic.hs @@ -59,7 +59,7 @@ diffBlobPairs renderer = fmap toS . distributeFoldMap (diffBlobPair renderer) . -- | A task to parse a pair of 'SourceBlob's, diff them, and render the 'Diff'. diffBlobPair :: DiffRenderer output -> Both SourceBlob -> Task output diffBlobPair renderer blobs = case (renderer, effectiveLanguage) of - (ToCDiffRenderer, Just Language.Python) -> run (\ source -> parse pythonParser source >>= decorate (declarationAlgebra (Proxy :: Proxy Python.Error) source) . hoistCofree (weaken . weaken :: Union fs a -> Union (Declaration.Function ': Declaration.Method ': fs) a)) diffLinearly (renderToC blobs) + (ToCDiffRenderer, Just Language.Python) -> run (\ source -> parse pythonParser source >>= decorate (declarationAlgebra (Proxy :: Proxy Python.Error) source) . hoistCofree (weaken :: Union fs a -> Union (Declaration.Method ': fs) a)) diffLinearly (renderToC blobs) (ToCDiffRenderer, _) -> run (\ source -> parse syntaxParser source >>= decorate (syntaxDeclarationAlgebra source)) diffTerms (renderToC blobs) (JSONDiffRenderer, Just Language.Python) -> run (parse pythonParser) diffLinearly (renderJSONDiff blobs) (JSONDiffRenderer, _) -> run (decorate identifierAlgebra <=< parse syntaxParser) diffTerms (renderJSONDiff blobs)