isCOBOL Evolve : Appendices : Library Routines : W$MENU : WMENU-SET-ATTRIBUTE
WMENU-SET-ATTRIBUTE
The WMENU-SET-ATTRIBUTE function sets the attributes for the next menu bars created via WMENU-NEW and WMENU-NEW-HAMBURGER functions. All the next calls to W$MENU in the current runtime session will be affected by these attributes.
Syntax:
 CALL "W$MENU" USING WMENU-SET-ATTRIBUTE
                     attributeName
                     attributeValue
              GIVING returnCode
Parameters:
WMENU-SET-ATTRIBUTE
Constant
 
attributeName
PIC X(n)
Identifies the attribute to set. Valid values are listed below.
attributeValue
PIC X(n)
Specifies the attribute value
List of supported attributes:
Attribute
Description
Possible values
Default Value
check-icon
Icon shown after checked menu items in the tree-view representation of the hamburger menu
A PIC S9(9) COMP-4 data item representing the handle of a bitmap
Internal icon showing a check symbol
default-background-color
Background color of menu area and unselected items in the tree-view representation of the hamburger menu
Any numeric value representing either a COBOL color or an RGB color. See Color management for more information.
The RGB color x#F0F0F0
default-font
Font of unselected items in the tree-view representation of the hamburger menu
HANDLE OF FONT
The Arial font, plain, with size 10
default-text-color
Text color of unselected items in the tree-view representation of the hamburger menu
Any numeric value representing either a COBOL color or an RGB color. See Color management for more information.
The RGB color x#4091C9
disabled-background-color
Background color of disabled items in the tree-view representation of the hamburger menu
Any numeric value representing either a COBOL color or an RGB color. See Color management for more information.
The color specified by the default-background-color attribute
disabled-font
Font of disabled items in the tree-view representation of the hamburger menu
HANDLE OF FONT
The font specified by the default-font attribute
disabled-text-color
Text color of disabled items in the tree-view representation of the hamburger menu
Any numeric value representing either a COBOL color or an RGB color. See Color management for more information.
The RGB color x#C0C0C0
dropdown-icon
Icon of collapsed groups in the tree-view representation of the hamburger menu
A PIC S9(9) COMP-4 data item representing the handle of a bitmap
Internal icon showing a chevron right
dropdown-open-icon
Icon of expanded groups in the tree-view representation of the hamburger menu
A PIC S9(9) COMP-4 data item representing the handle of a bitmap
Internal icon showing a chevron down
hamburger-icon
Icon shown in the menu bar when the hamburger menu is not visible
A PIC S9(9) COMP-4 data item representing the handle of a bitmap
Internal icon showing three horizontal bars
hamburger-open-icon
Icon shown in the menu bar when the hamburger menu is visible
A PIC S9(9) COMP-4 data item representing the handle of a bitmap
The icon specified by the hamburger-icon attribute
hover-background-color
Background color of menu items hovered by the mouse in the tree-view representation of the hamburger menu
Any numeric value representing either a COBOL color or an RGB color. See Color management for more information.
The RGB color x#5C8EB9
hover-font
Font of menu items hovered by the mouse in the tree-view representation of the hamburger menu
HANDLE OF FONT
The font specified by the default-font attribute
hover-text-color
Text color of menu items hovered by the mouse in the tree-view representation of the hamburger menu
Any numeric value representing either a COBOL color or an RGB color. See Color management for more information.
The RGB color x#FFFFFF
menu-bar-flavor
Default representation of the menu bar created by the WMENU-NEW function
"menu-bar" or "hamburger"
 
 
"menu-bar"
position
Hamburger button position on the menu bar. By default it’s on the left side of the window.
"left" or "right"
"left"
tool-bar-covering
Tells if the tool-bar on the window should covered or not by the tree-view representation of the hamburger menu
"yes" or "no"
"yes"
style
Style of the hamburger menu. By default the hamburger menu is represented by a tree-view that appears from the side of the window. Setting this attribute to "laf" causes the hamburger menu to be a pop-up menu that appears when the hamburger button is clicked
"web" or "laf"
"web"
width
Width in pixels of the area covered by the hamburger menu with
Any positive integer value
300
Return code:
returnCode can be any signed numeric data item and provides additional information:
<=0
Operation failed.
>0
Operation successful.