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

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

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

Name: VMMaker.oscog-eem.587
Author: eem
Time: 21 January 2014, 3:24:12.518 pm
UUID: 3ae6428c-5746-4c6a-9125-c61345f80382
Ancestors: VMMaker.oscog-eem.586

Fix bug in Cogit>>unlinkSendsOf:isMNUSelector:, used by
primitiveFlushCacheBySelector.  The method could leave sends
linked to freed MNU PICs.  Looks like this only causes assert failures.

Add abort check assert to relocateCallsAndSelfReferencesInMethod:

Nuke unused method.  Fix a couple of typos.

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

Item was changed:
  ----- Method: CoInterpreter>>ceMNUFromPICMNUMethod:receiver: (in category 'trampolines') -----
  ceMNUFromPICMNUMethod: aMethodObj receiver: rcvr
  <api>
  | cPIC primitiveIndex |
  <var: #cPIC type: #'CogMethod *'>
  self assert: (objectMemory addressCouldBeOop: rcvr).
  self assert: (aMethodObj = 0
  or: [(objectMemory addressCouldBeObj: aMethodObj)
  and: [objectMemory isOopCompiledMethod: aMethodObj]]).
  cPIC := self cCoerceSimple: self popStack - cogit mnuOffset to: #'CogMethod *'.
+ self assert: (cPIC cmType = CMClosedPIC or: [cPIC cmType = CMOpenPIC]).
- self assert: cPIC cmType = CMClosedPIC.
  argumentCount := cPIC cmNumArgs.
  messageSelector := cPIC selector.
  aMethodObj ~= 0 ifTrue:
  [instructionPointer := self popStack.
  self createActualMessageTo: (objectMemory fetchClassOf: rcvr).
  (self maybeMethodHasCogMethod: aMethodObj) ifTrue:
  [self push: instructionPointer.
  self executeCogMethod: (self cogMethodOf: aMethodObj)
  fromUnlinkedSendWithReceiver: rcvr.
  "NOTREACHED"
  self assert: false].
  newMethod := aMethodObj.
  primitiveIndex := self primitiveIndexOf: aMethodObj.
  primitiveFunctionPointer := self functionPointerFor: primitiveIndex inClass: objectMemory nilObject.
  ^self interpretMethodFromMachineCode].
  self handleMNU: SelectorDoesNotUnderstand
  InMachineCodeTo: rcvr
  classForMessage: (objectMemory fetchClassOf: rcvr).
  "NOTREACHED"
  self assert: false!

Item was added:
+ ----- Method: CogMethodZone>>methodBytesFreedSinceLastCompaction (in category 'accessing') -----
+ methodBytesFreedSinceLastCompaction
+ <cmacro: '() methodBytesFreedSinceLastCompaction'>
+ ^methodBytesFreedSinceLastCompaction!

Item was added:
+ ----- Method: CogMethodZone>>printOpenPICList (in category 'accessing') -----
+ printOpenPICList
+ <api>
+ | openPIC |
+ <var: #openPIC type: #'CogMethod *'>
+ openPIC := openPICList.
+ [openPIC == nil] whileFalse:
+ [self printCogMethod: openPIC.
+ openPIC := self cCoerceSimple: openPIC nextOpenPIC to: #'CogMethod *']!

Item was changed:
  ----- Method: Cogit class>>initializeCogMethodConstants (in category 'class initialization') -----
  initializeCogMethodConstants
+ CMOpenPIC := 1 + (CMClosedPIC := 1 + (CMBlock := 1 + (CMMethod := 1 + (CMFree := 1))))!
- CMOpenPIC := 1 + (CMClosedPIC := 1 + (CMBlock := 1 +(CMMethod := 1 + (CMFree := 1))))!

Item was removed:
- ----- Method: Cogit>>compileProlog (in category 'compile abstract instructions') -----
- compileProlog
- "The start of a CogMethod has a call to a run-time abort routine that either
- handles an in-line cache failure or a stack overflow.  The routine selects the
- path depending on ReceiverResultReg; if zero it takes the stack overflow
- path; if nonzero the in-line cache miss path.  Neither of these paths returns.
- The abort routine must be called;  In the callee the method is located by
- adding the relevant offset to the return address of the call."
- stackOverflowCall := self MoveCq: 0 R: ReceiverResultReg.
- sendMissCall := self Call: (self methodAbortTrampolineFor: methodOrBlockNumArgs)!

Item was changed:
  ----- Method: Cogit>>relocateCallsAndSelfReferencesInMethod: (in category 'compaction') -----
  relocateCallsAndSelfReferencesInMethod: cogMethod
  <var: #cogMethod type: #'CogMethod *'>
  | delta |
  delta := cogMethod objectHeader.
+ self assert: (cogMethod cmType = CMMethod or: [cogMethod cmType = CMOpenPIC]).
+ self assert: (backEnd callTargetFromReturnAddress: cogMethod asInteger + missOffset)
+ = (cogMethod cmType = CMMethod
+ ifTrue: [self methodAbortTrampolineFor: cogMethod cmNumArgs]
+ ifFalse: [self picAbortTrampolineFor: cogMethod cmNumArgs]).
  backEnd relocateCallBeforeReturnPC: cogMethod asInteger + missOffset by: delta negated.
  self mapFor: cogMethod
  performUntil: #relocateIfCallOrMethodReference:mcpc:delta:
  arg: delta!

Item was added:
+ ----- Method: Cogit>>unlinkIfFreeOrLinkedSend:pc:of: (in category 'in-line cacheing') -----
+ unlinkIfFreeOrLinkedSend: annotation pc: mcpc of: theSelector
+ <var: #mcpc type: #'char *'>
+ | entryPoint targetMethod offset sendTable unlinkedRoutine |
+ <var: #targetMethod type: #'CogMethod *'>
+ <var: #sendTable type: #'sqInt *'>
+ (self isSendAnnotation: annotation) ifTrue:
+ [entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
+ entryPoint > methodZoneBase
+ ifTrue: "It's a linked send."
+ [self
+ offsetAndSendTableFor: entryPoint
+ annotation: annotation
+ into: [:off :table| offset := off. sendTable := table].
+ targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
+ (targetMethod cmType = CMFree
+ or: [targetMethod selector = theSelector]) ifTrue:
+ [unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
+ backEnd
+ rewriteInlineCacheAt: mcpc asInteger
+ tag: targetMethod selector
+ target: unlinkedRoutine.
+ codeModified := true]]
+ ifFalse:
+ [self cppIf: NewspeakVM ifTrue:
+ [entryPoint = ceImplicitReceiverTrampoline ifTrue:
+ [(backEnd inlineCacheTagAt: mcpc asInteger) = theSelector ifTrue:
+ [backEnd
+ unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize put: 0;
+ unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop put: 0]]]]].
+ ^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkSendsOf:isMNUSelector: (in category 'jit - api') -----
  unlinkSendsOf: selector isMNUSelector: isMNUSelector
  <api>
  "Unlink all sends in cog methods."
+ | freeSpace cogMethod |
- | cogMethod |
  <var: #cogMethod type: #'CogMethod *'>
  methodZoneBase isNil ifTrue: [^self].
  cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
+ freeSpace := methodZone methodBytesFreedSinceLastCompaction.
  "First check if any method actually has the selector; if not there can't
  be any linked send to it."
  [cogMethod < methodZone limitZony
  and: [cogMethod selector ~= selector]] whileTrue:
+ [(cogMethod cmType ~= CMFree
+  and: [(isMNUSelector and: [cogMethod cpicHasMNUCase])
+ or: [cogMethod selector = selector]]) ifTrue:
+ [methodZone freeMethod: cogMethod].
+ cogMethod := methodZone methodAfter: cogMethod].
+ (cogMethod >= methodZone limitZony
+ and: [freeSpace = methodZone methodBytesFreedSinceLastCompaction]) ifTrue:
- [cogMethod := methodZone methodAfter: cogMethod].
- cogMethod >= methodZone limitZony ifTrue:
  [^self].
  codeModified := false.
  cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  [cogMethod < methodZone limitZony] whileTrue:
+ [cogMethod cmType = CMMethod ifTrue:
+ [self mapFor: cogMethod
+ performUntil: #unlinkIfFreeOrLinkedSend:pc:of:
+ arg: selector].
- [cogMethod cmType = CMMethod
- ifTrue:
- [self mapFor: cogMethod
- performUntil: #unlinkIfLinkedSend:pc:of:
- arg: selector]
- ifFalse:
- [(cogMethod cmType ~= CMFree
-  and: [(isMNUSelector and: [cogMethod cpicHasMNUCase])
- or: [cogMethod selector = selector]]) ifTrue:
- [methodZone freeMethod: cogMethod]].
  cogMethod := methodZone methodAfter: cogMethod].
  codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
  [processor flushICacheFrom: methodZoneBase to: methodZone limitZony asInteger]!

Item was changed:
  ----- Method: VMMaker>>needsToRegenerateInterpreterFile (in category 'initialize') -----
  needsToRegenerateInterpreterFile
  "Check the timestamp for the relevant classes and then the timestamp for the main
  source file (e.g. interp.c) if it already exists.  Answer if the file needs regenerating."
 
  | classes tStamp |
  classes := self interpreterClass withAllSuperclasses copyUpTo: VMClass.
  self interpreterClass objectMemoryClass ifNotNil:
  [:objectMemoryClass|
  classes addAllLast: (objectMemoryClass  withAllSuperclasses copyUpTo: VMClass)].
  classes copy do:
  [:class| classes addAllLast: (class ancilliaryClasses: self options)].
  tStamp := classes inject: 0 into: [:tS :cl| tS max: cl timeStamp].
 
  "don't translate if the file is newer than my timeStamp"
  (self coreVMDirectory entryAt: self interpreterFilename ifAbsent: [nil]) ifNotNil:
  [:fstat|
  tStamp < fstat modificationTime ifTrue:
+ [^self confirm: 'The ', self configurationNameIfAny, 'interpreter classes have not been modified since\ the interpreter file was last generated.\Do you still want to regenerate the source file?' withCRs]].
- [^self confirm: 'The ', self configurationNameIfAny, 'interpreter classes have not been modified since\ the interpreter file was last generated.\Do you still want to regenerate their source file?' withCRs]].
  ^true
  !