MenuPanel.st
changeset 5439 ab2f6d6f41de
parent 5416 9da5642194a6
child 5464 ba69f1d9e99c
--- a/MenuPanel.st	Sat Feb 04 22:14:06 2017 +0100
+++ b/MenuPanel.st	Sat Feb 04 22:15:55 2017 +0100
@@ -1534,17 +1534,19 @@
     ^ enabled
 !
 
-enabled:aState
+enabled:aBooleanOrNil
     "change enabled state of menu"
 
     |state|
 
-    state := aState ? true.
+    state := aBooleanOrNil ? true.
 
     enabled ~~ state ifTrue:[
-	enabled := state.
-	self invalidate.
-    ].
+        enabled := state.
+        self invalidate.
+    ].
+
+    "Modified (format): / 04-02-2017 / 21:32:51 / cg"
 !
 
 enabledAt:stringOrNumber
@@ -1553,10 +1555,12 @@
   ^ self itemAt:stringOrNumber do:[:el| el enabled ] ifAbsent:false
 !
 
-enabledAt:stringOrNumber put:aState
+enabledAt:stringOrNumber put:aBoolean
     "sets the enabled state of an item"
 
-    self itemAt:stringOrNumber do:[:el| el enabled:aState ]
+    self itemAt:stringOrNumber do:[:el| el enabled:aBoolean ]
+
+    "Modified (format): / 04-02-2017 / 21:33:01 / cg"
 !
 
 exclusivePointer:aBoolean
@@ -2056,43 +2060,45 @@
     anItem isButton ifTrue:[ ^ 0 ].
 
     stringOffsetX isNil ifTrue:[
-	stringOffsetX := 0.
-
-	(self isPopUpView and:[self verticalLayout]) ifTrue:[
-	    self do:[:el|
-		el isVisible ifTrue:[
-		    (    (label := el indicatorForm) notNil
-		     or:[(label := el choiceForm) notNil]
-		    ) ifTrue:[
-			stringOffsetX := stringOffsetX max:(label width + 2).
-		    ] ifFalse:[
-			label := el displayLabel.
-			label class == LabelAndIcon ifTrue:[
-			    stringOffsetX := stringOffsetX max:(label xOfString).
-			].
-		    ].
-		].
-	    ].
-	].
+        stringOffsetX := 0.
+
+        (self isPopUpView and:[self verticalLayout]) ifTrue:[
+            self do:[:el|
+                el isVisible ifTrue:[
+                    (    (label := el indicatorForm) notNil
+                     or:[(label := el choiceForm) notNil]
+                    ) ifTrue:[
+                        stringOffsetX := stringOffsetX max:(label width + 2).
+                    ] ifFalse:[
+                        label := el displayLabel.
+                        label isLabelAndIcon ifTrue:[
+                            stringOffsetX := stringOffsetX max:(label xOfString).
+                        ].
+                    ].
+                ].
+            ].
+        ].
     ].
     w := 0.
 
     (    (label := anItem indicatorForm) notNil
      or:[(label := anItem choiceForm) notNil]
     ) ifTrue:[
-	w := label width + 2.
+        w := label width + 2.
     ].
     stringOffsetX == 0 ifTrue:[
-	^ w
+        ^ w
     ].
     w == 0 ifTrue:[
-	label := anItem displayLabel.
-
-	label class == LabelAndIcon ifTrue:[
-	    ^ stringOffsetX - label xOfString
-	].
+        label := anItem displayLabel.
+
+        label isLabelAndIcon ifTrue:[
+            ^ stringOffsetX - label xOfString
+        ].
     ].
     ^ stringOffsetX.
+
+    "Modified: / 04-02-2017 / 22:11:38 / cg"
 !
 
 subMenuIndicationWidth
@@ -2229,11 +2235,12 @@
     ^ false
 !
 
-fitFirstPanel:aState
-    "sets true if the first panel in the menu hierarchy must be fit
-     to the extent of its superView
-
-     NOT SUPPORTED"
+fitFirstPanel:aBoolean
+    "NOT SUPPORTED.
+     should return true if the first panel in the menu hierarchy must fit
+     to the extent of its superView"
+
+    "Modified (comment): / 04-02-2017 / 21:33:36 / cg"
 !
 
 level:anInt
@@ -2265,13 +2272,15 @@
     ^ showGroupDivider
 !
 
-showGroupDivider:aState
+showGroupDivider:aBoolean
     "set the enabled flag for showing groupDiveders"
 
-    showGroupDivider ~~ aState ifTrue:[
-	showGroupDivider := aState.
-	self mustRearrange.
+    showGroupDivider ~~ aBoolean ifTrue:[
+        showGroupDivider := aBoolean.
+        self mustRearrange.
     ]
+
+    "Modified (format): / 04-02-2017 / 21:33:47 / cg"
 !
 
 showSeparatingLines
@@ -2280,13 +2289,15 @@
     ^ showSeparatingLines
 !
 
-showSeparatingLines:aState
+showSeparatingLines:aBoolean
     "turn on/off drawing of separating lines."
 
-    aState ~~ showSeparatingLines ifTrue:[
-	showSeparatingLines := aState.
-	self mustRearrange
-    ].
+    aBoolean ~~ showSeparatingLines ifTrue:[
+        showSeparatingLines := aBoolean.
+        self mustRearrange
+    ].
+
+    "Modified (format): / 04-02-2017 / 21:33:51 / cg"
 !
 
 verticalLayout
@@ -2299,17 +2310,19 @@
     ^ verticalLayout
 !
 
-verticalLayout:aState
+verticalLayout:aBoolean
     "set the layout: vertical( true ) or horizontal( false )"
 
-    aState ~~ verticalLayout ifTrue:[
-	verticalLayout isNil ifTrue:[
-	    verticalLayout := aState
-	] ifFalse:[
-	    verticalLayout := aState.
-	    self mustRearrange.
-	].
-    ].
+    aBoolean ~~ verticalLayout ifTrue:[
+        verticalLayout isNil ifTrue:[
+            verticalLayout := aBoolean
+        ] ifFalse:[
+            verticalLayout := aBoolean.
+            self mustRearrange.
+        ].
+    ].
+
+    "Modified (format): / 04-02-2017 / 21:33:58 / cg"
 ! !
 
 !MenuPanel methodsFor:'accessing-style'!
@@ -8255,40 +8268,42 @@
     disabledDisplayLabel := displayLabel ? ''.
 
     disabledDisplayLabel isString ifTrue:[
-	^ disabledDisplayLabel
+        ^ disabledDisplayLabel
     ].
 
     block := [:el| |rslt|
-	(rslt := el) notNil ifTrue:[
-	    el isImageOrForm ifTrue:[
-		el colorMap notNil ifTrue:[
-		    rslt := menuPanel lightenedImageOnDevice:el
-		]
-	    ] ifFalse:[
-		(displayLabel isKindOf:LabelAndIcon) ifTrue:[
-		    ((form := el icon) notNil and:[form colorMap notNil]) ifTrue:[
-			form := menuPanel lightenedImageOnDevice:form
-		    ].
-		    ((image := el image) notNil and:[image colorMap notNil]) ifTrue:[
-			image := menuPanel lightenedImageOnDevice:image
-		    ].
-		    rslt := LabelAndIcon form:form image:image string:(el string).
-		]
-	    ]
-	].
-	rslt
+        (rslt := el) notNil ifTrue:[
+            el isImageOrForm ifTrue:[
+                el colorMap notNil ifTrue:[
+                    rslt := menuPanel lightenedImageOnDevice:el
+                ]
+            ] ifFalse:[
+                (displayLabel isLabelAndIcon) ifTrue:[
+                    ((form := el icon) notNil and:[form colorMap notNil]) ifTrue:[
+                        form := menuPanel lightenedImageOnDevice:form
+                    ].
+                    ((image := el image) notNil and:[image colorMap notNil]) ifTrue:[
+                        image := menuPanel lightenedImageOnDevice:image
+                    ].
+                    rslt := LabelAndIcon form:form image:image string:(el string).
+                ]
+            ]
+        ].
+        rslt
     ].
 
     displayLabel isArray ifTrue:[
-	disabledDisplayLabel := Array new:(displayLabel size).
-
-	displayLabel keysAndValuesDo:[:anIndex :aLabel|
-	    disabledDisplayLabel at:anIndex put:(block value:aLabel)
-	]
+        disabledDisplayLabel := Array new:(displayLabel size).
+
+        displayLabel keysAndValuesDo:[:anIndex :aLabel|
+            disabledDisplayLabel at:anIndex put:(block value:aLabel)
+        ]
     ] ifFalse:[
-	disabledDisplayLabel := block value:displayLabel
+        disabledDisplayLabel := block value:displayLabel
     ].
     ^ disabledDisplayLabel
+
+    "Modified: / 04-02-2017 / 22:11:45 / cg"
 !
 
 fetchDeviceResources
@@ -8300,44 +8315,44 @@
 fetchImages
     "fetch my icon images"
 
-    |icon|
+    |icon device makeDeviceImage|
 
     (displayLabel isNil or:[displayLabel isString]) ifTrue:[
-	^ self
-    ].
-    displayLabel isImageOrForm ifTrue:[
-	displayLabel := menuPanel imageOnMyDevice:displayLabel.
-	^ self.
-    ].
-
-    (displayLabel isKindOf:LabelAndIcon) ifTrue:[
-	(icon := displayLabel image) notNil ifTrue:[
-	    displayLabel image:(menuPanel imageOnMyDevice:icon)
-	].
-	(icon := displayLabel icon) notNil ifTrue:[
-	    displayLabel icon:(menuPanel imageOnMyDevice:icon)
-	].
-	^ self
-    ].
-
-    displayLabel isArray ifFalse:[^ self].
-
-    displayLabel keysAndValuesDo:[:i :el|
-	(el notNil and:[el isString not]) ifTrue:[
-	    el isImageOrForm ifTrue:[
-		displayLabel at:i put:(menuPanel imageOnMyDevice:el).
-	    ] ifFalse:[
-		el class == LabelAndIcon ifTrue:[
-		    (icon := el image) notNil ifTrue:[
-			el image:(menuPanel imageOnMyDevice:icon)
-		    ].
-		    (icon := el icon) notNil ifTrue:[
-			el icon:(menuPanel imageOnMyDevice:icon)
-		    ]
-		]
-	    ]
-	]
-    ].
+        ^ self
+    ].
+    (device := menuPanel device) isNil ifTrue:[^ self].
+
+    makeDeviceImage :=
+        [:thingy |
+            thingy isImageOrForm ifTrue:[
+                thingy onDevice:device.
+                "/ menuPanel imageOnMyDevice:thingy.
+            ] ifFalse:[
+                (thingy isLabelAndIcon) ifTrue:[
+                    (icon := thingy image) notNil ifTrue:[
+                        thingy image:(icon onDevice:device)
+                        "/ thingy image:(menuPanel imageOnMyDevice:icon)
+                    ].
+                    (icon := thingy icon) notNil ifTrue:[
+                        thingy icon:(icon onDevice:device)
+                        "/ thingy icon:(menuPanel imageOnMyDevice:icon)
+                    ].
+                ].
+                thingy
+            ].    
+       ].
+
+    displayLabel isArray ifFalse:[
+        displayLabel := makeDeviceImage value:displayLabel.
+    ] ifTrue:[
+        displayLabel doWithIndex:[:el :i |
+            (el notNil and:[el isString not]) ifTrue:[
+                displayLabel at:i put:(makeDeviceImage value:el)
+            ]
+        ]
+    ].
+
+    "Modified: / 04-02-2017 / 22:08:43 / cg"
 !
 
 updateAccessCharacterFor:aLabel
@@ -8346,17 +8361,17 @@
     accessCharacter notNil ifTrue:[^ aLabel].
 
     aLabel isString ifFalse:[
-	aLabel class == LabelAndIcon ifTrue:[
-	    aLabel string:(self updateAccessCharacterFor:(aLabel string))
-	].
-	^ aLabel
+        aLabel isLabelAndIcon ifTrue:[
+            aLabel string:(self updateAccessCharacterFor:(aLabel string))
+        ].
+        ^ aLabel
     ].
 
     ^ MenuPanel
-		processAmpersandCharactersFor:aLabel
-		withAccessCharacterPosition:(menuItem accessCharacterPosition).
-
-    "Modified: / 15-02-2012 / 18:53:11 / cg"
+                processAmpersandCharactersFor:aLabel
+                withAccessCharacterPosition:(menuItem accessCharacterPosition).
+
+    "Modified: / 04-02-2017 / 22:09:04 / cg"
 ! !
 
 !MenuPanel::Item methodsFor:'printing & storing'!