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

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

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

Name: VMMaker.oscog-eem.2440
Author: eem
Time: 18 September 2018, 3:37:44.633153 pm
UUID: d7f5e4fc-4d3c-4afa-aa43-5d8668d0b5c9
Ancestors: VMMaker.oscog-eem.2439

More Pharo compatibility.

Refactor FilePluginSimulator simulation of primitiveDirectoryEntry & primitiveDirectoryLookup (primLookupEntryIn:name: & primLookupEntryIn:index:) so that the actual primitives in FilePlugin are simulated.  Modify Slang to strip trailing underscores from selectors when constructing C function names, allowing a nice "varargs" convention (we should use this to get rid of my horrible hacks such as mem:cp:y:, st:rn:cpy: et al, which are too difficult to read or remember).  Improve CObjectAccessor printing for cases like dir_[Entry]Lookup:_:_:_:_:_:_:_:_:_:_:_: so we can see the fake pointer accessors.

Eliminate the variation on dir_[Entry]Lookup between PharoVM and SqueakVM, leaving the difference only in makeDirEntryName:size:createDate:modDate:isDir:fileSize:[posixPermissions:isSymlink:].  (Hence a new FilePlugin must be coordinated with platfiorm code changes).

Fix a bug in attemptToComputeTempNamesFor: with methods with blocks but no top level temps.

Haver statementsFor:varName: work in Pharo as well as Squeak.

Remove an and:and: from bindVariableUsesIn:andConstantFoldIf:in:

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

Item was changed:
  ----- Method: CCodeGenerator>>cFunctionNameFor: (in category 'C code generator') -----
  cFunctionNameFor: aSelector
  "Create a C function name from the given selector by finding
+ a specific translation, or if none, simply omitting colons, and
+ any trailing underscores (this supports a varargs convention)."
+ ^selectorTranslations
+ at: aSelector
+ ifAbsent:
+ [| cSelector |
+ cSelector := aSelector copyWithout: $:.
+ [cSelector last = $_] whileTrue:
+ [cSelector := cSelector allButLast].
+ cSelector]!
- a specific translation, or if none, simply omitting colons."
- ^selectorTranslations at: aSelector ifAbsent: [aSelector copyWithout: $:]!

Item was removed:
- ----- Method: CObjectAccessor>>printOnStream: (in category 'printing') -----
- printOnStream: aStream
- super printOnStream: aStream.
- aStream
- print:' on: ';
- write: object.!

Item was added:
+ ----- Method: CPluggableAccessor>>printOn: (in category 'printing') -----
+ printOn: aStream
+ super printOn: aStream.
+ (object isNil and: [readBlock notNil or: [writeBlock notNil]]) ifTrue:
+ [[aStream nextPutAll: ' in '; print: (readBlock home tempAt: 2) home]
+ on: Error
+ do: [:ex| ]]!

Item was removed:
- ----- Method: CogVMSimulator>>makeDirEntryName:size:createDate:modDate:isDir:fileSize: (in category 'file primitives') -----
- makeDirEntryName: entryName size: entryNameSize
- createDate: createDate modDate: modifiedDate
- isDir: dirFlag fileSize: fileSize
-
- ^(pluginList
- detect: [:assoc| assoc key = 'FilePlugin']
- ifNone: [self error: 'this message should not be sent unless the FilePlugin has been loaded']) value
- makeDirEntryName: entryName size: entryNameSize
- createDate: createDate modDate: modifiedDate
- isDir: dirFlag fileSize: fileSize!

Item was removed:
- ----- Method: CogVMSimulator>>makeDirEntryName:size:createDate:modDate:isDir:fileSize:posixPermissions:isSymlink: (in category 'as yet unclassified') -----
- makeDirEntryName: entryName size: entryNameSize createDate: createDate modDate: modifiedDate isDir: dirFlag fileSize: fileSize posixPermissions: posixPermissions isSymlink: symlinkFlag
-
- ^(pluginList
- detect: [:assoc| assoc key = 'FilePlugin']
- ifNone: [self error: 'this message should not be sent unless the FilePlugin has been loaded']) value
- makeDirEntryName: entryName size: entryNameSize
- createDate: createDate modDate: modifiedDate
- isDir: dirFlag fileSize: fileSize
- posixPermissions: fileSize isSymlink: symlinkFlag!

Item was removed:
- ----- Method: CogVMSimulator>>primitiveDirectoryEntry (in category 'file primitives') -----
- primitiveDirectoryEntry
- | name pathName arrayNilOrSymbol result |
- name := self stringOf: self stackTop.
- pathName := self stringOf: (self stackValue: 1).
-
- 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])]
- 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!

Item was removed:
- ----- Method: CogVMSimulator>>primitiveDirectoryLookup (in category 'file primitives') -----
- primitiveDirectoryLookup
- | index pathName array result |
- index := self stackIntegerValue: 0.
- pathName := self stringOf: (self stackValue: 1).
-
- self successful ifFalse:
- [^self primitiveFail].
-
- array := FileDirectory default primLookupEntryIn: pathName index: index.
-
- array ifNil:
- [self pop: 3 thenPush: objectMemory nilObject.
- ^array].
- array == #badDirectoryPath ifTrue:
- [^self "halt" primitiveFail].
-
- result := PharoVM
- ifTrue: [self makeDirEntryName: (array at: 1) size: (array at: 1) size
- createDate: (array at: 2) modDate: (array at: 3)
- isDir: (array at: 4) fileSize: (array at: 5)
- posixPermissions: (array at: 6 ifAbsent: 8r664) isSymlink: (array at: 7 ifAbsent: [false]) ]
- ifFalse: [self makeDirEntryName: (array at: 1) size: (array at: 1) size
- createDate: (array at: 2) modDate: (array at: 3)
- isDir: (array at: 4) fileSize: (array at: 5)].
-
- self pop: 3 thenPush: result!

Item was changed:
  ----- Method: Cogit class>>attemptToComputeTempNamesFor: (in category 'in-image compilation support') -----
  attemptToComputeTempNamesFor: aCompiledMethod
  (aCompiledMethod respondsTo: #tempNames) ifTrue:
  [| schematicTemps blocks |
  schematicTemps := aCompiledMethod methodNode schematicTempNamesString.
  blocks := aCompiledMethod embeddedBlockClosures.
  InitializationOptions
  at: #tempNames
  put: (Dictionary newFrom: {aCompiledMethod initialPC -> (self decomposeSchematicTemps: (schematicTemps copyUpTo: $[))},
  (blocks
  ifEmpty: [#()]
  ifNotEmpty:
  [aCompiledMethod embeddedBlockClosures
+ with: (schematicTemps first = $[
+ ifTrue: [schematicTemps piecesCutWhere: [:a :b| b = $[]]
+ ifFalse: [(schematicTemps piecesCutWhere: [:a :b| b = $[]) allButFirst])
- with: (schematicTemps piecesCutWhere: [:a :b| b = $[]) allButFirst
  collect: [:c :s| c startpc -> (self decomposeSchematicTemps: (s copyWithoutAll: '[]'))]]))]!

Item was changed:
  ----- Method: CompiledMethod>>asTranslationMethodOfClass: (in category '*VMMaker-C translation') -----
  asTranslationMethodOfClass: aTMethodClass
    "Answer a TMethod (or subclass) derived from the receiver."
  ^((CompiledMethod includesSelector: #ast)
+ ifTrue: [self parseTree] "Pharo Opal Bytecode Compiler"
- ifTrue: [self ast] "Pharo Opal Bytecode Compiler"
  ifFalse: [self methodNode]) "Squeak Smalltalk-80 Bytecode Compiler"
  asTranslationMethodOfClass: aTMethodClass!

Item was changed:
  ----- Method: FilePlugin>>primitiveDirectoryEntry (in category 'directory primitives') -----
  primitiveDirectoryEntry
 
  "Two arguments - directory path, and simple file name;
    returns an array (see primitiveDirectoryLookup) describing the file or directory,
    or nil if it does not exist.  
  Primitive fails if the outer path does not identify a readable directory.
  (This is a lookup-by-name variant of primitiveDirectoryLookup.)"
 
  | requestedName pathName pathNameIndex pathNameSize status entryName entryNameSize createDate modifiedDate dirFlag posixPermissions symlinkFlag fileSize okToList reqNameIndex reqNameSize |
 
  <var: 'entryName' declareC: 'char entryName[256]'>
  <var: 'pathNameIndex' type: 'char *'>
  <var: 'reqNameIndex' type: 'char *'>
  <var: 'fileSize' type: 'squeakFileOffsetType'>
  <export: true>
 
  requestedName := interpreterProxy stackValue: 0.
  pathName := interpreterProxy stackValue: 1.
+ (interpreterProxy isBytes: pathName) ifFalse:
+ [^interpreterProxy primitiveFail].
- (interpreterProxy isBytes: pathName)
- ifFalse: [^interpreterProxy primitiveFail].
 
  "Outbound string parameters"
  pathNameIndex := interpreterProxy firstIndexableField: pathName.
  pathNameSize := interpreterProxy byteSizeOf: pathName.
 
  reqNameIndex := interpreterProxy firstIndexableField: requestedName.
  reqNameSize := interpreterProxy byteSizeOf: requestedName.
+ self cCode: '' inSmalltalk:
+ [entryName := ByteString new: 256.
+ entryNameSize := createDate := modifiedDate := dirFlag := fileSize := posixPermissions := symlinkFlag := nil].
-
  "If the security plugin can be loaded, use it to check for permission.
+ If not, assume it's ok"
+ okToList := sCLPfn ~= 0
+ ifTrue: [self cCode: '((sqInt (*)(char *, sqInt))sCLPfn)(pathNameIndex, pathNameSize)' inSmalltalk: [true]]
+ ifFalse: [true].
+ status := okToList
+ ifTrue:
+ [self dir_EntryLookup: pathNameIndex _: pathNameSize
+ _: reqNameIndex _: reqNameSize
+ _: entryName _: (self addressOf: entryNameSize put: [:v| entryNameSize := v])
+ _: (self addressOf: createDate put: [:v| createDate := v])
+ _: (self addressOf: modifiedDate put: [:v| modifiedDate := v])
+ _: (self addressOf: dirFlag put: [:v| dirFlag := v])
+ _: (self addressOf: fileSize put: [:v| fileSize := v])
+ _: (self addressOf: posixPermissions put: [:v| posixPermissions := v])
+ _: (self addressOf: symlinkFlag put: [:v| symlinkFlag := v])]
+ ifFalse:
+ [DirNoMoreEntries].
- If not, assume it's ok"
- sCLPfn ~= 0
- ifTrue: [okToList := self cCode: '((sqInt (*)(char *, sqInt))sCLPfn)(pathNameIndex, pathNameSize)']
- ifFalse: [okToList := true].
- okToList
- ifTrue: [
- self
- cppIf: PharoVM
- ifTrue: [
- status := self cCode: 'dir_EntryLookup(pathNameIndex, pathNameSize, reqNameIndex, reqNameSize,  
- entryName, &entryNameSize, &createDate,
- &modifiedDate, &dirFlag, &fileSize,
- &posixPermissions, &symlinkFlag)' ]
- ifFalse: [
- status := self cCode: 'dir_EntryLookup(pathNameIndex, pathNameSize, reqNameIndex, reqNameSize,
-  entryName, &entryNameSize, &createDate,
-  &modifiedDate, &dirFlag, &fileSize)'] ]
- ifFalse: [status := DirNoMoreEntries].
 
+ interpreterProxy failed ifTrue:
+ [^nil].
+ status = DirNoMoreEntries ifTrue: "no entry; return nil"
+ [interpreterProxy "pop pathName, index, rcvr"
+ pop: 3 thenPush: interpreterProxy nilObject.
- interpreterProxy failed
- ifTrue: [^nil].
- status = DirNoMoreEntries
- ifTrue: ["no entry; return nil"
- interpreterProxy pop: 3 "pop pathName, index, rcvr"
- thenPush: interpreterProxy nilObject.
  ^nil].
+ status = DirBadPath ifTrue:
+ [^interpreterProxy primitiveFail]."bad path"
- status = DirBadPath
- ifTrue: [^interpreterProxy primitiveFail]."bad path"
 
+ interpreterProxy
+ pop: 3 "pop pathName, index, rcvr"
+ thenPush:
+ (self
+ cppIf: PharoVM
+ ifTrue:
+ [self
+ makeDirEntryName: entryName
+ size: entryNameSize
+ createDate: createDate
+ modDate: modifiedDate
+ isDir: dirFlag
+ fileSize: fileSize
+ posixPermissions: posixPermissions
+ isSymlink: symlinkFlag]
+ ifFalse:
+ [self
+ makeDirEntryName: entryName
+ size: entryNameSize
+ createDate: createDate
+ modDate: modifiedDate
+ isDir: dirFlag
+ fileSize: fileSize])!
- self
- cppIf: PharoVM
- ifTrue: [
- interpreterProxy
- pop: 3 "pop pathName, index, rcvr"
- thenPush: (self
- makeDirEntryName: entryName
- size: entryNameSize
- createDate: createDate
- modDate: modifiedDate
- isDir: dirFlag
- fileSize: fileSize
- posixPermissions: posixPermissions
- isSymlink: symlinkFlag) ]
- ifFalse: [
- interpreterProxy
- pop: 3 "pop pathName, fName, rcvr"
- thenPush: (self
- makeDirEntryName: entryName
- size: entryNameSize
- createDate: createDate
- modDate: modifiedDate
- isDir: dirFlag
- fileSize: fileSize) ]!

Item was changed:
  ----- Method: FilePlugin>>primitiveDirectoryLookup (in category 'directory primitives') -----
  primitiveDirectoryLookup
 
  | index pathName pathNameIndex pathNameSize status entryName entryNameSize createDate modifiedDate dirFlag symlinkFlag posixPermissions fileSize okToList |
 
  <var: 'entryName' declareC: 'char entryName[256]'>
  <var: 'pathNameIndex' type: 'char *'>
  <var: 'fileSize' type: 'squeakFileOffsetType'>
  <export: true>
 
  index := interpreterProxy stackIntegerValue: 0.
  pathName := interpreterProxy stackValue: 1.
  (interpreterProxy isBytes: pathName)
  ifFalse: [^interpreterProxy primitiveFail].
  pathNameIndex := interpreterProxy firstIndexableField: pathName.
  pathNameSize := interpreterProxy byteSizeOf: pathName.
+ self cCode: '' inSmalltalk:
+ [entryName := ByteString new: 256.
+ entryNameSize := createDate := modifiedDate := dirFlag := fileSize := posixPermissions := symlinkFlag := nil].
  "If the security plugin can be loaded, use it to check for permission.
  If not, assume it's ok"
+ okToList := sCLPfn ~= 0
+ ifTrue: [self cCode: '((sqInt (*)(char *, sqInt))sCLPfn)(pathNameIndex, pathNameSize)' inSmalltalk: [true]]
+ ifFalse: [true].
+ status := okToList
+ ifTrue:
+ [self dir_Lookup: pathNameIndex _: pathNameSize
+ _: index
+ _: entryName _: (self addressOf: entryNameSize put: [:v| entryNameSize := v])
+ _: (self addressOf: createDate put: [:v| createDate := v])
+ _: (self addressOf: modifiedDate put: [:v| modifiedDate := v])
+ _: (self addressOf: dirFlag put: [:v| dirFlag := v])
+ _: (self addressOf: fileSize put: [:v| fileSize := v])
+ _: (self addressOf: posixPermissions put: [:v| posixPermissions := v])
+ _: (self addressOf: symlinkFlag put: [:v| symlinkFlag := v])]
+ ifFalse: [DirNoMoreEntries].
+ interpreterProxy failed ifTrue:
+ [^nil].
+ status = DirNoMoreEntries ifTrue: "no more entries; return nil"
+ [interpreterProxy "pop pathName, index, rcvr"
+ pop: 3 thenPush: interpreterProxy nilObject.
+ ^nil].
+ status = DirBadPath ifTrue:
+ [^interpreterProxy primitiveFail]."bad path"
- sCLPfn ~= 0
- ifTrue: [okToList := self cCode: '((sqInt (*)(char *, sqInt))sCLPfn)(pathNameIndex, pathNameSize)']
- ifFalse: [okToList := true].
- okToList
- ifTrue: [
- self
- cppIf: PharoVM
- ifTrue: [
- status := self cCode: 'dir_Lookup(pathNameIndex, pathNameSize, index,
- entryName, &entryNameSize, &createDate,
- &modifiedDate, &dirFlag, &fileSize,
- &posixPermissions, &symlinkFlag)' ]
- ifFalse: [
- status := self cCode: 'dir_Lookup(pathNameIndex, pathNameSize, index,
- entryName, &entryNameSize, &createDate,
- &modifiedDate, &dirFlag, &fileSize)' ] ]
- ifFalse: [status := DirNoMoreEntries].
- interpreterProxy failed
- ifTrue: [^nil].
- status = DirNoMoreEntries
- ifTrue: ["no more entries; return nil"
- interpreterProxy pop: 3 "pop pathName, index, rcvr"
- thenPush: interpreterProxy nilObject.
- ^nil].
- status = DirBadPath
- ifTrue: [^interpreterProxy primitiveFail]."bad path"
 
+ interpreterProxy
+ pop: 3 "pop pathName, index, rcvr"
+ thenPush:
+ (self
+ cppIf: PharoVM
+ ifTrue:
+ [self
- self
- cppIf: PharoVM
- ifTrue: [
- interpreterProxy
- pop: 3 "pop pathName, index, rcvr"
- thenPush: (self
- makeDirEntryName: entryName
- size: entryNameSize
- createDate: createDate
- modDate: modifiedDate
- isDir: dirFlag
- fileSize: fileSize
- posixPermissions: posixPermissions
- isSymlink: symlinkFlag) ]
- ifFalse: [
- interpreterProxy
- pop: 3 "pop pathName, index, rcvr"
- thenPush: (self
  makeDirEntryName: entryName
  size: entryNameSize
  createDate: createDate
  modDate: modifiedDate
  isDir: dirFlag
+ fileSize: fileSize
+ posixPermissions: posixPermissions
+ isSymlink: symlinkFlag]
+ ifFalse:
+ [self
+ makeDirEntryName: entryName
+ size: entryNameSize
+ createDate: createDate
+ modDate: modifiedDate
+ isDir: dirFlag
+ fileSize: fileSize])!
- fileSize: fileSize) ]!

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 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 added:
+ ----- Method: FilePluginSimulator>>primLookupEntryIn:index: (in category 'simulation') -----
+ primLookupEntryIn: fullPath index: index
+ "Look up the index-th entry of the directory with the given fully-qualified path (i.e., starting from the root of the file hierarchy) and return an array containing:
+
+ <name> <creationTime> <modificationTime> <dirFlag> <fileSize>
+
+ The empty string enumerates the top-level files or drives. (For example, on Unix, the empty path enumerates the contents of '/'. On Macs and PCs, it enumerates the mounted volumes/drives.)
+
+ The creation and modification times are in seconds since the start of the Smalltalk time epoch. DirFlag is true if the entry is a directory. FileSize the file size in bytes or zero for directories. The primitive returns nil when index is past the end of the directory. It fails if the given path is bad."
+
+   <primitive: 'primitiveDirectoryLookup' module: 'FilePlugin' error: ec>
+ ^ec isInteger
+ ifTrue: [ec]
+ ifFalse:
+ [Smalltalk primitiveErrorTable
+ indexOf: ec
+ ifAbsent: [Smalltalk primitiveErrorTable size + 1]]!

Item was added:
+ ----- Method: FilePluginSimulator>>primLookupEntryIn:name: (in category 'simulation') -----
+ primLookupEntryIn: fullPath name: fName
+ "Look up <fName> (a simple file name) in the directory identified by <fullPath>
+   and return an array containing:
+
+ <fName> <creationTime> <modificationTime> <dirFlag> <fileSize>
+
+ On Unix, the empty path denotes '/'.
+       On Macs and PCs, it is the container of the system volumes.)
+
+ The creation and modification times are in seconds since the start of the Smalltalk time epoch. DirFlag is true if the entry is a directory. FileSize the file size in bytes or zero for directories. The primitive returns nil when index is past the end of the directory. It fails if the given path is bad."
+
+   <primitive: 'primitiveDirectoryEntry' module: 'FilePlugin' error: ec>
+ ^ec isInteger
+ ifTrue: [ec]
+ ifFalse:
+ [Smalltalk primitiveErrorTable
+ indexOf: ec
+ ifAbsent: [Smalltalk primitiveErrorTable size + 1]]!

Item was removed:
- ----- Method: FilePluginSimulator>>primitiveDirectoryEntry (in category 'simulation') -----
- primitiveDirectoryEntry
- ^interpreterProxy interpreter primitiveDirectoryEntry!

Item was removed:
- ----- Method: FilePluginSimulator>>primitiveDirectoryLookup (in category 'simulation') -----
- primitiveDirectoryLookup
- ^interpreterProxy interpreter primitiveDirectoryLookup!

Item was removed:
- ----- Method: InterpreterSimulator>>makeDirEntryName:size:createDate:modDate:isDir:fileSize: (in category 'file primitives') -----
- makeDirEntryName: entryName size: entryNameSize
- createDate: createDate modDate: modifiedDate
- isDir: dirFlag fileSize: fileSize
-
- ^(pluginList
- detect: [:assoc| assoc key = 'FilePlugin']
- ifNone: [self error: 'this message should not be sent unless the FilePlugin has been loaded']) value
- makeDirEntryName: entryName size: entryNameSize
- createDate: createDate modDate: modifiedDate
- isDir: dirFlag fileSize: fileSize!

Item was removed:
- ----- Method: InterpreterSimulator>>makeDirEntryName:size:createDate:modDate:isDir:fileSize:posixPermissions:isSymlink: (in category 'file primitives') -----
- makeDirEntryName: entryName size: entryNameSize createDate: createDate modDate: modifiedDate isDir: dirFlag fileSize: posixPermissions posixPermissions: fileSize isSymlink: symlinkFlag
-
- ^(pluginList
- detect: [:assoc| assoc key = 'FilePlugin']
- ifNone: [self error: 'this message should not be sent unless the FilePlugin has been loaded']) value
- makeDirEntryName: entryName size: entryNameSize
- createDate: createDate modDate: modifiedDate
- isDir: dirFlag fileSize: fileSize
- posixPermissions: fileSize isSymlink: symlinkFlag!

Item was removed:
- ----- Method: InterpreterSimulator>>primitiveDirectoryEntry (in category 'file primitives') -----
- primitiveDirectoryEntry
- | name pathName array result |
- name := self stringOf: self stackTop.
- pathName := self stringOf: (self stackValue: 1).
-
- successFlag ifFalse:
- [^self primitiveFail].
-
- array := FileDirectory default primLookupEntryIn: pathName name: name.
- array == nil ifTrue:
- [self pop: 3 thenPush: nilObj.
- ^array].
- array == #badDirectoryPath ifTrue:
- [self halt.
- ^self primitiveFail].
-
- PharoVM
- ifTrue: [
- result := self makeDirEntryName: (array at: 1) size: (array at: 1) size
- createDate: (array at: 2) modDate: (array at: 3)
- isDir: (array at: 4) fileSize: (array at: 5)
- posixPermissions: (array at: 6) isSymlink: (array at: 7) ]
- ifFalse: [
- result := self makeDirEntryName: (array at: 1) size: (array at: 1) size
- createDate: (array at: 2) modDate: (array at: 3)
- isDir: (array at: 4)  fileSize: (array at: 5) ].
- self pop: 3.
- self push: result!

Item was removed:
- ----- Method: InterpreterSimulator>>primitiveDirectoryLookup (in category 'file primitives') -----
- primitiveDirectoryLookup
- | index pathName array result |
- index := self stackIntegerValue: 0.
- pathName := (self stringOf: (self stackValue: 1)).
-
- successFlag ifFalse: [
- ^self primitiveFail.
- ].
-
- array := FileDirectory default primLookupEntryIn: pathName index: index.
-
- array == nil ifTrue: [
- self pop: 3.
- self push: nilObj.
- ^array.
- ].
- array == #badDirectoryPath ifTrue: [self halt.
- ^self primitiveFail.
- ].
-
- PharoVM
- ifTrue: [
- result := self makeDirEntryName: (array at: 1) size: (array at: 1) size
- createDate: (array at: 2) modDate: (array at: 3)
- isDir: (array at: 4) fileSize: (array at: 5)
- posixPermissions: (array at: 6) isSymlink: (array at: 7) ]
- ifFalse: [
- result := self makeDirEntryName: (array at: 1) size: (array at: 1) size
- createDate: (array at: 2) modDate: (array at: 3)
- isDir: (array at: 4)  fileSize: (array at: 5) ].
- self pop: 3.
- self push: result.
- !

Item was added:
+ ----- Method: SlangTests>>testStatementsHaveNoArguments (in category 'tests') -----
+ testStatementsHaveNoArguments
+ "The inliner expects the body of a TMethod to have no arguments."
+
+ | tMethod |
+ tMethod := InterpreterStackPages>>#pageIndexFor: asTranslationMethodOfClass: TMethod.
+ self assert: (tMethod parseTree args isNil or: [tMethod parseTree args isEmpty])!

Item was removed:
- ----- Method: StackInterpreterSimulator>>makeDirEntryName:size:createDate:modDate:isDir:fileSize: (in category 'file primitives') -----
- makeDirEntryName: entryName size: entryNameSize
- createDate: createDate modDate: modifiedDate
- isDir: dirFlag fileSize: fileSize
-
- ^(pluginList
- detect: [:assoc| assoc key = 'FilePlugin']
- ifNone: [self error: 'this message should not be sent unless the FilePlugin has been loaded']) value
- makeDirEntryName: entryName size: entryNameSize
- createDate: createDate modDate: modifiedDate
- isDir: dirFlag fileSize: fileSize!

Item was removed:
- ----- Method: StackInterpreterSimulator>>makeDirEntryName:size:createDate:modDate:isDir:fileSize:posixPermissions:isSymlink: (in category 'file primitives') -----
- makeDirEntryName: entryName size: entryNameSize createDate: createDate modDate: modifiedDate isDir: dirFlag fileSize: fileSize posixPermissions: posixPermissions isSymlink: symlinkFlag
-
- ^(pluginList
- detect: [:assoc| assoc key = 'FilePlugin']
- ifNone: [self error: 'this message should not be sent unless the FilePlugin has been loaded']) value
- makeDirEntryName: entryName size: entryNameSize
- createDate: createDate modDate: modifiedDate
- isDir: dirFlag fileSize: fileSize
- posixPermissions: fileSize isSymlink: symlinkFlag!

Item was removed:
- ----- Method: StackInterpreterSimulator>>primitiveDirectoryEntry (in category 'file primitives') -----
- primitiveDirectoryEntry
- | name pathName arrayNilOrSymbol result |
- name := self stringOf: self stackTop.
- pathName := self stringOf: (self stackValue: 1).
-
- 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]) ]
- 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!

Item was removed:
- ----- Method: StackInterpreterSimulator>>primitiveDirectoryLookup (in category 'file primitives') -----
- primitiveDirectoryLookup
- | index pathName array result |
- index := self stackIntegerValue: 0.
- pathName := self stringOf: (self stackValue: 1).
-
- self successful ifFalse:
- [^self primitiveFail].
-
- array := FileDirectory default primLookupEntryIn: pathName index: index.
-
- array ifNil:
- [self pop: 3 thenPush: objectMemory nilObject.
- ^array].
- array == #badDirectoryPath ifTrue:
- [^self "halt" primitiveFail].
-
- result := PharoVM
- ifTrue: [self makeDirEntryName: (array at: 1) size: (array at: 1) size
- createDate: (array at: 2) modDate: (array at: 3)
- isDir: (array at: 4) fileSize: (array at: 5)
- posixPermissions: (array at: 6 ifAbsent: 8r664) isSymlink: (array at: 7 ifAbsent: [false]) ]
- ifFalse: [self makeDirEntryName: (array at: 1) size: (array at: 1) size
- createDate: (array at: 2) modDate: (array at: 3)
- isDir: (array at: 4) fileSize: (array at: 5)].
-
- self pop: 3 thenPush: result!

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.
- s := WriteStream on: ''.
- s nextPutAll: 'temp'; cr; cr; tab.
  self printTempsAndVar: varName on: s.
  s nextPutAll: sourceText.
+ ^ (([Smalltalk compiler parse: s contents] "Pharo"
+ on: MessageNotUnderstood
+ do: [:ex|
+ ex message selector == #compiler ifFalse:
+ [ex pass].
+ Compiler new parse: s contents in: Object notifying: nil]) "Squeak"
- ^ ((Compiler new parse: s contents in: Object notifying: nil)
  asTranslationMethodOfClass: self class)
  removeFinalSelfReturnIn: nil;
  statements
  !

Item was changed:
  ----- Method: TSendNode>>bindVariableUsesIn:andConstantFoldIf:in: (in category 'transformations') -----
  bindVariableUsesIn: aDictionary andConstantFoldIf: constantFold in: codeGen
  "Answer either the receiver, if it contains no references to the given variables, or a new node with the given variables rebound.
  Attempt to constant-fold and answer a constant node commented with the original expression.
  Commenting with the original expression is important because it allows us to detect shared cases.
  e.g. currentBytecode bitAnd: 15 is the same in case 1 and case 17, but '1 /* 1 bitAnd: 15 */' differs
  from '1 /* 17 bitAnd: 15 */', whereas '1 /* currentBytecode bitAnd: 15 */' doesn't change."
  | newReceiver newArguments |
  "Constant-fold shiftForWord, but not BytesPerWord"
  ((VMBasicConstants mostBasicConstantSelectors includes: selector)
  and: [(codeGen isBuiltinSelector: selector) not]) ifTrue:
  [codeGen isConstantNode: self valueInto:
  [:val|
  ^TConstantNode new
  setValue: val;
  yourself]].
  newReceiver := receiver bindVariableUsesIn: aDictionary andConstantFoldIf: constantFold in: codeGen.
  newArguments := arguments collect: [:a| a bindVariableUsesIn: aDictionary andConstantFoldIf: constantFold in: codeGen].
  (newReceiver = receiver
  and: [newArguments = arguments]) ifTrue:
  [^self].
  (constantFold
+ and: [newReceiver isConstant and: [newReceiver value isInteger
- and: [newReceiver isConstant and: [newReceiver value isInteger]
  and: [(newArguments allSatisfy: [:ea| ea isConstant and: [ea value isInteger]])
+ and: [codeGen isBuiltinSelector: selector]]]]) ifTrue:
- and: [codeGen isBuiltinSelector: selector]]]) ifTrue:
  [| value |
  value := [newReceiver value perform: selector withArguments: (newArguments collect: [:ea| ea value])]
  on: Error
  do: [:ea| nil].
  (value isInteger
  or: [value == true
  or: [value == false]]) ifTrue:
  [^TConstantNode new
  setValue: value;
  "We assume Message prints its keywords and arguments interleaved.
  e.g. that (Message selector: #between:and: arguments: #(0 1)) printString = 'between: 0 and: 1'"
  comment: (receiver isLeaf
  ifTrue: [receiver printString]
  ifFalse: ['(', receiver printString, ')']),
  ' ',
  (Message selector: selector arguments: (arguments collect: [:ea| ea value])) printString;
  yourself]].
  ^self shallowCopy
  receiver: newReceiver;
  arguments: newArguments;
  yourself
  !