bug-gnucobol
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

Re: [open-cobol-list] possibly bug: accept into numeric field


From: Alain Lucari
Subject: Re: [open-cobol-list] possibly bug: accept into numeric field
Date: Wed Nov 12 08:36:15 2003

Le Tue, 11 Nov 2003 18:34:37 -0600
"William M. Klein" <address@hidden> a écrit:

> I haven't followed ALL of this thread, but I did want to make
> certain that everyone reading this understands what the '85 ANSI/ISO
> Standard says about this.  
> 
> On page VI-71  GR(2) says,
> 
> "(2) The implementor will define, for each hardware device, the size
> of a data transfer.
> 
> Then GR4a goes on to say,
> 
> "a. If the size of the receiving data item (or of the portion of the
> data item not yet currently occupied by transferred data)lexceeds
> the the transferred data, the transferred data is stored aligned to
> the left receiving data item (or the portion of the receiving data
> item not yet occupied), and additional data is requested. In level
> 1, only one transfer of provided."
> 
> It is worth noting:
> 
> A) This wording remains the same in the 2002 Standard
> B) It is "fairly" clear that you left align and do NOT numeric
> justify when doing an ACCEPT from a "smaller" to a "larger" field.
> 
> > -----Original Message-----
> > From: address@hidden 
> > [mailto:address@hidden On 
> > Behalf Of Alain Lucari
> > Sent: Tuesday, November 11, 2003 5:54 AM
> > To: address@hidden
> > Subject: Re: [open-cobol-list] possibly bug: accept into numeric
> > field
> > 
> > 
> > Le Tue, 11 Nov 2003 10:43:55 +0900
> > Keisuke Nishida <address@hidden> a écrit:
> > 
> > > 
> > > What results do you suppose to obtain (or do you get
> > > from other compilers) by the following ACCEPT?
> > > 
> > >   Data item          Input
> > >   ---------          -----
> > >   01 X-1 PIC 99.     "123"
> > >   01 X-2 PIC 99V9.   "1"
> > >   01 X-3 PIC 99V9.   "123.4"
> > > 
> > > Maybe "23", "010", and "234"?  But it seems the standard
> > > requires X-1 to be "12". (At leat the NIST Test Suite has
> > > a test for this.)  Gee.
> > > 
> > I suppose that the quotes are just for explanation and not typed,
> > IMHO exactly 23, 010 and 23V4 with numerics receivers above
> > or "12", "1  ", "123" if the receivers are pic XX and XXX
> >  and "123.4" if the receiver is PIC X(5)
> > exactly like from a move.
> > 
>From many years I was thinking that an accept (from crt or command-line),
_not_ in screen section, should be done to an alphanumeric item and
treated by the program using a subroutine like that :

 IDENTIFICATION DIVISION.
 PROGRAM-ID. DECODE.
* fonction:  decodification d'une zone alphanum en num
 ENVIRONMENT DIVISION.
 CONFIGURATION SECTION.
 INPUT-OUTPUT SECTION.
 FILE-CONTROL.
 DATA DIVISION.
 FILE SECTION.
 WORKING-STORAGE SECTION.
 01  VALIN             PIC X(18).
 01  VAL-ENTIERE       PIC X(18).
 01  ENTIERS REDEFINES VAL-ENTIERE PIC 9(18).
 01  VAL-KE REDEFINES VAL-ENTIERE.
     03  KE OCCURS 18  PIC X.
 01  VAL-DECIMAL       PIC X(18).
 01  DECIMAL REDEFINES VAL-DECIMAL PIC V9(18).
 01  VAL-KD REDEFINES VAL-DECIMAL.
     03  KD OCCURS 18  PIC X.
*
 01  NB-ENTIER         PIC 99.
 01  NB-DECIMAL        PIC 99.
 01  NB-SPACE          PIC 99.
*
 01  VAL-KR.
     03  KR OCCURS 18  PIC X.
*
 01  I                 PIC 99.
 01  J                 PIC 99.
 01  SIGNE-VAL         PIC 99.
*
 LINKAGE SECTION.
 01  ZONE-DECOD.
     03  VAL-DECOD     PIC X(18).
     03  OUT-DECOD     PIC S9(12)V9(6).
     03  TST-DECOD     PIC X.
 PROCEDURE DIVISION USING ZONE-DECOD.
 DEBUT.
     MOVE 18 TO J.
     MOVE ALL "0" TO VAL-KR.
     MOVE zero TO SIGNE-VAL.
     MOVE zero TO OUT-DECOD.
     MOVE zero TO NB-SPACE.
     MOVE SPACES TO TST-DECOD.
     MOVE SPACES TO VAL-ENTIERE.
     MOVE SPACES TO VAL-DECIMAL.
*
     MOVE VAL-DECOD TO VALIN.
     INSPECT VALIN TALLYING SIGNE-VAL FOR ALL "-".
     INSPECT VALIN REPLACING ALL "-" BY " ".
     INSPECT VALIN REPLACING ALL "+" BY " ".
     INSPECT VALIN REPLACING ALL "," BY ".".
*
     UNSTRING VALIN DELIMITED BY "."
          INTO VAL-ENTIERE VAL-DECIMAL
          ON OVERFLOW MOVE "2" TO TST-DECOD GO TO FIN.
     MOVE 18 TO I.
 RAZ.
     IF KD (I) = " "  MOVE "0" TO KD (I)
                      ELSE GO TO SUITE.
     IF I NOT = 1  SUBTRACT 1 FROM I
                   GO TO RAZ.
 SUITE.
     INSPECT VAL-ENTIERE REPLACING LEADING " " BY "0".
     INSPECT VAL-ENTIERE TALLYING NB-SPACE FOR ALL " ".
     SUBTRACT NB-SPACE FROM 18 GIVING NB-ENTIER.
     IF VAL-DECIMAL NOT NUMERIC
            MOVE "1" TO TST-DECOD
            GO TO FIN.
     PERFORM RECADRAGE VARYING I FROM NB-ENTIER BY -1 UNTIL I = 0.
     MOVE VAL-KR TO VAL-ENTIERE.
     ADD ENTIERS DECIMAL GIVING OUT-DECOD.
     IF SIGNE-VAL > zero MULTIPLY -1 BY OUT-DECOD.
     GO TO FIN.
*
 RECADRAGE.
     IF KE (I) NOT NUMERIC  MOVE "1" TO TST-DECOD.
     MOVE KE (I) TO KR (J).
     SUBTRACT 1 FROM J.
*
 FIN.
     IF TST-DECOD NOT = SPACE MOVE zero TO OUT-DECOD
        MOVE SPACE TO TST-DECOD.
     EXIT PROGRAM.

Also, I was thinking that it is not possible to move an
pic X to a Pic 9 without a redefinition of the sender.

But Open-Cobol (and TC and perhaps new versions of M*F and Acu, etc ...)
accept the move from alphanumeric to numeric.

Also, I am reading  in "iso_iec_fcd1989:2001" page 412
14/ Any conversion of data required between the hardware device
and the data items referenced in screen-name-1 is defined by
the implementor.

So, IMHO, if the compiler is treating the accept with the same
rules for the move, you can respect the (standard ?) by defining 
the "to" field as  alphanumeric data item (and use your own
decoding routine like above) or use a numeric item as receiver
and hope that the rules for the MOVE are also used for ACCEPT,
but it seem to me stupid that an accept of 000123 on pic 9(5)
give 00012 instead of 00123 because one too more 0.

Sorry for my bad english,

Regards,
-- 
Alain Lucari (Eurlix)

reply via email to

[Prev in Thread] Current Thread [Next in Thread]