Announcement

Collapse
No announcement yet.

Convert Figures to Words

Collapse
X
 
  • Filter
  • Time
  • Show
Clear All
new posts

  • Convert Figures to Words

    I believe that some time ago I saw some source
    code for converting figures to Words, as on a
    cheque.
    For example, $101.25 would be converted to
    One Hundred and One Dollars and Twenty-Five Cents.
    Help would be appreciated.
    Brian.

    Brian.

  • #2
    Try this..

    Yes there are ways to code this with functions, less GOTO's and GOSUBS's, but
    it works.. Came from the old HEATH/ZENITH REMARK magazine in the PD in 1985,
    I think.. Article called "Million Dollar Check Writer", if my memory is
    correct..

    The curious DEF SEG statements before and after the WIDTH LPRINT 132
    statement May not be valuable to you nor needed. We work in OS/2's DOS-VDM
    sessions and with QEMM 7.4 or later in V 6.22 of DOS. As part of our
    hard-won experience with PB 3.5 here and greater than 10,000 line programs,
    we have isolated some things which block memory corruption for us.. in large
    multi-segmented programs. We have discovered that, in the case of programs
    with the WIDTH statement which is LPRINT related, we can dispose of the
    corruption by simply bracketing that statement with a DEF SEG statement.
    Removing it on either side of the statement pops us right back into the
    corruption mode..

    Bob Zale may, again, say it isn't so, but it looks to an outsider that,
    somehow, in memory models in which the parallel port I/O is involved, and
    you, at the top of the program, define WIDTH LPRINT, where the pre-emptive
    OP system or the memory manager may "stick" the I/O locations for that I/O
    elsewhere for it's intercepted purposes, troubles may arise. I speculate
    that, at the time this function of PB is used at the head of the main
    program PB 3.5 knows where to find that location. I don't pose to be an
    expert at any of this.

    However, just like doing direct screen writes, it might be that one could,
    in theory, perhaps, jump to some location to do 'advanced' parallel port
    I/O. Perhaps PB 3.5 is using something like a "direct" printer write,
    like it is possible to use "direct" screen writes as a method for making
    printing faster, like you can do for screen I/O. Then somehow, for
    whatever reason the DOS (Disk Operating System - not DOS .. in a Gatesian
    sense) does some other manipulation of the LPRINT OBJECT, leaving the whole
    access to the LPRINT OBJECT in a state which isn't quite what PB thinks it
    should be. Then ..

    Later on, in another segment of your source, this only happens in LARGE
    multi-segmented programs, if you call for the LPRINT statement, it seems
    not to be in memory where it was remembered to be, somehow, by PB.. That
    I speculate, may lead to overlay of what is now something else at that
    points to the old location in memory. Yes, I can see where this can be
    related to either DOS (As we 'defined' it earlier above), or an expanded
    memory manager, or a 32 bit memory extender or whatever. Yes, I also
    can easily believe that even after a thousand hours of trying to find one
    like this, it still resists solution.

    Believe me, I understand!

    We actually found this DEF SEG bracketed WIDTH LPRINT "fix" inside this
    exact "Million Dollar Check Writer" snip, by wierd coincidence! The
    corruption suddenly appeared at the subroutine 12990 below. O7% was
    set - the LPRINT statement, for a "ONE" dollar check printed the word
    "ONE", then the code corrupted as it tried to print "DOLLAR".. !

    We, in this case, have been sampling stack residual size at several places
    inside the program and screen displaying it for observation. It never is
    below 1000 bytes or so. Further, adding stack space seems not to cure
    the problem. True it may be corrupting, but, at least, it seems that it
    has enough space.

    Addition of just ONE line of new source code, with any new variable, just
    ABOVE that line, of course, moves the error off center, such as adding a
    new string variable never before seen in the program. However, one stunt
    which has proven to shove an error like this elsewhere, is to add DEF SEG
    statement, or to simply break the program up with a $SEGMENT statement.
    In that it is impossible to find this error, at least has been for us even
    with what has been furnished as ideas, since the addition of ANY other code
    to do this simply moves the error away, there is yet one other trick we
    might use to, perhaps isolate it.

    We moved the DEF SEG statement UPWARDS in the code back toward the beginning.
    We marched it all the way back to the WIDTH LPRINT statement which already
    had a DEF SEG standardizing statement AHEAD of it. The corruption vanished
    on moving it all the way back to there. If on the other hand, with now two
    of these curious DEF SEG statments bracketing the WIDTH LPRINT statement,
    we removed either the DEF SEG statement AHEAD of the WIDTH LPRINT statement,
    or the trailing DEF SEG statement, poof - it blows up.

    Similarly, if we remove the WIDTH LPRINT statement and either or both of the
    DEF SEG statements - no corruption.

    We *HAVE* furnished code to PB that illustrates a start at where one might
    go to find these things I and a few others here have reported seeing. The
    TEST5 suite furnished to Bob Zale does, in fact, have a WIDTH LPRINT 132
    statement in the 100 lines of main source out of about 6000 lines of source
    and included librrary code that illustrates a starting point to where one
    might find all this that we have seen fail on some 8 systems, including
    DOS 6.20 and QEMM, as well as WIN-95 and WIN-98 boxes, yet curiously, does
    not fail on one OS/2 DOS-VDM box for the TEST5 suite we furnished. It was
    durnished BEFORE we found this latest Curious George but if source insite.

    I toss this out to you in that it is impossible to print some variants of a
    million dollar check. without using a line printer with of about 132 bytes!!
    You will need to use the WIDTH LPRINT statement to set your program to print
    these checks after you get things working.

    We've not seen any of three of our executables that use this code snip, all
    of which are in the 340K executable size range and over 15,000 line source
    size, fail, in this curious mode, since adding the pair of curious DEF SEG
    calls into them... Further, we, obviously, found it in only one of them.
    We, purely out of caution, bracketed all of the WIDTH LPRINT statements in
    some 40 executables or so that had them, blowing two line of source code
    space in the process, what seemed a cheap ounce of 'prevention' ??



    Your Mileage May Vary as of course, as yet may ours too in the future, over
    all this, but I can't toss code out there in he Forum which I have seen fail
    this way, in fairness, without telling you what we found that would, somehow,
    get the problem out of the way so we could go forward with the work...

    It's funny you you should have posted a request for an exact source block
    where we hit the WIDTH LPRINT statement deal. The error is an error that,
    apparently, is oblique.. I post what I have seen ..

    Code:
        DEF SEG '                                   Reset before init
        WIDTH LPRINT 132 '                          Set lprint max
        DEF SEG '                                   Reset after init
    
        G2$ = "$#########.##" '                     Screen format
        DATA ONE,TWO,THREE,FOUR,FIVE,SIX,SEVEN,EIGHT,NINE,TEN,ELEVEN,TWELVE
        DATA THIRTEEN,FOURTEEN,FIFTEEN,SIXTEEN,SEVENTEEN,EIGHTEEN,NINETEEN
        DATA TWENTY,THIRTY,FORTY,FIFTY,SIXTY,SEVENTY,EIGHTY,NINETY
    
    12585 ' 'QB# ' is ck amt. O7% = 1 toggles printer '     Checkwriter routine
             IF O7% = 1 THEN '                      Written check
                LPRINT TAB(6); "***";
             END IF
             IF QB# <= 0 THEN '                     No amount or neg - no check
                GOTO 13525
             END IF
          QG# = QB#
          QN1# = INT(QG#)
             IF QN1# > 999999! THEN
                GOTO 13525
             END IF
             IF QN1# = 0 THEN
                GOTO 12885
             END IF
             IF QN1# <= 99999! THEN
                QN1# = INT(QG# / 1000)
                GOTO 12800
             END IF
          C8% = INT(QN1# / 100000!)
          RESTORE
             FOR X% = 1 TO C8%
                READ X0$
             NEXT X%
             IF O7% = 0 THEN
                PRINT X0$; " HDRD ";
             ELSE
                LPRINT X0$; " HUNDRED ";
             END IF
          QM0% = QG# - C8% * 100000!
             IF QM0% = 0 THEN
                IF O7% = 0 THEN
                   PRINT "THND DOL*";
                ELSE
                   LPRINT "THOUSAND DOLLARS*** ";
                END IF
                GOTO 13235
             END IF
          QG# = QM0%
          QN1# = INT(QG# / 1000)
    12800    IF QN1# = 0 AND ABS(QA#) > 1000 THEN
                IF O7% = 0 THEN
                   PRINT "THND ";
                ELSE
                   LPRINT "THND ";
                END IF
             END IF
             IF QN1# <> 0 THEN
                GOSUB 13295
                IF O7% = 0 THEN
                   PRINT "THND ";
                ELSE
                   LPRINT "THOUSAND ";
                END IF
                BH% = 1000
                BI% = 1000
             END IF
    12885 QG# = QG# - QN1# * 1000
          QN1# = INT(QG# / 100)
             IF QN1# <> 0 THEN
                GOSUB 13295
                IF O7% = 0 THEN
                   PRINT "HDRD ";
                ELSE
                   LPRINT "HUNDRED ";
                END IF
                BH% = 1000
                BI% = 1000
             END IF
          QG# = QG# - QN1# * 100
          QN1# = INT(QG#)
             IF QN1# = 0 THEN
                IF QB# >= 1 THEN
                   GOTO 12990
                END IF
                GOTO 13055
             END IF
          GOSUB 13295
    12990    IF X0$ = "ONE" AND BH% = 0 THEN
                IF O7% = 0 THEN
                   PRINT "DLR";
                ELSE
                   LPRINT "DOLLAR";
                END IF
             ELSE
                IF O7% = 0 THEN
                   PRINT "DLRS";
                ELSE
                   LPRINT "DOLLARS";
                END IF
             END IF
    13055 QG# = QG# - QN1#
             IF QG# * 100 < .95 THEN
                IF O7% = 1 THEN
                   LPRINT "***";
                END IF
                GOTO 13205
             END IF
    13090    IF QB# >= 1 THEN
                IF O7% = 0 THEN
                   PRINT " AND";
                ELSE
                   LPRINT " AND";
                END IF
             END IF
          QG# = QG# * 100
             IF BI% = 1000 THEN
                QG# = INT(QG# + .5)
                IF O7% = 0 THEN
                   PRINT QG#; "CTS";
                ELSE
                  LPRINT QG#; "CENTS***";
                END IF
                GOTO 13205
             END IF
          QG# = INT(QG# * 10 + .5) / 10
             IF O7% = 0 THEN
                PRINT QG#; "CTS";
             ELSE
                LPRINT QG#; "CENTS***";
             END IF
    13205 BH% = 0
             IF O7% = 1 THEN
                GOSUB 13260
                LPRINT TAB(60); DX$; TAB(76); USING G2$; QB#
             END IF
          RETURN
    13235    IF O7% = 1 THEN
                GOSUB 13260
                LPRINT TAB(60); DX$; TAB(76); USING G2$; QB#
             END IF
          RETURN
    13260    IF O7% = 1 THEN
                FOR X% = 1 TO 4
                   LPRINT
                   NEXT X%
                LPRINT TAB(16); NY$;
             END IF
          RETURN
    13295    IF QN1# < 21 THEN
                GOTO 13475
             END IF
          RESTORE
             FOR X% = 1 TO INT((QN1# - 20) / 10) + 20
                READ X0$
             NEXT X%
             IF O7% = 0 THEN
                PRINT X0$;
             ELSE
                LPRINT X0$;
             END IF
          C7% = QN1# - INT(QN1# / 10) * 10
             IF C7% = 0 THEN
                IF O7% = 0 THEN
                   PRINT " ";
                ELSE
                   LPRINT " ";
                END IF
                RETURN
             END IF
             IF O7% = 0 THEN
                PRINT "-";
             ELSE
                LPRINT "-";
             END IF
          RESTORE
             FOR X% = 1 TO C7%
                READ X0$
             NEXT X%
             IF O7% = 0 THEN
                PRINT X0$; " ";
             ELSE
                LPRINT X0$; " ";
             END IF
          RETURN
    13475 RESTORE
             FOR X% = 1 TO QN1#
                READ X0$
             NEXT X%
             IF O7% = 0 THEN
                PRINT X0$; " ";
             ELSE
                LPRINT X0$; " ";
             END IF
          RETURN
    13525    IF O7% = 0 THEN
                PRINT "******* V O I D **********";
             ELSE
                 LPRINT "******* V O I D **********"
             END IF
          GOTO 13205
    Mike Luther
    [email protected]
    Mike Luther
    [email protected]

    Comment


    • #3
      I thought I'd have a little fun by working out a routine to do this. Here is my submission.

      Ian Cairns

      Code:
      cls
      ' Input Number as String with or without dollar symbols
      amount$ = "15,301,211.21"
      CALL ConvertNumberToWords(amount$,dollars$,cents$, total$)
      PRINT "Numeric: " + amount$
      PRINT "String Dollars: " + dollars$
      PRINT "  String Cents: " + cents$
      PRINT "String Total:"
      PRINT total$
      
      '*****
      SUB ConvertNumberToWords(inAmount$, dollars$, cents$, total$)
      ' Initialize Return values
        dollars$ = ""
        cents$ = ""
        total$ = ""
      ' Create arrays to hold conversion Info (Denom$ = Denomination)
        DIM Denom$(1:3), Tens$(1:9), Ones$(1:19)
      ' Fill Arrays with Equivalent Values
        Denom$(1) = "Hundred"
        Denom$(2) = "Thousand"
        Denom$(3) = "Million"
        Ones$(1) = "One" : Ones$(2) = "Two" : Ones$(3) = "Three"
        Ones$(4) = "Four" : Ones$(5) = "Five" : Ones$(6) = "Six"
        Ones$(7) = "Seven" : Ones$(8) = "Eight" : Ones$(9) = "Nine"
        Ones$(10) = "Ten" : Ones$(11) = "Eleven" : Ones$(12) = "Twelve"
        Ones$(13) = "Thirteen" : Ones$(14) = "Fourteen" : Ones$(15) = "Fifteen"
        Ones$(16) = "Sixteen" : Ones$(17) = "Seventeen" : Ones$(18) = "Eighteen"
        Ones$(19) = "Nineteen"
        Tens$(1) = "Ten" : Tens$(2) = "Twenty" : Tens$(3) = "Thirty"
        Tens$(4) = "Forty" : Tens$(5) = "Fifty" : Tens$(6) = "Sixty"
        Tens$(7) = "Seventy" : Tens$(8) = "Eighty" : Tens$(9) = "Ninety"
      
      'Remove "$" or "," symbols
        tAmount$ = REMOVE$(inAmount$, ANY "$,")
      
      'Remove any initial leading blanks or 0's with
        tAmount$ = LTRIM$(tAmount$, ANY " 0")
      
      'Find the decimal
        dPntr% = INSTR(tAmount$,".")
      
      ' Check for a number > 999,999,999.
        IF dPntr% > 10 THEN
          PRINT "Number too large"
          EXIT SUB
        END IF
      
      ' Deal with the cents first
        IF dPntr% = 0 OR dPntr% = LEN(tAmount$) THEN
      'You might convert this to "No Cents"
          Cents$ = "0 Cents"
        ELSE
          IF VAL(MID$(tAmount$,dPntr%+1,2)) < 20 THEN
            Cents$ = Ones$(VAL(MID$(tAmount$,dPntr%+1,2)))
          ELSE
            temp$ = MID$(tAmount$,dPntr%+1,1)
            IF temp$ = "0" THEN
              Cents$ = ""
            ELSE
              Cents$ = Tens$(VAL(temp$)) + " "
            END IF
            temp$ = MID$(tAmount$,dPntr%+2,1)
            IF temp$ <> "0" THEN
              Cents$ = Cents$ + Ones$(VAL(temp$))
            END IF
          END IF
          Cents$ = Cents$ + " Cents"
        END IF
      ' Get rid of the decimal to avoid confusion
        IF dPntr% = 1 THEN
      ' No Dollar Amounts to work with!
          Dollars$ = "No Dollars"
          Total$ = Dollars$ + " and " + Cents$
        ELSE
          tAmount$ = LEFT$(tAmount$,dPntr%-1)
        END IF
      ' Get String Length
        sLen% = LEN(tAmount$)
      'Now Pad tAmount$ to the largest value of its denomination
        DO WHILE (sLen%\3) * 3 <> sLen%
          tAmount$ = "0" +tAmount$
          INCR sLen%, 1
        LOOP
      
      ' Break tAmount$ into Denomination Groupings: million/thousand/hundred
        FOR denomination% = 3 TO 1 STEP -1
          IF sLen% < 3*(denomination%-1)+1 THEN ITERATE FOR
          hFlag% = 0  ' flag for AND to be added after "Hundreds"
      ' pad words with spaces as required
          IF LEN(dollars$) AND RIGHT$(dollars$,1)<> " " THEN _
             dollars$ = dollars$ + " "
          group$ = MID$(tAmount$,sLen%-denomination%*3+1,3)
      ' digit 1
          digit$ = LEFT$(group$,1)
          IF digit$ <> "0" THEN
            dollars$ = dollars$ + Ones$(VAL(digit$)) + " Hundred"
            hFlag% = 1
          END IF
      ' digit 2
      ' check for digits 1&2 < 20
          IF VAL(MID$(group$,2))<20 THEN
            IF hFlag% = 1 THEN dollars$ = dollars$ + " and " : hFlag% = -1
            dollars$ = dollars$ + Ones$(VAL(MID$(group$,2)))
          ELSE
            digit$ = MID$(group$,2,1)
            IF digit$ <> "0" THEN
              IF hFlag% = 1 THEN dollars$ = dollars$ + " and " : hFlag% = -1
              dollars$ = dollars$ + Tens$(VAL(digit$))
            END IF
      ' digit 3
            digit$ = RIGHT$(group$,1)
            IF digit$ <> "0" THEN
              IF RIGHT$(dollars$,1) = " " THEN dollars$ = RTRIM$(dollars$)
              IF hFlag% = 1 THEN dollars$ = dollars$ + " and " : hFlag% = -1
              dollars$ = dollars$ + " " + Ones$(VAL(digit$))
            END IF
          END IF
          dollars$ = Dollars$ + " "
          IF denomination% <> 1 OR (denomination% = 1 AND hFlag% = 0) THEN _
            dollars$ = dollars$ + Denom$(denomination%)
        NEXT denomination%
        total$ = ""
        IF dollars$ <> "" THEN
          dollars$ = RTRIM$(dollars$) + " Dollars"
          total$ = dollars$ + " and "
        END IF
        total$ = total$ + Cents$
      
      END SUB
      '*****
      :) IRC :)

      Comment


      • #4
        Mike and Ian,

        Thank you both for your help and the trouble
        you have taken.

        Regards,
        Brian.

        Brian.

        Comment


        • #5
          "For example, $101.25 would be converted to
          One Hundred and One Dollars and Twenty-Five Cents."

          No, it should be converted to "One Hundred One Dollars and twenty-five cents."


          There is no "and" between "one hundred" and "one."

          (Unless you are gramatically challenged or a product of the Chicago Public Schools, that is).

          MCM

          Michael Mattias
          Tal Systems (retired)
          Port Washington WI USA
          [email protected]
          http://www.talsystems.com

          Comment


          • #6
            I would like to apologize for an error in my code.

            Insert the indicated line in the proper place in the denomination loop for correct results.
            Michael is correct (Thanks Michael) in pointing out the additional grammatical error.

            Sorry, Ian

            Code:
              FOR denomination% = 3 TO 1 STEP -1
                IF sLen% < 3*(denomination%-1)+1 THEN ITERATE FOR
                hFlag% = 0  ' flag for AND to be added after "Hundreds"
            ' pad words with spaces as required
                IF LEN(dollars$) AND RIGHT$(dollars$,1)<> " " THEN _
                   dollars$ = dollars$ + " "
                group$ = MID$(tAmount$,sLen%-denomination%*3+1,3)
            ' *** Check for Zero Values
                IF VAL(group$)<1 THEN ITERATE FOR
            ' *** Insert the line above for proper operation!
            ' digit 1
            :) IRC :)

            Comment


            • #7
              In reply to Michael Mattias' comment:

              "For example, $101.25 would be converted to
              One Hundred and One Dollars and Twenty-Five Cents."
              No, it should be converted to "One Hundred
              One Dollars and twenty-five cents."
              There is no "and" between "one hundred" and "one."
              (Unless you are gramatically challenged or
              a product of the Chicago Public Schools, that is).

              Michael, I can assure you I am not a product
              of a Chicago Public School. Here in Australia
              we have a fairly good grasp of the English language.
              I respectfully refer you to Henry Higgins' recitation
              in My Fair Lady, referring to the useage of the
              English language, he says: "Why, in America
              they haven't used it for years."

              Regards,
              Brian Reynolds,
              Longreach,
              Outback Queensland,
              Australia.


              Brian.

              Comment


              • #8
                Well that's a very interesting problem. A few years ago I wrote a program that solves this problem, but too bad it is in portuguese (what can I do) but the principle is always the same:

                Any number can n\be written with a combination of 3 digit numbers with the respective "separators" :
                1233 -> <One> thousand <two hundred and twenty three>

                I checked the program for grammar errors but I couldn't find any mistake, even though portuguese is grammar is much more difficult than english.

                If anyone is interested, the source code is in the source code area

                Comment


                • #9
                  Dear Ian,


                  I tried using your code in one of my programs however,

                  When amount$ contains a .00 (zero cents), the program crashes.
                  If amount$ contains a huge number, it is converted perfectly into words, but if amount$ contains something like "23" (Twenty Three Dollars), the result is (Twenty Three Hundred Dollars) - couldn't figure out why.
                  One of the lines read INCR slen%,1 - I guess this should be INCR slen% since I got a syntax error while compiling (I hope this is not the reason why the "hundred" is being printed)

                  Thankyou for whatever help you may provide.

                  Daniel


                  ------------------
                  mailto:[email protected][email protected]</A>
                  mailto:[email protected][email protected]</A>

                  Comment


                  • #10
                    Like to add a recitation of G.B. Shaw:
                    "The only thing that parts them (he ment: English and Americans) is the language."

                    ------------------
                    mailto:[email protected][email protected]</A>
                    www.basicguru.com/zijlema/

                    Egbert Zijlema, journalist and programmer (zijlema at basicguru dot eu)
                    http://zijlema.basicguru.eu
                    *** Opinions expressed here are not necessarily untrue ***

                    Comment


                    • #11
                      The amended sub for convertwordstofigures is posted below

                      SUB ConvertNumberToWords(inAmount$, dollars$, cents$, total$)
                      ' Initialize Return values
                      dollars$ = ""
                      cents$ = ""
                      total$ = ""
                      ' Create arrays to hold conversion Info (Denom$ = Denomination)
                      DIM Denom$(1:3), Tens$(1:9), Ones$(0:19)
                      ' Fill Arrays with Equivalent Values
                      Denom$(1) = "Hundred"
                      Denom$(2) = "Thousand"
                      Denom$(3) = "Million"
                      Ones$(0) = "Zero"
                      Ones$(1) = "One" : Ones$(2) = "Two" : Ones$(3) = "Three"
                      Ones$(4) = "Four" : Ones$(5) = "Five" : Ones$(6) = "Six"
                      Ones$(7) = "Seven" : Ones$(8) = "Eight" : Ones$(9) = "Nine"
                      Ones$(10) = "Ten" : Ones$(11) = "Eleven" : Ones$(12) = "Twelve"
                      Ones$(13) = "Thirteen" : Ones$(14) = "Fourteen" : Ones$(15) = "Fifteen"
                      Ones$(16) = "Sixteen" : Ones$(17) = "Seventeen" : Ones$(18) = "Eighteen"
                      Ones$(19) = "Nineteen"
                      Tens$(1) = "Ten" : Tens$(2) = "Twenty" : Tens$(3) = "Thirty"
                      Tens$(4) = "Forty" : Tens$(5) = "Fifty" : Tens$(6) = "Sixty"
                      Tens$(7) = "Seventy" : Tens$(8) = "Eighty" : Tens$(9) = "Ninety"

                      'Remove "$" or "," symbols
                      tAmount$ = REMOVE$(inAmount$, ANY "$,")

                      'Remove any initial leading blanks or 0's with
                      tAmount$ = LTRIM$(tAmount$, ANY " 0")

                      'Find the decimal
                      dPntr% = INSTR(tAmount$,".")

                      ' Check for a number > 999,999,999.
                      IF dPntr% > 10 THEN
                      MSGBOX "Number too large"
                      EXIT SUB
                      END IF

                      ' Deal with the cents first
                      IF dPntr% = 0 OR dPntr% = LEN(tAmount$) THEN
                      'You might convert this to "No Cents"
                      Cents$ = "No Cents"
                      ELSE
                      IF VAL(MID$(tAmount$,dPntr%+1,2)) < 20 THEN
                      Cents$ = Ones$(VAL(MID$(tAmount$,dPntr%+1,2)))
                      ELSE
                      temp$ = MID$(tAmount$,dPntr%+1,1)
                      IF temp$ = "0" THEN
                      Cents$ = ""
                      ELSE
                      Cents$ = Tens$(VAL(temp$)) + " "
                      END IF
                      temp$ = MID$(tAmount$,dPntr%+2,1)
                      IF temp$ <> "0" THEN
                      Cents$ = Cents$ + Ones$(VAL(temp$))
                      END IF
                      END IF
                      Cents$ = Cents$ + " Cents"
                      END IF
                      ' Get rid of the decimal to avoid confusion
                      IF dPntr% = 1 THEN
                      ' No Dollar Amounts to work with!
                      Dollars$ = "Zero Maltese Liri"
                      Total$ = Dollars$ + " and " + Cents$
                      ELSE
                      tAmount$ = LEFT$(tAmount$,dPntr%-1)
                      END IF
                      ' Get String Length
                      sLen% = LEN(tAmount$)
                      'Now Pad tAmount$ to the largest value of its denomination
                      DO WHILE (sLen%\3) * 3 <> sLen%
                      tAmount$ = "0" +tAmount$
                      INCR sLen%
                      ' INCR sLen%, 1
                      LOOP

                      ' Break tAmount$ into Denomination Groupings: million/thousand/hundred
                      FOR denomination% = 3 TO 1 STEP -1
                      IF sLen% < 3*(denomination%-1)+1 THEN ITERATE FOR
                      hFlag% = 2 ' flag for AND to be added after "Hundreds" ****************
                      ' pad words with spaces as required
                      IF LEN(dollars$) AND RIGHT$(dollars$,1)<> " " THEN _
                      dollars$ = dollars$ + " "
                      group$ = MID$(tAmount$,sLen%-denomination%*3+1,3)
                      ' *** Check for Zero Values
                      IF VAL(group$)<1 THEN ITERATE FOR
                      ' *** Insert the line above for proper operation!
                      ' digit 1
                      digit$ = LEFT$(group$,1)
                      IF digit$ <> "0" THEN
                      dollars$ = dollars$ + Ones$(VAL(digit$)) + " Hundred"
                      hFlag% = 1
                      END IF
                      ' digit 2
                      ' check for digits 1&2 < 20
                      IF VAL(MID$(group$,2))<20 THEN
                      IF hFlag% = 1 THEN dollars$ = dollars$ + " and " : hFlag% = -1
                      dollars$ = dollars$ + Ones$(VAL(MID$(group$,2)))
                      ELSE
                      digit$ = MID$(group$,2,1)
                      IF digit$ <> "0" THEN
                      IF hFlag% = 1 THEN dollars$ = dollars$ + " and " : hFlag% = -1
                      dollars$ = dollars$ + Tens$(VAL(digit$))
                      END IF
                      ' digit 3
                      digit$ = RIGHT$(group$,1)
                      IF digit$ <> "0" THEN
                      IF RIGHT$(dollars$,1) = " " THEN dollars$ = RTRIM$(dollars$)
                      IF hFlag% = 1 THEN dollars$ = dollars$ + " and " : hFlag% = -1
                      dollars$ = dollars$ + " " + Ones$(VAL(digit$))
                      END IF
                      END IF
                      dollars$ = Dollars$ + " "

                      IF denomination% <> 1 OR (denomination% = 1 AND hFlag% = 0) THEN _
                      dollars$ = dollars$ + Denom$(denomination%)


                      NEXT denomination%


                      total$ = ""
                      IF dollars$ <> "" THEN
                      dollars$ = RTRIM$(dollars$) + " Maltese Liri"
                      total$ = dollars$ + " and "
                      END IF
                      total$ = total$ + Cents$

                      END SUB




                      ------------------
                      mailto:d[email protected][email protected]</A>
                      mailto:[email protected][email protected]</A>

                      Comment


                      • #12
                        Like to add a recitation of G.B. Shaw:
                        "The only thing that parts them (he ment: English and Americans) is the language."
                        I once heard a variation of that: "The English and the Americans are two peoples separated by a common language."

                        (Churchill?)

                        MCM
                        Michael Mattias
                        Tal Systems (retired)
                        Port Washington WI USA
                        [email protected]
                        http://www.talsystems.com

                        Comment

                        Working...
                        X