home *** CD-ROM | disk | FTP | other *** search
- /* symtab.h:
-
- Shared declarations for symbol-table routines. Note: uses
- declarations in defs.h.
-
- Copyright (C) 1991 by Robert K. Moniot.
- This program is free software. Permission is granted to
- modify it and/or redistribute it, retaining this notice.
- No guarantees accompany this software.
-
-
- */
-
- #ifdef SYMTAB /* "home" for variables is symtab.c */
- #define SYM_SHARED
- #else
- #define SYM_SHARED extern
- #endif
-
-
- /* Definitions of symbol table information */
-
- /* Token subclasses (classes are in tokdefs.h)
- */
-
- #define relop_EQ 0
- #define relop_NE 1
- #define relop_LE 2
- #define relop_LT 3
- #define relop_GE 4
- #define relop_GT 5
-
-
-
- /* Storage Class types for variables, consts, and externals */
- #define class_VAR 0
- #define class_SUBPROGRAM 1
- #define class_COMMON_BLOCK 2
- #define class_STMT_FUNCTION 3
- #define class_LABEL 4
-
-
- /* Data types for variables, consts, and externals */
- /* N.B. 0 thru 7 are wired into lookup tables in exprtype.c */
- #define type_UNDECL 0
- #define type_INTEGER 1
- #define type_REAL 2
- #define type_DP 3
- #define type_COMPLEX 4
- #define type_LOGICAL 5
- #define type_STRING 6
- #define type_HOLLERITH 7
- #define type_GENERIC 8
- #define type_SUBROUTINE 9
- #define type_COMMON_BLOCK 10
- #define type_PROGRAM 11
- #define type_BLOCK_DATA 12
- #define type_LABEL 13
-
- /* test for types usable in exprs */
- #define is_computational_type(t) ((t) <= 7)
- /* test for arith, char, or logical type */
- #define is_const_type(t) ((datatype_of(t) > 0) && (datatype_of(t) <= 6))
-
-
- typedef unsigned char BYTE;
-
-
- /* Array of class and type name translations */
- #ifdef SYMTAB
- char *class_name[] = {
- "",
- "subprog",
- "common",
- "stmt fun",
- "label",
- };
- char *type_name[] = {
- "undf",
- "intg",
- "real",
- "dble",
- "cplx",
- "logl",
- "char",
- "holl",
- "genr",
- "subr",
- "comm",
- "prog",
- "data",
- "labl",
- };
-
- /* Typical sizes of objects of each data type */
- BYTE type_size[]={ /* for use in check_mixed_common */
- 0, /*undf*/
- 4, /*intg*/
- 4, /*real*/
- 8, /*dble*/
- 8, /*cplx*/
- 4, /*logl*/
- 1, /*char*/
- 4, /*holl*/
- 0, /*genr*/
- 0, /*subr*/
- 0, /*comm*/
- 0, /*prog*/
- 0, /*data*/
- 0, /*labl*/
- };
-
- #else
- extern char *class_name[];
- extern char *type_name[];
- extern BYTE type_size[];
- #endif
-
-
- /* implicit and default typing lookup table */
- SYM_SHARED
- int implicit_type[26]; /* indexed by [char - 'A'] */
-
-
-
- /* Declaration of Token data structure. N.B. do not change without
- consulting preamble of fortran.y for uses with nonterminals.
- */
- struct tokstruct {
- union {
- int integer;
- double dbl;
- char *string;
- } value;
- struct tokstruct *next_token;
- short class,subclass;
- unsigned line_num; /* Line and column where token occurred */
- unsigned col_num : 8;
- };
-
- typedef struct tokstruct Token;
-
- #define YYSTYPE Token /* Type defn for yylval and Yacc stack */
-
-
-
- SYM_SHARED
- unsigned long loc_symtab_top, /* Next avail spot in local symbol table */
- glob_symtab_top; /* Ditto global */
-
- SYM_SHARED
- char strspace[STRSPACESZ]; /* String space for storing identifiers */
- /* Stringspace is partitioned into local (growing from bottom up)
- and global (growing from top down). */
-
- SYM_SHARED
- unsigned long loc_str_top, /* Top of local stringspace */
- glob_str_bot; /* Bottom of global stringspace */
-
- SYM_SHARED
- unsigned long token_space_top; /* Top of token space */
- SYM_SHARED
- Token tokenspace[TOKENSPACESZ];
-
-
- /* Define names for anonymous things */
- #ifdef SYMTAB
- char *blank_com_name = "%BLANK", /* id for blank common entry in symtab */
- *unnamed_prog="%MAIN"; /* id for unnamed program module */
- #else
- extern char *blank_com_name,
- *unnamed_prog;
- #endif
-
- /* Symbol table argument list declarations */
-
- typedef union { /* InfoUnion: misc info about symtab entry */
- unsigned long array_dim; /* array size and no. of dims */
- struct ALHead *arglist; /* ptr to func/subr argument list */
- struct CMHead *comlist; /* ptr to common block list */
- struct TLHead *toklist; /* ptr to token list */
- struct IInfo *intrins_info;/* ptr to intrinsic func info */
- int int_value; /* value of integer parameter */
- } InfoUnion;
-
- typedef struct { /* ArgListElement: holds subprog argument data */
- InfoUnion info;
- BYTE type;
- unsigned is_lvalue: 1,
- set_flag: 1,
- assigned_flag: 1,
- used_before_set: 1,
- array_var: 1,
- array_element: 1,
- declared_external: 1;
- } ArgListElement;
-
-
- typedef struct ALHead { /* ArgListHeader: head node of argument list */
- BYTE type;
- short numargs;
- ArgListElement *arg_array;
- struct SymtEntry *module;
- char *filename,*topfile;
- unsigned
- line_num,
- is_defn: 1,
- is_call: 1,
- external_decl: 1, /* EXTERNAL decl, not arg list */
- actual_arg: 1; /* subprog passed as arg */
- struct ALHead *next;
- } ArgListHeader;
-
- /* Symbol table common block list declarations */
-
- typedef struct { /* ComListElement: holds common var data */
- unsigned long dimen_info;
- BYTE type;
- } ComListElement;
-
- typedef struct CMHead { /* ComListHeader: head node of common var list */
- short numargs;
- short flags;
- unsigned line_num;
- ComListElement *com_list_array;
- struct SymtEntry *module;
- char *filename,*topfile;
- struct CMHead *next;
- } ComListHeader;
-
-
- typedef struct TLHead { /* TokenListHeader: head node of token list */
- Token *tokenlist;
- struct TLHead *next;
- char *filename;
- unsigned line_num;
- unsigned
- external_decl:1,
- actual_arg:1;
- } TokenListHeader;
-
-
- /* Structure for intrinsic-function info */
- typedef struct IInfo{
- char *name;
- short num_args,arg_type,result_type;
- } IntrinsInfo;
-
-
-
-
- /* Identifier symbol table declaration */
-
-
- typedef struct SymtEntry{
- char *name; /* Identifier name in stringspace */
- InfoUnion info;
- struct SymtEntry *equiv_link; /* Link for equivalence lists */
- BYTE type; /* Type & storage class: see macros below */
- /* Flags: if changed, update macro clear_symtab_flags below */
- unsigned
- used_flag: 1,
- set_flag: 1,
- assigned_flag: 1,
- used_before_set: 1,
- is_current_module: 1,
- library_module: 1,
- array_var: 1,
- common_var: 1,
- entry_point: 1,
- parameter: 1,
- argument: 1,
- external: 1,
- intrinsic: 1,
- invoked_as_func: 1,
- defined_in_include: 1,
- declared_external: 1;
- } symtab;
-
-
-
- /* Macro to clear all flags in symbol table entry */
-
- #define clear_symtab_flags(S) ((S)->used_flag= (S)->set_flag= \
- (S)->assigned_flag= (S)->used_before_set= (S)->is_current_module= \
- (S)->library_module= \
- (S)->array_var= (S)->common_var= (S)->entry_point= (S)->parameter= \
- (S)->argument= (S)->external= (S)->intrinsic= \
- (S)->invoked_as_func= (S)->defined_in_include= \
- (S)->declared_external= \
- 0)
-
-
- /* These macros pack and unpack datatype and storage class in type
- field of symbol table entry. Datatype is least 4 bits. */
-
- #define datatype_of(TYPE) ((TYPE) & 0xF)
- #define storage_class_of(TYPE) ((TYPE) >> 4)
- #define type_byte(SCLASS,DTYPE) (((SCLASS)<<4) + (DTYPE))
-
-
- /* This macro is for pattern matching in flag checking */
-
- #define flag_combo(A,B,C) (((A)<<2) | ((B)<<1) | (C))
-
-
- /* These macros are for dimensions & sizes of arrays */
-
- #define array_dims(dim_info) ((dim_info)&0xF)
- #define array_size(dim_info) ((dim_info)>>4)
- #define array_dim_info(dim,size) (((long)(size)<<4)+(dim))
-
-
-
- /* Defns used by expression type propagation mechanisms
- in fortran.y and exprtype.c The flags go in token.subclass
- */
-
- #define make_true(flag,x) ((x) |= (flag)) /* x.flag <-- true */
- #define make_false(flag,x) ((x) &= ~(flag)) /* x.flag <-- false */
- #define is_true(flag,x) ((x) & (flag)) /* x.flag == true? */
- #define copy_flag(flag,x,y) ((x) |= ((y)&(flag))) /* x.flag <-- y.flag */
-
- #define ID_EXPR 0x1
- #define LVALUE_EXPR 0x2
- #define CONST_EXPR 0x4
- #define NUM_CONST 0x8
- #define ARRAY_ID_EXPR 0x10
- #define INT_QUOTIENT_EXPR 0x20
- #define STMT_FUNCTION_EXPR 0x40
- #define SET_FLAG 0x80 /* these are for id's and lvalues */
- #define ASSIGNED_FLAG 0x100
- #define USED_BEFORE_SET 0x200
- #define COMMA_FLAG 0x400 /* keeps track of extra or missing commas
- in exprlists */
-
-
- SYM_SHARED
- symtab glob_symtab[GLOBSYMTABSZ],
- loc_symtab[LOCSYMTABSZ];
-
- /* Identifier hashtable declaration */
-
- SYM_SHARED
- struct {
- char *name; /* Identifier name in stringspace */
- symtab *loc_symtab, /* Local symtab entry for vars etc. */
- *glob_symtab, /* Global symtab entry for vars etc. */
- *com_loc_symtab,/* Local symtab entry for common blocks */
- *com_glob_symtab;/* Global ditto */
- } hashtab[HASHSZ];
-
-
-
- /* Shared routines */
-
- /* in fortran.y/fortran.c */
- void
- check_seq_header();
-
- /* in prsymtab.c */
- void
- debug_symtabs(), print_loc_symbols();
-
- /* in symtab.c */
- void
- call_func(), call_subr(), declare_type(), def_arg_name(),
- def_array_dim(), def_com_block(), def_com_variable(),
- def_equiv_name(), def_ext_name(), def_function(), def_intrins_name(),
- def_parameter(),
- def_stmt_function(), do_ASSIGN(), do_assigned_GOTO(), do_ENTRY(),
- do_RETURN(), equivalence(),
- init_globals(), init_symtab(),
- process_lists(), ref_array(), ref_variable(),
- set_implicit_type(),
- stmt_function_stmt(),use_actual_arg(), use_implied_do_index(),
- use_io_keyword(),
- use_lvalue(), use_parameter(),
- use_var_as_subscr(), use_variable();
-
- Token
- *new_token();
-
- symtab
- *install_local(), *install_global();
-
- unsigned
- hash_lookup();
-
- int
- def_curr_module(), get_type(), int_expr_value();
-
- char *
- token_name();
- /* in hash.c (now symtab.c) */
- unsigned long
- hash(), kwd_hash(), rehash();
-
- /* in symtab2.c */
- void /* exprtype routines */
- binexpr_type(),unexpr_type(),assignment_stmt_type(),
- func_ref_expr(),primary_id_expr();
-
-
-
-
-