COBOL Programming DAY 2. Copyright © 2005, Infosys Technologies Ltd 2 ER/CORP/CRS/LA01/003 Version 1.0  Data Movement verbs.  Sequence Control verbs.

Slides:



Advertisements
Similar presentations
Lecture 2 Introduction to C Programming
Advertisements

Introduction to C Programming
7-1 COBOL for the 21 st Century Nancy Stern Hofstra University Robert A. Stern Nassau Community College James P. Ley University of Wisconsin-Stout (Emeritus)
Objectives In this chapter, you will learn about:
© Copyright 1992–2004 by Deitel & Associates, Inc. and Pearson Education Inc. All Rights Reserved. 1 Chapter 4 – C Program Control Outline 4.1Introduction.
Copyright © 2009 Pearson Education, Inc. Publishing as Pearson Addison-Wesley Java Software Solutions Foundations of Program Design Sixth Edition by Lewis.
Data types and variables
© 2004 Pearson Addison-Wesley. All rights reserved5-1 Iterations/ Loops The while Statement Other Repetition Statements.
C++ for Engineers and Scientists Third Edition
Introduction to C Programming
 2008 Pearson Education, Inc. All rights reserved JavaScript: Control Statements II.
CONTROL STATEMENTS Lakhbir Singh(Lect.IT) S.R.S.G.P.C.G. Ludhiana.
Fundamentals of Python: From First Programs Through Data Structures
Objectives You should be able to describe: Data Types
Fundamentals of Python: First Programs
4-1 Coding Complete COBOL Programs: The PROCEDURE DIVISION Chapter 4.
4-1 COBOL for the 21 st Century Nancy Stern Hofstra University Robert A. Stern Nassau Community College James P. Ley University of Wisconsin-Stout (Emeritus)
COBOL Basics 1. COBOL coding rules  Almost all COBOL compilers treat a line of COBOL code as if it contained two distinct areas. These are known as;
4-1 COBOL for the 21 st Century Nancy Stern Hofstra University Robert A. Stern Nassau Community College James P. Ley University of Wisconsin-Stout (Emeritus)
1 Chapter 4. To familiarize you with methods used to 1. Access input and output files 2. Read data from an input file 3. Perform simple move operations.
Chapter 5 Using Data and COBOL Operators. Initializing Variables When you define a variable in WORKING- STORAGE, you also can assign it an initial value.
1 Chapter 4: Selection Structures. In this chapter, you will learn about: – Selection criteria – The if-else statement – Nested if statements – The switch.
Lecture 4 C Program Control Acknowledgment The notes are adapted from those provided by Deitel & Associates, Inc. and Pearson Education Inc.
Lecture 31 Numeric Edited Alphabetic (A) AlphaNumeric (X) Numeric (9, V, S) Numeric Edited (9, Z, comma, decimal point, minus sign) –Z = zero suppressed.
COBOL Basics 2. H E N N E S S Y R M L M F Group Items/Records StudentDetails WORKING-STORAGE SECTION. 01StudentDetailsPIC X(26).
7-1 Chapter 7.  Basic Arithmetic Verbs  Options Available with Arithmetic Verbs  COMPUTE Statement  Signed Numbers in Arithmetic Operations  Intrinsic.
© Copyright 1992–2004 by Deitel & Associates, Inc. and Pearson Education Inc. All Rights Reserved. Chapter 2 Chapter 2 - Introduction to C Programming.
Programming Logic and Design Sixth Edition Chapter 5 Looping.
CPS120: Introduction to Computer Science Decision Making in Programs.
Statement Syntax1 THE SELECT STATEMENT Purpose: designates a file and points to its physical location Syntax Definition : SELECT file-name-1 ASSIGN TO.
CPSC3111/CISM3111 COBOL Structured COBOL Programming Text: murach’s structured COBOL Authors: Murach, Prince, Menendez.
9-1 COBOL for the 21 st Century Nancy Stern Hofstra University Robert A. Stern Nassau Community College James P. Ley University of Wisconsin-Stout (Emeritus)
9-1 Iteration: Beyond the Basic PERFORM Chapter 9.
Visual Basic Programming
Microsoft Visual Basic 2005: Reloaded Second Edition Chapter 3 Variables, Constants, Methods, and Calculations.
An Object-Oriented Approach to Programming Logic and Design Fourth Edition Chapter 4 Looping.
Figure 9.9Duplicate Data Names 01 STUDENT-RECORD. 05 STUDENT-NAMEPIC X(20). 05 SOCIAL-SECURITY-NUMPIC 9(9). 05 STUDENT-ADDRESS. 10 STREETPIC X(15). 10.
11- 1 Chapter 11.  Avoiding Logic Errors by Validating Input  What to Do If Input Errors Occur  Global Considerations in COBOL  When Data Should Be.
7-1 COBOL for the 21 st Century Nancy Stern Hofstra University Robert A. Stern Nassau Community College James P. Ley University of Wisconsin-Stout (Emeritus)
1 Chapter 5 – The Procedure Division File handling statements –OPEN statement Initiates processing for a file Input Output Each file opened must have been.
1 Chapter 9. To familiarize you with  Simple PERFORM  How PERFORM statements are used for iteration  Options available with PERFORM 2.
CPS120 Introduction to Computer Science Iteration (Looping)
CHAPTER 2 PROBLEM SOLVING USING C++ 1 C++ Programming PEG200/Saidatul Rahah.
11- 1 Chapter 11.  Avoiding Logic Errors by Validating Input  What to Do If Input Errors Occur  Global Considerations in COBOL  When Data Should Be.
The PERFORM. The PERFORM Verb  Iteration is an important programming construct. We use iteration when we need to repeat the same instructions over and.
 2007 Pearson Education, Inc. All rights reserved. A Simple C Program 1 /* ************************************************* *** Program: hello_world.
 2006 Pearson Education, Inc. All rights reserved Control Statements: Part 2.
Programming in Java (COP 2250) Lecture 12 & 13 Chengyong Yang Fall, 2005.
An Introduction to Programming with C++ Sixth Edition Chapter 5 The Selection Structure.
4 - Conditional Control Structures CHAPTER 4. Introduction A Program is usually not limited to a linear sequence of instructions. In real life, a programme.
FILES AND EXCEPTIONS Topics Introduction to File Input and Output Using Loops to Process Files Processing Records Exceptions.
A First Book of C++ Chapter 4 Selection.
LOGICAL CONTROL STRUCTURES (chp. 8)
Chapter 4 – C Program Control
Visual Basic 6 (VB6) Data Types, And Operators
The Selection Structure
Programming in COBOL.
Chapter 2 - Introduction to C Programming
Chapter 2 - Introduction to C Programming
Iteration: Beyond the Basic PERFORM
Programming in COBOL-85 For IBM Mainframe System 390
Chapter 2 - Introduction to C Programming
Agenda Collating sequence / Sorting data
Computing in COBOL: The Arithmetic Verbs and Intrinsic Functions
Chapter 2 - Introduction to C Programming
Using C++ Arithmetic Operators and Control Structures
Introduction to C Programming
Decision Making Using the IF and EVALUATE Statements
Programming in COBOL.
Presentation transcript:

COBOL Programming DAY 2

Copyright © 2005, Infosys Technologies Ltd 2 ER/CORP/CRS/LA01/003 Version 1.0  Data Movement verbs.  Sequence Control verbs.  Types of conditions.  REDEFINES, RENAMES, USAGE clauses.  Design and development of sample programs. Agenda for Day2

Copyright © 2005, Infosys Technologies Ltd 3 ER/CORP/CRS/LA01/003 Version 1.0 The MOVE copies data from the source identifier or literal to one or more destination identifiers. The source and destination identifiers can be group or elementary data items. When the destination item is alphanumeric or alphabetic (PIC X or A) data is copied into the destination area from left to right with space filling or truncation on the right. When data is MOVEd into an item the contents of the item are completely replaced. If the source data is too small to fill the destination item entirely the remaining area is zero or space filled. MOVE VERB

Copyright © 2005, Infosys Technologies Ltd 4 ER/CORP/CRS/LA01/003 Version 1.0 MOVE verb…

Copyright © 2005, Infosys Technologies Ltd 5 ER/CORP/CRS/LA01/003 Version 1.0 (1) MOVE (2) MOVE... CORRESPONDING ( CORR ) (3) MOVE... OF... TO... OF DATA movement verbs…

Copyright © 2005, Infosys Technologies Ltd 6 ER/CORP/CRS/LA01/003 Version 1.0 Before WS00-OUT1 ‘BEST’ WS00-OUT Before WS00-OUT1 ‘ ’ WS00-OUT2 0 Before WS00-OUT After WS00-OUT Before WS00-OUT4 ‘PAYAL PAREKH’ After WS00-OUT4 ‘SHUTI DEY’

Copyright © 2005, Infosys Technologies Ltd 7 ER/CORP/CRS/LA01/003 Version 1.0 MOVE to a numeric item When the destination item is numeric, or edited numeric, then data is aligned along the decimal point with zero filling or truncation as necessary. When the decimal point is not explicitly specified in either the source or destination items, the item is treated as if it had an assumed decimal point immediately after its rightmost character.

Copyright © 2005, Infosys Technologies Ltd 8 ER/CORP/CRS/LA01/003 Version 1.0 Before WS00-OUT WS00-OUT Before WS00-OUT WS00-OUT Before WS00-OUT After WS00-OUT Before WS00-OUT After WS00-OUT

Copyright © 2005, Infosys Technologies Ltd 9 ER/CORP/CRS/LA01/003 Version 1.0 MOVE.. example **************************** WS00-OUT1 : HARAYANA WS00-OUT2 : HARAYANA **************************** Output SPOOL

Copyright © 2005, Infosys Technologies Ltd 10 ER/CORP/CRS/LA01/003 Version 1.0 Is used to change the default type movement of alphabetic and alphanumeric data. Example 01 NAME PIC X(10) JUSTIFIED RIGHT. MOVE “KAJOL” TO NAME. Contents of NAME field is bbbbbKAJOL JUSTIFIED RIGHT clause

Copyright © 2005, Infosys Technologies Ltd 11 ER/CORP/CRS/LA01/003 Version 1.0 JUSTIFIED RIGHT clause.. example ********************************************* WS00-OUT1 : ABCDEFGHIJKLMNOPQRSTUVWXYZ WS00-OUT2 : ABCDEFGHIJKLMNOPQRSTUVWXYZ ********************************************* Output SPOOL

Copyright © 2005, Infosys Technologies Ltd 12 ER/CORP/CRS/LA01/003 Version 1.0 Facilitates movement of value of sub-item of a group item to a similar named sub-item of another group item Syntax MOVE { CORRESPONDING, CORR } identifier-1 TO identifier-2 where identifier-1 and identifier-2 are group items. MOVE CORRESPONDING

Copyright © 2005, Infosys Technologies Ltd 13 ER/CORP/CRS/LA01/003 Version 1.0 MOVE CORRESPONDING.. example **************************** WS00-GR2 : NISHANT **************************** Output SPOOL

Copyright © 2005, Infosys Technologies Ltd 14 ER/CORP/CRS/LA01/003 Version 1.0 Facilitates the movement of a particular field of a record to a particular field of another record. (in other words it facilitates movement of value of a individual/group item of one group item to an individual/group item of another group item). Example: MOVE NAME OF STUD-REC TO WS-NAME OF WS-STUD-REC. MOVE... OF... TO... OF

Copyright © 2005, Infosys Technologies Ltd 15 ER/CORP/CRS/LA01/003 Version 1.0 Certain combinations of sending and receiving data types are not permitted. AlphabeticAlphanu meric Edited Alphan umeric NumericNumeric non integer Edited numeric AlphabeticYYYNNN AlphanumericYYYYYY Edited Alphanumeric YYYNNN NumericNYYYYY Numeric non integer NNNYYY Edited numeric NYYYYY Receiving field Sending field LEGAL MOVES

Copyright © 2005, Infosys Technologies Ltd 16 ER/CORP/CRS/LA01/003 Version 1.0 GOTO IF... THEN... PERFORM EVALUATE STOP RUN SEQUENCE CONTROL verbs

Copyright © 2005, Infosys Technologies Ltd 17 ER/CORP/CRS/LA01/003 Version 1.0 Syntax-1 GO TO Paragraph Name. Example GO TO 400-READ-PARA. GO TO Verb

Copyright © 2005, Infosys Technologies Ltd 18 ER/CORP/CRS/LA01/003 Version 1.0 Syntax-2 GO TO paragraph-name-1 [paragraph-name-2 ]... DEPENDING ON identifier. Example GO TO 500-INSERT-PARA, 600-UPDATE-PARA, 700-DELETE-PARA DEPENDING ON TRANS-CODE. GO TO... DEPENDING ON...

Copyright © 2005, Infosys Technologies Ltd 19 ER/CORP/CRS/LA01/003 Version 1.0 Syntax-1 IF condition [ THEN ] {statement-1, NEXT SENTENCE} [ELSE {statement-2, NEXT SENTENCE}] [ END-IF ]. Examples (1)IF MARKS >= 80 THEN MOVE ‘A’ TO GRADE ELSE MOVE ‘B’ TO GRADE END-IF. (2) IF NOT OK-BALANCE THEN MOVE 2 TO BALANCE-CODE ELSE NEXT-SENTENCE END-IF IF statement

Copyright © 2005, Infosys Technologies Ltd 20 ER/CORP/CRS/LA01/003 Version 1.0 Syntax-2 ( Nested IF ) IF condition-1 [ THEN ] statement-1 ELSE IF condition-2 [ THEN ] statement-2 ELSE statement-3 END-IF END-IF. Example IF ( Var1 < 10 ) THEN DISPLAY “Zero” ELSE IF Var2 = 14 THEN DISPLAY “First” ELSE DISPLAY “Second” END-IF END-IF. IF statement

Copyright © 2005, Infosys Technologies Ltd 21 ER/CORP/CRS/LA01/003 Version 1.0 Example IF TIME 1 THEN MOVE “SLOW” TO SPEED END-IF. Is equivalent to IF TIME 1 THEN MOVE “SLOW” TO SPEED. Note: The following statement is invalid. IF TOT-1 OR TOT-2 = 7 THEN DISPLAY “ The Sum is 7.”. IF statement - Implied Operands

Copyright © 2005, Infosys Technologies Ltd 22 ER/CORP/CRS/LA01/003 Version 1.0 Relational condition Sign condition Class condition Compound condition Condition-name Classification of Conditions

Copyright © 2005, Infosys Technologies Ltd 23 ER/CORP/CRS/LA01/003 Version 1.0 Relational condition

Copyright © 2005, Infosys Technologies Ltd 24 ER/CORP/CRS/LA01/003 Version 1.0 Syntax Example IF DISCRIMINANT IS NEGATIVE THEN DISPLAY “The roots are imaginary”. Sign condition

Copyright © 2005, Infosys Technologies Ltd 25 ER/CORP/CRS/LA01/003 Version 1.0 Syntax Example IF REGNO IS NOT NUMERIC THEN DISPLAY “Records will not be sorted”. Class condition

Copyright © 2005, Infosys Technologies Ltd 26 ER/CORP/CRS/LA01/003 Version 1.0 Syntax Condition-1 { AND, OR } Condition-2 Examples (1) IF PERCENT > 80 AND TOTAL > 480 THEN MOVE ‘A’ TO GRADE. (2) IF ROW-NUMBER > 24 OR COLUMN > 80 THEN DISPLAY “Page Error ! “. Compound Condition

Copyright © 2005, Infosys Technologies Ltd 27 ER/CORP/CRS/LA01/003 Version 1.0 Are essentially boolean variables. Are always associated with data names called condition variables. Is defined in the DATA DIVISION with level number 88. Syntax 88 condition-name {VALUE IS, VALUES ARE } literal-1 [ { THRU, THROUGH } literal-2 ]. Condition Names

Copyright © 2005, Infosys Technologies Ltd 28 ER/CORP/CRS/LA01/003 Version MARITAL STATUS PIC SINGLEVALUE IS ZERO. 88 MARRIEDVALUE IS WIDOWED VALUE IS DIVORCED VALUE IS ONCE-MARRIED VALUES ARE 1, 2, VALID-STATUS VALUES ARE 0 THRU 3. PROCEDURE DIVISION Statements. IF SINGLE SUBTRACT 125 FROM DEDUCTIONS. IF ONCE-MARRIED ADD 300 TO SPECIAL-PAY. IF MARRIED PERFORM B000-MARRIAGE-GIFT. Condition Variable Condition Names Condition-Names.. example

Copyright © 2005, Infosys Technologies Ltd 29 ER/CORP/CRS/LA01/003 Version 1.0 Condition Names are defined using the special level number 88 in the DATA DIVISION of a COBOL program. They are defined immediately after the definition of the data item with which they are associated with. We can use Condition Names for a group as well as an elementary item. A condition name takes the value TRUE or FALSE depending on the value of the data item with which it is associated. The VALUE clause of the associated data item is used to identify the values which make the Condition Name TRUE. Defining Condition Names.

Copyright © 2005, Infosys Technologies Ltd 30 ER/CORP/CRS/LA01/003 Version 1.0 Before WS00-MARKS 000 WS00-DISP After WS00-MARKS 050 WS00-DISP NOT CLEARED COMPRE Before WS00-MARKS 000 WS00-DISP After WS00-MARKS 081 WS00-DISP PASSED COMPRE JCL //ER4857C JOB,,NOTIFY=&SYSUID,CLASS=B //STEP1 EXEC PGM=COND //STEPLIB DD DSN=OPERN.CICS3.LOADLIB,DISP=SHR //SYSIN DD * /*

Copyright © 2005, Infosys Technologies Ltd 31 ER/CORP/CRS/LA01/003 Version 1.0 Break

Copyright © 2005, Infosys Technologies Ltd 32 ER/CORP/CRS/LA01/003 Version 1.0 Iteration constructs are used when we need to repeat the same instructions over and over again in our programs. Other programming languages have a variety of iteration / looping constructs (e.g. WHILE, FOR, REPEAT). Each of these in turn facilitate the creation of different ‘types’ of iteration structure. In COBOL we have ‘PERFORM’ verb which is used to create these looping constructs. The PERFORM has several variations each of which simulates different looping constructs of other programming languages. The PERFORM Verb

Copyright © 2005, Infosys Technologies Ltd 33 ER/CORP/CRS/LA01/003 Version 1.0 Paragraphs - Revisited A PARAGRAPH comprises of one or more sentences. The paragraph-name indicates the start of a paragraph. The next paragraph or section name or the end of the program text terminates the paragraph. Paragraph names are either user defined or language enforced. They are followed by a full stop. –B0000-PERF-PARA. –PROGRAM-ID.

Copyright © 2005, Infosys Technologies Ltd 34 ER/CORP/CRS/LA01/003 Version 1.0 P0000-PROCESS-RECORD. DISPLAY StudentRecord READ StudentFile AT END MOVE HIGH-VALUES TO StudentRecord END-READ. D0000-PRODUCE-OUTPUT. DISPLAY “Here is a message”. NOTE Scope of P0000-PROCESS-RECORD is delimited by the occurrence the paragraph name D0000-PRODUCE-OUTPUT.NOTE Paragraph Example

Copyright © 2005, Infosys Technologies Ltd 35 ER/CORP/CRS/LA01/003 Version 1.0 Simple PERFORM In-line PERFORM Nested PERFORM PERFORM... THRU PERFORM... UNTIL PERFORM... TIMES PERFORM... VARYING PERFORM Verb - variations

Copyright © 2005, Infosys Technologies Ltd 36 ER/CORP/CRS/LA01/003 Version 1.0 Syntax PERFORM Paragraph-Name. Example PERFORM 500-PROCESS-PARA. This is not iterative but instructs the computer to execute the chunk of code inside the mentioned paragraph before reverting back to the sentence following the PERFORM coded. PERFORM Verb - Simple PERFORM

Copyright © 2005, Infosys Technologies Ltd 37 ER/CORP/CRS/LA01/003 Version 1.0 PERFORM Verb – Simple PERFORM example **************************************** WE ARE INSIDE B000-LAST-PARA WE ARE INSIDE B001-FIRST-PARA WE ARE INSIDE B002-MIDDLE-PARA **************************************** Output SPOOL

Copyright © 2005, Infosys Technologies Ltd 38 ER/CORP/CRS/LA01/003 Version 1.0 Syntax PERFORM imperative-statements. Example PERFORM MOVE NUM-1 TO MAX IF NUM-2 > MAX THEN MOVE NUM-2 TO MAX DISPLAY “Maximum is ” MAX. END-PERFORM Lets see an example.. PERFORM Verb - In-line PERFORM

Copyright © 2005, Infosys Technologies Ltd 39 ER/CORP/CRS/LA01/003 Version 1.0 INLINE PERFORM PROGRAM

Copyright © 2005, Infosys Technologies Ltd 40 ER/CORP/CRS/LA01/003 Version 1.0 JCL FOR THE INLINE PERFORM PROGRAM

Copyright © 2005, Infosys Technologies Ltd 41 ER/CORP/CRS/LA01/003 Version 1.0 When SYSIN data satisfies the condition WS-STRING = ‘KARINA’ the scope of the INLINE PERFORM gets terminated

Copyright © 2005, Infosys Technologies Ltd 42 ER/CORP/CRS/LA01/003 Version 1.0 Syntax Paragraph-Name-1. PERFORM Paragraph-Name Paragraph-Name-2. PERFORM Paragraph-Name Paragraph-Name-3. MOVE A TO B PERFORM Verb – Nested PERFORM

Copyright © 2005, Infosys Technologies Ltd 43 ER/CORP/CRS/LA01/003 Version 1.0 PERFORM Verb – Nested PERFORM **************************************** WE ARE INSIDE B000-LAST-PARA WE ARE INSIDE B001-FIRST-PARA WE ARE INSIDE B002-MIDDLE-PARA **************************************** Output SPOOL

Copyright © 2005, Infosys Technologies Ltd 44 ER/CORP/CRS/LA01/003 Version 1.0 Syntax PERFORM Paragraph-Name-1 [ { THRU, THROUGH } Paragraph-Name-2 ]. Example PERFORM 300-READ-PARA THRU 600-UPDATE-PARA. PERFORM Verb – PERFORM … THRU …

Copyright © 2005, Infosys Technologies Ltd 45 ER/CORP/CRS/LA01/003 Version 1.0 PERFORM … THRU … - example **************************** WE ARE INSIDE B000-DISP-PARA WE ARE INSIDE B001-DISP-PARA WE ARE INSIDE B002-DISP-PARA **************************** Output SPOOL

Copyright © 2005, Infosys Technologies Ltd 46 ER/CORP/CRS/LA01/003 Version 1.0 Syntax PERFORM Paragraph-Name-1 [ { THRU, THROUGH } Paragraph-Name-2 ] UNTIL condition. Example PERFORM 300-READ-PARA UNTIL EOF = ‘N’. PERFORM Verb – PERFORM.. UNTIL..

Copyright © 2005, Infosys Technologies Ltd 47 ER/CORP/CRS/LA01/003 Version 1.0 Syntax PERFORM Paragraph-Name-1 [ { THRU, THROUGH } Paragraph-Name-2 ] [WITH TEST {BEFORE, AFTER}] UNTIL condition. Example PERFORM 300-PROCESS-PARA WITH TEST AFTER UNTIL VALUE NOT = 0. PERFORM Verb – PERFORM.. UNTIL.. WITH TEST AFTER OPTION

Copyright © 2005, Infosys Technologies Ltd 48 ER/CORP/CRS/LA01/003 Version 1.0 This format is used where the WHILE or REPEAT constructs are used in other languages. If the WITH TEST BEFORE phrase is used the PERFORM behaves like a WHILE loop and the condition is tested before the loop body is entered. If the WITH TEST AFTER phrase is used the PERFORM behaves like a REPEAT loop and the condition is tested after the loop body is entered. The WITH TEST BEFORE phrase is the default and so is rarely explicitly stated. PERFORM.. UNTIL.. WITH TEST AFTER OPTION

Copyright © 2005, Infosys Technologies Ltd 49 ER/CORP/CRS/LA01/003 Version 1.0 PERFORM Verb – PERFORM.. UNTIL.. WITH TEST BEFORE **************************** Output SPOOL

Copyright © 2005, Infosys Technologies Ltd 50 ER/CORP/CRS/LA01/003 Version 1.0 PERFORM Verb – PERFORM.. UNTIL.. WITH TEST AFTER **************************** WE ARE INSIDE B000-PERF-PARA **************************** Output SPOOL 10 Times!! Why?

Copyright © 2005, Infosys Technologies Ltd 51 ER/CORP/CRS/LA01/003 Version 1.0 Syntax PERFORM Paragraph-Name-1 [ { THRU, THROUGH } Paragraph-Name-2 ] { integer, identifier } TIMES. Example PERFORM 500-PROCESS-PARA THRU 800-END-PARA 8 TIMES. PERFORM Verb – PERFORM.. TIMES

Copyright © 2005, Infosys Technologies Ltd 52 ER/CORP/CRS/LA01/003 Version 1.0 PERFORM Verb – PERFORM.. TIMES …… Example **************************** HELLO GUEST. WELCOME TO E&R TRAINING **************************** Output SPOOL

Copyright © 2005, Infosys Technologies Ltd 53 ER/CORP/CRS/LA01/003 Version 1.0 Syntax PERFORM Paragraph-Name-1 [ { THRU, THROUGH } Paragraph-Name-2 ] VARYING identifier-1 FROM {identifier-2, integer-1} BY { identifier-3, integer-2 } UNTIL condition. Example PERFORM 500-WRITE-PARA VARYING I FROM 1 BY 1 UNTIL I > 5. PERFORM Verb - PERFORM... VARYING

Copyright © 2005, Infosys Technologies Ltd 54 ER/CORP/CRS/LA01/003 Version 1.0 PERFORM Verb - PERFORM... VARYING **************************** HELLO GUEST. WISH YOU ALL THE BEST **************************** Output SPOOL

Copyright © 2005, Infosys Technologies Ltd 55 ER/CORP/CRS/LA01/003 Version 1.0 Is used to transfer the control back to the statement following the “PERFORM statement” from within a paragraph invoked by the PERFORM statement. Syntax EXIT. Note: It is recommended to avoid using EXIT similar to GO TO since it is against the idea of structured programming. EXIT statement

Copyright © 2005, Infosys Technologies Ltd 56 ER/CORP/CRS/LA01/003 Version 1.0 The EVALUATE verb provides a very powerful construct to carry out DATA validation. It is similar to the SWITCH statement in C programs. It assists us in implementing decision table logic. Syntax EVALUATE subject-1 [ ALSO subject-2 ]... { { WHEN object-1 [ ALSO object-2 ]... }... } imperative-statement-1 }... Where subject = { identifier, expression, TRUE, FALSE } and object = { condition, TRUE, FALSE }. EVALUATE Verb

Copyright © 2005, Infosys Technologies Ltd 57 ER/CORP/CRS/LA01/003 Version 1.0 The Evaluate

Copyright © 2005, Infosys Technologies Ltd 58 ER/CORP/CRS/LA01/003 Version 1.0 EVALUATE Verb.. example There are two valid ranges which the logic checks for – 1) Marks > 79 2) Marks > 64 & <= 79 ************************************* YOU HAVE CLEARED EXAM WITH A GRADE ************************************* Output SPOOL

Copyright © 2005, Infosys Technologies Ltd 59 ER/CORP/CRS/LA01/003 Version 1.0 Syntax:STOP RUN. Instructs the computer to terminate the program. Closes all the files that were opened for file operations. The STOP RUN is usually the last statement in the main paragraph. STOP RUN statement

Copyright © 2005, Infosys Technologies Ltd 60 ER/CORP/CRS/LA01/003 Version 1.0 Facilitates two or more data-names to point to the same memory location Syntax data-name-1 REDEFINES data-name-2. Example 01 STUD-DETAILS. 05 STUD-NAME. 10 FIRST-NAME PIC A(15). 10 MIDDLE-NAME PIC A(10). 10 LAST-NAME PIC A(10). 05 NAME REDEFINES STUD-NAME. REDEFINES Clause

Copyright © 2005, Infosys Technologies Ltd 61 ER/CORP/CRS/LA01/003 Version 1.0 Rules governing REDEFINES clause Multiple REDEFINES is allowed for a data-item. REDEFINES clause must not be used for 01 level in FILE SECTION. Must not be used for data-items defined in level numbers 66 and 88. The REDEFINING item should not have an OCCURS clause. Any change in REDEFINED item reflects on the value of the REDEFINING item and vice-versa. REDEFINES Clause

Copyright © 2005, Infosys Technologies Ltd 62 ER/CORP/CRS/LA01/003 Version 1.0 REDEFINES CLAUSE … example ************************************ YEAR FOR ENTERED DATE IS : 2005 MONTH FOR ENTERED DATE IS : 01 DAY FOR ENTERED DATE IS : 01 ************************************ Output SPOOL WS00-YEAR2 redefines WS00-YEAR1. It is the same 8 bytes of information which WS00-YEAR2 provides in the Year, Month & Day format in it’s sub-items. Any change in WS00-YEAR1 changes value of WS00-YEAR2 and vice-versa.

Copyright © 2005, Infosys Technologies Ltd 63 ER/CORP/CRS/LA01/003 Version 1.0 Facilitates re-grouping of elementary data items in a record. After the renames enforcement the elementary items would belong to the original (renamed) group item as well as the new (renaming) group item. Syntax 66 data-name-1 RENAMES data-name-2 THRU data-name-3. Rules to be followed while using RENAMES RENAMES must be used after the description of the fields required. Must be coded only with level number 66. Data-names 2 and 3 should not have level numbers 01 and OCCURS Clause. The elementary items getting renamed should be contiguous. RENAMES Clause

Copyright © 2005, Infosys Technologies Ltd 64 ER/CORP/CRS/LA01/003 Version 1.0 Example 01 STUD-DETAILS. 05 REG-NO PIC 9(5). 05 S-F-NAMEPIC X(15). 05 S-M-NAMEPIC X(12). 05 S-L-NAMEPIC X(8). 66 STUD-NAME RENAMES S-F-NAME THRU S-L-NAME. RENAMES Clause

Copyright © 2005, Infosys Technologies Ltd 65 ER/CORP/CRS/LA01/003 Version 1.0 RENAMES clause.. example ********************************* WS-REN VALUE IS : ********************************* Output SPOOL WS-REN would be picking up the value of the sub-items from WS-IN12 to WS-22 (spreading across WS-IN1 & WS-IN2 values). Note that WS-IN11 is left out.

Copyright © 2005, Infosys Technologies Ltd 66 ER/CORP/CRS/LA01/003 Version 1.0 Is used to specify the internal form in which the data is to be stored. Every variable will have an attached usage clause (even if not declared by the programmer). Syntax USAGE IS {DISPLAY, COMPUTATIONAL, COMP} [ - {1, 2, 3}]. USAGE Clause

Copyright © 2005, Infosys Technologies Ltd 67 ER/CORP/CRS/LA01/003 Version 1.0 USAGE is DISPLAY –Each character of the data is represented in one byte USAGE IS COMPUTATIONAL –The data item is represented as pure binary USAGE IS COMP-1 –The data item is represented as a single precision floating point number (similar to real or float). USAGE IS COMP-2 –The data item is represented internally as Double precision floating number (similar to Long or Double). USAGE IS COMP-3 –In decimal form but 1 digit takes half a byte (nibble). The sign is stored as right most half a byte character. USAGE Clause

Copyright © 2005, Infosys Technologies Ltd 68 ER/CORP/CRS/LA01/003 Version 1.0 Rules to followed while using USAGE clause Usage clause cannot be used with data items declared with 66 or 88 levels. Usage clause when declared for a group item, ensures that all the sub-items of the group item default to the same USAGE clause as the group item’s. USAGE Clause

Copyright © 2005, Infosys Technologies Ltd 69 ER/CORP/CRS/LA01/003 Version 1.0 USAGE Clause.. example B0001-POPULATE-FIELDS. MOVE TO WS00-COMP-FORM MOVE TO WS00-COMP1-FORM MOVE TO WS00-COMP2-FORM MOVE TO WS00-COMP3-FORM B0002-DISPLAY-FIELDS. DISPLAY '******************************************' DISPLAY '* COMP DISPLAY IS : ' WS00-COMP-FORM DISPLAY '* COMP1 DISPLAY IS : ' WS00-COMP1-FORM DISPLAY '* COMP2 DISPLAY IS : ' WS00-COMP2-FORM DISPLAY '* COMP3 DISPLAY IS : ' WS00-COMP3-FORM DISPLAY '******************************************' ****************************************** * COMP DISPLAY IS : * COMP1 DISPLAY IS : E 05 * COMP2 DISPLAY IS : E 05 * COMP3 DISPLAY IS : ****************************************** Output SPOOL

Copyright © 2005, Infosys Technologies Ltd 70 ER/CORP/CRS/LA01/003 Version 1.0  Data Movement verbs. (MOVE)  Sequence Control verbs (IF,PERFORM,EVALUATE)  Types of conditions.  REDEFINES, RENAMES, USAGE clauses Review

Copyright © 2005, Infosys Technologies Ltd 71 ER/CORP/CRS/LA01/003 Version 1.0 What is wrong with the following code (1) IF A EQUALS B MOVE 1 TO A END –IF This should be ; IF A IS EQUAL TO B Review questions

Copyright © 2005, Infosys Technologies Ltd 72 ER/CORP/CRS/LA01/003 Version 1.0 How many times will the paragraph named 100-PARA be executed by the following PERFORM STATEMENT PERFORM 100-PARA VARYING X FROM 1 BY 1 UNTIL X=10 PERFORM 100-PARA VARYING X FROM 1 BY 1 UNTIL X > 10 PERFORM 100-PARA VARYING X FROM 0 BY 1 UNTIL X=10 9 TIMES 10 TIMES Review questions..

Copyright © 2005, Infosys Technologies Ltd 73 ER/CORP/CRS/LA01/003 Version 1.0 State true or false –The justified clause can be used for any data type –The redefines clause can be used to redefine only elementary items –The data item at the level 49 will always have a picture clause –In a move statement, though the sending field is one, the receiving fields may be more than one. False True Review questions

Copyright © 2005, Infosys Technologies Ltd 74 ER/CORP/CRS/LA01/003 Version 1.0 Summary Data Movement verbs. Sequence Control verbs. Types of conditions. REDEFINES, RENAMES, USAGE clauses. Design and development of sample programs

Copyright © 2005, Infosys Technologies Ltd 75 ER/CORP/CRS/LA01/003 Version 1.0 Thank You!