Menu

ACCEPT a number from console to PIC 9(09)V99. Will produce error when

GnuCOBOL
2024-07-03
2024-07-08
  • Michael F Gleason

    Simon Sobisch
    Should I open a BUG on this?
    After checking with the P.G., I wrote a routine that accepts a number from the console.
    The spec calls for a 1-9 digit number plus 2 decimals, with or without comas and a decimal point, to be entered from the console. The entered number is then converted to a number in words.
    Under the condition that the user types more characters than 8 before typing a decimal point, the receiving field does not contain the number entered. For example, typing 123456789.12 results in 123456789.10 being the value of the receiving field. Why does it end with a zero? It is because of the decimal being entered.
    The same with the commas, they take up a space in the conversion. Changing the pic to 9(10)V99 will allow the period/decimal to be entered. But now there is a leading 0. Changing the pic to 9(12)V99 will allow the period/decimal and comas to be entered. But now the number being entered without comas exceeds the original spec of a nine-digit identifier-1. (See DISPLAY2.COB TEST2 for the following)
    Typing in 123,456,789.12 results 123456789.00.
    typing in -123,456,789.1234 results 012345678.00. Note: identifier-1 is un-signed.
    Typing in 1,123,456,789.12 results 011234567.00.
    Typing in 12345678.12 results 012345678.12.
    Typing in 123,,,456.36 results 000123456.30. Note: ACCEPT correctly throws away all comas.
    Typing 12,,,345.67 results 000012345.67. Note: this is correct.
    When you type fewer than 9 characters with or without comas, identifier-1 is always correct.
    By the way, defining identifier-1 as PIC 9(09)V99 COMP-3. gives identical results.

    This behavior does not happen when receiving fields is numeric edited. PIC 999,999,999.00. always receives correctly. It also correctly truncates excessive leading and trailing digits.

    To my way of thinking ACCEPT should be tweaked to work with a numeric identifier-1 as well as it does with a numeric edited identifier-1. Zero fill when necessary and truncate on both ends while aligning with the decimal position as required.

    Attached are two programs.
    DISPLAY2.COB is the program I was writing when I discovered the problem. And the workaround. DISPLAY3.COB is a tiny program to test/demonstrate the issue.

    The solution is JUST DON'T DO THAT. when entering numbers from the console.

    Testing on a windows11 laptop running Gnucobol-X32-BDB-V33 from Chuck H.
    cobc (GnuCOBOL) 3.3-dev.0
    Copyright (C) 2024 Free Software Foundation, Inc.
    License GPLv3+: GNU GPL version 3 or later https://gnu.org/licenses/gpl.html
    This is free software; see the source for copying conditions. There is NO
    warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
    Written by Keisuke Nishida, Roger While, Ron Norman, Simon Sobisch, Edward Hart
    Built Jun 23 2024 19:18:59
    Packaged Jun 24 2024 00:18:44 UTC
    C version (MinGW) "14.1.0"

    Michael :-)

     
  • Vincent (Bryan) Coen

    Example 1 (DISPLAY2.COB) uses a numeric field so you can only input digits 0 - 9.
    So trying to input comma should NOT be accepted.

    The use of inputting a period should also be rejected but the numeric input processing is flacky in not having code that rejects invalid data correctly.

    My experience of input numbers is that one method with a second optional but still under test, can be used namely:

    1. Use a PIC X(size required such as 12 for your example)
      Then use NUMVAL to move to a numeric picture such as 9(9)v99 (with or without sign) as required. This can be preceded by using TEST_NUMVAL to test the input pre move. For both see PG for details of usage.

    2. Use Chuck H's C routine ACCEPT_NUMERIC to receive a number into say a s9(9)v99 comp-3 field. Then move it to where and as required.

    You can redefine the Pic X field as numeric edited to display it without any moves AFTER testing it using TEST_NUMVAL if needed otherwise.

     
  • Michael F Gleason

    Bryan
    The P.G. says

    1. If identifier-1 is a numeric data item, the character value read from the console or
      standard-input device will be parsed according to the rules for input to the NUMVAL
      intrinsic function (see [NUMVAL], page 502), except that none of the trailing sign
      formats are honoured.

    So, either the P.G. is in error or the ACCEPT statement should reject the input.

    Currently, the ACCEPT works as documented. '+' '-' '.' ',' and numbers 0-9 are accepted and parsed, as long as you do not enter more characters than the picture defines.
    If you enter anything else, the accept will return zero '0' into identifier-1. Mind you, the zero could be an edited data item. Take a peek at DISPLAY3.COB for the compare for what amounts to as a '0' zero.

    So, to my way of thinking, the ACCEPT, when identifier-1 is a numeric data item, needs a little bit of fixing and one should not need to go the NUMVAL way as ACCEPT says it is doing that for you.

    In the past, when accepting numbers FROM CONSOLE, I wrote the parsing myself. I just figured that I could go by the P.G. while playing around.

    Also, since accepting in a numeric edited data item seems to work without the error, I could go that Rought. I am still working on other ways to get the variable length number into a fixed length data item.

    The ACCEPT is extremely good/powerful but is only 99.999% perfect.
    If you don't have an implied decimal point in identifier-1, there is no problem as long as you don't break the rules.
    Take PIC 9(09) for identifier-1.
    If you enter fewer digits than identifier-1 defines, it right justifies and zero fills identifier-1.
    Enter 123 you get 000000123 in identifier-1. That's good.
    If you enter a number with comas and a decimal point and your data is not too long, it's OK.
    Enter 123,456.789 you get 000123456.That's OK.
    If you enter more digits than is defined, it is LEFT JUSTIFIED and truncated on the right.
    Enter 123456789123 you get 123456789 in identifier-1. I expected 456789123.
    If you enter a number with comas and a decimal point and to many characters.
    Enter 123,456,789.23 you get 001234567 in identifier-1

    As for chucks routine, we did a skype session and he showed it to me.

    If this were a production program and not one for my own amusement, I would be taking in the number or other data using the screen section. Then the problem does not exist.

    There are probably not too many production programs accepting data from a PC terminal using non-extended mode accepts. So, I can see that my issue is not to worry about. Just don't let a user get ahold of my programs and don't make data entry errors.
    As I said before, JUST DON'T DO THAT.

    Michael :-)

     
  • Vincent (Bryan) Coen

    Early this year I took on a migration of an OE (Order Entry) system written for Tandy Cobol that was RM Cobol v1.3 or .4 . It was to run under Xenix on a TRS80 series PC with ram from 640K and this left around 500k for applications.
    This was written by one US company that then passed it to another who in turn gave Tandy marketing rights. The various Tandy archives do NOT have this version of OE and there is no documentation for OE or any other Cobol based accounting system that I have found anywhere.
    In addition all three companies involved with OE and for that matter the other accounting suites are long gone. I should point out that there is various version for accounting also on the achive sites but all written in Basic where some manuals provide the source code but all look very lacking in functionality and even then only just about usable in the USA in the early 80's and no I did not look very hard - no point.

    They did also have CPM and may be later MPM when ram was extended but not by a lot.
    The programmers (but may well have only been one) had to contend with the Ram restriction by making use of Section numbering so that numbers above 50 are loaded and overlayed as and when called. Nothing new here as my ACAS system did the same which forced programs to be split into more than one program by sub functions using files to pass data between - This was changed in the late 80's early 90's to be merged into on program for these sub steps.
    But back to OE - as a further step to help keep ram tight the program also created two additional modules / programs that are called by all the other OE programs/
    1. For processing all reports but passing data via record in linkage.
    2. For processing ALL screen input and output (no screen section as too early).
    The screen program for numerics uses a pic s9(12)v9999 field to pass data between the caller and screen module and while it might be working with RM Cobol it does not with GC (v3.2) and while the data passing uses character specific addressing it is flaky in the way it is coded and not compatible with GC.

    So I changed all these numeric accepts etc., to use Chucks routine that inputs mostly to comp-3 fields.

    This works but NOT if you use a SS block. Now this might change as and when it is integrated into GC runtime etc as SS produces calls to process each field defined in turn so accept_numeric can also be used as direct C calls. Remember GC produces C code that in turn is compiled using gcc.

    My idea was to consider adding OE to ACAS as a supplemental sub suite to Sales Ledger Invoicing as it possibly had features not in invoicing BUT there was only extra two features it did have namely - 1. Salesman commission (despite no link to payroll) but some to AR (account Receivable) but no programming to transfer them .
    2. Back Order processing which just creating a file holding the order it could not action and a simple report on records.

    For -
    1. I have totally ignored as I have never meet a company that uses it - as all staff are on salary so no need.
    2. BO - at one point it was looked at but no customer using ACAS has requested it but that may not mean a great deal as they may just have processed those manually outside ACAS.

    So I have been adding Back Order processing into ACAS invoicing and with Stock Control and this functions as :
    Produces reports by Customer of stock items on BO and also a report by items on BO.
    Work on Stock Control program changes is complete with some testing/
    Work for producing the BO file records is complete and with some testing.
    Work to read in BO records and create new invoices (credit), Receipts (prepaid's), Proformas is currently close to completing programming.
    This last block of functions are not in the above OE application so the usefulness of OE is for me zero but OE has been tested (hence verifying the lack of extra functionality).

    OE does use accept_numeric routine for numeric processing and that all works.
    You are welcome to grab the code for OE and for that matter ACAS nightly builds from my website at : http://www.applewood.linkpc.net/files/acas/nightlybuilds/

    There are three files that are built each night at midnight - UK local time so latest at GMT+1.
    These are :
    ACAS-Test-Data.rar --- contains ACAS test data
    ACAS-Nightly.rar --- ACAS nightly build source content including manuals, build & run scripts etc.
    OE-nightly.rar ----- OE nightly build source code. docs & build scripts etc.

    Note OE may need ACAS sources to be installed if only for the common copy books as the OE menu program has some code in to link with ACAS should it have happened.

    Help yourself and the same applies to any one else interested - Note ACAS includes the suites :

    1. IRS (Nominal / General) Ledger.
    2. General Ledger but for users requiring Profit Centre / Branch processing - otherwise use IRS as it is easier to use. GL has not had much testing since migration to GnuCobol from MF Workbench.
    3. Sales Ledger - Accounts Receivable
    4. Purchase Ledger - Accounts Payables
    5. Stock Control - Inventory

    Warning: ACAS v3.02 is still having daily-ish changes to Sales Ledger invoicing program sl910 although I do try and remember that it passes a compile but it has NOT YET been tested for the BO processing.

    Also on the above site one level up is folder v3.01 which contains the previous version v3.01.
    The primary difference is that v3.02 supports both using Cobol Files and databases from MySql and Mariadb set via the ACAS system parameter file.

    Bug fixes and functional improvements have also occurred in v3.02 that are not present within v3.01 as I have not back ported them,

    for both versions the current version of the GnuCobol compiler v3.2 Final has been used for all dev and testing. All manuals written using Libre Office Writer - the free to obtain and use WP.

    Vincent

     
  • Michael F Gleason

    Vincent
    Very interesting. Back in my days on the mainframe I designed and had my programmers write an inventory system that included multi warehouse inventory with automated item location receiving. The system included purchase ordering that was combined automated and manual. Sales order entry. interface into accounts receiving and paying and general ledger. It did order filling with backorder too. Basically, the system did everything but personnel keeping. The big PCs were 640k IBM xt. We did not seriously do any PC work. Anyway, the whole thing was in COBOL with functions I wrote in assembler and 3270 CICS for users' inputs and inquiries. Those were the days.

    Anyway, back to the topic of this thread.

    I did some playing around with NUMVAL. It is pretty good. I took a PIC X(25) and moved it to a PIC 9(09)V99. It is so smart that it filters out everything but 0-9 and '.' decimal. I entered 123NUTS.15/100 and got 000000123.15. This may well be one of my favorites for taking in numbers when writing low level programs. GIDO Garbage In Data Out.

    Now just make ACCEPT that smart BY including the NUMVAL code like the PG/manual says it does.

    Michael :-)

     
  • Vincent (Bryan) Coen

    Sorry I only try and keep the manual up to date, compiler thats down to Simon and others.

     
  • Michael F Gleason

    Vincent
    Well then, see attached minor things to update the manual.
    I was keeping track of typos and misstatements to submit some day. So some day is here.

    Michael :-)

     
  • Ralph Linkletter

    Color - Colour
    Honor - Honour

    I guess it makes no difference no matter what side of the pond you call home :-)

     

    Last edit: Ralph Linkletter 2024-07-04
  • Vincent (Bryan) Coen

    For PG-Errors-07 ---
    The example should be if condition else ... end-if
    similar as the last tests - done.
    Typo tp -> to done.
    Spelling honoured - is correct, I am British not American :)

    Comma example changed as not correct anyway as an example so corrected and created 2nd example showing usage of zzz,zzz,zz9.

    Floating symbols corrected as you suggest.
    Latest version of the manuals PG and PR updated and on site.

    Thanks for all.

     
  • Michael F Gleason

    Back to the topic the ACCEPT statement can return the wrong number.
    Instead of using ACCEPT into a numeric data item, with its problem. I am now using ACCEPT into a PIC X(100) data item then using the function TEST-NUMVAL-C to validate the entered data and if TEST-NUMVAL-C returns 0/zero I use the function NUMVAL to move/convert the picture X input to a PIC S9(09)V99 COMP-3 data item. I now can feel secure that I have a valid 9 position, 2 decimal place number to process.

    The input is now forced to be the numbers 0-9, + or - sign, trailing DB or CR, comas and a decimal point, leading and or trailing spaces and the $ sign.

    What will happen if the input is greater than 9.2 characters is I let the NUMVAL truncate extra leading and or trailing digits. I don't care in this program if the user (me) inputs too large a number.

    What started out as an afternoon project for fun has grown into a weeks' worth of time that I did not get into trouble for being idle.

    Michael :-)

     
    • Simon Sobisch

      Simon Sobisch - 2024-07-05

      Note: to cater for truncation you could add

      IF tmp-var <> FUNCTION NUMVAL (inp-var)
      

      Just saying....
      Simon

       
  • Michael F Gleason

    Simon
    It looks to me that ACCEPT, when identifier-1 is a numeric data item, uses the number of characters that are represented by the statement as the size of var-inp. For example, it uses 11 for the length of var-inp when you have '05 VAR-INP PIC S9(09)V99 defined. What it should be is 12, not 11. This then allows for the input to have a decimal '.' in it. Because the data item is defined as having two decimal places, ACCEPT should be working with 12 characters for var-inp. More compensation is required to allowing input of comas, signs and the '$' character.

    Here is a snippet of code that is in place of ACCEPT to a numeric data item.

    ' ' '

    015800 005-BEGIN-PROGRAM.
    015900
    016000     DISPLAY SPACE.
    016100     DISPLAY "ENTER AMOUNT=" WITH NO ADVANCING.
    016200     MOVE SPACE                  TO WS-NUMBER-IN.
    016300     ACCEPT WS-NUMBER-IN. *> This is a PIC X(100).
    016400     IF WS-NUMBER-IN EQUAL SPACE
    016500         GO TO 900-EOP-GOBACK
    016600     END-IF.
    016700     MOVE TEST-NUMVAL-C(WS-NUMBER-IN) TO RETURN-CODE
    016800     IF RETURN-CODE = 0
    016900         CONTINUE *> Not doing anything if a good number
    017000     ELSE
    017100         MOVE RETURN-CODE        TO WS-RETURN-CODE
    017200         PERFORM UNTIL WS-RETURN-CODE(1:1) NOT EQUAL "0"
    017300             MOVE WS-RETURN-CODE(2:8) TO WS-RETURN-CODE(1:)
    017400         END-PERFORM
    017500         DISPLAY "INVALID DATA @ POSITION " WS-RETURN-CODE
    017600         GO TO 005-BEGIN-PROGRAM
    017700     END-IF
    017800     MOVE NUMVAL(WS-NUMBER-IN)   TO WS-NUMBER.
    

    ``
    ' ' '
    I started to type up a BUG but decided to post here first. What I was going to post is in the attached txt file ACCEPT-SOLUTION.TXT.

    I only thought it would be a BUG because the documentation's mentioning that it does what NUMVAL does.

    I hate the word BUG. It goes into my group as a 4-letter word. 'BUGS' is definitely a 4-letter word.

    Michael :-)

     

    Last edit: Michael F Gleason 2024-07-08
  • Michael F Gleason

    Why does it always mess up the indentation when I paste something

     
    • Simon Sobisch

      Simon Sobisch - 2024-07-07

      You want to put that in a code block - please edit your post surrounding it by

      ```cobol
      ```
      

      Which will add nice syntax highlighting as well.

       
      • Michael F Gleason

        I sort of figured it out. The thingy did the trick. I was always wondering how people did that. Thanks for the lesson.

        Michael :-)

         
  • Michael F Gleason

    Here is the snippet I tried to post doing a copy paste

     
    • Ralph Linkletter

      Persistence in using the screen section (and associated procedure division code) is an anomaly to me.
      Those kinds of manipulations and edits should be the applications domain. Outside the auspices of a screen section or the associated procedure division code. Definitely not part and not parcel of a COBOL compiler.

      Michael, I think it was you that stated in previous zOS / M VS engagements you wrote assembler subroutines to provide edit and manipulation services for CICS data fields to and from a CICS terminal via a COBOL program.

      I suspect that subroutines akin to what you wrote for zOS are needed for Linux terminals as well.

      Chuck H. created a wonderful service (and utilities) that removes any dependence on the vendor specific Screen Section. I do not believe any GnuCOBOL aficionados have attempted to use Chucks Screen Section. Y'all should.

      What runs with MF, or Fujitsu, or GnuCOBOL will execute identically if Chuck's service is deployed on any of the many COBOL vendor platforms.

      Just sayin :-)
      Ralph

       

Log in to post a comment.