The following COBOL statements can act on the properties that are assigned to controls and forms:
MOVE
ADD
SUBTRACT
COMPUTE
IF
DISPLAY
EVALUATE
There are some restrictions on the syntax and usage of these statements when they are used to set and refer to properties.
MOVE CONTROL-PROPERTY TO RECEIVE-CONTROL
The 'receive-control' must be a data control.
Only one 'receive-control' can be identified per MOVE statement.
The CORRESPONDING statement cannot be used with a MOVE statement.
Refer to the "NetCOBOL Language Reference" for additional information.
Move the current value of the horizontal scroll bar control (CmScroll1) to the variable defined in the WORKING-STORAGE section.
DATA DIVISION. WORKING-STORAGE SECTION. 01 CURR-SCROLL-VALUE PIC S9(9) COMP-5. : PROCEDURE DIVISION. : MOVE "Value" OF CmScroll1 TO CURR-SCROLL-VALUE.
Note
Every property has attributes. In the above example, the attribute for Value is S9(9) COMP-5.
ADD CONTROL-PROPERTY TO {DATA-NAME [ROUNDED]}
[ON SIZE ERROR UNCONDITIONAL-STATEMENT]
[NOT ON SIZE ERROR UNCONDITIONAL-STATEMENT]
[END-ADD]
No more than one control can precede the TO statement.
The GIVING statement cannot be used with the ADD statement.
The CORRESPONDING statement cannot be used with the ADD statement.
Refer to the "NetCOBOL Language Reference" for additional information.
ADD the large step of vertical scroll bar control (CmScroll2) to the CURR-VALUE, which is maintained in the WORKING-STORAGE section.
DATA DIVISION. WORKING-STORAGE SECTION. 01 CURR-VALUE PIC S9(9) COMP-5 VALUE IS 0. : PROCEDURE DIVISION. : ADD "LargeStep" OF CmScroll2 TO CURR-VALUE. :
SUBTRACT CONTROL-PROPERTY
FROM {CONTROL-NAME [ROUNDED]} ...
[ON SIZE ERROR UNCONDITIONAL-STATEMENT ]
[NOT ON SIZE ERROR UNCONDITIONAL-STATEMENT ]
[END-SUBTRACT]
No more than one control can precede the FROM clause.
The GIVING statement cannot be used with the SUBTRACT statement.
The CORRESPONDING statement cannot be used with a SUBTRACT statement.
Refer to the "NetCOBOL Language Reference" for additional information.
SUBTRACT the large step of the vertical scroll bar control (CmScroll2) from the CURR-VALUE, which is maintained in the WORKING-STORAGE section.
DATA DIVISION. WORKING-STORAGE SECTION. 01 CURR-VALUE PIC S9(9) COMP-5 VALUE IS 0. : PROCEDURE DIVISION. : SUBTRACT "LARGESTEP" OF CmScroll2 FROM CURR-VALUE. :
The COMPUTE statement is used to calculate the numeric value of a control using the numeric value of another.
COMPUTE Unique-Data-Name = Arithmetic-formula
property may be included in an Arithmetic-Formula.
Only a single data name (i.e. "Unique-Data-Name") may be specified in the receiving field.
Refer to the "NetCOBOL Language Reference" for additional information.
Set the font size of StaticText control (CmStatic1) to be 2 points larger than the font size of CommandButton control (CmCommand1).
DATA DIVISION.
WORKING-STORAGE SECTION.
PROCEDURE DIVISION.
...
COMPUTE "Size" OF "Font" OF CmStatic1 = "Size" OF "Font" OF CmCommand1 + 2
IF CONTROL-PROPERTY COMPARISON OPERATOR
RIGHT-SIDE-OF-CONDITION
THEN {{STATEMENT-1} ... | NEXT SENTENCE }
{
{ELSE {STATEMENT-2} ... [END-IF]}|
{ELSE NEXT SENTENCE }|
{END-IF}}
The property of a control can be used as the left side of an IF statement. Refer to the "NetCOBOL Language Reference" for a complete list of the rules for using IF statements.
If the CheckBox control (CmCheck1) is checked then the image called 'IMAGE-BMP' is displayed. If it is not checked then nothing is displayed.
IF "Value" OF CmCheck1 = 1 MOVE "IMAGE-BMP" TO "ImageName" OF CmImage1 END-IF.
DISPLAY {UNIQUE-NAME | CONSTANT | CONTROL-PROPERTY}
[UPON CALL-NAME]
Refer to the "NetCOBOL Language Reference" for a complete list of rules for using the DISPLAY statement.
Display the image name of image control (CmImage1) on the console window.
DISPLAY "Current displayed image is " "ImageName" OF CmImage1.
EVALUATE CONTROL-PROPERTY
WHEN OBJECT-TO-SELECT
...
WHEN OBJECT-TO-SELECT
...
:
END-EVALUATE
You can use the EVALUATE statement to set the properties of a control based on the condition under evaluation.
The ALSO statement cannot be used with an EVALUATE statement.
Refer to the "NetCOBOL Language Reference" for a complete list of rules for using the EVALUATE statement.
EVALUATE "Caption" OF COLOR-NAME WHEN "BLACK" MOVE "BLACK " TO "Caption" OF COLOR-TEXT WHEN "RED" MOVE "RED" TO "Caption" OF COLOR-TEXT WHEN "YELLOW" MOVE "YELLOW" TO "Caption" OF COLOR-TEXT WHEN OTHER MOVE "INVALID COLOR" TO "Caption" OF COLOR-NAME END-EVALUATE