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

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

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

Name: VMMaker.oscog-eem.2353
Author: eem
Time: 10 March 2018, 1:50:16.720571 pm
UUID: debae926-b191-475c-b463-955cc4399122
Ancestors: VMMaker.oscog-eem.2352

Cogits:
Fix pc mapping for genStore[AndPop]RemoteTempLongBytecode.  Neither of these are isMappedIfImmutability unless they are used for inst var assignment of arbitrary objects; in which case we need to add an annotation when they're used for indirect temp access.

Fix ceSend:aboveClassBinding:to:numArgs:, which forgot to indirect through the binding before sending ceSend:above:to:numArgs:.

Fix confusion in updateSimSpillBase.

Fix typos.

Plugins:
Fix simulation of primitiveDirectoryCreate

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

Item was changed:
  ----- Method: CoInterpreter>>ceSend:aboveClassBinding:to:numArgs: (in category 'trampolines') -----
  ceSend: selector aboveClassBinding: methodClassBinding to: rcvr numArgs: numArgs
  "Entry-point for an unlinked directed super send in a CogMethod.  Smalltalk stack looks like
  receiver
  args
  head sp -> sender return pc
  methodClassBinding is an association whose value is the class above which to start the lookup."
  <api>
  <option: #BytecodeSetHasDirectedSuperSend>
  self ceSend: selector
+ above: (self fetchPointer: ValueIndex
+ ofObject: (objectMemory followMaybeForwarded: methodClassBinding))
- above: (objectMemory followMaybeForwarded: methodClassBinding)
  to: rcvr
  numArgs: numArgs!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur class>>numTrampolines (in category 'accessing') -----
  numTrampolines
  ^super numTrampolines
+ + (SistaV1BytecodeSet
+ ifTrue: [9] "(small,large)x(method,block,fullBlock) context creation,
+ ceNewHashTrampoline, ceStoreCheckContextReceiverTrampoline and ceScheduleScavengeTrampoline"
+ ifFalse: [7] "(small,large)x(method,block) context creation,
+ ceNewHashTrampoline, ceStoreCheckContextReceiverTrampoline and ceScheduleScavengeTrampoline")
+ + NumStoreTrampolines
+ + (SistaVM
+ ifTrue: [1] "inline newHash"
+ ifFalse: [0])!
- + (SistaV1BytecodeSet
- ifTrue: [9] "(small,large)x(method,block,fullBlock) context creation,
- ceNewHashTrampoline, ceStoreCheckContextReceiverTrampoline and ceScheduleScavengeTrampoline"
- ifFalse: [7] "(small,large)x(method,block) context creation,
- ceNewHashTrampoline, ceStoreCheckContextReceiverTrampoline and ceScheduleScavengeTrampoline")
- + NumStoreTrampolines
- + ((initializationOptions at: #SistaVM ifAbsent: [false])
- ifTrue: [1] "inline newHash"
- ifFalse: [0]) !

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreTrampolineCall: (in category 'compile abstract instructions') -----
  genStoreTrampolineCall: instVarIndex
  <inline: true>
+ self assert: IMMUTABILITY.
  instVarIndex >= (NumStoreTrampolines - 1)
  ifTrue:
  [ cogit MoveCq: instVarIndex R: TempReg.
   cogit CallRT: (ceStoreTrampolines at: NumStoreTrampolines - 1) ]
  ifFalse:
  [ cogit CallRT: (ceStoreTrampolines at: instVarIndex) ].
  cogit annotateBytecode: cogit Label!

Item was changed:
  ----- Method: FilePlugin>>primitiveDirectoryCreate (in category 'directory primitives') -----
  primitiveDirectoryCreate
 
  | dirName dirNameIndex dirNameSize okToCreate |
  <var: #dirNameIndex type: 'char *'>
  <export: true>
 
  dirName := interpreterProxy stackValue: 0.
  (interpreterProxy isBytes: dirName) ifFalse:
  [^interpreterProxy primitiveFail].
  dirNameIndex := interpreterProxy firstIndexableField: dirName.
  dirNameSize := interpreterProxy byteSizeOf: dirName.
  "If the security plugin can be loaded, use it to check for permission.
  If not, assume it's ok"
  sCCPfn ~= 0 ifTrue:
  [okToCreate := self cCode: ' ((sqInt (*)(char *, sqInt))sCCPfn)(dirNameIndex, dirNameSize)'
  inSmalltalk: [true].
  okToCreate ifFalse:
  [^interpreterProxy primitiveFail]].
  (self
  cCode: 'dir_Create(dirNameIndex, dirNameSize)'
+ inSmalltalk: [self createDirectory: (interpreterProxy asString: dirNameIndex size: dirNameSize)]) ifFalse:
- inSmalltalk: [self createDirectory: (interpreterProxy asString: dirNameIndex)]) ifFalse:
  [^interpreterProxy primitiveFail].
  interpreterProxy pop: 1!

Item was changed:
  ----- Method: SimpleStackBasedCogit class>>initializeBytecodeTableForSistaV1 (in category 'class initialization') -----
  initializeBytecodeTableForSistaV1
  "SimpleStackBasedCogit initializeBytecodeTableForSistaV1"
 
  BytecodeSetHasDirectedSuperSend := true.
  FirstSpecialSelector := 96.
  NumSpecialSelectors := 32.
  self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  self generatorTableFrom: #(
  "1 byte bytecodes"
  "pushes"
  (1    0   15 genPushReceiverVariableBytecode isInstVarRef)
  (1  16   31 genPushLiteralVariable16CasesBytecode needsFrameNever: 1)
  (1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  (1  64   75 genPushTemporaryVariableBytecode)
  (1  76   76 genPushReceiverBytecode)
  (1  77   77 genPushConstantTrueBytecode needsFrameNever: 1)
  (1  78   78 genPushConstantFalseBytecode needsFrameNever: 1)
  (1  79   79 genPushConstantNilBytecode needsFrameNever: 1)
  (1  80   80 genPushConstantZeroBytecode needsFrameNever: 1)
  (1  81   81 genPushConstantOneBytecode needsFrameNever: 1)
  (1  82   82 genExtPushPseudoVariable)
  (1  83   83 duplicateTopBytecode needsFrameNever: 1)
 
  (1  84   87 unknownBytecode)
 
  "returns"
  (1  88   88 genReturnReceiver return needsFrameIfInBlock: isMappedInBlock 0)
  (1  89   89 genReturnTrue return needsFrameIfInBlock: isMappedInBlock 0)
  (1  90   90 genReturnFalse return needsFrameIfInBlock: isMappedInBlock 0)
  (1  91   91 genReturnNil return needsFrameIfInBlock: isMappedInBlock 0)
  (1  92   92 genReturnTopFromMethod return needsFrameIfInBlock: isMappedInBlock -1)
  (1  93   93 genReturnNilFromBlock return needsFrameNever: -1)
  (1  94   94 genReturnTopFromBlock return needsFrameNever: -1)
  (1  95   95 genExtNopBytecode needsFrameNever: 0)
 
  "sends"
  (1   96 117 genSpecialSelectorSend isMapped) "#+ #- #< #> #<= #>= #= #~= #* #/ #\\ #@ #bitShift: #// #bitAnd: #bitOr: #at: #at:put: #size #next #nextPut: #atEnd"
  (1 118 118 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  (1 119 119 genSpecialSelectorClass needsFrameNever: notMapped 0) "not mapped because it is directly inlined (for now)"
  (1 120 120 genSpecialSelectorNotEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  (1 121 127 genSpecialSelectorSend isMapped) "#value #value: #do: #new #new: #x #y"
 
  (1 128 143 genSendLiteralSelector0ArgsBytecode isMapped)
  (1 144 159 genSendLiteralSelector1ArgBytecode isMapped)
  (1 160 175 genSendLiteralSelector2ArgsBytecode isMapped)
 
  "jumps"
  (1 176 183 genShortUnconditionalJump branch v3:ShortForward:Branch:Distance:)
  (1 184 191 genShortJumpIfTrue branch isBranchTrue isMapped "because of mustBeBoolean"
  v3:ShortForward:Branch:Distance:)
  (1 192 199 genShortJumpIfFalse branch isBranchFalse isMapped "because of mustBeBoolean"
  v3:ShortForward:Branch:Distance:)
 
  "stores"
  (1 200 207 genStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability needsFrameIfImmutability: -1)
  (1 208 215 genStoreAndPopTemporaryVariableBytecode)
 
  (1 216 216 genPopStackBytecode needsFrameNever: -1)
 
  (1 217 217 genUnconditionalTrapBytecode isMapped)
 
  (1 218 223 unknownBytecode)
 
  "2 byte bytecodes"
  (2 224 224 extABytecode extension)
  (2 225 225 extBBytecode extension)
 
  "pushes"
  (2 226 226 genExtPushReceiverVariableBytecode isInstVarRef) "Needs a frame for context inst var access"
  (2 227 227 genExtPushLiteralVariableBytecode needsFrameNever: 1)
  (2 228 228 genExtPushLiteralBytecode needsFrameNever: 1)
  (2 229 229 genLongPushTemporaryVariableBytecode)
  (2 230 230 unknownBytecode)
  (2 231 231 genPushNewArrayBytecode)
  (2 232 232 genExtPushIntegerBytecode needsFrameNever: 1)
  (2 233 233 genExtPushCharacterBytecode needsFrameNever: 1)
 
  "returns"
  "sends"
  (2 234 234 genExtSendBytecode isMapped)
  (2 235 235 genExtSendSuperBytecode isMapped)
 
  "sista bytecodes"
  (2 236 236 unknownBytecode)
 
  "jumps"
  (2 237 237 genExtUnconditionalJump branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  (2 238 238 genExtJumpIfTrue branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  (2 239 239 genExtJumpIfFalse branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
 
  "stores"
  (2 240 240 genExtStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
  (2 241 241 genExtStoreAndPopLiteralVariableBytecode isMappedIfImmutability)
  (2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
  (2 243 243 genExtStoreReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
  (2 244 244 genExtStoreLiteralVariableBytecode isMappedIfImmutability)
  (2 245 245 genLongStoreTemporaryVariableBytecode)
 
  (2 246 247 unknownBytecode)
 
  "3 byte bytecodes"
  (3 248 248 genCallPrimitiveBytecode)
  (3 249 249 genExtPushFullClosureBytecode)
  (3 250 250 genExtPushClosureBytecode block v4:Block:Code:Size:)
  (3 251 251 genPushRemoteTempLongBytecode)
+ (3 252 252 genStoreRemoteTempLongBytecode)
+ (3 253 253 genStoreAndPopRemoteTempLongBytecode)
- (3 252 252 genStoreRemoteTempLongBytecode isMappedIfImmutability)
- (3 253 253 genStoreAndPopRemoteTempLongBytecode isMappedIfImmutability)
 
  (3 254 255 unknownBytecode))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit class>>initializeBytecodeTableForSistaV1 (in category 'class initialization') -----
  initializeBytecodeTableForSistaV1
  "StackToRegisterMappingCogit initializeBytecodeTableForSistaV1"
 
  numPushNilsFunction := #sistaV1:Num:Push:Nils:.
  pushNilSizeFunction := #sistaV1PushNilSize:numInitialNils:.
  BytecodeSetHasDirectedSuperSend := true.
  FirstSpecialSelector := 96.
  NumSpecialSelectors := 32.
  self flag:
  'Special selector send class must be inlined to agree with the interpreter, which
   inlines class.  If class is sent to e.g. a general instance of ProtoObject then unless
   class is inlined there will be an MNU.  It must be that the Cointerpreter and Cogit
   have identical semantics.  We get away with not hardwiring the other special
   selectors either because in the Cointerpreter they are not inlined or because they
   are inlined only to instances of classes for which there will always be a method.'.
  self generatorTableFrom: #(
  "1 byte bytecodes"
  "pushes"
  (1    0   15 genPushReceiverVariableBytecode isInstVarRef needsFrameNever: 1)
  (1  16   31 genPushLiteralVariable16CasesBytecode needsFrameNever: 1)
  (1  32   63 genPushLiteralConstantBytecode needsFrameNever: 1)
  (1  64   75 genPushTemporaryVariableBytecode needsFrameIfMod16GENumArgs: 1)
  (1  76   76 genPushReceiverBytecode needsFrameNever: 1)
  (1  77   77 genPushConstantTrueBytecode needsFrameNever: 1)
  (1  78   78 genPushConstantFalseBytecode needsFrameNever: 1)
  (1  79   79 genPushConstantNilBytecode needsFrameNever: 1)
  (1  80   80 genPushConstantZeroBytecode needsFrameNever: 1)
  (1  81   81 genPushConstantOneBytecode needsFrameNever: 1)
  (1  82   82 genExtPushPseudoVariable)
  (1  83   83 duplicateTopBytecode needsFrameNever: 1)
 
  (1  84   87 unknownBytecode)
 
  "returns"
  (1  88   88 genReturnReceiver return needsFrameIfInBlock: isMappedInBlock 0)
  (1  89   89 genReturnTrue return needsFrameIfInBlock: isMappedInBlock 0)
  (1  90   90 genReturnFalse return needsFrameIfInBlock: isMappedInBlock 0)
  (1  91   91 genReturnNil return needsFrameIfInBlock: isMappedInBlock 0)
  (1  92   92 genReturnTopFromMethod return needsFrameIfInBlock: isMappedInBlock -1)
  (1  93   93 genReturnNilFromBlock return needsFrameNever: -1)
  (1  94   94 genReturnTopFromBlock return needsFrameNever: -1)
  (1  95   95 genExtNopBytecode needsFrameNever: 0)
 
  "sends"
  (1  96   96 genSpecialSelectorArithmetic isMapped AddRR)
  (1  97   97 genSpecialSelectorArithmetic isMapped SubRR)
  (1  98   98 genSpecialSelectorComparison isMapped JumpLess)
  (1  99   99 genSpecialSelectorComparison isMapped JumpGreater)
  (1 100 100 genSpecialSelectorComparison isMapped JumpLessOrEqual)
  (1 101 101 genSpecialSelectorComparison isMapped JumpGreaterOrEqual)
  (1 102 102 genSpecialSelectorComparison isMapped JumpZero)
  (1 103 103 genSpecialSelectorComparison isMapped JumpNonZero)
  (1 104 109 genSpecialSelectorSend isMapped) " #* #/ #\\ #@ #bitShift: //"
  (1 110 110 genSpecialSelectorArithmetic isMapped AndRR)
  (1 111 111 genSpecialSelectorArithmetic isMapped OrRR)
  (1 112 117 genSpecialSelectorSend isMapped) "#at: #at:put: #size #next #nextPut: #atEnd"
  (1 118 118 genSpecialSelectorEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  (1 119 119 genSpecialSelectorClass needsFrameIfStackGreaterThanOne: notMapped 0) "not mapped because it is directly inlined (for now)"
  (1 120 120 genSpecialSelectorNotEqualsEquals needsFrameNever: notMapped -1) "not mapped because it is directly inlined (for now)"
  (1 121 127 genSpecialSelectorSend isMapped) "#value #value: #do: #new #new: #x #y"
 
  (1 128 143 genSendLiteralSelector0ArgsBytecode isMapped)
  (1 144 159 genSendLiteralSelector1ArgBytecode isMapped)
  (1 160 175 genSendLiteralSelector2ArgsBytecode isMapped)
 
  "jumps"
  (1 176 183 genShortUnconditionalJump branch v3:ShortForward:Branch:Distance:)
  (1 184 191 genShortJumpIfTrue branch isBranchTrue isMapped "because of mustBeBoolean"
  v3:ShortForward:Branch:Distance:)
  (1 192 199 genShortJumpIfFalse branch isBranchFalse isMapped "because of mustBeBoolean"
  v3:ShortForward:Branch:Distance:)
  (1 200 207 genStoreAndPopReceiverVariableBytecode isInstVarRef is1ByteInstVarStore isMappedIfImmutability needsFrameIfImmutability: -1)
 
  (1 208 215 genStoreAndPopTemporaryVariableBytecode)
 
  (1 216 216 genPopStackBytecode needsFrameNever: -1)
 
  (1 217 217 genUnconditionalTrapBytecode isMapped)
 
  (1 218 223 unknownBytecode)
 
  "2 byte bytecodes"
  (2 224 224 extABytecode extension)
  (2 225 225 extBBytecode extension)
 
  "pushes"
  (2 226 226 genExtPushReceiverVariableBytecode isInstVarRef) "Needs a frame for context inst var access"
  (2 227 227 genExtPushLiteralVariableBytecode needsFrameNever: 1)
  (2 228 228 genExtPushLiteralBytecode needsFrameNever: 1)
  (2 229 229 genLongPushTemporaryVariableBytecode)
  (2 230 230 unknownBytecode)
  (2 231 231 genPushNewArrayBytecode)
  (2 232 232 genExtPushIntegerBytecode needsFrameNever: 1)
  (2 233 233 genExtPushCharacterBytecode needsFrameNever: 1)
 
  "returns"
  "sends"
  (2 234 234 genExtSendBytecode isMapped)
  (2 235 235 genExtSendSuperBytecode isMapped)
 
  "sista bytecodes"
  (2 236 236 genCallMappedInlinedPrimitive isMapped hasUnsafeJump)
 
  "jumps"
  (2 237 237 genExtUnconditionalJump branch isMapped "because of interrupt check" v4:Long:Branch:Distance:)
  (2 238 238 genExtJumpIfTrue branch isBranchTrue isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
  (2 239 239 genExtJumpIfFalse branch isBranchFalse isMapped "because of mustBeBoolean" v4:Long:Branch:Distance:)
 
  "stores"
  (2 240 240 genExtStoreAndPopReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
  (2 241 241 genExtStoreAndPopLiteralVariableBytecode isMappedIfImmutability)
  (2 242 242 genLongStoreAndPopTemporaryVariableBytecode)
  (2 243 243 genExtStoreReceiverVariableBytecode isInstVarRef isMappedIfImmutability)
  (2 244 244 genExtStoreLiteralVariableBytecode isMappedIfImmutability)
  (2 245 245 genLongStoreTemporaryVariableBytecode)
 
  (2 246 247 unknownBytecode)
 
  "3 byte bytecodes"
  (3 248 248 genCallPrimitiveBytecode hasUnsafeJump)
  (3 249 249 genExtPushFullClosureBytecode)
  (3 250 250 genExtPushClosureBytecode block v4:Block:Code:Size:)
  (3 251 251 genPushRemoteTempLongBytecode)
+ (3 252 252 genStoreRemoteTempLongBytecode)
+ (3 253 253 genStoreAndPopRemoteTempLongBytecode)
- (3 252 252 genStoreRemoteTempLongBytecode isMappedIfImmutability)
- (3 253 253 genStoreAndPopRemoteTempLongBytecode isMappedIfImmutability)
 
  (3 254 255 unknownBytecode))!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>doubleExtendedDoAnythingBytecode (in category 'bytecode generators') -----
  doubleExtendedDoAnythingBytecode
  "Replaces the Blue Book double-extended send [132], in which the first byte was wasted on 8 bits of argument count.
  Here we use 3 bits for the operation sub-type (opType),  and the remaining 5 bits for argument count where needed.
  The last byte give access to 256 instVars or literals.
  See also secondExtendedSendBytecode"
  | opType |
  opType := byte1 >> 5.
  opType = 0 ifTrue:
  [^self genSend: byte2 numArgs: (byte1 bitAnd: 31)].
  opType = 1 ifTrue:
  [^self genSendSuper: byte2 numArgs: (byte1 bitAnd: 31)].
  "We need a map entry for this bytecode for correct parsing.
  The sends will get an IsSend entry anyway.  The other cases need a fake one."
  opType caseOf: {
  [2] -> [(coInterpreter isReadMediatedContextInstVarIndex: byte2)
  ifTrue: [self genPushMaybeContextReceiverVariable: byte2]
  ifFalse: [self genPushReceiverVariable: byte2.
  self annotateInstructionForBytecode.
  ^0]].
  [3] -> [self genPushLiteralIndex: byte2.
  self annotateInstructionForBytecode.
  ^0].
  [4] -> [self genPushLiteralVariable: byte2.].
  [7] -> [self genStorePop: false LiteralVariable: byte2.
  self cppIf: IMMUTABILITY ifTrue: [ "genStorePop:LiteralVariable: annotates; don't annotate twice" ^0 ] ] }
  otherwise: "5 & 6"
  [(coInterpreter isWriteMediatedContextInstVarIndex: byte2)
  ifTrue: [self genStorePop: opType = 6 MaybeContextReceiverVariable: byte2]
  ifFalse: [self genStorePop: opType = 6 ReceiverVariable: byte2].
+ self cppIf: IMMUTABILITY ifTrue: [ "genStorePop:...ReceiverVariable: annotate; don't annotate twice" ^0 ]].
- self cppIf: IMMUTABILITY ifTrue: [ "genStorePop:LiteralVariable: annotates; don't annotate twice" ^0 ]].
  "We need a map entry for this bytecode for correct parsing (if the method builds a frame)."
  self assert: needsFrame.
+ "genPushMaybeContextInstVar, pushLitVar, store & storePop all generate code"
- "genPushMaybeContextInstVar, pushListVar, store & storePop all generate code"
  self assert: self prevInstIsPCAnnotated not.
  self annotateBytecode: self Label.
  ^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>updateSimSpillBase (in category 'simulation stack') -----
  updateSimSpillBase
  "Something volatile has been pushed on the stack; update simSpillBase accordingly."
  <inline: true>
  self assert: ((simSpillBase > methodOrBlockNumTemps
  and: [simStackPtr >= methodOrBlockNumTemps])
  or: [self maybeCompilingFirstPassOfBlockWithInitialPushNil]).
  simSpillBase > simStackPtr
  ifTrue:
  [simSpillBase := simStackPtr + 1.
+ [simSpillBase - 1 > methodOrBlockNumTemps
- [simSpillBase > methodOrBlockNumTemps
    and: [(self simStackAt: simSpillBase - 1) spilled not]] whileTrue:
  [simSpillBase := simSpillBase - 1]]
  ifFalse:
  [[(self simStackAt: simSpillBase) spilled
    and: [simSpillBase <= simStackPtr]] whileTrue:
  [simSpillBase := simSpillBase + 1]].
  methodOrBlockNumTemps + 1 to: (simSpillBase - 1 min: simStackPtr) do:
  [:i|
+ self assert: (self simStackAt: i) spilled == true].
+ self assert: (simSpillBase > simStackPtr or: [(self simStackAt: simSpillBase) spilled == false])!
- self assert: (self simStackAt: i) spilled == true]!