[prev in list] [next in list] [prev in thread] [next in thread] 

List:       squeak-vm-dev
Subject:    Re: [Vm-dev] VM Maker: VMMaker.oscog-sk.2367.mcz
From:       Sophie Kaleba <sophie.kaleba () gmail ! com>
Date:       2018-04-23 21:15:19
Message-ID: CANnjgqde_u_fyK0TJ0_CgYkk=uNZ7ZFvPLKpyT_S=akz+P_12w () mail ! gmail ! com
[Download RAW message or body]

[Attachment #2 (text/plain)]

 
[Attachment #3 (multipart/alternative)]


2018-04-19 13:33 GMT+02:00 Nicolas Cellier <
nicolas.cellier.aka.nice@gmail.com>:

>
>
>
> 2018-04-19 12:14 GMT+02:00 Sophie Kaleba <sophie.kaleba@gmail.com>:
>
>>
>> Hi,
>>
>> I got a timeout error during the upload because of my slow internet
>> connexion. Hope this won't cause any problem.
>> I finally found time to commit this new primitive! If you spot any
>> mistake, contact me!
>>
>> I have updated the related methods in Squeak (updating previous senders
>> of compare:with:collated so they call this primitive instead) + the tests
>> methods but I can't commit to the repository. I can send the .st files to
>> someone who does have the rights.
>>
>> Sophie
>>
>>
> Hi Sophie,
> you can always commit to the inbox (http://source.squeak.org/inbox/).
>


Hi
Thanks! I will check I did not forget anything and will commit there

Sophie



>
> cheers
>
>
>> 2018-04-19 12:02 GMT+02:00 <commits@source.squeak.org>:
>>
>>>
>>> Sophie Kaleba uploaded a new version of VMMaker to project VM Maker:
>>> http://source.squeak.org/VMMaker/VMMaker.oscog-sk.2367.mcz
>>>
>>> ==================== Summary ====================
>>>
>>> Name: VMMaker.oscog-sk.2367
>>> Author: sk
>>> Time: 19 April 2018, 12:02:35.661622 pm
>>> UUID: 0c2401e3-1450-4f73-8e81-958f50171595
>>> Ancestors: VMMaker.oscog- nice.2366
>>>
>>> ** new primitive to compare strings (slang + JIT)
>>> answers negative smi, 0 or positive smi (instead of 1, 2 or 3 in the
>>> MiscPlugin)
>>>
>>> * Slang (primitiveCompareWith)
>>> order is optionnal.
>>> comparison loop performed in rawCompare: string1 length: strLength1
>>> with: string2 length: strLength2 accessBlock: accessBlock
>>>
>>> * JIT (genPrimitiveStringCompareWith)
>>> the JIT primitive does not take order as parameter (assumed asciiOrder)
>>> quick jump if one of the strings is empty
>>>
>>> =============== Diff against VMMaker.oscog- nice.2366 ===============
>>>
>>> Item was added:
>>> + ----- Method: CogObjectRepresentation>>genPrimitiveStringCompareWith
>>> (in category 'primitive generators') -----
>>> + genPrimitiveStringCompareWith
>>> +       "subclasses override if they can"
>>> +       ^UnimplementedPrimitive!
>>>
>>> Item was added:
>>> + ----- Method: CogObjectRepresentationForSpur
>>> >>genPrimitiveStringCompareWith (in category 'primitive generators')
>>> -----
>>> + genPrimitiveStringCompareWith
>>> +       "primitiveCompareWith:"
>>> +
>>> +       | instr jump jumpAbove jumpIncorrectFormat1 jumpIncorrectFormat2
>>> jumpIncorrectFormat3 jumpIncorrectFormat4 jumpMidFailure jumpSuccess
>>> minSizeReg string1CharOrByteSizeReg string2CharOrByteSizeReg string1Reg
>>> string2Reg |
>>> +
>>> +       <var: #jumpIncorrectFormat1 type: #'AbstractInstruction *'>
>>> +       <var: #jumpIncorrectFormat2 type: #'AbstractInstruction *'>
>>> +       <var: #jumpIncorrectFormat3 type: #'AbstractInstruction *'>
>>> +       <var: #jumpIncorrectFormat4 type: #'AbstractInstruction *'>
>>> +       <var: #jumpAbove type: #'AbstractInstruction *'>
>>> +       <var: #jumpSuccess type: #'AbstractInstruction *'>
>>> +       <var: #jump type: #'AbstractInstruction *'>
>>> +       <var: #jumpMidFailure type: #'AbstractInstruction *'>
>>> +
>>> +       "I redefine those name to ease program comprehension"
>>> +       string1Reg := ReceiverResultReg.
>>> +       string2Reg := Arg0Reg.
>>> +       string1CharOrByteSizeReg := Arg1Reg.
>>> +       string2CharOrByteSizeReg := ClassReg.
>>> +       minSizeReg := SendNumArgsReg.
>>> +
>>> +       "Load arguments in reg"
>>> +       cogit genLoadArgAtDepth: 0 into: string2Reg.
>>> +
>>> +       "checks if string1 is a byteobject and get its size in bytes"
>>> +       self genGetFormatOf: string1Reg into: TempReg.
>>> +       cogit CmpCq: objectMemory firstByteFormat R: TempReg.
>>> +       jumpIncorrectFormat1 := cogit JumpLess: 0.
>>> +       cogit CmpCq: objectMemory firstCompiledMethodFormat R: TempReg.
>>> +       jumpIncorrectFormat2 := cogit JumpAboveOrEqual: 0.
>>> +
>>> +       self genGetNumSlotsOf: string1Reg into: string1CharOrByteSizeReg.
>>> +       (cogit LogicalShiftLeftCq: objectMemory shiftForWord R:
>>> string1CharOrByteSizeReg).
>>> +       cogit AndCq: objectMemory wordSize - 1 R: TempReg R: TempReg.
>>> +       cogit SubR: TempReg R: string1CharOrByteSizeReg.
>>> +
>>> +       "checks if string2 is a byteobject and get its size in bytes"
>>> +       self genGetFormatOf: string2Reg into: TempReg.
>>> +       cogit CmpCq: objectMemory firstByteFormat R: TempReg.
>>> +       jumpIncorrectFormat3 := cogit JumpLess: 0.
>>> +       cogit CmpCq: objectMemory firstCompiledMethodFormat R: TempReg.
>>> +       jumpIncorrectFormat4 := cogit JumpAboveOrEqual: 0.
>>> +
>>> +       self genGetNumSlotsOf: string2Reg into: string2CharOrByteSizeReg.
>>> +       (cogit LogicalShiftLeftCq: objectMemory shiftForWord R:
>>> string2CharOrByteSizeReg).
>>> +       cogit AndCq: objectMemory wordSize - 1 R: TempReg R: TempReg.
>>> +       cogit SubR: TempReg R: string2CharOrByteSizeReg.
>>> +
>>> +       "Type and number of arguments are correct"
>>> +       "Compute the min"
>>> +       cogit CmpR: string1CharOrByteSizeReg R: string2CharOrByteSizeReg.
>>> +       jumpAbove := cogit JumpBelow: 0.
>>> +       cogit MoveR: string1CharOrByteSizeReg R: minSizeReg.
>>> +       jump := cogit Jump: 0.
>>> +       jumpAbove jmpTarget: (cogit MoveR: string2CharOrByteSizeReg R:
>>> minSizeReg).
>>> +       jump jmpTarget: (cogit CmpCq: 0 R: minSizeReg).
>>> +       jumpSuccess := cogit JumpZero: 0. "if one of the string is
>>> empty, no need to go through the comparing loop"
>>> +
>>> +       "Compare the bytes"
>>> +       cogit MoveCq: objectMemory baseHeaderSize  R: TempReg.
>>> +       cogit AddCq: objectMemory baseHeaderSize R: minSizeReg.
>>> +
>>> +       instr := cogit MoveXbr: TempReg R: string1Reg R:
>>> string1CharOrByteSizeReg.
>>> +       cogit MoveXbr: TempReg R: string2Reg R: string2CharOrByteSizeReg.
>>> +       cogit SubR: string2CharOrByteSizeReg R:
>>> string1CharOrByteSizeReg.
>>> +       jumpMidFailure := cogit JumpNonZero: 0. "the 2 compared
>>> characters are different, exit the loop"
>>> +       cogit AddCq: 1 R: TempReg.
>>> +       cogit CmpR: TempReg R: minSizeReg.
>>> +       cogit JumpNonZero: instr.
>>> +
>>> +       "all bytes from 1 to minSize are equal"
>>> +       self genGetNumBytesOf: string1Reg into: string1CharOrByteSizeReg.
>>> +       self genGetNumBytesOf: string2Reg into: string2CharOrByteSizeReg.
>>> +       jumpSuccess jmpTarget: (cogit SubR: string2CharOrByteSizeReg R:
>>> string1CharOrByteSizeReg).
>>> +       jumpMidFailure  jmpTarget: (cogit MoveR:
>>> string1CharOrByteSizeReg R: ReceiverResultReg).
>>> +       self genConvertIntegerToSmallIntegerInReg: ReceiverResultReg.
>>> +       cogit genPrimReturn.
>>> +
>>> +       jumpIncorrectFormat4
>>> +               jmpTarget: (jumpIncorrectFormat3
>>> +                       jmpTarget: (jumpIncorrectFormat2
>>> +                               jmpTarget: (jumpIncorrectFormat1
>>> jmpTarget: cogit Label))).
>>> +
>>> +       ^ CompletePrimitive!
>>>
>>> Item was changed:
>>>   ----- Method: Interpreter class>>initializePrimitiveTable (in
>>> category 'initialization') -----
>>> (excessive size, no diff calculated)
>>>
>>> Item was added:
>>> + ----- Method: InterpreterPrimitives>>primitiveCompareWith (in
>>> category 'string primitives') -----
>>> + primitiveCompareWith
>>> +       "<string1> primitiveCompareWith: string2 [collated: order] "
>>> +       <export: true>
>>> +
>>> +       | string1 string2 order strLength1 strLength2 result |
>>> +
>>> +       "1 - fetch the parameters from the stack"
>>> +       (argumentCount = 0 or: [argumentCount > 2]) ifTrue:
>>> +               [^self primitiveFailFor: PrimErrBadNumArgs].
>>> +       argumentCount = 1
>>> +                       ifFalse: "argCount must be 2"
>>> +                               [order := self stackTop.
>>> +                               (objectMemory isBytes: order) ifFalse:
>>> [^self primitiveFailFor: PrimErrBadArgument]].
>>> +       string1 := self stackValue: argumentCount.
>>> +       string2 := self stackValue: argumentCount - 1.
>>> +
>>> +       "2 - check their types - all parameters are ByteObject"
>>> +       ((objectMemory isBytes: string1)
>>> +       and: [objectMemory isBytes: string2 ])
>>> +               ifFalse:
>>> +                       [^self primitiveFailFor: PrimErrBadArgument].
>>> +
>>> +       "3 - compare the strings"
>>> +       strLength1 := objectMemory numBytesOfBytes: string1.
>>> +       strLength2 := objectMemory numBytesOfBytes: string2.
>>> +       result := order
>>> +               ifNil: [self rawCompare: string1 length: strLength1
>>> with: string2 length: strLength2 accessBlock: [:str :index | objectMemory
>>> fetchByte: index ofObject: str ]]
>>> +               ifNotNil:
>>> +                       [self rawCompare: string1 length: strLength1
>>> with: string2 length: strLength2 accessBlock: [:str :index | objectMemory
>>> fetchByte: (objectMemory fetchByte: index ofObject: str) +1 ofObject: order
>>> ]].
>>> +       self pop: argumentCount + 1 thenPush: (objectMemory
>>> integerObjectOf: result)
>>> +
>>> +
>>> +
>>> +
>>> +
>>> +       !
>>>
>>> Item was added:
>>> + ----- Method: InterpreterPrimitives>>rawComp
>>> are:length:with:length:accessBlock: (in category 'string primitives')
>>> -----
>>> + rawCompare: string1 length: strLength1 with: string2 length:
>>> strLength2 accessBlock: accessBlock
>>> +       | c1 c2 min |
>>> +       <inline: true> "needs to be forced else slang does not inline it
>>> by default"
>>> +       min := strLength1 min: strLength2.
>>> +       0 to: min-1 do:
>>> +               [:i | c1 := accessBlock value: string1 value: i.
>>> +                       c2 := accessBlock value: string2 value: i.
>>> +                       c1 = c2 ifFalse: [^c1 - c2]].
>>> +       ^strLength1 - strLength2
>>> +
>>> +
>>> +
>>> +
>>> +       !
>>>
>>> Item was changed:
>>>   ----- Method: SimpleStackBasedCogit class>>initializePrimitiveTableForSqueak
>>> (in category 'class initialization') -----
>>>   initializePrimitiveTableForSqueak
>>>         "Initialize the table of primitive generators.  This does not
>>> include normal primitives implemented in the coInterpreter.
>>>          N.B. primitives that don't have an explicit arg count (the
>>> integer following the generator) may be variadic."
>>>         "SimpleStackBasedCogit initializePrimitiveTableForSqueak"
>>>         MaxCompiledPrimitiveIndex := self objectRepresentationClass
>>> wordSize = 8
>>>
>>>         ifTrue: [555]
>>>
>>>         ifFalse: [222].
>>>         primitiveTable := CArrayAccessor on: (Array new:
>>> MaxCompiledPrimitiveIndex + 1).
>>>         self table: primitiveTable from:
>>>         #(      "Integer Primitives (0-19)"
>>>                 (1 genPrimitiveAdd                              1)
>>>                 (2 genPrimitiveSubtract                 1)
>>>                 (3 genPrimitiveLessThan         1)
>>>                 (4 genPrimitiveGreaterThan              1)
>>>                 (5 genPrimitiveLessOrEqual              1)
>>>                 (6 genPrimitiveGreaterOrEqual   1)
>>>                 (7 genPrimitiveEqual                    1)
>>>                 (8 genPrimitiveNotEqual         1)
>>>                 (9 genPrimitiveMultiply                 1)
>>>                 (10 genPrimitiveDivide                  1)
>>>                 (11 genPrimitiveMod                     1)
>>>                 (12 genPrimitiveDiv                             1)
>>>                 (13 genPrimitiveQuo                     1)
>>>                 (14 genPrimitiveBitAnd                  1)
>>>                 (15 genPrimitiveBitOr                   1)
>>>                 (16 genPrimitiveBitXor                  1)
>>>                 (17 genPrimitiveBitShift                        1)
>>>                 "(18 primitiveMakePoint)"
>>>                 "(19 primitiveFail)"
>>> "Guard primitive for simulation -- *must* fail"
>>>
>>>                 "LargeInteger Primitives (20-39)"
>>>                 "(20 primitiveFail)"
>>>                 "(21 primitiveAddLargeIntegers)"
>>>                 "(22 primitiveSubtractLargeIntegers)"
>>>                 "(23 primitiveLessThanLargeIntegers)"
>>>                 "(24 primitiveGreaterThanLargeIntegers)"
>>>                 "(25 primitiveLessOrEqualLargeIntegers)"
>>>                 "(26 primitiveGreaterOrEqualLargeIntegers)"
>>>                 "(27 primitiveEqualLargeIntegers)"
>>>                 "(28 primitiveNotEqualLargeIntegers)"
>>>                 "(29 primitiveMultiplyLargeIntegers)"
>>>                 "(30 primitiveDivideLargeIntegers)"
>>>                 "(31 primitiveModLargeIntegers)"
>>>                 "(32 primitiveDivLargeIntegers)"
>>>                 "(33 primitiveQuoLargeIntegers)"
>>>                 "(34 primitiveBitAndLargeIntegers)"
>>>                 "(35 primitiveBitOrLargeIntegers)"
>>>                 "(36 primitiveBitXorLargeIntegers)"
>>>                 "(37 primitiveBitShiftLargeIntegers)"
>>>
>>>                 "Float Primitives (38-59)"
>>>                 "(38 genPrimitiveFloatAt)"
>>>                 "(39 genPrimitiveFloatAtPut)"
>>>                 (40 genPrimitiveAsFloat
>>>  0)
>>>                 (41 genPrimitiveFloatAdd
>>> 1)
>>>                 (42 genPrimitiveFloatSubtract                   1)
>>>                 (43 genPrimitiveFloatLessThan                   1)
>>>                 (44 genPrimitiveFloatGreaterThan                1)
>>>                 (45 genPrimitiveFloatLessOrEqual                1)
>>>                 (46 genPrimitiveFloatGreaterOrEqual     1)
>>>                 (47 genPrimitiveFloatEqual
>>> 1)
>>>                 (48 genPrimitiveFloatNotEqual                   1)
>>>                 (49 genPrimitiveFloatMultiply                   1)
>>>                 (50 genPrimitiveFloatDivide
>>>  1)
>>>                 "(51 genPrimitiveTruncated)"
>>>                 "(52 genPrimitiveFractionalPart)"
>>>                 "(53 genPrimitiveExponent)"
>>>                 "(54 genPrimitiveTimesTwoPower)"
>>>                 (55 genPrimitiveFloatSquareRoot         0)
>>>                 "(56 genPrimitiveSine)"
>>>                 "(57 genPrimitiveArctan)"
>>>                 "(58 genPrimitiveLogN)"
>>>                 "(59 genPrimitiveExp)"
>>>
>>>                 "Subscript and Stream Primitives (60-67)"
>>>                 (60 genPrimitiveAt                              1)
>>>                 (61 genPrimitiveAtPut                   2)
>>>                 (62 genPrimitiveSize                    0)
>>>                 (63 genPrimitiveStringAt                1)
>>>                 (64 genPrimitiveStringAtPut             2)
>>>                 "The stream primitives no longer pay their way; normal
>>> Smalltalk code is faster."
>>>                 (65 genFastPrimFail)"was primitiveNext"
>>>                 (66 genFastPrimFail) "was primitiveNextPut"
>>>                 (67 genFastPrimFail) "was primitiveAtEnd"
>>>
>>>                 "StorageManagement Primitives (68-79)"
>>>                 (68 genPrimitiveObjectAt                        1)
>>> "Good for debugger/InstructionStream performance"
>>>                 "(69 primitiveObjectAtPut)"
>>>                 (70 genPrimitiveNew                     0)
>>>                 (71 genPrimitiveNewWithArg      1)
>>>                 "(72 primitiveArrayBecomeOneWay)"               "Blue
>>> Book: primitiveBecome"
>>>                 "(73 primitiveInstVarAt)"
>>>                 "(74 primitiveInstVarAtPut)"
>>>                 (75 genPrimitiveIdentityHash    0)
>>>                 "(76 primitiveStoreStackp)"
>>>        "Blue Book: primitiveAsObject"
>>>                 "(77 primitiveSomeInstance)"
>>>                 "(78 primitiveNextInstance)"
>>>                 (79 genPrimitiveNewMethod       2)
>>>
>>>                 "Control Primitives (80-89)"
>>>                 "(80 primitiveFail)"
>>>                 "Blue Book: primitiveBlockCopy"
>>>                 "(81 primitiveFail)"
>>>                 "Blue Book: primitiveValue"
>>>                 "(82 primitiveFail)"
>>>                 "Blue Book: primitiveValueWithArgs"
>>>                 (83 genPrimitivePerform)
>>>                 "(84 primitivePerformWithArgs)"
>>>                 "(85 primitiveSignal)"
>>>                 "(86 primitiveWait)"
>>>                 "(87 primitiveResume)"
>>>                 "(88 primitiveSuspend)"
>>>                 "(89 primitiveFlushCache)"
>>>
>>>                 "(90 primitiveMousePoint)"
>>>                 "(91 primitiveTestDisplayDepth)"
>>> "Blue Book: primitiveCursorLocPut"
>>>                 "(92 primitiveSetDisplayMode)"
>>> "Blue Book: primitiveCursorLink"
>>>                 "(93 primitiveInputSemaphore)"
>>>                 "(94 primitiveGetNextEvent)"
>>> "Blue Book: primitiveSampleInterval"
>>>                 "(95 primitiveInputWord)"
>>>                 "(96 primitiveFail)"    "primitiveCopyBits"
>>>                 "(97 primitiveSnapshot)"
>>>                 "(98 primitiveStoreImageSegment)"
>>>                 "(99 primitiveLoadImageSegment)"
>>>                 "(100 primitivePerformInSuperclass)"            "Blue
>>> Book: primitiveSignalAtTick"
>>>                 "(101 primitiveBeCursor)"
>>>                 "(102 primitiveBeDisplay)"
>>>                 "(103 primitiveScanCharacters)"
>>>                 "(104 primitiveFail)"   "primitiveDrawLoop"
>>>                 (105 genPrimitiveStringReplace)
>>>                 "(106 primitiveScreenSize)"
>>>                 "(107 primitiveMouseButtons)"
>>>                 "(108 primitiveKbdNext)"
>>>                 "(109 primitiveKbdPeek)"
>>>
>>>
>>>                 "System Primitives (110-119)"
>>>                 (110 genPrimitiveIdentical 1)
>>>                 (111 genPrimitiveClass)                         "Support
>>> both class and Context>>objectClass:"
>>>                 "(112 primitiveBytesLeft)"
>>>                 "(113 primitiveQuit)"
>>>                 "(114 primitiveExitToDebugger)"
>>>                 "(115 primitiveChangeClass)"
>>>         "Blue Book: primitiveOopsLeft"
>>>                 "(116 primitiveFlushCacheByMethod)"
>>>                 "(117 primitiveExternalCall)"
>>>                 "(118 primitiveDoPrimitiveWithArgs)"
>>>                 "(119 primitiveFlushCacheSelective)"
>>>
>>>                 (148 genPrimitiveShallowCopy 0)                 "a.k.a.
>>> clone"
>>>
>>> +               (158 genPrimitiveStringCompareWith 1)
>>>                 (159 genPrimitiveHashMultiply 0)
>>>
>>>                 (169 genPrimitiveNotIdentical 1)
>>>
>>>                 (170 genPrimitiveAsCharacter)
>>>  "SmallInteger>>asCharacter, Character class>>value:"
>>>                 (171 genPrimitiveImmediateAsInteger 0)
>>> "Character>>value SmallFloat64>>asInteger"
>>>
>>>                 "(173 primitiveSlotAt 1)"
>>>                 "(174 primitiveSlotAtPut 2)"
>>>                 (175 genPrimitiveIdentityHash   0)
>>> "Behavior>>identityHash"
>>>
>>>                 "Old closure primitives"
>>>                 "(186 primitiveFail)" "was primitiveClosureValue"
>>>                 "(187 primitiveFail)" "was primitiveClosureValueWithArgs"
>>>
>>>                 "Perform method directly"
>>>                 "(188 primitiveExecuteMethodArgsArray)"
>>>                 "(189 primitiveExecuteMethod)"
>>>
>>>                 "Unwind primitives"
>>>                 "(195 primitiveFindNextUnwindContext)"
>>>                 "(196 primitiveTerminateTo)"
>>>                 "(197 primitiveFindHandlerContext)"
>>>                 (198 genFastPrimFail "primitiveMarkUnwindMethod")
>>>                 (199 genFastPrimFail "primitiveMarkHandlerMethod")
>>>
>>>                 "new closure primitives"
>>>                 "(200 primitiveClosureCopyWithCopiedValues)"
>>>                 (201 genPrimitiveClosureValue   0) "value"
>>>                 (202 genPrimitiveClosureValue   1) "value:"
>>>                 (203 genPrimitiveClosureValue   2) "value:value:"
>>>                 (204 genPrimitiveClosureValue   3) "value:value:value:"
>>>                 (205 genPrimitiveClosureValue   4)
>>> "value:value:value:value:"
>>>                 "(206 genPrimitiveClosureValueWithArgs)"
>>> "valueWithArguments:"
>>>
>>>                 (207 genPrimitiveFullClosureValue)
>>> "value[:value:value:value:] et al"
>>>                 "(208 genPrimitiveFullClosureValueWithArgs)"
>>> "valueWithArguments:"
>>>                 (209 genPrimitiveFullClosureValue)
>>> "valueNoContextSwitch[:value:] et al"
>>>
>>>                 "(210 primitiveContextAt)"
>>>                 "(211 primitiveContextAtPut)"
>>>                 "(212 primitiveContextSize)"
>>>
>>>                 "(218 primitiveDoNamedPrimitiveWithArgs)"
>>>                 "(219 primitiveFail)"   "reserved for Cog primitives"
>>>
>>>                 "(220 primitiveFail)"           "reserved for Cog
>>> primitives"
>>>
>>>                 (221 genPrimitiveClosureValue   0) "valueNoContextSwitch"
>>>                 (222 genPrimitiveClosureValue   1)
>>> "valueNoContextSwitch:"
>>>
>>>                 "SmallFloat primitives (540-559)"
>>>                 (541 genPrimitiveSmallFloatAdd
>>> 1)
>>>                 (542 genPrimitiveSmallFloatSubtract
>>>  1)
>>>                 (543 genPrimitiveSmallFloatLessThan
>>>  1)
>>>                 (544 genPrimitiveSmallFloatGreaterThan          1)
>>>                 (545 genPrimitiveSmallFloatLessOrEqual          1)
>>>                 (546 genPrimitiveSmallFloatGreaterOrEqual
>>>  1)
>>>                 (547 genPrimitiveSmallFloatEqual
>>>         1)
>>>                 (548 genPrimitiveSmallFloatNotEqual
>>>  1)
>>>                 (549 genPrimitiveSmallFloatMultiply
>>>          1)
>>>                 (550 genPrimitiveSmallFloatDivide
>>>        1)
>>>                 "(551 genPrimitiveSmallFloatTruncated
>>>  0)"
>>>                 "(552 genPrimitiveSmallFloatFractionalPart
>>> 0)"
>>>                 "(553 genPrimitiveSmallFloatExponent
>>> 0)"
>>>                 "(554 genPrimitiveSmallFloatTimesTwoPower       1)"
>>>                 (555 genPrimitiveSmallFloatSquareRoot
>>>  0)
>>>                 "(556 genPrimitiveSmallFloatSine
>>>         0)"
>>>                 "(557 genPrimitiveSmallFloatArctan
>>>         0)"
>>>                 "(558 genPrimitiveSmallFloatLogN
>>>         0)"
>>>                 "(559 genPrimitiveSmallFloatExp
>>>  0)"
>>>         )!
>>>
>>> Item was changed:
>>>   ----- Method: StackInterpreter class>>initializePrimitiveTable (in
>>> category 'initialization') -----
>>> (excessive size, no diff calculated)
>>>
>>>
>>
>>
>
>

[Attachment #6 (text/html)]

<div dir="ltr"><br><div class="gmail_extra"><br><div class="gmail_quote">2018-04-19 \
13:33 GMT+02:00 Nicolas Cellier <span dir="ltr">&lt;<a \
href="mailto:nicolas.cellier.aka.nice@gmail.com" \
target="_blank">nicolas.cellier.aka.nice@gmail.com</a>&gt;</span>:<br><blockquote \
class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc \
solid;padding-left:1ex"> <br><div dir="ltr"><br><div class="gmail_extra"><br><div \
class="gmail_quote">2018-04-19 12:14 GMT+02:00 Sophie Kaleba <span dir="ltr">&lt;<a \
href="mailto:sophie.kaleba@gmail.com" \
target="_blank">sophie.kaleba@gmail.com</a>&gt;</span>:<br><blockquote \
class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc \
solid;padding-left:1ex"> <br><div dir="ltr"><div><div><div><div>Hi,<br><br></div>I \
got a timeout error during the upload because of my slow internet connexion. Hope \
this won&#39;t cause any problem.<br></div>I finally found time to commit this new \
primitive! If you spot any mistake, contact me!<br><br></div>I have updated the \
related methods in Squeak (updating previous senders of compare:with:collated so they \
call this primitive instead) + the tests methods but I can&#39;t commit to the \
repository. I can send the .st files to someone who does have the \
rights.<br><br></div>Sophie<br></div><div \
class="gmail_extra"><br></div></blockquote><div><br></div><div>Hi \
Sophie,<br></div><div>you can always commit to the inbox (<a \
href="http://source.squeak.org/inbox/" \
target="_blank">http://source.squeak.org/<wbr>inbox/</a>).<br></div></div></div></div></blockquote><div><br><br></div><div>Hi<br></div><div>Thanks! \
I will check I did not forget anything and will commit \
there<br><br></div><div>Sophie<br></div><div><br> </div><blockquote \
class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc \
solid;padding-left:1ex"><div dir="ltr"><div class="gmail_extra"><div \
class="gmail_quote"><div></div><div></div><div><br></div><div>cheers<br></div><div> \
<br></div><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px \
#ccc solid;padding-left:1ex"><div class="gmail_extra"><div \
class="gmail_quote">2018-04-19 12:02 GMT+02:00  <span dir="ltr">&lt;<a \
href="mailto:commits@source.squeak.org" \
target="_blank">commits@source.squeak.org</a>&gt;</span>:<br><blockquote \
class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc \
solid;padding-left:1ex"> <br> Sophie Kaleba uploaded a new version of VMMaker to \
project VM Maker:<br> <a \
href="http://source.squeak.org/VMMaker/VMMaker.oscog-sk.2367.mcz" rel="noreferrer" \
target="_blank">http://source.squeak.org/VMMak<wbr>er/VMMaker.oscog-sk.2367.mcz</a><br>
 <br>
==================== Summary ====================<br>
<br>
Name: VMMaker.oscog-sk.2367<br>
Author: sk<br>
Time: 19 April 2018, 12:02:35.661622 pm<br>
UUID: 0c2401e3-1450-4f73-8e81-958f50<wbr>171595<br>
Ancestors: VMMaker.oscog- nice.2366<br>
<br>
** new primitive to compare strings (slang + JIT)<br>
answers negative smi, 0 or positive smi (instead of 1, 2 or 3 in the MiscPlugin)<br>
<br>
* Slang (primitiveCompareWith)<br>
order is optionnal. <br>
comparison loop performed in rawCompare: string1 length: strLength1 with: string2 \
length: strLength2 accessBlock: accessBlock<br> <br>
* JIT (genPrimitiveStringCompareWith<wbr>)<br>
the JIT primitive does not take order as parameter (assumed asciiOrder)<br>
quick jump if one of the strings is empty<br>
<br>
=============== Diff against VMMaker.oscog- nice.2366 ===============<br>
<br>
Item was added:<br>
+ ----- Method: CogObjectRepresentation&gt;&gt;genPr<wbr>imitiveStringCompareWith (in \
category &#39;primitive generators&#39;) -----<br> + \
genPrimitiveStringCompareWith<br> +       &quot;subclasses override if they \
can&quot;<br> +       ^UnimplementedPrimitive!<br>
<br>
Item was added:<br>
+ ----- Method: CogObjectRepresentationForSpur<wbr>&gt;&gt;genPrimitiveStringCompareWit<wbr>h \
(in category &#39;primitive generators&#39;) -----<br> + \
genPrimitiveStringCompareWith<br> +       &quot;primitiveCompareWith:&quot;<br>
+       <br>
+       | instr jump jumpAbove jumpIncorrectFormat1 jumpIncorrectFormat2 \
jumpIncorrectFormat3 jumpIncorrectFormat4 jumpMidFailure jumpSuccess minSizeReg \
string1CharOrByteSizeReg string2CharOrByteSizeReg string1Reg string2Reg |<br> +       \
<br> +       &lt;var: #jumpIncorrectFormat1 type: #&#39;AbstractInstruction \
*&#39;&gt;<br> +       &lt;var: #jumpIncorrectFormat2 type: #&#39;AbstractInstruction \
*&#39;&gt;<br> +       &lt;var: #jumpIncorrectFormat3 type: #&#39;AbstractInstruction \
*&#39;&gt;<br> +       &lt;var: #jumpIncorrectFormat4 type: #&#39;AbstractInstruction \
*&#39;&gt;<br> +       &lt;var: #jumpAbove type: #&#39;AbstractInstruction \
*&#39;&gt;<br> +       &lt;var: #jumpSuccess type: #&#39;AbstractInstruction \
*&#39;&gt;<br> +       &lt;var: #jump type: #&#39;AbstractInstruction *&#39;&gt;<br>
+       &lt;var: #jumpMidFailure type: #&#39;AbstractInstruction *&#39;&gt;<br>
+       <br>
+       &quot;I redefine those name to ease program comprehension&quot;<br>
+       string1Reg := ReceiverResultReg.<br>
+       string2Reg := Arg0Reg.<br>
+       string1CharOrByteSizeReg := Arg1Reg.<br>
+       string2CharOrByteSizeReg := ClassReg.<br>
+       minSizeReg := SendNumArgsReg.<br>
+       <br>
+       &quot;Load arguments in reg&quot;<br>
+       cogit genLoadArgAtDepth: 0 into: string2Reg.<br>
+       <br>
+       &quot;checks if string1 is a byteobject and get its size in bytes&quot;<br>
+       self genGetFormatOf: string1Reg into: TempReg.<br>
+       cogit CmpCq: objectMemory firstByteFormat R: TempReg.<br>
+       jumpIncorrectFormat1 := cogit JumpLess: 0.<br>
+       cogit CmpCq: objectMemory firstCompiledMethodFormat R: TempReg.<br>
+       jumpIncorrectFormat2 := cogit JumpAboveOrEqual: 0.<br>
+               <br>
+       self genGetNumSlotsOf: string1Reg into: string1CharOrByteSizeReg.<br>
+       (cogit LogicalShiftLeftCq: objectMemory shiftForWord R: \
string1CharOrByteSizeReg). <br> +       cogit AndCq: objectMemory wordSize - 1 R: \
TempReg R: TempReg. <br> +       cogit SubR: TempReg R: string1CharOrByteSizeReg. \
<br> +       <br>
+       &quot;checks if string2 is a byteobject and get its size in bytes&quot;<br>
+       self genGetFormatOf: string2Reg into: TempReg.<br>
+       cogit CmpCq: objectMemory firstByteFormat R: TempReg.<br>
+       jumpIncorrectFormat3 := cogit JumpLess: 0.<br>
+       cogit CmpCq: objectMemory firstCompiledMethodFormat R: TempReg.<br>
+       jumpIncorrectFormat4 := cogit JumpAboveOrEqual: 0.<br>
+               <br>
+       self genGetNumSlotsOf: string2Reg into: string2CharOrByteSizeReg.<br>
+       (cogit LogicalShiftLeftCq: objectMemory shiftForWord R: \
string2CharOrByteSizeReg).<br> +       cogit AndCq: objectMemory wordSize - 1 R: \
TempReg R: TempReg.<br> +       cogit SubR: TempReg R: string2CharOrByteSizeReg.<br>
+       <br>
+       &quot;Type and number of arguments are correct&quot;<br>
+       &quot;Compute the min&quot;        <br>
+       cogit CmpR: string1CharOrByteSizeReg R: string2CharOrByteSizeReg.<br>
+       jumpAbove := cogit JumpBelow: 0. <br>
+       cogit MoveR: string1CharOrByteSizeReg R: minSizeReg. <br>
+       jump := cogit Jump: 0. <br>
+       jumpAbove jmpTarget: (cogit MoveR: string2CharOrByteSizeReg R: minSizeReg). \
<br> +       jump jmpTarget: (cogit CmpCq: 0 R: minSizeReg). <br>
+       jumpSuccess := cogit JumpZero: 0. &quot;if one of the string is empty, no \
need to go through the comparing loop&quot;<br> +       <br>
+       &quot;Compare the bytes&quot;<br>
+       cogit MoveCq: objectMemory baseHeaderSize  R: TempReg.<br>
+       cogit AddCq: objectMemory baseHeaderSize R: minSizeReg.<br>
+       <br>
+       instr := cogit MoveXbr: TempReg R: string1Reg R: \
string1CharOrByteSizeReg.<br> +       cogit MoveXbr: TempReg R: string2Reg R: \
string2CharOrByteSizeReg.<br> +       cogit SubR: string2CharOrByteSizeReg R: \
string1CharOrByteSizeReg. <br> +       jumpMidFailure := cogit JumpNonZero: 0. \
&quot;the 2 compared characters are different, exit the loop&quot;<br> +       cogit \
AddCq: 1 R: TempReg.<br> +       cogit CmpR: TempReg R: minSizeReg. <br>
+       cogit JumpNonZero: instr.<br>
+       <br>
+       &quot;all bytes from 1 to minSize are equal&quot;<br>
+       self genGetNumBytesOf: string1Reg into: string1CharOrByteSizeReg.<br>
+       self genGetNumBytesOf: string2Reg into: string2CharOrByteSizeReg.<br>
+       jumpSuccess jmpTarget: (cogit SubR: string2CharOrByteSizeReg R: \
string1CharOrByteSizeReg).<br> +       jumpMidFailure  jmpTarget: (cogit MoveR: \
string1CharOrByteSizeReg R: ReceiverResultReg).        <br> +       self \
genConvertIntegerToSmallIntege<wbr>rInReg: ReceiverResultReg.<br> +       cogit \
genPrimReturn.<br> +       <br>
+       jumpIncorrectFormat4 <br>
+               jmpTarget: (jumpIncorrectFormat3 <br>
+                       jmpTarget: (jumpIncorrectFormat2 <br>
+                               jmpTarget: (jumpIncorrectFormat1 jmpTarget: cogit \
Label))).<br> +       <br>
+       ^ CompletePrimitive!<br>
<br>
Item was changed:<br>
  ----- Method: Interpreter class&gt;&gt;initializePrimitiveTabl<wbr>e (in category \
&#39;initialization&#39;) -----<br> (excessive size, no diff calculated)<br>
<br>
Item was added:<br>
+ ----- Method: InterpreterPrimitives&gt;&gt;primiti<wbr>veCompareWith (in category \
&#39;string primitives&#39;) -----<br> + primitiveCompareWith<br>
+       &quot;&lt;string1&gt; primitiveCompareWith: string2 [collated: order] \
&quot;<br> +       &lt;export: true&gt;<br>
+       <br>
+       | string1 string2 order strLength1 strLength2 result |<br>
+ <br>
+       &quot;1 - fetch the parameters from the stack&quot;       <br>
+       (argumentCount = 0 or: [argumentCount &gt; 2]) ifTrue:<br>
+               [^self primitiveFailFor: PrimErrBadNumArgs].<br>
+       argumentCount = 1<br>
+                       ifFalse: &quot;argCount must be 2&quot;<br>
+                               [order := self stackTop.<br>
+                               (objectMemory isBytes: order) ifFalse: [^self \
primitiveFailFor: PrimErrBadArgument]].<br> +       string1 := self stackValue: \
argumentCount.<br> +       string2 := self stackValue: argumentCount - 1. <br>
+                       <br>
+       &quot;2 - check their types - all parameters are ByteObject&quot;<br>
+       ((objectMemory isBytes: string1)<br>
+       and: [objectMemory isBytes: string2 ])<br>
+               ifFalse: <br>
+                       [^self primitiveFailFor: PrimErrBadArgument].<br>
+       <br>
+       &quot;3 - compare the strings&quot;       <br>
+       strLength1 := objectMemory numBytesOfBytes: string1.<br>
+       strLength2 := objectMemory numBytesOfBytes: string2.<br>
+       result := order <br>
+               ifNil: [self rawCompare: string1 length: strLength1 with: string2 \
length: strLength2 accessBlock: [:str :index | objectMemory fetchByte: index \
ofObject: str ]]<br> +               ifNotNil: <br>
+                       [self rawCompare: string1 length: strLength1 with: string2 \
length: strLength2 accessBlock: [:str :index | objectMemory fetchByte: (objectMemory \
fetchByte: index ofObject: str) +1 ofObject: order ]].<br> +       self pop: \
argumentCount + 1 thenPush: (objectMemory integerObjectOf: result)<br> +       <br>
+ <br>
+ <br>
+       <br>
+       <br>
+       !<br>
<br>
Item was added:<br>
+ ----- Method: InterpreterPrimitives&gt;&gt;rawComp<wbr>are:length:with:length:accessB<wbr>lock: \
(in category &#39;string primitives&#39;) -----<br> + rawCompare: string1 length: \
strLength1 with: string2 length: strLength2 accessBlock: accessBlock<br> +       | c1 \
c2 min |<br> +       &lt;inline: true&gt; &quot;needs to be forced else slang does \
not inline it by default&quot;<br> +       min := strLength1 min: strLength2.<br>
+       0 to: min-1 do: <br>
+               [:i | c1 := accessBlock value: string1 value: i.<br>
+                       c2 := accessBlock value: string2 value: i.<br>
+                       c1 = c2 ifFalse: [^c1 - c2]].<br>
+       ^strLength1 - strLength2<br>
+ <br>
+ <br>
+       <br>
+       <br>
+       !<br>
<br>
Item was changed:<br>
  ----- Method: SimpleStackBasedCogit \
class&gt;&gt;initializePrimitiveTabl<wbr>eForSqueak (in category &#39;class \
initialization&#39;) -----<br>  initializePrimitiveTableForSqu<wbr>eak<br>
        &quot;Initialize the table of primitive generators.  This does not include \
                normal primitives implemented in the coInterpreter.<br>
         N.B. primitives that don&#39;t have an explicit arg count (the integer \
                following the generator) may be variadic.&quot;<br>
        &quot;SimpleStackBasedCogit initializePrimitiveTableForSqu<wbr>eak&quot;<br>
        MaxCompiledPrimitiveIndex := self objectRepresentationClass wordSize = 8<br>
                                                                                \
                ifTrue: [555]<br>
                                                                                \
                ifFalse: [222].<br>
        primitiveTable := CArrayAccessor on: (Array new: MaxCompiledPrimitiveIndex + \
1).<br>  self table: primitiveTable from: <br>
        #(      &quot;Integer Primitives (0-19)&quot;<br>
                (1 genPrimitiveAdd                              1)<br>
                (2 genPrimitiveSubtract                 1)<br>
                (3 genPrimitiveLessThan         1)<br>
                (4 genPrimitiveGreaterThan              1)<br>
                (5 genPrimitiveLessOrEqual              1)<br>
                (6 genPrimitiveGreaterOrEqual   1)<br>
                (7 genPrimitiveEqual                    1)<br>
                (8 genPrimitiveNotEqual         1)<br>
                (9 genPrimitiveMultiply                 1)<br>
                (10 genPrimitiveDivide                  1)<br>
                (11 genPrimitiveMod                     1)<br>
                (12 genPrimitiveDiv                             1)<br>
                (13 genPrimitiveQuo                     1)<br>
                (14 genPrimitiveBitAnd                  1)<br>
                (15 genPrimitiveBitOr                   1)<br>
                (16 genPrimitiveBitXor                  1)<br>
                (17 genPrimitiveBitShift                        1)<br>
                &quot;(18 primitiveMakePoint)&quot;<br>
                &quot;(19 primitiveFail)&quot;                                    \
&quot;Guard primitive for simulation -- *must* fail&quot;<br> <br>
                &quot;LargeInteger Primitives (20-39)&quot;<br>
                &quot;(20 primitiveFail)&quot;<br>
                &quot;(21 primitiveAddLargeIntegers)&quot;<br>
                &quot;(22 primitiveSubtractLargeIntegers<wbr>)&quot;<br>
                &quot;(23 primitiveLessThanLargeIntegers<wbr>)&quot;<br>
                &quot;(24 primitiveGreaterThanLargeInteg<wbr>ers)&quot;<br>
                &quot;(25 primitiveLessOrEqualLargeInteg<wbr>ers)&quot;<br>
                &quot;(26 primitiveGreaterOrEqualLargeIn<wbr>tegers)&quot;<br>
                &quot;(27 primitiveEqualLargeIntegers)&quot;<br>
                &quot;(28 primitiveNotEqualLargeIntegers<wbr>)&quot;<br>
                &quot;(29 primitiveMultiplyLargeIntegers<wbr>)&quot;<br>
                &quot;(30 primitiveDivideLargeIntegers)&quot;<br>
                &quot;(31 primitiveModLargeIntegers)&quot;<br>
                &quot;(32 primitiveDivLargeIntegers)&quot;<br>
                &quot;(33 primitiveQuoLargeIntegers)&quot;<br>
                &quot;(34 primitiveBitAndLargeIntegers)&quot;<br>
                &quot;(35 primitiveBitOrLargeIntegers)&quot;<br>
                &quot;(36 primitiveBitXorLargeIntegers)&quot;<br>
                &quot;(37 primitiveBitShiftLargeIntegers<wbr>)&quot;<br>
<br>
                &quot;Float Primitives (38-59)&quot;<br>
                &quot;(38 genPrimitiveFloatAt)&quot;<br>
                &quot;(39 genPrimitiveFloatAtPut)&quot;<br>
                (40 genPrimitiveAsFloat                                 0)<br>
                (41 genPrimitiveFloatAdd                                1)<br>
                (42 genPrimitiveFloatSubtract                   1)<br>
                (43 genPrimitiveFloatLessThan                   1)<br>
                (44 genPrimitiveFloatGreaterThan                1)<br>
                (45 genPrimitiveFloatLessOrEqual                1)<br>
                (46 genPrimitiveFloatGreaterOrEqua<wbr>l     1)<br>
                (47 genPrimitiveFloatEqual                              1)<br>
                (48 genPrimitiveFloatNotEqual                   1)<br>
                (49 genPrimitiveFloatMultiply                   1)<br>
                (50 genPrimitiveFloatDivide                             1)<br>
                &quot;(51 genPrimitiveTruncated)&quot;<br>
                &quot;(52 genPrimitiveFractionalPart)&quot;<br>
                &quot;(53 genPrimitiveExponent)&quot;<br>
                &quot;(54 genPrimitiveTimesTwoPower)&quot;<br>
                (55 genPrimitiveFloatSquareRoot         0)<br>
                &quot;(56 genPrimitiveSine)&quot;<br>
                &quot;(57 genPrimitiveArctan)&quot;<br>
                &quot;(58 genPrimitiveLogN)&quot;<br>
                &quot;(59 genPrimitiveExp)&quot;<br>
<br>
                &quot;Subscript and Stream Primitives (60-67)&quot;<br>
                (60 genPrimitiveAt                              1)<br>
                (61 genPrimitiveAtPut                   2)<br>
                (62 genPrimitiveSize                    0)<br>
                (63 genPrimitiveStringAt                1)<br>
                (64 genPrimitiveStringAtPut             2)<br>
                &quot;The stream primitives no longer pay their way; normal Smalltalk \
code is faster.&quot;<br>  (65 genFastPrimFail)&quot;was primitiveNext&quot;<br>
                (66 genFastPrimFail) &quot;was primitiveNextPut&quot;<br>
                (67 genFastPrimFail) &quot;was primitiveAtEnd&quot;<br>
<br>
                &quot;StorageManagement Primitives (68-79)&quot;<br>
                (68 genPrimitiveObjectAt                        1)      &quot;Good \
for debugger/InstructionStream performance&quot;<br>  &quot;(69 \
primitiveObjectAtPut)&quot;<br>  (70 genPrimitiveNew                     0)<br>
                (71 genPrimitiveNewWithArg      1)<br>
                &quot;(72 primitiveArrayBecomeOneWay)&quot;               &quot;Blue \
Book: primitiveBecome&quot;<br>  &quot;(73 primitiveInstVarAt)&quot;<br>
                &quot;(74 primitiveInstVarAtPut)&quot;<br>
                (75 genPrimitiveIdentityHash    0)<br>
                &quot;(76 primitiveStoreStackp)&quot;                                 \
&quot;Blue Book: primitiveAsObject&quot;<br>  &quot;(77 \
primitiveSomeInstance)&quot;<br>  &quot;(78 primitiveNextInstance)&quot;<br>
                (79 genPrimitiveNewMethod       2)<br>
<br>
                &quot;Control Primitives (80-89)&quot;<br>
                &quot;(80 primitiveFail)&quot;                                        \
                &quot;Blue Book: primitiveBlockCopy&quot;<br>
                &quot;(81 primitiveFail)&quot;                                        \
                &quot;Blue Book: primitiveValue&quot;<br>
                &quot;(82 primitiveFail)&quot;                                        \
&quot;Blue Book: primitiveValueWithArgs&quot;<br>  (83 genPrimitivePerform)<br>
                &quot;(84 primitivePerformWithArgs)&quot;<br>
                &quot;(85 primitiveSignal)&quot;<br>
                &quot;(86 primitiveWait)&quot;<br>
                &quot;(87 primitiveResume)&quot;<br>
                &quot;(88 primitiveSuspend)&quot;<br>
                &quot;(89 primitiveFlushCache)&quot;<br>
<br>
                &quot;(90 primitiveMousePoint)&quot;<br>
                &quot;(91 primitiveTestDisplayDepth)&quot;                        \
                &quot;Blue Book: primitiveCursorLocPut&quot;<br>
                &quot;(92 primitiveSetDisplayMode)&quot;                          \
&quot;Blue Book: primitiveCursorLink&quot;<br>  &quot;(93 \
                primitiveInputSemaphore)&quot;<br>
                &quot;(94 primitiveGetNextEvent)&quot;                            \
&quot;Blue Book: primitiveSampleInterval&quot;<br>  &quot;(95 \
                primitiveInputWord)&quot;<br>
                &quot;(96 primitiveFail)&quot;    &quot;primitiveCopyBits&quot;<br>
                &quot;(97 primitiveSnapshot)&quot;<br>
                &quot;(98 primitiveStoreImageSegment)&quot;<br>
                &quot;(99 primitiveLoadImageSegment)&quot;<br>
                &quot;(100 primitivePerformInSuperclass)&quot;<wbr>            \
&quot;Blue Book: primitiveSignalAtTick&quot;<br>  &quot;(101 \
primitiveBeCursor)&quot;<br>  &quot;(102 primitiveBeDisplay)&quot;<br>
                &quot;(103 primitiveScanCharacters)&quot;<br>
                &quot;(104 primitiveFail)&quot;   &quot;primitiveDrawLoop&quot;<br>
                (105 genPrimitiveStringReplace)<br>
                &quot;(106 primitiveScreenSize)&quot;<br>
                &quot;(107 primitiveMouseButtons)&quot;<br>
                &quot;(108 primitiveKbdNext)&quot;<br>
                &quot;(109 primitiveKbdPeek)&quot;<br>
<br>
<br>
                &quot;System Primitives (110-119)&quot;<br>
                (110 genPrimitiveIdentical 1)<br>
                (111 genPrimitiveClass)                         &quot;Support both \
class and Context&gt;&gt;objectClass:&quot;<br>  &quot;(112 \
primitiveBytesLeft)&quot;<br>  &quot;(113 primitiveQuit)&quot;<br>
                &quot;(114 primitiveExitToDebugger)&quot;<br>
                &quot;(115 primitiveChangeClass)&quot;                                \
&quot;Blue Book: primitiveOopsLeft&quot;<br>  &quot;(116 \
primitiveFlushCacheByMethod)&quot;<br>  &quot;(117 primitiveExternalCall)&quot;<br>
                &quot;(118 primitiveDoPrimitiveWithArgs)&quot;<br>
                &quot;(119 primitiveFlushCacheSelective)&quot;<br>
<br>
                (148 genPrimitiveShallowCopy 0)                 &quot;a.k.a. \
clone&quot;<br> <br>
+               (158 genPrimitiveStringCompareWith 1)<br>
                (159 genPrimitiveHashMultiply 0)<br>
<br>
                (169 genPrimitiveNotIdentical 1)<br>
<br>
                (170 genPrimitiveAsCharacter)                           \
                &quot;SmallInteger&gt;&gt;asCharacter, Character \
                class&gt;&gt;value:&quot;<br>
                (171 genPrimitiveImmediateAsInteger 0)  &quot;Character&gt;&gt;value \
SmallFloat64&gt;&gt;asInteger&quot;<br> <br>
                &quot;(173 primitiveSlotAt 1)&quot;<br>
                &quot;(174 primitiveSlotAtPut 2)&quot;<br>
                (175 genPrimitiveIdentityHash   0)              \
&quot;Behavior&gt;&gt;identityHash&quot;<br> <br>
                &quot;Old closure primitives&quot;<br>
                &quot;(186 primitiveFail)&quot; &quot;was \
                primitiveClosureValue&quot;<br>
                &quot;(187 primitiveFail)&quot; &quot;was \
primitiveClosureValueWithArgs&quot;<br> <br>
                &quot;Perform method directly&quot;<br>
                &quot;(188 primitiveExecuteMethodArgsArra<wbr>y)&quot;<br>
                &quot;(189 primitiveExecuteMethod)&quot;<br>
<br>
                &quot;Unwind primitives&quot;<br>
                &quot;(195 primitiveFindNextUnwindContext<wbr>)&quot;<br>
                &quot;(196 primitiveTerminateTo)&quot;<br>
                &quot;(197 primitiveFindHandlerContext)&quot;<br>
                (198 genFastPrimFail &quot;primitiveMarkUnwindMethod&quot;)<br>
                (199 genFastPrimFail &quot;primitiveMarkHandlerMethod&quot;)<br>
<br>
                &quot;new closure primitives&quot;<br>
                &quot;(200 primitiveClosureCopyWithCopied<wbr>Values)&quot;<br>
                (201 genPrimitiveClosureValue   0) &quot;value&quot;<br>
                (202 genPrimitiveClosureValue   1) &quot;value:&quot;<br>
                (203 genPrimitiveClosureValue   2) &quot;value:value:&quot;<br>
                (204 genPrimitiveClosureValue   3) &quot;value:value:value:&quot;<br>
                (205 genPrimitiveClosureValue   4) \
                &quot;value:value:value:value:&quot;<br>
                &quot;(206 genPrimitiveClosureValueWithAr<wbr>gs)&quot; \
&quot;valueWithArguments:&quot;<br> <br>
                (207 genPrimitiveFullClosureValue) &quot;value[:value:value:value:] \
                et al&quot;<br>
                &quot;(208 genPrimitiveFullClosureValueWi<wbr>thArgs)&quot; \
                &quot;valueWithArguments:&quot;<br>
                (209 genPrimitiveFullClosureValue) \
&quot;valueNoContextSwitch[:value:] et al&quot;<br> <br>
                &quot;(210 primitiveContextAt)&quot;<br>
                &quot;(211 primitiveContextAtPut)&quot;<br>
                &quot;(212 primitiveContextSize)&quot;<br>
<br>
                &quot;(218 primitiveDoNamedPrimitiveWithA<wbr>rgs)&quot;<br>
                &quot;(219 primitiveFail)&quot;   &quot;reserved for Cog \
primitives&quot;<br> <br>
                &quot;(220 primitiveFail)&quot;           &quot;reserved for Cog \
primitives&quot;<br> <br>
                (221 genPrimitiveClosureValue   0) \
                &quot;valueNoContextSwitch&quot;<br>
                (222 genPrimitiveClosureValue   1) \
&quot;valueNoContextSwitch:&quot;<br> <br>
                &quot;SmallFloat primitives (540-559)&quot;<br>
                (541 genPrimitiveSmallFloatAdd                          1)<br>
                (542 genPrimitiveSmallFloatSubtract<wbr>                     1)<br>
                (543 genPrimitiveSmallFloatLessThan<wbr>                     1)<br>
                (544 genPrimitiveSmallFloatGreaterT<wbr>han          1)<br>
                (545 genPrimitiveSmallFloatLessOrEq<wbr>ual          1)<br>
                (546 genPrimitiveSmallFloatGreaterO<wbr>rEqual               1)<br>
                (547 genPrimitiveSmallFloatEqual                                \
                1)<br>
                (548 genPrimitiveSmallFloatNotEqual<wbr>                     1)<br>
                (549 genPrimitiveSmallFloatMultiply<wbr>                             \
                1)<br>
                (550 genPrimitiveSmallFloatDivide                               \
                1)<br>
                &quot;(551 genPrimitiveSmallFloatTruncate<wbr>d                   \
                0)&quot;<br>
                &quot;(552 genPrimitiveSmallFloatFraction<wbr>alPart              \
                0)&quot;<br>
                &quot;(553 genPrimitiveSmallFloatExponent<wbr>                    \
                0)&quot;<br>
                &quot;(554 genPrimitiveSmallFloatTimesTwo<wbr>Power       \
                1)&quot;<br>
                (555 genPrimitiveSmallFloatSquareRo<wbr>ot                   0)<br>
                &quot;(556 genPrimitiveSmallFloatSine                                \
                0)&quot;<br>
                &quot;(557 genPrimitiveSmallFloatArctan                              \
                0)&quot;<br>
                &quot;(558 genPrimitiveSmallFloatLogN                                \
                0)&quot;<br>
                &quot;(559 genPrimitiveSmallFloatExp                         \
0)&quot;<br>  )!<br>
<br>
Item was changed:<br>
  ----- Method: StackInterpreter class&gt;&gt;initializePrimitiveTabl<wbr>e (in \
category &#39;initialization&#39;) -----<br> (excessive size, no diff calculated)<br>
<br>
</blockquote></div><br></div>
<br></blockquote></div><br></div></div>
<br></blockquote></div><br></div></div>



[prev in list] [next in list] [prev in thread] [next in thread] 

Configure | About | News | Add a list | Sponsored by KoreLogic