The Trunk: Compiler-eem.403.mcz

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

The Trunk: Compiler-eem.403.mcz

commits-2
Eliot Miranda uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-eem.403.mcz

==================== Summary ====================

Name: Compiler-eem.403
Author: eem
Time: 19 March 2019, 11:58:47.238202 am
UUID: a0f07dce-0a58-422e-af37-32d5a3bd6546
Ancestors: Compiler-eem.402

Fixed yhree typos in a comment, and improved the class comments for ParseNodeEnumerator & subclass.

=============== Diff against Compiler-eem.402 ===============

Item was changed:
  ParseNodeVisitor subclass: #ParseNodeEnumerator
  instanceVariableNames: 'theBlock theSelectBlock'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Compiler-Support'!
 
+ !ParseNodeEnumerator commentStamp: 'eem 3/19/2019 11:58' prior: 0!
- !ParseNodeEnumerator commentStamp: 'eem 8/31/2010 11:41' prior: 0!
  ParseNodeEnumerator implements ParseNode>>nodesDo:.  It can be used to enumerate an entire tree via
  aParseNode accept: (ParseNodeEnumerator ofBlock: aBlock)
  or selectively, excluding the node and subnodes for which selectBlock answers false, via
  aParseNode accept: (ParseNodeEnumerator
  ofBlock: aBlock
  select: selectBlock)
+ Instance Variables
+ theBlock: <BlockClosure>
+ theSelectBlock: <BlockClosure | nil>
 
+ theBlock
+ - the block that is evaluated with the parse nodes the receiver visits.
+
+ theSelectBlock
+ - an optional block used to select blocks to visit and descend into.
+
  Here's a doIt that generates and compiles the visiting methods:
 
  self superclass selectors do:
  [:s|
  self compile: (String streamContents:
  [:str| | arg |
  arg := 'a', (s allButFirst: 5) allButLast.
  str nextPutAll: s, ' ', arg; crtab;
  nextPutAll: '(theSelectBlock isNil or: [theSelectBlock value: '; nextPutAll: arg; nextPutAll: ']) ifFalse:'; crtab;
  tab: 2; nextPutAll: '[^nil].'; crtab;
  nextPutAll: 'theBlock value: '; nextPutAll: arg; nextPut: $.; crtab;
  nextPutAll: '^super '; nextPutAll: s, ' ', arg])]!

Item was changed:
  ParseNodeEnumerator subclass: #ParseNodeWithPrecedingStatementEnumerator
  instanceVariableNames: 'precedingStatement'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Compiler-Support'!
+
+ !ParseNodeWithPrecedingStatementEnumerator commentStamp: 'eem 3/19/2019 11:55' prior: 0!
+ A ParseNodeWithPrecedingStatementEnumerator is a ParseNodeEnumerator that accepts a binary block in ofBlock:, and hence enumerates statement nodes with their preceding statement, or nil if they are the first.
+
+ Instance Variables
+ precedingStatement: <ParseNode | nil>
+
+ precedingStatement
+ - the preceding statement node, if any
+ !

Item was changed:
  ----- Method: ParseNodeWithPrecedingStatementEnumerator>>ofBlock: (in category 'initialize-release') -----
  ofBlock: aBlock
  "N.B. This enumerator visits a node before any of the node's children.
+ Hence, when enumerating statements in a block, we can ensure that
+ the second argument to the block, the preceding statement, is non-nil
+ only for top-level statements in the block by nilling out precedingStatement
- Hence, when enumewrating statements in a block, we can ensure that
- the second argument to the block, the preceeding statement, is non-nil
- only for top-level statements in the block by nilling out preceedingStatement
  once the block is evaluated. Perhaps stronger would be to capture its value
  in a temporary and nil it before evaluating, but this is good enough."
  theBlock := [:node|
  aBlock value: node value: precedingStatement.
  precedingStatement := nil]!


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Compiler-eem.403.mcz

Eliot Miranda-2


On Tue, Mar 19, 2019 at 11:58 AM <[hidden email]> wrote:
Eliot Miranda uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-eem.403.mcz

==================== Summary ====================

Name: Compiler-eem.403
Author: eem
Time: 19 March 2019, 11:58:47.238202 am
UUID: a0f07dce-0a58-422e-af37-32d5a3bd6546
Ancestors: Compiler-eem.402

Fixed yhree typos in a comment, and improved the class comments for ParseNodeEnumerator & subclass.

Oh really?  Three steps forward, one step back.  Boy this is a humiliating business ;-)
 

=============== Diff against Compiler-eem.402 ===============

Item was changed:
  ParseNodeVisitor subclass: #ParseNodeEnumerator
        instanceVariableNames: 'theBlock theSelectBlock'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Compiler-Support'!

+ !ParseNodeEnumerator commentStamp: 'eem 3/19/2019 11:58' prior: 0!
- !ParseNodeEnumerator commentStamp: 'eem 8/31/2010 11:41' prior: 0!
  ParseNodeEnumerator implements ParseNode>>nodesDo:.  It can be used to enumerate an entire tree via
        aParseNode accept: (ParseNodeEnumerator ofBlock: aBlock)
  or selectively, excluding the node and subnodes for which selectBlock answers false, via
        aParseNode accept: (ParseNodeEnumerator
                                                        ofBlock: aBlock
                                                        select: selectBlock)
+ Instance Variables
+       theBlock:                       <BlockClosure>
+       theSelectBlock:         <BlockClosure | nil>

+ theBlock
+       - the block that is evaluated with the parse nodes the receiver visits.
+
+ theSelectBlock
+       - an optional block used to select blocks to visit and descend into.
+
  Here's a doIt that generates and compiles the visiting methods:

  self superclass selectors do:
        [:s|
        self compile: (String streamContents:
                [:str| | arg |
                arg := 'a', (s allButFirst: 5) allButLast.
                str nextPutAll: s, ' ', arg; crtab;
                        nextPutAll: '(theSelectBlock isNil or: [theSelectBlock value: '; nextPutAll: arg; nextPutAll: ']) ifFalse:'; crtab;
                        tab: 2; nextPutAll: '[^nil].'; crtab;
                        nextPutAll: 'theBlock value: '; nextPutAll: arg; nextPut: $.; crtab;
                        nextPutAll: '^super '; nextPutAll: s, ' ', arg])]!

Item was changed:
  ParseNodeEnumerator subclass: #ParseNodeWithPrecedingStatementEnumerator
        instanceVariableNames: 'precedingStatement'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Compiler-Support'!
+
+ !ParseNodeWithPrecedingStatementEnumerator commentStamp: 'eem 3/19/2019 11:55' prior: 0!
+ A ParseNodeWithPrecedingStatementEnumerator is a ParseNodeEnumerator that accepts a binary block in ofBlock:, and hence enumerates statement nodes with their preceding statement, or nil if they are the first.
+
+ Instance Variables
+       precedingStatement:             <ParseNode | nil>
+
+ precedingStatement
+       - the preceding statement node, if any
+ !

Item was changed:
  ----- Method: ParseNodeWithPrecedingStatementEnumerator>>ofBlock: (in category 'initialize-release') -----
  ofBlock: aBlock
        "N.B. This enumerator visits a node before any of the node's children.
+        Hence, when enumerating statements in a block, we can ensure that
+        the second argument to the block, the preceding statement, is non-nil
+        only for top-level statements in the block by nilling out precedingStatement
-        Hence, when enumewrating statements in a block, we can ensure that
-        the second argument to the block, the preceeding statement, is non-nil
-        only for top-level statements in the block by nilling out preceedingStatement
         once the block is evaluated. Perhaps stronger would be to capture its value
         in a temporary and nil it before evaluating, but this is good enough."
        theBlock := [:node|
                                aBlock value: node value: precedingStatement.
                                precedingStatement := nil]!




--
_,,,^..^,,,_
best, Eliot


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Compiler-eem.403.mcz

Karl Ramberg
I thought that was a deliberate typo. He he

Best,
Karl

On Tue, Mar 19, 2019 at 8:00 PM Eliot Miranda <[hidden email]> wrote:


On Tue, Mar 19, 2019 at 11:58 AM <[hidden email]> wrote:
Eliot Miranda uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-eem.403.mcz

==================== Summary ====================

Name: Compiler-eem.403
Author: eem
Time: 19 March 2019, 11:58:47.238202 am
UUID: a0f07dce-0a58-422e-af37-32d5a3bd6546
Ancestors: Compiler-eem.402

Fixed yhree typos in a comment, and improved the class comments for ParseNodeEnumerator & subclass.

Oh really?  Three steps forward, one step back.  Boy this is a humiliating business ;-)
 

=============== Diff against Compiler-eem.402 ===============

Item was changed:
  ParseNodeVisitor subclass: #ParseNodeEnumerator
        instanceVariableNames: 'theBlock theSelectBlock'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Compiler-Support'!

+ !ParseNodeEnumerator commentStamp: 'eem 3/19/2019 11:58' prior: 0!
- !ParseNodeEnumerator commentStamp: 'eem 8/31/2010 11:41' prior: 0!
  ParseNodeEnumerator implements ParseNode>>nodesDo:.  It can be used to enumerate an entire tree via
        aParseNode accept: (ParseNodeEnumerator ofBlock: aBlock)
  or selectively, excluding the node and subnodes for which selectBlock answers false, via
        aParseNode accept: (ParseNodeEnumerator
                                                        ofBlock: aBlock
                                                        select: selectBlock)
+ Instance Variables
+       theBlock:                       <BlockClosure>
+       theSelectBlock:         <BlockClosure | nil>

+ theBlock
+       - the block that is evaluated with the parse nodes the receiver visits.
+
+ theSelectBlock
+       - an optional block used to select blocks to visit and descend into.
+
  Here's a doIt that generates and compiles the visiting methods:

  self superclass selectors do:
        [:s|
        self compile: (String streamContents:
                [:str| | arg |
                arg := 'a', (s allButFirst: 5) allButLast.
                str nextPutAll: s, ' ', arg; crtab;
                        nextPutAll: '(theSelectBlock isNil or: [theSelectBlock value: '; nextPutAll: arg; nextPutAll: ']) ifFalse:'; crtab;
                        tab: 2; nextPutAll: '[^nil].'; crtab;
                        nextPutAll: 'theBlock value: '; nextPutAll: arg; nextPut: $.; crtab;
                        nextPutAll: '^super '; nextPutAll: s, ' ', arg])]!

Item was changed:
  ParseNodeEnumerator subclass: #ParseNodeWithPrecedingStatementEnumerator
        instanceVariableNames: 'precedingStatement'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Compiler-Support'!
+
+ !ParseNodeWithPrecedingStatementEnumerator commentStamp: 'eem 3/19/2019 11:55' prior: 0!
+ A ParseNodeWithPrecedingStatementEnumerator is a ParseNodeEnumerator that accepts a binary block in ofBlock:, and hence enumerates statement nodes with their preceding statement, or nil if they are the first.
+
+ Instance Variables
+       precedingStatement:             <ParseNode | nil>
+
+ precedingStatement
+       - the preceding statement node, if any
+ !

Item was changed:
  ----- Method: ParseNodeWithPrecedingStatementEnumerator>>ofBlock: (in category 'initialize-release') -----
  ofBlock: aBlock
        "N.B. This enumerator visits a node before any of the node's children.
+        Hence, when enumerating statements in a block, we can ensure that
+        the second argument to the block, the preceding statement, is non-nil
+        only for top-level statements in the block by nilling out precedingStatement
-        Hence, when enumewrating statements in a block, we can ensure that
-        the second argument to the block, the preceeding statement, is non-nil
-        only for top-level statements in the block by nilling out preceedingStatement
         once the block is evaluated. Perhaps stronger would be to capture its value
         in a temporary and nil it before evaluating, but this is good enough."
        theBlock := [:node|
                                aBlock value: node value: precedingStatement.
                                precedingStatement := nil]!




--
_,,,^..^,,,_
best, Eliot



Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Compiler-eem.403.mcz

timrowledge


>
> Fixed yhree typos in a comment, and improved the class comments for ParseNodeEnumerator & subclass.
>
> Oh really?  Three steps forward, one step back.  Boy this is a humiliating business ;-)

You need one of them dehumilifier things.


tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Any program that runs right is obsolete.