The Trunk: System-ar.221.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: System-ar.221.mcz

commits-2
Andreas Raab uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-ar.221.mcz

==================== Summary ====================

Name: System-ar.221
Author: ar
Time: 4 January 2010, 4:38:21 am
UUID: d8529e06-88a5-a343-8ae6-921b43a77a0c
Ancestors: System-ar.220

Making Tests unloadable: Move tests out of System package and into Tests.

=============== Diff against System-ar.220 ===============

Item was changed:
  SystemOrganization addCategory: #'System-Applications'!
  SystemOrganization addCategory: #'System-Change Notification'!
  SystemOrganization addCategory: #'System-Changes'!
  SystemOrganization addCategory: #'System-Digital Signatures'!
- SystemOrganization addCategory: #'System-Digital Signatures-Tests'!
  SystemOrganization addCategory: #'System-Download'!
  SystemOrganization addCategory: #'System-FilePackage'!
  SystemOrganization addCategory: #'System-FilePackage-Tests'!
  SystemOrganization addCategory: #'System-FileRegistry'!
  SystemOrganization addCategory: #'System-Finalization'!
  SystemOrganization addCategory: #'System-Localization'!
  SystemOrganization addCategory: #'System-Object Events'!
- SystemOrganization addCategory: #'System-Object Events-Tests'!
  SystemOrganization addCategory: #'System-Object Storage'!
  SystemOrganization addCategory: #'System-Pools'!
  SystemOrganization addCategory: #'System-Preferences'!
  SystemOrganization addCategory: #'System-Serial Port'!
  SystemOrganization addCategory: #'System-Support'!
- SystemOrganization addCategory: #'System-Support-Tests'!
  SystemOrganization addCategory: #'System-Tools'!

Item was removed:
- ----- Method: EventManagerTest>>testBlockReceiverNoArgs (in category 'running-dependent action') -----
- testBlockReceiverNoArgs
- eventSource when: #anEvent evaluate:[self heardEvent].
- eventSource triggerEvent: #anEvent.
- self should: [succeeded]!

Item was removed:
- ----- Method: TextDiffBuilderTest>>testEmptyLcs1 (in category 'tests') -----
- testEmptyLcs1
-
- | patch |
- patch := self patchSequenceFor: #(a b c) and: #().
- self assert: patch size = 3.
- self assert: (patch allSatisfy: [ :each | each key = #remove ])!

Item was removed:
- ----- Method: EventManagerTest>>testMultipleValueSuppliersEventHasArguments (in category 'running-broadcast query') -----
- testMultipleValueSuppliersEventHasArguments
-
- eventSource
- when: #needsValue:
- send: #getFalse:
- to: self.
- eventSource
- when: #needsValue:
- send: #getTrue:
- to: self.
- succeeded := eventSource triggerEvent: #needsValue: with: 'kolme'.
- self should: [succeeded]!

Item was removed:
- ----- Method: TextDiffBuilderTest>>testIfSequence2 (in category 'tests') -----
- testIfSequence2
-
- | patch |
- patch := self patchSequenceFor: #(a b c d) and: #(c d b a).
- self assert: patch size = 6. "lcs is cd"
- self assert: (patch count: [ :each | each key = #match ]) = 2.
- self assert: (patch count: [ :each | each key = #insert ]) = 2.
- self assert: (patch count: [ :each | each key = #remove ]) = 2.
- patch do: [ :each |
- each key = #match
- ifTrue: [ self assert: ('cd' includes: each value first) ]
- ifFalse: [ self assert: ('ab' includes: each value first) ] ]!

Item was removed:
- ----- Method: TextDiffBuilderTest>>testSameSequence (in category 'tests') -----
- testSameSequence
-
- | patch |
- patch := self patchSequenceFor: #(a b c) and: #(a b c).
- self assert: patch size = 3.
- self assert: (patch allSatisfy: [ :each | each key = #match ])!

Item was removed:
- ----- Method: StandardSystemFontsTest>>assert:familyName:pointSize: (in category 'utilities') -----
- assert: selector familyName: aString pointSize: anInteger
- | font |
- font := Preferences perform: selector.
- self assert: aString equals: font familyName.
- self assert: anInteger equals: font pointSize!

Item was removed:
- ----- Method: EventManagerTest>>testReturnValueWithNoListeners (in category 'running-dependent value') -----
- testReturnValueWithNoListeners
-
- | value |
- value := eventSource triggerEvent: #needsValue.
- self should: [value == nil]!

Item was removed:
- ----- Method: TextDiffBuilderTest>>convertToString: (in category 'private') -----
- convertToString: array
-
- ^String streamContents: [ :stream |
- array do: [ :each |
- stream nextPutAll: each asString; cr ] ]!

Item was removed:
- TestCase subclass: #TextDiffBuilderTest
- instanceVariableNames: ''
- classVariableNames: ''
- poolDictionaries: ''
- category: 'System-FilePackage-Tests'!

Item was removed:
- ----- Method: SystemVersionTest>>testMajorMinorVersion (in category 'as yet unclassified') -----
- testMajorMinorVersion
- "
- SystemVersionTest run: #testMajorMinorVersion
- "
- self assert: (SystemVersion new version: 'Squeak3.7alpha') majorMinorVersion = 'Squeak3.7'.
- self assert: (SystemVersion new version: 'Squeak3.7') majorMinorVersion = 'Squeak3.7'.
- self assert: (SystemVersion new version: 'Squeak3') majorMinorVersion = 'Squeak3'.
- self assert: (SystemVersion new version: '') majorMinorVersion = ''.
- !

Item was removed:
- ----- Method: EventManagerTest>>testSingleValueSupplier (in category 'running-broadcast query') -----
- testSingleValueSupplier
-
- eventSource
- when: #needsValue
- send: #getTrue
- to: self.
- succeeded := eventSource triggerEvent: #needsValue.
- self should: [succeeded]!

Item was removed:
- TestCase subclass: #StandardSystemFontsTest
- instanceVariableNames: ''
- classVariableNames: ''
- poolDictionaries: ''
- category: 'System-Support-Tests'!

Item was removed:
- ----- Method: EventManagerTest>>testCopy (in category 'running-copying') -----
- testCopy
- "Ensure that the actionMap is zapped when
- you make a copy of anEventManager"
-
- eventSource when: #blah send: #yourself to: eventListener.
- self assert: eventSource actionMap keys isEmpty not.
- self assert: eventSource copy actionMap keys isEmpty!

Item was removed:
- ----- Method: EventManagerTest>>getTrue (in category 'private') -----
- getTrue
-
- ^true!

Item was removed:
- ----- Method: EventManagerTest>>testBlockReceiverTwoArgs (in category 'running-dependent action') -----
- testBlockReceiverTwoArgs
- eventSource when: #anEvent:info: evaluate:[:arg1 :arg2| self addArg1: arg1 addArg2: arg2].
- eventSource triggerEvent: #anEvent:info: withArguments: #( 9 42 ).
- self should: [(eventListener includes: 9) and: [eventListener includes: 42]]!

Item was removed:
- ----- Method: EventManagerTest>>testNoArgumentEventDependentSuppliedArgument (in category 'running-dependent action supplied arguments') -----
- testNoArgumentEventDependentSuppliedArgument
-
- eventSource when: #anEvent send: #add: to: eventListener with: 'boundValue'.
- eventSource triggerEvent: #anEvent.
- self should: [eventListener includes: 'boundValue']!

Item was removed:
- ----- Method: StandardSystemFontsTest>>testRestoreDefaultFonts (in category 'testing') -----
- testRestoreDefaultFonts
- self saveStandardSystemFontsDuring: [
- Preferences restoreDefaultFonts.
- self assert: #standardDefaultTextFont familyName: 'Bitmap DejaVu Sans' pointSize: 9.
- self assert: #standardListFont familyName: 'Bitmap DejaVu Sans' pointSize: 9.
- self assert: #standardFlapFont familyName: 'Accushi' pointSize: 12.
- self assert: #standardEToysFont familyName: 'BitstreamVeraSans' pointSize: 9.
- self assert: #standardMenuFont familyName: 'Bitmap DejaVu Sans' pointSize: 9.
- self assert: #windowTitleFont familyName: 'Bitmap DejaVu Sans' pointSize: 12.
- self assert: #standardBalloonHelpFont familyName: 'Accujen' pointSize: 9.
- self assert: #standardCodeFont familyName: 'Bitmap DejaVu Sans' pointSize: 9.
- self assert: #standardButtonFont familyName: 'BitstreamVeraSansMono' pointSize: 9]!

Item was removed:
- ----- Method: EventManagerTest>>testNoValueSupplier (in category 'running-broadcast query') -----
- testNoValueSupplier
-
- succeeded := eventSource
- triggerEvent: #needsValue
- ifNotHandled: [true].
- self should: [succeeded]!

Item was removed:
- ----- Method: ObjectFinalizerTests>>testFinalization (in category 'tests') -----
- testFinalization
- "self run: #testFinalization"
-
- | repetitions |
- repetitions := 100.
- 1 to: repetitions
- do: [:i |
- log addLast: 'o' , i asString , ' created'.
- Object new
- toFinalizeSend: #finalize:
- to: self
- with: 'o' , i asString].
- Smalltalk garbageCollect.
- self finalizationRegistry finalizeValues.
- 1 to: repetitions
- do: [:i |
- self assert: (log includes: 'o' , i asString , ' created').
- self assert: (log includes: 'o' , i asString , ' finalized')]!

Item was removed:
- ----- Method: EventManagerTest>>testNoArgumentEvent (in category 'running-dependent action') -----
- testNoArgumentEvent
-
- eventSource when: #anEvent send: #heardEvent to: self.
- eventSource triggerEvent: #anEvent.
- self should: [succeeded]!

Item was removed:
- ----- Method: EventManagerTest>>testTwoArgumentEvent (in category 'running-dependent action') -----
- testTwoArgumentEvent
-
- eventSource when: #anEvent:info: send: #addArg1:addArg2: to: self.
- eventSource triggerEvent: #anEvent:info: withArguments: #( 9 42 ).
- self should: [(eventListener includes: 9) and: [eventListener includes: 42]]!

Item was removed:
- ----- Method: TextDiffBuilderTest>>testIfPatchIsMinimal (in category 'tests') -----
- testIfPatchIsMinimal
-
- | patch |
- patch := self patchSequenceFor: #(a a a b) and: #(a b a a).
- self assert: patch size = 5. "lcs is aaa"
- self assert: (patch count: [ :each | each key = #match ]) = 3.
- self assert: (patch count: [ :each | each key = #insert ]) = 1.
- self assert: (patch count: [ :each | each key = #remove ]) = 1.
- patch do: [ :each |
- each key = #match
- ifTrue: [ self assert: each value first = $a ]
- ifFalse: [ self assert: each value first = $b ] ]!

Item was removed:
- ----- Method: LocaleTest>>testLocaleChanged (in category 'testing') -----
- testLocaleChanged
- "self debug: #testLocaleChanged"
- "LanguageEnvironment >> startUp is called from Prject >> localeChanged"
- Project current updateLocaleDependents.
- self assert: (ActiveHand instVarNamed: 'keyboardInterpreter') isNil.
- self assert: (Clipboard default instVarNamed: 'interpreter') isNil.
- Locale switchToID: (LocaleID isoLanguage: 'ja').
- self assert: Preferences useFormsInPaintBox.
- Locale switchToID: (LocaleID isoLanguage: 'en').
- self assert: Preferences useFormsInPaintBox not.
- !

Item was removed:
- ----- Method: EventManagerTest>>getFalse (in category 'private') -----
- getFalse
-
- ^false!

Item was removed:
- ----- Method: TextDiffBuilderTest>>testIfSequence5 (in category 'tests') -----
- testIfSequence5
-
- | patch matches nonMatches |
- patch := self patchSequenceFor: #(a b c d) and: #(c d a b).
- self assert: patch size = 6. "lcs is ab or cd"
- matches := (patch select: [ :each | each key = #match ])
- collect: [ :each | each value first ] as: String.
- self assert: (#('ab' 'cd') includes: matches).
- self assert: (patch count: [ :each | each key = #insert ]) = 2.
- self assert: (patch count: [ :each | each key = #remove ]) = 2.
- nonMatches := #('ab' 'cd') detect: [ :each | each ~= matches ].
- patch do: [ :each |
- each key = #match
- ifTrue: [ self assert: (matches includes: each value first) ]
- ifFalse: [ self assert: (nonMatches includes: each value first) ] ]!

Item was removed:
- TestCase subclass: #LocaleTest
- instanceVariableNames: ''
- classVariableNames: ''
- poolDictionaries: ''
- category: 'System-Localization'!
-
- !LocaleTest commentStamp: 'tak 8/3/2005 18:24' prior: 0!
- LocaleTest buildSuite run!

Item was removed:
- ----- Method: EventManagerTest>>setUp (in category 'running') -----
- setUp
-
- super setUp.
- eventSource := EventManager new.
- eventListener := Bag new.
- succeeded := false!

Item was removed:
- ClassTestCase subclass: #SecureHashAlgorithmTest
- instanceVariableNames: 'hash'
- classVariableNames: ''
- poolDictionaries: ''
- category: 'System-Digital Signatures-Tests'!
-
- !SecureHashAlgorithmTest commentStamp: '<historical>' prior: 0!
- This is the unit test for the class SecureHashAlgorithm. 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!

Item was removed:
- ----- Method: SecureHashAlgorithmTest>>testExample3 (in category 'testing - examples') -----
- testExample3
-
- "This is the third example from the specification document (FIPS PUB 180-1).
- This example may take several minutes."
-
- hash := SecureHashAlgorithm new hashMessage: (String new: 1000000 withAll: $a).
- self assert: (hash = 16r34AA973CD4C4DAA4F61EEB2BDBAD27316534016F).!

Item was removed:
- TestCase subclass: #SmalltalkImageTest
- instanceVariableNames: ''
- classVariableNames: ''
- poolDictionaries: ''
- category: 'System-Support-Tests'!

Item was removed:
- ----- Method: EventManagerTest>>testRemoveActionsTwiceForEvent (in category 'running-remove actions') -----
- testRemoveActionsTwiceForEvent
-
- eventSource
- when: #anEvent send: #size to: eventListener;
- when: #anEvent send: #getTrue to: self;
- when: #anEvent: send: #fizzbin to: self.
- eventSource removeActionsForEvent: #anEvent.
- self assert: (eventSource hasActionForEvent: #anEvent) not.
- eventSource removeActionsForEvent: #anEvent.
- self assert: (eventSource hasActionForEvent: #anEvent) not.!

Item was removed:
- ----- Method: TextDiffBuilderTest>>testEmptyLcs2 (in category 'tests') -----
- testEmptyLcs2
-
- | patch |
- patch := self patchSequenceFor: #() and: #(a b c).
- self assert: patch size = 3.
- self assert: (patch allSatisfy: [ :each | each key = #insert ])!

Item was removed:
- ----- Method: TextDiffBuilderTest>>testIfSequence3 (in category 'tests') -----
- testIfSequence3
-
- | patch |
- patch := self patchSequenceFor: #(a b c d) and: #(b d c a).
- self assert: patch size = 6. "lcs is bd"
- self assert: (patch count: [ :each | each key = #match ]) = 2.
- self assert: (patch count: [ :each | each key = #insert ]) = 2.
- self assert: (patch count: [ :each | each key = #remove ]) = 2.
- patch do: [ :each |
- each key = #match
- ifTrue: [ self assert: ('bd' includes: each value first) ]
- ifFalse: [ self assert: ('ac' includes: each value first) ] ]!

Item was removed:
- ----- Method: EventManagerTest>>testRemoveActionsForEvent (in category 'running-remove actions') -----
- testRemoveActionsForEvent
-
- eventSource
- when: #anEvent send: #size to: eventListener;
- when: #anEvent send: #getTrue to: self;
- when: #anEvent: send: #fizzbin to: self.
- eventSource removeActionsForEvent: #anEvent.
- self shouldnt: [eventSource hasActionForEvent: #anEvent]!

Item was removed:
- ----- Method: EventManagerTest>>getTrue: (in category 'private') -----
- getTrue: anArg
-
- ^true!

Item was removed:
- ----- Method: SecureHashAlgorithmTest>>testExample1 (in category 'testing - examples') -----
- testExample1
-
- "This is the first example from the specification document (FIPS PUB 180-1)"
-
- hash := SecureHashAlgorithm new hashMessage: 'abc'.
- self assert: (hash = 16rA9993E364706816ABA3E25717850C26C9CD0D89D).
- !

Item was removed:
- ----- Method: EventManagerTest>>testMultipleValueSuppliers (in category 'running-broadcast query') -----
- testMultipleValueSuppliers
-
- eventSource
- when: #needsValue
- send: #getFalse
- to: self.
- eventSource
- when: #needsValue
- send: #getTrue
- to: self.
- succeeded := eventSource triggerEvent: #needsValue.
- self should: [succeeded]!

Item was removed:
- ----- Method: TextDiffBuilderTest>>testSameSequenceWithRepetitions (in category 'tests') -----
- testSameSequenceWithRepetitions
-
- | patch |
- patch := self patchSequenceFor: #(a a b a) and: #(a a b a).
- self assert: patch size = 4.
- self assert: (patch allSatisfy: [ :each | each key = #match ])!

Item was removed:
- ----- Method: TextDiffBuilderTest>>testIfSequence1 (in category 'tests') -----
- testIfSequence1
-
- | patch |
- patch := self patchSequenceFor: #(a b c d) and: #(d c b a).
- self assert: patch size = 7. "lcs is any one letter sequence"
- self assert: (patch count: [ :each | each key = #match ]) = 1.
- self assert: (patch count: [ :each | each key = #insert ]) = 3.
- self assert: (patch count: [ :each | each key = #remove ]) = 3.
- patch do: [ :each |
- each key = #match
- ifTrue: [ self assert: each value first = $d ]
- ifFalse: [ self assert: ('abc' includes: each value first) ] ]!

Item was removed:
- ----- Method: SmalltalkImageTest>>testImageName (in category 'testing') -----
- testImageName
- "Non regression test for http://bugs.squeak.org/view.php?id=7351"
- | shortImgName fullImgName fullChgName |
- shortImgName := 'Squeak3.10.2-7179-basic'.
- fullImgName := SmalltalkImage current fullNameForImageNamed: shortImgName.
- fullChgName := SmalltalkImage current fullNameForChangesNamed: shortImgName.
- FileDirectory splitName: fullImgName to: [:path :name |
- self assert: path = SmalltalkImage current imagePath.
- self assert: name = 'Squeak3.10.2-7179-basic.image'.].
- FileDirectory splitName: fullChgName to: [:path :name |
- self assert: path = SmalltalkImage current imagePath.
- self assert: name = 'Squeak3.10.2-7179-basic.changes'.].!

Item was removed:
- ----- Method: LocaleTest>>testFontFullName (in category 'testing') -----
- testFontFullName
- "self debug: #testFontFullName"
- | env dir |
- env := (Locale isoLanguage: 'ja') languageEnvironment.
- dir := FileDirectory on: SecurityManager default untrustedUserDirectory.
- [dir recursiveDelete]
- on: Error
- do: [:e | e].
- env fontFullName.
- self assert: dir exists!

Item was removed:
- ----- Method: LocaleTest>>testEncodingName (in category 'testing') -----
- testEncodingName
- "self debug: #testEncodingName"
- | locale |
- locale := Locale isoLanguage: 'ja'.
- self assert: locale languageEnvironment fontEncodingName = #FontJapaneseEnvironment!

Item was removed:
- ----- Method: EventManagerTest>>testReturnValueWithOneListener (in category 'running-dependent value') -----
- testReturnValueWithOneListener
-
- | value |
- eventSource
- when: #needsValue
- send: #yourself
- to: eventListener.
- value := eventSource triggerEvent: #needsValue.
- self should: [value == eventListener]!

Item was removed:
- ----- Method: StandardSystemFontsTest>>saveStandardSystemFontsDuring: (in category 'utilities') -----
- saveStandardSystemFontsDuring: aBlock
- | standardDefaultTextFont standardListFont standardEToysFont standardMenuFont
- windowTitleFont standardBalloonHelpFont standardCodeFont standardButtonFont |
-
- standardDefaultTextFont := Preferences standardDefaultTextFont.
- standardListFont := Preferences standardListFont.
- standardEToysFont := Preferences standardEToysFont.
- standardMenuFont := Preferences standardMenuFont.
- windowTitleFont := Preferences windowTitleFont.
- standardBalloonHelpFont := Preferences standardBalloonHelpFont.
- standardCodeFont := Preferences standardCodeFont.
- standardButtonFont := Preferences standardButtonFont.
- [aBlock value] ensure: [
- Preferences setSystemFontTo: standardDefaultTextFont.
- Preferences setListFontTo: standardListFont.
- Preferences setEToysFontTo: standardEToysFont.
- Preferences setMenuFontTo: standardMenuFont.
- Preferences setWindowTitleFontTo: windowTitleFont.
- Preferences setBalloonHelpFontTo: standardBalloonHelpFont.
- Preferences setCodeFontTo: standardCodeFont.
- Preferences setButtonFontTo: standardButtonFont]!

Item was removed:
- ----- Method: EventManagerTest>>tearDown (in category 'running') -----
- tearDown
-
- eventSource releaseActionMap.
- eventSource := nil.
- eventListener := nil.
- super tearDown.
- !

Item was removed:
- ----- Method: LocaleTest>>testIsFontAvailable (in category 'testing') -----
- testIsFontAvailable
- "self debug: #testIsFontAvailable"
- (Locale isoLanguage: 'ja') languageEnvironment removeFonts.
- self assert: (Locale isoLanguage: 'en') languageEnvironment isFontAvailable.
- "Next test should fail after installing Japanese font"
- self assert: (Locale isoLanguage: 'ja') languageEnvironment isFontAvailable not.
- (Locale isoLanguage: 'ja') languageEnvironment installFont.
- self assert: (Locale isoLanguage: 'ja') languageEnvironment isFontAvailable!

Item was removed:
- ----- Method: EventManagerTest>>getFalse: (in category 'private') -----
- getFalse: anArg
-
- ^false!

Item was removed:
- ----- Method: ObjectFinalizerTests>>finalize: (in category 'finalization handling') -----
- finalize: anObject
- log addLast: anObject asString, ' ', 'finalized'.!

Item was removed:
- ----- Method: EventManagerTest>>heardEvent (in category 'private') -----
- heardEvent
-
- succeeded := true!

Item was removed:
- ----- Method: TextDiffBuilderTest>>testIfSequence6 (in category 'tests') -----
- testIfSequence6
-
- | patch |
- patch := self patchSequenceFor: #(a b c d) and: #(d a b c).
- self assert: patch size = 5. "lcs is abc"
- self assert: (patch count: [ :each | each key = #match ]) = 3.
- self assert: (patch count: [ :each | each key = #insert ]) = 1.
- self assert: (patch count: [ :each | each key = #remove ]) = 1.
- patch do: [ :each |
- each key = #match
- ifTrue: [ self assert: ('abc' includes: each value first) ]
- ifFalse: [ self assert: each value first = $d ] ]!

Item was removed:
- ----- Method: TextDiffBuilderTest>>patchSequenceFor:and: (in category 'private') -----
- patchSequenceFor: x and: y
-
- ^(TextDiffBuilder
- from: (self convertToString: x)
- to:  (self convertToString: y)) buildPatchSequence!

Item was removed:
- ----- Method: EventManagerTest>>testBlockReceiverOneArg (in category 'running-dependent action') -----
- testBlockReceiverOneArg
- eventSource when: #anEvent: evaluate:[:arg1| eventListener add: arg1].
- eventSource triggerEvent: #anEvent: with: 9.
- self should: [eventListener includes: 9]!

Item was removed:
- TestCase subclass: #ObjectFinalizerTests
- instanceVariableNames: 'log'
- classVariableNames: ''
- poolDictionaries: ''
- category: 'System-Finalization'!

Item was removed:
- ----- Method: EventManagerTest>>testNoArgumentEventDependentSuppliedArguments (in category 'running-dependent action supplied arguments') -----
- testNoArgumentEventDependentSuppliedArguments
-
- eventSource
- when: #anEvent
- send: #addArg1:addArg2:
- to: self
- withArguments: #('hello' 'world').
- eventSource triggerEvent: #anEvent.
- self should: [(eventListener includes: 'hello') and: [eventListener includes: 'world']]!

Item was removed:
- ----- Method: EventManagerTest>>testReturnValueWithManyListeners (in category 'running-dependent value') -----
- testReturnValueWithManyListeners
-
- | value newListener |
- newListener := 'busybody'.
- eventSource
- when: #needsValue
- send: #yourself
- to: eventListener.
- eventSource
- when: #needsValue
- send: #yourself
- to: newListener.
- value := eventSource triggerEvent: #needsValue.
- self should: [value == newListener]!

Item was removed:
- ----- Method: EventManagerTest>>addArg1:addArg2: (in category 'private') -----
- addArg1: arg1
- addArg2: arg2
-
- eventListener
- add: arg1;
- add: arg2!

Item was removed:
- TestCase subclass: #SystemVersionTest
- instanceVariableNames: ''
- classVariableNames: ''
- poolDictionaries: ''
- category: 'System-Support-Tests'!
-
- !SystemVersionTest commentStamp: 'tlk 11/14/2004 10:47' prior: 0!
- I am an sunit test for SystemVersion.  Originally created to test SqueakMapSystemVersionFix change set.
- I have no test fixtures.!

Item was removed:
- ----- Method: TextDiffBuilderTest>>testEmptyLcs3 (in category 'tests') -----
- testEmptyLcs3
-
- | patch |
- patch := self patchSequenceFor: #(a b c) and: #(d e f g).
- self assert: patch size = 7.
- patch do: [ :each |
- each key = #remove ifTrue: [ self assert: ('abc' includes: each value first) ].
- each key = #insert ifTrue: [ self assert: ('defg' includes: each value first) ] ]!

Item was removed:
- ----- Method: TextDiffBuilderTest>>testIfSequence4 (in category 'tests') -----
- testIfSequence4
-
- | patch |
- patch := self patchSequenceFor: #(a b c d) and: #(d b c a).
- self assert: patch size = 6. "lcs is bc"
- self assert: (patch count: [ :each | each key = #match ]) = 2.
- self assert: (patch count: [ :each | each key = #insert ]) = 2.
- self assert: (patch count: [ :each | each key = #remove ]) = 2.
- patch do: [ :each |
- each key = #match
- ifTrue: [ self assert: ('bc' includes: each value first) ]
- ifFalse: [ self assert: ('ad' includes: each value first) ] ]!

Item was removed:
- ----- Method: EventManagerTest>>testRemoveActionsWithReceiver (in category 'running-remove actions') -----
- testRemoveActionsWithReceiver
-
- | action |
- eventSource
- when: #anEvent send: #size to: eventListener;
- when: #anEvent send: #getTrue to: self;
- when: #anEvent: send: #fizzbin to: self.
- eventSource removeActionsWithReceiver: self.
- action := eventSource actionForEvent: #anEvent.
- self assert: (action respondsTo: #receiver).
- self assert: ((action receiver == self) not)!

Item was removed:
- ----- Method: EventManagerTest>>testNoValueSupplierHasArguments (in category 'running-broadcast query') -----
- testNoValueSupplierHasArguments
-
- succeeded := eventSource
- triggerEvent: #needsValue:
- with: 'nelja'
- ifNotHandled: [true].
- self should: [succeeded]!

Item was removed:
- ----- Method: EventManagerTest>>testOneArgumentEvent (in category 'running-dependent action') -----
- testOneArgumentEvent
-
- eventSource when: #anEvent: send: #add: to: eventListener.
- eventSource triggerEvent: #anEvent: with: 9.
- self should: [eventListener includes: 9]!

Item was removed:
- ----- Method: SecureHashAlgorithmTest>>testExample2 (in category 'testing - examples') -----
- testExample2
-
- "This is the second example from the specification document (FIPS PUB 180-1)"
-
- hash := SecureHashAlgorithm new hashMessage:
- 'abcdbcdecdefdefgefghfghighijhijkijkljklmklmnlmnomnopnopq'.
- self assert: (hash = 16r84983E441C3BD26EBAAE4AA1F95129E5E54670F1).!

Item was removed:
- ----- Method: TextDiffBuilderTest>>testEmptySequences (in category 'tests') -----
- testEmptySequences
-
- | patch |
- patch := self patchSequenceFor: #() and: #().
- self assert: patch isEmpty!

Item was removed:
- ----- Method: ObjectFinalizerTests>>setUp (in category 'running') -----
- setUp
- super setUp.
- log := OrderedCollection new.!

Item was removed:
- ClassTestCase subclass: #EventManagerTest
- instanceVariableNames: 'eventSource eventListener succeeded'
- classVariableNames: ''
- poolDictionaries: ''
- category: 'System-Object Events-Tests'!