[PATCH 0/3] rewrite parsing of literal arrays and fix compilation of ##(...) within arrays

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
6 messages Options
Reply | Threaded
Open this post in threaded view
|

[PATCH 0/3] rewrite parsing of literal arrays and fix compilation of ##(...) within arrays

Paolo Bonzini-2
Hi all,

please review!

Unfortunately, this change introduces a new kind of parse tree node,
and thus requires modifying all visitors to support the new node.  This
is a small backwards incompatibility.

Gwen, please note a small change to the VisualGST syntax highlighter.
I have not tested it, but all combinations of old (before this patch)
and new code should be okay.  "#(" and ")" will not be highlighted
with new parser and old syntax highlighter, but that's just a nit.

Paolo


Paolo Bonzini (3):
  stinst: extract RBParser/RBScanner tests to new files
  stinst: prepare for rewrite of #(...) parsing
  stinst: rewrite parsing of literal arrays and fix compilation of ##(...)
    within arrays

 ChangeLog                                |   4 +
 kernel/SeqCollect.st                     |  15 +++
 packages/blox/browser/ChangeLog          |   4 +
 packages/blox/browser/PCode.st           |  13 +++
 packages/stinst/parser/ChangeLog         |  22 +++++
 packages/stinst/parser/RBFormatter.st    |   9 ++
 packages/stinst/parser/RBParseNodes.st   | 158 ++++++++++++++++++++++++++++++-
 packages/stinst/parser/RBParser.st       | 132 ++++++++++++++++----------
 packages/stinst/parser/RBParserTests.st  | 103 ++++++++++++++++++++
 packages/stinst/parser/RBScannerTests.st | 103 ++++++++++++++++++++
 packages/stinst/parser/RBToken.st        |  23 +++++
 packages/stinst/parser/RewriteTests.st   |  66 -------------
 packages/stinst/parser/STCompiler.st     |  17 +++-
 packages/stinst/parser/package.xml       |   2 +
 packages/visualgst/SyntaxHighlighter.st  |   7 ++
 15 files changed, 562 insertions(+), 116 deletions(-)
 create mode 100644 packages/stinst/parser/RBParserTests.st
 create mode 100644 packages/stinst/parser/RBScannerTests.st

--
1.8.4.2


_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

[PATCH 1/3] stinst: extract RBParser/RBScanner tests to new files

Paolo Bonzini-2
packages/stinst/parser:
2014-01-07  Paolo Bonzini <[hidden email]>

        * RBParserTests.st: New, extracted from RewriteTests.st.
        * RBScannerTests.st: New, extracted from RewriteTests.st.
        * RewriteTests.st: Remove code extracted to new files.
---
 packages/stinst/parser/ChangeLog         |  6 +++
 packages/stinst/parser/RBParserTests.st  | 71 ++++++++++++++++++++++++++++++++
 packages/stinst/parser/RBScannerTests.st | 50 ++++++++++++++++++++++
 packages/stinst/parser/RewriteTests.st   | 64 ----------------------------
 packages/stinst/parser/package.xml       |  2 +
 5 files changed, 129 insertions(+), 64 deletions(-)
 create mode 100644 packages/stinst/parser/RBParserTests.st
 create mode 100644 packages/stinst/parser/RBScannerTests.st

diff --git a/packages/stinst/parser/ChangeLog b/packages/stinst/parser/ChangeLog
index 2bd7eeb..4add5b9 100644
--- a/packages/stinst/parser/ChangeLog
+++ b/packages/stinst/parser/ChangeLog
@@ -1,3 +1,9 @@
+2014-01-07  Paolo Bonzini <[hidden email]>
+
+ * RBParserTests.st: New, extracted from RewriteTests.st.
+ * RBScannerTests.st: New, extracted from RewriteTests.st.
+ * RewriteTests.st: Remove code extracted to new files.
+
 2013-12-19  Holger Hans Peter Freyther  <[hidden email]>
 
  * STCompiler.st: Rename STCompiler>>#addPool: to
diff --git a/packages/stinst/parser/RBParserTests.st b/packages/stinst/parser/RBParserTests.st
new file mode 100644
index 0000000..f569821
--- /dev/null
+++ b/packages/stinst/parser/RBParserTests.st
@@ -0,0 +1,71 @@
+"======================================================================
+|
+|   Smalltalk in Smalltalk RBParser tests
+|
+|
+ ======================================================================"
+
+"======================================================================
+|
+| Copyright 2007, 2013, 2014 Free Software Foundation, Inc.
+|
+| This file is part of GNU Smalltalk.
+|
+| GNU Smalltalk is free software; you can redistribute it and/or modify it
+| under the terms of the GNU General Public License as published by the Free
+| Software Foundation; either version 2, or (at your option) any later version.
+|
+| GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
+| ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
+| FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
+| details.
+|
+| You should have received a copy of the GNU General Public License along with
+| GNU Smalltalk; see the file COPYING.  If not, write to the Free Software
+| Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.  
+|
+ ======================================================================"
+
+
+TestCase subclass: TestParser [
+    <comment: 'Test aspects of the RBParser'>
+
+    testNumberParsing [
+
+        | node |
+        node := RBParser parseExpression: '3'.
+        self assert: node value = 3.
+        node := RBParser parseExpression: '-3'.
+        self assert: node value = -3.
+        node := RBParser parseExpression: '-16r3'.
+        self assert: node value = -3.
+        node := RBParser parseExpression: '16r-3'.
+        self assert: node value = -3.
+        node := RBParser parseExpression: '- 16r3'.
+        self assert: node value = -3.
+        node := RBParser parseExpression: '16r-3.23'.
+        self assert: node value = 16r-3.23.
+        node := RBParser parseExpression: '16r-3s23_0'.
+        self assert: node value = 16r-3s23_0.
+        node := RBParser parseExpression: '3_000_000'.
+        self assert: node value = 3_000_000.
+        node := RBParser parseExpression: '3_000_000e1233'.
+        self assert: node value = 3_000_000e1233.
+        node := RBParser parseExpression: '3_000_000d1233'.
+        self assert: node value = 3_000_000d1233.
+        node := RBParser parseExpression: '3_000_000q1233'.
+        self assert: node value = 3_000_000q1233.
+    ]
+
+    testLiteralArrayParsing [
+        | node |
+
+        node := RBParser parseExpression: '#(-3 -2 -16r1)'.
+        self assert: node value first = -3.
+        self assert: node value second = -2.
+        self assert: node value third = -1.
+
+        node := RBParser parseExpression: '#(16r-1)'.
+        self assert: node value first = -1.
+    ]
+]
diff --git a/packages/stinst/parser/RBScannerTests.st b/packages/stinst/parser/RBScannerTests.st
new file mode 100644
index 0000000..41ecfd9
--- /dev/null
+++ b/packages/stinst/parser/RBScannerTests.st
@@ -0,0 +1,50 @@
+"======================================================================
+|
+|   Smalltalk in Smalltalk RBScanner tests
+|
+|
+ ======================================================================"
+
+"======================================================================
+|
+| Copyright 2007, 2013, 2014 Free Software Foundation, Inc.
+|
+| This file is part of GNU Smalltalk.
+|
+| GNU Smalltalk is free software; you can redistribute it and/or modify it
+| under the terms of the GNU General Public License as published by the Free
+| Software Foundation; either version 2, or (at your option) any later version.
+|
+| GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
+| ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
+| FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
+| details.
+|
+| You should have received a copy of the GNU General Public License along with
+| GNU Smalltalk; see the file COPYING.  If not, write to the Free Software
+| Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.  
+|
+ ======================================================================"
+
+
+TestCase subclass: TestScanner [
+    <comment: 'I do test the RBScanner/Tokenizer.'>
+
+    testScanner [
+        | scanner num |
+        scanner := RBScanner on: '3' readStream.
+        num := scanner next.
+        self assert: num value = 3.
+    ]
+
+    testScannerConcatStream [
+        | scanner num |
+        "This is different to >>#testScanner by using a different kind of stream with
+        a different species."
+
+        scanner := RBScanner on: (Kernel.ConcatenatedStream with: '3' readStream).
+        num := scanner next.
+        self assert: num value = 3.
+    ]
+]
+
diff --git a/packages/stinst/parser/RewriteTests.st b/packages/stinst/parser/RewriteTests.st
index 3712f92..322ac38 100644
--- a/packages/stinst/parser/RewriteTests.st
+++ b/packages/stinst/parser/RewriteTests.st
@@ -331,70 +331,6 @@ TestCase subclass: TestFormat [
     ]
 ]
 
-TestCase subclass: TestScanner [
-    <comment: 'Test aspects of the RBScanner'>
-
-    testScanner [
-        | scanner num |
-        scanner := RBScanner on: '3' readStream.
-        num := scanner next.
-        self assert: num value = 3.
-    ]
-
-    testScannerConcatStream [
-        | scanner num |
-        "This is different to >>#testScanner by using a different kind of stream with
-        a different species."
-
-        scanner := RBScanner on: (Kernel.ConcatenatedStream with: '3' readStream).
-        num := scanner next.
-        self assert: num value = 3.
-    ]
-]
-
-TestCase subclass: TestParser [
-    <comment: 'Test aspects of the RBParser'>
-
-    testNumberParsing [
-
-        | node |
-        node := RBParser parseExpression: '3'.
-        self assert: node value = 3.
-        node := RBParser parseExpression: '-3'.
-        self assert: node value = -3.
-        node := RBParser parseExpression: '-16r3'.
-        self assert: node value = -3.
-        node := RBParser parseExpression: '16r-3'.
-        self assert: node value = -3.
-        node := RBParser parseExpression: '- 16r3'.
-        self assert: node value = -3.
-        node := RBParser parseExpression: '16r-3.23'.
-        self assert: node value = 16r-3.23.
-        node := RBParser parseExpression: '16r-3s23_0'.
-        self assert: node value = 16r-3s23_0.
-        node := RBParser parseExpression: '3_000_000'.
-        self assert: node value = 3_000_000.
-        node := RBParser parseExpression: '3_000_000e1233'.
-        self assert: node value = 3_000_000e1233.
-        node := RBParser parseExpression: '3_000_000d1233'.
-        self assert: node value = 3_000_000d1233.
-        node := RBParser parseExpression: '3_000_000q1233'.
-        self assert: node value = 3_000_000q1233.
-    ]
-
-    testLiteralArrayParsing [
-        | node |
-
-        node := RBParser parseExpression: '#(-3 -2 -16r1)'.
-        self assert: node value first = -3.
-        self assert: node value second = -2.
-        self assert: node value third = -1.
-
-        node := RBParser parseExpression: '#(16r-1)'.
-        self assert: node value first = -1.
-    ]
-]
-
 TestCase subclass: TestRewrite [
     <comment: 'I test that rewriting a method for the OldSyntaxExport and
     SqueakExporter will pick up the new code.'>
diff --git a/packages/stinst/parser/package.xml b/packages/stinst/parser/package.xml
index 6102af7..f3516fc 100644
--- a/packages/stinst/parser/package.xml
+++ b/packages/stinst/parser/package.xml
@@ -44,6 +44,8 @@
    <filein>STLoaderObjsTests.st</filein>
    <filein>GSTParserTests.st</filein>
    <filein>STCompilerTests.st</filein>
+   <filein>RBScannerTests.st</filein>
+   <filein>RBParserTests.st</filein>
   </test>
 
   <file>ChangeLog</file>
--
1.8.4.2



_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

[PATCH 2/3] stinst: prepare for rewrite of #(...) parsing

Paolo Bonzini-2
In reply to this post by Paolo Bonzini-2
2014-01-07  Paolo Bonzini  <[hidden email]>

        * kernel/SeqCollect.st: Add #with:allSatisfy:.

packages/blox/browser:
2014-01-07  Paolo Bonzini  <[hidden email]>

        * PCode.st: Add #acceptLiteralArrayNode:.

packages/stinst/parser:
2014-01-07  Paolo Bonzini  <[hidden email]>

        * RBFormatter.st: Add #acceptLiteralArrayNode:.
        * RBParseNodes.st: Implement RBLiteralArrayNode.
        * STCompiler.st: Add #acceptLiteralArrayNode:.
---
 ChangeLog                               |   4 +
 kernel/SeqCollect.st                    |  15 +++
 packages/blox/browser/ChangeLog         |   4 +
 packages/blox/browser/PCode.st          |  13 +++
 packages/stinst/parser/ChangeLog        |   5 +
 packages/stinst/parser/RBFormatter.st   |   9 ++
 packages/stinst/parser/RBParseNodes.st  | 158 +++++++++++++++++++++++++++++++-
 packages/stinst/parser/STCompiler.st    |  17 +++-
 packages/visualgst/SyntaxHighlighter.st |   7 ++
 9 files changed, 230 insertions(+), 2 deletions(-)

diff --git a/ChangeLog b/ChangeLog
index ea47151..2a71965 100644
--- a/ChangeLog
+++ b/ChangeLog
@@ -1,3 +1,7 @@
+2014-01-07  Paolo Bonzini  <[hidden email]>
+
+ * kernel/SeqCollect.st: Add #with:allSatisfy:.
+
 2013-12-14  Holger Hans Peter Freyther  <[hidden email]>
 
  * configure.ac: Check for environ with AC_CHECK_DECLS.
diff --git a/kernel/SeqCollect.st b/kernel/SeqCollect.st
index d79ddaa..74ba166 100644
--- a/kernel/SeqCollect.st
+++ b/kernel/SeqCollect.st
@@ -957,6 +957,21 @@ some access and manipulation methods.'>
     do: [:i | aBlock value: (self at: i)]
     ]
 
+    with: aSequenceableCollection allSatisfy: aBlock [
+ "Evaluate aBlock for each pair of elements took respectively from
+ the receiver and from aSequenceableCollection. Return true if the
+         block returns true for each pair of elements, false otherwise.  Fail
+ if the receiver has not the same size as aSequenceableCollection."
+
+ <category: 'enumerating'>
+ self size = aSequenceableCollection size
+    ifFalse: [^SystemExceptions.InvalidSize signalOn: aSequenceableCollection].
+ 1 to: self size do: [:i |
+            (aBlock value: (self at: i) value: (aSequenceableCollection at: i))
+                ifFalse: [^false]].
+        ^true
+    ]
+
     with: aSequenceableCollection do: aBlock [
  "Evaluate aBlock for each pair of elements took respectively from
  the receiver and from aSequenceableCollection. Fail if the receiver
diff --git a/packages/blox/browser/ChangeLog b/packages/blox/browser/ChangeLog
index 1c1ddee..557908f 100644
--- a/packages/blox/browser/ChangeLog
+++ b/packages/blox/browser/ChangeLog
@@ -1,3 +1,7 @@
+2014-01-07  Paolo Bonzini  <[hidden email]>
+
+ * PCode.st: Add #acceptLiteralArrayNode:.
+
 2010-12-04  Paolo Bonzini  <[hidden email]>
 
  * package.xml: Remove now superfluous <file> tags.
diff --git a/packages/blox/browser/PCode.st b/packages/blox/browser/PCode.st
index 3efa9ca..d85b78f 100644
--- a/packages/blox/browser/PCode.st
+++ b/packages/blox/browser/PCode.st
@@ -372,6 +372,19 @@ STInST.STInST.RBProgramNodeVisitor subclass: SyntaxHighlighter [
  widget highlightAs: #special at: semi ]"]
     ]
 
+    acceptLiteralArrayNode: aLiteralArrayNode [
+ <category: 'visitor-double dispatching'>
+ widget
+    highlightAs: #literal
+    from: aLiteralNode start
+    to: aLiteralNode start + 1.
+        super acceptLiteralArrayNode: aLiteralArrayNode
+ widget
+    highlightAs: #literal
+    from: aLiteralNode stop
+    to: aLiteralNode stop.
+    ]
+
     acceptLiteralNode: aLiteralNode [
  <category: 'visitor-double dispatching'>
  widget
diff --git a/packages/stinst/parser/ChangeLog b/packages/stinst/parser/ChangeLog
index 4add5b9..a1c35cb 100644
--- a/packages/stinst/parser/ChangeLog
+++ b/packages/stinst/parser/ChangeLog
@@ -1,3 +1,8 @@
+2014-01-07  Paolo Bonzini  <[hidden email]>
+
+ * RBFormatter.st: Add #acceptLiteralArrayNode:.
+ * RBParseNodes.st: Implement RBLiteralArrayNode.
+
 2014-01-07  Paolo Bonzini <[hidden email]>
 
  * RBParserTests.st: New, extracted from RewriteTests.st.
diff --git a/packages/stinst/parser/RBFormatter.st b/packages/stinst/parser/RBFormatter.st
index ddd5215..f57f79d 100644
--- a/packages/stinst/parser/RBFormatter.st
+++ b/packages/stinst/parser/RBFormatter.st
@@ -483,6 +483,15 @@ RBProgramNodeVisitor subclass: RBFormatter [
     separatedBy: [codeStream nextPut: $;]]
     ]
 
+    acceptLiteralArrayNode: aLiteralArrayNode [
+ <category: 'visitor-double dispatching'>
+ codeStream nextPutAll: '#('.
+ aLiteralArrayNode nodes
+            do: [:each | self visitNode: each]
+    separatedBy: [codeStream nextPut: $ ].
+ codeStream nextPut: $).
+    ]
+
     acceptLiteralNode: aLiteralNode [
  <category: 'visitor-double dispatching'>
  ^self formatLiteral: aLiteralNode token
diff --git a/packages/stinst/parser/RBParseNodes.st b/packages/stinst/parser/RBParseNodes.st
index 2600497..fe43987 100644
--- a/packages/stinst/parser/RBParseNodes.st
+++ b/packages/stinst/parser/RBParseNodes.st
@@ -76,6 +76,11 @@ Object subclass: RBProgramNodeVisitor [
 
     ]
 
+    acceptLiteralArrayNode: aLiteralArrayNode [
+ <category: 'visitor-double dispatching'>
+ aLiteralArrayNode nodes do: [:each | self visitNode: each]
+    ]
+
     acceptMessageNode: aMessageNode [
  <category: 'visitor-double dispatching'>
  self visitNode: aMessageNode receiver.
@@ -1839,6 +1844,153 @@ Instance Variables:
 
 
 
+RBValueNode subclass: RBLiteralArrayNode [
+    | left right nodes |
+    
+    <category: 'Refactory-Parser'>
+    <comment: 'RBLiteralArrayNode is an AST node that represents a literal array "#(...)".
+
+Instance Variables:
+    nodes   <Array of: RBLiteralNode|RBLiteralArrayNode|RBOptimizedNode>    the items of the array
+    left    <Integer>    position of #(
+    right    <Integer>    position of )
+
+'>
+
+    RBLiteralArrayNode class >> nodes: anArray [
+ <category: 'instance creation'>
+ ^(self new)
+    nodes: anArray;
+    yourself
+    ]
+
+    RBLiteralArrayNode class >> left: leftInteger nodes: anArray right: rightInteger [
+ <category: 'instance creation'>
+ ^(self new)
+    left: leftInteger;
+ nodes: anArray;
+ right: rightInteger;
+    yourself
+    ]
+
+    acceptVisitor: aProgramNodeVisitor [
+ <category: 'visitor'>
+ ^aProgramNodeVisitor acceptLiteralArrayNode: self
+    ]
+
+    compiler: compiler [
+ <category: 'compile-time binding'>
+        nodes do: [:each | each compiler: compiler]
+    ]
+
+    nodes [
+ <category: 'accessing'>
+ ^nodes
+    ]
+
+    nodes: anArray [
+ <category: 'accessing'>
+ nodes := anArray.
+    ]
+
+    children [
+ <category: 'accessing'>
+ ^nodes
+    ]
+
+    left [
+ <category: 'accessing'>
+ ^left
+    ]
+
+    left: anObject [
+ <category: 'accessing'>
+ left := anObject
+    ]
+
+    precedence [
+ <category: 'accessing'>
+ ^0
+    ]
+
+    right [
+ <category: 'accessing'>
+ ^right
+    ]
+
+    right: anObject [
+ <category: 'accessing'>
+ right := anObject
+    ]
+
+    startWithoutParentheses [
+ <category: 'accessing'>
+ ^left
+    ]
+
+    stopWithoutParentheses [
+ <category: 'accessing'>
+ ^right
+    ]
+
+    = anObject [
+ <category: 'comparing'>
+ self == anObject ifTrue: [^true].
+ self class = anObject class ifFalse: [^false].
+ ^self nodes = anObject nodes
+    ]
+
+    equalTo: anObject withMapping: aDictionary [
+ <category: 'comparing'>
+ self class = anObject class ifFalse: [^false].
+ self nodes size = anObject nodes size ifFalse: [^false].
+ ^self nodes with: anObject nodes allSatisfy:
+            [ :n1 :n2 | n1 equalTo: n2 withMapping: aDictionary ]
+    ]
+
+    hash [
+ <category: 'comparing'>
+ ^self nodes hash
+    ]
+
+    postCopy [
+ <category: 'copying'>
+ super postCopy.
+ nodes := nodes collect: [ :each | each copy ]
+    ]
+
+    copyInContext: aDictionary [
+ <category: 'matching'>
+ ^self class nodes: (nodes copyInContext: aDictionary)
+    ]
+
+    match: aNode inContext: aDictionary [
+ <category: 'matching'>
+ aNode class == self class ifFalse: [^false].
+ aNode nodes size == self nodes size ifFalse: [^false].
+ ^self nodes with: aNode nodes allSatisfy:
+    [:ours :theirs | ours match: theirs inContext: aDictionary]
+    ]
+
+    replaceNode: aNode withNode: anotherNode [
+ <category: 'replacing'>
+ nodes keysAndValuesDo: [ :i :each |
+            each == aNode ifTrue: [nodes at: i put: anotherNode]]
+    ]
+
+    directlyUses: aNode [
+ <category: 'testing'>
+ ^nodes anySatisfy: [ :each | each directlyUses: aNode]
+    ]
+
+    references: aVariableName [
+ <category: 'testing'>
+ ^nodes anySatisfy: [ :each | each references: aVariableName]
+    ]
+]
+
+
+
 RBStatementListNode subclass: RBOptimizedNode [
     
     <category: 'Browser-Parser'>
@@ -1851,6 +2003,10 @@ RBOptimizedNode is an AST node that represents ##(...) expressions. These expres
  ^aProgramNodeVisitor acceptOptimizedNode: self
     ]
 
+    compiler: compiler [
+ <category: 'compile-time binding'>
+    ]
+
     isImmediate [
  <category: 'testing'>
  ^true
@@ -3140,7 +3296,7 @@ Instance Variables:
 
     matchLiteral: aNode inContext: aDictionary [
  <category: 'matching'>
- ^aNode class == RBLiteralNode
+       ^(aNode class == RBLiteralNode or: [aNode class == RBLiteralArrayNode])
     and: [(aDictionary at: self ifAbsentPut: [aNode]) = aNode]
     ]
 
diff --git a/packages/stinst/parser/STCompiler.st b/packages/stinst/parser/STCompiler.st
index 098437d..06798e0 100644
--- a/packages/stinst/parser/STCompiler.st
+++ b/packages/stinst/parser/STCompiler.st
@@ -621,11 +621,26 @@ indexed'' bytecode. The resulting stream is
  it represents."
 
  <category: 'visiting RBLiteralNodes'>
- self depthIncr.
  aNode compiler: self.
+ self depthIncr.
  self pushLiteral: aNode value
     ]
 
+    acceptLiteralArrayNode: aNode [
+ "STLiteralNode has one instance variable, the token for the literal
+ it represents."
+
+ <category: 'visiting RBLiteralNodes'>
+        | value |
+ aNode compiler: self.
+        value := aNode nodes collect: [ :each |
+            each isOptimized
+                ifTrue: [ self class evaluate: each body parser: parser ]
+                ifFalse: [ each value ] ].
+ self depthIncr.
+ self pushLiteral: value
+    ]
+
     acceptAssignmentNode: aNode [
  "First compile the assigned, then the assignment to the assignee..."
 
diff --git a/packages/visualgst/SyntaxHighlighter.st b/packages/visualgst/SyntaxHighlighter.st
index 93a008c..84b6dfe 100644
--- a/packages/visualgst/SyntaxHighlighter.st
+++ b/packages/visualgst/SyntaxHighlighter.st
@@ -112,6 +112,13 @@ STInST.STInST.RBProgramNodeVisitor subclass: SyntaxHighlighter [
  textBuffer applyTagByName: #literal startOffset: (aLiteralNode start - 1) endOffset: aLiteralNode stop
     ]
 
+    acceptLiteralArrayNode: aLiteralArrayNode [
+ <category: 'visitor-double dispatching'>
+ textBuffer applyTagByName: #literal startOffset: (aLiteralNode start - 1) endOffset: aLiteralNode start.
+       super acceptLiteralArrayNode: aLiteralArrayNode.
+ textBuffer applyTagByName: #literal startOffset: (aLiteralNode stop - 1) endOffset: aLiteralNode stop.
+    ]
+
     acceptMessageNode: aMessageNode [
  <category: 'visitor-double dispatching'>
 
--
1.8.4.2



_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

[PATCH 3/3] stinst: rewrite parsing of literal arrays and fix compilation of ##(...) within arrays

Paolo Bonzini-2
In reply to this post by Paolo Bonzini-2
packages/stinst/parser:
2014-01-07  Paolo Bonzini  <[hidden email]>

        * RBParser.st: Move parsing of literal arrays to RBParser.  The
        scanner now returns just a RBLiteralArrayStartToken.
        * RBToken.st: Add RBLiteralArrayStartToken.
        * RewriteTests.st: Do not inspect the RBLiteralNode that is
        returned in TestFormat>>#testArrayRewrite, this will be covered
        by the parser tests.
        * RBScannerTests.st: Add tests for ##(...).
        * RBParserTests.st: Add more literal array tests.
---
 packages/stinst/parser/ChangeLog         |  11 +++
 packages/stinst/parser/RBParser.st       | 132 ++++++++++++++++++++-----------
 packages/stinst/parser/RBParserTests.st  |  42 ++++++++--
 packages/stinst/parser/RBScannerTests.st |  53 +++++++++++++
 packages/stinst/parser/RBToken.st        |  23 ++++++
 packages/stinst/parser/RewriteTests.st   |   2 -
 6 files changed, 208 insertions(+), 55 deletions(-)

diff --git a/packages/stinst/parser/ChangeLog b/packages/stinst/parser/ChangeLog
index a1c35cb..9f44c4d 100644
--- a/packages/stinst/parser/ChangeLog
+++ b/packages/stinst/parser/ChangeLog
@@ -1,5 +1,16 @@
 2014-01-07  Paolo Bonzini  <[hidden email]>
 
+ * RBParser.st: Move parsing of literal arrays to RBParser.  The
+ scanner now returns just a RBLiteralArrayStartToken.
+ * RBToken.st: Add RBLiteralArrayStartToken.
+ * RewriteTests.st: Do not inspect the RBLiteralNode that is
+ returned in TestFormat>>#testArrayRewrite, this will be covered
+ by the parser tests.
+ * RBScannerTests.st: Add tests for ##(...).
+ * RBParserTests.st: Add more literal array tests.
+
+2014-01-07  Paolo Bonzini  <[hidden email]>
+
  * RBFormatter.st: Add #acceptLiteralArrayNode:.
  * RBParseNodes.st: Implement RBLiteralArrayNode.
 
diff --git a/packages/stinst/parser/RBParser.st b/packages/stinst/parser/RBParser.st
index b953762..99b8d2b 100644
--- a/packages/stinst/parser/RBParser.st
+++ b/packages/stinst/parser/RBParser.st
@@ -538,9 +538,8 @@ Object subclass: RBParser [
     parseNegatedNumber [
  <category: 'private-parsing'>
  | token |
- self step.
  token := currentToken.
- (token value respondsTo: #negated) ifFalse: [
+ token value isNumber ifFalse: [
     ^self parserError: 'Number expected' ].
  token value negative ifTrue: [
     ^self parserError: 'Positive number expected' ].
@@ -562,17 +561,96 @@ Object subclass: RBParser [
  currentToken isIdentifier ifTrue: [^self parsePrimitiveIdentifier].
  currentToken isLiteral ifTrue: [^self parsePrimitiveLiteral].
  (currentToken isBinary and: [ currentToken value == #- ])
-    ifTrue: [^self parseNegatedNumber].
+    ifTrue: [^self step; parseNegatedNumber].
  currentToken isSpecial
     ifTrue:
  [currentToken value == $[ ifTrue: [^self parseBlock].
  currentToken value == ${ ifTrue: [^self parseArrayConstructor].
  currentToken value == $( ifTrue: [^self parseParenthesizedExpression]].
+ currentToken isLiteralArrayStart ifTrue: [^self parseLiteralArray].
  currentToken isPatternBlock ifTrue: [^self parsePatternBlock].
  currentToken isOptimized ifTrue: [^self parseOptimizedExpression].
  self parserError: 'Variable expected'
     ]
 
+    parseLiteralArray [
+ <category: 'private-parsing'>
+ | arrayStream start stop |
+ arrayStream := WriteStream on: (Array new: 10).
+ start := currentToken start.
+ self step.
+
+ [currentToken isSpecial and: [currentToken value == $)]]
+ whileFalse:
+    [arrayStream nextPut: self parseLiteralArrayParts].
+ stop := currentToken stop.
+ self step.
+ ^RBLiteralArrayNode
+    left: start
+    nodes: arrayStream contents
+    right: stop
+    ]
+
+    parseByteArray [
+        "FIXME: it's ugly that this is both here for #( [1 2 3] )
+         and in RBScanner for #[1 2 3]."
+ <category: 'private-parsing'>
+ | byteStream number start stop |
+ byteStream := WriteStream on: (ByteArray new: 100).
+ start := currentToken start.
+
+ [self step.
+ currentToken isLiteral] whileTrue:
+    [number := currentToken value.
+    (number isInteger and: [number between: 0 and: 255])
+ ifFalse: [self scannerError: 'Expecting 8-bit integer'].
+    byteStream nextPut: number].
+        (currentToken isSpecial and: [ currentToken value == $] ])
+             ifFalse: [self scannerError: ''']'' expected'].
+ stop := currentToken stop.
+ self step. "]"
+ ^RBLiteralNode literalToken: (RBLiteralToken
+    value: byteStream contents
+    start: start
+    stop: stop)
+    ]
+
+    parseLiteralArrayParts [
+ <category: 'private-parsing'>
+ currentToken isLiteral ifTrue: [^self parsePrimitiveLiteral].
+ currentToken isIdentifier
+    ifTrue:
+ [| token value |
+        token := currentToken.
+ value := self parsePrimitiveIdentifier.
+ value isVariable ifTrue: [
+    value := RBLiteralNode literalToken: (RBLiteralToken
+    value: token value asSymbol
+    start: token start
+    stop: token stop)].
+ ^value].
+ currentToken isBinary
+    ifTrue: [
+                | token |
+                token := currentToken.
+                self step.
+                (token value == #- and: [token stop + 1 = currentToken start and: [
+                    currentToken isLiteral and: [
+                    currentToken value isNumber and: [
+                    currentToken value positive ]]]]) ifTrue: [^self parseNegatedNumber].
+                ^RBLiteralNode literalToken: (RBLiteralToken
+    value: token value
+    start: token start
+    stop: token stop)].
+ currentToken isSpecial
+    ifTrue:
+ [currentToken value == $[ ifTrue: [^self parseByteArray].
+ currentToken value == $( ifTrue: [^self parseLiteralArray]].
+ currentToken isLiteralArrayStart ifTrue: [^self parseLiteralArray].
+ currentToken isOptimized ifTrue: [^self parseOptimizedExpression].
+ ^self parserError: 'literal array element expected'
+    ]
+
     parseResourceTag [
  <category: 'private-parsing'>
  | start |
@@ -1206,57 +1284,15 @@ Stream subclass: RBScanner [
  characterType == #binary
     ifTrue: [^(self scanBinary: RBLiteralToken) stop: self previousStepPosition].
  currentCharacter == $' ifTrue: [^self scanStringSymbol].
- currentCharacter == $( ifTrue: [^self scanLiteralArray].
+ currentCharacter == $( ifTrue: [
+                self step.
+                ^RBLiteralArrayStartToken start: tokenStart].
  currentCharacter == $[ ifTrue: [^self scanByteArray].
  currentCharacter == ${ ifTrue: [^self scanQualifier].
  currentCharacter == $# ifTrue: [^self scanExtendedLiterals].
  self scannerError: 'Expecting a literal type'
     ]
 
-    scanLiteralArray [
- <category: 'private-scanning'>
- | arrayStream start |
- arrayStream := WriteStream on: (Array new: 10).
- self step.
- start := tokenStart.
-
- [self stripSeparators.
- tokenStart := stream position.
- currentCharacter == $)]
- whileFalse:
-    [arrayStream nextPut: self scanLiteralArrayParts.
-    buffer reset].
- self step.
- ^RBLiteralToken
-    value: arrayStream contents
-    start: start
-    stop: self previousStepPosition
-    ]
-
-    scanLiteralArrayParts [
- <category: 'private-scanning'>
- currentCharacter == $# ifTrue: [^self scanLiteral].
- characterType == #alphabetic
-    ifTrue:
- [| token value |
- token := self scanSymbol.
- value := token value.
- value == #nil ifTrue: [token value: nil].
- value == #true ifTrue: [token value: true].
- value == #false ifTrue: [token value: false].
- ^token].
- (characterType == #digit
-    or: [currentCharacter == $- and: [(self classify: stream peek) == #digit]])
- ifTrue: [^self scanNumber].
- characterType == #binary
-    ifTrue: [^(self scanBinary: RBLiteralToken) stop: self previousStepPosition].
- currentCharacter == $' ifTrue: [^self scanLiteralString].
- currentCharacter == $$ ifTrue: [^self scanLiteralCharacter].
- currentCharacter == $( ifTrue: [^self scanLiteralArray].
- currentCharacter == $[ ifTrue: [^self scanByteArray].
- ^self scannerError: 'Unknown character in literal array'
-    ]
-
     scanLiteralCharacter [
  <category: 'private-scanning'>
  | token value char tokenStop |
diff --git a/packages/stinst/parser/RBParserTests.st b/packages/stinst/parser/RBParserTests.st
index f569821..f0df0d1 100644
--- a/packages/stinst/parser/RBParserTests.st
+++ b/packages/stinst/parser/RBParserTests.st
@@ -58,14 +58,46 @@ TestCase subclass: TestParser [
     ]
 
     testLiteralArrayParsing [
-        | node |
+        | node nested |
 
         node := RBParser parseExpression: '#(-3 -2 -16r1)'.
-        self assert: node value first = -3.
-        self assert: node value second = -2.
-        self assert: node value third = -1.
+        self assert: node nodes first value = -3.
+        self assert: node nodes second value = -2.
+        self assert: node nodes third value = -1.
 
         node := RBParser parseExpression: '#(16r-1)'.
-        self assert: node value first = -1.
+        self assert: node nodes first value = -1.
+
+        node := RBParser parseExpression: '#(- 2)'.
+        self assert: node nodes first value = #-.
+        self assert: node nodes second value = 2.
+
+        node := RBParser parseExpression: '#(true false nil foo)'.
+        self assert: node nodes first value = true.
+        self assert: node nodes second value = false.
+        self assert: node nodes third value = nil.
+        self assert: node nodes fourth value = #foo.
+
+        node := RBParser parseExpression: '#(1 #[2 3] 4)'.
+        self assert: node nodes first value = 1.
+        self assert: node nodes second value = #[2 3].
+        self assert: node nodes third value = 4.
+
+        node := RBParser parseExpression: '#(1 [2 3] 4)'.
+        self assert: node nodes first value = 1.
+        self assert: node nodes second value = #[2 3].
+        self assert: node nodes third value = 4.
+
+        node := RBParser parseExpression: '#(1 (2 3) 4)'.
+        self assert: node nodes first value = 1.
+        nested := node nodes second.
+        self assert: nested nodes first value = 2.
+        self assert: nested nodes second value = 3.
+        self assert: node nodes third value = 4.
+
+        node := RBParser parseExpression: '#(1 ##(2/3) 4)'.
+        self assert: node nodes first value = 1.
+        self assert: node nodes second class == RBOptimizedNode.
+        self assert: node nodes third value = 4.
     ]
 ]
diff --git a/packages/stinst/parser/RBScannerTests.st b/packages/stinst/parser/RBScannerTests.st
index 41ecfd9..451e876 100644
--- a/packages/stinst/parser/RBScannerTests.st
+++ b/packages/stinst/parser/RBScannerTests.st
@@ -46,5 +46,58 @@ TestCase subclass: TestScanner [
         num := scanner next.
         self assert: num value = 3.
     ]
+
+    testEmbeddedCompiletimeConstant [
+        | scanner token value |
+        scanner := RBScanner on: '#(##(1))' readStream.
+
+        "Token is the literal"
+        token := scanner next.
+        self assert: token isLiteralArrayStart.
+
+        "Token is for optimized code"
+        token := scanner next.
+        self assert: token isOptimized.
+
+        "Token is the '1'"
+        token := scanner next.
+        self assert: token isLiteral.
+        self assert: token value equals: 1.
+
+        "Token is the ')'"
+        token := scanner next.
+        self assert: token isSpecial.
+        self assert: token value equals: $).
+
+        "Token is the ')'"
+        token := scanner next.
+        self assert: token isSpecial.
+        self assert: token value equals: $).
+
+        "And we are at the end"
+        self assert: scanner atEnd.
+    ]
+
+    testDirectCompiletimeConstant [
+        | scanner token |
+        scanner := RBScanner on: '##(1)' readStream.
+
+        "Token is for optimized code"
+        token := scanner next.
+        self assert: token isOptimized.
+
+        "Token is the '1'"
+        token := scanner next.
+        self assert: token isLiteral.
+        self assert: token value equals: 1.
+
+        "Token is the ')'"
+        token := scanner next.
+        self assert: token isSpecial.
+        self assert: token value equals: $).
+
+        "And we are at the end"
+        self assert: scanner atEnd.
+    ]
 ]
 
diff --git a/packages/stinst/parser/RBToken.st b/packages/stinst/parser/RBToken.st
index 399a6db..7c22c9c 100644
--- a/packages/stinst/parser/RBToken.st
+++ b/packages/stinst/parser/RBToken.st
@@ -95,6 +95,11 @@ Object subclass: RBToken [
  ^false
     ]
 
+    isLiteralArrayStart [
+ <category: 'testing'>
+ ^false
+    ]
+
     isOptimized [
  <category: 'testing'>
  ^false
@@ -391,6 +396,24 @@ RBValueToken subclass: RBKeywordToken [
 
 
 
+RBToken subclass: RBLiteralArrayStartToken [
+    
+    <category: 'Refactory-Scanner'>
+    <comment: nil>
+
+    isLiteralArrayStart [
+ <category: 'testing'>
+ ^true
+    ]
+
+    length [
+ <category: 'testing'>
+ ^2
+    ]
+]
+
+
+
 RBToken subclass: RBOptimizedToken [
     
     <category: 'Refactory-Scanner'>
diff --git a/packages/stinst/parser/RewriteTests.st b/packages/stinst/parser/RewriteTests.st
index 322ac38..05130a4 100644
--- a/packages/stinst/parser/RewriteTests.st
+++ b/packages/stinst/parser/RewriteTests.st
@@ -273,8 +273,6 @@ TestCase subclass: TestFormat [
     testArrayRewrite [
  | inp res |
  inp := RBParser parseExpression: '#(16r01 2r01 16rFF )'.
- self assert: inp value = (Array with: 1 with: 1 with: 255).
-
  res := RBFormatter new formatAll: (Array with: inp).
  self assert: res = '#(16r01 2r01 16rFF)'.
     ]
--
1.8.4.2


_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH 2/3] stinst: prepare for rewrite of #(...) parsing

Holger Freyther
In reply to this post by Paolo Bonzini-2
On Tue, Jan 07, 2014 at 12:35:56PM +0100, Paolo Bonzini wrote:

> + self size = aSequenceableCollection size
...
> + 1 to: self size do: [:i |
...
> +        ^true


tabs vs. spaces?

> +    acceptLiteralArrayNode: aLiteralArrayNode [
> + <category: 'visitor-double dispatching'>
> + widget
> +    highlightAs: #literal
> +    from: aLiteralNode start
> +    to: aLiteralNode start + 1.
> +        super acceptLiteralArrayNode: aLiteralArrayNode
> + widget
> +    highlightAs: #literal
> +    from: aLiteralNode stop
> +    to: aLiteralNode stop.

it references aLiteralNode. Probably wrong too.


> +    acceptLiteralArrayNode: aLiteralArrayNode [
> + <category: 'visitor-double dispatching'>
> + textBuffer applyTagByName: #literal startOffset: (aLiteralNode start - 1) endOffset: aLiteralNode start.
> +       super acceptLiteralArrayNode: aLiteralArrayNode.
> + textBuffer applyTagByName: #literal startOffset: (aLiteralNode stop - 1) endOffset: aLiteralNode stop.
> +    ]
> +

You need to add Array to four of these variable names. Found by starting
up gst-browser as found in master. :)

_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [PATCH 0/3] rewrite parsing of literal arrays and fix compilation of ##(...) within arrays

Holger Freyther
In reply to this post by Paolo Bonzini-2
On Tue, Jan 07, 2014 at 12:35:54PM +0100, Paolo Bonzini wrote:

> Unfortunately, this change introduces a new kind of parse tree node,
> and thus requires modifying all visitors to support the new node.  This
> is a small backwards incompatibility.

Lovely! So it does work on '#(##(1/2) 3)' and I felt lucky to try to
import GNUplot now.

        heads := (#((' nohead' ' backhead') (' head') (' heads'))
                    at: (head ifTrue: [ 2 ] ifFalse: [ 1 ]))
                        at: (tail ifTrue: [ 2 ] ifFalse: [ 1 ]).


It fails with "each isOptimized" being DNU for the RBLiteralArrayNode.
I don't have a testcase yet but I think it breaks with a literl array
containing another one. :)


holger

_______________________________________________
help-smalltalk mailing list
[hidden email]
https://lists.gnu.org/mailman/listinfo/help-smalltalk