Skip to content

Commit

Permalink
Merge pull request #15654 from MarcusDenker/reduce-users-slotsFromString
Browse files Browse the repository at this point in the history
do not use #slotsFromString: / sharedVariablesFromString:
  • Loading branch information
MarcusDenker authored Dec 4, 2023
2 parents 30bf79b + 0da0cc0 commit 76910c2
Show file tree
Hide file tree
Showing 30 changed files with 79 additions and 129 deletions.
2 changes: 1 addition & 1 deletion src/Epicea-Tests/EpCodeChangeIntegrationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -140,7 +140,7 @@ EpCodeChangeIntegrationTest >> testInstanceVariableAddition [
{ #category : 'tests' }
EpCodeChangeIntegrationTest >> testInstanceVariableRemoval [

aClass := classFactory make: [ :aBuilder | aBuilder slotsFromString: 'x' ].
aClass := classFactory make: [ :aBuilder | aBuilder slots: #(x) ].

self assert: (self countLogEventsWith: EpClassModification) equals: 0.
aClass removeInstVarNamed: #x.
Expand Down
10 changes: 5 additions & 5 deletions src/Equals-Tests/TEqualityTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -27,7 +27,7 @@ TEqualityTest >> testSetContainsOnlyOneInstanceOfAClassWithIVs [
class := classFactory make: [ :aBuilder |
aBuilder
superclass: ComparableObjectForEqualityTest;
slotsFromString: 'x y' ].
slots: #(x y) ].
class compile: 'x: newX y: newY
x := newX.
y := newY'.
Expand Down Expand Up @@ -63,11 +63,11 @@ TEqualityTest >> testSetContainsTwoInstancesOfTwoDiffrentClassesWithIVs [
otherClass := classFactory make: [ :aBuilder |
aBuilder
superclass: ComparableObjectForEqualityTest;
slotsFromString: 'x y' ].
slots: #(x y) ].
yetAnotherClass := classFactory make: [ :aBuilder |
aBuilder
superclass: ComparableObjectForEqualityTest;
slotsFromString: 'x y' ].
slots: #(x y) ].
{
otherClass.
yetAnotherClass } do: [ :class |
Expand Down Expand Up @@ -106,7 +106,7 @@ TEqualityTest >> testTwoInstancesOfTheSameClassWithDifferentIvValuessAreNotEqual
class := classFactory make: [ :aBuilder |
aBuilder
superclass: ComparableObjectForEqualityTest;
slotsFromString: 'x y' ].
slots: #(x y) ].
class compile: 'x: newX y: newY
x := newX.
y := newY'.
Expand All @@ -133,7 +133,7 @@ TEqualityTest >> testTwoInstancesOfTheSameClassWithSameIvValuessAreEqual [
class := classFactory make: [ :aBuilder |
aBuilder
superclass: ComparableObjectForEqualityTest;
slotsFromString: 'x y' ].
slots: #(x y) ].
class compile: 'x: newX y: newY
x := newX.
y := newY'.
Expand Down
2 changes: 1 addition & 1 deletion src/Fuel-Core-Tests/FLBasicSerializationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -400,7 +400,7 @@ FLBasicSerializationTest >> testExceptions [
FLBasicSerializationTest >> testExecuteAfterMaterialization [

| anObject result aClass |
aClass := self classFactory silentlyMake: [ :aBuilder | aBuilder slotsFromString: 'a' ].
aClass := self classFactory silentlyMake: [ :aBuilder | aBuilder slots: #(a) ].
self classFactory silentlyCompile: 'fuelAfterMaterialization a := #A' in: aClass.
anObject := aClass new.

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -127,7 +127,7 @@ FLBlockClosureSerializationTest >> testBlockClosureChangeSameBytecodesConstant [
FLBlockClosureSerializationTest >> testBlockClosureMaterializesClassVariablesCorrectly [

| class closure method |
class := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariablesFromString: 'ClassVariableForTesting' ].
class := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariables: #(ClassVariableForTesting)].
self classFactory silentlyCompile: 'methodWithClosure ^ [ ClassVariableForTesting ]' in: class.

method := class methodNamed: #methodWithClosure.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -85,7 +85,7 @@ FLCompiledMethodSerializationTest >> testInstalledModified [
FLCompiledMethodSerializationTest >> testMethodAccessingAClassVariable [

| aClassWithVariable aMethod materializedMethod |
aClassWithVariable := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariablesFromString: 'A' ].
aClassWithVariable := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariables: #(A) ].

self classFactory silentlyCompile: 'm1 A:= 3' in: aClassWithVariable.
aMethod := aClassWithVariable >> #m1.
Expand All @@ -101,7 +101,7 @@ FLCompiledMethodSerializationTest >> testMethodAccessingAClassVariable [
FLCompiledMethodSerializationTest >> testMethodAccessingAClassVariableInADoit [

| aClassWithVariable aMethod materializedMethod |
aClassWithVariable := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariablesFromString: 'A' ].
aClassWithVariable := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariables: #(A)].

self classFactory silentlyCompile: 'DoIt A:= 3' in: aClassWithVariable.
aMethod := aClassWithVariable >> #DoIt.
Expand Down
2 changes: 1 addition & 1 deletion src/Fuel-Core-Tests/FLConfigurationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -362,7 +362,7 @@ FLConfigurationTest >> testStreamFinalizerDefault [

<ignoreNotImplementedSelectors: #( _log )>
| logClass log |
logClass := self classFactory silentlyMake: [ :aBuilder | aBuilder slotsFromString: 'log' ].
logClass := self classFactory silentlyMake: [ :aBuilder | aBuilder slots: #(log) ].
self classFactory
silentlyCompile: 'initialize log := OrderedCollection new' in: logClass;
silentlyCompile: '_log ^ log' in: logClass;
Expand Down
14 changes: 7 additions & 7 deletions src/Fuel-Core-Tests/FLCreateClassSerializationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -105,7 +105,7 @@ FLCreateClassSerializationTest >> testCreateClassWithClassVariable [
"Tests materialization a class not defined in the image, with a class variable."

| aClass materializedClass |
aClass := self classFactory make: [ :aBuilder | aBuilder sharedVariablesFromString: #ClassVariable ].
aClass := self classFactory make: [ :aBuilder | aBuilder sharedVariables: #(ClassVariable) ].
(aClass classVariableNamed: #ClassVariable) write: #test.

materializedClass := self resultOfSerializeRemoveAndMaterialize: aClass.
Expand Down Expand Up @@ -145,13 +145,13 @@ FLCreateClassSerializationTest >> testCreateClassWithCreatedTraitWithInstanceVar
The trait has instance variables."

| aClass aTrait result materializedClass materializedTrait materializedObject |
aClass := self classFactory silentlyMake: [ :aBuilder | aBuilder slotsFromString: 'ivar' ].
aClass := self classFactory silentlyMake: [ :aBuilder | aBuilder slots: #(ivar) ].
self classFactory silentlyCompile: 'ivar: x ivar := x' in: aClass.
self classFactory silentlyCompile: 'ivar ^ ivar' in: aClass.
aTrait := self classFactory silentlyMake: [ :aBuilder |
aBuilder
beTrait;
slotsFromString: 'traitIvar' ].
slots: #(traitIvar) ].
self classFactory silentlyCompile: 'traitIvar: x traitIvar := x' in: aTrait.
self classFactory silentlyCompile: 'traitIvar ^ traitIvar' in: aTrait.
aClass addToComposition: aTrait.
Expand Down Expand Up @@ -188,7 +188,7 @@ FLCreateClassSerializationTest >> testCreateClassWithInstance [
"Tests materialization of a class who references an instance of itself."

| aClass anInstance materializedClass materializedInstance |
aClass := self classFactory make: [ :aBuilder | aBuilder slotsFromString: 'name' ].
aClass := self classFactory make: [ :aBuilder | aBuilder slots: #(name) ].
aClass class instanceVariableNames: 'instance'.

anInstance := aClass new
Expand Down Expand Up @@ -272,7 +272,7 @@ FLCreateClassSerializationTest >> testCreateClassWithVariables [
"Tests materialization of a class not defined in the image, with instance variables."

| aClass materializedClass |
aClass := self classFactory make: [ :aBuilder | aBuilder slotsFromString: 'var1 var2' ].
aClass := self classFactory make: [ :aBuilder | aBuilder slots: #(var1 var2) ].

materializedClass := self resultOfSerializeRemoveAndMaterialize: aClass.

Expand Down Expand Up @@ -445,7 +445,7 @@ FLCreateClassSerializationTest >> testCreateWithClassVariableAccessors [
"Tests materialization of a compiled method in a class not defined in the image. The class defines accessors for a class variable."

| aClass materializedClass instance |
aClass := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariablesFromString: 'AnFLClassVariable' ].
aClass := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariables: #(AnFLClassVariable) ].
self classFactory
silentlyCompile: 'classVariable ^AnFLClassVariable' in: aClass;
silentlyCompile: 'classVariable: value AnFLClassVariable := value' in: aClass.
Expand Down Expand Up @@ -511,7 +511,7 @@ FLCreateClassSerializationTest >> testMaterializationDoesNotModifySerializedClas
"Tests that materialization does not change the source class."

| aClass materializedClass |
aClass := self classFactory make: [ :aBuilder | aBuilder slotsFromString: 'var' ].
aClass := self classFactory make: [ :aBuilder | aBuilder slots: #(var) ].

self serializer fullySerializeBehavior: aClass.
self serialize: aClass.
Expand Down
4 changes: 2 additions & 2 deletions src/Fuel-Core-Tests/FLFullBasicSerializationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -94,11 +94,11 @@ FLFullBasicSerializationTest >> testCreateClassWithChangedSuperclassFormat [
"Tests issue #221"

| a b |
a := self classFactory make: [ :aBuilder | aBuilder slotsFromString: 'one' ].
a := self classFactory make: [ :aBuilder | aBuilder slots: #(one) ].
b := self classFactory make: [ :aBuilder |
aBuilder
superclass: a;
slotsFromString: 'two' ].
slots: #(two) ].
self serializer fullySerializeBehavior: b.
self serialize: {
b new.
Expand Down
4 changes: 2 additions & 2 deletions src/Fuel-Core-Tests/FLFullHeaderSerializationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ FLFullHeaderSerializationTest >> testPostMaterializationActions [
| aClass |
CompilationContext optionCleanBlockClosure ifTrue: [ ^ self skip ].

aClass := self classFactory make: [ :aBuilder | aBuilder sharedVariablesFromString: 'TestClassVariable TestClassVariable2' ].
aClass := self classFactory make: [ :aBuilder | aBuilder sharedVariables: #(TestClassVariable TestClassVariable2) ].
self classFactory
silentlyCompile: 'postLoadMethod TestClassVariable := 1' in: aClass class;
silentlyCompile: 'postLoadMethod2 TestClassVariable := 2' in: aClass class;
Expand Down Expand Up @@ -72,7 +72,7 @@ FLFullHeaderSerializationTest >> testPreMaterializationActions [
| aClass |
CompilationContext optionCleanBlockClosure ifTrue: [ ^ self skip ].

aClass := self classFactory make: [ :aBuilder | aBuilder sharedVariablesFromString: 'TestClassVariable TestClassVariable2' ].
aClass := self classFactory make: [ :aBuilder | aBuilder sharedVariables: #(TestClassVariable TestClassVariable2) ].
self classFactory
silentlyCompile: 'postLoadMethod TestClassVariable := 1' in: aClass class;
silentlyCompile: 'postLoadMethod2 TestClassVariable := 2' in: aClass class;
Expand Down
4 changes: 2 additions & 2 deletions src/Fuel-Core-Tests/FLGlobalTraitSerializationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -18,13 +18,13 @@ FLGlobalTraitSerializationTest >> testCreateClassWithCreatedTraitWithInstanceVar
The trait has instance variables."

| aClass aTrait result materializedClass materializedTrait materializedObject |
aClass := self classFactory silentlyMake: [ :aBuilder | aBuilder slotsFromString: 'ivar' ].
aClass := self classFactory silentlyMake: [ :aBuilder | aBuilder slots: #(ivar) ].
self classFactory silentlyCompile: 'ivar: x ivar := x' in: aClass.
self classFactory silentlyCompile: 'ivar ^ ivar' in: aClass.
aTrait := self classFactory silentlyMake: [ :aBuilder |
aBuilder
beTrait;
slotsFromString: 'traitIvar' ].
slots: #(traitIvar) ].
self classFactory silentlyCompile: 'traitIvar: x traitIvar := x' in: aTrait.
self classFactory silentlyCompile: 'traitIvar ^ traitIvar' in: aTrait.
aClass addToComposition: aTrait.
Expand Down
4 changes: 2 additions & 2 deletions src/Fuel-Core-Tests/FLHeaderSerializationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ FLHeaderSerializationTest >> testPostMaterializationActions [
| aClass |
CompilationContext optionCleanBlockClosure ifTrue: [ ^ self skip ].

aClass := self classFactory make: [ :aBuilder | aBuilder sharedVariablesFromString: 'TestClassVariable TestClassVariable2' ].
aClass := self classFactory make: [ :aBuilder | aBuilder sharedVariables: #(TestClassVariable TestClassVariable2) ].
self classFactory
silentlyCompile: 'postLoadMethod TestClassVariable := 1' in: aClass class;
silentlyCompile: 'postLoadMethod2 TestClassVariable := 2' in: aClass class;
Expand Down Expand Up @@ -75,7 +75,7 @@ FLHeaderSerializationTest >> testPreMaterializationActions [
| aClass |
CompilationContext optionCleanBlockClosure ifTrue: [ ^ self skip ].

aClass := self classFactory make: [ :aBuilder | aBuilder sharedVariablesFromString: 'TestClassVariable TestClassVariable2' ].
aClass := self classFactory make: [ :aBuilder | aBuilder sharedVariables: #(TestClassVariable TestClassVariable2) ].
self classFactory
silentlyCompile: 'postLoadMethod TestClassVariable := 1' in: aClass class;
silentlyCompile: 'postLoadMethod2 TestClassVariable := 2' in: aClass class;
Expand Down
12 changes: 6 additions & 6 deletions src/Fuel-Core-Tests/FLHookedSubstitutionTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ FLHookedSubstitutionTest >> testAvoidRecursion [
FLHookedSubstitutionTest >> testClassWithCachedValueByNil [

| aClassWithCachedValue result original |
aClassWithCachedValue := self classFactory silentlyMake: [ :aBuilder | aBuilder slotsFromString: 'cache' ].
aClassWithCachedValue := self classFactory silentlyMake: [ :aBuilder | aBuilder slots: #(cache) ].
self classFactory
silentlyCompile: 'cache ^cache' in: aClassWithCachedValue;
silentlyCompile: 'cache: x cache := x' in: aClassWithCachedValue;
Expand Down Expand Up @@ -54,7 +54,7 @@ FLHookedSubstitutionTest >> testObjectByProxyThatBecomesItsContent [
"Tests a substitution of an object by a proxy that becomes another object on materialization."

| aProxyClass result |
aProxyClass := self classFactory silentlyMake: [ :aBuilder | aBuilder slotsFromString: 'someState' ].
aProxyClass := self classFactory silentlyMake: [ :aBuilder | aBuilder slots: #(someState) ].
self classFactory
silentlyCompile: 'initialize someState := 5@1' in: aProxyClass;
silentlyCompile: 'fuelAccept: aVisitor
Expand All @@ -72,7 +72,7 @@ FLHookedSubstitutionTest >> testObjectByProxyThatBecomesItsContent [
FLHookedSubstitutionTest >> testProxyByTarget [

| aProxyClass result original |
aProxyClass := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariablesFromString: 'Target' ].
aProxyClass := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariables: #(Target) ].
self classFactory
silentlyCompile: 'target: x Target := x' in: aProxyClass;
silentlyCompile: 'fuelAccept: aVisitor
Expand All @@ -94,7 +94,7 @@ FLHookedSubstitutionTest >> testProxyByTarget [
FLHookedSubstitutionTest >> testProxyByTargetAnalisysIsPropagated [

| aProxyClass result pair original |
aProxyClass := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariablesFromString: 'Target' ].
aProxyClass := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariables: #(Target) ].
self classFactory
silentlyCompile: 'target: x Target := x' in: aProxyClass;
silentlyCompile: 'fuelAccept: aVisitor
Expand Down Expand Up @@ -122,7 +122,7 @@ FLHookedSubstitutionTest >> testProxyByTargetAnalisysIsPropagated [
FLHookedSubstitutionTest >> testProxyByTargetInsideObjectAndAnalisysIsPropagated [

| aProxyClass result original pair pairRoot |
aProxyClass := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariablesFromString: 'Target' ].
aProxyClass := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariables: #(Target) ].
self classFactory
silentlyCompile: 'target: x Target := x' in: aProxyClass;
silentlyCompile: 'fuelAccept: aVisitor
Expand Down Expand Up @@ -154,7 +154,7 @@ FLHookedSubstitutionTest >> testProxyByTargetInsideObjectAndAnalisysIsPropagated
FLHookedSubstitutionTest >> testProxyInsideObjectByTarget [

| aProxyClass result original pair |
aProxyClass := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariablesFromString: 'Target' ].
aProxyClass := self classFactory silentlyMake: [ :aBuilder | aBuilder sharedVariables: #(Target) ].
self classFactory
silentlyCompile: 'target: x Target := x' in: aProxyClass;
silentlyCompile: 'fuelAccept: aVisitor
Expand Down
8 changes: 4 additions & 4 deletions src/Fuel-Core-Tests/FLIgnoredVariablesTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,7 @@ Class {
FLIgnoredVariablesTest >> testAllVariablesIgnored [

| anObject result aClass |
aClass := self classFactory make: [ :aBuilder | aBuilder slotsFromString: 'a b' ].
aClass := self classFactory make: [ :aBuilder | aBuilder slots: #(a b) ].
self classFactory silentlyCompile: 'fuelIgnoredInstanceVariableNames ^#(a b)' in: aClass class.
anObject := aClass new
instVarAt: 1 put: $A;
Expand All @@ -30,7 +30,7 @@ FLIgnoredVariablesTest >> testAllVariablesIgnored [
FLIgnoredVariablesTest >> testIgnoredValueIsNotMaterialized [

| anObject materialized aClass |
aClass := self classFactory make: [ :aBuilder | aBuilder slotsFromString: 'a' ].
aClass := self classFactory make: [ :aBuilder | aBuilder slots: #(a) ].
self classFactory silentlyCompile: 'fuelIgnoredInstanceVariableNames ^#(a)' in: aClass class.
anObject := aClass new
instVarAt: 1 put: #A;
Expand All @@ -46,7 +46,7 @@ FLIgnoredVariablesTest >> testIgnoredValueIsNotMaterialized [
FLIgnoredVariablesTest >> testOneIgnoredVariable [

| anObject result aClass |
aClass := self classFactory make: [ :aBuilder | aBuilder slotsFromString: 'a b c' ].
aClass := self classFactory make: [ :aBuilder | aBuilder slots: #(a b c) ].
self classFactory silentlyCompile: 'fuelIgnoredInstanceVariableNames ^#(b)' in: aClass class.
anObject := aClass new
instVarAt: 1 put: $A;
Expand All @@ -65,7 +65,7 @@ FLIgnoredVariablesTest >> testOneIgnoredVariable [
FLIgnoredVariablesTest >> testTwoIgnoredVariables [

| anObject result aClass |
aClass := self classFactory make: [ :aBuilder | aBuilder slotsFromString: 'a b c' ].
aClass := self classFactory make: [ :aBuilder | aBuilder slots: #(a b c) ].
self classFactory silentlyCompile: 'fuelIgnoredInstanceVariableNames ^#(a c)' in: aClass class.
anObject := aClass new
instVarAt: 1 put: $A;
Expand Down
Loading

0 comments on commit 76910c2

Please sign in to comment.