MVS38J, Reporting, Sorting

Reporting in MVS38J

Overview

Report generation continues to be a major product of electronic data processing, whether a preliminary college class roster, class summary of average grades or a detail retail inventory report. Reports are physically printed and distributed to business owners or logically distributed via microfiche or report distribution systems for online viewing using 3270 terminals

Wow! This statement sounds so very retro – 1970’s 1980’s…

From yester-years (many of them!!!), as a computer science college student, I carried 80-column punch cards of my assigned programs and associated program listings as I attend various programming classes.

The college data center always had various administrative type reports printing in private printer rooms not to mention student program listings in the computer lab.

Of course, with today’s digital computing platforms and technology stacks, business applications render data (reports, pages) on personal devices using graphical user interfaces and use screen gestures (or mouse clicks) to drill-down or step-up the various levels of data detail.

Reports from a business application in the MVS38J era were printed on green-bar paper using COBOL or RPG, to name two programming languages. This post will illustrate the differences in lines of code and program language representation required to produce simple report with one control break using COBOL and RPG.

The source input field names will be kept the same across programs to maintain data flow transparency.

Reporting Task Problem Statement:
o Order data by itemno, plant
o Print report and column headings at start of page
o Print inventory detail line (plant, itemno, item, loc, qnty, price, extended cost)
o Accumulate total record count
o Accumulate items, qnty and extended cost at itemno level
o On change of itemno, print itemno and item on first line only
o On change of itemno, print summary line of plants listed, qnty, and extended cost and print subsequent line of asterisks
o At end of data, print final summary line including records read, total items listed, and total extended cost for plant

The Report

The following represents the inventory report to be generated by the sample reporting programs.

      Sample Inventory Report Layout                                                    
0        1         2         3         4         5         6         7         8
1...+....0....+....0....+....0....+....0....+....0....+....0....+....0....+....0
MM/DD/YY                 HARDWARE PLANT INVENTORY REPORT           PAGE   XX   ----- 1. Report Heading 
                                                                               ---\- 2. Report Column 
    Item    Item Description    Plant Location Quantity   Price  Extended      ---/      Heading 

                                  0 Plants-           0             $0.00*
***************************************************************************
    0001    BOLT #7               001     0010      100     .15     15.00
                                  002     0045      100     .15     15.00
                                  005     0057      100     .15     15.00
                                                                               ---\- 3. Control Break 
                                  3 Plants-         300            $45.00*     ---|      print lines
***************************************************************************    ---/       for ITEM
    0002    NUT  #7               001     0010       50     .15      7.50
                                  002     0027       47     .15      7.05

                                  2 Plants-          97            $14.55*
***************************************************************************
    0003    WASHER #7             001     0010      266     .15     39.90
                                  002     0046       46     .15      6.90

                                  2 Plants-         312            $46.80*
***************************************************************************
    0012    Woodscrew #4          001     0015      623     .09     56.07
                                  002     0020       55     .09      4.95
                                  003     0022      623     .09     56.07
                                  005     0050      731     .09     65.79

                                  4 Plants-       2,032           $182.88*
***************************************************************************
    0013    U-Bolt 2"             001     0025      122    1.25    152.50
                                  002     0003       98    1.25    122.50

                                  2 Plants-         220           $275.00*
***************************************************************************
    0016    Door stop brown       001     0050       22    2.45     53.90
                                  002     0057      177    2.45    433.65

                                  2 Plants-         199           $487.55*
***************************************************************************
    0023    Door stop black       001     0050       25    2.45     61.25
                                  002     0061      231    2.45    565.95
                                                                            
                                  2 Plants-         256           $627.20*   
***************************************************************************   
      17 Records            7 Items                Total         $1,678.98**   ----- 4. Final Total Line 











                               REPORT-PAGE-01                        ---\-- 5. Report Footer 
                               END OF REPORT                         ---/       Lines (COBOL ONLY) 

















The Data

The following sample inventory data will be used across reporting programs.

Col 01-03  03 bytes  PLANT
Col 08-11  04 bytes  ITEMNO  (control break)
Col 15-30  16 bytes  ITEM  
Col 31-34  04 bytes  LOC   
Col 39-42  04 bytes  QNTY   (numeric integer)  
Col 46-49  04 bytes  PRICE  (numeric, implied 2 decimals, 99V99)

HERC01.RPTS00.CNTL(INVTRY00)
0        1         2         3         4         5         6         7         8
1...+....0....+....0....+....0....+....0....+....0....+....0....+....0....+....0

001    0001   BOLT #7         0010    0100   0015
001    0002   NUT  #7         0010    0050   0015
001    0003   WASHER #7       0010    0266   0015
001    0012   Woodscrew #4    0015    0623   0009
001    0013   U-Bolt 2"       0025    0122   0125
001    0016   Door stop brown 0050    0022   0245
001    0023   Door stop black 0050    0025   0245
002    0001   BOLT #7         0045    0100   0015
002    0002   NUT  #7         0027    0047   0015
002    0003   WASHER #7       0046    0046   0015
002    0012   Woodscrew #4    0020    0055   0009
002    0013   U-Bolt 2"       0003    0098   0125
002    0016   Door stop brown 0057    0177   0245
002    0023   Door stop black 0061    0231   0245
003    0012   Woodscrew #4    0022    0623   0009
005    0001   BOLT #7         0057    0100   0015
005    0012   Woodscrew #4    0050    0731   0009

RPG Report

The MVS38J OS includes the RPG v1m10 language compiler. RPG is a fill-in-the-blank type language using predefined forms with a specific processing cycle using switches (indicators). In brief and interest of this post, that processing cycle includes input, calculate and output phases that are defined through various source statements to read a file and generate a specific report.

As computer science students, RPG coding forms accompanied our punched cards and program listings. That explains the brief cases used carry our supplies during our college days!

The program, CDPRPTR, is comprised of less than 65 source statements, excluding comments, satisfying the problem statement.

F (File Description Specifications) source statements define files
(2 statements).
I (Input Specifications) source statements define input record layout
(7 statements).
C (Calculation Specifications) source statements define calculations and accumulations
(7 statements).
O (Output Format Specifications) source statements define report print lines
(44 statements).

For more details using RPG on MVS38J and the various RPG coding forms, refer to C24-3337-3 IBM OS Report Program Generator Language Guide which can be searched for on the Internet.

HERC01.RPTS00.CNTL(RPTRPG)                                                    
0        1         2         3         4         5         6         7         8
1...+....0....+....0....+....0....+....0....+....0....+....0....+....0....+....0
//HERC01C  JOB (SYS),'RPG RPT',                  <-- Review and Modify 
//             CLASS=A,MSGCLASS=A,               <-- Review and Modify
//             MSGLEVEL=(1,1),NOTIFY=HERC01      <-- Review and Modify
//* -------------------------------------------------------*
//* *  Reporting sample using RPG:                         *
//* *    1) Sort INVENTORY DATA                            *
//* *    2) RPG Inventory Report                           *
//* -------------------------------------------------------*
//STEP010  EXEC PGM=SORT,PARM='MSG=AP'
//SORTLIB  DD DISP=SHR,DSN=SYS1.SORTLIB                      
//SORTWK01 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK02 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK03 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK04 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK05 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK06 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTIN   DD DSN=HERC01.RPTS00.CNTL(INVTRY00),DISP=SHR
//SYSPRINT DD SYSOUT=*                          
//SYSOUT   DD SYSOUT=*                          
//*SORTOUT  DD SYSOUT=*,DCB=(LRECL=80,BLKSIZE=3600,RECFM=FB)
//SORTOUT  DD DSN=&&INVDATA,DISP=(NEW,PASS),         
//            SPACE=(CYL,(1,1)),UNIT=SYSALLDA,
//            DCB=(LRECL=80,BLKSIZE=3600,RECFM=FB)
//SYSIN    DD *                                    
 SORT FIELDS=(08,04,A,01,03,A),FORMAT=CH             
 RECORD TYPE=F,LENGTH=(80)
/*
//*
//RPGCLG   EXEC RPGECLG,COND.LKED=(9,LT,RPG)
//RPG.SYSUT3 DD UNIT=SYSDA
//RPG.SYSUT2 DD UNIT=SYSDA
//RPG.SYSUT1 DD UNIT=SYSDA
//RPG.SYSGO DD  UNIT=SYSDA
//RPG.SYSIN DD  *
     H
     H******************************************************************
     H*                                                                *
     H* Program: CDPRPTR                                               *
     H*                                                                *
     H* Author : Larry Belmontes                                       *
     H*          https://www.shareabitofit.net/Reporting-in-MVS38J     *
     H*                                                                *
     H*                                                                *
     H* Purpose: This program reads inventory data and create an       *
     H*          inventory report using control breaks and report      *
     H*          page management.                                      *
     H*                                                                *
     H*  Disclaimer:                                                   *
     H*  ==============================================================*     
     H*                                                                *        
     H*     No guarantee; No warranty; Install / Use at your own risk. *
     H*                                                                *
     H*     This software is provided "AS IS" and without any expressed*
     H*  or implied warranties, including, without limitation, the     *
     H*  implied warranties of merchantability and fitness for a       *
     H*  particular purpose.                                           *
     H*                                                                *
     H*     The author requests keeping authors name intact in any     *
     H*  modified versions.                                            *
     H*                                                                *
     H*     In addition, the author requests submissions regarding any *
     H*  code modifications / enhancements and/or associated comments  *
     H*  for consideration into a subsequent release (giving credit    *
     H*  to contributor(s)) thus, improving overall functionality      *
     H*  benefiting the MVS 3.8J hobbyist public domain community.     *
     H*                                                                *        
     H*  ==============================================================*     
     H*                                                                *
     H*                                                                *
     H******************************************************************
     F* File Definitions                                               *
     F******************************************************************
     FINVFILE IP  F3600  80            DISK14       S 
     FPRNTFLE O   F 132 132     OF     PRINTER
     I******************************************************************
     I* Input file description                                         *
     I******************************************************************
     IINVFILE AA  01       
     I                                       01  03 PLANT
     I                                       08  11 ITEMNOL1
     I                                       15  30 ITEM  
     I                                       31  34 LOC   
     I                                       39  420QNTY  
     I                                       46  492UPRICE
     C******************************************************************
     C* Computations for every record read                             *
     C* Some fields zeroed in OUTPUT section (e.g. IQNTY)              *
     C******************************************************************
     C   01      RCOUNT    ADD  1         RCOUNT  30
     C   01      ICOUNT    ADD  1         ICOUNT  30
     C   01      QNTY      MULT UPRICE    EXTD    72 
     C   01      IQNTY     ADD  QNTY      IQNTY   70
     C   01      IEXTD     ADD  EXTD      IEXTD   92
     C   01      TEXTD     ADD  EXTD      TEXTD   92
     C   01 L1   TCOUNT    ADD  1         TCOUNT  30
     O******************************************************************
     O* Report Heading (First time (1P) & page overflow (OF)           *
     O******************************************************************
     OPRNTFLE H  201   1P
     O       OR        OF
     O*                        UDATE      8 '0 /  /  '    
     O                         UMONTH     2               
     O                                    3 '/'           
     O                         UDAY       5               
     O                                    6 '/'           
     O                         UYEAR      8               
     O                                   39 'HARDWARE PLANT'
     O                                   56 'INVENTORY REPORT'
     O                                   71 'PAGE'
     O                         PAGE  Z   76 
     O******************************************************************
     O* Report Column Headings (First time (1P) & page overflow (OF)   *
     O******************************************************************
     O        H  1     1P
     O       OR        OF
     O                                   08 'Item'
     O                                   28 'Item Description'
     O                                   37 'Plant'
     O                                   46 'Location'
     O                                   55 'Quantity'
     O                                   63 'Price'
     O                                   73 'Extended'
     O******************************************************************
     O* Print detail line for every record read.  ITEMNO and ITEM      *
     O* are print first time only for item group.                      *
     O******************************************************************
     O        D  1     01
     O                 L1      ITEMNO    08
     O                 L1      ITEM      28
     O                         PLANT     37
     O                         LOC       46           
     O                         QNTY      55 '   0'    
     O                         UPRICE    63 ' 0.  '
     O                         EXTD      73 '   ,  0.  '
     O******************************************************************
     O* On LEVEL 1 (L1) break, print ITEM totals for all plants        *
     O******************************************************************
     O        T 11     L1   
     O                         ICOUNTZB  35
     O                                   43 'Plants-'
     O                         IQNTY  B  55 ' ,   ,  0' 
     O                         IEXTD  B  73 '   ,   , $0.  '
     O                                   74 '*'
     O        T  1     L1   
     O                                   15 '***************'
     O                                   30 '***************'
     O                                   45 '***************'
     O                                   60 '***************'
     O                                   75 '***************'
     O******************************************************************
     O* On LAST RECORD (LR), print grand totals                        *
     O******************************************************************
     O        T  1     LR   
     O                         RCOUNTZ   08
     O                                   16 'Records'
     O                         TCOUNTZ   29
     O                                   35 'Items'   
     O                                   56 'Total'   
     O                         TEXTD     73 '   ,   , $0.  '
     O                                   75 '**'
/*
//GO.SYSUDUMP DD SYSOUT=A
//GO.INVFILE  DD DSN=&&INVDATA,DISP=(OLD,DELETE)          
//GO.PRNTFLE  DD SYSOUT=A
//

COBOL Report Writer

The MVS38J OS COBOL compiler includes a report writer feature making report generation easier than using native COBOL programming, but more involved than RPG specification statements.

The program, CDPRPTC, defines the Inventory Report using the REPORT SECTION that includes an RD (Report Definition) definition followed by each reporting print line type with keywords for print line and column positioning, field grouping and summary.

CDPRPTC is comprised of less than 300 COBOL statements (with comments) which includes 30 Data Division statements and 21 Procedure Division statements. Approximately, 85 source statements declare report writer definitions. As a reminder, a COBOL source statement can span across lines!

For more details using COBOL and Report Writer feature on MVS38J, refer to GC28-6399-2 IBM OS Full American National Standard COBOL Compiler and Library Programmer’s Guide which can be searched for on the Internet.

HERC01.RPTS00.CNTL(RPTRPG)                                                    
0        1         2         3         4         5         6         7         8
1...+....0....+....0....+....0....+....0....+....0....+....0....+....0....+....0
//HERC01C  JOB (SYS),'COB RPT',                  <-- Review and Modify 
//             CLASS=A,MSGCLASS=A,               <-- Review and Modify
//             MSGLEVEL=(1,1),NOTIFY=HERC01      <-- Review and Modify
//* -------------------------------------------------------*
//* *  Reporting sample using COBOL Report Writer          *
//* *    1) Sort INVENTORY DATA                            *
//* *    2) COB Inventory Report                           *
//* -------------------------------------------------------*
//STEP010  EXEC PGM=SORT,PARM='MSG=AP'
//SORTLIB  DD DISP=SHR,DSN=SYS1.SORTLIB                      
//SORTWK01 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK02 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK03 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK04 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK05 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK06 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTIN   DD DSN=HERC01.RPTS00.CNTL(INVTRY00),DISP=SHR
//SYSPRINT DD SYSOUT=*                          
//SYSOUT   DD SYSOUT=*                          
//*SORTOUT  DD SYSOUT=*,DCB=(LRECL=80,BLKSIZE=3600,RECFM=FB)
//SORTOUT  DD DSN=&&INVDATA,DISP=(NEW,PASS),         
//            SPACE=(CYL,(1,1)),UNIT=SYSALLDA,
//            DCB=(LRECL=80,BLKSIZE=3600,RECFM=FB)
//SYSIN    DD *                                    
 SORT FIELDS=(08,04,A,01,03,A),FORMAT=CH             
 RECORD TYPE=F,LENGTH=(80)
/*
//*
//STEP01  EXEC COBUCLG,CPARM1='LIST,LOAD,NODECK,PMAP,DMAP'
//COB.SYSLIB   DD DSN=HERC01.TEST.CNTL,DISP=SHR
//COB.SYSPUNCH DD DUMMY
//COB.SYSIN DD *
       IDENTIFICATION DIVISION.
       PROGRAM-ID.             CDPRPTCR.
       AUTHOR.                 Larry Belmontes.
       REMARKS. 
                               This program reads inventory data
                               and creates an inventory report
                               using control breaks and report page
                               management via Report Writer.            
       
           https://www.shareabitofit.net/Reporting-in-MVS38J         */
                                                                     */
                                                                     */
           Disclaimer:                                               */
           -----------                                               */
           No guarantee; No warranty; Install / Use at your own risk.*/
                                                                     */
           This software is provided “AS IS” and without any         */
           expressed or implied warranties, including, without       */
           limitation, the implied warranties of merchantability     */
           and fitness for a particular purpose.                     */
                                                                     */
           The author requests keeping authors name intact in any    */
           modified versions.                                        */
                                                                     */
           In addition, the author requests submissions regarding    */
           any code modifications / enhancements and/or associated   */
           comments for consideration into a subsequent release      */
           (giving credit to contributor(s)) thus, improving overall */
           functionality benefiting the MVS 3.8J hobbyist public     */
           domain community.                                         */
       EJECT
       ENVIRONMENT DIVISION.

       CONFIGURATION SECTION.
       SOURCE-COMPUTER.        IBM-4341.
       OBJECT-COMPUTER.        IBM-4341.

       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
      *                                                                         
           SELECT INFILE      ASSIGN TO UT-2314-S-CARDIN.                       
           SELECT REPORT-FILE ASSIGN TO UR-1403-S-PRTOUT.                      
      *                                                                         
       EJECT
       DATA DIVISION.

       FILE SECTION.
       FD  INFILE                                                               
           RECORDING MODE IS F                                                  
           RECORD CONTAINS 080 CHARACTERS                                       
           BLOCK  CONTAINS 000 CHARACTERS                                       
           LABEL RECORDS ARE STANDARD                                           
           DATA RECORD IS INPUT-RECORD.                                         
       01  INPUT-RECORD.                                                        
           05  PLANT               PIC X(03).                                   
           05  FILLER              PIC X(04).                                   
           05  ITEMNO              PIC X(04).                                   
           05  FILLER              PIC X(03).                                   
           05  ITEM                PIC X(16).                                   
           05  LOC                 PIC X(04).                                   
           05  FILLER              PIC X(04).                                   
           05  QNTY                PIC 9(04).                                   
           05  FILLER              PIC X(03).                                   
           05  UPRICE              PIC 9(02)V9(02).                             
           05  FILLER              PIC X(31).                                   
            
       FD  REPORT-FILE                                                          
           RECORDING MODE IS F                                                  
           RECORD CONTAINS 133 CHARACTERS                                       
           LABEL RECORDS ARE OMITTED                                            
           REPORT IS INVENTORY-REPORT.                                          
                                                                                

       WORKING-STORAGE SECTION.


       01  WS-DATA-FIELDS.
      *    Inventory File EOF switch                       *
           05  INVFILE-EOF-SW      PIC X(01)    VALUE 'N'.
               88  INVFILE-EOF                  VALUE 'Y'.
      *    Item Number HOLD area                           *
           05  ITEMNO-HOLD     PIC X(04)        VALUE SPACES.       
      *    Extended cost                                   *
           05  EXTD            PIC S9(05)V9(02) COMP-3  VALUE 0.
      *    Record count                                    *
           05  RCOUNT          PIC S9(03)       COMP-3  VALUE 0.
      *    Plant item count for item control break         *
           05  ICOUNT          PIC S9(03)       COMP-3  VALUE 0.
      *    Total item count for final control break        *
           05  TCOUNT          PIC S9(03)       COMP-3  VALUE 0.
       EJECT
       REPORT SECTION.
       RD  INVENTORY-REPORT
           CONTROLS ARE FINAL, ITEM
           PAGE 59 LINES
           HEADING 1
           FIRST DETAIL 4
           LAST  DETAIL 48
           FOOTING 52.
            
      ******************************************************
      * Report Heading                                     *
      ******************************************************
       01  REPORT-HEAD         
           TYPE REPORT HEADING.
           05  LINE 01  COLUMN 01   PIC X(08)   
               SOURCE CURRENT-DATE.                         
           05  LINE 01  COLUMN 26   PIC X(31)
               VALUE 'HARDWARE PLANT INVENTORY REPORT'.
           05  LINE 01  COLUMN 68   PIC X(04)
               VALUE 'PAGE'.
           05  LINE 01  COLUMN 75   PIC Z9
               SOURCE PAGE-COUNTER.
                
      ******************************************************
      * Page Heading                                       *
      ******************************************************
       01  PAGE-HEAD                                  
           TYPE PAGE HEADING  LINE 3.
           05  LINE 3  COLUMN 5     PIC X(35)
               VALUE 'Item    Item Description    Plant L'.
           05          COLUMN 40    PIC X(34)
               VALUE 'ocation Quantity   Price  Extended'.
                
      ******************************************************
      * Detail line                                        *
      ******************************************************
       01  DETAIL-LINE
           TYPE DETAIL LINE PLUS 1.
           05          COLUMN 5  GROUP INDICATE  PIC X(04)
               SOURCE ITEMNO.
           05          COLUMN 13 GROUP INDICATE  PIC X(16)
               SOURCE ITEM.
           05          COLUMN 35                 PIC X(03)
               SOURCE PLANT.
           05          COLUMN 43                 PIC X(04)
               SOURCE LOC.           
           05          COLUMN 52                 PIC ZZZ9  
               SOURCE QNTY.           
           05          COLUMN 59                 PIC ZZ.99
               SOURCE UPRICE.
           05          COLUMN 64                 PIC ZZZ,ZZ9.99
               SOURCE EXTD.  
                
       EJECT    
      ******************************************************
      * Item control break                                 *
      ******************************************************
       01  ITEM-GROUP
           TYPE CONTROL FOOTING ITEM LINE PLUS 2.
           05          COLUMN 33                 PIC ZZ9 
               SOURCE ICOUNT.       
           05          COLUMN 37                 PIC X(07)
               VALUE 'Plants-'.
           05          COLUMN 47                 PIC Z,ZZZ,ZZ9
               SUM QNTY.
           05          COLUMN 60                 PIC $$$,$$$,$$9.99  
               SUM EXTD.            
           05          COLUMN 74                 PIC X(01) 
               VALUE ALL '*'.      
           05  LINE PLUS 1                                   
                       COLUMN  1                 PIC X(75)    
               VALUE ALL '*'.                  
                
      ******************************************************
      * Final Footer                                       *
      ******************************************************
       01  FINAL-FOOTING                                   
           TYPE CONTROL FOOTING FINAL LINE PLUS 1.
           05          COLUMN 06                 PIC ZZ9
               SOURCE RCOUNT.     
           05          COLUMN 10                 PIC X(07) 
               VALUE 'Records'.                   
           05          COLUMN 27                 PIC ZZ9
               SOURCE TCOUNT.     
           05          COLUMN 31                  PIC X(05) 
               VALUE 'Items'.                   
           05          COLUMN 52                 PIC X(05) 
               VALUE 'Total'.                   
           05          COLUMN 60                 PIC $$$,$$$,$$9.99  
               SUM EXTD.           
           05          COLUMN 74                 PIC X(02) 
               VALUE ALL '*'.      
                
       EJECT    
      ******************************************************
      * Page Footer                                        *
      ******************************************************
       01  PAGE-FOOTING                                   
           TYPE PAGE FOOTING LINE 55.                  
           05  LINE 57 COLUMN 32                 PIC X(12) 
               VALUE 'REPORT-PAGE-'.
           05          COLUMN 44                 PIC 99
               SOURCE PAGE-COUNTER.
                
      ******************************************************
      * Report Footer                                      *
      ******************************************************
       01  REPORT-FOOTING                                   
           TYPE REPORT FOOTING.                        
           05  LINE PLUS 1                                 
                       COLUMN 32                 PIC X(13) 
               VALUE 'END OF REPORT'.
       EJECT
       PROCEDURE DIVISION.
       
       0000-MAINLINE SECTION.

      ******************************************************
      * Open Files                                         *
      ******************************************************
           OPEN INPUT  INFILE,  
                OUTPUT REPORT-FILE.

      ******************************************************
      * Prime Input File                                   *
      ******************************************************
           PERFORM 9100-READ-INVFILE THRU
                   9100-READ-INVFILE-EXIT.
                       
      ******************************************************
      * Start Report Writer                                *
      ******************************************************
           INITIATE INVENTORY-REPORT.

      ******************************************************
      * Process inventory report w report writer           *
      ******************************************************
           PERFORM 9200-DO-RPT-WRITER THRU
                   9200-DO-RPT-WRITER-EXIT
                   UNTIL INVFILE-EOF.

      ******************************************************
      * Terminate Report Writer                            *
      ******************************************************
           TERMINATE INVENTORY-REPORT.

      ******************************************************
      * Close files                                        *
      ******************************************************
           CLOSE INFILE, REPORT-FILE.

      ******************************************************
      * Return to OS                                       *
      ******************************************************
           GOBACK.   

       EJECT
      ******************************************************
      * SUBROUTINES Section                                *
      ******************************************************
       Z9000-SUBROUTINES SECTION.


      ******************************************************
      * Read Inventory File                                *
      ******************************************************
       9100-READ-INVFILE.              

           READ INFILE,   
                AT END
                   MOVE 'Y' TO INVFILE-EOF-SW.
                    
       9100-READ-INVFILE-EXIT.         
           EXIT.

       EJECT
      ******************************************************
      * Do Report Writing                                  *
      ******************************************************
       9200-DO-RPT-WRITER.             
        
      *    *************************************************
      *    * Accumulate record count                       *
      *    *************************************************
           ADD +1   TO RCOUNT.
        
      *    *************************************************
      *    * Calculate extended item price                 *
      *    *************************************************
           COMPUTE EXTD = QNTY * UPRICE.
        
      *    *************************************************
      *    * Generate inventory report                     *
      *    *************************************************
           GENERATE DETAIL-LINE.
        
      *    *************************************************
      *    * Item control break accumulations              *
      *    *************************************************
           IF ITEMNO = ITEMNO-HOLD
               ADD +1 TO ICOUNT
           ELSE
               ADD +1      TO TCOUNT
               MOVE ITEMNO TO ITEMNO-HOLD
               MOVE +1     TO ICOUNT.
              
      *    **************************************************
      *    * Read another inventory record                  *
      *    **************************************************
           PERFORM 9100-READ-INVFILE THRU
                   9100-READ-INVFILE-EXIT.
            
       9200-DO-RPT-WRITER-EXIT.        
           EXIT.
/*    
//GO.CARDIN   DD DSN=&&INVDATA,DISP=(OLD,DELETE)                 
//GO.SYSPRINT DD SYSOUT=*      
//GO.SYSOUT   DD SYSOUT=*      
//GO.PRTOUT   DD SYSOUT=*      
//

COBOL Reporting

Program, CDPRPTCN, uses native COBOL putting the programmer in full control of all reporting logic including report pagination and control break processing.

CDPRPTCN is comprised of approximately 450 source statements (with comments) which includes 100 Data Division statements and 77 Procedure Division statements.

For more details using COBOL on MVS38J, refer to GC28-6399-2 IBM OS Full American National Standard COBOL Compiler and Library Programmer’s Guide which can be searched for on the Internet.

HERC01.RPTS00.CNTL(COBCOB)                                                    
0        1         2         3         4         5         6         7         8
1...+....0....+....0....+....0....+....0....+....0....+....0....+....0....+....0
//HERC01C  JOB (SYS),'COB COB',                  <-- Review and Modify 
//             CLASS=A,MSGCLASS=A,               <-- Review and Modify
//             MSGLEVEL=(1,1),NOTIFY=HERC01      <-- Review and Modify
//* -------------------------------------------------------*
//* *  Reporting sample using COBOL Natively               *
//* *    1) Sort INVENTORY DATA                            *
//* *    2) COB Inventory Report                           *
//* -------------------------------------------------------*
//STEP010  EXEC PGM=SORT,PARM='MSG=AP'
//SORTLIB  DD DISP=SHR,DSN=SYS1.SORTLIB                      
//SORTWK01 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK02 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK03 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK04 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK05 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTWK06 DD UNIT=2314,SPACE=(CYL,(5,5))
//SORTIN   DD DSN=HERC01.RPTS000.CNTL(INVTRY00),DISP=SHR 
//SYSPRINT DD SYSOUT=*                          
//SYSOUT   DD SYSOUT=*                          
//*SORTOUT  DD SYSOUT=*,DCB=(LRECL=80,BLKSIZE=3600,RECFM=FB)
//SORTOUT  DD DSN=&&INVDATA,DISP=(NEW,PASS),         
//            SPACE=(CYL,(1,1)),UNIT=SYSALLDA,
//            DCB=(LRECL=80,BLKSIZE=3600,RECFM=FB)
//SYSIN    DD *                                    
 SORT FIELDS=(08,04,A,01,03,A),FORMAT=CH             
 RECORD TYPE=F,LENGTH=(80)
/*
//*
//STEP01  EXEC COBUCLG,CPARM1='LIST,LOAD,NODECK,PMAP,DMAP'
//COB.SYSLIB   DD DSN=HERC01.TEST.CNTL,DISP=SHR
//COB.SYSPUNCH DD DUMMY
//COB.SYSIN DD *
       IDENTIFICATION DIVISION.
       PROGRAM-ID.             CDPRPTCN.
       AUTHOR.                 Larry Belmontes.
       REMARKS. 
                               This program reads inventory data
                               and creates an inventory report
                               using control breaks and report page
                               management using native COBOL.           
       
           https://www.shareabitofit.net/Reporting-in-MVS38J         */
                                                                     */
                                                                     */
           Disclaimer:                                               */
           -----------                                               */
           No guarantee; No warranty; Install / Use at your own risk.*/
                                                                     */
           This software is provided “AS IS” and without any         */
           expressed or implied warranties, including, without       */
           limitation, the implied warranties of merchantability     */
           and fitness for a particular purpose.                     */
                                                                     */
           The author requests keeping authors name intact in any    */
           modified versions.                                        */
                                                                     */
           In addition, the author requests submissions regarding    */
           any code modifications / enhancements and/or associated   */
           comments for consideration into a subsequent release      */
           (giving credit to contributor(s)) thus, improving overall */
           functionality benefiting the MVS 3.8J hobbyist public     */
           domain community.                                         */
       EJECT
       ENVIRONMENT DIVISION.

       CONFIGURATION SECTION.
       SOURCE-COMPUTER.        IBM-4341.
       OBJECT-COMPUTER.        IBM-4341.
       SPECIAL-NAMES.          C01 IS TO-TOP-OF-PAGE.

       INPUT-OUTPUT SECTION.
       FILE-CONTROL.
      *                                                                         
           SELECT INFILE      ASSIGN TO UT-2314-S-CARDIN.                       
           SELECT REPORT-FILE ASSIGN TO UR-1403-S-PRTOUT.                      
      *                                                                         
       EJECT
       DATA DIVISION.

       FILE SECTION.
       FD  INFILE                                                               
           RECORDING MODE IS F                                                  
           RECORD CONTAINS 080 CHARACTERS                                       
           BLOCK  CONTAINS 000 CHARACTERS                                       
           LABEL RECORDS ARE STANDARD                                           
           DATA RECORD IS INPUT-RECORD.                                         
       01  INPUT-RECORD.                                                        
           05  PLANT               PIC X(03).                                   
           05  FILLER              PIC X(04).                                   
           05  ITEMNO              PIC X(04).                                   
           05  FILLER              PIC X(03).                                   
           05  ITEM                PIC X(16).                                   
           05  LOC                 PIC X(04).                                   
           05  FILLER              PIC X(04).                                   
           05  QNTY                PIC 9(04).                                   
           05  FILLER              PIC X(03).                                   
           05  UPRICE              PIC 9(02)V9(02).                             
           05  FILLER              PIC X(31).                                   
            
       FD  REPORT-FILE                                                          
           RECORDING MODE IS F                                                  
           RECORD CONTAINS 133 CHARACTERS                                       
           LABEL RECORDS ARE OMITTED                                            
           DATA RECORD IS REPORT-LINE.                                          
       01  REPORT-LINE                         
           05  CC                  PIC X(01).
           05  FILLER              PIC X(132). 

       EJECT
       WORKING-STORAGE SECTION.

       01  WS-DATA-FIELDS.
      *    Page and Line counters                          *
           05  WS-LINES            PIC S9(03) VALUE +99.          
           05  WS-LINES-MAX        PIC S9(03) VALUE +60.          
           05  WS-PAGE             PIC S9(03) VALUE +0.           
      *    Report Footer Lines to advance, calculated      *
           05  WS-FOOTER           PIC S9(03) VALUE +0.
      *    Inventory File EOF Flag                         *
           05  INVFILE-EOF-FLAG    PIC X(01) VALUE 'N'.
               88  INVFILE-EOF               VALUE 'Y'.
      *    Item Number Break Flag                          *
           05  IG-BREAK-FLAG       PIC X(01).
               88  IG-BREAK        VALUE 'Y'. 
      *    Item Number HOLD area                           *
           05  ITEMNO-HOLD         PIC X(04) VALUE SPACES.       
      *    Extended cost                                   *
           05  EXTD                PIC S9(05)V9(02) COMP-3  VALUE 0.
      *    Record count                                    *
           05  RCOUNT              PIC S9(03)       COMP-3  VALUE 0.
      *    Plant item count for item control break         *
           05  ICOUNT              PIC S9(03)       COMP-3  VALUE 0.
      *    Total item count for final control break        *
           05  TCOUNT              PIC S9(03)       COMP-3  VALUE 0.
      *    Extended cost Item total                        *
           05  IEXTD               PIC S9(09)V9(02) COMP-3  VALUE 0.
      *    Extended cost Item final total                  *
           05  TEXTD               PIC S9(09)V9(02) COMP-3  VALUE 0.
      *    Quantity Item total                             *
           05  IQNTY               PIC S9(09)       COMP-3  VALUE 0.
            
       EJECT
      ******************************************************
      * Report Heading                                     *
      ******************************************************
       01  REPORT-HEAD.        
           05  CC                  PIC X(01)  VALUE SPACES.
           05  RH-DATE             PIC X(08).  
           05  FILLER              PIC X(17)  VALUE SPACES.
           05  FILLER              PIC X(42)  VALUE
               'HARDWARE PLANT INVENTORY REPORT'.
           05  FILLER              PIC X(04)  VALUE
               'PAGE'.
           05  FILLER              PIC X(03)  VALUE SPACES.
           05  RH-PAGE             PIC Z9.
                
      ******************************************************
      * Page Heading                                       *
      ******************************************************
       01  PAGE-HEAD.                                 
           05  CC                  PIC X(01)  VALUE SPACES.
           05  FILLER              PIC X(04)  VALUE SPACES.
           05  FILLER              PIC X(35)  VALUE
               'Item    Item Description    Plant L'.
           05  FILLER              PIC X(34)  VALUE
               'ocation Quantity   Price  Extended'.
                
       EJECT    
      ******************************************************
      * Detail line                                        *
      ******************************************************
       01  DETAIL-LINE.
           05  CC                  PIC X(01)  VALUE SPACES.
           05  FILLER              PIC X(04)  VALUE SPACES.
           05  DL-ITEMNO           PIC X(04).
           05  FILLER              PIC X(04)  VALUE SPACES.
           05  DL-ITEM             PIC X(16).
           05  FILLER              PIC X(06)  VALUE SPACES.
           05  DL-PLANT            PIC X(03).
           05  FILLER              PIC X(05)  VALUE SPACES.
           05  DL-LOC              PIC X(04).
           05  FILLER              PIC X(05)  VALUE SPACES.
           05  DL-QNTY             PIC ZZZ9. 
           05  FILLER              PIC X(03)  VALUE SPACES.
           05  DL-UPRICE           PIC ZZ.99. 
           05  DL-EXTD             PIC ZZZ,ZZ9.99.
       
                
       EJECT    
      ******************************************************
      * Item control break                                 *
      ******************************************************
       01  ITEM-GROUP.
           05  CC                  PIC X(01)  VALUE SPACES.
           05  FILLER              PIC X(32)  VALUE SPACES.
           05  IG-ICOUNT           PIC ZZ9.                 
           05  FILLER              PIC X(01)  VALUE SPACES.
           05  FILLER              PIC X(07)  VALUE
               'Plants-'.
           05  FILLER              PIC X(03)  VALUE SPACES.
           05  IG-IQNTY            PIC Z,ZZZ,ZZ9.       
           05  FILLER              PIC X(04)  VALUE SPACES.
           05  IG-IEXTD            PIC $$$,$$$,$$9.99.  
           05  FILLER              PIC X(01)  VALUE '*'.    
            
       01  ITEM-GROUP-2.
           05  CC                  PIC X(01)  VALUE SPACES.
           05  FILLER              PIC X(75)  VALUE ALL '*'.
            
       EJECT    
      ******************************************************
      * Final Footer                                       *
      ******************************************************
       01  FINAL-FOOTING.                                  
           05  CC                  PIC X(01)  VALUE SPACES.
           05  FILLER              PIC X(05)  VALUE SPACES.
           05  FF-RCOUNT           PIC ZZ9.                 
           05  FILLER              PIC X(01)  VALUE SPACES.
           05  FILLER              PIC X(07)  VALUE
               'Records'.
           05  FILLER              PIC X(10)  VALUE SPACES.
           05  FF-TCOUNT           PIC ZZ9.                 
           05  FILLER              PIC X(01)  VALUE SPACES.
           05  FILLER              PIC X(05)  VALUE
               'Items'.
           05  FILLER              PIC X(16)  VALUE SPACES.
           05  FILLER              PIC X(05)  VALUE
               'Total'.
           05  FILLER              PIC X(03)  VALUE SPACES.
           05  FF-TEXTD            PIC $$$,$$$,$$9.99.  
           05  FILLER              PIC X(02)  VALUE '**'.    
                
      ******************************************************
      * Page Footer  @ Line 57                             *
      ******************************************************
       01  PAGE-FOOTING.                                  
           05  CC                  PIC X(01)  VALUE SPACES.
           05  FILLER              PIC X(31)  VALUE SPACES.
           05  FILLER              PIC X(12)  VALUE
               'REPORT-PAGE-'.
           05  PF-PAGE             PIC 99.                 
                
      ******************************************************
      * Report Footer                                      *
      ******************************************************
       01  REPORT-FOOTING.                                
           05  CC                  PIC X(01)  VALUE SPACES.
           05  FILLER              PIC X(31)  VALUE SPACES.
           05  FILLER              PIC X(13)  VALUE
               'END OF REPORT'.
       EJECT
       PROCEDURE DIVISION.
       
       0000-MAINLINE SECTION.

      ******************************************************
      * Open Files                                         *
      ******************************************************
           OPEN INPUT  INFILE,  
                OUTPUT REPORT-FILE.

      ******************************************************
      * Prime Input File                                   *
      ******************************************************
           PERFORM 9100-READ-INVFILE THRU
                   9100-READ-INVFILE-EXIT.
                       
      ******************************************************
      * Start Report - Print Headings                      *
      ******************************************************
           PERFORM 9300-RPT-HEADINGS THRU
                   9300-RPT-HEADINGS-EXIT.

      ******************************************************
      * Process inventory report                           *
      ******************************************************
           PERFORM 9200-DO-RPT-WRITER THRU
                   9200-DO-RPT-WRITER-EXIT
                   UNTIL INVFILE-EOF.

      ******************************************************
      * Terminate Report - Print breaks and footers        *
      ******************************************************
           PERFORM 9600-RPT-FINAL THRU
                   9600-RPT-FINAL-EXIT.

      ******************************************************
      * Close files                                        *
      ******************************************************
           CLOSE INFILE, REPORT-FILE.

      ******************************************************
      * Return to OS                                       *
      ******************************************************
           GOBACK.   

       EJECT
      ******************************************************
      * SUBROUTINES Section                                *
      ******************************************************
       Z9000-SUBROUTINES SECTION.


      ******************************************************
      * Read Inventory File                                *
      ******************************************************
       9100-READ-INVFILE.              

           READ INFILE,   
                AT END
                   MOVE 'Y' TO INVFILE-EOF-FLAG.
                    
       9100-READ-INVFILE-EXIT.         
           EXIT.

       EJECT
      ******************************************************
      * Do Report Writing                                  *
      ******************************************************
       9200-DO-RPT-WRITER.             
        
      *    *************************************************
      *    * Accumulate record count                       *
      *    *************************************************
           ADD +1   TO RCOUNT.
        
      *    *************************************************
      *    * Print report headings                         *
      *    *************************************************
           PERFORM 9300-RPT-HEADINGS THRU
                   9300-RPT-HEADINGS-EXIT.
                
      *    *************************************************
      *    * Print control break - ITEMNO                  *
      *    *************************************************
           PERFORM 9400-RPT-ITEM-BREAK THRU
                   9400-RPT-ITEM-BREAK-EXIT.
            
      *    *************************************************
      *    * Print detail line                             *
      *    *************************************************
           PERFORM 9500-RPT-DETAIL THRU
                   9500-RPT-DETAIL-EXIT.
       
      *    *************************************************
      *    * Item count                                    *
      *    *************************************************
           ADD +1 TO ICOUNT.
              
      *    *************************************************
      *    * Read another inventory record                 *
      *    *************************************************
           PERFORM 9100-READ-INVFILE THRU
                   9100-READ-INVFILE-EXIT.
            
       9200-DO-RPT-WRITER-EXIT.        
           EXIT.
            
       EJECT
      ******************************************************
      * Report Headings                                    *
      ******************************************************
       9300-RPT-HEADINGS.        
            
           IF WS-LINES > WS-LINES-MAX
               MOVE CURRENT-DATE TO RH-DATE 
               ADD +1            TO WS-PAGE 
               MOVE WS-PAGE      TO RH-PAGE 
               WRITE REPORT-LINE FROM REPORT-HEAD 
                     AFTER ADVANCING TO-TOP-OF-PAGE  
               MOVE +1           TO WS-LINES
               WRITE REPORT-LINE FROM PAGE-HEAD 
                     AFTER ADVANCING 2                  
               ADD +2           TO WS-LINES.
            
       9300-RPT-HEADINGS-EXIT.        
           EXIT.
            
       EJECT
      ******************************************************
      * Report ITEM Level Break                            *
      ******************************************************
       9400-RPT-ITEM-BREAK.      
            
           MOVE 'N'          TO IG-BREAK-FLAG.
           IF ITEMNO = ITEMNO-HOLD
               NEXT SENTENCE
           ELSE
               MOVE 'Y'          TO IG-BREAK-FLAG
               MOVE ITEMNO       TO ITEMNO-HOLD
               IF ITEMNO-HOLD = SPACES
                   NEXT SENTENCE                   
               ELSE
                   MOVE ICOUNT   TO IG-ICOUNT
                   MOVE IQNTY    TO IG-IQNTY 
                   MOVE IEXTD    TO IG-IEXTD 
                   WRITE REPORT-LINE FROM ITEM-GROUP 
                         AFTER ADVANCING 2                  
                   ADD +2        TO WS-LINES 
                   WRITE REPORT-LINE FROM ITEM-GROUP-2
                         AFTER ADVANCING 1                  
                   ADD +1        TO WS-LINES 
                      
                   MOVE ZEROS    TO ICOUNT
                   MOVE ZEROS    TO IQNTY
                   MOVE ZEROS    TO IEXTD.
                                                                              
       9400-RPT-ITEM-BREAK-EXIT.      
           EXIT.
            
       EJECT                                                     
      ******************************************************
      * Report detail line                                 *
      ******************************************************
       9500-RPT-DETAIL.
            
      *    *************************************************
      *    * Only first item in group displays in detail   *
      *    *************************************************
           IF IG-BREAK                
               MOVE ITEMNO   TO DL-ITEMNO
               MOVE ITEM     TO DL-ITEM 
               ADD +1        TO TCOUNT
           ELSE
               MOVE SPACES   TO DL-ITEMNO 
               MOVE SPACES   TO DL-ITEM.  
                
           MOVE PLANT        TO DL-PLANT.
           MOVE LOC          TO DL-LOC. 
           MOVE QNTY         TO DL-QNTY.
           MOVE UPRICE       TO DL-UPRICE.
           COMPUTE EXTD = QNTY * UPRICE.
           MOVE EXTD         TO DL-EXTD.  
           ADD QNTY TO IQNTY.
           ADD EXTD TO IEXTD.
           ADD EXTD TO TEXTD.
            
           WRITE REPORT-LINE FROM DETAIL-LINE
                 AFTER ADVANCING 1.                 
           ADD +1           TO WS-LINES.
            
       9500-RPT-DETAIL-EXIT.
           EXIT.
            
       EJECT
      ******************************************************
      * Report final breaks and footers                    *
      ******************************************************
       9600-RPT-FINAL.           
            
      *    *************************************************
      *    * Force Item Break Print                        *
      *    *************************************************
           MOVE HIGH-VALUES TO ITEMNO.
            
           PERFORM 9400-RPT-ITEM-BREAK THRU
                   9400-RPT-ITEM-BREAK-EXIT.
                                                                              
      *    *************************************************
      *    * Print Final footer                            *
      *    *************************************************
           MOVE RCOUNT TO FF-RCOUNT.
           MOVE TCOUNT TO FF-TCOUNT.
           MOVE TEXTD  TO FF-TEXTD.
           WRITE REPORT-LINE FROM FINAL-FOOTING
                 AFTER ADVANCING 1.
           ADD +1      TO WS-LINES.
            
      *    *************************************************
      *    * Print Page and Report footers                 *
      *    *************************************************
           MOVE WS-PAGE TO PF-PAGE.
           COMPUTE WS-FOOTER = 57 - WS-LINES.
            
           WRITE REPORT-LINE FROM PAGE-FOOTING
                 AFTER ADVANCING WS-FOOTER LINES.
           ADD WS-FOOTER TO WS-LINES.
            
           WRITE REPORT-LINE FROM REPORT-FOOTING
                 AFTER ADVANCING 1 LINES.
           ADD +1      TO WS-LINES.
                                                                              
       9600-RPT-FINAL-EXIT.      
           EXIT.
            
            
/*    
//GO.CARDIN   DD DSN=&&INVDATA,DISP=(OLD,DELETE)                 
//GO.SYSPRINT DD SYSOUT=*      
//GO.SYSOUT   DD SYSOUT=*      
//GO.PRTOUT   DD SYSOUT=*      
//


Software Disclosure

No guarantee; No warranty; Install / Use at your own risk.

This software is provided “AS IS” and without any expressed or implied warranties, including, without limitation, the implied warranties of merchantability and fitness for a particular purpose.

The author requests keeping authors name intact to any modified versions.

In addition, the author requests readers to submit any code modifications / enhancements and associated comments for consideration into a subsequent release (giving credit to contributors) thus, improving overall functionality benefiting the MVS 3.8J hobbyist public domain community.

Download

Click here to download a ZIP file containing installation JCL, text (.TXT) files and HET (Hercules Emulated Tape) file which includes sort data and programs with compile-link-go JCL .

Once the ZIP file is downloaded and extracted, use the following JCL to load the HET tape to your MVS38J system.

//$INST01  JOB (SYS),'Load HET RPTS000',         <-- Review and Modify
//             CLASS=A,MSGCLASS=A,               <-- Review and Modify
//             MSGLEVEL=(1,1)                    <-- Review and Modify
//* -------------------------------------------------------*
//* *  Sorting in MVS38J / Hercules                        *
//* *                                                      *
//* *  JOB: $INST01                                        *
//* *       Load CNTL data set from distribution tape      *
//* -------------------------------------------------------*
//STEP001  EXEC PGM=IEBCOPY                                           
//SYSPRINT DD  SYSOUT=*                                              
//SYSUT1   DD  DSN=RPTS000.V1R0M00.TAPE,DISP=OLD,                                
//             VOL=SER=VS1000,LABEL=(1,SL),                  
//             UNIT=480                          <-- Review and Modify   
//SYSUT2   DD  DSN=HERC01.RPTS000.CNTL,
//             DISP=(,CATLG),DCB=(RECFM=FB,LRECL=80,BLKSIZE=19040),
//             SPACE=(TRK,(100,10,10)), 
//             UNIT=3350,VOL=SER=PUB000          <-- Review and Modify   
//SYSIN    DD  DUMMY                                                    
/*                                                                  
//

Upon completion of download and installation, review / modify / run the three reporting programs (COBCOB, REPTCOB, RPTRPG)!

In Closing

All included software was developed and tested successfully on MVS38J TK3 running under the Hercules 3.13 emulator and MVS38J TK4- Update 8 running under the Hercules 4.00 emulator. Both Hercules emulators run on MS Windows 10 Professional.

After reviewing the above reporting examples, you should be able to compare and contrast the level of coding design and definition, including overall duration, of one detail report with one control break, across two programming languages.

Happy Report Writing!
Larry Belmontes

Tagged ,

Leave a Reply

Your email address will not be published. Required fields are marked *


CAPTCHA Image
Reload Image

This site uses Akismet to reduce spam. Learn how your comment data is processed.