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

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

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

Name: VMMaker.oscog-eem.2451
Author: eem
Time: 9 October 2018, 4:05:16.455082 pm
UUID: 19cb967a-1123-4dbd-83b3-702e1d8350b5
Ancestors: VMMaker.oscog-cb.2450

Spur: Tweak followClassTable toi not waste effort following hiddenRootsObj.
FilePlugin: avoid createDirectory: hack.
Recategorise asString:[size:]

=============== Diff against VMMaker.oscog-cb.2450 ===============

Item was changed:
  ----- Method: FilePlugin>>primitiveDirectoryCreate (in category 'directory primitives') -----
  primitiveDirectoryCreate
-
  | dirName dirNameIndex dirNameSize okToCreate |
+ <var: #dirNameIndex type: #'char *'>
- <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 dir_Create: dirNameIndex _: dirNameSize) ifFalse:
- (self
- cCode: 'dir_Create(dirNameIndex, dirNameSize)'
- inSmalltalk: [self createDirectory: (interpreterProxy asString: dirNameIndex size: dirNameSize)]) ifFalse:
  [^interpreterProxy primitiveFail].
  interpreterProxy pop: 1!

Item was removed:
- ----- Method: FilePluginSimulator>>createDirectory: (in category 'simulation') -----
- createDirectory: aString
- ^[FileDirectory default primCreateDirectory: aString.
-   true]
- on: Error
- do: [:ex| false]
- !

Item was added:
+ ----- Method: FilePluginSimulator>>dir_Create:_: (in category 'simulation') -----
+ dir_Create: dirNameIndex _: dirNameSize
+ ^[FileDirectory default
+ primCreateDirectory: (interpreterProxy interpreter
+ asString: dirNameIndex
+ size: dirNameSize).
+   true]
+ on: Error
+ do: [:ex| false]!

Item was removed:
- ----- Method: FilePluginSimulator>>dir_EntryLookup: (in category 'simulation') -----
- dir_EntryLookup: pathString _: pathStringLength _: entryNameString _: entryNameStringLength _: name _: nameLength _: creationDate _: modificationDate _: isDirectory _: sizeIfFile _: posixPermissions _: isSymlink
- "sqInt dir_EntryLookup(char *pathString, sqInt pathStringLength, char *nameString, sqInt nameStringLength,
- /* outputs: */ char *name, sqInt *nameLength, sqInt *creationDate, sqInt *modificationDate,
-        sqInt *isDirectory, squeakFileOffsetType *sizeIfFile, sqInt *posixPermissions, sqInt *isSymlink)"
- | result pathName entryName |
- pathName := ((0 to: pathStringLength - 1) collect: [:i| (pathString at: i) asCharacter]) as: ByteString.
- entryName := ((0 to: entryNameStringLength - 1) collect: [:i| (entryNameString at: i) asCharacter]) as: ByteString.
- result := self primLookupEntryIn: pathName name: entryName.
- result ifNil: [^DirNoMoreEntries].
- result isInteger ifTrue:
- [result > 1 ifTrue:
- [interpreterProxy primitiveFailFor: result].
- ^DirBadPath].
- name replaceFrom: 1 to: result first size with: result first startingAt: 1.
- nameLength at: 0 put: result first size.
- creationDate at: 0 put: (result at: 2).
- modificationDate at: 0 put: (result at: 3).
- isDirectory at: 0 put: (result at: 4).
- sizeIfFile at: 0 put: (result at: 5).
- posixPermissions at: 0 put: (result at: 6 ifAbsent: [(result at: 4) ifTrue: [8r755] ifFalse: [8r644]]).
- isSymlink at: 0 put: (result at: 7 ifAbsent: [false]).
- ^DirEntryFound!

Item was added:
+ ----- Method: FilePluginSimulator>>dir_EntryLookup:_:_:_:_:_:_:_:_:_:_:_: (in category 'simulation') -----
+ dir_EntryLookup: pathString _: pathStringLength _: entryNameString _: entryNameStringLength _: name _: nameLength _: creationDate _: modificationDate _: isDirectory _: sizeIfFile _: posixPermissions _: isSymlink
+ "sqInt dir_EntryLookup(char *pathString, sqInt pathStringLength, char *nameString, sqInt nameStringLength,
+ /* outputs: */ char *name, sqInt *nameLength, sqInt *creationDate, sqInt *modificationDate,
+        sqInt *isDirectory, squeakFileOffsetType *sizeIfFile, sqInt *posixPermissions, sqInt *isSymlink)"
+ | result pathName entryName |
+ pathName := ((0 to: pathStringLength - 1) collect: [:i| (pathString at: i) asCharacter]) as: ByteString.
+ entryName := ((0 to: entryNameStringLength - 1) collect: [:i| (entryNameString at: i) asCharacter]) as: ByteString.
+ result := self primLookupEntryIn: pathName name: entryName.
+ result ifNil: [^DirNoMoreEntries].
+ result isInteger ifTrue:
+ [result > 1 ifTrue:
+ [interpreterProxy primitiveFailFor: result].
+ ^DirBadPath].
+ name replaceFrom: 1 to: result first size with: result first startingAt: 1.
+ nameLength at: 0 put: result first size.
+ creationDate at: 0 put: (result at: 2).
+ modificationDate at: 0 put: (result at: 3).
+ isDirectory at: 0 put: (result at: 4).
+ sizeIfFile at: 0 put: (result at: 5).
+ posixPermissions at: 0 put: (result at: 6 ifAbsent: [(result at: 4) ifTrue: [8r755] ifFalse: [8r644]]).
+ isSymlink at: 0 put: (result at: 7 ifAbsent: [false]).
+ ^DirEntryFound!

Item was removed:
- ----- Method: FilePluginSimulator>>dir_Lookup: (in category 'simulation') -----
- dir_Lookup: pathString _: pathStringLength _: index _: name _: nameLength _: creationDate _: modificationDate _: isDirectory _: sizeIfFile _: posixPermissions _: isSymlink
- "sqInt dir_Lookup( char *pathString, sqInt pathStringLength, sqInt index,
- /* outputs: */ char *name, sqInt *nameLength, sqInt *creationDate, sqInt *modificationDate,
-   sqInt *isDirectory, squeakFileOffsetType *sizeIfFile, sqInt * posixPermissions, sqInt *isSymlink)"
- | result pathName |
- pathName := ((0 to: pathStringLength - 1) collect: [:i| (pathString at: i) asCharacter]) as: ByteString.
- result := self primLookupEntryIn: pathName index: index.
- result ifNil: [^DirNoMoreEntries].
- result isInteger ifTrue:
- [result > 1 ifTrue:
- [interpreterProxy primitiveFailFor: result].
- ^DirBadPath].
- name replaceFrom: 1 to: result first size with: result first startingAt: 1.
- nameLength at: 0 put: result first size.
- creationDate at: 0 put: (result at: 2).
- modificationDate at: 0 put: (result at: 3).
- isDirectory at: 0 put: (result at: 4).
- sizeIfFile at: 0 put: (result at: 5).
- posixPermissions at: 0 put: (result at: 6 ifAbsent: [(result at: 4) ifTrue: [8r755] ifFalse: [8r644]]).
- isSymlink at: 0 put: (result at: 7 ifAbsent: [false]).
- ^DirEntryFound!

Item was added:
+ ----- Method: FilePluginSimulator>>dir_Lookup:_:_:_:_:_:_:_:_:_:_: (in category 'simulation') -----
+ dir_Lookup: pathString _: pathStringLength _: index _: name _: nameLength _: creationDate _: modificationDate _: isDirectory _: sizeIfFile _: posixPermissions _: isSymlink
+ "sqInt dir_Lookup( char *pathString, sqInt pathStringLength, sqInt index,
+ /* outputs: */ char *name, sqInt *nameLength, sqInt *creationDate, sqInt *modificationDate,
+   sqInt *isDirectory, squeakFileOffsetType *sizeIfFile, sqInt * posixPermissions, sqInt *isSymlink)"
+ | result pathName |
+ pathName := ((0 to: pathStringLength - 1) collect: [:i| (pathString at: i) asCharacter]) as: ByteString.
+ result := self primLookupEntryIn: pathName index: index.
+ result ifNil: [^DirNoMoreEntries].
+ result isInteger ifTrue:
+ [result > 1 ifTrue:
+ [interpreterProxy primitiveFailFor: result].
+ ^DirBadPath].
+ name replaceFrom: 1 to: result first size with: result first startingAt: 1.
+ nameLength at: 0 put: result first size.
+ creationDate at: 0 put: (result at: 2).
+ modificationDate at: 0 put: (result at: 3).
+ isDirectory at: 0 put: (result at: 4).
+ sizeIfFile at: 0 put: (result at: 5).
+ posixPermissions at: 0 put: (result at: 6 ifAbsent: [(result at: 4) ifTrue: [8r755] ifFalse: [8r644]]).
+ isSymlink at: 0 put: (result at: 7 ifAbsent: [false]).
+ ^DirEntryFound!

Item was removed:
- ----- Method: InterpreterPlugin>>strncpy: (in category 'simulation support') -----
- strncpy: aString _: bString _: n
- <doNotGenerate>
- ^interpreterProxy strncpy: aString _: bString _: n!

Item was added:
+ ----- Method: InterpreterPlugin>>strncpy:_:_: (in category 'simulation support') -----
+ strncpy: aString _: bString _: n
+ <doNotGenerate>
+ ^interpreterProxy strncpy: aString _: bString _: n!

Item was removed:
- ----- Method: Spur64BitMemoryManager>>memmove: (in category 'simulation only') -----
- memmove: destAddress _: sourceAddress _: bytes
- <doNotGenerate>
- | dst src  |
- dst := destAddress asInteger.
- src := sourceAddress asInteger.
- "Emulate the c library memmove function"
- self assert: bytes \\ 4 = 0.
- destAddress > sourceAddress
- ifTrue:
- [bytes - 4 to: 0 by: -4 do:
- [:i| self long32At: dst + i put: (self long32At: src + i)]]
- ifFalse:
- [0 to: bytes - 4 by: 4 do:
- [:i| self long32At: dst + i put: (self long32At: src + i)]]!

Item was added:
+ ----- Method: Spur64BitMemoryManager>>memmove:_:_: (in category 'simulation only') -----
+ memmove: destAddress _: sourceAddress _: bytes
+ <doNotGenerate>
+ | dst src  |
+ dst := destAddress asInteger.
+ src := sourceAddress asInteger.
+ "Emulate the c library memmove function"
+ self assert: bytes \\ 4 = 0.
+ destAddress > sourceAddress
+ ifTrue:
+ [bytes - 4 to: 0 by: -4 do:
+ [:i| self long32At: dst + i put: (self long32At: src + i)]]
+ ifFalse:
+ [0 to: bytes - 4 by: 4 do:
+ [:i| self long32At: dst + i put: (self long32At: src + i)]]!

Item was changed:
  ----- Method: SpurMemoryManager>>followClassTable (in category 'selective compaction') -----
  followClassTable
+ "In addition to postBecomeScanClassTable:, I follow the pages in the class table.
+ Because hiddenRootsObj follows nil, false, true and the freeLists, it can never be forwarded."
+ self deny: (self isForwarded: hiddenRootsObj).
- "In addition to postBecomeScanClassTable:, I follow hiddenRootObj and its pages"
- (self isForwarded: hiddenRootsObj) ifTrue: [hiddenRootsObj := self followForwarded: hiddenRootsObj].
  0 to: numClassTablePages - 1 do:
  [:i| | page |
  page := self followField: i ofObject: hiddenRootsObj.
  0 to: (self numSlotsOf: page) - 1 do:
  [:j| | classOrNil |
  classOrNil := self fetchPointer: j ofObject: page.
  classOrNil ~= nilObj ifTrue:
  [(self isForwarded: classOrNil) ifTrue:
  [classOrNil := self followForwarded: classOrNil.
  self storePointer: j ofObject: page withValue: classOrNil].
  (self rawHashBitsOf: classOrNil) = 0 ifTrue:
  [self storePointerUnchecked: j ofObject: page withValue: nilObj.
  "If the removed class is before the classTableIndex, set the
   classTableIndex to point to the empty slot so as to reuse it asap."
  (i << self classTableMajorIndexShift + j) < classTableIndex ifTrue:
  [classTableIndex := i << self classTableMajorIndexShift + j]]]]].
  "classTableIndex must never index the first page, which is reserved for classes known to the VM."
  self assert: classTableIndex >= (1 << self classTableMajorIndexShift).
+ self assert: self validClassTableRootPages!
- self assert: self validClassTableRootPages.!

Item was removed:
- ----- Method: SpurMemoryManager>>memcpy: (in category 'simulation') -----
- memcpy: destAddress _: sourceAddress _: bytes
- "For SpurGenerationScavenger>>copyToFutureSpace:bytes:. N.B. If ranges overlap, must use memmove."
- <doNotGenerate>
- self deny: ((destAddress <= sourceAddress and: [destAddress asInteger + bytes > sourceAddress])
- or: [sourceAddress <= destAddress and: [sourceAddress asInteger + bytes > destAddress]]).
- ^self memmove: destAddress _: sourceAddress _: bytes!

Item was added:
+ ----- Method: SpurMemoryManager>>memcpy:_:_: (in category 'simulation') -----
+ memcpy: destAddress _: sourceAddress _: bytes
+ "For SpurGenerationScavenger>>copyToFutureSpace:bytes:. N.B. If ranges overlap, must use memmove."
+ <doNotGenerate>
+ self deny: ((destAddress <= sourceAddress and: [destAddress asInteger + bytes > sourceAddress])
+ or: [sourceAddress <= destAddress and: [sourceAddress asInteger + bytes > destAddress]]).
+ ^self memmove: destAddress _: sourceAddress _: bytes!

Item was changed:
+ ----- Method: VMClass>>asString: (in category 'C library extensions') -----
- ----- Method: VMClass>>asString: (in category 'C library simulation') -----
  asString: aStringOrStringIndex
  "aStringOrStringIndex is either a string or an address in the heap.
  Create a String of the requested length form the bytes in the
  heap starting at stringIndex."
  <doNotGenerate>
  | sz |
  aStringOrStringIndex isString ifTrue:
  [^aStringOrStringIndex].
  sz := self strlen: aStringOrStringIndex.
  ^self strncpy: (ByteString new: sz) _: aStringOrStringIndex _: sz!

Item was changed:
+ ----- Method: VMClass>>asString:size: (in category 'C library extensions') -----
- ----- Method: VMClass>>asString:size: (in category 'C library simulation') -----
  asString: stringIndex size: stringSize
  "stringIndex is an address in the heap.  Create a String of the requested length
  form the bytes in the heap starting at stringIndex."
  <doNotGenerate>
  ^self strncpy: (ByteString new: stringSize) _: stringIndex _: stringSize!

Item was removed:
- ----- Method: VMClass>>memcpy: (in category 'C library simulation') -----
- memcpy: dString _: sString _: bytes
- <doNotGenerate>
- "implementation of memcpy(3). N.B. If ranges overlap, must use memmove."
- (dString isString or: [sString isString]) ifFalse:
- [| destAddress sourceAddress |
- dString class == ByteArray ifTrue:
- [ByteString adoptInstance: dString.
- ^[self memcpy: dString _: sString _: bytes] ensure:
- [ByteArray adoptInstance: dString]].
- destAddress := dString asInteger.
- sourceAddress := sString asInteger.
- self deny: ((destAddress <= sourceAddress and: [destAddress + bytes > sourceAddress])
- or: [sourceAddress <= destAddress and: [sourceAddress + bytes > destAddress]])].
- dString isString
- ifTrue:
- [1 to: bytes do:
- [:i| | v |
- v := sString isString
- ifTrue: [sString at: i]
- ifFalse: [Character value: (self byteAt: sString + i - 1)].
- dString at: i put: v]]
- ifFalse:
- [1 to: bytes do:
- [:i| | v |
- v := sString isString
- ifTrue: [(sString at: i) asInteger]
- ifFalse: [self byteAt: sString + i - 1].
- self byteAt: dString + i - 1 put: v]].
- ^dString!

Item was added:
+ ----- Method: VMClass>>memcpy:_:_: (in category 'C library simulation') -----
+ memcpy: dString _: sString _: bytes
+ <doNotGenerate>
+ "implementation of memcpy(3). N.B. If ranges overlap, must use memmove."
+ (dString isString or: [sString isString]) ifFalse:
+ [| destAddress sourceAddress |
+ dString class == ByteArray ifTrue:
+ [ByteString adoptInstance: dString.
+ ^[self memcpy: dString _: sString _: bytes] ensure:
+ [ByteArray adoptInstance: dString]].
+ destAddress := dString asInteger.
+ sourceAddress := sString asInteger.
+ self deny: ((destAddress <= sourceAddress and: [destAddress + bytes > sourceAddress])
+ or: [sourceAddress <= destAddress and: [sourceAddress + bytes > destAddress]])].
+ dString isString
+ ifTrue:
+ [1 to: bytes do:
+ [:i| | v |
+ v := sString isString
+ ifTrue: [sString at: i]
+ ifFalse: [Character value: (self byteAt: sString + i - 1)].
+ dString at: i put: v]]
+ ifFalse:
+ [1 to: bytes do:
+ [:i| | v |
+ v := sString isString
+ ifTrue: [(sString at: i) asInteger]
+ ifFalse: [self byteAt: sString + i - 1].
+ self byteAt: dString + i - 1 put: v]].
+ ^dString!

Item was removed:
- ----- Method: VMClass>>memmove: (in category 'C library simulation') -----
- memmove: destAddress _: sourceAddress _: bytes
- <doNotGenerate>
- | dst src  |
- dst := destAddress asInteger.
- src := sourceAddress asInteger.
- "Emulate the c library memmove function"
- self assert: bytes \\ 4 = 0.
- destAddress > sourceAddress
- ifTrue:
- [bytes - 4 to: 0 by: -4 do:
- [:i| self longAt: dst + i put: (self longAt: src + i)]]
- ifFalse:
- [0 to: bytes - 4 by: 4 do:
- [:i| self longAt: dst + i put: (self longAt: src + i)]]!

Item was added:
+ ----- Method: VMClass>>memmove:_:_: (in category 'C library simulation') -----
+ memmove: destAddress _: sourceAddress _: bytes
+ <doNotGenerate>
+ | dst src  |
+ dst := destAddress asInteger.
+ src := sourceAddress asInteger.
+ "Emulate the c library memmove function"
+ self assert: bytes \\ 4 = 0.
+ destAddress > sourceAddress
+ ifTrue:
+ [bytes - 4 to: 0 by: -4 do:
+ [:i| self longAt: dst + i put: (self longAt: src + i)]]
+ ifFalse:
+ [0 to: bytes - 4 by: 4 do:
+ [:i| self longAt: dst + i put: (self longAt: src + i)]]!

Item was removed:
- ----- Method: VMClass>>strcat: (in category 'C library simulation') -----
- strcat: aString _: bString
- <doNotGenerate>
- "implementation of strcat(3)"
- ^(self asString: aString), (self asString: bString)!

Item was added:
+ ----- Method: VMClass>>strcat:_: (in category 'C library simulation') -----
+ strcat: aString _: bString
+ <doNotGenerate>
+ "implementation of strcat(3)"
+ ^(self asString: aString), (self asString: bString)!

Item was removed:
- ----- Method: VMClass>>strncmp: (in category 'C library simulation') -----
- strncmp: aString _: bString _: n
- <doNotGenerate>
- "implementation of strncmp(3)"
- bString isString ifTrue:
- [1 to: n do:
- [:i|
- (aString at: i) asCharacter ~= (bString at: i) ifTrue:
- [^i]].
- ^0].
- 1 to: n do:
- [:i| | v |
- v := (aString at: i) asInteger - (self byteAt: bString + i - 1).
- v ~= 0 ifTrue: [^v]].
- ^0!

Item was added:
+ ----- Method: VMClass>>strncmp:_:_: (in category 'C library simulation') -----
+ strncmp: aString _: bString _: n
+ <doNotGenerate>
+ "implementation of strncmp(3)"
+ bString isString ifTrue:
+ [1 to: n do:
+ [:i|
+ (aString at: i) asCharacter ~= (bString at: i) ifTrue:
+ [^i]].
+ ^0].
+ 1 to: n do:
+ [:i| | v |
+ v := (aString at: i) asInteger - (self byteAt: bString + i - 1).
+ v ~= 0 ifTrue: [^v]].
+ ^0!

Item was removed:
- ----- Method: VMClass>>strncpy: (in category 'C library simulation') -----
- strncpy: aString _: bString _: n
- <doNotGenerate>
- "implementation of strncpy(3)"
- aString isString
- ifTrue:
- [1 to: n do:
- [:i| | v |
- v := bString isString
- ifTrue: [bString at: i]
- ifFalse: [Character value: (self byteAt: bString + i - 1)].
- aString at: i put: v.
- v asInteger = 0 ifTrue: [^aString]]]
- ifFalse:
- [1 to: n do:
- [:i| | v |
- v := bString isString
- ifTrue: [(bString at: i) asInteger]
- ifFalse: [self byteAt: bString + i - 1].
- self byteAt: aString + i - 1 put: v.
- v = 0 ifTrue: [^aString]]].
- ^aString!

Item was added:
+ ----- Method: VMClass>>strncpy:_:_: (in category 'C library simulation') -----
+ strncpy: aString _: bString _: n
+ <doNotGenerate>
+ "implementation of strncpy(3)"
+ aString isString
+ ifTrue:
+ [1 to: n do:
+ [:i| | v |
+ v := bString isString
+ ifTrue: [bString at: i]
+ ifFalse: [Character value: (self byteAt: bString + i - 1)].
+ aString at: i put: v.
+ v asInteger = 0 ifTrue: [^aString]]]
+ ifFalse:
+ [1 to: n do:
+ [:i| | v |
+ v := bString isString
+ ifTrue: [(bString at: i) asInteger]
+ ifFalse: [self byteAt: bString + i - 1].
+ self byteAt: aString + i - 1 put: v.
+ v = 0 ifTrue: [^aString]]].
+ ^aString!