VM Maker: VMMaker.oscog-eem.2493.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.2493.mcz

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

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

Name: VMMaker.oscog-eem.2493
Author: eem
Time: 18 December 2018, 6:13:17.614216 pm
UUID: d7437cc5-75c7-4a43-af6b-0f85bf0cebe6
Ancestors: VMMaker.oscog-nice.2492

SmartSyntaxPlugin Slang:
Improve failure guard & result returning interleaving to avoid extra returns and tests of failed (see fixUpReturnOneStmt:on:).  Eliminate the unused suppressFailureGuards: support and inst vars.

Separate argument validation from argument marshalling to fix the bug Levente identified in SocketPlugin>>primitiveSocket:connectTo:port:/primitiveSocketConnectToPort.  Because the old scheme interleaved validation and marshalling, marshalling could be done on invalid objects and cause crashes.  See http://lists.squeakfoundation.org/pipermail/vm-dev/2018-December/029511.html.  Also have teh primitives answer primErrBadArgument if validation fails.

To this end add InterpreterProxy>>isBooleanObject: & InterpreterProxy>>isPositiveMachineIntegerObject:

Remember to mark the 1.14 InterpreterProxy methods as being of that version.

=============== Diff against VMMaker.oscog-nice.2492 ===============

Item was changed:
  ----- Method: CogVMSimulator>>primitiveDoPrimitiveWithArgs (in category 'debugging traps') -----
  primitiveDoPrimitiveWithArgs
  | primIndex |
  primIndex := objectMemory integerValueOf: (self stackValue: 1).
  NewspeakVM ifFalse:
  [transcript nextPutAll: 'DO PRIMITIVE: '; print: (self functionPointerFor: primIndex inClass: nil); cr; flush].
+ (#(76 "primitiveStoreStackp" 188 189 "eval method") includes: primIndex) ifTrue:
- primIndex = 76 ifTrue:
  [self halt].
  ^super primitiveDoPrimitiveWithArgs!

Item was added:
+ ----- Method: InterpreterPrimitives>>isPositiveMachineIntegerObject: (in category 'primitive support') -----
+ isPositiveMachineIntegerObject: oop
+ "Answer if oop is a value of an integer in address range, i.e up to the size of a machine word.
+ The object may be either a positive SmallInteger or a LargePositiveInteger of size <= word size."
+ | ok |
+ (objectMemory isIntegerObject: oop) ifTrue:
+ [^(objectMemory integerValueOf: oop) >= 0].
+
+ (objectMemory isNonIntegerImmediate: oop) ifTrue:
+ [^false].
+
+ ok := objectMemory
+ isClassOfNonImm: oop
+ equalTo: (objectMemory splObj: ClassLargePositiveInteger)
+ compactClassIndex: ClassLargePositiveIntegerCompactIndex.
+ ^ok and: [(objectMemory numBytesOfBytes: oop) <= (self sizeof: #'usqIntptr_t')]!

Item was added:
+ ----- Method: InterpreterProxy>>isBooleanObject: (in category 'testing') -----
+ isBooleanObject: oop
+ <option: #(atLeastVMProxyMajor:minor: 1 15)>
+ ^oop == true or: [oop == false]!

Item was added:
+ ----- Method: InterpreterProxy>>isPositiveMachineIntegerObject: (in category 'testing') -----
+ isPositiveMachineIntegerObject: oop
+ <option: #(atLeastVMProxyMajor:minor: 1 15)>
+ ^oop isInteger and: [oop >= 0 and: [oop digitLength <= Smalltalk wordSize]]!

Item was changed:
  ----- Method: InterpreterProxy>>primitiveFailForFFIException:at: (in category 'other') -----
  primitiveFailForFFIException: exceptionCode at: pc
  <var: 'exceptionCode' type: #usqLong>
  <var: 'pc' type: #usqInt>
+ <option: #(atLeastVMProxyMajor:minor: 1 14)>
  "Set PrimErrFFIException primitive failure and associated exceptionCode (a.k.a.
  osErrorCode) and exceptionPC."
  <primitive: 255>
  osErrorCode := exceptionCode.
  exceptionPC := pc.
  ^primFailCode := PrimErrFFIException!

Item was changed:
  ----- Method: InterpreterProxy>>primitiveFailForOSError: (in category 'other') -----
  primitiveFailForOSError: osError
  <var: 'osError' type: #sqLong>
+ <option: #(atLeastVMProxyMajor:minor: 1 14)>
  "Set PrimErrOSError primitive failure and associated osErrorCode.
  Primitive 255 is called to indicate that we are currently simulating a primitive that should fail and the VM should handle that case appropriately (if supported by the VM)."
  <primitive: 255>
  osErrorCode := osError.
  ^primFailCode := PrimErrOSError!

Item was changed:
  ----- Method: InterpreterProxy>>statNumGCs (in category 'other') -----
  statNumGCs
+ <option: #(atLeastVMProxyMajor:minor: 1 14)>
  ^(Smalltalk vmParameterAt: 7 "statFullGCs") + (Smalltalk vmParameterAt: 9 "statScavenges/statIncrGCs")!

Item was changed:
  ----- Method: InterpreterProxy>>stringForCString: (in category 'testing') -----
  stringForCString: aCString
  "Answer a ByteString object containing the bytes (possibly UTF-8?) in the null-terminated C string aCString."
+ <option: #(atLeastVMProxyMajor:minor: 1 14)>
  <returnTypeC: #sqInt>
  <var: #aCString type: #'char *'>
  self notYetImplemented!

Item was added:
+ ----- Method: NewObjectMemory>>isBooleanObject: (in category 'simulation only') -----
+ isBooleanObject: oop
+ "hack around the CoInterpreter/ObjectMemory split refactoring"
+ <doNotGenerate>
+ ^coInterpreter isBooleanObject: oop!

Item was added:
+ ----- Method: NewObjectMemory>>isPositiveMachineIntegerObject: (in category 'simulation only') -----
+ isPositiveMachineIntegerObject: oop
+ "hack around the CoInterpreter/ObjectMemory split refactoring"
+ <doNotGenerate>
+ ^coInterpreter isPositiveMachineIntegerObject: oop!

Item was added:
+ SmartSyntaxPluginPrologCodeGenerator subclass: #SmartSyntaxPluginAssignmentCodeGenerator
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'VMMaker-SmartSyntaxPlugins'!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>assign:coerceTo:from: (in category 'coercing support') -----
+ assign: variableName coerceTo: cType from: stackIndex
+ ^String streamContents:
+ [:aStream |
+ aStream
+ nextPutAll: variableName;
+ nextPutAll: ' := self cCoerce: (interpreterProxy firstIndexableField:';
+ nextPutAll: (self stackAccessorFor: stackIndex);
+ nextPutAll: ') to: ';
+ store: cType]!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asBooleanValueFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asBooleanValueFrom: stackIndex
+ ^(aString, ' := '), (self loadAs: #booleanValueOf: from: stackIndex)!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asCharPtrFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asCharPtrFrom: stackIndex
+ ^self assign: aString coerceTo: #'char *' from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asCharPtrFrom:andThen: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asCharPtrFrom: stackIndex andThen: valBlock
+ ^self assign: aString coerceTo: #'char *' from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asFloatValueFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asFloatValueFrom: anInteger
+ ^String streamContents:
+ [:aStream |
+ aStream
+ nextPutAll: aString;
+ nextPutAll: ' := interpreterProxy stackFloatValue: ';
+ print: anInteger]!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asIntPtrFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asIntPtrFrom: stackIndex
+ ^self assign: aString coerceTo: #'int *' from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asIntPtrFrom:andThen: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asIntPtrFrom: stackIndex andThen: valBlock
+ ^self assign: aString coerceTo: #'int *' from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asIntegerValueFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asIntegerValueFrom: anInteger
+ ^String streamContents:
+ [:aStream |
+ aStream
+ nextPutAll: aString;
+ nextPutAll: ' := interpreterProxy stackIntegerValue: ';
+ print: anInteger]!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asKindOf:from: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asKindOf: aClass from: stackIndex
+ ^self ccgLoad: aBlock expr: aString asRawOopFrom: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asKindOfIntegerFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asKindOfIntegerFrom: stackIndex
+ ^self ccgLoad: aBlock expr: aString asRawOopFrom: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asMemberOf:from: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asMemberOf: aClass from: stackIndex
+ ^self ccgLoad: aBlock expr: aString asRawOopFrom: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asMemberOfLargeNegativeIntegerFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asMemberOfLargeNegativeIntegerFrom: stackIndex
+ ^self ccgLoad: aBlock expr: aString asRawOopFrom: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asMemberOfLargePositiveIntegerFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asMemberOfLargePositiveIntegerFrom: stackIndex
+ ^self ccgLoad: aBlock expr: aString asRawOopFrom: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asNonIntegerValueFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asNonIntegerValueFrom: stackIndex
+ ^self ccgLoad: aBlock expr: aString asRawOopFrom: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asOopPtrFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asOopPtrFrom: stackIndex
+ ^self assign: aString coerceTo: 'sqInt *' from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asOopPtrFrom:andThen: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asOopPtrFrom: stackIndex andThen: valBlock
+ ^self assign: aString coerceTo: 'sqInt *' from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asRawOopFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asRawOopFrom: stackIndex
+ ^aString, ' := ', (self stackAccessorFor: stackIndex)!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asUnsignedPtrFrom:andThen: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asUnsignedPtrFrom: stackIndex andThen: valBlock
+ ^self assign: aString coerceTo: 'unsigned *' from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asUnsignedValueFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asUnsignedValueFrom: stackIndex
+ ^String streamContents:
+ [:aStream |
+ aStream
+ nextPutAll: aString;
+ nextPutAll: ' := (interpreterProxy bytesPerOop = 4';
+ crtab: 2;
+ nextPutAll: 'ifTrue: [interpreterProxy positive32BitValueOf:';
+ nextPutAll: (self stackAccessorFor: stackIndex);
+ nextPutAll: '] ifFalse: [interpreterProxy positive64BitValueOf:';
+ nextPutAll: (self stackAccessorFor: stackIndex);
+ nextPutAll: '])']!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asWBCharPtrFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asWBCharPtrFrom: stackIndex
+ ^self assign: aString coerceTo: #'char *' from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asWBFloatPtrFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asWBFloatPtrFrom: stackIndex
+ ^self assign: aString coerceTo: #'float *' from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgLoad:expr:asWBIntPtrFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asWBIntPtrFrom: stackIndex
+ ^self assign: aString coerceTo: #'int *' from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>ccgValBlock: (in category 'coercing support') -----
+ ccgValBlock: aString
+ "ignore"!

Item was added:
+ ----- Method: SmartSyntaxPluginAssignmentCodeGenerator>>loadAs:from: (in category 'coercing support') -----
+ loadAs: coercionSelector from: stackIndex
+
+ ^String streamContents:
+ [:aStream |
+ aStream
+ nextPutAll: 'interpreterProxy ';
+ nextPutAll: coercionSelector;
+ nextPutAll: (self stackAccessorFor: stackIndex)]!

Item was added:
+ ----- Method: SmartSyntaxPluginCodeGenerator>>anyMethodNamed: (in category 'utilities') -----
+ anyMethodNamed: selector
+ "Answer any method in the code base (including api methods) with the given selector.
+ Override to find smart syntax methods that get  entered in the dictionary under the
+ name specified in the primitive:parameters: send."
+
+ ^(super anyMethodNamed: selector) ifNil:
+ [methods
+ detect: [:m| m smalltalkSelector == selector]
+ ifNone: []]!

Item was removed:
- ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asNamedPtr:from: (in category 'coercing') -----
- ccgLoad: aBlock expr: exprString asNamedPtr: recordString from: anInteger
- "Answer codestring for integer pointer to first indexable field of object (without validating side-effect), as described in comment to ccgLoad:expr:asRawOopFrom:"
-
- ^aBlock value: (String streamContents: [:aStream | aStream
- nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
- crtab: 4;
- nextPutAll: '(interpreterProxy stackValue:';
- nextPutAll: anInteger asString;
- nextPutAll: '))';
- crtab: 3;
- nextPutAll: 'to: ''';
- nextPutAll: recordString;
- nextPutAll: ' *'''])!

Item was removed:
- ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asNamedPtr:from:andThen: (in category 'coercing') -----
- ccgLoad: aBlock expr: exprString asNamedPtr: recordString from: anInteger andThen: valBlock
- "Answer codestring for integer pointer to first indexable field of object (without validating side-effect), as described in comment to ccgLoad:expr:asRawOopFrom:"
-
- ^(valBlock value: anInteger), '.',
- (aBlock value: (String streamContents: [:aStream | aStream
- nextPutAll: 'self cCoerce: (interpreterProxy firstIndexableField:';
- crtab: 4;
- nextPutAll: '(interpreterProxy stackValue:';
- nextPutAll: anInteger asString;
- nextPutAll: '))';
- crtab: 3;
- nextPutAll: 'to: ''';
- nextPutAll: recordString;
- nextPutAll: ' *''']))!

Item was changed:
  ----- Method: SmartSyntaxPluginCodeGenerator>>ccgLoad:expr:asRawOopFrom: (in category 'coercing') -----
  ccgLoad: aBlock expr: aString asRawOopFrom: anInteger
+ "Answer a string for a Slang expression that will load an oop (without validation) from stack index anInteger.  Apply aBlock that when passed an expression, will answer a string assigning the expression to the desired identifier, to the string before answering.  aString is a Slang expression that refers to the stack value, once it has been loaded."
- "Answer a string for a Slang expression that will load an oop (without validation) from stack index anInteger.  Apply aBlock, a BlockContext instance that when passed an expression, will return a string assigning the expression to the desired identifier, to the string before answering.  aString is a Slang expression that refers to the stack value, once it has been loaded."
 
+ ^aBlock value: 'interpreterProxy stackValue: ', anInteger printString!
- ^aBlock value: (String streamContents: [:aStream | aStream
- nextPutAll: 'interpreterProxy stackValue: ';
- nextPutAll: anInteger asString])!

Item was added:
+ Object subclass: #SmartSyntaxPluginPrologCodeGenerator
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'VMMaker-SmartSyntaxPlugins'!
+
+ !SmartSyntaxPluginPrologCodeGenerator commentStamp: 'eem 12/17/2018 10:08' prior: 0!
+ SmartSyntaxPluginPrologCodeGenerator is an abstract superclass for two subclasses that generate the validations and assignments at the beginning of SmartSyntaxInterpreterPlugin primitives in response to the primitive:parameters:... sends.!

Item was added:
+ ----- Method: SmartSyntaxPluginPrologCodeGenerator>>stackAccessorFor: (in category 'utilities') -----
+ stackAccessorFor: index
+ self assert: index isInteger.
+ ^'(interpreterProxy stackValue: ', (index printString, ')')!

Item was changed:
  TMethod subclass: #SmartSyntaxPluginTMethod
+ instanceVariableNames: 'isPrimitive fullSelector fullArgs parmSpecs rcvrSpec'
+ classVariableNames: 'Them'
- instanceVariableNames: 'isPrimitive suppressingFailureGuards fullSelector fullArgs parmSpecs rcvrSpec'
- classVariableNames: ''
  poolDictionaries: ''
  category: 'VMMaker-SmartSyntaxPlugins'!
 
  !SmartSyntaxPluginTMethod commentStamp: 'eem 6/6/2018 14:06' prior: 0!
  Variation of TMethod node of the Smalltalk C Code Generator, used in conjunction with SmartSyntaxPluginCodeGenerator and SmartSyntaxInterpreterPlugin to generate named primitives from methods containing type coercion specifications such as
  primitive: functionName parameters: #(Boolean Oop String WordsArray WordsOrBytes)
  primitive: functionName parameters: #(SmallInteger LargeNegativeInteger LargePositiveInteger Integer Unsigned) receiver: #Oop!

Item was removed:
- ----- Method: SmartSyntaxPluginTMethod>>extractSuppressFailureGuardDirective (in category 'transforming') -----
- extractSuppressFailureGuardDirective
- "Scan the top-level statements for a pragma directive of the form:
-
- self suppressFailureGuards: <boolean>
-
- and remove the directive from the method body. Answer the argument
- of the directive or false if there is no #supressFailureGuards: directive."
-
- ^self
- extractDirective: #suppressFailureGuards:
- valueBlock: [:sendNode| sendNode args first name = 'true']
- default: false!

Item was changed:
  ----- Method: SmartSyntaxPluginTMethod>>fixUpReturnOneStmt:on: (in category 'transforming') -----
  fixUpReturnOneStmt: stmt on: sStream
+ | expr exprRetStmts "p t" |
-
  stmt isReturn ifFalse: [^sStream nextPut: stmt].
+ expr := stmt expression.
+ (expr isSend
+ and: [self resultSendAlwaysFails: expr]) ifTrue:
+ ["failure returns"
+ sStream nextPut: expr; nextPut: self nullReturnExpr.
- (stmt expression isSend
- and: [#('primitiveFail' 'primitiveFailFor:') includes: stmt expression selector]) ifTrue:
- ["failure return"
- sStream nextPut: stmt expression.
- sStream nextPut: self nullReturnExpr.
  ^nil].
+ (expr isVariable and: ['nil' = expr name]) ifTrue:
- (stmt expression isVariable and: ['nil' = stmt expression name]) ifTrue:
  ["^ nil -- this is never right unless automatically generated"
  sStream nextPut: stmt.
  ^nil].
+ (expr isVariable and: ['self' = expr name]) ifTrue:
- (stmt expression isVariable and: ['self' = stmt expression name]) ifTrue:
  ["^ self"
+ fullArgs isEmpty ifFalse:
+ [sStream nextPut: (self statementGuardedWithSuccess: (self popExpr: fullArgs size))].
- self generateFailureGuardOn: sStream.
- fullArgs isEmpty ifFalse:[ sStream nextPut: (self popExpr: fullArgs size)].
  sStream nextPut: self nullReturnExpr.
  ^nil].
+ (expr isVariable or: [expr isConstant]) ifTrue:
- (stmt expression isVariable | stmt expression isConstant | suppressingFailureGuards) ifTrue:
  ["^ variable or ^ constant or ^ expr without guardchecking"
+ fullArgs isEmpty ifFalse:
+ [sStream nextPut: (self statementGuardedWithSuccess: (self pop: fullArgs size + 1 thenReturnExpr: expr))].
- self generateFailureGuardOn: sStream.
- sStream nextPut: (self pop: fullArgs size + 1 thenReturnExpr: stmt expression).
  sStream nextPut: self nullReturnExpr.
  ^nil].
  "^ expr with necessary guard checking"
+ "p := sStream position."
+ exprRetStmts := Array streamContents:
+ [:ersStream|
+ (self resultExpressionCanFail: expr)
+ ifTrue:
+ ["t := 1."
+ ersStream
+ nextPut: (self assign: (self oopVariable: '_return_value') expression: expr);
+ nextPut: (self statementGuardedWithSuccess: (self pop: fullArgs size + 1
+ thenReturnExpr: (self oopVariable: '_return_value')))]
+ ifFalse:
+ ["t := 2."
+ ersStream nextPut: (self pop: fullArgs size + 1 thenReturnExpr: expr)]].
+ sStream isEmpty "No statements to cause failure, therefore no need for an initial failure guard."
+ ifTrue: [sStream nextPutAll: exprRetStmts]
+ ifFalse:
+ ["t := t + 2."
+ sStream nextPut: (self statementGuardedWithSuccess: exprRetStmts)].
+ sStream nextPut: self nullReturnExpr.
+ "Them := Dictionary new"
+ "(Them at: t ifAbsentPut: [Dictionary new])
+ at: self selector
+ put: (sStream originalContents copyFrom: p + 1 to: sStream position)"!
- sStream isEmpty ifFalse: [self generateFailureGuardOn: sStream].
- (self resultExpressionAlwaysFails: stmt expression)
- ifTrue:
- [sStream nextPut: stmt expression]
- ifFalse:
- [sStream nextPut: (self assign: (self oopVariable: '_return_value') expression: stmt expression).
- (self resultExpressionCanFail: stmt expression) ifTrue:
- [self generateFailureGuardOn: sStream].
- sStream nextPut: (self pop: fullArgs size + 1 thenReturnExpr: (self oopVariable: '_return_value'))].
- sStream nextPut: self nullReturnExpr!

Item was removed:
- ----- Method: SmartSyntaxPluginTMethod>>generateFailureGuardOn: (in category 'private') -----
- generateFailureGuardOn: sStream
- suppressingFailureGuards ifTrue: [^nil].
- sStream nextPutAll: self checkSuccessExpr
- !

Item was changed:
  ----- Method: SmartSyntaxPluginTMethod>>handlePrimitiveDirective:on: (in category 'specifying primitives') -----
  handlePrimitiveDirective: aStmt on: sStream
 
  isPrimitive := true.
  fullArgs := args.
  locals addAll: args.
  args := OrderedCollection new.
  fullArgs with: parmSpecs do:
  [:argName :spec |
  self declarationAt: argName
  put: (spec ccgDeclareCForVar: argName)].
  aStmt isAssignment ifTrue:
  [self declarationAt: aStmt variable name
  put: (rcvrSpec ccgDeclareCForVar: aStmt variable name).
  sStream nextPutAll: (self
  statementsFor:
  (rcvrSpec
+ ccg: SmartSyntaxPluginCodeGenerator new
- ccg: SmartSyntaxPluginCodeGenerator new
  prolog:  [:expr | aStmt variable name, ' := ', expr]
  expr: aStmt variable name
+ index: fullArgs size)
- index: (fullArgs size))
  varName: '')].
 
  "only add the failure guard if there are args or it is an assignment"
+ (fullArgs isEmpty not or: [aStmt isAssignment]) ifTrue:
+ [sStream nextPutAll: self checkSuccessExpr].
- (fullArgs isEmpty not or:[aStmt isAssignment]) ifTrue:[self generateFailureGuardOn: sStream].
  ^true.
  !

Item was changed:
  ----- Method: SmartSyntaxPluginTMethod>>namedPrimitiveProlog (in category 'specifying primitives') -----
  namedPrimitiveProlog
+ "Generate the code for a primitive:parameters:... send.  This is in two parts.
+ The first is validation; the second is coercing assignment."
+ | statements validator validations assigner |
+ fullArgs isEmpty ifTrue:
+ [^#()].
+ validator := SmartSyntaxPluginValidationCodeGenerator new.
+ statements := OrderedCollection new.
+ validations := fullArgs withIndexCollect:
+ [:arg :i|
+ (parmSpecs at: i)
+ ccg: validator
+ prolog:  nil
+ expr: arg
+ index: (fullArgs size - i)].
+ validations := validations reject: [:validation| validation isNil].
+ validations isEmpty ifFalse:
+ [statements addAllLast: (self statementsFor:
+ (String streamContents:
+ [:s|
+ s nextPut: $(.
+ validations
+ do: [:validation| s nextPut: $(; nextPutAll: validation; nextPut: $)]
+ separatedBy: [s crtab; nextPutAll: 'and: ['].
+ s next: validations size - 1 put: $].
+ s nextPutAll: ') ifFalse:';
+ crtab: 2;
+ nextPutAll: '[interpreterProxy primitiveFailFor: PrimErrBadArgument.';
+ crtab: 2;
+ nextPutAll: '^nil';
+ crtab: 2;
+ nextPut: $]])
+ varName: '')].
+ assigner := SmartSyntaxPluginAssignmentCodeGenerator new.
+ fullArgs withIndexDo:
+ [:arg :i|
+ statements addAllLast:
+ (self
+ statementsFor:
+ ((parmSpecs at: i)
+ ccg: assigner
+ prolog:  nil
+ expr: arg
+ index: (fullArgs size - i))
+ varName: '')].
+ ^statements!
-
- | cg |
- cg := SmartSyntaxPluginCodeGenerator new.
- ^Array streamContents: [:sStream |
- 1 to: fullArgs size do:
- [:i |
- sStream nextPutAll:
- (self
- statementsFor:
- ((parmSpecs at: i)
- ccg: cg
- prolog:  [:expr | (fullArgs at: i), ' := ', expr]
- expr: (fullArgs at: i)
- index: (fullArgs size - i))
- varName: '')]]!

Item was changed:
  ----- Method: SmartSyntaxPluginTMethod>>pop:thenReturnExpr: (in category 'private') -----
  pop: anInteger thenReturnExpr: anExpression
 
  ^TSendNode new
  setSelector: #pop:thenPush:
  receiver: (TVariableNode new setName: 'interpreterProxy')
+ arguments: {TConstantNode new setValue: anInteger. anExpression}!
- arguments: (Array
- with: (TConstantNode new
- setValue: anInteger)
- with: anExpression)!

Item was changed:
  ----- Method: SmartSyntaxPluginTMethod>>printTempsAndVar:on: (in category 'private') -----
  printTempsAndVar: varName on: aStream
  "add the required temps and the varname to the stream"
+ aStream nextPut: $|; space.
+ (#('rcvr' 'stackPointer' 'interpreterProxy') reject: [:each | locals includes: each]) do:
+ [:each | aStream nextPutAll: each;  space].
+ (locals reject: [:each | each first = $_]) do:
+ [:each | aStream nextPutAll: each;  space].
- aStream nextPutAll: '| '.
- (#('rcvr' 'stackPointer' 'interpreterProxy') reject: [:each | locals includes: each])
- do: [:each | aStream nextPutAll: each;
- space].
- (locals reject: [:each | each first = $_])
- do: [:each | aStream nextPutAll: each;
- space].
  "don't add varName twice. Probably a deeper reason for this, but WTH. TPR"
+ (locals includes: varName) ifFalse:
+ [aStream nextPutAll: varName; space].
+ aStream nextPut: $|; cr!
- (locals includes: varName) ifFalse:[aStream nextPutAll: varName].
- aStream nextPutAll: '|';
- cr!

Item was removed:
- ----- Method: SmartSyntaxPluginTMethod>>resultExpressionAlwaysFails: (in category 'private') -----
- resultExpressionAlwaysFails: aTSendNode
- ^aTSendNode selector == #success:
- and: [aTSendNode args first isConstant
- and: [aTSendNode args first value == false]]!

Item was changed:
  ----- Method: SmartSyntaxPluginTMethod>>resultExpressionCanFail: (in category 'private') -----
  resultExpressionCanFail: aTSendNode
  "Neither asSmallIntegerObj nor asBooleanObj can fail."
+ ^(#(asSmallIntegerObj asBooleanObj nilObject trueObject falseObject) includes: aTSendNode selector) not!
- ^(#(asSmallIntegerObj asBooleanObj) includes: aTSendNode selector) not!

Item was added:
+ ----- Method: SmartSyntaxPluginTMethod>>resultSendAlwaysFails: (in category 'private') -----
+ resultSendAlwaysFails: aTSendNode
+ ^(#(primitiveFail primitiveFailFor:) includes: aTSendNode selector)
+ or: [aTSendNode selector == #success:
+ and: [aTSendNode args first isConstant
+ and: [aTSendNode args first value == false]]]!

Item was changed:
  ----- Method: SmartSyntaxPluginTMethod>>setSelector:definingClass:args:locals:block:primitive:properties:comment: (in category 'initialization') -----
  setSelector: sel definingClass: class args: argList locals: localList block: aBlockNode primitive: aNumber properties: methodProperties comment: aComment
  "Initialize this method using the given information."
 
  selector := sel.
  definingClass := class.
  returnType := #sqInt. "assume return type is sqInt for now"
  args := argList asOrderedCollection collect: [:arg | arg key].
  locals := (localList collect: [:arg | arg key]) asSet.
  declarations := Dictionary new.
  primitive := aNumber.
  properties := methodProperties.
  comment := aComment.
  parseTree := aBlockNode asTranslatorNodeIn: self.
  labels := Set new.
  complete := false.  "set to true when all possible inlining has been done"
  export := self extractExportDirective.
  static := self extractStaticDirective.
  self extractSharedCase.
  isPrimitive := false.  "set to true only if you find a primtive direction."
- suppressingFailureGuards := self extractSuppressFailureGuardDirective.
  self recordDeclarationsIn: CCodeGenerator basicNew. "Just for conventionalTypeForType:"
  self extractPrimitiveDirectives.
  !

Item was added:
+ ----- Method: SmartSyntaxPluginTMethod>>statementGuardedWithSuccess: (in category 'private') -----
+ statementGuardedWithSuccess: aTParseNodeOrSequenceThereof
+ "Answer a TSendNode for interpreterProxy failed ifFalse: [aTParseNodeOrSequenceThereof]"
+ ^TSendNode new
+ setSelector: #ifFalse:
+ receiver: (TSendNode new
+ setSelector: #failed
+ receiver: (TVariableNode new setName: 'interpreterProxy')
+ arguments: #())
+ arguments: {(aTParseNodeOrSequenceThereof isTParseNode and: [aTParseNodeOrSequenceThereof isStmtList])
+ ifTrue: [aTParseNodeOrSequenceThereof]
+ ifFalse: [TStmtListNode new
+ setArguments: #()
+ statements: (aTParseNodeOrSequenceThereof isCollection
+ ifTrue: [aTParseNodeOrSequenceThereof]
+ ifFalse: [{aTParseNodeOrSequenceThereof}])]}!

Item was added:
+ SmartSyntaxPluginPrologCodeGenerator subclass: #SmartSyntaxPluginValidationCodeGenerator
+ instanceVariableNames: ''
+ classVariableNames: ''
+ poolDictionaries: ''
+ category: 'VMMaker-SmartSyntaxPlugins'!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asBooleanValueFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asBooleanValueFrom: stackIndex
+ ^self loadAs: #isBooleanObject: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asCharPtrFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asCharPtrFrom: stackIndex
+ ^self loadAs: #isWordsOrBytes: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asCharPtrFrom:andThen: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asCharPtrFrom: stackIndex andThen: validationString
+ ^validationString, (self stackAccessorFor: stackIndex)!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asFloatValueFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asFloatValueFrom: stackIndex
+ ^self loadAs: #isFloatObject: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asIntPtrFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asIntPtrFrom: stackIndex
+ ^self loadAs: #isWordsOrBytes: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asIntPtrFrom:andThen: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asIntPtrFrom: stackIndex andThen: validationString
+ ^validationString, (self stackAccessorFor: stackIndex)!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asIntegerValueFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asIntegerValueFrom: stackIndex
+ ^self loadAs: #isIntegerObject: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asKindOf:from: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asKindOf: aClass from: stackIndex
+ ^self loadAs: #is:KindOf: class: aClass from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asKindOfIntegerFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asKindOfIntegerFrom: stackIndex
+ ^self loadAs: #isKindOfInteger: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asMemberOf:from: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asMemberOf: aClass from: stackIndex
+ ^self loadAs: #is:MemberOf: class: aClass from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asMemberOfLargeNegativeIntegerFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asMemberOfLargeNegativeIntegerFrom: stackIndex
+ ^self loadAs: #isLargeNegativeIntegerObject: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asMemberOfLargePositiveIntegerFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asMemberOfLargePositiveIntegerFrom: stackIndex
+ ^self loadAs: #isLargePositiveIntegerObject: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asNonIntegerValueFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asNonIntegerValueFrom: stackIndex
+ ^self loadAs: #isNonImmediate: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asOopPtrFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asOopPtrFrom: stackIndex
+ ^self loadAs: #isNonImmediate: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asOopPtrFrom:andThen: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asOopPtrFrom: stackIndex andThen: validationString
+ ^String streamContents:
+ [:s|
+ s nextPut: $(;
+ nextPutAll: (self loadAs: #isPointers: from: stackIndex);
+ nextPutAll: ') and: [';
+ nextPutAll: validationString;
+ nextPutAll: (self stackAccessorFor: stackIndex);
+ nextPut: $]]!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asRawOopFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asRawOopFrom: anInteger
+ ^nil!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asUnsignedPtrFrom:andThen: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asUnsignedPtrFrom: stackIndex andThen: validationString
+ ^validationString, (self stackAccessorFor: stackIndex)!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asUnsignedValueFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asUnsignedValueFrom: stackIndex
+ ^self loadAs: #isPositiveMachineIntegerObject: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asWBCharPtrFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asWBCharPtrFrom: stackIndex
+ ^self loadAs: #isWordsOrBytes: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asWBFloatPtrFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asWBFloatPtrFrom: stackIndex
+ ^self loadAs: #isWordsOrBytes: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgLoad:expr:asWBIntPtrFrom: (in category 'coercing') -----
+ ccgLoad: aBlock expr: aString asWBIntPtrFrom: stackIndex
+ ^self loadAs: #isWordsOrBytes: from: stackIndex!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>ccgValBlock: (in category 'coercing support') -----
+ ccgValBlock: aString
+ ^'interpreterProxy ', (aString, ': ')!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>loadAs:class:from: (in category 'coercing support') -----
+ loadAs: classMembershipSelector class: aClass from: stackIndex
+
+ ^String streamContents:
+ [:aStream | | keywords |
+ keywords := classMembershipSelector keywords.
+ aStream
+ nextPutAll: 'interpreterProxy ';
+ nextPutAll: keywords first;
+ nextPutAll: (self stackAccessorFor: stackIndex);
+ space;
+ nextPutAll: keywords last;
+ nextPutAll: ' ''';
+ nextPutAll: aClass asString;
+ nextPutAll: '''']!

Item was added:
+ ----- Method: SmartSyntaxPluginValidationCodeGenerator>>loadAs:from: (in category 'coercing support') -----
+ loadAs: classMembershipSelector from: stackIndex
+
+ ^String streamContents:
+ [:aStream |
+ aStream
+ nextPutAll: 'interpreterProxy ';
+ nextPutAll: classMembershipSelector;
+ nextPutAll: (self stackAccessorFor: stackIndex)]!

Item was changed:
  ----- Method: SocketPlugin>>socketValueOf: (in category 'primitives') -----
  socketValueOf: socketOop
+ "Answer a pointer to the first byte of of the socket record within the  
- "Return a pointer to the first byte of of the socket record within the  
  given Smalltalk object, or nil if socketOop is not a socket record."
+ <returnTypeC: #SocketPtr>
+ ^((interpreterProxy isBytes: socketOop)
+   and: [(interpreterProxy byteSizeOf: socketOop) = self socketRecordSize])
+ ifTrue: [self cCoerce: (interpreterProxy firstIndexableField: socketOop) to: #SocketPtr]
+ ifFalse: [interpreterProxy primitiveFailFor: PrimErrBadArgument. nil]!
- <returnTypeC: 'SocketPtr'>
- interpreterProxy success: ((interpreterProxy isBytes: socketOop)
- and: [(interpreterProxy byteSizeOf: socketOop)
- = self socketRecordSize]).
- ^interpreterProxy failed
- ifTrue: [nil]
- ifFalse: [self cCoerce: (interpreterProxy firstIndexableField: socketOop) to: 'SocketPtr']!

Item was added:
+ ----- Method: SpurMemoryManager>>isBooleanObject: (in category 'simulation only') -----
+ isBooleanObject: oop
+ "hack around the CoInterpreter/ObjectMemory split refactoring"
+ <doNotGenerate>
+ ^coInterpreter isBooleanObject: oop!

Item was added:
+ ----- Method: SpurMemoryManager>>isPositiveMachineIntegerObject: (in category 'simulation only') -----
+ isPositiveMachineIntegerObject: oop
+ "hack around the CoInterpreter/ObjectMemory split refactoring"
+ <doNotGenerate>
+ ^coInterpreter isPositiveMachineIntegerObject: oop!

Item was added:
+ ----- Method: StackInterpreter>>isBooleanObject: (in category 'plugin primitive support') -----
+ isBooleanObject: oop
+ ^oop = objectMemory trueObject or: [oop = objectMemory falseObject]!

Item was changed:
  ----- Method: TMethod>>statementsFor:varName: (in category 'primitive compilation') -----
  statementsFor: sourceText varName: varName
  "Return the parse tree for the given expression. The result is the statements list of the method parsed from the given source text."
  "Details: Various variables are declared as locals to avoid Undeclared warnings from the parser."
 
  | s |
  s := WriteStream on: String new.
  s nextPutAll: 'temp'; cr; crtab.
  self printTempsAndVar: varName on: s.
  s nextPutAll: sourceText.
+ ^(([ | compiler |
+ compiler := Smalltalk compiler class: VMBasicConstants. "for primitive error codes"
+ (compiler parse: s contents)
- ^ (([ | compiler |
- compiler := Smalltalk compiler class: Object.
-   (compiler parse: s contents)
  compilationContext: compiler compilationContext;
  yourself] "Pharo"
+ on: MessageNotUnderstood
+ do: [:ex|
+ ex message selector == #compiler ifFalse:
+ [ex pass].
+ Compiler new parse: s contents in: VMBasicConstants notifying: nil]) "Squeak"
+ asTranslationMethodOfClass: self class)
+ removeFinalSelfReturnIn: nil;
+ statements!
- on: MessageNotUnderstood
- do: [:ex|
- ex message selector == #compiler ifFalse:
- [ex pass].
- Compiler new parse: s contents in: Object notifying: nil]) "Squeak"
- asTranslationMethodOfClass: self class)
- removeFinalSelfReturnIn: nil;
- statements!

Item was added:
+ ----- Method: TestOSAPlugin class>>shouldBeTranslated (in category 'translation') -----
+ shouldBeTranslated
+ "As yet this can't be translated because a DescType parameter can't be handled."
+ ^false!