diff --git a/Hermes-Extensions/HEDuplicationModeStrategy.class.st b/Hermes-Extensions/HEDuplicationModeStrategy.class.st index b2f97a1..06c347e 100644 --- a/Hermes-Extensions/HEDuplicationModeStrategy.class.st +++ b/Hermes-Extensions/HEDuplicationModeStrategy.class.st @@ -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 ] ] @@ -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 ] ] @@ -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 ] ] diff --git a/Hermes-Extensions/HEExtendedInstaller.class.st b/Hermes-Extensions/HEExtendedInstaller.class.st index 84ad7d9..d86fece 100644 --- a/Hermes-Extensions/HEExtendedInstaller.class.st +++ b/Hermes-Extensions/HEExtendedInstaller.class.st @@ -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 } @@ -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' } @@ -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 ] diff --git a/Hermes/HEAdditionalMethodState.class.st b/Hermes/HEAdditionalMethodState.class.st index 28188ad..ab34c50 100644 --- a/Hermes/HEAdditionalMethodState.class.st +++ b/Hermes/HEAdditionalMethodState.class.st @@ -21,7 +21,7 @@ Class { { #category : #accessing } HEAdditionalMethodState class >> tag [ - ^ 1. + ^ 1 ] { #category : #converting } @@ -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 } diff --git a/Hermes/HEArray.class.st b/Hermes/HEArray.class.st index 9d447d8..0a695ef 100644 --- a/Hermes/HEArray.class.st +++ b/Hermes/HEArray.class.st @@ -19,7 +19,7 @@ Class { { #category : #accessing } HEArray class >> tag [ - ^ 2. + ^ 2 ] { #category : #converting } @@ -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 } diff --git a/Hermes/HEAssociation.class.st b/Hermes/HEAssociation.class.st index a864c62..17ecf0a 100644 --- a/Hermes/HEAssociation.class.st +++ b/Hermes/HEAssociation.class.st @@ -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 ] diff --git a/Hermes/HEBinaryReader.class.st b/Hermes/HEBinaryReader.class.st index fd782fe..8ef7202 100644 --- a/Hermes/HEBinaryReader.class.st +++ b/Hermes/HEBinaryReader.class.st @@ -24,7 +24,7 @@ Class { { #category : #initialization } HEBinaryReader >> close [ - self stream close. + self stream close ] { #category : #sizes } @@ -40,7 +40,7 @@ HEBinaryReader >> readByte [ { #category : #reading } HEBinaryReader >> readByteArray [ | byteArray size | - size := self readInt32. + size := self readInt32. byteArray := stream next: size. ^ byteArray ] @@ -52,7 +52,7 @@ HEBinaryReader >> readByteString [ { #category : #reading } HEBinaryReader >> readByteSymbol [ - ^ self readByteString asSymbol + ^ self readByteString asSymbol ] { #category : #reading } diff --git a/Hermes/HEByteArray.class.st b/Hermes/HEByteArray.class.st index b5fe2f5..ad42757 100644 --- a/Hermes/HEByteArray.class.st +++ b/Hermes/HEByteArray.class.st @@ -21,5 +21,5 @@ HEByteArray >> asLiteralIn: env [ { #category : #reading } HEByteArray >> doReadFrom: aReader [ - value := aReader readByteArray. + value := aReader readByteArray ] diff --git a/Hermes/HEByteString.class.st b/Hermes/HEByteString.class.st index 7769a3c..ac04538 100644 --- a/Hermes/HEByteString.class.st +++ b/Hermes/HEByteString.class.st @@ -11,7 +11,7 @@ Class { { #category : #accessing } HEByteString class >> tag [ - ^ 4. + ^ 4 ] { #category : #converting } @@ -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) ] diff --git a/Hermes/HECharacter.class.st b/Hermes/HECharacter.class.st index 410148e..f0724de 100644 --- a/Hermes/HECharacter.class.st +++ b/Hermes/HECharacter.class.st @@ -12,7 +12,7 @@ Class { { #category : #accessing } HECharacter class >> tag [ - ^ 5. + ^ 5 ] { #category : #converting } @@ -22,5 +22,5 @@ HECharacter >> asLiteralIn: env [ { #category : #accessing } HECharacter >> value: aValue [ - value := aValue asString. + value := aValue asString ] diff --git a/Hermes/HEClass.class.st b/Hermes/HEClass.class.st index 203095c..950cc25 100644 --- a/Hermes/HEClass.class.st +++ b/Hermes/HEClass.class.st @@ -97,7 +97,7 @@ HEClass >> layoutClass: anObject [ { #category : #accessing } HEClass >> name [ - + ^ self className ] diff --git a/Hermes/HEClassTrait.class.st b/Hermes/HEClassTrait.class.st index 17c289b..3458b10 100644 --- a/Hermes/HEClassTrait.class.st +++ b/Hermes/HEClassTrait.class.st @@ -23,5 +23,5 @@ HEClassTrait >> asLiteralIn: env [ { #category : #accessing } HEClassTrait >> value: aClassTrait [ - value := aClassTrait instanceSide name. + value := aClassTrait instanceSide name ] diff --git a/Hermes/HEClassVariable.class.st b/Hermes/HEClassVariable.class.st index da2cffa..6442b82 100644 --- a/Hermes/HEClassVariable.class.st +++ b/Hermes/HEClassVariable.class.st @@ -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 ] diff --git a/Hermes/HECompiledBlock.class.st b/Hermes/HECompiledBlock.class.st index 774c29f..5987b27 100644 --- a/Hermes/HECompiledBlock.class.st +++ b/Hermes/HECompiledBlock.class.st @@ -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 @@ -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) ] diff --git a/Hermes/HEConstantBlock.class.st b/Hermes/HEConstantBlock.class.st index c180aaf..86f80df 100644 --- a/Hermes/HEConstantBlock.class.st +++ b/Hermes/HEConstantBlock.class.st @@ -30,7 +30,7 @@ HEConstantBlock >> doReadFrom: aReader [ numArgs := aReader readUInt32. literal := HEExportedLiteral readFrom: aReader. - compiledBlock := HEExportedLiteral readFrom: aReader. + compiledBlock := HEExportedLiteral readFrom: aReader ] { #category : #comparing } diff --git a/Hermes/HEExportedLiteral.class.st b/Hermes/HEExportedLiteral.class.st index f8ec346..6477634 100644 --- a/Hermes/HEExportedLiteral.class.st +++ b/Hermes/HEExportedLiteral.class.st @@ -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 } diff --git a/Hermes/HEExportedMetaclass.class.st b/Hermes/HEExportedMetaclass.class.st index 92c8122..8ebdd5f 100644 --- a/Hermes/HEExportedMetaclass.class.st +++ b/Hermes/HEExportedMetaclass.class.st @@ -23,5 +23,5 @@ HEExportedMetaclass >> asLiteralIn: env [ { #category : #accessing } HEExportedMetaclass >> value: aMetaclass [ - value := aMetaclass instanceSide name. + value := aMetaclass instanceSide name ] diff --git a/Hermes/HEFloat.class.st b/Hermes/HEFloat.class.st index 16470f9..257e34a 100644 --- a/Hermes/HEFloat.class.st +++ b/Hermes/HEFloat.class.st @@ -14,12 +14,12 @@ Class { { #category : #accessing } HEFloat class >> tag [ - ^ 3. + ^ 3 ] { #category : #converting } HEFloat >> asLiteralIn: env [ - ^ value. + ^ value ] { #category : #reading } @@ -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 ] diff --git a/Hermes/HEFraction.class.st b/Hermes/HEFraction.class.st index 66d33c5..9eadb4a 100644 --- a/Hermes/HEFraction.class.st +++ b/Hermes/HEFraction.class.st @@ -9,7 +9,7 @@ Class { } { #category : #accessing } -HEFraction class >> tag [ +HEFraction class >> tag [ ^ 24 ] @@ -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 ] diff --git a/Hermes/HEGlobalVariable.class.st b/Hermes/HEGlobalVariable.class.st index de093fb..ec54650 100644 --- a/Hermes/HEGlobalVariable.class.st +++ b/Hermes/HEGlobalVariable.class.st @@ -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 ] diff --git a/Hermes/HEInstaller.class.st b/Hermes/HEInstaller.class.st index 3e59b58..afb1972 100644 --- a/Hermes/HEInstaller.class.st +++ b/Hermes/HEInstaller.class.st @@ -71,45 +71,10 @@ HEInstaller >> build: aHEClass [ sharedPools: aHEClass sharedPools; category: aHEClass category; classSlots: (self asSlots: aHEClass classInstancevariables) ]. - - self processTraitsFrom: aHEClass in: newClass. - - ^newClass. - -] -{ #category : #'creating traits' } -HEInstaller >> buildTrait: aTraitDefinition [ - | newTrait traitComposition traitClass| - - (self existingTrait: aTraitDefinition) ifNotNil: [:x | ^ x ]. - - traitClass := Smalltalk globals at: #Trait ifAbsent: [ self error: 'Trait support is not installed' ]. - - traitComposition := self buildTraitCompositionFor: aTraitDefinition traitComposition. - - newTrait := traitClass - named: aTraitDefinition traitName - uses: traitComposition - package: aTraitDefinition category - env: environment. - - newTrait classTrait traitComposition: (self buildTraitCompositionFor: aTraitDefinition classTraitComposition). - - ^ newTrait -] - -{ #category : #'creating traits' } -HEInstaller >> buildTraitCompositionFor: traitComposition [ + self processTraitsFrom: aHEClass in: newClass. - | aLiteral | - - aLiteral := (traitComposition asLiteralIn: environment). - aLiteral isArray - ifTrue: [ ^ aLiteral - ifEmpty: [ TaEmptyComposition new ] - ifNotEmpty: [ TaSequence withAll: (aLiteral collect: [:each | each asTraitComposition]) ] ] - ifFalse: [ ^ aLiteral asTraitComposition ] + ^newClass ] { #category : #accessing } @@ -120,7 +85,7 @@ HEInstaller >> classNamed: aSymbol [ { #category : #'reporting undeclared' } HEInstaller >> createdUndeclared [ - ^ (Undeclared associations reject: [ :asoc | originalUndeclareds associations includes: asoc]) asDictionary + ^ (Undeclared associations reject: [ :asoc | originalUndeclareds associations includes: asoc]) asDictionary ] { #category : #'installing package' } @@ -128,7 +93,7 @@ HEInstaller >> doInstallPackage: aHEPackage [ | newTraits newClasses | "Creating the package. It requires a number of steps. 1. Register the package in the organizer." - RPackageOrganizer default registerPackageNamed: aHEPackage packageName. + self packageOrganizer ensurePackage: aHEPackage packageName. "2. Install the traits" newTraits := aHEPackage traits collect: [ :exportedTrait | self buildTrait: exportedTrait ]. @@ -145,7 +110,7 @@ HEInstaller >> doInstallPackage: aHEPackage [ "6. Install extension methods" aHEPackage extensionMethods do: [ :e | self installExtensionMethod: e ]. - + "7. After all I validate if there are no new undeclared variables created in the environment. A new undeclared is a sign of an improper modularization." self validateNoNewUndeclared @@ -171,10 +136,10 @@ HEInstaller >> existingClass: aHEClass [ { #category : #'validating existence' } HEInstaller >> existingTrait: aHETrait [ - (environment includesKey: aHETrait traitName) ifTrue:[ + (environment includesKey: aHETrait traitName) ifTrue:[ self error: (self messageExistingTrait: aHETrait) ]. - + ^nil ] @@ -182,17 +147,17 @@ HEInstaller >> existingTrait: aHETrait [ HEInstaller >> initialize [ environment := self class environment. originalUndeclareds := Undeclared copy. - hasTraits := Smalltalk globals hasClassNamed: #Trait. + hasTraits := Smalltalk globals hasClassNamed: #Trait ] { #category : #'installing methods' } HEInstaller >> installExtensionMethod: extensionMethod [ | aClass | aClass := self environment classNamed: extensionMethod className. - + aClass ifNil: [ self error: 'Required class named: ' , extensionMethod className, ' does not exists.' ]. - - self rebuildMethod: extensionMethod into: aClass. + + self rebuildMethod: extensionMethod into: aClass ] { #category : #'installing methods' } @@ -205,10 +170,9 @@ HEInstaller >> installMethods: exportedClass into: aClass [ { #category : #'installing package' } HEInstaller >> installPackage: aHEPackage [ - | storedAnnouncements | - - storedAnnouncements := SystemAnnouncer uniqueInstance suspendAllWhileStoring: [ self doInstallPackage: aHEPackage ]. - storedAnnouncements do: [ :e | SystemAnnouncer uniqueInstance announce: e ]. + + (SystemAnnouncer uniqueInstance suspendAllWhileStoring: [ self doInstallPackage: aHEPackage ]) + do: [ :storedAnnouncement | SystemAnnouncer announce: storedAnnouncement ] ] { #category : #messages } @@ -234,22 +198,21 @@ HEInstaller >> processTraitsFrom: aHEClass in: newClass [ hasTraits ifFalse: [ ^ self ]. newClass setTraitComposition: (self buildTraitCompositionFor: aHEClass traitComposition). - newClass class setTraitComposition: (self buildTraitCompositionFor: aHEClass classTraitComposition). - + newClass class setTraitComposition: (self buildTraitCompositionFor: aHEClass classTraitComposition) ] { #category : #'installing methods' } HEInstaller >> rebuildMethod: aMethod into: aClass [ | newMethod literalSpace extendedEnvironment | - - (self shouldBuildMethod: aMethod in: aClass) ifFalse: [ ^ self ]. + + (self shouldBuildMethod: aMethod in: aClass) ifFalse: [ ^ self ]. extendedEnvironment := HEExtendedEnvironment new. extendedEnvironment inner: environment. extendedEnvironment newClass: aClass. extendedEnvironment newSelector: aMethod name. - newMethod := CompiledMethod newMethod: aMethod bytecode size header: (aMethod headerFor: extendedEnvironment). + newMethod := CompiledMethod newMethod: aMethod bytecode size + CompiledMethod trailerSize header: (aMethod headerFor: extendedEnvironment). extendedEnvironment newMethod: newMethod. @@ -277,8 +240,8 @@ HEInstaller >> reportNewUndeclareds: newUndeclareds [ HEInstaller >> shouldBuildMethod: aHEMethod in: aClass [ aClass compiledMethodAt: aHEMethod name - ifPresent: [ :m | - (m isFromTrait and:[aClass isTrait not]) ifTrue:[ ^ true ]. + ifPresent: [ :m | + (m isFromTrait and:[aClass isTrait not]) ifTrue:[ ^ true ]. self error: (self messageMethod: aHEMethod alreadyExistsIn: aClass ) ] ifAbsent: [ ^ true ] ] @@ -286,7 +249,7 @@ HEInstaller >> shouldBuildMethod: aHEMethod in: aClass [ { #category : #'reporting undeclared' } HEInstaller >> validateNoNewUndeclared [ self reportNewUndeclareds: self createdUndeclared. - + SystemNotification signal: ('[Hermes] Remaining Undeclared variables in the system: ' , Undeclared keys printString) ] diff --git a/Hermes/HEMethod.class.st b/Hermes/HEMethod.class.st index 1dad5c3..ce376f3 100644 --- a/Hermes/HEMethod.class.st +++ b/Hermes/HEMethod.class.st @@ -60,7 +60,7 @@ HEMethod >> 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) ] @@ -109,7 +109,7 @@ HEMethod >> readFrom: aReader [ name := aReader readByteSymbol. className := aReader readByteSymbol. protocol := aReader readByteSymbol. - + encoderClassName := aReader readByteString. numArgs := aReader readUInt32. numTemps := aReader readUInt32. diff --git a/Hermes/HEMethodLiteral.class.st b/Hermes/HEMethodLiteral.class.st index 78e51a9..5412b0c 100644 --- a/Hermes/HEMethodLiteral.class.st +++ b/Hermes/HEMethodLiteral.class.st @@ -15,7 +15,7 @@ Class { { #category : #accessing } HEMethodLiteral class >> tag [ - ^ 10. + ^ 10 ] { #category : #converting } @@ -38,13 +38,11 @@ HEMethodLiteral >> className: anObject [ { #category : #reading } HEMethodLiteral >> doReadFrom: aReader [ className := aReader readByteSymbol. - selector := aReader readByteSymbol. - - + selector := aReader readByteSymbol ] { #category : #accessing } HEMethodLiteral >> value: aMethod [ className := aMethod methodClass name. - selector := aMethod selector. + selector := aMethod selector ] diff --git a/Hermes/HEPackage.class.st b/Hermes/HEPackage.class.st index 0d96cb4..9a1db14 100644 --- a/Hermes/HEPackage.class.st +++ b/Hermes/HEPackage.class.st @@ -36,7 +36,7 @@ HEPackage class >> formatVersion [ { #category : #adding } HEPackage >> addClass: anExportedClass [ - classes add: anExportedClass. + classes add: anExportedClass ] { #category : #accessing } @@ -65,7 +65,7 @@ HEPackage >> initialize [ classes := OrderedCollection new. traits := OrderedCollection new. - extensionMethods := OrderedCollection new. + extensionMethods := OrderedCollection new ] { #category : #accessing } @@ -88,17 +88,16 @@ HEPackage >> printOn: aStream [ { #category : #reading } HEPackage >> readClassFrom: aReader [ - classes add: (HEClass readFrom: aReader). - + classes add: (HEClass readFrom: aReader) ] { #category : #reading } HEPackage >> readFrom: aReader [ | numberOfTraits numberOfClasses numberOfExtensionMethods | version := aReader readInt32. - + version = self class formatVersion ifFalse:[self error:'Invalid Hermes file version, expecting: ' , self class formatVersion asString , ' but was: ' , version asString]. - + packageName := aReader readByteSymbol. numberOfTraits := aReader readInt32. @@ -108,7 +107,7 @@ HEPackage >> readFrom: aReader [ 1 to: numberOfClasses do: [ :idx | classes add: (HEClass readFrom: aReader)]. numberOfExtensionMethods := aReader readInt32. - 1 to: numberOfExtensionMethods do: [ :idx | extensionMethods add: (HEMethod readFrom: aReader) ] + 1 to: numberOfExtensionMethods do: [ :idx | extensionMethods add: (HEMethod readFrom: aReader) ] ] { #category : #accessing } diff --git a/Hermes/HEPragma.class.st b/Hermes/HEPragma.class.st index a8a04cf..50947e8 100644 --- a/Hermes/HEPragma.class.st +++ b/Hermes/HEPragma.class.st @@ -20,7 +20,7 @@ Class { { #category : #accessing } HEPragma class >> tag [ - ^ 11. + ^ 11 ] { #category : #accessing } @@ -37,7 +37,7 @@ HEPragma >> asLiteralIn: env [ HEPragma >> doReadFrom: aReader [ method := HEExportedLiteral readFrom: aReader. keyword := HEExportedLiteral readFrom: aReader. - arguments := HEExportedLiteral readFrom: aReader. + arguments := HEExportedLiteral readFrom: aReader ] { #category : #accessing } @@ -54,5 +54,5 @@ HEPragma >> method [ HEPragma >> value: aPragma [ method := aPragma method asExportedLiteral. keyword := aPragma selector asExportedLiteral. - arguments := aPragma arguments asExportedLiteral + arguments := aPragma arguments asExportedLiteral ] diff --git a/Hermes/HEScaledDecimal.class.st b/Hermes/HEScaledDecimal.class.st index fbeabf8..3120cea 100644 --- a/Hermes/HEScaledDecimal.class.st +++ b/Hermes/HEScaledDecimal.class.st @@ -10,7 +10,7 @@ Class { } { #category : #accessing } -HEScaledDecimal class >> tag [ +HEScaledDecimal class >> tag [ ^ 25 ] @@ -19,8 +19,6 @@ HEScaledDecimal >> doReadFrom: aReader [ | scale | super doReadFrom: aReader. scale := HEExportedLiteral readFrom: aReader. - - value := ScaledDecimal newFromNumber: value scale: scale value. - - + + value := ScaledDecimal newFromNumber: value scale: scale value ] diff --git a/Hermes/HESendMessage.class.st b/Hermes/HESendMessage.class.st index fae17bf..e354291 100644 --- a/Hermes/HESendMessage.class.st +++ b/Hermes/HESendMessage.class.st @@ -49,16 +49,16 @@ HESendMessage >> asLiteralIn: env [ aReceiver := receiver asLiteralIn: env. aSelector := selector asLiteralIn: env. args := arguments asLiteralIn: env. - + ^ aReceiver perform: aSelector withArguments: args ] { #category : #reading } -HESendMessage >> doReadFrom: aReader [ +HESendMessage >> doReadFrom: aReader [ selector := (HEExportedLiteral readFrom: aReader). receiver := (HEExportedLiteral readFrom: aReader). - arguments := (HEExportedLiteral readFrom: aReader). + arguments := (HEExportedLiteral readFrom: aReader) ] { #category : #accessing } diff --git a/Hermes/HESymbol.class.st b/Hermes/HESymbol.class.st index 4626ebc..d58a67b 100644 --- a/Hermes/HESymbol.class.st +++ b/Hermes/HESymbol.class.st @@ -11,10 +11,10 @@ Class { { #category : #accessing } HESymbol class >> tag [ - ^ 9. + ^ 9 ] { #category : #reading } HESymbol >> doConvertValue: aValue [ - ^ aValue asSymbol. + ^ aValue asSymbol ] diff --git a/Hermes/HETrait.class.st b/Hermes/HETrait.class.st index a067afc..a3f6b7f 100644 --- a/Hermes/HETrait.class.st +++ b/Hermes/HETrait.class.st @@ -14,7 +14,7 @@ Class { { #category : #reading } HETrait >> doReadHeaderFrom: aReader [ - traitName := aReader readByteSymbol. + traitName := aReader readByteSymbol ] { #category : #accessing } diff --git a/Hermes/HETraitLiteral.class.st b/Hermes/HETraitLiteral.class.st index c8ebbd9..5acfef6 100644 --- a/Hermes/HETraitLiteral.class.st +++ b/Hermes/HETraitLiteral.class.st @@ -23,5 +23,5 @@ HETraitLiteral >> asLiteralIn: env [ { #category : #accessing } HETraitLiteral >> value: aTrait [ - value := aTrait name. + value := aTrait name ] diff --git a/Hermes/HEWideString.class.st b/Hermes/HEWideString.class.st index a64cf6c..8f2b348 100644 --- a/Hermes/HEWideString.class.st +++ b/Hermes/HEWideString.class.st @@ -16,5 +16,5 @@ HEWideString class >> tag [ { #category : #reading } HEWideString >> doReadFrom: aReader [ - value := aReader readByteArray utf8Decoded. + value := aReader readByteArray utf8Decoded ] diff --git a/Hermes/HermesCommandLineHandler.class.st b/Hermes/HermesCommandLineHandler.class.st index 3a6e1a1..0e6560c 100644 --- a/Hermes/HermesCommandLineHandler.class.st +++ b/Hermes/HermesCommandLineHandler.class.st @@ -56,9 +56,9 @@ HermesCommandLineHandler class >> description [ HermesCommandLineHandler >> activate [ self activateHelp ifTrue: [ ^ self ]. self validateParameters. - + self processFiles. - + (self hasOption: 'save') ifTrue: [ Smalltalk snapshot: true andQuit: false ]. @@ -67,13 +67,13 @@ HermesCommandLineHandler >> activate [ { #category : #'processing files' } HermesCommandLineHandler >> createInstaller [ - "In the basic installation, the bootstraped version of Hermes, - there is only one Installer, the HEInstaller. + "In the basic installation, the bootstraped version of Hermes, + there is only one Installer, the HEInstaller. When the extensions are installed the new installer to use is the HEExtendedInstaller." ^ Smalltalk globals at: #HEExtendedInstaller - ifPresent: [ :instClass | + ifPresent: [ :instClass | instClass new forOptions: self commandLine; yourself ]