Added tool to update copyright notices in files based on commits
authorJan Vrany <jan.vrany@fit.cvut.cz>
Tue, 17 Apr 2018 14:58:16 +0100
changeset 817 e38e4f23a097
parent 816 1d895084db29
child 833 860d1fc77665
Added tool to update copyright notices in files based on commits For more details see documentation of class `HGCopyrightUpdateTool`
mercurial/HGChangeset.st
mercurial/HGChangesetFile.st
mercurial/HGContribution.st
mercurial/HGCopyrightLine.st
mercurial/HGCopyrightUpdateTool.st
mercurial/HGCopyrightUpdater.st
mercurial/HGStXTests.st
mercurial/HGTagOrBookmark.st
mercurial/HGWorkingCopyFile.st
mercurial/Make.proto
mercurial/Make.spec
mercurial/abbrev.stc
mercurial/bc.mak
mercurial/libInit.cc
mercurial/stx_libscm_mercurial.st
--- a/mercurial/HGChangeset.st	Thu Mar 29 22:22:31 2018 +0100
+++ b/mercurial/HGChangeset.st	Tue Apr 17 14:58:16 2018 +0100
@@ -656,6 +656,14 @@
     "Created: / 22-01-2013 / 13:38:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+isMerge
+    "Return `true`, if the changeset is a 'merge' changeset, `false` otherwise."
+
+    ^ self parent2 notNil.
+
+    "Created: / 23-04-2018 / 22:43:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 isObsolete
     "Return `true`, if the changeset is obsolete, `false` otherwise."
 
--- a/mercurial/HGChangesetFile.st	Thu Mar 29 22:22:31 2018 +0100
+++ b/mercurial/HGChangesetFile.st	Tue Apr 17 14:58:16 2018 +0100
@@ -18,6 +18,8 @@
 "
 "{ Package: 'stx:libscm/mercurial' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#HGChangesetFile
 	instanceVariableNames:'changeset name parent children'
 	classVariableNames:''
@@ -217,6 +219,16 @@
     ^self changeset repository
 
     "Created: / 17-11-2012 / 00:05:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+sha1
+    "Returns a SHA1 sum of file's contents"
+    | sha1 |
+
+    self readingFileDo:[:s | sha1 := SHA1Stream hashValueOf:s].
+    ^ sha1
+
+    "Created: / 24-04-2018 / 15:37:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !HGChangesetFile methodsFor:'accessing-private'!
@@ -240,6 +252,23 @@
     "Created: / 01-12-2012 / 01:29:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!HGChangesetFile methodsFor:'enumerating'!
+
+recursiveDirectoryContentsDo:aBlock 
+    "Evaluates `aBlock` for itself and all children recursivelly,
+     passing the child to the block."
+
+    children notEmptyOrNil ifTrue:[ 
+        children do:[:each | 
+            aBlock value: each.    
+            each recursiveDirectoryContentsDo:aBlock.
+        ]
+    ].
+
+    "Created: / 13-04-2018 / 22:46:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 23-04-2018 / 22:38:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !HGChangesetFile methodsFor:'initialization'!
 
 setChangeset: anHGChangeset name: aString
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/mercurial/HGContribution.st	Tue Apr 17 14:58:16 2018 +0100
@@ -0,0 +1,264 @@
+"
+stx:libscm - a new source code management library for Smalltalk/X
+Copyright (C) 2012-2015 Jan Vrany
+
+This library is free software; you can redistribute it and/or
+modify it under the terms of the GNU Lesser General Public
+License as published by the Free Software Foundation; either
+version 2.1 of the License. 
+
+This library is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
+Lesser General Public License for more details.
+
+You should have received a copy of the GNU Lesser General Public
+License along with this library; if not, write to the Free Software
+Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+"
+"{ Package: 'stx:libscm/mercurial' }"
+
+"{ NameSpace: Smalltalk }"
+
+Object subclass:#HGContribution
+	instanceVariableNames:'changesets'
+	classVariableNames:'Date1 Date2'
+	poolDictionaries:''
+	category:'SCM-Mercurial-StX-Tools'
+!
+
+!HGContribution class methodsFor:'documentation'!
+
+copyright
+"
+stx:libscm - a new source code management library for Smalltalk/X
+Copyright (C) 2012-2015 Jan Vrany
+
+This library is free software; you can redistribute it and/or
+modify it under the terms of the GNU Lesser General Public
+License as published by the Free Software Foundation; either
+version 2.1 of the License. 
+
+This library is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
+Lesser General Public License for more details.
+
+You should have received a copy of the GNU Lesser General Public
+License along with this library; if not, write to the Free Software
+Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+"
+! !
+
+!HGContribution class methodsFor:'initialization'!
+
+initialize
+    "Invoked at system start or when the class is dynamically loaded."
+    Date1 := Timestamp fromString: '2011-04-01'.
+    Date2 := Timestamp fromString: '2015-03-31'.
+
+    "Modified: / 24-04-2018 / 15:31:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGContribution class methodsFor:'instance creation'!
+
+summaryFromChangesets:aCollection 
+    "of HGChangeser"
+    
+    | author2ChangesetMap |
+
+    author2ChangesetMap := Dictionary new.
+    aCollection do:[:cs |(author2ChangesetMap at:cs author ifAbsentPut:[Set new]) add:cs].  
+    ^ author2ChangesetMap values 
+        collect:[:changesets | self new setChangesets:changesets ].
+
+    "Created: / 16-04-2018 / 22:40:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 14-05-2018 / 20:06:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+summaryFromFile: anHGChangesetFile
+    | path branch revset changesets|
+
+    path := anHGChangesetFile pathName.
+    branch := anHGChangesetFile changeset branch name.
+    revset := 'ancestors(.) and filelog(''%1'') and !!merge() and branch(%2)' bindWith: path with: branch.
+    changesets := anHGChangesetFile repository log:revset limit:nil.
+    changesets := changesets select:[:each | self hasChangeset: each contributedTo: path ].
+    ^ self summaryFromChangesets: changesets
+
+    "
+    HGChangesetBrowser openOnRepository: anHGChangesetFile repository revset: (HGRevset fromString: revset).
+    "
+
+    "Created: / 17-04-2018 / 13:46:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 11-06-2018 / 09:39:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGContribution class methodsFor:'queries'!
+
+hasChangeset: anHGChangeset contributedTo: aString
+    "
+    Given a changeset and file, return true, if the changeset contains
+    changes that count as meaningful a 'contribution'.
+
+    Naively, each changeset that modifies a file is a 'contribution'. 
+    Due to long and complex history, not each changeset actually adds
+    anything meaningful. Namely:
+
+     1. Merge changesets are not counted as 'contribution'. Sadly, not
+        all merges are tracked in mercurial history since we've been
+        using SubVersion for a long time and subversion merges are
+        note recorded.
+
+     2. For couple years, JV was contracted by eXept. To be on a safe
+        side, in that period no changes of his counts as his contribution
+        (might be, but would be hard to tell and argue :-)
+
+     3. Modifications involving only version methods and/or #copyright method 
+        do not count as a 'contribution'.
+
+     Complicated. isn't it?
+    "
+
+    "/ 1. Merge changesets are not counted as 'contribution'.
+    anHGChangeset isMerge ifTrue:[ ^ false ].
+    (anHGChangeset summary includesString: 'trunk' caseSensitive: false) ifTrue:[ ^ false ].
+    (anHGChangeset summary includesString: 'merge' caseSensitive: false) ifTrue:[ ^ false ].
+
+    "/ 2. For couple years, JV was contracted by eXept
+    ((anHGChangeset author includesString: 'jan vrany' caseSensitive: false)
+        and:[ anHGChangeset timestamp between: Date1 and: Date2]) ifTrue:[ ^ false ].
+
+    "/ 3. Modifications involving only version methods do not count as
+    (aString endsWith:'.st') ifTrue:[ 
+        | file parent |
+
+        file := anHGChangeset / aString.
+        self assert: file notNil.
+        [
+            parent := anHGChangeset parent1 / aString.
+        ] on: HGError do:[:ex |
+            "/ HGChangeset >> #/ throws an `HGError` when file
+            "/ does not exist in that changeset. In that case,
+            "/ consider the changeset as contribution (it
+            "/ added the file),
+            ^ true.
+        ].
+        (parent notNil and:[ file sha1 ~= parent sha1 ]) ifTrue:[ 
+            | fileCS parentCS diffs |
+
+            [ 
+                file readingFileDo:[:s | fileCS := ChangeSet fromStream: s ].
+                parent readingFileDo:[:s | parentCS := ChangeSet fromStream: s ].
+            ] on: Error do:[:ex | 
+                "/ In case of an error, we cannot check. Let's play safe side
+                "/ and consider it no contribution.
+                ^ false
+            ].
+
+            diffs := fileCS diffSetsAgainst: parentCS.
+            diffs isEmpty ifTrue:[ ^ false ].
+
+            ((diffs changed allSatisfy: [ :pair | self isVersionOrCopyrightMethodChange: pair first ])
+                and:[ (diffs onlyInReceiver allSatisfy: [ :chg | self isVersionOrCopyrightMethodChange: chg])
+                and:[ (diffs onlyInArg allSatisfy: [ :chg | self isVersionOrCopyrightMethodChange: chg])]])
+                    ifTrue:[ ^ false ].    
+        ].
+    ].
+    ^ true.
+
+    "
+    HGCopyrightUpdater main:#('--cwd' 'libbasic' 'UnorderedNumbersError.st')
+    "
+
+    "Created: / 24-04-2018 / 14:56:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 30-05-2018 / 09:28:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGContribution class methodsFor:'testing'!
+
+isVersionOrCopyrightMethodChange:aChange
+    ^ aChange isMethodChange
+        and:[ (AbstractSourceCodeManager isVersionMethodSelector: aChange selector)
+                or:[ aChange selector == #copyright ] ]
+
+    "Created: / 14-05-2018 / 08:25:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGContribution methodsFor:'accessing'!
+
+author
+    ^ changesets anyOne author
+
+    "Created: / 16-04-2018 / 22:59:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+changesets
+    ^ changesets
+!
+
+name
+    ^ (self author upTo: $<) trimSeparators
+
+    "Created: / 16-04-2018 / 23:02:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+years
+    | years current |
+
+    years := OrderedCollection new.
+    changesets do:[:changeset | 
+        | year |
+
+        year := changeset timestamp year.
+        current isNil ifTrue:[ 
+            current := year to: year.
+        ] ifFalse:[                 
+            self assert: (current isKindOf: Interval).
+            (current stop ~~ year) ifTrue:[
+                current stop = (year - 1) ifTrue:[ 
+                    current stop: year.
+                ] ifFalse:[ 
+                    years add: current.
+                    current := year to: year.
+                ].
+            ].
+        ].
+    ].
+    years add: current.
+    ^ years.
+
+    "Created: / 23-04-2018 / 16:02:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 14-05-2018 / 12:32:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGContribution methodsFor:'initialization'!
+
+setChangesets: aChangessets
+    changesets := aChangessets asArray sort: [ :a :b | a timestamp < b timestamp ].
+
+    "Created: / 16-04-2018 / 22:45:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGContribution methodsFor:'printing & storing'!
+
+printOn:aStream
+    "append a printed representation of the receiver to the argument, aStream"
+
+    super printOn:aStream.
+    aStream nextPut: $(.
+    aStream nextPutAll: self author.
+    aStream nextPut: $).
+
+    "Modified: / 03-05-2018 / 23:16:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGContribution class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
+
+HGContribution initialize!
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/mercurial/HGCopyrightLine.st	Tue Apr 17 14:58:16 2018 +0100
@@ -0,0 +1,236 @@
+"
+stx:libscm - a new source code management library for Smalltalk/X
+Copyright (C) 2012-2015 Jan Vrany
+
+This library is free software; you can redistribute it and/or
+modify it under the terms of the GNU Lesser General Public
+License as published by the Free Software Foundation; either
+version 2.1 of the License. 
+
+This library is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
+Lesser General Public License for more details.
+
+You should have received a copy of the GNU Lesser General Public
+License along with this library; if not, write to the Free Software
+Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+"
+"{ Package: 'stx:libscm/mercurial' }"
+
+"{ NameSpace: Smalltalk }"
+
+Object subclass:#HGCopyrightLine
+	instanceVariableNames:'line prefix years holder'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'SCM-Mercurial-StX-Tools'
+!
+
+!HGCopyrightLine class methodsFor:'documentation'!
+
+copyright
+"
+stx:libscm - a new source code management library for Smalltalk/X
+Copyright (C) 2012-2015 Jan Vrany
+
+This library is free software; you can redistribute it and/or
+modify it under the terms of the GNU Lesser General Public
+License as published by the Free Software Foundation; either
+version 2.1 of the License. 
+
+This library is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
+Lesser General Public License for more details.
+
+You should have received a copy of the GNU Lesser General Public
+License along with this library; if not, write to the Free Software
+Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+"
+! !
+
+!HGCopyrightLine class methodsFor:'instance creation'!
+
+readFrom:aStringOrStream onError:aBlock 
+    "Parse a copyright line from given `aStringOrStream` (line). If given
+     stream does not contain copyright line, return value of `aBlock`"
+    
+    | l  s  c  p  y1  y2 |
+
+    l := aStringOrStream readStream contents.
+    s := l readStream.
+     
+    "/ skip leading whitespaces:    
+    
+    s skipSeparators.
+     
+    "/ skip (optional) asterisk and whitespace following it.    
+    
+    s peek == $* ifTrue:[
+        s next.
+        s skipSeparators.
+    ].
+     
+    "/ look for 'Copyright (c)' string. If found, this is a copyright
+    "/ line, otherwise it is not and we return `nil` to indicate that.
+    
+    c := (s "'COPYRIGHT (c) ' size" nextAvailable:14) asLowercase.
+    c = 'copyright (c) ' ifFalse:[
+        ^ aBlock value
+    ].
+    p := s position.
+     
+    "/ parse years
+    
+    s skipSeparators.
+    s peek isDigit ifTrue:[
+        y1 := y2 := s nextAvailable:4.
+        s skipSeparators.
+        s peek == $- ifTrue:[
+            s next.
+            s skipSeparators.
+            y2 := (s nextAvailable:4) trimSeparators.
+            s skipSeparators.
+        ].
+        (y1 allSatisfy:[:c | c isDigit ]) ifTrue:[
+            y1 := y1 asNumber.
+        ].
+        (y2 allSatisfy:[:c | c isDigit ]) ifTrue:[
+            y2 := y2 asNumber.
+        ].
+    ].
+    ^ (HGCopyrightLine new)
+        prefix:(l copyTo:p - 1);
+        years:(y1 notNil ifTrue:[
+                    y1 to:y2
+                ] ifFalse:[ nil ]);
+        holder:(l copyFrom:s position + 1);
+        yourself
+
+    "
+     HGCopyrigtLine readFrom: ' COPYRIGHT (c) 1994 by Claus Gittinger'
+     HGCopyrigtLine readFrom: '              All Rights Reserved'
+
+     HGCopyrigtLine readFrom: ' * COPYRIGHT (c) 1988-1995 by Claus Gittinger'
+     HGCopyrigtLine readFrom: ' *              All Rights Reserved'
+
+     HGCopyrigtLine readFrom: ' * COPYRIGHT (c) 2011-now Jan Vrany'
+     HGCopyrigtLine readFrom: ' *              All Rights Reserved'
+
+     HGCopyrigtLine readFrom: ' COPYRIGHT (c) Claus Gittinger / eXept Software AG'"
+    "Created: / 14-05-2018 / 16:12:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGCopyrightLine methodsFor:'accessing'!
+
+holder
+    ^ holder
+!
+
+holder:something
+    holder := something.
+!
+
+line
+    ^ line
+!
+
+line:something
+    line := something.
+!
+
+prefix
+    ^ prefix ? ' COPYRIGHT (C)'
+
+    "Modified: / 15-05-2018 / 13:16:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+prefix:something
+    prefix := something.
+!
+
+years
+    ^ years
+!
+
+years:something
+    years := something.
+! !
+
+!HGCopyrightLine methodsFor:'comparing'!
+
+< another
+    years ~= another years ifTrue:[ 
+        ^ years start < another years start
+            or:[ years stop < another years stop ]
+    ] ifFalse:[ 
+        ^ holder < another holder
+    ].
+
+    "Created: / 14-05-2018 / 16:54:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+= another
+    ^ self class == another class
+        and: [ prefix = another prefix
+        and: [ years = another years 
+        and: [ holder = another holder ]]]
+
+    "Created: / 14-05-2018 / 16:50:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+hash
+
+    "/ This is a really bad hash function, we need #hashMultiply:
+    "/ For now...
+    ^ prefix hash bitXor: (years hash bitXor: holder hash)
+
+    "Created: / 14-05-2018 / 16:48:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGCopyrightLine methodsFor:'converting'!
+
+asString
+    ^ String streamContents:[ :s|
+        s nextPutAll: self prefix; space.
+        years notNil ifTrue:[
+            years start printOn: s.
+            years start ~~ years stop ifTrue:[
+                s nextPut:$-.
+                years stop printOn: s.        
+            ].
+            s space.
+        ].
+        s nextPutAll: holder.
+    ].
+
+    "Created: / 14-05-2018 / 15:45:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-05-2018 / 13:16:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGCopyrightLine methodsFor:'printing & storing'!
+
+printOn:aStream
+    "append a printed representation of the receiver to the argument, aStream"
+
+    super printOn:aStream.
+    aStream nextPut:$(.
+    aStream nextPutAll: self asString.
+    aStream nextPut:$).
+
+    "Modified: / 14-05-2018 / 15:50:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGCopyrightLine methodsFor:'testing'!
+
+isYearToNow
+    "
+    Return true, if this copyright years is in form YYYY-now (such as 20017-now).
+    These are now considered invalid
+    "
+    ^ years notNil and:[ years stop = 'now' ]
+
+    "Created: / 15-05-2018 / 06:14:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/mercurial/HGCopyrightUpdateTool.st	Tue Apr 17 14:58:16 2018 +0100
@@ -0,0 +1,180 @@
+"
+stx:libscm - a new source code management library for Smalltalk/X
+Copyright (C) 2012-2015 Jan Vrany
+
+This library is free software; you can redistribute it and/or
+modify it under the terms of the GNU Lesser General Public
+License as published by the Free Software Foundation; either
+version 2.1 of the License. 
+
+This library is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
+Lesser General Public License for more details.
+
+You should have received a copy of the GNU Lesser General Public
+License along with this library; if not, write to the Free Software
+Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+"
+"{ Package: 'stx:libscm/mercurial' }"
+
+"{ NameSpace: Smalltalk }"
+
+StandaloneStartupHeadless subclass:#HGCopyrightUpdateTool
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'SCM-Mercurial-StX-Tools'
+!
+
+!HGCopyrightUpdateTool class methodsFor:'documentation'!
+
+copyright
+"
+stx:libscm - a new source code management library for Smalltalk/X
+Copyright (C) 2012-2015 Jan Vrany
+
+This library is free software; you can redistribute it and/or
+modify it under the terms of the GNU Lesser General Public
+License as published by the Free Software Foundation; either
+version 2.1 of the License. 
+
+This library is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
+Lesser General Public License for more details.
+
+You should have received a copy of the GNU Lesser General Public
+License along with this library; if not, write to the Free Software
+Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+"
+!
+
+documentation
+"
+Update copyright in files based on information in commits.
+
+It works as follows:
+
+ 1. For given file, it computes contributions from commits that 
+    'contributed' to that particular file. Not every commit that 
+    modifies a file is consider a contribution. See comment in
+    `HGContribution class >> hasChangeset:contributedTo:`.
+
+ 2. Based on contribution generate a set copyright lines. The 
+    years and name of copyright holder is taken from contributing
+    commits.
+
+ 3. Parse file contents and collect existing copyrights.
+
+ 4. Finally, add missing copyrights and save updated contents
+    backs.
+
+NOTE: that this tool never removes a copyright line, except in one 
+very specific case - if copyright line is in form YYYY-now and option
+`--remove-year-now` is given.
+
+"
+! !
+
+!HGCopyrightUpdateTool class methodsFor:'instance creation'!
+
+new
+    "return an initialized instance"
+
+    ^ self basicNew initialize.
+! !
+
+!HGCopyrightUpdateTool class methodsFor:'constants & defaults'!
+
+applicationUUID
+    "answer an application-specific unique uuid.
+     This is used as the name of some exclusive OS-resource, which is used to find out,
+     if another instance of this application is already running.
+     Under win32, a mutex is used; under unix, an exclusive file in the tempDir could be used.
+     If redefined, please return a real UUID (i.e. UUID fromString:'.....') and not a string or
+     similar possibly conflicting identifier.
+     You can paste a fresh worldwide unique id via the editor's 'more'-'misc'-'paste UUID' menu function."
+
+    ^ UUID fromString:'65a29670-3f5e-11e8-982c-606720e43e2c'
+! !
+
+!HGCopyrightUpdateTool class methodsFor:'startup'!
+
+main: argv
+    "Application entry point. `argv` is the array of command arguments (as Array of Strings)"
+
+    | optparser cwd verbose dryrun removeYearToNow patterns |
+
+    verbose := 0.
+    dryrun := removeYearToNow := false.
+    optparser := CmdLineParser new.
+    optparser
+        on: #('--cwd') do:[ :value | cwd := value ];
+        on: #('-v' '--verbose') do:[ verbose := verbose + 1 ];
+        on: #(     '--dry-run') do:[ dryrun := true ];
+        on: #(     '--remove-year-now') do:[ removeYearToNow := true ];
+        on: #('-h' '--help') do:[ self usage. Smalltalk exitIfStandalone:0 ].
+    [
+        patterns := optparser parse:argv.
+    ] on: CmdLineOptionError do:[:ex |
+        Stderr nextPutAll: 'ERROR: '; nextPutLine: ex description.
+        Smalltalk exitIfStandalone:0.        
+    ].
+    [
+        | updater repo |
+
+        updater := HGCopyrightUpdater new.
+        updater setVerbose: verbose.
+        updater setDryRun: dryrun.
+        updater setRemoveYearToNow: removeYearToNow.  
+
+        repo := HGRepository on: cwd ? '.'.
+
+        repo workingCopy parent1 root recursiveDirectoryContentsDo:[:file|
+            (file isDirectory not and:[patterns isEmpty or:[ patterns anySatisfy: [:each | file pathName matches: each ] ] ]) ifTrue:[
+                [ 
+                    updater updateFile: file.
+                ] on: Warning do:[:warning | 
+                    Stderr nextPutAll: 'WARNING: '; nextPutLine: warning description.
+                ].
+            ]
+        ].
+        Smalltalk exitIfStandalone: 0.  
+    ] on: Error do:[:ex | 
+        Stderr nextPutAll: 'ERROR: '; nextPutLine: ex description.
+        Smalltalk isStandAloneApp ifTrue:[ 
+            Smalltalk exit:1
+        ] ifFalse:[ 
+            ex pass.
+        ].
+    ].
+
+    "Modified: / 10-06-2018 / 21:00:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+usage
+    Stdout nextPutLine: 'Usage: stx --run ', self name, ' [options...] [pattern...]'.
+    Stdout nextPutLine: self commentOrDocumentationString.
+    Stdout 
+        nextPutLine:'Available options:';  
+        nextPutLine:'  --cwd DIR ............ change working directory DIR';
+        nextPutLine:'  -v | --verbose ....... verbose output (repeat for more info)';
+        nextPutLine:'  --dry-run ............ do not modify any file';
+        nextPutLine:'  --remove-year-now .... remove copyrights with years in form ''YYYY-now''';
+        nextPutLine:'  --help ............... output this message'.
+
+    "
+    HGCopyrightUpdateTool usage.
+    "
+
+    "Modified: / 17-05-2018 / 15:10:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGCopyrightUpdateTool class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/mercurial/HGCopyrightUpdater.st	Tue Apr 17 14:58:16 2018 +0100
@@ -0,0 +1,345 @@
+"
+stx:libscm - a new source code management library for Smalltalk/X
+Copyright (C) 2012-2015 Jan Vrany
+
+This library is free software; you can redistribute it and/or
+modify it under the terms of the GNU Lesser General Public
+License as published by the Free Software Foundation; either
+version 2.1 of the License. 
+
+This library is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
+Lesser General Public License for more details.
+
+You should have received a copy of the GNU Lesser General Public
+License along with this library; if not, write to the Free Software
+Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+"
+"{ Package: 'stx:libscm/mercurial' }"
+
+"{ NameSpace: Smalltalk }"
+
+Object subclass:#HGCopyrightUpdater
+	instanceVariableNames:'verbose dryrun removeYearToNow'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'SCM-Mercurial-StX-Tools'
+!
+
+!HGCopyrightUpdater class methodsFor:'documentation'!
+
+copyright
+"
+stx:libscm - a new source code management library for Smalltalk/X
+Copyright (C) 2012-2015 Jan Vrany
+
+This library is free software; you can redistribute it and/or
+modify it under the terms of the GNU Lesser General Public
+License as published by the Free Software Foundation; either
+version 2.1 of the License. 
+
+This library is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
+Lesser General Public License for more details.
+
+You should have received a copy of the GNU Lesser General Public
+License along with this library; if not, write to the Free Software
+Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA  02110-1301  USA
+"
+! !
+
+!HGCopyrightUpdater methodsFor:'initialization'!
+
+initialize
+    "Invoked when a new instance is created."
+
+    "/ please change as required (and remove this comment)
+    "/ repository := nil.
+    "/ patterns := nil.
+    "/ wc := nil.
+    verbose := 0.
+    dryrun := false.
+    removeYearToNow := false.
+
+    "/ super initialize.   -- commented since inherited method does nothing
+
+    "Modified: / 17-05-2018 / 11:42:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+setDryRun: aBoolean
+    
+    dryrun := aBoolean
+
+    "Created: / 14-05-2018 / 19:57:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+setRemoveYearToNow: aBoolean
+    removeYearToNow := aBoolean
+
+    "Created: / 17-05-2018 / 11:41:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+setVerbose: anInteger
+    
+    verbose := anInteger
+
+    "Created: / 03-05-2018 / 22:36:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGCopyrightUpdater methodsFor:'private'!
+
+collectCopyrightsFromContributionsTo:anHGChangesetFile 
+    | contributions  copyrights |
+
+    contributions := self searchForContributions:anHGChangesetFile.
+    contributions isEmpty ifTrue:[
+        ^ #()
+    ].
+    copyrights := OrderedCollection new.
+    contributions do:[:contribution | 
+        contribution years do:[:years | 
+            copyrights add:((HGCopyrightLine new)
+                        years:years;
+                        holder:contribution name)
+        ].
+    ].
+    ^ copyrights
+
+    "Created: / 15-05-2018 / 13:17:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+collectCopyrightsFromText:lines 
+    | current  copyrights  lineNr |
+
+    copyrights := OrderedCollection new.
+    current := nil.
+    lineNr := 1.
+    [ lineNr <= lines size ] whileTrue:[
+        | line  copyright |
+
+        line := lines at:lineNr.
+        copyright := HGCopyrightLine readFrom:line onError:[ nil ].
+        copyright notNil ifTrue:[
+            copyright line:lineNr.
+            current isNil ifTrue:[
+                current := OrderedCollection with:copyright.
+            ] ifFalse:[
+                current add:copyright
+            ].
+        ] ifFalse:[
+            current notNil ifTrue:[
+                copyrights add:current.
+                current := nil.
+            ].
+        ].
+        lineNr := lineNr + 1.
+    ].
+    current notNil ifTrue:[
+        copyrights add:current.
+        current := nil.
+    ].
+    ^ copyrights
+
+    "Created: / 17-04-2018 / 13:50:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 16-05-2018 / 13:49:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+collectMissing1: computed in: present
+    "
+    Return a list of copyright lines missing in `present`. 
+    Both `present` and `computed` lines MUST have the same holder.
+
+    WARNING: do not use this method, this is a helper for
+    #collectMissing:in:
+    "
+
+    | missing |
+
+    missing := Set new.
+    computed do:[:c |
+        (present noneSatisfy:[:p|(c years start in: p years) and:[c years stop in: p years]]) ifTrue:[ 
+            missing add: c.
+        ].
+    ].
+    ^ missing.
+
+    "Created: / 16-05-2018 / 09:33:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 16-05-2018 / 13:57:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+collectMissing: computed in: present
+    "
+    Return a list of copyright lines missing in `present`
+    "
+
+    | presentHolders buckets missing |
+
+    "/ First, sort copyright lines into 'buckets' by copyright holder.
+    buckets := Dictionary new.
+    presentHolders := Set new.
+    present do:[:each | 
+        (buckets at: each holder ifAbsentPut: [Array with: Set new with: Set new]) second add: each.
+        presentHolders add: each holder.
+    ].
+    computed do:[:each | 
+        | holder |
+
+        holder := presentHolders detect:[:holder | holder includesString: each holder caseSensitive: false ] ifNone:[ each holder ].
+        (buckets at: each holder ifAbsentPut: [Array with: Set new with: Set new]) first add: each.
+    ].
+    missing := SortedCollection new.
+    buckets do:[:bucket | 
+        missing addAll: (self collectMissing1: bucket first in: bucket second).
+    ].
+    ^ missing.
+
+    "Created: / 15-05-2018 / 13:34:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 16-05-2018 / 09:31:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+searchForContributions: anHGChangesetFile
+    "
+    Return a list of contributions (as HGContribution) for given changeset file.
+    "
+    | contributions |
+    contributions := HGContribution summaryFromFile:anHGChangesetFile.
+    (contributions notEmpty and:[verbose > 1]) ifTrue:[ 
+        Transcript showCR:'Contributions:'.  
+        contributions do:[:contribution |  
+            Transcript space; show: contribution author; show: ': '; cr.
+            contribution changesets do:[:changeset | 
+                Transcript show: '  * '; show: changeset id printString; show:' ('; show: changeset timestamp printString; show: ')'.
+                verbose > 3 ifTrue:[ 
+                    Transcript cr; nextPutAll: changeset message; cr.
+                ] ifFalse:[ 
+                    Transcript space; showCR: changeset summary
+                ].
+            ].
+        ]
+    ].    
+    ^ contributions
+
+    "Created: / 15-05-2018 / 13:08:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+updateCopyrights: computed present: present in: lines
+    | changed missingInsertPosition missing |
+
+    self assert: present notEmpty.
+    self assert: present last line notNil.
+
+    missingInsertPosition := present last line .
+    changed := false.
+
+    verbose > 0 ifTrue:[ 
+        Transcript showCR: 'Copyrights:'.
+        present do:[:copyright | Transcript show: ((removeYearToNow and:[copyright isYearToNow]) ifTrue:[ '- ' ] ifFalse:[ '  ']); showCR: copyright asString ]
+    ].
+
+    "/ Reject (invalid) copyright lines in form YYYY-now (such as 2016-now)
+    present copy reverseDo:[ :copyright |
+        (removeYearToNow and:[ copyright isYearToNow ]) ifTrue:[ 
+            present remove: copyright.
+            lines removeIndex: copyright line.
+            missingInsertPosition := missingInsertPosition - 1.
+            changed := true.
+        ].
+    ].
+
+    "/ Add all missing copyrights
+    missing := self collectMissing: computed in: present. 
+    missing isEmpty ifTrue:[ ^ changed ].
+    verbose > 0 ifTrue:[ 
+        missing do:[:copyright | Transcript show: '+ '; showCR: copyright asString ].
+    ].
+    missing withIndexDo:[ :copyright :index |
+        lines add: copyright asString beforeIndex: missingInsertPosition + index.
+        changed := true.
+    ].
+    ^ changed
+
+    "Created: / 23-04-2018 / 15:55:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 17-05-2018 / 11:42:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGCopyrightUpdater methodsFor:'utilities'!
+
+updateFile:file
+    "
+    For given file (as `HGWorkingCopyFile`) add missing copyright lines
+    based on commits and saves update contents back to file (unless dry-run
+    is specified, see #setDryRun:)
+    "
+
+    | wc computed lines presentRuns changed |
+
+    verbose > 0 ifTrue:[ 
+       Transcript show:'File '; showCR: file baseName.  
+    ].
+
+    wc := file repository workingCopy.
+
+    self assert:(wc parent1Id = file changesetId).
+    self assert:(wc / file pathName) exists.
+
+    "/ Collect copyright lines from file contents....
+    lines := (wc / file pathName) contents.
+    presentRuns := self collectCopyrightsFromText:lines.
+
+    "/ Compute copyright lines from contributions (i.e., based on commit authors)
+    computed := self collectCopyrightsFromContributionsTo: file.  
+    computed isEmpty ifTrue:[ ^ self ].
+
+    "/ At this point, we know that there has been a contribution.
+    "/ If there are existing no copytight notices in the file
+    "/ (i.e, `presentRuns` is empty), raise a warning.
+    presentRuns isEmpty ifTrue:[ 
+        Warning raiseErrorString: ('File %1 has contributions but not copyright notice!!' bindWith: file pathName).
+        ^ self 
+    ].
+
+    computed do:[:each | each prefix: presentRuns first last prefix ].
+
+    changed := false.
+    presentRuns reverseDo:[:copyright |
+        changed := (self updateCopyrights: computed present: copyright in: lines) or:[ changed ].
+    ].
+    (changed and:[dryrun not]) ifTrue:[ 
+        (wc / file pathName) contents: lines.
+    ].
+    verbose > 0 ifTrue:[ 
+       Transcript showCR:'--'; cr.
+    ]. 
+    "
+    HGCopyrightUpdateTool main:#('--cwd' 'goodies/regression'   '-v' '-v' '-v' '--dry-run')
+
+    HGCopyrightUpdateTool main:#('--cwd' 'librun'   '-v' '-v' '-v' '--dry-run' 'send.c')
+    HGCopyrightUpdateTool main:#('--cwd' 'librun'   '-v' '-v' '-v' '--dry-run' 'hmm.c')
+
+    HGCopyrightUpdateTool main:#('--cwd' '../..'   '-v' '-v' '-v' '--dry-run' 'LICENSE.txt')
+
+    HGCopyrightUpdateTool main:#('--cwd' 'goodies/smallsense'   '-v' '-v' '-v' '--dry-run' 'SmallSense__SmalltalkQuickFixer.st')
+    HGCopyrightUpdateTool main:#('--cwd' 'goodies/smallsense'   '-v' '-v' '-v' '--dry-run' 'SmallSense__SmalltalkEditSupportTests.st')
+
+    HGCopyrightUpdateTool main:#('--cwd' 'libbasic' '-v' '-v' '-v' '--dry-run')
+    HGCopyrightUpdateTool main:#('--cwd' 'libbasic' '-v' '-v' '-v' '--dry-run' 'SmalltalkChunkFileSourceReader.st')
+    HGCopyrightUpdateTool main:#('--cwd' 'libbasic' '-v' '-v' '-v' '--dry-run' 'UnorderedNumbersError.st')
+    HGCopyrightUpdateTool main:#('--cwd' 'libbasic' '-v' '-v' '-v' '--dry-run' 'Method.st')
+    HGCopyrightUpdateTool main:#('--cwd' 'libbasic' '-v' '-v' '-v' '--dry-run' 'Array.st')
+    HGCopyrightUpdateTool main:#('--cwd' 'libbasic' '-v' '-v' '-v' '--dry-run' 'WeakArray.st')
+    HGCopyrightUpdateTool main:#('--cwd' 'libbasic' '-v' '-v' '-v' '--dry-run' 'UnixOperatingSystem.st')
+    "
+
+    "Created: / 16-05-2018 / 23:01:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 10-06-2018 / 21:02:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!HGCopyrightUpdater class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/mercurial/HGStXTests.st	Thu Mar 29 22:22:31 2018 +0100
+++ b/mercurial/HGStXTests.st	Tue Apr 17 14:58:16 2018 +0100
@@ -4117,6 +4117,66 @@
     "Created: / 20-01-2015 / 19:54:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!HGStXTests methodsFor:'tests - copyright updater'!
+
+test_copyright_line_01
+    | line |
+
+    line := HGCopyrightLine readFrom: ' COPYRIGHT (c) 1994 by Claus Gittinger'.
+    self 
+        assert: line prefix = ' COPYRIGHT (c)';
+        assert: line years = (1994 to: 1994);
+        assert: line holder = 'by Claus Gittinger';
+        assert: line asString = ' COPYRIGHT (c) 1994 by Claus Gittinger'.
+
+
+    line := HGCopyrightLine readFrom: '              All Rights Reserved' onError: [ 1 ].
+    self 
+        assert: line == 1.
+
+    line := HGCopyrightLine readFrom: ' COPYRIGHT (c) 1994-1998 by Claus Gittinger'.
+    self 
+        assert: line prefix = ' COPYRIGHT (c)';
+        assert: line years = (1994 to: 1998);
+        assert: line holder = 'by Claus Gittinger';
+        assert: line asString = ' COPYRIGHT (c) 1994-1998 by Claus Gittinger'.
+
+    line := HGCopyrightLine readFrom: ' COPYRIGHT (c) 2005-now Jan Vrany'.
+    self 
+        assert: line prefix = ' COPYRIGHT (c)';
+        assert: line years = (2005 to: 'now');
+        assert: line holder = 'Jan Vrany';
+        assert: line asString = ' COPYRIGHT (c) 2005-now Jan Vrany'.
+
+    line := HGCopyrightLine readFrom: ' COPYRIGHT (c) Claus Gittinger / eXept Software AG'.
+    self 
+        assert: line prefix = ' COPYRIGHT (c)';
+        assert: line years isNil;
+        assert: line holder = 'Claus Gittinger / eXept Software AG';
+        assert: line asString = ' COPYRIGHT (c) Claus Gittinger / eXept Software AG'.
+
+    "Created: / 14-05-2018 / 16:18:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 12-06-2018 / 08:38:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+test_copyright_line_02
+    | lines |
+
+    lines := #( ' COPYRIGHT (c) 1994-1997 BB'        
+                ' COPYRIGHT (c) 1995-1997 DD'
+                ' COPYRIGHT (c) 1995-1997 CC'
+                ' COPYRIGHT (c) 1994 AA'
+                ) collect:[:l | HGCopyrightLine readFrom: l ].
+    lines sort.
+    self assert: lines first holder = 'AA'.
+    self assert: lines second holder = 'BB'.
+    self assert: lines third holder = 'CC'.
+    self assert: lines fourth holder = 'DD'.
+
+    "Created: / 14-05-2018 / 16:54:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 12-06-2018 / 08:38:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !HGStXTests methodsFor:'tests - manager API'!
 
 test_log_01
--- a/mercurial/HGTagOrBookmark.st	Thu Mar 29 22:22:31 2018 +0100
+++ b/mercurial/HGTagOrBookmark.st	Tue Apr 17 14:58:16 2018 +0100
@@ -18,6 +18,8 @@
 "
 "{ Package: 'stx:libscm/mercurial' }"
 
+"{ NameSpace: Smalltalk }"
+
 HGChangesetLabel subclass:#HGTagOrBookmark
 	instanceVariableNames:'changeset'
 	classVariableNames:''
@@ -86,3 +88,10 @@
     "Created: / 20-03-2014 / 01:47:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+!HGTagOrBookmark class methodsFor:'documentation'!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+! !
+
--- a/mercurial/HGWorkingCopyFile.st	Thu Mar 29 22:22:31 2018 +0100
+++ b/mercurial/HGWorkingCopyFile.st	Tue Apr 17 14:58:16 2018 +0100
@@ -180,6 +180,16 @@
     "Modified: / 08-02-2014 / 22:02:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+sha1
+    "Returns a SHA1 sum of file's contents"
+    | sha1 |
+
+    filename readingFileDo:[:s | sha1 := SHA1Stream hashValueOf:s].
+    ^ sha1
+
+    "Created: / 24-04-2018 / 15:38:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 status
     | statuses  |
 
--- a/mercurial/Make.proto	Thu Mar 29 22:22:31 2018 +0100
+++ b/mercurial/Make.proto	Tue Apr 17 14:58:16 2018 +0100
@@ -34,7 +34,7 @@
 # add the path(es) here:,
 # ********** OPTIONAL: MODIFY the next lines ***
 # LOCALINCLUDES=-Ifoo -Ibar
-LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/goodies/sunit -I$(INCLUDE_TOP)/stx/libbasic -I$(INCLUDE_TOP)/stx/libbasic2 -I$(INCLUDE_TOP)/stx/libbasic3 -I$(INCLUDE_TOP)/stx/libhtml -I$(INCLUDE_TOP)/stx/libjava -I$(INCLUDE_TOP)/stx/libjava/tools -I$(INCLUDE_TOP)/stx/libscm/common -I$(INCLUDE_TOP)/stx/libtool -I$(INCLUDE_TOP)/stx/libtool2 -I$(INCLUDE_TOP)/stx/libview -I$(INCLUDE_TOP)/stx/libview2 -I$(INCLUDE_TOP)/stx/libwidg -I$(INCLUDE_TOP)/stx/libwidg2
+LOCALINCLUDES= -I$(INCLUDE_TOP)/stx/libbasic -I$(INCLUDE_TOP)/stx/libbasic2 -I$(INCLUDE_TOP)/stx/libbasic3 -I$(INCLUDE_TOP)/stx/libhtml -I$(INCLUDE_TOP)/stx/libscm/common -I$(INCLUDE_TOP)/stx/libtool -I$(INCLUDE_TOP)/stx/libtool2 -I$(INCLUDE_TOP)/stx/libview -I$(INCLUDE_TOP)/stx/libview2 -I$(INCLUDE_TOP)/stx/libwidg -I$(INCLUDE_TOP)/stx/libwidg2
 
 
 # if you need any additional defines for embedded C code,
@@ -178,6 +178,9 @@
 $(OUTDIR)HGCommandParser.$(O) HGCommandParser.$(C) HGCommandParser.$(H): HGCommandParser.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)HGCommitDialog.$(O) HGCommitDialog.$(C) HGCommitDialog.$(H): HGCommitDialog.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libscm/common/SCMAbstractCommitDialog.$(H) $(INCLUDE_TOP)/stx/libscm/common/SCMAbstractDialog.$(H) $(INCLUDE_TOP)/stx/libview2/ApplicationModel.$(H) $(INCLUDE_TOP)/stx/libview2/Model.$(H) $(INCLUDE_TOP)/stx/libview2/SimpleDialog.$(H) $(STCHDR)
 $(OUTDIR)HGCommitTask.$(O) HGCommitTask.$(C) HGCommitTask.$(H): HGCommitTask.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libscm/common/SCMAbstractCommitTask.$(H) $(INCLUDE_TOP)/stx/libscm/common/SCMAbstractFileoutLikeTask.$(H) $(INCLUDE_TOP)/stx/libscm/common/SCMAbstractTask.$(H) $(STCHDR)
+$(OUTDIR)HGContribution.$(O) HGContribution.$(C) HGContribution.$(H): HGContribution.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)HGCopyrightLine.$(O) HGCopyrightLine.$(C) HGCopyrightLine.$(H): HGCopyrightLine.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)HGCopyrightUpdater.$(O) HGCopyrightUpdater.$(C) HGCopyrightUpdater.$(H): HGCopyrightUpdater.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)HGDebugFlags.$(O) HGDebugFlags.$(C) HGDebugFlags.$(H): HGDebugFlags.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SharedPool.$(H) $(STCHDR)
 $(OUTDIR)HGError.$(O) HGError.$(C) HGError.$(H): HGError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)HGIconLibrary.$(O) HGIconLibrary.$(C) HGIconLibrary.$(H): HGIconLibrary.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/mercurial/Make.spec	Thu Mar 29 22:22:31 2018 +0100
+++ b/mercurial/Make.spec	Tue Apr 17 14:58:16 2018 +0100
@@ -66,6 +66,9 @@
 	HGCommandParser \
 	HGCommitDialog \
 	HGCommitTask \
+	HGContribution \
+	HGCopyrightLine \
+	HGCopyrightUpdater \
 	HGDebugFlags \
 	HGError \
 	HGIconLibrary \
@@ -132,6 +135,9 @@
     $(OUTDIR)HGCommandParser.$(O) \
     $(OUTDIR)HGCommitDialog.$(O) \
     $(OUTDIR)HGCommitTask.$(O) \
+    $(OUTDIR)HGContribution.$(O) \
+    $(OUTDIR)HGCopyrightLine.$(O) \
+    $(OUTDIR)HGCopyrightUpdater.$(O) \
     $(OUTDIR)HGDebugFlags.$(O) \
     $(OUTDIR)HGError.$(O) \
     $(OUTDIR)HGIconLibrary.$(O) \
--- a/mercurial/abbrev.stc	Thu Mar 29 22:22:31 2018 +0100
+++ b/mercurial/abbrev.stc	Tue Apr 17 14:58:16 2018 +0100
@@ -16,6 +16,9 @@
 HGCommandParser HGCommandParser stx:libscm/mercurial 'SCM-Mercurial-Internal' 0
 HGCommitDialog HGCommitDialog stx:libscm/mercurial 'SCM-Mercurial-StX-Interface' 2
 HGCommitTask HGCommitTask stx:libscm/mercurial 'SCM-Mercurial-StX-Tasks' 0
+HGContribution HGContribution stx:libscm/mercurial 'SCM-Mercurial-StX-Tools' 0
+HGCopyrightUpdater HGCopyrightUpdater stx:libscm/mercurial 'SCM-Mercurial-StX-Tools' 0
+HGCopyrightLine HGCopyrightLine stx:libscm/mercurial 'SCM-Mercurial-StX-Tools' 0
 HGDebugFlags HGDebugFlags stx:libscm/mercurial 'SCM-Mercurial-Internal' 0
 HGError HGError stx:libscm/mercurial 'SCM-Mercurial-Core' 1
 HGIconLibrary HGIconLibrary stx:libscm/mercurial 'SCM-Mercurial-StX-Interface' 0
@@ -68,3 +71,4 @@
 HGTests HGTests stx:libscm/mercurial 'SCM-Mercurial-Tests' 1
 HGCommandParserTests HGCommandParserTests stx:libscm/mercurial 'SCM-Mercurial-Tests' 1
 HGInstaller HGInstaller stx:libscm/mercurial 'SCM-Mercurial-StX-Installer' 1
+HGCopyrightUpdateTool HGCopyrightUpdateTool stx:libscm/mercurial 'SCM-Mercurial-StX-Tools' 1
--- a/mercurial/bc.mak	Thu Mar 29 22:22:31 2018 +0100
+++ b/mercurial/bc.mak	Tue Apr 17 14:58:16 2018 +0100
@@ -40,7 +40,7 @@
 
 
 
-LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\goodies\sunit -I$(INCLUDE_TOP)\stx\libbasic -I$(INCLUDE_TOP)\stx\libbasic2 -I$(INCLUDE_TOP)\stx\libbasic3 -I$(INCLUDE_TOP)\stx\libhtml -I$(INCLUDE_TOP)\stx\libjava -I$(INCLUDE_TOP)\stx\libjava\tools -I$(INCLUDE_TOP)\stx\libscm\common -I$(INCLUDE_TOP)\stx\libtool -I$(INCLUDE_TOP)\stx\libtool2 -I$(INCLUDE_TOP)\stx\libview -I$(INCLUDE_TOP)\stx\libview2 -I$(INCLUDE_TOP)\stx\libwidg -I$(INCLUDE_TOP)\stx\libwidg2
+LOCALINCLUDES= -I$(INCLUDE_TOP)\stx\libbasic -I$(INCLUDE_TOP)\stx\libbasic2 -I$(INCLUDE_TOP)\stx\libbasic3 -I$(INCLUDE_TOP)\stx\libhtml -I$(INCLUDE_TOP)\stx\libscm\common -I$(INCLUDE_TOP)\stx\libtool -I$(INCLUDE_TOP)\stx\libtool2 -I$(INCLUDE_TOP)\stx\libview -I$(INCLUDE_TOP)\stx\libview2 -I$(INCLUDE_TOP)\stx\libwidg -I$(INCLUDE_TOP)\stx\libwidg2
 LOCALDEFINES=
 
 STCLOCALOPT=-package=$(PACKAGE) -I. $(LOCALINCLUDES) -headerDir=. $(STCLOCALOPTIMIZATIONS) $(STCWARNINGS) $(LOCALDEFINES)  -varPrefix=$(LIBNAME)
@@ -110,6 +110,9 @@
 $(OUTDIR)HGCommandParser.$(O) HGCommandParser.$(C) HGCommandParser.$(H): HGCommandParser.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)HGCommitDialog.$(O) HGCommitDialog.$(C) HGCommitDialog.$(H): HGCommitDialog.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libscm\common\SCMAbstractCommitDialog.$(H) $(INCLUDE_TOP)\stx\libscm\common\SCMAbstractDialog.$(H) $(INCLUDE_TOP)\stx\libview2\ApplicationModel.$(H) $(INCLUDE_TOP)\stx\libview2\Model.$(H) $(INCLUDE_TOP)\stx\libview2\SimpleDialog.$(H) $(STCHDR)
 $(OUTDIR)HGCommitTask.$(O) HGCommitTask.$(C) HGCommitTask.$(H): HGCommitTask.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libscm\common\SCMAbstractCommitTask.$(H) $(INCLUDE_TOP)\stx\libscm\common\SCMAbstractFileoutLikeTask.$(H) $(INCLUDE_TOP)\stx\libscm\common\SCMAbstractTask.$(H) $(STCHDR)
+$(OUTDIR)HGContribution.$(O) HGContribution.$(C) HGContribution.$(H): HGContribution.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)HGCopyrightLine.$(O) HGCopyrightLine.$(C) HGCopyrightLine.$(H): HGCopyrightLine.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)HGCopyrightUpdater.$(O) HGCopyrightUpdater.$(C) HGCopyrightUpdater.$(H): HGCopyrightUpdater.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)HGDebugFlags.$(O) HGDebugFlags.$(C) HGDebugFlags.$(H): HGDebugFlags.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SharedPool.$(H) $(STCHDR)
 $(OUTDIR)HGError.$(O) HGError.$(C) HGError.$(H): HGError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)HGIconLibrary.$(O) HGIconLibrary.$(C) HGIconLibrary.$(H): HGIconLibrary.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
--- a/mercurial/libInit.cc	Thu Mar 29 22:22:31 2018 +0100
+++ b/mercurial/libInit.cc	Tue Apr 17 14:58:16 2018 +0100
@@ -31,6 +31,9 @@
 extern void _HGCommandParser_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _HGCommitDialog_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _HGCommitTask_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _HGContribution_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _HGCopyrightLine_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _HGCopyrightUpdater_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _HGDebugFlags_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _HGError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _HGIconLibrary_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -106,6 +109,9 @@
     _HGCommandParser_Init(pass,__pRT__,snd);
     _HGCommitDialog_Init(pass,__pRT__,snd);
     _HGCommitTask_Init(pass,__pRT__,snd);
+    _HGContribution_Init(pass,__pRT__,snd);
+    _HGCopyrightLine_Init(pass,__pRT__,snd);
+    _HGCopyrightUpdater_Init(pass,__pRT__,snd);
     _HGDebugFlags_Init(pass,__pRT__,snd);
     _HGError_Init(pass,__pRT__,snd);
     _HGIconLibrary_Init(pass,__pRT__,snd);
--- a/mercurial/stx_libscm_mercurial.st	Thu Mar 29 22:22:31 2018 +0100
+++ b/mercurial/stx_libscm_mercurial.st	Tue Apr 17 14:58:16 2018 +0100
@@ -113,10 +113,7 @@
      Please also take a look at the #mandatoryPreRequisites method"
 
     ^ #(
-        #'stx:goodies/sunit'    "TestAsserter - superclass of HGCommandParserTests"
         #'stx:libhtml'    "HTMLDocumentView - referenced by HGSourceCodeManagementSettingsAppl>>help"
-        #'stx:libjava'    "Java - referenced by HGStXTests>>test_commit_16a"
-        #'stx:libjava/tools'    "JavaCompiler - referenced by HGStXTests>>test_commit_java_01a"
         #'stx:libtool2'    "Tools::ObjectModuleInformation - referenced by HGSourceCodeManager class>>revisionInfoFromString:"
         #'stx:libwidg'    "DialogBox - referenced by AbstractFileBrowser>>hgClone"
         #'stx:libwidg2'    "ProgressIndicator - referenced by AbstractFileBrowser>>hgClone"
@@ -181,77 +178,78 @@
      Each entry in the list may be: a single class-name (symbol),
      or an array-literal consisting of class name and attributes.
      Attributes are: #autoload or #<os> where os is one of win32, unix,..."
-
-    ^ #(
-        "<className> or (<className> attributes...) in load order"
-        HG2CVS
-        HGAuthorQuery
-        HGCachedFileData
-        HGChange
-        HGChangesetBrowser
-        HGChangesetDialog
-        HGChangesetFile
-        HGChangesetId
-        HGChangesetLabelsView
-        HGChangesetList
-        HGChangesetPresenter
-        HGChangesetViewer
-        HGCommandParser
-        HGCommitDialog
-        HGCommitTask
-        HGDebugFlags
-        HGError
-        HGIconLibrary
-        HGMergeInfo
-        HGMergeTool
-        HGNotification
-        HGPackageRevision
-        HGPackageWorkingCopy
-        HGPackageWorkingCopyRegistry
-        HGPushPullInfo
-        HGRepositoryObject
-        HGRevisionAnnotation
-        HGRevisionInfo
-        HGRevset
-        HGRevsetEditor
-        HGSourceCodeManagementSettingsAppl
-        HGSourceCodeManager
-        HGSourceCodeManagerUtilities
-        HGStatus
-        HGWarning
-        HGWorkingCopyFile
-        #'stx_libscm_mercurial'
-        HGBookmarkError
-        HGChangeset
-        HGChangesetLabel
-        HGCommand
-        HGCommandError
-        HGCommandServer
-        HGCommitError
-        HGConfig
-        HGNoSuchBranchError
-        HGRemote
-        HGRepository
-        HGRepositoryError
-        HGWorkingCopy
-        HGBranch
-        HGCommandParseError
-        HGInvalidExecutableError
-        HGInvalidVersionError
-        HGObsoleteRevisionError
-        HGPushError
-        HGTagOrBookmark
-        HGUnknownRevisionError
-        HGBookmark
-        HGPushWouldCreateNewHeadError
-        HGTag
-        (HGRepositoriesResource autoload)
-        (HGTestCase autoload)
-        (HGStXTests autoload)
-        (HGTests autoload)
-        (HGCommandParserTests autoload)
-        (HGInstaller autoload)
-    )
+    
+    ^ "<className> or (<className> attributes...) in load order" #( #HG2CVS
+     #HGAuthorQuery
+     #HGCachedFileData
+     #HGChange
+     #HGChangesetBrowser
+     #HGChangesetDialog
+     #HGChangesetFile
+     #HGChangesetId
+     #HGChangesetLabelsView
+     #HGChangesetList
+     #HGChangesetPresenter
+     #HGChangesetViewer
+     #HGCommandParser
+     #HGCommitDialog
+     #HGCommitTask
+     #HGContribution
+     #HGCopyrightUpdater
+     #HGCopyrightLine
+     #HGDebugFlags
+     #HGError
+     #HGIconLibrary
+     #HGMergeInfo
+     #HGMergeTool
+     #HGNotification
+     #HGPackageRevision
+     #HGPackageWorkingCopy
+     #HGPackageWorkingCopyRegistry
+     #HGPushPullInfo
+     #HGRepositoryObject
+     #HGRevisionAnnotation
+     #HGRevisionInfo
+     #HGRevset
+     #HGRevsetEditor
+     #HGSourceCodeManagementSettingsAppl
+     #HGSourceCodeManager
+     #HGSourceCodeManagerUtilities
+     #HGStatus
+     #HGWarning
+     #HGWorkingCopyFile
+     #'stx_libscm_mercurial'
+     #HGBookmarkError
+     #HGChangeset
+     #HGChangesetLabel
+     #HGCommand
+     #HGCommandError
+     #HGCommandServer
+     #HGCommitError
+     #HGConfig
+     #HGNoSuchBranchError
+     #HGRemote
+     #HGRepository
+     #HGRepositoryError
+     #HGWorkingCopy
+     #HGBranch
+     #HGCommandParseError
+     #HGInvalidExecutableError
+     #HGInvalidVersionError
+     #HGObsoleteRevisionError
+     #HGPushError
+     #HGTagOrBookmark
+     #HGUnknownRevisionError
+     #HGBookmark
+     #HGPushWouldCreateNewHeadError
+     #HGTag
+     #(HGRepositoriesResource autoload)
+     #(HGTestCase autoload)
+     #(HGStXTests autoload)
+     #(HGTests autoload)
+     #(HGCommandParserTests autoload)
+     #(HGInstaller autoload)
+     #(HGCopyrightUpdateTool autoload) )
 !
 
 extensionMethodNames