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 strongm on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

STRING Table of errors into one field for output 4

Status
Not open for further replies.

SiouxCityElvis

Programmer
Jun 6, 2003
228
US
I am trying to figure out how to go about putting a table of errors into a field for output.

My errors Working Storage table is:

Code:
       01  WS-STRING-OUT          PIC X(1000).
       01  STRING-IDX             PIC 999 VALUE 0.
       01  WS-ERROR-IDX           PIC 999 VALUE 0.
       01  WS-CUST-ERROR-TABLE.
           03 WS-CUST-ERRORS OCCURS 999 TIMES.
              05 WS-CUST-ERROR     PIC X(15).
              05 WS-CUST-DELIMITER PIC X(1) VALUE "^".

I use the STRING on other message out subroutines, but I am wondering if I can do that with the Table of errors above. I want to store the string of errors in one huge string delimited by "^" between each error.
example:
WS-STRING-OUT would be populated with
"pin error^signon error^idiot error^......^etc"

My guess would be:

Code:
  STRING WS-CUST-ERRORS DELIMITED BY SIZE
   INTO WS-STRING-OUT
  END-STRING

I'm going to try this, but have doubts that using the WS-CUST-ERRORS field will work. My guess is that WS-CUST-ERROR with and index will need to be used, but I'm wondering how to iterate through all indexed errors, and string them all into one field.

Thanks.
-David
 
move 1 to pointer
perform varying wi from 1 by 1
until wi > 999
move WS-STRING-OUT(wi)(1:size_of_ws-string-out_error_text) to out-string(pointer:)
add size_of_ws-string-out_error_text to pointer
move "^" to out-string(pointer:1)
add 1 to pointer
end-perform.

where size_of_ws-string-out_error_text
needs to be calculated by you with another perform such as

perform varying wsize from 15 by - 1
until wsize = 0
or ws-string-out(wsize:1) not = spaces
continue
end-perform



Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
Am I missing something here? You want to get the table of error messages put into WS-STRING-OUT, right?

01 WS-STRING-OUT PIC X(1000).
01 STRING-IDX PIC 999 VALUE 0.
01 WS-ERROR-IDX PIC 999 VALUE 0.
01 WS-CUST-ERROR-TABLE.
03 WS-CUST-ERRORS OCCURS 999 TIMES.
05 WS-CUST-ERROR PIC X(15).
05 WS-CUST-DELIMITER PIC X(1) VALUE "^".

Why not just use

MOVE WS-CUST-ERROR-TABLE TO WS-STRING-OUT.

Isn't that what you're trying to do with the STRING?

You do realize that WS-STRING-OUT is not large enough to contain the possible number of errors that can be stored in the table.
 
David -

I think Frederico has the right idea for what you want to do. (I think he got some data names switched around though.)

Note in your first attemtp that the DELIMITED BY SIZE says that the number of characters moved will be the size of the sending field. In your case, 15 bytes. That would result in WS-STRING-OUT being equivalent to the first 1,000 bytes of WS-CUST-ERROR-TABLE (i.e. with spaces between each error message and the following caret). Not what you had in mind I suspect.

Note also that we had a lengthy discussion a few months back on how to determine the length of a character string. There was an elegant solution proposed based on using the REVERSE intrinsic function. You might check the archives for that.

Regards.

Glenn
 
Hi

Is that error table necessary?

Why not u r storing the messages in a string at the first place. U can write a small procedure which u can call at every place where u r moving the error_message in the error_table.


01 temp string pic x(3000) value spaces.
01 space-delimeter pic (1500) values spaces.
01 error_msg-string pic x(1500) values spaces.
01 string-delimeter pic x value spaces.
01 sw-first-time pic x(01) value 'Y'.
88 first-time value 'Y'.

procedure division.

*Let say u r receving error msg in ws-error-msg.
*ur proc could be

concat-para.
if first-time.
move 'N' to sw-first-time
move spaces to string-delimeter
else
move '^' to string-delimeter
end-if.

move sapces to temp-string
move error-msg-string to temp-string
string temp-string string-delimeter ws-error-msg
delimeted by space-delimeter
into error_msg-string.


devesh


 
David, Glenn,

However, David is using RM/COBOL which does not have the REVERSE intrinsic function. More about this later...

David, you did not specify in your problem statement such things as:
- trailing space suppression required?
- what exactly is in the 15 characters? For example, from your problem statement, I would take the word 'error' to be redundant; is the word 'error' stored or should it be appended? If not stored, is it the case that there are no embedded spaces in the error text.
- is a final "^" required, or prohibited?

Now, assuming that the goal is to remove trailing spaces, consider the following possibilities:

1. If the array is just an intermediate step of little consequence, eliminate the step entirely by STRINGing directly into the result:
Code:
       01  WS-STRING-OUT          PIC X(1000).
       01  WS-STRING-OUT-PTR      PIC 9(4) BINARY.
... initialization
       MOVE SPACES TO WS-STRING-OUT.
       MOVE 1 TO WS-STRING-OUT-PTR.
... then when you wish to append an error message
... use STRING instead of MOVE
       STRING "pin error^" DELIMITED BY SIZE 
           INTO WS-STRING-OUT
           POINTER WS-STRING-OUT-PTR
         ON OVERFLOW
           <handle too many errors condition>
       END-STRING
...
       STRING &quot;signon error^&quot; DELIMITED BY SIZE 
           INTO WS-STRING-OUT
           POINTER WS-STRING-OUT-PTR
         ON OVERFLOW
           <handle too many errors condition>
       END-STRING
...
       STRING &quot;some rather long elaborate error^&quot; 
               DELIMITED BY SIZE 
           INTO WS-STRING-OUT
           POINTER WS-STRING-OUT-PTR
           POINTER WS-STRING-OUT-PTR
         ON OVERFLOW
           <handle too many errors condition>
       END-STRING

2. If the array is important, and error messages must contain embedded spaces, then do a small trick to make the trailing spaces the only spaces in the fields, then use INSPECT at the end to insert embedded spaces. (This obviates the need for REVERSE.)
Code:
       01  WS-STRING-OUT          PIC X(1000).
       01  WS-STRING-OUT-PTR      PIC 9(4) BINARY.
       01  STRING-IDX             PIC 999 VALUE 0.
       01  WS-ERROR-IDX           PIC 999 VALUE 0.
       01  WS-CUST-ERROR-TABLE.
           03 WS-CUST-ERRORS OCCURS 999 TIMES.
              05 WS-CUST-ERROR     PIC X(15).
... placing an error in the table
       ADD 1 to WS-ERROR-IDX.
       MOVE &quot;pin@error&quot; to WS-CUST-ERROR (WS-ERROR-IDX).
       ADD 1 to WS-ERROR-IDX.
       MOVE &quot;signon@error&quot; to WS-CUST-ERROR (WS-ERROR-IDX).
... the following won't work so well!
       ADD 1 to WS-ERROR-IDX.
       MOVE &quot;some@rather@long@elaborate@error&quot; 
            to WS-CUST-ERROR (WS-ERROR-IDX).
... then when you wish to create the output string
       MOVE SPACES TO WS-STRING-OUT.
       MOVE 1 TO WS-STRING-OUT-PTR.
       PERFORM VARYING STRING-IDX FROM 1 BY 1
                 UNTIL STRING-IDX >= WS-ERROR-IDX
           STRING WS-CUST-ERROR (STRING-IDX) 
                       DELIMITED BY SPACE
                  &quot;^&quot;  DELIMITED BY SIZE
               INTO WS-STRING-OUT
               POINTER WS-STRING-OUT-PTR
             ON OVERFLOW
               <handle too many errors condition>
           END-STRING
       END-PERFORM
       SUBTRACT 1 FROM WS-STRING-OUT-PTR.
       IF WS-STRING-OUT-PTR > 0
           INSPECT WS-STRING-OUT (1:WS-STRING-OUT-PTR)
               RERPLACING ALL &quot;@&quot; BY SPACE
       END-IF.
Note that example 1 reduces the constraint on length of erro messages. Note also that example 2 eliminates the storage you have devoted to 999 copies of &quot;^&quot; by having the STRING do the work.

Perhaps one of these modified approaches will work...

Tom Morrison
 
Two thoughts here. If you don't care about the spaces at the end of each message
(&quot;pin error ^signon error ^idiot error ^...etc&quot;)
Lunkers suggestion is the way to go. That appears to be the case, since that looks like what you were trying to do with your original string statement. If you want to strip out spaces you could do something like the following to avoid the continuous looping.

MOVE FUNCTION REVERSE(ws-string-out(wi)) TO STRING-REVERSED.
MOVE +0 TO X.
INSPECT STRING-REVERSED TALLYING X FOR LEADING SPACES.
COMPUTE X = LENGTH OF WS-CUSTOMER-ERROR - X.

Now you can...

MOVE WS-STRING-OUT(wi)(1:X) to out-string(pointer:)

This would basically replace the

perform varying wsize from 15 by - 1
until wsize = 0
or ws-string-out(wsize:1) not = spaces
continue
end-perform

Just another idea for your consideration.

Stacey
 
The reason why I didn't use the string delimited by spaces is that I was assuming that a &quot;error message&quot; could have embedded spaces on it, and on this case it would not work as expected (e.g. from &quot;error message&quot; we would end up just with &quot;error&quot;)

string delimited by size won't work either on it's own, so the only way for this to work is to know the size of the string

As an alternative to my first option

move 1 to apointer
perform varying wi from 1 by 1
until wi > 999
str_size = get_string_size
string WS-CUST-ERROR(1:str_size)
&quot;^&quot; delimited by size
into WS-STRING-OUT
pointer apointer
end-perform.

But all this are just examples that may not be the best option for what David requires.

(Glenn. Yes I did get the names wrong. Oops)
David,

In order for us to give you a &quot;better&quot; solution we need to know exactly what you are trying to accomplish, including origin/format of the errors (with some real examples), as this will have some impact on the definition of the fields, size wise and not only.


Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
Using RMCOBOL-85 version 8, I took an approach similar to Lunker's above. However I just did a WRITE directly from my WS table variable. In other words, I eliminated the WS-STRING-OUT variable.

Here's what I came up with:

Code:
FILE SECTION.
FD  FILE-RECORD.

       01  FILE-REC.
           02 FILE-NAME          PIC X(43).
           02 FILE-FILLER        PIC X(957).
       01 FILE-OUT-REC           PIC X(1000).


WORKING-STORAGE SECTION.       
       01  WS-ERROR-IDX           PIC 999 VALUE 0.
       01  WS-CUST-ERROR-TABLE.
           03 WS-TABLE-ERROR-FLAG PIC X(2) VALUE &quot;Y^&quot;.
           03 WS-CUST-ERRORS OCCURS 999 TIMES.
              05 WS-CUST-ERROR    PIC X(15).
              05 WS-DELIMITER     PIC X VALUE &quot;^&quot;.


PROCEDURE DIVISION.
....do code that determines if it passes or fails setting WS-CUST-ERROR-FLAG accordingly...

           IF WS-CUST-ERROR-FLAG = &quot;Y&quot;
             MOVE SPACES TO FILE-OUT-REC,
                       WS-FILE-OUT-RECORD
             MOVE WS-RFMT-FILE-NAME TO FILE-NAME
             MOVE &quot;Y^&quot; TO WS-TABLE-ERROR-FLAG
             OPEN OUTPUT FILE-RECORD
             WRITE FILE-OUT-REC FROM WS-CUST-ERROR-TABLE
             CLOSE FILE-RECORD
             GO TO END-IT
           END-IF.

I know that FILE-OUT-REC is PIC X(1000) and that the WS-CUST-ERROR-TABLE can hold potentially way more than 1000, but for now it will work fine. I just want to make sure that I can have multiple errors sent out on a result set for the Java programmer, in the event that the customer may have made multiple errors i.e. PIN incorrect as well as some other kind of error down the road. I don't expect that we'll have scenarios where they can actually have multiple errors upon entering a transaction and hitting my program and end up with errors that accumulate to over 1000 in length. That would be 60 some odd errors if you take 1000 divided by 15.

THanks for the help on all of this.
-David
 
By the way, I just want to thank all of you on this post. Wow, it seems like I caught nothing but experts on this one! Thanks for this ... learning still.

-David
 
Hi David,

This won't be a solution to your particular problem but I think you might find it useful in the future. One of the new features in RM/COBOL version 8.00 is the use of Concatenation Expressions. See page 1-18 of the RM/COBOL v8.0 Language Reference Manual.

These expressions may be used anywhere a nonnumeric literal may be used. A concatenation expression is of the form:

literal-1 & literal-2

Besides making continuation of long literals more elegant (since it avoids the weird unbalanced quotes used in 1968/1974/1985 standard COBOL), this feature allows new combinations of literals to be formed at compile time. That is because literal-1 or literal-2 may be a symbolic-character constant or a constant-name constant, which can then be combined with another literal in a concatenation expression in ways that were not previously possible except at runtime (with a STRING statement or reference modification).

A simple example:

Move &quot;pin error&quot; & &quot;^&quot; to ws-error-out.

The literals can be 78 level constant names, figurative constants (Space, Quote, high-values, low-values), program-id, symbolic literals, hexadecimal literals (e.g. &quot;^&quot; would be x&quot;5e&quot;), the ALL phrase may be used.

-Rob
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top