From: santlou on
I'm using NUMVAL to convert an Alphanumeric field to numeric data, but
NUMVAL is not working the way it is documented.

Here is what I have:

05 WS-NUM-A PIC 9(10) VALUE ZERO.

...

COMPUTE WS-NUM-A = FUNCTION NUMVAL ("12345678")

After this stmt, WS-NUM-A = 0012345678
...

COMPUTE WS-NUM-A = FUNCTION NUMVAL ("123456789")

After this stmt, WS-NUM-A = 6784000075

According to the documentation, NUMVAL is accurate up to 18 digits.

Why is it that when I process a 9-digit field, the result is Totally
different and doesnt make any sense?

Any assistance that you can provide will be appreciated.

Using z/os.

--
Message posted using http://www.talkaboutprogramming.com/group/comp.lang.cobol/
More information at http://www.talkaboutprogramming.com/faq.html

From: Howard Brazee on
On Thu, 24 Jul 2008 13:45:51 -0500, "santlou" <santlou(a)comcast.net>
wrote:

>I'm using NUMVAL to convert an Alphanumeric field to numeric data, but
>NUMVAL is not working the way it is documented.
>
>Here is what I have:
>
>05 WS-NUM-A PIC 9(10) VALUE ZERO.
>
>..
>
>COMPUTE WS-NUM-A = FUNCTION NUMVAL ("12345678")
>
>After this stmt, WS-NUM-A = 0012345678
>..
>
>COMPUTE WS-NUM-A = FUNCTION NUMVAL ("123456789")
>
>After this stmt, WS-NUM-A = 6784000075
>
>According to the documentation, NUMVAL is accurate up to 18 digits.
>
>Why is it that when I process a 9-digit field, the result is Totally
>different and doesnt make any sense?
>
>Any assistance that you can provide will be appreciated.
>
>Using z/os.

Here's what I get:

WS-NUM-A="0012345678"
WS-NUM-A="0123456789"


PP 5655-G53 IBM Enterprise COBOL for z/OS 3.4.1 Date 07/24/2008 Time
14:06:04 Page 1
Invocation parameters:
TEST,XREF,MAP,OUTDD(SYSOUX),DYNAM,SSRANGE,RENT,BUFSIZE(20000) Options
in effect: NOADATA NOADV APOST ARITH(COMPAT)
NOAWO BUFSIZE(20000) NOCICS CODEPAGE(1140)
NOCOMPILE(E) NOCURRENCY DATA(31) NODATEPROC DBCS
NODECK NODIAGTRUNC NODLL NODUMP DYNAM NOEXIT
NOEXPORTALL
NOFASTSRT
FLAG(I,I)
NOFLAGSTD
INTDATE(ANSI)
LANGUAGE(EN)
LIB
LINECOUNT(60)
NOLIST
MAP
NOMDECK
NONAME
NSYMBOL(NATIONAL)
NONUMBER
NUMPROC(NOPFD)
OBJECT
NOOFFSET
NOOPTIMIZE
OUTDD(SYSOUX)
PGMNAME(COMPAT)
RENT
RMODE(AUTO)
SEQUENCE
SIZE(MAX)
SOURCE
SPACE(1)
NOSQL
SQLCCSID
SSRANGE
NOTERM
TEST(ALL,SYM,NOSEPARATE)
NOTHREAD
TRUNC(STD)
NOVBREF
PP 5655-G53 IBM Enterprise COBOL for z/OS 3.4.1
NOWORD
XREF(FULL)
YEARWINDOW(1900)
ZWB
From: Howard Brazee on
EDIT UMS.D44201.COBOL(BRAZEE) - 01.29 7 CHARS
'WS-NUM-A'
Command ===> Scroll
===> CSR
****** ****************************** Top of Data
*******************************
- - - - - - - - - - - - - - - - - - - 43 Line(s) not
Displayed
003640 05 WS-NUM-A PIC 9(10) VALUE ZERO. - - - - - - - - -
- - - - - - - - - - 30 Line(s) not Displayed
006150 COMPUTE WS-NUM-A = FUNCTION NUMVAL ("12345678"). 006151
DISPLAY 'WS-NUM-A="' WS-NUM-A '"'. 006160 COMPUTE WS-NUM-A =
FUNCTION NUMVAL ("123456789") 006170 DISPLAY 'WS-NUM-A="'
WS-NUM-A '"'. - - - - - - - - - - - - - - - - - - -
12 Line(s) not Displayed
From: HeyBub on
santlou wrote:
> I'm using NUMVAL to convert an Alphanumeric field to numeric data, but
> NUMVAL is not working the way it is documented.
>
> Here is what I have:
>
> 05 WS-NUM-A PIC 9(10) VALUE ZERO.
>
> ..
>
> COMPUTE WS-NUM-A = FUNCTION NUMVAL ("12345678")
>
> After this stmt, WS-NUM-A = 0012345678
> ..
>
> COMPUTE WS-NUM-A = FUNCTION NUMVAL ("123456789")
>
> After this stmt, WS-NUM-A = 6784000075
>
> According to the documentation, NUMVAL is accurate up to 18 digits.
>
> Why is it that when I process a 9-digit field, the result is Totally
> different and doesnt make any sense?
>
> Any assistance that you can provide will be appreciated.
>

Can't duplicate your results - I get the expected answers.


From: William M. Klein on
The results are certainly "unexpected". What compiler (vendor and
version/release) are you using on what platform?

It is with noting that NUMVAL is NOT required to produce "exact" results, i.e.
it MAY (in a Standard conforming implementation) return a floating-point value
which MAY be different than what is expected. However, I would consider what
you report to be a "bug". Have you contacted your vendor?

--
Bill Klein
wmklein <at> ix.netcom.com
"santlou" <santlou(a)comcast.net> wrote in message
news:614c9cdabd83e6e6e9658d88e4c85eea(a)localhost.talkaboutprogramming.com...
> I'm using NUMVAL to convert an Alphanumeric field to numeric data, but
> NUMVAL is not working the way it is documented.
>
> Here is what I have:
>
> 05 WS-NUM-A PIC 9(10) VALUE ZERO.
>
> ..
>
> COMPUTE WS-NUM-A = FUNCTION NUMVAL ("12345678")
>
> After this stmt, WS-NUM-A = 0012345678
> ..
>
> COMPUTE WS-NUM-A = FUNCTION NUMVAL ("123456789")
>
> After this stmt, WS-NUM-A = 6784000075
>
> According to the documentation, NUMVAL is accurate up to 18 digits.
>
> Why is it that when I process a 9-digit field, the result is Totally
> different and doesnt make any sense?
>
> Any assistance that you can provide will be appreciated.
>
> Using z/os.
>
> --
> Message posted using
> http://www.talkaboutprogramming.com/group/comp.lang.cobol/
> More information at http://www.talkaboutprogramming.com/faq.html
>