Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Sun, 09 Oct 2016 22:55:02 +0100
branchjv
changeset 17133 f9f20407fbf9
parent 17132 17d361c666c2 (current diff)
parent 16918 beb0c0bf33c8 (diff)
child 17134 c4cce8b7a95d
Merge
AbstractDirectoryBrowser.st
AbstractFileBrowser.st
AbstractLauncherApplication.st
AbstractSettingsApplication.st
CodeGeneratorTool.st
DirectoryContentsBrowser.st
NewLauncher.st
SmalltalkCodeGeneratorTool.st
SystemBrowser.st
Tools__BrowserList.st
Tools__ChangeSetDiffTool.st
Tools__CodeView2.st
Tools__Inspector2.st
Tools__MethodList.st
Tools__NavigationState.st
Tools__NewClassWizardDialog.st
Tools__NewSystemBrowser.st
resources/de.rs
--- a/AbstractDirectoryBrowser.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/AbstractDirectoryBrowser.st	Sun Oct 09 22:55:02 2016 +0100
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libtool' }"
 
+"{ NameSpace: Smalltalk }"
+
 AbstractFileBrowser subclass:#AbstractDirectoryBrowser
 	instanceVariableNames:'inDropMode canDropItem browser updateToExternFileHolderLock'
 	classVariableNames:''
@@ -198,7 +200,7 @@
 
     "/ cg: used to be unconditionally true hew;
     "/ but then, when a FileDialog (which is not an AbstractFileBrowser) is opened,
-    "/ the commonPostBuild will not properly update its enable chanels;
+    "/ the commonPostBuild will not properly update its enable channels;
     "/ especially the enableDirectoryUp is false.
     "/ This whole FileBrowser is so complicated that it became almost unusable.
     "/ (too much inheritance and knowledge - DirTree and DirContents should each only do
@@ -228,10 +230,10 @@
 !AbstractDirectoryBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/AbstractDirectoryBrowser.st,v 1.27 2014-12-17 15:32:42 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/AbstractDirectoryBrowser.st,v 1.27 2014-12-17 15:32:42 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/AbstractFileBrowser.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/AbstractFileBrowser.st	Sun Oct 09 22:55:02 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2002 by eXept Software AG
               All Rights Reserved
@@ -7941,7 +7939,7 @@
                 ] ifFalse:[
                     msg := 'Same contents.'
                 ].
-                self information:(resources string:msg)
+                self information:msg
             ] ifFalse:[
                 d := DiffTextView 
                         openOn:text1 label:l1
@@ -8375,7 +8373,7 @@
             ] ifFalse:[sig == HaltInterrupt ifTrue:[ |sender|
                 label := msg := 'Breakpoint/Halt in fileIn'.
                 sender := ex suspendedContext.
-                msg := msg , ('\\in %1 » %2' bindWith:(sender receiver class name) with:(sender sender selector))
+                msg := msg , ('\\in %1 » %2' bindWith:(sender receiver class name) with:(sender sender selector))
             ] ifFalse:[
                 label := 'Error in fileIn'.
                 msg := 'error in fileIn: %1'
--- a/AbstractLauncherApplication.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/AbstractLauncherApplication.st	Sun Oct 09 22:55:02 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1997 by eXept Software AG
               All Rights Reserved
@@ -1369,6 +1367,17 @@
         title:'All breakPointed/traced methods'
 !
 
+browseContainingString
+    "open a browser after asking for a string"
+
+    |browserClass|
+
+    browserClass := UserPreferences systemBrowserClass.
+    self withWaitCursorDo:[
+        browserClass new browseMenuMethodsWithString
+    ].
+!
+
 browseImplementors
     "open an implementors- browser after asking for a selector"
 
@@ -7193,6 +7202,7 @@
     |p|
     
     (p := backgroundPackageFindProcess) notNil ifTrue:[
+        backgroundPackageFindProcess := nil.
         p isDead ifFalse:[
             p terminate
         ]
@@ -7610,7 +7620,7 @@
                 repos := eachSelectedItem parent info.                    
                 MCRepositoryBrowser openOnRepository:repos forPackage:eachSelectedItem label.
             ] ifFalse:[
-                package := packageIdByItem at:eachSelectedItem ifAbsent:nil.
+                package := packageIdByItem at:eachSelectedItem ifAbsent:[nil].
                 package notNil ifTrue:[
                     self loadPackageAndUpdate:package browse:doBrowse subPackages:false item:eachSelectedItem
                 ].
--- a/AbstractSettingsApplication.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/AbstractSettingsApplication.st	Sun Oct 09 22:55:02 2016 +0100
@@ -1414,7 +1414,8 @@
 !
 
 basicSaveSettings
-    UserPreferences current autoloadedPackages:(packageChooser listOfSelectedItems value asArray).
+    UserPreferences current 
+        autoloadedPackages:(packageChooser listOfSelectedItems value asArray collect:[:each | each asStirng string]).
 ! !
 
 !AbstractSettingsApplication::AutoloadedPackagesSettingsAppl methodsFor:'aspects'!
--- a/CodeGeneratorTool.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/CodeGeneratorTool.st	Sun Oct 09 22:55:02 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2002 by eXept Software AG
               All Rights Reserved
@@ -1166,6 +1164,7 @@
     "raise an error: must be redefined in concrete subclass(es)"
 
     ^ self subclassResponsibility
+
 !
 
 createStandardPrintOnMethodIn:aClass
--- a/DirectoryContentsBrowser.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/DirectoryContentsBrowser.st	Sun Oct 09 22:55:02 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2002 by eXept Software AG
               All Rights Reserved
@@ -1538,9 +1536,12 @@
     ].             
     changedObject == self selectionInFileList ifTrue:[
         (changedObject value ? #()) do:[:eachSelectedItem |
+            |fn|
+            
             (eachSelectedItem modificationTime notNil
-              and:[ eachSelectedItem fileName notNil
-              and:[ eachSelectedItem fileName modificationTime > eachSelectedItem modificationTime ]]
+              and:[ (fn := eachSelectedItem fileName) notNil
+              and:[ fn exists
+              and:[ fn modificationTime > eachSelectedItem modificationTime ]]]
             ) ifTrue:[
                 "/ the file was modified in the meantime.
                 "/ flush its info.
--- a/NewLauncher.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/NewLauncher.st	Sun Oct 09 22:55:02 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1997-1998 by eXept Software AG
 	      All Rights Reserved
@@ -4449,6 +4451,10 @@
                         label: 'References to Class...'
                         itemValue: [self browseReferencesToClass];
                         activeHelpKey: #browseReferencesToClass).
+    menu addItem: (MenuItem new
+                        label: 'Search String...'
+                        itemValue: [self browseContainingString];
+                        activeHelpKey: #browseContainingString).
     classHistory notEmptyOrNil ifTrue:[
         menu addSeparator.
         menu addItem: (MenuItem new
--- a/SmalltalkCodeGeneratorTool.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/SmalltalkCodeGeneratorTool.st	Sun Oct 09 22:55:02 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2002 by eXept Software AG
               All Rights Reserved
@@ -2613,7 +2611,7 @@
      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 menuFunction."
+     You can paste a fresh worldwide unique id via the editor''s ''more''-''misc''-''paste UUID'' menu function."
 
     ^ UUID fromString:''', UUID genUUID printString, '''
 '.
@@ -2664,10 +2662,14 @@
 codeFor_standAloneUsage
     ^
 'usage
+    "output some command-line usage infos on stderr"
+    
     Stderr nextPutLine:''usage: '',self applicationName,'' [options...]''.
-    Stderr nextPutLine:''  -h .................. output this message''.
-
-    Smalltalk isStandAloneApp ifTrue:[ Smalltalk exitIfStandalone:1 ].
+    Stderr nextPutLine:''  --noInfoPrint ........ disable diagnostic messages''.
+    Stderr nextPutLine:''  -h ................... output this message''.
+    Stderr nextPutLine:''  -a <file> ............ a-argument(s)''.
+    Stderr nextPutLine:''  -b <file> ............ b-argument(s)''.
+    Stderr nextPutLine:''  -c ................... c-option''.
 '.
 
     "Created: / 19-08-2011 / 02:22:46 / cg"
--- a/SystemBrowser.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/SystemBrowser.st	Sun Oct 09 22:55:02 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
               All Rights Reserved
@@ -122,7 +120,7 @@
 
 openInClass:aClass selector:aSelector
     "launch a standard browser which immediately switches
-     to aClass » aSelector. Returns the browser"
+     to aClass » aSelector. Returns the browser"
 
     |brwsr classesName|
 
@@ -969,6 +967,12 @@
     ^ self doNotEnterIcon
 !
 
+disabledBreakpointIcon
+    <resource: #programImage>
+
+    ^ ToolbarIconLibrary breakpointDisabled9x9
+!
+
 doNotEnterIcon
     <resource: #image>
     "This resource specification was automatically generated
@@ -7090,8 +7094,8 @@
         ('*>>*' match:sel) ifTrue:[
             sep := $>
         ] ifFalse:[
-            ('*»*' match:sel) ifTrue:[
-                sep := $»
+            ('*»*' match:sel) ifTrue:[
+                sep := $»
             ] ifFalse:[
                 ('* *' match:sel) ifTrue:[
                     sep := Character space
@@ -7130,7 +7134,7 @@
 
     aString isEmptyOrNil ifTrue:[^ nil].
 
-    (idx := aString indexOf:$») ~~ 0 ifTrue:[
+    (idx := aString indexOf:$») ~~ 0 ifTrue:[
         s := (aString copyFrom:idx+1) withoutSeparators.
         s isEmpty ifTrue:[^ nil]. 
     ] ifFalse:[    
@@ -7180,7 +7184,7 @@
      self extractSelectorFrom:'self at:something put:someValue'
      self extractSelectorFrom:'(self at:something put:someValue)' 
      self extractSelectorFrom:'[self at:something put:someValue] value' 
-     self extractSelectorFrom:'Array » at:put:' 
+     self extractSelectorFrom:'Array » at:put:' 
      self extractSelectorFrom:'Array>>at:put:' 
      self extractSelectorFrom:'Array>>#at:put:' 
      self extractSelectorFrom:'Array>>#''at:put:''' 
@@ -7353,7 +7357,7 @@
     ].
     selector notNil ifTrue:[ 
         aGCOrStream
-            nextPutAll:' » ';
+            nextPutAll:' » ';
             emphasis:#bold;
             nextPutAll:selector;
             emphasis:nil.
--- a/Tools__BrowserList.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/Tools__BrowserList.st	Sun Oct 09 22:55:02 2016 +0100
@@ -1092,6 +1092,12 @@
     ^ self fetchIcon:#deprecatedMethodIcon selector:#deprecatedMethodIcon
 !
 
+disabledBreakpointIcon
+    "answer an icon to mark methods with disabled breakpoints"
+
+    ^ self fetchIcon:#disabledBreakpointIcon selector:#disabledBreakpointIcon
+!
+
 fetchIcon:name selector:fetchSelector
     "answer an icon to mark methods"
 
--- a/Tools__ChangeSetDiffTool.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/Tools__ChangeSetDiffTool.st	Sun Oct 09 22:55:02 2016 +0100
@@ -2608,8 +2608,8 @@
     loadA disable.
     loadB := menu atNameKey:#LoadVersionB.
     loadB disable.
-    "/ cg: what is the purpose of this select?
-    (diffs select:[:e | true ]) do:[:diff | 
+
+    diffs do:[:diff | 
         diff versionA 
             ifNotNil:[
                 loadA 
--- a/Tools__CodeView2.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/Tools__CodeView2.st	Sun Oct 09 22:55:02 2016 +0100
@@ -42,7 +42,7 @@
 !
 
 AbstractBackground subclass:#AnnotationShowingScrollerBackground
-	instanceVariableNames:'annotations textView'
+	instanceVariableNames:'annotations breakpoints textView'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:CodeView2
@@ -1094,24 +1094,42 @@
     "this changes the scroller's background, to show the positions of
      warnings, for easy location of interesting spots"
      
-    |allAnnotations scroller newBackground|
+    |allAnnotations allBreakpoints scroller newBackground verticalScrollBar|
 
     allAnnotations := OrderedCollection new.
+    allBreakpoints := OrderedCollection new.
     services do:[:eachService |
-        allAnnotations addAll:(eachService annotations ? #())
+        allAnnotations addAll:(eachService annotations ? #()).
+        eachService isBreakpointService ifTrue:[
+            allBreakpoints addAll:(eachService breakpoints ? #()).
+        ].    
     ].
 
-    scroller := textViewScroller verticalScrollBar thumb.
-    allAnnotations isEmptyOrNil ifTrue:[
+    verticalScrollBar := textViewScroller verticalScrollBar.
+    verticalScrollBar notNil ifTrue:[
+        scroller := verticalScrollBar thumb.
+    ].
+
+    (allAnnotations isEmpty and:[allBreakpoints isEmpty]) ifTrue:[
         "/ nothing special to show
-        scroller viewBackground isColor ifTrue:[^ self].
-        scroller initStyle
+        scroller notNil ifTrue:[
+            scroller viewBackground isColor ifTrue:[^ self].
+            scroller initStyle
+        ].
     ] ifFalse:[
         "/ yep, there are some annotations
-        newBackground := (AnnotationShowingScrollerBackground new annotations:allAnnotations; textView:textView; yourself ).
-        scroller viewBackground:newBackground.
+        newBackground := AnnotationShowingScrollerBackground new.
+        newBackground textView:textView.
+        newBackground annotations:allAnnotations; breakpoints:allBreakpoints.
+
+        scroller notNil ifTrue:[
+            scroller viewBackground:newBackground.
+        ].
     ].
-    scroller invalidate.
+
+    scroller notNil ifTrue:[
+        scroller invalidate.
+    ].
 ! !
 
 !CodeView2 methodsFor:'channels'!
@@ -2292,8 +2310,12 @@
 
 !CodeView2::AnnotationShowingScrollerBackground methodsFor:'accessing'!
 
-annotations:something
-    annotations := something.
+annotations:aCollectionOfAnnotations
+    annotations := aCollectionOfAnnotations.
+!
+
+breakpoints:aCollectionOfBreakpoints
+    breakpoints := aCollectionOfBreakpoints.
 !
 
 textView:something
@@ -2306,38 +2328,65 @@
     "I am asked to draw the background of aScroller.
      If any annotation is in that range, draw it"
     
-    |overAllHeight|
-
-    annotations isEmptyOrNil ifTrue:[^ self ].
-
+    |overAllHeight drawRect scrollerHeight|
+
+    annotations isEmptyOrNil ifTrue:[
+        breakpoints isEmptyOrNil ifTrue:[
+            ^ self 
+        ].
+    ].
+    
+    scrollerHeight := aScroller height.
+    drawRect :=
+        [:lineNr :clrInside |
+            |clrBorder yThumb|
+            
+            yThumb := (scrollerHeight * (lineNr / overAllHeight)) rounded.
+            (yThumb between:y-5 and:(y + h + 5)) ifTrue:[
+                clrBorder := clrInside darkened.
+                aScroller paint:clrInside.
+                aScroller fillRectangleX:3 y:(yThumb-5 max:0) width:aScroller width-5 height:8.
+                aScroller paint:clrBorder.
+                aScroller displayRectangleX:3 y:(yThumb-5 max:0) width:aScroller width-5 height:9.
+            ].    
+        ].
+        
     overAllHeight := textView numberOfLines.
     overAllHeight = 0 ifTrue:[ ^ self ].
 
-    annotations do:[:eachAnnotation |
-        |lineNr yThumb baseColor clr1 clr2 severity|
-
-        (lineNr := eachAnnotation line) notNil ifTrue:[    
-            yThumb := (aScroller height * (lineNr / overAllHeight)) rounded.
-            (yThumb between:y-5 and:(y + h + 5)) ifTrue:[
+    annotations notEmptyOrNil ifTrue:[
+        annotations do:[:eachAnnotation |
+            |lineNr severityColor severity|
+
+            (lineNr := eachAnnotation line) notNil ifTrue:[ 
                 severity := eachAnnotation rule severity.
                 severity == #error ifTrue:[
-                    baseColor := Color red.
+                    severityColor := Color red.
                 ] ifFalse:[
                     severity == #warning ifTrue:[
-                        baseColor := Color yellow.
+                        severityColor := Color yellow.
                     ] ifFalse:[
-                        baseColor := Color blue.
+                        severityColor := Color blue.
                     ].    
                 ].    
-                clr1 := baseColor lightened lightened.
-                clr2 := clr1 darkened.
-                aScroller paint:clr1.
-                aScroller fillRectangleX:3 y:(yThumb-5 max:0) width:aScroller width-5 height:8.
-                aScroller paint:clr2.
-                aScroller displayRectangleX:3 y:(yThumb-5 max:0) width:aScroller width-5 height:9.
+                drawRect value:lineNr value:severityColor lightened.
             ].
         ].
-    ]
+    ].
+    breakpoints notEmptyOrNil ifTrue:[
+        breakpoints do:[:eachBreakpoint |
+            (eachBreakpoint isVisible and:[eachBreakpoint isEnabled]) ifTrue:[ 
+                |lineNr bpntColor|
+
+                (lineNr := eachBreakpoint line) notNil ifTrue:[    
+                    bpntColor := eachBreakpoint isTracepoint
+                                    ifTrue:[ Color blue lightened]
+                                    ifFalse:[ Color red ].
+                    drawRect value:lineNr value:bpntColor.
+                ].
+            ].
+        ].
+    ].
 ! !
 
 !CodeView2::AnnotationShowingScrollerBackground methodsFor:'ignored conversion'!
--- a/Tools__Inspector2.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/Tools__Inspector2.st	Sun Oct 09 22:55:02 2016 +0100
@@ -852,7 +852,7 @@
     "/ Do not show language combo when language is Smalltalk.
     "/ For those not working with multiple languages is too disturbing.
     ^ BlockValue
-        with:[:o | o class programmingLanguage isSmalltalk not ]
+        with:[:o | o class programmingLanguage notNil and:[o class programmingLanguage isSmalltalk not] ]
         argument:self currentObjectHolder
 
     "Modified (comment): / 25-10-2013 / 19:39:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -1033,11 +1033,11 @@
     | currentObject currentObjectLanguage |
 
     currentObject := self currentObject.
-    currentObjectLanguage := currentObject class programmingLanguage.
-    currentObjectLanguage isSmalltalk ifFalse:[
+    currentObjectLanguage := currentObject class programmingLanguage ? SmalltalkLanguage instance.
+    currentObjectLanguage isSmalltalk ifTrue:[
+        self evaluationLanguageList value: (Array with: currentObjectLanguage).
+    ] ifFalse:[
         self evaluationLanguageList value: (Array with: currentObjectLanguage with: SmalltalkLanguage instance)
-    ] ifTrue:[
-        self evaluationLanguageList value: (Array with: currentObjectLanguage).
     ].
 
     self evaluationLanguageHolder value:(EvaluationLanguageMap at: currentObjectLanguage ifAbsent:[currentObjectLanguage])
@@ -1416,10 +1416,8 @@
 
     |tab|
 
-    tab := self tabs at: self selectionIndex.
-    ^tab 
-        ifNil:[nil]
-        ifNotNil:[tab view].
+    tab := self tabs at:self selectionIndex ifAbsent:nil.
+    ^ tab isNil ifTrue:[nil] ifFalse:[tab view].
 
     "Created: / 16-01-2008 / 17:31:19 / janfrog"
 !
@@ -1513,7 +1511,7 @@
     tabs := OrderedCollection new.        
 
     "/ Old style - tabs are specified by method #inspector2Tabs
-    selectors := theObject inspector2Tabs asSet.
+    selectors := (theObject inspector2Tabs ? #(inspector2TabCommon)) asSet.
 
     "/ New style - tab are defined by methods with <inspector2Tab> annotation
     theObject class withAllSuperclassesDo:[:eachClass| 
--- a/Tools__MethodList.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/Tools__MethodList.st	Sun Oct 09 22:55:02 2016 +0100
@@ -1688,7 +1688,11 @@
             aMethod hasEnabledBreakpoints ifTrue:[ 
                 icn := self lineBreakPointedIcon
             ] ifFalse:[    
-                icn := self lineTracePointedIcon
+                aMethod hasEnabledTracepoints ifTrue:[ 
+                    icn := self lineTracePointedIcon
+                ] ifFalse:[    
+                    icn := self disabledBreakpointIcon
+                ]    
             ].
         ].
     ].
--- a/Tools__NavigationState.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/Tools__NavigationState.st	Sun Oct 09 22:55:02 2016 +0100
@@ -196,7 +196,7 @@
     (codeView notNil and:[codeView isCodeView2]) ifTrue:[
         | xlatedCodeAspect |
 
-        xlatedCodeAspect := CodeAspectTranslations at: aSymbolOrNil ifAbsent: aSymbolOrNil.
+        xlatedCodeAspect := CodeAspectTranslations at: aSymbolOrNil ifAbsent:[aSymbolOrNil].
         codeView codeAspect: xlatedCodeAspect
     ].
 
--- a/Tools__NewClassWizardDialog.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/Tools__NewClassWizardDialog.st	Sun Oct 09 22:55:02 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2009 by eXept Software AG
               All Rights Reserved
@@ -303,7 +301,7 @@
          label: 'Class Creation Wizard'
          name: 'Class Creation Wizard'
          min: (Point 10 10)
-         bounds: (Rectangle 0 0 558 609)
+         bounds: (Rectangle 0 0 592 639)
        )
        component: 
       (SpecCollection
@@ -324,14 +322,14 @@
           (LabelSpec
              label: 'Programming Language:'
              name: 'Label9'
-             layout: (LayoutFrame 10 0 90 0 180 0 112 0)
+             layout: (LayoutFrame 7 0 90 0 301 0 112 0)
              activeHelpKey: programmingLanguage
              translateLabel: true
              adjust: right
            )
           (ComboListSpec
              name: 'ComboList1'
-             layout: (LayoutFrame 190 0 90 0 -32 1 112 0)
+             layout: (LayoutFrame 308 0 90 0 -32 1 112 0)
              activeHelpKey: programmingLanguage
              model: languageHolder
              comboList: listOfLanguages
@@ -340,14 +338,14 @@
           (LabelSpec
              label: 'Stereotype:'
              name: 'Label13'
-             layout: (LayoutFrame 10 0 120 0 180 0 142 0)
+             layout: (LayoutFrame 10 0 143 0 180 0 165 0)
              activeHelpKey: stereotype
              translateLabel: true
              adjust: right
            )
           (ComboListSpec
              name: 'ComboList3'
-             layout: (LayoutFrame 190 0 119 0 -32 1 141 0)
+             layout: (LayoutFrame 190 0 142 0 -32 1 164 0)
              activeHelpKey: stereotype
              model: stereotypeHolder
              comboList: listOfStereotypes
@@ -356,14 +354,14 @@
           (LabelSpec
              label: 'Class Name:'
              name: 'Label1'
-             layout: (LayoutFrame 10 0 149 0 180 0 171 0)
+             layout: (LayoutFrame 10 0 172 0 180 0 194 0)
              activeHelpKey: className
              translateLabel: true
              adjust: right
            )
           (InputFieldSpec
              name: 'EntryField1'
-             layout: (LayoutFrame 190 0 149 0 -32 1 171 0)
+             layout: (LayoutFrame 190 0 172 0 -32 1 194 0)
              activeHelpKey: className
              model: classNameHolder
              acceptOnReturn: true
@@ -374,20 +372,20 @@
           (LabelSpec
              label: '*'
              name: 'Label14'
-             layout: (LayoutFrame 180 0 150 0 190 0 172 0)
+             layout: (LayoutFrame 180 0 173 0 190 0 195 0)
              translateLabel: true
            )
           (LabelSpec
              label: 'Superclass:'
              name: 'Label2'
-             layout: (LayoutFrame 10 0 179 0 180 0 201 0)
+             layout: (LayoutFrame 10 0 202 0 180 0 224 0)
              activeHelpKey: superclass
              translateLabel: true
              adjust: right
            )
           (ComboBoxSpec
              name: 'ComboBox1'
-             layout: (LayoutFrame 190 0 179 0 -32 1 201 0)
+             layout: (LayoutFrame 190 0 202 0 -32 1 224 0)
              activeHelpKey: superclass
              model: superclassNameHolder
              acceptOnLostFocus: true
@@ -397,13 +395,13 @@
           (LabelSpec
              label: '*'
              name: 'Label15'
-             layout: (LayoutFrame 180 0 179 0 190 0 201 0)
+             layout: (LayoutFrame 180 0 202 0 190 0 224 0)
              translateLabel: true
            )
           (ActionButtonSpec
              label: '...'
              name: 'Button1'
-             layout: (LayoutFrame -22 1 179 0 -2 1 201 0)
+             layout: (LayoutFrame -22 1 202 0 -2 1 224 0)
              activeHelpKey: chooseSuperclass
              translateLabel: true
              model: openSuperClassChooser
@@ -411,14 +409,14 @@
           (LabelSpec
              label: 'Package ID:'
              name: 'Label3'
-             layout: (LayoutFrame 10 0 220 0 180 0 242 0)
+             layout: (LayoutFrame 10 0 243 0 180 0 265 0)
              activeHelpKey: package
              translateLabel: true
              adjust: right
            )
           (ComboBoxSpec
              name: 'ComboBox2'
-             layout: (LayoutFrame 190 0 219 0 -32 1 241 0)
+             layout: (LayoutFrame 190 0 242 0 -32 1 264 0)
              activeHelpKey: package
              model: packageHolder
              acceptOnReturn: true
@@ -430,7 +428,7 @@
           (ActionButtonSpec
              label: '...'
              name: 'Button4'
-             layout: (LayoutFrame -22 1 219 0 -2 1 241 0)
+             layout: (LayoutFrame -22 1 242 0 -2 1 264 0)
              activeHelpKey: packageChooser
              translateLabel: true
              model: openPackageChooser
@@ -438,14 +436,14 @@
           (LabelSpec
              label: 'Namespace:'
              name: 'Label4'
-             layout: (LayoutFrame 10 0 249 0 180 0 271 0)
+             layout: (LayoutFrame 10 0 272 0 180 0 294 0)
              activeHelpKey: namespace
              translateLabel: true
              adjust: right
            )
           (ComboListSpec
              name: 'ComboList2'
-             layout: (LayoutFrame 190 0 249 0 -32 1 271 0)
+             layout: (LayoutFrame 190 0 272 0 -32 1 294 0)
              activeHelpKey: namespace
              model: nameSpaceHolder
              comboList: listOfNamespaces
@@ -453,7 +451,7 @@
           (ActionButtonSpec
              label: '...'
              name: 'Button5'
-             layout: (LayoutFrame -22 1 249 0 -2 1 271 0)
+             layout: (LayoutFrame -22 1 272 0 -2 1 294 0)
              activeHelpKey: namespaceChooser
              translateLabel: true
              model: openNamespaceChooser
@@ -461,14 +459,14 @@
           (LabelSpec
              label: 'Category:'
              name: 'Label12'
-             layout: (LayoutFrame 10 0 279 0 180 0 301 0)
+             layout: (LayoutFrame 10 0 302 0 180 0 324 0)
              activeHelpKey: category
              translateLabel: true
              adjust: right
            )
           (ComboBoxSpec
              name: 'ComboBox3'
-             layout: (LayoutFrame 190 0 279 0 -32 1 301 0)
+             layout: (LayoutFrame 190 0 302 0 -32 1 324 0)
              activeHelpKey: category
              model: categoryHolder
              acceptOnLostFocus: true
@@ -477,7 +475,7 @@
           (ActionButtonSpec
              label: '...'
              name: 'Button6'
-             layout: (LayoutFrame -22 1 279 0 -2 1 301 0)
+             layout: (LayoutFrame -22 1 302 0 -2 1 324 0)
              activeHelpKey: categoryChooser
              translateLabel: true
              model: openCategoryChooser
@@ -485,14 +483,14 @@
           (LabelSpec
              label: 'Instance Variables:'
              name: 'Label5'
-             layout: (LayoutFrame 10 0 319 0 180 0 341 0)
+             layout: (LayoutFrame 10 0 342 0 180 0 364 0)
              activeHelpKey: instanceVariableNames
              translateLabel: true
              adjust: right
            )
           (InputFieldSpec
              name: 'EntryField4'
-             layout: (LayoutFrame 190 0 319 0 -32 1 341 0)
+             layout: (LayoutFrame 190 0 342 0 -32 1 364 0)
              activeHelpKey: instanceVariableNames
              model: instVarNamesHolder
              acceptOnReturn: true
@@ -503,14 +501,14 @@
           (LabelSpec
              label: 'Class Variables:'
              name: 'Label6'
-             layout: (LayoutFrame 10 0 349 0 180 0 371 0)
+             layout: (LayoutFrame 10 0 372 0 180 0 394 0)
              activeHelpKey: classVariableNames
              translateLabel: true
              adjust: right
            )
           (InputFieldSpec
              name: 'EntryField5'
-             layout: (LayoutFrame 190 0 349 0 -32 1 371 0)
+             layout: (LayoutFrame 190 0 372 0 -32 1 394 0)
              activeHelpKey: classVariableNames
              model: classVarNamesHolder
              acceptOnReturn: true
@@ -519,16 +517,16 @@
              acceptOnPointerLeave: true
            )
           (LabelSpec
-             label: 'Class Instance Variables:'
+             label: 'Class InstVars:'
              name: 'Label7'
-             layout: (LayoutFrame 10 0 379 0 180 0 401 0)
+             layout: (LayoutFrame 10 0 402 0 180 0 424 0)
              activeHelpKey: classInstVariableNames
              translateLabel: true
              adjust: right
            )
           (InputFieldSpec
              name: 'EntryField6'
-             layout: (LayoutFrame 190 0 379 0 -32 1 401 0)
+             layout: (LayoutFrame 190 0 402 0 -32 1 424 0)
              activeHelpKey: classInstVariableNames
              model: classInstVarNamesHolder
              acceptOnReturn: true
@@ -539,14 +537,14 @@
           (LabelSpec
              label: 'Create:'
              name: 'Label8'
-             layout: (LayoutFrame 10 0 419 0 110 0 441 0)
+             layout: (LayoutFrame 10 0 442 0 110 0 464 0)
              translateLabel: true
              adjust: right
            )
           (CheckBoxSpec
              label: 'Accessors'
              name: 'CheckBox1'
-             layout: (LayoutFrame 120 0 419 0 280 0 441 0)
+             layout: (LayoutFrame 120 0 442 0 280 0 464 0)
              activeHelpKey: createAccessors
              model: createAccessorsHolder
              translateLabel: true
@@ -554,7 +552,7 @@
           (CheckBoxSpec
              label: 'Initial Template Code'
              name: 'CheckBox6'
-             layout: (LayoutFrame 310 0 419 0 -36 1 441 0)
+             layout: (LayoutFrame 310 0 442 0 -36 1 464 0)
              activeHelpKey: createInitialGUICode
              model: createInitialGUICodeHolder
              translateLabel: true
@@ -562,7 +560,7 @@
           (CheckBoxSpec
              label: 'Initializer'
              name: 'CheckBox2'
-             layout: (LayoutFrame 120 0 449 0 0 1 471 0)
+             layout: (LayoutFrame 120 0 472 0 0 1 494 0)
              activeHelpKey: createInitializer
              model: createInitializerHolder
              translateLabel: true
@@ -570,7 +568,7 @@
           (CheckBoxSpec
              label: 'Update Method'
              name: 'CheckBox5'
-             layout: (LayoutFrame 120 0 479 0 0 1 501 0)
+             layout: (LayoutFrame 120 0 502 0 0 1 524 0)
              activeHelpKey: createUpdateMethod
              model: createUpdateMethodHolder
              translateLabel: true
@@ -578,7 +576,7 @@
           (CheckBoxSpec
              label: 'Required Methods (Subclass responsibilities)'
              name: 'CheckBox3'
-             layout: (LayoutFrame 120 0 509 0 0 1 531 0)
+             layout: (LayoutFrame 120 0 532 0 0 1 554 0)
              activeHelpKey: createRequiredMethods
              model: createRequiredMethodsHolder
              translateLabel: true
@@ -586,7 +584,7 @@
           (CheckBoxSpec
              label: 'Print Method'
              name: 'CheckBox4'
-             layout: (LayoutFrame 120 0 539 0 0 1 561 0)
+             layout: (LayoutFrame 120 0 562 0 0 1 584 0)
              activeHelpKey: createPrintMethod
              visibilityChannel: false
              model: createPrintMethodHolder
--- a/Tools__NewSystemBrowser.st	Mon Oct 03 15:15:56 2016 +0100
+++ b/Tools__NewSystemBrowser.st	Sun Oct 09 22:55:02 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2000 by eXept Software AG
               All Rights Reserved
@@ -414,6 +412,9 @@
 #launchSelectedApplication
 'Launch the selected application'
 
+#packageSelectedApplication
+'Package the selected application for deployment'
+
 #runTestCases
 'Run selected testCase(s)'
 
@@ -8910,7 +8911,7 @@
 
     <resource: #menu>
 
-    ^
+    ^ 
      #(Menu
         (
          (MenuItem
@@ -8919,7 +8920,7 @@
           )
          (MenuItem
             label: 'Smalltalk...'
-            submenu:
+            submenu: 
            (Menu
               (
                (MenuItem
@@ -8935,17 +8936,25 @@
                   itemValue: classMenuNewDialog
                 )
                (MenuItem
+                  label: 'Widget (View)'
+                  itemValue: classMenuNewWidgetClass
+                )
+               (MenuItem
                   label: 'WebService'
                   itemValue: classMenuNewWebService
                 )
                (MenuItem
+                  label: '-'
+                )
+               (MenuItem
                   label: 'WebApplication'
                   itemValue: classMenuNewWebApplication
                   isVisible: false
                 )
                (MenuItem
-                  label: 'Widget (View)'
-                  itemValue: classMenuNewWidgetClass
+                  label: 'Console Application'
+                  itemValue: classMenuNewConsoleApplication
+                  isVisible: false
                 )
                (MenuItem
                   label: 'Standalone Startup'
@@ -17903,7 +17912,7 @@
 
     <resource: #menu>
 
-    ^
+    ^ 
      #(Menu
         (
          (MenuItem
@@ -18050,19 +18059,6 @@
             isVisible: hasClassSelectedHolder
           )
          (MenuItem
-            activeHelpKey: launchSelectedApplication
-            label: 'Launch Selected Application'
-            itemValue: launchSelectedApplication
-            isButton: true
-            isVisible: hasStartableApplicationSelectedHolder
-            labelImage: (ResourceRetriever ToolbarIconLibrary start22x22Icon)
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-            isVisible: hasStartableApplicationSelectedHolder
-          )
-         (MenuItem
             activeHelpKey: executeSelectedClassMethod
             label: 'Execute Selected Class Method'
             itemValue: executeSelectedClassMethod
@@ -18089,6 +18085,32 @@
             isVisible: hasSharedPoolSelectedHolder
           )
          (MenuItem
+            activeHelpKey: launchSelectedApplication
+            label: 'Launch Selected Application'
+            itemValue: launchSelectedApplication
+            isButton: true
+            isVisible: hasStartableApplicationSelectedHolder
+            labelImage: (ResourceRetriever ToolbarIconLibrary start22x22Icon)
+            showBusyCursorWhilePerforming: true
+          )
+         (MenuItem
+            label: '-'
+            isVisible: hasStartableApplicationSelectedHolder
+          )
+         (MenuItem
+            activeHelpKey: packageSelectedApplication
+            label: 'Package Selected Application...'
+            itemValue: packageSelectedApplication
+            isButton: true
+            isVisible: hasPackagableApplicationSelectedHolder
+            labelImage: (ResourceRetriever ToolbarIconLibrary packageIn24x24Icon)
+            showBusyCursorWhilePerforming: true
+          )
+         (MenuItem
+            label: '-'
+            isVisible: hasPackagableApplicationSelectedHolder
+          )
+         (MenuItem
             activeHelpKey: runTestCases
             label: 'Run Tests'
             itemValue: runTestCases
@@ -22602,6 +22624,27 @@
         ^ anyWrap and:[anyBreak not]
 !
 
+hasPackagableApplicationSelected
+    |cls|
+
+    ^ (cls := self theSingleSelectedClass) notNil
+    and:[ cls theNonMetaclass isProjectDefinition 
+          or:[ (cls inheritsFrom:StandaloneStartup)
+               and:[ cls isAbstract not ]
+             ]
+        ]
+!
+
+hasPackagableApplicationSelectedHolder
+    |holder|
+
+    (holder := builder bindingAt:#hasPackagableApplicationSelectedHolder) isNil ifTrue:[
+        holder := ValueHolder with:false.
+        builder aspectAt:#hasPackagableApplicationSelectedHolder put: holder.
+    ].
+    ^ holder
+!
+
 hasPerforceRepositoryFor: package
     "is there a perforce source repository for package?"
 
@@ -23581,7 +23624,7 @@
 !
 
 isMethodListBrowser
-    ^ navigationState isMethodListBrowser
+    ^ navigationState notNil and:[navigationState isMethodListBrowser]
 !
 
 isMethodListBrowserHolder
@@ -23899,6 +23942,7 @@
     self updateExecuteMethodVisibility.
     self updateInitSharedPoolVisibility.
     self updateLaunchApplicationVisibility.
+    self updatePackageApplicationVisibility.
     self updateTextEditorBehavior.
     "/ self delayedUpdateCode.
     self updateLintEnablement.
@@ -24919,6 +24963,11 @@
     "Created: / 27-02-2008 / 08:42:56 / janfrog"
 !
 
+updatePackageApplicationVisibility
+    self hasPackagableApplicationSelectedHolder
+            value:(self hasPackagableApplicationSelected)
+!
+
 updatePluginVisibility
     |naviState pluginVisible  frame  pluginApp  pluginView |
 
@@ -27633,6 +27682,7 @@
     self updateExecuteMethodVisibility.
     self updateInitSharedPoolVisibility.
     self updateLaunchApplicationVisibility.
+    self updatePackageApplicationVisibility.
     self updateToolBarButtonEnablement.
 
     "/ force update of the menus orgMode aspect
@@ -31582,6 +31632,18 @@
     "Modified: / 09-04-2014 / 12:37:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+classMenuNewConsoleApplication
+    "create a class-definition prototype for a console application"
+
+    self
+        classClassDefinitionTemplateFor:StandaloneStartupHeadless
+        in:(self theSingleSelectedCategory ? 'Console Applications')
+        asNamespace:false
+        private:false.
+
+    self codeAspect:#newConsoleApplication.
+!
+
 classMenuNewDialog
     "create a class-definition prototype for a dialog"
 
@@ -31692,6 +31754,8 @@
         asNamespace:false
         private:false.
 
+    self codeAspect:#newStandaloneApplication.
+
     "Created: / 08-08-2011 / 07:46:47 / cg"
 !
 
@@ -33343,11 +33407,12 @@
      (and optionally the packageID of any methods (if they are from different packages)"
 
     |anyClassMoved anyMethodMoved classesNotYetInRepository classesAlreadyInRepository
-     sourceInfoPerClassOfClassesAlreadyInRepository oldPackagePerClass newProjectDefinition|
+     sourceInfoPerClassOfClassesAlreadyInRepository oldPackagePerClass newProjectDefinition
+     thereWasASourceCodeManagerError|
 
     (newProject = PackageId noProjectID) ifTrue:[
         (Dialog confirm:(resources
-                            stringWithCRs:'Do you really want to move those items to "%1"?\\(this will actually make them unassigned)'
+                            stringWithCRs:'Do you really want to move those items to "%1"?\\(this will actually make them unassigned from any package)'
                             with:newProject))
         ifFalse:[
             ^ self
@@ -33359,13 +33424,22 @@
     sourceInfoPerClassOfClassesAlreadyInRepository := Dictionary new.
     oldPackagePerClass := Dictionary new.
 
+    thereWasASourceCodeManagerError := false.
+    
     classes do:[:eachClass | 
-        |oldProject theClass mgr|
+        |oldProject theClass mgr vsn|
 
         theClass := eachClass theNonMetaclass.
         mgr := theClass sourceCodeManager.
 
-        (theClass sourceCodeManager isNil or:[ (mgr newestRevisionOf:theClass) isNil ]) ifTrue:[
+        mgr notNil ifTrue:[ 
+            SourceCodeManagerError handle:[:ex |
+                thereWasASourceCodeManagerError := true
+            ] do:[    
+                vsn := mgr newestRevisionOf:theClass.
+            ].
+        ].
+        vsn isNil ifTrue:[
             classesNotYetInRepository add:eachClass
         ] ifFalse:[
             classesAlreadyInRepository add:eachClass.
@@ -33421,8 +33495,13 @@
     anyClassMoved ifTrue:[
         environment changed:#projectOrganization.
     ].
+    (newProject = PackageId noProjectID) ifTrue:[^ self].
+    
     self rememberLastProjectMoveTo:newProject.
-
+    thereWasASourceCodeManagerError ifTrue:[
+        Dialog warn:(resources stringWithCRs:'There was a problem accessing the source code repository.\\Please check your settings and/or network connection').
+        ^ self
+    ].    
     "/ Only checkin classes managed by old (non-stx:libscm) based managers
     "/ since stx:libscm care for this itself and makes this warning a little
     "/ annoying...
@@ -33524,6 +33603,20 @@
     ]
 !
 
+packageSelectedApplication
+    "either projectDefiniton or
+     a subclass of standaloneStartup is selected"
+     
+    |cls|
+
+    cls := self theSingleSelectedClass.
+    cls isNil ifTrue:[
+        Dialog warn:'Please select a project definition or startup class.'.
+        ^ self.
+    ].
+    Tools::ProjectBuilderAssistantApplication openOn:cls theNonMetaclass.
+!
+
 printOutClass:aClass withSelector:aSelector
     |printStream|
 
@@ -34005,10 +34098,9 @@
                     self class
                         findMethodsIn:setOfClasses
                         where:[:cls :mthdIn :sel |
-                            |mthd mSource isCandidate isReference usedGlobals|
+                            |mthd mSource isCandidate isReference usedGlobals tryInLiterals|
 
                             mthd := mthdIn originalMethodIfWrapped.
-
                             "/ kludge: Lazy methods do not include symbols in the literal array - sigh
                             mthd isLazyMethod ifTrue:[
                                 mSource := mthd source.
@@ -34039,7 +34131,13 @@
                             ].
                             isReference ifFalse:[
                                 "/ also search for class-refs in specs
-                                mthd hasCanvasResource ifTrue:[
+                                tryInLiterals := mthd hasCanvasResource.
+                                tryInLiterals ifFalse:[
+                                    tryInLiterals := mthd mclass isMeta
+                                                     and:[ mthd mclass theNonMetaClass isProjectDefinition 
+                                                     and:[mthd selector == #classNamesAndAttributes]].
+                                ].                    
+                                tryInLiterals ifTrue:[
                                     isReference := (mthd refersToLiteral:sym)
                                                     or:[(mthd refersToLiteral:fullNameSym)
                                                     or:[ localNameSym notNil
@@ -34091,11 +34189,12 @@
         "/ therefore, we setup a multiple pattern search here (sigh)
         patternsForCodeSearch := OrderedCollection new.
         aCollectionOfClasses do:[:each |
-            |nm nm2 nm3|
-
-            nm := each theNonMetaclass name.
-            nm2 := each theNonMetaclass nameWithoutPrefix.
-            nm3 := each theNonMetaclass nameWithoutNameSpacePrefix.
+            |nonMeta nm nm2 nm3|
+
+            nonMeta := each theNonMetaclass.    
+            nm := nonMeta name.
+            nm2 := nonMeta nameWithoutPrefix.
+            nm3 := nonMeta nameWithoutNameSpacePrefix.
             patternsForCodeSearch add:nm.
             nm2 ~= nm ifTrue:[ patternsForCodeSearch add:nm2 ].
             nm3 ~= nm ifTrue:[ patternsForCodeSearch add:nm3 ].
@@ -41096,16 +41195,17 @@
     Tools::ProjectBuilderAssistantApplication new
         projectType:projectDefinition projectType.
 
+    projectBuilder := Tools::ProjectBuilder new.
+    projectBuilder makeExeOnly:exeOnly; package:projectToBuild.
+
     Transcript isView ifTrue:[
         Transcript topView raise.
     ].
-
-    projectBuilder := Tools::ProjectBuilder new.
-    projectBuilder
-        makeExeOnly:exeOnly;
-        package:projectToBuild;
-        "/ build
-        buildWithColorizedOutputTo:Transcript.
+    Transcript showCR:'*******************'.
+    Transcript showCR:('building in %1...' bindWith:projectBuilder buildDirectory pathName).
+    
+    "/ build
+    projectBuilder buildWithColorizedOutputTo:Transcript.
 
     buildDir := projectToBuild asPackageId pathRelativeToTopDirectory:projectBuilder buildDirectory.
 
@@ -41116,6 +41216,7 @@
         self activityNotification:'Showing result in filebrowser.'.
         FileBrowserV2 openOnDirectory:buildDir
     ].
+    Transcript showCR:('buil finished.').
 
     "Created: / 21-01-2012 / 13:53:34 / cg"
 !
@@ -47115,7 +47216,7 @@
 
         self activityNotification:nil.
         browser := (UserPreferences current changeSetBrowserClass) openOn:previousMethods.
-        browser window label:(resources string:'Revisions of %1 » %2' with:mclass name with:mselector).
+        browser window label:(resources string:'Revisions of %1  %2' with:mclass name with:mselector).
         browser readOnly:true.
     ].
 
@@ -51702,7 +51803,7 @@
             label:[:chg | 
                 |lbl|
                 "/ lbl := chg printString
-                lbl := (chg className ? '???') , ' » ' , (chg selector  ? '???') allBold.
+                lbl := (chg className ? '???') , '  ' , (chg selector  ? '???') allBold.
                 (chg isMethodChange and:[chg changeMethod isNil]) ifTrue:[
                     lbl := lbl asText allStrikedOut,' ','(removed)' allItalic.
                 ].    
@@ -56221,7 +56322,7 @@
         withMatch:withMatch
         withMethodList:withMethodList
         allowFind:(self navigationState isMethodBrowser)
-        allowBuffer:true
+        allowBuffer:(builder notNil)
         allowBrowser:true
         withTextEntry:withTextEntry.
     
@@ -59064,6 +59165,7 @@
     ^ selectorCompletion
 ! !
 
+
 !NewSystemBrowser methodsFor:'private-semantic checks'!
 
 checkAcceptedMethod:aMethod inClass:aClass
@@ -61532,11 +61634,13 @@
     mcls := aClass theMetaclass.
 
     codeAspect := self codeAspect.
-    codeAspect == #newApplication ifTrue:[ msg := 'Generate initial application code ?' ].
-    codeAspect == #newDialog ifTrue:[ msg := 'Generate initial dialog code ?' ].
-    codeAspect == #newWebService ifTrue:[ msg := 'Generate initial webService code ?' ].
-    codeAspect == #newWebPage ifTrue:[ msg := 'Generate initial webPage code ?' ].
-    codeAspect == #newWidget ifTrue:[ msg := 'Generate initial widget code ?' ].
+    codeAspect == #newApplication ifTrue:[ msg := 'Generate initial application code?' ].
+    codeAspect == #newConsoleApplication ifTrue:[ msg := 'Generate initial console application code?' ].
+    codeAspect == #newStandaloneApplication ifTrue:[ msg := 'Generate initial application code?' ].
+    codeAspect == #newDialog ifTrue:[ msg := 'Generate initial dialog code?' ].
+    codeAspect == #newWebService ifTrue:[ msg := 'Generate initial webService code?' ].
+    codeAspect == #newWebPage ifTrue:[ msg := 'Generate initial webPage code?' ].
+    codeAspect == #newWidget ifTrue:[ msg := 'Generate initial widget code?' ].
 
     (msg notNil and:[self confirm:(resources string:msg)])
     ifTrue:[
@@ -61554,6 +61658,12 @@
             SmalltalkCodeGeneratorTool createExamplesMethodFor:mcls.
             SmalltalkCodeGeneratorTool createApplicationCodeFor:cls.
         ].
+        codeAspect == #newConsoleApplication ifTrue:[
+            SmalltalkCodeGeneratorTool createApplicationCodeFor:cls.
+        ].
+        codeAspect == #newStandaloneApplication ifTrue:[
+            SmalltalkCodeGeneratorTool createStandaloneStartupCodeFor:cls
+        ].
         codeAspect == #newWidget ifTrue:[
             SmalltalkCodeGeneratorTool createWidgetCodeFor:cls.
         ].
--- a/resources/de.rs	Mon Oct 03 15:15:56 2016 +0100
+++ b/resources/de.rs	Sun Oct 09 22:55:02 2016 +0100
@@ -146,6 +146,7 @@
 'Add Text Editor'                                                                                       'Neuer Texteditor'
 'Add Text Editor Page'                                                                                  'Neue Texteditor-Seite'
 'Add ValueHolder'                                                                                       'ValueHolder Hinzufügen'
+'Add Variable'                                                                                          'Variable Hinzufügen'
 'Add Workspace Variable'                                                                                'Workspace Variable hinzufügen'
 'Add a tab with an embedded console-terminal'                                                           'Neue Seite mit Terminal-Konsole hinzufügen'
 'Add another page (tab)'                                                                                'Neue Seite (Tab) hinzufügen'