VM Maker: VMMaker.oscog-cb.2148.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-cb.2148.mcz

commits-2
 
ClementBera uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-cb.2148.mcz

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

Name: VMMaker.oscog-cb.2148
Author: cb
Time: 13 March 2017, 4:26:04.291103 pm
UUID: 7ad32bbc-667b-4b98-9588-6bbd8f15d214
Ancestors: VMMaker.oscog-dtl.2147

I do not merge with Eliot's version as it seems buggy.

- Changed pushFullClosure code to worj around a slang compilation bug
- fixes and improvements in SocketSimulatorPlugin and StackInterpreterSimulator to support Pharo simulation better

=============== Diff against VMMaker.oscog-dtl.2147 ===============

Item was changed:
  ----- Method: CoInterpreter>>pushFullClosureNumArgs:copiedValues:compiledBlock:receiverIsOnStack:ignoreContext: (in category 'stack bytecodes') -----
  pushFullClosureNumArgs: numArgs copiedValues: numCopiedArg compiledBlock: compiledBlock receiverIsOnStack: receiverIsOnStack ignoreContext: ignoreContext
  "The compiler has pushed the values to be copied, if any. The receiver has been pushed on stack before if specified.
  Create a Closure with space for the copiedValues and pop numCopied values off the stack into the closure.
  Sets outerContext, compiledBlock, numArgs and receiver as specified.."
  <inline: true>
  | numCopied newClosure context startIndex |
  "No need to record the pushed copied values in the outerContext."
+ ignoreContext
+ ifTrue: [context := objectMemory nilObject ]
+ ifFalse: [context := self ensureFrameIsMarried: localFP SP: localSP + (numCopiedArg * objectMemory bytesPerOop)].
- context := ignoreContext
- ifTrue: [objectMemory nilObject ]
- ifFalse: [self ensureFrameIsMarried: localFP SP: localSP + (numCopiedArg * objectMemory bytesPerOop)].
  newClosure := self
  fullClosureIn: context
  numArgs: numArgs
  numCopiedValues: numCopiedArg
  compiledBlock: compiledBlock.
  cogit recordSendTrace ifTrue:
  [self recordTrace: TraceBlockCreation thing: newClosure source: TraceIsFromInterpreter].
  receiverIsOnStack
  ifFalse:
  [ startIndex := FullClosureFirstCopiedValueIndex.
    objectMemory storePointerUnchecked: FullClosureReceiverIndex
  ofObject: newClosure
  withValue: self receiver.
  numCopied := numCopiedArg ]
  ifTrue:
  [ startIndex := FullClosureReceiverIndex.
  numCopied := numCopiedArg + 1 ].
  numCopied > 0 ifTrue:
  [0 to: numCopied - 1 do:
  [ :i |
  "Assume: have just allocated a new BlockClosure; it must be young.
  Thus, can use unchecked stores."
  objectMemory storePointerUnchecked: i + startIndex
  ofObject: newClosure
  withValue: (self internalStackValue: numCopied - i - 1)].
  self internalPop: numCopied].
  self fetchNextBytecode.
  self internalPush: newClosure!

Item was added:
+ ----- Method: SocketPluginSimulator>>sqResolverLocalAddress (in category 'simulation') -----
+ sqResolverLocalAddress
+ "For now don't simulate the implicit semaphore."
+ | bytes |
+ bytes := NetNameResolver primLocalAddress.
+ self assert: bytes size = 4.
+ "Effectively netAddressToInt: bytes"
+ ^ ((bytes at: 4)) +
+ ((bytes at: 3) <<8) +
+ ((bytes at: 2) <<16) +
+ ((bytes at: 1) <<24)!

Item was changed:
  ----- Method: StackInterpreter>>pushFullClosureNumArgs:copiedValues:compiledBlock:receiverIsOnStack:ignoreContext: (in category 'stack bytecodes') -----
  pushFullClosureNumArgs: numArgs copiedValues: numCopiedArg compiledBlock: compiledBlock receiverIsOnStack: receiverIsOnStack ignoreContext: ignoreContext
  "The compiler has pushed the values to be copied, if any. The receiver has been pushed on stack before if specified.
  Create a Closure with space for the copiedValues and pop numCopied values off the stack into the closure.
  Sets outerContext, compiledBlock, numArgs and receiver as specified.."
  <inline: true>
  | numCopied newClosure context startIndex |
  "No need to record the pushed copied values in the outerContext."
+ ignoreContext
+ ifTrue: [context := objectMemory nilObject ]
+ ifFalse: [context := self ensureFrameIsMarried: localFP SP: localSP + (numCopiedArg * objectMemory bytesPerOop)].
- context := ignoreContext
- ifTrue: [objectMemory nilObject ]
- ifFalse: [self ensureFrameIsMarried: localFP SP: localSP + (numCopiedArg * objectMemory bytesPerOop)].
  newClosure := self
  fullClosureIn: context
  numArgs: numArgs
  numCopiedValues: numCopiedArg
  compiledBlock: compiledBlock.
  receiverIsOnStack
  ifFalse:
  [ startIndex := FullClosureFirstCopiedValueIndex.
    objectMemory storePointerUnchecked: FullClosureReceiverIndex
  ofObject: newClosure
  withValue: self receiver.
  numCopied := numCopiedArg ]
  ifTrue:
  [ startIndex := FullClosureReceiverIndex.
  numCopied := numCopiedArg + 1 ].
  numCopied > 0 ifTrue:
  [0 to: numCopied - 1 do:
  [ :i |
  "Assume: have just allocated a new BlockClosure; it must be young.
  Thus, can use unchecked stores."
  objectMemory storePointerUnchecked: i + startIndex
  ofObject: newClosure
  withValue: (self internalStackValue: numCopied - i - 1)].
  self internalPop: numCopied].
  self fetchNextBytecode.
  self internalPush: newClosure!

Item was removed:
- ----- Method: StackInterpreterSimulator>>externalWriteBackHeadFramePointers (in category 'stack pages') -----
- externalWriteBackHeadFramePointers
- self assert: (localFP = framePointer
- or: [localFP = (self frameCallerFP: framePointer)]).
- super externalWriteBackHeadFramePointers!

Item was changed:
  ----- Method: StackInterpreterSimulator>>getErrorObjectFromPrimFailCode (in category 'debugging traps') -----
  getErrorObjectFromPrimFailCode
+ (primFailCode > 1 and: [(#(primitiveNew primitiveFetchNextMourner) includes: primitiveFunctionPointer) not]) ifTrue: [self halt].
- primFailCode > 1 ifTrue: [self halt].
  ^super getErrorObjectFromPrimFailCode!

Item was changed:
  ----- Method: StackInterpreterSimulator>>primitiveDirectoryEntry (in category 'file primitives') -----
  primitiveDirectoryEntry
  | name pathName arrayNilOrSymbol result |
  name := self stringOf: self stackTop.
  pathName := self stringOf: (self stackValue: 1).
 
- "temporary work-around to make it work in Pharo..."
- self cppIf: PharoVM ifTrue: [ pathName := Smalltalk imagePath ].
-
  self successful ifFalse:
  [^self primitiveFail].
 
  arrayNilOrSymbol := FileDirectory default primLookupEntryIn: pathName name: name.
  arrayNilOrSymbol ifNil:
  [self pop: 3 thenPush: objectMemory nilObject.
  ^self].
  arrayNilOrSymbol isArray ifFalse:
  ["arrayNilOrSymbol ~~ #primFailed ifTrue:
  [self halt]. "
  self transcript show: name , ' NOT FOUND'.
  ^self primitiveFail].
 
  result := PharoVM
  ifTrue:
  [self makeDirEntryName: (arrayNilOrSymbol at: 1) size: (arrayNilOrSymbol at: 1) size
  createDate: (arrayNilOrSymbol at: 2) modDate: (arrayNilOrSymbol at: 3)
  isDir: (arrayNilOrSymbol at: 4) fileSize: (arrayNilOrSymbol at: 5)
+ posixPermissions: (arrayNilOrSymbol at: 6 ifAbsent: [8r644]) isSymlink: (arrayNilOrSymbol at: 7 ifAbsent: [false]) ]
- posixPermissions: (arrayNilOrSymbol at: 6) isSymlink: (arrayNilOrSymbol at: 7) ]
  ifFalse:
  [self makeDirEntryName: (arrayNilOrSymbol at: 1) size: (arrayNilOrSymbol at: 1) size
  createDate: (arrayNilOrSymbol at: 2) modDate: (arrayNilOrSymbol at: 3)
  isDir: (arrayNilOrSymbol at: 4) fileSize: (arrayNilOrSymbol at: 5) ].
  self pop: 3 thenPush: result!