Skip to content

Accept Statement

The ACCEPT Statement gives the program access to data either through direct user interaction, or through interaction with the operating environment.

General Format:

Format 1 ACCEPT data-field

The Format 1 ACCEPT Statement describes the ACCEPT of a field described in the Data Division.

       ACCEPT data-1 
              [ AT ]   LINE        numeric-1 
              [ AT ] { COLUMN   }    numeric-2
                     { POSITION } 

              [ WITH [NO] {BELL} ] 
                          {BEEP} 

              [ WITH BLINK ] 

              [ { WITH HIGHLIGHT } ] 
                { WITH LOWLIGHT  } 

              [ WITH REVERSE-VIDEO ] 

              [ { WITH UNDERLINE } ] 
                { WITH OVERLINE  } 

              [ FOREGROUND-COLOR IS numeric-3 ] 
              [ BACKGROUND-COLOR IS numeric-4 ] 

              [ SCROLL { UP   } ] 
                       { DOWN } 

              [ AUTO ] 

              [ FULL ] 

              [ REQUIRED ] 

              [ SECURE ] 

              [ UPDATE ] 

              [ PROMPT [ CHARACTER IS literal-1 ] ] 

              [ TIMEOUT timeout-value ] 

              [ ON EXCEPTION [crtstatus-var] statement-1 ] 
              [ NOT ON EXCEPTION statement-2 ] 
              [ END-ACCEPT ]

Syntax:

  1. data-n is a data item.
  2. numeric-n is a literal or data item that is numeric.
  3. literal-n is a character string.
  4. statement-n is an imperative statement.
  5. crtstatus-var is a numeric data field, declared either as PIC 9(4) or PIC 9(6).
  6. time-out-value is a literal or data item that is numeric.

General Rules:

Details on all of the SCREEN attributes below are described in the Screen Description Entries section.

  1. The LINE clause positions the cursor vertically on the screen.
  2. The COLUMN clause positions the cursor horizontally on the screen.
  3. The BELL attribute generates an audible “beep” sound when the input field is entered.
  4. The BLINK attribute causes the screen item to blink.
  5. The HIGHLIGHT attribute causes the screen item to display in high intensity.
  6. The LOWLIGHT attribute causes the screen item to display in low intensity.
  7. The REVERSE-VIDEO attribute reverses the foreground and background colors in the display of the screen item.
  8. The UNDERLINE attribute underlines the screen item.
  9. The OVERLINE attribute places a line over the screen item.
  10. The FOREGROUND-COLOR attribute assigns one of 8 colors to the foreground text.
  11. The BACKGROUND-COLOR attribute assigns one of 8 colors to the background color.
  12. The SCROLL phrase scrolls the screen up or down be a designated number of lines.
  13. The AUTO phrase automatically moves to the next data entry field when the current field is full.
  14. The FULL phrase requires that the field be FULL before it is exited.
  15. The REQUIRED phrase requires that the field have data entered before it is exited.
  16. The SECURE attribute allows data entry that does not echo to the screen.
  17. The UPDATE phrase causes the value of the field associated with the screen item to update the screen field prior to data entry.
  18. The PROMPT phrase allows the user to provide different char acters for the PROMPT of a field.
  19. The TIMEOUT phrase allows for an ACCEPT statement to be automatically terminated after a number of seconds, as defined in [timeout-value]. If no data has been entered into the ACCEPT statement in the time defined in [time out-value], then the ACCEPT statement terminates, generating an exception condition, and an exception value.
  20. If any data is entered into the ACCEPT before the designated timeout value, then the timeout timer is restarted.
  21. If no data is entered into the ACCEPT before the designated timeout value, then an exception condition occurs, and the COB-SCR-TIMEOUT exception value of 9001 is generated into the CRT STATUS variable.
    As an example, with an ACCEPT TIMEOUT of 5 seconds:
       ACCEPT data-1 TIMEOUT 5
              ON EXCEPTION
                     IF CRT-STATUS = COB-SCR-TIMEOUT
                            DISPLAY TIMED OUT LINE 10 COL 10
                     END-IF
       END-ACCEPT.

The ON EXCEPTION condition is triggered when an exception key is pressed, or an exception condition occurs, terminating the ACCEPT statement. When an ON EXCEPTION condition is triggered, and the ON EXCEPTION phrase is included in the ACCEPT statement:

The statement-list insided the scope of the ON EXCEPTION clause is executed. Control passes to the next statement after the ACCEPT statement. The NOT ON EXCEPTION condition is triggered when the ACCEPT statement is terminated normally. When an ACCEPT statement is terminated normally, the NOT ON EXCEPTION clause causes the statement–list inside the scope of the NOT ON EXCEPTION clause to be executed. Control then passes to the next statement after the ACCEPT statement.

Compiler Flags

The following compiler flags affect the behaviour of the field level or Screen Section ACCEPT:

Compiler Flag Description
-faccept-with-auto Causes the WITH AUTO clause to be assumed on field-level ACCEPT statements.
-faccept-with-update Causes the WITH UPDATE clause to be assumed on field-level ACCEPT statements.

Compiler Configuration File Flags

The following compiler configuration file flags affect the behaviour of the field level or Screen Section ACCEPT:

Compiler Flag Description
accept-with-update:yes | no Mimics the behavior of –faccept-with-update.
crtstatus-map: cit-value user-value Allows the user to re-map default crt status values for function keys, and other keystrokes. If no crtstatus-map is defined, CRT STATUS values are converted to PIC 9(4) and copied into the crt-status-var.
screen-exceptions Mimics the behavior the the environment variable COB_SCREEN_EXCEPTIONS. Enables the use of Page-Up, Page-Down, Up Arrown, Down Arrow keys on a field-level ACCEPT statement.
screen-raw-keys Mimics the behavior of the environment variable COB_SCREEN_RAW_KEYS. Enables the use of the Home, End, Insert, Delete, and Erase EOL keys.

Pressing the DEL key deletes the current character and moves the cursor one character to the left. A SPACE is inserted at the end of the field.

The EOL key erases to the end of the line.

The BACKSPACE key shifts the contents of the field one character to the left, beginning at the current character.

Runtime environment variables

The following runtime environment variables affect the behaviour of the field-level ACCEPT:

Environment Variable Description
COB_SCREEN_EXCEPTIONS When set to Y, enables the use of the Page Up, Page Down, Up Arrow, and Down Arrow keys on field-level ACCEPT statements.
COB_SCREEN_UPDATE_FIRST_KEY_ERASE When set to Y, causes the first key pressed in an input field to record the keystroke, and erase the rest of the field, for all field-level ACCEPT WITH UPDATE statements.
COB_SCREEN_DISABLE_REFORMAT When set to Y, disables the COB_SCREEN_UPDATE_FIRST_KEY_ERASE behaviour.

Format 2: ACCEPT screen

The Format 2 ACCEPT Statement describes the ACCEPT of a screen described in the Screen Section.

General Format:

       ACCEPT screen-1 
              [ AT ] LINE numeric-1 
              [ AT ] { COLUMN } numeric-2 
                     { POSITION } 

              [ WITH BELL ]

              [ WITH BLINK ] 

              [ { WITH HIGHLIGHT } ] 
                { WITH LOWLIGHT  } 

              [ WITH REVERSE-VIDEO ] 

              [ { WITH UNDERLINE } ] 
                { WITH OVERLINE  } 

              [ FOREGROUND-COLOR IS numeric-3 ] 
              [ BACKGROUND-COLOR IS numeric-4 ] 

              [ SCROLL { UP   } ] 
                       { DOWN } 

              [ AUTO ] 

              [ FULL ] 

              [ REQUIRED ] 

              [ SECURE ] 

              [ UPDATE ] 

              [ PROMPT [ CHARACTER IS literal-1 ] ]

              [ TIMEOUT timeout-value ] 

              [ ON EXCEPTION [crtstatus-var] statement-1       ] 
              [ NOT ON EXCEPTION statement-2 ] 
              [ END-ACCEPT ]

Syntax:

  1. screen-1 is a screen declared in the Screen Section.
  2. numeric-n is a literal or data item that is numeric.
  3. literal-n is a character string.
  4. statement-n is an imperative statement.
  5. crtstatus-var is a numeric data field, declared either as PIC 9(4) or PIC 9(6).
  6. timeout-value is a literal or data item that is numeric.

General Rules:

Details on all of the SCREEN attributes below are described in the Screen Description Entries section.

  1. The LINE clause positions the cursor vertically on the screen.
  2. The COLUMN clause positions the cursor horizontally on the screen.
  3. The BELL attribute generates an audible “beep” sound when the input field is entered.
  4. The BLINK attribute causes the screen item to bli nk.
  5. The HIGHLIGHT attribute causes the screen item to display in high intensity.
  6. The LOWLIGHT attribute causes the screen item to display in low intensity.
  7. The REVERSE-VIDEO attribute reverses the foreground and background colors in the display of the screen item.
  8. The UNDERLINE attribute underlines the screen item.
  9. The OVERLINE attribute places a line over the screen item.
  10. The FOREGROUND-COLOR attribute assigns one of 8 colors to the foreground text.
  11. The BACKGROUND-COLOR attribute assigns one of 8 colors to the background color.
  12. The SCROLL phrase scrolls the screen up or down be a designated number of lines.
  13. The AUTO phrase automatically moves to the next data entry field when the current field is full.
  14. The FULL phrase requires that the field be FULL before it is exited.
  15. The REQUIRED phrase requires that the field have data entered before it is exited.
  16. The SECURE attribute allows data entry that does not echo to the screen.
  17. The UPDATE phrase causes the value of the field associated with the screen item to update the screen field prior to data entry.
  18. The PROMPT phrase allows the user to provide different characters for the PROMPT of a field.
  19. The TIMEOUT phrase allows for an ACCEPT statement to be automatically terminated after a number of seconds, as defined in [timeout-value]. If no data has been entered into the ACCEPT statement in the time defined in [timeout-value], then the ACCEPT statement terminates, generating an exception condition, and an exception value.
    • If any data is entered into the ACCEPT before the designated timeout value, then the timeout timer is restarted.
    • If no data is entered into the ACCEPT before the designated timeout value, then an exception condition occurs, and the COB-SCR-TIMEOUT exception value of 9001 is generated into the CRT STATUS variable.
      Note that COB-SCR-TIMEOUT, and out default screen exception values are described in the file screenio.cpy, located in the $COBOLITDIR\copy directory.

      As an example, with a ACCEPT TIMEOUTof 5 seconds:
        ACCEPT screen-1 TIMEOUT 5
         ON EXCEPTION
          IF CRT-STATUS = 9001
           DISPLAY “TIMED OUT” LINE 10 COL 10
          END-IF
        END-ACCEPT.
    • The ON EXCEPTION condition is triggered when an exception key is pressed, terminating the ACCEPT statement. When an ON EXCEPTION condition is triggered, and the ON EXCEPTION phrase is included in the ACCEPT statement:
    • The statement-list insided the scope of the ON EXCEPTION clause is executed. Control passes to the next statement after the ACCEPT statement.
    • The NOT ON EXCEPTION condition is triggered when the ACCEPT statement is terminated normally. When an ACCEPT statement is terminated normally, the NOT ON EXCEPTION clause causes the statement-list inside the scope of the NOT ON EXCEPTION clause to be executed. Control then passes to the next statement after the ACCEPT statement.
  20. The following runtime environment variables affect the behaviour of the Screen Section ACCEPT:
    • COB_SCREEN_DISABLE_REFORMAT, when set to Y, disables the reformatting associated by default with the COB_SCREEN_UPDATE_FIRST_KEY_ERASE behavior.
    • COB_SCREEN_ESC, when set to Y, enables use of the escape key. Note that Page Up, Page Down, Up Arrow, and Down Arrow are enabled by default when ACCEPTing a Screen.
    • COB_SCREEN_INPUT_BOLDED, when set to Y, causes all input fields to be displayed in bold.
    • COB_SCREEN_INPUT_FILLER, when set to [char], changes the PROMPT character to [char].
    • COB_SCREEN_INPUT_INSERT_TOGGLE, when set to Y, causes the INS key to toggle between Overwrite and Insert mode. By default, pressing the INS key inserts a SPACE at the current cursor position.
    • COB_SCREEN_INPUT_REVERSED, when set to Y, causes all input fields to be displayed in REVERSE.
    • COB_SCREEN_INPUT_UNDERLINED, when set to Y, causes all input fields to be displayed with UNDERLINE.
    • COB_SCREEN_RAW_KEYS, when set to Y, enables use of the HOME, END, Ins, Del, and Erase EOL keys.

Code sample:

       IDENTIFICATION DIVISION. 
       PROGRAM-ID. ACCEPT-1. 
      * ACCEPT SCREEN 
      * ... LINE {PLUS/+} [ LINE NUMBER ] 
      * ... COL {PLUS/+} [ COL NUMBER ] 
      * PIC X 
      * TO [ WS-FLD-NAME ] 
      * USING [ WS-FLD-NAME ] 
      * VALUE [ LITERAL-1 ] 
      * BLANK SCREEN 
      * PROMPT CHARACTER 
       AUTHOR. CAVANAGH. 
       ENVIRONMENT DIVISION. 
       INPUT-OUTPUT SECTION. 
       DATA DIVISION. 
       WORKING-STORAGE SECTION. 
       77 WS-CHOICE PIC X VALUE SPACES. 
              88 VALID-SELECTION VALUE"B", "S", "F", "H", "T". 
       77 WS-ALLSTAR PIC X(40) VALUE SPACES. 

       SCREEN SECTION. 
       01 MENU-SCREEN. 
              05 VALUE "SELECT A PROFESSIONAL SPORT " 
                     BLANK SCREEN LINE 02 COL 26. 
              05 VALUE "B - BASEBALL" LINE + 2 COL 05. 
              05 VALUE "S - SOCCER" LINE PLUS 2 COL 05. 
              05 VALUE "F - FOOTBALL" LINE 08 COL 05. 
              05 VALUE "H - HOCKEY" LINE 10 COL 05. 
              05 VALUE "T - TERMINATE PROGRAM" LINE 12 COL 05. 
              05 VALUE "ENTER CHOICE:" LINE17 COL PLUS 5. 
              05 MENU-ANS-SCR LINE 17 COL + 15 
                     PIC X TO WS-CHOICE 
                     PROMPT CHARACTER IS "+". 
              05 MENU-ALLSTAR PIC X(40) LINE 20 COL 20 
                     USING WS-ALLSTAR. 
      * 
       PROCEDURE DIVISION. 
       MAINLINE. 
              DISPLAY MENU-SCREEN. 
              PERFORM ACCEPT-LOOP UNTIL WS-CHOICE = "T". 
              STOP RUN. 
      * 
       ACCEPT-LOOP. 
              ACCEPT MENU-SCREEN. 
              EVALUATE WS-CHOICE 
                     WHEN "B" MOVE "WILLY MAYS" TO WS-ALLSTAR 
                     WHEN "S" MOVE "RONALDO" TO WS-ALLSTAR 
                     WHEN "F" MOVE "PEYTON MANNING" TO WS-ALLSTAR 
                     WHEN "H" MOVE "BOBBY ORR" TO WS-ALLSTAR 
                     WHEN "T" CONTINUE 
                     WHEN OTHER MOVE "INVALID ENTRY" TO WS-ALLSTAR 
              END-EVALUATE. 
              DISPLAY MENU-ALLSTAR.

Format 2: Return Terminal Size characteristics

       ACCEPT numeric-1 FROM { LINES   } 
                             { COLUMNS }

Syntax:

numeric-n is a 3-digit numeric data item that returns the number of LINES/COLUMNS on the terminal.

General Rules:

  1. The ACCEPT numeric-1 FROM LINES statement retrieves the number of lines on the terminal console in which the program is executing.
  2. The ACCEPT numeric-1 FROM COLUMNS statement retrieves the number of columns on the terminal console in which the program is executing.
  3. Values returned represent the height and width characteristics, in characters, of the terminal console in which the program is executing.

Code Sample:

       IDENTIFICATION DIVISION. 
       PROGRAM-ID. ACCEPT-2. 
      * ACCEPT NUMERIC FROM LINES 
      * ACCEPT NUMERIC FROM COLUMNS 
       AUTHOR. CAVANAGH. 
       ENVIRONMENT DIVISION. 
       DATA DIVISION. 
       WORKING-STORAGE SECTION. 
       77 TEST-VAR1 PIC 999. 
       77 TEST-VAR2 PIC 999. 
       77 DUMMY PIC X. 
       SCREEN SECTION. 
       PROCEDURE DIVISION. 
       MAIN. 
              DISPLAY "TESTING ACCEPT VAR FROM LINES" LINE 10 COL 10. 
              ACCEPT TEST-VAR1 FROM LINES. 
              DISPLAY TEST-VAR1 LINE 12 COL 10. 

              DISPLAY "TESTING ACCEPT VAR FROM COLUMNS" LINE 15 COL 10. 
              ACCEPT TEST-VAR2 FROM COLUMNS. 
              DISPLAY TEST-VAR2 LINE 17 COL 10. 
              DISPLAY "ACCEPT FROM LINES/COLUMNS FINISHED!" 
                            LINE 20 COL 10. 
              ACCEPT DUMMY LINE 20 COL 45. 
              STOP RUN.

Format 3: Return Date-Time, and Command-line arguments

       ACCEPT data-3 FROM          { DATE } [ YYYYMMDD ] 
                                   { DAY  }
                                   { DAY-OF-WEEK } 
                                   { TIME } 
                                   { COMMAND-LINE } 
                                   { ARGUMENT-NUMBER }

Syntax:

data-n is a data item.

General Rules:

  1. ACCEPT data-3 FROM DATE returns the date in the format yymmdd.
  2. ACCEPT data-3 FROM DATE YYYYMMDD returns the date in the format yyyymmdd.
  3. ACCEPT data-3 FROM DAY returns the date in the Julian format YYDDD where DDD represents the ordinal position of the current day of the year.
  4. ACCEPT data-3 FROM DAY YYYYMMDD returns the date in the Julian format YYYYDDD where DDD represents the ordinal position of the current day of the year.
  5. ACCEPT data-3 FROM DAY OF WEEK returns a numeric value between 1 and 7, with 1 representing Monday, 2 representing Tuesday, etc... and 7 representing Sunday.
  6. ACCEPT data-3 FROM TIME returns the time in the format HHMMSShh, where:
    • HH refers to Hours, and is returned as an integer between 0 and 23.
    • MM refers to Minutes, and is returned as an integer between 0 and 59.
    • SS refers to Seconds, and is returned as an integer between 0 and 59.
    • hh refers to hundredths of seconds, and is returned as an integer between 0 and 99 .
  7. ACCEPT data-3 FROM COMMAND-LINE returns the arguments that were included on the command line after the program name.
    As an example, the command line below for running the program myprog contains 2 arguments, which are hello world.:

    >cobcrun myprog hello world

    In this example, ACCEPT data-3 FROM COMMAND-LINE returns the string “hello world” into data-3.
  8. ACCEPT data-3 FROM ARGUMENT-NUMBER returns the number of arguments on the command line. In the example above, there are 2 arguments, so the integer “ 2 ” would be returned.
    • To determine the ARGUMENT-NUMBER, COBOL-IT parses the command line, treating spaces as delimiters, except when they are enclosed within quotation (“ “) characters. Words contained within quotation characters are treated as a single argument.

Code Sample:

       IDENTIFICATION DIVISION. 
       PROGRAM-ID. ACCEPT-3. 
      *FORMAT 3 ACCEPT 
      * ACCEPT DATA-3 FROM  { DATE } [ YYYYMMDD ] 
      *                     { DAY  } 
      *                     { DAY-OF-WEEK } 
      *                     { TIME }
      *                     { COMMAND-LINE } 
      *                     { ARGUMENT-NUMBER } 
       ENVIRONMENT DIVISION. 
       DATA DIVISION. 
       WORKING-STORAGE SECTION. 
       77 VAR1A      PIC 9(6). 
       77 VAR1B      PIC 9(8). 
       77 VAR2       PIC 9(5). 
       77 VAR3       PIC 9. 
       77 VAR4       PIC 9(8). 
       77 VAR5       PIC X(10). 
       77 VAR6       PIC 9. 

       77 DUMMY PIC X. 
       SCREEN SECTION. 
       PROCEDURE DIVISION. 
       MAIN. 
              ACCEPT VAR1A FROM DATE. 
              DISPLAY VAR1A LINE 5 COL 10. 

              ACCEPT VAR1B FROM DATE YYYYMMDD. 
              DISPLAY VAR1B LINE 6 COL 10. 

              ACCEPT VAR2 FROM DAY. 
              DISPLAY VAR2 LINE 7 COL 10. 

              ACCEPT VAR3 FROM DAY-OF-WEEK. 
              DISPLAY VAR3 LINE 9 COL 10. 

              ACCEPT VAR4 FROM TIME. 
              DISPLAY VAR4 LINE 10 COL 10. 

              ACCEPT VAR5 FROM COMMAND-LINE. 
              DISPLAY VAR5 LINE 11 COL 10. 

              ACCEPT VAR6 FROM ARGUMENT-NUMBER. 
              DISPLAY VAR6 LINE 12 COL10. 

              DISPLAY "ACCEPT-3 FINISHED!" LINE 20 COL10. 
              ACCEPT DUMMY LINE 20 COL 45. 
              STOP RUN. 
      *

Format 4: Return the value of Environment Variables

       ACCEPT data-4 FROM ENVIRONMENT “[environment-variable-name]” 
              [ ON EXCEPTION statement-1 ] 
              [ NOT ON EXCEPTION statement-2 ] 
              [ END-ACCEPT ]

Syntax:

  1. data-n is a data item.
  2. environment-variable-name is the name of the environment variable being interrogated.
  3. statement-n is an imperative statement.

General Rules:

  1. ACCEPT data-4 FROM ENVIRONMENT interrogates the current command shell for the value of a given environment-variable-name.
  2. If the environment variable named by environment-variable-name does not exist, an EXCEPTION condition is created, and statement-1is executed in the formulation ON EXCEPTION statement-1.
  3. EXCEPTION conditions can only be detected through the ON EXCEPTION clause.
  4. The ON EXCEPTION clause is not required.
  5. The NOT ON EXCEPTION clause is parsed but is otherwise treated as commentary.

Code Sample:

       IDENTIFICATION DIVISION. 
       PROGRAM-ID. ACCEPT-4. 
      * ACCEPT VAR FROM ENVIRONMENT 
       ENVIRONMENT DIVISION. 
       DATA DIVISION. 
       WORKING-STORAGE SECTION. 
       77DATA-4 PIC X(30) VALUE SPACES. 
       77 DUMMY PIC X. 
       SCREEN SECTION. 
       PROCEDURE DIVISION. 
       MAIN. 
      *FORMAT 3 
      *ACCEPT DATA-4 FROM ENVIRONMENT 

              ACCEPT DATA-4 FROM ENVIRONMENT "COBOLITDIR". 
              DISPLAY DATA-4 LINE 10 COL 10. 

              DISPLAY "ACCEPT-4 FINISHED!" LINE 20 COL 10. 
              ACCEPT DUMMY LINE 20 COL 45. 
              STOP RUN.

Format 5: Return Argument-value

       ACCEPT data-5 FROM ARGUMENT-VALUE 
              [ ON EXCEPTION statement-1 ] 
              [ NOT ON EXCEPTION statement-2 ] 
              [ END-ACCEPT ]

Syntax:

  1. data-n is a data item.
  2. statement-n is an imperative statement.

General Rules:

  1. ACCEPT data-5 FROM ARGUMENT-VALUE processes the command line as a series of space delimited parameters.
  2. ACCEPT data-5 FROM ARGUMENT-VALUE can be used iteratively to return the values of all of the arguments on the command line.
  3. If there are no argument s on the command line, or if the values of all of the arguments on the command line have been returned, an an EXCEPTION condition is created, and statement-1 is executed in the formulation:

    ON EXCEPTION statement-1

    EXCEPTION conditions can only be detected through the ON EXCEPTION clause.
  4. The ON EXCEPTION clause is not required.
  5. The NOT ON EXCEPTION clause is parsed but is otherwise treated as commentary.

Code Sample:

       IDENTIFICATION DIVISION. 
       PROGRAM-ID. ACCEPT5. 
      * ACCEPT...FROM ARGUMENT NUMBER/ARGUMENT-VALUE 
      * THIS STATEMENT PROCESSES THE COMMAND LINE AS 
      * A SERIES OF SPACE-DELIMITED 
      * PARAMETERS. SEE YOUR LANGUAGE REFERENCE FOR DETAILS. 
      * RUN COBCRUN ACCEPT-5 ARG1 ARG2 ARG3 
      * ACCEPT VAR FROM ENVIRONMENT 
       ENVIRONMENT DIVISION. 
       DATA DIVISION. 
       WORKING-STORAGE SECTION. 
       77 DATA-1     PIC X(20). 
       77 DATA-2     PIC 9. 
       77 LINE-NUM   PIC 9. 
       77 DATA-3     PIC X(20) VALUE SPACES. 
       77 DUMMY      PIC X. 
       SCREEN SECTION. 
       PROCEDURE DIVISION. 
       MAIN. 
              ACCEPT DATA-1 FROM COMMAND-LINE. 
              ACCEPT DATA-2 FROM ARGUMENT-NUMBER. 

              MOVE 2 TO LINE-NUM 
              ADD 1 TO DATA-2 
              PERFORM DISPLAY-ARGUMENT-VALUES DATA-2 TIMES
              DISPLAY "ACCEPT5 FINISHED!" LINE 10 COL 10. 
              ACCEPT DUMMY LINE 10 COL 30. 

              STOP RUN. 
      * 
       DISPLAY-ARGUMENT-VALUES. 
              ACCEPT DATA-3 FROM ARGUMENT-VALUE 
                     ON EXCEPTION 
                            DISPLAY "THAT IS ALL FOLKS!" LINE LINE-NUM COL 10 
                     END-ACCEPT. 

                     IF DATA-3 NOT = SPACES 
                            DISPLAY DATA-3 LINE LINE-NUM COL 10 
                            ADD 1 TO LINE-NUM 
                            INITIALIZE DATA-3 
                     END-IF.

Format 6: ACCEPT FROM SYSIN/CONSOLE

ACCEPT data-6 FROM { mnemonic-name }

Syntax:

  1. data-n is a data item.
  2. mnemonic-name names the hardware device from which data is being transferred by the ACCEPT statement.

General Rules:

mnemonic-name must be either SYSIN or CONSOLE.

Code Sample:

       IDENTIFICATION DIVISION. 
       PROGRAM-ID. ACCEPT-6. 
      * ACCEPT...FROM SYSIN 
       ENVIRONMENT DIVISION. 
       DATA DIVISION. 
       WORKING-STORAGE SECTION. 
       77 DATA-1 PIC X(20). 
       77 DUMMY PIC X. 
       SCREEN SECTION. 
       PROCEDURE DIVISION. 
       MAIN. 
              ACCEPT DATA-1 FROM SYSIN. 
              DISPLAY DATA-1 LINE 8 COL 10. 

              DISPLAY "ACCEPT-6 FINISHED!" LINE 10 COL 10. 
              ACCEPT DUMMY LINE 10 COL 30. 

              STOP RUN.

Format 7: ACCEPT FROM [WORD]

ACCEPT data-7 FROM [WORD]

Syntax:

  1. data-n is a data item.
  2. WORD is associated with a hardware device in SPECIAL NAMES.

General Rules:

WORD is a user defined word that is assigned to SYSIN or CONSOLE in SPECIAL-NAMES.

Code Sample:

       IDENTIFICATION DIVISION. 
       PROGRAM-ID. ACCEPT-7. 
       ENVIRONMENTDIVISION. 
       CONFIGURATION SECTION. 
       SPECIAL-NAMES. 
              SYSIN IS KEYBOARD. 
       DATA DIVISION. 
       WORKING-STORAGE SECTION. 
       77 DATA-1 PIC X(30). 
       77 DUMMY PIC X. 
       PROCEDURE DIVISION. 
       MAIN. 
              ACCEPT DATA-1 FROM KEYBOARD. 
              DISPLAY DATA-1 LINE 10 COL 10. 

              DISPLAY "ACCEPT-7 FINISHED!" LINE 12 COL 10. 
              ACCEPT DUMMY LINE 12 COL 30. 
              STOP RUN.

Format 8: ACCEPT FROM ESCAPE KEY

ACCEPT FROM ESCAPE KEY is used to retrieve the value of the CRT STATUS variable when an ON EXCEPTION condition is triggered on an ACCEPT statement without having to declare CRT STATUS in SPECIAL-NAMES.

General Format:

ACCEPT data-8 FROM ESCAPE KEY

Syntax:

data-8 is a numeric data item that is 4 bytes in length.

General Rules:

  1. ACCEPT FROM ESCAPE KEY is used to retrieve the exception value returned on an exception condition.
  2. ACCEPT FROM ESCAPE KEY is executed inside the scope of the ON EXCEPTION clause.

Code Sample:

       IDENTIFICATION DIVISION. 
       PROGRAM-ID. ACCEPT-8. 
       ENVIRONMENT DIVISION. 
       CONFIGURATION SECTION. 
       SPECIAL-NAMES. 
       DATA DIVISION. 
       WORKING-STORAGE SECTION. 
       77 CRT-STAT PIC 9(4). 
       77 DATA-1 PIC X(10). 
       77 DUMMY PIC X. 
       PROCEDURE DIVISION. 
       MAIN. 
              DISPLAY "DATA 1: " LINE 10 COL 10. 
              ACCEPT DATA-1 
                     ON EXCEPTION 
                            ACCEPT CRT-STAT FROM ESCAPE KEY 
                     END-ACCEPT. 

                     DISPLAY CRT-STAT LINE 15 COL 10. 

                     DISPLAY "ACCEPT-8 FINISHED!" LINE 18 COL 10. 
                     ACCEPT DUMMY LINE 18 COL 30. 
                     STOP RUN.
Back to top