0

My problem is I get a different out put from what I am supposed to get: look very below for the output wanted. here is the output I get:

978-1734314502   (correct and valid)

978-1734314509   (incorrect, contains a non-digit)

978-1788399081   (correct and valid)

978-1788399083   (incorrect, contains a non-digit)

Here is what's the question is asking me to do:

  1. do a modern Cobol program to perform ISBN validation of a series of 10-digit ISBNs stored in a user-inputted file.

  2. Include three “subprograms” in the form of paragraphs:
    2.1. readISBNnum - Prompts the user for the name of an ASCII file containing the list of ISBN numbers. Reads the values of the ISBN numbers and processes them. If the file does not exist, the program should produce an error message and re-prompt for the filename.
    2.2. isValidate - Checks the validity of the ISBN, i.e. whether or not it contains
    characters it shouldn’t. Responses should include an indication of whether a number contains erroneous characters.
    2.3. checkSUM - Extracts the individual digits, and calculates the checksum digit.

  3. Produce an output for each ISBN number in the file, identifying whether it is valid or not

Here is what I have done so far:

  IDENTIFICATION DIVISION.
     
           PROGRAM-ID. testSubs.
           ENVIRONMENT DIVISION.
     
           CONFIGURATION SECTION.
           REPOSITORY.
               FUNCTION ALL INTRINSIC
               FUNCTION validISBN13.
     
           INPUT-OUTPUT SECTION.
           FILE-CONTROL.
     
           DATA DIVISION.
     
           FILE SECTION.
     
           WORKING-STORAGE SECTION.
     
           01  IX                          PIC S9(4) COMP.
           01  TEST-ISBNS.
               02  FILLER                  PIC X(14) VALUE '978-1734314502'.
               02  FILLER                  PIC X(14) VALUE '978-1734314509'.
               02  FILLER                  PIC X(14) VALUE '978-1788399081'.
               02  FILLER                  PIC X(14) VALUE '978-1788399083'.
           01  TEST-ISBN                   REDEFINES TEST-ISBNS
                                           OCCURS 4 TIMES
                                           PIC X(14).
     
           PROCEDURE DIVISION.
     
           MAIN-PROCEDURE.
     
               PERFORM 
                 VARYING IX 
                 FROM 1
                 BY 1
                 UNTIL IX > 4
     
                 DISPLAY TEST-ISBN (IX) '   ' WITH NO ADVANCING
                 END-DISPLAY
                 IF validISBN13(TEST-ISBN (IX)) = -1
                   DISPLAY '(incorrect, contains a non-digit)'
                 ELSE
                   DISPLAY '(correct and valid)'
                 END-IF
     
               END-PERFORM.
     
               GOBACK.
     
           END PROGRAM testSubs.
    IDENTIFICATION DIVISION.
     
           FUNCTION-ID. validISBN13.
           ENVIRONMENT DIVISION.
     
           CONFIGURATION SECTION.
           REPOSITORY.
               FUNCTION ALL INTRINSIC.
     
           INPUT-OUTPUT SECTION.
           FILE-CONTROL.
     
           DATA DIVISION.
     
           FILE SECTION.
     
           WORKING-STORAGE SECTION.
     
           01  PASSED-SIZE                 PIC S9(6) COMP-5.
           01  IX                          PIC S9(4) COMP.
     
           01  WORK-FIELDS.
               02  WF-DIGIT                PIC X.
               02  WF-COUNT                PIC 9(2).
                   88  WEIGHT-1  VALUE 1, 3, 5, 7, 9, 11, 13.
                   88  WEIGHT-3  VALUE 2, 4, 6, 8, 10, 12.
               02  WF-SUM                  PIC S9(8) COMP.
     
           LINKAGE SECTION.
     
           01  PASSED-ISBN                 PIC X ANY LENGTH.
           01  RETURN-VALUE                PIC S9.
     
           PROCEDURE DIVISION USING PASSED-ISBN
                              RETURNING RETURN-VALUE.
     
               CALL 'C$PARAMSIZE'
                 USING 1
                 GIVING PASSED-SIZE
               END-CALL.
     
           COMPUTE-CKDIGIT.
     
               INITIALIZE WORK-FIELDS.
               PERFORM 
                 VARYING IX 
                 FROM 1 
                 BY 1
                 UNTIL IX GREATER THAN PASSED-SIZE
     
                   MOVE PASSED-ISBN (IX:1) TO WF-DIGIT
                   IF WF-DIGIT IS NUMERIC
                     ADD 1 TO WF-COUNT
                     IF WEIGHT-1
                       ADD NUMVAL(WF-DIGIT) TO WF-SUM
                     ELSE
                       COMPUTE WF-SUM = WF-SUM + 
                         (NUMVAL(WF-DIGIT) * 3)
                       END-COMPUTE
                     END-IF
                   END-IF
     
               END-PERFORM.
     
               IF MOD(WF-SUM, 10) = 0
                 MOVE +0 TO RETURN-VALUE
               ELSE
                 MOVE -1 TO RETURN-VALUE
               END-IF.
     
               GOBACK.
    ===================================================================================
IDENTIFICATION DIVISION.
PROGRAM-ID. sedol.
 
ENVIRONMENT DIVISION.
INPUT-OUTPUT SECTION.
FILE-CONTROL.
    SELECT sedol-file ASSIGN "sedol.txt"
        ORGANIZATION LINE SEQUENTIAL
        FILE STATUS sedol-file-status.
 
DATA DIVISION.
FILE SECTION.
FD  sedol-file.
01  sedol                               PIC X(6).
 
WORKING-STORAGE SECTION.
01  sedol-file-status                   PIC XX.
    88  sedol-file-ok                   VALUE "00".
 
01  digit-num                           PIC 9 COMP.
 
01  digit-weights-area                  VALUE "1317391".
    03  digit-weights                   PIC 9 OCCURS 7 TIMES.
 
01  weighted-sum-parts-area.
    03  weighted-sum-parts              PIC 9(3) COMP OCCURS 6 TIMES.
 
01  weighted-sum                        PIC 9(3) COMP.
 
01  check-digit                         PIC 9.
 
PROCEDURE DIVISION.
    OPEN INPUT sedol-file
    PERFORM UNTIL NOT sedol-file-ok
        READ sedol-file
            AT END
                EXIT PERFORM
        END-READ
 
        MOVE FUNCTION UPPER-CASE(sedol) TO sedol
 
        PERFORM VARYING digit-num FROM 1 BY 1 UNTIL digit-num > 6
            EVALUATE TRUE
                WHEN sedol (digit-num:1) IS ALPHABETIC-UPPER
                    IF sedol (digit-num:1) = "A" OR "E" OR "I" OR "O" OR "U"
                        DISPLAY "Invalid SEDOL: " sedol
                        EXIT PERFORM CYCLE
                    END-IF
 
                    COMPUTE weighted-sum-parts (digit-num) =
                        (FUNCTION ORD(sedol (digit-num:1)) - FUNCTION ORD("A")
                        + 10) * digit-weights (digit-num)
 
                WHEN sedol (digit-num:1) IS NUMERIC
                    MULTIPLY FUNCTION NUMVAL(sedol (digit-num:1))
                        BY digit-weights (digit-num)
                        GIVING weighted-sum-parts (digit-num)
 
                WHEN OTHER
                    DISPLAY "Invalid SEDOL: " sedol
                    EXIT PERFORM CYCLE
            END-EVALUATE
        END-PERFORM
 
        INITIALIZE weighted-sum
        PERFORM VARYING digit-num FROM 1 BY 1 UNTIL digit-num > 6
            ADD weighted-sum-parts (digit-num) TO weighted-sum
        END-PERFORM
 
        COMPUTE check-digit =
            FUNCTION MOD(10 - FUNCTION MOD(weighted-sum, 10), 10)
 
        DISPLAY sedol check-digit
    END-PERFORM
 
    CLOSE sedol-file
    .
END PROGRAM sedol.

However, I should get the output to look like this:

1856266532 correct and valid
0864500572 correct and valid with leading zero
0201314525 correct and valid with leading zero
159486781X correct and valid with trailing uppercase X
159486781x correct and valid with trailing lowercase X
0743287290 correct and valid with leading and training zero
081185213X correct and valid with leading zero, trailing X
1B56266532 incorrect, contains a non-digit
159486781Z incorrect, contains a non-digit/X in check digit
1856266537 correct, but not valid (invalid check digit)
Maëlan
  • 3,586
  • 1
  • 15
  • 35
  • So what's not working? – Andy Lester Mar 25 '22 at 14:56
  • @AndyLester It's working though I cant get the same output that question wants – fashionable Mar 25 '22 at 16:08
  • So edit the question to show the output that you do get, as well as the output that you want, and explain the differences between the two. From there we can help you figure out what needs to change. – Andy Lester Mar 25 '22 at 16:13
  • @AndyLester I edited the question please help – fashionable Mar 25 '22 at 17:31
  • So the problem seems to be that `978-1734314509 (incorrect, contains a non-digit)` is wrong, because the error says there is a non-digit, but there isn't a non-digit. Is that it? – Andy Lester Mar 25 '22 at 18:43
  • @AndyLester not only that but also see the set of outputs the question has given me it has different series of number and different comments or explinations. now how can I change the code exactly to get the same output as the question – fashionable Mar 25 '22 at 18:54
  • 2
    The "question [] asking me to do" and the samples given are based on 10-digit ISBNs, yet the code provided is based on 13-digit ISBNs. Because the algorithms for 10- and 13-digit ISBN check digits are different, one cannot use the 13-digit code to validate 10-digit numbers. The code must rewritten to implement the algorithm for 10-digit ISBNs. – Rick Smith Apr 08 '22 at 17:28
  • @RickSmith your comment is actually the answer for that question, do you mind creating such? – Simon Sobisch Jun 24 '22 at 09:41

1 Answers1

0

Based on the assignment given in the post, the following code implements 2.2 isValidate and 2.3 checkSUM procedures for 10-digit ISBNs and 3. identifies each sample ISBN as valid or not.

Code:

   data division.
   working-storage section.
   01 isbn-table.
     03 isbn-test-numbers.
       05 pic x(10) value "1856266532".
       05 pic x(10) value "0864500572".
       05 pic x(10) value "0201314525".
       05 pic x(10) value "159486781X".
       05 pic x(10) value "159486781x".
       05 pic x(10) value "0743287290".
       05 pic x(10) value "081185213X".
       05 pic x(10) value "1B56266532".
       05 pic x(10) value "159486781Z".
       05 pic x(10) value "1856266537".
     03 isbn-10-number redefines isbn-test-numbers
          pic x(10) occurs 10 indexed isbn-idx.
   01 isbn-work.
     03 isbn-digit pic 9 occurs 9.
     03 pic x.
   01 check-digit.
     03 check-digit-9 pic 9.
   01 digit-position comp pic 9(4).
   01 digit-weight comp pic 9(4).
   01 weighted-sum comp pic 9(4).
   01 validation-flags.
   88 no-messages value all "0".
     03 pic 9.
     88 invalid-checksum value 1.
     03 pic 9.
     88 invalid-content value 1.
   01 isbn-message pic x(50).
   procedure division.
       perform varying isbn-idx from 1 by 1
       until isbn-idx > 10
           move isbn-10-number (isbn-idx) to isbn-work
           perform isValidate
           display isbn-message
       end-perform
       stop run
       .

   isValidate.
       set no-messages to true
       if isbn-work (1:9) is numeric
           perform checkSUM
           if function upper-case (isbn-work (10:1))
             not equal check-digit
               set invalid-checksum to true
           end-if
       else
           set invalid-content to true
       end-if
       move spaces to isbn-message
       evaluate true
       when invalid-checksum
           string isbn-work " invalid checksum"
           delimited size into isbn-message
       when invalid-content
           string isbn-work " invalid content"
           delimited size into isbn-message
       when other
           string isbn-work " valid ISBN"
           delimited size into isbn-message
       end-evaluate
       .

    checkSUM.
       move 0 to weighted-sum
       perform varying digit-position from 1 by 1
       until digit-position > 9
           compute digit-weight = (11 - digit-position)
           compute weighted-sum = weighted-sum
               + (isbn-digit (digit-position) * digit-weight)
       end-perform
       compute weighted-sum = 11 - function mod (weighted-sum 11)
       compute weighted-sum = function mod (weighted-sum 11)
       if weighted-sum = 10
           move "X" to check-digit
       else
           move weighted-sum to check-digit-9
       end-if
       .

Output:

1856266532 valid ISBN
0864500572 valid ISBN
0201314525 valid ISBN
159486781X valid ISBN
159486781x valid ISBN
0743287290 valid ISBN
081185213X valid ISBN
1B56266532 invalid content
159486781Z invalid checksum
1856266537 invalid checksum
Rick Smith
  • 3,962
  • 6
  • 13
  • 24