About merging metaclass and methods extraction

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
5 messages Options
Reply | Threaded
Open this post in threaded view
|

About merging metaclass and methods extraction

stepharo
Hi

I'm wondering how we handle the following case:
     - we have a method with the same name on instance and class
     - we import by merging class and metaclass.

I remember that I payed attention to that for ClassVariable but I do not see
how I handle it in the SmalltalkImporter.

Does one of you remember?

Stef
_______________________________________________
Moose-dev mailing list
[hidden email]
https://www.iam.unibe.ch/mailman/listinfo/moose-dev
Reply | Threaded
Open this post in threaded view
|

Re: About merging metaclass and methods extraction

stepharo
I forgot to mention that I'm talking in MooseVW :).

importClass: aClass

     | class comment |
     importingContext shouldImportClass ifTrue: [
             class := self ensureClass: aClass.
             class stub: false.
             aClass subclasses do: [ :each | self ensureClass: each ].

             importingContext shouldImportMethod ifTrue: [
                 aClass methodDictionary values do: [ :each | self
ensureMethod: each ].
                 (class methods contains: [:each | each isAbstract])
ifTrue: [ class isAbstract: true ]].

             importingContext shouldImportComment ifTrue: [
                 aClass comment isEmpty ifFalse: [
                     comment := self addEntity: FAMIXComment new.
                     comment content: aClass comment.
                     comment setBelongsTo: class.
                     class addComment: comment]].

             aClass isMeta ifFalse: [ self importClass: aClass class ]].


createMethod: aCompiledMethod

     | method thisClass |
     method := methods at: aCompiledMethod put: FAMIXMethod new.
     method setName: aCompiledMethod selector.
     thisClass := aCompiledMethod mclass.
     method setBelongsTo: (self ensureClass: thisClass).
     method belongsTo addMethod: method.
     method packagedIn: (self ensurePackage: aCompiledMethod
containingPackage).
     (method belongsTo packagedIn ~~ method packagedIn) ifTrue: [
         method packagedIn addExtendedClass: method belongsTo.
         method belongsTo addExtendedInPackages: method packagedIn
     ].
     method setHasClassScope: (aCompiledMethod mclass isMeta).
     method setCategory: (aCompiledMethod mclass organization
categoryOfElement: aCompiledMethod selector).
     method bePublic.

     importingContext shouldImportMethodBody ifTrue: [
         | visitor |
         visitor := SmalltalkMethodVisitor on: self.
         visitor runWith: aCompiledMethod and: method ].
     ^method


I will check in our lovely moose and our incredibly more efficient
environment.

Stef





Le 10/3/15 13:01, stepharo a écrit :

> Hi
>
> I'm wondering how we handle the following case:
>     - we have a method with the same name on instance and class
>     - we import by merging class and metaclass.
>
> I remember that I payed attention to that for ClassVariable but I do
> not see
> how I handle it in the SmalltalkImporter.
>
> Does one of you remember?
>
> Stef
> _______________________________________________
> Moose-dev mailing list
> [hidden email]
> https://www.iam.unibe.ch/mailman/listinfo/moose-dev
>

_______________________________________________
Moose-dev mailing list
[hidden email]
https://www.iam.unibe.ch/mailman/listinfo/moose-dev
Reply | Threaded
Open this post in threaded view
|

Re: About merging metaclass and methods extraction

stepharo
In pharo this is nearly the same. So it means that we should not merge a
class and metaclass when importing.
Doru do you remember?

Stef



createClass: aClass
     | class inheritance |

     importingContext shouldMergeClassAndMetaclass
         ifFalse: [ class := self basicClassCreation: aClass ]
         ifTrue:
             [ aClass isMeta
                 ifTrue: [ class := self ensureClass: aClass
soleInstance. classes at: aClass put: class ]
                 ifFalse: [ class := self basicClassCreation: aClass ] ].
     importingContext shouldImportPackage ifTrue:
         [ class parentPackage: (self ensurePackage: (aClass package)) ].
     importingContext shouldImportInheritance ifTrue:
         [ (aClass superclass ~~ nil and:
             [ importingContext shouldMergeClassAndMetaclass
                 ifFalse: [ true ]
                 ifTrue: [ aClass isMeta not ] ])
                     ifTrue: [ inheritance := self addEntity:
FAMIXInheritance new.
                             inheritance superclass: (self ensureClass:
aClass superclass).
                             inheritance subclass: class ]
         ].
     aClass isMeta ifFalse: [ self ensureClass: aClass class ].
     importingContext shouldImportAttribute
         ifTrue:
             [aClass instVarNames
                 do: [:eachName | self ensureAttribute: eachName for:
aClass].
             "since the classVar of a class are not the same as the
classVar of the class class"

             "with latest pharo class classVar = class class classVar so
we should not need that anymore"
             aClass isMeta
                 ifTrue: [aClass soleInstance classVarNames
                             do: [:eachClassVarName | self
ensureClassVarAttribute: eachClassVarName for: aClass soleInstance]]
                 ifFalse: [ aClass classVarNames
                             do: [:eachClassVarName | self
ensureClassVarAttribute: eachClassVarName for: aClass]]].
     ^ class




createMethod: aCompiledMethod
     | method thisClass parentPackage |
     method := methods
         at: aCompiledMethod
         put: FAMIXMethod new.
     method name: aCompiledMethod selector.
     thisClass := aCompiledMethod methodClass.
     method parentType: (self ensureClass: thisClass).
     method signature: aCompiledMethod signature.
     "here we have two possibilities for the parentPackage of the method:
     => the method belong to a package extension, we should refer to
this extending packages
     => if not, we should not refer to package of the class"
     "parentPackage := aCompiledMethod methodClass package."
     aCompiledMethod methodClass extendingPackages do: [:aRPackage |
         (aCompiledMethod isExtensionInPackage: aRPackage)
             ifTrue: [
                 method parentPackage: (self ensurePackage: aRPackage).
             ].
         ].

     method hasClassScope: aCompiledMethod methodClass isMeta.
     method category: (aCompiledMethod methodClass organization
categoryOfElement: aCompiledMethod selector).
     method isPublic: true.
     method timeStamp: aCompiledMethod timeStamp.
     importingContext shouldImportMethodBody ifTrue:
         [ | visitor |
         visitor := SmalltalkMethodVisitor on: self.
         visitor
             runWith: aCompiledMethod
             and: method ].

     method sourceAnchor:
         (FAMIXPharoAnchor new
             element: method;
             pharoEntity: aCompiledMethod;
             yourself).

     ^ method






Le 10/3/15 13:06, stepharo a écrit :

> I forgot to mention that I'm talking in MooseVW :).
>
> importClass: aClass
>
>     | class comment |
>     importingContext shouldImportClass ifTrue: [
>             class := self ensureClass: aClass.
>             class stub: false.
>             aClass subclasses do: [ :each | self ensureClass: each ].
>
>             importingContext shouldImportMethod ifTrue: [
>                 aClass methodDictionary values do: [ :each | self
> ensureMethod: each ].
>                 (class methods contains: [:each | each isAbstract])
> ifTrue: [ class isAbstract: true ]].
>
>             importingContext shouldImportComment ifTrue: [
>                 aClass comment isEmpty ifFalse: [
>                     comment := self addEntity: FAMIXComment new.
>                     comment content: aClass comment.
>                     comment setBelongsTo: class.
>                     class addComment: comment]].
>
>             aClass isMeta ifFalse: [ self importClass: aClass class ]].
>
>
> createMethod: aCompiledMethod
>
>     | method thisClass |
>     method := methods at: aCompiledMethod put: FAMIXMethod new.
>     method setName: aCompiledMethod selector.
>     thisClass := aCompiledMethod mclass.
>     method setBelongsTo: (self ensureClass: thisClass).
>     method belongsTo addMethod: method.
>     method packagedIn: (self ensurePackage: aCompiledMethod
> containingPackage).
>     (method belongsTo packagedIn ~~ method packagedIn) ifTrue: [
>         method packagedIn addExtendedClass: method belongsTo.
>         method belongsTo addExtendedInPackages: method packagedIn
>     ].
>     method setHasClassScope: (aCompiledMethod mclass isMeta).
>     method setCategory: (aCompiledMethod mclass organization
> categoryOfElement: aCompiledMethod selector).
>     method bePublic.
>
>     importingContext shouldImportMethodBody ifTrue: [
>         | visitor |
>         visitor := SmalltalkMethodVisitor on: self.
>         visitor runWith: aCompiledMethod and: method ].
>     ^method
>
>
> I will check in our lovely moose and our incredibly more efficient
> environment.
>
> Stef
>
>
>
>
>
> Le 10/3/15 13:01, stepharo a écrit :
>> Hi
>>
>> I'm wondering how we handle the following case:
>>     - we have a method with the same name on instance and class
>>     - we import by merging class and metaclass.
>>
>> I remember that I payed attention to that for ClassVariable but I do
>> not see
>> how I handle it in the SmalltalkImporter.
>>
>> Does one of you remember?
>>
>> Stef
>> _______________________________________________
>> Moose-dev mailing list
>> [hidden email]
>> https://www.iam.unibe.ch/mailman/listinfo/moose-dev
>>
>
> _______________________________________________
> Moose-dev mailing list
> [hidden email]
> https://www.iam.unibe.ch/mailman/listinfo/moose-dev
>
>

_______________________________________________
Moose-dev mailing list
[hidden email]
https://www.iam.unibe.ch/mailman/listinfo/moose-dev
Reply | Threaded
Open this post in threaded view
|

Re: About merging metaclass and methods extraction

Tudor Girba-2
Hi Stef,

This should work as expected actually. We do not store entities based on names.

Try this:

Object subclass: #MMM
instanceVariableNames: ''
classVariableNames: ''
category: 'MMM'.
MMM compile: 'someMethod'.

MMM class compile: 'someMethod ^ self new someMethod'.

model := MooseModel new.
importTask := MoosePharoImporterTask new.
importTask importerClass: SmalltalkImporter.
importTask
importingContext:
(MooseImportingContext new
importClassMethodInheritanceAttributeAccessInvocation
mergeClassAndMetaclass;
yourself).
importTask addClass: MMM.
importTask model: model.
importer := importTask run.
model allMethods 
==> 2


Cheers,
Doru



On Tue, Mar 10, 2015 at 2:20 PM, stepharo <[hidden email]> wrote:
In pharo this is nearly the same. So it means that we should not merge a class and metaclass when importing.
Doru do you remember?

Stef



createClass: aClass
    | class inheritance |

    importingContext shouldMergeClassAndMetaclass
        ifFalse: [ class := self basicClassCreation: aClass ]
        ifTrue:
            [ aClass isMeta
                ifTrue: [ class := self ensureClass: aClass soleInstance. classes at: aClass put: class ]
                ifFalse: [ class := self basicClassCreation: aClass ] ].
    importingContext shouldImportPackage ifTrue:
        [ class parentPackage: (self ensurePackage: (aClass package)) ].
    importingContext shouldImportInheritance ifTrue:
        [ (aClass superclass ~~ nil and:
            [ importingContext shouldMergeClassAndMetaclass
                ifFalse: [ true ]
                ifTrue: [ aClass isMeta not ] ])
                    ifTrue: [ inheritance := self addEntity: FAMIXInheritance new.
                            inheritance superclass: (self ensureClass: aClass superclass).
                            inheritance subclass: class ]
        ].
    aClass isMeta ifFalse: [ self ensureClass: aClass class ].
    importingContext shouldImportAttribute
        ifTrue:
            [aClass instVarNames
                do: [:eachName | self ensureAttribute: eachName for: aClass].
            "since the classVar of a class are not the same as the classVar of the class class"

            "with latest pharo class classVar = class class classVar so we should not need that anymore"
            aClass isMeta
                ifTrue: [aClass soleInstance classVarNames
                            do: [:eachClassVarName | self ensureClassVarAttribute: eachClassVarName for: aClass soleInstance]]
                ifFalse: [ aClass classVarNames
                            do: [:eachClassVarName | self ensureClassVarAttribute: eachClassVarName for: aClass]]].
    ^ class




createMethod: aCompiledMethod
    | method thisClass parentPackage |
    method := methods
        at: aCompiledMethod
        put: FAMIXMethod new.
    method name: aCompiledMethod selector.
    thisClass := aCompiledMethod methodClass.
    method parentType: (self ensureClass: thisClass).
    method signature: aCompiledMethod signature.
    "here we have two possibilities for the parentPackage of the method:
    => the method belong to a package extension, we should refer to this extending packages
    => if not, we should not refer to package of the class"
    "parentPackage := aCompiledMethod methodClass package."
    aCompiledMethod methodClass extendingPackages do: [:aRPackage |
        (aCompiledMethod isExtensionInPackage: aRPackage)
            ifTrue: [
                method parentPackage: (self ensurePackage: aRPackage).
            ].
        ].

    method hasClassScope: aCompiledMethod methodClass isMeta.
    method category: (aCompiledMethod methodClass organization categoryOfElement: aCompiledMethod selector).
    method isPublic: true.
    method timeStamp: aCompiledMethod timeStamp.
    importingContext shouldImportMethodBody ifTrue:
        [ | visitor |
        visitor := SmalltalkMethodVisitor on: self.
        visitor
            runWith: aCompiledMethod
            and: method ].

    method sourceAnchor:
        (FAMIXPharoAnchor new
            element: method;
            pharoEntity: aCompiledMethod;
            yourself).

    ^ method






Le 10/3/15 13:06, stepharo a écrit :

I forgot to mention that I'm talking in MooseVW :).

importClass: aClass

    | class comment |
    importingContext shouldImportClass ifTrue: [
            class := self ensureClass: aClass.
            class stub: false.
            aClass subclasses do: [ :each | self ensureClass: each ].

            importingContext shouldImportMethod ifTrue: [
                aClass methodDictionary values do: [ :each | self ensureMethod: each ].
                (class methods contains: [:each | each isAbstract]) ifTrue: [ class isAbstract: true ]].

            importingContext shouldImportComment ifTrue: [
                aClass comment isEmpty ifFalse: [
                    comment := self addEntity: FAMIXComment new.
                    comment content: aClass comment.
                    comment setBelongsTo: class.
                    class addComment: comment]].

            aClass isMeta ifFalse: [ self importClass: aClass class ]].


createMethod: aCompiledMethod

    | method thisClass |
    method := methods at: aCompiledMethod put: FAMIXMethod new.
    method setName: aCompiledMethod selector.
    thisClass := aCompiledMethod mclass.
    method setBelongsTo: (self ensureClass: thisClass).
    method belongsTo addMethod: method.
    method packagedIn: (self ensurePackage: aCompiledMethod containingPackage).
    (method belongsTo packagedIn ~~ method packagedIn) ifTrue: [
        method packagedIn addExtendedClass: method belongsTo.
        method belongsTo addExtendedInPackages: method packagedIn
    ].
    method setHasClassScope: (aCompiledMethod mclass isMeta).
    method setCategory: (aCompiledMethod mclass organization categoryOfElement: aCompiledMethod selector).
    method bePublic.

    importingContext shouldImportMethodBody ifTrue: [
        | visitor |
        visitor := SmalltalkMethodVisitor on: self.
        visitor runWith: aCompiledMethod and: method ].
    ^method


I will check in our lovely moose and our incredibly more efficient environment.

Stef





Le 10/3/15 13:01, stepharo a écrit :
Hi

I'm wondering how we handle the following case:
    - we have a method with the same name on instance and class
    - we import by merging class and metaclass.

I remember that I payed attention to that for ClassVariable but I do not see
how I handle it in the SmalltalkImporter.

Does one of you remember?

Stef
_______________________________________________
Moose-dev mailing list
[hidden email]
https://www.iam.unibe.ch/mailman/listinfo/moose-dev


_______________________________________________
Moose-dev mailing list
[hidden email]
https://www.iam.unibe.ch/mailman/listinfo/moose-dev



_______________________________________________
Moose-dev mailing list
[hidden email]
https://www.iam.unibe.ch/mailman/listinfo/moose-dev



--

"Every thing has its own flow"

_______________________________________________
Moose-dev mailing list
[hidden email]
https://www.iam.unibe.ch/mailman/listinfo/moose-dev
Reply | Threaded
Open this post in threaded view
|

Re: About merging metaclass and methods extraction

abergel
Interesting code snippet!

Alexandre
-- 
_,.;:~^~:;._,.;:~^~:;._,.;:~^~:;._,.;:~^~:;._,.;:
Alexandre Bergel  http://www.bergel.eu
^~:;._,.;:~^~:;._,.;:~^~:;._,.;:~^~:;._,.;:~^~:;.



On Mar 10, 2015, at 11:18 AM, Tudor Girba <[hidden email]> wrote:

Hi Stef,

This should work as expected actually. We do not store entities based on names.

Try this:

Object subclass: #MMM
instanceVariableNames: ''
classVariableNames: ''
category: 'MMM'.
MMM compile: 'someMethod'.

MMM class compile: 'someMethod ^ self new someMethod'.

model := MooseModel new.
importTask := MoosePharoImporterTask new.
importTask importerClass: SmalltalkImporter.
importTask
importingContext:
(MooseImportingContext new
importClassMethodInheritanceAttributeAccessInvocation
mergeClassAndMetaclass;
yourself).
importTask addClass: MMM.
importTask model: model.
importer := importTask run.
model allMethods 
==> 2


Cheers,
Doru



On Tue, Mar 10, 2015 at 2:20 PM, stepharo <[hidden email]> wrote:
In pharo this is nearly the same. So it means that we should not merge a class and metaclass when importing.
Doru do you remember?

Stef



createClass: aClass
    | class inheritance |

    importingContext shouldMergeClassAndMetaclass
        ifFalse: [ class := self basicClassCreation: aClass ]
        ifTrue:
            [ aClass isMeta
                ifTrue: [ class := self ensureClass: aClass soleInstance. classes at: aClass put: class ]
                ifFalse: [ class := self basicClassCreation: aClass ] ].
    importingContext shouldImportPackage ifTrue:
        [ class parentPackage: (self ensurePackage: (aClass package)) ].
    importingContext shouldImportInheritance ifTrue:
        [ (aClass superclass ~~ nil and:
            [ importingContext shouldMergeClassAndMetaclass
                ifFalse: [ true ]
                ifTrue: [ aClass isMeta not ] ])
                    ifTrue: [ inheritance := self addEntity: FAMIXInheritance new.
                            inheritance superclass: (self ensureClass: aClass superclass).
                            inheritance subclass: class ]
        ].
    aClass isMeta ifFalse: [ self ensureClass: aClass class ].
    importingContext shouldImportAttribute
        ifTrue:
            [aClass instVarNames
                do: [:eachName | self ensureAttribute: eachName for: aClass].
            "since the classVar of a class are not the same as the classVar of the class class"

            "with latest pharo class classVar = class class classVar so we should not need that anymore"
            aClass isMeta
                ifTrue: [aClass soleInstance classVarNames
                            do: [:eachClassVarName | self ensureClassVarAttribute: eachClassVarName for: aClass soleInstance]]
                ifFalse: [ aClass classVarNames
                            do: [:eachClassVarName | self ensureClassVarAttribute: eachClassVarName for: aClass]]].
    ^ class




createMethod: aCompiledMethod
    | method thisClass parentPackage |
    method := methods
        at: aCompiledMethod
        put: FAMIXMethod new.
    method name: aCompiledMethod selector.
    thisClass := aCompiledMethod methodClass.
    method parentType: (self ensureClass: thisClass).
    method signature: aCompiledMethod signature.
    "here we have two possibilities for the parentPackage of the method:
    => the method belong to a package extension, we should refer to this extending packages
    => if not, we should not refer to package of the class"
    "parentPackage := aCompiledMethod methodClass package."
    aCompiledMethod methodClass extendingPackages do: [:aRPackage |
        (aCompiledMethod isExtensionInPackage: aRPackage)
            ifTrue: [
                method parentPackage: (self ensurePackage: aRPackage).
            ].
        ].

    method hasClassScope: aCompiledMethod methodClass isMeta.
    method category: (aCompiledMethod methodClass organization categoryOfElement: aCompiledMethod selector).
    method isPublic: true.
    method timeStamp: aCompiledMethod timeStamp.
    importingContext shouldImportMethodBody ifTrue:
        [ | visitor |
        visitor := SmalltalkMethodVisitor on: self.
        visitor
            runWith: aCompiledMethod
            and: method ].

    method sourceAnchor:
        (FAMIXPharoAnchor new
            element: method;
            pharoEntity: aCompiledMethod;
            yourself).

    ^ method






Le 10/3/15 13:06, stepharo a écrit :

I forgot to mention that I'm talking in MooseVW :).

importClass: aClass

    | class comment |
    importingContext shouldImportClass ifTrue: [
            class := self ensureClass: aClass.
            class stub: false.
            aClass subclasses do: [ :each | self ensureClass: each ].

            importingContext shouldImportMethod ifTrue: [
                aClass methodDictionary values do: [ :each | self ensureMethod: each ].
                (class methods contains: [:each | each isAbstract]) ifTrue: [ class isAbstract: true ]].

            importingContext shouldImportComment ifTrue: [
                aClass comment isEmpty ifFalse: [
                    comment := self addEntity: FAMIXComment new.
                    comment content: aClass comment.
                    comment setBelongsTo: class.
                    class addComment: comment]].

            aClass isMeta ifFalse: [ self importClass: aClass class ]].


createMethod: aCompiledMethod

    | method thisClass |
    method := methods at: aCompiledMethod put: FAMIXMethod new.
    method setName: aCompiledMethod selector.
    thisClass := aCompiledMethod mclass.
    method setBelongsTo: (self ensureClass: thisClass).
    method belongsTo addMethod: method.
    method packagedIn: (self ensurePackage: aCompiledMethod containingPackage).
    (method belongsTo packagedIn ~~ method packagedIn) ifTrue: [
        method packagedIn addExtendedClass: method belongsTo.
        method belongsTo addExtendedInPackages: method packagedIn
    ].
    method setHasClassScope: (aCompiledMethod mclass isMeta).
    method setCategory: (aCompiledMethod mclass organization categoryOfElement: aCompiledMethod selector).
    method bePublic.

    importingContext shouldImportMethodBody ifTrue: [
        | visitor |
        visitor := SmalltalkMethodVisitor on: self.
        visitor runWith: aCompiledMethod and: method ].
    ^method


I will check in our lovely moose and our incredibly more efficient environment.

Stef





Le 10/3/15 13:01, stepharo a écrit :
Hi

I'm wondering how we handle the following case:
    - we have a method with the same name on instance and class
    - we import by merging class and metaclass.

I remember that I payed attention to that for ClassVariable but I do not see
how I handle it in the SmalltalkImporter.

Does one of you remember?

Stef
_______________________________________________
Moose-dev mailing list
[hidden email]
https://www.iam.unibe.ch/mailman/listinfo/moose-dev


_______________________________________________
Moose-dev mailing list
[hidden email]
https://www.iam.unibe.ch/mailman/listinfo/moose-dev



_______________________________________________
Moose-dev mailing list
[hidden email]
https://www.iam.unibe.ch/mailman/listinfo/moose-dev



--

"Every thing has its own flow"
_______________________________________________
Moose-dev mailing list
[hidden email]
https://www.iam.unibe.ch/mailman/listinfo/moose-dev


_______________________________________________
Moose-dev mailing list
[hidden email]
https://www.iam.unibe.ch/mailman/listinfo/moose-dev