MainframeMaster

COBOL Tutorial

COBOL NEGATIVE Class Condition

The NEGATIVE class condition represents sophisticated numeric validation and sign testing capabilities within COBOL programming environments, providing comprehensive negative value detection, advanced sign processing features, and intelligent numeric validation mechanisms that enable reliable data verification, efficient sign-based conditional logic, and robust numeric data handling. This condition embodies modern data validation principles by supporting precise sign testing, enabling comprehensive numeric validation workflows, and facilitating business logic requirements while maintaining computational efficiency, ensuring accurate numeric processing, and enabling scalable validation architectures across enterprise applications requiring reliable negative number detection, financial data processing, and predictable sign-based decision making throughout complex business calculations and data validation scenarios.

NEGATIVE Condition Syntax

NEGATIVE Class Condition Usage
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
*> Basic NEGATIVE condition syntax IF data-name IS NEGATIVE imperative-statements END-IF. IF data-name IS NOT NEGATIVE imperative-statements END-IF. *> Examples with different numeric types 01 WS-SIGNED-NUMBERS. 05 WS-BALANCE PIC S9(8)V99 COMP-3. 05 WS-TEMPERATURE PIC S9(3) DISPLAY SIGN LEADING. 05 WS-PROFIT-LOSS PIC S9(10)V99 USAGE COMP. 05 WS-ADJUSTMENT PIC S9(6)V99. PROCEDURE DIVISION. *> Test for negative balance IF WS-BALANCE IS NEGATIVE DISPLAY "Account overdrawn" PERFORM OVERDRAFT-PROCESSING END-IF *> Test for negative temperature IF WS-TEMPERATURE IS NEGATIVE DISPLAY "Temperature below freezing" PERFORM FREEZING-ALERT END-IF *> Test for losses IF WS-PROFIT-LOSS IS NEGATIVE DISPLAY "Financial loss detected" PERFORM LOSS-ANALYSIS ELSE DISPLAY "Profitable operation" END-IF *> Multiple conditions IF WS-BALANCE IS NEGATIVE AND WS-ADJUSTMENT IS NEGATIVE DISPLAY "Both balance and adjustment are negative" END-IF. *> NEGATIVE in EVALUATE statements EVALUATE TRUE WHEN WS-BALANCE IS POSITIVE PERFORM CREDIT-PROCESSING WHEN WS-BALANCE IS NEGATIVE PERFORM DEBIT-PROCESSING WHEN WS-BALANCE IS ZERO PERFORM ZERO-BALANCE-PROCESSING END-EVALUATE. *> NEGATIVE with arrays 01 WS-TRANSACTION-AMOUNTS OCCURS 100 TIMES PIC S9(6)V99. PERFORM VARYING WS-INDEX FROM 1 BY 1 UNTIL WS-INDEX > 100 IF WS-TRANSACTION-AMOUNTS(WS-INDEX) IS NEGATIVE ADD 1 TO WS-NEGATIVE-COUNT ADD WS-TRANSACTION-AMOUNTS(WS-INDEX) TO WS-NEGATIVE-TOTAL END-IF END-PERFORM.
Class Condition
Sign Testing
Validation

Comprehensive NEGATIVE Examples

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
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
IDENTIFICATION DIVISION. PROGRAM-ID. NEGATIVE-CONDITION-DEMO. DATA DIVISION. WORKING-STORAGE SECTION. *> Financial data with signed fields 01 WS-FINANCIAL-DATA. 05 WS-ACCOUNT-BALANCE PIC S9(10)V99 COMP-3. 05 WS-MONTHLY-CHANGE PIC S9(8)V99 COMP-3. 05 WS-INTEREST-EARNED PIC S9(6)V99 COMP-3. 05 WS-FEES-CHARGED PIC S9(5)V99 COMP-3. 05 WS-NET-WORTH PIC S9(12)V99 COMP-3. *> Temperature monitoring system 01 WS-TEMPERATURE-DATA. 05 WS-CURRENT-TEMP PIC S9(3) DISPLAY SIGN LEADING. 05 WS-TEMP-CHANGE PIC S9(2) DISPLAY SIGN LEADING. 05 WS-MIN-TEMP PIC S9(3) DISPLAY SIGN LEADING. 05 WS-MAX-TEMP PIC S9(3) DISPLAY SIGN LEADING. 05 WS-DAILY-READINGS OCCURS 24 TIMES. 10 WS-HOURLY-TEMP PIC S9(3) DISPLAY SIGN LEADING. *> Business metrics 01 WS-BUSINESS-METRICS. 05 WS-REVENUE PIC S9(10)V99. 05 WS-EXPENSES PIC S9(10)V99. 05 WS-PROFIT-LOSS PIC S9(10)V99. 05 WS-GROWTH-RATE PIC S9(3)V99. 05 WS-VARIANCE PIC S9(8)V99. *> Inventory adjustments 01 WS-INVENTORY-DATA. 05 WS-QUANTITY-CHANGE PIC S9(6). 05 WS-VALUE-ADJUSTMENT PIC S9(8)V99. 05 WS-SHRINKAGE PIC S9(6)V99. 05 WS-REORDER-POINT PIC S9(6). *> Validation and processing counters 01 WS-PROCESSING-COUNTERS. 05 WS-NEGATIVE-COUNT PIC 9(6) VALUE 0. 05 WS-POSITIVE-COUNT PIC 9(6) VALUE 0. 05 WS-ZERO-COUNT PIC 9(6) VALUE 0. 05 WS-TOTAL-PROCESSED PIC 9(6) VALUE 0. 05 WS-ERROR-COUNT PIC 9(4) VALUE 0. *> Status and control fields 01 WS-PROCESSING-STATUS. 05 WS-ALERT-FLAG PIC X VALUE 'N'. 05 WS-WARNING-LEVEL PIC 9 VALUE 0. 05 WS-PROCESS-CODE PIC X(5). 05 WS-ERROR-MESSAGE PIC X(100). PROCEDURE DIVISION. MAIN-NEGATIVE-DEMO. DISPLAY "=== COBOL NEGATIVE CONDITION DEMONSTRATION ===" DISPLAY SPACES PERFORM DEMONSTRATE-BASIC-NEGATIVE PERFORM DEMONSTRATE-FINANCIAL-VALIDATION PERFORM DEMONSTRATE-TEMPERATURE-MONITORING PERFORM DEMONSTRATE-BUSINESS-ANALYSIS PERFORM DEMONSTRATE-INVENTORY-PROCESSING PERFORM DEMONSTRATE-BATCH-VALIDATION DISPLAY "=== NEGATIVE CONDITION DEMO COMPLETE ===" STOP RUN. DEMONSTRATE-BASIC-NEGATIVE. DISPLAY "=== BASIC NEGATIVE CONDITION USAGE ===" DISPLAY SPACES DISPLAY "Testing NEGATIVE class condition with various values:" *> Test with different negative values MOVE -1234.56 TO WS-ACCOUNT-BALANCE IF WS-ACCOUNT-BALANCE IS NEGATIVE DISPLAY " Balance " WS-ACCOUNT-BALANCE " is NEGATIVE ✓" ADD 1 TO WS-NEGATIVE-COUNT ELSE DISPLAY " Balance " WS-ACCOUNT-BALANCE " is NOT negative ✗" END-IF *> Test with positive value MOVE 5000.00 TO WS-ACCOUNT-BALANCE IF WS-ACCOUNT-BALANCE IS NEGATIVE DISPLAY " Balance " WS-ACCOUNT-BALANCE " is NEGATIVE ✗" ELSE DISPLAY " Balance " WS-ACCOUNT-BALANCE " is NOT negative ✓" ADD 1 TO WS-POSITIVE-COUNT END-IF *> Test with zero MOVE 0 TO WS-ACCOUNT-BALANCE IF WS-ACCOUNT-BALANCE IS NEGATIVE DISPLAY " Balance " WS-ACCOUNT-BALANCE " is NEGATIVE ✗" ELSE DISPLAY " Balance " WS-ACCOUNT-BALANCE " is NOT negative ✓" ADD 1 TO WS-ZERO-COUNT END-IF *> Test with very small negative value MOVE -0.01 TO WS-ACCOUNT-BALANCE IF WS-ACCOUNT-BALANCE IS NEGATIVE DISPLAY " Balance " WS-ACCOUNT-BALANCE " is NEGATIVE ✓" ADD 1 TO WS-NEGATIVE-COUNT END-IF DISPLAY " Summary: " WS-NEGATIVE-COUNT " negative, " WS-POSITIVE-COUNT " positive, " WS-ZERO-COUNT " zero" DISPLAY SPACES. DEMONSTRATE-FINANCIAL-VALIDATION. DISPLAY "=== FINANCIAL DATA VALIDATION ===" DISPLAY SPACES DISPLAY "Processing financial account data..." *> Initialize financial data MOVE -2500.75 TO WS-ACCOUNT-BALANCE MOVE -150.00 TO WS-MONTHLY-CHANGE MOVE 25.50 TO WS-INTEREST-EARNED MOVE -45.00 TO WS-FEES-CHARGED DISPLAY "Account Analysis:" DISPLAY " Current balance: $" WS-ACCOUNT-BALANCE *> Validate account balance IF WS-ACCOUNT-BALANCE IS NEGATIVE DISPLAY " ⚠️ OVERDRAFT ALERT: Account is overdrawn" MOVE 'Y' TO WS-ALERT-FLAG MOVE 3 TO WS-WARNING-LEVEL MOVE "OVRD" TO WS-PROCESS-CODE *> Check severity of overdraft IF WS-ACCOUNT-BALANCE < -1000 DISPLAY " 🚨 SEVERE OVERDRAFT: Balance exceeds $1,000 limit" MOVE 5 TO WS-WARNING-LEVEL END-IF ELSE DISPLAY " ✓ Account balance is positive" MOVE "NORM" TO WS-PROCESS-CODE END-IF *> Analyze monthly change DISPLAY " Monthly change: $" WS-MONTHLY-CHANGE IF WS-MONTHLY-CHANGE IS NEGATIVE DISPLAY " 📉 Account decreased this month" IF WS-ACCOUNT-BALANCE IS NEGATIVE DISPLAY " 💡 Recommendation: Deposit funds immediately" END-IF ELSE DISPLAY " 📈 Account increased this month" END-IF *> Calculate net activity COMPUTE WS-NET-WORTH = WS-INTEREST-EARNED + WS-FEES-CHARGED DISPLAY " Net fees/interest: $" WS-NET-WORTH IF WS-NET-WORTH IS NEGATIVE DISPLAY " 📊 Net fees exceed interest earned" ELSE DISPLAY " 📊 Interest earnings exceed fees" END-IF DISPLAY " Alert status: " WS-ALERT-FLAG DISPLAY " Warning level: " WS-WARNING-LEVEL DISPLAY " Process code: " WS-PROCESS-CODE DISPLAY SPACES. DEMONSTRATE-TEMPERATURE-MONITORING. DISPLAY "=== TEMPERATURE MONITORING SYSTEM ===" DISPLAY SPACES DISPLAY "Processing temperature sensor data..." *> Initialize temperature readings MOVE -5 TO WS-CURRENT-TEMP MOVE -2 TO WS-TEMP-CHANGE MOVE -15 TO WS-MIN-TEMP MOVE 8 TO WS-MAX-TEMP DISPLAY "Temperature Analysis:" DISPLAY " Current temperature: " WS-CURRENT-TEMP "°C" *> Check for freezing conditions IF WS-CURRENT-TEMP IS NEGATIVE DISPLAY " 🥶 FREEZING ALERT: Temperature below 0°C" MOVE 'Y' TO WS-ALERT-FLAG IF WS-CURRENT-TEMP < -10 DISPLAY " ❄️ EXTREME COLD: Temperature below -10°C" MOVE 4 TO WS-WARNING-LEVEL ELSE MOVE 2 TO WS-WARNING-LEVEL END-IF ELSE DISPLAY " 🌡️ Temperature above freezing" MOVE 0 TO WS-WARNING-LEVEL END-IF *> Analyze temperature trend DISPLAY " Temperature change: " WS-TEMP-CHANGE "°C" IF WS-TEMP-CHANGE IS NEGATIVE DISPLAY " 📉 Temperature falling" IF WS-CURRENT-TEMP IS NEGATIVE AND WS-TEMP-CHANGE IS NEGATIVE DISPLAY " ⚠️ CONTINUED COOLING: Already below freezing" END-IF ELSE DISPLAY " 📈 Temperature rising" IF WS-CURRENT-TEMP IS NEGATIVE AND WS-TEMP-CHANGE > 0 DISPLAY " 🌤️ WARMING TREND: May rise above freezing" END-IF END-IF *> Check daily extremes DISPLAY " Daily range: " WS-MIN-TEMP "°C to " WS-MAX-TEMP "°C" IF WS-MIN-TEMP IS NEGATIVE DISPLAY " ❄️ Daily minimum below freezing" END-IF DISPLAY " Warning level: " WS-WARNING-LEVEL DISPLAY SPACES. DEMONSTRATE-BUSINESS-ANALYSIS. DISPLAY "=== BUSINESS PERFORMANCE ANALYSIS ===" DISPLAY SPACES DISPLAY "Analyzing business metrics..." *> Initialize business data MOVE 150000.00 TO WS-REVENUE MOVE 175000.00 TO WS-EXPENSES COMPUTE WS-PROFIT-LOSS = WS-REVENUE - WS-EXPENSES MOVE -5.25 TO WS-GROWTH-RATE MOVE -12500.50 TO WS-VARIANCE DISPLAY "Financial Performance:" DISPLAY " Revenue: $" WS-REVENUE DISPLAY " Expenses: $" WS-EXPENSES DISPLAY " Profit/Loss: $" WS-PROFIT-LOSS *> Analyze profitability IF WS-PROFIT-LOSS IS NEGATIVE DISPLAY " 📉 LOSS DETECTED: Business operating at a loss" MOVE "LOSS" TO WS-PROCESS-CODE MOVE 'Y' TO WS-ALERT-FLAG *> Calculate loss percentage COMPUTE WS-VARIANCE = (WS-PROFIT-LOSS / WS-REVENUE) * 100 DISPLAY " Loss percentage: " WS-VARIANCE "%" IF WS-VARIANCE < -20 DISPLAY " 🚨 CRITICAL: Loss exceeds 20% of revenue" MOVE 5 TO WS-WARNING-LEVEL ELSE MOVE 3 TO WS-WARNING-LEVEL END-IF ELSE DISPLAY " ✓ PROFITABLE: Business generating profit" MOVE "PROF" TO WS-PROCESS-CODE END-IF *> Analyze growth rate DISPLAY " Growth rate: " WS-GROWTH-RATE "%" IF WS-GROWTH-RATE IS NEGATIVE DISPLAY " 📉 DECLINING: Negative growth rate" IF WS-PROFIT-LOSS IS NEGATIVE AND WS-GROWTH-RATE IS NEGATIVE DISPLAY " ⚠️ DOUBLE NEGATIVE: Both profit and growth declining" END-IF ELSE DISPLAY " 📈 GROWING: Positive growth rate" END-IF DISPLAY " Process code: " WS-PROCESS-CODE DISPLAY " Alert status: " WS-ALERT-FLAG DISPLAY SPACES. DEMONSTRATE-INVENTORY-PROCESSING. DISPLAY "=== INVENTORY ADJUSTMENT PROCESSING ===" DISPLAY SPACES DISPLAY "Processing inventory adjustments..." *> Initialize inventory data MOVE -150 TO WS-QUANTITY-CHANGE MOVE -2500.75 TO WS-VALUE-ADJUSTMENT MOVE -125.50 TO WS-SHRINKAGE MOVE -25 TO WS-REORDER-POINT DISPLAY "Inventory Analysis:" DISPLAY " Quantity change: " WS-QUANTITY-CHANGE " units" *> Process quantity changes IF WS-QUANTITY-CHANGE IS NEGATIVE DISPLAY " 📦 INVENTORY REDUCTION: Stock decreased" MOVE "REDN" TO WS-PROCESS-CODE *> Check if significant reduction IF WS-QUANTITY-CHANGE < -100 DISPLAY " ⚠️ LARGE REDUCTION: Over 100 units removed" MOVE 3 TO WS-WARNING-LEVEL END-IF ELSE DISPLAY " 📈 INVENTORY INCREASE: Stock added" MOVE "INCR" TO WS-PROCESS-CODE END-IF *> Process value adjustments DISPLAY " Value adjustment: $" WS-VALUE-ADJUSTMENT IF WS-VALUE-ADJUSTMENT IS NEGATIVE DISPLAY " 💰 VALUE DECREASE: Inventory value reduced" IF WS-QUANTITY-CHANGE IS NEGATIVE AND WS-VALUE-ADJUSTMENT IS NEGATIVE DISPLAY " 📉 BOTH NEGATIVE: Quantity and value both decreased" END-IF ELSE DISPLAY " 💰 VALUE INCREASE: Inventory value increased" END-IF *> Process shrinkage DISPLAY " Shrinkage: $" WS-SHRINKAGE IF WS-SHRINKAGE IS NEGATIVE DISPLAY " 🔍 SHRINKAGE DETECTED: Inventory loss identified" MOVE 'Y' TO WS-ALERT-FLAG END-IF *> Check reorder point DISPLAY " Reorder point adjustment: " WS-REORDER-POINT IF WS-REORDER-POINT IS NEGATIVE DISPLAY " 📊 REORDER LOWERED: Reduced reorder threshold" END-IF DISPLAY " Process code: " WS-PROCESS-CODE DISPLAY " Alert triggered: " WS-ALERT-FLAG DISPLAY SPACES. DEMONSTRATE-BATCH-VALIDATION. DISPLAY "=== BATCH DATA VALIDATION ===" DISPLAY SPACES DISPLAY "Validating batch of hourly temperature readings..." *> Initialize sample temperature readings MOVE -8 TO WS-HOURLY-TEMP(1) MOVE -5 TO WS-HOURLY-TEMP(2) MOVE -2 TO WS-HOURLY-TEMP(3) MOVE 1 TO WS-HOURLY-TEMP(4) MOVE 3 TO WS-HOURLY-TEMP(5) MOVE 5 TO WS-HOURLY-TEMP(6) MOVE 7 TO WS-HOURLY-TEMP(7) MOVE 8 TO WS-HOURLY-TEMP(8) MOVE 6 TO WS-HOURLY-TEMP(9) MOVE 3 TO WS-HOURLY-TEMP(10) MOVE 0 TO WS-HOURLY-TEMP(11) MOVE -3 TO WS-HOURLY-TEMP(12) *> Reset counters MOVE 0 TO WS-NEGATIVE-COUNT MOVE 0 TO WS-POSITIVE-COUNT MOVE 0 TO WS-ZERO-COUNT *> Process 12 hours of data PERFORM VARYING WS-TOTAL-PROCESSED FROM 1 BY 1 UNTIL WS-TOTAL-PROCESSED > 12 DISPLAY " Hour " WS-TOTAL-PROCESSED ": " WS-HOURLY-TEMP(WS-TOTAL-PROCESSED) "°C" IF WS-HOURLY-TEMP(WS-TOTAL-PROCESSED) IS NEGATIVE DISPLAY " ❄️ Below freezing" ADD 1 TO WS-NEGATIVE-COUNT ELSE IF WS-HOURLY-TEMP(WS-TOTAL-PROCESSED) IS ZERO DISPLAY " 🌡️ At freezing point" ADD 1 TO WS-ZERO-COUNT ELSE DISPLAY " 🌤️ Above freezing" ADD 1 TO WS-POSITIVE-COUNT END-IF END-IF END-PERFORM DISPLAY SPACES DISPLAY "Batch Processing Summary:" DISPLAY " Total readings processed: " WS-TOTAL-PROCESSED DISPLAY " Negative temperatures: " WS-NEGATIVE-COUNT DISPLAY " Positive temperatures: " WS-POSITIVE-COUNT DISPLAY " Zero temperatures: " WS-ZERO-COUNT *> Calculate percentages COMPUTE WS-VARIANCE = (WS-NEGATIVE-COUNT / WS-TOTAL-PROCESSED) * 100 DISPLAY " Percentage below freezing: " WS-VARIANCE "%" IF WS-NEGATIVE-COUNT > (WS-TOTAL-PROCESSED / 2) DISPLAY " ⚠️ MAJORITY FREEZING: Most readings below 0°C" MOVE 'Y' TO WS-ALERT-FLAG ELSE DISPLAY " ✓ MOSTLY ABOVE FREEZING: Majority of readings positive" END-IF DISPLAY SPACES DISPLAY "NEGATIVE condition benefits demonstrated:" DISPLAY " ✓ Clear semantic meaning for sign testing" DISPLAY " ✓ Efficient validation of negative values" DISPLAY " ✓ Simplified conditional logic" DISPLAY " ✓ Enhanced code readability" DISPLAY " ✓ Reliable numeric sign detection" DISPLAY SPACES.

NEGATIVE Condition Applications

Financial Applications
  • • Account overdraft detection
  • • Loss and deficit identification
  • • Credit balance validation
  • • Financial performance analysis
Business Operations
  • • Inventory shrinkage detection
  • • Performance variance analysis
  • • Quality control measurements
  • • Temperature monitoring systems

Interactive Tutorial

Hands-On Exercise: Account Management System
Practice using NEGATIVE conditions for financial account validation

Exercise 1: Overdraft Protection System

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
01 WS-ACCOUNT-DATA. 05 WS-CURRENT-BALANCE PIC S9(8)V99. 05 WS-TRANSACTION-AMOUNT PIC S9(6)V99. 05 WS-OVERDRAFT-LIMIT PIC S9(6)V99 VALUE -500.00. 05 WS-OVERDRAFT-FEE PIC S9(4)V99 VALUE -35.00. 05 WS-PROJECTED-BALANCE PIC S9(8)V99. PROCEDURE DIVISION. OVERDRAFT-PROTECTION. MOVE 125.50 TO WS-CURRENT-BALANCE MOVE -200.00 TO WS-TRANSACTION-AMOUNT *> Calculate projected balance COMPUTE WS-PROJECTED-BALANCE = WS-CURRENT-BALANCE + WS-TRANSACTION-AMOUNT DISPLAY "Account Overdraft Check:" DISPLAY " Current balance: $" WS-CURRENT-BALANCE DISPLAY " Transaction: $" WS-TRANSACTION-AMOUNT DISPLAY " Projected balance: $" WS-PROJECTED-BALANCE *> Check if transaction would cause overdraft IF WS-PROJECTED-BALANCE IS NEGATIVE DISPLAY " ⚠️ OVERDRAFT WARNING" *> Check if within overdraft limit IF WS-PROJECTED-BALANCE < WS-OVERDRAFT-LIMIT DISPLAY " 🚫 TRANSACTION DENIED: Exceeds overdraft limit" DISPLAY " Overdraft limit: $" WS-OVERDRAFT-LIMIT ELSE DISPLAY " ✓ Transaction approved with overdraft fee" DISPLAY " Overdraft fee: $" WS-OVERDRAFT-FEE COMPUTE WS-PROJECTED-BALANCE = WS-PROJECTED-BALANCE + WS-OVERDRAFT-FEE DISPLAY " Final balance: $" WS-PROJECTED-BALANCE END-IF ELSE DISPLAY " ✓ Transaction approved - no overdraft" END-IF.

Exercise 2: Performance Dashboard

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
01 WS-PERFORMANCE-METRICS. 05 WS-METRICS OCCURS 5 TIMES. 10 WS-METRIC-NAME PIC X(20). 10 WS-METRIC-VALUE PIC S9(8)V99. 10 WS-TARGET-VALUE PIC S9(8)V99. 10 WS-VARIANCE PIC S9(8)V99. 05 WS-NEGATIVE-METRICS PIC 9(2) VALUE 0. 05 WS-WARNING-COUNT PIC 9(2) VALUE 0. PROCEDURE DIVISION. PERFORMANCE-DASHBOARD. *> Initialize performance data MOVE "Revenue Growth" TO WS-METRIC-NAME(1) MOVE -2.5 TO WS-METRIC-VALUE(1) MOVE 5.0 TO WS-TARGET-VALUE(1) MOVE "Customer Satisfaction" TO WS-METRIC-NAME(2) MOVE 8.2 TO WS-METRIC-VALUE(2) MOVE 8.0 TO WS-TARGET-VALUE(2) MOVE "Cost Reduction" TO WS-METRIC-NAME(3) MOVE -15.3 TO WS-METRIC-VALUE(3) MOVE -10.0 TO WS-TARGET-VALUE(3) DISPLAY "Performance Dashboard Analysis:" DISPLAY "================================" PERFORM VARYING WS-COUNTER FROM 1 BY 1 UNTIL WS-COUNTER > 3 COMPUTE WS-VARIANCE(WS-COUNTER) = WS-METRIC-VALUE(WS-COUNTER) - WS-TARGET-VALUE(WS-COUNTER) DISPLAY WS-METRIC-NAME(WS-COUNTER) ":" DISPLAY " Actual: " WS-METRIC-VALUE(WS-COUNTER) DISPLAY " Target: " WS-TARGET-VALUE(WS-COUNTER) DISPLAY " Variance: " WS-VARIANCE(WS-COUNTER) IF WS-VARIANCE(WS-COUNTER) IS NEGATIVE DISPLAY " Status: ⚠️ BELOW TARGET" ADD 1 TO WS-NEGATIVE-METRICS IF WS-VARIANCE(WS-COUNTER) < -5 DISPLAY " Alert: 🚨 SIGNIFICANT UNDERPERFORMANCE" ADD 1 TO WS-WARNING-COUNT END-IF ELSE DISPLAY " Status: ✓ MEETING OR EXCEEDING TARGET" END-IF DISPLAY " " END-PERFORM DISPLAY "Summary:" DISPLAY " Metrics below target: " WS-NEGATIVE-METRICS " of 3" DISPLAY " Critical alerts: " WS-WARNING-COUNT.

Best Practices

Knowledge Check

Test Your Understanding

Question 1: NEGATIVE Condition Purpose

What is the primary purpose of the NEGATIVE class condition?

Answer: NEGATIVE tests whether a signed numeric field contains a value less than zero. It provides a clear, semantic way to check for negative values in business applications, particularly useful for financial data validation and sign-based conditional logic.

Question 2: Data Type Requirements

What types of fields can be tested with the NEGATIVE condition?

Answer: NEGATIVE can only be used with signed numeric fields (those with 'S' in the picture clause). It works with DISPLAY, COMP, PACKED-DECIMAL, and other signed numeric formats, but cannot be used with unsigned fields.

Question 3: Business Applications

What are common business scenarios where NEGATIVE conditions are useful?

Answer: Common applications include account overdraft detection, financial loss identification, inventory shrinkage monitoring, temperature below-freezing alerts, performance variance analysis, and any scenario requiring reliable detection of negative values in business data.

Related Pages