MainframeMaster

COBOL DOWN Keyword

Master screen positioning and cursor movement with the DOWN keyword for effective terminal-based user interface development in COBOL applications.

Overview

The DOWN keyword in COBOL is used for screen positioning and cursor movement in terminal-based applications. It provides precise control over vertical positioning, allowing programs to move the cursor or screen position downward by a specified number of lines. This functionality is essential for creating interactive user interfaces, forms, and screen-based applications in mainframe environments.

DOWN is particularly valuable in environments like CICS (Customer Information Control System), IMS (Information Management System), and other transaction processing systems where screen control is crucial for user interaction. It enables developers to create sophisticated terminal interfaces with precise positioning control.

Understanding DOWN and its applications is fundamental for developing professional mainframe applications that require user-friendly interfaces, data entry forms, and interactive menus. It works in conjunction with other positioning keywords to provide comprehensive screen control capabilities.

Basic DOWN Syntax and Usage

Simple DOWN Movement

The basic syntax for DOWN involves specifying the number of lines to move:

cobol
1
2
3
DISPLAY "Current Position" AT LINE 10 COL 20 DISPLAY "Moved Down" DOWN 3 LINES DISPLAY "Further Down" DOWN 2

This example demonstrates moving the cursor down from its current position. The first DISPLAY establishes a starting position, then subsequent displays move progressively downward.

DOWN with Numeric Variables

DOWN can use variables to specify dynamic positioning:

cobol
1
2
3
4
5
6
7
8
9
10
WORKING-STORAGE SECTION. 01 WS-LINE-OFFSET PIC 9(2) VALUE 5. 01 WS-MENU-SPACING PIC 9(1) VALUE 2. PROCEDURE DIVISION. DISPLAY-MENU. DISPLAY "MAIN MENU" AT LINE 5 COL 30 DISPLAY "1. Customer Entry" DOWN WS-MENU-SPACING DISPLAY "2. Order Processing" DOWN WS-MENU-SPACING DISPLAY "3. Reports" DOWN WS-MENU-SPACING.

Using variables with DOWN provides flexibility for adjusting screen layouts dynamically based on program logic or user preferences.

Screen Positioning Applications

Menu Creation

DOWN is commonly used to create well-formatted menus:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
DISPLAY-MAIN-MENU. DISPLAY SPACES WITH BLANK SCREEN DISPLAY "╔══════════════════════════════════╗" AT LINE 5 COL 25 DISPLAY "║ CUSTOMER SYSTEM ║" DOWN 1 DISPLAY "║ ║" DOWN 1 DISPLAY "║ 1. Add New Customer ║" DOWN 1 DISPLAY "║ 2. Update Customer ║" DOWN 1 DISPLAY "║ 3. Delete Customer ║" DOWN 1 DISPLAY "║ 4. Customer Reports ║" DOWN 1 DISPLAY "║ 5. Exit System ║" DOWN 1 DISPLAY "║ ║" DOWN 1 DISPLAY "╚══════════════════════════════════╝" DOWN 1.

This creates a professional-looking menu with consistent spacing using DOWN for vertical positioning.

Form Layout Design

DOWN helps create organized data entry forms:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
DISPLAY-CUSTOMER-FORM. DISPLAY SPACES WITH BLANK SCREEN DISPLAY "CUSTOMER INFORMATION ENTRY" AT LINE 3 COL 25 DISPLAY "Customer ID : " AT LINE 6 COL 10 DISPLAY "Customer Name : " DOWN 2 DISPLAY "Address Line 1 : " DOWN 2 DISPLAY "Address Line 2 : " DOWN 2 DISPLAY "City : " DOWN 2 DISPLAY "State : " DOWN 2 DISPLAY "ZIP Code : " DOWN 2 DISPLAY "Phone Number : " DOWN 2.

This form uses DOWN to create consistent spacing between input fields, making the form easy to read and navigate.

Advanced DOWN Techniques

Conditional Positioning

DOWN can be used conditionally based on program logic:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
WORKING-STORAGE SECTION. 01 WS-ERROR-FLAG PIC X(1) VALUE "N". 01 WS-ERROR-COUNT PIC 9(2) VALUE ZERO. 01 WS-CURRENT-LINE PIC 9(2) VALUE 10. PROCEDURE DIVISION. DISPLAY-MESSAGES. DISPLAY "Processing Status:" AT LINE WS-CURRENT-LINE COL 10 IF WS-ERROR-FLAG = "Y" ADD 2 TO WS-CURRENT-LINE DISPLAY "ERROR: Invalid input detected" DOWN 2 WITH FOREGROUND-COLOR RED ADD 1 TO WS-ERROR-COUNT ELSE DISPLAY "Processing completed successfully" DOWN 2 WITH FOREGROUND-COLOR GREEN END-IF.

This example shows conditional use of DOWN based on error conditions, creating dynamic screen layouts.

Scrolling and Pagination

DOWN can be used to implement scrolling functionality:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
WORKING-STORAGE SECTION. 01 WS-PAGE-SIZE PIC 9(2) VALUE 15. 01 WS-CURRENT-ROW PIC 9(2) VALUE 1. 01 WS-RECORDS-SHOWN PIC 9(2) VALUE ZERO. 01 WS-START-LINE PIC 9(2) VALUE 5. PROCEDURE DIVISION. DISPLAY-PAGE. MOVE WS-START-LINE TO WS-CURRENT-ROW MOVE ZERO TO WS-RECORDS-SHOWN PERFORM UNTIL WS-RECORDS-SHOWN >= WS-PAGE-SIZE OR END-OF-FILE PERFORM READ-NEXT-RECORD IF NOT END-OF-FILE DISPLAY CUSTOMER-RECORD AT LINE WS-CURRENT-ROW COL 5 ADD 1 TO WS-CURRENT-ROW ADD 1 TO WS-RECORDS-SHOWN END-IF END-PERFORM DISPLAY "Press ENTER for next page..." DOWN 2 WITH HIGHLIGHT.

This creates a pagination system using DOWN for consistent record positioning and page navigation.

CICS Integration with DOWN

CICS Screen Handling

In CICS environments, DOWN works with map definitions and screen control:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
WORKING-STORAGE SECTION. 01 WS-MAP-FIELDS. 05 WS-CURSOR-POS. 10 WS-CURSOR-LINE PIC 9(2) VALUE 10. 10 WS-CURSOR-COL PIC 9(2) VALUE 20. PROCEDURE DIVISION. SEND-CUSTOMER-MAP. EXEC CICS SEND MAP('CUSTMAP') MAPSET('CUSTSET') CURSOR(WS-CURSOR-POS) ERASE END-EXEC * Position for error messages IF EIBRESP = DFHRESP(NORMAL) DISPLAY "Customer data sent successfully" AT LINE 20 COL 10 ELSE DISPLAY "Error sending customer map" DOWN 2 WITH FOREGROUND-COLOR RED DISPLAY "Please contact system administrator" DOWN 1 END-IF.

This example shows how DOWN can be used in conjunction with CICS commands for screen positioning.

Interactive Field Navigation

DOWN helps create logical field navigation patterns:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
FIELD-NAVIGATION. EVALUATE WS-CURRENT-FIELD WHEN "CUSTID" MOVE "CUSTNAME" TO WS-CURRENT-FIELD DISPLAY CURSOR AT LINE 8 COL 25 WHEN "CUSTNAME" MOVE "ADDRESS1" TO WS-CURRENT-FIELD DISPLAY CURSOR DOWN 2 WHEN "ADDRESS1" MOVE "ADDRESS2" TO WS-CURRENT-FIELD DISPLAY CURSOR DOWN 2 WHEN "ADDRESS2" MOVE "CITY" TO WS-CURRENT-FIELD DISPLAY CURSOR DOWN 2 WHEN OTHER MOVE "CUSTID" TO WS-CURRENT-FIELD DISPLAY CURSOR AT LINE 6 COL 25 END-EVALUATE.

This creates a logical tab order using DOWN to move between form fields in a predictable pattern.

Error Handling and Validation

Error Message Positioning

DOWN is useful for positioning error messages consistently:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
WORKING-STORAGE SECTION. 01 WS-ERROR-LINE PIC 9(2) VALUE 22. 01 WS-ERROR-MESSAGES. 05 WS-ERR-REQUIRED PIC X(30) VALUE "* Required field missing". 05 WS-ERR-INVALID PIC X(30) VALUE "* Invalid data format". 05 WS-ERR-DUPLICATE PIC X(30) VALUE "* Duplicate entry found". PROCEDURE DIVISION. VALIDATE-INPUT. * Clear error area first DISPLAY SPACES AT LINE WS-ERROR-LINE COL 1 IF CUST-ID = SPACES DISPLAY WS-ERR-REQUIRED AT LINE WS-ERROR-LINE COL 10 WITH FOREGROUND-COLOR RED ADD 1 TO WS-ERROR-LINE END-IF IF CUST-NAME = SPACES DISPLAY WS-ERR-REQUIRED DOWN 1 WITH FOREGROUND-COLOR RED ADD 1 TO WS-ERROR-LINE END-IF IF NOT VALID-ZIP-CODE DISPLAY WS-ERR-INVALID DOWN 1 WITH FOREGROUND-COLOR RED END-IF.

This approach uses DOWN to stack error messages vertically, creating a clear error display area.

Validation Feedback

DOWN can provide immediate validation feedback:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
REAL-TIME-VALIDATION. PERFORM VALIDATE-CUSTOMER-ID IF VALIDATION-ERROR DISPLAY "✗ Invalid Customer ID format" DOWN 1 WITH FOREGROUND-COLOR RED DISPLAY " Use format: CUST-99999" DOWN 1 ELSE DISPLAY "✓ Customer ID valid" DOWN 1 WITH FOREGROUND-COLOR GREEN END-IF PERFORM VALIDATE-PHONE-NUMBER IF VALIDATION-ERROR DISPLAY "✗ Invalid phone number" DOWN 1 WITH FOREGROUND-COLOR RED DISPLAY " Use format: (999) 999-9999" DOWN 1 ELSE DISPLAY "✓ Phone number valid" DOWN 1 WITH FOREGROUND-COLOR GREEN END-IF.

This provides immediate visual feedback using DOWN to position validation messages next to input fields.

Performance and Best Practices

Efficient Screen Updates

Optimize screen updates when using DOWN extensively:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
WORKING-STORAGE SECTION. 01 WS-SCREEN-BUFFER. 05 WS-BUFFER-LINES OCCURS 24 TIMES. 10 WS-LINE-DATA PIC X(80). 01 WS-CURRENT-LINE PIC 9(2) VALUE 1. PROCEDURE DIVISION. BUILD-SCREEN-BUFFER. * Build entire screen in memory first MOVE "CUSTOMER REPORT" TO WS-LINE-DATA(5) MOVE ALL "-" TO WS-LINE-DATA(6) PERFORM VARYING WS-RECORD-COUNT FROM 1 BY 1 UNTIL WS-RECORD-COUNT > 15 ADD 2 TO WS-CURRENT-LINE STRING CUST-ID(WS-RECORD-COUNT) " " CUST-NAME(WS-RECORD-COUNT) " " CUST-BALANCE(WS-RECORD-COUNT) INTO WS-LINE-DATA(WS-CURRENT-LINE) END-PERFORM * Display entire screen at once PERFORM DISPLAY-SCREEN-BUFFER. DISPLAY-SCREEN-BUFFER. DISPLAY SPACES WITH BLANK SCREEN PERFORM VARYING WS-CURRENT-LINE FROM 1 BY 1 UNTIL WS-CURRENT-LINE > 24 IF WS-LINE-DATA(WS-CURRENT-LINE) NOT = SPACES DISPLAY WS-LINE-DATA(WS-CURRENT-LINE) AT LINE WS-CURRENT-LINE COL 1 END-IF END-PERFORM.

This approach builds the entire screen in memory before displaying, reducing screen flicker and improving performance.

Memory Management

Manage screen positioning variables efficiently:

cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
WORKING-STORAGE SECTION. 01 WS-SCREEN-CONTROL. 05 WS-SCREEN-LIMITS. 10 WS-MAX-LINES PIC 9(2) VALUE 24. 10 WS-MAX-COLS PIC 9(2) VALUE 80. 10 WS-MIN-LINE PIC 9(2) VALUE 1. 10 WS-MIN-COL PIC 9(2) VALUE 1. 05 WS-CURRENT-POS. 10 WS-CURR-LINE PIC 9(2) VALUE 1. 10 WS-CURR-COL PIC 9(2) VALUE 1. PROCEDURE DIVISION. SAFE-DOWN-MOVEMENT. IF WS-CURR-LINE + WS-DOWN-AMOUNT <= WS-MAX-LINES ADD WS-DOWN-AMOUNT TO WS-CURR-LINE DISPLAY WS-MESSAGE AT LINE WS-CURR-LINE COL WS-CURR-COL ELSE PERFORM SCROLL-SCREEN-UP DISPLAY WS-MESSAGE AT LINE WS-MAX-LINES COL WS-CURR-COL END-IF.

This ensures safe cursor movement that respects screen boundaries and handles overflow conditions.

Hands-on Exercise

Exercise: Interactive Menu System

Create an interactive menu system using DOWN for positioning that includes error handling and user navigation.

Requirements:

  • Create a main menu with at least 5 options using DOWN for spacing
  • Implement error messages positioned with DOWN
  • Include input validation with positioned feedback
  • Use DOWN for creating consistent screen layouts
  • Handle screen boundary conditions safely
View Solution
cobol
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
WORKING-STORAGE SECTION. 01 WS-MENU-CONTROL. 05 WS-USER-CHOICE PIC X(1). 05 WS-VALID-CHOICE PIC X(1) VALUE "N". 05 WS-EXIT-FLAG PIC X(1) VALUE "N". 01 WS-SCREEN-POSITIONS. 05 WS-TITLE-LINE PIC 9(2) VALUE 3. 05 WS-MENU-START PIC 9(2) VALUE 7. 05 WS-PROMPT-LINE PIC 9(2) VALUE 15. 05 WS-ERROR-LINE PIC 9(2) VALUE 17. PROCEDURE DIVISION. MAIN-MENU-LOOP. PERFORM UNTIL WS-EXIT-FLAG = "Y" PERFORM DISPLAY-MAIN-MENU PERFORM GET-USER-CHOICE PERFORM VALIDATE-CHOICE IF WS-VALID-CHOICE = "Y" PERFORM PROCESS-MENU-CHOICE ELSE PERFORM DISPLAY-ERROR-MESSAGE END-IF END-PERFORM GOBACK. DISPLAY-MAIN-MENU. DISPLAY SPACES WITH BLANK SCREEN DISPLAY "═══════════════════════════════════" AT LINE WS-TITLE-LINE COL 25 DISPLAY " INVENTORY SYSTEM " DOWN 1 DISPLAY "═══════════════════════════════════" DOWN 1 DISPLAY "1. Add New Item" AT LINE WS-MENU-START COL 30 DISPLAY "2. Update Item" DOWN 2 DISPLAY "3. Delete Item" DOWN 2 DISPLAY "4. Search Items" DOWN 2 DISPLAY "5. Generate Reports" DOWN 2 DISPLAY "6. Exit System" DOWN 2 DISPLAY "Enter your choice (1-6): " AT LINE WS-PROMPT-LINE COL 25 WITH NO ADVANCING. GET-USER-CHOICE. ACCEPT WS-USER-CHOICE DISPLAY SPACES AT LINE WS-ERROR-LINE COL 1. VALIDATE-CHOICE. IF WS-USER-CHOICE >= "1" AND WS-USER-CHOICE <= "6" MOVE "Y" TO WS-VALID-CHOICE ELSE MOVE "N" TO WS-VALID-CHOICE END-IF. DISPLAY-ERROR-MESSAGE. DISPLAY "✗ Invalid choice. Please enter 1-6." AT LINE WS-ERROR-LINE COL 25 WITH FOREGROUND-COLOR RED DISPLAY "Press ENTER to continue..." DOWN 1 WITH HIGHLIGHT ACCEPT WS-USER-CHOICE. PROCESS-MENU-CHOICE. EVALUATE WS-USER-CHOICE WHEN "1" PERFORM ADD-NEW-ITEM WHEN "2" PERFORM UPDATE-ITEM WHEN "3" PERFORM DELETE-ITEM WHEN "4" PERFORM SEARCH-ITEMS WHEN "5" PERFORM GENERATE-REPORTS WHEN "6" MOVE "Y" TO WS-EXIT-FLAG DISPLAY "Thank you for using Inventory System" AT LINE 20 COL 25 WITH FOREGROUND-COLOR GREEN DISPLAY "System shutting down..." DOWN 2 END-EVALUATE. ADD-NEW-ITEM. DISPLAY SPACES WITH BLANK SCREEN DISPLAY "ADD NEW INVENTORY ITEM" AT LINE 3 COL 30 DISPLAY "Item Code : " AT LINE 6 COL 20 DISPLAY "Description : " DOWN 2 DISPLAY "Quantity : " DOWN 2 DISPLAY "Unit Price : " DOWN 2 DISPLAY "Category : " DOWN 2 DISPLAY "Press ENTER when complete..." DOWN 3 WITH HIGHLIGHT ACCEPT WS-USER-CHOICE.

Quiz

Test Your Knowledge

1. What is the primary purpose of the DOWN keyword in COBOL?

2. Which statement correctly uses DOWN with a numeric value?

3. In which environments is DOWN primarily supported?

View Answers

1. To move cursor or screen position downward - DOWN is used for vertical positioning and cursor movement in screen-based applications.

2. DISPLAY "Text" DOWN 3 LINES - This is the correct syntax for moving down 3 lines from the current position.

3. Systems with screen handling capabilities like CICS - DOWN requires screen handling support and is commonly used in CICS, IMS, and similar environments.

Frequently Asked Questions