Change.st
author Claus Gittinger <cg@exept.de>
Fri, 13 Oct 2006 00:51:23 +0200
changeset 1873 2cbdfc5da6d7
parent 1868 301a5aeb8176
child 2135 dddad5c46e91
permissions -rw-r--r--
changes for compare-project functionality

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

Object subclass:#Change
	instanceVariableNames:'source timeOfChangeIfKnown'
	classVariableNames:''
	poolDictionaries:''
	category:'System-Changes'
!

!Change 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 all kind of changes - managed in changeSets.

    [author:]
        Claus Gittinger
"
! !

!Change class methodsFor:'support'!

isSource:source1Arg sameSourceAs:source2Arg
    "return true, if the given sources are the same, ignoring tabs and whitespace differences."

    |source1 source2|

    source1 := source1Arg.
    source2 := source2Arg.

    source1 = source2 ifTrue:[^ true].

    source1 := source1 withoutTrailingSeparators asCollectionOfLines.
    source2 := source2 withoutTrailingSeparators asCollectionOfLines.
    source1 size ~~ source2 size ifTrue:[^ false].
    source1 := source1 collect:[:line | line withTabsExpanded withoutTrailingSeparators].
    source2 := source2 collect:[:line | line withTabsExpanded withoutTrailingSeparators].
    ^ source1 = source2

    "Created: / 25-07-2006 / 11:22:21 / cg"
! !

!Change methodsFor:'accessing'!

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

    ^ nil

!

changeSelector
    ^ nil

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

className
    "the className of the change"

    ^ nil

    "Modified: / 15.7.1996 / 09:26:34 / cg"
    "Created: / 6.2.1998 / 13:06:56 / cg"
!

file
    ^ nil "/ to be added as instvar
!

file:aFile position:anInteger
    ^ self "/ to be added 
!

objectType:aSymbol
    ^ self "/ to be added as instvar
!

prettyPrintedSource
    "return the prettyPrinted or normal source of the change"

    ^ self source
!

selector
    ^ nil

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

source
    "return the source of the change"

    |s|

    source isNil ifTrue:[
        s := String writeStream.
        self printOn:s.
        ^ s contents.
    ].
    ^ source

    "Modified: 15.7.1996 / 09:26:34 / cg"
!

source:someString
    "set the source of the change"

    "/ debugging only ...
    someString isString ifFalse:[
        (someString respondsTo:#string) ifFalse:[
            self halt:'argument should be string-like'
        ]
    ].
    source := someString

    "Modified: / 15.7.1996 / 09:26:34 / cg"
    "Created: / 16.2.1998 / 13:05:16 / cg"
!

timeOfChangeIfKnown
    ^ timeOfChangeIfKnown
!

timeStamp:aTimestamp
    timeOfChangeIfKnown := aTimestamp
! !

!Change methodsFor:'applying'!

apply
    "apply the change"

    self subclassResponsibility

    "Modified: / 13-10-2006 / 00:41:05 / cg"
! !

!Change methodsFor:'change notification'!

sendChangeNotificationThroughSmalltalk
    "intentionally left blank"
! !

!Change 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.)."

    ^ false

!

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

    ^ false

!

sameSourceAs:changeB
    "return true, if the given change has the same source as the receiver."

    ^ self class isSource:(self source) sameSourceAs:(changeB source)

    "Modified: / 25-07-2006 / 11:22:46 / cg"
! !

!Change methodsFor:'printing & storing'!

printStringWithoutClassName
    |s|

    s := String writeStream.
    self printWithoutClassNameOn:s.
    ^ s contents
!

printWithoutClassNameOn:aStream
    self printOn:aStream


! !

!Change methodsFor:'queries'!

isClassCategoryChange
    ^ false

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

isClassChange
    ^ false

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

isClassCommentChange
    ^ false

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

isClassDefinitionChange
    ^ false

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

isClassInstVarDefinitionChange
    ^ false

!

isClassRemoveChange
    ^ false

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

isClassRenameChange
    ^ false

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

isDoIt
    ^ false

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

isMethodCategoryChange
    ^ false
!

isMethodCategoryRenameChange
    ^ false

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

isMethodChange
    ^ false

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

isMethodDefinitionChange
    ^ false
!

isMethodRemoveChange
    ^ false
!

isPrimitiveChange
    ^ false

!

isPrimitiveDefinitionsChange
    ^ false

!

isPrimitiveFunctionsChange
    ^ false

!

isPrimitiveVariablesChange
    ^ false

!

isPrivateClassDefinitionChange
    ^ false

    "Created: / 12-10-2006 / 22:59:04 / cg"
! !

!Change class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic3/Change.st,v 1.44 2006-10-12 22:51:23 cg Exp $'
! !