<div dir="ltr">Don't load this one - somehow it deleted several tests.  Very weird.</div><div class="gmail_extra"><br><div class="gmail_quote">On Wed, Mar 21, 2018 at 9:41 PM,  <span dir="ltr"><<a href="mailto:commits@source.squeak.org" target="_blank">commits@source.squeak.org</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">A new version of KernelTests was added to project The Inbox:<br>
<a href="http://source.squeak.org/inbox/KernelTests-cbc.336.mcz" rel="noreferrer" target="_blank">http://source.squeak.org/<wbr>inbox/KernelTests-cbc.336.mcz</a><br>
<br>
==================== Summary ====================<br>
<br>
Name: KernelTests-cbc.336<br>
Author: cbc<br>
Time: 21 March 2018, 9:41:20.439568 pm<br>
UUID: 0ad1f79d-ea7e-0243-9c7e-<wbr>ccfcc72aa1ef<br>
Ancestors: KernelTests-eem.335, KernelTests-fn.333<br>
<br>
updated for Kernel-cbc.1163<br>
<br>
=============== Diff against KernelTests-eem.335 ===============<br>
<br>
Item was changed:<br>
  ----- Method: FalseTest>>testXor (in category 'tests') -----<br>
  testXor<br>
        self assert: (false xor: true) = true.<br>
        self assert: (false xor: false) = false.<br>
+       self assert: (false xor: [true]) = true.<br>
+       self assert: (false xor: [false]) = false.!<br>
-<br>
-       self<br>
-               should: [(false xor: [false])<br>
-                       ifTrue: ["This should never be true, do not signal an Error and let the test fail"]<br>
-                       ifFalse: [self error: 'OK, this should be false, raise an Error']]<br>
-               raise: Error<br>
-               description: 'a Block argument is not allowed. If it were, answer would be false'.!<br>
<br>
Item was removed:<br>
- TestCase subclass: #LiteralRefLocatorTest<br>
-       instanceVariableNames: ''<br>
-       classVariableNames: ''<br>
-       poolDictionaries: ''<br>
-       category: 'KernelTests-Methods'!<br>
<br>
Item was removed:<br>
- ----- Method: LiteralRefLocatorTest>><wbr>testFindLiteralsInBytecode (in category 'tests') -----<br>
- testFindLiteralsInBytecode<br>
-       "Create a method referencing integers, characters, special selectors and nil, true & false.<br>
-        Compile it and check that the objects are found."<br>
-       | source primary secondary binarySpecials integers characters |<br>
-       binarySpecials := Smalltalk specialSelectors select: [:s| s isSymbol and: [s isBinary]].<br>
-       "-65536 to 65535 in powers of two"<br>
-       integers := ((16 to: 1 by: -1) collect: [:power| (2 raisedTo: power) negated]),<br>
-                               ((0 to: 16) collect: [:power| (2 raisedTo: power) - 1]).<br>
-       "some printable characters; alas none have code > 255"<br>
-       characters := (0 to: 65535)<br>
-                                       select: [:n| (n between: 132 and: 160) not "these have no glyph in typical fonts"<br>
-                                                               and: [(Character value: n) shouldBePrintedAsLiteral]]<br>
-                                       thenCollect: [:n| Character value: n].<br>
-       [characters size > 32] whileTrue:<br>
-               [characters := (1 to: characters size by: 2) collect: [:i| characters at: i]].<br>
-<br>
-       #(('' '') ('^[' ']')) do: "And the locators should work whether in a block or not"<br>
-               [:pFixes|<br>
-               source := ByteString streamContents:<br>
-                                       [:s| | binaries |<br>
-                                       binaries := binarySpecials readStream.<br>
-                                       s nextPutAll: 'exampleMethod'; crtab; nextPutAll: pFixes first.<br>
-                                       integers<br>
-                                               do: [:n| s print: n]<br>
-                                               separatedBy:<br>
-                                                       [binaries atEnd ifTrue: [binaries reset].<br>
-                                                        s space; nextPutAll: binaries next; space].<br>
-                                       s nextPut: $.; crtab.<br>
-                                       s nextPut: ${; space.<br>
-                                       characters<br>
-                                               do: [:c| s print: c]<br>
-                                               separatedBy: [s nextPut: $.; space].<br>
-                                       s space; nextPut: $}; nextPut: $.; crtab.<br>
-                                       s nextPutAll: 'true ifTrue: [^nil] ifFalse: [^false]'; nextPutAll: pFixes last].<br>
-               primary := CompiledCode classPool at: #<wbr>PrimaryBytecodeSetEncoderClass<wbr>.<br>
-               secondary := CompiledCode classPool at: #<wbr>SecondaryBytecodeSetEncoderCla<wbr>ss.<br>
-               { primary. secondary } do:<br>
-                       [:encoderClass| | method |<br>
-                       method := (Parser new<br>
-                                                               encoderClass: encoderClass;<br>
-                                                               parse: source class: self class)<br>
-                                                       generate: CompiledMethodTrailer empty.<br>
-                       binarySpecials, integers, characters, #(nil false true) do:<br>
-                               [:literal|<br>
-                               self assert: (method<br>
-                                                               refersTo: literal<br>
-                                                               primaryBytecodeScanner: (primary scanBlockOrNilForLiteral: literal)<br>
-                                                               secondaryBytecodeScanner: (secondary scanBlockOrNilForLiteral: literal)<br>
-                                                               thorough: false).<br>
-                               (encoderClass scanBlockOrNilForLiteral: literal)<br>
-                                       ifNil: [self assert: (method hasLiteral: literal)]<br>
-                                       ifNotNil: [:scanBlock|<br>
-                                                       self assert: ((method scanFor: scanBlock)<br>
-                                                                               or: [method literals anySatisfy: [:l| l isCompiledCode and: [l scanFor: scanBlock]]])]].<br>
-<br>
-                       "Now test for false positives..."<br>
-                       integers, characters, #(nil false true) do:<br>
-                               [:literal| | simpleSource simpleMethod |<br>
-                               simpleSource := ByteString streamContents:<br>
-                                                                       [:s| s nextPutAll: 'exampleMethod'; crtab; nextPutAll: pFixes first; print: literal; nextPutAll: ' class'; nextPutAll: pFixes last].<br>
-                               simpleMethod := (Parser new<br>
-                                                                               encoderClass: encoderClass;<br>
-                                                                               parse: simpleSource class: self class)<br>
-                                                                       generate: CompiledMethodTrailer empty.<br>
-                               binarySpecials, integers, characters, #(nil false true) do:<br>
-                                       [:anyLiteral|<br>
-                                       anyLiteral == literal<br>
-                                               ifTrue:<br>
-                                                       [self assert: (simpleMethod<br>
-                                                                                       refersTo: anyLiteral<br>
-                                                                                       primaryBytecodeScanner: (primary scanBlockOrNilForLiteral: anyLiteral)<br>
-                                                                                       secondaryBytecodeScanner: (secondary scanBlockOrNilForLiteral: anyLiteral)<br>
-                                                                                       thorough: false).<br>
-                                                       (encoderClass scanBlockOrNilForLiteral: anyLiteral)<br>
-                                                               ifNil: [self assert: (simpleMethod hasLiteral: anyLiteral)]<br>
-                                                               ifNotNil: [:scanBlock|<br>
-                                                                               self assert: ((simpleMethod scanFor: scanBlock)<br>
-                                                                               or: [simpleMethod literals anySatisfy: [:l| l isCompiledCode and: [l scanFor: scanBlock]]])]]<br>
-                                               ifFalse:<br>
-                                                       [self deny: (simpleMethod<br>
-                                                                                       refersTo: anyLiteral<br>
-                                                                                       primaryBytecodeScanner: (primary scanBlockOrNilForLiteral: anyLiteral)<br>
-                                                                                       secondaryBytecodeScanner: (secondary scanBlockOrNilForLiteral: anyLiteral)<br>
-                                                                                       thorough: false).<br>
-                                                       (encoderClass scanBlockOrNilForLiteral: anyLiteral)<br>
-                                                               ifNil: [self deny: (simpleMethod hasLiteral: anyLiteral)]<br>
-                                                               ifNotNil: [:scanBlock|<br>
-                                                                               self deny: ((simpleMethod scanFor: scanBlock)<br>
-                                                                               or: [simpleMethod literals anySatisfy: [:l| l isCompiledCode and: [l scanFor: scanBlock]]])]]]]]]!<br>
<br>
Item was removed:<br>
- ----- Method: LiteralRefLocatorTest>><wbr>testThoroughFindLiteralsInByte<wbr>code (in category 'tests') -----<br>
- testThoroughFindLiteralsInByte<wbr>code<br>
-       "Create a method referencing integers, characters, special selectors and nil, true & false.<br>
-        Compile it and check that the objects are found."<br>
-       | literals problem primary secondary |<br>
-       literals := #(-1 0 1 $0 $1 1.0 #[1 2 3 4] 'one' #one nil true false NaN).<br>
-       problem := Float bindingOf: #NaN.<br>
-       primary := CompiledCode classPool at: #<wbr>PrimaryBytecodeSetEncoderClass<wbr>.<br>
-       secondary := CompiledCode classPool at: #<wbr>SecondaryBytecodeSetEncoderCla<wbr>ss.<br>
-       { primary. secondary } do:<br>
-               [:encoderClass| | method |<br>
-               #(('' '') ('^[' ']')) do: "And the locators should work whether in a block or not"<br>
-                       [:pFixes|<br>
-                       "NaN's binding should still be found even though (Float bindingOf: #NaN) ~= (Float bindingOf: #NaN)"<br>
-                       method := (Parser new<br>
-                                                               encoderClass: encoderClass;<br>
-                                                               parse: 'foo ', pFixes first, '^NaN', pFixes last class: Float)<br>
-                                                       generate: CompiledMethodTrailer empty.<br>
-                       [:literal|<br>
-                        self assert: (method<br>
-                                                       refersTo: literal<br>
-                                                       primaryBytecodeScanner: (primary scanBlockOrNilForLiteral: literal)<br>
-                                                       secondaryBytecodeScanner: (secondary scanBlockOrNilForLiteral: literal)<br>
-                                                       thorough: false).<br>
-                        self assert: (method<br>
-                                                       refersTo: literal<br>
-                                                       primaryBytecodeScanner: (primary scanBlockOrNilForLiteral: literal)<br>
-                                                       secondaryBytecodeScanner: (secondary scanBlockOrNilForLiteral: literal)<br>
-                                                       thorough: true)] value: problem.<br>
-<br>
-                       "All the literals should be found in a thorough search, but not otherwise"<br>
-                       method := (Parser new<br>
-                                                               encoderClass: encoderClass;<br>
-                                                               parse: 'foo ', pFixes first, '^', literals storeString, pFixes last class: Float)<br>
-                                                       generate: CompiledMethodTrailer empty.<br>
-                       literals, {problem. problem key} do:<br>
-                               [:literal|<br>
-                               self deny: (method<br>
-                                                               refersTo: literal<br>
-                                                               primaryBytecodeScanner: (primary scanBlockOrNilForLiteral: literal)<br>
-                                                               secondaryBytecodeScanner: (secondary scanBlockOrNilForLiteral: literal)<br>
-                                                               thorough: false).<br>
-                               self assert: (method<br>
-                                                               refersTo: literal<br>
-                                                               primaryBytecodeScanner: (primary scanBlockOrNilForLiteral: literal)<br>
-                                                               secondaryBytecodeScanner: (secondary scanBlockOrNilForLiteral: literal)<br>
-                                                               thorough: true)]].<br>
-<br>
-               "Likewise if in a pragma"<br>
-               method := (Parser new<br>
-                                                       encoderClass: encoderClass;<br>
-                                                       parse: 'foo <pragma: ', literals storeString, ' with: ', problem key storeString, '>' class: Float)<br>
-                                               generate: CompiledMethodTrailer empty.<br>
-               literals, {problem. problem key} do:<br>
-                       [:literal|<br>
-                       self deny: (method<br>
-                                                       refersTo: literal<br>
-                                                       primaryBytecodeScanner: (primary scanBlockOrNilForLiteral: literal)<br>
-                                                       secondaryBytecodeScanner: (secondary scanBlockOrNilForLiteral: literal)<br>
-                                                       thorough: false).<br>
-                       self assert: (method<br>
-                                                       refersTo: literal<br>
-                                                       primaryBytecodeScanner: (primary scanBlockOrNilForLiteral: literal)<br>
-                                                       secondaryBytecodeScanner: (secondary scanBlockOrNilForLiteral: literal)<br>
-                                                       thorough: true)]]!<br>
<br>
Item was changed:<br>
  ----- Method: PromiseTest>>testTimeout (in category 'testing') -----<br>
  testTimeout<br>
        | promise |<br>
        promise := Promise new.<br>
        self shouldnt: [promise waitTimeoutMSecs: 1].<br>
        self shouldnt: [promise isResolved].<br>
-       self shouldnt: [promise isRejected].<br>
        promise resolveWith: 45.<br>
        self should: [promise waitTimeoutMSecs: 1].<br>
        self should: [promise isResolved].<br>
+       !<br>
-       self shouldnt: [promise isRejected].!<br>
<br>
Item was removed:<br>
- ----- Method: PromiseTest>><wbr>testTimeoutRejected (in category 'testing') -----<br>
- testTimeoutRejected<br>
-       | promise |<br>
-       promise := Promise new.<br>
-       self shouldnt: [promise waitTimeoutMSecs: 1].<br>
-       self shouldnt: [promise isResolved].<br>
-       self shouldnt: [promise isRejected].<br>
-       promise rejectWith: 45.<br>
-       self shouldnt: [promise waitTimeoutMSecs: 1].<br>
-       self shouldnt: [promise isResolved].<br>
-       self should: [promise isRejected].!<br>
<br>
Item was changed:<br>
  ----- Method: TrueTest>>testXor (in category 'testing') -----<br>
  testXor<br>
        self assert: (true xor: true) = false.<br>
        self assert: (true xor: false) = true.<br>
+       self assert: (true xor: [true]) = false.<br>
+       self assert: (true xor: [false]) = true.!<br>
-<br>
-       self<br>
-               should: [(true xor: [true])<br>
-                       ifTrue: ["This should never be true, do not signal an Error and let the test fail"]<br>
-                       ifFalse: [self error: 'OK, this should be false, raise an Error']]<br>
-               raise: Error<br>
-               description: 'a Block argument is not allowed. If it were, answer would be false'.!<br>
<br>
<br>
</blockquote></div><br></div>