MethodChange.st
author Claus Gittinger <cg@exept.de>
Thu, 26 Jul 2012 01:22:03 +0200
changeset 2846 221a345239fb
parent 2625 5dc802065e4b
child 2872 0d5507d570cd
permissions -rw-r--r--
comment/format in: #imageSource

"
 COPYRIGHT (c) 1993 by Claus Gittinger
	       All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic3' }"

ClassChange subclass:#MethodChange
	instanceVariableNames:'selector methodCategory privacy previousVersion'
	classVariableNames:'LastReplacementClass'
	poolDictionaries:''
	category:'System-Changes'
!

MethodChange subclass:#NamedMethodChange
	instanceVariableNames:'changeName'
	classVariableNames:''
	poolDictionaries:''
	privateIn:MethodChange
!

!MethodChange class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 by Claus Gittinger
	       All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    instances represent method-changes (as done in the browser). 
    They are typically held in a ChangeSet.

    [author:]
        Claus Gittinger
"
! !

!MethodChange class methodsFor:'instance creation'!

class:cls selector:sel category:cat 
    ^ self basicNew class:cls selector:sel category:cat


!

class:cls selector:sel source:src category:cat
    ^ self basicNew class:cls selector:sel source:src category:cat
!

className:clsName selector:sel category:cat 
    ^ self basicNew className:clsName selector:sel category:cat

    "Created: / 12-11-2006 / 15:54:25 / cg"
!

className:clsName selector:sel source:src category:cat
    ^ self basicNew className:clsName selector:sel source:src category:cat
! !

!MethodChange methodsFor:'accessing'!

category
    ^ methodCategory 
!

category: aCategory
    methodCategory := aCategory

    "Created: / 7.2.1998 / 19:47:53 / cg"
!

changeMethod
    |cls|

    cls := self changeClass.
    cls isNil ifTrue:[^ nil].
    ^ cls compiledMethodAt:selector 

    "Created: / 7.2.1998 / 19:47:53 / cg"
!

changeSelector
    ^ selector

    "Created: / 6.2.1998 / 13:29:25 / cg"
!

class:cls selector:sel source:src category:cat
    self className:(cls name) selector:sel source:src category:cat
!

className:clsName selector:sel source:src category:cat
    self className:clsName selector:sel source:src category:cat privacy:nil
!

className:clsName selector:sel source:src category:cat privacy:priv
    self assert:(src isString).
    self assert:(sel isString or:[sel isSymbol]).

    className := clsName.
    selector := sel.
    source := src.
    methodCategory := cat.
    privacy := priv.

    "Created: / 16.2.1998 / 12:29:49 / cg"
    "Modified: / 16.2.1998 / 14:28:12 / cg"
!

delta
    "/ obsolete: please use deltaDetail

    | mth |

    self isMethodCodeChange ifFalse:[^super delta].
    mth := self changeMethod.
    mth isNil ifTrue:[^#+].
    ^(self class isSource: self source sameSourceAs: mth source)
        ifTrue:[#=]
        ifFalse:[#~]

    "Modified: / 18-11-2011 / 14:48:50 / cg"
!

deltaDetail
    "Returns a delta to the current state as a ChangeDelta object"

    | mth mySource imageSource|

    self isMethodCodeChange ifFalse:[^super deltaDetail].
    mth := self changeMethod.
    mth isNil ifTrue:[^ ChangeDeltaInformation added ].
    mySource := self source.
    imageSource := mth source.
    ^(self class isSource: mySource sameSourceAs: imageSource)
        ifTrue:[ ChangeDeltaInformation identical ]
        ifFalse:[ ChangeDeltaInformation different ]

    "Created: / 31-08-2011 / 10:27:58 / cg"
!

imageSource
    "return the source for the in-image version of the method"

    | mth |

    self isMethodCodeChange ifFalse:[^ super imageSource].
    mth := self changeMethod.
    ^ mth isNil 
        ifTrue: [nil] 
        ifFalse:[mth source]

    "Created: / 19-07-2011 / 12:02:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (format): / 25-07-2012 / 17:37:52 / cg"
!

methodCategory

    ^ methodCategory

    "Created: / 7.2.1998 / 19:47:53 / cg"
!

previousPackage
    | isNewMethod |
    isNewMethod := self previousVersion isNil.
    isNewMethod ifFalse:[
        ^ self previousVersion package.
    ].

    ^ nil
!

previousVersion
    "return the value of the instance variable 'previousVersion' (automatically generated)"

    ^ previousVersion
!

previousVersion:something
    "set the value of the instance variable 'previousVersion' (automatically generated)"

    previousVersion := something.
!

previousVersionSource
    "return the value of the instance variable 'previousVersion' (automatically generated)"

    previousVersion isNil ifTrue:[^ nil].
    ^ previousVersion source
!

selector
    ^ selector

    "Created: / 6.2.1998 / 13:29:25 / cg"
!

selector:aSymbol
    self assert:(aSymbol isSymbol).

    selector := aSymbol

    "Created: / 6.2.1998 / 13:29:25 / cg"
! !

!MethodChange methodsFor:'applying'!

apply
    "apply the change"

    |class replacementClassName suggestion|

    class := self changeClass.
    class isNil ifTrue:[
        "/ try the same replacement class again
        (LastReplacementClass notEmptyOrNil 
            and:[ (class := Smalltalk classNamed:LastReplacementClass) notNil
            and:[ 
                (className endsWith:' class') ifTrue:[
                    class := class theMetaclass
                ] ifFalse:[
                    class := class theNonMetaclass
                ].
                class nameWithoutPrefix = className    
            ]])
        ifFalse:[
            "/ try a replacement class in the same namespace again
            suggestion := LastReplacementClass.
            (class notNil
            and:[ (class := class nameSpace classNamed:className) notNil
            and:[ 
                (className endsWith:' class') ifTrue:[
                    class := class theMetaclass
                ] ifFalse:[
                    class := class theNonMetaclass
                ].
                class nameWithoutPrefix = className    
            ]])
            ifFalse:[
                "/ ask for a replacement class
                replacementClassName := Dialog 
                                request:('Cannot apply change for missing class: %1\\Use replacement class (or press cancel)' bindWith:className) withCRs
                                initialAnswer:suggestion.
                replacementClassName isNil ifTrue:[ AbortSignal raise ].

                (replacementClassName isEmptyOrNil
                or:[ (class := Smalltalk classNamed:replacementClassName) isNil]) ifTrue:[
                    self error:('Cannot apply change for missing class: ' , replacementClassName) mayProceed:true.
                    ^ self
                ].
                (className endsWith:' class') ifTrue:[
                    class := class theMetaclass
                ] ifFalse:[
                    class := class theNonMetaclass
                ].
                LastReplacementClass := replacementClassName
            ]
        ]
    ].
    class compile:source classified:methodCategory logged:true.

    "Modified: / 07-09-2011 / 21:09:19 / cg"
! !

!MethodChange methodsFor:'comparing'!

isForSameAs:changeB
    "return true, if the given change represents a change for the same
     thingy as the receiver (i.e. same method, same definition etc.)."

    "/ I am a methodChange - B must be as well.
    changeB isMethodChange ifFalse:[^ false].   

    selector ~= changeB selector ifTrue:[^ false].
    className ~= changeB className ifTrue:[^ false].

    ^ true
!

sameAs:changeB
    "return true, if the given change represents the same change as the receiver."

    (self isForSameAs:changeB) ifFalse:[^ false].   
    (self sameSourceAs:changeB) ifTrue:[^ true].

    ^ false.

    "Modified: / 25-07-2006 / 11:23:27 / cg"
! !

!MethodChange methodsFor:'converting'!

asNamedMethodChange
    ^ NamedMethodChange fromMethodChange:self
! !

!MethodChange methodsFor:'fileout'!

basicFileOutOn: aStream

    |cat |

    self isMethodCodeChange ifFalse:[^super basicFileOutOn: aStream].



    aStream nextPutChunkSeparator.
    self className printOn:aStream.
"/        self printClassNameOn:aStream.

    (privacy ? #public) ~~ #public ifTrue:[
        aStream space; nextPutAll:privacy; nextPutAll:'MethodsFor:'.
    ] ifFalse:[
        aStream nextPutAll:' methodsFor:'.
    ].

    cat := methodCategory ? ''.
    aStream nextPutAll:cat asString storeString.
    aStream nextPutChunkSeparator; cr; cr.

    source := self source.
    source isNil ifTrue:[
        ClassDescription fileOutErrorSignal
            raiseRequestWith:self
            errorString:(' - no source for method: ' ,
                         self className , '>>' , selector).

    ] ifFalse:[
        aStream nextChunkPut:source.
    ].
    aStream space.
    aStream nextPutChunkSeparator.
    aStream cr; cr

    "Modified: / 05-12-2009 / 12:38:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!MethodChange methodsFor:'printing & storing'!

printOn:aStream
    "append a user printed representation of the receiver to aStream.
     The format is suitable for a human - not meant to be read back."

    aStream
	nextPutAll:(self className ? 'unnamed');
	nextPutAll:'>>';
	nextPutAll:(selector ? '?');
	nextPutAll:' {';
	nextPutAll:(methodCategory ? '?');
	nextPutAll:'}'

    "Modified: / 04-10-2006 / 16:46:01 / cg"
    "Modified: / 07-11-2008 / 08:29:03 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

printWithoutClassNameOn:aStream
    (className endsWith:' class') ifTrue:[
        aStream nextPutAll:'class '
    ].
    aStream nextPutAll:selector 
!

printWithoutOwningClassOn:aStream
    self breakPoint:#cg.
    (className endsWith:' class') ifTrue:[
        aStream nextPutAll:'class '
    ].
    aStream nextPutAll:selector 
!

sourceForMethod
    ^ '(' , className , ' compiledMethodAt:' , selector asSymbol storeString, ')'

    "Created: / 09-10-2006 / 13:58:09 / cg"
! !


!MethodChange methodsFor:'testing'!

isMethodChange
    "true if this is a method related change"

    ^ true

    "Created: / 7.2.1998 / 19:26:59 / cg"
!

isMethodChangeForVersionMethod
    ^  self isMethodCodeChange
    and:[ AbstractSourceCodeManager isVersionMethodSelector:self selector ]
!

isMethodCodeChange
    "true if this is a method's code change (not package, category etc.)"

    ^ true
! !

!MethodChange methodsFor:'visiting'!

acceptChangeVisitor:aVisitor
    ^ aVisitor visitMethodChange:self.

    "Created: / 25-11-2011 / 17:13:50 / cg"
! !

!MethodChange::NamedMethodChange class methodsFor:'instance creation'!

fromMethodChange:aMethodChange
    ^ self new cloneInstanceVariablesFrom:aMethodChange
! !

!MethodChange::NamedMethodChange methodsFor:'accessing'!

changeName:something
    changeName := something.
! !

!MethodChange::NamedMethodChange methodsFor:'printing & storing'!

printOn:aStream
    changeName notNil ifTrue:[
        changeName printOn:aStream.
        ^ self.
    ].
    super printOn:aStream
! !

!MethodChange class methodsFor:'documentation'!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic3/MethodChange.st,v 1.65 2012-07-25 23:22:03 cg Exp $'
!

version_SVN
    ^ '§ Id: MethodChange.st 1867 2011-06-08 21:57:08Z vranyj1  §'
! !