[Vm-dev] VM Maker: VMMaker.oscog-cb.2450.mcz

Jan Barger barniisk at gmail.com
Mon Oct 8 17:00:44 UTC 2018


unsubscribe

po 8. 10. 2018 o 16:10 <commits at source.squeak.org> napĂ­sal(a):

>
> ClementBera uploaded a new version of VMMaker to project VM Maker:
> http://source.squeak.org/VMMaker/VMMaker.oscog-cb.2450.mcz
>
> ==================== Summary ====================
>
> Name: VMMaker.oscog-cb.2450
> Author: cb
> Time: 8 October 2018, 4:07:59.681908 pm
> UUID: 48299b6e-2ad2-49b2-858f-3ff2e0ddbf84
> Ancestors: VMMaker.oscog-cb.2449
>
> Fix a bug in lilliputian management in selectivecompactor when adding a
> segment to compact into while there is none available.
>
> =============== Diff against VMMaker.oscog-cb.2449 ===============
>
> 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_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 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: InterpreterPlugin>>strncpy: (in category 'simulation
> support') -----
> + strncpy: aString _: bString _: n
> +       <doNotGenerate>
> +       ^interpreterProxy strncpy: aString _: bString _: n!
>
> Item was removed:
> - ----- Method: InterpreterPlugin>>strncpy:_:_: (in category 'simulation
> support') -----
> - strncpy: aString _: bString _: n
> -       <doNotGenerate>
> -       ^interpreterProxy strncpy: aString _: bString _: n!
>
> 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 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: 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 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 changed:
>   ----- Method: SpurSelectiveCompactor>>findAndSetSegmentToFill (in
> category 'segment to fill') -----
>   findAndSetSegmentToFill
>         | segInfo firstEntity |
>         <var: 'segInfo' type: #'SpurSegmentInfo *'>
>         0 to: manager numSegments - 1 do:
>                 [:i|
>                  segInfo := self addressOf: (manager segmentManager
> segments at: i).
>                  firstEntity := manager objectStartingAt: segInfo segStart.
>                  ((manager isFreeObject: firstEntity) and: [(manager
> objectAfter: firstEntity limit: manager endOfMemory) = (manager
> segmentManager bridgeFor: segInfo)])
> +                       ifTrue: [segmentToFill := segInfo. ^i]].
> +       ^-1
> -                       ifTrue: [segmentToFill := segInfo. ^0]].
>         !
>
> Item was changed:
>   ----- Method: SpurSelectiveCompactor>>findOrAllocateSegmentToFill (in
> category 'segment to fill') -----
>   findOrAllocateSegmentToFill
>         "There was no compacted segments from past GC that we can directly
> re-use.
>          We need either to find an empty segment or allocate a new one."
> +       | segIndex |
>         self findAndSetSegmentToFill.
>         segmentToFill ifNotNil: [^0].
>         "No empty segment. We need to allocate a new one"
>         self allocateSegmentToFill.
>         "We don't know which segment it is that we've just allocated... So
> we look for it... This is a bit dumb."
> +       segIndex := self findAndSetSegmentToFill.
> +       "Lilliputian performance hack management... Last lilliputian of
> new segment is same as prev because no lilliputian in new segment"
> +       self setLastLilliputianChunkAtindex: segIndex to: (self
> lastLilliputianChunkAtIndex: segIndex - 1).
> -       self findAndSetSegmentToFill.
>         self assert: segmentToFill ~~ nil.
>         !
>
> 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>>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>>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>>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>>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>>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>>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>>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>>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 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!
>
>

-- 
Ing. Jan Barger

www.napri.sk
www.barnet.sk
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.squeakfoundation.org/pipermail/vm-dev/attachments/20181008/856e1e4c/attachment-0001.html>


More information about the Vm-dev mailing list