
Meet COBOL - Part 3
- Tutorial
Unfortunately, I forgot to indicate several important keywords in the previous article:
for DIVIDE.
DIVIDE WS-B BY WS-A GIVING WS-RESULT REMAINDER <variable>.
Using REMAINDER we specify a variable in which the RESIDUE from division is written.
For any mathematical operations:
Also, adding ROUNDED after the operation, we achieve that the result will be rounded, and not just “discard” the extra tail.
ADD WS-A TO WS-B GIVING WS-RESULT ROUNDED.
And now we continue to learn new things. Fulfilling the promise to dispel the surprise of the strange derivation of variable values, this time we will analyze PICTURE IS (aka PIC) and variable formats.
And again we return to DATA DIVISION.
Consider once again the line with the variable description:
01 - level of the variable;
WS-B is the name of the variable;
PIC is a keyword indicating that the description of the format of the variable follows, the old form is PICTURE IS.
9 (3) - the type of characters in the variable “9” and their number “3”.
LEVEL VARIABLE.
For ordinary variables, the user can access levels from 01 to 49 inclusively and 77. The level of a variable describes its hierarchy in a group of variables, the higher the number, the lower the variable in the “ladder”. For example
01 CUSTOMER-RECORD.
05 CUSTOMER-NAME PIC X (10).
05 CUSTOMER-ADDRESS PIC X (30).
Level 77 declares a variable as ELEMENTARY, that is, it cannot have sub-variables.
Level 88 declares the variable as conditional, and in a rather sophisticated and richly functional form, more about them next time.
There are some other levels that are introduced either by compiler manufacturers, or we do not need them now.
NAME OF VARIABLE.
The variable name can consist of numbers, letters and “-”, but should not begin with “-”.
The variable name must be no longer than 30 characters.
DESCRIPTION OF VARIABLE FORMAT.
Consider what descriptive characters exist for variables in COBOL.
They are divided into two groups: “ordinary” and “editing”.
The usual ones include
9 - one digit;
V is the sign separating the integer part from the decimal (can be applied ONLY once in each variable).
S - “±” sign, must be the very first character in the variable format (can be applied ONLY once in each variable).
X is one alphanumeric character, i.e. number, letter, space, special. characters.
A is a single letter sign or space.
Editing symbols - thanks to them, variables are described that will not participate in the calculations, but allow you to fine-tune the appearance in which the variable will be displayed / printed:
Z - replaces 9'ki with the difference that all leading zeros are removed.
$ - “currency symbol” specified for the compiler, by default, basically a dollar sign, is used ONLY as the FIRST character in the description. It can be used only once. Its value is set in ENVIRONMENT DIVISION. via
* Is an analog of Z, but the leading zeros are replaced by *.
- (minus) - can be indicated by both the first and the last character, but only once. If the number is negative, then minus will be displayed, otherwise empty space.
+ (plus) - the analogue of “-” (minus), BUT in the case of a positive number, “+” will be displayed, and in the case of a negative number, “-” will be displayed.
. (dot) is the decimal point. In its place, the “dot” will be displayed.
, (comma) - a comma. Maybe a little in a variable.
/ (slash) - a slash sign. Maybe a few. Outputs a “slash”, popular in dates.
0 (zero) - “zero”. Just at this point 0.
B will be displayed. (From blank, empty) - “space”.
But most importantly, as you can understand, all these symbols are combined and allow you to get very flexible forms and types. There is actually only one rule here - numerical variables should not exceed 18 characters, alphanumeric - 160 characters. But here again, much depends on the compiler and its parameters.
DELICIOUS ADDITIONS or IS LIFE AFTER PIC'a!
In addition, when describing a variable after its format, additional “options” can be added:
BLANK WHEN ZERO - if the variable is 0, then an empty space will be displayed instead of it, not zeros.
VALUE “value” - immediately assigns a specific value to a variable.
There are others, but mentioning them now would be useless.
So now, let's just feel them all in different forms.
And what do we get as a result.
As you can see, the output of the “formatted” and raw variables is different and customizable.
Naturally, this is not just your right, but the obligation to play around with the variables and see how they will behave.
And by the way, if you carefully watched the output of your program, you might have noticed a very unpleasant “trifle” - values that did not fit into the variable, if this did not happen for you, then try to experiment.
Until next meeting! There will be many more interesting things ahead)
Vorontsov “nerfur” Vyacheslav. 2011.
for DIVIDE.
DIVIDE WS-B BY WS-A GIVING WS-RESULT REMAINDER <variable>.
Using REMAINDER we specify a variable in which the RESIDUE from division is written.
For any mathematical operations:
Also, adding ROUNDED after the operation, we achieve that the result will be rounded, and not just “discard” the extra tail.
ADD WS-A TO WS-B GIVING WS-RESULT ROUNDED.
And now we continue to learn new things. Fulfilling the promise to dispel the surprise of the strange derivation of variable values, this time we will analyze PICTURE IS (aka PIC) and variable formats.
And again we return to DATA DIVISION.
Consider once again the line with the variable description:
01 - level of the variable;
WS-B is the name of the variable;
PIC is a keyword indicating that the description of the format of the variable follows, the old form is PICTURE IS.
9 (3) - the type of characters in the variable “9” and their number “3”.
LEVEL VARIABLE.
For ordinary variables, the user can access levels from 01 to 49 inclusively and 77. The level of a variable describes its hierarchy in a group of variables, the higher the number, the lower the variable in the “ladder”. For example
01 CUSTOMER-RECORD.
05 CUSTOMER-NAME PIC X (10).
05 CUSTOMER-ADDRESS PIC X (30).
Level 77 declares a variable as ELEMENTARY, that is, it cannot have sub-variables.
Level 88 declares the variable as conditional, and in a rather sophisticated and richly functional form, more about them next time.
There are some other levels that are introduced either by compiler manufacturers, or we do not need them now.
NAME OF VARIABLE.
The variable name can consist of numbers, letters and “-”, but should not begin with “-”.
The variable name must be no longer than 30 characters.
DESCRIPTION OF VARIABLE FORMAT.
Consider what descriptive characters exist for variables in COBOL.
They are divided into two groups: “ordinary” and “editing”.
The usual ones include
9 - one digit;
V is the sign separating the integer part from the decimal (can be applied ONLY once in each variable).
S - “±” sign, must be the very first character in the variable format (can be applied ONLY once in each variable).
X is one alphanumeric character, i.e. number, letter, space, special. characters.
A is a single letter sign or space.
Editing symbols - thanks to them, variables are described that will not participate in the calculations, but allow you to fine-tune the appearance in which the variable will be displayed / printed:
Z - replaces 9'ki with the difference that all leading zeros are removed.
$ - “currency symbol” specified for the compiler, by default, basically a dollar sign, is used ONLY as the FIRST character in the description. It can be used only once. Its value is set in ENVIRONMENT DIVISION. via
* Is an analog of Z, but the leading zeros are replaced by *.
- (minus) - can be indicated by both the first and the last character, but only once. If the number is negative, then minus will be displayed, otherwise empty space.
+ (plus) - the analogue of “-” (minus), BUT in the case of a positive number, “+” will be displayed, and in the case of a negative number, “-” will be displayed.
. (dot) is the decimal point. In its place, the “dot” will be displayed.
, (comma) - a comma. Maybe a little in a variable.
/ (slash) - a slash sign. Maybe a few. Outputs a “slash”, popular in dates.
0 (zero) - “zero”. Just at this point 0.
B will be displayed. (From blank, empty) - “space”.
But most importantly, as you can understand, all these symbols are combined and allow you to get very flexible forms and types. There is actually only one rule here - numerical variables should not exceed 18 characters, alphanumeric - 160 characters. But here again, much depends on the compiler and its parameters.
DELICIOUS ADDITIONS or IS LIFE AFTER PIC'a!
In addition, when describing a variable after its format, additional “options” can be added:
BLANK WHEN ZERO - if the variable is 0, then an empty space will be displayed instead of it, not zeros.
VALUE “value” - immediately assigns a specific value to a variable.
There are others, but mentioning them now would be useless.
So now, let's just feel them all in different forms.
000100 IDENTIFICATION DIVISION. 000200 PROGRAM-ID. VARIABLES-TEST. 000300 AUTHOR. ME 000400 ENVIRONMENT DIVISION. 000500 DATA DIVISION. 000600 WORKING-STORAGE SECTION. 000,700 01 HUMAN-CONTAINER. 000800 05 HUMAN-NAME PIC A (30). 000 900 05 HUMAN-ADDRESS PIC X (160). 001000 77 SQUARE-METERS PIC 9 (18). 001100 77 SQUARE-PRICE PIC 9 (15) V9 (2). 001150 77 FLAT-PRICE PIC 9 (15) V9 (2). 001200 77 TAX-PERCENT PIC 9 (2). 001300 77 TAX-SUMM PIC 9 (15) V9 (2). 001350 77 NEGATIVE-VALUE PIC S9 (10) V9 (6). 001400 * --- OOOOMG! --- 001500 77 SQUARE-METERS-OUT PIC Z (17) 9. 001600 77 SQUARE-PRICE-OUT PIC Z (14) 9.Z (2). 001650 77 FLAT-PRICE-OUT-1 PIC Z (3), Z (3), Z (3), Z (3) .9 (2). 001660 77 FLAT-PRICE-OUT-2 PIC Z (3) BZ (3) BZ (3) BZ (3) .9 (2). 001700 77 TAX-PERCENT-OUT PIC Z (2). 001800 77 TAX-SUMM-OUT PIC Z (14) 9.9 (2). 001900 77 NEGATIVE-VALUE-OUT-1 PIC + Z (10) .9 (6). 002000 77 NEGATIVE-VALUE-OUT-2 PIC -Z (10). * (6). 002100 * -------------------------------- 002200 PROCEDURE DIVISION. 002,300 BEGIN. 002400 DISPLAY "Please enter Name:". 002500 ACCEPT HUMAN-NAME. 002550 DISPLAY "Please enter Address:". 002600 ACCEPT HUMAN-ADDRESS. 002700 DISPLAY "Please enter square meters of flat:". 002800 ACCEPT SQUARE-METERS. 002900 DISPLAY "Please enter square meter's price:". 003000 ACCEPT SQUARE-PRICE. 003100 DISPLAY "Please enter percent of tax:". 003200 ACCEPT TAX-PERCENT. 003300 DISPLAY "Enter any really big NEGATIVE value:". 003400 ACCEPT NEGATIVE-VALUE. 003500 DISPLAY "---------------------------------------". 003600 DISPLAY "". 003700 DISPLAY HUMAN-NAME. 003800 DISPLAY HUMAN-ADDRESS. 003900 DISPLAY "SQUARE-METERS:", SQUARE-METERS. 004000 MOVE SQUARE-METERS TO SQUARE-METERS-OUT. 004100 DISPLAY "SQUARE-METERS-OUT:", SQUARE-METERS-OUT. 004200 DISPLAY "SQUARE-PRICE:", SQUARE-PRICE. 004300 MOVE SQUARE-PRICE TO SQUARE-PRICE-OUT. 004400 DISPLAY "SQUARE-PRICE-OUT:", SQUARE-PRICE-OUT. 004500 MULTIPLY SQUARE-METERS BY SQUARE-PRICE GIVING FLAT-PRICE. 004600 DISPLAY "FLAT-PRICE:", FLAT-PRICE. 004700 MOVE FLAT-PRICE TO FLAT-PRICE-OUT-1 FLAT-PRICE-OUT-2. 004800 DISPLAY "FLAT-PRICE-OUT-1:", FLAT-PRICE-OUT-1. 004850 DISPLAY "FLAT-PRICE-OUT-2:", FLAT-PRICE-OUT-2. 004900 DISPLAY "TAX-PERCENT:", TAX-PERCENT. 005000 MOVE TAX-PERCENT TO TAX-PERCENT-OUT. 005100 DISPLAY "TAX-PERCENT-OUT:", TAX-PERCENT-OUT. 005200 DISPLAY "TAX-SUMM:", TAX-SUMM. 005300 MOVE TAX-SUMM TO TAX-SUMM-OUT. 005400 DISPLAY "TAX-SUMM-OUT:", TAX-SUMM-OUT. 005500 DISPLAY "NEGATIVE-VALUE:", NEGATIVE-VALUE. 005600 MOVE NEGATIVE-VALUE TO NEGATIVE-VALUE-OUT-1 NEGATIVE-VALUE-OUT-2. 005700 DISPLAY "NEGATIVE-VALUE-OUT-1:", NEGATIVE-VALUE-OUT-1. 005800 DISPLAY "NEGATIVE-VALUE-OUT-2:", NEGATIVE-VALUE-OUT-2. 005900 STOP RUN.
And what do we get as a result.
Please enter Name: Slava Please enter Address: Moscow 15 Please enter square meters of flat: 44 Please enter square meter's price: 1234123 Please enter percent of tax: 20 Enter any really big NEGATIVE value: -123123213213 --------------------------------------- Slava Moscow 15 SQUARE-METERS: 000000000000000044 SQUARE-METERS-OUT: 44 SQUARE-PRICE: 000000001234123.00 SQUARE-PRICE-OUT: 1234123.00 FLAT-PRICE: 000000054301412.00 FLAT-PRICE-OUT-1: 54,301,412.00 FLAT-PRICE-OUT-2: 54 301 412.00 TAX-PERCENT: 20 TAX-PERCENT-OUT: 20 TAX-SUMM: 000000000000000.00 TAX-SUMM-OUT: 0.00 NEGATIVE-VALUE: -3123213213.000000 NEGATIVE-VALUE-OUT-1: -3123213213.000000 NEGATIVE-VALUE-OUT-2: -3123213213.000000
As you can see, the output of the “formatted” and raw variables is different and customizable.
Naturally, this is not just your right, but the obligation to play around with the variables and see how they will behave.
And by the way, if you carefully watched the output of your program, you might have noticed a very unpleasant “trifle” - values that did not fit into the variable, if this did not happen for you, then try to experiment.
Until next meeting! There will be many more interesting things ahead)
Vorontsov “nerfur” Vyacheslav. 2011.