View previous topic :: View next topic |
Author |
Message |
shekar123 Advanced
Joined: 22 Jul 2005 Posts: 528 Topics: 90 Location: Bangalore India
|
Posted: Thu Aug 25, 2005 6:26 am Post subject: Report Program COBOL needed |
|
|
Hi, i am basically trying to generate a report / write a report program COBOL to get my desired output.I am very new to report writing programs and i want to try to practise this as a exercise.Can anyone help me about how should i go about it ? How do i test my report program whether it is working fine or not ? Morever cananyone guide me the JCL to execute this program also ? If anybody can give me link to a sample Report Program ,it will be really helpful for me.
My requirement:
---------------
I have a input dataset with 20 records of fixed bytes with lrecl = 80,i should write a program to read the input file record by record and calculate the sum of individual marks of each student and write a report as shown below with total marks and calculating average also.If average > 60 declare as first class ,if avg > 40 and < 60 declare second class and if avg is < 40 declare as fail and the report should be 133 record length where in i can print on a printer.If my report exceeds more than 1 page how should i take care of the report with the page number also.
Code: |
SERIAL NO NAME M1 M2 M3 M4 M5
--------- ------ --- --- --- --- ---
1 SHEKAR 65 87 98 46 40
2 B
3 C
4 D
5 E
6 F
7 G
8 H
9 I
10 J
11 K
12 L
13 M
14 N
15 O
16 P
17 Q
18 R
19 S
20 T
01 INPUT-REC.
05 SERIAL PIC 9(2).
05 FILLER PIC X(1) VALUE SPACE.
05 NAME PIC X(20).
05 FILLER PIC X(1) VALUE SPACE.
05 M1 PIC 9(3).
05 FILLER PIC X(1) VALUE SPACE.
05 M1 PIC 9(3).
05 FILLER PIC X(1) VALUE SPACE.
05 M2 PIC 9(3).
05 FILLER PIC X(1) VALUE SPACE.
05 M3 PIC 9(3).
05 FILLER PIC X(1) VALUE SPACE.
05 M4 PIC 9(3).
05 FILLER PIC X(1) VALUE SPACE.
05 M5 PIC 9(3).
05 FILLER PIC X(33) VALUE SPACES.
|
Code: |
-----------------------------------------------------------------
PAGE NO:
DATE :
TIME :
ABC UNIVERSTITY NAME
MARK SHEET OF STUDENTS
SERIAL NO NAME M1 M2 M3 M4 M5 TOTAL MARKS AVG RESULT
--------- ------ --- --- --- --- --- ------------ --- ------
1 SHEKAR 65 87 98 46 40 326 65.2 FIRST CLASS
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
TOTAL STUDENTS PASSED WITH FIRST CLASS : XXXX
TOTAL STUDENTS PASSED WITH SECOND CLASS : XXXX
TOTAL STUDENTS FAILED : XXXX
***************END OF REPORT******************************************************
|
|
|
Back to top |
|
 |
kolusu Site Admin

Joined: 26 Nov 2002 Posts: 12378 Topics: 75 Location: San Jose
|
Posted: Thu Aug 25, 2005 12:04 pm Post subject: |
|
|
Shekhar,
I guess this is a class room exercise. So I am not going to write the code out for you. But I will explain briefly.
1. Declare 2 variables for individual totals and average.
Code: |
01 WS-INDV-TOT-MARKS PIC 9(06).
02 WS-INV-AVG-MARKS PIC 9(03)V9(2).
|
2. Declare 3 variables for GRAND TOTAL Counts.
Code: |
01 WS-TOT-FCLASS-COUNT PIC 9(06).
01 WS-TOT-SCLASS-COUNT PIC 9(06).
01 WS-TOT-TCLASS-COUNT PIC 9(06).
|
2. Read the file and perform calculations till the end of file.
Code: |
COMPUTE WS-INDV-TOT-MARKS = M1 + M2 + M3 + M4 + M5
COMPUTE WS-INDV-AVG-MARKS = WS-INDV-TOT-MARKS / 5
|
3. Define report file layout for 133 bytes and define rpt headers as follows
Code: |
01 P-RPT-HEADER1.
05 P-H1-CC PIC X(01) VALUE '1'.
05 FILLER PIC X(14) VALUE
' PAGE NO: '.
05 P-H1-PAGE-NO PIC ZZZ,ZZ9 VALUE ZERO.
05 FILLER PIC X(111) VALUE SPACES.
... so on
|
4. Define a variable to hold the no: of lines written on the report.
Code: |
WS-RPT-LINE-COUNT PIC 9(02) VALUE 0.
|
Everytime you write a output record , increment the counter and once it reaches 55 write the headers once again.
Code: |
IF WS-RPT-LINE-COUNT > 55
MOVE ZEROES TO WS-RPT-LINE-COUNT
ADD +1 TO THE WS-PAGE-COUNTER
PERFORM WRITE-RPT-HEADERS
END-IF
|
It is as simple as that. Now try to code the pgm with the above suggestions and comeback if you have any questions.
Hope this helps...
Cheers
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
 |
shekar123 Advanced
Joined: 22 Jul 2005 Posts: 528 Topics: 90 Location: Bangalore India
|
Posted: Thu Aug 25, 2005 2:45 pm Post subject: Report Program COBOL needed |
|
|
Thanks Kolusu,
I have understood how to go about the requirement now after seeing u answer.i need a small clarification here why is the concept of 55 number is required as my records are only 20 ."Everytime you write a output record , increment the counter and once it reaches 55 write the headers once again" .Can u briefly highlight the concept of 55 for report programs. |
|
Back to top |
|
 |
Mervyn Moderator

Joined: 02 Dec 2002 Posts: 415 Topics: 6 Location: Hove, England
|
Posted: Thu Aug 25, 2005 3:50 pm Post subject: |
|
|
Shekhar,
55 is just a reasonable value for the maximum number of lines on a page.
If you know there are only 20 records, you can do without the heading routine, but I'd consider that to be pretty careless. _________________ The day you stop learning the dinosaur becomes extinct |
|
Back to top |
|
 |
God Beginner
Joined: 31 Aug 2005 Posts: 1 Topics: 0
|
Posted: Wed Aug 31, 2005 12:59 am Post subject: |
|
|
Hi kolusu, iam a beginner, so my quries might me silly , but i would be happy, if you could help me out.
i have dataset which has a header , deatil records and trailer part.
the header portion is of 10 lines and the trailer portion is of 10 lines and the 50 detail records.
i need to write a program to copy this dataset to another dataset. how do i do it ??
Details:
dataset : PS
record length: 170.
record Format : FB
can you kindly guide me.
Thanks
stanly |
|
Back to top |
|
 |
kolusu Site Admin

Joined: 26 Nov 2002 Posts: 12378 Topics: 75 Location: San Jose
|
Posted: Wed Aug 31, 2005 3:13 am Post subject: |
|
|
Quote: |
I need to write a program to copy this dataset to another dataset. how do i do it ??
|
stanly,
You can use an utility to copy the dataset to another dataset. EX you can use IDCAMS repro or sort to copy.
Code: |
//STEP0100 EXEC PGM=IDCAMS
//SYSPRINT DD SYSOUT=*
//IN DD DSN=YOUR INPUT DATASET,
// DISP=SHR
//OUT DD DSN=YOUR OUTPUT DATASET,
// DISP=(NEW,CATLG,DELETE),
// UNIT=SYSDA,
// SPACE=(CYL,(X,Y),RLSE)
//SYSIN DD *
REPRO INFILE (IN) OUTFILE (OUT)
/*
|
OR
Code: |
//STEP0100 EXEC PGM=SORT
//SYSOUT DD SYSOUT=*
//SORTIN DD DSN=YOUR INPUT DATASET,
// DISP=SHR
//SORTOUT DD DSN=YOUR OUTPUT DATASET,
// DISP=(NEW,CATLG,DELETE),
// UNIT=SYSDA,
// SPACE=(CYL,(X,Y),RLSE)
//SYSIN DD *
SORT FIELDS=COPY
/*
|
Programmatically
Code: |
1. Open both input and output files.
2. Peform until eof of input file.
read the input file
write to the output file
end-perform
3. Close both input and output files.
|
Hope this helps...
Cheers
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
 |
shekar123 Advanced
Joined: 22 Jul 2005 Posts: 528 Topics: 90 Location: Bangalore India
|
Posted: Fri Sep 02, 2005 4:52 am Post subject: REPORT PROGRAM NEEDED |
|
|
Hi Kolusu,
It would be really helful to me if u can give me the code to look in as i can practise it with easy understanding for other examples also.I can try some other report programs as well too. |
|
Back to top |
|
 |
kolusu Site Admin

Joined: 26 Nov 2002 Posts: 12378 Topics: 75 Location: San Jose
|
Posted: Fri Sep 02, 2005 6:26 am Post subject: |
|
|
Quote: |
It would be really helful to me if u can give me the code to look in as i can practise it with easy understanding for other examples also.I can try some other report programs as well too.
|
Nope ! I am not going to write the entire pgm . By taking my code , you will learn nothing. Show me what you have written till now and I will correct/add the necessary code.
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
 |
shekar123 Advanced
Joined: 22 Jul 2005 Posts: 528 Topics: 90 Location: Bangalore India
|
Posted: Sun Sep 04, 2005 9:31 am Post subject: REPORT PROGRAM NEEDED |
|
|
Hai Kolusu,
I have coded as per the suggestions from you but i am unable to complete the task.Please guide me further to complete the coding for the program.
My code
--------
Code: |
IDENTFICATION DIVISION.
PROGRAM-ID. REPORTPGM.
AUTHOR. SHEKAR.
DATE-WRITTEN. 09/02.
DATE-COMPILED. 09/02.
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
SOURCE-COMPUTER. S/390.
OBJECT-COMPUTER. S/390.
INPUT-OUTPUT SECTION.
FILE CONTROL.
SELECT INPUT-FILE ASSIGN TO INPUT
FILE STATUS IS INPUT-FILE-STATUS.
SELECT REPORT-FILE ASSIGN TO REPORTRPT
FILE STATUS IS REPORT-FILE-STATUS.
DATA DIVISION.
FILE SECTION.
FD INPUT-FILE
RECORDING MODE F
RECORD CONTAINS 0 CHARACTERS
DATA RECORD IS INPUT-REC.
01 INPUT-REC.
05 I-SERIAL PIC 9(2).
05 FILLER PIC X(1) VALUE SPACE.
05 I-NAME PIC X(20).
05 FILLER PIC X(1) VALUE SPACE.
05 I-M1 PIC 9(3).
05 FILLER PIC X(1) VALUE SPACE.
05 I-M2 PIC 9(3).
05 FILLER PIC X(1) VALUE SPACE.
05 I-M3 PIC 9(3).
05 FILLER PIC X(1) VALUE SPACE.
05 I-M4 PIC 9(3).
05 FILLER PIC X(1) VALUE SPACE.
05 I-M5 PIC 9(3).
05 FILLER PIC X(33) VALUE SPACES.
FD REPORT-FILE
RECORDING MODE F
RECORD CONTAINS 0 CHARACTERS
DATA RECORD IS REPORT-REC.
01 REPORT-REC.
05 R-SERIAL PIC 9(2).
05 FILLER PIC X(1) VALUE SPACE.
05 R-NAME PIC X(20).
05 FILLER PIC X(1) VALUE SPACE.
05 R-M1 PIC 9(3).
05 FILLER PIC X(1) VALUE SPACE.
05 R-M2 PIC 9(3).
05 FILLER PIC X(1) VALUE SPACE.
05 R-M3 PIC 9(3).
05 FILLER PIC X(1) VALUE SPACE.
05 R-M4 PIC 9(3).
05 FILLER PIC X(1) VALUE SPACE.
05 R-M5 PIC 9(3).
05 FILLER PIC X(1) VALUE SPACE.
05 INDV-TOT-MARKS PIC 9(06).
05 FILLER PIC X(1) VALUE SPACE.
05 INDV-AVG-MARKS PIC 9(03)V99.
05 FILLER PIC X(78) VALUE SPACES.
WORKING-STORAGE SECTION.
01 WS-FILE-STATS.
05 INPUT-FILE-STATUS PIC X(02) VALUE ZERO.
88 INPUT-FILE-IO-OKAY VALUE '00'.
88 INPUT-FILE-END VALUE '10'.
05 REPORT-FILE-STATUS PIC X(02) VALUE ZERO.
88 REPORT-FILE-IO-OKAY VALUE '00'.
88 REPORT-FILE-END VALUE '10'.
01 WS-FLAGS.
05 INPUT-EOF-SWITCH PIC X(01) VALUE SPACE.
88 INPUT-EOF VALUE 'Y'.
88 INPUT-NOT-EOF VALUE 'N'.
01 WS-INDV-TOT-MARKS PIC 9(06).
01 WS-INDV-AVG-MARKS PIC 9(03)V9(2).
01 EDITED-INDV-AVG-MARKS PIC 9(3).9(2).
01 WS-RPT-LINE-COUNT PIC 9(02) VALUE 0.
01 WS-PAGE-COUNTER PIC 9(02) VALUE 0.
01 TOTALS.
05 WS-TOT-FCLASS-COUNT PIC 9(06).
05 WS-TOT-SCLASS-COUNT PIC 9(06).
05 WS-TOT-TCLASS-COUNT PIC 9(06).
*******************************************************************
* REPORT HEADINGS *
* *
*******************************************************************
01 P-RPT-HEADER1.
05 P-H1-CC PIC X(01) VALUE '1'.
05 FILLER PIC X(14) VALUE
' PAGE NO: '.
05 P-H1-PAGE-NO PIC ZZZ,ZZ9 VALUE ZERO.
05 FILLER PIC X(111) VALUE SPACES.
01 P-RPT-HEADER2.
05 P-H2-CC PIC X(01) VALUE '1'.
05 FILLER PIC X(14) VALUE
' DATE: '.
05 P-H1-DATE PIC X(10) VALUE SPACES.
05 FILLER PIC X(109) VALUE SPACES.
01 P-RPT-HEADER3.
05 P-H3-CC PIC X(01) VALUE '1'.
05 FILLER PIC X(14) VALUE
' TIME: '.
05 P-H1-TIME PIC X(10) VALUE SPACES.
05 FILLER PIC X(109) VALUE SPACES.
01 P-RPT-HEADER4.
05 P-H4-CC PIC X(01) VALUE '1'.
05 FILLER PIC X(30) VALUE SPACES.
05 P-H4 PIC X(50) VALUE "ABC UNIVERSITY NAME".
05 FILLER PIC X(52) VALUE SPACES.
01 P-RPT-HEADER5.
05 P-H5-CC PIC X(01) VALUE '1'.
05 FILLER PIC X(30) VALUE SPACES.
05 P-H5 PIC X(50) VALUE "MARK SHEET OF STUDENTS".
05 FILLER PIC X(52) VALUE SPACES.
01 P-RPT-HEADER6.
05 P-H6-CC PIC X(01) VALUE '1'.
05 FILLER PIC X(10) VALUE "SERIAL NO".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(5) VALUE "NAME".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(2) VALUE "M1".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(2) VALUE "M2".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(2) VALUE "M3".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(2) VALUE "M4".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(2) VALUE "M5".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(12) VALUE "TOTAL MARKS".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(03) VALUE "AVG".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(10) VALUE "RESULT".
05 FILLER PIC X(73) VALUE SPACE.
01 P-RPT-HEADER7.
05 P-H7-CC PIC X(01) VALUE '1'.
05 FILLER PIC X(10) VALUE "---------".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(5) VALUE "-----".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(3) VALUE "---".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(3) VALUE "---".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(3) VALUE "---".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(3) VALUE "---".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(3) VALUE "---".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(12) VALUE "------------".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(03) VALUE "---".
05 FILLER PIC X(1) VALUE SPACE.
05 FILLER PIC X(10) VALUE "----------".
05 FILLER PIC X(68) VALUE SPACES.
01 P-RPT-HEADER8.
05 P-H8-CC PIC X(01) VALUE '1'.
05 FILLER PIC X(50) VALUE
"TOTAL STUDENTS PASSED WITH FIRST CLASS: ".
05 FILLER PIC X(1) VALUE SPACE.
05 WS-TOT-FCLASS-COUNT PIC ZZZZ99 VALUE ZERO.
05 FILLER PIC X(75) VALUE SPACES.
01 P-RPT-HEADER9.
05 P-H9-CC PIC X(01) VALUE '1'.
05 FILLER PIC X(50) VALUE
"TOTAL STUDENTS PASSED WITH SECOND CLASS: ".
05 FILLER PIC X(1) VALUE SPACE.
05 WS-TOT-SCLASS-COUNT PIC ZZZZ99 VALUE ZERO.
05 FILLER PIC X(75) VALUE SPACES.
01 P-RPT-HEADER10.
05 P-H10-CC PIC X(01) VALUE '1'.
05 FILLER PIC X(50) VALUE
"TOTAL STUDENTS PASSED WITH FAILED: ".
05 FILLER PIC X(1) VALUE SPACE.
05 WS-TOT-TCLASS-COUNT PIC ZZZZ99 VALUE ZERO.
05 FILLER PIC X(75) VALUE SPACES.
01 P-RPT-HEADER11.
05 P-H11-CC PIC X(01) VALUE '1'.
05 FILLER PIC X(50) VALUE
"*************END OF REPORT************".
05 FILLER PIC X(82) VALUE SPACES.
PROCEDURE DIVISION.
000-MAINPARA.
PERFROM 100-STARTUP.
PERFORM 200-PROCESS-DATA.
PERFORM 300-FINISH.
STOP RUN.
100-STARTUP.
OPEN INPUT INPUT-FILE.
IF INPUT-FILE-STATUS NOT EQUAL TO ZERO
DISPLAY 'INPUT FILE FAILED TO OPEN' INPUT-FILE-STATUS
PERFORM ABEND-PARA
END-IF.
OPEN OUTPUT REPORT-FILE.
IF REPORT-FILE-STATUS NOT EQUAL TO ZERO
DISPLAY 'REPORT FILE FAILED TO OPEN' REPORT-FILE-STATUS
PERFORM ABEND-PARA
END-IF.
200-PROCESS-DATA.
INITIALIZE REPORT-REC.
PERFORM UNTIL INPUT-EOF
READ INPUT-FILE INTO REPORT-REC
AT END
SET INPUT-EOF TO TRUE
NOT AT END
PERFORM 210-READ-DATA
IF INPUT-FILE-STATUS IS EQUAL TO '00
ADD 1 TO WS-IN-CNT
ELSE
DISPLAY '200:READ FAILED FOR INPUT FILE'
DISPLAY 'INPUT FILE STATUS' INPUT-FILE-STATUS
PERFORM ABEND-PARA
END-IF
COMPUTE WS-INDV-TOT-MARKS = R-M1 + R-M2 + R-M3 + R-M4 + R-M5.
COMPUTE WS-INDV-AVG-MARKS = WS-INDV-TOT-MARKS / 5.
MOVE WS-INDV-AVG-MARKS TO EDITED-INDV-AVG-MARKS.
MOVE WS-INDV-TOT-MARKS TO INDV-TOT-MARKS
MOVE EDITED-INDV-AVG-MARKS TO INDV-AVG-MARKS
IF EDITED-AVG-MARKS > 60
MOVE "FIRST CLASS" TO R-RESULT
ADD +1 TO WS-TOT-FCLASS-COUNT
IF EDITED-AVG-MARKS > 40 AND < 60
MOVE "SECOND CLASS" TO R-RESULT
ADD +1 TO WS-TOT-SCLASS-COUNT
IF EDITED-AVG-MARKS < 40
MOVE "FAIL" TO R-RESULT
ADD +1 TO WS-TOT-TCLASS-COUNT
END-IF
END-IF
END-IF
ADD +1 TO WS-RPT-LINE-COUNTER
IF WS-RPT-LINE-COUNT > 55
MOVE ZEROES tO WS-RPT-LINE-COUNT
ADD +1 TO THE WS-PAGE-COUNTER
WRITE 250-WRITE-RPT-HEADERS
END-IF
END-PERFORM.
200-READ-DATA.
MOVE I-SERIAL TO R-SERIAL.
MOVE I-NAME TO R-NAME.
MOVE I-M1 TO R-M1.
MOVE I-M2 TO R-M2.
MOVE I-M3 TO R-M3.
MOVE I-M4 TO R-M4.
MOVE I-M5 TO R-M5.
250-WRITE-RPT-HEADERS.
WRITE REPORT-FILE FROM P-RPT-HEADER1 AFTER ADVANCING PAGE.
WRITE REPORT-FILE FROM P-RPT-HEADER2
WRITE REPORT-FILE FROM P-RPT-HEADER3
WRITE REPORT-FILE FROM P-RPT-HEADER4
WRITE REPORT-FILE FROM P-RPT-HEADER5
WRITE REPORT-FILE FROM P-RPT-HEADER6
WRITE REPORT-FILE FROM P-RPT-HEADER7
WRITE REPORT-FILE FROM REPORT-REC
WRITE REPORT-FILE FROM P-RPT-HEADER8
WRITE REPORT-FILE FROM P-RPT-HEADER9
WRITE REPORT-FILE FROM P-RPT-HEADER10
WRITE REPORT-FILE FROM P-RPT-HEADER11
300-FINISH.
CLOSE INPUT-FILE.
IF INPUT-FILE-IO-OKAY
CONTINUE
ELSE
DISPLAY 'INPUT FILE FAILED TO CLOSE' INPUT-FILE-STATUS
PERFORM ABEND-PARA
END-IF.
OPEN OUTPUT REPORT-FILE.
IF REPORT-FILE-IO-OKAY
CONTINUE
ELSE
DISPLAY 'REPORT FILE FAILED TO CLOSE' REPORT-FILE-STATUS
PERFORM ABEND-PARA
END-IF.
ABEND-PARA.
DISPLAY '*************ERROR*********************'.
DISPLAY 'ABEND OCCURED'.
DISPLAY '***************************************'.
STOP RUN.
|
|
|
Back to top |
|
 |
kolusu Site Admin

Joined: 26 Nov 2002 Posts: 12378 Topics: 75 Location: San Jose
|
Posted: Mon Sep 05, 2005 10:15 am Post subject: |
|
|
Shekhar123,
That is a good start. However you have a couple of mistakes in your code.
1. You have open output file statement in the 300-finish
2. If your file is FB(fixed block file) you don't have to use READ INTO
3. Never code a paragraph bigger than a page.
4. change the definiton of INDV-AVG-MARKS to PIC 9(03).99.
5. write a short description of the paragraphs
This is how your code you should look like.(Untested)
Code: |
000-MAINPARA.
PERFROM 100-STARTUP
PERFORM 200-PROCESS-DATA UNTIL INPUT-EOF
PERFORM 300-FINISH
GOBACK.
100-STARTUP.
*************************************************************
* THIS PARAGRAPH OPENS INPUT AND OUTPUT FILES AND DOES THE *
* PRIME READ OF THE INPUT FILE. *
*************************************************************
OPEN INPUT INPUT-FILE
IF INPUT-FILE-STATUS NOT EQUAL TO ZERO
DISPLAY 'INPUT FILE FAILED TO OPEN' INPUT-FILE-STATUS
PERFORM 900-ABEND-PARA
END-IF
OPEN OUTPUT REPORT-FILE
IF REPORT-FILE-STATUS NOT EQUAL TO ZERO
DISPLAY 'REPORT FILE FAILED TO OPEN' REPORT-FILE-STATUS
PERFORM 900-ABEND-PARA
END-IF
PERFORM 210-READ-INPUT-FILE
PERFORM 240-WRITE-RPT-HEADERS
.
200-PROCESS-DATA.
*************************************************************
* THIS PARAGRAPH PERFORMS THE MAIN LOGIC *
*************************************************************
COMPUTE WS-INDV-TOT-MARKS = I-M1 + I-M2 + I-M3 + I-M4 + I-M5
COMPUTE WS-INDV-AVG-MARKS = WS-INDV-TOT-MARKS / 5
PERFORM 220-POPULATE-REPORT-FIELDS
PERFORM 230-WRITE-REPORT-FILE
PERFORM 210-READ-INPUT-FILE
.
210-READ-INPUT-FILE.
*************************************************************
* THIS PARAGRAPH READS THE INPUT-FILE *
*************************************************************
READ INPUT-FILE
AT END
SET INPUT-EOF TO TRUE
END-READ
.
220-POPULATE-REPORT-FIELDS.
*************************************************************
* THIS PARAGRAPH POUPULATES THE REPORT VARIABLES *
*************************************************************
INITIALIZE REPORT-REC
MOVE I-SERIAL TO R-SERIAL.
MOVE I-NAME TO R-NAME.
MOVE I-M1 TO R-M1.
MOVE I-M2 TO R-M2.
MOVE I-M3 TO R-M3.
MOVE I-M4 TO R-M4.
MOVE I-M5 TO R-M5.
MOVE WS-INDV-TOT-MARKS TO INDV-TOT-MARKS
IF WS-INDV-AVG-MARKS > 60
MOVE "FIRST CLASS" TO R-RESULT
ADD +1 TO WS-TOT-FCLASS-COUNT
END-IF
IF WS-INDV-AVG-MARKS > 40 AND WS-INDV-AVG-MARKS < 60
MOVE "SECOND CLASS" TO R-RESULT
ADD +1 TO WS-TOT-SCLASS-COUNT
END-IF
IF WS-INDV-AVG-MARKS < 40
MOVE "FAIL" TO R-RESULT
ADD +1 TO WS-TOT-TCLASS-COUNT
END-IF
.
230-WRITE-REPORT-FILE.
*************************************************************
* THIS PARAGRAPH WRITES THE REPORT *
*************************************************************
IF WS-RPT-LINE-COUNT > 55
MOVE ZEROES tO WS-RPT-LINE-COUNT
ADD +1 TO THE WS-PAGE-COUNTER
WRITE 240-WRITE-RPT-HEADERS
END-IF
WRITE REPORT-REC
ADD +1 TO WS-RPT-LINE-COUNTER
.
240-WRITE-RPT-HEADERS.
*************************************************************
* THIS PARAGRAPH WRITES THE HEADER OF THE REPORT *
*************************************************************
WRITE REPORT-FILE FROM P-RPT-HEADER1 AFTER ADVANCING PAGE
WRITE REPORT-FILE FROM P-RPT-HEADER2
WRITE REPORT-FILE FROM P-RPT-HEADER3
WRITE REPORT-FILE FROM P-RPT-HEADER4
WRITE REPORT-FILE FROM P-RPT-HEADER5
WRITE REPORT-FILE FROM P-RPT-HEADER6
WRITE REPORT-FILE FROM P-RPT-HEADER7
WRITE REPORT-FILE FROM P-RPT-HEADER8
WRITE REPORT-FILE FROM P-RPT-HEADER9
WRITE REPORT-FILE FROM P-RPT-HEADER10
WRITE REPORT-FILE FROM P-RPT-HEADER11
ADD +11 TO WS-RPT-LINE-COUNTER
.
300-FINISH.
*************************************************************
* THIS PARAGRAPH CLOSES THE INPUT & OUTPUT FILES. *
*************************************************************
CLOSE INPUT-FILE
REPORT-FILE
.
900-ABEND-PARA.
*************************************************************
* THIS PARAGRAPH INVOKES THE THE STANDARD ABEND ROUTINE *
*************************************************************
DISPLAY '*************ERROR*********************'
DISPLAY 'ABEND OCCURED'
DISPLAY '***************************************'
STOP RUN
.
|
Hope this helps...
Cheers
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
 |
shekar123 Advanced
Joined: 22 Jul 2005 Posts: 528 Topics: 90 Location: Bangalore India
|
Posted: Mon Sep 05, 2005 9:00 pm Post subject: REPORT PROGRAM NEEDED |
|
|
Kolusu,
Thanks a lot for helping a beginer like me to the maximum possible extent and i am learning a lot from u suggestions.Now i am
understanding well how to write a Report Program.However i have few doubts after i saw u code.
1.WS-INDV-AVG-MARKS is not moved to INDV-AVG-MARKS after WS-INDV-TOT-MARKS is moved to INDV-TOT-MARKS.
2.After opening both input and report file in the para 100-STARTUP,why are we calling the paragraph PERFORM 210-READ-INPUT-
FILE ,in which we are reading the Input File , is it only for reading the first record of the Input File and then performing
the calculations.However i understand the meaning of the PERFORM 200-PROCESS-DATA UNTIL INPUT-EOF ,as u are trying to read
till the end of the file as i have used Inline Perform in my code.
3.How do i print the report headers before actually printing the report rec.I am quite confused how do i do that as i want to
get the headers print first and then the detail rec.In your code , you are printing the headers only after the line count
reaches 55 as
IF WS-RPT-LINE-COUNT > 55
MOVE ZEROES tO WS-RPT-LINE-COUNT
ADD +1 TO THE WS-PAGE-COUNTER
WRITE 240-WRITE-RPT-HEADERS
END-IF
WRITE REPORT-REC
ADD +1 TO WS-RPT-LINE-COUNTER.
REPORT
------
PAGE NO:
DATE :
TIME :
ABC UNIVERSTITY NAME
MARK SHEET OF STUDENTS
SERIAL NO NAME M1 M2 M3 M4 M5 TOTAL MARKS AVG RESULT
--------- ------ --- --- --- --- --- ------------ --- ------
01 SHEKAR 65 87 98 46 40 326 65.2 FIRST CLASS
.
.
.
.
4.why are u adding ADD +11 TO WS-RPT-LINE-COUNTER / WS-RPT-LINE-COUNT to the counter ?
Can u please answer my queries to clear of my doubts. |
|
Back to top |
|
 |
kolusu Site Admin

Joined: 26 Nov 2002 Posts: 12378 Topics: 75 Location: San Jose
|
Posted: Mon Sep 05, 2005 9:57 pm Post subject: |
|
|
Shekhar123,
Quote: |
1.WS-INDV-AVG-MARKS is not moved to INDV-AVG-MARKS after WS-INDV-TOT-MARKS is moved to INDV-TOT-MARKS
|
No Idea as to what you are talking about. However if you are talking about moving to EDITED-INDV-AVG-MARKS , you actually don't have to move.
Quote: |
2.After opening both input and report file in the para 100-STARTUP,why are we calling the paragraph PERFORM 210-READ-INPUT- FILE ,in which we are reading the Input File , is it only for reading the first record of the Input File and then performing the calculations.However i understand the meaning of the PERFORM 200-PROCESS-DATA UNTIL INPUT-EOF ,as u are trying to read till the end of the file as i have used Inline Perform in my code.
|
Well I am reading the first record in the startup it self so that you have the fields ready when you are actually processing the data. Yes I replaced your inline perform with more readable code.
Quote: |
How do i print the report headers before actually printing the report rec.I am quite confused how do i do that as i want to get the headers print first and then the detail rec.In your code , you are printing the headers only after the line count
|
Look at the 100-statup carefully . I am actually writting the headers in the startup paragraph itself.
Code: |
PERFORM 240-WRITE-RPT-HEADERS
|
This will print the report headers initially , and later on we will use the the line counter to print the headers.
Quote: |
4.why are u adding ADD +11 TO WS-RPT-LINE-COUNTER / WS-RPT-LINE-COUNT to the counter ?
|
The total headers in your pgm are 11 lines. So I am adding to +11 to the WS-RPT-LINE-COUNT to keep track of no: of lines written.
Hope this helps...
Cheers
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
 |
shekar123 Advanced
Joined: 22 Jul 2005 Posts: 528 Topics: 90 Location: Bangalore India
|
Posted: Tue Sep 06, 2005 4:08 am Post subject: REPORT PROGRAM NEEDED |
|
|
Hai Kolusu,
I got all my doubts cleared by now and thanks a lot for guiding me and explaining the entire process.I am quite confident enough to code the program. |
|
Back to top |
|
 |
kolusu Site Admin

Joined: 26 Nov 2002 Posts: 12378 Topics: 75 Location: San Jose
|
Posted: Tue Sep 06, 2005 7:37 am Post subject: |
|
|
Quote: |
I am quite confident enough to code the program.
|
Shekhar123,
Are you ready to code another program if a detailed spec is given?
Kolusu _________________ Kolusu
www.linkedin.com/in/kolusu |
|
Back to top |
|
 |
shekar123 Advanced
Joined: 22 Jul 2005 Posts: 528 Topics: 90 Location: Bangalore India
|
Posted: Tue Sep 06, 2005 12:40 pm Post subject: REPORT PROGRAM NEEDED |
|
|
Hai Kolusu,
Yes i am quite confident to code another program if specs are given & i would like to take it as a practise excercise. |
|
Back to top |
|
 |
|
|