products/sources/formale Sprachen/JCL/jcl3 image not shown  

Quellcode-Bibliothek

© Kompilation durch diese Firma

[Weder Korrektheit noch Funktionsfähigkeit der Software werden zugesichert.]

Datei: cblparc2.cbl   Sprache: Cobol

       IDENTIFICATION DIVISION.
       PROGRAM-ID.    CBLPARC2.
       AUTHOR.        SIMOTIME ENTERPRISES.
      *****************************************************************
      * Copyright (C) 1987-2005 SimoTime Enterprises, LLC.            *
      *                                                               *
      * All rights reserved.  Unpublished, all rights reserved under  *
      * copyright law and international treaty.  Use of a copyright   *
      * notice is precautionary only and does not imply publication   *
      * or disclosure.                                                *
      *                                                               *
      * Permission to use, copy, modify and distribute this software  *
      * for any non-commercial purpose and without fee is hereby      *
      * granted, provided the SimoTime copyright notice appear on all *
      * copies of the software. The SimoTime name or Logo may not be  *
      * used in any advertising or publicity pertaining to the use    *
      * of the software without the written permission of SimoTime    *
      * Enterprises.                                                  *
      *                                                               *
      * Permission to use, copy, modify and distribute this software  *
      * for any commercial purpose requires a fee to be paid to       *
      * SimoTime Enterprises. Once the fee is received by SimoTime    *
      * the latest version of the software will be delivered and a    *
      * license will be granted for use within an enterprise,         *
      * provided the SimoTime copyright notice appear on all copies   *
      * of the software. The SimoTime name or Logo may not be used    *
      * in any advertising or publicity pertaining to the use of the  *
      * software without the written permission of SimoTime           *
      * Enterprises.                                                  *
      *                                                               *
      * SimoTime Enterprises makes no warranty or representations     *
      * about the suitability of the software for any purpose. It is  *
      * provided "AS IS" without any express or implied warranty,     *
      * including the implied warranties of merchantability, fitness  *
      * for a particular purpose and non-infringement. SimoTime       *
      * Enterprises shall not be liable for any direct, indirect,     *
      * special or consequential damages resulting from the loss of   *
      * use, data or projects, whether in an action of contract or    *
      * tort, arising out of or in connection with the use or         *
      * performance of this software                                  *
      *                                                               *
      * SimoTime Enterprises                                          *
      * 15 Carnoustie Drive                                           *
      * Novato, CA 94949-5849                                         *
      * 415.883.6565                                                  *
      *                                                               *
      * RESTRICTED RIGHTS LEGEND                                      *
      * Use, duplication, or disclosure by the Government is subject  *
      * to restrictions as set forth in subparagraph (c)(1)(ii) of    *
      * the Rights in Technical Data and Computer Software clause at  *
      * DFARS 52.227-7013 or subparagraphs (c)(1) and (2) of          *
      * Commercial  Computer Software - Restricted Rights  at 48      *
      * CFR 52.227-19, as applicable.  Contact SimoTime Enterprises,  *
      * 15 Carnoustie Drive, Novato, CA 94949-5849.                   *
      *                                                               *
      *****************************************************************
      *      This program is provided by SimoTime Enterprises         *
      *        Our e-mail address is: [email protected]           *
      *     Also, visit our Web Site at http://www.simotime.com       *
      *                                                               *
      *****************************************************************
      *
      *****************************************************************
      * Source Member: CBLPARC2.CBL
      *****************************************************************
      *
      * CBLPARC2 - This program will process a SYSIN parameter.
      *
      * CALLING PROTOCOL
      * ----------------
      * USE STANDARD PROCEDURE TO EXECUTE, RUN OR ANIMATE.
      *
      * DESCRIPTION
      * -----------
      * This program will process the JCL parameter from SYSIN.
      *
      * //SYSIN   DD  *
      * Parameter from SYSIN...
      * //*
      *
      * or a DUMMY is required to avoid an ABEND on the ACCEPT...
      *
      * //SYSIN   DD DUMMY
      *
      * This program will simply display the text string.
      *
      ****************************************************************
      *
      * MAINTENANCE
      * -----------
      * 1997/02/27 Simmons, Created program.
      *
      *****************************************************************
      *
       DATA DIVISION.
       WORKING-STORAGE SECTION.
      *
      *****************************************************************
      *    Data-structure for Title and Copyright...
      *    ------------------------------------------------------------
       01  SIM-TITLE.
           05  T1 pic X(11) value '* CBLPARC2 '.
           05  T2 pic X(34) value 'Sample, Process SYSIN Parameter '.
           05  T3 pic X(10) value ' v03.12.02'.
           05  T4 pic X(24) value ' http://www.simotime.com'.
       01  SIM-COPYRIGHT.
           05  C1 pic X(11) value '* CBLPARC2 '.
           05  C2 pic X(20) value 'Copyright 1987-2005 '.
           05  C3 pic X(28) value ' SimoTime Enterprises, LLC '.
           05  C4 pic X(20) value ' All Rights Reserved'.

       01  SIM-THANKS-01.
           05  C1 pic X(11) value '* CBLPARC2 '.
           05  C2 pic X(32) value 'Thank you for using this sample '.
           05  C3 pic X(32) value 'by SimoTime Enterprises, LLC '.
           05  C4 pic X(04) value ' '.

       01  SIM-THANKS-02.
           05  C1 pic X(11) value '* CBLPARC2 '.
           05  C2 pic X(32) value 'Please send comments or suggesti'.
           05  C3 pic X(32) value 'ons to [email protected] '.
           05  C4 pic X(04) value ' '.

       01  FIRST-TIME              pic X       value 'Y'.

       01  MESSAGE-BUFFER.
           05  MESSAGE-HEADER      pic X(11)   value '* CBLPARC2 '.
           05  MESSAGE-TEXT        pic X(128).

       01  MESSAGE-TEXT-01.
           05  filler   pic X(20)  value 'Parameter length is '.
           05  JCL-PARM-LENGTH     pic 9(5)    value 0.

       01  SYSIN-PARAMETER         pic X(80)  value SPACES.
       01  SYSIN-LENGTH            pic 9(5)    value 0.

       01  IX-1                    pic 9(3)    value 0.

      *****************************************************************
       PROCEDURE DIVISION.
           if  FIRST-TIME not = 'N'
               perform Z-POST-COPYRIGHT
               move 'N' to FIRST-TIME
      *>       A DD statement is required or a hard ABEND will occur
      *>       on the ACCEPT. If no parameters are passed then a
      *>       //SYSIN DD DUMMY is required to prevent the COBOL
      *>       program from ABENDING on the ACCEPT ... from SYSIN.
               accept SYSIN-PARAMETER from SYSIN
           end-if

           subtract SYSIN-LENGTH from SYSIN-LENGTH
           if  SYSIN-PARAMETER = SPACES
               add SYSIN-LENGTH to ZERO giving JCL-PARM-LENGTH
               move MESSAGE-TEXT-01 to MESSAGE-TEXT
               perform Z-POST-MESSAGE
           else
               perform CALCULATE-TEXT-LENGTH
               add SYSIN-LENGTH to ZERO giving JCL-PARM-LENGTH
               move MESSAGE-TEXT-01 to MESSAGE-TEXT
               perform Z-POST-MESSAGE
               move SYSIN-PARAMETER  to MESSAGE-TEXT
               perform Z-POST-MESSAGE
           end-if

           perform Z-THANK-YOU.

           GOBACK.

      *****************************************************************
       CALCULATE-TEXT-LENGTH.
           add 1 to ZERO giving IX-1
           perform 80 times
               if  SYSIN-PARAMETER(IX-1:1) not = SPACE
                   add IX-1 to ZERO giving SYSIN-LENGTH
               end-if
               add 1 to IX-1
           end-perform
           exit.

      *****************************************************************
      *    Display Copyright or Program Messages...
      *****************************************************************
       Z-POST-COPYRIGHT.
           display SIM-TITLE      upon console
           display SIM-COPYRIGHT  upon console
           exit.

      *****************************************************************
       Z-POST-MESSAGE.
           display MESSAGE-BUFFER upon console
           move SPACES to MESSAGE-TEXT
           exit.

      *****************************************************************
       Z-THANK-YOU.
           display SIM-THANKS-01  upon console
           display SIM-THANKS-02  upon console
           exit.
      *****************************************************************
      *      This example is provided by SimoTime Enterprises         *
      *        Our e-mail address is: [email protected]           *
      *     Also, visit our Web Site at http://www.simotime.com       *
      *****************************************************************

¤ Dauer der Verarbeitung: 0.1 Sekunden  (vorverarbeitet)  ¤





Download des
Quellennavigators
Download des
sprechenden Kalenders

in der Quellcodebibliothek suchen




Haftungshinweis

Die Informationen auf dieser Webseite wurden nach bestem Wissen sorgfältig zusammengestellt. Es wird jedoch weder Vollständigkeit, noch Richtigkeit, noch Qualität der bereit gestellten Informationen zugesichert.


Bemerkung:

Die farbliche Syntaxdarstellung ist noch experimentell.


Bot Zugriff