diff --git a/src/Collections-Support/WeakKeyAssociation.class.st b/src/Collections-Support/WeakKeyAssociation.class.st index b576c0c6dcf..fab74dd3eb4 100644 --- a/src/Collections-Support/WeakKeyAssociation.class.st +++ b/src/Collections-Support/WeakKeyAssociation.class.st @@ -113,7 +113,7 @@ WeakKeyAssociation >> printOn: aStream [ { #category : #printing } WeakKeyAssociation >> storeOn: aStream [ - "Store in the format (key->value)" + "Store in the format (WeakKeyAssociation key: theKey value: theValue)" aStream nextPut: $(; nextPutAll: self class name. diff --git a/src/Collections-Tests/AssociationTest.class.st b/src/Collections-Tests/AssociationTest.class.st index 36a1ed2f075..432604aac7e 100644 --- a/src/Collections-Tests/AssociationTest.class.st +++ b/src/Collections-Tests/AssociationTest.class.st @@ -55,3 +55,22 @@ AssociationTest >> testIsSelfEvaluating [ description: 'a self evaluating should evaluate as self']. ] + +{ #category : #tests } +AssociationTest >> testStoreOnNegativeInteger [ + | association storeString | + association := 'a'-> -1. + + storeString := String streamContents: [ :s | association storeOn: s ]. + + self assert: storeString equals: '(''a''-> -1)' +] + +{ #category : #tests } +AssociationTest >> testStoreOnPositiveInteger [ + | association storeString | + association := 'a'-> 1. + storeString := String streamContents: [ :s | association storeOn: s ]. + + self assert: storeString equals: '(''a''->1)' +] diff --git a/src/Collections-Tests/DictionaryTest.class.st b/src/Collections-Tests/DictionaryTest.class.st index e3f48633e6a..2f545dfa17d 100644 --- a/src/Collections-Tests/DictionaryTest.class.st +++ b/src/Collections-Tests/DictionaryTest.class.st @@ -719,6 +719,16 @@ DictionaryTest >> testSelectIsNotShallowCopy [ description: 'modifying a selection should not modify the original' ] +{ #category : #'tests - printing' } +DictionaryTest >> testStoreOnWithNegativeInteger [ + | dictionary | + dictionary := { 'x' -> -1 } as: self classToBeTested. + + self + assert: (String streamContents: [ :s | dictionary storeOn: s ]) + equals: '((',self classToBeTested name,' new) add: (''x''-> -1); yourself)' +] + { #category : #requirements } DictionaryTest >> valueNotIn [ " return a value not included in nonEmpty " diff --git a/src/Collections-Tests/SmallDictionaryTest.class.st b/src/Collections-Tests/SmallDictionaryTest.class.st index f1312b701ab..e9358ad11d2 100644 --- a/src/Collections-Tests/SmallDictionaryTest.class.st +++ b/src/Collections-Tests/SmallDictionaryTest.class.st @@ -23,5 +23,5 @@ SmallDictionaryTest >> classToBeTested [ SmallDictionaryTest >> testStoreOn [ "self debug: #testStoreOn" - self assert: self nonEmptyDict storeString = ('((', self nonEmptyDict class printString , ' new) add: (#a->1); add: (#b->30); add: (#c->1); add: (#d->-2); yourself)') + self assert: self nonEmptyDict storeString = ('((', self nonEmptyDict class printString , ' new) add: (#a->1); add: (#b->30); add: (#c->1); add: (#d-> -2); yourself)') ] diff --git a/src/Collections-Tests/WeakKeyDictionaryTest.class.st b/src/Collections-Tests/WeakKeyDictionaryTest.class.st index 6327f30d7ed..d75653cd561 100644 --- a/src/Collections-Tests/WeakKeyDictionaryTest.class.st +++ b/src/Collections-Tests/WeakKeyDictionaryTest.class.st @@ -114,3 +114,13 @@ WeakKeyDictionaryTest >> testGrow [ "Keys are gone but not yet finalized." dict grow. ] + +{ #category : #'tests - printing' } +WeakKeyDictionaryTest >> testStoreOnWithNegativeInteger [ + | dictionary | + dictionary := { 'x' -> -1 } as: self classToBeTested. + + self + assert: (String streamContents: [ :s | dictionary storeOn: s ]) + equals: '((',self classToBeTested name,' new) add: (WeakKeyAssociation key: ''x'' value: -1); yourself)' +] diff --git a/src/Kernel-Tests-WithCompiler/AssociationTest.extension.st b/src/Kernel-Tests-WithCompiler/AssociationTest.extension.st new file mode 100644 index 00000000000..f1352f243dd --- /dev/null +++ b/src/Kernel-Tests-WithCompiler/AssociationTest.extension.st @@ -0,0 +1,24 @@ +Extension { #name : #AssociationTest } + +{ #category : #'*Kernel-Tests-WithCompiler' } +AssociationTest >> testStoreOnNegativeIntegerRoundtrip [ + | association storeString evaluated | + association := 'a'-> -1. + + storeString := String streamContents: [ :s | association storeOn: s ]. + + evaluated := Compiler evaluate: storeString. + + self assert: association equals: evaluated +] + +{ #category : #'*Kernel-Tests-WithCompiler' } +AssociationTest >> testStoreOnPositiveIntegerRoundtrip [ + | association storeString evaluated | + association := 'a'-> 1. + storeString := String streamContents: [ :s | association storeOn: s ]. + + evaluated := Compiler evaluate: storeString. + + self assert: association equals: evaluated +] diff --git a/src/Kernel-Tests-WithCompiler/SmallDictionaryTest.extension.st b/src/Kernel-Tests-WithCompiler/SmallDictionaryTest.extension.st new file mode 100644 index 00000000000..407ba8e4b2e --- /dev/null +++ b/src/Kernel-Tests-WithCompiler/SmallDictionaryTest.extension.st @@ -0,0 +1,15 @@ +Extension { #name : #SmallDictionaryTest } + +{ #category : #'*Kernel-Tests-WithCompiler' } +SmallDictionaryTest >> testStoreOnRoundTrip [ + | dictionary storeString evalutated | + dictionary := self classToBeTested new. + dictionary + add: #a -> 1; + add: #b -> 30; + add: #c -> 1; + add: #d -> -2. + storeString := String streamContents: [ :s | dictionary storeOn: s ]. + evalutated := Compiler evaluate: storeString. + self assert: dictionary equals: evalutated +] diff --git a/src/Kernel-Tests/FloatTest.class.st b/src/Kernel-Tests/FloatTest.class.st index 11446124add..8afd069abc3 100644 --- a/src/Kernel-Tests/FloatTest.class.st +++ b/src/Kernel-Tests/FloatTest.class.st @@ -960,6 +960,18 @@ FloatTest >> testStoreBase16 [ description: 'the radix prefix should not be omitted, except in base 10' ] +{ #category : #'tests - printing' } +FloatTest >> testStoreOn [ + | float | + float := -1.2. + + self assert: (String streamContents: [ :s | float storeOn: s ]) equals: ' -1.2'. + + float := 1.2. + + self assert: (String streamContents: [ :s | float storeOn: s ]) equals: '1.2' +] + { #category : #'tests - conversion' } FloatTest >> testStringAsNumber [ "This covers parsing in Number>>readFrom:" diff --git a/src/Kernel-Tests/IntegerTest.class.st b/src/Kernel-Tests/IntegerTest.class.st index 7b0b0405035..6bfeebb5238 100644 --- a/src/Kernel-Tests/IntegerTest.class.st +++ b/src/Kernel-Tests/IntegerTest.class.st @@ -1535,6 +1535,18 @@ IntegerTest >> testSqrtFloor [ ] +{ #category : #'tests - printing' } +IntegerTest >> testStoreOn [ + | integer | + integer := 42. + + self assert: (String streamContents: [ :s | integer storeOn: s ]) equals: '42'. + + integer := -42. + + self assert: (String streamContents: [ :s | integer storeOn: s ]) equals: ' -42'. +] + { #category : #'tests - instance creation' } IntegerTest >> testStringAsNumber [ "This covers parsing in Number>>readFrom: diff --git a/src/Kernel-Tests/LargeNegativeIntegerTest.class.st b/src/Kernel-Tests/LargeNegativeIntegerTest.class.st index 438aef5393d..8165b362e9a 100644 --- a/src/Kernel-Tests/LargeNegativeIntegerTest.class.st +++ b/src/Kernel-Tests/LargeNegativeIntegerTest.class.st @@ -17,3 +17,12 @@ LargeNegativeIntegerTest >> testEmptyTemplate [ self assert: i printString = '-0'. self assert: i normalize = 0 ] + +{ #category : #'tests-printing' } +LargeNegativeIntegerTest >> testStoreOn [ + | integer | + integer := -1073741825. + self + assert: integer class equals: LargeNegativeInteger; + assert: (String streamContents: [ :s | integer storeOn: s ]) equals: ' -1073741825'. +] diff --git a/src/Kernel-Tests/LargePositiveIntegerTest.class.st b/src/Kernel-Tests/LargePositiveIntegerTest.class.st index bafbf55ab91..2807be5b4d3 100644 --- a/src/Kernel-Tests/LargePositiveIntegerTest.class.st +++ b/src/Kernel-Tests/LargePositiveIntegerTest.class.st @@ -65,3 +65,12 @@ LargePositiveIntegerTest >> testNormalize [ self should: ((SmallInteger minVal - 1 + 1) == SmallInteger minVal). self assert: (SmallInteger minVal - 3 + 6) == (SmallInteger minVal+3). ] + +{ #category : #'tests-printing' } +LargePositiveIntegerTest >> testStoreOn [ + | integer | + integer := 1073741824. + self + assert: integer class equals: LargePositiveInteger; + assert: (String streamContents: [ :s | integer storeOn: s ]) equals: '1073741824'. +] diff --git a/src/Kernel/Float.class.st b/src/Kernel/Float.class.st index 9eee84604db..cd3765ff468 100644 --- a/src/Kernel/Float.class.st +++ b/src/Kernel/Float.class.st @@ -1404,7 +1404,7 @@ Float >> storeOn: aStream [ Float >> storeOn: aStream base: base [ "Print the Number exactly so it can be interpreted back unchanged" self isFinite - ifTrue: [self signBit = 1 ifTrue: [aStream nextPutAll: '-']. + ifTrue: [self signBit = 1 ifTrue: [aStream nextPutAll: ' -']. base = 10 ifFalse: [aStream print: base; nextPut: $r]. self = 0.0 ifTrue: [aStream nextPutAll: '0.0'] diff --git a/src/Kernel/Integer.class.st b/src/Kernel/Integer.class.st index f67d49db5bf..61fe57ea7a0 100644 --- a/src/Kernel/Integer.class.st +++ b/src/Kernel/Integer.class.st @@ -2038,6 +2038,14 @@ Integer >> sqrtFloor [ ^guess ] +{ #category : #printing } +Integer >> storeOn: aStream [ + self < 0 + ifTrue: [ aStream space ]. + + super storeOn: aStream. +] + { #category : #'printing-numerative' } Integer >> storeOn: aStream base: base [ "Print a representation of the receiver on the stream