[Pkg] Installer: KernelTests-dc.74.mcz

Damien Cassou damien.cassou at gmail.com
Sun Sep 28 14:55:07 UTC 2008


Please remove this file, it was a mistake. Sorry

On Sun, Sep 28, 2008 at 3:56 PM,
<squeak-dev-noreply at lists.squeakfoundation.org> wrote:
> A new version of KernelTests was added to project Installer:
> http://www.squeaksource.com/Installer/KernelTests-dc.74.mcz
>
> ==================== Summary ====================
>
> Name: KernelTests-dc.74
> Author: dc
> Time: 28 September 2008, 3:55:30 pm
> UUID: 1df204cd-ab1f-4f38-8c19-585464b3380f
> Ancestors: KernelTests-marcus.denker.73
>
> - Categorize BehaviorTest>>testBinding
>
> ==================== Snapshot ====================
>
> SystemOrganization addCategory: #'KernelTests-Chronology'!
> SystemOrganization addCategory: #'KernelTests-Classes'!
> SystemOrganization addCategory: #'KernelTests-Methods'!
> SystemOrganization addCategory: #'KernelTests-Numbers'!
> SystemOrganization addCategory: #'KernelTests-Objects'!
> SystemOrganization addCategory: #'KernelTests-Processes'!
>
> TestCase subclass: #BasicBehaviorClassMetaclassTest
>        instanceVariableNames: ''
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Classes'!
>
> !BasicBehaviorClassMetaclassTest commentStamp: '<historical>' prior: 0!
> This class contains some tests regarding the classes
>        Behavior
>                ClassDescription
>                        Class
>                        Metaclass
> ---
>        !
>
> ----- Method: BasicBehaviorClassMetaclassTest>>testBehaviorClassClassDescriptionMetaclassHierarchy (in category 'testing') -----
> testBehaviorClassClassDescriptionMetaclassHierarchy
>        "self run: #testBehaviorClassClassDescriptionMetaclassHierarchy"
>
>        self assert: Class superclass  == ClassDescription.
>        self assert: Metaclass superclass == ClassDescription.
>
>        self assert: ClassDescription superclass  == Behavior.
>        self assert: Behavior superclass  = Object.
>
>        self assert: Class class class ==  Metaclass.
>        self assert: Metaclass class class  == Metaclass.
>        self assert: ClassDescription class class == Metaclass.
>        self assert: Behavior class class == Metaclass.
>
>
>
>
>
>
>
>
>
>
>
>
>
>        !
>
> ----- Method: BasicBehaviorClassMetaclassTest>>testClassDescriptionAllSubInstances (in category 'testing') -----
> testClassDescriptionAllSubInstances
>        "self run: #testClassDescriptionAllSubInstances"
>
>        | cdNo clsNo metaclsNo |
>        cdNo := ClassDescription allSubInstances size.
>        clsNo := Class allSubInstances size .
>        metaclsNo := Metaclass allSubInstances size.
>
>        self assert: cdNo = (clsNo + metaclsNo).
>
>
>
>
>
>
>
>
>
>
>        !
>
> ----- Method: BasicBehaviorClassMetaclassTest>>testMetaclass (in category 'testing') -----
> testMetaclass
>        "self run: #testMetaclass"
>
>        self assert: OrderedCollection class class == Metaclass.
>        self assert: Dictionary class class == Metaclass.
>        self assert: Object class class == Metaclass.
>
>
>
>
>
>
>
>
>
>
>
>
>
>        !
>
> ----- Method: BasicBehaviorClassMetaclassTest>>testMetaclassName (in category 'testing') -----
> testMetaclassName
>        "self run: #testMetaclassName"
>
>        self assert: Dictionary class  name = 'Dictionary class'.
>        self assert: OrderedCollection class name = 'OrderedCollection class'.
>        !
>
> ----- Method: BasicBehaviorClassMetaclassTest>>testMetaclassNumberOfInstances (in category 'testing') -----
> testMetaclassNumberOfInstances
>        "self run: #testMetaclassNumberOfInstances"
>
>        self assert: Dictionary class allInstances size  = 1.
>        self assert: OrderedCollection class allInstances size  = 1.!
>
> ----- Method: BasicBehaviorClassMetaclassTest>>testMetaclassPointOfCircularity (in category 'testing') -----
> testMetaclassPointOfCircularity
>        "self run: #testMetaclassPointOfCircularity"
>
>        self assert: Metaclass class instanceCount = 1.
>        self assert: Metaclass class someInstance == Metaclass.
>
>
>
>
>
>
>
>
>
>
>
>        !
>
> ----- Method: BasicBehaviorClassMetaclassTest>>testMetaclassSuperclass (in category 'testing') -----
> testMetaclassSuperclass
>        "self run: #testMetaclassSuperclass"
>
>        self assert: Dictionary class superclass == Set class.
>        self assert: OrderedCollection class superclass == SequenceableCollection class.
>
>        !
>
> ----- Method: BasicBehaviorClassMetaclassTest>>testMetaclassSuperclassHierarchy (in category 'testing') -----
> testMetaclassSuperclassHierarchy
>        "self run: #testMetaclassSuperclassHierarchy"
>
>        | s |
>        self assert: SequenceableCollection class instanceCount  = 1.
>        self assert: Collection class instanceCount  = 1.
>        self assert: Object class instanceCount  = 1.
>        self assert: ProtoObject class instanceCount  = 1.
>
>        s := OrderedCollection new.
>        s add: SequenceableCollection class.
>        s add: Collection class.
>        s add: Object class.
>        s add: ProtoObject class.
>
>        s add: Class.
>        s add: ClassDescription.
>        s add: Behavior.
>        s add: Object.
>        s add: ProtoObject.
>
>        self assert: OrderedCollection class allSuperclasses  = s.
>
>
>
>
>
>
>        !
>
> ----- Method: BasicBehaviorClassMetaclassTest>>testObjectAllSubclasses (in category 'testing') -----
> testObjectAllSubclasses
>        "self run: #testObjectAllSubclasses"
>
>        | n2 |
>        n2 := Object allSubclasses size.
>        self assert: n2 = (Object allSubclasses
>                        select: [:cls | cls class class == Metaclass
>                                        or: [cls class == Metaclass]]) size!
>
> ----- Method: BasicBehaviorClassMetaclassTest>>testSuperclass (in category 'testing') -----
> testSuperclass
>        "self run: #testSuperclass"
>
>        | s |
>        self assert: Dictionary superclass == Set.
>        self assert: OrderedCollection superclass == SequenceableCollection.
>
>        s := OrderedCollection new.
>        s add: SequenceableCollection.
>        s add: Collection.
>        s add: Object.
>        s add: ProtoObject.
>
>        self assert: OrderedCollection allSuperclasses = s.
>
>
>        !
>
> TestCase subclass: #BehaviorTest
>        instanceVariableNames: ''
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Classes'!
>
> ----- Method: BehaviorTest>>testBehaviorSubclasses (in category 'tests') -----
> testBehaviorSubclasses
>        "self run: #testBehaviorSubclasses"
>
>        | b b2 |
>        b := Behavior new.
>        b superclass: OrderedCollection.
>        b methodDictionary: MethodDictionary new.
>        self shouldnt: [b subclasses ] raise: Error.
>        self shouldnt: [b withAllSubclasses] raise: Error.
>        self shouldnt: [b allSubclasses] raise: Error.
>        b2 := Behavior new.
>        b2 superclass: b.
>        b2 methodDictionary: MethodDictionary new.
>        self assert: (b subclasses includes: b2).
>        self assert: (b withAllSubclasses includes: b).!
>
> ----- Method: BehaviorTest>>testBehaviornewnewShouldNotCrash (in category 'tests') -----
> testBehaviornewnewShouldNotCrash
>
>        Behavior new new.
>        "still not working correctly but at least does not crash the image"
>        !
>
> ----- Method: BehaviorTest>>testBinding (in category 'tests') -----
> testBinding
>        self assert: Object binding value = Object.
>        self assert: Object binding key = #Object.
>
>        self assert: Object class binding value = Object class.
>
>        "returns nil for Metaclasses... like Encoder>>#associationFor:"
>
>        self assert: Object class binding key isNil.!
>
> ----- Method: BehaviorTest>>testChange (in category 'tests') -----
> testChange
>        "self debug: #testChange"
>
>        | behavior model |
>        behavior := Behavior new.
>        behavior superclass: Model.
>        behavior setFormat: Model format.
>        model := Model new.
>        model primitiveChangeClassTo: behavior new.
>        behavior compile: 'thisIsATest  ^ 2'.
>        self assert: model thisIsATest = 2.
>        self should: [Model new thisIsATest] raise: MessageNotUnderstood.
>
>
> !
>
> TestCase subclass: #BlockContextTest
>        instanceVariableNames: 'aBlockContext contextOfaBlockContext'
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Methods'!
>
> !BlockContextTest commentStamp: 'jrp 10/17/2004 12:22' prior: 0!
> I am an SUnit Test of BlockContext and its supertype ContextPart.  See also MethodContextTest.
>
> My fixtures are:
> aBlockContext     - just some trivial block, i.e., [100 at 100 corner: 200 at 200].
>
> NOTES ABOUT AUTOMATING USER INPUTS
>
> When executing non-interactive programs you will inevitably run into programs (like SqueakMap or Monticello installation packages -- and other programs, to be fair) that require user input during their execution and these sort of problems shoot the whole non-interactiveness of your enclosing program.
>
> BlockContext helper methods have been made available and tests of these helpers are provided in this class to demonstrate that it can intercept PopUpMenu and FillInTheBlankMorph requests for user interaction.  Of course, PopUpMenu and FillInTheBlankMorph were modified to first signal a ProvideAnswerNotification and if someone handles that (e.g. the enclosing block) then the user interaction will be circumvented and the provided answer of the enclosing block will be used.  The basic syntax looks like:
>
>        [self confirm: 'Install spyware?'] valueSupplyingAnswer: #('Install spyware?' false)
>
> There a few variants on this theme making it easy to provide a literal list of answers for the block so that you can handle a bunch of questions in a block with appropriate answers.
>
> Additionally, it is possible to suppress Object>>inform: modal dialog boxes as these get in the way of automating anything.  After applying this changeset you should be able to tryout the following code snippets to see the variants on this theme that are available.
>
> Examples:
>
> So you don't need any introduction here -- this one works like usual.
> [self inform: 'hello'. #done] value.
>
> Now let's suppress all inform: messages.
> [self inform: 'hello'; inform: 'there'. #done] valueSuppressingAllMessages.
>
> Here we can just suppress a single inform: message.
> [self inform: 'hi'; inform: 'there'. #done] valueSuppressingMessages: #('there')
>
> Here you see how you can suppress a list of messages.
> [self inform: 'hi'; inform: 'there'; inform: 'bill'. #done] valueSuppressingMessages: #('hi' 'there')
>
> Enough about inform:, let's look at confirm:. As you see this one works as expected.
> [self confirm: 'You like Squeak?'] value
>
> Let's supply answers to one of the questions -- check out the return value.
> [{self confirm: 'You like Smalltalk?'. self confirm: 'You like Squeak?'}]
>        valueSupplyingAnswer: #('You like Smalltalk?' true)
>
> Here we supply answers using only substrings of the questions (for simplicity).
> [{self confirm: 'You like Squeak?'. self confirm: 'You like MVC?'}]
>        valueSupplyingAnswers: #( ('Squeak' true) ('MVC' false) )
>
> This time let's answer all questions exactly the same way.
> [{self confirm: 'You like Squeak?'. self confirm: 'You like Morphic?'}]
>        valueSupplyingAnswer: true
>
> And, of course, we can answer FillInTheBlank questions in the same manner.
> [FillInTheBlank request: 'What day is it?']
>        valueSupplyingAnswer: 'the first day of the rest of your life'
>
> We can also return whatever the initialAnswer of the FillInTheBlank was by using the #default answer.
> [FillInTheBlank request: 'What day is it?' initialAnswer: DateAndTime now dayOfWeekName]
>        valueSupplyingAnswer: #default
>
> Finally, you can also do regex matches on any of the question text (or inform text) (should you have VB-Regex enhancements in your image).
> [FillInTheBlank request: 'What day is it?']
>        valueSupplyingAnswers: { {'What day.*\?'. DateAndTime now dayOfWeekName} }!
>
> ----- Method: BlockContextTest>>setUp (in category 'setup') -----
> setUp
>        super setUp.
>        aBlockContext := [100 at 100 corner: 200 at 200].
>        contextOfaBlockContext := thisContext.!
>
> ----- Method: BlockContextTest>>testBlockIsBottomContext (in category 'tests') -----
> testBlockIsBottomContext
>        self    should: [aBlockContext client ] raise: Error. "block's sender is nil, a block has no client"
>        self assert: aBlockContext bottomContext = aBlockContext.
>        self assert: aBlockContext secondFromBottom isNil.!
>
> ----- Method: BlockContextTest>>testCopyStack (in category 'tests') -----
> testCopyStack
>        self assert: aBlockContext copyStack printString = aBlockContext printString.!
>
> ----- Method: BlockContextTest>>testDecompile (in category 'tests - printing') -----
> testDecompile
>        self assert: ([3 + 4] decompile printString = '{[3 + 4]}').!
>
> ----- Method: BlockContextTest>>testFindContextSuchThat (in category 'tests') -----
> testFindContextSuchThat
>        self assert: (aBlockContext findContextSuchThat: [:each| true]) printString = aBlockContext printString.
>        self assert: (aBlockContext hasContext: aBlockContext).  !
>
> ----- Method: BlockContextTest>>testNew (in category 'tests') -----
> testNew
>        self    should: [ContextPart new: 5] raise: Error.
>        [ContextPart new: 5]
>                ifError: [:error :receiver | error = 'Error: Contexts must only be created with newForMethod:'].
>        [ContextPart new]
>                ifError: [:error :receiver | error = 'Error: Contexts must only be created with newForMethod:'].
>        [ContextPart basicNew]
>                ifError: [:error :receiver | error = 'Error: Contexts must only be created with newForMethod:'].
>
> !
>
> ----- Method: BlockContextTest>>testNoArguments (in category 'tests') -----
> testNoArguments
>        [10
>                timesRepeat: [:arg | 1 + 2]]
>                ifError: [:err :rcvr | self deny: err = 'This block requires 1 arguments.'].
>        [10
>                timesRepeat: [:arg1 :arg2 | 1 + 2]]
>                ifError: [:err :rcvr | self deny: err = 'This block requires 2 arguments.'] !
>
> ----- Method: BlockContextTest>>testOneArgument (in category 'tests') -----
> testOneArgument
>        | c |
>        c := OrderedCollection new.
>        c add: 'hello'.
>        [c
>                do: [1 + 2]]
>                ifError: [:err :rcvr | self deny: err = 'This block requires 0 arguments.'].
>        [c
>                do: [:arg1 :arg2 | 1 + 2]]
>                ifError: [:err :rcvr | self deny: err = 'This block requires 2 arguments.'] !
>
> ----- Method: BlockContextTest>>testRunSimulated (in category 'tests') -----
> testRunSimulated
>        self assert: (ContextPart runSimulated: aBlockContext) class = Rectangle.!
>
> ----- Method: BlockContextTest>>testSetUp (in category 'tests') -----
> testSetUp
>        "Note: In addition to verifying that the setUp worked the way it was expected to, testSetUp is used to illustrate the meaning of the simple access methods, methods that are not normally otherwise 'tested'"
>        self deny: aBlockContext isBlockClosure.
>        self deny: aBlockContext isMethodContext.
>        self deny: aBlockContext isPseudoContext.
>        self deny: aBlockContext isDead.
>        self assert: aBlockContext home = contextOfaBlockContext.
>        self assert: aBlockContext blockHome = contextOfaBlockContext.
>        self assert: aBlockContext receiver = self.
>        self assert: (aBlockContext method isKindOf: CompiledMethod).
>        self assert: aBlockContext methodNode selector = 'setUp'.
>        self assert: (aBlockContext methodNodeFormattedAndDecorated: true) selector = 'setUp'.!
>
> ----- Method: BlockContextTest>>testSupplyAnswerOfFillInTheBlank (in category 'testing') -----
> testSupplyAnswerOfFillInTheBlank
>
>        self should: ['blue' = ([UIManager default request: 'Your favorite color?']
>                valueSupplyingAnswer: #('Your favorite color?' 'blue'))]!
>
> ----- Method: BlockContextTest>>testSupplyAnswerOfFillInTheBlankUsingDefaultAnswer (in category 'testing') -----
> testSupplyAnswerOfFillInTheBlankUsingDefaultAnswer
>
>        self should: ['red' = ([UIManager default  request: 'Your favorite color?' initialAnswer: 'red']
>                valueSupplyingAnswer: #('Your favorite color?' #default))]!
>
> ----- Method: BlockContextTest>>testSupplyAnswerThroughNestedBlocks (in category 'tests') -----
> testSupplyAnswerThroughNestedBlocks
>
>        self should: [true = ([[self confirm: 'You like Smalltalk?']
>                valueSupplyingAnswer: #('Blub' false)] valueSupplyingAnswer: #('Smalltalk' true))]!
>
> ----- Method: BlockContextTest>>testSupplyAnswerUsingOnlySubstringOfQuestion (in category 'tests') -----
> testSupplyAnswerUsingOnlySubstringOfQuestion
>
>        self should: [false = ([self confirm: 'You like Smalltalk?']
>                valueSupplyingAnswer: #('like' false))]!
>
> ----- Method: BlockContextTest>>testSupplyAnswerUsingRegexMatchOfQuestion (in category 'tests') -----
> testSupplyAnswerUsingRegexMatchOfQuestion
>
>        (String includesSelector: #matchesRegex:) ifFalse: [^ self].
>
>        self should: [true = ([self confirm: 'You like Smalltalk?']
>                valueSupplyingAnswer: #('.*Smalltalk\?' true))]!
>
> ----- Method: BlockContextTest>>testSupplyAnswerUsingTraditionalMatchOfQuestion (in category 'tests') -----
> testSupplyAnswerUsingTraditionalMatchOfQuestion
>
>        self should: [true = ([self confirm: 'You like Smalltalk?']
>                valueSupplyingAnswer: #('*Smalltalk#' true))]!
>
> ----- Method: BlockContextTest>>testSupplySameAnswerToAllQuestions (in category 'tests') -----
> testSupplySameAnswerToAllQuestions
>
>        self should: [true = ([self confirm: 'You like Smalltalk?'] valueSupplyingAnswer: true)].
>
>        self should: [#(true true) = ([{self confirm: 'One'. self confirm: 'Two'}] valueSupplyingAnswer: true)].!
>
> ----- Method: BlockContextTest>>testSupplySeveralAnswersToSeveralQuestions (in category 'tests') -----
> testSupplySeveralAnswersToSeveralQuestions
>
>        self should: [#(false true) = ([{self confirm: 'One'. self confirm: 'Two'}]
>                valueSupplyingAnswers: #( ('One' false) ('Two' true) ))].
>
>        self should: [#(true false) = ([{self confirm: 'One'. self confirm: 'Two'}]
>                valueSupplyingAnswers: #( ('One' true) ('Two' false) ))]!
>
> ----- Method: BlockContextTest>>testSupplySpecificAnswerToQuestion (in category 'tests') -----
> testSupplySpecificAnswerToQuestion
>
>        self should: [false = ([self confirm: 'You like Smalltalk?']
>                valueSupplyingAnswer: #('You like Smalltalk?' false))]!
>
> ----- Method: BlockContextTest>>testSuppressInform (in category 'tests') -----
> testSuppressInform
>
>        self should: [[nil inform: 'Should not see this message or this test failed!!'] valueSuppressingAllMessages isNil]!
>
> ----- Method: BlockContextTest>>testSuppressInformUsingStringMatchOptions (in category 'tests') -----
> testSuppressInformUsingStringMatchOptions
>
>        self should: [([nil inform: 'Should not see this message or this test failed!!'] valueSuppressingMessages: #('Should not see this message or this test failed!!')) isNil].
>
>        self should: [([nil inform: 'Should not see this message or this test failed!!'] valueSuppressingMessages: #('not see this message')) isNil].
>
>        self should: [([nil inform: 'Should not see this message or this test failed!!'] valueSuppressingMessages: #('*message*failed#')) isNil].
> !
>
> ----- Method: BlockContextTest>>testTallyInstructions (in category 'tests') -----
> testTallyInstructions
>        self assert: (ContextPart tallyInstructions: aBlockContext) size = 15.!
>
> ----- Method: BlockContextTest>>testTallyMethods (in category 'tests') -----
> testTallyMethods
>        self assert: (ContextPart tallyMethods: aBlockContext) size = 3.!
>
> ----- Method: BlockContextTest>>testTempNamed (in category 'tests') -----
> testTempNamed
>        | block |
>        block := [ | oneTemp | oneTemp := 1. oneTemp].
>        self assert: block value = 1.
>
>        self assert: (block tempNamed: 'oneTemp') =  1.
>        !
>
> ----- Method: BlockContextTest>>testTempNamedPut (in category 'tests') -----
> testTempNamedPut
>        | block |
>        block := [ | oneTemp | oneTemp := 1. oneTemp].
>        self assert: block value = 1.
>        self assert: (block tempNamed: 'oneTemp') =  1.
>        block tempNamed: 'oneTemp' put: 2.
>        self assert: (block tempNamed: 'oneTemp')  = 2.
>
>        !
>
> ----- Method: BlockContextTest>>testTrace (in category 'tests') -----
> testTrace
>        self assert: (ContextPart trace: aBlockContext) class = Rectangle.!
>
> ----- Method: BlockContextTest>>testValueWithArguments (in category 'tests - evaluating') -----
> testValueWithArguments
>        self
>                should: [aBlockContext
>                                valueWithArguments: #(1 )]
>                raise: Error.
>        self
>                shouldnt: [aBlockContext
>                                valueWithArguments: #()]
>                raise: Error.
>        [aBlockContext
>                valueWithArguments: #(1 )]
>                ifError: [:err :rcvr | self assert: err = 'Error: This block accepts 0 arguments, but was called with 1.'].
>        [[:i | 3 + 4]
>                valueWithArguments: #(1 2)]
>                ifError: [:err :rcvr | self assert: err = 'Error: This block accepts 1 argument, but was called with 2.']!
>
> ----- Method: BlockContextTest>>testValueWithExitBreak (in category 'tests - evaluating') -----
> testValueWithExitBreak
>
>        | val |
>
>        [ :break |
>            1 to: 10 do: [ :i |
>                        val := i.
>                        i = 4 ifTrue: [break value].
>                ]
>        ] valueWithExit.
>
>        self assert: val = 4.!
>
> ----- Method: BlockContextTest>>testValueWithExitContinue (in category 'tests - evaluating') -----
> testValueWithExitContinue
>
>        | val last |
>        val := 0.
>
>        1 to: 10 do: [ :i |
>                [ :continue |
>                        i = 4 ifTrue: [continue value].
>                        val := val + 1.
>                        last := i
>                ] valueWithExit.
>        ].
>
>        self assert: val = 9.
>        self assert: last = 10. !
>
> ----- Method: BlockContextTest>>testValueWithPossibleArgs (in category 'tests - evaluating') -----
> testValueWithPossibleArgs
>        | block  blockWithArg blockWith2Arg |
>
>        block := [1].
>        blockWithArg  := [:arg | arg].
>        blockWith2Arg := [:arg1 :arg2 | {arg1. arg2}].
>
>        self assert: (block valueWithPossibleArgs: #()) = 1.
>        self assert: (block valueWithPossibleArgs: #(1)) = 1.
>
>        self assert: (blockWithArg valueWithPossibleArgs: #()) = nil.
>        self assert: (blockWithArg valueWithPossibleArgs: #(1)) = 1.
>        self assert: (blockWithArg valueWithPossibleArgs: #(1 2)) = 1.
>
>        self assert: (blockWith2Arg valueWithPossibleArgs: #()) = {nil .nil}.
>        self assert: (blockWith2Arg valueWithPossibleArgs: #(1)) =  {1 . nil}.
>        self assert: (blockWith2Arg valueWithPossibleArgs: #(1 2)) =  #(1 2).
>        self assert: (blockWith2Arg valueWithPossibleArgs: #(1 2 3)) = #(1 2).
>
>
>        !
>
> ----- Method: BlockContextTest>>testValueWithPossibleArgument (in category 'tests - evaluating') -----
> testValueWithPossibleArgument
>        | block  blockWithArg blockWith2Arg |
>
>        block := [1].
>        blockWithArg  := [:arg | arg].
>        blockWith2Arg := [:arg1 :arg2 | {arg1. arg2}].
>
>        self assert: (block valueWithPossibleArgument: 1) = 1.
>
>        self assert: (blockWithArg valueWithPossibleArgument: 1) = 1.
>
>        self assert: (blockWith2Arg valueWithPossibleArgument: 1) = {1 . nil}.
>
>
>        !
>
> TestCase subclass: #ClassBuilderChangeClassTypeTest
>        instanceVariableNames: 'baseClass subClass'
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Classes'!
>
> ----- Method: ClassBuilderChangeClassTypeTest>>baseClassName (in category 'utilities') -----
> baseClassName
>
>   ^'TestClassForClassChangeTest'!
>
> ----- Method: ClassBuilderChangeClassTypeTest>>cleanup (in category 'utilities') -----
> cleanup
>        baseClass ifNotNil:[baseClass removeFromSystem].!
>
> TestCase subclass: #ClassBuilderFormatTests
>        instanceVariableNames: 'baseClass subClass'
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Classes'!
>
> ----- Method: ClassBuilderFormatTests>>baseClassName (in category 'utilities') -----
> baseClassName
>        ^#DummyClassBuilderFormatTestSuperClass!
>
> ----- Method: ClassBuilderFormatTests>>cleanup (in category 'utilities') -----
> cleanup
>        subClass ifNotNil:[subClass removeFromSystem].
>        baseClass ifNotNil:[baseClass removeFromSystem].!
>
> ----- Method: ClassBuilderFormatTests>>makeByteVariableSubclassOf: (in category 'utilities') -----
> makeByteVariableSubclassOf: aClass
>        subClass := aClass variableByteSubclass: self subClassName
>                instanceVariableNames: ''
>                classVariableNames: ''
>                poolDictionaries: ''
>                category: 'Kernel-Tests-ClassBuilder'!
>
> ----- Method: ClassBuilderFormatTests>>makeIVarsSubclassOf: (in category 'utilities') -----
> makeIVarsSubclassOf: aClass
>        subClass := aClass subclass: self subClassName
>                instanceVariableNames: 'var3 var4'
>                classVariableNames: ''
>                poolDictionaries: ''
>                category: 'Kernel-Tests-ClassBuilder'!
>
> ----- Method: ClassBuilderFormatTests>>makeNormalSubclassOf: (in category 'utilities') -----
> makeNormalSubclassOf: aClass
>        subClass := aClass subclass: self subClassName
>                instanceVariableNames: ''
>                classVariableNames: ''
>                poolDictionaries: ''
>                category: 'Kernel-Tests-ClassBuilder'!
>
> ----- Method: ClassBuilderFormatTests>>makeVariableSubclassOf: (in category 'utilities') -----
> makeVariableSubclassOf: aClass
>        subClass := aClass variableSubclass: self subClassName
>                instanceVariableNames: ''
>                classVariableNames: ''
>                poolDictionaries: ''
>                category: 'Kernel-Tests-ClassBuilder'.!
>
> ----- Method: ClassBuilderFormatTests>>makeWeakSubclassOf: (in category 'utilities') -----
> makeWeakSubclassOf: aClass
>        subClass := aClass weakSubclass: self subClassName
>                instanceVariableNames: ''
>                classVariableNames: ''
>                poolDictionaries: ''
>                category: 'Kernel-Tests-ClassBuilder'!
>
> ----- Method: ClassBuilderFormatTests>>makeWordVariableSubclassOf: (in category 'utilities') -----
> makeWordVariableSubclassOf: aClass
>        subClass := aClass variableWordSubclass: self subClassName
>                instanceVariableNames: ''
>                classVariableNames: ''
>                poolDictionaries: ''
>                category: 'Kernel-Tests-ClassBuilder'!
>
> ----- Method: ClassBuilderFormatTests>>subClassName (in category 'utilities') -----
> subClassName
>        ^#DummyClassBuilderFormatTestSubClass!
>
> ----- Method: ClassBuilderFormatTests>>testByteVariableSubclass (in category 'testing') -----
> testByteVariableSubclass
>        "Ensure that the invariants for superclass/subclass format are preserved"
>        baseClass := Object variableByteSubclass: self baseClassName
>                instanceVariableNames: ''
>                classVariableNames: ''
>                poolDictionaries: ''
>                category: 'Kernel-Tests-ClassBuilder'.
>        [
>
>        self shouldnt:[self makeNormalSubclassOf: baseClass] raise: Error.
>        self deny: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self assert: (subClass isBytes).
>        subClass removeFromSystem.
>
>        "pointer classes"
>        self should:[self makeIVarsSubclassOf: baseClass] raise: Error.
>        self should:[self makeVariableSubclassOf: baseClass] raise: Error.
>        self should:[self makeWeakSubclassOf: baseClass] raise: Error.
>
>        "bit classes"
>        self shouldnt:[self makeByteVariableSubclassOf: baseClass] raise: Error.
>        self deny: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self assert: (subClass isBytes).
>        subClass removeFromSystem.
>
>        self should:[self makeWordVariableSubclassOf: baseClass] raise: Error.
>
>        ] ensure:[self cleanup].!
>
> ----- Method: ClassBuilderFormatTests>>testSubclass (in category 'testing') -----
> testSubclass
>        "Ensure that the invariants for superclass/subclass format are preserved"
>        baseClass := Object subclass: self baseClassName
>                instanceVariableNames: ''
>                classVariableNames: ''
>                poolDictionaries: ''
>                category: 'Kernel-Tests-ClassBuilder'.
>        [
>        self shouldnt:[self makeNormalSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self deny: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        "pointer classes"
>        self shouldnt:[self makeIVarsSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self deny: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        self shouldnt:[self makeVariableSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self assert:(subClass isVariable).
>        self deny: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        self shouldnt:[self makeWeakSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self assert:(subClass isVariable).
>        self assert:(subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        "bit classes"
>        self shouldnt:[self makeByteVariableSubclassOf: baseClass] raise: Error.
>        self deny: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self assert: (subClass isBytes).
>        subClass removeFromSystem.
>
>        self shouldnt:[self makeWordVariableSubclassOf: baseClass] raise: Error.
>        self deny: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>        ] ensure:[self cleanup].!
>
> ----- Method: ClassBuilderFormatTests>>testSubclassWithInstanceVariables (in category 'testing') -----
> testSubclassWithInstanceVariables
>        "Ensure that the invariants for superclass/subclass format are preserved"
>        baseClass := Object subclass: self baseClassName
>                instanceVariableNames: 'var1 var2'
>                classVariableNames: ''
>                poolDictionaries: ''
>                category: 'Kernel-Tests-ClassBuilder'.
>        [
>        self shouldnt:[self makeNormalSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self deny: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        "pointer classes"
>        self shouldnt:[self makeIVarsSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self deny: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        self shouldnt:[self makeVariableSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        self shouldnt:[self makeWeakSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self assert: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        "bit classes"
>        self should:[self makeByteVariableSubclassOf: baseClass] raise: Error.
>        self should:[self makeWordVariableSubclassOf: baseClass] raise: Error.
>        ] ensure:[self cleanup].!
>
> ----- Method: ClassBuilderFormatTests>>testVariableSubclass (in category 'testing') -----
> testVariableSubclass
>        "Ensure that the invariants for superclass/subclass format are preserved"
>        baseClass := Object variableSubclass: self baseClassName
>                instanceVariableNames: ''
>                classVariableNames: ''
>                poolDictionaries: ''
>                category: 'Kernel-Tests-ClassBuilder'.
>        [
>        "pointer classes"
>        self shouldnt:[self makeNormalSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        self shouldnt:[self makeIVarsSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        self shouldnt:[self makeVariableSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        self shouldnt:[self makeWeakSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self assert: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        "bit classes"
>        self should:[self makeByteVariableSubclassOf: baseClass] raise: Error.
>        self should:[self makeWordVariableSubclassOf: baseClass] raise: Error.
>        ] ensure:[self cleanup].!
>
> ----- Method: ClassBuilderFormatTests>>testWeakSubclass (in category 'testing') -----
> testWeakSubclass
>        "Ensure that the invariants for superclass/subclass format are preserved"
>        baseClass := Object weakSubclass: self baseClassName
>                instanceVariableNames: ''
>                classVariableNames: ''
>                poolDictionaries: ''
>                category: 'Kernel-Tests-ClassBuilder'.
>        [
>        "pointer classes"
>        self shouldnt:[self makeNormalSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self assert: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        self shouldnt:[self makeIVarsSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self assert: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        self shouldnt:[self makeVariableSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        self shouldnt:[self makeWeakSubclassOf: baseClass] raise: Error.
>        self assert: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self assert: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        "bit classes"
>        self should:[self makeByteVariableSubclassOf: baseClass] raise: Error.
>        self should:[self makeWordVariableSubclassOf: baseClass] raise: Error.
>        ] ensure:[self cleanup].!
>
> ----- Method: ClassBuilderFormatTests>>testWordVariableSubclass (in category 'testing') -----
> testWordVariableSubclass
>        "Ensure that the invariants for superclass/subclass format are preserved"
>        baseClass := Object variableWordSubclass: self baseClassName
>                instanceVariableNames: ''
>                classVariableNames: ''
>                poolDictionaries: ''
>                category: 'Kernel-Tests-ClassBuilder'.
>        [
>        self shouldnt:[self makeNormalSubclassOf: baseClass] raise: Error.
>        self deny: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        "pointer classes"
>        self should:[self makeIVarsSubclassOf: baseClass] raise: Error.
>        self should:[self makeVariableSubclassOf: baseClass] raise: Error.
>        self should:[self makeWeakSubclassOf: baseClass] raise: Error.
>
>        "bit classes"
>        self should:[self makeByteVariableSubclassOf: baseClass] raise: Error.
>        self shouldnt:[self makeWordVariableSubclassOf: baseClass] raise: Error.
>        self deny: (subClass isPointers).
>        self assert: (subClass isVariable).
>        self deny: (subClass isWeak).
>        self deny: (subClass isBytes).
>        subClass removeFromSystem.
>
>        ] ensure:[self cleanup].!
>
> TestCase subclass: #ClassTest
>        instanceVariableNames: 'className renamedName'
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Classes'!
>
> ----- Method: ClassTest>>deleteClass (in category 'setup') -----
> deleteClass
>        | cl |
>        cl := Smalltalk at: className ifAbsent: [^self].
>        cl removeFromChanges; removeFromSystemUnlogged
>        !
>
> ----- Method: ClassTest>>deleteRenamedClass (in category 'setup') -----
> deleteRenamedClass
>        | cl |
>        cl := Smalltalk at: renamedName ifAbsent: [^self].
>        cl removeFromChanges; removeFromSystemUnlogged
>        !
>
> ----- Method: ClassTest>>setUp (in category 'setup') -----
> setUp
>        className := #TUTU.
>        renamedName := #RenamedTUTU.
>        self deleteClass.
>        self deleteRenamedClass.
>        Object subclass: className
>                instanceVariableNames: ''
>                classVariableNames: ''
>                poolDictionaries: ''
>                category: 'KernelTests-Classes'!
>
> ----- Method: ClassTest>>tearDown (in category 'setup') -----
> tearDown
>        self deleteClass.
>        self deleteRenamedClass!
>
> ----- Method: ClassTest>>testAddInstVarName (in category 'testing') -----
> testAddInstVarName
>        "self run: #testAddInstVarName"
>
>
>        | tutu |
>        tutu := Smalltalk at: #TUTU.
>        tutu addInstVarName: 'x'.
>        self assert: (tutu instVarNames = #('x')).
>        tutu addInstVarName: 'y'.
>        self assert: (tutu instVarNames = #('x' 'y'))
>
>        !
>
> ----- Method: ClassTest>>testCompileAll (in category 'testing - compiling') -----
> testCompileAll
>
>        self shouldnt: [ClassTest compileAll] raise: Error.!
>
> ----- Method: ClassTest>>testHaSharedPools (in category 'testing - access') -----
> testHaSharedPools
>        "self run: #testHaSharedPools"
>
>        self deny: Point hasSharedPools.
>        self assert: Date hasSharedPools!
>
> ----- Method: ClassTest>>testRenaming (in category 'testing') -----
> testRenaming
>        "self debug: #testRenaming"
>        "self run: #testRenaming"
>
>        | oldName newMetaclassName class |
>        oldName := className.
>        newMetaclassName := (renamedName, #' class') asSymbol.
>        class := Smalltalk at: oldName.
>        class class compile: 'dummyMeth'.
>        class rename: renamedName.
>        self assert: class name = renamedName.
>        self assert: (ChangeSet current changedClassNames includes: renamedName).
>        self assert: (ChangeSet current changedClassNames includes: newMetaclassName).
>        !
>
> TestCase subclass: #ComplexTest
>        instanceVariableNames: ''
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Numbers'!
>
> ----- Method: ComplexTest>>testAbs (in category 'tests') -----
> testAbs
>        "self run: #testAbs"
>        "self debug: #testAbs"
>
>        | c |
>        c := (6 - 6 i).
>        self assert: c abs  = 72 sqrt.
>        !
>
> ----- Method: ComplexTest>>testAdding (in category 'tests') -----
> testAdding
>        "self run: #testAdding"
>
>        | c |
>        c := (5 - 6 i) + (-5 + 8 i).     "Complex with Complex"
>        self assert: (c =  (0 + 2 i)).!
>
> ----- Method: ComplexTest>>testArg (in category 'tests') -----
> testArg
>        "self run: #testArg"
>        "self debug: #testArg"
>
>        | c |
>        c := (0 + 5 i) .
>        self assert: c arg  = (Float pi/ 2).
>        !
>
> ----- Method: ComplexTest>>testBug1 (in category 'testing - bugs') -----
> testBug1
>
>        self assert: (0.5 * (2+0i) ln) exp = (0.5 * 2 ln) exp.!
>
> ----- Method: ComplexTest>>testComplexCollection (in category 'tests') -----
> testComplexCollection
>        "self run: #testComplexCollection"
>        "self debug: #testComplexCollection"
>
>        | array array2 |
>        array := Array with: 1 + 2i with:  3 + 4i with: 5 + 6i.
>        array2 := 2 * array.
>        array with:  array2 do: [:one :two | self assert: (2 * one) = two ] !
>
> ----- Method: ComplexTest>>testConversion (in category 'tests') -----
> testConversion
>        "self run: #testConversion"
>        "self debug: #testConversion"
>
>        self assert: ((1 + 2i) + 1) =  (2 + 2 i).
>        self assert: (1 + (1 + 2i)) =  (2 + 2 i).
>        self assert: ((1 + 2i) + 1.0) =  (2.0 + 2 i).
>        self assert: (1.0 + (1 + 2i)) =  (2.0 + 2 i).
>        self assert: ((1 + 2i) + (2/3)) = ((5/3) + 2 i ).
>        self assert: ((2/3) + (1 + 2i)) = ((5/3) + 2 i )!
>
> ----- Method: ComplexTest>>testCreation (in category 'tests') -----
> testCreation
>        "self run: #testCreation"
>
>        | c |
>        c := 5 i.
>        self assert: (c real = 0).
>        self assert: (c imaginary = 5).
>
>        c := 6 + 7 i.
>        self assert: (c real = 6).
>        self assert: ( c imaginary = 7).
>
>        c := 5.6 - 8 i.
>        self assert: (c real = 5.6).
>        self assert: (c imaginary = -8).
>
>        c := Complex real: 10 imaginary: 5.
>        self assert: (c real = 10).
>        self assert: (c imaginary = 5).
>
>        c := Complex abs: 5 arg: (Float pi/2).
>        self assert: (c real rounded = 0).
>        self assert: (c imaginary = 5).
>        !
>
> ----- Method: ComplexTest>>testDivision1 (in category 'tests') -----
> testDivision1
>        "self run: #testDivision1"
>        "self debug: #testDivision1"
>
>        | c1 c2 quotient |
>        c1 := 2.0e252 + 3.0e70 i.
>        c2 := c1.
>        quotient := c1 / c2.
>        self deny: (quotient - 1) isZero.
>
>        "This test fails due to the wonders of floating point arithmetic.
>         Please have a look at Complex>>divideSecureBy: and #divideFastAndSecureBy:
>        how this can be avoided."
>
> !
>
> ----- Method: ComplexTest>>testEquality (in category 'testing') -----
> testEquality
>        "self run: #testEquality"
>        "self debug: #testEquality"
>
>        self assert: 0i = 0.
>        self assert: (2 - 5i) = ((1 -4 i) + (1 - 1i)).
>        self assert: 0i isZero.
>        self deny: (1 + 3 i) = 1.
>        self deny: (1 + 3 i) = (1 + 2i).
>
> "Some more stuff"
>        self deny: (1 i) = nil.
>        self deny: nil = (1 i).
>
>        self deny: (1 i) = #(1 2 3).
>        self deny: #(1 2 3) = (1 i).
>
>        self deny: (1 i) = 0.
>        self deny: 0 = (1 i).
>
>        self assert:  (1 + 0 i) = 1.
>        self assert:  1 = (1+ 0 i).
>
>        self assert:  (1 + 0 i) = 1.0.
>        self assert:  1.0 = (1+ 0 i).
>
>        self assert:  (1/2 + 0 i) = (1/2).
>        self assert:  (1/2) = (1/2+ 0 i).!
>
> ----- Method: ComplexTest>>testLn (in category 'tests') -----
> testLn
>        self assert: (Float e + 0 i) ln = Float e ln "See Bug 1815 on Mantis"!
>
> ----- Method: ComplexTest>>testNegated (in category 'tests') -----
> testNegated
>        "self run: #testNegated"
>        "self debug: #testNegated"
>
>        | c |
>        c := (2 + 5 i) .
>        self assert: c negated  = (-2 - 5i).
>        !
>
> ----- Method: ComplexTest>>testReciprocal (in category 'tests') -----
> testReciprocal
>        "self run: #testReciprocal"
>        "self debug: #testReciprocal"
>
>        | c |
>        c := (2 + 5 i).
>        self assert: c reciprocal  = ((2/29) - (5/29)i).
>        !
>
> ----- Method: ComplexTest>>testReciprocalError (in category 'tests') -----
> testReciprocalError
>        "self run: #testReciprocalError"
>        "self debug: #testReciprocalError"
>
>        | c |
>        c := (0 i).
>        self should: [c reciprocal] raise: ZeroDivide
>        !
>
> ----- Method: ComplexTest>>testSecureDivision1 (in category 'tests') -----
> testSecureDivision1
>        "self run: #testSecureDivision1"
>        "self debug: #testSecureDivision1"
>
>        | c1 c2 quotient |
>        c1 := 2.0e252 + 3.0e70 i.
>        c2 := c1.
>        quotient := c1 divideSecureBy: c2.
>        self assert: (quotient - 1) isZero.
>        !
>
> ----- Method: ComplexTest>>testSecureDivision2 (in category 'tests') -----
> testSecureDivision2
>        "self run: #testSecureDivision2"
>        "self debug: #testSecureDivision2"
>
>        | c1 c2 quotient |
>        c1 := 2.0e252 + 3.0e70 i.
>        c2 := c1.
>        quotient := c1 divideFastAndSecureBy: c2.
>        self assert: (quotient - 1) isZero.
>        !
>
> ----- Method: ComplexTest>>testSquared (in category 'tests') -----
> testSquared
>        "self run: #testSquared"
>        "self debug: #testSquared"
>
>        | c c2 |
>        c := (6 - 6 i).
>        c2 := (c squared).
>        self assert: c2 imaginary = -72.
>        self assert: c2 real = 0.!
>
> TestCase subclass: #DateAndTimeEpochTest
>        instanceVariableNames: 'aDateAndTime aDuration aTimeZone localTimeZoneToRestore'
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Chronology'!
>
> !DateAndTimeEpochTest commentStamp: 'tlk 1/6/2004 18:27' prior: 0!
> I represent one of several Sunit test Cases intentended to provide complete coverage  for the Chronology set of classes as part of the external testing. The other Chronology sunit test cases are:
>  DateTestCase
>  DateAndTimeLeapTestCase,
>  DurationTestCase,
>  ScheduleTestCase
>  TimeStampTestCase
>  TimespanDoTestCase,
>  TimespanDoSpanAYearTestCase,
>  TimespanTestCase,
>  YearMonthWeekTestCase.
> These tests attempt to exercise all public and private methods.  Except, they do not explicitly depreciated methods. tlk
> My fixtures are:
> aDateAndTime = January 01, 1901 midnight (the start of the Squeak epoch) with localTimeZone = Grenwhich Meridian (local offset = 0 hours)
> aDuration = 1 day, 2 hours, 3, minutes, 4 seconds and 5 nano seconds.
> aTimeZone =  'Epoch Test Time Zone', 'ETZ' , offset: 12 hours, 15 minutes. !
>
> ----- Method: DateAndTimeEpochTest>>setUp (in category 'running') -----
> setUp
>     localTimeZoneToRestore := DateAndTime localTimeZone.
>        aDateAndTime :=  DateAndTime localTimeZone: TimeZone default; epoch.
>        aTimeZone := TimeZone offset: (Duration minutes: 135) name: 'Epoch Test Time Zone' abbreviation: 'ETZ'.
>        aDuration := Duration days: 1 hours: 2 minutes: 3 seconds: 4 nanoSeconds: 5 !
>
> ----- Method: DateAndTimeEpochTest>>tearDown (in category 'running') -----
> tearDown
>     DateAndTime localTimeZone: localTimeZoneToRestore.
>     "wish I could remove the time zones I added earlier, tut there is no method for that"
> !
>
> ----- Method: DateAndTimeEpochTest>>testAsDate (in category 'testing') -----
> testAsDate
>        self assert: aDateAndTime asDate =   'January 1, 1901' asDate.
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testAsDateAndTime (in category 'testing') -----
> testAsDateAndTime
>        self assert: aDateAndTime asDateAndTime =  aDateAndTime
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testAsDuration (in category 'testing') -----
> testAsDuration
>        self assert: aDateAndTime asDuration =  0 asDuration
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testAsLocal (in category 'testing') -----
> testAsLocal
>        self assert: aDateAndTime asLocal =  aDateAndTime.
>        self assert: aDateAndTime asLocal = (aDateAndTime utcOffset: aDateAndTime class localOffset)
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testAsMonth (in category 'testing') -----
> testAsMonth
>        self assert: aDateAndTime asMonth = (Month month: 'January' year: 1901).
> !
>
> ----- Method: DateAndTimeEpochTest>>testAsNanoSeconds (in category 'testing') -----
> testAsNanoSeconds
>        self assert: aDateAndTime asNanoSeconds =  0 asDuration asNanoSeconds
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testAsSeconds (in category 'testing') -----
> testAsSeconds
>        self assert: aDateAndTime asSeconds =  0 asDuration asSeconds
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testAsTime (in category 'testing') -----
> testAsTime
>        self assert: aDateAndTime asTime =  Time midnight.
> !
>
> ----- Method: DateAndTimeEpochTest>>testAsTimeStamp (in category 'testing') -----
> testAsTimeStamp
>        self assert: aDateAndTime asTimeStamp =  TimeStamp new.
> !
>
> ----- Method: DateAndTimeEpochTest>>testAsUTC (in category 'testing') -----
> testAsUTC
>        self assert: aDateAndTime asUTC =  aDateAndTime
>          !
>
> ----- Method: DateAndTimeEpochTest>>testAsWeek (in category 'testing') -----
> testAsWeek
>        self assert: aDateAndTime asWeek = (Week starting: '12-31-1900' asDate).
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testAsYear (in category 'testing') -----
> testAsYear
>        self assert: aDateAndTime asYear =   (Year starting: '01-01-1901' asDate).
> !
>
> ----- Method: DateAndTimeEpochTest>>testCurrent (in category 'testing') -----
> testCurrent
>        self deny: aDateAndTime =  (DateAndTime current).
> !
>
> ----- Method: DateAndTimeEpochTest>>testDateTime (in category 'testing') -----
> testDateTime
>        self assert: aDateAndTime =  (DateAndTime date: '01-01-1901' asDate time: '00:00:00' asTime)
> !
>
> ----- Method: DateAndTimeEpochTest>>testDay (in category 'testing') -----
> testDay
>        self assert: aDateAndTime day =   DateAndTime new day
> !
>
> ----- Method: DateAndTimeEpochTest>>testDayMonthYearDo (in category 'testing') -----
> testDayMonthYearDo
>        |iterations|
>        iterations := 0.
>        self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear |  iterations := iterations + 1])  = 1.
>        self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear |  eachYear])  = 1901.
>        self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear |  eachMonth]) = 1.
>        self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear |  eachDay]) = 1.
> !
>
> ----- Method: DateAndTimeEpochTest>>testDayOfMonth (in category 'testing') -----
> testDayOfMonth
>        self assert: aDateAndTime dayOfMonth  = 1.
> !
>
> ----- Method: DateAndTimeEpochTest>>testDayOfWeek (in category 'testing') -----
> testDayOfWeek
>        self assert: aDateAndTime dayOfWeek  = 3.
>        self assert: aDateAndTime dayOfWeekAbbreviation = 'Tue'.
>        self assert: aDateAndTime dayOfWeekName = 'Tuesday'.
> !
>
> ----- Method: DateAndTimeEpochTest>>testDayOfYear (in category 'testing') -----
> testDayOfYear
>        self assert: aDateAndTime dayOfYear  = 1.
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testDaysInMonth (in category 'testing') -----
> testDaysInMonth
>        self assert: aDateAndTime daysInMonth  = 31.
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testDaysInYear (in category 'testing') -----
> testDaysInYear
>        self assert: aDateAndTime daysInYear  = 365.
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testDaysLeftInYear (in category 'testing') -----
> testDaysLeftInYear
>        self assert: aDateAndTime daysLeftInYear  = 364.
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testDuration (in category 'testing') -----
> testDuration
>        self assert: aDateAndTime duration  = 0 asDuration.
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testEpoch (in category 'testing') -----
> testEpoch
>        self assert: aDateAndTime =  '1901-01-01T00:00:00+00:00'.
> !
>
> ----- Method: DateAndTimeEpochTest>>testFirstDayOfMonth (in category 'testing') -----
> testFirstDayOfMonth
>        self assert: aDateAndTime firstDayOfMonth =   1
> !
>
> ----- Method: DateAndTimeEpochTest>>testFromSeconds (in category 'testing') -----
> testFromSeconds
>        self assert: aDateAndTime =  (DateAndTime fromSeconds: 0).
> !
>
> ----- Method: DateAndTimeEpochTest>>testFromString (in category 'testing') -----
> testFromString
>        self assert: aDateAndTime =  (DateAndTime fromString: ' 1901-01-01T00:00:00+00:00').
>        self assert: aDateAndTime =  (DateAndTime fromString: ' 1901-01-01T00:00:00').
>        self assert: aDateAndTime =  (DateAndTime fromString: ' 1901-01-01T00:00').
>        self assert: aDateAndTime =  (DateAndTime fromString: ' 1901-01-01T00:00:00+00:00').
> !
>
> ----- Method: DateAndTimeEpochTest>>testHash (in category 'testing') -----
> testHash
>        self assert: aDateAndTime hash = DateAndTime new hash!
>
> ----- Method: DateAndTimeEpochTest>>testHour (in category 'testing') -----
> testHour
>        self assert: aDateAndTime hour =    aDateAndTime hour24.
>        self assert: aDateAndTime hour =    0.
>        self assert: aDateAndTime hour =    aDateAndTime hours
> !
>
> ----- Method: DateAndTimeEpochTest>>testHour12 (in category 'testing') -----
> testHour12
>        self assert: aDateAndTime hour12  = DateAndTime new hour12.
>        self assert: aDateAndTime hour12  = 12
> !
>
> ----- Method: DateAndTimeEpochTest>>testIsLeapYear (in category 'testing') -----
> testIsLeapYear
>        self deny: aDateAndTime isLeapYear
> !
>
> ----- Method: DateAndTimeEpochTest>>testJulianDayNumber (in category 'testing') -----
> testJulianDayNumber
>        self assert: aDateAndTime =  (DateAndTime julianDayNumber: 2415386).
>        self assert: aDateAndTime julianDayNumber = 2415386.!
>
> ----- Method: DateAndTimeEpochTest>>testLessThan (in category 'testing') -----
> testLessThan
>        self assert: aDateAndTime  < (aDateAndTime + '1:00:00:00').
>        self assert: aDateAndTime + -1 < aDateAndTime.
>        !
>
> ----- Method: DateAndTimeEpochTest>>testMeridianAbbreviation (in category 'testing') -----
> testMeridianAbbreviation
>        self assert: aDateAndTime meridianAbbreviation = 'AM'.
>
>        !
>
> ----- Method: DateAndTimeEpochTest>>testMiddleOf (in category 'testing') -----
> testMiddleOf
>        self assert: (aDateAndTime middleOf: '2:00:00:00' asDuration) =
>         (Timespan starting: '12-31-1900' asDate duration: 2 days).
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testMidnight (in category 'testing') -----
> testMidnight
>        self assert: aDateAndTime midnight =  aDateAndTime
> !
>
> ----- Method: DateAndTimeEpochTest>>testMinus (in category 'testing') -----
> testMinus
>        self assert: aDateAndTime - aDateAndTime =  '0:00:00:00' asDuration.
>        self assert: aDateAndTime - '0:00:00:00' asDuration = aDateAndTime.
>        self assert: aDateAndTime - aDuration =  (DateAndTime year: 1900 month: 12 day: 30 hour: 21 minute: 56 second: 55 nanoSecond: 999999995 offset: 0 hours ).
>        " I believe this Failure is a bug in the nanosecond part of (DateAndTime >> year:month:day:hour:minute:second:nanoSecond:offset:)" !
>
> ----- Method: DateAndTimeEpochTest>>testMinute (in category 'testing') -----
> testMinute
>        self assert: aDateAndTime minute =  0
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testMinutes (in category 'testing') -----
> testMinutes
>        self assert: aDateAndTime minutes = 0
> !
>
> ----- Method: DateAndTimeEpochTest>>testMonth (in category 'testing') -----
> testMonth
>        self assert: aDateAndTime month  = 1.
>        self assert: aDateAndTime monthAbbreviation = 'Jan'.
>        self assert: aDateAndTime monthName = 'January'.
>        self assert: aDateAndTime monthIndex = 1.!
>
> ----- Method: DateAndTimeEpochTest>>testNanoSecond (in category 'testing') -----
> testNanoSecond
>        self assert: aDateAndTime nanoSecond =  0
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testNew (in category 'testing') -----
> testNew
>        self assert: aDateAndTime =  (DateAndTime new).
> !
>
> ----- Method: DateAndTimeEpochTest>>testNoon (in category 'testing') -----
> testNoon
>        self assert: aDateAndTime noon =  '1901-01-01T12:00:00+00:00'.
> !
>
> ----- Method: DateAndTimeEpochTest>>testNow (in category 'testing') -----
> testNow
>        self deny: aDateAndTime =  (DateAndTime now).
> !
>
> ----- Method: DateAndTimeEpochTest>>testOffset (in category 'testing') -----
> testOffset
>        self assert: aDateAndTime offset =  '0:00:00:00' asDuration.
>     self assert: (aDateAndTime offset: '0:12:00:00') =  '1901-01-01T00:00:00+12:00'.
> !
>
> ----- Method: DateAndTimeEpochTest>>testPlus (in category 'testing') -----
> testPlus
>        self assert: aDateAndTime + '0:00:00:00' = aDateAndTime.
>        self assert: aDateAndTime + 0 = aDateAndTime.
>        self assert: aDateAndTime + aDuration = (DateAndTime year: 1901 month: 1 day: 2 hour: 2 minute: 3 second: 4 nanoSecond: 5 offset: 0 hours )
>        " I believe this is a bug in the nanosecond part of (DateAndTime >> year:month:day:hour:minute:second:nanoSecond:offset:)"
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testPrintOn (in category 'testing') -----
> testPrintOn
>        | cs rw |
>        cs := '1901-01-01T00:00:00+00:00' readStream.
>        rw := ReadWriteStream on: ''.
>        aDateAndTime printOn: rw.
>        self assert: rw contents = cs contents.
>        cs := 'a TimeZone(ETZ)' readStream.
>        rw := ReadWriteStream on: ''.
>        aTimeZone printOn: rw.
>        self assert: rw contents = cs contents!
>
> ----- Method: DateAndTimeEpochTest>>testSecond (in category 'testing') -----
> testSecond
>        self assert: aDateAndTime second =  0
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testSeconds (in category 'testing') -----
> testSeconds
>        self assert: aDateAndTime seconds =  0
>
> !
>
> ----- Method: DateAndTimeEpochTest>>testTicks (in category 'testing') -----
> testTicks
>        self assert: aDateAndTime ticks =  (DateAndTime julianDayNumber: 2415386) ticks.
>        self assert: aDateAndTime ticks = #(2415386 0 0)!
>
> ----- Method: DateAndTimeEpochTest>>testTicksOffset (in category 'testing') -----
> testTicksOffset
>        self assert: aDateAndTime =  (aDateAndTime ticks:  #(2415386 0 0) offset: DateAndTime localOffset).
> !
>
> ----- Method: DateAndTimeEpochTest>>testTo (in category 'testing') -----
> testTo
>        self assert: (aDateAndTime to: aDateAndTime) = (DateAndTime new to: DateAndTime new)
>        "MessageNotUnderstood: UndefinedObject>>starting:ending:  where UndefinedObject is Timespan "!
>
> ----- Method: DateAndTimeEpochTest>>testToBy (in category 'testing') -----
> testToBy
>        self assert: (aDateAndTime to: aDateAndTime + 10 days by: 5 days) =
>                                (DateAndTime new to: DateAndTime new + 10 days by: 5 days )
>        "MessageNotUnderstood: UndefinedObject>>starting:ending:  where UndefinedObject is Timespan "!
>
> ----- Method: DateAndTimeEpochTest>>testToByDo (in category 'testing') -----
> testToByDo
>        "self assert: (aDateAndTime to: aDateAndTime + 10 days by: 5 days do: []) =  "
>        "MessageNotUnderstood: UndefinedObject>>starting:ending:  where UndefinedObject is Timespan "!
>
> ----- Method: DateAndTimeEpochTest>>testToday (in category 'testing') -----
> testToday
>        self deny: aDateAndTime =  (DateAndTime today).
> !
>
> ----- Method: DateAndTimeEpochTest>>testTommorrow (in category 'testing') -----
> testTommorrow
>        self assert: (DateAndTime today + 24 hours) =  (DateAndTime tomorrow).
>        self deny: aDateAndTime =  (DateAndTime tomorrow).
>     "MessageNotUnderstood: Date class>>starting:"!
>
> ----- Method: DateAndTimeEpochTest>>testUtcOffset (in category 'testing') -----
> testUtcOffset
>     self assert: (aDateAndTime utcOffset: '0:12:00:00') =  '1901-01-01T12:00:00+12:00'.
> !
>
> ----- Method: DateAndTimeEpochTest>>testYear (in category 'testing') -----
> testYear
>        self assert: aDateAndTime year = 1901.
>
>        !
>
> ----- Method: DateAndTimeEpochTest>>testYearDay (in category 'testing') -----
> testYearDay
>        self assert: aDateAndTime =  (DateAndTime year: 1901 day: 1).
> !
>
> ----- Method: DateAndTimeEpochTest>>testYearDayHourMinuteSecond (in category 'testing') -----
> testYearDayHourMinuteSecond
>        self assert: aDateAndTime =  (DateAndTime year: 1901 day: 1 hour: 0 minute: 0 second: 0).
> !
>
> ----- Method: DateAndTimeEpochTest>>testYearMonthDay (in category 'testing') -----
> testYearMonthDay
>        self assert: aDateAndTime =  (DateAndTime year: 1901 month: 1 day: 1).
> !
>
> ----- Method: DateAndTimeEpochTest>>testYearMonthDayHourMinuteSecond (in category 'testing') -----
> testYearMonthDayHourMinuteSecond
>        self assert: aDateAndTime =  (DateAndTime year: 1901 month: 1 day: 1 hour: 0 minute: 0 second: 0).
> !
>
> ----- Method: DateAndTimeEpochTest>>testYearMonthDayHourMinuteSecondNanosSecondOffset (in category 'testing') -----
> testYearMonthDayHourMinuteSecondNanosSecondOffset
>        self assert: aDateAndTime =  (DateAndTime year: 1901 month: 1 day: 1 hour: 0 minute: 0 second: 0 nanoSecond: 0 offset:0 hours ).
>        self assert: ((DateAndTime year: 1 month: 1 day: 1 hour: 0 minute: 0 second: 0 nanoSecond: 0 offset: 0 hours ) +
>                                (Duration days: 1 hours: 2 minutes: 3 seconds: 4  nanoSeconds: 5) ) =
>                                (DateAndTime year: 1 month: 1 day: 2 hour: 2 minute: 3 second: 4 nanoSecond: 5 offset: 0 hours )
>        " I believe this is a bug in the nanosecond part of (DateAndTime >> year:month:day:hour:minute:second:nanoSecond:offset:)"" I believe this is a bug in the nanosecond part of (DateAndTime >> year:month:day:hour:minute:second:nanoSecond:offset:)"
> !
>
> ----- Method: DateAndTimeEpochTest>>testYesterday (in category 'testing') -----
> testYesterday
>        self deny: aDateAndTime =  (DateAndTime yesterday).
> !
>
> ----- Method: DateAndTimeEpochTest>>testtimeZone (in category 'testing') -----
> testtimeZone
>        self assert: aDateAndTime timeZoneName  = 'Universal Time'.
>        self assert: aDateAndTime timeZoneAbbreviation  =  'UTC'
>
> !
>
> TestCase subclass: #DateAndTimeLeapTest
>        instanceVariableNames: 'aDateAndTime aDuration aTimeZone localTimeZoneToRestore'
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Chronology'!
>
> !DateAndTimeLeapTest commentStamp: 'tlk 1/6/2004 17:54' prior: 0!
> I represent one of several Sunit test Cases intentended to provide complete coverage for the Chronology set of classes as part of the external testing. tlk.
> My fixtures are:
> aDateAndTime = February 29, 2004 1:33 PM with offset: 2 hours
> aDuration = 15 days, 14 hours, 13 minutes, 12 seconds and 11 nano seconds.
> aTimeZone =  Grenwhich Meridian (local offset = 0 hours) !
>
> ----- Method: DateAndTimeLeapTest>>setUp (in category 'running') -----
> setUp
>        localTimeZoneToRestore := DateAndTime localTimeZone.
>        DateAndTime localTimeZone: TimeZone default.
>        aDateAndTime := (DateAndTime year: 2004 month: 2 day: 29 hour: 13 minute: 33 second: 0 offset: 2 hours).
>        aTimeZone := TimeZone default.
>        aDuration := Duration days: 0 hours: 13 minutes: 33 seconds: 0 nanoSeconds: 0
> !
>
> ----- Method: DateAndTimeLeapTest>>tearDown (in category 'running') -----
> tearDown
>     DateAndTime localTimeZone: localTimeZoneToRestore.
>     "wish I could remove the time zones I added earlier, tut there is no method for that"
> !
>
> ----- Method: DateAndTimeLeapTest>>testAsDate (in category 'testing') -----
> testAsDate
>        self assert: aDateAndTime asDate =   'February 29, 2004' asDate.
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testAsDuration (in category 'testing') -----
> testAsDuration
>        self assert: aDateAndTime asDuration =  aDuration
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testAsLocal (in category 'testing') -----
> testAsLocal
>        self assert: aDateAndTime asLocal =  aDateAndTime.
>        self assert: aDateAndTime asLocal = (aDateAndTime utcOffset: aDateAndTime class localOffset)
>
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testAsMonth (in category 'testing') -----
> testAsMonth
>        self assert: aDateAndTime asMonth = (Month month: 'February' year: 2004).
> !
>
> ----- Method: DateAndTimeLeapTest>>testAsNanoSeconds (in category 'testing') -----
> testAsNanoSeconds
>        self assert: aDateAndTime asNanoSeconds =  aDuration asNanoSeconds.
>        self assert: aDateAndTime asNanoSeconds = 48780000000000
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testAsSeconds (in category 'testing') -----
> testAsSeconds
>        self assert: aDuration asSeconds =  48780.
>        self assert: aDateAndTime asSeconds =  3255507180
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testAsTime (in category 'testing') -----
> testAsTime
>        self assert: aDateAndTime asTime = (Time hour: 13 minute: 33 second: 0)
> !
>
> ----- Method: DateAndTimeLeapTest>>testAsTimeStamp (in category 'testing') -----
> testAsTimeStamp
>        self assert: aDateAndTime asTimeStamp =  ((TimeStamp readFrom: '2-29-2004 1:33 pm' readStream) offset: 2 hours).
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testAsUTC (in category 'testing') -----
> testAsUTC
>        self assert: aDateAndTime asUTC =  aDateAndTime
>
>          !
>
> ----- Method: DateAndTimeLeapTest>>testAsWeek (in category 'testing') -----
> testAsWeek
>        self assert: aDateAndTime asWeek =    (Week starting: '02-29-2004' asDate).
> !
>
> ----- Method: DateAndTimeLeapTest>>testAsYear (in category 'testing') -----
> testAsYear
>        self assert: aDateAndTime asYear =   (Year starting: '02-29-2004' asDate).
>        self deny: aDateAndTime asYear =   (Year starting: '01-01-2004' asDate)
> !
>
> ----- Method: DateAndTimeLeapTest>>testDay (in category 'testing') -----
> testDay
>        self assert: aDateAndTime day =   60.
>        self deny: aDateAndTime day =   29 !
>
> ----- Method: DateAndTimeLeapTest>>testDayMonthYearDo (in category 'testing') -----
> testDayMonthYearDo
>        self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear |  eachYear])  = 2004.
>        self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear |  eachMonth]) = 2.
>        self assert: (aDateAndTime dayMonthYearDo: [:eachDay :eachMonth :eachYear |  eachDay]) = 29.
> !
>
> ----- Method: DateAndTimeLeapTest>>testDayOfMonth (in category 'testing') -----
> testDayOfMonth
>        self assert: aDateAndTime dayOfMonth  = 29.
> !
>
> ----- Method: DateAndTimeLeapTest>>testDayOfWeek (in category 'testing') -----
> testDayOfWeek
>        self assert: aDateAndTime dayOfWeek  = 1.
>        self assert: aDateAndTime dayOfWeekAbbreviation = 'Sun'.
>        self assert: aDateAndTime dayOfWeekName = 'Sunday'.
> !
>
> ----- Method: DateAndTimeLeapTest>>testDayOfYear (in category 'testing') -----
> testDayOfYear
>        self assert: aDateAndTime dayOfYear  = 60.
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testDaysInMonth (in category 'testing') -----
> testDaysInMonth
>        self assert: aDateAndTime daysInMonth  = 29.
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testDaysInYear (in category 'testing') -----
> testDaysInYear
>        self assert: aDateAndTime daysInYear  = 366.
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testDaysLeftInYear (in category 'testing') -----
> testDaysLeftInYear
>        self assert: aDateAndTime daysLeftInYear  = 306.
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testFirstDayOfMonth (in category 'testing') -----
> testFirstDayOfMonth
>        self deny: aDateAndTime firstDayOfMonth =  1.
>        self assert: aDateAndTime firstDayOfMonth = 32
> !
>
> ----- Method: DateAndTimeLeapTest>>testFromString (in category 'testing') -----
> testFromString
>        self assert: aDateAndTime =  (DateAndTime fromString: ' 2004-02-29T13:33:00+02:00').
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testHour (in category 'testing') -----
> testHour
>        self assert: aDateAndTime hour =    aDateAndTime hour24.
>        self assert: aDateAndTime hour =    13.
>        self assert: aDateAndTime hour =    aDateAndTime hours
> !
>
> ----- Method: DateAndTimeLeapTest>>testHour12 (in category 'testing') -----
> testHour12
>        self assert: aDateAndTime hour12  =   1.
> !
>
> ----- Method: DateAndTimeLeapTest>>testIsLeapYear (in category 'testing') -----
> testIsLeapYear
>        self assert: aDateAndTime isLeapYear
> !
>
> ----- Method: DateAndTimeLeapTest>>testLessThan (in category 'testing') -----
> testLessThan
>        self assert: aDateAndTime  < (aDateAndTime + '1:00:00:00').
>        self assert: aDateAndTime + -1 < aDateAndTime.
>        !
>
> ----- Method: DateAndTimeLeapTest>>testMeridianAbbreviation (in category 'testing') -----
> testMeridianAbbreviation
>        self assert: aDateAndTime meridianAbbreviation = 'PM'.
>
>        !
>
> ----- Method: DateAndTimeLeapTest>>testMiddleOf (in category 'testing') -----
> testMiddleOf
>        self assert: (aDateAndTime middleOf: aDuration)  =
>         (Timespan starting: (DateAndTime year: 2004 month: 2 day: 29 hour: 6 minute: 46 second: 30 offset: 2 hours)
>        duration: (Duration days: 0 hours: 13 minutes: 33 seconds: 0 nanoSeconds: 0 ))
>        !
>
> ----- Method: DateAndTimeLeapTest>>testMidnight (in category 'testing') -----
> testMidnight
>        self assert: aDateAndTime midnight =  '2004-02-29T00:00:00+00:00'.
>        self deny: aDateAndTime midnight =  '2004-02-29T00:00:00+02:00'
> !
>
> ----- Method: DateAndTimeLeapTest>>testMinute (in category 'testing') -----
> testMinute
>        self assert: aDateAndTime minute =  33
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testMinutes (in category 'testing') -----
> testMinutes
>        self assert: aDateAndTime minutes = 33
> !
>
> ----- Method: DateAndTimeLeapTest>>testMonth (in category 'testing') -----
> testMonth
>        self assert: aDateAndTime month  = 2.
>        self assert: aDateAndTime monthAbbreviation = 'Feb'.
>        self assert: aDateAndTime monthName = 'February'.
>        self assert: aDateAndTime monthIndex = 2.!
>
> ----- Method: DateAndTimeLeapTest>>testNanoSecond (in category 'testing') -----
> testNanoSecond
>        self assert: aDateAndTime nanoSecond =  0
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testNoon (in category 'testing') -----
> testNoon
>        self assert: aDateAndTime noon =  '2004-02-29T12:00:00+00:00'.
> !
>
> ----- Method: DateAndTimeLeapTest>>testOffset (in category 'testing') -----
> testOffset
>        self assert: aDateAndTime offset =  '0:02:00:00' asDuration.
>     self assert: (aDateAndTime offset: '0:12:00:00') =  '2004-02-29T13:33:00+12:00'.
> !
>
> ----- Method: DateAndTimeLeapTest>>testPrintOn (in category 'testing') -----
> testPrintOn
>        | cs rw |
>        cs := '2004-02-29T13:33:00+02:00' readStream.
>        rw := ReadWriteStream on: ''.
>        aDateAndTime printOn: rw.
>        self assert: rw contents = cs contents.
>        cs := 'a TimeZone(UTC)' readStream.
>        rw := ReadWriteStream on: ''.
>        aTimeZone printOn: rw.
>        self assert: rw contents = cs contents!
>
> ----- Method: DateAndTimeLeapTest>>testSecond (in category 'testing') -----
> testSecond
>        self assert: aDateAndTime second =  0
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testSeconds (in category 'testing') -----
> testSeconds
>        self assert: aDateAndTime seconds =  0
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testTicks (in category 'testing') -----
> testTicks
>        self assert: aDateAndTime ticks =  ((DateAndTime julianDayNumber: 2453065) + 48780 seconds) ticks.
>        self assert: aDateAndTime ticks =  #(2453065 48780 0)!
>
> ----- Method: DateAndTimeLeapTest>>testTicksOffset (in category 'testing') -----
> testTicksOffset
>        self assert: aDateAndTime =  (aDateAndTime ticks:  #(2453065 48780 0) offset: DateAndTime localOffset).
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testUtcOffset (in category 'testing') -----
> testUtcOffset
>     self assert: (aDateAndTime utcOffset: '0:02:00:00') =  '2004-02-29T13:33:00+02:00'.
>
> !
>
> ----- Method: DateAndTimeLeapTest>>testYear (in category 'testing') -----
> testYear
>        self assert: aDateAndTime year = 2004.
>
>        !
>
> ----- Method: DateAndTimeLeapTest>>testYearDayHourMinuteSecond (in category 'testing') -----
> testYearDayHourMinuteSecond
>        self assert: aDateAndTime =  ((DateAndTime year: 2004 day: 60 hour: 13 minute: 33 second: 0) offset: 2 hours).
> !
>
> ----- Method: DateAndTimeLeapTest>>testYearMonthDayHourMinuteSecond (in category 'testing') -----
> testYearMonthDayHourMinuteSecond
>        self assert: aDateAndTime =  ((DateAndTime year: 2004 month: 2 day: 29 hour: 13 minute: 33 second: 0) offset: 2 hours).
> !
>
> ----- Method: DateAndTimeLeapTest>>testtimeZone (in category 'testing') -----
> testtimeZone
>        self assert: aDateAndTime timeZoneName  = 'Universal Time'.
>        self assert: aDateAndTime timeZoneAbbreviation  =  'UTC'
>
> !
>
> TestCase subclass: #DelayTest
>        instanceVariableNames: ''
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Processes'!
>
> ----- Method: DelayTest>>testBounds (in category 'testing') -----
> testBounds
>        "self run: #testBounds"
>
>        self should: [Delay forMilliseconds: -1] raise: Error.
>        self should: [Delay forMilliseconds: SmallInteger maxVal // 2 + 1] raise: Error. "Not longer than a day"
>        self shouldnt: [Delay forMilliseconds: SmallInteger maxVal // 2] raise: Error.
>        self shouldnt: [(Delay forMilliseconds: Float pi) wait] raise: Error. "Wait 3ms"
> !
>
> ----- Method: DelayTest>>testSemaphore (in category 'testing') -----
> testSemaphore
>        "When we provide our own semaphore for a Delay, it should be used"
>        "See http://bugs.squeak.org/view.php?id=6834"
>
>        "self run: #testSemaphore"
>
>        | sem process |
>        sem := Semaphore new.
>        [
>                process := [Delay timeoutSemaphore: sem afterMSecs: 0. sem wait] newProcess.
>                process priority: Processor highIOPriority.
>                process resume.
>                self assert: process isTerminated.
>        ] ensure: [sem signal]!
>
> TestCase subclass: #IVsAndClassVarNamesConflictTest
>        instanceVariableNames: 'class className'
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Classes'!
>
> ----- Method: IVsAndClassVarNamesConflictTest>>setUp (in category 'setup') -----
> setUp
>        super setUp.
>        className := #ClassForTestToBeDeleted.
>        class := Object subclass: className
>                instanceVariableNames: ''
>                classVariableNames: ''
>                poolDictionaries: ''
>                category: self class category!
>
> ----- Method: IVsAndClassVarNamesConflictTest>>tearDown (in category 'setup') -----
> tearDown
>        super tearDown.
>        class ifNil:[^self].
>        class isObsolete ifFalse: [
>                class removeFromChanges.
>                class removeFromSystemUnlogged].
>        ChangeSet current
>                        removeClassChanges: className;
>                        removeClassChanges: className, ' class'!
>
> ----- Method: IVsAndClassVarNamesConflictTest>>testClassWithInvalidClassVariablesShouldNotBeReferencedByItsSuperclass (in category 'tests') -----
> testClassWithInvalidClassVariablesShouldNotBeReferencedByItsSuperclass
>        | initialSubclasses |
>        initialSubclasses := Object subclasses.
>        self should: [Object subclass: className
>                instanceVariableNames: 'a b c'
>                classVariableNames: 'a b c'
>                poolDictionaries: ''
>                category: self class category]
>                raise: Exception.
>        self assert: initialSubclasses = Object subclasses
> !
>
> ----- Method: IVsAndClassVarNamesConflictTest>>testIvNamesAndClassVarNamesShouldBeDifferent (in category 'tests') -----
> testIvNamesAndClassVarNamesShouldBeDifferent
>        self should: [Object subclass: className
>                instanceVariableNames: 'a b c'
>                classVariableNames: 'a b c'
>                poolDictionaries: ''
>                category: self class category]
>                raise: Exception.
>        self should: [Object subclass: className
>                instanceVariableNames: 'A B C'
>                classVariableNames: 'A B C'
>                poolDictionaries: ''
>                category: self class category]
>                raise: Exception.
> !
>
> TestCase subclass: #InstVarRefLocatorTest
>        instanceVariableNames: 'tt'
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Methods'!
>
> !InstVarRefLocatorTest commentStamp: '<historical>' prior: 0!
> This is the unit test for the class InstVarRefLocator. Unit tests are a good way to exercise the functionality of your system in a repeatable and automatic manner. They are therefore recommended if you plan to release anything. For more information, see:
>        - http://www.c2.com/cgi/wiki?UnitTest
>        - http://minnow.cc.gatech.edu/squeak/1547
>        - the sunit class category!
>
> ----- Method: InstVarRefLocatorTest>>example1 (in category 'examples') -----
> example1
>        | ff |
>        (1 < 2) ifTrue: [tt ifNotNil: [ff := 'hallo']].
>        ^ ff.!
>
> ----- Method: InstVarRefLocatorTest>>example2 (in category 'examples') -----
> example2
>        | ff|
>        ff := 1.
>        (1 < 2) ifTrue: [ff ifNotNil: [ff := 'hallo']].
>        ^ ff.!
>
> ----- Method: InstVarRefLocatorTest>>hasInstVarRef: (in category 'private') -----
> hasInstVarRef: aMethod
>        "Answer whether the receiver references an instance variable."
>
>        | scanner end printer |
>
>        scanner := InstructionStream on: aMethod.
>        printer := InstVarRefLocator new.
>        end := scanner method endPC.
>
>        [scanner pc <= end] whileTrue: [
>                (printer interpretNextInstructionUsing: scanner) ifTrue: [^true].
>        ].
>        ^false!
>
> ----- Method: InstVarRefLocatorTest>>testExample1 (in category 'tests') -----
> testExample1
>        | method |
>
>        method := self class compiledMethodAt: #example1.
>        self assert: (self hasInstVarRef: method).!
>
> ----- Method: InstVarRefLocatorTest>>testExample2 (in category 'tests') -----
> testExample2
>        | method |
>
>        method := self class compiledMethodAt: #example2.
>        self deny: (self hasInstVarRef: method).!
>
> ----- Method: InstVarRefLocatorTest>>testInstructions (in category 'tests') -----
> testInstructions
>
>        | scanner end printer |
>
>        Object methods do: [:method |
>                scanner := InstructionStream on: method.
>                printer := InstVarRefLocator new.
>                end := scanner method endPC.
>
>                [scanner pc <= end] whileTrue: [
>                        self shouldnt: [printer interpretNextInstructionUsing: scanner] raise: Error.
>                ].
>        ].!
>
> TestCase subclass: #InstructionClientTest
>        instanceVariableNames: ''
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Methods'!
>
> !InstructionClientTest commentStamp: '<historical>' prior: 0!
> This is the unit test for the class InstructionClient. Unit tests are a good way to exercise the functionality of your system in a repeatable and automatic manner. They are therefore recommended if you plan to release anything. For more information, see:
>        - http://www.c2.com/cgi/wiki?UnitTest
>        - http://minnow.cc.gatech.edu/squeak/1547
>        - the sunit class category!
>
> ----- Method: InstructionClientTest>>testInstructions (in category 'tests') -----
> testInstructions
>        "just interpret all of methods of Object"
>
>        | client scanner|
>
>        client := InstructionClient new.
>
>        Object methods do: [:method |
>                        scanner := (InstructionStream on: method).
>                        [scanner pc <= method endPC] whileTrue: [
>                                        self shouldnt: [scanner interpretNextInstructionFor: client] raise: Error.
>                        ].
>        ].
> !
>
> TestCase subclass: #IntegerDigitLogicTest
>        instanceVariableNames: ''
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Numbers'!
>
> ----- Method: IntegerDigitLogicTest>>testAndSingleBitWithMinusOne (in category 'tests') -----
> testAndSingleBitWithMinusOne
>        "And a single bit with -1 and test for same value"
>        1 to: 100 do: [:i | self assert: ((1 bitShift: i) bitAnd: -1) = (1 bitShift: i)].!
>
> ----- Method: IntegerDigitLogicTest>>testMixedSignDigitLogic (in category 'tests') -----
> testMixedSignDigitLogic
>        "Verify that mixed sign logic with large integers works."
>        self assert: (-2 bitAnd: 16rFFFFFFFF) = 16rFFFFFFFE!
>
> ----- Method: IntegerDigitLogicTest>>testNBitAndNNegatedEqualsN (in category 'tests') -----
> testNBitAndNNegatedEqualsN
>        "Verify that (n bitAnd: n negated) = n for single bits"
>        | n |
>        1 to: 100 do: [:i | n := 1 bitShift: i.
>                                self assert: (n bitAnd: n negated) = n]!
>
> ----- Method: IntegerDigitLogicTest>>testNNegatedEqualsNComplementedPlusOne (in category 'tests') -----
> testNNegatedEqualsNComplementedPlusOne
>        "Verify that n negated = (n complemented + 1) for single bits"
>        | n |
>        1 to: 100 do: [:i | n := 1 bitShift: i.
>                                self assert: n negated = ((n bitXor: -1) + 1)]!
>
> ----- Method: IntegerDigitLogicTest>>testShiftMinusOne1LeftThenRight (in category 'tests') -----
> testShiftMinusOne1LeftThenRight
>        "Shift -1 left then right and test for 1"
>        1 to: 100 do: [:i | self assert: ((-1 bitShift: i) bitShift: i negated) = -1].
> !
>
> ----- Method: IntegerDigitLogicTest>>testShiftOneLeftThenRight (in category 'tests') -----
> testShiftOneLeftThenRight
>        "Shift 1 bit left then right and test for 1"
>        1 to: 100 do: [:i | self assert: ((1 bitShift: i) bitShift: i negated) = 1].
> !
>
> TestCase subclass: #IntegerTest
>        instanceVariableNames: ''
>        classVariableNames: ''
>        poolDictionaries: ''
>        category: 'KernelTests-Numbers'!
>
> ----- Method: IntegerTest>>testBadBase (in category 'tests - printing') -----
> testBadBase
>        "This used to get into an endless loop.
>        See Pharo #114"
>
>        self should: [2 printStringBase: 1] raise: Error.!
>
> ----- Method: IntegerTest>>testBenchFib (in category 'tests - benchmarks') -----
> testBenchFib
>
>        self assert: (0 benchFib = 1).
>        self assert: (1 benchFib = 1).
>        self assert: (2 benchFib = 3).
>        !
>
> ----- Method: IntegerTest>>testBitLogic (in category 'tests - bitLogic') -----
> testBitLogic
>        "This little suite of tests is designed to verify correct operation of most
>        of Squeak's bit manipulation code, including two's complement
>        representation of negative values.  It was written in a hurry and
>        is probably lacking several important checks."
>
>        "Shift 1 bit left then right and test for 1"
>        "self run: #testBitLogic"
>        | n |
>        1 to: 100 do: [:i | self assert: ((1 bitShift: i) bitShift: i negated) = 1].
>
>        "Shift -1 left then right and test for 1"
>        1 to: 100 do: [:i | self assert: ((-1 bitShift: i) bitShift: i negated) = -1].
>
>        "And a single bit with -1 and test for same value"
>        1 to: 100 do: [:i | self assert: ((1 bitShift: i) bitAnd: -1) = (1 bitShift: i)].
>
>        "Verify that (n bitAnd: n negated) = n for single bits"
>        1 to: 100 do: [:i |  n := 1 bitShift: i. self assert: (n bitAnd: n negated) = n].
>
>        "Verify that n negated = (n complemented + 1) for single bits"
>        1 to: 100 do: [:i |
>                                        n := 1 bitShift: i.
>                                        self assert: n negated = ((n bitXor: -1) + 1)].
>
>        "Verify that (n + n complemented) = -1 for single bits"
>        1 to: 100 do: [:i |
>                                        n := 1 bitShift: i.
>                                        self assert: (n + (n bitXor: -1)) = -1].
>
>        "Verify that n negated = (n complemented +1) for single bits"
>        1 to: 100 do: [:i |
>                                        n := 1 bitShift: i.
>                                        self assert: n negated = ((n bitXor: -1) + 1)].
>
>        self assert: (-2 bitAnd: 16rFFFFFFFF) = 16rFFFFFFFE.!
>
> ----- Method: IntegerTest>>testCreationFromBytes1 (in category 'tests - instance creation') -----
> testCreationFromBytes1
>        "self run: #testCreationFromBytes1"
>        "it is illegal for a LargeInteger to be less than SmallInteger maxVal."
>        "here we test that Integer>>byte!!byte2:byte3:byte4: resconstructs SmallInteger maxVal as an instance of SmallInteger. "
>
>        | maxSmallInt hexString byte1 byte2 byte3 byte4
>        builtInteger |
>        maxSmallInt := SmallInteger maxVal.
>        hexString := maxSmallInt printStringHex.
>        self assert: hexString size = 8.
>        byte4 := Number readFrom: (hexString copyFrom: 1 to: 2) base: 16.
>        byte3 := Number readFrom: (hexString copyFrom: 3 to: 4) base: 16.
>        byte2 := Number readFrom: (hexString copyFrom: 5 to: 6) base: 16.
>        byte1 := Number readFrom: (hexString copyFrom: 7 to: 8) base: 16.
>        builtInteger := Integer byte1: byte1 byte2: byte2 byte3: byte3 byte4: byte4.
>        self assert: builtInteger = maxSmallInt.
>        self assert: builtInteger class = SmallInteger
> !
>
> ----- Method: IntegerTest>>testCreationFromBytes2 (in category 'tests - instance creation') -----
> testCreationFromBytes2
>        "self run: #testCreationFromBytes2"
>
>        "it is illegal for a LargeInteger to be less than SmallInteger maxVal."
>        "here we test that Integer>>byte!!byte2:byte3:byte4: resconstructs (SmallInteger maxVal + 1) as an instance of LargePositiveInteger. "
>        | maxSmallInt hexString byte1 byte2 byte3 byte4 builtInteger |
>        maxSmallInt := SmallInteger maxVal.
>        hexString := (maxSmallInt + 1) printStringHex.
>        self assert: hexString size = 8.
>        byte4 := Number readFrom: (hexString copyFrom: 1 to: 2) base: 16.
>        byte3 := Number readFrom: (hexString copyFrom: 3 to: 4) base: 16.
>        byte2 := Number readFrom: (hexString copyFrom: 5 to: 6) base: 16.
>        byte1 := Number readFrom: (hexString copyFrom: 7 to: 8) base: 16.
>        builtInteger := Integer byte1: byte1 byte2: byte2 byte3: byte3 byte4: byte4.
>        self assert: builtInteger = (maxSmallInt + 1).
>        self deny: builtInteger class = SmallInteger
> !
>
> ----- Method: IntegerTest>>testCreationFromBytes3 (in category 'tests - instance creation') -----
> testCreationFromBytes3
>        "self run: #testCreationFromBytes3"
>
>        "it is illegal for a LargeInteger to be less than SmallInteger maxVal."
>        "here we test that Integer>>byte!!byte2:byte3:byte4: resconstructs (SmallInteger maxVal - 1) as an instance of SmallInteger. "
>        | maxSmallInt hexString byte1 byte2 byte3 byte4
>    builtInteger |
>        maxSmallInt := SmallInteger maxVal.
>        hexString := (maxSmallInt - 1) printStringHex.
>        self assert: hexString size = 8.
>        byte4 := Number readFrom: (hexString copyFrom: 1 to: 2) base: 16.
>        byte3 := Number readFrom: (hexString copyFrom: 3 to: 4) base: 16.
>        byte2 := Number readFrom: (hexString copyFrom: 5 to: 6) base: 16.
>        byte1 := Number readFrom: (hexString copyFrom: 7 to: 8) base: 16.
>        builtInteger := Integer byte1: byte1 byte2: byte2 byte3: byte3 byte4: byte4.
>        self assert: builtInteger = (maxSmallInt - 1).
>        self assert: builtInteger class = SmallInteger
> !
>
> ----- Method: IntegerTest>>testCrossSumBase (in category 'testing - arithmetic') -----
> testCrossSumBase
>        "self run: #testCrossSumBase"
>
>        self assert: (
>                ((-20 to: 20) collect: [:each | each crossSumBase: 10]) asArray =
>                #(2 10 9 8 7 6 5 4 3 2 1 9 8 7 6 5 4 3 2 1 0 1 2 3 4 5 6 7 8 9 1 2 3 4 5 6 7 8 9 10 2)).
>        self assert: (
>                ((-20 to: 20) collect: [:each | each crossSumBase: 2]) asArray =
>                #(2 3 2 2 1 4 3 3 2 3 2 2 1 3 2 2 1 2 1 1 0 1 1 2 1 2 2 3 1 2 2 3 2 3 3 4 1 2 2 3 2)).
>        self should: [10 crossSumBase: 1] raise: AssertionFailure!
>
> ----- Method: IntegerTest>>testDegreeCos (in category 'tests - basic') -----
> testDegreeCos
>        "self run: #testDegreeCos"
>
>        self shouldnt: [ 45 degreeCos] raise: Error.
>        self assert: 45  degreeCos printString =  (2 sqrt / 2) asFloat printString !
>
> ----- Method: IntegerTest>>testDifferentBases (in category 'tests - instance creation') -----
> testDifferentBases
>        "self run: #testDifferentBases"
>        "| value |
>        2 to: 36 do: [:each|
>                value := 0.
>                1 to: each-1 do: [:n| value := value + (n * (each raisedToInteger: n))].
>                value := value negated.
>                Transcript tab; show: 'self assert: (', value printString, ' printStringBase: ', each printString, ') = ''', (value printStringBase: each), '''.'; cr.
>                Transcript tab; show: 'self assert: (', value printString, ' radix: ', each printString, ') = ''', (value radix: each), '''.'; cr.
>                Transcript tab; show: 'self assert: ', value printString, ' printStringHex = ''', (value printStringBase: 16), '''.'; cr.
>                Transcript tab; show: 'self assert: (', value printString, ' storeStringBase: ', each printString, ') = ''', (value storeStringBase: each), '''.'; cr.
>                Transcript tab; show: 'self assert: ', value printString, ' storeStringHex = ''', (value storeStringBase: 16), '''.'; cr.
>
>
> ].
>        "
>
>        self assert: 2r10 = 2.
>        self assert: 3r210 = 21.
>        self assert: 4r3210 = 228.
>        self assert: 5r43210 = 2930.
>        self assert: 6r543210 = 44790.
>        self assert: 7r6543210 = 800667.
>        self assert: 8r76543210 = 16434824.
>        self assert: 9r876543210 = 381367044.
>        self assert: 10r9876543210 = 9876543210.
>        self assert: 11rA9876543210 = 282458553905.
>        self assert: 12rBA9876543210 = 8842413667692.
>        self assert: 13rCBA9876543210 = 300771807240918.
>        self assert: 14rDCBA9876543210 = 11046255305880158.
>        self assert: 15rEDCBA9876543210 = 435659737878916215.
>        self assert: 16rFEDCBA9876543210 = 18364758544493064720.
>        self assert: 17rGFEDCBA9876543210 = 824008854613343261192.
>        self assert: 18rHGFEDCBA9876543210 = 39210261334551566857170.
>        self assert: 19rIHGFEDCBA9876543210 = 1972313422155189164466189.
>        self assert: 20rJIHGFEDCBA9876543210 = 104567135734072022160664820.
>        self assert: 21rKJIHGFEDCBA9876543210 = 5827980550840017565077671610.
>        self assert: 22rLKJIHGFEDCBA9876543210 = 340653664490377789692799452102.
>        self assert: 23rMLKJIHGFEDCBA9876543210 = 20837326537038308910317109288851.
>        self assert: 24rNMLKJIHGFEDCBA9876543210 = 1331214537196502869015340298036888.
>        self assert: 25rONMLKJIHGFEDCBA9876543210 = 88663644327703473714387251271141900.
>        self assert: 26rPONMLKJIHGFEDCBA9876543210 = 6146269788878825859099399609538763450.
>        self assert: 27rQPONMLKJIHGFEDCBA9876543210 = 442770531899482980347734468443677777577.
>        self assert: 28rRQPONMLKJIHGFEDCBA9876543210 = 33100056003358651440264672384704297711484.
>        self assert: 29rSRQPONMLKJIHGFEDCBA9876543210 = 2564411043271974895869785066497940850811934.
>        self assert: 30rTSRQPONMLKJIHGFEDCBA9876543210 = 205646315052919334126040428061831153388822830.
>        self assert: 31rUTSRQPONMLKJIHGFEDCBA9876543210 = 17050208381689099029767742314582582184093573615.
>        self assert: 32rVUTSRQPONMLKJIHGFEDCBA9876543210 = 1459980823972598128486511383358617792788444579872.
>        self assert: 33rWVUTSRQPONMLKJIHGFEDCBA9876543210 = 128983956064237823710866404905431464703849549412368.
>        self assert: 34rXWVUTSRQPONMLKJIHGFEDCBA9876543210 = 11745843093701610854378775891116314824081102660800418.
>        self assert: 35rYXWVUTSRQPONMLKJIHGFEDCBA9876543210 = 1101553773143634726491620528194292510495517905608180485.
>        self assert: 36rZYXWVUTSRQPONMLKJIHGFEDCBA9876543210 = 106300512100105327644605138221229898724869759421181854980.
>
>        self assert: -2r10 = -2.
>        self assert: -3r210 = -21.
>        self assert: -4r3210 = -228.
>        self assert: -5r43210 = -2930.
>        self assert: -6r543210 = -44790.
>        self assert: -7r6543210 = -800667.
>        self assert: -8r76543210 = -16434824.
>        self assert: -9r876543210 = -381367044.
>        self assert: -10r9876543210 = -9876543210.
>        self assert: -11rA9876543210 = -282458553905.
>        self assert: -12rBA9876543210 = -8842413667692.
>        self assert: -13rCBA9876543210 = -300771807240918.
>        self assert: -14rDCBA9876543210 = -11046255305880158.
>        self assert: -15rEDCBA9876543210 = -435659737878916215.
>        self assert: -16rFEDCBA9876543210 = -18364758544493064720.
>        self assert: -17rGFEDCBA9876543210 = -824008854613343261192.
>        self assert: -18rHGFEDCBA9876543210 = -39210261334551566857170.
>        self assert: -19rIHGFEDCBA9876543210 = -1972313422155189164466189.
>        self assert: -20rJIHGFEDCBA9876543210 = -104567135734072022160664820.
>        self assert: -21rKJIHGFEDCBA9876543210 = -5827980550840017565077671610.
>        self assert: -22rLKJIHGFEDCBA9876543210 = -340653664490377789692799452102.
>        self assert: -23rMLKJIHGFEDCBA9876543210 = -20837326537038308910317109288851.
>        self assert: -24rNMLKJIHGFEDCBA9876543210 = -1331214537196502869015340298036888.
>        self assert: -25rONMLKJIHGFEDCBA9876543210 = -88663644327703473714387251271141900.
>        self assert: -26rPONMLKJIHGFEDCBA9876543210 = -6146269788878825859099399609538763450.
>        self assert: -27rQPONMLKJIHGFEDCBA9876543210 = -442770531899482980347734468443677777577.
>        self assert: -28rRQPONMLKJIHGFEDCBA9876543210 = -33100056003358651440264672384704297711484.
>        self assert: -29rSRQPONMLKJIHGFEDCBA9876543210 = -2564411043271974895869785066497940850811934.
>        self assert: -30rTSRQPONMLKJIHGFEDCBA9876543210 = -205646315052919334126040428061831153388822830.
>        self assert: -31rUTSRQPONMLKJIHGFEDCBA9876543210 = -17050208381689099029767742314582582184093573615.
>        self assert: -32rVUTSRQPONMLKJIHGFEDCBA9876543210 = -1459980823972598128486511383358617792788444579872.
>        self assert: -33rWVUTSRQPONMLKJIHGFEDCBA9876543210 = -128983956064237823710866404905431464703849549412368.
>        self assert: -34rXWVUTSRQPONMLKJIHGFEDCBA9876543210 = -11745843093701610854378775891116314824081102660800418.
>        self assert: -35rYXWVUTSRQPONMLKJIHGFEDCBA9876543210 = -1101553773143634726491620528194292510495517905608180485.
>        self assert: -36rZYXWVUTSRQPONMLKJIHGFEDCBA9876543210 = -106300512100105327644605138221229898724869759421181854980.!
>
> ----- Method: IntegerTest>>testEven (in category 'tests - basic') -----
> testEven
>
>        self deny: (1073741825 even).
>        self assert: (1073741824  even).
>        !
>
> ----- Method: IntegerTest>>testHex (in category 'tests - printing') -----
> testHex
>        self assert: 0 hex = '0'.
>        self assert: 12 hex = 'C'.
>        self assert: 1234 hex = '4D2'.!
>
> ----- Method: IntegerTest>>testIntegerByteEncoded (in category 'tests - printing') -----
> testIntegerByteEncoded
>        self assert: (ByteEncoder stream writeNumber: 2 base: 2; yourself) contents = '10'.
>        self assert: (ByteEncoder stream writeNumber: 21 base: 3; yourself) contents = '210'.
>        self assert: (ByteEncoder stream writeNumber: 228 base: 4; yourself) contents = '3210'.
>        self assert: (ByteEncoder stream writeNumber: 2930 base: 5; yourself) contents = '43210'.
>        self assert: (ByteEncoder stream writeNumber: 44790 base: 6; yourself) contents = '543210'.
>        self assert: (ByteEncoder stream writeNumber: 800667 base: 7; yourself) contents = '6543210'.
>        self assert: (ByteEncoder stream writeNumber: 16434824 base: 8; yourself) contents = '76543210'.
>        self assert: (ByteEncoder stream writeNumber: 381367044 base: 9; yourself) contents = '876543210'.
>        self assert: (ByteEncoder stream writeNumber: 9876543210 base: 10; yourself) contents = '9876543210'.
>        self assert: (ByteEncoder stream writeNumber: 282458553905 base: 11; yourself) contents = 'A9876543210'.
>        self assert: (ByteEncoder stream writeNumber: 8842413667692 base: 12; yourself) contents = 'BA9876543210'.
>        self assert: (ByteEncoder stream writeNumber: 300771807240918 base: 13; yourself) contents = 'CBA9876543210'.
>        self assert: (ByteEncoder stream writeNumber: 11046255305880158 base: 14; yourself) contents = 'DCBA9876543210'.
>        self assert: (ByteEncoder stream writeNumber: 435659737878916215 base: 15; yourself) contents = 'EDCBA9876543210'.
>        self assert: (ByteEncoder stream writeNumber: 18364758544493064720 base: 16; yourself) contents = 'FEDCBA9876543210'.
>
>        self assert: (ByteEncoder stream writeNumber: -2 base: 2; yourself) contents = '-10'.
>        self assert: (ByteEncoder stream writeNumber: -21 base: 3; yourself) contents = '-210'.
>        self assert: (ByteEncoder stream writeNumber: -228 base: 4; yourself) contents = '-3210'.
>        self assert: (ByteEncoder stream writeNumber: -2930 base: 5; yourself) contents = '-43210'.
>        self assert: (ByteEncoder stream writeNumber: -44790 base: 6; yourself) contents = '-543210'.
>        self assert: (ByteEncoder stream writeNumber: -800667 base: 7; yourself) contents = '-6543210'.
>        self assert: (ByteEncoder stream writeNumber: -16434824 base: 8; yourself) contents = '-76543210'.
>        self assert: (ByteEncoder stream writeNumber: -381367044 base: 9; yourself) contents = '-876543210'.
>        self assert: (ByteEncoder stream writeNumber: -9876543210 base: 10; yourself) contents = '-9876543210'.
>        self assert: (ByteEncoder stream writeNumber: -282458553905 base: 11; yourself) contents = '-A9876543210'.
>        self assert: (ByteEncoder stream writeNumber: -8842413667692 base: 12; yourself) contents = '-BA9876543210'.
>        self assert: (ByteEncoder stream writeNumber: -300771807240918 base: 13; yourself) contents = '-CBA9876543210'.
>        self assert: (ByteEncoder stream writeNumber: -11046255305880158 base: 14; yourself) contents = '-DCBA9876543210'.
>        self assert: (ByteEncoder stream writeNumber: -435659737878916215 base: 15; yourself) contents = '-EDCBA9876543210'.
>        self assert: (ByteEncoder stream writeNumber: -18364758544493064720 base: 16; yourself) contents = '-FEDCBA9876543210'.!
>
> ----- Method: IntegerTest>>testIntegerPadding (in category 'tests - printing') -----
> testIntegerPadding
>        "self run: #testIntegerPadding"
>
>        self assert: (1 printStringBase: 10 length: 0 padded: false) = '1'.
>        self assert: (1 printStringBase: 10 length: 1 padded: false) = '1'.
>        self assert: (1 printStringBase: 10 length: 2 padded: false) = ' 1'.
>        self assert: (1024 printStringBase: 10 length: 19 padded: false) = '               1024'.
>        self assert: (1024 printStringBase: 10 length: -1 padded: false) = '1024'.
>        self assert: (1024 printStringBase: 10 length: 5 padded: false) =  ' 1024'.
>        self assert: (-1024 printStringBase: 10 length: 5 padded: false) =   '-1024'.
>        self assert: (-1024 printStringBase: 10 length: 19 padded: false) =  '              -1024'.
>
>        self assert: (1 printStringBase: 10 length: 0 padded: true) = '1'.
>        self assert: (1 printStringBase: 10 length: 1 padded: true) = '1'.
>        self assert: (1 printStringBase: 10 length: 2 padded: true) = '01'.
>        self assert: (1024 printStringBase: 10 length: 19 padded: true) = '0000000000000001024'.
>        self assert: (1024 printStringBase: 10 length: -1 padded: true) = '1024'.
>        self assert: (1024 printStringBase: 10 length: 5 padded: true) =  '01024'.
>        self assert: (-1024 printStringBase: 10 length: 5 padded: true) =   '-1024'.
>        self assert: (-1024 printStringBase: 10 length: 19 padded: true) =  '-000000000000001024'.
>
>        self assert: (1 printStringBase: 16 length: 0 padded: false) = '1'.
>        self assert: (1 printStringBase: 16 length: 1 padded: false) = '1'.
>        self assert: (1 printStringBase: 16 length: 2 padded: false) = ' 1'.
>        self assert: (2047 printStringBase: 16 length: 19 padded: false) =  '                7FF'.
>        self assert: (2047 printStringBase: 16 length: -1 padded: false) =  '7FF'.
>        self assert: (2047 printStringBase: 16 length: 4 padded: false) =  ' 7FF'.
>        self assert: (-2047 printStringBase: 16 length: 4 padded: false) = '-7FF'.
>        self assert: (-2047 printStringBase: 16 length: 19 padded: false) =  '               -7FF'.
>
>        self assert: (1 printStringBase: 16 length: 0 padded: true) = '1'.
>        self assert: (1 printStringBase: 16 length: 1 padded: true) = '1'.
>        self assert: (1 printStringBase: 16 length: 2 padded: true) = '01'.
>        self assert: (2047 printStringBase: 16 length: 19 padded: true) =  '00000000000000007FF'.
>        self assert: (2047 printStringBase: 16 length: -1 padded: true) =  '7FF'.
>        self assert: (2047 printStringBase: 16 length: 4 padded: true) =  '07FF'.
>        self assert: (-2047 printStringBase: 16 length: 4 padded: true) = '-7FF'.
>        self assert: (-2047 printStringBase: 16 length: 19 padded: true) =  '-0000000000000007FF'.
>
>        self assert: (1 storeStringBase: 10 length: 0 padded: false) = '1'.
>        self assert: (1 storeStringBase: 10 length: 1 padded: false) = '1'.
>        self assert: (1 storeStringBase: 10 length: 2 padded: false) = ' 1'.
>        self assert: (1024 storeStringBase: 10 length: 19 padded: false) = '               1024'.
>        self assert: (1024 storeStringBase: 10 length: -1 padded: false) = '1024'.
>        self assert: (1024 storeStringBase: 10 length: 5 padded: false) =  ' 1024'.
>        self assert: (-1024 storeStringBase: 10 length: 5 padded: false) =   '-1024'.
>        self assert: (-1024 storeStringBase: 10 length: 19 padded: false) =  '              -1024'.
>
>        self assert: (1 storeStringBase: 10 length: 0 padded: true) = '1'.
>        self assert: (1 storeStringBase: 10 length: 1 padded: true) = '1'.
>        self assert: (1 storeStringBase: 10 length: 2 padded: true) = '01'.
>        self assert: (1024 storeStringBase: 10 length: 19 padded: true) = '0000000000000001024'.
>        self assert: (1024 storeStringBase: 10 length: -1 padded: true) = '1024'.
>        self assert: (1024 storeStringBase: 10 length: 5 padded: true) =  '01024'.
>        self assert: (-1024 storeStringBase: 10 length: 5 padded: true) =   '-1024'.
>        self assert: (-1024 storeStringBase: 10 length: 19 padded: true) =  '-000000000000001024'.
>
>        self assert: (1 storeStringBase: 16 length: 0 padded: false) = '16r1'.
>        self assert: (1 storeStringBase: 16 length: 4 padded: false) = '16r1'.
>        self assert: (1 storeStringBase: 16 length: 5 padded: false) = ' 16r1'.
>        self assert: (2047 storeStringBase: 16 length: 19 padded: false) =  '             16r7FF'.
>        self assert: (2047 storeStringBase: 16 length: -1 padded: false) =  '16r7FF'.
>        self assert: (2047 storeStringBase: 16 length: 7 padded: false) =  ' 16r7FF'.
>        self assert: (-2047 storeStringBase: 16 length: 7 padded: false) = '-16r7FF'.
>        self assert: (-2047 storeStringBase: 16 length: 19 padded: false) =  '            -16r7FF'.
>
>        self assert: (1 storeStringBase: 16 length: 0 padded: true) = '16r1'.
>        self assert: (1 storeStringBase: 16 length: 4 padded: true) = '16r1'.
>        self assert: (1 storeStringBase: 16 length: 5 padded: true) = '16r01'.
>        self assert: (2047 storeStringBase: 16 length: 19 padded: true) =  '16r00000000000007FF'.
>        self assert: (2047 storeStringBase: 16 length: -1 padded: true) =  '16r7FF'.
>        self assert: (2047 storeStringBase: 16 length: 7 padded: true) =  '16r07FF'.
>        self assert: (-2047 storeStringBase: 16 length: 7 padded: true) = '-16r7FF'.
>        self assert: (-2047 storeStringBase: 16 length: 19 padded: true) =  '-16r0000000000007FF'.
> !
>
> ----- Method: IntegerTest>>testIntegerReadFrom (in category 'tests - instance creation') -----
> testIntegerReadFrom
>        self assert: (Integer readFrom: '123' readStream base: 10) = 123.
>        self assert: (Integer readFrom: '-123' readStream base: 10) = -123.
>        self assert: (Integer readFrom: 'abc' readStream base: 10) = 0.
>        self assert: (Integer readFrom: 'D12' readStream base: 10) = 0.
>        self assert: (Integer readFrom: '1two3' readStream base: 10) = 1.
> !
>
> ----- Method: IntegerTest>>testIsInteger (in category 'tests - basic') -----
> testIsInteger
>
>        self assert: (0 isInteger).
>        !
>
> ----- Method: IntegerTest>>testIsPowerOfTwo (in category 'tests - basic') -----
> testIsPowerOfTwo
>
>        self assert: (0 isPowerOfTwo).
>        self assert: (1 isPowerOfTwo).
>        self assert: (2 isPowerOfTwo).
>        self deny:  (3 isPowerOfTwo).
>        self assert: (4 isPowerOfTwo).
>        !
>
> ----- Method: IntegerTest>>testIsPrime (in category 'tests - basic') -----
> testIsPrime
>
>        "The following tests should return 'true'"
>        self assert: 17 isPrime.
>        self assert: 78901 isPrime.
>        self assert: 104729 isPrime.
>        self assert: 15485863 isPrime.
>        self assert: 2038074743 isPrime.
>        self assert: 29996224275833 isPrime.
>
>        "The following tests should return 'false' (first 5 are Carmichael integers)"
>        self deny: 561 isPrime.
>        self deny: 2821 isPrime.
>        self deny: 6601 isPrime.
>        self deny: 10585 isPrime.
>        self deny: 15841 isPrime.
>        self deny: 256 isPrime.
>        self deny: 29996224275831 isPrime.!
>
> ----- Method: IntegerTest>>testLargePrimesUpTo (in category 'tests - basic') -----
> testLargePrimesUpTo
>
>        | nn |
>        nn := (2 raisedTo: 17) - 1.
>        self deny: (Integer primesUpTo: nn) last = nn.
>        self assert: (Integer primesUpTo: nn + 1) last  = nn.
>
>
> !
>
> ----- Method: IntegerTest>>testNegativeIntegerPrinting (in category 'tests - printing') -----
> testNegativeIntegerPrinting
>        "self run: #testnegativeIntegerPrinting"
>
>        self assert: (-2 printStringBase: 2) = '-10'.
>        self assert: (-2 radix: 2) = '-10'.
>        self assert: -2 printStringHex = '-2'.
>        self assert: (-2 storeStringBase: 2) = '-2r10'.
>        self assert: -2 storeStringHex = '-16r2'.
>        self assert: (-21 printStringBase: 3) = '-210'.
>        self assert: (-21 radix: 3) = '-210'.
>        self assert: -21 printStringHex = '-15'.
>        self assert: (-21 storeStringBase: 3) = '-3r210'.
>        self assert: -21 storeStringHex = '-16r15'.
>        self assert: (-228 printStringBase: 4) = '-3210'.
>        self assert: (-228 radix: 4) = '-3210'.
>        self assert: -228 printStringHex = '-E4'.
>        self assert: (-228 storeStringBase: 4) = '-4r3210'.
>        self assert: -228 storeStringHex = '-16rE4'.
>        self assert: (-2930 printStringBase: 5) = '-43210'.
>        self assert: (-2930 radix: 5) = '-43210'.
>        self assert: -2930 printStringHex = '-B72'.
>        self assert: (-2930 storeStringBase: 5) = '-5r43210'.
>        self assert: -2930 storeStringHex = '-16rB72'.
>        self assert: (-44790 printStringBase: 6) = '-543210'.
>        self assert: (-44790 radix: 6) = '-543210'.
>        self assert: -44790 printStringHex = '-AEF6'.
>        self assert: (-44790 storeStringBase: 6) = '-6r543210'.
>        self assert: -44790 storeStringHex = '-16rAEF6'.
>        self assert: (-800667 printStringBase: 7) = '-6543210'.
>        self assert: (-800667 radix: 7) = '-6543210'.
>        self assert: -800667 printStringHex = '-C379B'.
>        self assert: (-800667 storeStringBase: 7) = '-7r6543210'.
>        self assert: -800667 storeStringHex = '-16rC379B'.
>        self assert: (-16434824 printStringBase: 8) = '-76543210'.
>        self assert: (-16434824 radix: 8) = '-76543210'.
>        self assert: -16434824 printStringHex = '-FAC688'.
>        self assert: (-16434824 storeStringBase: 8) = '-8r76543210'.
>        self assert: -16434824 storeStringHex = '-16rFAC688'.
>        self assert: (-381367044 printStringBase: 9) = '-876543210'.
>        self assert: (-381367044 radix: 9) = '-876543210'.
>        self assert: -381367044 printStringHex = '-16BB3304'.
>        self assert: (-381367044 storeStringBase: 9) = '-9r876543210'.
>        self assert: -381367044 storeStringHex = '-16r16BB3304'.
>        self assert: (-9876543210 printStringBase: 10) = '-9876543210'.
>        self assert: (-9876543210 radix: 10) = '-9876543210'.
>        self assert: -9876543210 printStringHex = '-24CB016EA'.
>        self assert: (-9876543210 storeStringBase: 10) = '-9876543210'.
>        self assert: -9876543210 storeStringHex = '-16r24CB016EA'.
>        self assert: (-282458553905 printStringBase: 11) = '-A9876543210'.
>        self assert: (-282458553905 radix: 11) = '-A9876543210'.
>        self assert: -282458553905 printStringHex = '-41C3D77E31'.
>        self assert: (-282458553905 storeStringBase: 11) = '-11rA9876543210'.
>        self assert: -282458553905 storeStringHex = '-16r41C3D77E31'.
>        self assert: (-8842413667692 printStringBase: 12) = '-BA9876543210'.
>        self assert: (-8842413667692 radix: 12) = '-BA9876543210'.
>        self assert: -8842413667692 printStringHex = '-80AC8ECF56C'.
>        self assert: (-8842413667692 storeStringBase: 12) = '-12rBA9876543210'.
>        self assert: -8842413667692 storeStringHex = '-16r80AC8ECF56C'.
>        self assert: (-300771807240918 printStringBase: 13) = '-CBA9876543210'.
>        self assert: (-300771807240918 radix: 13) = '-CBA9876543210'.
>        self assert: -300771807240918 printStringHex = '-1118CE4BAA2D6'.
>        self assert: (-300771807240918 storeStringBase: 13) = '-13rCBA9876543210'.
>        self assert: -300771807240918 storeStringHex = '-16r1118CE4BAA2D6'.
>        self assert: (-11046255305880158 printStringBase: 14) = '-DCBA9876543210'.
>        self assert: (-11046255305880158 radix: 14) = '-DCBA9876543210'.
>        self assert: -11046255305880158 printStringHex = '-273E82BB9AF25E'.
>        self assert: (-11046255305880158 storeStringBase: 14) = '-14rDCBA9876543210'.
>        self assert: -11046255305880158 storeStringHex = '-16r273E82BB9AF25E'.
>        self assert: (-435659737878916215 printStringBase: 15) = '-EDCBA9876543210'.
>        self assert: (-435659737878916215 radix: 15) = '-EDCBA9876543210'.
>        self assert: -435659737878916215 printStringHex = '-60BC6392F366C77'.
>        self assert: (-435659737878916215 storeStringBase: 15) = '-15rEDCBA9876543210'.
>        self assert: -435659737878916215 storeStringHex = '-16r60BC6392F366C77'.
>        self assert: (-18364758544493064720 printStringBase: 16) = '-FEDCBA9876543210'.
>        self assert: (-18364758544493064720 radix: 16) = '-FEDCBA9876543210'.
>        self assert: -18364758544493064720 printStringHex = '-FEDCBA9876543210'.
>        self assert: (-18364758544493064720 storeStringBase: 16) = '-16rFEDCBA9876543210'.
>        self assert: -18364758544493064720 storeStringHex = '-16rFEDCBA9876543210'.
>        self assert: (-824008854613343261192 printStringBase: 17) = '-GFEDCBA9876543210'.
>        self assert: (-824008854613343261192 radix: 17) = '-GFEDCBA9876543210'.
>        self assert: -824008854613343261192 printStringHex = '-2CAB6B877C1CD2D208'.
>        self assert: (-824008854613343261192 storeStringBase: 17) = '-17rGFEDCBA9876543210'.
>        self assert: -824008854613343261192 storeStringHex = '-16r2CAB6B877C1CD2D208'.
>        self assert: (-39210261334551566857170 printStringBase: 18) = '-HGFEDCBA9876543210'.
>        self assert: (-39210261334551566857170 radix: 18) = '-HGFEDCBA9876543210'.
>        self assert: -39210261334551566857170 printStringHex = '-84D97AFCAE81415B3D2'.
>        self assert: (-39210261334551566857170 storeStringBase: 18) = '-18rHGFEDCBA9876543210'.
>        self assert: -39210261334551566857170 storeStringHex = '-16r84D97AFCAE81415B3D2'.
>        self assert: (-1972313422155189164466189 printStringBase: 19) = '-IHGFEDCBA9876543210'.
>        self assert: (-1972313422155189164466189 radix: 19) = '-IHGFEDCBA9876543210'.
>        self assert: -1972313422155189164466189 printStringHex = '-1A1A75329C5C6FC00600D'.
>        self assert: (-1972313422155189164466189 storeStringBase: 19) = '-19rIHGFEDCBA9876543210'.
>        self assert: -1972313422155189164466189 storeStringHex = '-16r1A1A75329C5C6FC00600D'.
>        self assert: (-104567135734072022160664820 printStringBase: 20) = '-JIHGFEDCBA9876543210'.
>        self assert: (-104567135734072022160664820 radix: 20) = '-JIHGFEDCBA9876543210'.
>        self assert: -104567135734072022160664820 printStringHex = '-567EF3C9636D242A8C68F4'.
>        self assert: (-104567135734072022160664820 storeStringBase: 20) = '-20rJIHGFEDCBA9876543210'.
>        self assert: -104567135734072022160664820 storeStringHex = '-16r567EF3C9636D242A8C68F4'.
>        self assert: (-5827980550840017565077671610 printStringBase: 21) = '-KJIHGFEDCBA9876543210'.
>        self assert: (-5827980550840017565077671610 radix: 21) = '-KJIHGFEDCBA9876543210'.
>        self assert: -5827980550840017565077671610 printStringHex = '-12D4CAE2B8A09BCFDBE30EBA'.
>        self assert: (-5827980550840017565077671610 storeStringBase: 21) = '-21rKJIHGFEDCBA9876543210'.
>        self assert: -5827980550840017565077671610 storeStringHex = '-16r12D4CAE2B8A09BCFDBE30EBA'.
>        self assert: (-340653664490377789692799452102 printStringBase: 22) = '-LKJIHGFEDCBA9876543210'.
>        self assert: (-340653664490377789692799452102 radix: 22) = '-LKJIHGFEDCBA9876543210'.
>        self assert: -340653664490377789692799452102 printStringHex = '-44CB61B5B47E1A5D8F88583C6'.
>        self assert: (-340653664490377789692799452102 storeStringBase: 22) = '-22rLKJIHGFEDCBA9876543210'.
>        self assert: -340653664490377789692799452102 storeStringHex = '-16r44CB61B5B47E1A5D8F88583C6'.
>        self assert: (-20837326537038308910317109288851 printStringBase: 23) = '-MLKJIHGFEDCBA9876543210'.
>        self assert: (-20837326537038308910317109288851 radix: 23) = '-MLKJIHGFEDCBA9876543210'.
>        self assert: -20837326537038308910317109288851 printStringHex = '-1070108876456E0EF115B389F93'.
>        self assert: (-20837326537038308910317109288851 storeStringBase: 23) = '-23rMLKJIHGFEDCBA9876543210'.
>        self assert: -20837326537038308910317109288851 storeStringHex = '-16r1070108876456E0EF115B389F93'.
>        self assert: (-1331214537196502869015340298036888 printStr...
>
> [Message clipped]



-- 
Damien Cassou
Peter von der Ahé: «I'm beginning to see why Gilad wished us good
luck». (http://blogs.sun.com/ahe/entry/override_snafu)


More information about the Packages mailing list