Check Digit Mod 11 Please use speaker notes

  • Slides: 10
Download presentation
Check Digit - Mod 11 Please use speaker notes for additional information!

Check Digit - Mod 11 Please use speaker notes for additional information!

Mod 11 Find the check digit for 2530618: 2 5 3 0 6 1

Mod 11 Find the check digit for 2530618: 2 5 3 0 6 1 8 x 7 x 6 x 5 x 4 x 3 x 2 16 + 35 + 18 + 0 + 24 + 3 + 16 = 10 remainder 2 11)112 11 - 2 = 9 Number with check digit 25306189 digits multiply by weight 112

Mod 11 Validate the check digit for 25306189: 2 5 3 0 6 1

Mod 11 Validate the check digit for 25306189: 2 5 3 0 6 1 8 9 x 8 x 7 x 6 x 5 x 4 x 3 x 2 x 1 16 + 35 + 18 + 0 + 24 + 3 + 16 + 9 = 11 11)121 Remainder is 0 When the remainder is 0, we know the number with the check digit is valid! Number with check digit 25306189 digits multiply by weight 121

Mod 11 CHK-DGT must be redefined as a character field to accommodate the X

Mod 11 CHK-DGT must be redefined as a character field to accommodate the X that might be there. I have defined the number in WS as having 7 digits. I have then added the 8 th digit which is the check digit and redefined it. I have then redefined the whole so I can move the entire number with the check digit even if the check digit is X. These are the work areas that I have set up to do the calculation. Note that WT which stands for weight starts with an initial value of 8. This will need to be reset if I am calculated multiple check digits. IDENTIFICATION DIVISION. PROGRAM-ID. MOD 11 CHK. AUTHOR. GROCER. ENVIRONMENT DIVISION. INPUT-OUTPUT SECTION. FILE-CONTROL. DATA DIVISION. WORKING-STORAGE SECTION. 01 ID-NUM. 05 DGT PIC 9 OCCURS 7 TIMES. 05 CHK-DGT PIC 9. 05 RDF-CHK-DGT REDEFINES CHK-DGT PIC X. 01 RDF-ID-NUM REDEFINES ID-NUM PIC X(8). 01 SUBSCRIPTZ. 05 SUB-DGT PIC 9 VALUE 1. 01 RESPONSEZ. 05 MENU-ANS PIC X VALUE SPACES. 05 RESPNSE PIC X VALUE SPACES. 05 MSG PIC X(29) VALUE SPACES. 01 WORK-ANS. 05 WT PIC 9 VALUE 8. 05 MULT-ANS PIC 99 VALUE 0. 05 SUM-DGTS PIC 999 VALUE 0. 05 DIVIDE-ANS PIC 99 VALUE 0. 05 REM-ANS PIC 99 VALUE 0. 05 SUBT-ANS PIC 99 VALUE 0.

Mod 11 Menu screen to choose to calculate the check digit or validate the

Mod 11 Menu screen to choose to calculate the check digit or validate the check digit. If the user choose to calculate a check digit, then they will enter the 7 digit number here. SCREEN SECTION. 01 MENU-SCR. 05 VALUE "MENU" 05 05 05 01 TAKE-IN-ID-SCR. 05 VALUE "PLEASE ENTER NEW ID" 05 01 If the user choose to validate a check digit, then they will enter the 8 digit number here. VALUE "1 - CALCULATE CHECK DIGIT" VALUE "2 - VALIDATE CHECK DIGIT" VALUE "3 - END PROCESSING" VALUE "ENTER SELECTION" TAKE-IN-MENU-ANS PIC X TO MENU-ANS. ID-INPUT PIC 9(7) TO ID-NUM. 05 "PRESS ANY KEY TO CONTINUE. . . " 05 TAKE-IN-FIRST-ANS PIC X TO RESPNSE. TAKE-IN-WHOLE-SCR. 05 VALUE "PLEASE ENTER ID TO VALIDATE" 05 05 05 WHOLE-INPUT PIC X(8) TO RDF-ID-NUM. "PRESS ANY KEY TO CONTINUE. . . " TAKE-IN-SECOND-ANS PIC X TO RESPNSE. BLANK SCREEN LINE 5 COL 30. LINE 8 COL 10. LINE 9 COL 10. LINE 11 COL 10. LINE 13 COL 20. LINE 13 COL 36 BLANK SCREEN LINE 5 COL 10. LINE 5 COL 30 LINE 10 COL 10. LINE 10 COL 40 BLANK SCREEN LINE 5 COL 10. LINE 5 COL 40 LINE 10 COL 10. LINE 10 COL 40

Mod 11 01 SHOW-RESULT-SCR. 05 VALUE "THE ID WITH CHECK DIGIT IS" 05 05

Mod 11 01 SHOW-RESULT-SCR. 05 VALUE "THE ID WITH CHECK DIGIT IS" 05 05 BLANK SCREEN LINE 5 COL 10. LINE 5 COL 40 COMPLETED-ID PIC X(8) FROM ID-NUM. MSG-AREA LINE 7 COL 20 PIC X(30) FROM MSG. VALUE "PRESS ANY KEY TO CONTINUE. . . " LINE 10 COL 10. TAKE-IN-THIRD-ANS LINE 10 COL 40 PIC X TO RESPNSE. The results of calculating the check digit are displayed here along with the check digit.

Mod 11 Initial take-in of the choice to calculate or verify from the menu.

Mod 11 Initial take-in of the choice to calculate or verify from the menu. Checking of the menu to determine processing. Display and accept to take in menu choices after the initializing choice. PROCEDURE DIVISION. MAINLINE. PERFORM B-100 -PROCESS. STOP RUN. B-100 -PROCESS. DISPLAY MENU-SCR. ACCEPT MENU-SCR. PERFORM B-200 -LOOP UNTIL MENU-ANS = "3". B-200 -LOOP. IF MENU-ANS = "1" PERFORM B-300 -CALC ELSE IF MENU-ANS = "2" PERFORM B-310 -VALIDATE. DISPLAY MENU-SCR. ACCEPT MENU-SCR.

Mod 11 Take in screen to take in the identification number. Initialize weight at

Mod 11 Take in screen to take in the identification number. Initialize weight at 8 since there will be 8 digits (currently there are 7), SUB-DGT (the pointer) to 1 and zero out the sum in SUM-DIGITS. Perform the routine to do the weight multiplication and accumulate the sum 7 times since there are 7 digits. Do the remaining math work of dividing to get the remainder and subtracting the remainder to get the answer. If the answer is 10 move X to the check digit, if 11 move 0 to the check digit, otherwise move the result of the subtraction to the check digit. Display the results of the calculation on the screen. B-300 -CALC. MOVE SPACES TO RDF-ID-NUM. MOVE SPACES TO MSG. DISPLAY TAKE-IN-ID-SCR. ACCEPT TAKE-IN-ID-SCR. MOVE 8 TO WT. MOVE 1 TO SUB-DGT. MOVE 0 TO SUM-DGTS. PERFORM B-400 -MULT-ROUT 7 TIMES. DIVIDE SUM-DGTS BY 11 GIVING DIVIDE-ANS REMAINDER REM-ANS. SUBTRACT REM-ANS FROM 11 GIVING SUBT-ANS. IF SUBT-ANS = 10 MOVE "X" TO RDF-CHK-DGT ELSE IF SUBT-ANS = 11 MOVE 0 TO CHK-DGT ELSE MOVE SUBT-ANS TO CHK-DGT. DISPLAY SHOW-RESULT-SCR. ACCEPT SHOW-RESULT-SCR.

B-310 -VALIDATE. MOVE SPACES TO RDF-ID-NUM. Take in screen to take in the MOVE

B-310 -VALIDATE. MOVE SPACES TO RDF-ID-NUM. Take in screen to take in the MOVE SPACES TO MSG. whole identification number DISPLAY TAKE-IN-WHOLE-SCR. including the check digit. . ACCEPT TAKE-IN-WHOLE-SCR. If the check digit is MOVE 8 TO WT. X, 10 is added to the MOVE 1 TO SUB-DGT. Initialize weight at 8 since there are sum otherwise the MOVE 0 TO SUM-DGTS. 8 digits, SUB-DGT (the pointer) to value of the check PERFORM B-400 -MULT-ROUT 1 and zero out the sum in SUMdigit is added to the 7 TIMES. DIGITS. sum. IF RDF-CHK-DGT = "X" ADD 10 TO SUM-DGTS Perform the routine to do the weight ELSE multiplication and accumulate the sum ADD CHK-DGT TO SUM-DGTS. 7 times since there are 7 digits before DIVIDE SUM-DGTS BY 11 the check digit. GIVING DIVIDE-ANS REMAINDER REM-ANS. Divide the sum of all 8 digits IF REM-ANS > 0 (including the check digit by 11 and MOVE "****** ERROR IN ID ******" TO MSG get the remainder. If the remainder is ELSE 0 then the check digit is valid. MOVE "****** VALID ID ******" TO MSG. DISPLAY SHOW-RESULT-SCR. ACCEPT SHOW-RESULT-SCR. If the remainder is greater than 0 an Mod 11 error message is moved to the screen. If the remainder is 0 a valid message is moved to the screen. The screen is displayed showing the number and a message confirming validity or highlighting an error.

Mod 11 This is the routine that multiplies each digit by its weight and

Mod 11 This is the routine that multiplies each digit by its weight and as each is multiplied, adds it to the total. It than subtracts 1 from the weight to prepare for the next pass through the routine and increments the subscript by 1 to again prepare for the next pass. B-400 -MULT-ROUT. MULTIPLY DGT (SUB-DGT) BY WT GIVING MULT-ANS. ADD MULT-ANS TO SUM-DGTS. SUBTRACT 1 FROM WT. ADD 1 TO SUB-DGT.