mercurial/HGWorkingCopyFile.st
author vranyj1@bd9d3459-6c23-4dd9-91de-98eeebb81177
Sat, 17 Nov 2012 01:11:36 +0000
changeset 67 985488894699
parent 63 77b0d42eebd0
child 69 17045d49309f
permissions -rw-r--r--
HGCommitDialog: nicer icons, fix for file list HGWorkingCopyFile>>pathNameRelative fixed

"{ Package: 'stx:libscm/mercurial' }"

Object subclass:#HGWorkingCopyFile
	instanceVariableNames:'wc children filename'
	classVariableNames:''
	poolDictionaries:''
	category:'SCM-Mercurial-Core'
!


!HGWorkingCopyFile class methodsFor:'instance creation'!

wc: aHGWorkingCopy path: aStringOrFilename
    ^self new setWorkingCopy: aHGWorkingCopy path: aStringOrFilename

    "Created: / 24-09-2012 / 13:52:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGWorkingCopyFile methodsFor:'accessing'!

pathName
    ^filename pathName

    "Created: / 12-11-2012 / 22:43:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

pathNameRelative
    ^self == wc root
        ifTrue:['']
        ifFalse:[filename pathName copyFrom: (wc root pathName size + 2)]

    "Created: / 25-09-2012 / 00:28:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 16-11-2012 / 11:23:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

status
    | cmd statuses  |

    cmd := HGCommand status.
    cmd workingDirectory: filename directory.
    cmd path: filename pathName.
    statuses := cmd execute.
    self assert: statuses size == 1.
    self assert: statuses first second = filename baseName.
    ^statuses first first.

    "Created: / 24-09-2012 / 22:27:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 09-11-2012 / 12:09:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGWorkingCopyFile methodsFor:'delegating'!

doesNotUnderstand: aMessage

    ^(filename respondsTo: aMessage selector) ifTrue:[
        aMessage sendTo: filename
    ] ifFalse:[
        super doesNotUnderstand: aMessage
    ].

    "Created: / 24-09-2012 / 13:46:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGWorkingCopyFile methodsFor:'enumerating-contents'!

directoryContentsAsFilenamesDo:aBlock
    "evaluate aBlock for each file in the directory represented by the receiver.
     The block is invoked with a filename-argument.
     The enumerations order is undefined - i.e. usually NOT sorted by
     filenames (but by creation time - on some systems).
     This excludes entries for '.' or '..'.
     NoOp for non-existing directories; however, this behavior
     may be changed in the near future, to raise an exception instead.
     So users of this method better test for existing directory before.
     Notice: this enumerates fileName objects; see also
     #directoryContentsDo:, which enumerates strings."

    self directoryContentsDo:[:entry |
        aBlock value:(self construct:entry).
    ]

    "
     '.' asFilename directoryContentsAsFilenamesDo:[:fn | Transcript showCR:fn pathName].
    "

    "Modified: / 18.9.1997 / 18:42:23 / stefan"
    "Modified: / 23.12.1999 / 20:56:35 / cg"
! !

!HGWorkingCopyFile methodsFor:'initialization'!

setWorkingCopy: aHGWorkingCopy path: aStringOrFilename

    wc := aHGWorkingCopy.
    filename := aStringOrFilename asFilename.

    "Created: / 24-09-2012 / 13:53:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGWorkingCopyFile methodsFor:'inspecting'!

browse
    "Opens a file browser on the working copy"

    UserPreferences current fileBrowserClass
        openOnDirectory: filename

    "Created: / 04-02-2012 / 17:14:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 15-11-2012 / 17:00:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGWorkingCopyFile methodsFor:'instance creation'!

/ aString
    ^self construct: aString

    "Created: / 24-09-2012 / 13:49:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

construct: aString
    ^(aString includes: Filename separator) ifTrue:[
        self components: (aString tokensBasedOn: Filename separator)
    ] ifFalse:[
        self component: aString
    ]

    "Created: / 24-09-2012 / 13:50:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGWorkingCopyFile methodsFor:'instance creation-private'!

component: aString
    children isNil ifTrue: [ children := Dictionary new ].
    ^children 
        at: aString 
        ifAbsentPut:[HGWorkingCopyFile wc: wc path: (filename construct: aString)]

    "Created: / 24-09-2012 / 23:26:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-10-2012 / 13:50:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

components: anArray"OfStrings"
    ^anArray inject: self into:[:entry :name | entry component: name ]

    "Created: / 24-09-2012 / 23:25:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGWorkingCopyFile methodsFor:'operations'!

moveTo: destination
    "Make sure that this entry is tracked by Mercurial"

    self isTracked ifTrue:[
        HGCommand mv
            workingDirectory: filename directory;
            source: filename pathName;
            destination: destination pathName;
            execute.
    ].
    filename moveTo: destination pathName

    "Created: / 15-11-2012 / 00:23:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

remove
    "Make sure that this entry is tracked by Mercurial"

    self isTracked ifTrue:[
        HGCommand remove
            workingDirectory: filename directory;
            paths: { filename baseName }
            execute
    ].
    filename remove

    "Created: / 15-11-2012 / 00:08:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

track
    "Make sure that this entry is tracked by Mercurial"

    self isUntracked ifTrue:[
        HGCommand add
            workingDirectory: filename directory;
            paths: { filename baseName };
            execute.
    ]

    "Created: / 15-11-2012 / 00:08:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGWorkingCopyFile methodsFor:'printing & storing'!

printOn:aStream
    "append a printed representation if the receiver to the argument, aStream"

    | path |

    aStream nextPut:$[.
    path := filename pathName.
    path := path copyFrom: wc path pathName size + 1.
    aStream nextPutAll: path.
    aStream nextPut:$].

    "Modified: / 17-10-2012 / 13:51:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGWorkingCopyFile methodsFor:'reading-directories'!

directoryContentsAsFilenames
    "return the contents of the directory as a collection of filenames.
     This excludes any entries for '.' or '..'.
     Returns nil for non-existing directories; however, this behavior
     may be changed in the near future, to raise an exception instead.
     So users of this method better test for existing directory before.
     Notice: 
        this returns the file-names as fileName instances; 
        see also #directoryContents, which returns strings."

    |names|

    names := filename directoryContents.
    names isNil ifTrue:[^ nil].
    ^ names collect:[:entry | self construct:entry].

    "
     '.' asFilename directoryContentsAsFilenames   
     '/XXXdoesNotExist' asFilename directoryContentsAsFilenames
    "

    "Modified: / 15-11-2012 / 01:13:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

directoryContentsAsFilenamesMatching: patternOrCollectionOfThose

    "
        Same as directoryContentsAsFilenames, but returns only files
        that matches given patterns. This uses String>>matches:
        for pattern matching
    "

    |names|

    names := filename directoryContentsMatching: patternOrCollectionOfThose .
    names isNil ifTrue:[^ nil].
    ^ names asOrderedCollection collect:[:entry | self construct:entry].

    "
    '/etc' asFilename
        directoryContentsAsFilenamesMatching: 'pass*'

    '/etc' asFilename
            directoryContentsAsFilenamesMatching: #('pass*' 'nsswitch.conf')
    "

    "Created: / 03-06-2009 / 09:57:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 15-11-2012 / 01:13:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

recursiveDirectoryContentsAsFilenames
    "return the contents of the directory and all subdirectories
     as a collection of filenames.
     This excludes any entries for '.' or '..'.
     Returns nil for non-existing directories; however, this behavior
     may be changed in the near future, to raise an exception instead.
     So users of this method better test for existing directory before.
     Notice: 
        this returns the file-names as fileName instances; 
        see also #recursiveDirectoryContents, which returns strings.

     Warning: this may take a long time to execute."

    |names|

    names := filename recursiveDirectoryContents.
    names isNil ifTrue:[^ nil].
    ^ names collect:[:entry | self construct:entry].

    "Created: / 15-11-2012 / 01:11:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGWorkingCopyFile methodsFor:'testing'!

isAdded
    ^ self status isAdded

    "Modified: / 23-10-2012 / 11:13:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isClean
    ^ self status isClean

    "Modified: / 23-10-2012 / 11:13:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isCleanOrIgnored
    | s |

    s := self status.
    ^s isClean or:[s isIgnored]

    "Created: / 15-11-2012 / 01:25:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isIgnored
    ^ self status isIgnored

    "Modified: / 23-10-2012 / 11:13:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isMissing
    ^ self status isMissing

    "Modified: / 23-10-2012 / 11:12:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isModified
    ^ self status isModified

    "Modified: / 23-10-2012 / 11:13:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isNotTracked
    ^ self status isNotTracked

    "Modified: / 23-10-2012 / 11:13:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isRemoved
    ^ self status isRemoved

    "Modified: / 23-10-2012 / 11:13:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isTracked
    | s |

    s := self status.
    ^s isNotTracked not and:[s isIgnored not and:[s isRemoved not]]

    "Created: / 15-11-2012 / 00:11:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isUntracked
    "An alias for not-tracked"
    ^ self isNotTracked

    "Created: / 14-11-2012 / 23:56:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isUntrackedOrIgnored
    | s |

    s := self status.
    ^s isNotTracked or:[s isIgnored]

    "Created: / 15-11-2012 / 01:23:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isUnversioned
    "An alias for not-tracked"
    ^ self isNotTracked

    "Created: / 14-11-2012 / 23:56:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!HGWorkingCopyFile class methodsFor:'documentation'!

version_HG
    "Never, ever change this method. Ask JV or CG why"
    ^thisContext method mclass theNonMetaclass instVarNamed: #revision
!

version_SVN
    ^ '§Id::                                                                                                                        §'
! !