MVSFORUMS.com Forum Index MVSFORUMS.com
A Community of and for MVS Professionals
 
 FAQFAQ   SearchSearch   Quick Manuals   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

NUMERIC check and NUMVAL function

 
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Application Programming
View previous topic :: View next topic  
Author Message
Dip
Beginner


Joined: 24 Mar 2006
Posts: 27
Topics: 14

PostPosted: Tue Apr 04, 2006 7:34 pm    Post subject: NUMERIC check and NUMVAL function Reply with quote

Code:

01  FILEIN-RECORD.
05  VAR1.                                         
          10  VAR1-LEN          PIC S9(4)  USAGE COMP.   
          10  VAR1-TEXT         PIC X(100).             
-------------
-------------   
05  WS-ATTRIB-NU                  PIC 9(18)  VALUE ZEROS.

05  WS-VAR1.                                           
          49  WS-VAR1-LEN          PIC S9(4)  USAGE COMP.   
          49  WS-VAR1-TEXT         PIC X(100).               

I am reading the records froma file in VAR1 (extracted varchar field froma table) which can contain both NUMERIC (49000) and NON NUMERIC value.
The value of VAR1 will be compared with NUMERIC item and based on the compaison i have some other move statements.
When the value of the VAR1 is not numeric i want to move this as it is from the file.how can i do this?

I tried this :
Code:

IF    (WS-VAR1-TEXT IS NOT NUMERIC)             
   display 'I AM IN THE NOT NUMERIC IF'
   MOVE VAR1-TEXT(1:VAR1-LEN)             
                              TO WS-VAR1-TEXT   
   MOVE VAR1-LEN         TO WS-VAR1-LEN   
ELSE
   display 'I AM IN THE NOT NUMERIC ELSE'                                                   
   COMPUTE WS-ATTRIB-NU      =                       
               FUNCTION NUMVAL(WS-VAR1-TEXT)   
    IF     WS-ATTRIB-NU  < 50000                     
       MOVE '< $50000' TO WS-VAR1-TEXT           
       MOVE 8          TO WS-VAR1-LEN           
    ELSE IF 
       WS-ATTRIB-NU  =< 100000
       other conditions
       ----------------
       ----------------
    END-IF.   

For any value (numeric and non numeric)the control is going to the first IF loop.
I am getting the dispaly 'I AM IN THE NOT NUMERIC IF' for VAR1 = 10000000, 10, '< $50000'

Can anyone help me to resolve this.

Thanks!
Dip.
Back to top
View user's profile Send private message Yahoo Messenger
deepeshk79
Beginner


Joined: 20 Jun 2003
Posts: 112
Topics: 48
Location: Bangalore

PostPosted: Wed Apr 05, 2006 3:04 am    Post subject: Reply with quote

Dip,

The variable VAR1 is defined as X(100). So if it has 1000000 in it then the remaining is spaces. So it fails the NUMERIC test. Check if you can reduce the field length of VAR1 and then do this.

Regards,
Deepesh
Back to top
View user's profile Send private message AIM Address
Mervyn
Moderator


Joined: 02 Dec 2002
Posts: 415
Topics: 6
Location: Hove, England

PostPosted: Wed Apr 05, 2006 3:20 am    Post subject: Reply with quote

Have you tried reference modification?

Code:
IF    (VAR1-TEXT(1:VAR1-LEN) IS NOT NUMERIC)

_________________
The day you stop learning the dinosaur becomes extinct
Back to top
View user's profile Send private message
Dip
Beginner


Joined: 24 Mar 2006
Posts: 27
Topics: 14

PostPosted: Thu Apr 06, 2006 1:25 am    Post subject: Reply with quote

Hi,

I tried reference modification and its working.

Thanks a lot for all the help.

-Dip.
Back to top
View user's profile Send private message Yahoo Messenger
Jaya
Beginner


Joined: 02 Sep 2005
Posts: 77
Topics: 10
Location: Cincinnati

PostPosted: Fri Jul 07, 2006 6:32 am    Post subject: Reply with quote

Hi,

I have an IDMS ALPHANUMERIC database field with picture clause X(65) which contains a numeric rate value with 2 decimal places like 1.5 or 15.5 upto 99.99 and no embedded signs.The numeric data can have leading and trailing spaces only.

I have to extract that rate value to a NUMERIC field with picture
9(2)V9(2).

I used EXTRACT function in ADSO for similar requirement. In batch cobol i am trying to use NUMVAL function to achieve the same.

But my compiler
Quote:
1PP 5668-958 IBM VS COBOL II Release 3.2

doesn't recognise any function.

Please give the effecient method of extracting the numeric value.

Thanks,
Jaya.
_________________
"Great spirits have always encountered violent opposition from mediocre minds."
-Albert Einstein
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12370
Topics: 75
Location: San Jose

PostPosted: Fri Jul 07, 2006 7:21 am    Post subject: Reply with quote

Jaya,

Your version of COBOL does not support any Intrinsic Functions. So try this code.

Code:

01 W-STR                 PIC X(65).                       
01 S-DOT-FOUND           PIC X(01) VALUE 'N'.             
01 W-SUB                 PIC S9(04) COMP.                 
01 W-NUM-VAL.                                             
   05 W-INT              PIC 9(02).                       
   05 W-DOT              PIC X.                           
   05 W-DEC              PIC 9(02).                       
                                                         
PROCEDURE DIVISION.                                       
                                                         
     PERFORM VARYING W-SUB FROM 65 BY -1 UNTIL W-SUB < 1 
          OR S-DOT-FOUND = 'Y'                             
          IF W-STR (W-SUB : 1) = '.'                       
             MOVE 'Y'                  TO S-DOT-FOUND
             MOVE W-STR(W-SUB - 2 : 2) TO W-INT           
             MOVE W-STR(W-SUB     : 1) TO W-DOT           
             MOVE W-STR(W-SUB + 1 : 2) TO W-DEC           
         END-IF                                           
     END-PERFORM                                         
                                                         
     INSPECT W-NUM-VAL REPLACING ALL ' ' BY '0'           

     DISPLAY 'NUM-VAL : ' W-NUM-VAL                       


Hope this helps...

Cheers

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
Jaya
Beginner


Joined: 02 Sep 2005
Posts: 77
Topics: 10
Location: Cincinnati

PostPosted: Mon Jul 10, 2006 5:02 am    Post subject: Reply with quote

Kolusu,

Thanks for your solution.. It works fine even for the boundary values which i thought, it wouldn't work.

If a numeric value say 1.5 or .05 is present in the first 3 bytes of the alphanumeric field X(65), the reference modification starting position for
Code:
MOVE W-STR(W-SUB - 2 : 2) TO W-INT   
will be less than 1, which according to VS cobol 2 manual will make the program abort.

But the above code works fine even for the above cases with SSRANGE and NOSSRANGE compile options.

I am not sure how am i getting the correct results.
Please correct me if my understanding is wrong..

Thanks,
Jaya.
_________________
"Great spirits have always encountered violent opposition from mediocre minds."
-Albert Einstein
Back to top
View user's profile Send private message
Jaya
Beginner


Joined: 02 Sep 2005
Posts: 77
Topics: 10
Location: Cincinnati

PostPosted: Tue Jul 11, 2006 2:48 am    Post subject: Reply with quote

Hi,

I am more concerned about the above logic, since i am about to update many IDMS records based on the extracted rate value based calculations.

Also the above code doesn't work for 2 digit integer values like 2 or 15 embedded in X(65).

My workaround is
1. Find the number of dots using Inspect tallying to confirm whether embedded number is integer or real.
2. If real proceed with kolusu's above solution (can somebody confirm that solution whether it will always run fine)
3. If integer execute the following code
Code:

                                                           
IF WS-DOT-COUNT = 0                                         
   MOVE ZEROES TO WS-SPACE-COUNT                           
   MOVE ZEROES TO WS-DEC                                   
   INSPECT WS-DATA TALLYING WS-SPACE-COUNT       
           FOR LEADING ' '                                 
   IF WS-DATA (WS-SPACE-COUNT + 2 : 1)           
                                           IS NOT NUMERIC   
     MOVE WS-DATA (WS-SPACE-COUNT + 1 : 1)       
                                   TO WS-INT               
   ELSE                                                     
     MOVE WS-DATA (WS-SPACE-COUNT + 1 : 2)       
                                   TO WS-INT               
   END-IF                                                   
END-IF                                                     



Thanks,
Jaya.
_________________
"Great spirits have always encountered violent opposition from mediocre minds."
-Albert Einstein
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12370
Topics: 75
Location: San Jose

PostPosted: Tue Jul 11, 2006 4:41 am    Post subject: Reply with quote

Jaya,

My solution will NOT work in case of integers without a decimal point. Also as you pointed out, it will not work for boundary values. You need to come out with complete details of various formats of the input data. I gave the sample code based on your data.

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
Jaya
Beginner


Joined: 02 Sep 2005
Posts: 77
Topics: 10
Location: Cincinnati

PostPosted: Wed Jul 12, 2006 1:48 am    Post subject: Reply with quote

Kolusu,

Thanks a lot for the reply!!!
Sorry for not mentioning the complete details in the beginning as i have seen such data in database very recently.This data is updated through online screens.

The possible values of data are
Quote:
.5bbb upto 65
1.5bbb upto 65
b.05bbb upto 65
bb.5
12.25 upto 65
1bbb upto 65
b2bbbb
bbb25
bb.2bb

b- blank

I made changes to your code to suit my requirement and are working fine.
F.Y.I..
Code:
01   WS-NUM-VAL.                                         
       05 WS-INT                   PIC 9(02).               
       05 WS-DEC                   PIC 9(02).               
  01   WS-RATE   REDEFINES  WS-NUM-VAL   PIC 9(2)V9(2).
 *                                                         

      MOVE ZEROES TO WS-DOT-COUNT.                             
      INSPECT WS-DATA TALLYING WS-DOT-COUNT         
              FOR ALL '.'.                                     
      DISPLAY 'WS-DOT-COUNT:' WS-DOT-COUNT.                   
      IF WS-DOT-COUNT > +1         
         DISPLAY 'invalid rate:'                           
         MOVE +1234       TO WS-USER-CODE                     
         CALL 'ILBOABN0' USING WS-USER-CODE                   
      END-IF.                                                 
      IF WS-DOT-COUNT = +1                  Real number                   
        MOVE 'N'          TO WS-DOT-FOUND                     
        PERFORM VARYING WS-SUB FROM 1 BY 1 UNTIL WS-SUB > 65   
                  OR WS-DOT-FOUND = 'Y'                         
            IF WS-DATA (WS-SUB : 1) = '.'             
              MOVE 'Y'                  TO WS-DOT-FOUND         
              DISPLAY 'WS-SUB:' WS-SUB                           
              EVALUATE WS-SUB                                   
                  WHEN 1                                         
                      MOVE ZEROES TO WS-INT                     
                      MOVE WS-DATA (WS-SUB + 1 : 2)   
                            TO WS-DEC                           
                  WHEN 2                                         
                      MOVE WS-DATA (WS-SUB - 1 : 1)   
                            TO WS-INT                           
                      MOVE WS-DATA (WS-SUB + 1 : 2)   
                            TO WS-DEC                           
                  WHEN 64                                       
                      MOVE WS-DATA (WS-SUB - 2 : 2)   
                            TO WS-INT                           
                      MOVE WS-DATA (WS-SUB + 1 : 1)   
                            TO WS-DEC     
                      MULTIPLY WS-DEC BY 10 GIVING WS-DEC
                  WHEN 65                                       
                      MOVE WS-DATA (WS-SUB - 2 : 2)   
                            TO WS-INT                           
                      MOVE ZEROES TO WS-DEC                     
                  WHEN OTHER                                     
                      MOVE WS-DATA (WS-SUB - 2 : 2)   
                            TO WS-INT                           
                      MOVE WS-DATA (WS-SUB + 1 : 2)   
                            TO WS-DEC                           
              END-EVALUATE                                       
            END-IF                                               
        END-PERFORM                                             
     END-IF.                                                     
*                                                               
     IF WS-DOT-COUNT = 0                     integer number                   
        MOVE ZEROES TO WS-SPACE-COUNT                           
        MOVE ZEROES TO WS-DEC                                   
        INSPECT WS-DATA TALLYING WS-SPACE-COUNT     
                FOR LEADING ' '                                 
        IF WS-DATA (WS-SPACE-COUNT + 2 : 1)         
                                                IS NOT NUMERIC 
          MOVE WS-DATA (WS-SPACE-COUNT + 1 : 1)     
                                        TO WS-INT               
        ELSE                                                   
          MOVE WS-DATA (WS-SPACE-COUNT + 1 : 2)     
                                        TO WS-INT               
        END-IF                                                 
     END-IF                                                     
*                                                               
     INSPECT WS-NUM-VAL REPLACING ALL ' ' BY '0'         
     DISPLAY 'WS-RATE=>' WS-RATE                 


Thanks again,
Jaya.
_________________
"Great spirits have always encountered violent opposition from mediocre minds."
-Albert Einstein
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> Application Programming All times are GMT - 5 Hours
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


MVSFORUMS
Powered by phpBB © 2001, 2005 phpBB Group