Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Wed, 11 May 2016 09:39:07 +0200
branchjv
changeset 5738 9498dfe97f83
parent 5737 98bc0782ffa1 (current diff)
parent 5731 00e37b96afea (diff)
child 5739 edab5a6a8d4f
Merge
EditField.st
EditTextView.st
ScrollableView.st
TextView.st
WorkspaceCompletionSupport.st
--- a/Button.st	Mon May 09 21:43:19 2016 +0200
+++ b/Button.st	Wed May 11 09:39:07 2016 +0200
@@ -878,12 +878,8 @@
 
     |f|
 
-    (ReturnForm notNil and:[aDevice == ReturnForm graphicsDevice]) ifTrue:[
-        ^ ReturnForm
-    ].
-    f := Smalltalk imageFromFileNamed:'Return.xbm' inPackage:#'stx:libwidg'.
-    f notNil ifTrue:[
-        f := f onDevice:aDevice
+    ReturnForm notNil ifTrue:[
+        ^ ReturnForm onDevice:aDevice.
     ] ifFalse:[
         f := Form width:24 height:14 fromArray:#[2r00000000 2r00000000 2r00000000
                                                  2r00000000 2r00000000 2r00000000
@@ -899,10 +895,12 @@
                                                  2r00000001 2r10000000 2r00000000
                                                  2r00000000 2r00000000 2r00000000
                                                  2r00000000 2r00000000 2r00000000]
-                                              onDevice:aDevice
-    ].
-    ReturnForm := f.
-    ^ f
+                                              onDevice:aDevice.
+        aDevice == Display ifTrue:[
+            ReturnForm := f.
+        ].
+        ^ f.
+    ]. 
 
     "Modified: / 3.11.1997 / 09:12:37 / cg"
 !
@@ -911,14 +909,11 @@
     "return the form used for the return arrow light pixels (3D only);
      cache the one for Display for the next round"
 
+
     |f|
 
-    (ReturnLightForm notNil and:[aDevice == ReturnLightForm graphicsDevice]) ifTrue:[
-        ^ ReturnLightForm
-    ].
-    f := Smalltalk imageFromFileNamed:'ReturnLight.xbm' inPackage:#'stx:libwidg'.
-    f notNil ifTrue:[
-        f := f onDevice:aDevice
+    ReturnLightForm notNil ifTrue:[
+        ^ ReturnLightForm onDevice:aDevice.    
     ] ifFalse:[
         f := Form width:24 height:14 fromArray:#[2r00000000 2r00000000 2r00000000
                                                  2r00000000 2r00000000 2r00000000
@@ -934,10 +929,12 @@
                                                  2r00000000 2r10000000 2r00000000
                                                  2r00000000 2r00000000 2r00000000
                                                  2r00000000 2r00000000 2r00000000]
-                                              onDevice:aDevice
+                                              onDevice:aDevice.
+        aDevice == Display ifTrue:[
+            ReturnLightForm := f.
+        ].
+        ^ f.
     ].
-    ReturnLightForm := f.
-    ^ f
 
     "Modified: / 3.11.1997 / 09:12:23 / cg"
 !
@@ -948,12 +945,8 @@
 
     |f|
 
-    (ReturnShadowForm notNil and:[aDevice == ReturnShadowForm graphicsDevice]) ifTrue:[
-        ^ ReturnShadowForm
-    ].
-    f := Smalltalk imageFromFileNamed:'ReturnShadow.xbm' inPackage:#'stx:libwidg'.
-    f notNil ifTrue:[
-        f := f onDevice:aDevice
+    ReturnShadowForm notNil ifTrue:[
+        ^ ReturnShadowForm onDevice:aDevice.    
     ] ifFalse:[
         f := Form width:24 height:14 fromArray:#[2r00000000 2r00000000 2r00000000
                                                  2r00000000 2r00000000 2r00000000
@@ -969,10 +962,13 @@
                                                  2r00000001 2r00000000 2r00000000
                                                  2r00000000 2r00000000 2r00000000
                                                  2r00000000 2r00000000 2r00000000]
-                                              onDevice:aDevice
+                                              onDevice:aDevice.
+        aDevice == Display ifTrue:[
+            ReturnShadowForm := f.
+        ].
+        ^ f.
     ].
-    ReturnShadowForm := f.
-    ^ f
+
 
     "Modified: / 3.11.1997 / 09:12:11 / cg"
 !
--- a/EditField.st	Mon May 09 21:43:19 2016 +0200
+++ b/EditField.st	Wed May 11 09:39:07 2016 +0200
@@ -2210,7 +2210,7 @@
     and:[ self hasFocus not 
     and:[ visLineNr == 1 ]]])
     ifTrue:[
-        ^ emptyText allItalic colorizeAllWith:Color lightGray.
+        ^ emptyText allItalic withColor:Color lightGray.
     ].
 
     ^ s
--- a/EditTextView.st	Mon May 09 21:43:19 2016 +0200
+++ b/EditTextView.st	Wed May 11 09:39:07 2016 +0200
@@ -1215,7 +1215,7 @@
             self isReadOnly ifTrue:[
                 ''
             ] ifFalse:[
-                l ifTrue:[ 'L' allBold colorizeAllWith:Color red]
+                l ifTrue:[ 'L' allBold withColor:#red]
                   ifFalse:[ e infoPrintString]]]
         argument:(self editModeHolder)
         argument:(self learnModeHolder).
--- a/ScrollableView.st	Mon May 09 21:43:19 2016 +0200
+++ b/ScrollableView.st	Wed May 11 09:39:07 2016 +0200
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
               All Rights Reserved
@@ -1784,54 +1786,86 @@
     ].
     
     vScrollBar notNil ifTrue:[
-        vScrollBar scrollAction:[:position |
-            lockUpdates := true.
-            scrolledView scrollVerticalToPercent:position.
-            lockUpdates := false
-        ].
-        vScrollBar 
-            scrollUpAction:[ |sensor|
-                            sensor := self sensor.
-                            (sensor shiftDown or:[sensor ctrlDown]) ifTrue:[
-                                scrolledView scrollToTop
-                            ] ifFalse:[
-                                scrolledView scrollUp
-                            ]
-                           ].
-        vScrollBar 
-            scrollDownAction:[|sensor|
-                            sensor := self sensor.
-                            (sensor shiftDown or:[sensor ctrlDown]) ifTrue:[
-                                scrolledView scrollToBottom
-                            ] ifFalse:[
-                                scrolledView scrollDown
-                            ]
-                           ].
+        vScrollBar scrollAction:
+            [:position |
+                "/ in case the event came after the view was already deconstructed
+                scrolledView notNil ifTrue:[
+                    lockUpdates := true.
+                    scrolledView scrollVerticalToPercent:position.
+                    lockUpdates := false
+                ].
+            ].
+
+        vScrollBar scrollUpAction:
+            [   
+                |sensor|
+                "/ in case the event came after the view was already deconstructed
+                scrolledView notNil ifTrue:[
+                    sensor := self sensor.
+                    (sensor shiftDown or:[sensor ctrlDown]) ifTrue:[
+                        scrolledView scrollToTop
+                    ] ifFalse:[
+                        scrolledView scrollUp
+                    ]
+                ].
+            ].
+
+        vScrollBar scrollDownAction:
+            [   
+                |sensor|
+
+                "/ in case the event came after the view was already deconstructed
+                scrolledView notNil ifTrue:[
+                    sensor := self sensor.
+                    (sensor shiftDown or:[sensor ctrlDown]) ifTrue:[
+                        scrolledView scrollToBottom
+                    ] ifFalse:[
+                        scrolledView scrollDown
+                    ]
+                ].
+            ].
     ].
+
     hScrollBar notNil ifTrue:[
-        hScrollBar scrollAction:[:position |
-            lockUpdates := true.
-            scrolledView scrollHorizontalToPercent:position.
-            lockUpdates := false
-        ].
-        hScrollBar 
-            scrollUpAction:[|sensor|
-                            sensor := self sensor.
-                            (sensor shiftDown or:[sensor ctrlDown]) ifTrue:[
-                                scrolledView scrollToLeft
-                            ] ifFalse:[
-                                scrolledView scrollLeft
-                            ]
-                           ].
-        hScrollBar 
-            scrollDownAction:[|sensor|
-                            sensor := self sensor.
-                            (sensor shiftDown or:[sensor ctrlDown]) ifTrue:[
-                                scrolledView scrollToRight
-                            ] ifFalse:[
-                                scrolledView scrollRight
-                            ]
-                             ].
+        hScrollBar scrollAction:
+            [:position |
+                "/ in case the event came after the view was already deconstructed
+                scrolledView notNil ifTrue:[
+                    lockUpdates := true.
+                    scrolledView scrollHorizontalToPercent:position.
+                    lockUpdates := false
+                ].
+            ].
+
+        hScrollBar scrollUpAction:
+            [   
+                |sensor|
+
+                "/ in case the event came after the view was already deconstructed
+                scrolledView notNil ifTrue:[
+                    sensor := self sensor.
+                    (sensor shiftDown or:[sensor ctrlDown]) ifTrue:[
+                        scrolledView scrollToLeft
+                    ] ifFalse:[
+                        scrolledView scrollLeft
+                    ]
+                ].
+            ].
+
+        hScrollBar scrollDownAction:
+            [
+                |sensor|
+
+                "/ in case the event came after the view was already deconstructed
+                scrolledView notNil ifTrue:[
+                    sensor := self sensor.
+                    (sensor shiftDown or:[sensor ctrlDown]) ifTrue:[
+                        scrolledView scrollToRight
+                    ] ifFalse:[
+                        scrolledView scrollRight
+                    ]
+                ].
+            ].
     ].
 
     scrolledView addDependent:self.
--- a/TextView.st	Mon May 09 21:43:19 2016 +0200
+++ b/TextView.st	Wed May 11 09:39:07 2016 +0200
@@ -357,13 +357,13 @@
 'If checked, lines containing the matched string are selected.'
 
 #replacePreserveCase
-'Preserve the case of replaced text'
+'Preserve the title case of replaced text'
 
 #replaceAll
 'Search and replace all occurrences of the searched string'
 
 #searchWithWrap
-'Wrap around at the end of the text, an continue the search from the top'
+'Wrap around at the end of the text, and continue the search from the top'
 
 #matchWithRegex
 'Use regex pattern for search (as opposed to glob pattern)'
--- a/VariablePanel.st	Mon May 09 21:43:19 2016 +0200
+++ b/VariablePanel.st	Wed May 11 09:39:07 2016 +0200
@@ -628,11 +628,9 @@
             cursor := DefaultVCursor
         ] ifFalse:[
             device isWindowsPlatform ifFalse:[
-                cursor := Cursor 
-                            sourceForm:(Smalltalk imageFromFileNamed:'VVPanel.xbm' forClass:self)
-                            maskForm:(Smalltalk imageFromFileNamed:'VVPanel_m.xbm' forClass:self)
-                            hotX:8
-                            hotY:8.
+                cursor := Cursor
+                            fromImage:self verticalResizeCursor
+                            hotSpot:8@8.
             ].
 
             "
@@ -653,11 +651,9 @@
             cursor := DefaultHCursor
         ] ifFalse:[
             device isWindowsPlatform ifFalse:[
-                cursor := Cursor 
-                            sourceForm:(Smalltalk imageFromFileNamed:'VHPanel.xbm' forClass:self)
-                            maskForm:(Smalltalk imageFromFileNamed:'VHPanel_m.xbm' forClass:self)
-                            hotX:8
-                            hotY:8.
+                cursor := Cursor
+                            fromImage:self horizontalResizeCursor
+                            hotSpot:8@8.
             ].
             "
              if bitmaps are not available or under Win95, 
@@ -769,6 +765,28 @@
 
 !VariablePanel class methodsFor:'image specs'!
 
+horizontalResizeCursor
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self horizontalResizeCursor inspect
+     ImageEditor openOnClass:self andSelector:#horizontalResizeCursor
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'VariablePanel horizontalResizeCursor'
+        ifAbsentPut:[(Depth1Image width:16 height:16) bits:(ByteArray fromPackedString:'@X@A @F@@X@!!!!AFHBYC=/0&PDX !!!!@F@@X@A @F@@@@b')
+            colorMapFromArray:#[255 255 255 0 0 0]
+            mask:((ImageMask width:16 height:16) bits:(ByteArray fromPackedString:'@<@C0@O@X<Y33#/\????????N=133&OF@<@C0@O@@@@b'); yourself); yourself]
+!
+
 snapIconDown
     <resource: #image>
     "This resource specification was automatically generated
@@ -960,6 +978,28 @@
                             yourself);
                 yourself
         ]
+!
+
+verticalResizeCursor
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self verticalResizeCursor inspect
+     ImageEditor openOnClass:self andSelector:#verticalResizeCursor
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'VariablePanel verticalResizeCursor'
+        ifAbsentPut:[(Depth1Image width:16 height:16) bits:(ByteArray fromPackedString:'@P@A@@$ AT@C @D@@@C??/?>@@@A@@N@AT@IH@D@@P@b')
+            colorMapFromArray:#[255 255 255 0 0 0]
+            mask:((ImageMask width:16 height:16) bits:(ByteArray fromPackedString:'@8@[,A?0C>@G0@N@??;??/?>??8C @_@C>@_<A.0@8@b'); yourself); yourself]
 ! !
 
 !VariablePanel methodsFor:'accessing-look'!
--- a/Workspace.st	Mon May 09 21:43:19 2016 +0200
+++ b/Workspace.st	Wed May 11 09:39:07 2016 +0200
@@ -1748,7 +1748,9 @@
     "evaluate the code and open a browser on the resulting class (if it evaluates to one),
      or the class of the resulting object (if it does not evaluate to a class).
 
-     Added feature: if selection is of the form class >> selector,  immediately switch to that selector."
+     Added feature: 
+        if selection is of the form class >> selector,  
+        immediately switch to that selector."
 
     |codeToEvaluate el idx selector evaluatedValue classToBrowse gotResult|
 
@@ -1760,15 +1762,24 @@
     ] ifFalse:[
         codeToEvaluate := (self selectionOrTextOfCursorLine ? '') withoutSeparators.
     ].
-    idx := codeToEvaluate indexOfSubCollection:'>>'.
+    idx := codeToEvaluate indexOf:'»'.
     idx ~~ 0 ifTrue:[
-        selector := (codeToEvaluate copyFrom:idx+2) withoutSeparators string.
+        selector := (codeToEvaluate copyFrom:idx+1) withoutSeparators string.
         (selector startsWith:'#') ifTrue:[
             selector := Symbol readFrom:selector.
         ].
         codeToEvaluate := codeToEvaluate copyTo:idx-1.
+    ] ifFalse:[
+        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.
+        ].
     ].
-
+    
     (Parser parseErrorSignal , MessageNotUnderstood) handle:[:ex |
         |className words|
 
--- a/WorkspaceCompletionSupport.st	Mon May 09 21:43:19 2016 +0200
+++ b/WorkspaceCompletionSupport.st	Wed May 11 09:39:07 2016 +0200
@@ -86,7 +86,7 @@
         numLast := 5.
         numSkipped := suggestions size-numShown.    
         suggestions := (suggestions copyTo:numShown-5) 
-                        , { ('<< %1 more skipped >>' bindWith:numSkipped) colorizeAllWith:Color grey }  
+                        , { ('<< %1 more skipped >>' bindWith:numSkipped) withColor:Color grey }  
                         , (suggestions copyLast:5).
         implementations isArray ifTrue:[ 
             implementations := (implementations copyTo:numShown-5),#(nil),(implementations copyLast:5).
@@ -117,7 +117,7 @@
                     suggestions isEmpty ifFalse:[ suggestions := suggestions copyWith: '-' ]. 
                     suggestions := suggestions copyWith: ( '%1 %2'
                                             bindWith:(sniplet asStringCollection first "contractTo:25")
-                                            with: ( ('("',abbrev,'" snippet)') colorizeAllWith:Color gray)).
+                                            with: ( ('("',abbrev,'" snippet)') withColor:Color gray)).
                     indexOfSnippet := suggestions size.
 
                     "/ change below, when reversing the order in above code