[squeak-dev] The Inbox: KernelTests-cbc.336.mcz

Chris Cunningham cunningham.cb at gmail.com
Thu Mar 22 04:48:05 UTC 2018


Don't load this one - somehow it deleted several tests.  Very weird.

On Wed, Mar 21, 2018 at 9:41 PM, <commits at source.squeak.org> wrote:

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


More information about the Squeak-dev mailing list