Skip to content

Commit

Permalink
Merge pull request #20 from astares/resynch
Browse files Browse the repository at this point in the history
Resycnhronize to fix #14384 in pharoproject/pharo
  • Loading branch information
tesonep authored Oct 11, 2023
2 parents bddd7cd + 504c7b7 commit 25999ae
Show file tree
Hide file tree
Showing 31 changed files with 112 additions and 156 deletions.
32 changes: 16 additions & 16 deletions Hermes-Extensions/HEDuplicationModeStrategy.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -19,27 +19,27 @@ HEDuplicationModeStrategy class >> forOption: keyword [

{ #category : #'validating existence' }
HEDuplicationModeStrategy >> doExistingClass: aClass hermesClass: aHEClass installer: installer [
self subclassResponsibility
self subclassResponsibility
]

{ #category : #'validating existence' }
HEDuplicationModeStrategy >> doExistingTrait: aTrait hermesTrait: aHETrait installer: installer [
self subclassResponsibility
self subclassResponsibility
]

{ #category : #'validating existence' }
HEDuplicationModeStrategy >> doShouldBuildMethod: aHEMethod in: installer installer: aClass original: aMethod [
self subclassResponsibility
self subclassResponsibility
]

{ #category : #'validating existence' }
HEDuplicationModeStrategy >> existingClass: aHEClass on: installer [
^ installer environment
at: aHEClass className
ifPresent: [ :aClass |
self
doExistingClass: aClass
hermesClass: aHEClass
ifPresent: [ :aClass |
self
doExistingClass: aClass
hermesClass: aHEClass
installer: installer ]
ifAbsent: [ nil ]
]
Expand All @@ -48,10 +48,10 @@ HEDuplicationModeStrategy >> existingClass: aHEClass on: installer [
HEDuplicationModeStrategy >> existingTrait: aHETrait on: installer [
^ installer environment
at: aHETrait traitName
ifPresent: [ :aTrait |
self
doExistingTrait: aTrait
hermesTrait: aHETrait
ifPresent: [ :aTrait |
self
doExistingTrait: aTrait
hermesTrait: aHETrait
installer: installer ]
ifAbsent: [ nil ]
]
Expand All @@ -60,13 +60,13 @@ HEDuplicationModeStrategy >> existingTrait: aHETrait on: installer [
HEDuplicationModeStrategy >> shouldBuildMethod: aHEMethod in: aClass installer: installer [
^ aClass
compiledMethodAt: aHEMethod name
ifPresent: [ :m |
ifPresent: [ :m |
(m isFromTrait and: [ aClass isTrait not ])
ifTrue: [ ^ true ].
self
doShouldBuildMethod: aHEMethod
in: installer
installer: aClass
self
doShouldBuildMethod: aHEMethod
in: installer
installer: aClass
original: m]
ifAbsent: [ true ]
]
10 changes: 5 additions & 5 deletions Hermes-Extensions/HEExtendedInstaller.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -26,12 +26,12 @@ HEExtendedInstaller >> duplicationMode: anObject [

{ #category : #'validating existence' }
HEExtendedInstaller >> existingClass: aHEClass [
^ duplicationMode existingClass: aHEClass on: self.
^ duplicationMode existingClass: aHEClass on: self
]

{ #category : #'validating existence' }
HEExtendedInstaller >> existingTrait: aHETrait [
^ duplicationMode existingTrait: aHETrait on: self.
^ duplicationMode existingTrait: aHETrait on: self
]

{ #category : #accessing }
Expand All @@ -43,14 +43,14 @@ HEExtendedInstaller >> failOnUndeclared: anObject [
HEExtendedInstaller >> forOptions: aCommandLine [
failOnUndeclared := (aCommandLine hasOption: 'no-fail-on-undeclared') not.

duplicationMode := HEDuplicationModeStrategy forOption: (aCommandLine optionAt: 'on-duplication' ifAbsent: [ 'fail' ]).
duplicationMode := HEDuplicationModeStrategy forOption: (aCommandLine optionAt: 'on-duplication' ifAbsent: [ 'fail' ])
]

{ #category : #initialization }
HEExtendedInstaller >> initialize [
super initialize.
failOnUndeclared := true.
duplicationMode := HEFailOnDuplication new.
duplicationMode := HEFailOnDuplication new
]

{ #category : #'reporting undeclared' }
Expand All @@ -65,5 +65,5 @@ HEExtendedInstaller >> reportNewUndeclareds: newUndeclareds [

{ #category : #'validating existence' }
HEExtendedInstaller >> shouldBuildMethod: aHEMethod in: aClass [
^ duplicationMode shouldBuildMethod: aHEMethod in: aClass installer: self.
^ duplicationMode shouldBuildMethod: aHEMethod in: aClass installer: self
]
5 changes: 2 additions & 3 deletions Hermes/HEAdditionalMethodState.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ Class {

{ #category : #accessing }
HEAdditionalMethodState class >> tag [
^ 1.
^ 1
]

{ #category : #converting }
Expand All @@ -40,8 +40,7 @@ HEAdditionalMethodState >> asLiteralIn: env [
HEAdditionalMethodState >> doReadFrom: aReader [
method := HEExportedLiteral readFrom: aReader.
selector := HEExportedLiteral readFrom: aReader.
value := HEExportedLiteral readFrom: aReader.

value := HEExportedLiteral readFrom: aReader
]

{ #category : #accessing }
Expand Down
8 changes: 4 additions & 4 deletions Hermes/HEArray.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ Class {

{ #category : #accessing }
HEArray class >> tag [
^ 2.
^ 2
]

{ #category : #converting }
Expand All @@ -30,12 +30,12 @@ HEArray >> asLiteralIn: env [

{ #category : #reading }
HEArray >> doReadFrom: aReader [
| size |
| size |
"The size of the array is stored as a 32bits integer. Before any of the elements"
size := aReader readInt32.
value := Array new:size.
1 to:size do:[:idx | value at:idx put: (HEExportedLiteral readFrom: aReader)].

1 to:size do:[:idx | value at:idx put: (HEExportedLiteral readFrom: aReader)]
]

{ #category : #accessing }
Expand Down
5 changes: 2 additions & 3 deletions Hermes/HEAssociation.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -26,12 +26,11 @@ HEAssociation >> asLiteralIn: env [
{ #category : #reading }
HEAssociation >> doReadFrom: aReader [
key := HEExportedLiteral readFrom: aReader.
value := HEExportedLiteral readFrom: aReader.

value := HEExportedLiteral readFrom: aReader
]

{ #category : #accessing }
HEAssociation >> value: anAssociation [
value := anAssociation value asExportedLiteral.
key := anAssociation key asExportedLiteral.
key := anAssociation key asExportedLiteral
]
6 changes: 3 additions & 3 deletions Hermes/HEBinaryReader.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ Class {

{ #category : #initialization }
HEBinaryReader >> close [
self stream close.
self stream close
]

{ #category : #sizes }
Expand All @@ -40,7 +40,7 @@ HEBinaryReader >> readByte [
{ #category : #reading }
HEBinaryReader >> readByteArray [
| byteArray size |
size := self readInt32.
size := self readInt32.
byteArray := stream next: size.
^ byteArray
]
Expand All @@ -52,7 +52,7 @@ HEBinaryReader >> readByteString [

{ #category : #reading }
HEBinaryReader >> readByteSymbol [
^ self readByteString asSymbol
^ self readByteString asSymbol
]

{ #category : #reading }
Expand Down
2 changes: 1 addition & 1 deletion Hermes/HEByteArray.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -21,5 +21,5 @@ HEByteArray >> asLiteralIn: env [

{ #category : #reading }
HEByteArray >> doReadFrom: aReader [
value := aReader readByteArray.
value := aReader readByteArray
]
6 changes: 3 additions & 3 deletions Hermes/HEByteString.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ Class {

{ #category : #accessing }
HEByteString class >> tag [
^ 4.
^ 4
]

{ #category : #converting }
Expand All @@ -22,10 +22,10 @@ HEByteString >> asLiteralIn: env [
{ #category : #reading }
HEByteString >> doConvertValue: aValue [
"My subclasses are able to do something else to convert the readed value"
^ aValue.
^ aValue
]

{ #category : #reading }
HEByteString >> doReadFrom: aReader [
value := self doConvertValue:(aReader readByteString).
value := self doConvertValue:(aReader readByteString)
]
4 changes: 2 additions & 2 deletions Hermes/HECharacter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ Class {

{ #category : #accessing }
HECharacter class >> tag [
^ 5.
^ 5
]

{ #category : #converting }
Expand All @@ -22,5 +22,5 @@ HECharacter >> asLiteralIn: env [

{ #category : #accessing }
HECharacter >> value: aValue [
value := aValue asString.
value := aValue asString
]
2 changes: 1 addition & 1 deletion Hermes/HEClass.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -97,7 +97,7 @@ HEClass >> layoutClass: anObject [

{ #category : #accessing }
HEClass >> name [

^ self className
]

Expand Down
2 changes: 1 addition & 1 deletion Hermes/HEClassTrait.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -23,5 +23,5 @@ HEClassTrait >> asLiteralIn: env [

{ #category : #accessing }
HEClassTrait >> value: aClassTrait [
value := aClassTrait instanceSide name.
value := aClassTrait instanceSide name
]
6 changes: 3 additions & 3 deletions Hermes/HEClassVariable.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -13,16 +13,16 @@ Class {

{ #category : #accessing }
HEClassVariable class >> tag [
^ 6.
^ 6
]

{ #category : #converting }
HEClassVariable >> asLiteralIn: env [
"I ask the binding to the class that is currently being deserialized"
^ env newClass bindingOf: value
^ env newClass bindingOf: value
]

{ #category : #accessing }
HEClassVariable >> value: aClassVariable [
value := aClassVariable name.
value := aClassVariable name
]
8 changes: 4 additions & 4 deletions Hermes/HECompiledBlock.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -22,12 +22,12 @@ HECompiledBlock class >> tag [
HECompiledBlock >> asLiteralIn: anEnvironment [

| containingBlockOrMethod newBlock literalSpace previousBlock|

previousBlock := anEnvironment newBlock.
containingBlockOrMethod := previousBlock ifNil: [ anEnvironment newMethod ].

newBlock := CompiledBlock newMethod: bytecode size header: (self headerFor: anEnvironment).

anEnvironment newBlock: newBlock.

literals
Expand Down Expand Up @@ -66,7 +66,7 @@ HECompiledBlock >> headerFor: anEnvironment [
| encoderClass|
"When a method is deserialized its header should be recalculated"
encoderClass := anEnvironment classNamed: encoderClassName.

^ (CompiledMethod headerFlagForEncoder: encoderClass) + (numArgs bitShift: 24) + (numTemps bitShift: 18) + literals size + (hasPrimitive bitShift: 16)
]

Expand Down
2 changes: 1 addition & 1 deletion Hermes/HEConstantBlock.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ HEConstantBlock >> doReadFrom: aReader [

numArgs := aReader readUInt32.
literal := HEExportedLiteral readFrom: aReader.
compiledBlock := HEExportedLiteral readFrom: aReader.
compiledBlock := HEExportedLiteral readFrom: aReader
]

{ #category : #comparing }
Expand Down
2 changes: 1 addition & 1 deletion Hermes/HEExportedLiteral.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ HEExportedLiteral >> asLiteralIn: anEnvironment [
{ #category : #reading }
HEExportedLiteral >> doReadFrom: aReader [
"Main template method to read the instance from the reader stream"
self subclassResponsibility.
self subclassResponsibility
]

{ #category : #accessing }
Expand Down
2 changes: 1 addition & 1 deletion Hermes/HEExportedMetaclass.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -23,5 +23,5 @@ HEExportedMetaclass >> asLiteralIn: env [

{ #category : #accessing }
HEExportedMetaclass >> value: aMetaclass [
value := aMetaclass instanceSide name.
value := aMetaclass instanceSide name
]
8 changes: 4 additions & 4 deletions Hermes/HEFloat.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -14,12 +14,12 @@ Class {

{ #category : #accessing }
HEFloat class >> tag [
^ 3.
^ 3
]

{ #category : #converting }
HEFloat >> asLiteralIn: env [
^ value.
^ value
]

{ #category : #reading }
Expand All @@ -28,7 +28,7 @@ HEFloat >> doReadFrom: aReader [
originalValue := BoxedFloat64 new.
originalValue at:1 put: (aReader readUInt32).
originalValue at:2 put: (aReader readUInt32).

"Force the conversion to SmallFloat64 or BoxedFloat64"
value := originalValue - 0.0.
value := originalValue - 0.0
]
6 changes: 3 additions & 3 deletions Hermes/HEFraction.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ Class {
}

{ #category : #accessing }
HEFraction class >> tag [
HEFraction class >> tag [
^ 24
]

Expand All @@ -23,6 +23,6 @@ HEFraction >> doReadFrom: aReader [
| denominator numerator |
numerator := HEExportedLiteral readFrom: aReader.
denominator := HEExportedLiteral readFrom: aReader.
value := Fraction numerator: numerator value denominator: denominator value.

value := Fraction numerator: numerator value denominator: denominator value
]
8 changes: 4 additions & 4 deletions Hermes/HEGlobalVariable.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -14,20 +14,20 @@ Class {

{ #category : #accessing }
HEGlobalVariable class >> tag [
^ 7.
^ 7
]

{ #category : #converting }
HEGlobalVariable >> asLiteralIn: env [
| bind |
bind := env newClass bindingOf: value.

bind ifNotNil: [ ^ bind ].

^UndeclaredVariable registeredWithName: value
]

{ #category : #accessing }
HEGlobalVariable >> value: aClassVariable [
value := aClassVariable name.
value := aClassVariable name
]
Loading

0 comments on commit 25999ae

Please sign in to comment.