ClassChange.st
author Claus Gittinger <cg@exept.de>
Sun, 02 Feb 2003 16:51:57 +0100
changeset 1201 f3966132ad65
parent 1197 bc742b87f66d
child 1203 379d9644b880
permissions -rw-r--r--
care for namespace setting

"
 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' }"

Change subclass:#ClassChange
	instanceVariableNames:'className'
	classVariableNames:''
	poolDictionaries:''
	category:'System-Changes'
!

!ClassChange 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
"
    Abstract superclass for class related changes
    They are typically held in a ChangeSet.

    [author:]
        Claus Gittinger
"
! !

!ClassChange class methodsFor:'instance creation'!

class:aClass
    ^ self new class:aClass

    "Created: 3.12.1995 / 14:01:32 / cg"
!

class:aClass source:source
    ^ self new class:aClass source:source

    "Created: 3.12.1995 / 14:01:32 / cg"
! !

!ClassChange methodsFor:'accessing'!

changeClass
    "the class of the change (nil if not present)"

    |className ns cls|

    className := self className.
    className isNil ifTrue:[^ nil].

    ns := (Class nameSpaceQuerySignal query) ? Smalltalk.
    cls := ns classNamed:className.
    cls isNil ifTrue:[
        ns ~~ Smalltalk ifTrue:[
            cls := Smalltalk classNamed:className
        ].
    ].
    ^ cls
!

changeClass:aClass
    "set the class of the change"

    className := aClass name.
!

class:aClass
    "set the class of the change"

    className := aClass name.

    "Created: 3.12.1995 / 14:01:45 / cg"
    "Modified: 15.7.1996 / 09:28:26 / cg"
!

class:aClass source:newSource
    "set both class and source of the change"

    className := aClass name.
    source := newSource.

    "Created: 3.12.1995 / 14:01:45 / cg"
    "Modified: 15.7.1996 / 09:28:26 / cg"
!

className 
    "return the className of the change"

    ^ self cutNameSpaceOf:className

    "Modified: 15.7.1996 / 09:28:35 / cg"
!

className:aString 
    "set the className of the change"

    className := aString

    "Modified: / 15.7.1996 / 09:28:35 / cg"
    "Created: / 16.2.1998 / 13:05:36 / cg"
! !

!ClassChange methodsFor:'applying'!

apply
    "apply the change"

    |ns|

    ns := Class nameSpaceQuerySignal isHandled 
            ifTrue:[ Class nameSpaceQuerySignal query ]
            ifFalse:[ self nameSpace ].

    Class nameSpaceQuerySignal answer:ns do:[
        Parser evaluate:(self source)
    ].
!

nameSpace
    |nsName nameSpace|

    (nsName := self nameSpaceName) notNil ifTrue:[
        ^ NameSpace name:nsName.
    ].
    ^ Smalltalk
!

nameSpaceName
    (className includes:$:) ifTrue:[
        "/ in a namespace
        ^ className upTo:$:.
    ].
    (className includes:$.) ifTrue:[
        "/ in a namespace
        ^ className upTo:$..
    ].
    ^ nil
! !

!ClassChange 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."

    source isNil ifTrue:[
        aStream nextPutAll:'an empty change'.
        ^ self
    ].
    aStream nextPutAll:(self class name , ' - ' , source string asCollectionOfLines first , '...').
! !

!ClassChange methodsFor:'queries'!

cutNameSpaceOf:aString
    aString notNil ifTrue:[
        (aString startsWith:'Kernel.') ifTrue:[
            ^ aString copyFrom:'Kernel.' size+1
        ].
        (aString startsWith:'Core.') ifTrue:[
            ^ aString copyFrom:'Core.' size+1
        ].
    ].
    ^ aString
!

isClassChange
    ^ true
! !

!ClassChange class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic3/ClassChange.st,v 1.32 2003-02-02 15:51:57 cg Exp $'
! !