Skip to content

Commit

Permalink
Updating hermes tests to run in Pharo 7
Browse files Browse the repository at this point in the history
  • Loading branch information
carolahp committed Nov 28, 2018
1 parent 8ddb809 commit 0b2ebfd
Show file tree
Hide file tree
Showing 4 changed files with 50 additions and 46 deletions.
10 changes: 5 additions & 5 deletions Hermes-Exporter/HEMethodContainer.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -4,16 +4,16 @@ Extension { #name : #HEMethodContainer }
HEMethodContainer >> doFromMethodContainer: aMethodContainer [
"When a class or a trait is transformed all the methods should be transformed.
In both the class and instance side. Also the trait composition should be handled"

category := aMethodContainer category.
traitComposition := aMethodContainer traitComposition asExportedLiteral.
classTraitComposition := aMethodContainer theMetaClass traitComposition
traitComposition := aMethodContainer traitComposition
asExportedLiteral.
classTraitComposition := aMethodContainer classSide traitComposition
asExportedLiteral.

methods := aMethodContainer localMethods
select: [ :e | e isExtension not ]
thenCollect: [ :e | HEMethod for: e ].

classSideMethods := aMethodContainer theMetaClass localMethods
classSideMethods := aMethodContainer classSide localMethods
select: [ :e | e isExtension not ]
thenCollect: [ :e | HEMethod for: e ]
]
Expand Down
10 changes: 7 additions & 3 deletions Hermes-Tests/HEExportingTraitTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -9,11 +9,15 @@ HEExportingTraitTest >> doTestExportingTrait: traitUnderTest [
| new old nonExtensionMethodsClassSide nonExtensionMethods |
old := HETrait for: traitUnderTest.

nonExtensionMethods := (traitUnderTest localMethods reject: #isExtension) size.
nonExtensionMethodsClassSide := (traitUnderTest theMetaClass localMethods reject: #isExtension) size.
nonExtensionMethods := (traitUnderTest localMethods
reject: #isExtension) size.
nonExtensionMethodsClassSide := (traitUnderTest classSide
localMethods reject: #isExtension) size.

self assert: old methods size equals: nonExtensionMethods.
self assert: old classSideMethods size equals: nonExtensionMethodsClassSide.
self
assert: old classSideMethods size
equals: nonExtensionMethodsClassSide.

old writeInto: writer.
writer flush.
Expand Down
51 changes: 27 additions & 24 deletions Hermes-Tests/HEInstallerSimpleTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ HEInstallerSimpleTest >> testCreatingAClassUsingTraits [
obj := aClass someClassSideMessage.

self assert: aClass slots isEmpty.
self assert: aClass class slots isEmpty.
self assert: (aClass class slots collect:#name) equals: #(users).

self assert: obj oneMessage equals: 1234.
self assert: obj otherMessage equals: 4321.
Expand Down Expand Up @@ -159,43 +159,46 @@ HEInstallerSimpleTest >> testCreatingASimpleClassExportingToFile [
{ #category : #tests }
HEInstallerSimpleTest >> testCreatingASimpleTrait [
| exportedTrait |
exportedTrait := HETrait for: THEOneTestTrait.

exportedTrait := HETrait for: THEOneTestTrait.
self changeNameOf: exportedTrait to: #THEOneTestTraitNew.
aTrait := installer buildTrait: exportedTrait.

aTrait := installer buildTrait: exportedTrait.
installer installMethods: exportedTrait into: aTrait.

self assert: aTrait traitComposition isEmpty.
self assert: aTrait theMetaClass traitComposition isEmpty.

self assert: aTrait classSide traitComposition isEmpty.
self assert: aTrait methods size equals: THEOneTestTrait methods size.
self assert: aTrait classTrait methods size equals: THEOneTestTrait classTrait methods size.


self
assert: aTrait classTrait methods size
equals: THEOneTestTrait classTrait methods size.

aTrait >> #oneMessage.
aTrait >> #oneMessageRequired
]

{ #category : #tests }
HEInstallerSimpleTest >> testCreatingATraitUsingOthers [
| exportedTrait |

exportedTrait := HETrait for: THEATraitUsingOthers.
self changeNameOf: exportedTrait to: #THEATraitUsingOthersNew.

aTrait := installer buildTrait: exportedTrait.
exportedTrait := HETrait for: THEATraitUsingOthers.
self changeNameOf: exportedTrait to: #THEATraitUsingOthersNew.
aTrait := installer buildTrait: exportedTrait.
installer installMethods: exportedTrait into: aTrait.

self deny: aTrait traitComposition isEmpty.
self deny: aTrait theMetaClass traitComposition isEmpty.

self assert: aTrait methods size equals: THEATraitUsingOthers methods size.
self assert: aTrait classTrait methods size equals: THEATraitUsingOthers classTrait methods size.

self assert: aTrait traitComposition printString equals: THEATraitUsingOthers traitComposition printString.

self assert: aTrait classTrait traitComposition printString equals: THEATraitUsingOthers classTrait traitComposition printString.

self deny: aTrait classSide traitComposition isEmpty.
self
assert: aTrait methods size
equals: THEATraitUsingOthers methods size.
self
assert: aTrait classTrait methods size
equals: THEATraitUsingOthers classTrait methods size.
self
assert: aTrait traitComposition printString
equals: THEATraitUsingOthers traitComposition printString.
self
assert: aTrait classTrait traitComposition printString
equals: THEATraitUsingOthers classTrait traitComposition printString.
aTrait >> #oneMessage.
aTrait >> #oneMessageRequired
]
Expand Down
25 changes: 11 additions & 14 deletions Hermes/HEInstaller.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -225,32 +225,29 @@ HEInstaller >> processTraitsFrom: aHEClass in: newClass [
{ #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
header: (aMethod headerFor: extendedEnvironment).
extendedEnvironment newMethod: newMethod.

aMethod literals
doWithIndex:
[ :literal :idx | newMethod literalAt: idx put: (literal asLiteralIn: extendedEnvironment) ].

doWithIndex: [ :literal :idx |
newMethod
literalAt: idx
put: (literal asLiteralIn: extendedEnvironment) ].
newMethod classBinding: aClass binding.
literalSpace := (aMethod literals size + 1) * Smalltalk wordSize.

aMethod bytecode doWithIndex: [ :e :idx | newMethod at: idx + literalSpace put: e ].

aMethod bytecode
doWithIndex: [ :e :idx | newMethod at: idx + literalSpace put: e ].
aClass
addAndClassifySelector: aMethod name
withMethod: newMethod
inProtocol: aMethod protocol
notifying: nil
]

{ #category : #'reporting undeclared' }
Expand Down

0 comments on commit 0b2ebfd

Please sign in to comment.