help-smalltalk
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

[Help-smalltalk] [PATCH] Fix most comment woes


From: Paolo Bonzini
Subject: [Help-smalltalk] [PATCH] Fix most comment woes
Date: Thu, 09 Aug 2007 16:08:11 +0200
User-agent: Thunderbird 2.0.0.6 (Macintosh/20070728)

There is still one disappearing comment when pretty-printing scripts/Convert.st, but most remain.

Paolo
2007-08-09  Paolo Bonzini  <address@hidden>

        * STFileParser.st: Change #parseDoit: to #parseDoit, change
        #parseStatements to include only the block it had inside, localize
        MappedCollection hack in a single place.
        * SIFParser.st: Change #parseStatements to #parseDoit.
        * GSTParser.st: Override #evaluate: to include comments.  Don't
        create MappedCollection here.  Split part of #parseStatements into
        a #parseDoit override.


* looking for address@hidden/smalltalk--devo--2.2--patch-504 to compare with
* comparing to address@hidden/smalltalk--devo--2.2--patch-504
M  packages/stinst/parser/STFileParser.st
M  packages/stinst/parser/SIFParser.st
M  packages/stinst/parser/GSTParser.st
M  packages/stinst/parser/ChangeLog

* modified files

--- orig/packages/stinst/parser/GSTParser.st
+++ mod/packages/stinst/parser/GSTParser.st
@@ -31,7 +31,7 @@
  ======================================================================"
 
 STInST.STFileInParser subclass: GSTFileInParser [
-    | class |
+    | class currentDeclaration |
 
     parseStatements [
         | returnPosition statements node |
@@ -39,25 +39,28 @@ STInST.STFileInParser subclass: GSTFileI
         (currentToken isSpecial and: [currentToken value == $!]) 
           ifTrue: [ ^RBSequenceNode statements: #() ].
 
-        statements := OrderedCollection new.
-
-        (currentToken isSpecial and: [currentToken value == $^]) 
+        node := (currentToken isSpecial and: [currentToken value == $^]) 
             ifTrue: [returnPosition := currentToken start.  
                      self step.
-                     node := RBReturnNode return: returnPosition value: self 
parseAssignment.
-                     self addCommentsTo: node.
-                     statements add: node]
-            ifFalse: [node := self parseAssignment.
-                      self addCommentsTo: node.
-                      statements add: node].
+                     RBReturnNode return: returnPosition value: self 
parseAssignment]
+            ifFalse: [self parseAssignment].
+
+        self addCommentsTo: node.
+        ^RBSequenceNode statements: { node }
+    ]
 
-        (currentToken isSpecial and: [self skipToken: $[])
-            ifTrue: [self parseDeclaration: node. ^nil].
+    parseDoit [
+       | node |
+       node := super parseDoit.
+        (currentToken isSpecial and: [ self skipToken: $[ ])
+            ifTrue: [self parseDeclaration: node statements first. ^nil].
 
-        ^RBSequenceNode statements: statements
+        currentToken isSpecial ifTrue: [ self skipToken: $. ].
+       ^node
     ]
 
     parseDeclaration: node [
+       currentDeclaration := node parent.
         node isMessage ifTrue: [
             (node selectorParts first value = 'subclass:')
                 ifTrue: [self parseClass: node. ^self].
@@ -255,16 +258,13 @@ STInST.STFileInParser subclass: GSTFileI
     ]
     
     parseMethodSource: patternNode on: classNode [
-        "TODO: parse category tag inside methods"
-        | methodNode source start stop |
+        | methodNode start stop |
         
         start := patternNode selectorParts first start - 1.
         methodNode := self parseMethodInto: patternNode.
         stop := currentToken start - 1.
         self skipExpectedToken: $].
-        source := scanner stream copyFrom: start to: stop.
-        source := MappedCollection collection: source map: (1 - start to: 
stop).
-        methodNode source: source.
+        methodNode := self addSourceFrom: start to: stop to: methodNode.
         
         self evaluateMessageOn: classNode
              selector: #methodsFor:
@@ -300,20 +300,41 @@ STInST.STFileInParser subclass: GSTFileI
     ]
     
     evaluateStatement: node [
-        ^self evaluate: (self makeSequenceNode: node).
+       ^self evaluate: (self makeSequenceNode: node)
     ]
     
-    makeSequenceNode: stmt [
+    evaluate: seq [
+       | emptySeq |
+       (currentDeclaration notNil and: [ currentDeclaration comments notEmpty 
])
+           ifTrue: [
+               seq parent isNil
+                   ifTrue: [
+                       seq comments: currentDeclaration comments.
+                       seq parent: currentDeclaration parent ]
+                   ifFalse: [
+                       emptySeq := self makeSequenceNode.
+                       emptySeq comments: currentDeclaration comments.
+                       emptySeq parent: currentDeclaration parent.
+                       super evaluate: emptySeq ] ].
+       currentDeclaration := nil.
+        ^super evaluate: seq
+    ]
+
+    makeSequenceNode [
         | seq |
        seq := RBSequenceNode
             leftBar: nil
             temporaries: #()
             rightBar: nil.
-        seq statements: { stmt }.
         seq periods: #().
+        seq statements: #().
        ^seq
     ]
     
+    makeSequenceNode: stmt [
+        ^self makeSequenceNode statements: { stmt }.
+    ]
+    
     makeClassOf: node [
         ^RBMessageNode
            receiver: node


--- orig/packages/stinst/parser/SIFParser.st
+++ mod/packages/stinst/parser/SIFParser.st
@@ -183,7 +183,7 @@ evaluateGlobalInitializer: stmt
     "Convert `Foo initializer' syntax to GNU Smalltalk file-out syntax."
     | node |
     stmt receiver name = 'Global' ifTrue: [
-       node := self parseStatements.
+       node := self parseDoit.
         scanner stripSeparators.
         self step.
        ^super evaluate: node ].
@@ -197,7 +197,7 @@ evaluateInitializerFor: key in: receiver
     position := currentToken start.
     node := RBOptimizedNode
                 left: position
-                body: self parseStatements
+                body: self parseDoit
                 right: currentToken start.
 
     scanner stripSeparators.


--- orig/packages/stinst/parser/STFileParser.st
+++ mod/packages/stinst/parser/STFileParser.st
@@ -82,17 +82,17 @@ evaluate: node
 !STFileParser methodsFor: 'utility'!
 
 parseStatements
-    ^self parseDoit: [ self parseStatements: false ]!
+    ^self parseStatements: false!
 
-parseDoit: aBlock
-    | node method start stop comments source |
+parseDoit
+    | node start stop comments |
     comments := scanner getComments.
     start := comments isNil
                ifTrue: [ currentToken start - 1 ]
                ifFalse: [ comments first first - 1 ].
        
     tags := nil.
-    node := aBlock value.
+    node := self parseStatements.
     node comments isNil
        ifTrue: [ node comments: comments ]
        ifFalse: [
@@ -102,11 +102,19 @@ parseDoit: aBlock
      other drops the bang because we have a one-token lookahead."
     stop := currentToken start - 2.
 
-    method := RBMethodNode selectorParts: #() arguments: #().
+    ^self addSourceFrom: start to: stop to: node!
+
+addSourceFrom: start to: stop to: node
+    | method source |
+    node isMethod
+       ifTrue: [
+           method := node ]
+       ifFalse: [
+           method := RBMethodNode selectorParts: #() arguments: #().
+           node parent: method ].
     source := scanner stream copyFrom: start to: stop.
     source := MappedCollection collection: source map: (1 - start to: stop).
     method source: source.
-    node parent: method.
     ^node! !
 
 !STFileParser class methodsFor: 'accessing'!
@@ -153,7 +161,7 @@ parseDoits
     | node |
     [
        self atEnd ifTrue: [ ^false ].
-       node := self parseStatements.
+       node := self parseDoit.
         scanner stripSeparators.
        self evaluate: node
     ] whileFalse: [
@@ -172,9 +180,7 @@ parseMethodFromFile
     "One -1 accounts for base-1 vs. base-0 (as above), the
      other drops the bang because we have a one-token lookahead."
     stop := currentToken start - 2.
-    source := scanner stream copyFrom: start to: stop.
-    source := MappedCollection collection: source map: (1 - start to: stop).
-    node source: source.
+    node := self addSourceFrom: start to: stop to: node.
 
     scanner stripSeparators.
     self step.           "gobble method terminating bang"




reply via email to

[Prev in Thread] Current Thread [Next in Thread]