Previous Up Next

The scanner module
(scanner)

Introduction

This module contains the scanner. The scanner reads the input file and returns the symbols it has recognized, together with their representation. This is called lexical analysis.

The lexical analysis is not done in a separate pass, but is intermingled with parsing. The scanner scans one symbol at a time in the input file on request from the parser.

As well as the elementary scanning procedure that reads the next symbol from the input, this module also contains a number of parsing tools. There are a number of different kinds of symbols. Together these symbols form the non-terminals of the context-free grammar of the attributed abstract program tree grammar.

1 Usage of the scanner

There are three procedures that control the usage of the scanner modules. These procedures have to be called in the correct order to ensure correct operation of the scanner. The header of the procedure that must be called first is:

This procedure requests an input file name on the terminal, and opens the input file with this name.

The second procedure to be called is the scanner initialization procedure. Because this procedure also reads the first symbol from the input, the listing file generator has to be initialized [listing 1] and because this could also result in errors, the error-handler must also be initialized [errors 1]. The header of this procedure is:

The last procedure must be called after the entire input has been scanned (read). This procedure closes the input file. The header of this procedure is:

2 Main scanning procedure

The header of the procedure that is called by the parser to scan the next symbol is:

This procedure has to be called with the input file variable as the argument of the parameter infile. When the end of the input file is reached, the symbol end of file is returned by the procedure. Otherwise a number (at least one) of characters from the input is read until a symbol is recognized. An error is reported if an illegal character is encountered or if the representation of the symbol is too long. The alphabetic representation of the last scanned symbol is stored in the variable scansym, and the kind of symbol is stored in the variable sym.

As a side effect the screen-management module is informed about the position of the last scanned symbol.

3 Parsing tools

The parsing tools consist of three procedures that are frequently used to check whether a symbol that is expected according to the grammar is found in the input file, or to skip possible rubbish (unexpected symbols) in the input file. In each of the following subsections we deal with one of these procedures.

3.1 Expect

The first procedure that can be used as a parsing tool is the procedure that tests whether an expected symbol is found in the input file. The header of this procedure is:

The first parameter infile should always be the input file variable. The second parameter s represents the symbol that is expected to be the next symbol in the input file, assuming that this symbol has just been scanned. If this symbol is not equal to the expected symbol, an error message is generated in which the value of the last parameter correct is used to describe the missing symbol. Otherwise, no error message is generated, and if the value of the third parameter skip is equal to TRUE, the next symbol is scanned by calling the procedure nextsym.

3.2 Skip rubbish

The second procedure that can be used as a parsing tool is the procedure that skips unexpected symbols in the input file. The header of this procedure is:

The first parameter infile should always be the input file variable. The other parameter followers is the set of symbols that are expected. The procedure skips symbols, which are not in this set of symbols, until a symbol is found which is in the set, or until the end of the input file is reached. The skipped symbols are reported to the error-handler [errors 3.1].

3.3 Back on the rails

The last procedure that can be used as a parsing tool is a kind of combination of the previous procedures. The header of this procedure is:

The first parameter infile is the input file variable. The second parameter s represents the set of expected symbols, and the third parameter followers represents the sets of symbols that may not be skipped. If the next scanned symbol is not in one of these sets of symbols, then symbols are skipped until a symbol is found which is in one of the sets, or until the end of the input file is reached. The skipped symbols are reported to the error-handler [error 3.1]. If a symbol is found in the input file that is in the set of expected symbols (represented by s), and the last parameter skip is equal to TRUE, then the procedure nextsym is again called. If no symbol is found in the set of expected symbols, then the error represented by the parameter error number with the extra message represented by the parameter correct is reported to the error-handler.

4 Interface with error-handler module

The error-handler makes use of a number of positions that are determined by the scanner module. Because this module inherits the environment of the error-handler module, three global functions are defined that are called within the error-handler module. The headers of these functions are:

These functions return the current input line number, the start position of the last scanned symbol, and the last position of the previously scanned symbol on the current line (respectively).

5 Implementation of the module

The main scanning module is implemented in three layers of procedures. The lowest layer reads lines from the input file into an internal buffer, and echoes these lines on the listing. The middle layer handles comments and the ends of lines. The highest layer recognizes the symbols. We deal with these three layers in the following subsections.

5.1 Highest layer: nextsym

The procedure nextsym calls the procedure nextch which returns the characters read by the middle layer, and has the following outline:

The variables previous pos and start pos, which are used by the functions at previous pos and at start pos, are updated by this procedure. The variables sym and scansym contain the representation and the kind of the symbol scanned by this procedure.

If the first non-space is an alphabetic character, a name is read by the procedure read name, and the procedure keyword checks whether this name is one of the keywords. If this is the case, then the variable scansym is changed into the associated symbol kind. Otherwise it remains equal to some sym, and the procedure check name is called, which generates an error message if the name has a form that could lead to errors in the generated Pascal program.

If the first non-space is not an alphabetic character, then the boolean variable end file, which is set by the lowest layer, is inspected to check whether the end of the file is reached. In this case, the variable scansym is set to the value end of file. Otherwise, the procedure special char is called, which attempts to scan a special symbol. If no symbol is found by this procedure, an error is signaled to the error-handler, and the procedure nextsym is recursively called.

The procedure read name reads characters (using the middle level procedure readch) until a non-identifier character is found. These characters are stored in the variable sym. An error is signaled to the error-handler if the name is too long.

The procedure check name checks whether the second character of the name is not an underscore-character and whether the second and the third characters are not both digits. In either of these cases an error is signaled to the error-handler.

5.2 Middle layer: nextch

The middle layer consists of the procedure nextch and the variable ch. Whenever this procedure is called the variable ch contains the next character from the input file. A single space character is returned for each comment and end of line. A comment is enclosed between question-mark characters. The procedure makes use of the lowest level procedures get one char and the lowest layer variable end file. Calling the procedure when the variable end file is equal to TRUE, leads to unpredictable behaviour.

5.3 Lowest layer: get one char

The lowest layer contains the procedure get one char and the variable end file. The procedure get one char returns the next character from the input file. All control characters are converted into spaces. The boolean variable end file is set to TRUE when the entire input file has been read.

This layer makes use of the variable get newline to delay the calls of the procedure read line, which reads the next line from the input file. This prevents the reading of the following input line before the last symbol of the current input line has been processed by the parser. If errors had been reported to the error-handler and the following line had been read, the error messages generated by the error-handler would have occurred on the line after the correct line.

6 Interface

This module used declarations from the following modules:

6.1 Exported types

The following type declarations are exported by this module:

6.2 Exported variables

The following variable declarations are exported by this module:

6.3 Exported functions and procedures

The following functions and procedure declarations are exported by this module:

This function returns the number of the current input line. See section 4

This function returns the start position of the last read symbol. See section 4

This function returns the last position of the previous read symbol. See section 4

This function returns the uppercase of ch when it was a lowercase.

This function returns the lowercase of ch when it was a capital.

This function returns the alfa x its corresponding capital alfa.

This function returns TRUE, when ch is an alphabetic character.

This function returns TRUE, when ch is a quote character.

This procedure reads a few characters (at least one) from the buffer and tries to recognize that group of characters as a symbol. If the buffer is empty a new line is read from the file infile. If this group is a special symbol, its corresponding symbol type is put in the global variable scansym. See section 5.1

This procedures expects to have read symbol s. If not, a syntax error message will be given. See section 3.1

This procedure checks if scansym is in the expected set of symbols, as represented by s. If so, the procedure nextsym is called if skip is equal to TRUE, but if scansym is not an expected symbol an error message is given and the procedure nextsym is called until scansym is in s or in followers or until the end of file is reached. If, after this skipping, scansym is in the set of expected symbols s, then the procedure nextsym is called once again, if skip is equal to TRUE. See section 3.3

This procedure skips all symbols unequal to followers or end_of_file. If skipping takes place, messages are given on the terminal and the listing. See section 3.2

This procedure opens the input file from which the input will be read. See section 1

This procedure initializes some global variables. See section 1

This procedure finalizes the scanner. See section 1

7 The listing

[ENVIRONMENT ('scanner.pen'),
 INHERIT     ('definitions.pen',
              '[-.screen]openfiles.pen',
              '[-.screen]screen.pen',
              'perform.pen',
              'listing.pen',
              'errors.pen')]

MODULE scanner;

(*  This module contains the scanner. The scanner reads the input and       *)
(*  returns the terminal symbols read by the parser. Besides this, the      *)
(*  module also makes a copy of the input into the listing. Because of this *)
(*  input lines are stored in a line buffer before being read.              *)
(*  It also includes some procedures to get back on the rails during the    *)
(*  parsing process.                                                        *)

[HIDDEN]
CONST
(* local for this module *)
  max_number        =   99; (* the maximum number which can be read         *)

  HT                =chr(9);(* horizontal tab                               *)
  ord_0             =   48; (* = ord ('0')                                  *)
  difference        =   32; (* = ord ('a') - ord ('A')                      *)

  apsgn_include     = '-include     : ';
  start_comment     = '?';           (* begin of comment *)
  end_comment       = '?';           (* end of comment   *)

TYPE
  input_symbols     = (                    (* represented by :     *)
                    end_of_file,        (* [end of file]        *)
                    some_sym,           (* [a name]             *)
                    options_sym,        (* OPTIONS              *)
                    classes_sym,        (* CLASSES              *)
                    node_sym,           (* NODE                 *)
                    types_sym,          (* TYPES                *)
                    functions_sym,      (* FUNCTIONS            *)
                    attribute_sym,      (* ATTRIBUTES           *)
                    rules_sym,          (* RULES                *)
                    root_sym,           (* ROOT                 *)
                    syn_sym,            (* SYNTHESIZED  or  SYN *)
                    inh_sym,            (* INHERITED   or   INH *)
                    at_sym,             (* AT                   *)
                    of_sym,             (* OF                   *)
                    case_sym,           (* CASE                 *)
                    esac_sym,           (* ESAC                 *)
                    others_sym,         (* OTHERS               *)
                    input_sym,          (* INPUT                *)
                    output_sym,         (* OUTPUT               *)
                    open_sym,           (* (                    *)
                    close_sym,          (* )                    *)
                    open_class_sym,     {} {                    *}
                    close_class_sym,    {* }                    {}
                    open_bracket_sym,   (* [                    *)
                    close_bracket_sym,  (* ]                    *)
                    becomes_sym,        (* =>                   *)
                    equal_sym,          (* =                    *)
                    colon_sym,          (* :                    *)
                    period_sym,         (* .                    *)
                    semicolon_sym,      (* ;                    *)
                    comma_sym,          (* ,                    *)
                    main_sym            (* #                    *)
                   );
  symbol_set    = SET OF input_symbols;

VAR
(* used in module OPTIONS *)
  inpas              : TEXT;
  sym                : alfa;     (* last read input name                   *)
  scansym            : input_symbols; (* internal repr. of just read symbol*)
  nr_value           : integer;

(* local for this module *)
  ch                 : [HIDDEN] char; (* current input character           *)
  alfastring         : [HIDDEN] alfa; (* last read input string            *)
  digits            ,                (* set of digits         : '0'..'9'   *)
  letters           ,                (* set of capital letters: 'A'..'Z'   *)
  id_characters      : [HIDDEN] SET OF char;  (* set of legal identifier characters *)


  input_buffer       : [HIDDEN] input_line;

  line_pos          ,  (* current position in the input line               *)
  start_pos         ,  (* the start position of the just read symbol       *)
  previous_pos      ,  (* the start position of the previous read symbol   *)
  input_linenr         (* the line number of the current input line        *)
                     : [HIDDEN] integer;

  get_newline       ,            (* TRUE if a new line should be read      *)
  end_file                       (* TRUE if the inputfile has become empty *)
                     : [HIDDEN] boolean;

7.1 Some global and elementary procedures



(*      SOME GLOBAL AND ELEMENTARY PROCEDURES                                *)

  [GLOBAL]
  FUNCTION input_line_nr : integer;                  (* used in module ERRORS *)
  (* This function returns the number of the current input line.              *)
  BEGIN
    input_line_nr := input_linenr
  END;

  [GLOBAL]
  FUNCTION at_start_pos : integer;                   (* used in module ERRORS *)
  (* This function returns the start position of the last read symbol.        *)
  BEGIN
     at_start_pos := start_pos
  END;

  [GLOBAL]
  FUNCTION at_previous_pos : integer;                (* used in module ERRORS *)
  (* This function returns the last position of the previous symbol.          *)
  BEGIN
     at_previous_pos := previous_pos
  END;


  FUNCTION upperconv (ch : char): char;
  (* This function returns the uppercase of ch when it was a lowercase.       *)
  BEGIN
    IF ch IN ['a'..'z']
    THEN upperconv := chr (ord (ch) - difference)
    ELSE upperconv := ch
  END;

  FUNCTION lowerconv (ch : char) :char;
  (* This function returns the lowercase of ch when it was a capital.         *)
  BEGIN
    IF ch IN ['A'..'Z']
    THEN lowerconv := chr (ord (ch) + difference)
    ELSE lowerconv := ch
  END;

  FUNCTION upperalfa (x : alfa) : alfa;
  (* This function returns the alfa x in its corresponding capital alfa.      *)
  VAR i : integer;
      upper : alfa;
  BEGIN
    upper := x;
    FOR i := 1 TO length(upper)
    DO upper[i] := upperconv (upper[i]);
    upperalfa := upper
  END;

  FUNCTION is_letter(ch:char):boolean;
  BEGIN
    is_letter := ch IN ['A'..'Z','a'..'z']
  END;

  FUNCTION is_quote(ch:CHAR):boolean;
  BEGIN
    is_quote := (ch='''') OR (ch='"')
  END;

7.2 Reading characters from the input


(*  This page contains the procedures that read single characters from the   *)
(*  input file. Input lines are read, and stored in an internal buffer.      *)

  [HIDDEN]
  PROCEDURE read_line(VAR infile:TEXT);
  (* This procedure reads one input line from infile into a buffer.          *)
  (* Lines longer than max_buffer_length are split without warning. The line *)
  (* is echoed in the listing with a line number which is increased first.   *)
  (* Tab characters are converted into 8 spaces. The boolean get_newline is  *)
  (* set to FALSE and the boolean end_file is set to TRUE if the end of the  *)
  (* input file is found.                                                    *)
  VAR
    c : char;
    i : integer;
  BEGIN
    input_buffer := '';
    get_newline:= FALSE;
    IF eof(infile)
    THEN end_file := TRUE
    ELSE BEGIN
           WHILE NOT eoln(infile) AND NOT eof(infile)
                 AND (length(input_buffer) < max_buffer_length)
           DO BEGIN
                read(infile, c);
                IF c = HT
                THEN input_buffer := input_buffer + '        '
                ELSE input_buffer := input_buffer + c
              END;
           IF eoln(infile) AND NOT eof(infile)
           THEN readln(infile);
           input_linenr := input_linenr + 1;
           echo_line_in_listing(input_linenr, input_buffer);
           IF   with_scan_echo
           THEN echo_line_on_screen(input_linenr, input_buffer);
           line_pos     := 1;
           previous_pos := 0
         END
  END;

  [HIDDEN]
  FUNCTION end_of_line : boolean;
  (* This procedure returns TRUE if the current contents of *)
  (* the buffer is completely used.                         *)
  BEGIN
    end_of_line := line_pos > length(input_buffer)
  END;

  [HIDDEN]
  FUNCTION get_one_char(VAR infile:TEXT) : char;
  (* This function gets one character from the input buffer. *)
  (* Characters smaller than space are converted to a space. *)
  (* If necessary a new line is read.                        *)
  VAR
    c : char;
  BEGIN
    perf_nr_calls(perf_get_one_char); (* for performance analysis *)
    IF get_newline
    THEN read_line(infile);
    IF end_of_line
    THEN BEGIN c := ' ';
               get_newline := TRUE
         END
    ELSE BEGIN
           c := input_buffer[line_pos];
           line_pos := line_pos + 1;
           IF c < ' '
           THEN c := ' '
         END;
    get_one_char := c
  END;

  [HIDDEN]
  PROCEDURE nextch(VAR infile:TEXT);
  (* This procedure gets a new character and skips comment *)

    PROCEDURE skip_comment;
    (* This procedure skips comment. It stops when end_comment is *)
    (* read or when the end of the file is reached                *)
    BEGIN
      WHILE (ch <> end_comment) AND NOT end_file
      DO ch := get_one_char(infile);
      ch := ' '
    END;

  BEGIN (* of nextch *)
    ch := get_one_char(infile);
    IF ch = start_comment
    THEN skip_comment
  END;

7.3 Main scanning procedure



(*      NEXT SYMBOL                                                           *)

  PROCEDURE nextsym(VAR infile:TEXT);
  (* This procedure reads a few (at least one) characters from the input *)
  (* buffer and tries to recognize that group of characters as a symbol. *)
  (* If this group is a special symbol, its corresponding symboltype is  *)
  (* put in scansym.                                                     *)

    PROCEDURE read_name;
    (* This procedure reads a name from the input buffer and converts *)
    (* lowercase letters to uppercase                                 *)
    BEGIN
      perf_nr_calls(perf_name);
      REPEAT
           sym := sym + lowerconv (ch);
           nextch(infile);
      UNTIL NOT ((length(sym) < alfaleng) AND (ch IN id_characters));
      IF ch IN id_characters
      THEN BEGIN
             mark_last_symbol(start_pos, length(sym));
             error(s_ntl,sym);
             WHILE ch IN id_characters
             DO nextch(infile);
           END
    END;


    PROCEDURE check_name(sym : alfa);
    (* This procedure checks whether the name can be used in the code         *)
    (* generation of the implementation. If not so a syntax error is          *)
    (* generated.                                                             *)
    BEGIN
      IF   sym.length > 1
      THEN IF   sym[2] = '_'
           THEN error(i_iln)
           ELSE IF   ('0' <= sym[2]) AND (sym[2] <= '9') AND (sym.length > 2)
                THEN IF   ('0' <= sym[3]) AND (sym[3] <= '9')
                     THEN error(i_iln)
    END;


    PROCEDURE keyword;
    (* This procedure tries to identify the just read sym as a keyword. This  *)
    (* is done by first looking at length of the sym, and then test whether   *)
    (* it is equal to one of the keywords that has this length.               *)
    BEGIN (* of identify *)
      scansym := some_sym;
      CASE sym.length OF
         2 : IF sym = 'at'          THEN scansym := at_sym         ELSE
             IF sym = 'of'          THEN scansym := of_sym;
         3 : IF sym = 'inh'         THEN scansym := inh_sym        ELSE
             IF sym = 'syn'         THEN scansym := syn_sym;
         4 : IF sym = 'case'        THEN scansym := case_sym       ELSE
             IF sym = 'esac'        THEN scansym := esac_sym       ELSE
             IF sym = 'node'        THEN scansym := node_sym       ELSE
             IF sym = 'root'        THEN scansym := root_sym;
         5 : IF sym = 'input'       THEN scansym := input_sym      ELSE
             IF sym = 'rules'       THEN scansym := rules_sym      ELSE
             IF sym = 'types'       THEN scansym := types_sym;
         6 : IF sym = 'others'      THEN scansym := others_sym     ELSE
             IF sym = 'output'      THEN scansym := output_sym;
         7 : IF sym = 'classes'     THEN scansym := classes_sym   ELSE
             IF sym = 'options'     THEN scansym := options_sym;
         9 : IF sym = 'functions'   THEN scansym := functions_sym ELSE
             IF sym = 'inherited'   THEN scansym := inh_sym;
        10 : IF sym = 'attributes'  THEN scansym := attribute_sym;
        11 : IF sym = 'synthesized' THEN scansym := syn_sym
      OTHERWISE
      END
    END;


    PROCEDURE special_char;
    (* This procedure tries to recognize sym as a special character. If this  *)
    (* is not possible, an error message will be given and the next character *)
    (* of the input is tried.                                                 *)

      PROCEDURE found (s: input_symbols);
      (* This procedure sets scansym to s and makes the next character of the *)
      (* input buffer available.                                              *)
      BEGIN
        scansym := s;
        nextch(infile)
      END;

    BEGIN (* of special char *)
      sym := ch;
      CASE ch OF
        '='   : BEGIN
                  nextch(infile);
                  IF   ch = '>'
                  THEN BEGIN
                         sym.length := 2;
                         sym[2] := '>';
                         found(becomes_sym);
                       END
                  ELSE scansym := equal_sym
                END;
        '{'   : found(open_class_sym);
        '}'   : found(close_class_sym);
        '#'   : found(main_sym);
        '['   : found(open_bracket_sym);
        ']'   : found(close_bracket_sym);
        '('   : found(open_sym);
        ')'   : found(close_sym);
        ','   : found(comma_sym);
        '.'   : found(period_sym);
        ':'   : found(colon_sym);
        ';'   : found(semicolon_sym)
      OTHERWISE  BEGIN
                   (* for screen module : *)
                   mark_last_symbol(start_pos, 1);
                   show_last_symbol(mark_skip);
                   error(s_ich,sym);
                   nextch(infile);
                   nextsym(infile)
                 END
      END
    END;

  BEGIN (* of nextsym *)
    perf_nr_calls(perf_nextsym);       (* for performance analysis *)
    show_last_symbol(mark_reset);      (* for screen module *)
    sym          := empty_alfa;
    previous_pos := line_pos-1;
    (* Skip spaces: *)
    WHILE (ch = ' ') AND NOT end_file
    DO nextch(infile);
    start_pos := pred(line_pos);
    IF   is_letter(ch)
    THEN (* a name is found *)
         BEGIN
           read_name;
           keyword;
           IF   scansym = some_sym
           THEN check_name(sym);
         END
    ELSE IF end_file
         THEN (* end of file is found *)
              scansym := end_of_file
         ELSE special_char;
    mark_last_symbol(start_pos, length(sym));
    show_last_symbol(mark_point);
  END;

7.4 Parsing tools



(*      GENERAL SCANNING PROCEDURES                                           *)

(*  This page contains some procedures that are often used by the parser and  *)
(*  take care of skipping parts of the input, until a correct symbol is       *)
(*  found.                                                                    *)

  PROCEDURE expect (VAR infile : TEXT; s : input_symbols; skip : boolean;
                    correct : alfa);
  (* This procedures expects s to have been read. If not, a syntax error      *)
  (* message will be given.                                                   *)
  BEGIN
    perf_nr_calls(perf_expect);
    IF   s <> scansym
    THEN error(m_sex, correct)
    ELSE IF   skip
         THEN nextsym(infile)
  END;

  PROCEDURE back_on_the_rails (VAR infile: TEXT; s, followers: symbol_set;
                                   correct: alfa; error_number: errors;
                                   skip: boolean);
  (* This procedure checks if scansym is the expected (= s) one.           *)
  (* If so, nextsym(infile) is called if skip is TRUE, but if scansym is   *)
  (* not expected an error message is given and nextsym(infile) is called  *)
  (* until scansym is s or in followers or end of file is reached.         *)
  (* If, after this skipping, scansym is expected (also IN s),             *)
  (* nextsym(infile) is called once again if skip is TRUE.                 *)
  BEGIN
    perf_nr_calls(perf_back_on_the_rails);
    followers := followers + s + [end_of_file];
    IF NOT(scansym IN followers)
    THEN BEGIN
           skip_start;
           REPEAT
             (* for screen module *)
             show_last_symbol(mark_skip);
             nextsym(infile)
           UNTIL (scansym IN followers);
           skip_end;
         END;
    IF scansym IN s
    THEN BEGIN
           IF skip
           THEN nextsym(infile)
         END
    ELSE error (error_number, correct);
  END;

  PROCEDURE skip_rubbish (VAR infile:TEXT; followers:symbol_set);
  (* This procedure skips all symbols unequal to followers or end_of_file. *)
  (* If skipping takes place, messages are given on the terminal and the   *)
  (* listing.                                                              *)
  BEGIN
    perf_nr_calls(perf_skip);
    followers := followers + [end_of_file];
    IF NOT (scansym IN followers)
    THEN BEGIN
           skip_start;
           REPEAT
             (* for screen module : *)
             show_last_symbol(mark_skip);
             nextsym(infile)
           UNTIL scansym IN followers;
           skip_end;
         END
  END;

7.5 Initialization and finalization



(*      INITIALIZATION AND FINALIZATION                                       *)

  PROCEDURE open_scanner_input_file;
  (* This procedure opens the input file from which the input will be read.   *)
  BEGIN
    ask_for_input_file(inpas, 'INP');
  END;

  PROCEDURE init_scanner;
  (* This procedure initializes some global variables *)
  VAR i : integer;
  BEGIN
    writeln (version);

    digits               := ['0'..'9'];
    letters              := ['A'..'Z','a'..'z'];
    id_characters        := letters + digits + ['_'];

    input_linenr         := 0;

    end_file             := FALSE;
    get_newline          := TRUE;
    sym                  := 'FIRST LINE'; (* in case of error in first line *)
    ch                   := ' ';

    nextsym(inpas)
  END;

  PROCEDURE fini_scanner;
  (* This procedure finalizes the scanner *)
  BEGIN
    close(inpas);
  END;

END.


My life as a hacker | My home page