Menu

Strange behavior of "ACCEPT" verb

cdg
2020-10-29
2022-02-13
  • cdg

    cdg - 2020-10-29
    02  JRN-AMOUNT                  PIC S9(09)V99 value zero.
    . . .
              DISPLAY "Expected income tax refund (amount due): "
                                      AT  line LINE-NUMBER
              ACCEPT JRN-AMOUNT       AT  line LINE-NUMBER col 42
    

    results in

    Expected income tax refund (amount due): 00000000000
    

    Why does "ACCEPT" verb display the value of the field being accepted (before anything is entered), and how can this be avoided?

     
    • Brian Tiffin

      Brian Tiffin - 2020-10-29

      Two things.

      First, as a mention. GnuCOBOL is suboptimal with numerics in extended IO. I don't code extended IO very often, and rarely in anger, but I've found using PIC X for screen items, and MOVE to the working field is easier on the brain, sometimes with FUNCTION TEST-NUMVAL, NUMVAL for even less thinking. USAGE BINARY in a screen is just out, screen items are treated as raw untyped character fields in libcob extended IO, much like a group move, even for elementary items. There are some edit restrictions for PIC 9 fields, but getting virtual decimal points is not part of numeric field ACCEPT yet. Umm, as far as I know, and I'm behind at the moment.

      Second thing. extended ACCEPT was coded to DISPLAY a screen or field first. There is a persistent settings of WITH NO UPDATE (default as per default.conf) or WITH UPDATE. Persistent as in, an ACCEPT AT WITH UPDATE, will persist and the next ACCEPT will also be WITH UPDATE until told otherwise. (There is a setting in /usr/local/share/gnucobol/config/default.conf for accept-update: no That only seems to work with PIC X fields here. All PIC 9 fields show digits here, regardless of WITH [NO] UPDATE or PROMPT combos. And don't honour virtual decimal point (aside from truncation to zero for those positions).

      As stated, I'm not up on latest and greatest for extended IO features, Carl, I don't use TUI often enough for numeric fields without PIC X intermediates and a MOVE.

      I'm sure others will have more details.

      Have good,
      Blue

       
      • cdg

        cdg - 2020-10-29

        I tried "ACCEPT with no update" but got the same result. I ended up accepting a non-numeric (pic x(11)) field, and doing my own conversion of the value to numeric, as I do in my screenio module. But it's curious I haven't encountered this before. Or perhaps I did, and simply forgot. :-(

         

        Last edit: cdg 2020-10-30
        • Eugenio Di Lorenzo

          please have a look at GnuCOBOL FAQ at chapter:
          3.32 How can I properly manage numeric fields with extended screen IO ?

           

          Last edit: James K. Lowden 2020-10-30
      • James K. Lowden

        James K. Lowden - 2020-10-30

        I want to make sure I understand this issue. It sounds like something that could be fixed.

        First, what is "extended" about extended I/O? I don't understand what the term means or where it came from.

        Second, what would be ideal in your opinion? How should it work? I think I know: when you read a field, it appears correctly in whatever working storage you designate, and when you write one, it appears correctly on the screen. No FAQ 3.32 shenanigans needed.

        Why doesn't it work as it should? Which information is missing?

        By they way, I noticed a typo in the FAQ:

        FieldZ is a working filed

        not to put, er, too fine a point on it. ;-)

         
        • cdg

          cdg - 2020-10-30

          I want to make sure I understand this issue. It sounds like something that could be fixed.

          Everything could be fixed. The question is whether it needs to be fixed or not.

          First, what is "extended" about extended I/O? I don't understand what the term means or where it came from.

          Extended would appear to be a misnomer, since (once invoked) it replaces the normal Cobol screenio routines, rather than enhancing them. Normal Cobol screenio doesn't included positioning of the cursor or field attributes, and "extended" does. Unfortunately, extended only operates on a single field, so you can't say "DISPLAY A, B, C at line ...", but rather need three separate display statements. Also, omission of line and column specification SHOULD default to the current cursor position, but instead it goes to line 1 col 1 (which is a bug that was reported at least a year ago). And, apparently, extended screenio does not handle numeric fields correctly, as I learned today. Extended screenio defaults to displaying the current value of the field being accepted, so you have to specify "without update" to return to normal ACCEPT verb action. There are numerous other features and differences, but that is what comes to mind.

          Second, what would be ideal in your opinion? How should it work? I think I know: when you read a field, it appears correctly in whatever working storage you designate, and when you write one, it appears correctly on the screen. No FAQ 3.32 shenanigans needed.

          IMO, extended screenio would ideally function exactly as normal screenio, PLUS the ability to position the cursor and (for those who need it) optionally display the initial value of a field, and any other "extended" features. The latter can be of value in specific cases, such as screen layouts, so the user can make a correction without retyping the entire field, or for defaults (e.g. "Enter some value, or press return to accept the default value displayed").

          I didn't bother to read 3.32, so I don't know if it describes shenanigans, or if it simply documents the status quo.

          Why doesn't it work as it should? Which information is missing?

          It doesn't "work as it should" because it wasn't designed to work as (we might think) it should, and probably because of the difficulty of programming it to do so. Handling multiple fields, field attributes and cursor positions is far more complicated than handling one set.

          Who said information is missing?

          By they way, I noticed a typo in the FAQ...

          This is a prime example of Muphry's law ("If you write anything criticizing editing or proofreading, there will be a fault of some kind in what you have written." )

          And to quote Aker, "Wer Rechtschreibfehler findet, darf sie behalten oder an den Meistbietenden versteigern" (Everybody finding a misspelling is allowed to keep or sell it.)

          :-)

           

          Last edit: cdg 2020-10-30
          • James K. Lowden

            James K. Lowden - 2020-10-31

            Thank you for taking the time to explain the situation. From what I have seen of GnuCOBOL's screen handling, it's much too code-intensive. Screens should be described by data and handled by a library, which returns a form that it maps to a data structure. CICS and BMS are a good model. HTML is another.

            Everybody finding a misspelling is allowed to keep or sell it

            That reminds me of the NetBSD man page for chat(1):

            The chat program is in public domain. This is not the GNU public
            license. If it breaks then you get to keep both pieces.

            Whenever I have received a correction on something I published, I considered it a service. My correction was offered in the same spirit.

             
            • Brian Tiffin

              Brian Tiffin - 2020-11-10

              On extended IO. Not sure when I first heard it mentioned that way, but internally use it as an expression of "curses mode turned on", which is persistent once any TUI feature is used in a program run.

              And yes. A PICTURE editor in screen section would be awesome. What we have for now is keycodes stuffed in fields, regardless of type.

              On the typo. Hmm, that's not my code listing, so it might not get fixed. Or it might, if the contrib entry is changed, and I re cut'n'paste the listing.

              Have good,
              Blue

               
          • Simon Sobisch

            Simon Sobisch - 2020-11-10

            "extended" possibly came from "more than the very old simple ACCEPTT from / DISPLAY to the operator". MicroFocus' docs seem to call it "enhanced screen i/o".

             
  • Anonymous

    Anonymous - 2020-10-29

    Does it need a "blank when zero"

     
    • cdg

      cdg - 2020-10-29

      Why would it need a "blank when zero"? ACCEPT isn't supposed to display anything. (I seem to recall there is a setting for the "extended screen i/o" that determines whether or not to do this, but I can't find an example anywhere).

       
      • Brian Tiffin

        Brian Tiffin - 2020-10-29

        blank when zero won't work for signed PIC S fields, regardless. (I tried the same thing) ;-)

         
        • cdg

          cdg - 2020-10-30

          The "blank when zero" clause makes no sense with a zoned- or packed-decimal numeric field. It is only intended for edited fields. which are non-numeric by definition.

           
  • Joe Reichart

    Joe Reichart - 2020-11-15

    Strange indeed... The ACCEPT is tied to DISPLAY. Unique.

     
    • Brian Tiffin

      Brian Tiffin - 2020-11-15

      Originally it was put in for SCREEN. An ACCEPT screen-var did an implicit DISPLAY first. Even with single fields and AT WITH, a TUI accept displays the current field data first, unless told otherwise.

      As hinted at above, GnuCOBOL TUI IO is sub-optimal at the moment. I'll opine that the subsystem is destined to get better. It will just take the right nerd with the right itch or sense of annoyance to make GnuCOBOL screenio.c more robust for everybody. In the meanwhile, the TUI Tools contribution by Eugenio is a worthy peruse for anyone wanting to know how to tackle the quirks in libcob screenio from COBOL sources.

      https://sourceforge.net/p/gnucobol/contrib/HEAD/tree/trunk/tools/TUI-TOOLS/

      And yeah, strange. :-)

      Have good,
      Blue

       
      • Joe Reichart

        Joe Reichart - 2020-11-16

        Not too bad to work around.
        Use a pic x field for ACCEPT input.
        Move pic x field to an edited field of choice - zz.99, -zzz.99, etc..
        Move it to a numeric field for storage or back to the pic x field for the screen.

        Down side: Operator must over key entire field.
        Up side: A lot less code than the TUI tool to accomplish the same thing.

         
        • cdg

          cdg - 2020-11-16

          The COBOL ACCEPT of a numeric field works differently than the COBOL ACCEPT of a non-numeric field, so your solution does NOT work.

          For example, if you ACCEPT a pic 9(5) field, COBOL will not allow any non-numeric characters, and will right-justify and zero fill the result (i.e., if you enter "A", it will be rejected; if you enter "1" you will get 00001.

          Some compilers also provide for the ACCEPT of a signed numeric field, and allow a leading sign.

          If you ACCEPT a pic x(5) field, COBOL will allow any character, and left-justify the result without space-filling the unused positions (so you need to initialize it to spaces if necessary).

          Your solution does NOT produce the same results. And requiring an entire field to be keyed on a screen layout is not a small downside.

          (My solution is to ACCEPT a non-numeric field, and call a subroutine to edit the field and return a numeric field (see attached); then (if the field is valid, echo it with the edit pattern of choice).

          GnuCOBOL "extended" screenio also produces different results, which is disappointing. Rather than adding row, column, color and other screen attributes, it replaces COBOL DISPLAY and ACCEPT with an entirely different process. If you don't use any "extended" features, you get COBOL, but once you invoke any "extended" feature, all screenio is handled differently. The worst thing about this is that it can't be fixed, since existing programs depend on it. :-(

           

          Last edit: cdg 2020-11-16
          • Joe Reichart

            Joe Reichart - 2020-11-16

            Sure it works - it's in production now.
            Its possible because GNUCOBOL does its type casting like other compilers. Not every field has to be bullet proof in some certain way.
            While what you state is true - it is not the only way.

            Works with integers, fixed point, and negative numbers.
            Try it play with it - see what you get. Add you own editing.

            A operator entering the data knows it wants numeric input and there are ways to edit it also. For small fields say 1 to 5 digits it's is not an issue for an operator who knows what they are doing(training/documentation).

            I have had issues with accepting a pic 9 fields. When testing for 0, zero(s), or some numeric value if the test is "true" it gives a "false".

            EG
            01 zipcode pic 9(5).

            accept zipcode at line...
            (operator keys in 99999)
            
            if zipcode = 99999 (test is false)
            if zipcode = "99999" (test is true)
            

            It is as if the compiler is using the generated alpha field to do the comparison. Thinks zipcode is alphanumeric.

            Now I do have a routine that will test and verify each character of input and left or right adjust the data etc.. Use it most of the time but depends on the situation. There is a place for everything.

             
          • Eugenio Di Lorenzo

            how come you say it doesn't work?
            Please see and give a try to the following sample.
            Checking and receiving the data entered by the user requires 7 lines of code and that's it. much simpler than the (very nice) example you attached.
            (also see Brian's FAQ at 3.32 How can I properly manage numeric fields with extended screen IO ?)

                   >>SOURCE FORMAT IS FREE
            IDENTIFICATION DIVISION.
            program-id. GCACCEPT.
            *> ***********************************************************************************
            *> GnuCOBOL
            *> Purpose:    SHOWS HOW TO ACCEPT & CHECK A NUMBER WITH DCIMALS & SIGN FROM A FILED ON SCREEN
            *> Tectonics:  cobc -x GCACCEPT.COB  (use GnuCOBOL 2.0 or greater)
            *> Usage:      GCACCEPT
            *> Author:     Eugenio Di Lorenzo - Italia (DILO)
            *> License:    Copyright 2017 E.Di Lorenzo - GNU Lesser General Public License, LGPL, 3.0 (or greater)
            *> Version:    1.0 2017.03.01
            *> Changelog:  1.0 first release.
            *> ***********************************************************************************
            ENVIRONMENT DIVISION.
            Configuration Section.
             SPECIAL-NAMES.
               CRT STATUS IS wKeyPressed
               Decimal-Point is Comma.
            
            DATA DIVISION.
            WORKING-STORAGE SECTION.
            78  K-ESCAPE      VALUE 2005.
            
            01 blue    constant as 1. 
            01 green   constant as 2.
            01 cyan    constant as 3.
            01 red     constant as 4.
            01 magenta constant as 5.
            01 yellow  constant as 6.
            01 white   constant as 7.
            01 pro         pic X value  '_'. 
            01 wKeyPressed pic 9999.
            01 black   constant as 0.
            
            01 wRetCode    PIC 9999.  
            
            *> ***************************************************************************************
            *> HOW IT WORKS:
            *> ***************************************************************************************
            *> Field9 is your numeric field you have to accept and next you can store for example in a file
            *> in this example it is PIC S9(7)V99 = 9 bytes, 7 integers & 2 decimals signed
            *> FieldX is the field you have to use in the ACCEPT statement
            *> in this example it is 11 bytes = 9 digits + the sign (+ or -) + the comma
            *> FieldZ is a working filed to display the num ber on screen after the ACCEPT (11 bytes)
            *> it is same length than FieldX but it is edited
            
            01 Field9   PIC S9(7)V99. *> this is the numeric field (example to be stored in a file)
            01 FieldX   PIC X(11).
            01 FieldZ   PIC -(7)9,99. *> max edited number is -9999999,99 (11 chars)
            
            
            *> **************************************************************
            *>           P R O C E D U R E   D I V I S I O N
            *> **************************************************************
            PROCEDURE DIVISION .
            
            *> sets in order to detect the PgUp, PgDn, PrtSc(screen print), Esc keys,
            set environment 'COB_SCREEN_EXCEPTIONS' TO 'Y'.
            set environment 'COB_SCREEN_ESC'        TO 'Y'. 
            
            Inizio.
              display 'Type an amount .....:'    at 0505 with  Background-Color white Foreground-Color blue reverse-video
              display 'signed with 2 decimals'   at 0540 with  Background-Color white Foreground-Color blue reverse-video
              display '12345678901'              at 0627 with  Background-Color white Foreground-Color blue reverse-video
              display '(decimal point is comma)' at 0640 with  Background-Color white Foreground-Color blue reverse-video
              display 'ESC = EXIT' at 2303 with  Background-Color white Foreground-Color blue reverse-video
              accept FieldX at 0527 with  Background-Color blue Foreground-Color cyan
                     update prompt character is pro auto-skip reverse-video
            
              if wKeyPressed = K-ESCAPE go to End-Program end-if
            
            *> intrinsic function test-numval(string) 
            *> --------------------------------------
            *> tests the given string for conformance to the rules used by intrinsic FUNCTION NUMVAL.
            *> Returns 0 if the value conforms, a character position of the first non conforming character,
            *> or the length of the field plus one for other cases such as all spaces.
            *> example: you can type +123,44 (is ok) or -145,,23 (is ko)
              move function test-numval(FieldX) to wRetCode
              display  'RetCode.............:' at 1305 with  Background-Color white Foreground-Color blue reverse-video
              display  wRetCode   at 1334 with  Background-Color white Foreground-Color blue reverse-video
            
              display '                                                                          '
                    at 1505 with  Background-Color white Foreground-Color black reverse-video
             if  wRetCode = ZERO 
                 move function numval(FieldX) to Field9 FieldZ
                 move FieldZ to FieldX
                 display 'correct format number '                 at 1505 with  Background-Color white Foreground-Color green reverse-video
                 display 'Edited Number.......:'                  at 0905 with  Background-Color white Foreground-Color blue reverse-video
                 display  FieldZ                                  at 0927 with  Background-Color white Foreground-Color blue reverse-video
                 display 'Number in memory....:'                  at 1105 with  Background-Color white Foreground-Color blue reverse-video
                 display  Field9                                  at 1129 with  Background-Color white Foreground-Color blue reverse-video
                 display 'PIC S9(7)V99 = 9 bytes, 7 int & 2 dec.' at 1140 with  Background-Color white Foreground-Color blue reverse-video
              else
                 if wRetCode >  length of FieldX
                     display 'empty field ! type at least one digit (also zero) ' at 1505 with  Background-Color white Foreground-Color red reverse-video
                 else
                     display 'incorrect format number '            at 1505 with  Background-Color white Foreground-Color red reverse-video
                     display '- wrong 1st character at position: ' at 1529 with  Background-Color white Foreground-Color red reverse-video
                     display wRetCode                              at 1564 with  Background-Color white Foreground-Color red reverse-video
                     *> following statement is used to display the edited amount after the ACCEPT
                     display FieldX                                at 0527 with  Background-Color white Foreground-Color blue reverse-video
                 end-if
              end-if
            
             go inizio
             .
            
            End-Program.
                goback.
            
            *> *****************************************************************************************************************************
            *> STATEMENTS TO MANAGE A NUMERIC FIELD ON SCREEN (whitout the demo statements)
            *> *****************************************************************************************************************************
            *> display  'Type an amount:' at 0510 with  Background-Color white Foreground-Color blue reverse-video
            *> accept FieldX              at 0527 with  Background-Color blue Foreground-Color cyan
            *>    update prompt character is pro auto-skip reverse-video
            *> if function test-numval(FieldX) = ZERO
            *>    move function numval(FieldX) to Field9 FieldZ
            *>    move FieldZ to FieldX
            *> else
            *>    display 'wrong amount ' at 2034 with  Background-Color white Foreground-Color red reverse-video
            *>    display  FieldX         at 0527 with  Background-Color white Foreground-Color blue reverse-video
            *> END-IF
            
             

            Last edit: Eugenio Di Lorenzo 2020-11-17
            • cdg

              cdg - 2020-11-17

              I didn't say it doesn't work. I said it doesn't produce the same results, and I provided a detailed example of the differences. To reiterate, the COBOL ACCEPT of an non-numeric field does not work the same way as the COBOL ACCEPT of a numeric field, so accepting a non-numeric field and moving it to a numeric field does not produce the same result as accepting a numeric field is supposed to do.

              The "NUMEDIT" subroutine allows the free-format input field to contain a leading or trailing sign, commas, decimals, fractions, etc., and thus provides far more capability than the method you suggest. Why is this of value? So you can display numeric data in an edited format on an "Inquiry" screen, and allow the user to change what he/she wishes without having to re-enter all the data. So the user can enter the data he/she wishes to change in the most convenient format, and have it converted to the required format.

              Of course there are other solutions. Mine pre-dated gnucobol, and still works well.

               
              • Ralph Linkletter

                BMS and MFS lack advanced numeric data edit and validation facilities.
                I wrote a subroutine akin to Carl's (not as complete in functionality) such that numeric fields from BMS or MFS screens could be entered without the need for leading zeroes, commas accepted, plus or minus sign accepted, decimal point accepted.

                With BMS or MFS the input data was maintained as keyed.
                The subroutine built a work area that primarily was used for IF NUMERIC validation of the massaged input data fields.
                If a data field failed an edit ,the data was left intact as keyed. Highlighted, cursor, and error message for the offending data field applied.

                IMHO expecting an extension to COBOL screen handling to provide functionality that only explicit logic can accommodate is well beyond the purview of COBOL semantics.
                Especially when data is presented to a display device in an edited numeric paradigm (hence regarded as COBOL ALPHAMERIC). Numeric operators need help in massaging the data to standard COBOL numeric arithmetic and comparative criteria.

                Subroutines like Carl's are indispensable in application logic.

                 

                Last edit: Ralph Linkletter 2020-11-18
              • Eugenio Di Lorenzo

                Hi Carl, frankly speaking it is not clear to me what can be the advantage of the subroutine you wrote over my method.
                it allows the free-format input field to contain a leading or trailing sign, commas, decimals ... as you said.
                in my method the availability of the intrinsic function function test-numval (string)is exploited, which makes all the checks on the presence of invalid characters, the presence of the - or + sign, the presence of the decimal point and signals an error if present and it also tells you which character is in error.
                eg if you have indicated the - sign more times, if you have indicated the decimal symbol more times ...
                the user can edit the data in any way for corrections or modifications.
                I understand the need for your code when you didn't have the test-numval function in the past but now it simplifies everything enormously !

                 

Anonymous
Anonymous

Add attachments
Cancel





Want the latest updates on software, tech news, and AI?
Get latest updates about software, tech news, and AI from SourceForge directly in your inbox once a month.