A clean way of evaluating several values (if value NOT = a or value = b etc)

Was stuck for a long time trying to figure out a clean way of executing an action if three numbers are NOT the value of a variable (inside of a read loop).

I first tried:
IF NOT TS-TYPE = 1 OR 2 OR 3

and something similar to:

   01  ERRTRAN-VALID-TYPES                     PIC X.
       88  V-VALID-TYPES                       VALUES "1" "2" "7".



       MOVE SPACE TO ERRTRAN-VALID-TYPES
       EVALUATE TRUE
           WHEN NOT V-VALID-TYPES
               DISPLAY "TYPE ERROR"
               SET V-ERROR TO TRUE

               MOVE AR-ACCNO           TO    ER-ACCNO
               MOVE AR-NAME            TO    ER-NAME
               MOVE TS-TYPE            TO    ER-TYPE
               MOVE TS-COMPLETED       TO    ER-COMPLETED
               MOVE "INVALID TYPE"     TO    ER-ERRORMSG
               WRITE ERR-PRINT-LINE OF ERRTRAN FROM ERROR-RECORDS
           WHEN OTHER
               DISPLAY "VALID"
               CONTINUE
       END-EVALUATE

But I could not get these 2 first way working, code compiled but the logic failed …
What eventually worked was the following, but is this really an ideal solution? I doubt it

EVALUATE TS-TYPE

               WHEN 1
               WHEN 2
               WHEN 7
                   CONTINUE
               WHEN OTHER

                   DISPLAY "TYPE ERROR"
                   SET V-ERROR TO TRUE

                   MOVE AR-ACCNO                  TO    ER-ACCNO
                   MOVE AR-NAME                    TO    ER-NAME
                   MOVE TS-TYPE                     TO    ER-TYPE
                   MOVE TS-COMPLETED        TO    ER-COMPLETED
                   MOVE "INVALID TYPE"         TO    ER-ERRORMSG

                   WRITE ERR-PRINT-LINE OF ERRTRAN FROM ERROR-RECORDS

           END-EVALUATE

Would be happy to see examples of what a more experienced Cobol programmer would use.

HI:
THIS CODE WILL WORK: :

IF NOT V-VALID-TYPES
DISPLAY “TYPE ERROR”
SET…
…
WRITE ERR-PRINT…
ELSE
DISPLAY “VALID”
END-IF

NOTE: As I’m new in this forum, my Internet was down when I first replied and maybe this reply is duplicated.
Regards.

Thanks for your reply, Indeed this did work:

01  ERRTRAN-VALID-TYPES              PIC X.
      88  V-VALID-TYPES                       VALUES "1" "2" "7".


          MOVE TS-TYPE TO ERRTRAN-VALID-TYPES
           IF NOT V-VALID-TYPES
                   DISPLAY "TYPE ERROR"
                   SET V-ERROR TO TRUE
                   MOVE "INVALID TYPE"     TO    ER-ERRORMSG
                   PERFORM PA-WRITE-ERRTRAN
           END-IF
2 Likes

I have not coded in COBOL for over 30 years. I don’t even remember being able to create a field with a list of valid values. But the COBOL I used was probably mid 80’s, though VAX COBOL was pretty sophisticated. I also don’t remember EVALUATE. But the IF field-name seems familiar, though that may have been from VAX BASIC. Regardless, I do appreciate how readable it can still be.

I have a favor to ask - Imagine such a routine (probably from screen entry), where you have a list of all possible viable answers, but where each time the acceptable list might be smaller. So you use the hard coded list for a quick result, and if it succeeds, THEN you do a DB or file lookup. You do it this way to avoid file IO in many cases, on the assumption that file IO takes a lot longer. Anyone have some suggested code for that? Don’t go crazy, of course.

Thanks!

Indeed, that’s how I would do it. 88 levels make validation so much easier to code and understand.

Personally, I like to see IF statements shown in the positive. Therefore, I would use the following.
IF V-VALID-TYPES
NEXT SENTENCE
ELSE
DISPLAY “TYPE ERROR”
ETC
END-IF

Dear thesharpes,
I agree with your statements, however, I call your attention to the command “NEXT SENTENCE” that belongs to COBOL I (Legacy) and was replaced by the command “CONTINUE” in COBOL II.
There is a subtle difference between the two, as “NEXT SENTENCE” deflects to the next point IGNORING all END-IFs, while “CONTINUE” deflects to the command immediately after “END-IF”.
Respectful Hugs.

1 Like

Dear rondtroy,
If I understand correctly, You will need to put the IN option in the SQL Command, identifying the amount of Maximum Item Values, and populating the items reported by completing the other items with a FAKE value, which You are sure will not exist in the Bank.
Hugs.

Dear rondtroy,
The EVALUATE Command was introduced in COBOL in the mid-1980s, when large computer manufacturers came together and agreed on COBOL II, which guaranteed compatibility, and portability, between the developed programs, in order to allow the Client to change of Equipment without Trauma and Cost.
In environments that use good practice control software, EVALUATE inhibits the limitation of IFs in the nest of IFs, but when the nest of IFs does not exceed this limit, in my option, it remains my option.
Hugs.

I’ve actually had to code something like this, recently!

First, I generally agree with the comments above, mainly, keep everything positive, if possible! “NOT” should be used sparingly, or not at all, because it is very difficult to untangle the logic later, especially for the maintenance programmer who didn’t originally write the code.

Correct ways to code the above, are:

IF (TS-TYPE = 1 OR 2 OR 3)
DISPLAY “YES, TS-TYPE IS 1 OR 2 OR 3”
ELSE
DISPLAY “NO, TS-TYPE IS NOT 1 OR 2 OR 3”
END-IF

Or, if using NOT makes more sense (only if it simplifies the coding):

IF NOT (TS-TYPE = 1 OR 2 OR 3)
DISPLAY “NO, TS-TYPE IS NOT 1 OR 2 OR 3”
ELSE
DISPLAY “YES, TS-TYPE IS 1 OR 2 OR 3”
END-IF

The key way of thinking, is to first try to resolve in your head, the “truth” of the statement within the parentheses. It’s easier if you begin without the “NOT”. The “NOT” then flips a true statement to a false one, and vice versa. Note: the parentheses are not needed in the first example, but are definitely needed in the second one! But, whenever you can avoid using “NOT”, the better!

ScottC

Please check your references. NEXT SENTENCE is a part of COBOL II. Check this IBM link. IF statement (ibm.com)

“NEXT SENTENCE” can still be used, but in actual practice, is used rarely, and in my opinion, should not be used any more, in favor of “CONTINUE”. In general, if any of you do not understand the difference of how these 2 verbs work, then you should learn by keeping a “test program” handy where you can try different statements and see how they work, before using the same logic in a program which is much harder to test.

Once you introduce the not in your evaluation, you must use “and” to ensure that the ensuing values are also included in the final generated algorithm by the compiler.

If you understand Assembler or Machine Language, then turn on this option when compiling and you will see the generated Assembler version.

The assembling of these “NOTs”, "ORs and “ANDs” are akso true when constructing sentences accordingly. Check your Language Teachers …

Regards …

I stand by my answer/reply above. It is trusted logic I have used recently.

Prezado “as pontas”, em momento algum neguei que “NEXTE SENTE” faz parte do COBOL II, mas chamei a atenção para o fato de que esta relacionada à questão do LEGADO.
Não existe qualquer justificativa para utilizar NEXT SENTE com “EN-IF”, uma vez que, o “NEXT SENTENCE” desestrutura o “ninho de Ifs estruturado pelo END-IF”, e o COBOL II induz a uma programação ESTRTUTURADA,