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 

Want to convert Alphanumeric to Numeric for computation.

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


Joined: 25 Sep 2006
Posts: 10
Topics: 2

PostPosted: Mon May 07, 2007 6:43 pm    Post subject: Want to convert Alphanumeric to Numeric for computation. Reply with quote

Hi all,

I am Arpit Vakharia. This is my first query on MVSForums.

I want to convert a range to a sequence. In the input I am having Min and Max as two different fields and a code. Now I want to convert the range i.e. from Min to Max one seperate record for each ZIP with same code. For eg: Consider that there are three fields:
Code:

ZIP_min   ZIP_MAX      Code
100            102     25
A01            A02     26.

Now in the output I want
Code:

ZIP             Code
A01              25
A01              25
A02              25.

But my problem is that the range also contains the Alphanumeric fields.

Can any one please suggest some utility or some function to achieve the desired result?

Thanks in Advance...
Arpit Vakharia.
Back to top
View user's profile Send private message
dbzTHEdinosauer
Supermod


Joined: 20 Oct 2006
Posts: 1411
Topics: 26
Location: germany

PostPosted: Tue May 08, 2007 3:24 am    Post subject: Reply with quote

I would use a COBOL solution to answer this intellectual exercise.
Code:

01  WORK-AREA.
      05  BINARY-4-2                  PIC S9 BINARY VALUE ZERO.
      05  DISPLAY-4-2                 PIC 99.
            88  MAX-VAL-4-DISPLAY     VALUE 99.
            88  MIN-VAL-4-DISPLAY     VALUE ZERO.
01  ITEM-GEN
     REDEFINES
     WORK-AREA.
     05  FILLER                       PIC X(1).
     05  ZIP-BUILD.
          10  FIRST-CHAR              PIC X(1).
                88  MAX-ALPHA-VAL     VALUE 'Z'.
                88  MAX-NUM-VAL       VALUE '9'.
                88  MIN-ALPHA-VAL     VALUE 'A'.
                88  MIN-NUM-VAL       VALUE '0'.
          10  LAST-TWO                PIC X(2).

:::::::::::::::::

MOVE MIN-ZIP                 
  TO ZIP-BUILD                                  IN ITEM-GEN

IF  MAX-VAL-4-DISPLAY                           IN DISPLAY-4-2
THEN
    SET MIN-VAL-4-DISPLAY                       IN DISPLAY-4-2
       TO TRUE

    EVALUATE TRUE
       WHEN MAX-NUM-VAL                         IN FIRST-CHAR
            SET MIN-ALPHA-VAL                   IN FIRST-CHAR
              TO TRUE
       WHEN MAX-ALPHA-VAL                       IN FIRST-CHAR
            CONTINUE
       WHEN OTHER
           ADD 1
            TO BINARY-4-2                       IN WORK-AREA
    END-EVALUATE
ELSE
    ADD 1
       TO DISPLAY-4-2                           IN WORK-AREA
END-IF

IF  ZIP-BUILD NOT > MAX-ZIP
THEN
    MOVE ZIP-BUILD                               
      TO <reference of your choice>
ELSE
    SET ZIP-RANGE-COMPLETE  TO TRUE
END-IF


this is predicated upon
  • zips are only and always 3 char
  • first char is alpha or numeric
  • first char is in range 0-9 thru A-Z and not A-Z thru 0-9
  • last two char are always numeric in the range 00 to 99


i consider this an intellectual exercise, because I don't know of any reason to expand the ranges.
in addition, at least take the time to post your question accurately. you output example is garbage.
_________________
Dick Brenholtz
American living in Varel, Germany
Back to top
View user's profile Send private message
CICS Guy
Intermediate


Joined: 30 Apr 2007
Posts: 292
Topics: 3

PostPosted: Tue May 08, 2007 3:25 am    Post subject: Reply with quote

Arpit,
Min and max, find the middle, that I can see, but two recs in and three out makes no sense......Please explain.
Back to top
View user's profile Send private message
v_arpit
Beginner


Joined: 25 Sep 2006
Posts: 10
Topics: 2

PostPosted: Tue May 08, 2007 12:32 pm    Post subject: Reply with quote

Sory for the confusion. Let me put my question in other way, with a better example this time:
Code:

MIN ZIP      MAX ZIP     CODE
A0A0A0       A0A9Z9       454

Now in the output I want the complete range from A0A0A0 to A0A9Z9 in different row for each ZIP with the same CODE (454).

Also in the ZIP, the 1st, 3rd and 5th digits are always ALPHANUMERIC, 2nd, 4th and 6th digits are always Numeric.

Thanks,
Arpit Vakharia.
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


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

PostPosted: Tue May 08, 2007 12:54 pm    Post subject: Reply with quote

v_arpit,

Try this


Code:

//STEP0100 EXEC PGM=SORT             
//SYSOUT   DD SYSOUT=*               
//SORTIN   DD *                       
----+----1----+----2----+----3----+---
A0A0A0       A0A9Z9       454         
//SORTOUT  DD SYSOUT=*               
//SYSIN    DD *                       
  SORT FIELDS=COPY                   
  OUTFIL OUTREC=(01,02,X,27,3,/,     
                 03,02,X,27,3,/,     
                 05,02,X,27,3,/,     
                 14,02,X,27,3,/,     
                 16,02,X,27,3,/,     
                 18,02,X,27,3)       
                                     
/*


the output is:

Code:

A0 454
A0 454
A0 454
A0 454
A9 454
Z9 454


Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
Frank Yaeger
Sort Forum Moderator
Sort Forum Moderator


Joined: 02 Dec 2002
Posts: 1618
Topics: 31
Location: San Jose

PostPosted: Tue May 08, 2007 1:01 pm    Post subject: Reply with quote

Quote:
Now in the output I want the complete range from A0A0A0 to A0A9Z9 in different row for each ZIP with the same CODE (454).


It's not clear to me what you mean by the "complete range from A0A0A0 to A0A9Z9". Is the output Kolusu shows what you want? If not, please show the output records you would expect for your input record example, and explain exactly what you mean by the "range".
_________________
Frank Yaeger - DFSORT Development Team (IBM)
Specialties: JOINKEYS, FINDREP, WHEN=GROUP, ICETOOL, Symbols, Migration
DFSORT is on the Web at:
www.ibm.com/storage/dfsort
Back to top
View user's profile Send private message Send e-mail Visit poster's website
dbzTHEdinosauer
Supermod


Joined: 20 Oct 2006
Posts: 1411
Topics: 26
Location: germany

PostPosted: Tue May 08, 2007 1:44 pm    Post subject: Reply with quote

The zip codes are 6 char,
the 1st, 3rd & 5th are alpha and range A-Z
the 2nd, 4th & 6th are numeric and range 0-9

to expand a minimum zip to a maximum zip, the following carry-rules apply:

when 1st, 3rd or 5th is a Z, the next zip should have an A in the char position and 1 is 'carried' to the 2nd, 4th or 6th.

when 2nd,4th or 6 is a 9, then next zip should have a 0 in the char position and 1 is 'carried' to the 1st,3rd or 5th.

just have to change you number base (and type) for each char position.
Code:

A0A0A0
A0A0A1
A0A0A2
A0A0A3
...
A0A0A9
A0A0B0
A0A0B1
...
A0A0Z9
A0A1A0
...
A0A9Y9 
A0A9Z0
..
A0A9Z8
A0A9Z9   <<<< end of range
A0B0A0



this would be fun with cobol internal tables; have fun with sort.

range of A0A0A0 to A0A9Z9 should generate
10 X 26 X 10 or 2600 output items.
then on to the next range.

wonder how many ranges are expected to be expanded?
_________________
Dick Brenholtz
American living in Varel, Germany


Last edited by dbzTHEdinosauer on Tue May 08, 2007 1:51 pm; edited 1 time in total
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


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

PostPosted: Tue May 08, 2007 1:48 pm    Post subject: Reply with quote

Quote:

The zip codes are 6 char,
the 1st, 3rd & 5th are alpha and range A-Z
the 2nd, 4th & 6th are numeric and range 0-9

to expand a minimum zip to a maximum zip, the following carry-rules apply:

when 1st, 3rd or 5th is a Z, the next zip should have an A in the char position and 1 is 'carried' to the 2nd, 4th or 6th.

when 2nd,4th or 6 is a 9, then next zip should have a 0 in the char position and 1 is 'carried' to the 1st,3rd or 5th.


dbzTHEdinosauer,

That is interesting. hmm is this the standard algorithm for zip-codes? Rolling Eyes

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


Joined: 20 Oct 2006
Posts: 1411
Topics: 26
Location: germany

PostPosted: Tue May 08, 2007 1:59 pm    Post subject: Reply with quote

don't think there is an international standard. depends on the country. some demand that there only be alpha in a certain char pos and some mix it. original poster seemed to indicate that there is no mixing.

I've had to play with zip code look-ups within 'ranges' for calculating transportation costs to countries other than the USA with their all numeric scheme. can be a lot of fun when the range file is generated and sorted in ascii and then transmitted to the mainframe.
_________________
Dick Brenholtz
American living in Varel, Germany
Back to top
View user's profile Send private message
Frank Yaeger
Sort Forum Moderator
Sort Forum Moderator


Joined: 02 Dec 2002
Posts: 1618
Topics: 31
Location: San Jose

PostPosted: Tue May 08, 2007 2:24 pm    Post subject: Reply with quote

Arpit Vakharia,

Does your input file have only one record with MIN and MAX for which you want the range, or does your input file have multiple records with MIN and MAX for each of which you want the range?
_________________
Frank Yaeger - DFSORT Development Team (IBM)
Specialties: JOINKEYS, FINDREP, WHEN=GROUP, ICETOOL, Symbols, Migration
DFSORT is on the Web at:
www.ibm.com/storage/dfsort
Back to top
View user's profile Send private message Send e-mail Visit poster's website
v_arpit
Beginner


Joined: 25 Sep 2006
Posts: 10
Topics: 2

PostPosted: Tue May 08, 2007 5:15 pm    Post subject: Reply with quote

Frank,

My input file has multiple records (aprox. 9000).

Thanks,
Arpit Vakharia.
Back to top
View user's profile Send private message
dbzTHEdinosauer
Supermod


Joined: 20 Oct 2006
Posts: 1411
Topics: 26
Location: germany

PostPosted: Thu May 10, 2007 4:24 am    Post subject: Reply with quote

not a sort solution, but:
Code:

/* REXX                                                */
/*                                                     */
/*                                                     */
/*                                                     */
/*                                                     */
/*                                                     */
/*     remove the following three lines and remove the */
/*     comment sentinals from the ARG when this is to  */
/*     be a callable routine                           */
zip_start = 'X9Z9Z9'
zip_end   = 'Z9Z9Z9'
code_to_propagate = 453
/*                                                     */
/*  ARG(zip_start, zip_end, code_to_propagate)         */
/*                                                     */
zip_build = ''
/* */
/*  used the asc-dec equivalant of the letter 'A' to   */
/*  build the alpha.tab. since it was easier           */
/* */
DO i=1 to 26
   alpha_tab.i = D2C(C2D('A') + (i-1))
END
pgm_ctr = 0                      /* number of records generated */
/* */
/*        ctl_tab to keep track of char pos and type  */
/* */
ctl_tab.1 = 'A'       /*  alpha   for pos 1 */
ctl_tab.2 = 'N'       /*  numeric for pos 2 */
ctl_tab.3 = 'A'       /*  alpha   for pos 3 */
ctl_tab.4 = 'N'       /*  numeric for pos 4 */
ctl_tab.5 = 'A'       /*  alpha   for pos 5 */
ctl_tab.6 = 'N'       /*  numeric for pos 6  not used */
/* */
PARSE VAR zip_start 1 zip_wrk.1 +1 zip_wrk.2 +1 zip_wrk.3 +1 zip_wrk.4 +1 zip_wrk.5 +1 zip_wrk.6 +1
zip_wrk.0 = 6
zip_build = ''
DO WHILE zip_build < zip_end
   zip_wrk.6 = zip_wrk.6 + 1
   IF zip_wrk.6 > 9 THEN
      DO
         zip_wrk.6 = 0
         adder = 1
      END
   ELSE
      adder = 0
   
   DO i=5 to 1 BY -1
      SELECT
         WHEN ctl_tab.i = 'A' THEN
/*                                                         */
/*      char is alpha                                      */
/*                                                         */
            IF adder > 0 THEN
               DO
/*  instead of scaning alpha.tab to find the letter, use C2D to set */
/*  the index                                                       */
                  p = C2D(zip_wrk.i) - C2D('A') + 1
                  IF p > 25 THEN
                     DO
                        p = 1
                        adder = 1
                     END
                  ELSE
                     DO
                        p = p + 1
                        adder = 0
                     END
                  zip_wrk.i = alpha_tab.p
               END
         OTHERWISE
/*                                                              */
/*            char is numeric                                   */
/*                                                              */
            DO
               IF adder > 0 THEN
                  DO
                     zip_wrk.i = zip_wrk.i + adder
                     adder = 0
                     IF zip_wrk.i > 9 THEN
                        DO
                           zip_wrk.i = 0
                           adder = 1
                        END
                  END
            END
      END
   END
   zip_build = ''
   DO i=1 to zip_wrk.0
      zip_build = zip_build || zip_wrk.i
   END
   zip_build = zip_build || '   ' || code_to_propagate
   pgm_ctr = pgm_ctr + 1
   SAY zip_build       /*<<<<<<<<<<<<<<<<this is the place to output the record */
END
SAY pgm_ctr 'Records Generated'
EXIT
/*                 */
/*       END OF REXX                                   */

_________________
Dick Brenholtz
American living in Varel, Germany
Back to top
View user's profile Send private message
waitling
Beginner


Joined: 12 Dec 2006
Posts: 15
Topics: 3

PostPosted: Fri Jun 08, 2007 9:49 am    Post subject: Reply with quote

try the following job , hope it is not too late
assuming your input file is FB 80
Code:
                                                                                                 
//STEP0100 EXEC PGM=ICETOOL                                             
//TOOLMSG  DD  SYSOUT=*                                                 
//DFSMSG   DD  SYSOUT=*                                                 
//IN       DD  *         
----+----1----+----2----+----3                                               
A0A0Y5    A0B2Z9    453                                                 
//T1       DD      <----- TEMP FILE
//T2       DD      <----- TEMP FILE
//OUT      DD      <----- OUTPUT FILE                             
//TOOLIN   DD  *                                                       
  COPY FROM(IN) USING(CTL1)                                             
  COPY FROM(T1) USING(CTL2)                                             
  COPY FROM(T2) USING(CTL3)                                             
//CTL1CNTL DD  *                                                       
  ALTSEQ CODE=(C100,C201,C302,C403,C504,C605,C706,C807,C908,           
               D109,D210,D311,D412,D513,D614,D715,D816,D917,           
               E218,E319,E420,E521,E622,E723,E824,E925,                 
               F00C,F11C,F22C,F33C,F44C,F55C,F66C,F77C,F88C,F99C)       
  INREC  BUILD=(1,20,TRAN=ALTSEQ,21,60)                                 
  OUTREC OVERLAY=(30:1,2,PD,MUL,+260,MUL,+260,ADD,(3,2,PD,MUL,+260),   
                  ADD,5,2,PD,TO=ZD,LENGTH=8,                           
                  40:11,2,PD,MUL,+260,MUL,+260,ADD,(13,2,PD,MUL,+260), 
                  ADD,15,2,PD,TO=ZD,LENGTH=8,                           
                  50:40,8,ZD,SUB,30,8,ZD,EDIT=(TTTTTTTT))               
  OUTFIL FNAMES=T1,BUILD=(1,6,10:21,3,80:X)                             
  OUTFIL FNAMES=CTL2CNTL,                                               
         BUILD=(2X,C'OUTFIL FNAMES=T2,REPEAT=',50,8,ZD,ADD,+1,         
                EDIT=(TTTTTTTT),                                       
                C',OVERLAY=(60:SEQNUM,8,ZD,START=0)',80:X)             
//CTL2CNTL DD  DSN=&&C1,DISP=(,PASS)                                   
//CTL3CNTL DD  *                                                       
  ALTSEQ CODE=(00C1,01C2,02C3,03C4,04C5,05C6,06C7,07C8,08C9,           
               09D1,10D2,11D3,12D4,13D5,14D6,15D7,16D8,17D9,           
               18E2,19E3,20E4,21E5,22E6,23E7,24E8,25E9,                 
               0CF0,1CF1,2CF2,3CF3,4CF4,5CF5,6CF6,7CF7,8CF8,9CF9)       
  INREC IFTHEN=(WHEN=INIT,                                             
           OVERLAY=(20:60,8,ZD,MOD,+260,EDIT=(TTT),                     
                    30:(60,8,ZD,SUB,20,3,ZD),DIV,+260,EDIT=(TTTTTTTT), 
                    40:30,8,ZD,MOD,+260,EDIT=(TTT),                     
                    50:(30,8,ZD,SUB,40,3,ZD),DIV,+260,EDIT=(TTT))),     
        IFTHEN=(WHEN=NONE,                                             
           OVERLAY=(1,2,PD,ADD,50,3,ZD,TO=PD,LENGTH=2,                 
                    3,2,PD,ADD,40,3,ZD,TO=PD,LENGTH=2,                 
                    5,2,PD,ADD,20,3,ZD,TO=PD,LENGTH=2))                 
  OUTREC IFTHEN=(WHEN=(5,2,PD,GE,+260),                                 
                 OVERLAY=(3:3,2,PD,ADD,+1,TO=PD,LENGTH=2,               
                          5:5,2,PD,SUB,+260,TO=PD,LENGTH=2),HIT=NEXT), 
         IFTHEN=(WHEN=(3,2,PD,GE,+260),                                 
                 OVERLAY=(1:1,2,PD,ADD,+1,TO=PD,LENGTH=2,               
                          3:3,2,PD,SUB,+260,TO=PD,LENGTH=2))           
  OUTFIL FNAMES=OUT,BUILD=(1,9,TRAN=ALTSEQ,10,3,80:X)                   
//*                                                                                                                         
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


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

PostPosted: Fri Jun 08, 2007 10:15 am    Post subject: Reply with quote

waitling,

You generate only partial list. look at this in the same thread where DBZ explained the rules

http://www.mvsforums.com/helpboards/viewtopic.php?p=39779#39779

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


Joined: 12 Dec 2006
Posts: 15
Topics: 3

PostPosted: Fri Jun 08, 2007 11:55 pm    Post subject: Reply with quote

Hi Kolusu

yes , only partial list , between A0A0Y5 and A0B2Z9
but you can expand to the list you want , by simply changing the input file.

waitling
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 -> Utilities 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