• Scrabble Score (exercism solution)

    From Bruce M. Axtens@2:250/1 to All on Monday, January 13, 2025 07:09:45
    While trying to solve the Scrabble Scores exercise on Exercism, I read in
    the GnuCOBOL FAQ about CLASS in SPECIAL-NAMES. Is this an okay use
    thereof?

    -Bruce

    IDENTIFICATION DIVISION.
    PROGRAM-ID. SCRABBLE-SCORE.
    ENVIRONMENT DIVISION.
    CONFIGURATION SECTION.
    SPECIAL-NAMES.
    CLASS ONES IS 'A', 'E', 'I', 'O', 'U', 'L', 'N', 'R', 'S', 'T'.
    CLASS TWOS IS 'D', 'G'.
    CLASS THREES IS 'B', 'C', 'M', 'P'.
    CLASS FOURS IS 'F', 'H', 'V', 'W', 'Y'.
    CLASS FIVES IS 'K'.
    CLASS EIGHTS IS 'J','X'.
    CLASS TENS IS 'Q','Z'.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    *Inputs
    01 WS-WORD PIC X(60).
    01 WS-WORD-ARRAY REDEFINES WS-WORD.
    03 WS-CHAR PIC X OCCURS 60 TIMES INDEXED BY CHAR-INDEX.
    *Outputs
    01 WS-RESULT PIC 99.
    PROCEDURE DIVISION.
    SCRABBLE-SCORE.
    INITIALIZE WS-RESULT.
    MOVE FUNCTION UPPER-CASE (WS-WORD) TO WS-WORD.
    SET CHAR-INDEX TO 1.
    PERFORM LENGTH OF WS-WORD TIMES
    IF WS-CHAR(CHAR-INDEX) EQUAL SPACE
    EXIT PERFORM
    END-IF
    EVALUATE WS-CHAR(CHAR-INDEX)
    WHEN IS ONES
    ADD 1 TO WS-RESULT
    WHEN IS TWOS
    ADD 2 TO WS-RESULT
    WHEN IS THREES
    ADD 3 TO WS-RESULT
    WHEN IS FOURS
    ADD 4 TO WS-RESULT
    WHEN IS FIVES
    ADD 5 TO WS-RESULT
    WHEN IS EIGHTS
    ADD 8 TO WS-RESULT
    WHEN IS TENS
    ADD 10 TO WS-RESULT
    END-EVALUATE
    SET CHAR-INDEX UP BY 1
    END-PERFORM

    --- MBSE BBS v1.1.0 (Linux-x86_64)
    * Origin: A noiseless patient Spider (2:250/1@fidonet)
  • From R Daneel Olivaw@2:250/1 to All on Monday, January 13, 2025 09:29:21
    Bruce M. Axtens wrote:
    While trying to solve the Scrabble Scores exercise on Exercism, I read in
    the GnuCOBOL FAQ about CLASS in SPECIAL-NAMES. Is this an okay use
    thereof?

    -Bruce

    IDENTIFICATION DIVISION.
    PROGRAM-ID. SCRABBLE-SCORE.
    ENVIRONMENT DIVISION.
    CONFIGURATION SECTION.
    SPECIAL-NAMES.
    CLASS ONES IS 'A', 'E', 'I', 'O', 'U', 'L', 'N', 'R', 'S', 'T'.
    CLASS TWOS IS 'D', 'G'.
    CLASS THREES IS 'B', 'C', 'M', 'P'.
    CLASS FOURS IS 'F', 'H', 'V', 'W', 'Y'.
    CLASS FIVES IS 'K'.
    CLASS EIGHTS IS 'J','X'.
    CLASS TENS IS 'Q','Z'.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    *Inputs
    01 WS-WORD PIC X(60).
    01 WS-WORD-ARRAY REDEFINES WS-WORD.
    03 WS-CHAR PIC X OCCURS 60 TIMES INDEXED BY CHAR-INDEX.
    *Outputs
    01 WS-RESULT PIC 99.
    PROCEDURE DIVISION.
    SCRABBLE-SCORE.
    INITIALIZE WS-RESULT.
    MOVE FUNCTION UPPER-CASE (WS-WORD) TO WS-WORD.
    SET CHAR-INDEX TO 1.
    PERFORM LENGTH OF WS-WORD TIMES
    IF WS-CHAR(CHAR-INDEX) EQUAL SPACE
    EXIT PERFORM
    END-IF
    EVALUATE WS-CHAR(CHAR-INDEX)
    WHEN IS ONES
    ADD 1 TO WS-RESULT
    WHEN IS TWOS
    ADD 2 TO WS-RESULT
    WHEN IS THREES
    ADD 3 TO WS-RESULT
    WHEN IS FOURS
    ADD 4 TO WS-RESULT
    WHEN IS FIVES
    ADD 5 TO WS-RESULT
    WHEN IS EIGHTS
    ADD 8 TO WS-RESULT
    WHEN IS TENS
    ADD 10 TO WS-RESULT
    END-EVALUATE
    SET CHAR-INDEX UP BY 1
    END-PERFORM


    WHEN OTHER ??

    You could probably put the test for SPACE in there, something which
    would remove any chance of a test on WS-CHAR (61).

    --- MBSE BBS v1.1.0 (Linux-x86_64)
    * Origin: To protect and to server (2:250/1@fidonet)
  • From Bruce M. Axtens@2:250/1 to All on Tuesday, January 14, 2025 02:59:32
    On Mon, 13 Jan 2025 10:29:21 +0100, R Daneel Olivaw wrote:

    WHEN OTHER ??

    You could probably put the test for SPACE in there, something which
    would remove any chance of a test on WS-CHAR (61).

    Yes, good advice. Thank you.

    --- MBSE BBS v1.1.0 (Linux-x86_64)
    * Origin: A noiseless patient Spider (2:250/1@fidonet)
  • From R Daneel Olivaw@2:250/1 to All on Tuesday, January 14, 2025 18:40:49
    Bruce M. Axtens wrote:
    On Mon, 13 Jan 2025 10:29:21 +0100, R Daneel Olivaw wrote:

    WHEN OTHER ??

    You could probably put the test for SPACE in there, something which
    would remove any chance of a test on WS-CHAR (61).

    Yes, good advice. Thank you.


    Just paranoia, 60 letters for one word is ridiculous, but I have no idea
    where the data comes from.

    --- MBSE BBS v1.1.0 (Linux-x86_64)
    * Origin: To protect and to server (2:250/1@fidonet)
  • From docdwarf@panix.com@2:250/1 to All on Tuesday, January 14, 2025 21:33:14
    In article <vm6b3h$3dcll$1@paganini.bofh.team>,
    R Daneel Olivaw <Danny@hyperspace.vogon.gov> wrote:
    Bruce M. Axtens wrote:
    On Mon, 13 Jan 2025 10:29:21 +0100, R Daneel Olivaw wrote:

    WHEN OTHER ??

    You could probably put the test for SPACE in there, something which
    would remove any chance of a test on WS-CHAR (61).

    Yes, good advice. Thank you.


    Just paranoia, 60 letters for one word is ridiculous, but I have no idea >where the data comes from.

    Bingo. Data are dirty unless proven otherwise. What you're using SPECIAL-NAMES for we used to do with 88s that ran on for pages.

    01 WS-TEST-INVOICE-DISTRICT PIC 9(6) VALUE ZEROES.
    COPY VALDSTRC.

    MOVE IV97928-INVOICE-REC TO WS-INVOICE-REC.
    MOVE WS-INVOICE-REC-DISTRICT TO WS-TEST-INVOICE-DISTRICT.
    IF VALID-DISTRICT
    NEXT SENTENCE
    ELSE
    PERFORM 8100-INVALID-INV-DSTRCT THRU 8100-IVD-EX
    GO TO 9999-CLOSE-N-EXIT.

    .... and The Guy in the Corner Cubicle - back in those days it was always a guy - had a list in the top-right drawer of his desk with the names of all
    the programs that had to be recompiled every time a new district was
    acquired.

    DD

    --- MBSE BBS v1.1.0 (Linux-x86_64)
    * Origin: Public Access Networks Corp. (2:250/1@fidonet)