Workspace.st
changeset 5053 ce5ca46e8388
parent 5024 d000eac18ce2
child 5065 8297b68f9fe1
--- a/Workspace.st	Tue Jun 10 12:05:46 2014 +0200
+++ b/Workspace.st	Tue Jun 10 12:24:04 2014 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -33,7 +33,7 @@
 copyright
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -55,35 +55,35 @@
     (thus you can put a workspace into more complex widgets, and
      control what should happen on 'doIt').
 
-    A useful default action is automatically defined, which simply 
-    evaluates the selection as a smalltalk expression. 
+    A useful default action is automatically defined, which simply
+    evaluates the selection as a smalltalk expression.
     (but, a lisp or prolog workspace would define its own action,
      to call for another compiler/interpreter  ...)
 
     Special workspace- and doIt variables:
-        workspaces can be configured to automatically define undefined variables
-        as either workspace- or doIt variables. When encountering undefined variables,
-        the parser asks for an action, which is responded with #workspace or doIt if a
-        workspace is the requestor of a doIt. Both are implemented as value holders, and
-        the parser will generate code sending value/value: instead of normal assignment.
-        Workspace variables are kept in the Workspace class and will both persist between doIts
-        and also be visible across workspaces. They are perfect for scripting (and therefore anabled
-        by default when stx is started with one of the scripting options).
-        DoIt variables are only valid during a single doIt.
-        Be aware that when you ask from the outside via workspaceVariableAt:, you'll get a valueHolder.
-        This is by purbose, as it allows for easy monitoring and tracing of changes.
-            
+	workspaces can be configured to automatically define undefined variables
+	as either workspace- or doIt variables. When encountering undefined variables,
+	the parser asks for an action, which is responded with #workspace or doIt if a
+	workspace is the requestor of a doIt. Both are implemented as value holders, and
+	the parser will generate code sending value/value: instead of normal assignment.
+	Workspace variables are kept in the Workspace class and will both persist between doIts
+	and also be visible across workspaces. They are perfect for scripting (and therefore anabled
+	by default when stx is started with one of the scripting options).
+	DoIt variables are only valid during a single doIt.
+	Be aware that when you ask from the outside via workspaceVariableAt:, you'll get a valueHolder.
+	This is by purbose, as it allows for easy monitoring and tracing of changes.
+
     Caveat:
-        in this version, Workspace does not yet support doIt in MVC setups.
-        For now, simulate this by setting the doItAction, to notify the
-        model manually about the doIt.
+	in this version, Workspace does not yet support doIt in MVC setups.
+	For now, simulate this by setting the doItAction, to notify the
+	model manually about the doIt.
 
 
     [instance variables:]
 
       doItAction      <Block>         block to evaluate for doIt
 
-      errorFgColor    <Color>         fg-Color to be used when highlighting errors 
+      errorFgColor    <Color>         fg-Color to be used when highlighting errors
 
       errorBgColor    <Color>         bg-Color to be used when highlighting errors
 
@@ -93,20 +93,20 @@
     [styleSheet values:]
 
       codeErrorSelectionForegroundColor     fg color to highlight errors
-                                            (default: selection fg)
+					    (default: selection fg)
 
       codeErrorSelectionBackgroundColor     bg color to highlight errors
-                                            (default: selection bg)
+					    (default: selection bg)
 
     [start with:]
-        Workspace open
+	Workspace open
 
     [see also:]
-        Workspace EditTextView 
-        Parser ByteCodeCompiler
+	Workspace EditTextView
+	Parser ByteCodeCompiler
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 "
 ! !
 
@@ -114,8 +114,8 @@
 
 sniplets
     Sniplets isNil ifTrue:[
-        Sniplets := Dictionary new.
-        self initializeDefaultAbbreviations.
+	Sniplets := Dictionary new.
+	self initializeDefaultAbbreviations.
     ].
     ^ Sniplets
 
@@ -148,152 +148,152 @@
     "default snippets/abbreviations. TODO: save/load sniplets"
 
     "flush and reinitialize sniplets with:
-         Sniplets := Dictionary new.
+	 Sniplets := Dictionary new.
     "
     "after a code change below, update with:
-         self initializeDefaultAbbreviations.
+	 self initializeDefaultAbbreviations.
     "
 
     #(
-        't'     'true'    
-        'f'     'false'
-        's'     'self'
-        'su'    'super'                  
-        'ss'    'super '            
-        'n'     'nil'
-        'y'     'yourself.'
+	't'     'true'
+	'f'     'false'
+	's'     'self'
+	'su'    'super'
+	'ss'    'super '
+	'n'     'nil'
+	'y'     'yourself.'
 
-        'in'    'isNil '
-        'nn'    'notNil '
-        'ie'    'isEmpty '
-        'ne'    'notEmpty '
-        'ien'   'isEmptyOrNil '
-        'nen'   'notEmptyOrNil '
+	'in'    'isNil '
+	'nn'    'notNil '
+	'ie'    'isEmpty '
+	'ne'    'notEmpty '
+	'ien'   'isEmptyOrNil '
+	'nen'   'notEmptyOrNil '
 
-        'it'    'ifTrue:[!!'
-        'if'    'ifFalse:[!!'
-        'itf'   'ifTrue:[!!] ifFalse:[].'
-        'int'   'isNil ifTrue:[!!].'
-        'inf'   'isNil ifFalse:[!!].'
-        'ints'  'isNil ifTrue:[^ self].'
-        'infs'  'isNil ifFalse:[^ self].'
-        'nnt'   'notNil ifTrue:[!!].'
-        'nnf'   'notNil ifFalse:[!!].'
-        'iet'   'isEmpty ifTrue:[!!].'
-        'net'   'notEmpty ifTrue:[!!].'
-        'ief'   'isEmpty ifFalse:[!!].'
-        'nef'   'notEmpty ifFalse:[!!].'
+	'it'    'ifTrue:[!!'
+	'if'    'ifFalse:[!!'
+	'itf'   'ifTrue:[!!] ifFalse:[].'
+	'int'   'isNil ifTrue:[!!].'
+	'inf'   'isNil ifFalse:[!!].'
+	'ints'  'isNil ifTrue:[^ self].'
+	'infs'  'isNil ifFalse:[^ self].'
+	'nnt'   'notNil ifTrue:[!!].'
+	'nnf'   'notNil ifFalse:[!!].'
+	'iet'   'isEmpty ifTrue:[!!].'
+	'net'   'notEmpty ifTrue:[!!].'
+	'ief'   'isEmpty ifFalse:[!!].'
+	'nef'   'notEmpty ifFalse:[!!].'
 
-        'wt'    'whileTrue:[!!]'
-        'wf'    'whileFalse:[!!]'
+	'wt'    'whileTrue:[!!]'
+	'wf'    'whileFalse:[!!]'
 
-        'do'    'do:[:each |!!]'
-        'd:'    'do:[:each |!!]'
-        'kdo'   'keysAndValuesDo:[:eachKey :eachValue |!!]'
-        'kvd'   'keysAndValuesDo:[:eachKey :eachValue |!!]'
-        'kv:'   'keysAndValuesDo:[:eachKey :eachValue |!!]'
-        'k:'    'keysDo:[:eachKey | !!]'
-        'dt'    'detect:[:each | !!]'   
-        'de'    'detect:[:each | !!]'
-        'det'   'detect:[:each | !!]'
-        'dtn'   'detect:[:each | !!] ifNone:[]'
-        'cl'    'collect:[:each | !!]'
-        'co'    'collect:[:each | !!]'
-        'col'   'collect:[:each | !!]'
-        'sl'    'select:[:each | !!]'
-        'se'    'select:[:each | !!]'
-        'sel'   'select:[:each | !!]'
-        'rj'    'reject:[:each | !!]'
-        're'    'reject:[:each | !!]'
-        'rej'   'reject:[:each | !!]'
-        'inj'   'inject:!! into:[:accum :each | ]'
+	'do'    'do:[:each |!!]'
+	'd:'    'do:[:each |!!]'
+	'kdo'   'keysAndValuesDo:[:eachKey :eachValue |!!]'
+	'kvd'   'keysAndValuesDo:[:eachKey :eachValue |!!]'
+	'kv:'   'keysAndValuesDo:[:eachKey :eachValue |!!]'
+	'k:'    'keysDo:[:eachKey | !!]'
+	'dt'    'detect:[:each | !!]'
+	'de'    'detect:[:each | !!]'
+	'det'   'detect:[:each | !!]'
+	'dtn'   'detect:[:each | !!] ifNone:[]'
+	'cl'    'collect:[:each | !!]'
+	'co'    'collect:[:each | !!]'
+	'col'   'collect:[:each | !!]'
+	'sl'    'select:[:each | !!]'
+	'se'    'select:[:each | !!]'
+	'sel'   'select:[:each | !!]'
+	'rj'    'reject:[:each | !!]'
+	're'    'reject:[:each | !!]'
+	'rej'   'reject:[:each | !!]'
+	'inj'   'inject:!! into:[:accum :each | ]'
 
-        'ex'    'Error handle:[ex | !!] do:[].'
-        'sh'    'self halt.'
-        'mt'    'MessageTally spyOn:[!!].'
+	'ex'    'Error handle:[ex | !!] do:[].'
+	'sh'    'self halt.'
+	'mt'    'MessageTally spyOn:[!!].'
 
-        'ih'    '!! ifTrue:[ self halt ].'
-        'ik'    'includesKey: #'
-        'is'    'includesString: #'
+	'ih'    '!! ifTrue:[ self halt ].'
+	'ik'    'includesKey: #'
+	'is'    'includesString: #'
 
-        'af'    'asFilename '
-        'as'    'asString '
-        'aoc'   'asOrderedCollection '
+	'af'    'asFilename '
+	'as'    'asString '
+	'aoc'   'asOrderedCollection '
 
-        'np'    'nextPut: '
-        'npa'   'nextPutAll: '
-        'npl'   'nextPutLine: '
+	'np'    'nextPut: '
+	'npa'   'nextPutAll: '
+	'npl'   'nextPutLine: '
 
-        'ps'    'printString'
-        'sr'    'self subclassResponsibility.'
+	'ps'    'printString'
+	'sr'    'self subclassResponsibility.'
 
-        'ati'   'at:!! ifAbsent: '
-        'atip'  'at:!! ifAbsentPut:[ ] '
-        'ap'    'at:!! '
+	'ati'   'at:!! ifAbsent: '
+	'atip'  'at:!! ifAbsentPut:[ ] '
+	'ap'    'at:!! '
 
-        'st'    'Smalltalk'
-        'ts'    'Transcript showCR:''!!''.'
-        'trs'   'Transcript showCR:''!!''.'
-        'abb'   'Workspace sniplets inspect.'
-        'ws'    'Delay waitForSeconds: 1.' 
-        'wfs'   'Delay waitForSeconds: 1.' 
-        'wfm'   'Delay waitForMilliseconds: 1000.' 
-        'ini'   'initialize\    super initialize.\    '
-        'newi'  'new\    ^ super new initialize.'
-        'upd'   'update:something with:aParameter from:changedObject\    !!\    ^ super update:something with:aParameter from:changedObject.'
-        'OC'    'OrderedCollection'
-        'oc'    'OrderedCollection'
-        'SC'    'SortedCollection'
-        'sc'    'SortedCollection'
-        'D'     'Dictionary'
-        'ID'    'IdentityDictionary'
-        'Id'    'IdentityDictionary'
-        'id'    'IdentityDictionary'
-        'iD'    'IdentityDictionary'
-        'OCn'   'OrderedCollection new.'
-        'ocn'   'OrderedCollection new.'
-        'SCn'   'SortedCollection new.'
-        'IDn'   'IdentityDictionary new'
-        'idn'   'IdentityDictionary new'
-        'Dn'    'Dictionary new'
-        'dn'    'Dictionary new'
-        'Sn'    'Set new'
-        'sn'    'Set new'
-        'A'     'Array'
-        'a'     'Array'
-        'An'    'Array new:'
-        'an'    'Array new:'
-        'Aw'    'Array with:'
-        'aw'    'Array with:'
-        'Aww'   'Array with:!! with:'
-        'sww'   'Array with:!! with:'
-        'Awww'  'Array with:!! with: with:'
-        'awww'  'Array with:!! with: with:'
-        'Awwww' 'Array with:!! with: with: with:'
-        'awwww' 'Array with:!! with: with: with:'
-        'aw2'   'Array with:!! with:'
-        'aw3'   'Array with:!! with: with:'
-        'aw4'   'Array with:!! with: with: with:'
-        '0'     '(0.0 @ 0.0)'
-        '1'     '(1.0 @ 1.0)'
-        '['     '[:!! ]'
-        '('     '(!! )'                                    
+	'st'    'Smalltalk'
+	'ts'    'Transcript showCR:''!!''.'
+	'trs'   'Transcript showCR:''!!''.'
+	'abb'   'Workspace sniplets inspect.'
+	'ws'    'Delay waitForSeconds: 1.'
+	'wfs'   'Delay waitForSeconds: 1.'
+	'wfm'   'Delay waitForMilliseconds: 1000.'
+	'ini'   'initialize\    super initialize.\    '
+	'newi'  'new\    ^ super new initialize.'
+	'upd'   'update:something with:aParameter from:changedObject\    !!\    ^ super update:something with:aParameter from:changedObject.'
+	'OC'    'OrderedCollection'
+	'oc'    'OrderedCollection'
+	'SC'    'SortedCollection'
+	'sc'    'SortedCollection'
+	'D'     'Dictionary'
+	'ID'    'IdentityDictionary'
+	'Id'    'IdentityDictionary'
+	'id'    'IdentityDictionary'
+	'iD'    'IdentityDictionary'
+	'OCn'   'OrderedCollection new.'
+	'ocn'   'OrderedCollection new.'
+	'SCn'   'SortedCollection new.'
+	'IDn'   'IdentityDictionary new'
+	'idn'   'IdentityDictionary new'
+	'Dn'    'Dictionary new'
+	'dn'    'Dictionary new'
+	'Sn'    'Set new'
+	'sn'    'Set new'
+	'A'     'Array'
+	'a'     'Array'
+	'An'    'Array new:'
+	'an'    'Array new:'
+	'Aw'    'Array with:'
+	'aw'    'Array with:'
+	'Aww'   'Array with:!! with:'
+	'sww'   'Array with:!! with:'
+	'Awww'  'Array with:!! with: with:'
+	'awww'  'Array with:!! with: with:'
+	'Awwww' 'Array with:!! with: with: with:'
+	'awwww' 'Array with:!! with: with: with:'
+	'aw2'   'Array with:!! with:'
+	'aw3'   'Array with:!! with: with:'
+	'aw4'   'Array with:!! with: with: with:'
+	'0'     '(0.0 @ 0.0)'
+	'1'     '(1.0 @ 1.0)'
+	'['     '[:!! ]'
+	'('     '(!! )'
 
-        "/ typos...
-        'eslf'  'self'
-        'slef'  'self'
-        'sefl'  'self'
-        'elf'   'self'
-        'slf'   'self'
-        'sef'   'self'
+	"/ typos...
+	'eslf'  'self'
+	'slef'  'self'
+	'sefl'  'self'
+	'elf'   'self'
+	'slf'   'self'
+	'sef'   'self'
 
-        'iftrue'   'ifTrue'
-        'iffalse'  'ifFalse'
-        'iftrue:'  'ifTrue:'
-        'iffalse:' 'ifFalse:'
+	'iftrue'   'ifTrue'
+	'iffalse'  'ifFalse'
+	'iftrue:'  'ifTrue:'
+	'iffalse:' 'ifFalse:'
     ) pairWiseDo:[:abbrev :text |
-        Sniplets
-            at:abbrev put:text "/ ifPresent:[ self error:'duplicate abbreviation key' ]
+	Sniplets
+	    at:abbrev put:text "/ ifPresent:[ self error:'duplicate abbreviation key' ]
     ].
 
     "Modified: / 26-09-2012 / 14:48:42 / cg"
@@ -303,8 +303,8 @@
     "extract values from the styleSheet and cache them in class variables"
 
     <resource: #style (#'codeErrorSelection.foregroundColor'
-                       #'codeErrorSelection.backgroundColor'
-                       #'codeView.backgroundColor' )>
+		       #'codeErrorSelection.backgroundColor'
+		       #'codeView.backgroundColor' )>
 
     DefaultErrorForegroundColor := StyleSheet colorAt:'codeErrorSelection.foregroundColor'.
     DefaultErrorBackgroundColor := StyleSheet colorAt:'codeErrorSelection.backgroundColor'.
@@ -318,9 +318,9 @@
 
     |scr topView workspace f|
 
-    topView := StandardSystemView 
-                label:(self classResources string:(self defaultLabel)) 
-                " minExtent:(100 @ 100)".
+    topView := StandardSystemView
+		label:(self classResources string:(self defaultLabel))
+		" minExtent:(100 @ 100)".
 
     scr := HVScrollableView for:self in:topView.
     scr origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).
@@ -349,27 +349,27 @@
     |server remoteCompiler workspace|
 
     RemoteObjectServer isNil ifTrue:[
-        self warn:'no remoteObjectServer available'.
-        ^ nil
+	self warn:'no remoteObjectServer available'.
+	^ nil
     ].
 
     server := RemoteObjectServer on:hostName.
     remoteCompiler := server get:#Compiler.
 
     workspace := self open.
-    workspace topView 
-        label:(self classResources string:'Remote Workspace {%1}' with:hostName).
+    workspace topView
+	label:(self classResources string:'Remote Workspace {%1}' with:hostName).
 
     workspace doItAction:
-                [:theCode |
-                    remoteCompiler 
-                        evaluate:theCode 
-                        in:nil 
-                        receiver:nil 
-                        notifying:workspace 
-                        logged:true 
-                        ifFail:nil 
-                ]
+		[:theCode |
+		    remoteCompiler
+			evaluate:theCode
+			in:nil
+			receiver:nil
+			notifying:workspace
+			logged:true
+			ifFail:nil
+		]
     "
      Workspace openForRemote:'andi'
     "
@@ -412,24 +412,24 @@
 
     string := aString asString string withoutSeparators.
     (string asCollectionOfWords size <= 1) ifTrue:[
-        Error handle:[:ex |
-            "/ unparsable
-            ^ self
-        ] do:[
-            ((Scanner new scanTokens:string) size <= 1) ifTrue:[
-                "it's a variable only"
-                ^ self
-            ]
-        ]
+	Error handle:[:ex |
+	    "/ unparsable
+	    ^ self
+	] do:[
+	    ((Scanner new scanTokens:string) size <= 1) ifTrue:[
+		"it's a variable only"
+		^ self
+	    ]
+	]
     ].
 
     DoItHistory isNil ifTrue:[
-        DoItHistory := OrderedCollection new.
+	DoItHistory := OrderedCollection new.
     ].
     DoItHistory remove:string ifAbsent:nil.
     DoItHistory addFirst:string.
     DoItHistory size > self doItHistorySize ifTrue:[
-        DoItHistory removeLast
+	DoItHistory removeLast
     ].
 ! !
 
@@ -474,8 +474,8 @@
     "delete a workspace variable"
 
     WorkspaceVariables notNil ifTrue:[
-        WorkspaceVariables removeKey:name ifAbsent:nil.
-        WorkspaceVariables := WorkspaceVariables asNilIfEmpty.
+	WorkspaceVariables removeKey:name ifAbsent:nil.
+	WorkspaceVariables := WorkspaceVariables asNilIfEmpty.
     ].
 !
 
@@ -486,7 +486,7 @@
 
     "
      Workspace workspaceVariableAt:'foo' put:1234.
-     Workspace workspaceVariableAt:'foo' 
+     Workspace workspaceVariableAt:'foo'
     "
 !
 
@@ -522,7 +522,7 @@
      That is a dictionary associating names to values."
 
     WorkspaceVariables isNil ifTrue:[
-        WorkspaceVariables := Dictionary new.
+	WorkspaceVariables := Dictionary new.
     ].
     ^ WorkspaceVariables
 
@@ -542,18 +542,18 @@
 
 autoDefineVariables
     "undefined variables handling:
-        are automatically defined as workspace variable if autoDefineVariables is #workspace.
-        are automatically defined as doit variable if autoDefineVariables is #doit.
-        are left undefined if autoDefineVariables is nil."
+	are automatically defined as workspace variable if autoDefineVariables is #workspace.
+	are automatically defined as doit variable if autoDefineVariables is #doit.
+	are left undefined if autoDefineVariables is nil."
 
-    ^ autoDefineVariables 
+    ^ autoDefineVariables
 !
 
 autoDefineVariables:nilOrSymbol
     "undefined variables handling:
-        are automatically defined as workspace variable if nilOrSymbol is #workspace.
-        are automatically defined as doit variable if nilOrSymbol is #doit.
-        are left undefined if nilOrSymbol is nil."
+	are automatically defined as workspace variable if nilOrSymbol is #workspace.
+	are automatically defined as doit variable if nilOrSymbol is #doit.
+	are left undefined if nilOrSymbol is nil."
 
     autoDefineVariables := nilOrSymbol.
 
@@ -568,7 +568,7 @@
     "/        '"/'
     "/        ('"' '"')
     "/    )
-    "/ where simple string elements define the EOL comment sequence, 
+    "/ where simple string elements define the EOL comment sequence,
     "/ and pairs define regular comment opening/closing seqeuences.
 
     commentStrings := anArrayOfCommentStrings
@@ -584,7 +584,7 @@
 
 doItAction:aOneArgBlock
     "define the action to be performed when 'doIt' is selected.
-     The block will be evaluated, passing the selection as a String argument. 
+     The block will be evaluated, passing the selection as a String argument.
      A default doItAction is set for you in the initialize method."
 
     doItAction := aOneArgBlock
@@ -601,13 +601,13 @@
 
 editedLanguage
     editedLanguage notNil ifTrue:[
-        ^ editedLanguage
+	^ editedLanguage
     ].
     editedMethod notNil ifTrue:[
-        ^ editedMethod programmingLanguage.
+	^ editedMethod programmingLanguage.
     ].
     editedClass notNil ifTrue:[
-        editedClass programmingLanguage.
+	editedClass programmingLanguage.
     ].
     ^ nil
 
@@ -617,7 +617,7 @@
 editedLanguage:aProgrammingLanguageOrNil
     editedLanguage := aProgrammingLanguageOrNil.
     aProgrammingLanguageOrNil notNil ifTrue:[
-        commentStrings := aProgrammingLanguageOrNil commentStrings.
+	commentStrings := aProgrammingLanguageOrNil commentStrings.
     ].
 !
 
@@ -752,77 +752,77 @@
     sameForAllHolder := false asValue.
 
     self highlightingErrorPosition:relPos to:relEndPos do:[
-        doNotShowAgainHolder := false asValue.
-        doNotShowAgainForThisMethodHolder := false asValue.
+	doNotShowAgainHolder := false asValue.
+	doNotShowAgainForThisMethodHolder := false asValue.
 
-        Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
-            |box declareButton makeSpaceOnlyOnce|
+	Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
+	    |box declareButton makeSpaceOnlyOnce|
 
-            box := ex box.
-            (box isKindOf:OptionBox) ifFalse:[ ex reject ].   "/ a bad hack for subDialogs... needs fix
-            makeSpaceOnlyOnce := [ box addVerticalSpace:10. makeSpaceOnlyOnce := nil ].
+	    box := ex box.
+	    (box isKindOf:OptionBox) ifFalse:[ ex reject ].   "/ a bad hack for subDialogs... needs fix
+	    makeSpaceOnlyOnce := [ box addVerticalSpace:10. makeSpaceOnlyOnce := nil ].
 
-            DoNotShowCompilerWarningAgainActionQuery isHandled ifTrue:[
-                makeSpaceOnlyOnce value.
-                box verticalPanel 
-                    add:(CheckBox 
-                            label: "addCheckBoxAtBottom:" 'Do not show this dialog again (reenable via Launcher''s settings dialog)' 
-                            model:doNotShowAgainHolder).
-            ].
-            DoNotShowCompilerWarningAgainForThisMethodActionQuery isHandled ifTrue:[
-                makeSpaceOnlyOnce value.
-                box verticalPanel
-                    add:(CheckBox
-                            label:(resources string:'Do not warn in this method (for %1 - reenable earlier via Launcher''s settings dialog)' with:ParserFlags perMethodDisableWarningTimeDuration)  
-                            model:doNotShowAgainForThisMethodHolder).
-            ].
-            SameForAllNotification isHandled ifTrue:[
-                box addVerticalSpace:10.
-                box addCheckBoxAtBottom:'Same action for all' on:sameForAllHolder
-            ].
+	    DoNotShowCompilerWarningAgainActionQuery isHandled ifTrue:[
+		makeSpaceOnlyOnce value.
+		box verticalPanel
+		    add:(CheckBox
+			    label: "addCheckBoxAtBottom:" 'Do not show this dialog again (reenable via Launcher''s settings dialog)'
+			    model:doNotShowAgainHolder).
+	    ].
+	    DoNotShowCompilerWarningAgainForThisMethodActionQuery isHandled ifTrue:[
+		makeSpaceOnlyOnce value.
+		box verticalPanel
+		    add:(CheckBox
+			    label:(resources string:'Do not warn in this method (for %1 - reenable earlier via Launcher''s settings dialog)' with:ParserFlags perMethodDisableWarningTimeDuration)
+			    model:doNotShowAgainForThisMethodHolder).
+	    ].
+	    SameForAllNotification isHandled ifTrue:[
+		box addVerticalSpace:10.
+		box addCheckBoxAtBottom:'Same action for all' on:sameForAllHolder
+	    ].
 
-            declareButton := box buttons at:2.
-            declareButton pressAction:declareButton controller releaseAction.
-            declareButton controller beTriggerOnDown.
-        ] do:[
-            |buttonLabels actions|
+	    declareButton := box buttons at:2.
+	    declareButton pressAction:declareButton controller releaseAction.
+	    declareButton controller beTriggerOnDown.
+	] do:[
+	    |buttonLabels actions|
 
-            buttonLabels := OrderedCollection new.
-            actions := OrderedCollection new.
-            buttonLabels add:'Cancel'. actions add:#abort.
-            possibleFixes do:[:each |
-                buttonLabels add:(each buttonLabel). actions add:each.
-            ].
-            buttonLabels add:'Continue'. actions add:#continue.
+	    buttonLabels := OrderedCollection new.
+	    actions := OrderedCollection new.
+	    buttonLabels add:'Cancel'. actions add:#abort.
+	    possibleFixes do:[:each |
+		buttonLabels add:(each buttonLabel). actions add:each.
+	    ].
+	    buttonLabels add:'Continue'. actions add:#continue.
 
-            action := OptionBox 
-                          request:aString
-                          label:(resources string:'Correctable Error')
-                          image:(WarningBox iconBitmap)
-                          buttonLabels:(resources array:buttonLabels)
-                          values:actions
-                          default:#continue
-                          onCancel:#abort.
-        ].
+	    action := OptionBox
+			  request:aString
+			  label:(resources string:'Correctable Error')
+			  image:(WarningBox iconBitmap)
+			  buttonLabels:(resources array:buttonLabels)
+			  values:actions
+			  default:#continue
+			  onCancel:#abort.
+	].
     ].
 
     sameForAllHolder value ifTrue:[
-        SameForAllNotification notify
+	SameForAllNotification notify
     ].
     doNotShowAgainHolder value == true ifTrue:[
-        DoNotShowCompilerWarningAgainActionQuery actionQuery value
+	DoNotShowCompilerWarningAgainActionQuery actionQuery value
     ].
     doNotShowAgainForThisMethodHolder value == true ifTrue:[
-        DoNotShowCompilerWarningAgainForThisMethodActionQuery actionQuery value
+	DoNotShowCompilerWarningAgainForThisMethodActionQuery actionQuery value
     ].
 
     action == #cancel ifTrue:[
-        ^ false
+	^ false
     ].
 
     action == #abort ifTrue:[
-        AbortOperationRequest raise.
-        ^ false
+	AbortOperationRequest raise.
+	^ false
     ].
     ^ action
 
@@ -838,35 +838,35 @@
     |action doNotShowAgainHolder|
 
     self highlightingWarningPosition:relPos to:relEndPos do:[
-        doNotShowAgainHolder := false asValue.
-        Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
-            MessageNotUnderstood catch:[
-                (aCompiler notNil and:[DoNotShowCompilerWarningAgainActionQuery isHandled]) ifTrue:[
-                    ex box addCheckBoxAtBottom:'Do not show this dialog again (reenable via Launchers Settings Dialog)' on:doNotShowAgainHolder.
-                ].
-            ].
-        ] do:[
-            action := OptionBox 
-                      request:aString
-                      label:(resources string:'Warning')
-                      image:(WarningBox iconBitmap)
-                      buttonLabels:(resources array:#('Cancel' 'Correct...' 'Generate' 'Continue'))
-                      values:#(#abort #correct #generate #continue)
-                      default:#continue
-                      onCancel:#abort.
-        ].
-        doNotShowAgainHolder value == true ifTrue:[
-            DoNotShowCompilerWarningAgainActionQuery actionQuery value
-        ].
+	doNotShowAgainHolder := false asValue.
+	Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
+	    MessageNotUnderstood catch:[
+		(aCompiler notNil and:[DoNotShowCompilerWarningAgainActionQuery isHandled]) ifTrue:[
+		    ex box addCheckBoxAtBottom:'Do not show this dialog again (reenable via Launchers Settings Dialog)' on:doNotShowAgainHolder.
+		].
+	    ].
+	] do:[
+	    action := OptionBox
+		      request:aString
+		      label:(resources string:'Warning')
+		      image:(WarningBox iconBitmap)
+		      buttonLabels:(resources array:#('Cancel' 'Correct...' 'Generate' 'Continue'))
+		      values:#(#abort #correct #generate #continue)
+		      default:#continue
+		      onCancel:#abort.
+	].
+	doNotShowAgainHolder value == true ifTrue:[
+	    DoNotShowCompilerWarningAgainActionQuery actionQuery value
+	].
     ].
 
     action == #generate ifTrue:[
-        ^ action
+	^ action
     ].
 
     (action isNil or:[action == #abort]) ifTrue:[
-        AbortOperationRequest raise.
-        ^ false
+	AbortOperationRequest raise.
+	^ false
     ].
     ^ action == #correct
 
@@ -892,7 +892,7 @@
 !
 
 error:aString position:relPos to:relEndPos from:aCompiler
-    "compiler notifies us of an error; hilight the error (relPos to relEndPos) 
+    "compiler notifies us of an error; hilight the error (relPos to relEndPos)
      and show a Box asking for continue/abort.
      Return true for correction, false of not (or not possible)"
 
@@ -911,59 +911,59 @@
     bg := asWarning ifTrue:[ self warningBackgroundColor ] ifFalse:[ self errorBackgroundColor ].
 
     self
-        highlightingErrorPosition:relPos to:relEndPos
-        withForeground:fg andBackground:bg
-        do:[
-            |box lbl doNotShowAgainHolder doNotShowAgainForThisMethodHolder l1 y1 y2 l2|
+	highlightingErrorPosition:relPos to:relEndPos
+	withForeground:fg andBackground:bg
+	do:[
+	    |box lbl doNotShowAgainHolder doNotShowAgainForThisMethodHolder l1 y1 y2 l2|
 
 "/            Warning isHandled ifTrue:[
 "/                Warning raiseErrorString:aString.
 "/                ^ false
 "/            ].
 
-            lbl := aCompiler isNil ifTrue:['Compiler'] ifFalse:[aCompiler class name].
-            asWarning ifTrue:[
-                lbl := lbl , ' Warning'
-            ] ifFalse:[
-                lbl := lbl , ' Error'.
-            ].
+	    lbl := aCompiler isNil ifTrue:['Compiler'] ifFalse:[aCompiler class name].
+	    asWarning ifTrue:[
+		lbl := lbl , ' Warning'
+	    ] ifFalse:[
+		lbl := lbl , ' Error'.
+	    ].
 
-            "
-             ask if we should abort or continue
-            "
-            Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
-                |box makeSpace|
+	    "
+	     ask if we should abort or continue
+	    "
+	    Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
+		|box makeSpace|
 
-                doNotShowAgainHolder := false asValue.
-                doNotShowAgainForThisMethodHolder := false asValue.
+		doNotShowAgainHolder := false asValue.
+		doNotShowAgainForThisMethodHolder := false asValue.
 
-                box := ex box.
-                box label:lbl.
-                box perform:#image: with:(WarningBox iconBitmap) ifNotUnderstood:[].
+		box := ex box.
+		box label:lbl.
+		box perform:#image: with:(WarningBox iconBitmap) ifNotUnderstood:[].
 
-                aCompiler notNil ifTrue:[
-                    makeSpace := [ box addVerticalSpace:10. makeSpace := nil ].
-                    DoNotShowCompilerWarningAgainActionQuery isHandled ifTrue:[
-                        makeSpace value.
-                        box verticalPanel
-                            add:(CheckBox label:'Do not show this dialog again (reenable via Launcher''s settings dialog)' 
-                                          model:doNotShowAgainHolder).
-                    ].
-                    DoNotShowCompilerWarningAgainForThisMethodActionQuery isHandled ifTrue:[
-                        makeSpace value.
-                        box verticalPanel
-                            add:(CheckBox label:(resources string:'Do not warn in this method (for %1 - reenable earlier via Launcher''s settings dialog)' with:ParserFlags perMethodDisableWarningTimeDuration) 
-                                          model:doNotShowAgainForThisMethodHolder).
-                    ].
-                ].
-            ] do:[
-                answer := OptionBox
-                        request:aString 
-                        buttonLabels:(resources array:#('Abort'  "'Keep Selected'" 'Continue')) 
-                        values:#(false "#keepSelected" true)
-                        default:(asWarning ifTrue:true ifFalse:false).
-                answer := answer ? false.   "/ if escaped
-            ].
+		aCompiler notNil ifTrue:[
+		    makeSpace := [ box addVerticalSpace:10. makeSpace := nil ].
+		    DoNotShowCompilerWarningAgainActionQuery isHandled ifTrue:[
+			makeSpace value.
+			box verticalPanel
+			    add:(CheckBox label:'Do not show this dialog again (reenable via Launcher''s settings dialog)'
+					  model:doNotShowAgainHolder).
+		    ].
+		    DoNotShowCompilerWarningAgainForThisMethodActionQuery isHandled ifTrue:[
+			makeSpace value.
+			box verticalPanel
+			    add:(CheckBox label:(resources string:'Do not warn in this method (for %1 - reenable earlier via Launcher''s settings dialog)' with:ParserFlags perMethodDisableWarningTimeDuration)
+					  model:doNotShowAgainForThisMethodHolder).
+		    ].
+		].
+	    ] do:[
+		answer := OptionBox
+			request:aString
+			buttonLabels:(resources array:#('Abort'  "'Keep Selected'" 'Continue'))
+			values:#(false "#keepSelected" true)
+			default:(asWarning ifTrue:true ifFalse:false).
+		answer := answer ? false.   "/ if escaped
+	    ].
 "/            box := YesNoBox
 "/                    title:aString
 "/                    yesText:(resources string:'Continue')
@@ -980,30 +980,30 @@
 "/            "/ answer := box confirm.
 "/            answer := box confirm.
 
-            doNotShowAgainHolder value == true ifTrue:[
-                DoNotShowCompilerWarningAgainActionQuery actionQuery value
-            ].
-            doNotShowAgainForThisMethodHolder value == true ifTrue:[
-                DoNotShowCompilerWarningAgainForThisMethodActionQuery actionQuery value
-            ].
+	    doNotShowAgainHolder value == true ifTrue:[
+		DoNotShowCompilerWarningAgainActionQuery actionQuery value
+	    ].
+	    doNotShowAgainForThisMethodHolder value == true ifTrue:[
+		DoNotShowCompilerWarningAgainForThisMethodActionQuery actionQuery value
+	    ].
 
 "/            box destroy.
-        ].
+	].
 
     answer == #keepSelected ifTrue:[
-        self hideCursor.
-        "redraw selection in normal color"
-        self invalidate.
-        AbortOperationRequest raise.
+	self hideCursor.
+	"redraw selection in normal color"
+	self invalidate.
+	AbortOperationRequest raise.
     ].
 
     "
      do the abort if we have to
     "
     answer ifFalse:[
-        "redraw selection in normal color"
-        self invalidate.
-        AbortOperationRequest raise.
+	"redraw selection in normal color"
+	self invalidate.
+	AbortOperationRequest raise.
     ].
     ^ false
 
@@ -1023,10 +1023,10 @@
 highlightingErrorPosition:relPos to:relEndPos do:aBlock
     "evaluate aBlock while some selection is shown highlighted with error colors."
 
-    self 
-        highlightingErrorPosition:relPos to:relEndPos 
-        withForeground:(self errorForegroundColor) andBackground:(self errorBackgroundColor) 
-        do:aBlock
+    self
+	highlightingErrorPosition:relPos to:relEndPos
+	withForeground:(self errorForegroundColor) andBackground:(self errorBackgroundColor)
+	do:aBlock
 !
 
 highlightingErrorPosition:relPos to:relEndPos withForeground:hilightFg andBackground:hilightBg do:aBlock
@@ -1051,10 +1051,10 @@
     codeStartPosition isNil ifTrue:[codeStartPosition := 1].
     absPosition := codeStartPosition + (relPos ? 1) - 1.
     relEndPos isNil ifTrue:[
-        self selectFromCharacterPosition:absPosition.
-        "/ self selectLineWhereCharacterPosition:absPosition.
+	self selectFromCharacterPosition:absPosition.
+	"/ self selectLineWhereCharacterPosition:absPosition.
     ] ifFalse:[
-        self selectFromCharacterPosition:absPosition to:(codeStartPosition + (relEndPos ? 1) - 1)
+	self selectFromCharacterPosition:absPosition to:(codeStartPosition + (relEndPos ? 1) - 1)
     ].
     expandingTop := true.       "/ hack to make the top of the selection visible
     self makeSelectionVisible.
@@ -1062,12 +1062,12 @@
     self flush.
 
     aBlock ensure:[
-        "
-         undo selection color change and show cursor again
-        "
-        selectionFgColor := oldFg.
-        selectionBgColor := oldBg.
-        self showCursor.
+	"
+	 undo selection color change and show cursor again
+	"
+	selectionFgColor := oldFg.
+	selectionBgColor := oldBg.
+	self showCursor.
     ].
 
     "Modified: / 30-06-2011 / 17:24:04 / cg"
@@ -1076,10 +1076,10 @@
 highlightingWarningPosition:relPos to:relEndPos do:aBlock
     "evaluate aBlock while some selection is shown highlighted with warning colors."
 
-    self 
-        highlightingErrorPosition:relPos to:relEndPos 
-        withForeground:(self warningForegroundColor) andBackground:(self warningBackgroundColor) 
-        do:aBlock
+    self
+	highlightingErrorPosition:relPos to:relEndPos
+	withForeground:(self warningForegroundColor) andBackground:(self warningBackgroundColor)
+	do:aBlock
 !
 
 unusedVariableWarning:aString position:relPos to:relEndPos from:aCompiler
@@ -1091,61 +1091,61 @@
     |action doNotShowAgainHolder doNotShowAgainForThisMethodHolder|
 
     self highlightingWarningPosition:relPos to:relEndPos do:[
-        doNotShowAgainHolder := false asValue.
-        doNotShowAgainForThisMethodHolder := false asValue.
-        Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
-            |box makeSpace|
+	doNotShowAgainHolder := false asValue.
+	doNotShowAgainForThisMethodHolder := false asValue.
+	Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
+	    |box makeSpace|
 
-            box := ex box.
-            aCompiler notNil ifTrue:[
-                makeSpace := [ box addVerticalSpace:10. makeSpace := nil ].
-                DoNotShowCompilerWarningAgainActionQuery isHandled ifTrue:[
-                    makeSpace value.
-                    box verticalPanel 
-                        add:(CheckBox 
-                                label: "addCheckBoxAtBottom:" 'Do not show this dialog again (reenable via Launcher''s settings dialog)' 
-                                model:doNotShowAgainHolder).
-                ].
-                DoNotShowCompilerWarningAgainForThisMethodActionQuery isHandled ifTrue:[
-                    makeSpace value.
-                    box verticalPanel
-                        add:(CheckBox
-                                label:(resources string:'Do not warn in this method (for %1 - reenable earlier via Launcher''s settings dialog)' with:ParserFlags perMethodDisableWarningTimeDuration)  
-                                model:doNotShowAgainForThisMethodHolder).
-                ].
-            ].
-        ] do:[
-            action := OptionBox 
-                      request:aString
-                      label:(resources string:'Warning')
-                      image:(WarningBox iconBitmap)
-                      buttonLabels:(resources array:#('Cancel' 'Remove Variable(s)' 'Continue'))
-                      values:#(#abort #correct #continue)
-                      default:#continue.
-            action isNil ifTrue:[ action := #abort].
-        ].
-        doNotShowAgainHolder value == true ifTrue:[
-            DoNotShowCompilerWarningAgainActionQuery actionQuery value
-        ].
-        doNotShowAgainForThisMethodHolder value == true ifTrue:[
-            DoNotShowCompilerWarningAgainForThisMethodActionQuery actionQuery value
-        ].
+	    box := ex box.
+	    aCompiler notNil ifTrue:[
+		makeSpace := [ box addVerticalSpace:10. makeSpace := nil ].
+		DoNotShowCompilerWarningAgainActionQuery isHandled ifTrue:[
+		    makeSpace value.
+		    box verticalPanel
+			add:(CheckBox
+				label: "addCheckBoxAtBottom:" 'Do not show this dialog again (reenable via Launcher''s settings dialog)'
+				model:doNotShowAgainHolder).
+		].
+		DoNotShowCompilerWarningAgainForThisMethodActionQuery isHandled ifTrue:[
+		    makeSpace value.
+		    box verticalPanel
+			add:(CheckBox
+				label:(resources string:'Do not warn in this method (for %1 - reenable earlier via Launcher''s settings dialog)' with:ParserFlags perMethodDisableWarningTimeDuration)
+				model:doNotShowAgainForThisMethodHolder).
+		].
+	    ].
+	] do:[
+	    action := OptionBox
+		      request:aString
+		      label:(resources string:'Warning')
+		      image:(WarningBox iconBitmap)
+		      buttonLabels:(resources array:#('Cancel' 'Remove Variable(s)' 'Continue'))
+		      values:#(#abort #correct #continue)
+		      default:#continue.
+	    action isNil ifTrue:[ action := #abort].
+	].
+	doNotShowAgainHolder value == true ifTrue:[
+	    DoNotShowCompilerWarningAgainActionQuery actionQuery value
+	].
+	doNotShowAgainForThisMethodHolder value == true ifTrue:[
+	    DoNotShowCompilerWarningAgainForThisMethodActionQuery actionQuery value
+	].
     ].
 
     action == #abort ifTrue:[
-        "/ self halt.
-        AbortOperationRequest raise.
-        ^ false
+	"/ self halt.
+	AbortOperationRequest raise.
+	^ false
     ].
     ^ action == #correct
 
     "Modified: / 08-03-2012 / 10:23:58 / cg"
 !
 
-warning:aString position:relPos to:relEndPos from:aCompiler 
+warning:aString position:relPos to:relEndPos from:aCompiler
     "compiler notifies us of a warning - same behavior as error"
 
-    self error:aString position:relPos to:relEndPos from:aCompiler asWarning:true 
+    self error:aString position:relPos to:relEndPos from:aCompiler asWarning:true
 ! !
 
 !Workspace methodsFor:'drag & drop'!
@@ -1159,7 +1159,7 @@
     allowValueDrop ifTrue:[^ true].
     ^ super canDrop:aDropContext
 
-"/    ^ aDropContext dropObjects 
+"/    ^ aDropContext dropObjects
 "/        contains:[:someObject| (someObject isTextObject or:[ someObject isFileObject ])].
 
     "Created: / 16-08-2005 / 22:01:13 / janfrog"
@@ -1180,59 +1180,59 @@
 
     |textObjects nonTextObjects answer text|
 
-    textObjects := aDropContext dropObjects 
-                            select:[:dropObject | dropObject isTextObject 
-                                                  or:[ dropObject isFileObject ]].
-    nonTextObjects := aDropContext dropObjects 
-                            reject:[:dropObject | dropObject isTextObject 
-                                                  or:[ dropObject isFileObject ]].
+    textObjects := aDropContext dropObjects
+			    select:[:dropObject | dropObject isTextObject
+						  or:[ dropObject isFileObject ]].
+    nonTextObjects := aDropContext dropObjects
+			    reject:[:dropObject | dropObject isTextObject
+						  or:[ dropObject isFileObject ]].
 
     self dropObjects:textObjects.
 
     nonTextObjects notEmpty ifTrue:[
-        answer := Dialog
-                confirmWithCancel:(resources 
-                                        string:'Drop as textual representation or as object reference ?')
-                labels:(resources array:#('Cancel' 'Reference' 'Name' 'Text'))
-                values:#(nil #ref #name #text)
-                default:4.
-        answer isNil ifTrue:[^ self].
-        (answer == #text or:[answer == #name]) ifTrue:[
-            text := String streamContents:[:s |
-                        nonTextObjects do:[:dropObject |
-                            |obj|
+	answer := Dialog
+		confirmWithCancel:(resources
+					string:'Drop as textual representation or as object reference ?')
+		labels:(resources array:#('Cancel' 'Reference' 'Name' 'Text'))
+		values:#(nil #ref #name #text)
+		default:4.
+	answer isNil ifTrue:[^ self].
+	(answer == #text or:[answer == #name]) ifTrue:[
+	    text := String streamContents:[:s |
+			nonTextObjects do:[:dropObject |
+			    |obj|
 
-                            obj := dropObject theObject.
-                            obj isMethod ifTrue:[
-                                s nextPutAll:(answer == #name ifTrue:[obj selector] ifFalse:[obj source]).
-                            ] ifFalse:[
-                                obj isClass ifTrue:[
-                                    s nextPutAll:(answer == #name ifTrue:[obj name] ifFalse:[obj source asString])
-                                ] ifFalse:[
-                                    s nextPutAll:(answer == #name ifTrue:[obj className] ifFalse:[obj printString]) .
-                                ].
-                            ].
-                        ].
-                    ].
-            self paste:text.
-        ] ifFalse:[
-            nonTextObjects do:[:dropObject |
-                name := Dialog 
-                        request:(resources 
-                                    string:'Name of the new Workspace Variable (refers to the dropped %1):'
-                                    with:dropObject theObject class name allBold
-                                 )
-                        initialAnswer:'droppedObject'
-                        okLabel:'Add'
-                        title:'Enter Variable Name'.
+			    obj := dropObject theObject.
+			    obj isMethod ifTrue:[
+				s nextPutAll:(answer == #name ifTrue:[obj selector] ifFalse:[obj source]).
+			    ] ifFalse:[
+				obj isClass ifTrue:[
+				    s nextPutAll:(answer == #name ifTrue:[obj name] ifFalse:[obj source asString])
+				] ifFalse:[
+				    s nextPutAll:(answer == #name ifTrue:[obj className] ifFalse:[obj printString]) .
+				].
+			    ].
+			].
+		    ].
+	    self paste:text.
+	] ifFalse:[
+	    nonTextObjects do:[:dropObject |
+		name := Dialog
+			request:(resources
+				    string:'Name of the new Workspace Variable (refers to the dropped %1):'
+				    with:dropObject theObject class name allBold
+				 )
+			initialAnswer:'droppedObject'
+			okLabel:'Add'
+			title:'Enter Variable Name'.
 
-                name notEmptyOrNil ifTrue:[
-                    Workspace addWorkspaceVariable:name.
-                    Workspace workspaceVariableAt:name put:dropObject theObject.
-                    self paste:name.
-                ].
-            ].
-        ]
+		name notEmptyOrNil ifTrue:[
+		    Workspace addWorkspaceVariable:name.
+		    Workspace workspaceVariableAt:name put:dropObject theObject.
+		    self paste:name.
+		].
+	    ].
+	]
     ].
 
     "Created: / 13-10-2006 / 17:34:07 / cg"
@@ -1243,32 +1243,32 @@
 commentFrom:line1 to:line2
     "convenient function to comment out a block.
      All lines from line1 to line2 get an end-of-line comment
-     in the first col 
+     in the first col
      (if no eol comment is available, a bracketing comment is used)."
 
     |eolComment opening closing|
 
     eolComment := commentStrings at:1.
     eolComment isNil ifTrue:[
-        opening := (commentStrings at:2) at:1.
-        closing := (commentStrings at:2) at:2.
-        (opening isNil or:[closing isNil]) ifTrue:[^ self].
+	opening := (commentStrings at:2) at:1.
+	closing := (commentStrings at:2) at:2.
+	(opening isNil or:[closing isNil]) ifTrue:[^ self].
     ].
 
     line1 to:line2 do:[:lineNr |
-        |l|
+	|l|
 
-        l := self listAt:lineNr.
-        l isNil ifTrue:[l := ''].
-        eolComment notNil ifTrue:[
-            l := eolComment , l
-        ] ifFalse:[
-            l := opening , l , closing
-        ].
-        self replaceLine:lineNr with:l.
-        widthOfWidestLine notNil ifTrue:[
-            widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:l).
-        ].
+	l := self listAt:lineNr.
+	l isNil ifTrue:[l := ''].
+	eolComment notNil ifTrue:[
+	    l := eolComment , l
+	] ifFalse:[
+	    l := opening , l , closing
+	].
+	self replaceLine:lineNr with:l.
+	widthOfWidestLine notNil ifTrue:[
+	    widthOfWidestLine := widthOfWidestLine max:(self widthOfLineString:l).
+	].
     ].
     self textChanged.
 
@@ -1286,39 +1286,39 @@
     (self checkModificationsAllowed) ifFalse:[ ^ self].
     commentStrings isNil ifTrue:[ self beep. ^ self].
 
-    selectionStartLine isNil ifTrue:[ 
-        self 
-            undoableDo:[ self commentFrom:cursorLine to:cursorLine ]
-            info:'Comment'.
-        ^ self
+    selectionStartLine isNil ifTrue:[
+	self
+	    undoableDo:[ self commentFrom:cursorLine to:cursorLine ]
+	    info:'Comment'.
+	^ self
     ].
 
-    self 
-        undoableDo:
-            [
-                (selectionStartCol == 1 and:[selectionEndCol == 0]) ifTrue:[
-                    self commentFrom:selectionStartLine to:selectionEndLine-1
-                ] ifFalse:[
-                    commentPair := commentStrings at:2 ifAbsent:nil.
-                    commentPair isNil ifTrue:[
-                        self beep.
-                    ] ifFalse:[
-                        opening := commentPair at:1.
-                        closing := commentPair at:2.
-                        (opening isNil or:[closing isNil]) ifTrue:[^ self].
+    self
+	undoableDo:
+	    [
+		(selectionStartCol == 1 and:[selectionEndCol == 0]) ifTrue:[
+		    self commentFrom:selectionStartLine to:selectionEndLine-1
+		] ifFalse:[
+		    commentPair := commentStrings at:2 ifAbsent:nil.
+		    commentPair isNil ifTrue:[
+			self beep.
+		    ] ifFalse:[
+			opening := commentPair at:1.
+			closing := commentPair at:2.
+			(opening isNil or:[closing isNil]) ifTrue:[^ self].
 
-                        e := selectionEndCol.
+			e := selectionEndCol.
 
-                        self insertString:closing atLine:selectionEndLine col:e+1.
-                        self insertString:opening atLine:selectionStartLine col:selectionStartCol.
+			self insertString:closing atLine:selectionEndLine col:e+1.
+			self insertString:opening atLine:selectionStartLine col:selectionStartCol.
 
-                        selectionStartLine == selectionEndLine ifTrue:[e := e + opening size].
-                        self selectFromLine:selectionStartLine col:selectionStartCol
-                                     toLine:selectionEndLine col:e+closing size.
-                    ]
-                ]
-            ]
-        info:'comment'
+			selectionStartLine == selectionEndLine ifTrue:[e := e + opening size].
+			self selectFromLine:selectionStartLine col:selectionStartCol
+				     toLine:selectionEndLine col:e+closing size.
+		    ]
+		]
+	    ]
+	info:'comment'
 
     "Created: / 9.11.1997 / 01:05:40 / cg"
     "Modified: / 5.4.1998 / 16:52:23 / cg"
@@ -1334,31 +1334,31 @@
 
     eolComment := commentStrings at:1.
     eolComment isNil ifTrue:[
-        opening := (commentStrings at:2) at:1.
-        closing := (commentStrings at:2) at:2.
-        (opening isNil or:[closing isNil]) ifTrue:[^ self].
+	opening := (commentStrings at:2) at:1.
+	closing := (commentStrings at:2) at:2.
+	(opening isNil or:[closing isNil]) ifTrue:[^ self].
     ] ifFalse:[
-        rest := eolComment size + 1.
+	rest := eolComment size + 1.
     ].
 
     line1 to:line2 do:[:lineNr |
-        |l|
+	|l|
 
-        l := self listAt:lineNr.
-        l notNil ifTrue:[
-            eolComment notNil ifTrue:[
-                (l startsWith:eolComment) ifTrue:[
-                    l := l copyFrom:rest
-                ]
-            ] ifFalse:[
-                ((l startsWith:opening)
-                and:[l endsWith:closing]) ifTrue:[
-                    l := l copyFrom:opening size + 1.
-                    l := l copyButLast:closing size.
-                ]
-            ].
-            self replaceLine:lineNr with:l.
-        ]
+	l := self listAt:lineNr.
+	l notNil ifTrue:[
+	    eolComment notNil ifTrue:[
+		(l startsWith:eolComment) ifTrue:[
+		    l := l copyFrom:rest
+		]
+	    ] ifFalse:[
+		((l startsWith:opening)
+		and:[l endsWith:closing]) ifTrue:[
+		    l := l copyFrom:opening size + 1.
+		    l := l copyButLast:closing size.
+		]
+	    ].
+	    self replaceLine:lineNr with:l.
+	]
     ].
     widthOfWidestLine := nil.
     self textChanged.
@@ -1375,50 +1375,50 @@
     |e commentPair opening closing sz1 sz2 l1 l2 c1 c2|
 
     (self checkModificationsAllowed) ifFalse:[ ^ self].
-    selectionStartLine isNil ifTrue:[ 
-        self 
-            undoableDo:[
-                self uncommentFrom:cursorLine to:cursorLine
-            ]
-            info:'Uncomment'.
-        ^ self
+    selectionStartLine isNil ifTrue:[
+	self
+	    undoableDo:[
+		self uncommentFrom:cursorLine to:cursorLine
+	    ]
+	    info:'Uncomment'.
+	^ self
     ].
 
-    self 
-        undoableDo:
-            [
-                (selectionStartCol == 1 and:[selectionEndCol == 0]) ifTrue:[
-                    self uncommentFrom:selectionStartLine to:selectionEndLine-1
-                ] ifFalse:[
-                    commentPair := commentStrings at:2.
-                    opening := commentPair at:1.
-                    closing := commentPair at:2.
-                    (opening isNil or:[closing isNil]) ifTrue:[^ self].
+    self
+	undoableDo:
+	    [
+		(selectionStartCol == 1 and:[selectionEndCol == 0]) ifTrue:[
+		    self uncommentFrom:selectionStartLine to:selectionEndLine-1
+		] ifFalse:[
+		    commentPair := commentStrings at:2.
+		    opening := commentPair at:1.
+		    closing := commentPair at:2.
+		    (opening isNil or:[closing isNil]) ifTrue:[^ self].
 
-                    sz1 := opening size.
-                    sz2 := closing size.
+		    sz1 := opening size.
+		    sz2 := closing size.
 
-                    ((self 
-                        stringAtLine:selectionStartLine 
-                        from:selectionStartCol
-                        to:selectionStartCol+sz1 - 1) = opening
-                    and:[(self 
-                        stringAtLine:selectionEndLine 
-                        from:selectionEndCol - sz2 + 1
-                        to:selectionEndCol) = closing ]) ifTrue:[
+		    ((self
+			stringAtLine:selectionStartLine
+			from:selectionStartCol
+			to:selectionStartCol+sz1 - 1) = opening
+		    and:[(self
+			stringAtLine:selectionEndLine
+			from:selectionEndCol - sz2 + 1
+			to:selectionEndCol) = closing ]) ifTrue:[
 
-                        l2 := selectionEndLine.   c2 := selectionEndCol.
-                        l1 := selectionStartLine. c1 := selectionStartCol.
-                        self deleteCharsAtLine:l2 fromCol:c2-sz2+1 toCol:c2.
-                        self deleteCharsAtLine:l1 fromCol:c1 toCol:c1+sz1-1.
+			l2 := selectionEndLine.   c2 := selectionEndCol.
+			l1 := selectionStartLine. c1 := selectionStartCol.
+			self deleteCharsAtLine:l2 fromCol:c2-sz2+1 toCol:c2.
+			self deleteCharsAtLine:l1 fromCol:c1 toCol:c1+sz1-1.
 
-                        e := c2 - sz2.
-                        l1 == l2 ifTrue:[e := e - sz1].
-                        self selectFromLine:l1 col:c1 toLine:l2 col:e.
-                    ]
-                ]
-            ]
-        info:'uncomment'
+			e := c2 - sz2.
+			l1 == l2 ifTrue:[e := e - sz1].
+			self selectFromLine:l1 col:c1 toLine:l2 col:e.
+		    ]
+		]
+	    ]
+	info:'uncomment'
 
     "Modified: / 7.1.1997 / 20:13:32 / cg"
     "Created: / 9.11.1997 / 01:05:46 / cg"
@@ -1427,9 +1427,9 @@
 !Workspace methodsFor:'event handling'!
 
 keyPress:key x:x y:y
-    <resource: #keyboard (#DoIt #InspectIt #PrintIt #ReplaceIt 
-                          #BrowseIt #ImplementorsOfIt #ExpandAbbreviation
-                          #CommentSelection #UncommentSelection)>
+    <resource: #keyboard (#DoIt #InspectIt #PrintIt #ReplaceIt
+			  #BrowseIt #ImplementorsOfIt #ExpandAbbreviation
+			  #CommentSelection #UncommentSelection)>
 
     (key == #DoIt)      ifTrue:[self doIt. ^ self].
     (key == #InspectIt) ifTrue:[self inspectIt. ^ self].
@@ -1449,8 +1449,8 @@
 !Workspace methodsFor:'executing'!
 
 do:code withValueDo:aBlock
-    "helper for doIt, printIt and inspectIt. 
-     Evaluate the selection and, if all went well, evaluate the argument, 
+    "helper for doIt, printIt and inspectIt.
+     Evaluate the selection and, if all went well, evaluate the argument,
      aBlock with the value.
      Most work is in preparing for proper cleanup in case of abort
      or other exception while the evaluation is performed.
@@ -1459,69 +1459,69 @@
     |selLine selCol endLine endCol cLine cCol cleanUp executeBlock|
 
     code notNil ifTrue:[
-        code asString withoutSeparators isEmpty ifTrue:[ ^ self ].
+	code asString withoutSeparators isEmpty ifTrue:[ ^ self ].
 
-        codeStartPosition := self characterPositionOfSelection.
+	codeStartPosition := self characterPositionOfSelection.
 
-        "
-         remember selection for later - if there is an error,
-         the notification method will highlight it.
-         thus destroying the current selection
-        "
-        selLine := selectionStartLine.
-        selCol := selectionStartCol.
-        endLine := selectionEndLine.
-        endCol := selectionEndCol.
-        cCol := cursorCol.
-        cLine := cursorLine.
+	"
+	 remember selection for later - if there is an error,
+	 the notification method will highlight it.
+	 thus destroying the current selection
+	"
+	selLine := selectionStartLine.
+	selCol := selectionStartCol.
+	endLine := selectionEndLine.
+	endCol := selectionEndCol.
+	cCol := cursorCol.
+	cLine := cursorLine.
 
-        "
-         cleanup: restore previous selection and cursor positions
-        "
-        cleanUp := [
-                self selectFromLine:selLine col:selCol toLine:endLine col:endCol.
-                cLine notNil ifTrue:[
-                    self cursorLine:cLine col:cCol
-                ].
-        ].
+	"
+	 cleanup: restore previous selection and cursor positions
+	"
+	cleanUp := [
+		self selectFromLine:selLine col:selCol toLine:endLine col:endCol.
+		cLine notNil ifTrue:[
+		    self cursorLine:cLine col:cCol
+		].
+	].
 
-        "
-         perform the action.
-         Be careful to release the reference to the value;
-         otherwise, we could keep lots of garbage from being freed
-         until the view gets closed
-        "
-        executeBlock := [
-                [
-                    AbortOperationRequest handle:[:ex |
-                         "/ aBlock value:'** Abortsignal cought **'.
-                         ex return
-                    ] do:[
-                        |value|
+	"
+	 perform the action.
+	 Be careful to release the reference to the value;
+	 otherwise, we could keep lots of garbage from being freed
+	 until the view gets closed
+	"
+	executeBlock := [
+		[
+		    AbortOperationRequest handle:[:ex |
+			 "/ aBlock value:'** Abortsignal caught **'.
+			 ex return
+		    ] do:[
+			|value|
 
-                        doItAction notNil ifTrue:[
-                            value := doItAction value:(code asString).
-                            cleanUp value. cleanUp := nil.
-                            aBlock notNil ifTrue:[
-                                aBlock value:value.
-                            ].
-                            value := nil.
-                            self class rememberDoIt:code.
-                        ]
-                    ]
-                ] ensure:[
-                    cleanUp notNil ifTrue:[
-                        cleanUp value. cleanUp := nil
-                    ].
-                ]
-            ].
-        aBlock isNil ifTrue:[
-            "no action is performed with the result - give the user a visible
-             feedback, that something has been done"
-            self topView withVisibleCursor:Cursor execute do:executeBlock.
-        ] ifFalse:[
-            self topView withCursor:Cursor execute do:executeBlock.
-        ].
+			doItAction notNil ifTrue:[
+			    value := doItAction value:(code asString).
+			    cleanUp value. cleanUp := nil.
+			    aBlock notNil ifTrue:[
+				aBlock value:value.
+			    ].
+			    value := nil.
+			    self class rememberDoIt:code.
+			]
+		    ]
+		] ensure:[
+		    cleanUp notNil ifTrue:[
+			cleanUp value. cleanUp := nil
+		    ].
+		]
+	    ].
+	aBlock isNil ifTrue:[
+	    "no action is performed with the result - give the user a visible
+	     feedback, that something has been done"
+	    self topView withVisibleCursor:Cursor execute do:executeBlock.
+	] ifFalse:[
+	    self topView withCursor:Cursor execute do:executeBlock.
+	].
     ]
 
     "Modified: / 22.4.1998 / 21:56:13 / ca"
@@ -1536,29 +1536,29 @@
 
     "JV@2012-03-19: Changed to reflect value of autoDefineVariables"
     [
-        result := ( compiler := (self compilerClass ? Compiler) new ) 
-                currentNameSpace:namespaceForDoits;
-                moreSharedPools:poolsConsideredInDoIts;
-                evaluate:theCode 
-                in:nil 
-                receiver:simulatedSelf 
-                notifying:self 
-                logged:true 
-                ifFail:nil
+	result := ( compiler := (self compilerClass ? Compiler) new )
+		currentNameSpace:namespaceForDoits;
+		moreSharedPools:poolsConsideredInDoIts;
+		evaluate:theCode
+		in:nil
+		receiver:simulatedSelf
+		notifying:self
+		logged:true
+		ifFail:nil
     ] on: Parser undefinedVariableNotification do:[:ex|
-        (ex parser == compiler and:[autoDefineVariables notNil]) ifTrue:[
-            ex proceedWith: #declare
-        ] ifFalse:[
-            ex proceedWith: nil
-        ].
+	(ex parser == compiler and:[autoDefineVariables notNil]) ifTrue:[
+	    ex proceedWith: #declare
+	] ifFalse:[
+	    ex proceedWith: nil
+	].
     ] on: Parser askForVariableTypeOfUndeclaredQuery do:[:ex|
-        autoDefineVariables == #workspace ifTrue:[
-            ex proceedWith:#WorkspaceVariable
-        ].
-        autoDefineVariables == #doIt ifTrue:[
-            ex proceedWith:#DoItTemporary
-        ].
-        ex pass.
+	autoDefineVariables == #workspace ifTrue:[
+	    ex proceedWith:#WorkspaceVariable
+	].
+	autoDefineVariables == #doIt ifTrue:[
+	    ex proceedWith:#DoItTemporary
+	].
+	ex pass.
     ].
     ^result
 
@@ -1574,8 +1574,8 @@
     super initStyle.
 
     DefaultViewBackground notNil ifTrue:[
-        viewBackground := DefaultViewBackground.
-        self backgroundColor:viewBackground.
+	viewBackground := DefaultViewBackground.
+	self backgroundColor:viewBackground.
     ].
 !
 
@@ -1588,9 +1588,9 @@
     allowValueDrop := true.
 
     commentStrings := #(
-                        '"/'
-                        ('"' '"')
-                       ).
+			'"/'
+			('"' '"')
+		       ).
 
     self initializeDoITAction.
     self initializeDragAndDrop.
@@ -1609,11 +1609,11 @@
 initializeDragAndDrop
     |target|
 
-    target := DropTarget 
-                    receiver:self
-                    argument:nil
-                    dropSelector:#drop:
-                    canDropSelector:#canDrop:.
+    target := DropTarget
+		    receiver:self
+		    argument:nil
+		    dropSelector:#drop:
+		    canDropSelector:#canDrop:.
     self dropTarget:target
 
     "Created: / 16-08-2005 / 22:03:36 / janfrog"
@@ -1626,15 +1626,15 @@
     "user selected 'browseClass' from menu; evaluate the code
      and open a browser on the resulting class (if it evaluates to one)"
 
-    ^ self 
-        do:(self selectionAsString) 
-        withValueDo:[:result | 
-            result isBehavior ifTrue:[
-                result browserClass openInClass:result selector:nil
-            ] ifFalse:[
-                self warn:'Selection does not evaluate to a class'
-            ]
-        ].
+    ^ self
+	do:(self selectionAsString)
+	withValueDo:[:result |
+	    result isBehavior ifTrue:[
+		result browserClass openInClass:result selector:nil
+	    ] ifFalse:[
+		self warn:'Selection does not evaluate to a class'
+	    ]
+	].
 
     "Modified: / 26.9.2001 / 17:37:35 / cg"
 !
@@ -1647,37 +1647,37 @@
 
     selectedText := self selectedTextOrSyntaxElement.
     selectedText notEmptyOrNil ifTrue:[
-        self windowGroup withWaitCursorDo:[
-            "/ hack, for now and expecco; must ask the Parser eventually...
-            (compilerClass notNil and:[compilerClass includesBehavior:JavaScriptParser]) ifTrue:[
-                "/ selector is in one piece anyway
-                (selectedText includes:$_) ifFalse:[
-                    "/ zero or one args - sigh (need to parse more to figure this out)
-                    selector := JavaScriptParser basicNew translatedSmalltalkSelectorFor:selectedText numArgs:1.
-                    selectedText := JavaScriptParser basicNew translatedSmalltalkSelectorFor:selectedText numArgs:0.
-                ] ifTrue:[
-                    "/ count _#s plus one arg - sigh
-                    na := (selectedText occurrencesOf:$_) + 1. 
-                    selector := JavaScriptParser basicNew translatedSmalltalkSelectorFor:selectedText numArgs:na
-                ].
-            ] ifFalse:[
-                selector := SystemBrowser extractSelectorFrom:selectedText.
-            ].
-            browserClass := UserPreferences systemBrowserClass.
+	self windowGroup withWaitCursorDo:[
+	    "/ hack, for now and expecco; must ask the Parser eventually...
+	    (compilerClass notNil and:[compilerClass includesBehavior:JavaScriptParser]) ifTrue:[
+		"/ selector is in one piece anyway
+		(selectedText includes:$_) ifFalse:[
+		    "/ zero or one args - sigh (need to parse more to figure this out)
+		    selector := JavaScriptParser basicNew translatedSmalltalkSelectorFor:selectedText numArgs:1.
+		    selectedText := JavaScriptParser basicNew translatedSmalltalkSelectorFor:selectedText numArgs:0.
+		] ifTrue:[
+		    "/ count _#s plus one arg - sigh
+		    na := (selectedText occurrencesOf:$_) + 1.
+		    selector := JavaScriptParser basicNew translatedSmalltalkSelectorFor:selectedText numArgs:na
+		].
+	    ] ifFalse:[
+		selector := SystemBrowser extractSelectorFrom:selectedText.
+	    ].
+	    browserClass := UserPreferences systemBrowserClass.
 
-            (selector notNil and:[selector ~= selectedText]) ifTrue:[
-                (SystemBrowser 
-                        findImplementorsOfAny:(Array with:selectedText) 
-                        in:(Smalltalk allClasses) 
-                        ignoreCase:false) isEmpty ifTrue:[
-                    browserClass browseImplementorsOf:selector
-                ] ifFalse:[
-                    browserClass browseImplementorsOfAny:(Set with:selector with:selectedText)
-                ].
-            ] ifFalse:[
-                browserClass browseImplementorsOf:(selector ? selectedText)
-            ]
-        ]
+	    (selector notNil and:[selector ~= selectedText]) ifTrue:[
+		(SystemBrowser
+			findImplementorsOfAny:(Array with:selectedText)
+			in:(Smalltalk allClasses)
+			ignoreCase:false) isEmpty ifTrue:[
+		    browserClass browseImplementorsOf:selector
+		] ifFalse:[
+		    browserClass browseImplementorsOfAny:(Set with:selector with:selectedText)
+		].
+	    ] ifFalse:[
+		browserClass browseImplementorsOf:(selector ? selectedText)
+	    ]
+	]
     ].
 
     "Created: / 5.11.2001 / 17:32:23 / cg"
@@ -1692,56 +1692,56 @@
 
     |codeToEvaluate el idx selector evaluatedValue classToBrowse gotResult|
 
-    (self selection isEmptyOrNil 
-        and:[ self supportsSyntaxElements 
-        and:[ (el := self syntaxElementForVariableUnderCursor) notNil ]])
-    ifTrue:[ 
-        codeToEvaluate := el name
+    (self selection isEmptyOrNil
+	and:[ self supportsSyntaxElements
+	and:[ (el := self syntaxElementForVariableUnderCursor) notNil ]])
+    ifTrue:[
+	codeToEvaluate := el name
     ] ifFalse:[
-        codeToEvaluate := (self selectionOrTextOfCursorLine ? '') withoutSeparators.
+	codeToEvaluate := (self selectionOrTextOfCursorLine ? '') withoutSeparators.
     ].
     idx := codeToEvaluate indexOfSubCollection:'>>'.
     idx ~~ 0 ifTrue:[
-        selector := (codeToEvaluate copyFrom:idx+2) withoutSeparators string.
-        (selector startsWith:'#') ifTrue:[
-            selector := Symbol readFrom:selector.
-        ].
-        codeToEvaluate := codeToEvaluate copyTo:idx-1.   
+	selector := (codeToEvaluate copyFrom:idx+2) withoutSeparators string.
+	(selector startsWith:'#') ifTrue:[
+	    selector := Symbol readFrom:selector.
+	].
+	codeToEvaluate := codeToEvaluate copyTo:idx-1.
     ].
 
     (Parser parseErrorSignal , MessageNotUnderstood) handle:[:ex |
-        |className|
+	|className|
 
-        (classToBrowse := Smalltalk classNamed:codeToEvaluate) isNil ifTrue:[
-            "/ fallback, if garbage is selected, look for matching classes.
-            className := SystemBrowser
-                askForClassNameMatching:codeToEvaluate 
-                inEnvironment:nil 
-                for:nil.
+	(classToBrowse := Smalltalk classNamed:codeToEvaluate) isNil ifTrue:[
+	    "/ fallback, if garbage is selected, look for matching classes.
+	    className := SystemBrowser
+		askForClassNameMatching:codeToEvaluate
+		inEnvironment:nil
+		for:nil.
 
-            className isNil ifTrue:[^ self].
-            classToBrowse := Smalltalk classNamed:className.
-        ]
+	    className isNil ifTrue:[^ self].
+	    classToBrowse := Smalltalk classNamed:className.
+	]
     ] do:[
-        gotResult := false.
+	gotResult := false.
 
-        self 
-            do:codeToEvaluate 
-            withValueDo:[:result | evaluatedValue := result. gotResult := true.].
+	self
+	    do:codeToEvaluate
+	    withValueDo:[:result | evaluatedValue := result. gotResult := true.].
 
-        gotResult ifFalse:[^ self].
+	gotResult ifFalse:[^ self].
 
-        evaluatedValue isNil ifTrue:[                       
-            codeToEvaluate asCollectionOfWords size == 1 ifTrue:[
-                codeToEvaluate isUppercaseFirst ifTrue:[
-                    Dialog information:(codeToEvaluate allBold , ' is unbound or nil').
-                    ^ self.
-                ].
-            ]
-        ].
-        classToBrowse := evaluatedValue isBehavior 
-                        ifTrue:[ evaluatedValue ] 
-                        ifFalse:[ evaluatedValue class ].
+	evaluatedValue isNil ifTrue:[
+	    codeToEvaluate asCollectionOfWords size == 1 ifTrue:[
+		codeToEvaluate isUppercaseFirst ifTrue:[
+		    Dialog information:(codeToEvaluate allBold , ' is unbound or nil').
+		    ^ self.
+		].
+	    ]
+	].
+	classToBrowse := evaluatedValue isBehavior
+			ifTrue:[ evaluatedValue ]
+			ifFalse:[ evaluatedValue class ].
     ].
 
     classToBrowse browserClass openInClass:classToBrowse selector:selector
@@ -1753,11 +1753,11 @@
     "user selected 'browseItsClass' from menu; evaluate the code
      and open a browser on the results class"
 
-    ^ self 
-        do:(self selectionAsString) 
-        withValueDo:[:result | 
-                        result class browserClass openInClass:result class selector:nil
-                    ]
+    ^ self
+	do:(self selectionAsString)
+	withValueDo:[:result |
+			result class browserClass openInClass:result class selector:nil
+		    ]
 
     "Modified: / 26.9.2001 / 17:38:06 / cg"
 !
@@ -1769,50 +1769,50 @@
 
     nameOfGlobal := self selectedTextOrSyntaxElement.
     nameOfGlobal notEmptyOrNil ifTrue:[
-        browserClass := UserPreferences systemBrowserClass.
-        self windowGroup withWaitCursorDo:[
-            |cls privateClass|
+	browserClass := UserPreferences systemBrowserClass.
+	self windowGroup withWaitCursorDo:[
+	    |cls privateClass|
 
-            "/ is it a class variable?
-            ((cls := self editedClass) notNil
-            and:[ (cls theNonMetaclass allClassVarNames includes:nameOfGlobal) ]) ifTrue:[
-                browserClass
-                    browseRefsTo:nameOfGlobal 
-                    classVars:true 
-                    in:(cls whichClassDefinesClassVar:nameOfGlobal) withAllSubclasses 
-                    modificationsOnly:false.
-            ] ifFalse:[
-                "/ is it a private class?
-                (cls notNil
-                and:[ (privateClass := cls theNonMetaclass privateClassNamed:nameOfGlobal) notNil ]) ifTrue:[
-                    browserClass browseReferendsOf:(privateClass name)
-                ] ifFalse:[
-                    |pool nsClass|
+	    "/ is it a class variable?
+	    ((cls := self editedClass) notNil
+	    and:[ (cls theNonMetaclass allClassVarNames includes:nameOfGlobal) ]) ifTrue:[
+		browserClass
+		    browseRefsTo:nameOfGlobal
+		    classVars:true
+		    in:(cls whichClassDefinesClassVar:nameOfGlobal) withAllSubclasses
+		    modificationsOnly:false.
+	    ] ifFalse:[
+		"/ is it a private class?
+		(cls notNil
+		and:[ (privateClass := cls theNonMetaclass privateClassNamed:nameOfGlobal) notNil ]) ifTrue:[
+		    browserClass browseReferendsOf:(privateClass name)
+		] ifFalse:[
+		    |pool nsClass|
 
-                    "/ is it a pool variable?
-                    cls notNil ifTrue:[
-                        pool := cls theNonMetaclass sharedPools 
-                                detect:[:pool | pool classVarNames includes:nameOfGlobal]
-                                ifNone:nil.
-                    ].
-                    pool notNil ifTrue:[
-                        browserClass browseReferendsOf:(pool name,':',nameOfGlobal)
-                    ] ifFalse:[
-                        (cls notNil
-                          and:[ cls nameSpace notNil
-                          and:[ nameOfGlobal knownAsSymbol
-                          and:[ (nsClass := cls nameSpace at:nameOfGlobal asSymbol) notNil
-                        ]]]) notNil ifTrue:[
-                            "/ a namespace class
-                            browserClass browseReferendsOf:nsClass name
-                        ] ifFalse:[
-                            "/ no, assume global
-                            browserClass browseReferendsOf:nameOfGlobal
-                        ]
-                    ]
-                ]
-            ]
-        ].
+		    "/ is it a pool variable?
+		    cls notNil ifTrue:[
+			pool := cls theNonMetaclass sharedPools
+				detect:[:pool | pool classVarNames includes:nameOfGlobal]
+				ifNone:nil.
+		    ].
+		    pool notNil ifTrue:[
+			browserClass browseReferendsOf:(pool name,':',nameOfGlobal)
+		    ] ifFalse:[
+			(cls notNil
+			  and:[ cls nameSpace notNil
+			  and:[ nameOfGlobal knownAsSymbol
+			  and:[ (nsClass := cls nameSpace at:nameOfGlobal asSymbol) notNil
+			]]]) notNil ifTrue:[
+			    "/ a namespace class
+			    browserClass browseReferendsOf:nsClass name
+			] ifFalse:[
+			    "/ no, assume global
+			    browserClass browseReferendsOf:nameOfGlobal
+			]
+		    ]
+		]
+	    ]
+	].
     ].
 
     "Created: / 5.11.2001 / 17:32:23 / cg"
@@ -1826,11 +1826,11 @@
 
     selectedText := self selectedTextOrSyntaxElement.
     selectedText notEmptyOrNil ifTrue:[
-        self windowGroup withWaitCursorDo:[
-            selector := SystemBrowser extractSelectorFrom:selectedText.
-            (UserPreferences systemBrowserClass)
-                browseAllCallsOn:(selector ? selectedText)
-        ]
+	self windowGroup withWaitCursorDo:[
+	    selector := SystemBrowser extractSelectorFrom:selectedText.
+	    (UserPreferences systemBrowserClass)
+		browseAllCallsOn:(selector ? selectedText)
+	]
     ].
 
     "Created: / 5.11.2001 / 17:32:23 / cg"
@@ -1844,15 +1844,15 @@
 
     sel := self selectedTextOrSyntaxElement.
     sel notEmptyOrNil ifTrue:[
-        sel := sel asSymbol.
-        self windowGroup withWaitCursorDo:[
-            SharedPool allSubclassesDo:[:eachPool |
-                (eachPool includesKey:sel) ifTrue:[
-                    (UserPreferences systemBrowserClass) 
-                        openInClass:eachPool class selector:#initialize
-                ].
-            ].
-        ].
+	sel := sel asSymbol.
+	self windowGroup withWaitCursorDo:[
+	    SharedPool allSubclassesDo:[:eachPool |
+		(eachPool includesKey:sel) ifTrue:[
+		    (UserPreferences systemBrowserClass)
+			openInClass:eachPool class selector:#initialize
+		].
+	    ].
+	].
     ].
 
     "Created: / 15-01-2011 / 14:01:39 / cg"
@@ -1862,9 +1862,9 @@
     "user selected 'doIt' from menu; show a wait-cursor, evaluate the code
      and finally restore cursor; return result of evaluation"
 
-    ^ self 
-        do:(self selectionOrTextOfCursorLine) 
-        withValueDo:nil
+    ^ self
+	do:(self selectionOrTextOfCursorLine)
+	withValueDo:nil
 
     "Modified: / 16.5.1998 / 16:45:01 / cg"
 !
@@ -1873,163 +1873,163 @@
     "return my popUpMenu; thats the superclasses menu
      PLUS st-evaluation items: doIt, printIt and inspectIt."
 
-    <resource: #keyboard (#DoIt #PrintIt #InspectIt 
-                          #CommentSelection #UncommentSelection
-                          #BrowseIt #ImplementorsOfIt
-                         )>
+    <resource: #keyboard (#DoIt #PrintIt #InspectIt
+			  #CommentSelection #UncommentSelection
+			  #BrowseIt #ImplementorsOfIt
+			 )>
     <resource: #programMenu>
 
     |m sub subsub idx sensor sel2 sel selectedSymbol|
 
     m := super editMenu.
     ((sensor := self sensor) notNil and:[sensor ctrlDown and:[sensor shiftDown not]]) ifTrue:[
-        sub := m.
-        m := nil.
+	sub := m.
+	m := nil.
     ] ifFalse:[
-        sub := m subMenuAt:#others.
+	sub := m subMenuAt:#others.
     ].
 
     sub notNil ifTrue:[
-        "
-         workspaces support #browse, implementors etc. add them after paste.
-        "
-        sub 
-            addItemList:#(
-                ('-'                                                                        )
-                ('Browse'                       browseIt                BrowseIt            )
-                ('Browse Pool'                  browseSharedPoolOfIt                        )
-                ('Senders of It'                browseSendersOfIt                           )
-                ('Implementors of It'           browseImplementorsOfIt  ImplementorsOfIt    )
-                ('References to It'             browseReferencesToIt                        )
+	"
+	 workspaces support #browse, implementors etc. add them after paste.
+	"
+	sub
+	    addItemList:#(
+		('-'                                                                        )
+		('Browse'                       browseIt                BrowseIt            )
+		('Browse Pool'                  browseSharedPoolOfIt                        )
+		('Senders of It'                browseSendersOfIt                           )
+		('Implementors of It'           browseImplementorsOfIt  ImplementorsOfIt    )
+		('References to It'             browseReferencesToIt                        )
 "/                ('Classes Containing It in Name'    browseClassesContainingItInName           )
 "/                ('Methods Contaníning It in Name'   browseMethodsContainingItInName           )
 "/                ('Methods Contaníning It in Source' browseMethodsContainingItInSource         )
-                ('-'                                                                )
-                ('TimeIt'               timeIt                                      )
-                ('SpyOnIt'              spyOnIt                                     ))
-          resources:resources  
-          after:#gotoLine.
+		('-'                                                                )
+		('TimeIt'               timeIt                                      )
+		('SpyOnIt'              spyOnIt                                     ))
+	  resources:resources
+	  after:#gotoLine.
 
-        subsub := sub subMenuAt:#tools.
-        subsub notNil ifTrue:[
-            subsub
-                addItemList:#(
-                    ('-'                                                                )
-                    ('CommentIt'            commentSelection        CommentSelection    )
-                    ('UncommentIt'          uncommentSelection      UncommentSelection  ))
-              resources:resources  
-              after:#'indent'.
-        ].
+	subsub := sub subMenuAt:#tools.
+	subsub notNil ifTrue:[
+	    subsub
+		addItemList:#(
+		    ('-'                                                                )
+		    ('CommentIt'            commentSelection        CommentSelection    )
+		    ('UncommentIt'          uncommentSelection      UncommentSelection  ))
+	      resources:resources
+	      after:#'indent'.
+	].
 
-        self hasSelection ifFalse:[
-            sub disableAll:#(browseImplementorsOfIt browseSendersOfIt 
-                             browseReferencesToIt timeIt spyOnIt
-                             browseSharedPoolOfIt browseIt). 
-            self supportsSyntaxElements ifTrue:[
-                self syntaxElementForSelectorUnderCursor notNil ifTrue:[
-                    sub enableAll:#(browseImplementorsOfIt browseSendersOfIt ) 
-                ] ifFalse:[
-                    |el|
+	self hasSelection ifFalse:[
+	    sub disableAll:#(browseImplementorsOfIt browseSendersOfIt
+			     browseReferencesToIt timeIt spyOnIt
+			     browseSharedPoolOfIt browseIt).
+	    self supportsSyntaxElements ifTrue:[
+		self syntaxElementForSelectorUnderCursor notNil ifTrue:[
+		    sub enableAll:#(browseImplementorsOfIt browseSendersOfIt )
+		] ifFalse:[
+		    |el|
 
-                    (el := self syntaxElementForVariableUnderCursor) notNil ifTrue:[
-                        el isGlobal ifTrue:[
-                            sub enable: #browseReferencesToIt
-                        ].
-                        el isClass ifTrue:[
-                            sub enable:#browseIt
-                        ]
-                    ]
-                ]
-            ].
-        ] ifTrue:[
-            sel := self selectionAsString.
-            sel notNil ifTrue:[
-                sel asSymbolIfInterned isNil ifTrue:[
-                    sel2 := SystemBrowser extractSelectorFrom:sel.
-                    sel2 notNil ifTrue:[
-                        sel2 := sel2 asSymbolIfInterned.
-                    ].
-                ].
-            ].
-            (sel2 isNil and:[sel isNil]) ifTrue:[
-                sub disableAll:#(browseImplementorsOfIt browseSendersOfIt).
-            ].
-            "/ a global or namespace-var selected ?
-            sel isNil ifTrue:[
-                sub disable:#browseReferencesToIt.
-            ] ifFalse:[
-                selectedSymbol := sel asSymbolIfInterned.
-                (selectedSymbol notNil
-                 and:[(Smalltalk includesKey:selectedSymbol)
-                      or:[(NameSpace allNameSpaces contains:[:ns | ns includesKey:selectedSymbol]) ]]
-                ) ifTrue:[
-                    "/ a global or namespace var selected
-                ] ifFalse:[
-                    |cls|
+		    (el := self syntaxElementForVariableUnderCursor) notNil ifTrue:[
+			el isGlobal ifTrue:[
+			    sub enable: #browseReferencesToIt
+			].
+			el isClass ifTrue:[
+			    sub enable:#browseIt
+			]
+		    ]
+		]
+	    ].
+	] ifTrue:[
+	    sel := self selectionAsString.
+	    sel notNil ifTrue:[
+		sel asSymbolIfInterned isNil ifTrue:[
+		    sel2 := SystemBrowser extractSelectorFrom:sel.
+		    sel2 notNil ifTrue:[
+			sel2 := sel2 asSymbolIfInterned.
+		    ].
+		].
+	    ].
+	    (sel2 isNil and:[sel isNil]) ifTrue:[
+		sub disableAll:#(browseImplementorsOfIt browseSendersOfIt).
+	    ].
+	    "/ a global or namespace-var selected ?
+	    sel isNil ifTrue:[
+		sub disable:#browseReferencesToIt.
+	    ] ifFalse:[
+		selectedSymbol := sel asSymbolIfInterned.
+		(selectedSymbol notNil
+		 and:[(Smalltalk includesKey:selectedSymbol)
+		      or:[(NameSpace allNameSpaces contains:[:ns | ns includesKey:selectedSymbol]) ]]
+		) ifTrue:[
+		    "/ a global or namespace var selected
+		] ifFalse:[
+		    |cls|
 
-                    cls := self editedClass.
-                    cls notNil ifTrue:[
-                        cls := cls theNonMetaclass.
-                        ((cls allClassVarNames includes:sel)
-                          or:[ (cls theNonMetaclass privateClassNamed:sel) notNil]) ifTrue:[
-                            "/ a classvar or private class
-                        ] ifFalse:[
-                            |pool|
-                            "/ is it a pool variable?
-                            pool := cls sharedPools 
-                                    detect:[:pool | pool classVarNames includes:sel]
-                                    ifNone:nil.
-                            pool isNil ifTrue:[
-                                "/ todo: an instvar selected?
-                                sub disable:#browseReferencesToIt.
-                            ].
-                        ].
-                    ] ifFalse:[
-                        sub disable:#browseReferencesToIt.
-                    ].
-                ].
-            ].
-            (selectedSymbol notNil 
-             and:[SharedPool allSubclasses contains:[:pool | pool includesKey:selectedSymbol]]) ifFalse:[
-                sub disable:#browseSharedPoolOfIt.
-            ].
-        ].
-        self isReadOnly ifTrue:[
-            sub disableAll:#(commentSelection uncommentSelection) 
-        ].
+		    cls := self editedClass.
+		    cls notNil ifTrue:[
+			cls := cls theNonMetaclass.
+			((cls allClassVarNames includes:sel)
+			  or:[ (cls theNonMetaclass privateClassNamed:sel) notNil]) ifTrue:[
+			    "/ a classvar or private class
+			] ifFalse:[
+			    |pool|
+			    "/ is it a pool variable?
+			    pool := cls sharedPools
+				    detect:[:pool | pool classVarNames includes:sel]
+				    ifNone:nil.
+			    pool isNil ifTrue:[
+				"/ todo: an instvar selected?
+				sub disable:#browseReferencesToIt.
+			    ].
+			].
+		    ] ifFalse:[
+			sub disable:#browseReferencesToIt.
+		    ].
+		].
+	    ].
+	    (selectedSymbol notNil
+	     and:[SharedPool allSubclasses contains:[:pool | pool includesKey:selectedSymbol]]) ifFalse:[
+		sub disable:#browseSharedPoolOfIt.
+	    ].
+	].
+	self isReadOnly ifTrue:[
+	    sub disableAll:#(commentSelection uncommentSelection)
+	].
     ].
 
     m notNil ifTrue:[
-        "
-         workspaces support #doIt, #printIt and #inspectIt
-         add them after paste.
-        "
-        idx := m indexOf:#paste.
-        idx == 0 ifTrue:[idx := m indexOf:#pasteOrReplace].
-        idx ~~ 0 ifTrue:[
-            m 
-              addItemList:#(
-                ('-'                                )
-                ('DoIt'         doIt        DoIt     )
-                ('PrintIt'      printIt     PrintIt  )
-                ('InspectIt'    inspectIt   InspectIt))
-              resources:resources  
-              after:idx.
+	"
+	 workspaces support #doIt, #printIt and #inspectIt
+	 add them after paste.
+	"
+	idx := m indexOf:#paste.
+	idx == 0 ifTrue:[idx := m indexOf:#pasteOrReplace].
+	idx ~~ 0 ifTrue:[
+	    m
+	      addItemList:#(
+		('-'                                )
+		('DoIt'         doIt        DoIt     )
+		('PrintIt'      printIt     PrintIt  )
+		('InspectIt'    inspectIt   InspectIt))
+	      resources:resources
+	      after:idx.
 
-        ].
+	].
 
-        (self hasSelectionOrTextInCursorLine) ifFalse:[
-            |lNr line|
+	(self hasSelectionOrTextInCursorLine) ifFalse:[
+	    |lNr line|
 
-            lNr := self cursorLine.
-            line := self listAt:lNr.
-            line isEmptyOrNil ifTrue:[
-                m disableAll:#(printIt doIt inspectIt browseIt) 
-            ].
-        ].
-        self isReadOnly ifTrue:[
-            m disable:#printIt 
-        ].
+	    lNr := self cursorLine.
+	    line := self listAt:lNr.
+	    line isEmptyOrNil ifTrue:[
+		m disableAll:#(printIt doIt inspectIt browseIt)
+	    ].
+	].
+	self isReadOnly ifTrue:[
+	    m disable:#printIt
+	].
     ].
 
     ^ m ? sub.
@@ -2046,9 +2046,9 @@
 
     shifted := self sensor shiftDown.
 
-    ^ self 
-        do:(self selectionOrTextOfCursorLine) 
-        withValueDo:[:result | shifted ifTrue:[result basicInspect] ifFalse:[result inspect] ]
+    ^ self
+	do:(self selectionOrTextOfCursorLine)
+	withValueDo:[:result | shifted ifTrue:[result basicInspect] ifFalse:[result inspect] ]
 
     "Modified: / 16.5.1998 / 16:44:56 / cg"
 !
@@ -2059,33 +2059,33 @@
      If the text is readOnly, do nothing."
 
     self isReadOnly ifTrue:[
-        self beep.
-        ^ self.
+	self beep.
+	^ self.
     ].
-    self 
-        undoableDo:[
-            self 
-                do:(self selectionOrTextOfCursorLine) 
-                withValueDo:[:result |
-                    |s printer|
+    self
+	undoableDo:[
+	    self
+		do:(self selectionOrTextOfCursorLine)
+		withValueDo:[:result |
+		    |s printer|
 
-                    self cursorLine:selectionEndLine col:(selectionEndCol + 1).
-                    (self editedLanguage notNil
-                    and:[(printer := self editedLanguage valuePrinterClass) notNil]) ifTrue:[
-                        s := printer printStringForPrintItOf:result
-                    ] ifFalse:[
-                        (result isInteger 
-                        and:[ result > 10 
-                        and:[ InspectorView defaultIntegerDisplayRadix ~= 10 ]]) ifTrue:[
-                            s := result displayString , ' "',(result radixPrintStringRadix: InspectorView defaultIntegerDisplayRadix),'"'.
-                        ] ifFalse:[
-                            s := result printStringForPrintIt "old: displayString" "very old: printString"
-                        ].
-                    ].
-                    self insertSelectedStringAtCursor:s
-                ]
-        ] 
-        info:'PrintIt'
+		    self cursorLine:selectionEndLine col:(selectionEndCol + 1).
+		    (self editedLanguage notNil
+		    and:[(printer := self editedLanguage valuePrinterClass) notNil]) ifTrue:[
+			s := printer printStringForPrintItOf:result
+		    ] ifFalse:[
+			(result isInteger
+			and:[ result > 10
+			and:[ InspectorView defaultIntegerDisplayRadix ~= 10 ]]) ifTrue:[
+			    s := result displayString , ' "',(result radixPrintStringRadix: InspectorView defaultIntegerDisplayRadix),'"'.
+			] ifFalse:[
+			    s := result printStringForPrintIt "old: displayString" "very old: printString"
+			].
+		    ].
+		    self insertSelectedStringAtCursor:s
+		]
+	]
+	info:'PrintIt'
 
     "Modified: / 08-03-2012 / 16:14:34 / cg"
 !
@@ -2102,20 +2102,20 @@
      pasting it after the selection."
 
     self isReadOnly ifTrue:[
-        self beep.
-        ^ self
+	self beep.
+	^ self
     ].
 
-    self 
-        undoableDo:[
-            self 
-                do:(self selectionOrTextOfCursorLine) 
-                withValueDo:[:result |
-                    self replaceSelectionBy:(result displayString "printString")
-                ].
-                undoSupport actionInfo:'ReplaceIt'.
-        ]
-        info:'ReplaceIt'
+    self
+	undoableDo:[
+	    self
+		do:(self selectionOrTextOfCursorLine)
+		withValueDo:[:result |
+		    self replaceSelectionBy:(result displayString "printString")
+		].
+		undoSupport actionInfo:'ReplaceIt'.
+	]
+	info:'ReplaceIt'
 
     "Created: / 08-11-2007 / 11:31:54 / cg"
 !
@@ -2135,9 +2135,9 @@
     |code|
 
     compilerClass == Smalltalk::Compiler ifFalse:[
-        "sigh - this measurement will include the time to compile - sigh"
-        aProfiler spyDetailedOn:[ self doIt ].
-        ^ self.
+	"sigh - this measurement will include the time to compile - sigh"
+	aProfiler spyDetailedOn:[ self doIt ].
+	^ self.
     ].
 
     code := aProfiler name,' spyDetailedOn:[' , (self selectionOrTextOfCursorLine), ']'.
@@ -2151,14 +2151,14 @@
     |code t|
 
     compilerClass == Smalltalk::Compiler ifFalse:[
-        "sigh - this measurement will include the time to compile - sigh"
-        t := Time millisecondsToRun:[ self doIt ].
-        Transcript showCR:'execution time: ' , t printString , ' ms'.
-        ^ self.
+	"sigh - this measurement will include the time to compile - sigh"
+	t := Time millisecondsToRun:[ self doIt ].
+	Transcript showCR:'execution time: ' , t printString , ' ms'.
+	^ self.
     ].
 
     code := '|t| t := Time millisecondsToRun:[' , self selectionAsString, '].
-             Transcript showCR:''execution time: '' , t printString , '' ms''.'.
+	     Transcript showCR:''execution time: '' , t printString , '' ms''.'.
     self do:code withValueDo:[:value | ].
 
     "Modified: / 22-04-1998 / 22:03:51 / ca"
@@ -2181,40 +2181,40 @@
     oldSelectionEndLine := self selectionEndLine.
     oldSelectionEndCol := self selectionEndCol.
 
-    abortExpandAction := 
-        [
-            self 
-                selectFromLine:oldSelectionStartLine col:oldSelectionStartCol 
-                toLine:oldSelectionEndLine col:oldSelectionEndCol.
-            self cursorLine:oldCursorLine col:oldCursorCol.
-        ].                                  
+    abortExpandAction :=
+	[
+	    self
+		selectFromLine:oldSelectionStartLine col:oldSelectionStartCol
+		toLine:oldSelectionEndLine col:oldSelectionEndCol.
+	    self cursorLine:oldCursorLine col:oldCursorCol.
+	].
 
     expandedString := self selectAbbreviationKeyBeforeCursor. "/ returns the new string AND selects the key
     expandedString isNil ifTrue:[
-        abortExpandAction value.
-        ^ self
+	abortExpandAction value.
+	^ self
     ].
     newCursorPos := expandedString indexOf:$!!.
     newCursorPos ~~ 0 ifTrue:[
-        expandedString := expandedString copyWithout:$!!.
+	expandedString := expandedString copyWithout:$!!.
     ].
     replStartCol := self selectionStartCol.
     self
-        undoableDo:[
-            self replaceSelectionBy: expandedString
-        ]
-        info:'Replace'.
+	undoableDo:[
+	    self replaceSelectionBy: expandedString
+	]
+	info:'Replace'.
 
     newCursorPos == 0 ifTrue:[
-        "/ cursor already fine (at the end)
+	"/ cursor already fine (at the end)
     ] ifFalse:[
-        self cursorCol:replStartCol+newCursorPos-1
+	self cursorCol:replStartCol+newCursorPos-1
     ]
 !
 
 findAbbreviationKeyBeforeCursor
     "after receiving an Alt-shift key-event, look for the string before the
-     cursor, find an abbrev for it, return the key and the abbreviation for it.   
+     cursor, find an abbrev for it, return the key and the abbreviation for it.
      If none is found, return nil"
 
     |snippets keys minMax maxKeyLen minKeyLen stringBeforeCursor|
@@ -2230,13 +2230,13 @@
     maxKeyLen := maxKeyLen min:stringBeforeCursor size.
 
     maxKeyLen to:minKeyLen by:-1 do:[:keyLen |
-        |lCharactersBeforeCursor expandedString|
+	|lCharactersBeforeCursor expandedString|
 
-        lCharactersBeforeCursor := stringBeforeCursor last:keyLen.
-        expandedString := snippets at:lCharactersBeforeCursor ifAbsent:nil.
-        expandedString notNil ifTrue:[
-            ^ { lCharactersBeforeCursor . expandedString withCRs }
-        ].
+	lCharactersBeforeCursor := stringBeforeCursor last:keyLen.
+	expandedString := snippets at:lCharactersBeforeCursor ifAbsent:nil.
+	expandedString notNil ifTrue:[
+	    ^ { lCharactersBeforeCursor . expandedString withCRs }
+	].
     ].
     ^ nil.
 
@@ -2245,16 +2245,16 @@
 
 selectAbbreviationKeyBeforeCursor
     "after receiving an Alt-shift key-event, look for the string before the
-     cursor, find an abbrev for it, select it and return the abbreviation for it.   
+     cursor, find an abbrev for it, select it and return the abbreviation for it.
      If none is found, do not select and return nil"
 
     |keyAndSnippet snippet key|
 
     (keyAndSnippet := self findAbbreviationKeyBeforeCursor) notNil ifTrue:[
-        key := keyAndSnippet first.
-        snippet := keyAndSnippet second.
-        self selectFromLine:cursorLine col:cursorCol-key size toLine:cursorLine col:cursorCol-1.
-        ^ snippet
+	key := keyAndSnippet first.
+	snippet := keyAndSnippet second.
+	self selectFromLine:cursorLine col:cursorCol-key size toLine:cursorLine col:cursorCol-1.
+	^ snippet
     ].
     ^ nil.
 
@@ -2266,12 +2266,12 @@
 
     selectedText := self selectionAsString.
     selectedText isEmptyOrNil ifTrue:[
-        self supportsSyntaxElements ifTrue:[
-            el := self syntaxElementForSelectorUnderCursor.
-            el notNil ifTrue:[ selectedText := el value ].
-        ]
+	self supportsSyntaxElements ifTrue:[
+	    el := self syntaxElementForSelectorUnderCursor.
+	    el notNil ifTrue:[ selectedText := el value ].
+	]
     ].
-    ^ selectedText 
+    ^ selectedText
 !
 
 syntaxElementForSelectorUnderCursor
@@ -2294,10 +2294,9 @@
 !Workspace class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/Workspace.st,v 1.329 2014-05-12 21:03:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/Workspace.st,v 1.330 2014-06-10 10:24:04 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libwidg/Workspace.st,v 1.329 2014-05-12 21:03:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/Workspace.st,v 1.330 2014-06-10 10:24:04 cg Exp $'
 ! !
-