Sunday, December 15, 2024

COBOL - Hyper-Extreme Numeric to Literal Translation Overkill

Back in March 2019 I posted a WinBatch routine that translates extremely large numeric values into it's literal English form. WinBatch - Hyper-Extreme Numeric to Literal Translation Overkill

The extremely nonsensical routine produces literal translations into the VIGINTILLIONS (I also have a more practical SQR version that is limited to Billions). Since I recently downloaded & installed OpenCobolIDE I've been having fun writing code - so why not replicate this practically useless but interesting function. 

Above: The WinBatch GUI with ridiculous Numeric-To-Literal translation.

The COBOL version will be kept much simpler - no need for a repeat of a GUI Check Interface. Just the function and a test module to produce the results.

Components:
TDFNLW.CPY - Numeric-To-Literal Working Storage CopyBook.
TDFNLP.CPY - Numeric-To-Literal Procedure CopyBook.
TDTESTNL.CBL - Test Module (Calls Function - Display Results)

TDFNLP.CPY - TDF-NL Function (Procedure)

      *****************************************************************
      *                                                               *
      *   MODULE: TDFNLP.CPY                                          *
      *   AUTHOR: TONY DELIA.                                         *
      *     DATE: 11/23/2024.                                         *
      *   SYSTEM: WINDOWS 11/OpenCobolIDE 4.7.6                       *
      *     DESC: COBOL USER FUNCTION - NUMERIC TO LITERAL.           *
      *                                                               *
      *****************************************************************
      *     NOTE: REQUIRES TDFNLW.CPY COPYBOOK (W-S SECTION).         *
      *           ALSO TDPROC.CPY/TDWORK.CPY FOR ADDL FUNCTIONS.      *
      *****************************************************************
      *                                                               *
      *  ROUTINE         DESCRIPTION                                  *
      *  --------------  -------------------------------------------- *
      *  TDF-NL          CONVERT NUMERIC VALUE TO LITERAL TEXT        *
      *                                                               *
      *****************************************************************

      *****************************************************************
      *    REVISIONS:                                                 *
      *****************************************************************
      *                                                               *
      *   DATE     PROGRAMMER      DESCRIPTION                        *
      * ---------- --------------- ---------------------------------- *
      *                                                               *
      * 11/23/2024 DELIA,TONY      ORIGINAL CODING.                   *
      *                                                               *
      *****************************************************************

      *****************************************************************
      *    TDF NL - CONVERT NUMERIC VALUE TO LITERAL TEXT             *
      *****************************************************************
      *                                                               *
      *    FIELD              I/O  DESCRIPTION                        *
      *    -----------------  ---  ---------------------------------- *
      *    TDX-NL-AMT          I   INPUT NUMERIC STRING               *
      *    TDX-NL-TEXT         O   RETURNS LITERAL TEXT CONVERSION    *
      *                                                               *
      *****************************************************************
      *                                                               *
      *    EXAMPLE:                                                   *
      *    ---------------------------------------------------------- *
      *    MOVE 789000000000093    TO TDX-NL-AMT                      *
      *    PERFORM TDF-NL                                             *
      *    DISPLAY 'TEXT: ' TDX-NL-TEXT                               *
      *    ---------------------------------------------------------- *
      *    RESULTS:                                                   *
      *    ---------------------------------------------------------- *
      *     IN: 789000000000093                                       *
      *    OUT: Seven Hundred Eighty-Nine Trillion Ninety-Three       *
      *    ---------------------------------------------------------- *
      *     IN: 72000009004000000000000                               *
      *    OUT: Seventy-Two Sextillion Nine Quadrillion Four Trillion *
      *    ---------------------------------------------------------- *
      *     IN: 123056                                                *
      *    OUT: One Hundred Twenty-Three Thousand Fifty-Six           *
      *                                                               *
      *****************************************************************

       TDF-NL.

           MOVE ZEROES TO TDX-NL-WRK
           MOVE SPACES TO TDX-NL-TEXT

           MOVE TDX-NL-AMT           TO TDX-LEN-FLD
           MOVE LENGTH OF TDX-NL-AMT TO TDX-LEN-VAL
           PERFORM TDF-LENGTH
           MOVE TDX-LEN-VAL          TO TDX-NL-LEN

           IF TDX-NL-LEN > LENGTH OF TDX-NL-WRK
              MOVE '***MAXIMUM LENGTH EXCEEDED***' TO TDX-NL-TEXT
           ELSE

           COMPUTE TDX-NL-X = 67 - TDX-NL-LEN

           MOVE TDX-NL-AMT(1:TDX-NL-LEN)
                TO TDX-NL-WRK(TDX-NL-X:TDX-NL-LEN)

           IF TDX-NL-WRK IS NOT NUMERIC
              MOVE '***INPUT NOT NUMERIC VALUE***' TO TDX-NL-TEXT
           ELSE

           MOVE 1 TO TDX-NL-POS
           MOVE 1 TO TDX-NL-LEV
           MOVE 1 TO TDX-NL-PTR

           PERFORM UNTIL TDX-NL-LEV > TDX-NL-MAX-B

             MOVE TDX-NL-WRK(TDX-NL-POS:3) TO TDX-NL-SEG

             IF  TDX-NL-SEG      <> '000'

                 IF TDX-NL-SEG-HI > 0

                    MOVE TDX-NL-LIT-A(TDX-NL-SEG-HI) TO TDX-NL-TMP
                    MOVE TDX-NL-TMP                  TO TDX-LEN-FLD
                    MOVE LENGTH OF TDX-NL-LIT-A      TO TDX-LEN-VAL
                    PERFORM TDF-LENGTH

                    ADD 1 TO TDX-LEN-VAL
                    MOVE ' Hundred' TO TDX-NL-TMP(TDX-LEN-VAL:8)
                    ADD 8 TO TDX-LEN-VAL

                    MOVE TDX-NL-TMP(1:TDX-LEN-VAL)
                      TO TDX-NL-TEXT(TDX-NL-PTR:TDX-LEN-VAL)

                    ADD TDX-LEN-VAL TO TDX-NL-PTR

                    IF TDX-NL-SEG-LO > 0
                       MOVE SPACE TO TDX-NL-TEXT(TDX-NL-PTR:1)
                    END-IF

                 END-IF

                 IF TDX-NL-SEG-LO > 20

                    DIVIDE TDX-NL-SEG-LO BY 10
                           GIVING TDX-NL-X REMAINDER TDX-NL-MOD
                    ADD 18 TO TDX-NL-X

                    MOVE TDX-NL-MOD TO TDX-NL-SEG-LO

                    MOVE TDX-NL-LIT-A(TDX-NL-X)  TO TDX-NL-TMP
                    MOVE TDX-NL-TMP              TO TDX-LEN-FLD
                    MOVE LENGTH OF TDX-NL-LIT-A  TO TDX-LEN-VAL
                    PERFORM TDF-LENGTH

                    MOVE TDX-NL-TMP(1:TDX-LEN-VAL)
                      TO TDX-NL-TEXT(TDX-NL-PTR:TDX-LEN-VAL)

                    ADD TDX-LEN-VAL TO TDX-NL-PTR

                    IF TDX-NL-SEG-LO > 0
                       MOVE '-' TO TDX-NL-TEXT(TDX-NL-PTR:1)
                       ADD 1 TO TDX-NL-PTR
                    END-IF

                 END-IF

                 IF TDX-NL-SEG-LO > 0

                    MOVE TDX-NL-LIT-A(TDX-NL-SEG-LO) TO TDX-NL-TMP
                    MOVE TDX-NL-TMP                  TO TDX-LEN-FLD
                    MOVE LENGTH OF TDX-NL-LIT-A      TO TDX-LEN-VAL
                    PERFORM TDF-LENGTH

                    MOVE TDX-NL-TMP(1:TDX-LEN-VAL)
                      TO TDX-NL-TEXT(TDX-NL-PTR:TDX-LEN-VAL)

                    ADD TDX-LEN-VAL TO TDX-NL-PTR

                    MOVE SPACE TO TDX-NL-TEXT(TDX-NL-PTR:1)
 
                 END-IF

                 MOVE TDX-NL-LIT-B(TDX-NL-LEV) TO TDX-NL-TMP
                 MOVE TDX-NL-TMP               TO TDX-LEN-FLD
                 MOVE LENGTH OF TDX-NL-LIT-B   TO TDX-LEN-VAL
                 PERFORM TDF-LENGTH

                 IF TDX-LEN-VAL > 0

                    MOVE TDX-NL-TMP(1:TDX-LEN-VAL)
                      TO TDX-NL-TEXT(TDX-NL-PTR:TDX-LEN-VAL)

                    ADD TDX-LEN-VAL TO TDX-NL-PTR

                    MOVE SPACE TO TDX-NL-TEXT(TDX-NL-PTR:1)
                    ADD  1     TO TDX-NL-PTR

                 END-IF

             END-IF

             ADD 1 TO TDX-NL-LEV
             ADD 3 TO TDX-NL-POS

           END-PERFORM

           IF TDX-NL-TEXT EQUAL SPACES
              MOVE 'Zero' TO TDX-NL-TEXT
           END-IF

           END-IF
           END-IF
           .
       TDF-NL-EXIT.
           EXIT.

      *****************************************************************
      *    END OF COPYBOOK                                            *
      *****************************************************************

TDFNLW.CPY - TDF-NL Working Storage/Variables

      *****************************************************************
      *                                                               *
      *   MODULE: TDFNLW.CPY                                          *
      *   AUTHOR: TONY DELIA.                                         *
      *     DATE: 11/23/2024.                                         *
      *   SYSTEM: WINDOWS 11/OpenCobolIDE 4.7.6                       *
      *     DESC: COBOL USER FUNCTION - NUMERIC TO LITERAL.           *
      *                                                               *
      *****************************************************************
      *     NOTE: REQUIRES TDFNLP.CPY COPYBOOK (PROCEDURE SECTION).   *
      *           ALSO TDPROC.CPY/TDWORK.CPY FOR ADDL FUNCTIONS.      *
      *****************************************************************
      *                                                               *
      *  ROUTINE         DESCRIPTION                                  *
      *  --------------  -------------------------------------------- *
      *  TDF-NL          CONVERT NUMERIC VALUE TO LITERAL TEXT        *
      *                                                               *
      *****************************************************************

      *****************************************************************
      *    REVISIONS:                                                 *
      *****************************************************************
      *                                                               *
      *   DATE     PROGRAMMER      DESCRIPTION                        *
      * ---------- --------------- ---------------------------------- *
      *                                                               *
      * 11/23/2024 DELIA,TONY      ORIGINAL CODING.                   *
      *                                                               *
      *****************************************************************

       01  TDF-NL-PARMS.
           05  TDX-NL-AMT           PIC X(70).
           05  TDX-NL-WRK           PIC X(66) VALUE ZEROES.
           05  TDX-NL-LEN           PIC 99.
           05  TDX-NL-X             PIC 99.
           05  TDX-NL-IDX           PIC 999.
           05  TDX-NL-MAX-A         PIC 999 VALUE 27.
           05  TDX-NL-MAX-B         PIC 999 VALUE 22.
           05  TDX-NL-POS           PIC 9(4).
           05  TDX-NL-LEV           PIC 99.
           05  TDX-NL-PTR           PIC 9(4).
           05  TDX-NL-MOD           PIC 99.
           05  TDX-NL-SEG.
               10  TDX-NL-SEG-HI    PIC 9.
               10  TDX-NL-SEG-LO    PIC 99.
           05  TDX-NL-TMP           PIC X(20).

           05  TDX-NL-MTX-A.
      *        Direct Indexing Literals
               10  FILLER           PIC X(10) VALUE 'One'.
               10  FILLER           PIC X(10) VALUE 'Two'.
               10  FILLER           PIC X(10) VALUE 'Three'.
               10  FILLER           PIC X(10) VALUE 'Four'.
               10  FILLER           PIC X(10) VALUE 'Five'.
               10  FILLER           PIC X(10) VALUE 'Six'.
               10  FILLER           PIC X(10) VALUE 'Seven'.
               10  FILLER           PIC X(10) VALUE 'Eight'.
               10  FILLER           PIC X(10) VALUE 'Nine'.
               10  FILLER           PIC X(10) VALUE 'Ten'.
               10  FILLER           PIC X(10) VALUE 'Eleven'.
               10  FILLER           PIC X(10) VALUE 'Twelve'.
               10  FILLER           PIC X(10) VALUE 'Thirteen'.
               10  FILLER           PIC X(10) VALUE 'Fourteen'.
               10  FILLER           PIC X(10) VALUE 'Fifteen'.
               10  FILLER           PIC X(10) VALUE 'Sixteen'.
               10  FILLER           PIC X(10) VALUE 'Seventeen'.
               10  FILLER           PIC X(10) VALUE 'Eighteen'.
               10  FILLER           PIC X(10) VALUE 'Nineteen'.
               10  FILLER           PIC X(10) VALUE 'Twenty'.
      *        Combination Indexing Literals
               10  FILLER           PIC X(10) VALUE 'Thirty'.
               10  FILLER           PIC X(10) VALUE 'Forty'.
               10  FILLER           PIC X(10) VALUE 'Fifty'.
               10  FILLER           PIC X(10) VALUE 'Sixty'.
               10  FILLER           PIC X(10) VALUE 'Seventy'.
               10  FILLER           PIC X(10) VALUE 'Eighty'.
               10  FILLER           PIC X(10) VALUE 'Ninety'.
           05  TDX-NL-MTX-X REDEFINES TDX-NL-MTX-A.
               10  TDX-NL-LIT-A     PIC X(10) OCCURS 27 TIMES.
           05  TDX-NL-MTX-B.
               10  FILLER           PIC X(20) VALUE ' Vigintillion'.
               10  FILLER           PIC X(20) VALUE ' Novemdecillion'.
               10  FILLER           PIC X(20) VALUE ' Octodecillion'.
               10  FILLER           PIC X(20) VALUE ' Septendecillion'.
               10  FILLER           PIC X(20) VALUE ' Sexdecillion'.
               10  FILLER           PIC X(20) VALUE ' Quindecillion'.
               10  FILLER           PIC X(20) VALUE ' Quatuordecillion'.
               10  FILLER           PIC X(20) VALUE ' Tredecillion'.
               10  FILLER           PIC X(20) VALUE ' Duodecillion'.
               10  FILLER           PIC X(20) VALUE ' Undecillion'.
               10  FILLER           PIC X(20) VALUE ' Decillion'.
               10  FILLER           PIC X(20) VALUE ' Nonillion'.
               10  FILLER           PIC X(20) VALUE ' Octillion'.
               10  FILLER           PIC X(20) VALUE ' Septillion'.
               10  FILLER           PIC X(20) VALUE ' Sextillion'.
               10  FILLER           PIC X(20) VALUE ' Quintillion'.
               10  FILLER           PIC X(20) VALUE ' Quadrillion'.
               10  FILLER           PIC X(20) VALUE ' Trillion'.
               10  FILLER           PIC X(20) VALUE ' Billion'.
               10  FILLER           PIC X(20) VALUE ' Million'.
               10  FILLER           PIC X(20) VALUE ' Thousand'.
               10  FILLER           PIC X(20) VALUE ' '.
           05  TDX-NL-MTX-Y REDEFINES TDX-NL-MTX-B.
               10  TDX-NL-LIT-B     PIC X(20) OCCURS 22 TIMES.
           05  TDX-NL-TEXT          PIC X(1000).

      *****************************************************************
      *    END OF COPYBOOK                                            *
      *****************************************************************

TDTESTNL.CBL - Test Module

Snippet of Working Storage - WS-TEXT will hold the initial numeric value. WS-SCALE will be displayed to illustrate the length of the numeric field and WS-BIG-NUM is a big number - the maximum accepted by the TDF-NL function.

      *****************************************************************
      *    WORKING STORAGE                                            *
      *****************************************************************

       WORKING-STORAGE SECTION.

       01  WS-TEXT                  PIC X(66).

       01  WS-SCALE.
           05  FILLER               PIC X(10) VALUE '1...5...10'.
           05  FILLER               PIC X(10) VALUE '...15...20'.
           05  FILLER               PIC X(10) VALUE '...25...30'.
           05  FILLER               PIC X(10) VALUE '...35...40'.
           05  FILLER               PIC X(10) VALUE '...45...50'.
           05  FILLER               PIC X(10) VALUE '...55...60'.
           05  FILLER               PIC X(10) VALUE '...65...70'.

       01  WS-BIG-NUM.
           05  FILLER               PIC X(15) VALUE '999999999999999'.
           05  FILLER               PIC X(15) VALUE '999999999999999'.
           05  FILLER               PIC X(15) VALUE '999999999999999'.
           05  FILLER               PIC X(15) VALUE '999999999999999'.
           05  FILLER               PIC X(6)  VALUE '999999'.

       COPY TDFNLW.

       COPY TDFWORK.

      *****************************************************************

Testing logic - some static samples are built into the TEST-NL procedure followed by an optional user entered loop. Enter any number or <ENTER> to break out.

      *****************************************************************
      *    PROCEDURE DIVISION                                         *
      *****************************************************************

       PROCEDURE DIVISION.

       MAIN-PROCEDURE.

           DISPLAY '*** STATIC TEST CASES ***'

           PERFORM TEST-NL

           DISPLAY '*** ENTER NUMBER OR <ENTER> ***'
           ACCEPT WS-TEXT

           PERFORM UNTIL WS-TEXT EQUALS SPACES

              MOVE WS-TEXT TO TDX-NL-AMT
              PERFORM TDF-NL

              DISPLAY ' '
              DISPLAY '---: ' WS-SCALE
              DISPLAY ' IN: ' TDX-NL-AMT
              DISPLAY 'OUT: ' TDX-NL-TEXT

              DISPLAY '*** ENTER NUMBER OR <ENTER> ***'
              ACCEPT WS-TEXT

           END-PERFORM

           STOP RUN.

      *****************************************************************

OUTPUT:


 Maximum Output:

---: 1...5...10...15...20...25...30...35...40...45...50...55...60...65...70

 IN: 999999999999999999999999999999999999999999999999999999999999999999

OUT: Nine Hundred Ninety-Nine Vigintillion Nine Hundred Ninety-Nine Novemdecillion Nine Hundred Ninety-Nine Octodecillion Nine Hundred Ninety-Nine Septendecillion Nine Hundred Ninety-Nine Sexdecillion Nine Hundred Ninety-Nine Quindecillion Nine Hundred Ninety-Nine Quatuordecillion Nine Hundred Ninety-Nine Tredecillion Nine Hundred Ninety-Nine Duodecillion Nine Hundred Ninety-Nine Undecillion Nine Hundred Ninety-Nine Decillion Nine Hundred Ninety-Nine Nonillion Nine Hundred Ninety-Nine Octillion Nine Hundred Ninety-Nine Septillion Nine Hundred Ninety-Nine Sextillion Nine Hundred Ninety-Nine Quintillion Nine Hundred Ninety-Nine Quadrillion Nine Hundred Ninety-Nine Trillion Nine Hundred Ninety-Nine Billion Nine Hundred Ninety-Nine Million Nine Hundred Ninety-Nine Thousand Nine Hundred Ninety-Nine

There's not much else to say about this - except to repeat it's ridiculous but also interesting & fun.


Friday, December 13, 2024

New Adventure - Function Replication in Multiple Languages/Platforms

I've always thought of developing programs, subroutines & functions as a kind of adventure. Opening a blank canvas in NotePad & mapping a course, filling in all the details, handling the twists & turns, and ultimately creating something special. This week I thought I'd set out on a short journey - taking some basic functionality I created long ago & replicating it in other languages. An ABA Routing Validation / Check Digit Calculation seemed interesting. Originally developed versions include SQR, PL/SQL & a generic Oracle/SQL Select. I set out to develop similar functionality in Assembler/370, COBOL, WinBatch, Python, Windows PowerShell and Java. Despite differences in syntax, structure & 'personalities' of each language the task was easily accomplished with all results synchronized between them.

  

ABA Routing Validation / Check Digit Calculation

The ABA Routing Number is the code used to identify a financial institution. You'll typically find the 9 digit ABA number on a personal check immediately before the account number. The first 4-digits are the Federal Reserve Routing Symbol, the next 4-digits the ABA Institution ID & the last digit is the check digit. The check digit is used to validate the ABA Routing Number & is calculated based on the first 8 digits. Each digit in order is matched & multiplied by the factors 3,7,1,3,7,1,3,7 - this means the first digit is multipled by 3, the 2nd digit by 7 and so on... each product should be accumulated into a net sum derived from all 8 digits. To determine the check digit the net sum must then be inserted into the following 'adjusted' formula:

CheckDigit = MOD(10 - MOD(NetSum, 10)), 10)

By 'Adjusted' I added an addition MOD() to encapsulate the basic formula - this is due to several computer language inconsistencies - the adjustment covers all the bases. Note, the structure of the algorithm may vary - for instance the initial NetSum Calc could multiply the values represented by digits 1+4+7 by 3, digits 2+5+8 by 7 and digits 3+6 by 1 - then add the results.

The assorted routines below will perform the calculation to determine the check digit & validate the existing check digit in the 9th position. Any input value will be rejected if it is not a 9-digit numeric value.

Assembler

Assembler is a low-level machine code instruction set. This version is for IBM MVS/370 mainframes - my favorite. Assembler is the basis for all other languages so I'll list this one first. The test program TDABA.ALC was assembled, linked & executed using the PC/370 emulator.

***********************************************************************
*        ABA CHECK DIGIT ROUTINE                                      *
***********************************************************************
         DC    F'0'                          RETURN ADDRESS SAVE AREA
ABA      EQU   *
         ST    6,*-4                         SAVE RETURN ADDRESS
*
         MVI   ABADIG,C'0'                   CLEAR CHECK DIGIT
         ZAP   ABASUM,=P'0'                  CLEAR ACCUMULATOR
*
         LA    3,8                           DIGIT COUNT
         LA    4,IABA                        ABA NUMBER ADDRESS
         LA    5,ABATAB                      FACTOR TABLE ADDRESS
ABALOOP  EQU   *
         PACK  ABANUM,0(1,4)                 PACK SINGLE DIGIT
         PACK  ABAFAC,0(1,5)                 PACK SINGLE FACTOR
         MP    ABANUM,ABAFAC                 MULTIPLY DIGIT BY FACTOR
         AP    ABASUM,ABANUM                 ACCUMULATE RESULTS
         LA    4,1(,4)                       INCREMENT NUM INDEX
         LA    5,1(,5)                       INCREMENT FAC INDEX
         BCT   3,ABALOOP                     LOOP UNTIL COMPLETE
*
         ZAP   ABADIV,ABASUM                 SET DIVISION HOLDER
         DP    ABADIV,=P'10'                 DIVIDE BY 10
         CP    ABADIV+2(2),=P'0'             REMAINDER ZERO?
         BE    *+10                          YES - CONTINUE PLEASE
         AP    ABADIV(2),=P'1'               NO  - APPLY CEILING
         ZAP   ABARND,ABADIV(2)              TRANSFER RESULT
         MP    ABARND,=P'10'                 MULTIPLY BY 10
         SP    ABARND,ABASUM                 SUBTRACT ACCUMULATOR
*
         UNPK  ABADIG,ABARND+3(1)            UNPACK CHECK DIGIT
         OI    ABADIG,X'F0'                  TURN ON ZONE BITS
ABAX     EQU   *
         L     6,ABA-4                       RESTORE LINK REGISTER
         BR    6                             BRANCH ON LINK REGISTER
***********************************************************************
ABATAB   DC    CL8'37137137'                 FACTOR TABLE
ABASUM   DC    PL4'0'                        ACCUMULATOR
ABADIV   DC    PL4'0'                        DIVISION HOLDER
ABARND   DC    PL4'0'                        ROUNDED AMOUNT
ABANUM   DC    PL2'0'                        SINGLE DIGIT                  
ABAFAC   DC    PL1'0'                        SINGLE FACTOR
ABADIG   DC    CL1' '                        CHECK DIGIT
***********************************************************************

Mainline Process - Reads file & calls the ABA Validation/Check Digit calc routine.

***********************************************************************
*        MAINLINE PROCEDURE                                           *
***********************************************************************
         PRINT NOGEN
*
         XFILI STDWKI                        OPEN INPUT  FILE
         XFILO STDWKO                        OPEN OUTPUT FILE
GETI     EQU   *
         XREAD IREC,80                       READ INPUT RECORD
         BNZ   EOFI                          EOF - EXIT ROUTINE
*
         BAL   6,PARSE                       PARSE RECORD
*
         B     GETI                          READ NEXT RECORD
EOFI     EQU   *
         B     RETURN                        EXIT PROGRAM PLEASE
***********************************************************************
         EJECT
***********************************************************************
*        PARSE RECORD                                                 *
***********************************************************************
         DC    F'0'                          RETURN ADDRESS SAVE AREA
PARSE    EQU   *
         ST    6,*-4                         SAVE RETURN ADDRESS
*
         CLI   IREC,C'*'                     COMMENT LINE?
         BE    PARSEX                        YES - EXIT ROUTINE
*
         MVC   OPRT(9),IABA                  MOVE ABA NUMBER
*
         LA    4,9                           SET FIELD LENGTH
         LA    5,IABA                        SET FIELD ADDRESS
         BAL   6,TESTNUM                     FIELD ALL NUMERIC?
         B     PARINV                        NO  - INVALID ABA
*
         BAL   6,ABA                         CHECK DIGIT ROUTINE
*
         CLC   ABADIG,IABA+8                 CHECK DIGIT MATCH?
         BNE   PARDIG                        NO  - WRITE ERROR
         MVC   OPRT+10(L'MSGVAL),MSGVAL      YES - VALID MESSAGE
         B     PAROUT                        WRITE OUTPUT RECORD
PARDIG   EQU   *
         MVC   OPRT+10(L'MSGDIG),MSGDIG      INVALID CHECK DIGIT
         MVC   OPRT+31(1),ABADIG             MOVE CHECK DIGIT
         B     PAROUT                        WRITE OUTPUT RECORD
PARINV   EQU   *
         MVC   OPRT+10(L'MSGINV),MSGINV      INVALID ABA FORMAT
PAROUT   EQU   *
         XPRNT OREC,80                       WRITE OUTPUT RECORD
         MVC   OPRT,OREC                     CLEAR OUTPUT LINE
PARSEX   EQU   *
         L     6,PARSE-4                     RESTORE LINK REGISTER
         BR    6                             BRANCH ON LINK REGISTER
***********************************************************************
         EJECT
***********************************************************************
*        NUMERIC TEST                                                 *
***********************************************************************
         CNOP  0,4                           SUBROUTINE ALLIGNMENT
TESTNUM  EQU   *
         CLI   0(5),X'F0'                    LESS THAN ZERO ???
         BL    TESTNUMX                      YES - ERROR - NOT-NUMERIC
         CLI   0(5),X'F9'                    MORE THAN NINE ???
         BH    TESTNUMX                      YES - ERROR - NOT-NUMERIC
         LA    5,1(,5)                       BUMP TO NEXT DIGIT
         BCT   4,TESTNUM                     LOOP TIL ALL DIGITS TESTED
         LA    6,4(,6)                       GOOD RETURN NEEDS +4
TESTNUMX EQU   *
         BR    6                             BRANCH ON LINK REGISTER
***********************************************************************

I created the input file C:\PC370\TDABA.TXT with the following records. It contains the ABA Routing Number and a Description. This input file will be used in some of the other language examples.

INPUT:

********* ****************************************
021272655 CITIBANK
021272650 CITIBANK *FAIL*
031201360 TDBANK
031201361 TDBANK *FAIL*
082907273 BANK OF THE OZARKS
031100908 CITIBANK -SIOUX FALLS, SD
026015079 GOLDMAN SACHS BANK USA
026015071 GOLDMAN SACHS BANK USA *FAIL*
123XYZ789 JUNK
********* ****************************************

OUTPUT:


The output is produced as expected.

COBOL

Now for some COBOL. I downloaded/installed OpenCobolIDE and was able to quickly write & test the ABA routine. I had to create some additional functions - TDF-LENGTH (Length) and TDF-RND (Rounding) - that aren't intrinsic functions in COBOL. There's a LENGTH OF operation that gives the length of the field but not the length of the data contained in the field. My Rounding function TDF-RND is for incremental rounding of any unit - in this application rounding up to the nearest increment of 10.

      *****************************************************************
      *    TDF ABA - VALIDATE ABA ROUTING NUMBER/CHECK DIGIT          *
      *****************************************************************
      *                                                               *
      *    FIELD              I/O  DESCRIPTION                        *
      *    -----------------  ---  ---------------------------------- *
      *    TDX-ABA-ROUTE       I   ABA ROUTING NUMBER                 *
      *    TDX-ABA-VALID       O   ABA VALID INDICATOR Y/N            *
      *    TDX-ABA-DIGIT       O   ABA CHECK DIGIT (CALCULATED)       *
      *                                                               *
      *****************************************************************
      *                                                               *
      *    EXAMPLE:                                                   *
      *    ---------------------------------------------------------- *
      *    MOVE 021272655          TO TDX-ABA-ROUTE                   *
      *    PERFORM TDF-ABA                                            *
      *    DISPLAY "VALID: " TDX-ABA-VALID                            *
      *    DISPLAY "DIGIT: " TDX-ABA-DIGIT                            *
      *    ---------------------------------------------------------- *
      *    RESULTS:                                                   *
      *    ---------------------------------------------------------- *
      *    TDX-ABA-ROUTE       TDX-ABA-VALID        TDX-ABA-DIGIT     *
      *    ------------------  -------------------  ----------------- *
      *    021272655           Y                    5                 *
      *    021272649           N                    2                 *
      *    031201360           Y                    0                 *
      *    031201361           N                    0                 *
      *****************************************************************

       TDF-ABA.

           MOVE SPACE TO TDX-ABA-DIGIT
           MOVE 'N'   TO TDX-ABA-VALID

           MOVE TDX-ABA-ROUTE           TO TDX-LEN-FLD
           MOVE LENGTH OF TDX-ABA-ROUTE TO TDX-LEN-VAL
           PERFORM TDF-LENGTH

           IF  TDX-LEN-VAL    = 9
           AND TDX-ABA-ROUTE IS NUMERIC

               MOVE 0      TO TDX-ABA-SUM
               MOVE 1      TO TDX-ABA-IDX

               PERFORM UNTIL  TDX-ABA-IDX > 8

                  MOVE TDX-ABA-ROUTE(TDX-ABA-IDX:1)  TO TDX-ABA-NUM
                  MOVE TDX-ABA-FACTOR(TDX-ABA-IDX:1) TO TDX-ABA-FAC

                  COMPUTE TDX-ABA-SUM = TDX-ABA-SUM
                                      + (TDX-ABA-NUM * TDX-ABA-FAC)

                  ADD 1    TO TDX-ABA-IDX

               END-PERFORM

               MOVE 'U'           TO TDX-RND-METH
               MOVE TDX-ABA-SUM   TO TDX-RND-AMT
               MOVE 10            TO TDX-RND-INC
               PERFORM TDF-RND
               MOVE TDX-RND-VAL   TO TDX-ABA-RND

               COMPUTE TDX-ABA-DIG = TDX-ABA-RND - TDX-ABA-SUM

               MOVE TDX-ABA-DIG   TO TDX-ABA-DIGIT

               IF TDX-ABA-DIGIT    = TDX-ABA-ROUTE(9:1)
                  MOVE 'Y'        TO TDX-ABA-VALID
               END-IF

           END-IF
           .
       TDF-ABA-EXIT.

           EXIT.

      *****************************************************************

Main procedure reads input file C:\PC370\TDABA.TXT and calls the TDF-ABA function for each record.

      *****************************************************************
      *    PROCEDURE DIVISION                                         *
      *****************************************************************

       PROCEDURE DIVISION.

           OPEN INPUT  I-FILE

           IF  I-STAT-OK

               PERFORM READ-INPUT UNTIL I-EOF-Y

               CLOSE I-FILE

           ELSE

               DISPLAY 'I-FILE ERROR: ' I-STAT

           END-IF

           STOP RUN.

      *****************************************************************
      *    READ INPUT FILE                                            *
      *****************************************************************

       READ-INPUT.

           READ I-FILE
              AT END
                 MOVE 'Y' TO I-EOF
              NOT AT END

                 IF I-ABA(1:1) <> "*"

                    MOVE I-ABA TO TDX-ABA-ROUTE
                    PERFORM TDF-ABA

                    DISPLAY TDX-ABA-ROUTE "."
                            I-DESC        "["
                            TDX-ABA-VALID "."
                            TDX-ABA-DIGIT "]"

                 END-IF
           END-READ

           .
       READ-INPUT-EXIT.

           EXIT.

      *****************************************************************

OUTPUT:

After pressing the OpenCOBOLIDE Run button the file is read with the results displayed.


 

SQR

SQR has been a long-time staple for PeopleSoft batch processes - despite being extremely powerful and efficient it is still one of the most underrated languages. When used properly there's nothing better for interfaces, conversions and large complex processes. This routine TDF_ABA I wrote long ago and is part of my TDF Function Library module.

!**********************************************************************
!*       Validate ABA Routing Number                                  *
!**********************************************************************
!*                                                                    *
!*        INPUT: $I_route   - ABA Routing#                            *
!*       OUTPUT: $O_digit   - Calculated Check Digit                  *
!*               $O_valid   - Valid Indicator (Y/N)                   *
!*                                                                    *
!**********************************************************************
!*                                                                    *
!*      EXAMPLE: let $I_route = '123456789'                           *
!*               do TDF_ABA($I_route, $O_digit, $O_valid)             *
!*               let $I_route = '123456706'                           *
!*               do TDF_ABA($I_route, $O_digit, $O_valid)             *
!*                                                                    *
!*      RESULTS: ABA# 123456789 is Invalid - Check Digit should be 0. *
!*               ABA# 123456706 is Valid   - Check Digit should be 6. *
!*                                                                    *
!**********************************************************************

begin-procedure TDF_ABA($I_route, :$O_digit, :$O_valid)

let $O_digit             = ''
let $O_valid             = 'N'

if  length($I_route)    <> 9
    goto TDF_ABA_Exit
end-if

let $W_route             = translate($I_route,'0123456789','0000000000')

if  $W_route            <> '000000000'
    goto TDF_ABA_Exit
end-if

let $W_factor            = '37137137'
let #W_add               = 0
let #idx                 = 1

while #idx              <= 8
    let #aba             = to_number(substr($I_route,  #idx, 1))
    let #fac             = to_number(substr($w_factor, #idx, 1))
    let #W_add           = #W_add + (#aba * #fac)
    let #idx             = #idx + 1
end-while

do TDF_RND('U', 10, #W_add, #W_up)

let $O_digit             = to_char(#W_up - #W_add)
if  $O_digit             = substr($I_route, 9, 1)
    let $O_valid         = 'Y'
end-if

TDF_ABA_Exit:

end-procedure

!**********************************************************************

 Usage notes/sample output is contained in the function comments.

WinBatch

WinBatch is a windows-based object-oriented batch automation scripting language that can be compiled as a stand-alone executable program. I've been using it since the mid-1990's for all kinds of utility programs. Here I'll create the user defined function ABA_Check and call it in the mainline logic of the program for each record read.

;**********************************************************************
;*       ABA ROUTING CHECK DIGIT CALCULATION                          *
;**********************************************************************
;*                                                                    *
;*        INPUT: I_aba      - ABA Routing Number                      *
;*       FORMAT: O_result   - Valid(Y/N)|Check Digit                  *
;*                                                                    *
;**********************************************************************

#DefineFunction ABA_Check(I_aba)

W_val             = 'N'
W_dig             = ' '

if StrLen(I_aba) == 9 && IsNumber(I_aba)

   W_tab          = '37137137'
   W_add          = 0
   idx            = 1

   while idx     <= 8
      W_aba       = StrSub(I_aba, idx, 1)
      W_fac       = StrSub(w_tab, idx, 1)
      W_add       = W_add + (W_aba * W_fac)
      idx         = idx   + 1
   endwhile

;  W_dig = mod(10 - mod(W_add,10), 10)
;  -----------------------------------
   W_mod          = W_add mod 10
   W_sub          = 10 - W_mod
   W_dig          = W_sub mod 10

   if  W_dig     == StrSub(I_aba, 9, 1)
       W_val      = 'Y'
   endif

endif

O_result          = StrCat(W_val,"|",W_dig)

Return O_result

#EndFunction

;**********************************************************************

I did find some anomolies with the WinBatch variables during arithmetic operations - namely the internal conversions between integers & floating point data types. The series of instructions above using modulus are written in a manner to avoid the issue. After some quick research I discovered this on the WinBatch Forum: WinBatch Bug (Divide as Integer)

Below is the main process that reads the input file, calls the ABA_Check() function and writes to results to the output file C:\WBT\TD_ABA.OUT.

;**********************************************************************
;*       PROCESS MAIN                                                 *
;**********************************************************************

I_file             = 'C:\PC370\TDABA.TXT'
O_file             = 'C:\WBT\TD_ABA.OUT'

if FileExist(I_file)

   I_no            = FileOpen(I_file, 'READ')
   O_no            = FileOpen(O_file, 'WRITE')

   while @TRUE

      I_rec        = FileRead(I_no)

      if I_rec    == "*EOF*"
         break
      endif

      I_id         = StrSub(I_rec,  1,  1)
      I_aba        = StrSub(I_rec,  1,  9)
      I_desc       = StrSub(I_rec, 11, 40)

      if I_id     <> '*'

         W_result  = ABA_Check(I_aba)

         X_val     = ItemExtract(1, W_result, '|')
         X_dig     = ItemExtract(2, W_result, '|')

         O_rec     = I_aba
         O_rec     = StrCat(O_rec,' Valid: %X_val% Check Digit: %X_dig%  Descr: %I_desc%')
         FileWrite(O_no, O_rec)

      endif
 
   endwhile

   FileClose(I_no)
   FileClose(O_no)

endif

Exit

;**********************************************************************

The expected results are produced for each record.

OUTPUT:

Oracle/SQL

Here's a quick version that runs in SQL*Plus, TOAD, SQL*Developer, etc. Just a simple Oracle SQL Select statement that reads a custom table that contains the ABA Routing Number (BNK_ID_NBR) and validates it - plus calculates what the check digit should be.  If the ABA# does not have a matching check digit an Error Message is produced.

/* ***************************************************************** */
/* *    VALIDATE ABA ROUTING# / CALCULATE CHECK DIGIT              * */
/* ***************************************************************** */

select a.bnk_id_nbr,
       mod(10 -
         mod((to_number(substr(a.bnk_id_nbr,1,1)) * 3)
           + (to_number(substr(a.bnk_id_nbr,2,1)) * 7)
           + (to_number(substr(a.bnk_id_nbr,3,1)) * 1)
           + (to_number(substr(a.bnk_id_nbr,4,1)) * 3)
           + (to_number(substr(a.bnk_id_nbr,5,1)) * 7)
           + (to_number(substr(a.bnk_id_nbr,6,1)) * 1)
           + (to_number(substr(a.bnk_id_nbr,7,1)) * 3)
           + (to_number(substr(a.bnk_id_nbr,8,1)) * 7),
             10),10)                 DIG_CALC,
       decode(a.chk_dig,
          to_char(mod(10
       - mod((to_number(substr(a.bnk_id_nbr,1,1)) * 3)
           + (to_number(substr(a.bnk_id_nbr,2,1)) * 7)
           + (to_number(substr(a.bnk_id_nbr,3,1)) * 1)
           + (to_number(substr(a.bnk_id_nbr,4,1)) * 3)
           + (to_number(substr(a.bnk_id_nbr,5,1)) * 7)
           + (to_number(substr(a.bnk_id_nbr,6,1)) * 1)
           + (to_number(substr(a.bnk_id_nbr,7,1)) * 3)
           + (to_number(substr(a.bnk_id_nbr,8,1)) * 7),
             10),10)),'*','*ERROR*') RESULT
  from ps_xx_vndr_car_cds         a
 where a.bnk_id_nbr            <> ' '
   and length(a.bnk_id_nbr)     = 9
   and translate(a.bnk_id_nbr,'0123456789','0000000000') = '000000000';

/* ***************************************************************** */

The SELECT filters out any values that are blank, length not equal 9 and is not numeric.

Python

I downloaded/installed Python and quickly produced the tdfABA routine and tested it successfully.

#**********************************************************************
#*       ABA ROUTING CHECK DIGIT CALCULATION                          *
#**********************************************************************
#*                                                                    *
#*        INPUT: iABA        - ABA Routing Number                     *
#*       OUTPUT: oResult     - Valid(Y/N)|Check Digit                 *
#*                                                                    *
#**********************************************************************

def tdfABA(iABA):

   wTbl          = "37137137"
   wFac          = 0
   wVal          = 0
   wAdd          = 0

   oResult       = "N" + "|" + " "

   if (iABA.isnumeric() and len(iABA) == 9):

      wIdx       = 0

      while wIdx < 8:
         wVal    = int(iABA[wIdx])
         wFac    = int(wTbl[wIdx])
         wAdd    = wAdd + (wVal * wFac)
         wIdx   += 1

      wDig       = (10 - (wAdd % 10)) % 10

      oResult    = "N" + "|" + str(wDig)

      if wDig   == int(iABA[8]):
         oResult = "Y" + "|" + str(wDig)

   return oResult

#**********************************************************************

The same input file was used again in the mainline logic.

#**********************************************************************
#*       PROCESS MAIN                                                 *
#**********************************************************************

iFile            = "C:/PC370/TDABA.TXT"
iNo              = open(iFile,"r")

for rec in iNo.readlines():
  if rec[0]     == "*":
     continue
  data           = rec.split()
  iABA           = data[0]
  iDesc          = rec[10:].rstrip()
  oResult        = tdfABA(iABA)

  print(oResult + " " + iABA + " " + iDesc)

iNo.close()

#**********************************************************************

Once again, the expected results were achieved.

OUTPUT:


Windows PowerShell

Next up is Windows PowerShell. I've used this before loading nVision ReportBook output to SharePoint folders or assigning employees to SharePoint Security groups depending on their attributes from PeopleSoft HCM. Here it's very similar to the other languages with the exception of some odd syntax variations.

#**********************************************************************
#*       ABA ROUTING CHECK DIGIT CALCULATION                          *
#**********************************************************************
#*                                                                    *
#*        INPUT: $I_aba      - ABA Routing Number                     *
#*       OUTPUT: $O_result   - Valid(Y/N)|Check Digit                 *
#*                                                                    *
#**********************************************************************

function TDF-ABA {

   param([string]$I_aba)

   [int]$W_add         = 0
   [int]$W_val         = 0
   [int]$W_fac         = 0
   [int]$W_idx         = 0
   [int]$W_dig         = 0

   $W_tbl              = '37137137'

   $W_len              = $I_aba.length

   $O_result           = 'N' + '|'

   if ($W_len -eq 9)
   {
      $X_aba           = $I_aba -replace '\d', '0'
 
       if ($X_aba -eq '000000000')
       {
          while ($W_idx -le 7)
          {
             $W_val    = $I_aba.Substring($W_idx,1)
             $W_fac    = $W_tbl.Substring($W_idx,1)
             $W_add    = $W_add + ($W_val * $W_fac)
             $W_idx    = $W_idx + 1
          }

          $W_dig       = (10 - ($W_add % 10)) % 10

          $O_val       = 'N'

          if  ($W_dig -eq $I_aba.Substring(8,1))
          {
              $O_val   = 'Y'
          }

          $O_result    = $O_val + '|' + $W_dig

       }

   }

   return $O_result

}

#**********************************************************************

The main process reads the file, performs the validation function TDF-ABA and writes the results to an output file.

#**********************************************************************
#*       PROCESS MAIN                                                 *
#**********************************************************************

$I_file                = 'c:\PC370\TDABA.TXT'
$O_file                = 'c:\temp\TDABA_PS.TXT'

Clear-Content $O_file

$I_no                  = Get-Content $I_file

foreach ($rec in $I_no)
{
  $I_aba               = $rec.split(' ')[0]
  $I_desc              = $rec.split(' ')[1]

  $I_id                = $I_aba.Substring(0,1)

  if ($I_id -ne '*')
  {

     $W_val            = TDF-ABA $I_aba

     $O_rec            = $rec.PadRight(53,' ') + '[' + $W_val + ']'

     Add-Content $O_file -value $O_rec

  }

 }

#**********************************************************************
#*    END OF PROGRAM                                                  *
#**********************************************************************

Expected results produced once again.

OUTPUT:


PL/SQL

PL/SQL is excellent for writing PeopleSoft functions that can be used by external systems (such as Content Server and OnBase) as well as PeopleSoft itself (PeopleCode, SQR, Etc.).

/* ***************************************************************** */
/* *   TDF_aba   - Return NULL when VALID                          * */
/* ***************************************************************** */
/* *                                                               * */
/* *      INPUT: I_aba - ABA Routing#                              * */
/* *     OUTPUT: O_tgt - NULL - Valid ABA/Check Digit Combo        * */
/* *                     Calculated Check Digit - INVALID ABA      * */
/* *                     X - INVALID ABA FORMAT (Length/Numeric)   * */
/* *                                                               * */
/* * *************************************************************** */

create or replace function TDF_aba(I_aba in varchar2)

return varchar2
is

   W_aba                           varchar2(50)  := ' ';
   W_dig                           varchar2(1)   := ' ';
   W_fac                           number        := 0;
   W_val                           number        := 0;
   W_idx                           number        := 0;
   W_add                           number        := 0;

   O_tgt                           varchar2(10)  := ' ';

BEGIN

   O_tgt             := 'X';

   if length(I_aba)   = 9 then

      W_aba          := translate(I_aba,'0123456789','0000000000');

      if w_aba        = '000000000' then

         W_add       := 0;
         W_idx       := 1;

         while W_idx <= 8
         loop
            W_val    := to_number(substr(I_aba,      W_idx, 1));
            W_fac    := to_number(substr('37137137', W_idx, 1));
            W_add    := W_add + (W_val * W_fac);
            W_idx    := W_idx + 1;
         end loop;

         W_dig       := to_char((10 * ceil(W_add / 10)) - W_add);

         O_tgt       := null;

         if W_dig    <> substr(I_aba, 9, 1) then
            O_tgt    := W_dig;
         end if;

      end if;

   end if;

   return O_tgt;

END;
/
/* * *************************************************************** */
/* *   END OF PL/SQL FUNCTION                                      * */
/* ***************************************************************** */

As per all other languages this produces the expected result. In this particular case a valid condition returns null, invalid format returns 'X' and invalid check digit returns the calculated check digit.

JAVA

Of course, a JAVA rendition needs to be included.

/* ***************************************************************** */
/* *                                                               * */
/* *   ABA Routing Check Digit Calculation                         * */
/* *                                                               * */
/* ***************************************************************** */
/* *                                                               * */
/* *      INPUT: iABA        - ABA Routing Number                  * */
/* *     OUTPUT: oResult     - Valid(Y/N)|Check Digit              * */
/* *                                                               * */
/* ***************************************************************** */

  public static String TDF_ABA(String iABA)
  {
 
    String wTbl       = "37137137";
    String wABA       = iABA;
    int    wLen       = 0;
    String wVal1;
    String wVal2;
    int    wInt1      = 0;
    int    wInt2      = 0;
    int    wIdx       = 0;
    int    wAdd       = 0;
    int    wDig       = 0;

    wLen              = wABA.length();
 
    String oResult    = "N" + "|" + " ";

    if (wLen         == 9 && isInteger(wABA))
    {
       wAdd           = 0;
       wIdx           = 0;

       while (wIdx    < 8)
       {
          wVal1       = wABA.substring(wIdx, wIdx+1);
          wVal2       = wTbl.substring(wIdx, wIdx+1);

          wInt1       = Integer.valueOf(wVal1);
          wInt2       = Integer.valueOf(wVal2);

          wAdd        = wAdd + (wInt1 * wInt2);

          wIdx++;
       }

       wDig           = (10 - (wAdd % 10)) % 10;

       wVal1          = wABA.substring(wIdx, wIdx+1);
       wInt1          = Integer.valueOf(wVal1);

       oResult        = "N" + "|";

       if (wDig      == wInt1)
       {
          oResult     = "Y" + "|";
       }

       oResult        = oResult + wDig;               
    }

    return oResult;
    
  }

/* ***************************************************************** */
/* *                                                               * */
/* *   Determine if String is an Integer (True/False)              * *
/* *                                                               * */
/* ***************************************************************** */

    public static boolean isInteger(String iStr)
    {
        return iStr != null && iStr.matches("[0-9]+");
    }

/* ***************************************************************** */

One more time - main logic reads the input file, performs the function (TDF_ABA) and prints the results.

/* ***************************************************************** */
/* *                                                               * */
/* *    MODULE: TD_ABA.java                                        * */
/* *    AUTHOR: TONY DELIA.                                        * */
/* *      DATE: 12/05/2024.                                        * */
/* *      DESC: ABA ROUTING VALIDATION/CHECK DIGIT.                * */
/* *                                                               * */
/* ***************************************************************** */

/* ***************************************************************** */
/* *   REVISIONS:                                                  * */
/* ***************************************************************** */
/* *                                                               * */
/* *   DATE     PROGRAMMER      DESCRIPTION                        * */
/* * ---------- --------------- ---------------------------------- * */
/* *                                                               * */
/* * 12/05/2024 DELIA,TONY      ORIGINAL CODING.                   * */
/* *                                                               * */
/* ***************************************************************** */

import java.io.File;
import java.io.FileNotFoundException;
import java.util.Scanner;

public class TD_ABA
{
  public static void main(String[] args)
  {
    String wABA;
    String wResult;

    try
    {
       String  iFile     = "C:\\PC370\\TDABA.TXT";
       File    iNo       = new File(iFile);
       Scanner iScan     = new Scanner(iNo);

       while (iScan.hasNextLine())
       {
          String iRec    = iScan.nextLine();
          String iInd    = iRec.substring(0,1);

          if (!iInd.equals("*"))
          {
             wABA        = iRec.substring(0,9);
             wResult     = TDF_ABA(wABA);
             System.out.println(" Result: " + wResult + " ABA: " + iRec);
          }
       }
    }
    catch (FileNotFoundException e)
    {
       System.out.println("Input File Error");
       e.printStackTrace();
    }

  }

/* ***************************************************************** */

OUTPUT:

Output in all cases matches perfectly - as expected.

This was fun...