SVN__WCEntry.st
author fm
Tue, 29 Sep 2009 17:18:15 +0200
changeset 168 71c57efc3d43
parent 40 aacce9a6ec9d
child 342 b9aa6e69af3e
permissions -rw-r--r--
changed: #version_SVN

"{ Package: 'cvut:stx/goodies/libsvn' }"

"{ NameSpace: SVN }"

Entry subclass:#WCEntry
	instanceVariableNames:'wc status'
	classVariableNames:''
	poolDictionaries:''
	category:'SVN-Working copy'
!


!WCEntry class methodsFor:'instance creation'!

path: aString

    ^self new
        path: aString;
        yourself

    "Created: / 27-08-2009 / 08:19:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

readFromXml: aXMLNode

    self assert: (aXMLNode isKindOf: XML::Node).
    ^self new readFromXml: aXMLNode

    "Created: / 18-08-2009 / 14:27:46 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!WCEntry methodsFor:'accessing'!

readStream

    ^self asFilename readStream

    "Created: / 27-08-2009 / 09:52:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

status
    ^ status

    "Created: / 17-08-2009 / 17:39:47 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

wc
    ^ wc
!

wc:aSVNWorkingCopy
    wc := aSVNWorkingCopy.
! !

!WCEntry methodsFor:'conversion'!

asFilename

    ^wc path / path

    "Created: / 27-08-2009 / 09:52:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!WCEntry methodsFor:'initialization'!

readFromXml: xmlNode

    path := xmlNode @ 'path'.
    status := Status withName: (xmlNode / 'wc-status' @ 'item').
    (status isUnversioned or:[status isAdded]) ifFalse:
        [| commitNode |
        commitNode := xmlNode / 'wc-status' / 'commit'.
        revision := (commitNode first
                        valueOfAttribute: 'revision' 
                        ifAbsent:[self error:'No revision attribute!!']) asNumber.
        author := (commitNode / 'author') characterData.
        date := Timestamp readISO8601From: (commitNode / 'date') characterData]

    "Modified: / 06-04-2008 / 21:36:51 / janfrog"
    "Created: / 18-08-2009 / 14:28:19 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!WCEntry methodsFor:'presentation'!

pathText

    ^status isNormal
        ifTrue:[path]
        ifFalse:[path asText allBold]

    "Created: / 11-04-2008 / 11:28:03 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

statusIcon
    ^ status icon

    "Created: / 17-08-2009 / 17:40:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!WCEntry methodsFor:'printing & storing'!

printOn: stream

    stream 
        space; nextPutAll: 'path:     '; nextPutAll: path; cr;
        space; nextPutAll: 'status:   '; nextPutAll: status printString; cr.
    status isUnversioned ifFalse:[
        stream
        space; nextPutAll: 'revision: '; nextPutAll: revision printString; cr;        
        space; nextPutAll: 'author:   '; nextPutAll: author ? '<unknown>'; cr;            
        space; nextPutAll: 'date:     '; nextPutAll: date printString; cr]

    "Created: / 16-03-2008 / 08:18:05 / janfrog"
    "Modified: / 11-04-2008 / 09:47:51 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!WCEntry methodsFor:'queries'!

sourceClassName

    "Guess name of the class contained in this source. Guess is based only
     on file name"

    | name |
    name := path copyFrom:(path lastIndexOf: $/) + 1 to: (path size - self sourceLanguage sourceFileSuffix size) - 1.
    name := name replaceAll:$_ with: $:.
    ^name asSymbol

    "Created: / 27-08-2009 / 08:40:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

sourceLanguage

    "Guess language of source, nil if not language guessed. Current 
     implementation is bit stupid - guess language by file suffix"

    ProgrammingLanguage allDo:
        [:lang|(path endsWith: lang sourceFileSuffix) ifTrue:[^lang]].
    ^nil

    "Created: / 27-08-2009 / 08:42:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!WCEntry methodsFor:'testing'!

isDirEntry

    ^kind isDir

    "Created: / 27-08-2009 / 08:38:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isFileEntry

    ^kind isFile

    "Created: / 27-08-2009 / 08:26:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isSourceFileEntry

    ^self isFile and: [self sourceLanguage notNil]

    "Created: / 27-08-2009 / 08:38:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!WCEntry class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
!

version_SVN
    ^'Id: SVN__WCEntry.st 113 2009-08-28 11:43:01Z vranyj1 '
! !