Skip to content

Commit

Permalink
chore: clean up tests
Browse files Browse the repository at this point in the history
  • Loading branch information
theseion committed Jan 18, 2025
1 parent abea8b6 commit db2889a
Show file tree
Hide file tree
Showing 4 changed files with 23 additions and 26 deletions.
24 changes: 12 additions & 12 deletions src/Fuel-Core-Tests/FLBlockClosureSerializationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -295,7 +295,7 @@ FLBlockClosureSerializationTest >> testBlockClosureWithThreeArguments [
FLBlockClosureSerializationTest >> testCleanBlockClosure [

| aClosure meterialized |
OCCompilationContext optionCleanBlockClosure ifFalse: [ ^ self skip ].
Smalltalk compiler compilationContext optionCleanBlockClosure ifFalse: [ ^ self skip ].

aClosure := [ :x | x objects detect: [ :y | y isInteger ] ].
self assert: aClosure isClean.
Expand All @@ -310,20 +310,11 @@ FLBlockClosureSerializationTest >> testCleanBlockClosure [
self assert: meterialized equals: 87
]

{ #category : 'tests-clean' }
FLBlockClosureSerializationTest >> testNestedBlockClosureConstant [
| closure materializedClosure |
closure := [ [ 42 ] ].
materializedClosure := self resultOfSerializeAndMaterialize: closure.
closure assertWellMaterializedInto: materializedClosure in: self.
self assert: materializedClosure value value equals: 42
]

{ #category : 'tests' }
FLBlockClosureSerializationTest >> testNestedCleanBlockClosure [
FLBlockClosureSerializationTest >> testNestedBlockClosureClean [

| aClosure meterialized |
OCCompilationContext optionCleanBlockClosure ifFalse: [ ^ self skip ].
Smalltalk compiler compilationContext optionCleanBlockClosure ifFalse: [ ^ self skip ].

aClosure := [ [ :x | x objects detect: [ :y | y isInteger ] ] ] value.
self assert: aClosure isClean.
Expand All @@ -337,3 +328,12 @@ FLBlockClosureSerializationTest >> testNestedCleanBlockClosure [

self assert: meterialized equals: 87
]

{ #category : 'tests-clean' }
FLBlockClosureSerializationTest >> testNestedBlockClosureConstant [
| closure materializedClosure |
closure := [ [ 42 ] ].
materializedClosure := self resultOfSerializeAndMaterialize: closure.
closure assertWellMaterializedInto: materializedClosure in: self.
self assert: materializedClosure value value equals: 42
]
15 changes: 6 additions & 9 deletions src/Fuel-Core-Tests/FLCreateClassSerializationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -349,20 +349,17 @@ FLCreateClassSerializationTest >> testCreateHierarchyWithExistingClasses [

{ #category : 'tests-bugs' }
FLCreateClassSerializationTest >> testCreateHierarchyWithSubclassSerializedBeforeSuperclass [
"Tests issue #210"
"Tests issue #210
See FLBehaviorCluster>>registerIndexesOn:"

| a b serializedClasses set |
| a b serializedClasses |
a := self classFactory silentlyNewClass.
b := self classFactory silentlyMake: [ :aBuilder | aBuilder superclass: a ].
serializedClasses := { a . b }.
"Behavior clusters use an FLLargeIdentitySet for their objects.
We need to be sure that the subclass is serialized before the superclass."
serializedClasses reversed withIndexDo: [ :class :index | self classFactory silentlyCompile: 'largeIdentityHash ^ ' , index asString in: class class ].
set := FLLargeIdentitySet new
addAll: serializedClasses;
yourself.
self assert: set asArray first identicalTo: b.

self shouldnt: [ self resultOfSerializeRemoveAndMaterializeAll: serializedClasses ] raise: MessageNotUnderstood.

serializedClasses := { b. a}.
self shouldnt: [ self resultOfSerializeRemoveAndMaterializeAll: serializedClasses ] raise: MessageNotUnderstood
]

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -67,7 +67,7 @@ FLFullBlockClosureSerializationTest >> testBlockClosureChangeDifferentBytecodesC
aClosure := aClass new perform: #methodWithClosure.
self assert: aClosure isClean.
self assertConstantBlockOuterContextBasedOnCompilationOption: aClosure.
OCCompilationContext optionConstantBlockClosure ifTrue: [
Smalltalk compiler compilationContext optionConstantBlockClosure ifTrue: [
self assert: aClosure class equals: (Smalltalk at: #ConstantBlockClosure) ].

self serializer fullySerializeMethod: aClosure compiledBlock method.
Expand Down Expand Up @@ -119,7 +119,7 @@ FLFullBlockClosureSerializationTest >> testBlockClosureChangeSameBytecodesConsta
aClosure := aClass new perform: #methodWithClosure.
self assert: aClosure isClean.
self assertConstantBlockOuterContextBasedOnCompilationOption: aClosure.
OCCompilationContext optionConstantBlockClosure ifTrue: [
Smalltalk compiler compilationContext optionConstantBlockClosure ifTrue: [
self assert: aClosure class equals: (Smalltalk at: #ConstantBlockClosure) ].

self serializer fullySerializeMethod: aClosure compiledBlock method.
Expand Down Expand Up @@ -168,7 +168,7 @@ FLFullBlockClosureSerializationTest >> testBlockClosureRemovedConstant [
aClosure := aClass new perform: #methodWithClosure.
self assert: aClosure isClean.
self assertConstantBlockOuterContextBasedOnCompilationOption: aClosure.
OCCompilationContext optionConstantBlockClosure ifTrue: [
Smalltalk compiler compilationContext optionConstantBlockClosure ifTrue: [
self assert: aClosure class equals: (Smalltalk at: #ConstantBlockClosure) ].

self serializer fullySerializeMethod: aClosure compiledBlock method.
Expand Down
4 changes: 2 additions & 2 deletions src/Fuel-Core-Tests/FLSerializationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -29,15 +29,15 @@ FLSerializationTest class >> resources [
{ #category : 'asserting' }
FLSerializationTest >> assertCleanBlockOuterContextBasedOnCompilationOption: aClosure [

OCCompilationContext optionCleanBlockClosure
Smalltalk compiler compilationContext optionCleanBlockClosure
ifTrue: [ self assert: aClosure outerContext isNil ]
ifFalse: [ self assert: aClosure outerContext isNotNil ]
]

{ #category : 'asserting' }
FLSerializationTest >> assertConstantBlockOuterContextBasedOnCompilationOption: aClosure [

OCCompilationContext optionConstantBlockClosure
Smalltalk compiler compilationContext optionConstantBlockClosure
ifTrue: [ self assert: aClosure outerContext isNil ]
ifFalse: [ self assert: aClosure outerContext isNotNil ]
]
Expand Down

0 comments on commit db2889a

Please sign in to comment.