Bruce an Glenn Discuss Jurassic July

@axtens before you start, there’s a PR already for Allergies, but it needs some love.

1 Like

Okay, I’ll let you continue with your PR of allergies. Compare yours to this. I think the only serious defect was the your weren’t moving “N” to WS-RESULT after each check in LIST-ALLERGENS.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. allergies.

       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 WS-SCORE       PIC 999.
       01 WS-ITEM        PIC X(12).
       01 WS-RESULT      PIC A.
       01 WS-RESULT-LIST PIC X(108).
       01 ALLERGENS PIC A(12) OCCURS 8 TIMES 
          VALUES "eggs",
                 "peanuts",
                 "shellfish",
                 "strawberries",
                 "tomatoes",
                 "chocolate",
                 "pollen",
                 "cats".
       01 INDEX-1        PIC 9.
       01 INDEX-2        PIC 9.
       01 ALLERGEN-VALUE PIC 999.
       01 SHIFTED        PIC 999.
       01 LIST-SEPARATOR PIC X.

       PROCEDURE DIVISION.
       ALLERGIC-TO.
           MOVE "N" TO WS-RESULT.
           MOVE 1 TO INDEX-1.
           PERFORM UNTIL INDEX-1 > 8
               IF ALLERGENS(INDEX-1) EQUAL TO WS-ITEM THEN
                   COMPUTE ALLERGEN-VALUE = 2 ** (INDEX-1 - 1)
                   DIVIDE WS-SCORE BY ALLERGEN-VALUE GIVING SHIFTED
                   IF FUNCTION REM(SHIFTED; 2) EQUAL TO 1 THEN
                       MOVE "Y" TO WS-RESULT
                       EXIT PERFORM
                   END-IF
               END-IF
               ADD 1 TO INDEX-1
           END-PERFORM.
           EXIT PARAGRAPH.

       LIST-ALLERGENS.
           MOVE "N" TO WS-RESULT
           MOVE SPACES TO WS-RESULT-LIST
           MOVE SPACE TO LIST-SEPARATOR
           MOVE 1 TO INDEX-2.
           PERFORM UNTIL INDEX-2 > 8
             MOVE ALLERGENS(INDEX-2) TO WS-ITEM
             PERFORM ALLERGIC-TO
             IF WS-RESULT EQUAL TO "Y" THEN
                   STRING
                       WS-RESULT-LIST DELIMITED BY SPACE
                       LIST-SEPARATOR DELIMITED BY SPACE
                       ALLERGENS(INDEX-2) DELIMITED BY SPACE
                       INTO WS-RESULT-LIST
                   END-STRING
                   MOVE "," TO LIST-SEPARATOR
               END-IF
               MOVE "N" TO WS-RESULT
               ADD 1 TO INDEX-2
           END-PERFORM.
           EXIT PARAGRAPH.

While I’ve got your attention, is using WS- for data identifiers best practice, or it is a personal style?

But ALLERGIC-TO does that for me.

Well take it out and demonstrate to me that it’s not necessary. Am i incapable of being wrong?

Slightly better. Uses INDEXED BY.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. allergies.

       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 WS-SCORE       PIC 999.
       01 WS-ITEM        PIC X(12).
       01 WS-RESULT      PIC A.
       01 WS-RESULT-LIST PIC X(108).
       01 ALLERGENS PIC A(12) OCCURS 8 TIMES
          INDEXED BY INDEX-1, INDEX-2
          VALUES "eggs",
                 "peanuts",
                 "shellfish",
                 "strawberries",
                 "tomatoes",
                 "chocolate",
                 "pollen",
                 "cats".
       01 ALLERGEN-VALUE PIC 999.
       01 SHIFTED        PIC 999.
       01 LIST-SEPARATOR PIC X.

       PROCEDURE DIVISION.
       ALLERGIC-TO.
           MOVE "N" TO WS-RESULT.
           SET INDEX-1 TO 1.
           PERFORM UNTIL INDEX-1 > 8
               IF ALLERGENS(INDEX-1) EQUAL TO WS-ITEM THEN
                   COMPUTE ALLERGEN-VALUE = 2 ** (INDEX-1 - 1)
                   DIVIDE WS-SCORE BY ALLERGEN-VALUE GIVING SHIFTED
                   IF FUNCTION REM(SHIFTED; 2) EQUAL TO 1 THEN
                       MOVE "Y" TO WS-RESULT
                       EXIT PERFORM
                   END-IF
               END-IF
               SET INDEX-1 UP BY 1
           END-PERFORM.
           EXIT PARAGRAPH.

       LIST-ALLERGENS.
           MOVE "N" TO WS-RESULT
           MOVE SPACES TO WS-RESULT-LIST
           MOVE SPACE TO LIST-SEPARATOR
           SET INDEX-2 TO 1.
           PERFORM UNTIL INDEX-2 > 8
             MOVE ALLERGENS(INDEX-2) TO WS-ITEM
             PERFORM ALLERGIC-TO
             IF WS-RESULT EQUAL TO "Y" THEN
                   STRING
                       WS-RESULT-LIST DELIMITED BY SPACE
                       LIST-SEPARATOR DELIMITED BY SPACE
                       ALLERGENS(INDEX-2) DELIMITED BY SPACE
                       INTO WS-RESULT-LIST
                   END-STRING
                   MOVE "," TO LIST-SEPARATOR
               END-IF
               MOVE "N" TO WS-RESULT
               SET INDEX-2 UP BY 1
           END-PERFORM.
           EXIT PARAGRAPH.

Yes, you’re right about my claim re “N”. Totally bogus.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. allergies.

       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 WS-SCORE       PIC 999.
       01 WS-ITEM        PIC X(12).
       01 WS-RESULT      PIC A.
       01 WS-RESULT-LIST PIC X(108).
       01 ALLERGENS PIC A(12) OCCURS 8 TIMES
          INDEXED BY INDEX-1, INDEX-2
          VALUES "eggs",
                 "peanuts",
                 "shellfish",
                 "strawberries",
                 "tomatoes",
                 "chocolate",
                 "pollen",
                 "cats".
       01 ALLERGEN-VALUE PIC 999.
       01 SHIFTED        PIC 999.
       01 LIST-SEPARATOR PIC X.

       PROCEDURE DIVISION.
       ALLERGIC-TO.
           MOVE "N" TO WS-RESULT.
           SET INDEX-1 TO 1.
           PERFORM UNTIL INDEX-1 > 8
               IF ALLERGENS(INDEX-1) EQUAL TO WS-ITEM THEN
                   COMPUTE ALLERGEN-VALUE = 2 ** (INDEX-1 - 1)
                   DIVIDE WS-SCORE BY ALLERGEN-VALUE GIVING SHIFTED
                   IF FUNCTION REM(SHIFTED; 2) EQUAL TO 1 THEN
                       MOVE "Y" TO WS-RESULT
                       EXIT PERFORM
                   END-IF
               END-IF
               SET INDEX-1 UP BY 1
           END-PERFORM.
           EXIT PARAGRAPH.

       LIST-ALLERGENS.
           MOVE "N" TO WS-RESULT
           MOVE SPACES TO WS-RESULT-LIST
           MOVE SPACE TO LIST-SEPARATOR
           SET INDEX-2 TO 1.
           PERFORM UNTIL INDEX-2 > 8
             MOVE ALLERGENS(INDEX-2) TO WS-ITEM
             PERFORM ALLERGIC-TO
             IF WS-RESULT EQUAL TO "Y" THEN
                   STRING
                       WS-RESULT-LIST DELIMITED BY SPACE
                       LIST-SEPARATOR DELIMITED BY SPACE
                       ALLERGENS(INDEX-2) DELIMITED BY SPACE
                       INTO WS-RESULT-LIST
                   END-STRING
                   MOVE "," TO LIST-SEPARATOR
               END-IF
      *        MOVE "N" TO WS-RESULT
               SET INDEX-2 UP BY 1
           END-PERFORM.
           EXIT PARAGRAPH.

I commented it out and the tests all still pass.

Note:

01 WS-SCORE       USAGE BINARY-CHAR UNSIGNED.

works. As WS-SCORE is never displayed, other optimisations for speed and size are possible

Great stuff, thanks Bruce!

By the way, you could use 88-levels for “Y” and “N” just to improve readability.

01 WS-RESULT PIC A.
  88 IS-ALLERGIC VALUE 'Y'.
  88 IS-NOT-ALLERGIC VALUE 'N'.

and then

SET IS-NOT-ALLERGIC TO TRUE.

I’m a bit hazy on the SET … TO TRUE. You may want to check that.

With this definition

       01 ALLERGENS      PIC A(12) OCCURS 8 TIMES 
                         INDEXED BY INDEX-1 INDEX-2
                         VALUES "eggs",
                                "peanuts",
                                "shellfish",
                                "strawberries",
                                "tomatoes",
                                "chocolate",
                                "pollen",
                                "cats".

I’m getting this error

test.cob:139: error: only level 88 items may have multiple values

where line 139 corresponds to the ALLERGENS def.

From what I’m reading, a child level is needed. For example GnuCOBOL FAQ and How To

I’m using

$ cobc --version
cobc (GnuCOBOL) 3.1.2.0
Copyright (C) 2020 Free Software Foundation, Inc.
License GPLv3+: GNU GPL version 3 or later <https://gnu.org/licenses/gpl.html>
This is free software; see the source for copying conditions.  There is NO
warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
Written by Keisuke Nishida, Roger While, Ron Norman, Simon Sobisch, Edward Hart
Built     Jun 08 2023 18:57:06
Packaged  Dec 23 2020 12:04:58 UTC
C version "Apple LLVM 14.0.3 (clang-1403.0.22.14.1)"

How would I test for that in the tst/allergens.cut file?

I would expect that the SET to TRUE puts “N” into the WS variable.

This passes all tests

       IDENTIFICATION DIVISION.
       PROGRAM-ID. allergies.

       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 WS-SCORE       USAGE BINARY-CHAR UNSIGNED.
       01 WS-ITEM        PIC X(12).
       01 WS-RESULT      PIC A.
          88 IS-ALLERGIC VALUES 'Y'.
          88 NOT-ALLERGIC VALUES 'N'.
       01 WS-RESULT-LIST PIC X(108).
       01 ALLERGENS PIC A(12) OCCURS 8 TIMES
          INDEXED BY INDEX-1, INDEX-2
          VALUES "eggs",
                 "peanuts",
                 "shellfish",
                 "strawberries",
                 "tomatoes",
                 "chocolate",
                 "pollen",
                 "cats".
       01 ALLERGEN-VALUE PIC 999.
       01 SHIFTED        PIC 999.
       01 LIST-SEPARATOR PIC X.

       PROCEDURE DIVISION.
       ALLERGIC-TO.
           SET NOT-ALLERGIC TO TRUE.
           SET INDEX-1 TO 1.
           PERFORM UNTIL INDEX-1 > 8
               IF ALLERGENS(INDEX-1) EQUAL TO WS-ITEM THEN
                   COMPUTE ALLERGEN-VALUE = 2 ** (INDEX-1 - 1)
                   DIVIDE WS-SCORE BY ALLERGEN-VALUE GIVING SHIFTED
                   IF FUNCTION REM(SHIFTED; 2) EQUAL TO 1 THEN
                       SET IS-ALLERGIC TO TRUE
                       EXIT PERFORM
                   END-IF
               END-IF
               SET INDEX-1 UP BY 1
           END-PERFORM.
           EXIT PARAGRAPH.

       LIST-ALLERGENS.
           SET NOT-ALLERGIC TO TRUE.
           MOVE SPACES TO WS-RESULT-LIST
           MOVE SPACE TO LIST-SEPARATOR
           SET INDEX-2 TO 1.
           PERFORM UNTIL INDEX-2 > 8
             MOVE ALLERGENS(INDEX-2) TO WS-ITEM
             PERFORM ALLERGIC-TO
             IF IS-ALLERGIC THEN
                   STRING
                       WS-RESULT-LIST DELIMITED BY SPACE
                       LIST-SEPARATOR DELIMITED BY SPACE
                       ALLERGENS(INDEX-2) DELIMITED BY SPACE
                       INTO WS-RESULT-LIST
                   END-STRING
                   MOVE "," TO LIST-SEPARATOR
               END-IF
               SET INDEX-2 UP BY 1
           END-PERFORM.
           EXIT PARAGRAPH.

Not for me. With that exact code:

$ bin/test allergies
CobolCheck: INFO 2023-06-24T00:49:19.387201Z INF001: Attempting to load config from config.properties.
CobolCheck: INFO 2023-06-24T00:49:19.387407Z INF002: Loaded config successfully from config.properties.
CobolCheck: INFO 2023-06-24T00:49:19.387427Z INF003: Cobol-Check starting
CobolCheck: INFO 2023-06-24T00:49:19.387435Z INF005: Log level is INFO.
CobolCheck: INFO 2023-06-24T00:49:19.387442Z INF006: Configuration settings: production.
CobolCheck: INFO 2023-06-24T00:49:19.388181Z INF014: Error log for the test suite parser is set to: /Users/glennj/src/exercism/tracks/cobol/exercises/practice/allergies/ParserErrorLog.txt.
CobolCheck: INFO 2023-06-24T00:49:19.389145Z INF013: Output for generated COBOL test program is set to: /Users/glennj/src/exercism/tracks/cobol/exercises/practice/allergies/test.cob.
CobolCheck: INFO 2023-06-24T00:49:19.401330Z INF012: Successfully generated COBOL test program for src/allergies.
CobolCheck: INFO 2023-06-24T00:49:19.401467Z INF004: Cobol-Check terminating: 0
COMPILE AND RUN TEST
test.cob:140: error: only level 88 items may have multiple values
test.cob:1018: warning: alphanumeric literal has zero length; a SPACE will be assumed [-Wothers]
allergies: proof solution did not pass the tests

and checklin line 140 in test.cob

$ cat -n exercises/practice/allergies/test.cob |less 
...
   136         01 WS-RESULT      PIC A.                                                 
   137            88 IS-ALLERGIC VALUES 'Y'.                                            
   138            88 NOT-ALLERGIC VALUES 'N'.                                           
   139         01 WS-RESULT-LIST PIC X(108).                                            
   140         01 ALLERGENS PIC A(12) OCCURS 8 TIMES                                    
   141            INDEXED BY INDEX-1, INDEX-2                                           
   142            VALUES "eggs",                                                        
   143                   "peanuts",                                                     
   144                   "shellfish",                                                   
   145                   "strawberries",                                                
   146                   "tomatoes",                                                    
   147                   "chocolate",                                                   
   148                   "pollen",                                                      
   149                   "cats".                                                        
...

Regarding HIGH-SCORES, I was working on this one, but I’ll leave you to finish and merge yours. I got bogged down with trying to implement ALL the tests in the problem-specification. I also got bogged down with putting the results into an array and then testing the array, viz

TestCase "Personal top three from a list of scores"
	MOVE '10,30,90,30,100,20,10,0,30,40,40,70,70' TO WS-SCORES
	MOVE "personalTopThree" TO WS-PROPERTY
	PERFORM HIGH-SCORES
	EXPECT WS-RESULT-ARRAY(1) = 100
	EXPECT WS-RESULT-ARRAY(2) = 90
	EXPECT WS-RESULT-ARRAY(3) = 70

Regarding

PERFORM WITH TEST BEFORE UNTIL SCORES(IDX) = "   "

you could use SPACES, viz

PERFORM WITH TEST BEFORE UNTIL SCORES(IDX) = SPACES
cobc (GnuCOBOL) 3.2-dev.0
Copyright (C) 2022 Free Software Foundation, Inc.
License GPLv3+: GNU GPL version 3 or later <https://gnu.org/licenses/gpl.html>
This is free software; see the source for copying conditions.  There is NO
warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
Written by Keisuke Nishida, Roger While, Ron Norman, Simon Sobisch, Edward Hart
Built     Jul 07 2022 09:17:27
Packaged  Jul 07 2022 08:40:44 UTC
C version (MinGW) "9.2.0"

That might have something to do with it. Might not. Perhaps report the issue at comp.lang.cobol

I’m using cobol-check 0.2.0 too but there aren’t many choices there

Oh, you’re bleeding edge. I’m running the same version as the repo’s CI scripts

and the test runner

Okay, well I’d better fix that and wind back to what everyone else is using. Shall be in touch.

And looking closer, I see the CI for windows is using 3.2: maybe this is the problem with armstrong-numbers.

Regarding HIGH-SCORES, I had this for parsing the incoming list of scores. Just FYI.

         INSPECT FUNCTION REVERSE(WS-SCORES) 
          TALLYING WS-COUNT FOR LEADING SPACE.   
         SUBTRACT WS-COUNT FROM FUNCTION LENGTH(WS-SCORES) 
          GIVING WS-ACTUAL-LENGTH.
         
         MOVE 1 TO WS-SCORES-PTR.
         SET WS-SCORES-IDX TO 1.
         PERFORM WITH TEST AFTER UNTIL WS-SCORES-PTR > WS-ACTUAL-LENGTH
           UNSTRING WS-SCORES DELIMITED BY "," 
             INTO WS-SCORES-ARRAY(WS-SCORES-IDX)
             WITH POINTER WS-SCORES-PTR
             TALLYING IN WS-SCORES-MAX
           END-UNSTRING
           SET WS-SCORES-IDX UP BY 1
         END-PERFORM.