The Trunk: EToys-nice.273.mcz

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

The Trunk: EToys-nice.273.mcz

commits-2
Nicolas Cellier uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-nice.273.mcz

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

Name: EToys-nice.273
Author: nice
Time: 30 October 2016, 10:44:29.550936 pm
UUID: 1a0759cf-36bc-4250-af34-ade1200d312a
Ancestors: EToys-nice.272

Remove obsolete code-generation methods

=============== Diff against EToys-nice.272 ===============

Item was removed:
- ----- Method: AssignmentNode>>sizeForEffect: (in category '*Etoys-Squeakland-code generation') -----
- sizeForEffect: encoder
-
- ^(value sizeForValue: encoder)
- + (variable sizeForStorePop: encoder)!

Item was removed:
- ----- Method: AssignmentNode>>sizeForValue: (in category '*Etoys-Squeakland-code generation') -----
- sizeForValue: encoder
-
- ^(value sizeForValue: encoder)
- + (variable sizeForStore: encoder)!

Item was removed:
- ----- Method: BlockNode>>emitForEvaluatedEffect:on: (in category '*Etoys-Squeakland-code generation') -----
- emitForEvaluatedEffect: stack on: aStream
-
- self returns
- ifTrue:
- [self emitForEvaluatedValue: stack on: aStream.
- stack pop: 1]
- ifFalse:
- [self emitExceptLast: stack on: aStream.
- statements last emitForEffect: stack on: aStream]!

Item was removed:
- ----- Method: BlockNode>>sizeForEvaluatedEffect: (in category '*Etoys-Squeakland-code generation') -----
- sizeForEvaluatedEffect: encoder
-
- self returns ifTrue: [^self sizeForEvaluatedValue: encoder].
- ^(self sizeExceptLast: encoder)
- + (statements last sizeForEffect: encoder)!

Item was removed:
- ----- Method: BlockNode>>sizeForEvaluatedValue: (in category '*Etoys-Squeakland-code generation') -----
- sizeForEvaluatedValue: encoder
-
- ^(self sizeExceptLast: encoder)
- + (statements last sizeForValue: encoder)!

Item was removed:
- ----- Method: BlockNode>>sizeForValue: (in category '*Etoys-Squeakland-code generation') -----
- sizeForValue: encoder
- nArgsNode := encoder encodeLiteral: arguments size.
- remoteCopyNode := encoder encodeSelector: #blockCopy:.
- size := (self sizeForEvaluatedValue: encoder)
- + (self returns ifTrue: [0] ifFalse: [1]). "endBlock"
- arguments := arguments collect:  "Chance to prepare debugger remote temps"
- [:arg | arg asStorableNode: encoder].
- arguments do: [:arg | size := size + (arg sizeForStorePop: encoder)].
- ^1 + (nArgsNode sizeForValue: encoder)
- + (remoteCopyNode size: encoder args: 1 super: false) + 2 + size!

Item was removed:
- ----- Method: CascadeNode>>sizeForValue: (in category '*Etoys-Squeakland-code generation') -----
- sizeForValue: encoder
-
- | size |
- size := (receiver sizeForValue: encoder) + (messages size - 1 * 2).
- messages do: [:aMessage | size := size + (aMessage sizeForValue: encoder)].
- ^size!

Item was removed:
- ----- Method: Collection>>toBraceStack: (in category '*Etoys-Squeakland-private') -----
- toBraceStack: itsSize
- "Push receiver's elements onto the stack of thisContext sender.  Error if receiver does
- not have itsSize elements or if receiver is unordered.
- Do not call directly: this is called by {a. b} := ... constructs."
-
- self size ~= itsSize ifTrue:
- [self error: 'Trying to store ', self size printString,
- ' values into ', itsSize printString, ' variables.'].
- thisContext sender push: itsSize fromIndexable: self!

Item was removed:
- ----- Method: LeafNode>>emitForEffect:on: (in category '*Etoys-Squeakland-code generation') -----
- emitForEffect: stack on: strm
-
- ^self!

Item was removed:
- ----- Method: LeafNode>>sizeForEffect: (in category '*Etoys-Squeakland-code generation') -----
- sizeForEffect: encoder
-
- ^0!

Item was removed:
- ----- Method: LiteralNode>>emitForValue:on: (in category '*Etoys-Squeakland-code generation') -----
- emitForValue: stack on: strm
-
- code < 256
- ifTrue: [strm nextPut: code]
- ifFalse: [self emitLong: LoadLong on: strm].
- stack push: 1!

Item was removed:
- ----- Method: MessageNode>>sizeForEffect: (in category '*Etoys-Squeakland-code generation') -----
- sizeForEffect: encoder
-
- special > 0
- ifTrue: [^self perform: (MacroSizers at: special) with: encoder with: false].
- ^super sizeForEffect: encoder!

Item was removed:
- ----- Method: MessageNode>>sizeForValue: (in category '*Etoys-Squeakland-code generation') -----
- sizeForValue: encoder
- | total argSize |
- special > 0
- ifTrue: [^self perform: (MacroSizers at: special) with: encoder with: true].
- receiver == NodeSuper
- ifTrue: [selector := selector copy "only necess for splOops"].
- total := selector size: encoder args: arguments size super: receiver == NodeSuper.
- receiver == nil
- ifFalse: [total := total + (receiver sizeForValue: encoder)].
- sizes := arguments collect:
- [:arg |
- argSize := arg sizeForValue: encoder.
- total := total + argSize.
- argSize].
- ^total!

Item was removed:
- ----- Method: MessageNode>>sizeIf:value: (in category '*Etoys-Squeakland-code generation') -----
- sizeIf: encoder value: forValue
- | thenExpr elseExpr branchSize thenSize elseSize |
- thenExpr := arguments at: 1.
- elseExpr := arguments at: 2.
- (forValue
- or: [(thenExpr isJust: NodeNil)
- or: [elseExpr isJust: NodeNil]]) not
- "(...not ifTrue: avoids using ifFalse: alone during this compile)"
- ifTrue:  "Two-armed IFs forEffect share a single pop"
- [^ super sizeForEffect: encoder].
- forValue
- ifTrue:  "Code all forValue as two-armed"
- [elseSize := elseExpr sizeForEvaluatedValue: encoder.
- thenSize := (thenExpr sizeForEvaluatedValue: encoder)
- + (thenExpr returns
- ifTrue: [0]  "Elide jump over else after a return"
- ifFalse: [self sizeJump: elseSize]).
- branchSize := self sizeBranchOn: false dist: thenSize]
- ifFalse:  "One arm is empty here (two-arms code forValue)"
- [(elseExpr isJust: NodeNil)
- ifTrue:
- [elseSize := 0.
- thenSize := thenExpr sizeForEvaluatedEffect: encoder.
- branchSize := self sizeBranchOn: false dist: thenSize]
- ifFalse:
- [thenSize := 0.
- elseSize := elseExpr sizeForEvaluatedEffect: encoder.
- branchSize := self sizeBranchOn: true dist: elseSize]].
- sizes := Array with: thenSize with: elseSize.
- ^ (receiver sizeForValue: encoder) + branchSize
- + thenSize + elseSize!

Item was removed:
- ----- Method: MessageNode>>sizeToDo:value: (in category '*Etoys-Squeakland-code generation') -----
- sizeToDo: encoder value: forValue
- " var := rcvr. L1: [var <= arg1] Bfp(L2) [block body. var := var + inc] Jmp(L1) L2: "
- | loopSize initStmt test block incStmt blockSize blockVar initSize limitInit |
- block := arguments at: 3.
- blockVar := block firstArgument.
- initStmt := arguments at: 4.
- test := arguments at: 5.
- incStmt := arguments at: 6.
- limitInit := arguments at: 7.
- initSize := initStmt sizeForEffect: encoder.
- limitInit == nil
- ifFalse: [initSize := initSize + (limitInit sizeForEffect: encoder)].
- blockSize := (block sizeForEvaluatedEffect: encoder)
- + (incStmt sizeForEffect: encoder) + 2.  "+2 for Jmp backward"
- loopSize := (test sizeForValue: encoder)
- + (self sizeBranchOn: false dist: blockSize)
- + blockSize.
- sizes := Array with: blockSize with: loopSize.
- ^ initSize + loopSize
- + (forValue ifTrue: [1] ifFalse: [0])    " +1 for value (push nil) "!

Item was removed:
- ----- Method: MessageNode>>sizeWhile:value: (in category '*Etoys-Squeakland-code generation') -----
- sizeWhile: encoder value: forValue
- "L1: ... Bfp(L2) ... Jmp(L1) L2: nil (nil for value only);
- justStmt, wholeLoop, justJump."
- | cond stmt stmtSize loopSize branchSize |
- cond := receiver.
- stmt := arguments at: 1.
- stmtSize := (stmt sizeForEvaluatedEffect: encoder) + 2.
- branchSize := self sizeBranchOn: (selector key == #whileFalse:)  "Btp for whileFalse"
- dist: stmtSize.
- loopSize := (cond sizeForEvaluatedValue: encoder)
- + branchSize + stmtSize.
- sizes := Array with: stmtSize with: loopSize.
- ^ loopSize    " +1 for value (push nil) "
- + (forValue ifTrue: [1] ifFalse: [0])!

Item was removed:
- ----- Method: ParseNode>>emitLong:code:on: (in category '*Etoys-Squeakland-code generation') -----
- emitLong: dist code: longCode on: aStream
- "Force a two-byte jump."
- | code distance |
- code := longCode.
- distance := dist.
- distance < 0
- ifTrue:
- [distance := distance + 1024.
- code := code - 4]
- ifFalse:
- [distance > 1023 ifTrue: [distance := -1]].
- distance < 0
- ifTrue:
- [self error: 'A block compiles more than 1K bytes of code']
- ifFalse:
- [aStream nextPut: distance // 256 + code.
- aStream nextPut: distance \\ 256]!

Item was removed:
- ----- Method: ParseNode>>sizeBranchOn:dist: (in category '*Etoys-Squeakland-code generation') -----
- sizeBranchOn: condition dist: dist
- dist = 0 ifTrue: [^1].
- ^ condition
- ifTrue: [2]  "Branch on true is always 2 bytes"
- ifFalse: [self sizeShortOrLong: dist]!

Item was removed:
- ----- Method: ParseNode>>sizeForEffect: (in category '*Etoys-Squeakland-code generation') -----
- sizeForEffect: encoder
-
- ^(self sizeForValue: encoder) + 1!

Item was removed:
- ----- Method: ParseNode>>sizeForReturn: (in category '*Etoys-Squeakland-code generation') -----
- sizeForReturn: encoder
-
- ^(self sizeForValue: encoder) + 1!

Item was removed:
- ----- Method: ParseNode>>sizeJump: (in category '*Etoys-Squeakland-code generation') -----
- sizeJump: dist
-
- dist = 0 ifTrue: [^0].
- ^self sizeShortOrLong: dist!

Item was removed:
- ----- Method: ReturnNode>>emitForReturn:on: (in category '*Etoys-Squeakland-code generation') -----
- emitForReturn: stack on: strm
-
- expr emitForReturn: stack on: strm.
- pc := strm position!

Item was removed:
- ----- Method: ReturnNode>>emitForValue:on: (in category '*Etoys-Squeakland-code generation') -----
- emitForValue: stack on: strm
-
- expr emitForReturn: stack on: strm.
- pc := strm position!

Item was removed:
- ----- Method: ReturnNode>>sizeForReturn: (in category '*Etoys-Squeakland-code generation') -----
- sizeForReturn: encoder
-
- ^expr sizeForReturn: encoder!

Item was removed:
- ----- Method: ReturnNode>>sizeForValue: (in category '*Etoys-Squeakland-code generation') -----
- sizeForValue: encoder
-
- ^expr sizeForReturn: encoder!

Item was removed:
- ----- Method: SelectorNode>>emit:args:on: (in category '*Etoys-Squeakland-code generation') -----
- emit: stack args: nArgs on: strm
-
- self emit: stack
- args: nArgs
- on: strm
- super: false!