ParseTreeRewriter tests & behavior

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

ParseTreeRewriter tests & behavior

S11001001
http://scompall.nocandysw.com/gst/ptrtests.st

This is a file of SUnit tests for "PTR" (ParseTreeRewriter).  (It's been
updated since I last mentioned it.)  File it in (fix up
RBSmallDictionary first, as described in list thread "copying
RBSmallDictionary") to load and execute the tests.

There are two behavioral changes I'm interested in making; both current
behaviors are tested in testCascadeCornerCases.  They are well described
by their comments:

     "If replacement isn't a cascade or message, it drops.  Oddly, PTS

      doesn't count this as a 'not found'; it doesn't descend into

      arguments of the original node in this case, and, as a result, it

      won't descend to the receiver.  I am considering changing this

      behavior, in which case use this shouldBe: content:

 

         obj.

         z display: x; display: y; nextPut: $q"

     self rewrite: 'stream display: obj.

                    (stream display: z) display: (stream display: x);

                        display: y; nextPut: $q'

          from: '``@receiver display: ``@object'

          to: '``@object'

          shouldBe: 'obj.

                     (stream display: z) display: (stream display: x);

                         display: y; nextPut: $q'.

I have a fix to make PTR (oops) count dropped replacements as 'not
found', so the PTR will descend into the originals' arguments.

Next up:

     "lookForMoreMatchesInContext: doesn't copy its values.  As a

      result, replacement in successful replacements later rejected by

      acceptCascadeNode: (after lookForMoreMatchesInContext: is already

      sent, after all) depends on where in the subtree a match

      happened.  This is why selective recursion into successful

      matches before giving outer contexts the opportunity to reject

      them isn't so great.  It can be 'fixed' by #copy-ing each value

      in the context before descending into it.  I would prefer

      removing that 'feature' altogether, and my own 'trampoline'

      rewriter does just this.

 

      This replacement test depends on the non-message rejection oddity

      described above, though fixing that won't entirely fix this

      issue.  If that issue is fixed, this test will require adding

      another pattern that successfully transforms one of the cascade's

      messages."

     self rewrite: 'qqq display: (qqq display: sss);

                        display: [qqq display: sss]'

          from: '``@recv display: ``@obj'

          to: '[``@obj]'

          shouldBe: 'qqq display: (qqq display: sss);

                         display: [[sss]]'.

The whole recusivelySearchInContext mess bothers me to some degree.  In
this small but important way, I can fight the insanity by simply copying
context nodes before descent.  This will make [[sss]] in the replacement
above be the less sensible [qqq display: sss], but only because of my
dislike of PTR's selective recursion -- it would seem to be more
consistent with the intent of selective recursion.

These behavioral changes are solely in the interest of making PTR more
consistent; my refactoring of PTR supports the current behavior, and can
be adjusted with even less change to fit the behavior I've described
above.  If you don't agree, it's not a big deal; my rewriter subclass
works around both issues by crudely cutting down on behavior complexity.

Strictly speaking, these changes will mean that PTR becomes
behavior-incompatible with the stock ParseTreeRewriter.

What do you think?

--
Stephen Compall
http://scompall.nocandysw.com/blog


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

Re: ParseTreeRewriter tests & behavior

Paolo Bonzini
 > What do you think?

I agree with the first, which is probably a bug (it's also in VW, by the
way).  The second I cannot parse:

>     self rewrite: 'qqq display: (qqq display: sss);
>                        display: [qqq display: sss]'
>          from: '``@recv display: ``@obj'
>          to: '[``@obj]'
>          shouldBe: 'qqq display: (qqq display: sss);
>                         display: [[sss]]'.

I would think that it becomes "qqq: display: [sss]; display: [[sss]]".
Why shouldn't this be the case?  What happens if you fix the first bug?

Paolo


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

Re: ParseTreeRewriter tests & behavior

S11001001
On Wed, 2007-01-10 at 13:21 +0100, Paolo Bonzini wrote:
> I agree with the first, which is probably a bug (it's also in VW, by the
> way).

As with Squeak.  The Refactory-Parser code seems to be largely untouched
from when it was last released by Brant & Roberts.

The fix is to add 'notFound add: each.' just below the warning that gets
printed if a replacement node isn't a message or cascade.

Do all the tests (taking out the gst-specific code, of course) pass in
VW?

> The second I cannot parse:
>
> >     self rewrite: 'qqq display: (qqq display: sss);
> >                        display: [qqq display: sss]'
> >          from: '``@recv display: ``@obj'
> >          to: '[``@obj]'
> >          shouldBe: 'qqq display: (qqq display: sss);
> >                         display: [[sss]]'.
>
> I would think that it becomes "qqq: display: [sss]; display: [[sss]]".
> Why shouldn't this be the case?
In the second message, qqq display: [qqq display: sss]: before
recusivelySearchInContext is sent from the rule, after match:inContext:
but before foundMatchFor:, which produces the final expansion:

RBVariableNode('``@recv') -> RBVariableNode(qqq)
RBVariableNode('``@obj') -> RBBlockNode([qqq display: sss])

The block node doesn't match.  So you descend into its body, which
descends into its statements, and matches the message, replacing it:

RBVariableNode('``@obj') -> RBBlockNode([[sss]])

The RBBlockNode that is the value of the Association above is == to the
block node that was originally destructured from the source.  So it
doesn't matter whether we accept [[sss]] as an expansion; even if we
don't, the originally matched message now is qqq display: [[sss]].

> What happens if you fix the first bug?

That will hide the example I've given, because arguments in the notFound
messages are rewritten.  This means, however, that certain arguments, or
parts thereof, will be rewritten *again*.  This can be seen by adding a
'`@recv value' => '`@recv' rewrite rule.  I'll add this to ptrtests.st
later.

--
Stephen Compall
http://scompall.nocandysw.com/blog

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

signature.asc (196 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: ParseTreeRewriter tests & behavior

S11001001
On Wed, 2007-01-10 at 14:14 -0600, Stephen Compall wrote:
> That will hide the example I've given, because arguments in the notFound
> messages are rewritten.  This means, however, that certain arguments, or
> parts thereof, will be rewritten *again*.  This can be seen by adding a
> '`@recv value' => '`@recv' rewrite rule.  I'll add this to ptrtests.st
> later.

I've named the two issues non-messages-are-found and rsic-doesnt-copy,
respectively.  Below are three new tests demonstrating three situations.

If you agree that both issues should be fixed, attached is a patch that
fixes them.  They succeed against a different version of the tests in:

http://scompall.nocandysw.com/gst/ptrtests-post-nmaf+rdc.st

Meanwhile, from http://scompall.nocandysw.com/gst/ptrtests.st :

    [| rsicCopiesPRewriter sourceExp |
     rsicCopiesPRewriter := self rewriterClass new
           replace: '``@recv display: ``@obj' with: '[``@obj]';
           replace: '`@recv value' with: '`@recv';
           yourself.
     sourceExp := RBParser parseExpression:
         'qqq display: (qqq display: sss value value);
              display: [qqq display: sss value value]'.
     self assert: (self rewriting: sourceExp
                        with: rsicCopiesPRewriter
                        yields:
                            'qqq display: (qqq display: sss value value);
                              display: [[sss value]]')
          description:
              'neither non-messages-are-found nor rsic-doesnt-copy fixed'.
     self deny: (self rewriting: sourceExp
                      with: rsicCopiesPRewriter
                      yields:
                          'qqq display: [sss value];
                            display: [[sss]]')
          description:
              'non-messages-are-found fixed, but not rsic-doesnt-copy'.
     self deny: (self rewriting: sourceExp
                      with: rsicCopiesPRewriter
                      yields:
                          'qqq display: [sss value];
                            display: [[sss value]]')
          description:
              'both non-messages-are-found and rsic-doesnt-copy fixed'.]
        value.

--
Stephen Compall
http://scompall.nocandysw.com/blog

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

pts-nmaf+rdc+rbsmalldict.diff (1K) Download Attachment
signature.asc (196 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: ParseTreeRewriter tests & behavior

S11001001
On Wed, 2007-01-10 at 22:53 -0600, Stephen Compall wrote:
> If you agree that both issues should be fixed, attached is a patch that
> fixes them.

Sorry, here is a changelog:

2006-01-10  Stephen Compall  <[hidden email]>

        * compiler/ParseTreeSearcher.st: Copy context node pattern
        variables before rewriting them, in case they are mutated and
        their containing replacement is later rejected.  Mark each
        message in a cascade node with an invalid replacement for
        visiting of its arguments.
        (RBSmallDictionary class>>#new:): Remove; fixes findIndex:.

--
Stephen Compall
http://scompall.nocandysw.com/blog

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

signature.asc (196 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

ParseTreeRewriter refactoring

S11001001
In reply to this post by S11001001
On Wed, 2007-01-10 at 22:53 -0600, Stephen Compall wrote:
> I've named the two issues non-messages-are-found and rsic-doesnt-copy,
> respectively.

Attached are alternate refactorings of ParseTreeRewriter.

ptrrefactor-pre-fixes.diff passes
http://scompall.nocandysw.com/gst/ptrtests.st .  It doesn't include
fixes for the two issues.

ptrrefactor-post-fixes.diff passes
http://scompall.nocandysw.com/gst/ptrtests-post-nmaf+rdc.st .  It does
include fixes.

Both have changelog entries.

--
Stephen Compall
http://scompall.nocandysw.com/blog

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

ptrrefactor-pre-fixes.diff (12K) Download Attachment
ptrrefactor-post-fixes.diff (12K) Download Attachment
signature.asc (196 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: ParseTreeRewriter tests & behavior

Paolo Bonzini
In reply to this post by S11001001
Stephen Compall wrote:
> http://scompall.nocandysw.com/gst/ptrtests.st
>
> This is a file of SUnit tests for "PTR" (ParseTreeRewriter).  (It's been
> updated since I last mentioned it.)  File it in (fix up
> RBSmallDictionary first, as described in list thread "copying
> RBSmallDictionary") to load and execute the tests.

Ok, I agree with you that both changes are desirable.  I've posted to
c.l.s for help.

I'll include ptrtests.st in 2.4 (possibly backporting it later to
2.3.1).  The full fix for RBSmallDictionary, which passes ptrtests.st,
is this:

--- orig/compiler/ParseTreeSearcher.st
+++ mod/compiler/ParseTreeSearcher.st
@@ -277,6 +277,17 @@ LookupTable variableSubclass: #RBSmallDi

  !RBSmallDictionary methodsFor: 'private'!

+whileGrowingAt: key put: value
+    tally := tally + 1.
+    self primAt: self size put: key.
+    self valueAt: self size put: value!
+
+incrementTally
+    tally := tally + 1.
+    ^tally > self primSize
+       ifTrue: [ self grow ];
+       yourself!
+
  findIndex: anObject
      "Tries to see if anObject exists as an indexed variable. As soon
as nil
      or anObject is found, the index of that slot is answered"
@@ -288,6 +299,7 @@ findIndex: anObject
          (element isNil or: [ element = anObject ])
              ifTrue: [ ^i ]
      ].
+    tally = self primSize ifTrue: [ self grow ].
      ^self size + 1! !

  RBSmallDictionary class
@@ -299,7 +311,7 @@ new
      ^self new: 2!

  new: anInteger
-    ^(self basicNew: anInteger) initialize: anInteger! !
+    ^(self primNew: anInteger) initialize: anInteger! !


  RBProgramNodeVisitor subclass: #ParseTreeSearcher


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

Re: ParseTreeRewriter refactoring

Paolo Bonzini
In reply to this post by S11001001
> * compiler/ParseTreeSearcher.st (ParseTreeRewriter): Add
> visitField:ofNode:, visitNode:onMatch:, visitListField:ofNode:,

I'm not a big fan of computing selector names.  Sorry. :-(

However, I like visitNode:onMatch: and the acceptCascadeNode: fixes.
With your tests in hand I can take care of merging only those parts.

Thanks!

Paolo


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

Re: ParseTreeRewriter refactoring

S11001001
On Thu, 2007-01-11 at 09:57 +0100, Paolo Bonzini wrote:
> I'm not a big fan of computing selector names.  Sorry. :-(

That's too bad.  I liked them because those accept*: can be pushed up to
RBProgramNodeVisitor.  Is there another way to generalize
RBProgramNodeVisitor in such a fashion?

> However, I like visitNode:onMatch: and the acceptCascadeNode: fixes.
> With your tests in hand I can take care of merging only those parts.

Might visitNodeList:visitor:onMatch: also be included and used where
relevant?  This gives just enough dynamism that my rewriter subclass
works without overriding accept*:.

--
Stephen Compall
http://scompall.nocandysw.com/blog

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

signature.asc (196 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: ParseTreeRewriter tests & behavior

S11001001
In reply to this post by Paolo Bonzini
On Thu, 2007-01-11 at 09:52 +0100, Paolo Bonzini wrote:
> I'll include ptrtests.st in 2.4 (possibly backporting it later to
> 2.3.1).

Thanks; please use http://scompall.nocandysw.com/gst/ptrtests-post-nmaf
+rdc.st if you haven't it already, assuming -- I suppose -- c.l.s agrees
that the behavior changes are worthwhile.

> The full fix for RBSmallDictionary, which passes ptrtests.st,
> is this:
>
> @@ -299,7 +311,7 @@ new
>       ^self new: 2!
>
>   new: anInteger
> -    ^(self basicNew: anInteger) initialize: anInteger! !
> +    ^(self primNew: anInteger) initialize: anInteger! !

*Ah*.  Thanks.

--
Stephen Compall
http://scompall.nocandysw.com/blog

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

signature.asc (196 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: ParseTreeRewriter refactoring

Paolo Bonzini
In reply to this post by S11001001

>> However, I like visitNode:onMatch: and the acceptCascadeNode: fixes.
>> With your tests in hand I can take care of merging only those parts.
>
> Might visitNodeList:visitor:onMatch: also be included and used where
> relevant?  This gives just enough dynamism that my rewriter subclass
> works without overriding accept*:.

Oh, yes, of course.  Just no selector names, everything else is ok.  Do
you need "visitor: #foo" or can it be hardcoded too #visitNode:onMatch:?

Thanks,

Paolo


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

Re: ParseTreeRewriter refactoring

S11001001
I'm a Lisper at heart, and it shows.  List list list list list!

On Thu, 2007-01-11 at 10:58 +0100, Paolo Bonzini wrote:
> Oh, yes, of course.  Just no selector names, everything else is ok.  Do
> you need "visitor: #foo" or can it be hardcoded too #visitNode:onMatch:?

I added it so that "node list" node fields would have the same semantic
possibilities as direct node fields, for both node lists (like
sequence's #statements) and argument lists (like sequence's #arguments).
I originally had #visitNodeList:onMatch: and
#visitArgumentList:onMatch:, but because I only used them once each in
#visitListField:onMatch: and #visitArgumentsField:onMatch: respectively,
I merged them.

Since the field visitors are gone, reintroducing #visitNodeList:onMatch:
and #visitArgumentList:onMatch: would be worthwhile again, but they need
to either call visitNodeList:visitor:onMatch: or be mostly copies of one
another, but for one selector.

If it influences you at all, I need to specialize
#visitNodeList:visitor:onMatch: or its equivalent, and I'll probably
remerge them in my subclass if you split them completely, just to reduce
duplication in my own code.  I'm no duplicatoclast in PTR, though, as
you can see by the definitions of #visit{Node,Argument}:onMatch:.  :)

I wish these sorts of things would be done by arguments, rather than
selectors :/

--
Stephen Compall
http://scompall.nocandysw.com/blog

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

signature.asc (196 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: ParseTreeRewriter refactoring

Paolo Bonzini
> Since the field visitors are gone, reintroducing #visitNodeList:onMatch:
> and #visitArgumentList:onMatch: would be worthwhile again, but they need
> to either call visitNodeList:visitor:onMatch: or be mostly copies of one
> another, but for one selector.

I'm losing you a bit, but I think this would please me a lot more.  Can
you prepare the patch?  (Sorry for the burden.)

> I wish these sorts of things would be done by arguments, rather than
> selectors :/

Agreed (I think...).

Paolo


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

Re: ParseTreeRewriter refactoring

S11001001
On Thu, 2007-01-11 at 11:30 +0100, Paolo Bonzini wrote:
> > Since the field visitors are gone, reintroducing #visitNodeList:onMatch:
> > and #visitArgumentList:onMatch: would be worthwhile again, but they need
> > to either call visitNodeList:visitor:onMatch: or be mostly copies of one
> > another, but for one selector.
>
> I'm losing you a bit, but I think this would please me a lot more.  Can
> you prepare the patch?  (Sorry for the burden.)

It's no problem.  However, do you mean you want the reintroduced methods
to call visitNodeList:visitor:onMatch:, or to be mostly copies of one
another?

I'll post a patch against the last version I have (which shouldn't
conflict, as it would be stuck in the middle of code you want to keep)
in 10 hours or so, after a good sleep.

> > I wish these sorts of things would be done by arguments, rather than
> > selectors :/
>
> Agreed (I think...).

I hate when interfaces split up concepts like visitNode: and
visitArgument: that subclassers will obviously want to continue matching
behaviors.  It all trickles down when you write interfaces that wrap
those concepts.  At one point in the refactoring, you could have a stack
like this:

accept*:
  visitListField:ofNode:
    visitCollectionField:visitor:ofNode:
      visitListNode:onMatch:
        visitListNode:visitor:onMatch:
          visitNode:onMatch:

--
Stephen Compall
http://scompall.nocandysw.com/blog

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

signature.asc (196 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: ParseTreeRewriter refactoring

Paolo Bonzini

>> I'm losing you a bit, but I think this would please me a lot more.  Can
>> you prepare the patch?  (Sorry for the burden.)
>
> It's no problem.  However, do you mean you want the reintroduced methods
> to call visitNodeList:visitor:onMatch:, or to be mostly copies of one
> another?

If you can eliminate "visitor:" keyword by having them be mostly copies,
do it.  If you can eliminate "visitor:" and not have them be mostly
copies, even better...

> I'll post a patch against the last version I have (which shouldn't
> conflict, as it would be stuck in the middle of code you want to keep)
> in 10 hours or so, after a good sleep.

Sure.  I don't have a clue what time zone you are in, so...

Paolo


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

Re: ParseTreeRewriter refactoring

S11001001
On Thu, 2007-01-11 at 11:44 +0100, Paolo Bonzini wrote:
> If you can eliminate "visitor:" keyword by having them be mostly copies,
> do it.  If you can eliminate "visitor:" and not have them be mostly
> copies, even better...

I could do it by merging #visitNode:onMatch: and #visitArgument:onMatch:
into calls to #visitNode:withSearches:onMatch:.

The attached patch doesn't do it that way.

> Sure.  I don't have a clue what time zone you are in, so...

UTC-0600, meaning my last message was sent at 4:40 AM.  I should really
learn normal waking hours...

--
Stephen Compall
http://scompall.nocandysw.com/blog

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

visitNodeList-onMatch.diff (2K) Download Attachment
signature.asc (196 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: ParseTreeRewriter refactoring

Paolo Bonzini
In reply to this post by S11001001

> Might visitNodeList:visitor:onMatch: also be included and used where
> relevant?  This gives just enough dynamism that my rewriter subclass
> works without overriding accept*:.

Ok, so here's my take.

As far as I understood, what you want is to not use the new instance if
nothing changed in the parse tree.  Which seems good.

Search for <<< to find the bug fixes; for now I'm not applying them.

Paolo

--- orig/compiler/ParseTreeSearcher.st
+++ mod/compiler/ParseTreeSearcher.st
@@ -758,16 +758,57 @@ foundMatch
     answer := true!
 
 lookForMoreMatchesInContext: oldContext
-    oldContext keysAndValuesDo:
-    [:key :value |
-    (key isString not and: [key recurseInto])
- ifTrue:
-    [oldContext at: key put: (value collect: [:each | self visitNode: each])]]! !
+    oldContext keysAndValuesDo: [:key :value || newValue |
+ (key isString not and: [key recurseInto]) ifTrue: [
+    "Of course, the following statement does nothing without the `deepCopy'
+     which fixes the bug."
+    newValue := oldContext at: key put: value "deepCopy <<<".
+    self visitNodes: newValue
+         onMatch: [:newValue |
+     oldContext at: key put: newValue]]]! !
 
 !ParseTreeRewriter methodsFor: 'visiting'!
 
-visitArguments: aNodeCollection
-    ^aNodeCollection collect: [:each | self visitArgument: each]! !
+visitNode: aNode
+    ^self visitNode: aNode searches: searches onMatch: [:newNode |]!
+
+visitNodes: aNodeList
+    ^self visitNodes: aNodeList searches: searches onMatch: [:newNodes |]!
+
+visitNodes: aNodeList onMatch: aBlock
+    ^self visitNodes: aNodeList searches: searches onMatch: aBlock!
+
+visitArgument: aNode
+    ^self visitNode: aNode searches: argumentSearches onMatch: [:newNode |]!
+
+visitArguments: aNodeList
+    ^self visitNodes: aNodeList searches: argumentSearches onMatch: [:newNodes |]!
+
+visitArguments: aNodeList onMatch: aBlock
+    ^self visitNodes: aNodeList searches: argumentSearches onMatch: aBlock!
+
+visitNode: aNode searches: theseSearches onMatch: aBlock
+    "Visit aNode, sending visitNode:'s answer to aBlock if
+     performSearches:on: finds a match."
+    | newNode |
+    newNode := self performSearches: theseSearches on: aNode.
+    ^newNode isNil ifTrue: [aNode acceptVisitor: self.  aNode]
+   ifFalse: [aBlock value: newNode.  newNode]!
+
+visitNodes: aNodeList searches: theseSearches onMatch: aBlock
+    "Answer aNodeList but with each element replaced by the result of
+     visitNode:onMatch: with said element (and a block of my own).  If
+     any matches occur, I'll call aBlock afterwards with the
+     replacement of aNodeList before answering it."
+    | replacementList rlHasMatch |
+    rlHasMatch := false.
+    replacementList := aNodeList collect: [:eltNode |
+ self visitNode: eltNode
+     searches: theseSearches
+     onMatch: [:newElt | rlHasMatch := true]].
+    ^rlHasMatch
+ ifTrue: [aBlock value: replacementList.  replacementList]
+ ifFalse: [aNodeList]! !
 
 !ParseTreeRewriter methodsFor: 'visitor-double dispatching'!
 
@@ -782,28 +823,35 @@ acceptBlockNode: aBlockNode
     aBlockNode arguments: (self visitArguments: aBlockNode arguments).
     aBlockNode body: (self visitNode: aBlockNode body)!
 
+searchCascadeNodeMessage: aMessageNode messagesTo: newMessages
+    "Helper for acceptCascadeNode: -- descend to aMessageNode, but no
+     further.  Add the resulting message or cascade of messages from
+     the tree rule's foundMatchFor: to newMessages and answer said
+     result if a match is found.  Add aMessageNode to newMessages and
+     answer nil otherwise."
+    | answer newNode |
+    answer := self performSearches: searches on: aMessageNode.
+    newNode := answer ifNil: [aMessageNode].
+    newNode isCascade
+ ifTrue: [newMessages addAll: newNode messages]
+ ifFalse: [newMessages add:
+      (newNode isMessage ifTrue: [newNode]
+ ifFalse: [Warning signal: 'Cannot replace message node inside of cascaded node with non-message node'.
+           "answer := nil. <<<"
+   aMessageNode])].
+    ^answer!
+
 acceptCascadeNode: aCascadeNode
     | newMessages notFound |
     newMessages := OrderedCollection new: aCascadeNode messages size.
     notFound := OrderedCollection new: aCascadeNode messages size.
-    aCascadeNode messages do:
-    [:each |
-    | newNode |
-    newNode := self performSearches: searches on: each.
-    newNode isNil
- ifTrue:
-    [newNode := each.
-    notFound add: newNode].
-    newNode isMessage
- ifTrue: [newMessages add: newNode]
- ifFalse:
-    [newNode isCascade
- ifTrue: [newMessages addAll: newNode messages]
- ifFalse:
-    [Transcript
- show: 'Cannot replace message node inside of cascaded node with non-message node.';
- cr.
-    newMessages add: each]]].
+    aCascadeNode messages do: [:each |
+ (self searchCascadeNodeMessage: each
+      messagesTo: newMessages)
+    isNil ifTrue: [notFound add: each]].
+
+    "Rewrite the receiver once and distribute it among the messages if
+     no replacements were made."
     notFound size == aCascadeNode messages size
  ifTrue:
     [| receiver |

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

Re: ParseTreeRewriter refactoring

S11001001
On Fri, 2007-01-12 at 09:13 +0100, Paolo Bonzini wrote:
> > Might visitNodeList:visitor:onMatch: also be included and used where
> > relevant?  This gives just enough dynamism that my rewriter subclass
> > works without overriding accept*:.
>
> Ok, so here's my take.
>
> As far as I understood, what you want is to not use the new instance if
> nothing changed in the parse tree.  Which seems good.

It also allows visitNode*:*: et al to customize the context in which
replacements are delivered to their final containing slots.

>  lookForMoreMatchesInContext: oldContext
> -    oldContext keysAndValuesDo:
> -    [:key :value |
> -    (key isString not and: [key recurseInto])
> - ifTrue:
> -    [oldContext at: key put: (value collect: [:each | self visitNode: each])]]! !
> +    oldContext keysAndValuesDo: [:key :value || newValue |
> + (key isString not and: [key recurseInto]) ifTrue: [
> +    "Of course, the following statement does nothing without the `deepCopy'
> +     which fixes the bug."
> +    newValue := oldContext at: key put: value "deepCopy <<<".
Please don't use deepCopy here; it copies too much data from the
original tree.  collect: [:node | node copy] does exactly the right
thing in both the single-node and node-collection cases.

> +visitNodes: aNodeList
> +    ^self visitNodes: aNodeList searches: searches onMatch: [:newNodes |]!

Why does this inline visitNodes:onMatch:?  (As with visitArguments:.)

--
Stephen Compall
http://scompall.nocandysw.com/blog

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

signature.asc (196 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: ParseTreeRewriter refactoring

Paolo Bonzini

> Please don't use deepCopy here; it copies too much data from the
> original tree.  collect: [:node | node copy] does exactly the right
> thing in both the single-node and node-collection cases.

No, it does exactly the same:

deepCopy
     "Returns a deep copy of the receiver (the instance variables are
      copies of the receiver's instance variables)"
     | class aCopy num |
     class := self class.
     aCopy := self shallowCopy.
     class isPointers
         ifTrue: [ num := class instSize + self basicSize ]
         ifFalse: [ num := class instSize ].

     " copy the instance variables (if any) "
     1 to: num do: [ :i |
         aCopy instVarAt: i put: (self instVarAt: i) copy.
     ].
     ^aCopy
! !

>> +visitNodes: aNodeList
>> +    ^self visitNodes: aNodeList searches: searches onMatch: [:newNodes |]!
>
> Why does this inline visitNodes:onMatch:?  (As with visitArguments:.)

Just because, I'll undo this inlining.

Thanks,

Paolo


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

Re: ParseTreeRewriter refactoring

S11001001
Paolo Bonzini wrote:
>     " copy the instance variables (if any) "
>     1 to: num do: [ :i |
>         aCopy instVarAt: i put: (self instVarAt: i) copy.

Ah!  For some reason I skimmed over this, assuming there was a deepCopy
at the end of this line rather than a copy.

Attached is a patch that uses the new onMatch: variants in the
accept*Node: methods where feasible, against patch-240.  Most of it was
written by a query-replace-regexp with some reindenting.  It passes
ptrtests-pre-nmaf+rdc.st.

--
Stephen Compall
http://scompall.nocandysw.com/blog

2006-01-12  Stephen Compall  <[hidden email]>

        * compiler/ParseTreeSearcher.st: Use the visit*:onMatch: variants
        of visit*: in accept*Node: methods of ParseTreeRewriter.  Add
        visitNode:onMatch:.

--- orig/compiler/ParseTreeSearcher.st
+++ mod/compiler/ParseTreeSearcher.st
@@ -772,6 +772,9 @@
 visitNode: aNode
     ^self visitNode: aNode searches: searches onMatch: [:newNode |]!
 
+visitNode: aNode onMatch: aBlock
+    ^self visitNode: aNode searches: searches onMatch: aBlock!
+
 visitNodes: aNodeList
     ^self visitNodes: aNodeList onMatch: [:newNodes |]!
 
@@ -813,15 +816,20 @@
 !ParseTreeRewriter methodsFor: 'visitor-double dispatching'!
 
 acceptAssignmentNode: anAssignmentNode
-    anAssignmentNode variable: (self visitNode: anAssignmentNode variable).
-    anAssignmentNode value: (self visitNode: anAssignmentNode value)!
+    self visitNode: anAssignmentNode variable
+ onMatch: [:newField | anAssignmentNode variable: newField].
+    self visitNode: anAssignmentNode value
+ onMatch: [:newField | anAssignmentNode value: newField]!
 
 acceptArrayConstructorNode: anArrayNode
-    anArrayNode body: (self visitNode: anArrayNode body)!
+    self visitNode: anArrayNode body
+ onMatch: [:newField | anArrayNode body: newField]!
 
 acceptBlockNode: aBlockNode
-    aBlockNode arguments: (self visitArguments: aBlockNode arguments).
-    aBlockNode body: (self visitNode: aBlockNode body)!
+    self visitArguments: aBlockNode arguments
+ onMatch: [:newField | aBlockNode arguments: newField].
+    self visitNode: aBlockNode body
+ onMatch: [:newField | aBlockNode body: newField]!
 
 searchCascadeNodeMessage: aMessageNode messagesTo: newMessages
     "Helper for acceptCascadeNode: -- descend to aMessageNode, but no
@@ -854,31 +862,39 @@
      no replacements were made."
     notFound size == aCascadeNode messages size
  ifTrue:
-    [| receiver |
-    receiver := self visitNode: aCascadeNode messages first receiver.
-    newMessages do: [:each | each receiver: receiver]].
+    [self visitNode: aCascadeNode messages first receiver
+  onMatch: [:receiver |
+      newMessages do: [:each | each receiver: receiver]]].
     notFound
- do: [:each | each arguments: (each arguments collect: [:arg | self visitNode: arg])].
+ do: [:each | self visitNodes: each arguments
+  onMatch: [:newArgs | each arguments: newArgs]].
     aCascadeNode messages: newMessages!
 
 acceptMessageNode: aMessageNode
-    aMessageNode receiver: (self visitNode: aMessageNode receiver).
-    aMessageNode
- arguments: (aMessageNode arguments collect: [:each | self visitNode: each])!
+    self visitNode: aMessageNode receiver
+ onMatch: [:newField | aMessageNode receiver: newField].
+    self visitNodes: aMessageNode arguments
+ onMatch: [:newField | aMessageNode arguments: newField]!
 
 acceptMethodNode: aMethodNode
-    aMethodNode arguments: (self visitArguments: aMethodNode arguments).
-    aMethodNode body: (self visitNode: aMethodNode body)!
+    self visitArguments: aMethodNode arguments
+ onMatch: [:newField | aMethodNode arguments: newField].
+    self visitNode: aMethodNode body
+ onMatch: [:newField | aMethodNode body: newField]!
 
 acceptOptimizedNode: anOptimizedNode
-    anOptimizedNode body: (self visitNode: anOptimizedNode body)!
+    self visitNode: anOptimizedNode body
+ onMatch: [:newField | anOptimizedNode body: newField]!
 
 acceptReturnNode: aReturnNode
-    aReturnNode value: (self visitNode: aReturnNode value)!
+    self visitNode: aReturnNode value
+ onMatch: [:newField | aReturnNode value: newField]!
 
 acceptSequenceNode: aSequenceNode
-    aSequenceNode temporaries: (self visitArguments: aSequenceNode temporaries).
-    aSequenceNode statements: (aSequenceNode statements collect: [:each | self visitNode: each])! !
+    self visitArguments: aSequenceNode temporaries
+ onMatch: [:newField | aSequenceNode temporaries: newField].
+    self visitNodes: aSequenceNode statements
+ onMatch: [:newField | aSequenceNode statements: newField]! !
 
 ParseTreeRewriter class
     instanceVariableNames: ''!

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