VM Maker: VMMaker.oscog-eem.2938.mcz

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

VM Maker: VMMaker.oscog-eem.2938.mcz

commits-2
 
Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2938.mcz

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

Name: VMMaker.oscog-eem.2938
Author: eem
Time: 20 January 2021, 7:17:02.642438 pm
UUID: d0498f14-0205-4d9d-925f-016fa65847a3
Ancestors: VMMaker.oscog-eem.2937

SmartSyntaxPlugin Slang compilation:
Eliminate a little dead code following final conditional return.
Don't bother to check for failure when returning results of positive32BitIntegerFor:, which cannot fail.
Cleaner adding of prologs/epilogs to parseTree's statements.

=============== Diff against VMMaker.oscog-eem.2937 ===============

Item was changed:
  ----- Method: SmartSyntaxPluginTMethod>>endsWithMethodReturnExpression (in category 'testing') -----
  endsWithMethodReturnExpression
  | operativeReturn methodReturns |
  operativeReturn := (parseTree statements last isReturn
  and: [parseTree statements last expression isLeaf])
  ifTrue: [(parseTree statements last: 2) first]
  ifFalse: [parseTree statements last].
+ (operativeReturn isSend
+ and: [operativeReturn selector == #ifFalse:
+ and: [operativeReturn receiver isSend
+ and: [operativeReturn receiver selector == #failed
+ and: [operativeReturn receiver receiver isLeaf
+ and: [operativeReturn receiver receiver name = 'interpreterProxy'
+ and: [operativeReturn args size = 1
+ and: [operativeReturn args first statements first isReturn]]]]]]]) ifTrue:
+ [operativeReturn := operativeReturn args first statements first expression].
  methodReturns := #( methodReturnReceiver
  methodReturnFloat:
  methodReturnValue:
  methodReturnInteger:
  methodReturnBool:
  methodReturnString:
+ methodReturnStringOrNil:
+
+ asBooleanObj
+ asFloatObj
+ asPositiveIntegerObj
+ asSmallIntegerObj).
- methodReturnStringOrNil:).
  ^operativeReturn isSend
  and: [(methodReturns includes: operativeReturn selector)
  or: [operativeReturn isConditionalSend
  and: [(operativeReturn args collect: [:stmts| stmts statements last]) anySatisfy:
  [:stmt| stmt isSend and: [methodReturns includes: stmt selector]]]]]!

Item was changed:
  ----- Method: SmartSyntaxPluginTMethod>>extractPrimitiveDirectives (in category 'specifying primitives') -----
  extractPrimitiveDirectives
  "Save selector in fullSelector and args in fullArgs.  Scan top-level statements for a directive of the form:
 
  self
  primitive: <string>
  or
  self
  primitive: <string>
  parameters: <list of class names>
  or
  self
  primitive: <string>
  parameters: <list of class names>
  receiver: <class name>
 
  or an assignment of that expression to a local, and manipulate the state and parse tree accordingly."
 
  parseTree setStatements: (Array streamContents:
  [:sStream |
  parseTree statements do:
  [:stmt |
  (self primitiveDirectiveWasHandled: stmt on: sStream)
  ifFalse: [sStream nextPut: stmt]]]).
  isPrimitive
  ifTrue:
  [export := true.
+ parseTree statements addAllFirst: self namedPrimitiveProlog.
- parseTree
- setStatements: self namedPrimitiveProlog,
- parseTree statements.
  self fixUpReturns.
  self replaceSizeMessages.
  ^true]
  ifFalse: [self removeFinalSelfReturnIn: nil].
  ^false!

Item was changed:
  ----- Method: SmartSyntaxPluginTMethod>>resultExpressionCanFail: (in category 'private') -----
  resultExpressionCanFail: aTSendNode
+ "Neither asSmallIntegerObj nor asBooleanObj nor asPositiveIntegerObj can fail.
+ asPositiveIntegerObj maps to positive32BitIntegerFor: which uses
+ eeInstantiateSmallClassIndex:format:numSlots: which does not GC and does not fail."
+ ^(#(asSmallIntegerObj asPositiveIntegerObj asBooleanObj nilObject trueObject falseObject) includes: aTSendNode selector) not!
- "Neither asSmallIntegerObj nor asBooleanObj can fail."
- ^(#(asSmallIntegerObj asBooleanObj nilObject trueObject falseObject) includes: aTSendNode selector) not!

Item was changed:
  ----- Method: TMethod>>preparePrimitivePrologue (in category 'primitive compilation') -----
  preparePrimitivePrologue
  "Add a prolog and postlog to a primitive method. The prolog copies any instance variables referenced by this primitive method into local variables. The postlog copies values of assigned-to variables back into the instance. The names of the new locals are added to the local variables list.
 
  The declarations dictionary defines the types of any non-integer variables (locals, arguments, or instance variables). In particular, it may specify the types:
 
  int * -- an array of 32-bit values (e.g., a BitMap)
  short * -- an array of 16-bit values (e.g., a SoundBuffer)
  char * -- an array of unsigned bytes (e.g., a String)
  double -- a double precision floating point number (e.g., 3.14159)
 
  Undeclared variables are taken to be integers and will be converted from Smalltalk to C ints."
 
  "Current restrictions:
  o method must not contain message sends
  o method must not allocate objects
  o method must not manipulate raw oops
  o method cannot access class variables
  o method can only return an integer"
 
  | prolog postlog instVarsUsed varsAssignedTo instVarList primArgCount varName endsWithReturn aClass |
  self assert: selector ~~ #setInterpreter:.
  aClass := definingClass.
  prolog := OrderedCollection new.
  postlog := OrderedCollection new.
  instVarsUsed := self freeVariableReferences asSet.
  varsAssignedTo := self variablesAssignedTo asSet.
  instVarList := aClass allInstVarNames.
  primArgCount := args size.
 
  "add receiver fetch and arg conversions to prolog"
  prolog addAll: self fetchRcvrExpr.
  1 to: args size do: [:argIndex |
  varName := args at: argIndex.
  prolog addAll:
  (self argConversionExprFor: varName stackIndex: args size - argIndex)].
 
  "add success check to postlog"
  postlog addAll: self checkSuccessExpr.
 
  "add instance variable fetches to prolog and instance variable stores to postlog"
  1 to: instVarList size do: [:varIndex |
  varName := instVarList at: varIndex.
  (instVarsUsed includes: varName) ifTrue: [
  locals add: varName.
  prolog addAll: (self instVarGetExprFor: varName offset: varIndex - 1).
  (varsAssignedTo includes: varName) ifTrue: [
  postlog addAll: (self instVarPutExprFor: varName offset: varIndex - 1)]]].
  prolog addAll: self checkSuccessExpr.
 
  ((locals includes: 'rcvr') or: [(locals intersection: args) notEmpty]) ifTrue:
  [self error: 'local name conflicts with instance variable name'].
  locals add: 'rcvr'; addAll: args.
  args := args class new.
  endsWithReturn := self endsWithReturn.
  self fixUpReturns: primArgCount postlog: postlog.
 
+ parseTree statements addAllFirst: prolog.
+ endsWithReturn ifFalse:
+ [postlog addAll: (self popArgsExpr: primArgCount).
+ parseTree statements addAllLast: postlog].
- endsWithReturn
- ifTrue: [parseTree setStatements: prolog, parseTree statements]
- ifFalse: [
- postlog addAll: (self popArgsExpr: primArgCount).
- parseTree setStatements: prolog, parseTree statements, postlog].
  !