Computers in Engineering WWW Site - Example 16.5

Example 16.5


FORTRAN Version

!
      PROGRAM P105
!
!
!      CLASS LIST RETRIEVAL PROGRAM
!      FIND SOME STUDENT GRADES
!      USING A HASHING SCHEME WITH THE ID AS THE KEY
!
!      DECLARE ARRAYS FOR FILE
!
      IMPLICIT NONE
      CHARACTER (LEN=25) :: NAMES(100),NAME
      INTEGER :: ID(100),MARKS(100,7),GRADES(7)
!
      INTERFACE
      SUBROUTINE HASH(ID,NR)
      IMPLICIT NONE
      INTEGER ,INTENT(IN OUT) :: ID(:),NR
      END SUBROUTINE HASH
      END INTERFACE
!
      PRINT *, 'This is Program >> P105 = Hashing'
!
!     Tell program where data for  READ is coming from
      OPEN(UNIT=5, FILE='P105.DAT')
! UNIT=5 is the default input
!
!
!===== ZERO OUT ALL ID'S FOR STARTERS
!
L1:   DO J=1,100
         ID(J)=0
      END DO L1
!
!==== READ IN FILE AND STORE IN MAIN MEMORY
!
L2:   DO J=1,100
         READ 15,KD,NAME,GRADES
15       FORMAT(I7,1X,A25,7I3)
         IF(KD == 0) GO TO 101
         Print 15,KD,NAME,GRADES
         CALL HASH(KD,NR)
31       IF(ID(NR) == 0) THEN
!           STORE AWAY THE DATA IN ANY EMPTY SLOT
            ID(NR)=KD
            NAMES(NR)=NAME
L3:         DO K=1,7
               MARKS(NR,K)=GRADES(K)
            END DO L3
!
!===  HERE WE DEAL WITH THE CASE OF A USED SLOT
!     TRY THE NEXT OVER, BUT WATCH FOR END OF THE FILE
!
         ELSE
            NR=NR+1
!              IF AT END - START AT BEGINNING
            IF(NR > 100) NR=1
            GO TO 31
         END IF
      END DO L2
      PRINT 16
16    FORMAT(/'TOO MUCH DATA FOR DEFINED ARRAYS'/  & 'INCREASE ARRAY SIZE AND RERUN'//)
      STOP
!
!==== READ AND PROCESS NAMES REQUESTED
!
101   NREC=J-1
      PRINT 102,NREC
102   FORMAT(/'CLASS LIST PROGRAM - RETRIEVAL BY NAME'/  & I5,' RECORDS ON FILE')
      NREQ=0
L4:   DO J=1,NREC
         READ 202,KID
202      FORMAT(I7)
         IF(KID == 0) THEN
            PRINT 203,NREQ
203         FORMAT(I5,' REQUESTS PROCESSED'/)
            STOP
         ELSE
            NREQ=NREQ+1
            CALL HASH(KID,NR)
231         IF(ID(NR) == 0) THEN
               PRINT 205,KID
205            FORMAT(I9,'   NOT ON FILE - CHECK SPELLING')
            ELSE
               IF(KID == ID(NR)) THEN
                  PRINT 206,KID,NAMES(NR),(MARKS(NR,I),I=1,7)
206               FORMAT(I9,'   ',A25,7I5)
               ELSE
                  NR=NR+1
                  IF(NR > 100) NR=1
                  GO TO 231
               END IF
            END IF
         END IF
      END DO L4
      STOP
      END PROGRAM P105
!
      SUBROUTINE HASH(ID,NR)
      IMPLICIT NONE
      INTEGER ,INTENT(IN OUT) :: ID(:),NR
      INTEGER :: NPRIME=97
      NR=MOD(ID,NPRIME)+1
      RETURN
      END SUBROUTINE HASH

C Version

/*
   Searching program with hashing method.
*/

#include<stdio.h>
#include<stdlib.h>

#define MAXSTUDENTS 50   /*  Constants */
#define HASH_SIZE 61

int hash( long int key, int n ){
  return( (int) ( key % (int)(n*1.4)) ) ;
}

main()
{
  /*  Declaration Statements  */
  char names[HASH_SIZE][25], temp_name[25];
  long int id[HASH_SIZE], key, temp_id;
  int i, n, hash_index, cont, counter, probe_worked, yes_no;

  printf("Zeroing all elements of the array\n\n");
  for( i=0;  i < (HASH_SIZE); i++)
     id[i] = 0;

  do{
     printf("How many students? (<%4d)",MAXSTUDENTS);
     scanf("%d",&n);
     }while( n>MAXSTUDENTS );

  printf("Enter students' names and ID #'s\n");
  printf("in this format ->Name:Doe,John[ENTER] (no spaces)\n");
  printf("               ->ID:9421234[ENTER]\n");

  /*  The following is along loop that carries out the hashing
       algorithm as each student is added to the list. */

  for( i=0; i<n; i++){
     printf("Student #%d:",i+1);
     printf("Name:");
     scanf("%s",temp_name);
     printf("ID:");
     scanf("%ld",&temp_id);

    hash_index = hash( temp_id,n );
 /*  This hash is legal! */

  /* Now, this is the part where we will check for collisions, and take
     appropriate action. */

    if( id[ hash_index ] == 0 ) {
       id[hash_index] = temp_id;
       strcpy( names[hash_index], temp_name );
       }
    else {         /* What to do if we had a collision */
       probe_worked = 0;
       do{
         /*  Check the next slot */
        hash_index++;

         /*  If we're at the end of the list, go back to beginning */
        if( hash_index >= HASH_SIZE)
          hash_index = 0;

         /*  If the next slot was empty, fill it, and get out of loop */
        if( id[ hash_index ] == 0 ){
          id[hash_index] = temp_id;
          strcpy( names[hash_index], temp_name );

       probe_worked = 1;  /*  A flag to exit the linear probing loop */
          }   /* end if */

     }while( probe_worked == 0 ); /* end of linear probing loop */

     } /* endif - this was the if that checked for a collision */

  }  /* end of outer loop that prompts user for names and id#'s */

/* This part of the program lets the user search the list
   using the hashing function */

 do {
   /* Keep on looking up names until user wants to quit */

  printf("Enter search key\n\n ID# :");
  scanf("%ld",&key);

  printf("\n  **SEARCHING**\n");

    hash_index = hash( key, n );

  /* Now, we will check for collisions, and take appropriate action. */

    if( id[ hash_index ] == key ) {
       strcpy( temp_name, names[hash_index] );
       }
    else {        /* What to do if we had a collision when storing */
                 /* the ID # that the user is requesting */

       /* Initialize a counter to make sure that we don't
          keep probing the whole list over and over again. */
       counter = 0;
       i = 0;
       do{
        counter++;
         /*  Check the next slot  */
        hash_index++;

         /*  If we're at the end of the list, go back to beginning */
 if( hash_index >= HASH_SIZE )
          hash_index = 0;

         /* If the next slot was the key, get name and get out of loop*/
        if( id[ hash_index ] == key ){
          strcpy( temp_name, names[hash_index] );

          i=1;  /*  This is a flag to exit the linear probing loop */
          }   /* end if */

        }while( i==0 && counter <= HASH_SIZE); /*end of linear probe*/

     } /* endif - this was the "if"that checked for a collision */

  cont = 0;
  if(counter > n){
    printf("Search key not found - check spelling\n");
    printf("Try again (1 for yes/0 for no)? ");
    scanf("%d",&yes_no);
    }
  else {
    printf("  **FOUND**\n");
    printf("ID#:%ld  Name:%s\n\n", key, temp_name);
    printf("Look up another student (1 for yes/0 for no)? ");
    scanf("%d",&yes_no);
    } /* End of if{} statement */

 }while(yes_no == 1);

}
/*  End of Hash.c program  */

/*
INPUT :

8
Milo,Bloom    9611684
Cat,theBill   9613986
Dallas,Steven 9412978
Cutter,John   9613693
Jones,Oliver  9515010
Binkley,Mike  9510633
Opus,Holland  9513221
Dummy,One     0000000

OUTPUT :

Zeroing all elements of the array

How many students? (<  50) 8
Enter students' names and ID #'s
in this format ->Name:Doe,John[ENTER](no spaces)
               ->ID:9421234[ENTER]
Student #1:
Name:Milo,Bloom
ID #:9611684
Student #2:
Name:Cat,theBill
ID #:9613986
Student #3:
Name:Dallas,Steven
ID #:9412978
Student #4:
Name:Cutter,John
ID #:9613693
Student #5:
Name:Jones,Oliver
ID #:9515010
Student #6:
Name:Binkley,Mike
ID #:9510633
Student #7:
Name:Opus,Holland
ID #:9513221
Student #8:
Name:Dummy,One
ID #:0000000
 ID# :9800012
  **SEARCHING**
Search key not found - check spelling
Try again (1 for yes/0 for no)? 0 
*/

Pascal Version

{$G256}
{$P512}
{D+}
PROGRAM p105 ( input, output );
{
     Class list retrieval program
     Find some student grades
     Using a hashing scheme with the id as the key

     Declare arrays for file
}
TYPE
  real_array = ARRAY[1..100] OF REAL;
  char_array = ARRAY[1..25] OF CHAR;
VAR
  names : ARRAY[1..100] OF char_array;
  name : char_array;
  marks : ARRAY [ 1..100, 1..7 ] OF INTEGER;
  id : real_array;
  grades : ARRAY[1..7] OF INTEGER;
  i, j, k, nr, rec, req, looped, loop : INTEGER;
  kd, kid : REAL;

PROCEDURE hash ( id : REAL;
                 VAR nr : INTEGER );
VAR
  prime : integer;
BEGIN
  prime := 97;
  nr := trunc ( id / 1000.0 );
  nr := ( nr mod prime ) + 1
END;

BEGIN
{
     Zero out all id's for starters
}
  FOR j := 1 TO 100 DO
    id[j] := 0;
{
     Read in file and store in main memory
}
  j := 0;
  REPEAT
    j := j + 1;
    read ( kd, name );
    FOR i := 1 TO 7 DO
      read ( grades[i] );
    readln;
    IF ( kd <> 0 ) THEN
      BEGIN
        hash ( kd, nr );
        looped := 0;
        WHILE ( ( id[nr] <> 0 ) AND ( looped < 2 ) ) DO
          BEGIN
            nr := nr + 1;
            {
                 If at end - start at beginning
            }
            IF ( nr > 100 ) THEN
              BEGIN
                nr := 1;
                looped := looped + 1
              END { end if }
          END;{ end while }
        {
             Store away the data in any empty slot
        }
        IF ( looped < 2 ) THEN
          BEGIN
            id[nr] := kd;
            names[nr] := name;
            FOR k := 1 TO 7 DO
              marks [ nr, k ] := grades[k]
          END { end if }
        ELSE
          BEGIN
            writeln;
            writeln ( 'too much data for defined arrays' );
            writeln ( ' increase array size and rerun' )
          END
      END
    ELSE
      BEGIN
      {
           Read and process names requested
      }
        rec := j - 1;
        writeln ( ^l );
        writeln ( 'Class list program - retrieval by name' );
        writeln;
        writeln ( rec:5, ' records on file' );
        writeln;
        req := 0;
        k := 0;
          REPEAT
            k := k + 1;
            readln ( kid );
            IF ( kid <> 0 ) THEN
              BEGIN
                req := req + 1;
                hash ( kid, nr );
                loop := 0;
                WHILE ( ( loop < 2 )
                        AND ( kid <> id[nr] ) ) DO
                  BEGIN
                    nr := nr + 1;
                    IF ( nr < 100 ) THEN
                      BEGIN
                        nr := 1;
                        loop := loop + 1
                      END { end if }
                  END; { end while }
                  IF ( kid = id[nr] ) THEN
                    BEGIN
                      write ( kid:9:0, ' ':3, names[nr] );
                      FOR i := 1 TO 7 DO
                        write ( marks [ nr, i ]:5 );
                      writeln
                    END; { end if }
                  IF ( loop >= 2) THEN
                  writeln ( kid:9:0, '     not on file - check spelling' )
              END
            ELSE
              BEGIN
                writeln;
                writeln ( req:5, ' requests processed' );
                writeln
              END { end else }
          UNTIL ( ( kid = 0 ) OR ( k > rec ) OR ( loop > 2 ) )
      END
  UNTIL ( ( j > 100 ) OR ( looped > 2 ) OR ( kd = 0 ) )
END.
DATA:
7611684 Opus                    15 16 16 17 17 39 76
7613986 Bloom Milo              16 17 16 18 17 41 79
7412978 Dallas Steven           13 12 11 13 14 31 64
7613693 Cat Bill the            18 18 19 17 19 41 82
7515010 John Cutter             15 16 15 15 15 38 77
7510633 Jones Oliver W          17 17 18 17 17 42 80
7513221 Mike Binkley            19 19 19 18 19 45 91
0000000 Dummy                    0  0  0  0  0  0  0
7611684
7613693
7511522
7513221
0000000

Last modified: 08/07/97