Merge jv
authorMerge Script
Tue, 16 Aug 2016 06:52:00 +0200
branchjv
changeset 4081 5a9726876c20
parent 4074 533d1c715e83 (current diff)
parent 4080 d36f01795eb2 (diff)
child 4086 aafed7101969
Merge
AbstractSourceCodeManager.st
CVSSourceCodeManager.st
ProjectChecker.st
ProjectProblem.st
SourceCodeManagerUtilities.st
--- a/AbstractSourceCodeManager.st	Wed Aug 10 18:11:27 2016 +0100
+++ b/AbstractSourceCodeManager.st	Tue Aug 16 06:52:00 2016 +0200
@@ -1309,7 +1309,10 @@
 
 directoryFromContainerPath:containerPath forPackage:packageID
     "given a full path as in an RCS header, 
-     extract the directory (i.e. package)."
+     extract the directory (i.e. package) within the module.
+     Notice: 
+        for top-level folder-only modules (like exept, smalltalk), 
+        an empty string is returned."
 
     |path idx|
 
@@ -1319,6 +1322,12 @@
     "/ these are always UNIX filenames ...
     idx := path indexOf:$/.
     idx ~~ 0 ifTrue:[
+        "/ be careful: for top-level module descriptions (folders),
+        "/ the directory is empty
+        (path indexOf:$/ startingAt:idx+1) == 0 ifTrue:[
+            "/ there is no directory
+            ^ ''
+        ].
         path := path copyFrom:(idx + 1)
     ].
 
@@ -1417,7 +1426,7 @@
     containerPath isNil ifTrue:[^ nil].
 
     packageID notNil ifTrue:[
-        idx := containerPath lastIndexOfSubCollection:(packageID copyReplaceAll:$: with:$/).
+        idx := containerPath indexOfSubCollection:((packageID copyReplaceAll:$: with:$/),'/').
         idx ~~ 0 ifTrue:[
             ^ containerPath copyFrom:idx.
         ].
@@ -1563,7 +1572,7 @@
     "helper: return a classes sourceCodeInfo by extracting its
      versionString components."
 
-    |cls packageInfo revInfo actualSourceFileName classFileNameBase
+    |cls clsPackage packageInfo revInfo actualSourceFileName classFileNameBase
      newInfo container expectedFileName
      directoryFromVersion moduleFromVersion fileNameFromVersion 
      directoryFromPackage moduleFromPackage repairedPath|
@@ -1590,9 +1599,16 @@
     "/ however, it only contains partial information (module:directory:libName).
     "/ (but is available even without a source)
     "/
-    cls name = cls package ifTrue:[
-        "/ very special - the top-modules FolderInfo
-        newInfo at:#module put:cls package.
+    clsPackage := cls package.
+    "/ hack: fix on-the-fly if corrupted top-module's package (FolderInfo)
+    (clsPackage endsWith:':') ifTrue:[
+        ('SourceCodeManager [warning]: fixing corrupted package identifier: ',clsPackage) infoPrintCR.
+        clsPackage := clsPackage copyButLast asSymbol.
+        cls setPackage:clsPackage.
+    ].
+    cls name = clsPackage ifTrue:[
+        "/ very special - the top-module's FolderInfo
+        newInfo at:#module put:clsPackage.
         newInfo at:#directory put:''.
     ] ifFalse:[        
         packageInfo := cls packageSourceCodeInfo.
--- a/CVSSourceCodeManager.st	Wed Aug 10 18:11:27 2016 +0100
+++ b/CVSSourceCodeManager.st	Tue Aug 16 06:52:00 2016 +0200
@@ -1658,11 +1658,11 @@
      instead, the code is checked in as given (Dangerous).
      Return true if ok, false if not."
 
-    |tempdir cmd checkoutName logMsg revision logTmp 
-     cmdOut whatHappened idx changeLog changesAsLogged l 
+    |tempdir cmd checkoutName logMsg revision logTmp
+     cmdOut whatHappened idx changeLog changesAsLogged l
      newRevision  msg answer didMerge
-     modulePath time 
-     editor checkInRepaired didAccept emphasizedText repairedText out 
+     modulePath time
+     editor checkInRepaired didAccept emphasizedText repairedText out
      emSep comment|
 
     revision := self newestRevisionInFile:containerFilename directory:packageDir module:moduleDir.
@@ -1674,14 +1674,14 @@
 
     packageDir isEmptyOrNil ifTrue:[
         modulePath := moduleDir
-    ] ifFalse:[        
-        modulePath :=  moduleDir , '/' , packageDir. 
-    ].        
+    ] ifFalse:[
+        modulePath :=  moduleDir , '/' , packageDir.
+    ].
     checkoutName :=  modulePath , '/' , containerFilename.
 
     revision isNil ifTrue:[
         "/ a new file ...
-        ^ self 
+        ^ self
             createContainerForText:someText inModule:moduleDir package:packageDir container:containerFilename
     ].
 
@@ -1713,9 +1713,9 @@
         "/ correct our current time, so that converting it will give us UTC
         time := Timestamp now asUtcTimestamp subtractSeconds:1.
 
-        self createEntryFor:checkoutName 
+        self createEntryFor:checkoutName
              module:moduleDir
-             in:(tempdir construct:modulePath) 
+             in:(tempdir construct:modulePath)
              revision:revision
              date:(self cvsTimeString:time)
              special:''
@@ -1741,8 +1741,8 @@
         self activityNotification:'CVS: Merging ' , containerFilename , ' with repository version...'.
 
         cmd := 'update ', CVSUpdateOptions, ' ', containerFilename, ' >', '"' , cmdOut name , '"'.
-        (self 
-            executeCVSCommand:cmd 
+        (self
+            executeCVSCommand:cmd
             module:moduleDir
             inDirectory:((tempdir construct:moduleDir) constructString:packageDir)
         ) ifFalse:[
@@ -1755,7 +1755,7 @@
             "/ check what happened - the contents of the cmdOut file may be:
             "/   empty   -> nothing changed
             "/   M xxx   -> merged-in changes from other users
-            "/   C xxx   -> a conflict occured and the differences have been merged into the source
+            "/   C xxx   -> a conflict occurred and the differences have been merged into the source
             "/              needs special action
             "/
             (cmdOut exists and:[cmdOut fileSize > 0]) ifTrue:[
@@ -1815,8 +1815,8 @@
             "/
             "/ merged in changes
             "/
-            (force 
-            or:[changeLog isNil 
+            (force
+            or:[changeLog isNil
             or:[(changeLog at:#revisions ifAbsent:[#()]) isEmpty]]) ifTrue:[
                 "/
                 "/ pretty good - nothing has changed in the meanwhile
@@ -1838,14 +1838,14 @@
                 mySource = mergedSource ifTrue:[
                     msg := 'The source of ' , containerFilename , ' has been changed in the meanwhile as listed below.
 
-I have merged your version with the newest repository version, 
+I have merged your version with the newest repository version,
 and found no differences between the result and your current version
 (i.e. your version seemed up-to-date).'.
 
                     self checkinTroubleDialog:'Merging versions'
-                                   message:msg 
+                                   message:msg
                                    log:changesAsLogged
-                                   abortable:false 
+                                   abortable:false
                                    option:nil.
                     didMerge := false.
                 ] ifFalse:[
@@ -1853,19 +1853,19 @@
 
 If you continue, your new changes (based upon rev. ' , revision printString , ') will be MERGED
 into the newest revision. This will combine the other version with your changes
-into a new common revision which may be different from both. 
-Although this is a nice feature, it may fail to create the expected result in certain situations. 
+into a new common revision which may be different from both.
+Although this is a nice feature, it may fail to create the expected result in certain situations.
 
 You should carefully check the result - by comparing the current version with the
 most recent version in the repository. If that does not contain an acceptable version,
-change methods as required and check in again. 
+change methods as required and check in again.
 Be aware, that after that, the actual repository version is different from your current classes,
 and you should update your class from the repository.
 
 Continue ?'.
 
                     answer := self checkinTroubleDialog:'Merging versions'
-                                   message:msg 
+                                   message:msg
                                    log:changesAsLogged
                                    abortable:true
                                    option:'Stop - see first'.
@@ -1876,7 +1876,7 @@
                                 label:'current version'
                                 and:mergedSource
                                 label:'merged version'.
-                                
+
                         ].
                         Transcript showCR:'checkin aborted - (no merge; repository unchanged)'.
                         ^ false.
@@ -1889,8 +1889,8 @@
 "/
 "/If you continue, your new changes (based upon rev. ' , revision , ') will be MERGED
 "/into the newest revision. This will combine the other version with your changes
-"/into a new common revision which is different from both. 
-"/Although convenient, it may fail to create the expected result in certain situations. 
+"/into a new common revision which is different from both.
+"/Although convenient, it may fail to create the expected result in certain situations.
 "/
 "/You should carefully check the result - by comparing the current version with the
 "/most recent version in the repository. If that does not contain an acceptable version,
@@ -1922,7 +1922,7 @@
 '.
 
                 answer := self checkinTroubleDialog:'Version conflict'
-                     message:msg 
+                     message:msg
                      log:changesAsLogged
                      abortable:false
                      option:'show conflicts'
@@ -1933,10 +1933,10 @@
                     "/ show conflicts in a 3-way DiffTextView ...
                     "/
                     Diff3TextView
-                        openOnMergedText:(tempdir construct:checkoutName) readStream contents 
-                        label:'your version (checkin attempt)' 
-                        label:'original (base version)' 
-                        label:'newest repository version'. 
+                        openOnMergedText:(tempdir construct:checkoutName) readStream contents
+                        label:'your version (checkin attempt)'
+                        label:'original (base version)'
+                        label:'newest repository version'.
                 ].
 
                 checkInRepaired := false.
@@ -1952,21 +1952,21 @@
                     emphasizedText := (tempdir construct:checkoutName) readStream contents.
                     emSep := (Array with:(#color->Color black)
                                  with:(#backgroundColor->Color green)).
-                    emphasizedText := Diff3TextView 
-                                emphasizeMergedDiff3Text:emphasizedText 
+                    emphasizedText := Diff3TextView
+                                emphasizeMergedDiff3Text:emphasizedText
                                 emphasize1:(Array with:(#color->Color white)
                                                   with:(#backgroundColor->Color blue))
                                 emphasize2:(Array with:(#color->Color white)
                                                   with:(#backgroundColor->Color red))
                                 emphasizeSep:emSep.
 
-                    comment := 
+                    comment :=
 '"/ ***************************************************************
 "/ This text contains your current versions code (blue)
 "/ merged with the conflicting code as found in the repository (red) which resulted
 "/ from some other checkin.
 "/ Each such conflict is surrounded by green text (like this paragraph).
-"/ 
+"/
 "/ Please have a look at ALL the conflicts and fix things as appropriate.
 "/ Delete the green lines as a confirmation - I will not checkin the changed text,
 "/ unless no more green parts are present. This includes this comment at the top.
@@ -1977,9 +1977,9 @@
 
                     didAccept := false. checkInRepaired := true.
                     [didAccept not and:[checkInRepaired]] whileTrue:[
-                        editor := RCSConflictEditTextView 
+                        editor := RCSConflictEditTextView
                                     setupWith:emphasizedText
-                                    title:'Resolve conflicts in ' , containerFilename , ', then accept & close to checkin'.    
+                                    title:'Resolve conflicts in ' , containerFilename , ', then accept & close to checkin'.
 
                         editor acceptAction:[:dummy |
                             repairedText := editor list.
@@ -2081,8 +2081,8 @@
                     with:cmdOut name
         ].
 
-        (self 
-            executeCVSCommand:cmd 
+        (self
+            executeCVSCommand:cmd
             module:moduleDir
             inDirectory:tempdir name
         ) ifFalse:[
@@ -2141,11 +2141,11 @@
      instead, the code is checked in as given (Dangerous).
      Return true if ok, false if not."
 
-    |tempdir cmd checkoutName logMsg revision newestRevision logTmp 
-     cmdOut whatHappened s entry idx changeLog changesAsLogged l 
+    |tempdir cmd checkoutName logMsg revision newestRevision logTmp
+     cmdOut whatHappened s entry idx changeLog changesAsLogged l
      newRevision newString binRevision className msg answer didMerge
-     modulePath time 
-     editor checkInRepaired checkInNew didAccept emphasizedText repairedText out 
+     modulePath time
+     editor checkInRepaired checkInNew didAccept emphasizedText repairedText out
      emSep comment force conflictResolvedManually revisionOption|
 
     force := forceArg.
@@ -2155,8 +2155,8 @@
         self reportError:'refuse to check in private classes.'.
         ^ false.
     ].
-    revision := "cls revision" cls revisionOfManager:self.        
-    (revision notNil and:[revision endsWith:$m]) 
+    revision := "cls revision" cls revisionOfManager:self.
+    (revision notNil and:[revision endsWith:$m])
     ifTrue:[
         "/ this class has already been checked in with a merge,
         "/ but not reloaded from the repository.
@@ -2194,7 +2194,7 @@
         logMsg isWideString ifTrue:[
             self reportError:'cvs cannot handle unicode in logMessage'.
             ^ false.
-        ].    
+        ].
     ].
 
     cmdOut := Filename newTemporary.
@@ -2223,8 +2223,8 @@
         packageDir isEmptyOrNil ifTrue:[
             modulePath := moduleDir
         ] ifFalse:[
-            modulePath :=  moduleDir , '/' , packageDir. 
-        ].        
+            modulePath :=  moduleDir , '/' , packageDir.
+        ].
         checkoutName :=  modulePath , '/' , classFileName.
 
         "/
@@ -2232,9 +2232,9 @@
         "/
         time := Timestamp now asUtcTimestamp subtractSeconds:1.
 
-        self createEntryFor:checkoutName 
+        self createEntryFor:checkoutName
              module:moduleDir
-             in:(tempdir construct:modulePath) 
+             in:(tempdir construct:modulePath)
              revision:revision
              date:(self cvsTimeString:time)
              special:''
@@ -2267,8 +2267,8 @@
             with:cmdOut name
             with:revisionOption.
 
-        (self 
-            executeCVSCommand:cmd 
+        (self
+            executeCVSCommand:cmd
             module:moduleDir
             inDirectory:((tempdir construct:moduleDir) constructString:packageDir)
         ) ifFalse:[
@@ -2296,8 +2296,8 @@
                         (Dialog confirm:('The source container for ',cls name allBold,' seems corrupted. Proceed?' withCRs)) ifFalse:[
                             ^ false
                         ].
-                        ^ self 
-                            checkinClass:cls fileName:classFileName directory:packageDir module:moduleDir 
+                        ^ self
+                            checkinClass:cls fileName:classFileName directory:packageDir module:moduleDir
                             source:sourceFileName logMessage:logMessage force:true.
                     ].
                 ].
@@ -2320,7 +2320,7 @@
             "/ check what happened - the contents of the cmdOut file may be:
             "/   empty   -> nothing changed
             "/   M xxx   -> merged-in changes from other users
-            "/   C xxx   -> a conflict occured and the differences have been merged into the source
+            "/   C xxx   -> a conflict occurred and the differences have been merged into the source
             "/              needs special action
             "/
             (cmdOut exists and:[cmdOut fileSize > 0]) ifTrue:[
@@ -2408,8 +2408,8 @@
             "/
             "/ merged in changes / resurrected
             "/
-            (force 
-            or:[changeLog isNil 
+            (force
+            or:[changeLog isNil
             or:[(changeLog at:#revisions ifAbsent:nil) isEmptyOrNil]]) ifTrue:[
                 "/
                 "/ pretty good - nothing has changed in the meanwhile
@@ -2433,14 +2433,14 @@
                 mySource = mergedSource ifTrue:[
                     msg := 'The source of ' , className , ' has been changed in the meanwhile as listed below.
 
-I have merged your version with the newest repository version, 
+I have merged your version with the newest repository version,
 and found no differences between the result and your current version
 (i.e. your version seemed up-to-date).'.
 
                     self checkinTroubleDialog:'Merging versions'
-                                   message:msg 
+                                   message:msg
                                    log:changesAsLogged
-                                   abortable:false 
+                                   abortable:false
                                    option:nil.
                     didMerge := false.
                 ] ifFalse:[
@@ -2448,19 +2448,19 @@
 
 If you continue, your new changes (based upon rev. ' , revision printString , ') will be MERGED
 into the newest revision. This will combine the other version with your changes
-into a new common revision which may be different from both. 
-Although this is a nice feature, it may fail to create the expected result in certain situations. 
+into a new common revision which may be different from both.
+Although this is a nice feature, it may fail to create the expected result in certain situations.
 
 You should carefully check the result - by comparing the current version with the
 most recent version in the repository. If that does not contain an acceptable version,
-change methods as required and check in again. 
+change methods as required and check in again.
 Be aware, that after that, the actual repository version is different from your current classes,
 and you should update your class from the repository.
 
 Continue ?'.
 
                     answer := self checkinTroubleDialog:'Merging versions'
-                                   message:msg 
+                                   message:msg
                                    log:changesAsLogged
                                    abortable:true
                                    option:'Stop - see first'
@@ -2496,8 +2496,8 @@
 "/
 "/If you continue, your new changes (based upon rev. ' , revision , ') will be MERGED
 "/into the newest revision. This will combine the other version with your changes
-"/into a new common revision which is different from both. 
-"/Although convenient, it may fail to create the expected result in certain situations. 
+"/into a new common revision which is different from both.
+"/Although convenient, it may fail to create the expected result in certain situations.
 "/
 "/You should carefully check the result - by comparing the current version with the
 "/most recent version in the repository. If that does not contain an acceptable version,
@@ -2529,7 +2529,7 @@
 '.
 
                 answer := self checkinTroubleDialog:'Version conflict'
-                     message:msg 
+                     message:msg
                      log:changesAsLogged
                      abortable:false
                      option:'Show conflicts'
@@ -2541,10 +2541,10 @@
                     "/ show conflicts in a 3-way DiffTextView ...
                     "/
                     Diff3TextView
-                        openOnMergedText:(tempdir construct:checkoutName) readStream contents 
-                        label:'your version (checkin attempt)' 
-                        label:'original (base version)' 
-                        label:'newest repository version'. 
+                        openOnMergedText:(tempdir construct:checkoutName) readStream contents
+                        label:'your version (checkin attempt)'
+                        label:'original (base version)'
+                        label:'newest repository version'.
                 ].
 
                 answer == #option2 ifTrue:[
@@ -2559,21 +2559,21 @@
                     emphasizedText := (tempdir construct:checkoutName) readStream contents.
                     emSep := (Array with:(#color->Color black)
                                  with:(#backgroundColor->Color green)).
-                    emphasizedText := Diff3TextView 
-                                emphasizeMergedDiff3Text:emphasizedText 
+                    emphasizedText := Diff3TextView
+                                emphasizeMergedDiff3Text:emphasizedText
                                 emphasize1:(Array with:(#color->Color white)
                                                   with:(#backgroundColor->Color blue))
                                 emphasize2:(Array with:(#color->Color white)
                                                   with:(#backgroundColor->Color red))
                                 emphasizeSep:emSep.
 
-                    comment := 
+                    comment :=
 '"/ ***************************************************************
 "/ This text contains your current versions code (blue)
 "/ merged with the conflicting code as found in the repository (red) which resulted
 "/ from some other checkin.
 "/ Each such conflict is surrounded by green text (like this paragraph).
-"/ 
+"/
 "/ Please have a look at ALL the conflicts and fix things as appropriate.
 "/ Delete the green lines as a confirmation - I will not checkin the changed text,
 "/ unless no more green parts are present. This includes this comment at the top.
@@ -2584,9 +2584,9 @@
 
                     didAccept := false. checkInRepaired := true.
                     [didAccept not and:[checkInRepaired]] whileTrue:[
-                        editor := RCSConflictEditTextView 
+                        editor := RCSConflictEditTextView
                                     setupWith:emphasizedText
-                                    title:'Resolve conflicts in ' , className , ', then accept & close to checkin'.    
+                                    title:'Resolve conflicts in ' , className , ', then accept & close to checkin'.
 
                         editor acceptAction:[:dummy |
                             repairedText := editor list.
@@ -2655,7 +2655,7 @@
                     ^ false.
                 ].
             ] ifFalse:[
-                ((whatHappened startsWith:'U ') 
+                ((whatHappened startsWith:'U ')
                 or:[ (whatHappened startsWith:'P ') ]) ifTrue:[
                     "/
                     "/ nothing changed here, but the repository already contains
@@ -2702,8 +2702,8 @@
             "/
             cmd := 'commit -m "', logMsg, '" ', checkoutName, ' >', '"', cmdOut name, '"' , ' 2>&1'.
         ].
-        (self 
-            executeCVSCommand:cmd 
+        (self
+            executeCVSCommand:cmd
             module:moduleDir
             inDirectory:tempdir name
         ) ifFalse:[
@@ -2808,8 +2808,8 @@
                     ]
                 ]
             ]
-        ] ifTrue:[      
-            "/ If the conflict was resolved manually, do NOT update the revision method 
+        ] ifTrue:[
+            "/ If the conflict was resolved manually, do NOT update the revision method
             "/ (to get a new conflict in the next check-in)
 
             "/ If there was a merge, update the revision method adding an 'm'"
@@ -2824,7 +2824,7 @@
     self postCheckInClass:cls.
 
     conflictResolvedManually ifTrue:[
-        (Dialog 
+        (Dialog
             confirm:'Now the repository contains a merge between your and the other changes.
 However, the class in your image does NOT contain the other changes.
 This will lead to more conflict-resolving whenever you check this class in again later,
--- a/ProjectChecker.st	Wed Aug 10 18:11:27 2016 +0100
+++ b/ProjectChecker.st	Tue Aug 16 06:52:00 2016 +0200
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2006 by eXept Software AG
               All Rights Reserved
@@ -618,6 +620,33 @@
     ^true
 
     "Created: / 11-04-2012 / 12:29:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+checkSubProjects
+    "Checks whether all subprojects listed in #subprojects are present."
+
+    |isValidName subProjectsListed invalidNames validNames subProjectsNotPresent|
+
+    isValidName := 
+        [:prj |
+            (prj first isLetter
+            and:[ ((prj occurrencesOf:$:) <= 1)
+            and:[ ((prj copyReplaceAll:$: with:$/) 
+                        conform:[:ch | ch isLetterOrDigit or:['/-_.' includes:ch]]) ]])
+        ].
+
+    subProjectsListed := currentPackageDef subProjects.
+    invalidNames := subProjectsListed select:[:prj | (isValidName value:prj) not].
+    validNames := subProjectsListed select:isValidName.
+
+    subProjectsNotPresent := validNames select:[:prj | prj asPackageId projectDefinitionClass isNil].
+
+    invalidNames do:[:eachBadName |                                
+        self addProblem: (ProjectProblem newInvalidPackageName badName:eachBadName).
+    ].
+    subProjectsNotPresent do:[:eachMissing |                                
+        self addProblem: (ProjectProblem newProjectDefinitionDoesNotExist missing: eachMissing).
+    ].
 ! !
 
 !ProjectChecker methodsFor:'checks-private'!
@@ -715,13 +744,15 @@
 !
 
 checkPackage
-    (currentPackageDef notNil and:[currentPackageDef isFolderForProjectsDefinition]) ifTrue:[^ self].
-
-    (checkExtensionsOnly ? false) ifFalse:[
-        self checkClassListConsistency.
+    currentPackageDef isNil ifTrue:[^ self].
+    currentPackageDef isFolderForProjectsDefinition ifFalse:[
+        (checkExtensionsOnly ? false) ifFalse:[
+            self checkClassListConsistency.
+        ].
+        self checkExtensionsListConsistency.
+        self checkExtensionsPrerequisites.
     ].
-    self checkExtensionsListConsistency.
-    self checkExtensionsPrerequisites.
+    self checkSubProjects.
 
     "add more here..."
 
@@ -763,11 +794,11 @@
 !ProjectChecker class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/ProjectChecker.st,v 1.33 2015-02-24 23:50:29 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic3/ProjectChecker.st,v 1.33 2015-02-24 23:50:29 cg Exp $'
+    ^ '$Header$'
 !
 
 version_HG
@@ -776,6 +807,6 @@
 !
 
 version_SVN
-    ^ '$Id: ProjectChecker.st,v 1.33 2015-02-24 23:50:29 cg Exp $'
+    ^ '$Id$'
 ! !
 
--- a/ProjectProblem.st	Wed Aug 10 18:11:27 2016 +0100
+++ b/ProjectProblem.st	Tue Aug 16 06:52:00 2016 +0200
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2006 by eXept Software AG
               All Rights Reserved
@@ -153,6 +155,13 @@
 	privateIn:ProjectProblem
 !
 
+ProjectProblem subclass:#InvalidPackageName
+	instanceVariableNames:'badName'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:ProjectProblem
+!
+
 ProjectProblem::MethodProblem subclass:#MethodCompilabilityIssue1
 	instanceVariableNames:'errors warnings'
 	classVariableNames:''
@@ -217,7 +226,7 @@
 !
 
 ProjectProblem subclass:#ProjectDefinitionDoesNotExist
-	instanceVariableNames:''
+	instanceVariableNames:'missing'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:ProjectProblem
@@ -368,6 +377,11 @@
     ^ExtensionMethodsClassDoesNotExist new
 !
 
+newInvalidPackageName
+
+    ^InvalidPackageName new
+!
+
 newMethodCompilabilityIssue1
     ^ MethodCompilabilityIssue1 new
 
@@ -1538,11 +1552,11 @@
 
     |mthd text|
 
-    text := 'Extension method %1 » %2 listed but in different package'.
+    text := 'Extension method %1 » %2 listed but in different package'.
 
     (mthd := self method) notNil ifTrue:[
         mthd package = mthd mclass package ifTrue:[
-            text := 'Extension method %1 » %2 listed but in classes package' 
+            text := 'Extension method %1 » %2 listed but in classes package' 
         ]
     ].
     ^ text
@@ -1603,7 +1617,7 @@
 label
     "Return the label (possibly instance if a Text) shortly describing the problem"
 
-    ^'Extension method %1 » %2 not listed in project definition "%3"' bindWith: className allBold with: selector allBold with:self packageDefinitionClass
+    ^'Extension method %1 » %2 not listed in project definition "%3"' bindWith: className allBold with: selector allBold with:self packageDefinitionClass
 
     "Modified: / 23-02-2012 / 14:22:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -1677,7 +1691,7 @@
 label
     "Return the label (possibly instance if a Text) shortly describing the problem"
 
-    ^'Extension method %1 » %2 listed but class not existing' 
+    ^'Extension method %1 » %2 listed but class not existing' 
         bindWith: className allBold 
         with: selector allBold
 
@@ -1754,6 +1768,36 @@
     ^true
 ! !
 
+!ProjectProblem::InvalidPackageName methodsFor:'accessing'!
+
+badName:something
+    badName := something.
+!
+
+severity
+    "Return a severity - one of #error, #warning, #info"
+
+    ^#error
+! !
+
+!ProjectProblem::InvalidPackageName methodsFor:'accessing-description'!
+
+description
+    "Return a (HTML) describing the problem."
+
+    ^
+'The package name "%1" is invalid.
+Names must be of the form "module:subpackage/..." or "module".
+<P>
+You <b>must</b> change this to a valid name, otherwise package management won''t work,
+and the package cannot be compiled to a binary dll.'
+    bindWith: (badName ? package)
+!
+
+label
+    ^'Invalid package name: "%1"' bindWith: (badName ? package)
+! !
+
 !ProjectProblem::MethodCompilabilityIssue1 methodsFor:'accessing'!
 
 severity
@@ -1801,8 +1845,8 @@
     "Return the label (possibly instance if a Text) shortly describing the problem"
 
     ^ (errors notNil 
-        ifTrue:[ 'Uncompilable method %1 » %2' ]
-        ifFalse:[ 'Warnings for method %1 » %2' ]) bindWith: className allBold with: selector allBold
+        ifTrue:[ 'Uncompilable method %1 » %2' ]
+        ifFalse:[ 'Warnings for method %1 » %2' ]) bindWith: className allBold with: selector allBold
 
 
     "Modified: / 11-04-2012 / 16:04:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -2045,8 +2089,8 @@
     "Return the label (possibly instance if a Text) shortly describing the problem"
 
     ^ ((self severity == #error) 
-        ifTrue:[ 'Uncompilable method %1 » %2' ]
-        ifFalse:[ 'Warnings for method %1 » %2' ]) bindWith: className allBold with: selector allBold
+        ifTrue:[ 'Uncompilable method %1 » %2' ]
+        ifFalse:[ 'Warnings for method %1 » %2' ]) bindWith: className allBold with: selector allBold
 
     "Modified: / 29-05-2014 / 15:39:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -2100,7 +2144,7 @@
 label
     "Return the label (possibly instance if a Text) shortly describing the problem"
 
-    ^'Unpackaged method %1 » %2' bindWith: className allBold with: selector allBold
+    ^'Unpackaged method %1 » %2' bindWith: className allBold with: selector allBold
 
     "Modified: / 23-02-2012 / 14:19:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -2230,7 +2274,7 @@
 label
     "Return the label (possibly instance if a Text) shortly describing the problem"
 
-    ^'Method %1 » %2 also present in other pacakge(s)' bindWith: className allBold with: selector allBold
+    ^'Method %1 » %2 also present in other pacakge(s)' bindWith: className allBold with: selector allBold
 ! !
 
 !ProjectProblem::MethodListedInOtherPackage methodsFor:'fixing'!
@@ -2287,7 +2331,7 @@
 label
     "Return the label (possibly instance if a Text) shortly describing the problem"
 
-    ^'Extension method %1 » %2 listed but not existing' bindWith: className allBold with: selector allBold
+    ^'Extension method %1 » %2 listed but not existing' bindWith: className allBold with: selector allBold
 
     "Modified: / 23-02-2012 / 14:22:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -2342,7 +2386,7 @@
 label
     "Return the label (possibly instance if a Text) shortly describing the problem"
 
-    ^ 'Corrupted source code for %1 » %2' bindWith: className allBold with: selector allBold
+    ^ 'Corrupted source code for %1 » %2' bindWith: className allBold with: selector allBold
 
     "Modified: / 11-04-2012 / 12:42:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -2375,13 +2419,17 @@
 label
     "Return the label (possibly instance if a Text) shortly describing the problem"
 
-    ^ 'Unavailable source code for %1 » %2' bindWith: className allBold with: selector allBold
+    ^ 'Unavailable source code for %1 » %2' bindWith: className allBold with: selector allBold
 
     "Modified: / 11-04-2012 / 12:41:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !ProjectProblem::ProjectDefinitionDoesNotExist methodsFor:'accessing'!
 
+missing:arg
+    missing := arg
+!
+
 severity
     "Return a severity - one of #error, #warning, #info"
 
@@ -2395,7 +2443,7 @@
 description
     "Return a (HTML) describing the problem."
 
-    package = 'stx' ifTrue:[
+    (missing ? package) = 'stx' ifTrue:[
         ^
 'Move your code to another package.
 <br>The package name "stx" is reserveed for exept''s ST/X development.'
@@ -2407,13 +2455,13 @@
 such as contents and build parameters.
 You <b>must</b> create it, otherwise package management won''t work,
 and the package cannot be compiled to a binary dll.'
-    bindWith: package
+    bindWith: (missing ? package)
 
     "Modified: / 23-02-2012 / 13:29:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 label
-    ^'Project definition class for "%1" does not exist' bindWith: package
+    ^'Project definition class for "%1" does not exist' bindWith: (missing ? package)
 
     "Modified: / 23-02-2012 / 13:21:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -2421,43 +2469,7 @@
 !ProjectProblem::ProjectDefinitionDoesNotExist methodsFor:'fixing'!
 
 alreadyFixed
-    ^ (ProjectDefinition definitionClassForPackage:package) notNil        
-!
-
-doCreateAs:whatType
-    |prjDef|
-
-    prjDef := ProjectDefinition
-        definitionClassForPackage:package
-        projectType: whatType
-        createIfAbsent:true.
-
-    prjDef
-        updateMethodsCodeUsingCompiler:Compiler 
-        ignoreOldDefinition:true
-!
-
-doCreateAsGUIApplication
-    self doCreateAs:ProjectDefinition guiApplicationType
-!
-
-doCreateAsLibrary
-    self doCreateAs:ProjectDefinition libraryType
-!
-
-doCreateAsNonGUIApplication
-    self doCreateAs:ProjectDefinition nonGuiApplicationType
-!
-
-fixes
-    "return a list of description-actionBlock pairs for possible fixes"
-
-    package = 'stx' ifTrue:[ ^ #() ].
-
-    ^ Array
-        with: (Array with: 'Create as Library'             with: [ self doCreateAsLibrary ]               )
-        with: (Array with: 'Create as GUI Application'     with: [ self doCreateAsGUIApplication ]        )
-        with: (Array with: 'Create as non-GUI Application' with: [ self doCreateAsNonGUIApplication ]     )
+    ^ (ProjectDefinition definitionClassForPackage:(missing ? package)) notNil        
 ! !
 
 !ProjectProblem class methodsFor:'documentation'!
--- a/SourceCodeManagerUtilities.st	Wed Aug 10 18:11:27 2016 +0100
+++ b/SourceCodeManagerUtilities.st	Tue Aug 16 06:52:00 2016 +0200
@@ -3390,10 +3390,23 @@
         (aClass package isNil or:[(aClass revisionOfManager:manager) "revision" isNil]) ifTrue:[ 
             initialLogMessage := 'initial checkin\\' withCRs , initialLogMessage
         ].
-        checkinInfo := self 
-                        getCheckinInfoFor:aClass name 
-                        initialAnswer:initialLogMessage.
+        aClass isProjectDefinition ifTrue:[
+            checkinInfo := self 
+                            getCheckinInfoFor:aClass name 
+                            initialAnswer:initialLogMessage
+                            withQuickOption:false
+                            withValidateConsistencyOption:true
+        ] ifFalse:[
+            checkinInfo := self 
+                            getCheckinInfoFor:aClass name 
+                            initialAnswer:initialLogMessage.
+        ].
         checkinInfo isNil ifTrue:[^ false].
+
+        (aClass isProjectDefinition and:[checkinInfo validateConsistency]) ifTrue:[
+            self validateConsistencyOfPackage:aClass package doClasses:false doExtensions:false.
+        ].
+
         logMessage := checkinInfo logMessage.
 
         reasonLine := '#OTHER'. 
@@ -4387,7 +4400,8 @@
      Return the info-object (actually: the dialog) or nil if aborted."
 
     ^  self 
-        getCheckinInfoFor:aClassNameOrPackageNameString initialAnswer:initialAnswerOrNil withQuickOption:withQuickOption
+        getCheckinInfoFor:aClassNameOrPackageNameString initialAnswer:initialAnswerOrNil 
+        withQuickOption:withQuickOption
         withValidateConsistencyOption:false
 
     "