Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations gkittelson on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Unstringing a long sentence 1

Status
Not open for further replies.

gust1480

Programmer
Mar 19, 2002
148
PH
I want to unstring something like this
'one hundred million three hundred twenty three thousand four hundred'
and place it in 3 variables witnout having an output like this:
var1 = one hundred million three hun
var2 = dred twenty three thousand fo
var3 = ur hundred
I want the output to cut it in the right place like this:

var1 = one hundred million three
var2 = hundred twenty three thousand
var3 = four hundred
 
Welcome to tek-tips.

First, use UNSTRING in a PERFORM loop to store each individual word into an array. Use the COUNT IN clause of UNSTRING to store the length of each word. Your array might look something like:
Code:
01  WORD-ARRAY.
    02  OCCURS 50.
        03  THE-WORD  PIC X(50).
        03  THE-WORD-LENGTH PIC 99.
and your UNSTRING statement might look something (but not exactly) like:
Code:
UNSTRING BIG-STRING 
   DELIMITED BY ALL SPACES
   INTO THE-WORD (I) 
   COUNT IN THE-WORD-LENGTH (I)
   POINTER J
END-UNSTRING.
Then, upon completion of the UNSTRING loop, you may reassemble the words using another loop (or set of loops, possibly) which STRING the words back together. If you push the envelope a bit, you may eliminate this second loop (hint: use the NOT ON OVERFLOW clause in the UNSTRING).

This should get you started. Let us know what you come up with.

Tom Morrison
 
I should have said:

"If you push the envelope a bit, you may eliminate this second loop and the array."
Tom Morrison
 
Hi gust,

What's the generalized format?

For example:

'x hundred million y hundred m (n) thousand p hundred (q (r))'

The () indicate optional elements of the string. Of course, even this doesn’t express the full flexibility (and complexity) of what can be found in the string. For example, 'x hundred million p hundred’.


If my assumption is right, the problem complexity multiplies. Tom's suggestion would have to be expanded to include checks for the presence or absence of these optional fields.

My suggestion would be to use reference modification instead of a 2nd string/unstring to facilitate checking for optional elements in the string.

If your desired variable content is arbitrary, I'd suggest ending each variable with the scalar label (e.g. million, thousand, etc.).

Jack


 
Jack,

I looked at his suggested result, and it seemed that the only "business rule" was that individual words not be chopped apart.

But, of course, I await feedback!
Tom Morrison
 
Aw, I just couldn't wait.

Code:
      identification division.
       program-id.  parse-sentence.
       data division.
       working-storage section.
       01  long-sentence               pic x(500) value
           "When in the Course of human events, it becomes necessary
      -    "for one people to dissolve the political bands which have
      -    "connected them with another, and to assume among the powers
      -    "of the earth, the separate and equal station to which the
      -    "Laws of Nature and of Nature's God entitle them, a decent
      -    "respect to the opinions of mankind requires that they
      -    "should declare the causes which impel them to the
      -    "separation.".

       01  shorter                     pic x(40).
       01  shorter-length              pic 999.

       01  a-word                      pic x(30).
       01  a-word-length               pic 99.
       01  word-count                  pic 999 value 0.
       01  in-ptr                      pic 999.
       01  out-ptr                     pic 999.
           88  is-max-out-ptr value 999.
       01                              pic x.
           88  is-first value "F" false "L".
       01  the-delimiter               pic x.
           88  is-full-stop value "." false space.

       procedure division.
       a.
           set is-full-stop to false.
           set is-first to true.
           move 1 to in-ptr.
           set is-max-out-ptr to true.
           move all "A" to a-word.
           move 0 to shorter-length.
           inspect shorter
               tallying shorter-length for characters.
           perform until is-full-stop
               move spaces to a-word
               unstring long-sentence
                   delimited by all spaces or "." or ","
                   into a-word
                   delimiter in the-delimiter
                   count in a-word-length
                   with pointer in-ptr
                   tallying in word-count
               end-unstring
               if a-word-length > 0 then
                   if (out-ptr + a-word-length) > shorter-length
                       if is-first
                           set is-first to false
                       else
                           display shorter
                       end-if
                       move 1 to out-ptr
                       move spaces to shorter
                   end-if
                   string a-word (1:a-word-length), " "
                       delimited by size
                       into shorter
                       with pointer out-ptr
                   end-string
               else
                   subtract 1 from word-count
               end-if
           end-perform.
           if out-ptr > 1 display shorter.
           display "Word count = ", word-count.
           stop run.
which produces the following output:
When in the Course of human events it
becomes necessary for one people to
dissolve the political bands which have
connected them with another and to
assume among the powers of the earth
the separate and equal station to which
the Laws of Nature and of Nature's God
entitle them a decent respect to the
opinions of mankind requires that they
should declare the causes which impel
them to the separation
Word count = 071


WARNING: The code shown above is not suitable for any purpose. It is a (probably flawed) sample code example only.
Tom Morrison
 
Thanks you guys for the suggestions I really appreciate it. Tom is right,I just want the individual word not to be chopped apart.
I'll just let you know when I've finished this program of mine. ok. Thanks again guys.
 
hello Tom,
I finally finished the unstringing. Thanks to you.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top