Two and three dimension tables Please use speaker notes for additional information!

Slides:



Advertisements
Similar presentations
DT266/2 Information Systems COBOL Revision. Chapters 1 & 2 Hutty & Spence Divisions of a Cobol Program Identification Division Program-ID. Environment.
Advertisements

Check Digit - Mod 11 Please use speaker notes for additional information!
2-1 Chapter 2.  Coding Requirements of IDENTIFICATION DIVISION  Sections of ENVIRONMENT DIVISION  Assigning Files to Devices in ENVIRONMENT DIVISION.
Final Total Lines in COBOL Please be sure you can see the speaker notes - they contain additional information!
Cobol application using ODBC or File processing Vandana Janeja CIS 365 With COBOL OR PowerCobol.
Program COBOL-2. *TABLE DATA EMBEDDED FOR REDEFINES OF TABLE BELOW ************************************************* 01 TABLE-WORK-AREA. 05 PT-SUB.
Chapter 15 Indexed Sequential Files. Disk File Organization File is collection of records Three major ways records stored or organized on disk - Sequential.
The IDENTIFICATION and ENVIRONMENT DIVISIONS Chapter 2.
Screen Section Please use speaker notes for additional information!
Processing with VSAM Files Please use speaker notes for additional information!
COBOL for the 21 st Century Stern, Stern, Ley Chapter 1 INTRODUCTION TO STRUCTURED PROGRAM DESIGN IN COBOL.
COBOL COmmon Business Oriented Language  Work began in 1959 and has never stopped.
COBOL for the 21st Century
Two dimensional arrays Please use speaker notes for additional information!
Advanced Sequential Files 1.. Single Record Type Files  In a file which contains only one record type (the kind we have examined so far) the record structure.
Relative Files.. Creating a Relative File $ SET SOURCEFORMAT"FREE" IDENTIFICATION DIVISION. PROGRAM-ID. CreateRelativeFromSeq. * Creates a Relative file.
Structured COBOL Programming, Stern & Stern, 9th edition
12-1 Structured COBOL Programming Nancy Stern Hofstra University Robert A. Stern Nassau Community College James P. Ley University of Wisconsin-Stout John.
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)
2-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 To familiarize you with  Why COBOL is a popular business-oriented language.  Programming practices and techniques  History of COBOL.
Modifications to program Addda.cbl Please use speaker notes for additional information!
History COBOL (Common Business Oriented Language) was one of the earliest high-level programming languages. COBOL was first proposed in 1959 by the Conference.
Programming Examples to Accompany Structure Topic Please use speaker notes for additional information!
Introduction to Tables/Arrays Please use the speaker notes for additional information. Tables/Arrays.
Totals on the Screen Please use speaker notes for additional information!
What is a Database? A Database is…  an organized set of stored information usually on one topic  a collection of records  a way to organize information.
Agenda Reporting Work on Assignment 4! Printing on power systems.
Lecture 31 Numeric Edited Alphabetic (A) AlphaNumeric (X) Numeric (9, V, S) Numeric Edited (9, Z, comma, decimal point, minus sign) –Z = zero suppressed.
1 Interactive vs Batch Programs Cobol suited for developing both types of programs Interactive programs Accept input data from keyboard Input data processed.
Printing on power systems Program/ Command Data Report Layout (Printer File) Job Output Queue *FILE Spooled File.
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).
Array - adding to array at run time Please see speaker notes for additional information!
Chapter 7 File I/O 1. File, Record & Field 2 The file is just a chunk of disk space set aside for data and given a name. The computer has no idea what.
Indexed and Relative File Processing
Edit Programs Please use speaker notes for additional information. Example: payedit.cbl payedit.cbl.
1 The Procedure Division Chapter 4. 2 Main Two Sections File Section –Used to define files and record formats –Field names within records Working Storage.
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.
Explanation of SAMPLEIF (if88in1.cbl or if88in1.html) Please use speaker notes for additional information!
Any Questions!. Test Coming Up! Agenda Printing with Externally Described Printer Files Arrays.
COBOL Screens Please use speaker notes for additional information!
Structured COBOL Programming, Stern & Stern, 9th Edition CHAPTER 2 Cobol Language Fundamentals.
1 Chapter 5 – The Procedure Division File handling statements –OPEN statement Initiates processing for a file Input Output Each file opened must have been.
2-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.  Introduction  The Benefits of the Report Writer Module ◦ For Detail and Summary Printing ◦ For Control Break Processing ◦ For Printing Headings.
IBM-Mainframes COBOL Class-1. Background and History  COBOL is an acronym for: Common Business Oriented Language  COBOL was developed in 1959 by the.
Module 1 1. Cobol Hierarchy Revised on COBOL Hierarchy There are four DIVISIONS:- IDENTIFICATION DIVISION. ENVIRONMENT DIVISION. DATA DIVISION.
Any Questions? Week 1 - 2nd Lecture Intro to COBOL Programming Defining Files and Processing Data.
Analysis of SAMPLE1.CBL Please check speaker notes for additional information!
Introduction to Arrays. Objectives Distinguish between a simple variable and a subscripted variable. Input, output, and manipulate values stored in a.
Indexed Files.. Creating an Indexed File $ SET SOURCEFORMAT"FREE" IDENTIFICATION DIVISION. PROGRAM-ID. CreateIndexedFromSeq. * Creates an indexed file.
Week 2/3 - 2nd Lecture Intro to COBOL Programming Defining Files and Processing Data.
371 Structured COBOL Programming Nancy Stern Hofstra University Robert A. Stern Nassau Community College James P. Ley University of Wisconsin-Stout John.
Random update Please use speaker notes for additional information!
Sequential Processing to Update a File Please use speaker notes for additional information!
Sequential Update Assignment Notes Please use speaker notes for additional information!
Introduction to Sequential Files. COBOL's forte  COBOL is generally used in situations where the volume of data to be processed is large.  These systems.
General Introduction Algorithms. Let’s write a program  A program is a collection of statements written in a language the computer understands.  A computer.
Notes: **A Row is considered one Record. **A Column is a Field. A Database is…  an organized set of stored information usually on one topic  a collection.
Submitting Instructions on web site CS 1024 students Read guide
TRADING STOCK PAGE 295 NAME, TEACHER AND DATE.
Programming in COBOL.
Any Questions?.
Structured Program Design
Minor, Intermediate and Major Breaks
Indexed File Processing
Using screens and adding two numbers - addda.cbl
Date Conversion Program
Presentation transcript:

Two and three dimension tables Please use speaker notes for additional information!

IDENTIFICATION DIVISION. PROGRAM-ID. TWODIM. AUTHOR. GROCER. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. SELECT INPUT-FILE ASSIGN TO "C:\PCOBWIN\CIS12FST\TWODIM.DAT". SELECT PRINT-FILE ASSIGN TO PRINTER. DATA DIVISION. FILE SECTION. FD INPUT-FILE DATA RECORD IS INPUT-REC. 01 INPUT-REC. 05 CUST-ID PIC X(4). 05 FROM-CITY PIC TO-CITY PIC 9. FD PRINT-FILE DATA RECORD IS PRINTZ. 01 PRINTZ. 05 FILLER PIC X(4). 05 CUST-ID-PR PIC X(4). 05 FILLER PIC X(15). 05 FROM-CITY-PR PIC X(10). 05 FILLER PIC X(5). 05 TO-CITY-PR PIC X(10). 05 FILLER PIC X(5). 05 FARE-PR PIC $ZZZ FILLER PIC X(20). twodim.cbl These two input fields are going to be used as the subscripts to get information out of the two dimension table. Input data: The fare from the two- dimensional table will print in this field. The city names from the 2 one-dimensional tables will print in these fields. WORKING-STORAGE SECTION. 01 PROGRAM-INDICATORS. 05 MORE-RECS PIC XXX VALUE "YES". 01 WORK-AREAS. 05 INV-VALUE-WS PIC 9(5)V99 VALUE 0.

01 FARE-TABLE. 05 FROM-BOSTON. 10 TO-ISTANBUL PIC 999V99 VALUE TO-BUDAPEST PIC 999V99 VALUE TO-FRANKFORT PIC 999V99 VALUE TO-LONDON PIC 999V99 VALUE TO-PRAGUE PIC 999V99 VALUE FROM-PROVIDENCE. 10 TO-ISTANBUL PIC 999V99 VALUE TO-BUDAPEST PIC 999V99 VALUE TO-FRANKFORT PIC 999V99 VALUE TO-LONDON PIC 999V99 VALUE TO-PRAGUE PIC 999V99 VALUE FROM-NEW-YORK. 10 TO-ISTANBUL PIC 999V99 VALUE TO-BUDABEST PIC 999V99 VALUE TO-FRANKFORT PIC 999V99 VALUE TO-LONDON PIC 999V99 VALUE TO-PRAGUE PIC 999V99 VALUE RDF-FARE-TABLE REDEFINES FARE-TABLE. 05 FROM-CITIES OCCURS 3 TIMES. 10 FARE PIC 999V99 OCCURS 5 TIMES. twodim.cbl

01 FROM-CITY-TABLE. 05 FILLER PIC X(10) VALUE "BOSTON ". 05 FILLER PIC X(10) VALUE "PROVIDENCE". 05 FILLER PIC X(10) VALUE "NEW YORK ". 01 RDF-FROM-CITY-TABLE REDEFINES FROM-CITY-TABLE. 05 FROM-CITY-NAME PIC X(10) OCCURS 3 TIMES. 01 TO-CITY-TABLE. 05 FILLER PIC X(10) VALUE "ISTANBUL ". 05 FILLER PIC X(10) VALUE "BUDAPEST ". 05 FILLER PIC X(10) VALUE "FRANKFORT ". 05 FILLER PIC X(10) VALUE "LONDON ". 05 FILLER PIC X(10) VALUE "PRAGUE ". 01 RDF-TO-CITY-TABLE REDEFINES TO-CITY-TABLE. 05 TO-CITY-NAME PIC X(10) OCCURS 5 TIMES. 01 FARE-TABLE. 05 FROM-BOSTON. 10 TO-ISTANBUL PIC 999V99 VALUE TO-BUDAPEST PIC 999V99 VALUE TO-FRANKFORT PIC 999V99 VALUE TO-LONDON PIC 999V99 VALUE TO-PRAGUE PIC 999V99 VALUE FROM-PROVIDENCE. 10 TO-ISTANBUL PIC 999V99 VALUE TO-BUDAPEST PIC 999V99 VALUE TO-FRANKFORT PIC 999V99 VALUE TO-LONDON PIC 999V99 VALUE TO-PRAGUE PIC 999V99 VALUE FROM-NEW-YORK. 10 TO-ISTANBUL PIC 999V99 VALUE TO-BUDABEST PIC 999V99 VALUE TO-FRANKFORT PIC 999V99 VALUE TO-LONDON PIC 999V99 VALUE TO-PRAGUE PIC 999V99 VALUE RDF-FARE-TABLE REDEFINES FARE-TABLE. 05 FROM-CITIES OCCURS 3 TIMES. 10 FARE PIC 999V99 OCCURS 5 TIMES. twodim.cbl FROM-CITY on the input has values of 1, 2, or 3. It will be used as a subscript to move the FROM-CITY-NAME from this table. MOVE FROM-CITY-NAME (FROM-CITY).. TO-CITY on the input has values of 1, 2, 3, 4 or 5. It will be used as a subscript to move the TO- CITY-NAME from this table. MOVE TO-CITY-NAME (TO-CITY)... You can see that there are three 05s that describe the 3 places you can fly from. In this example consider these the rows. Under the redefines, I am redefining these as 05 FROM-CITIES. Under each of the 05s, I have put five 10 levels to describe each of the cities I can fly to. In this example, consider them columns. On the redefines, these are called FARE with an occurs of 5 times. Looking at it, I have three 05s redefined as 05 occurs 3 times and under each 05 in the original table I have five 10s redefined as 10 FARE with a picture and occurs 5 times.

01 PAGE-CONTROL. 05 PAGE-NO PIC 99 VALUE LINE-CT PIC 99 VALUE DATE-WS. 05 YR-WS PIC 99 VALUE MO-WS PIC 99 VALUE DA-WS PIC 99 VALUE PAGE-HDR. 05 FILLER PIC XX VALUE SPACES. 05 DATE-HDR. 10 MO-HDR PIC FILLER PIC X VALUE "/". 10 DA-HDR PIC FILLER PIC X VALUE "/". 10 YR-HDR PIC FILLER PIC X(22) VALUE SPACES. 05 FILLER PIC X(16) VALUE "AIR FARE REPORT". 05 FILLER PIC X(20) VALUE SPACES. 05 FILLER PIC X(5) VALUE "PAGE ". 05 PAGE-NO-HDR PIC Z9. 05 FILLER PIC X(5) VALUE SPACES. 01 COLUMN-HDR. 05 FILLER PIC X VALUE SPACES. 05 FILLER PIC X(10) VALUE "PASSENGER ". 05 FILLER PIC X(12) VALUE SPACES. 05 FILLER PIC X(10) VALUE "ORIGINATE ". 05 FILLER PIC X(5) VALUE SPACES. 05 FILLER PIC X(11) VALUE "DESTINATION". 05 FILLER PIC X(6) VALUE SPACES. 05 FILLER PIC X(4) VALUE "FARE". 05 FILLER PIC X(16) VALUE SPACES. twodim.cbl

PROCEDURE DIVISION. MAINLINE. PERFORM A-100-STARTUP. PERFORM B-100-PROCESS. PERFORM C-100-WRAPUP. STOP RUN. A-100-STARTUP. OPEN INPUT INPUT-FILE OUTPUT PRINT-FILE. PERFORM U-000-DATE-ROUT. B-100-PROCESS. READ INPUT-FILE AT END MOVE "NO " TO MORE-RECS. PERFORM B-200-LOOP UNTIL MORE-RECS = "NO ". B-200-LOOP. PERFORM B-300-DETAIL. READ INPUT-FILE AT END MOVE "NO " TO MORE-RECS. B-300-DETAIL. IF LINE-CT > 55 OR PAGE-NO = 1 PERFORM B-400-HDR-ROUT. MOVE SPACES TO PRINTZ. MOVE CUST-ID TO CUST-ID-PR. MOVE FROM-CITY-NAME (FROM-CITY) TO FROM-CITY-PR. MOVE TO-CITY-NAME (TO-CITY) TO TO-CITY-PR. MOVE FARE (FROM-CITY, TO-CITY) TO FARE-PR. WRITE PRINTZ AFTER ADVANCING 1 LINES. ADD 1 TO LINE-CT. This line moves the FROM- CITY-NAME from the one dimensional table, subscripted by FROM-CITY from the input to the field on the print line. twodim.cbl This line moves the TO-CITY- NAME from the one dimensional table subscripted by TO-CITY from the input to the field on the print line. This line moves the FARE, first subscripted by FROM- CITY to get into the correct 05 level and then subscripted by TO-CITY to get into the correct 10 level. It moves the subscripted FARE to the field on the print line.

B-400-HDR-ROUT. MOVE PAGE-NO TO PAGE-NO-HDR. WRITE PRINTZ FROM PAGE-HDR AFTER ADVANCING PAGE. WRITE PRINTZ FROM COLUMN-HDR AFTER ADVANCING 2 LINES. MOVE SPACES TO PRINTZ. WRITE PRINTZ AFTER ADVANCING 1 LINES. ADD 1 TO PAGE-NO. MOVE 4 TO LINE-CT. U-000-DATE-ROUT. ACCEPT DATE-WS FROM DATE. MOVE MO-WS TO MO-HDR. MOVE DA-WS TO DA-HDR. MOVE YR-WS TO YR-HDR. C-100-WRAPUP. CLOSE INPUT-FILE PRINT-FILE. twodim.cbl

05/01/99 AIR FARE REPORT PAGE 1 PASSENGER ORIGINATE DESTINATION FARE 1111 PROVIDENCE FRANKFORT $ PROVIDENCE BUDAPEST $ NEW YORK FRANKFORT $ PROVIDENCE PRAGUE $ BOSTON LONDON $ BOSTON ISTANBUL $ NEW YORK PRAGUE $ This is the result of the MOVE FARE (FROM-CITY, TO-CITY) TO FARE-PR. This is the result of the: MOVE FROM-CITY-NAME (FROM-CITY) TO FROM-CITY-PR. twodim.cbl This is the result of the: MOVE TO-CITY-NAME (TO-CITY) TO TO-CITY-PR.

Alternate way of setting up the two dimension table: 01 FARE-TABLE-WAY2. 05 TO-ISTANBUL. 10 FROM-BOSTON PIC 999V99 VALUE FROM-PROV PIC 999V99 VALUE FROM-NEW-YORK PIC 999V99 VALUE TO-BUDAPEST. 10 FROM-BOSTON PIC 999V99 VALUE FROM-PROV PIC 999V99 VALUE FROM-NEW-YORK PIC 999V99 VALUE TO-FRANKFORT. 10 FROM-BOSTON PIC 999V99 VALUE FROM-PROV PIC 999V99 VALUE FROM-NEW-YORK PIC 999V99 VALUE TO-LONDON. 10 FROM-BOSTON PIC 99V99 VALUE FROM-PROV PIC 99V99 VALUE FROM-NEW-YORK PIC 999V99 VALUE TO-PRAGUE. 10 FROM-BOSTON PIC 99V99 VALUE FROM-PROV PIC 99V99 VALUE FROM-NEW-YORK PIC 999V99 VALUE RDF-FARE-TABLE REDEFINES FARE-TABLE. 05 TO-CITIES OCCURS 5 TIMES. 10 FARE PIC 999V99 OCCURS 3 TIMES.

01 FARE-TABLE-WAY2. 05 TO-ISTANBUL. 10 FROM-BOSTON PIC 999V99 VALUE FROM-PROV PIC 999V99 VALUE FROM-NEW-YORK PIC 999V99 VALUE TO-BUDAPEST. 10 FROM-BOSTON PIC 999V99 VALUE FROM-PROV PIC 999V99 VALUE FROM-NEW-YORK PIC 999V99 VALUE TO-FRANKFORT. 10 FROM-BOSTON PIC 999V99 VALUE FROM-PROV PIC 999V99 VALUE FROM-NEW-YORK PIC 999V99 VALUE TO-LONDON. 10 FROM-BOSTON PIC 99V99 VALUE FROM-PROV PIC 99V99 VALUE FROM-NEW-YORK PIC 999V99 VALUE TO-PRAGUE. 10 FROM-BOSTON PIC 99V99 VALUE FROM-PROV PIC 99V99 VALUE FROM-NEW-YORK PIC 999V99 VALUE RDF-FARE-TABLE REDEFINES FARE-TABLE. 05 TO-CITIES OCCURS 5 TIMES. 10 FARE PIC 999V99 OCCURS 3 TIMES. Alternate approach INPUT: 05 FROM-CITY PIC TO-CITY PIC 9. In the PROCEDURE DIVISION: MOVE FARE(TO-CITY, FROM-CITY) TO FARE-PR.

3 dimension table 01 THREE-DIM-TABLE. 05 DAY-RATES. 10 DAY-S-S. 15 TO-FR PIC 9V99 VALUE TO-NB PIC 9V99 VALUE TO-NP PIC 9V99 VALUE TO-PR PIC 9V99 VALUE DAY-P-P. 15 TO-FR PIC 9V99 VALUE TO-NB PIC 9V99 VALUE TO-NP PIC 9V99 VALUE TO-PR PIC 9V99 VALUE EVENING-RATES. 10 EVENING-S-S. 15 TO-FR PIC 9V99 VALUE TO-NB PIC 9V99 VALUE TO-NP PIC 9V99 VALUE TO-PR PIC 9V99 VALUE EVENING-P-P. 15 TO-FR PIC 9V99 VALUE TO-NB PIC 9V99 VALUE TO-NP PIC 9V99 VALUE TO-PR PIC 9V99 VALUE NIGHT-RATES. 10 NIGHT-S-S. 15 TO-FR PIC 9V99 VALUE TO-NB PIC 9V99 VALUE TO-NP PIC 9V99 VALUE TO-PR PIC 9V99 VALUE NIGHT-P-P. 15 TO-FR PIC 9V99 VALUE TO-NB PIC 9V99 VALUE TO-NP PIC 9V99 VALUE TO-PR PIC 9V99 VALUE RDF-THREE-DIM-TABLE REDEFINES THREE-DIM-TABLE. 05 TIME-PERIODS OCCURS 3 TIMES. 10 TYPE-CALLS OCCURS 2 TIMES. 15 RATE PIC 9V99 OCCURS 4 TIMES. 01 INPUT-RECORDS TIME-CODE PIC TYPE-CODE PIC PLACE-CODE PIC 9. MOVE RATE (TIME-CODE, TYPE-CODE, PLACE-CODE) TO RATE-PR. Here we move the RATE subscripted by the TIME-CODE which takes us to the correct 05 level, and the TYPE- CODE that takes us to the correct 10 level under the 05, and the PLACE- CODE which takes us to the correct 15 level.