Converting number into words in VC 9

I need to convert numbers into words. For example, I would like to convert the number 123 into “one hundred twenty three”. The range I need is 12,345,678 (twelve million three hundred forty-five thousand six hundred seventy eight). I am trying to achieve this in a coupe of ways but this is turning out more challenging than I expected. If anyone has the code to do this, I would greatly appreciate it. I am using Visual COBOL v9. on a Windows 11 Pro machine. Thanks in advance.

  • 0  

    This is so easy to program in cobol, i will see if i found any source program, we had do this for any years to fill/print checks.

    But this is today not necessary in Europe, there are no checks available!

    What do you plan?

    move the number in a variable as occurs and then pass each simple number

    Example:

    01  your-number      pic 9(13).

    01  number-string    pic x(256)

    01  i                         pic 9(02).

    01  ws-char            pic x(15).

    01  number-table.

          03  number-tab  occurs 13 pic 9(01).

    move your_number to number-table

    move ' ' to number-string

    perform varying i from 1 by 1 until i > 13

       if number-tab (i) > 0

          perform change-number-to-char

      end-if

    end-perform

    .

    change-number-to-char section.

          evaluate number-tab (i)

              when 1 move 'one' to ws-char

              when 2 move 'two' to ws-char

            when 3 move 'three' to ws-char

              when 4 move 'four' to ws-char

            when 5 move 'five' to ws-char

              when 6 move 'six' to ws-char

            when 7 move 'seven' to ws-char

              when 8 move 'eight' to ws-char

            when  move 'nine' to ws-char

         end-evaluate

         string number-string delemited by ' '

                  ' ' delimited by size

                 ws-char delimited by ' '

          into number-string

        end-string

        exit.

    this is free from my mind and must be a possible solution, test it

    cg

  • 0 in reply to   

    Greiner,

    I will try your code and let you know if I have any problems, thank you.

  • 0   in reply to 

    If you will have „Million“ and „thousand“ you Must Divide the number in three Parts and then 3 steps

  • 0  

    Here is a program that I put together that I think does what you want.

    It may not be the easiest way to do it, but it appears to work.

           identification division.
           program-id. Num2Words.
           data division.
           working-storage section.
           01  .
             05 ones-values.
                10 pic x value "1".
                10 pic x(10) value "one".
                10 pic x value "2".
                10 pic x(10) value "two".
                10 pic x value "3".
                10 pic x(10) value "three".
                10 pic x value "4".
                10 pic x(10) value "four".
                10 pic x value "5".
                10 pic x(10) value "five".
                10 pic x value "6".
                10 pic x(10) value "six".
                10 pic x value "7".
                10 pic x(10) value "seven".
                10 pic x value "8".
                10 pic x(10) value "eight".
                10 pic x value "9".
                10 pic x(10) value "nine".
             05 ones-table redefines ones-values occurs 9 times.
                10 ones-num-key pic x.
                10 ones-num-word pic x(10).
    
           01 .
              05 tens-values.
                 10 pic x     value "0".
                 10 pic x(10) value "ten".
                 10 pic x     value "1".
                 10 pic x(10) value "eleven".
                 10 pic x     value "2".
                 10 pic x(10) value "twelve".
                 10 pic x     value "3".
                 10 pic x(10) value "thirteen".
                 10 pic x     value "4".
                 10 pic x(10) value "fourteen".
                 10 pic x     value "5".
                 10 pic x(10) value "fifteen".
                 10 pic x     value "6".
                 10 pic x(10) value "sixteen".
                 10 pic x     value "7".
                 10 pic x(10) value "seventeen".
                 10 pic x     value "8".
                 10 pic x(10) value "eighteen".
                 10 pic x     value "9".
                 10 pic x(10) value "nineteen".
              05 tens-table redefines tens-values occurs 10 times.
                 10 tens-num-key pic x.
                 10 tens-num-word pic x(10).
    
           01 .
              05 tens-group-values.
                 10 pic x     value "2".
                 10 pic x(10) value "twenty".
                 10 pic x     value "3".
                 10 pic x(10) value "thirty".
                 10 pic x     value "4".
                 10 pic x(10) value "forty".
                 10 pic x     value "5".
                 10 pic x(10) value "fifty".
                 10 pic x     value "6".
                 10 pic x(10) value "sixty".
                 10 pic x     value "7".
                 10 pic x(10) value "seventy".
                 10 pic x     value "8".
                 10 pic x(10) value "eighty".
                 10 pic x     value "9".
                 10 pic x(10) value "ninety".
              05 tens-group-table redefines tens-group-values
                   occurs 8 times.
                 10 tens-group-num-key pic x.
                 10 tens-group-num-word pic x(10).
    
           01 num-sub               pic 9(3)   value zeroes.
           01 number-to-convert-raw pic 9(12)  value zeroes.
           01 number-to-convert     pic x(12)  just right.
           01 temp-area             pic x(3)   value spaces.
           01                       pic x      value "B".
              88 billions-flag                 value "B".
              88 millions-flag                 value "M".
              88 thousands-flag                value "T".
              88 hundreds-flag                 value "H".
           01 number-as-words       pic x(200) value spaces.
           01 word-pointer          pic 9(3)   value zeroes.
           procedure division.
    
               perform until exit
                  display "enter a number up to 999 billion"
                  display "enter zero to quit"
                  accept number-to-convert-raw
                  if number-to-convert-raw = zeroes
                     exit perform
                  else
                     perform 050-process-number
                     display number-as-words
                  end-if
               end-perform
               goback.
    
           050-process-number.
    
               move spaces to number-as-words
               move number-to-convert-raw to number-to-convert
               move 1 to word-pointer 
               move number-to-convert(1:3) to temp-area
               if temp-area not = zeroes
                  set billions-flag to true
                  perform 100-convert-num-to-words
               end-if
               move number-to-convert(4:3) to temp-area
               if temp-area not = zeroes
                  set millions-flag to true
                  perform 100-convert-num-to-words
               end-if
               move number-to-convert(7:3) to temp-area
               if temp-area not = zeroes
                  set thousands-flag to true
                  perform 100-convert-num-to-words
               end-if
               move number-to-convert(10:3) to temp-area
               if temp-area not = zeroes
                  set hundreds-flag to true
                  perform 100-convert-num-to-words
               end-if.
    
           100-convert-num-to-words.
    
               perform 200-convert-first-digit
               perform 205-convert-rest
               perform 210-add-group-type.
    
           200-convert-first-digit.
           
               if temp-area(1:1) not = "0"
                  perform varying num-sub from 1 by 1
                     until num-sub > 9
                     if temp-area(1:1) = ones-num-key(num-sub)
                        string ones-num-word(num-sub)
                           delimited by " "
                           " hundred " delimited by size
                           into number-as-words
                           with pointer word-pointer
                        end-string
                      end-if
                  end-perform
               end-if.
    
           205-convert-rest.
    
               if temp-area(2:1) = "1"
                   perform varying num-sub from 1 by 1
                     until num-sub > 10
                     if temp-area(3:1) = tens-num-key(num-sub)
                        string tens-num-word(num-sub)
                           delimited by " "
                           into number-as-words
                           with pointer word-pointer
                        end-string
                        exit perform
                     end-if
                   end-perform
                else
                   if temp-area(2:1) not = "0"
                      perform varying num-sub from 1 by 1
                        until num-sub > 8
                        if temp-area(2:1) = tens-group-num-key(num-sub)
                           string tens-group-num-word(num-sub)
                              delimited by " "
                              " " delimited by size
                              into number-as-words
                              with pointer word-pointer
                           end-string
                           exit perform
                        end-if
                      end-perform
                   end-if
                   if temp-area(3:1) not = "0"
                      perform varying num-sub from 1 by 1
                         until num-sub > 9
                         if temp-area(3:1) = ones-num-key(num-sub)
                            string ones-num-word(num-sub)
                               delimited by " "
                               " " delimited by size
                               into number-as-words
                               with pointer word-pointer
                            end-string
                            exit perform
                         end-if
                      end-perform
                   end-if
                end-if.
    
           210-add-group-type.
    
                evaluate true
                   when billions-flag
                      string "billion " delimited by size
                         into number-as-words
                         with pointer word-pointer
                      end-string
                   when millions-flag
                      string "million " delimited by size
                         into number-as-words
                         with pointer word-pointer
                      end-string
                   when thousands-flag
                      string "thousand " delimited by size
                         into number-as-words
                         with pointer word-pointer
                      end-string
                end-evaluate.
    
    

    Chris Glazier
    Rocket Software - Principal Technical Support Specialist
    If you found this post useful, give it a “Like” or click on "Verify Answer" under the "More" button

  • 0 in reply to   

    Thanks, Chris! I will try your code out. 

  • 0   in reply to   

    Chris: only one little error

    add following statement in 205-rest after delimited by " "

    new  " " delimited by size

    then million will be have a space before in converted text

    Super!

    my example was not complete, comes from my head and give a idea how to solve this in cobol

    But "Alex_Castro" don't not inform for what he need this!

    For long time we need this for cheques, but today there are not more in use!

  • 0   in reply to   

    Chris, how/why is it possible to keyin more then 12 digits for your field "number-to-convert-raw pic 9(12)  value zeroes"

    i can key 30 or more digits for this value! Bug or features?

  • 0   in reply to   

    It is neither a bug nor a feature, it is a simple sample program that I wrote very quickly to demonstrate how to convert numbers into words.

    You can change the behavior anyway that you see fit.

    In order to limit the number of characters entered you could do something like:

    01 any-key               pic x.
    procedure division.
    
         perform until exit
           move zeroes to number-to-convert-raw
           display "enter a number up to 999 billion" at 0501
              blank screen
           display "enter zero to quit" at 0601
           accept number-to-convert-raw at 0701 with size 12
           if number-to-convert-raw = zeroes
              exit perform
           else
              perform 050-process-number
              display number-as-words at 0801
              accept any-key at 0901
           end-if
        end-perform
        goback.

    Chris Glazier
    Rocket Software - Principal Technical Support Specialist
    If you found this post useful, give it a “Like” or click on "Verify Answer" under the "More" button