git/GitCommitDialog.st
author vranyj1@bd9d3459-6c23-4dd9-91de-98eeebb81177
Sat, 06 Oct 2012 22:35:46 +0000
changeset 31 d96d7eff6efc
parent 30 fe60ba16ea8b
child 32 ae16175e5140
permissions -rw-r--r--
- GitDiffDeltaStructure added: #version #version_GIT - GitCheckoutStrategy added: #version #version_GIT - GitDiffOptionsStructure added: #version #version_GIT - GitTreewalkModeType added: #version #version_GIT - GitRemoteHandle added: #version #version_GIT - GitIndex added: #version #version_GIT - GitIndexEntryUnmergedStructure added: #version #version_GIT - GitWorkingCopyEntry added: #printOn: #version #version_GIT - GitIndexTimeStructure added: #version #version_GIT - GitIndexerHandle added: #version #version_GIT - GitSubmoduleHandle added: #version #version_GIT - GitSourceCodeManager2 added:9 methods changed: #isResponsibleForPackage: #managerTypeName #repositoryNameForPackage: #revisionInfoFromString: - GitAttrType added: #version #version_GIT - GitTask added: #version #version_GIT - GitTreeHandle added: #version #version_GIT - GitWorkingCopy added: #version #version_GIT - GitReflogHandle added: #version #version_GIT - GitFilemodeType added: #version #version_GIT - GitSignatureQuery added: #version #version_GIT - GitPackage added:27 methods changed: #commitTask #package category of: #commitTask - GitIndexerStreamHandle added: #version #version_GIT - GitOdbBackendStructure added: #version #version_GIT - GitLibraryObject added: #version #version_GIT - GitStatusShowType added: #version #version_GIT - GitObjectHandle added: #version #version_GIT - GitOdbHandle added: #version #version_GIT - GitSubmoduleStatusType added: #version #version_GIT - GitSignatureStructure added: #version #version_GIT - GitBlobHandle added: #version #version_GIT - GitConfigHandle added: #version #version_GIT - GitCvarType added: #version #version_GIT - GitStringArray added: #version #version_GIT - GitRepository added: #discover: #version #version_GIT #workingCopyForPackage: changed: #open: - GitConfigFileStructure added: #version #version_GIT - GitPrimitives added: #version #version_GIT - GitRefType added: #version #version_GIT - GitResetType added: #version #version_GIT - GitReference added: #version #version_GIT - GitIndexHandle added: #version #version_GIT - GitRemoteCallbacksStructure added: #version #version_GIT - GitObjectType added: #version #version_GIT - GitSubmoduleIgnoreType added: #version #version_GIT - GitSubmoduleUpdateType added: #version #version_GIT - GitTagHandle added: #version #version_GIT - GitReflogEntryHandle added: #version #version_GIT - GitRefspecHandle added: #version #version_GIT - GitTreebuilderHandle added: #version #version_GIT - GitDialog added: #version #version_GIT - GitErrorKlass added: #version #version_GIT - GitRepositoryObject added: #version #version_GIT - GitRemote added: #version #version_GIT - GitPackageManager added: #packageNamed: #version #version_GIT #version_SVN changed: #initialize - GitOdbObjectHandle added: #version #version_GIT - GitRepositoryInitOptionsStructure added: #version #version_GIT - stx_libscm_git added: #version #version_GIT changed: #classNamesAndAttributes - GitBranchType added: #version #version_GIT - GitTimeStructure added: #version #version_GIT - GitSignature added: #version #version_GIT - GitCommand added: #version #version_GIT - GitDiffRangeStructure added: #version #version_GIT - GitRemoteCompletionType added: #version #version_GIT - GitErrorStructure added: #version #version_GIT - GitRepositoryHandle added: #version #version_GIT - GitCheckoutOptions added: #version #version_GIT - GitAuthorQuery added: #version #version_GIT - GitSourceCodeManagementSettingsAppl2 added:11 methods changed: #windowSpec - GitOdbStreamStructure added: #version #version_GIT - GitStructure added: #version #version_GIT - GitCommit added: #version #version_GIT - GitRemoteHeadStructure added: #version #version_GIT - GitTree added: #version #version_GIT - GitOidShortenHandle added: #version #version_GIT - GitStatusOptionsStructure added: #version #version_GIT - GitCvarMapStructure added: #version #version_GIT - GitReferenceHandle added: #version #version_GIT - GitCommitHandle added: #version #version_GIT - GitError added: #version #version_GIT - GitDiffListHandle added: #version #version_GIT - GitCommitterQuery added: #version #version_GIT - GitIndexerStatsStructure added: #version #version_GIT - GitNoteDataStructure added: #version #version_GIT - GitFileoutLikeTask added: #version #version_GIT changed:6 methods - GitObject added: #version #version_GIT - GitOid added: #version #version_GIT - GitTreeEntryHandle added: #version #version_GIT - GitDiffFileStructure added: #version #version_GIT - GitTag added: #version #version_GIT - GitDeltaType added: #version #version_GIT - GitIndexEntryStructure added: #version #version_GIT - GitRevwalkHandle added: #version #version_GIT - GitCommitDialog added: #version #version_GIT comment/format in: #doRunSanityChecks changed: #defaultSubtitle - GitStatusCodes added: #version #version_GIT - GitIconLibrary added: #version #version_GIT - GitNoteHandle added: #version #version_GIT - GitCommitTask added: #version #version_GIT changed: #doCommit #doSanityChecks - extensions ...

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

GitDialog subclass:#GitCommitDialog
	instanceVariableNames:'task messageView messageModifiedHolder fileSelectionHolder
		fileListShowOnlyModifiedHolder fileListHolder enabledHolder'
	classVariableNames:''
	poolDictionaries:''
	category:'SCM-Git-StX-Interface'
!

Object subclass:#FileEntry
	instanceVariableNames:'application entry include'
	classVariableNames:''
	poolDictionaries:''
	privateIn:GitCommitDialog
!


!GitCommitDialog class methodsFor:'interface specs'!

contentSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the UIPainter may not be able to read the specification."

    "
     UIPainter new openOnClass:SVN::CommitDialog2 andSelector:#contentSpec
     SVN::CommitDialog2 new openInterface:#contentSpec
    "

    <resource: #canvas>

    ^ 
     #(FullSpec
        name: contentSpec
        window: 
       (WindowSpec
          label: 'Commit...'
          name: 'Commit...'
          min: (Point 10 10)
          bounds: (Rectangle 0 0 698 529)
        )
        component: 
       (SpecCollection
          collection: (
           (VariableVerticalPanelSpec
              name: 'VariablePanel'
              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
              component: 
             (SpecCollection
                collection: (
                 (ViewSpec
                    name: 'MessageAndInfoPane'
                    component: 
                   (SpecCollection
                      collection: (
                       (SubCanvasSpec
                          name: 'InfoPanel'
                          layout: (LayoutFrame 0 0 0 0 0 1 40 0)
                          level: 0
                          initiallyInvisible: true
                          hasHorizontalScrollBar: false
                          hasVerticalScrollBar: false
                          clientKey: infoPanel
                          createNewBuilder: false
                        )
                       (ViewSpec
                          name: 'MessagePane'
                          layout: (LayoutFrame 0 0 0 0 0 1 0 1)
                          component: 
                         (SpecCollection
                            collection: (
                             (LabelSpec
                                label: 'Commit message:'
                                name: 'MessageLabel'
                                layout: (LayoutFrame 0 0 0 0 0 1 25 0)
                                translateLabel: true
                                adjust: left
                              )
                             (TextEditorSpec
                                name: 'Message'
                                layout: (LayoutFrame 0 0 30 0 0 1 0 1)
                                enableChannel: enabledHolder
                                hasHorizontalScrollBar: true
                                hasVerticalScrollBar: true
                                modifiedChannel: messageModifiedHolder
                                hasKeyboardFocusInitially: false
                                postBuildCallback: messageView:
                              )
                             )
                           
                          )
                        )
                       )
                     
                    )
                  )
                 (ViewSpec
                    name: 'FilePane'
                    component: 
                   (SpecCollection
                      collection: (
                       (UISubSpecification
                          name: 'FilePaneSpec'
                          layout: (LayoutFrame 0 0 0 0 0 1 0 1)
                          minorKey: filePaneSpec
                        )
                       )
                     
                    )
                  )
                 )
               
              )
              handles: (Any 0.5 1.0)
            )
           )
         
        )
      )
!

fileListColumnSpec
    "This resource specification was automatically generated
     by the DataSetBuilder of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the DataSetBuilder may not be able to read the specification."

    "
     DataSetBuilder new openOnClass:SVN::CommitDialog2 andSelector:#fileListColumnSpec
    "

    <resource: #tableColumns>

    ^#(
      (DataSetColumnSpec
         label: ''
         activeHelpKey: ''
         activeHelpKeyForLabel: ''
         labelButtonType: None
         width: 22
         minWidth: 22
         editorType: CheckToggle
         rendererType: CheckToggle
         model: include
         menuFromApplication: false
         printSelector: include
         showRowSeparator: false
         showColSeparator: false
       )
      (DataSetColumnSpec
         label: ''
         activeHelpKey: ''
         activeHelpKeyForLabel: ''
         labelButtonType: Button
         width: 22
         minWidth: 22
         menuFromApplication: false
         printSelector: statusIcon
         canSelect: false
         showRowSeparator: false
         showColSeparator: false
       )
      (DataSetColumnSpec
         label: 'Container'
         labelAlignment: left
         activeHelpKey: ''
         activeHelpKeyForLabel: ''
         labelButtonType: Button
         menuFromApplication: false
         printSelector: pathText
         canSelect: false
         showRowSeparator: false
         showColSeparator: false
       )
      (DataSetColumnSpec
         label: 'Rev'
         activeHelpKey: ''
         activeHelpKeyForLabel: ''
         labelButtonType: Button
         usePreferredWidth: true
         menuFromApplication: false
         printSelector: revision
         canSelect: false
         showRowSeparator: false
         showColSeparator: false
       )
      (DataSetColumnSpec
         label: 'Author'
         labelAlignment: left
         activeHelpKey: ''
         activeHelpKeyForLabel: ''
         labelButtonType: Button
         usePreferredWidth: true
         menuFromApplication: false
         printSelector: author
         canSelect: false
         showRowSeparator: false
         showColSeparator: false
       )
      (DataSetColumnSpec
         label: 'Date'
         activeHelpKey: ''
         activeHelpKeyForLabel: ''
         labelButtonType: Button
         usePreferredWidth: true
         menuFromApplication: false
         printSelector: date
         canSelect: false
         showRowSeparator: false
         showColSeparator: false
       )
      )
    
!

filePaneSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the UIPainter may not be able to read the specification."

    "
     UIPainter new openOnClass:SVN::CommitDialog2 andSelector:#filePaneSpec
     SVN::CommitDialog2 new openInterface:#filePaneSpec
    "

    <resource: #canvas>

    ^ 
     #(FullSpec
        name: filePaneSpec
        window: 
       (WindowSpec
          label: 'File List'
          name: 'File List'
          min: (Point 10 10)
          bounds: (Rectangle 0 0 586 403)
        )
        component: 
       (SpecCollection
          collection: (
           (LabelSpec
              label: 'Checked files will be commited to repository.'
              name: 'FileListLabel'
              layout: (LayoutFrame 0 0 10 0 0 1 35 0)
              translateLabel: true
              adjust: left
            )
           (DataSetSpec
              name: 'WCEntryTable'
              layout: (LayoutFrame 0 0 35 0 0 1 -30 1)
              enableChannel: enabledHolder
              model: fileSelectionHolder
              menu: fileListMenu
              hasHorizontalScrollBar: true
              hasVerticalScrollBar: true
              dataList: fileListHolder
              useIndex: false
              columnHolder: fileListColumnSpec
              showLabels: false
              multipleSelectOk: true
            )
           (CheckBoxSpec
              label: 'Show only modified entries'
              name: 'ShowOnlyChanged'
              layout: (LayoutFrame 0 0 -30 1 -170 1 0 1)
              enableChannel: enabledHolder
              model: fileListShowOnlyModifiedHolder
              translateLabel: true
            )
           (LinkButtonSpec
              label: 'Browse working copy'
              name: 'BrowseWC'
              layout: (LayoutFrame -170 1 -30 1 0 1 0 1)
              translateLabel: true
              labelChannel: browseWorkingCopyLabel
              adjust: right
              model: doBrowseWorkingCopy
            )
           )
         
        )
      )
! !

!GitCommitDialog class methodsFor:'menu specs'!

fileListMenu
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the MenuEditor may not be able to read the specification."


    "
     MenuEditor new openOnClass:SVN::CommitDialog2 andSelector:#fileListMenu
     (Menu new fromLiteralArrayEncoding:(SVN::CommitDialog2 fileListMenu)) startUp
    "

    <resource: #menu>

    ^ 
     #(Menu
        (
         (MenuItem
            label: 'Show differences'
            itemValue: doShowDiffsForEntry
            translateLabel: true
          )
         (MenuItem
            label: 'Show differences (against HEAD)'
            itemValue: doShowDiffsForEntryAgainstHEAD
            translateLabel: true
          )
         )
        nil
        nil
      )
! !

!GitCommitDialog methodsFor:'accessing'!

defaultSubtitle
    | t |

    t := self task.
    ^t package notNil ifTrue:[
        'Package: ' , t package name asText allItalic
    ] ifFalse:[
        t workingCopy branch url asText allItalic
    ]

    "Created: / 28-10-2008 / 09:14:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 06-10-2012 / 23:07:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fileListToCommit
    ^(self fileListHolder value ? #()) 
        select:[:entry|entry include]
        thenCollect:[:entry|entry path].

    "Created: / 08-02-2012 / 18:16:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

message

    ^messageView notNil 
        ifTrue:[messageView contents]
        ifFalse:[nil]

    "Created: / 31-03-2008 / 21:06:28 / janfrog"
    "Modified: / 09-04-2009 / 08:50:55 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 08-02-2012 / 18:07:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

message: aString

    ^messageView contents: aString

    "Created: / 08-04-2009 / 23:27:09 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 08-02-2012 / 18:08:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

task

    ^self model

    "Created: / 23-03-2009 / 11:49:15 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

task: aTask

    ^self model: aTask

    "Created: / 23-03-2009 / 11:49:24 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

workingCopy

    ^self task workingCopy

    "Created: / 08-02-2012 / 18:07:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GitCommitDialog methodsFor:'acessing-views'!

messageView: aView

    messageView := aView scrolledView.
"/    messageView model:
"/        (self class messages
"/            at: self task package
"/            ifAbsent:[self task message])

    "Created: / 08-02-2012 / 17:58:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GitCommitDialog methodsFor:'actions'!

doAccept

    self showProgressWhile:[
            self acceptEnabled:false.

            (self task)
                message:self message;
                paths: self fileListToCommit;
                doCommit.

            self accept value:true
    ]

    "Created: / 01-04-2008 / 18:59:12 / janfrog"
    "Modified: / 19-08-2009 / 14:26:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 08-02-2012 / 18:17:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

doBrowseWorkingCopy
    self workingCopy browse

    "Modified: / 04-02-2012 / 17:15:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

doShowDiffsForEntry

    self fileSelectionHolder value do:[:each|
        self doShowDiffsForEntry: each entry against: Revision base
    ].

    "Created: / 09-02-2012 / 14:51:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

doShowDiffsForEntry: entry against: rev
    |wc wcChangeSet repoChangeSet diffset lang |

    wc := self task workingCopy.
    lang := entry programmingLanguage.
    (lang notNil and: [lang isSmalltalk]) ifTrue:[
        wcChangeSet := wc changeSetForContainer:entry path.
        wcChangeSet name: wcChangeSet name, (resources string: ' (working copy - to be commited)').
        repoChangeSet := wc changeSetForContainer:entry path revision:rev.
        diffset := ChangeSetDiff versionA:wcChangeSet versionB:repoChangeSet.
        (Tools::ChangeSetDiffTool new)
            beSingleColumn;
            diffset:diffset;
            title:('%1: Diffbetween working copy and rev. %2 ' bindWith: entry path with: rev printString);
            showVersionMethodDiffs: false;
            open
    ] ifFalse:[
        | text1 text2 |
        text1 := (wc containerReadStreamFor: entry path) contents asString.
        text2 := wc cat: entry path revision: rev.
        "/Argh...backward compatibility..."
        (Tools::TextDiff2Tool ? Tools::TextDiffTool) new
            labelA: 'Working copy';
            labelB: ('r %1' bindWith: rev printString);
            textA: text1; textB: text2;
            title:('%1: Diffbetween working copy and rev. %2 ' bindWith: entry path with: rev printString);
            open
    ]

    "Created: / 09-02-2012 / 14:53:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

doShowDiffsForEntryAgainstHEAD

    self fileSelectionHolder value do:[:each|
        self doShowDiffsForEntry: each entry against: Revision head
    ].

    "Created: / 10-02-2012 / 10:00:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GitCommitDialog methodsFor:'aspects'!

acceptButtonTitleAspect

    ^'Commit'

    "Created: / 08-02-2012 / 17:46:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

browseWorkingCopyLabel

    ^'Browse working copy...' asText
        colorizeAllWith: Color blue;
        actionForAll:[ self doBrowseWorkingCopy ];
        yourself

    "Created: / 05-02-2012 / 01:28:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

enabledHolder
    <resource: #uiAspect>

    enabledHolder isNil ifTrue:[
        enabledHolder := true asValue.
    ].
    ^ enabledHolder.

    "Modified (comment): / 11-02-2012 / 23:28:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fileListHolder
    <resource: #uiAspect>

    "automatically generated by UIPainter ..."

    "*** the code below creates a default model when invoked."
    "*** (which may not be the one you wanted)"
    "*** Please change as required and accept it in the browser."
    "*** (and replace this comment by something more useful ;-)"

    fileListHolder isNil ifTrue:[
        fileListHolder := ValueHolder new.
"/ if your app needs to be notified of changes, uncomment one of the lines below:
"/       fileListHolder addDependent:self.
"/       fileListHolder onChangeSend:#fileListHolderChanged to:self.
    ].
    ^ fileListHolder.

    "Modified: / 08-02-2012 / 18:27:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fileListShowOnlyModifiedHolder
    <resource: #uiAspect>

    "automatically generated by UIPainter ..."

    "*** the code below creates a default model when invoked."
    "*** (which may not be the one you wanted)"
    "*** Please change as required and accept it in the browser."
    "*** (and replace this comment by something more useful ;-)"

    fileListShowOnlyModifiedHolder isNil ifTrue:[
        fileListShowOnlyModifiedHolder := true asValue.
"/ if your app needs to be notified of changes, uncomment one of the lines below:
"/       fileListShowOnlyModifiedHolder addDependent:self.
       fileListShowOnlyModifiedHolder onChangeSend:#updateFileList to:self.
    ].
    ^ fileListShowOnlyModifiedHolder.

    "Modified: / 08-02-2012 / 18:04:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fileSelectionHolder
    <resource: #uiAspect>

    "automatically generated by UIPainter ..."

    "*** the code below creates a default model when invoked."
    "*** (which may not be the one you wanted)"
    "*** Please change as required and accept it in the browser."
    "*** (and replace this comment by something more useful ;-)"

    fileSelectionHolder isNil ifTrue:[
        fileSelectionHolder := ValueHolder new.
"/ if your app needs to be notified of changes, uncomment one of the lines below:
"/       fileSelectionHolder addDependent:self.
"/       fileSelectionHolder onChangeSend:#fileSelectionHolderChanged to:self.
    ].
    ^ fileSelectionHolder.
!

infoPanel
    infoPanel isNil ifTrue:[
        infoPanel := Tools::InlineMessageDialog new.
        infoPanel panelHiddenHolder: self enabledHolder.
    ].
    ^ infoPanel

    "Created: / 09-02-2012 / 19:23:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

messageModifiedHolder
    "return/create the 'messageModifiedHolder' value holder (automatically generated)"

    messageModifiedHolder isNil ifTrue:[
        messageModifiedHolder := ValueHolder with: false.
        messageModifiedHolder onChangeEvaluate:[
            self acceptEnabled: (self message indexOfNonSeparator ~~ 0).
            messageModifiedHolder setValue: false.
        ]
    ].
    ^ messageModifiedHolder

    "Modified: / 08-02-2012 / 18:46:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GitCommitDialog methodsFor:'change & update'!

updateFileList
    | entries showOnlyModified |

    showOnlyModified := fileListShowOnlyModifiedHolder value.
    entries := self workingCopy status.
    entries := entries reject:
        [:e|
        e status isUnversionedOrIgnoredOrMissing or:
            [
                fileListShowOnlyModifiedHolder value and:[ e status isNormal ]
            ]].
    entries := entries collect:[:entry|FileEntry application: self entry: entry].
    self fileListHolder value: entries

    "Created: / 08-02-2012 / 18:05:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GitCommitDialog methodsFor:'hooks'!

commonPostBuild

    self window extent: 640@640

    "Created: / 08-02-2012 / 18:30:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

postOpenWith: anUIBuilder

    self showProgressWhile:[ 
        self doUpdateCode.
        self doRunSanityChecks
    ].

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

!GitCommitDialog methodsFor:'private'!

doRunSanityChecks

    | checker problems anyError |

    self task isPackageCommit ifFalse:[
        self doUpdateWorkingCopy.
        ^self.
    ].

    ActivityNotification notify: (self resources string:'Checking code...').
    problems := (checker := self task doSanityChecks) problems.
    problems isEmptyOrNil ifTrue:[ 
        self doUpdateWorkingCopy.
        ^self.
    ].

    anyError := problems anySatisfy:[:problem|problem severity == #error].
    self infoPanel 
        reset;
        beWarning;
        message: 
            (problems size == 1 
                ifTrue:[self resources string:'A problem has been found in the code']
                ifFalse:[problems size printString , (self resources string:' problems has been found in the code')]);

        addButtonWithLabel: (self resources string:'Show')
                    action: [
                        Tools::ProjectCheckerBrowser new projectChecker: checker; open. self doCancel 
                    ];

        addButton:((Button label: (self resources string:'OK') 
                    action: [
                        self infoPanel beProgress.
                        self doUpdateWorkingCopy.
                        self infoPanel hide
                    ]) enabled: anyError not; yourself);

        addButtonWithLabel: (self resources string:'Cancel') 
                    action:[self doCancel];

        show.
    ^anyError not

    "Created: / 10-05-2012 / 17:24:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

doUpdateCode
    self task doPrepareWorkingCopy1

    "Created: / 10-05-2012 / 17:24:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

doUpdateWorkingCopy

    self task doPrepareWorkingCopy2.
    self message: self task message.
    self messageModifiedHolder changed:#value.
    self updateFileList.

    "Created: / 10-05-2012 / 17:25:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GitCommitDialog::FileEntry class methodsFor:'instance creation'!

application:applicationArg entry:entryArg 

    ^self new application:applicationArg entry:entryArg

    "Created: / 09-02-2012 / 14:34:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GitCommitDialog::FileEntry methodsFor:'accessing'!

author
    ^entry author

    "Created: / 09-02-2012 / 14:36:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

date
    ^entry date

    "Created: / 09-02-2012 / 14:36:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

entry
    ^ entry
!

include
    ^ include
!

include:aBoolean
    include := aBoolean.
!

path
    ^entry path

    "Created: / 09-02-2012 / 14:39:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

pathText
    ^entry pathText

    "Created: / 09-02-2012 / 14:36:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

revision
    ^entry revision

    "Created: / 09-02-2012 / 14:36:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

statusIcon
    ^entry statusIcon

    "Created: / 09-02-2012 / 14:36:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GitCommitDialog::FileEntry methodsFor:'initialization'!

application:applicationArg entry:entryArg 
    application := applicationArg.
    entry := entryArg.
    include := true

    "Modified: / 09-02-2012 / 14:35:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!GitCommitDialog class methodsFor:'documentation'!

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

version_SVN
    ^ '$Id::                                                                                                                        $'
! !