v21i065: Pascal to C translator, Part20/32

Rich Salz rsalz at uunet.uu.net
Thu Mar 29 23:48:32 AEST 1990


Submitted-by: Dave Gillespie <daveg at csvax.caltech.edu>
Posting-number: Volume 21, Issue 65
Archive-name: p2c/part20

#! /bin/sh
# This is a shell archive.  Remove anything before this line, then unpack
# it by saving it into a file and typing "sh file".  To overwrite existing
# files, type "sh file -c".  You can also feed this as standard input via
# unshar, or by typing "sh <file", e.g..  If this archive is complete, you
# will see the following message at the end:
#		"End of archive 20 (of 32)."
# Contents:  src/trans.h.1
# Wrapped by rsalz at litchi.bbn.com on Mon Mar 26 14:29:43 1990
PATH=/bin:/usr/bin:/usr/ucb ; export PATH
if test -f 'src/trans.h.1' -a "${1}" != "-c" ; then 
  echo shar: Will not clobber existing file \"'src/trans.h.1'\"
else
echo shar: Extracting \"'src/trans.h.1'\" \(48347 characters\)
sed "s/^X//" >'src/trans.h.1' <<'END_OF_FILE'
X/* "p2c", a Pascal to C translator, version 1.14.
X   Copyright (C) 1989 David Gillespie.
X   Author's address: daveg at csvax.caltech.edu; 256-80 Caltech/Pasadena CA 91125.
X
XThis program is free software; you can redistribute it and/or modify
Xit under the terms of the GNU General Public License as published by
Xthe Free Software Foundation (any version).
X
XThis program is distributed in the hope that it will be useful,
Xbut WITHOUT ANY WARRANTY; without even the implied warranty of
XMERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
XGNU General Public License for more details.
X
XYou should have received a copy of the GNU General Public License
Xalong with this program; see the file COPYING.  If not, write to
Xthe Free Software Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. */
X
X
X
X
X#ifdef __STDC__
X# define PP(x)  x             /* use true prototypes */
X# define PV()   (void)
X# define Anyptr void
X# define __CAT__(a,b)a##b
X#else
X# define PP(x)  ()            /* use old-style declarations */
X# define PV()   ()
X# define Anyptr char
X# define __ID__(a)a
X# define __CAT__(a,b)__ID__(a)b
X#endif
X
X#define Static                /* For debugging purposes */
X
X
X
X#include <stdio.h>
X
X
X/* If the following heuristic fails, compile -DBSD=0 for non-BSD systems,
X   or -DBSD=1 for BSD systems. */
X
X#ifdef M_XENIX
X# define BSD 0
X#endif
X
X#ifdef FILE       /* a #define in BSD, a typedef in SYSV (hp-ux, at least) */
X# ifndef BSD
X#  define BSD 1
X# endif
X#endif
X
X#ifdef BSD
X# if !BSD
X#  undef BSD
X# endif
X#endif
X
X
X#ifdef __STDC__
X# include <stddef.h>
X# include <stdlib.h>
X# include <limits.h>
X#else
X# ifndef BSD
X#  include <malloc.h>
X#  include <memory.h>
X#  include <values.h>
X# endif
X# define EXIT_SUCCESS 0
X# define EXIT_FAILURE 1
X# define CHAR_BIT 8
X# define LONG_MAX (((unsigned long)~0L) >> 1)
X# define LONG_MIN (- LONG_MAX - 1)
X#endif
X
X
X
X#ifdef BSD
X# include <strings.h>
X# define memcpy(a,b,n) bcopy(b,a,n)
X# define memcmp(a,b,n) bcmp(a,b,n)
Xchar *malloc(), *realloc();
X#else
X# include <string.h>
X#endif
X
X#include <ctype.h>
X
X
X#ifdef __GNUC__      /* Fast, in-line version of strcmp */
X# define strcmp(a,b) ({ char *_aa = (a), *_bb = (b); int _diff;  \
X			for (;;) {    \
X			    if (!*_aa && !*_bb) { _diff = 0; break; }   \
X                            if (*_aa++ != *_bb++)    \
X				{ _diff = _aa[-1] - _bb[-1]; break; }   \
X			} _diff; })
X#endif
X
X
X#if defined(HASDUMPS) && defined(define_globals)
X# define DEFDUMPS
X#endif
X
X
X
X/* Constants */
X
X#undef MININT      /* we want the Pascal definitions, not the local C definitions */
X#undef MAXINT
X
X#define MININT     0x80000000
X#define MAXINT     0x7fffffff
X
X
X#ifndef EXIT_SUCCESS
X# define EXIT_SUCCESS  0
X# define EXIT_FAILURE  1
X#endif
X
X
X#ifndef P2C_HOME
X# ifdef citPWS
X#  define    P2C_HOME        "/lib/p2c"
X# else
X#  define    P2C_HOME        "/usr/local/p2c"     /* sounds reasonable... */
X# endif
X#endif
X
X#ifdef define_globals
Xchar *p2c_home = P2C_HOME;
X#else
Xextern char *p2c_home;
X#endif
X
X#define P2C_VERSION  "1.14"
X
X
X
X
X/* Types */
X
X#ifdef __STDC__
Xtypedef void *anyptr;
X#else
Xtypedef char *anyptr;
X#endif
X
Xtypedef unsigned char uchar;
X
X
X
X/* Ought to rearrange token assignments at the next full re-compile */
X
Xtypedef enum E_token {
X    TOK_NONE,
X
X    /* reserved words */
X    TOK_AND, TOK_ARRAY, TOK_BEGIN, TOK_CASE, TOK_CONST,
X    TOK_DIV, TOK_DO, TOK_DOWNTO, TOK_ELSE, TOK_END,
X    TOK_FILE, TOK_FOR, TOK_FUNCTION, TOK_GOTO, TOK_IF,
X    TOK_IN, TOK_LABEL, TOK_MOD, TOK_NIL, TOK_NOT,
X    TOK_OF, TOK_OR, TOK_PACKED, TOK_PROCEDURE, TOK_PROGRAM,
X    TOK_RECORD, TOK_REPEAT, TOK_SET, TOK_THEN, TOK_TO,
X    TOK_TYPE, TOK_UNTIL, TOK_VAR, TOK_WHILE, TOK_WITH,
X
X    /* symbols */
X    TOK_DOLLAR, TOK_STRLIT, TOK_LPAR, TOK_RPAR, TOK_STAR,
X    TOK_PLUS, TOK_COMMA, TOK_MINUS, TOK_DOT, TOK_DOTS,
X    TOK_SLASH, TOK_INTLIT, TOK_REALLIT, TOK_COLON, TOK_ASSIGN,
X    TOK_SEMI, TOK_NE, TOK_LT, TOK_GT, TOK_LE, TOK_GE,
X    TOK_EQ, TOK_LBR, TOK_RBR, TOK_HAT,
X    TOK_INCLUDE, TOK_ENDIF,
X    TOK_IDENT, TOK_MININT, TOK_EOF,
X
X    /* C symbols */
X    TOK_ARROW, TOK_AMP, TOK_VBAR, TOK_BANG,
X    TOK_TWIDDLE, TOK_PERC, TOK_QM,
X    TOK_LTLT, TOK_GTGT, TOK_EQEQ, TOK_BANGEQ,
X    TOK_PLPL, TOK_MIMI, TOK_ANDAND, TOK_OROR,
X    TOK_LBRACE, TOK_RBRACE, TOK_CHARLIT,
X
X    /* HP Pascal tokens */
X    TOK_ANYVAR, TOK_EXPORT, TOK_IMPLEMENT, TOK_IMPORT, TOK_MODULE,
X    TOK_OTHERWISE, TOK_RECOVER, TOK_TRY,
X
X    /* Turbo Pascal tokens */
X    TOK_SHL, TOK_SHR, TOK_XOR, TOK_INLINE, TOK_ABSOLUTE,
X    TOK_INTERRUPT, TOK_ADDR, TOK_HEXLIT,
X
X    /* Oregon Software Pascal tokens */
X    TOK_ORIGIN, TOK_INTFONLY,
X
X    /* VAX Pascal tokens */
X    TOK_REM, TOK_VALUE, TOK_VARYING, TOK_OCTLIT, TOK_COLONCOLON,
X    TOK_STARSTAR,
X
X    /* Modula-2 tokens */
X    TOK_BY, TOK_DEFINITION, TOK_ELSIF, TOK_FROM, TOK_LOOP,
X    TOK_POINTER, TOK_QUALIFIED, TOK_RETURN,
X
X    /* UCSD Pascal tokens */
X    TOK_SEGMENT,
X
X    TOK_LAST
X} Token;
X
X#ifdef define_globals
Xchar *toknames[(int)TOK_LAST] = { "",
X    "AND", "ARRAY", "BEGIN", "CASE", "CONST",
X    "DIV", "DO", "DOWNTO", "ELSE", "END",
X    "FILE", "FOR", "FUNCTION", "GOTO", "IF",
X    "IN", "LABEL", "MOD", "NIL", "NOT",
X    "OF", "OR", "PACKED", "PROCEDURE", "PROGRAM",
X    "RECORD", "REPEAT", "SET", "THEN", "TO",
X    "TYPE", "UNTIL", "VAR", "WHILE", "WITH",
X
X    "a '$'", "a string literal", "a '('", "a ')'", "a '*'",
X    "a '+'", "a comma", "a '-'", "a '.'", "'..'",
X    "a '/'", "an integer", "a real number", "a colon", "a ':='",
X    "a semicolon", "a '<>'", "a '<'", "a '>'", "a '<='", "a '>='",
X    "an '='", "a '['", "a ']'", "a '^'",
X    "an \"include\" file", "$end$",
X    "an identifier", "an integer", "end of file",
X
X    "an '->'", "an '&'", "a '|'", "a '!'", 
X    "a '~'", "a '%'", "a '?'",
X    "a '<<'", "a '>>'", "a '=='", "a '!='",
X    "a '++'", "a '--'", "a '&&'", "a '||'",
X    "a '{'", "a '}'", "a character literal",
X
X    "ANYVAR", "EXPORT", "IMPLEMENT", "IMPORT", "MODULE",
X    "OTHERWISE", "RECOVER", "TRY",
X
X    "SHL", "SHR", "XOR", "INLINE", "ABSOLUTE",
X    "INTERRUPT", "an '@'", "a hex integer",
X
X    "ORIGIN", "INTF-ONLY",
X
X    "REM", "VALUE", "VARYING", "an octal integer", "a '::'",
X    "a '**'",
X
X    "BY", "DEFINITION", "ELSIF", "FROM", "LOOP",
X    "POINTER", "QUALIFIED", "RETURN",
X
X    "SEGMENT"
X} ;
X#else
Xextern char *toknames[];
X#endif /*define_globals*/
X
Xtypedef struct S_strlist {
X    struct S_strlist *next;
X    long value;
X    char s[1];
X} Strlist;
X
X
X
Xtypedef struct S_value {
X    struct S_type *type;
X    long i;
X    char *s;
X} Value;
X
X
X
X/* "Symbol" notes:
X *
X * The symbol table is used for several things.  Mainly it records all
X * identifiers in the Pascal program (normally converted to upper case).
X * Also used for recording certain properties about C and Pascal names.
X *
X * The symbol table is a hash table of binary trees.
X */
X
X#define AVOIDNAME  0x1         /* Avoid this name in C code */
X#define WARNNAME   0x2	       /* Warn if using this name in C code */
X#define AVOIDGLOB  0x4	       /* Avoid C name except private to module */
X#define NOSIDEEFF  0x8	       /* Function by this name has no side effects */
X#define STRUCTF    0x10	       /* Function by this name is a StructFunction */
X#define STRLAPF    0x20	       /* Function by this name is a StrlapFunction */
X#define LEAVEALONE 0x40	       /* Do not use custom handler for function */
X#define DETERMF    0x80	       /* Function by this name is Deterministic */
X#define FMACREC    0x100       /* Used by FieldMacro stuff */
X#define AVOIDFIELD 0x200       /* Avoid this name as a struct field name */
X#define NEEDSTATIC 0x400       /* This name must be declared static */
X#define KWPOSS     0x800       /* This word may be a keyword */
X#define FUNCBREAK  0x7000      /* Line breaking flags (see sys.p2crc) */
X# define FALLBREAK  0x1000     /*  Break at all commas if at any */
X# define FSPCARG1   0x2000     /*  First argument is special */
X# define FSPCARG2   0x3000     /*  First two arguments are special */
X# define FSPCARG3   0x4000     /*  First three arguments are special */
X#define WARNLIBR   0x8000      /* Warn for all uses of this library function */
X#define FWDPARAM   0x10000     /* Was a param name for forward-declared func */
X#define SSYNONYM   0x20000     /* Symbol is a synonym for another */
X
Xtypedef struct S_symbol {
X    struct S_symbol *left;     /* Left pointer in binary tree */
X    struct S_symbol *right;    /* Right pointer in binary tree */
X    struct S_meaning *mbase;   /* First normal meaning for this symbol */
X    struct S_meaning *fbase;   /* First record-field meaning for this symbol */
X    Strlist *symbolnames;      /* List of NameOf's for this name */
X    long flags;		       /* (above) */
X    Token kwtok;	       /* Token, if symbol is a keyword */
X    char name[1];              /* Pascal name (actually variable-sized) */
X} Symbol;
X
X
X
X/* "Meaning" notes:
X *
X * This represents one meaning of a symbol (see below).  Meanings are
X * organized in a tree of contexts (i.e., scopes), and also in linked
X * lists of meanings per symbol.  Fields described in the following are
X * undefined for kinds where they are not listed.  Other fields are
X * defined in all kinds of meanings.
X *
X * MK_MODULE:  Program, module, or unit.
X *    mp->anyvarflag = 1 if main program, 0 if module.
X *    mp->cbase => First meaning in module's context.
X *
X * MK_CONST:  Pascal CONST.
X *    mp->type => Type of constant, same as mp->constdefn->type & mp->val.type.
X *    mp->anyvarflag = 1 if FoldConstants was true when defined.
X *    mp->constdefn => Expression for the value of the constant.
X *    mp->val = Value of the const, if can be evaluated, else val.type is NULL.
X *    mp->xnext => Next constant in enumeration, else NULL.
X *    mp->isreturn = 1 if constant was declared as a macro (with #define).
X *
X * MK_TYPE:  Pascal type name.
X *    mp->type => Type which name represents.
X *
X * MK_VAR:  Normal variable.
X *    mp->type => Type of variable.
X *    mp->constdefn => Initializer for variable, else NULL.
X *    mp->varstructflag = 1 if variable is in parent function's varstruct.
X *    mp->isforward = 1 if should be declared static.
X *    mp->isfunction = 1 if should be declared extern.
X *    mp->namedfile = 1 if this file variable has a shadow file-name variable.
X *    mp->bufferedfile = 1 if this file variable has a shadow buffer variable.
X *    mp->val.s => name format string if temporary var, else NULL.
X *
X * MK_VARREF:  Variable always referenced through a pointer.
X *    mp->type => Type "pointer to T" where T is type of variable.
X *    mp->constdefn => Initializer for the pointer, else NULL.
X *    (Others same as for MK_VAR.)
X *
X * MK_VARMAC:  Variable which has a VarMacro.
X *    mp->type => Type of variable.
X *    mp->constdefn => Expression for VarMacro definition.
X *    (Others same as for MK_VAR.)
X *
X * MK_SPVAR:  Special variable.
X *    mp->handler => C function to parse and translate the special variable.
X *
X * MK_FIELD:  Record/struct field name.
X *    mp->ctx, cbase = unused (unlike other meanings).
X *    mp->cnext => Next field in record or variant.
X *    mp->type => Type of field (base type if a bit-field).
X *    mp->rectype => Type of containing record.
X *    mp->constdefn => Expression for definition if FieldMacro, else NULL.
X *    mp->val.i = Number of bits if bit-field, or 0 if normal field.
X *    mp->val.type => True type of bit-field, else same as mp->type.
X *    mp->isforward = 1 if tag field for following variant, else 0.
X *    mp->namedfile = 1 if this file field has a shadow file-name field.
X *    mp->bufferedfile = 1 if this file field has a shadow buffer field.
X *
X * MK_VARIANT:  Header for variant record case.
X *    mp->ctx => First field in variant (unlike other meanings).
X *    mp->cbase = unused (unlike other meanings).
X *    mp->cnext => Next variant in record (or next sub-variant in variant).
X *    mp->rectype => Type of containing record.
X *    mp->val = Tag value of variant.
X *
X * MK_LABEL:  Statement label.
X *    mp->val.i => Case number if used by non-local gotos, else -1.
X *    mp->xnext => MK_VAR representing associated jmp_buf variable.
X *    (All optional fields are unused.)
X *
X * MK_FUNCTION:  Procedure or function.
X *    mp->type => TK_FUNCTION type.
X *    mp->cbase => First meaning in procedure's context (when isfunction is 1,
X *		   this will always be the return-value meaning.)
X *    mp->val.i => Body of the function (cast to Stmt *).
X *    mp->constdefn => Expression for definition if FuncMacro, else NULL.
X *    mp->handler => C function to adjust parse tree if predefined, else NULL.
X *    mp->isfunction = 1 if function, 0 if procedure.
X *    mp->isforward = 1 if function has been declared forward.
X *    mp->varstructflag = 1 if function has a varstruct.
X *    mp->needvarstruct = 1 if no varstruct yet but may need one.
X *    mp->namedfile = 1 if function should be declared "inline".
X *
X * MK_SPECIAL:  Special, irregular built-in function.
X *    mp->handler => C function to parse and translate the special function.
X *    mp->constdefn => Expression for definition if FuncMacro, else NULL.
X *    mp->isfunction = 1 if function, 0 if procedure.
X *
X * MK_PARAM:  Procedure or function parameter, or function return value.
X *    mp->type => Type of parameter.
X *    mp->isreturn = 1 if a function return value (not on parameter list).
X *    mp->xnext => Next parameter of function.
X *    mp->fakeparam = 1 if a fake parameter (e.g., conformant array size).
X *    mp->othername => Name of true param if this one is a local copy.
X *    mp->rectype => Type of true param if this one is a local copy.
X *		     If a normal copy param, will be "pointer to" mp->type.
X *		     If copied for varstruct reasons, will be same as mp->type.
X *    mp->varstructflag = 1 if variable is in parent function's varstruct.
X *
X * MK_VARPARAM:  VAR parameter, or StructFunction return value.
X *    mp->type => Type "pointer to T" where T is type of parameter.
X *    mp->anyvarflag = 1 if no type checking is to be applied to parameter.
X *    mp->isreturn = 1 if a StructFunction return value (will be first param).
X *    (Others same as for MK_PARAM.)
X *
X * MK_VARPARAM with mp->type == tp_anyptr:  Turbo "typeless var" parameter.
X *    mp->type = tp_anyptr.
X *    mp->anyvarflag = 1.
X *    (Others same as for MK_PARAM.)
X *
X * MK_VARPARAM with mp->type == tp_strptr:  HP Pascal "var s:string" parameter.
X *    mp->type = tp_strptr.
X *    mp->anyvarflag = 1 if a separate "strmax" parameter is passed.
X *    (Others same as for MK_PARAM.)
X *
X * MK_SYNONYM:  Meaning which should be treated as identical to another.
X *    mp->xnext => Actual meaning to be used.
X *
X */
X
Xenum meaningkind {
X    MK_NONE, MK_SPECIAL,
X    MK_MODULE, MK_FUNCTION, MK_CONST, MK_VAR, MK_TYPE,
X    MK_FIELD, MK_LABEL, MK_VARIANT,
X    MK_PARAM, MK_VARPARAM, MK_VARREF, MK_VARMAC,
X    MK_SPVAR, MK_SYNONYM,
X    MK_LAST
X} ;
X
X#ifdef DEFDUMPS
Xchar *meaningkindnames[(int)MK_LAST] = {
X    "MK_NONE", "MK_SPECIAL",
X    "MK_MODULE", "MK_FUNCTION", "MK_CONST", "MK_VAR", "MK_TYPE",
X    "MK_FIELD", "MK_LABEL", "MK_VARIANT",
X    "MK_PARAM", "MK_VARPARAM", "MK_VARREF", "MK_VARMAC",
X    "MK_SPVAR", "MK_SYNONYM"
X} ;
X#endif /*DEFDUMPS*/
X
Xtypedef struct S_meaning {
X    struct S_meaning *snext;   /* Next meaning for this symbol */
X    struct S_meaning *cnext;   /* Next meaning in this meaning's context */
X    struct S_meaning *cbase;   /* First meaning in this context */
X    struct S_meaning *ctx;     /* Context of this meaning */
X    struct S_meaning *xnext;   /* (above) */
X    struct S_symbol *sym;      /* Symbol of which this is a meaning */
X    struct S_type *type;       /* (above) */
X    struct S_type *rectype;    /* (above) */
X    struct S_expr *constdefn;  /* (above) */
X    enum meaningkind kind;     /* Kind of meaning */
X    unsigned needvarstruct:1,  /* (above) */
X             varstructflag:1,  /* (above) */
X             wasdeclared:1,    /* Declaration has been written for meaning */
X             istemporary:1,    /* Is a temporary variable */
X             isforward:1,      /* (above) */
X             isfunction:1,     /* (above) */
X             anyvarflag:1,     /* (above) */
X             isactive:1,       /* Meaning is currently in scope */
X             exported:1,       /* Meaning is visible outside this module */
X             warnifused:1,     /* WarnNames was 1 when meaning was declared */
X             dumped:1,	       /* Has been dumped (for debugging) */
X             isreturn:1,       /* (above) */
X             fakeparam:1,      /* (above) */
X             namedfile:1,      /* (above) */
X             bufferedfile:1,   /* (above) */
X             volatilequal:1,   /* Object has C "volatile" qualifier */
X             constqual:1,      /* Object has C "const" qualifier */
X             dummy17:1, dummy18:1, dummy19:1, 
X	     dummy20:1, dummy21:1, dummy22:1, dummy23:1, dummy24:1, dummy25:1, 
X	     dummy26:1, dummy27:1, dummy28:1, dummy29:1, dummy30:1, dummy31:1;
X    Value val;		       /* (above) */
X    int refcount;	       /* Number of references to meaning in program */
X    char *name;		       /* Print name (i.e., C name) of the meaning */
X    char *othername;	       /* (above) */
X    struct S_expr *(*handler)();   /* Custom translator for procedure */
X    Strlist *comments;	       /* Comments associated with meaning */
X} Meaning;
X
X
X
X/* "Type" notes:
X *
X * This struct represents a data type.  Types are stored in a strange
X * cross between Pascal and C semantics.  (This usually works out okay.)
X *
X * TK_INTEGER:  Base integer type.
X *    The following types are TK_INTEGER:
X *        tp_integer, tp_unsigned, tp_int, tp_uint, tp_sint.
X *    All other integer types are represented by subranges.
X *    tp->smin => Minimum value for integer.
X *    tp->smax => Maximum value for integer.
X *
X * TK_CHAR:  Base character type.
X *    The following types are TK_CHAR:  tp_char, tp_schar, tp_uchar.
X *    All other character types are represented by subranges.
X *    tp->smin => Minimum value for character.
X *    tp->smax => Maximum value for character.
X *
X * TK_BOOLEAN:  Boolean type.
X *    The only TK_BOOLEAN type is tp_boolean.
X *    tp->smin => "False" expression.
X *    tp->smax => "True" expression.
X *
X * TK_REAL:  Real types.
X *    The only TK_REAL types are tp_real, tp_longreal, and/or the SINGLE type.
X *
X * TK_VOID:  C "void" type.
X *    The only TK_VOID type is tp_void.
X *
X * TK_SUBR:  Subrange of ordinal type.
X *    tp->basetype => a TK_INTEGER, TK_CHAR, TK_BOOLEAN, or TK_ENUM type.
X *    tp->smin => Minimum ordinal value for subrange.
X *    tp->smax => Maximum ordinal value for subrange.
X *
X * TK_ENUM:  Enumerated type.
X *    tp->fbase => First enumeration constant.
X *    tp->smin => Minimum value (zero).
X *    tp->smax => Maximum value (number of choices minus 1).
X *
X * TK_POINTER:  Pointer type.
X *    tp->basetype => Base type of pointer.
X *    Only one pointer type is ever generated for a given other type;
X *    each tp->pointertype points back to that type if it has been generated.
X *
X * TK_STRING:  Pascal string or VARYING OF CHAR type.
X *    tp->basetype => tp_char.
X *    tp->indextype => TK_SUBR from 0 to maximum string length.
X *    tp->structdefd = 1 if type is for a conformant VARYING OF CHAR parameter.
X *
X * TK_RECORD:  Pascal record/C struct type.
X *    tp->fbase => First field in record.
X *    tp->structdefd = 1 if struct type has been declared in output.
X *
X * TK_ARRAY with smax == NULL:  Normal array type.
X *    tp->basetype => Element type of array.
X *    tp->indextype => Index type (usually a TK_SUBR).
X *    tp->smin => Integer constant if SkipIndices was used, else NULL.
X *    tp->smax = NULL.
X *    tp->structdefd = 1 if type is for a conformant array parameter.
X *
X * TK_ARRAY with smax != NULL:  Large packed array type.
X *    tp->basetype => Element type of C array (tp_ubyte/tp_sbyte/tp_sshort).
X *    tp->indextype => Index type (usually a TK_SUBR).
X *    tp->smin => Integer constant is SkipIndices was used, else NULL.
X *    tp->smax => EK_TYPENAME for element type of Pascal array.
X *    tp->escale = log-base-two of number of bits per packed element, else 0.
X *    tp->issigned = 1 if packed array elements are signed, 0 if unsigned.
X *    tp->structdefd = 1 if type is for a conformant array parameter.
X *
X * TK_SMALLARRAY:  Packed array fitting within a single integer.
X *    (Same as for packed TK_ARRAY.)
X *
X * TK_SET:  Normal set type.
X *    tp->basetype => tp_integer.
X *    tp->indextype => Element type of the set.
X *
X * TK_SMALLSET:  Set fitting within a single integer.
X *    (Same as for TK_SET.)
X *
X * TK_FILE:  File type (corresponds to C "FILE" type).
X *    tp->basetype => Type of file elements, or tp_abyte if UCSD untyped file.
X *    A Pascal "file" variable is represented as a TK_POINTER to a TK_FILE.
X *
X * TK_FUNCTION:  Procedure or procedure-pointer type.
X *    tp->basetype => Return type of function, or tp_void if procedure.
X *    tp->issigned = 1 if type has a generic static link.
X *    tp->fbase => First argument (or StructFunction return buffer pointer).
X *
X * TK_PROCPTR:  Procedure pointer with static link.
X *    tp->basetype => TK_FUNCTION type.
X *    tp->fbase => Internal Meaning struct associated with basetype.
X *    tp->escale = Value of StaticLinks when type was declared.
X *
X * TK_CPROCPTR:  Procedure pointer without static link.
X *    tp->basetype => TK_FUNCTION type.
X *    tp->fbase => Internal Meaning struct associated with basetype.
X *    tp->escale = Value of StaticLinks = 0.
X *
X * TK_SPECIAL:  Special strange data type.
X *    Only TK_SPECIAL type at present is tp_jmp_buf.
X *
X */
X
Xenum typekind {
X    TK_NONE,
X    TK_INTEGER, TK_CHAR, TK_BOOLEAN, TK_REAL, TK_VOID,
X    TK_SUBR, TK_ENUM, TK_POINTER, TK_STRING,
X    TK_RECORD, TK_ARRAY, TK_SET, TK_FILE, TK_FUNCTION,
X    TK_PROCPTR, TK_SMALLSET, TK_SMALLARRAY, TK_CPROCPTR,
X    TK_SPECIAL,
X    TK_LAST
X} ;
X
X#ifdef DEFDUMPS
Xchar *typekindnames[(int)TK_LAST] = {
X    "TK_NONE",
X    "TK_INTEGER", "TK_CHAR", "TK_BOOLEAN", "TK_REAL", "TK_VOID",
X    "TK_SUBR", "TK_ENUM", "TK_POINTER", "TK_STRING",
X    "TK_RECORD", "TK_ARRAY", "TK_SET", "TK_FILE", "TK_FUNCTION",
X    "TK_PROCPTR", "TK_SMALLSET", "TK_SMALLARRAY", "TK_CPROCPTR",
X    "TK_SPECIAL"
X} ;
X#endif /*DEFDUMPS*/
X
Xtypedef struct S_type {
X    enum typekind kind;        /* Kind of type */
X    struct S_type *basetype;   /* (above) */
X    struct S_type *indextype;  /* (above) */
X    struct S_type *pointertype; /* Pointer to this type */
X    struct S_meaning *meaning; /* Name of this type, if any */
X    struct S_meaning *fbase;   /* (above) */
X    struct S_expr *smin;       /* (above) */
X    struct S_expr *smax;       /* (above) */
X    unsigned issigned:1,       /* (above) */
X             dumped:1,         /* Has been dumped (for debugging) */
X             structdefd:1;     /* (above) */
X    short escale;              /* (above) */
X} Type;
X
X
X/* "Expr" notes:
X *
X * Expression trees generally reflect C notation and semantics.  For example,
X * EK_ASSIGN is not generated for string arguments; these would get an
X * EK_BICALL to strcpy instead.
X *
X * The data type of each expression node is stored in its "val.type" field.
X * The rest of the "val" field is used only when shown below.
X * The "nargs" field always contains the number of arguments; the "args"
X * array is allocated to that size and will contain non-NULL Expr pointers.
X *
X * EK_EQ, EK_NE, EK_LT, EK_GT, EK_LE, EK_GE:  Relational operators.
X *    ep->nargs = 2.
X *
X * EK_PLUS:  Addition.
X *    ep->nargs >= 2.
X *
X * EK_NEG:  Negation.
X *    ep->nargs = 1.
X *
X * EK_TIMES:  Multiplication.
X *    ep->nargs >= 2.
X *
X * EK_DIVIDE:  Real division.
X *    ep->nargs = 2.
X *
X * EK_DIV:  Integer division.
X *    ep->nargs = 2.
X *
X * EK_MOD:  Integer modulo (C "%" operator).
X *    ep->nargs = 2.
X *
X * EK_OR, EK_AND:  Logical operators (C "&&" and "||").
X *    ep->nargs = 2.
X *
X * EK_NOT:  Logical NOT (C "!" operator).
X *    ep->nargs = 1.
X *
X * EK_BAND, EK_BOR, EK_BXOR:  Bitwise operators (C "&", "|", "^").
X *    ep->nargs = 2.
X *
X * EK_BNOT:  Bitwise NOT (C "~" operator).
X *    ep->nargs = 1.
X *
X * EK_LSH, EK_RSH:  Shift operators.
X *    ep->nargs = 2.
X *
X * EK_HAT:  Pointer dereference.
X *    ep->nargs = 1.
X *
X * EK_INDEX:  Array indexing.
X *    ep->nargs = 2.
X *
X * EK_CAST:  "Soft" type cast, change data type retaining value.
X *    ep->type => New data type.
X *    ep->nargs = 1.
X *
X * EK_ACTCAST:  "Active" type cast, performs a computation as result of cast.
X *    ep->type => New data type.
X *    ep->nargs = 1.
X *
X * EK_LITCAST:  Literal type cast.
X *    ep->nargs = 2.
X *    ep->args[0] => EK_TYPENAME expression for name of new data type.
X *    ep->args[1] => Argument of cast.
X *
X * EK_DOT:  Struct field extraction.
X *    ep->nargs = 1.  (Only one of the following will be nonzero:)
X *    ep->val.i => MK_FIELD being extracted (cast to Meaning *), else 0.
X *    ep->val.s => Literal name of field being extracted, else NULL.
X *
X * EK_COND:  C conditional expression.
X *    ep->nargs = 3.
X *    ep->args[0] => Condition expression.
X *    ep->args[1] => "Then" expression.
X *    ep->args[2] => "Else" expression.
X *
X * EK_ADDR:  Address-of operator.
X *    ep->nargs = 1.
X *
X * EK_SIZEOF:  Size-of operator.
X *    ep->nargs = 1.
X *    ep->args[0] => Argument expression, may be EK_TYPENAME.
X *
X * EK_CONST:  Literal constant.
X *    ep->nargs = 0 or 1.
X *    ep->val = Value of constant.
X *    ep->args[0] => EK_NAME of printf format string for constant, if any.
X *
X * EK_LONGCONST:  Literal constant, type "long int".
X *    (Same as for EK_CONST.)
X *
X * EK_VAR:  Variable name.
X *    ep->nargs = 0.
X *    ep->val.i => Variable being referenced (cast to Meaning *).
X *
X * EK_ASSIGN:  Assignment operator.
X *    ep->nargs = 2.
X *    ep->args[0] => Destination l-value expression.
X *    ep->args[1] => Source expression.
X *
X * EK_POSTINC, EK_POSTDEC:  Post-increment/post-decrement operators.
X *    ep->nargs = 1.
X *
X * EK_MACARG:  Placeholder for argument in expression for FuncMacro, etc.
X *    ep->nargs = 0.
X *    ep->val.i = Code selecting which argument.
X *
X * EK_CHECKNIL:  Null-pointer check.
X *    ep->nargs = 1.
X *
X * EK_BICALL:  Call to literal function name.
X *    ep->val.s => Name of function.
X *
X * EK_STRUCTCONST:  Structured constant.
X *    ep->nargs = Number of elements in constant.
X *    (Note:  constdefn points to an EK_CONST whose val.i points to this.)
X *
X * EK_STRUCTOF:  Repeated element in structured constant.
X *    ep->nargs = 1.
X *    ep->val.i = Number of repetitions.
X *
X * EK_COMMA:  C comma operator.
X *    ep->nargs >= 2.
X *
X * EK_NAME:  Literal variable name.
X *    ep->nargs = 0.
X *    ep->val.s => Name of variable.
X *
X * EK_CTX:  Name of a context, with static links.
X *    ep->nargs = 0.
X *    ep->val.i => MK_FUNCTION or MK_MODULE to name (cast to Meaning *).
X *
X * EK_SPCALL:  Special function call.
X *    ep->nargs = 1 + number of arguments to function.
X *    ep->args[0] => Expression which is the function to call.
X *
X * EK_TYPENAME:  Type name.
X *    ep->nargs = 0.
X *    ep->val.type => Type whose name should be printed.
X *
X * EK_FUNCTION:  Normal function call.
X *    ep->val.i => MK_FUNCTION being called (cast to Meaning *).
X *
X */
X
Xenum exprkind {
X    EK_EQ, EK_NE, EK_LT, EK_GT, EK_LE, EK_GE,
X    EK_PLUS, EK_NEG, EK_TIMES, EK_DIVIDE,
X    EK_DIV, EK_MOD,
X    EK_OR, EK_AND, EK_NOT,
X    EK_BAND, EK_BOR, EK_BXOR, EK_BNOT, EK_LSH, EK_RSH,
X    EK_HAT, EK_INDEX, EK_CAST, EK_DOT, EK_COND,
X    EK_ADDR, EK_SIZEOF, EK_ACTCAST,
X    EK_CONST, EK_VAR, EK_FUNCTION,
X    EK_ASSIGN, EK_POSTINC, EK_POSTDEC, EK_CHECKNIL,
X    EK_MACARG, EK_BICALL, EK_STRUCTCONST, EK_STRUCTOF,
X    EK_COMMA, EK_LONGCONST, EK_NAME, EK_CTX, EK_SPCALL,
X    EK_LITCAST, EK_TYPENAME,
X    EK_LAST
X} ;
X
X#ifdef DEFDUMPS
Xchar *exprkindnames[(int)EK_LAST] = {
X    "EK_EQ", "EK_NE", "EK_LT", "EK_GT", "EK_LE", "EK_GE",
X    "EK_PLUS", "EK_NEG", "EK_TIMES", "EK_DIVIDE",
X    "EK_DIV", "EK_MOD",
X    "EK_OR", "EK_AND", "EK_NOT",
X    "EK_BAND", "EK_BOR", "EK_BXOR", "EK_BNOT", "EK_LSH", "EK_RSH",
X    "EK_HAT", "EK_INDEX", "EK_CAST", "EK_DOT", "EK_COND",
X    "EK_ADDR", "EK_SIZEOF", "EK_ACTCAST",
X    "EK_CONST", "EK_VAR", "EK_FUNCTION",
X    "EK_ASSIGN", "EK_POSTINC", "EK_POSTDEC", "EK_CHECKNIL",
X    "EK_MACARG", "EK_BICALL", "EK_STRUCTCONST", "EK_STRUCTOF",
X    "EK_COMMA", "EK_LONGCONST", "EK_NAME", "EK_CTX", "EK_SPCALL",
X    "EK_LITCAST", "EK_TYPENAME"
X} ;
X#endif /*DEFDUMPS*/
X
Xtypedef struct S_expr {
X    enum exprkind kind;
X    short nargs;
X    Value val;
X    struct S_expr *args[1];    /* (Actually, variable-sized) */
X} Expr;
X
X
X
X/* "Stmt" notes.
X *
X * Statements form linked lists along the "next" pointers.
X * All other pointers are NULL and unused unless shown below.
X *
X * SK_ASSIGN:  Assignment or function call (C expression statement).
X *    sp->exp1 => Expression to be evaluated.
X *
X * SK_RETURN:  C "return" statement.
X *    sp->exp1 => Value to return, else NULL.
X *
X * SK_CASE:  C "switch" statement.
X *    sp->exp1 => Switch selector expression.
X *    sp->stm1 => List of SK_CASELABEL statements, followed by list of
X *		  statements that make up the "default:" clause.
X *
X * SK_CASELABEL:  C "case" label.
X *    sp->exp1 => Case value.
X *    sp->stm1 => List of SK_CASELABELs labelling the same clause, followed
X *                by list of statements in that clause.
X *
X * SK_CASECHECK:  Case-value-range-error, occurs in "default:" clause.
X *
X * SK_IF:  C "if" statement.
X *    sp->exp1 => Conditional expression.
X *    sp->exp2 => Constant expression, "1" if this "if" should be else-if'd
X *		  on to parent "if".  NULL => follow ElseIf parameter.
X *    sp->stm1 => "Then" clause.
X *    sp->stm2 => "Else" clause.
X *
X * SK_FOR:  C "for" statement.
X *    sp->exp1 => Initialization expression (may be NULL).
X *    sp->exp2 => Conditional expression (may be NULL).
X *    sp->exp3 => Iteration expression (may be NULL).
X *    sp->stm1 => Loop body.
X *
X * SK_REPEAT:  C "do-while" statement.
X *    sp->exp1 => Conditional expression (True = continue loop).
X *    sp->stm1 => Loop body.
X *
X * SK_WHILE:  C "while" statement.
X *    sp->exp1 => Conditional expression.
X *    sp->stm1 => Loop body.
X *
X * SK_BREAK:  C "break" statement.
X *
X * SK_CONTINUE:  C "continue" statement.
X *
X * SK_TRY:  HP Pascal TRY-RECOVER statement.
X *    sp->exp1->val.i = Global serial number of the TRY statement.
X *    sp->exp2 = Non-NULL if must generate a label for RECOVER block.
X *    sp->stm1 => TRY block.
X *    sp->stm2 => RECOVER block.
X *
X * SK_GOTO:  C "goto" statement.
X *    sp->exp1 => EK_NAME for the label number or name.
X *
X * SK_LABEL:  C statement label.
X *    sp->exp1 => EK_NAME for the label number of name.
X *
X * SK_HEADER:  Function/module header.
X *    sp->exp1 => EK_VAR pointing to MK_FUNCTION or MK_MODULE.
X *    (This always comes first in a context's statement list.)
X *
X * SK_BODY:  Body of function/module.
X *    sp->stm1 => SK_HEADER that begins the body.
X *    (This exists only during fixblock.)
X *
X */
X
Xenum stmtkind {
X    SK_ASSIGN, SK_RETURN,
X    SK_CASE, SK_CASELABEL, SK_IF,
X    SK_FOR, SK_REPEAT, SK_WHILE, SK_BREAK, SK_CONTINUE,
X    SK_TRY, SK_GOTO, SK_LABEL,
X    SK_HEADER, SK_CASECHECK, SK_BODY,
X    SK_LAST
X} ;
X
X#ifdef DEFDUMPS
Xchar *stmtkindnames[(int)SK_LAST] = {
X    "SK_ASSIGN", "SK_RETURN",
X    "SK_CASE", "SK_CASELABEL", "SK_IF",
X    "SK_FOR", "SK_REPEAT", "SK_WHILE", "SK_BREAK", "SK_CONTINUE",
X    "SK_TRY", "SK_GOTO", "SK_LABEL",
X    "SK_HEADER", "SK_CASECHECK", "SK_BODY"
X} ;
X#endif /*DEFDUMPS*/
X
Xtypedef struct S_stmt {
X    enum stmtkind kind;
X    struct S_stmt *next, *stm1, *stm2;
X    struct S_expr *exp1, *exp2, *exp3;
X    long serial;
X} Stmt;
X
X
X
X/* Flags for out_declarator(): */
X
X#define ODECL_CHARSTAR      0x1
X#define ODECL_FREEARRAY     0x2
X#define ODECL_FUNCTION      0x4
X#define ODECL_HEADER        0x8
X#define ODECL_FORWARD       0x10
X
X
X/* Flags for fixexpr(): */
X
X#define ENV_EXPR    0       /* return value needed */
X#define ENV_STMT    1       /* return value ignored */
X#define ENV_BOOL    2       /* boolean return value needed */
X
X
X/* Flags for defmacro(): */
X#define MAC_VAR     0       /* VarMacro */
X#define MAC_CONST   1       /* ConstMacro */
X#define MAC_FIELD   2       /* FieldMacro */
X#define MAC_FUNC    3       /* FuncMacro */
X
X#define FMACRECname  "<rec>"
X
X
X/* Kinds of comment lines: */
X#define CMT_SHIFT   24
X#define CMT_MASK    ((1L<<CMT_SHIFT)-1)
X#define CMT_KMASK   ((1<<(32-CMT_SHIFT))-1)
X#define CMT_DONE    0       /* comment that has already been printed */
X#define CMT_PRE     1       /* comment line preceding subject */
X#define CMT_POST    2       /* comment line following subject */
X#define CMT_TRAIL   4       /* comment at end of line of code */
X#define CMT_ONBEGIN 6       /* comment on "begin" of procedure */
X#define CMT_ONEND   7       /* comment on "end" of procedure */
X#define CMT_ONELSE  8       /* comment on "else" keyword */
X#define CMT_NOT     256     /* negation of above, for searches */
X
X#ifdef define_globals
Xchar *CMT_NAMES[] = { "DONE", "PRE", "POST", "3", "TRAIL", "5",
X                      "BEGIN", "END", "ELSE" };
X#else
Xextern char *CMT_NAMES[];
X#endif
X
X#define getcommentkind(cmt)  (((cmt)->value >> CMT_SHIFT) & CMT_KMASK)
X
X
X/* Kinds of operator line-breaking: */
X#define BRK_LEFT     0x1
X#define BRK_RIGHT    0x2
X#define BRK_LPREF    0x4
X#define BRK_RPREF    0x8
X#define BRK_ALLNONE  0x10
X#define BRK_HANG     0x20
X
X
X
X
X/* Translation parameters: */
X
X#ifdef define_parameters
X# define extern
X#endif /* define_parameters */
X
Xextern enum {
X    UNIX_ANY, UNIX_BSD, UNIX_SYSV
X} which_unix;
X
Xextern enum {
X    LANG_HP, LANG_UCSD, LANG_TURBO, LANG_OREGON, LANG_VAX,
X    LANG_MODULA, LANG_MPW, LANG_BERK
X} which_lang;
X
Xextern short debug, tokentrace, quietmode, cmtdebug, copysource;
Xextern int showprogress, maxerrors;
Xextern short hpux_lang, integer16, doublereals, pascalenumsize;
Xextern short needsignedbyte, unsignedchar, importall;
Xextern short nestedcomments, pascalsignif, pascalcasesens;
Xextern short dollar_idents, ignorenonalpha, modula2;
Xextern short ansiC, cplus, signedchars, signedfield, signedshift;
Xextern short hassignedchar, voidstar, symcase, ucconsts, csignif;
Xextern short copystructs, usevextern, implementationmodules;
Xextern short useAnyptrMacros, usePPMacros;
Xextern short sprintf_value;
Xextern char codefnfmt[40], modulefnfmt[40], logfnfmt[40];
Xextern char headerfnfmt[40], headerfnfmt2[40], includefnfmt[40];
Xextern char constformat[40], moduleformat[40], functionformat[40];
Xextern char varformat[40], fieldformat[40], typeformat[40];
Xextern char enumformat[40], symbolformat[40];
Xextern char p2c_h_name[40], exportsymbol[40], export_symbol[40];
Xextern char externalias[40];
Xextern char memcpyname[40], sprintfname[40];
Xextern char roundname[40], divname[40], modname[40], remname[40];
Xextern char strposname[40], strcicmpname[40];
Xextern char strsubname[40], strdeletename[40], strinsertname[40];
Xextern char strmovename[40], strpadname[40];
Xextern char strltrimname[40], strrtrimname[40], strrptname[40];
Xextern char absname[40], oddname[40], evenname[40], swapname[40];
Xextern char mallocname[40], freename[40], freervaluename[40];
Xextern char randrealname[40], randintname[40], randomizename[40];
Xextern char skipspacename[40], readlnname[40], freopenname[40];
Xextern char eofname[40], eolnname[40], fileposname[40], maxposname[40];
Xextern char setunionname[40], setintname[40], setdiffname[40];
Xextern char setinname[40], setaddname[40], setaddrangename[40];
Xextern char setremname[40];
Xextern char setequalname[40], subsetname[40], setxorname[40];
Xextern char setcopyname[40], setexpandname[40], setpackname[40];
Xextern char getbitsname[40], clrbitsname[40], putbitsname[40];
Xextern char declbufname[40], declbufncname[40];
Xextern char resetbufname[40], setupbufname[40];
Xextern char getfbufname[40], chargetfbufname[40], arraygetfbufname[40];
Xextern char putfbufname[40], charputfbufname[40], arrayputfbufname[40];
Xextern char getname[40], chargetname[40], arraygetname[40];
Xextern char putname[40], charputname[40], arrayputname[40];
Xextern char storebitsname[40], signextname[40];
Xextern char filenotfoundname[40], filenotopenname[40];
Xextern char filewriteerrorname[40], badinputformatname[40], endoffilename[40];
Xextern short strcpyleft;
Xextern char language[40], target[40];
Xextern int sizeof_char, sizeof_short, sizeof_integer, sizeof_pointer, 
X           sizeof_double, sizeof_float, sizeof_enum, sizeof_int, sizeof_long;
Xextern short size_t_long;
Xextern int setbits, defaultsetsize, seek_base, integerwidth, realwidth;
Xextern short quoteincludes, expandincludes, collectnest;
Xextern int phystabsize, intabsize, linewidth, maxlinewidth;
Xextern int majorspace, minorspace, functionspace, minfuncspace;
Xextern int casespacing, caselimit;
Xextern int returnlimit, breaklimit, continuelimit;
Xextern short nullstmtline, shortcircuit, shortopt, usecommas, elseif;
Xextern short usereturns, usebreaks, infloopstyle, reusefieldnames;
Xextern short bracesalways, braceline, bracecombine, braceelse, braceelseline;
Xextern short newlinefunctions;
Xextern short eatcomments, spitcomments, spitorphancomments;
Xextern short commentafter, blankafter;
Xextern int tabsize, blockindent, bodyindent, argindent;
Xextern int switchindent, caseindent, labelindent;
Xextern int openbraceindent, closebraceindent;
Xextern int funcopenindent, funccloseindent;
Xextern int structindent, structinitindent, extrainitindent;
Xextern int constindent, commentindent, bracecommentindent, commentoverindent;
Xextern int declcommentindent;
Xextern int minspacing, minspacingthresh;
Xextern int extraindent, bumpindent;
Xextern double overwidepenalty, overwideextrapenalty;
Xextern double commabreakpenalty, commabreakextrapenalty;
Xextern double assignbreakpenalty, assignbreakextrapenalty;
Xextern double specialargbreakpenalty;
Xextern double opbreakpenalty, opbreakextrapenalty, exhyphenpenalty;
Xextern double morebreakpenalty, morebreakextrapenalty;
Xextern double parenbreakpenalty, parenbreakextrapenalty;
Xextern double qmarkbreakpenalty, qmarkbreakextrapenalty;
Xextern double wrongsidepenalty, earlybreakpenalty, extraindentpenalty;
Xextern double bumpindentpenalty, nobumpindentpenalty;
Xextern double indentamountpenalty, sameindentpenalty;
Xextern double showbadlimit;
Xextern long maxalts;
Xextern short breakbeforearith, breakbeforerel, breakbeforelog;
Xextern short breakbeforedot, breakbeforeassign;
Xextern short for_allornone;
Xextern short extraparens, breakparens, returnparens;
Xextern short variablearrays, stararrays;
Xextern short spaceexprs, implicitzero, starindex;
Xextern int casetabs;
Xextern short starfunctions, mixfields, alloczeronil, postincrement;
Xextern short mixvars, mixtypes, mixinits, nullcharconst, castnull, addindex;
Xextern short highcharints, highcharbits, hasstaticlinks;
Xextern short mainlocals, storefilenames, addrstdfiles, readwriteopen;
Xextern short charfiletext, messagestderr, literalfilesflag;
Xextern short printfonly, mixwritelns, usegets, newlinespace, binarymode;
Xextern char openmode[40], filenamefilter[40];
Xextern short atan2flag, div_po2, mod_po2, assumebits, assumesigns;
Xextern short fullstrwrite, fullstrread, whilefgets, buildreads, buildwrites;
Xextern short foldconsts, foldstrconsts, useconsts, useundef;
Xextern short elimdeadcode, offsetforloops, forevalorder;
Xextern short smallsetconst, bigsetconst, lelerange, unsignedtrick;
Xextern short useisalpha, useisspace, usestrncmp;
Xextern short casecheck, arraycheck, rangecheck, nilcheck, malloccheck;
Xextern short checkfileopen, checkfileisopen, checkfilewrite;
Xextern short checkreadformat, checkfileeof, checkstdineof, checkfileseek;
Xextern short squeezesubr, useenum, enumbyte, packing, packsigned, keepnulls;
Xextern short compenums, formatstrings, alwayscopyvalues;
Xextern short use_static, var_static, void_args, prototypes, fullprototyping;
Xextern short procptrprototypes, promote_enums;
Xextern short castargs, castlongargs, promoteargs;
Xextern short varstrings, varfiles, copystructfuncs;
Xextern long skipindices;
Xextern short stringleaders;
Xextern int stringceiling, stringdefault, stringtrunclimit, longstringsize;
Xextern short warnnames, warnmacros;
Xextern Strlist *importfrom, *importdirs, *includedirs, *includefrom;
Xextern Strlist *librfiles, *bufferedfiles, *unbufferedfiles;
Xextern Strlist *externwords, *cexternwords;
Xextern Strlist *varmacros, *constmacros, *fieldmacros;
Xextern Strlist *funcmacros, *funcmacroargs, *nameoflist;
Xextern Strlist *specialmallocs, *specialfrees, *specialsizeofs;
Xextern Strlist *initialcalls, *eatnotes, *literalfiles;
X
Xextern char fixedcomment[40], permanentcomment[40], interfacecomment[40];
Xextern char embedcomment[40],  skipcomment[40], noskipcomment[40];
Xextern char signedcomment[40], unsignedcomment[40];
X
Xextern char name_RETV[40], name_STRMAX[40], name_LINK[40];
Xextern char name_COPYPAR[40], name_TEMP[40], name_DUMMY[40];
Xextern char name_LOC[40], name_VARS[40], name_STRUCT[40];
Xextern char name_FAKESTRUCT[40], name_AHIGH[40], name_ALOW[40];
Xextern char name_UNION[40], name_VARIANT[40], name_LABEL[40], name_LABVAR[40];
Xextern char name_WITH[40], name_FOR[40], name_ENUM[40];
Xextern char name_PTR[40], name_STRING[40], name_SET[40];
Xextern char name_PROCEDURE[40], name_MAIN[40], name_UNITINIT[40];
Xextern char name_HSYMBOL[40], name_GSYMBOL[40];
Xextern char name_SETBITS[40], name_UCHAR[40], name_SCHAR[40];
Xextern char name_BOOLEAN[40], name_TRUE[40], name_FALSE[40], name_NULL[40];
Xextern char name_ESCAPECODE[40], name_IORESULT[40];
Xextern char name_ARGC[40], name_ARGV[40];
Xextern char name_ESCAPE[40], name_ESCIO[40], name_CHKIO[40], name_SETIO[40];
Xextern char name_OUTMEM[40], name_CASECHECK[40], name_NILCHECK[40];
Xextern char name_FNSIZE[40], name_FNVAR[40];
Xextern char alternatename1[40], alternatename2[40], alternatename[40];
X
X
X#ifndef define_parameters
Xextern
X#endif
Xstruct rcstruct {
X    char kind;
X    char chgmode;
X    char *name;
X    anyptr ptr;
X    long def;
X} rctable[]
X#ifdef define_parameters
X   = {
X    'S', 'R', "DEBUG",           (anyptr) &debug,             0,
X    'I', 'R', "SHOWPROGRESS",    (anyptr) &showprogress,      0,
X    'S', 'V', "TOKENTRACE",      (anyptr) &tokentrace,        0,
X    'S', 'V', "QUIET",           (anyptr) &quietmode,         0,
X    'S', 'V', "COPYSOURCE",      (anyptr) &copysource,        0,
X    'I', 'R', "MAXERRORS",	 (anyptr) &maxerrors,	      0,
X    'X', ' ', "INCLUDE",         (anyptr) NULL,               2,
X
X/* INPUT LANGUAGE */
X    'U', 'T', "LANGUAGE",        (anyptr)  language,         40,
X    'S', 'V', "MODULA2",         (anyptr) &modula2,          -1,
X    'S', 'T', "INTEGER16",       (anyptr) &integer16,        -1,
X    'S', 'T', "DOUBLEREALS",     (anyptr) &doublereals,      -1,
X    'S', 'V', "UNSIGNEDCHAR",    (anyptr) &unsignedchar,     -1,
X    'S', 'V', "NEEDSIGNEDBYTE",  (anyptr) &needsignedbyte,    0,
X    'S', 'V', "PASCALENUMSIZE",  (anyptr) &pascalenumsize,   -1,
X    'S', 'V', "NESTEDCOMMENTS",  (anyptr) &nestedcomments,   -1,
X    'S', 'V', "IMPORTALL",       (anyptr) &importall,        -1,
X    'S', 'V', "IMPLMODULES",     (anyptr) &implementationmodules, -1,
X    'A', 'V', "EXTERNWORDS",	 (anyptr) &externwords,	      0,
X    'A', 'V', "CEXTERNWORDS",	 (anyptr) &cexternwords,      0,
X    'S', 'V', "PASCALSIGNIF",    (anyptr) &pascalsignif,     -1,
X    'S', 'V', "PASCALCASESENS",  (anyptr) &pascalcasesens,   -1,
X    'S', 'V', "DOLLARIDENTS",    (anyptr) &dollar_idents,    -1,
X    'S', 'V', "IGNORENONALPHA",  (anyptr) &ignorenonalpha,   -1,
X    'I', 'V', "SEEKBASE",        (anyptr) &seek_base,        -1,
X    'I', 'R', "INPUTTABSIZE",    (anyptr) &intabsize,         8,
X
X/* TARGET LANGUAGE */
X    'S', 'T', "ANSIC",           (anyptr) &ansiC,            -1,
X    'S', 'T', "C++",             (anyptr) &cplus,            -1,
X    'S', 'T', "VOID*",           (anyptr) &voidstar,         -1,
X    'S', 'T', "HASSIGNEDCHAR",   (anyptr) &hassignedchar,    -1,
X    'S', 'V', "CASTNULL",        (anyptr) &castnull,         -1,
X    'S', 'V', "COPYSTRUCTS",     (anyptr) &copystructs,      -1,
X    'S', 'V', "VARIABLEARRAYS",  (anyptr) &variablearrays,   -1,
X    'S', 'V', "REUSEFIELDNAMES", (anyptr) &reusefieldnames,   1,
X    'S', 'V', "USEVEXTERN",      (anyptr) &usevextern,        1,
X    'S', 'V', "CSIGNIF",         (anyptr) &csignif,          -1,
X    'S', 'V', "USEANYPTRMACROS", (anyptr) &useAnyptrMacros,  -1,
X    'S', 'V', "USEPPMACROS",     (anyptr) &usePPMacros,      -1,
X
X/* TARGET MACHINE */
X    'U', 'T', "TARGET",          (anyptr)  target,           40,
X    'S', 'T', "SIGNEDCHAR",      (anyptr) &signedchars,      -1,
X    'S', 'T', "SIGNEDFIELD",     (anyptr) &signedfield,      -1,
X    'S', 'T', "SIGNEDSHIFT",     (anyptr) &signedshift,      -1,
X    'I', 'T', "CHARSIZE",        (anyptr) &sizeof_char,       0,
X    'I', 'T', "SHORTSIZE",       (anyptr) &sizeof_short,      0,
X    'I', 'T', "INTSIZE",         (anyptr) &sizeof_int,        0,
X    'I', 'T', "LONGSIZE",        (anyptr) &sizeof_long,       0,
X    'I', 'T', "PTRSIZE",         (anyptr) &sizeof_pointer,    0,
X    'I', 'T', "DOUBLESIZE",      (anyptr) &sizeof_double,     0,
X    'I', 'T', "FLOATSIZE",       (anyptr) &sizeof_float,      0,
X    'I', 'T', "ENUMSIZE",        (anyptr) &sizeof_enum,       0,
X    'S', 'T', "SIZE_T_LONG",     (anyptr) &size_t_long,      -1,
X
X/* BRACES */
X    'S', 'V', "NULLSTMTLINE",    (anyptr) &nullstmtline,      0,
X    'S', 'V', "BRACESALWAYS",    (anyptr) &bracesalways,     -1,
X    'S', 'V', "BRACELINE",       (anyptr) &braceline,        -1,
X    'S', 'V', "BRACECOMBINE",    (anyptr) &bracecombine,      0,
X    'S', 'V', "BRACEELSE",       (anyptr) &braceelse,         0,
X    'S', 'V', "BRACEELSELINE",   (anyptr) &braceelseline,     0,
X    'S', 'V', "ELSEIF",          (anyptr) &elseif,           -1,
X    'S', 'V', "NEWLINEFUNCS",    (anyptr) &newlinefunctions,  0,
X
X/* INDENTATION */
X    'I', 'R', "PHYSTABSIZE",     (anyptr) &phystabsize,       8,
X    'D', 'R', "INDENT",          (anyptr) &tabsize,           2,
X    'D', 'R', "BLOCKINDENT",     (anyptr) &blockindent,       0,
X    'D', 'R', "BODYINDENT",      (anyptr) &bodyindent,        0,
X    'D', 'R', "FUNCARGINDENT",   (anyptr) &argindent,      1000,
X    'D', 'R', "OPENBRACEINDENT", (anyptr) &openbraceindent,   0,
X    'D', 'R', "CLOSEBRACEINDENT",(anyptr) &closebraceindent,  0,
X    'D', 'R', "FUNCOPENINDENT",  (anyptr) &funcopenindent,    0,
X    'D', 'R', "FUNCCLOSEINDENT", (anyptr) &funccloseindent,   0,
X    'D', 'R', "SWITCHINDENT",    (anyptr) &switchindent,      0,
X    'D', 'R', "CASEINDENT",      (anyptr) &caseindent,       -2,
X    'D', 'R', "LABELINDENT",     (anyptr) &labelindent,    1000,
X    'D', 'R', "STRUCTINDENT",    (anyptr) &structindent,      0,
X    'D', 'R', "STRUCTINITINDENT",(anyptr) &structinitindent,  0,
X    'D', 'R', "EXTRAINITINDENT", (anyptr) &extrainitindent,   2,
X    'I', 'R', "EXTRAINDENT",     (anyptr) &extraindent,       2,
X    'I', 'R', "BUMPINDENT",      (anyptr) &bumpindent,        1,
X    'D', 'R', "CONSTINDENT",     (anyptr) &constindent,    1024,
X    'D', 'R', "COMMENTINDENT",   (anyptr) &commentindent,     3,
X    'D', 'R', "BRACECOMMENTINDENT",(anyptr)&bracecommentindent, 2,
X    'D', 'R', "DECLCOMMENTINDENT",(anyptr)&declcommentindent, -999,
X    'D', 'R', "COMMENTOVERINDENT",(anyptr)&commentoverindent, 4,  /*1000*/
X    'I', 'R', "MINSPACING",      (anyptr) &minspacing,        2,
X    'I', 'R', "MINSPACINGTHRESH",(anyptr) &minspacingthresh, -1,
X
X/* LINE BREAKING */
X    'I', 'R', "LINEWIDTH",       (anyptr) &linewidth,        78,
X    'I', 'R', "MAXLINEWIDTH",    (anyptr) &maxlinewidth,     90,
X    'R', 'V', "OVERWIDEPENALTY",       (anyptr) &overwidepenalty,         2500,
X    'R', 'V', "OVERWIDEEXTRAPENALTY",  (anyptr) &overwideextrapenalty,     100,
X    'R', 'V', "COMMABREAKPENALTY",     (anyptr) &commabreakpenalty,       1000,
X    'R', 'V', "COMMABREAKEXTRAPENALTY",(anyptr) &commabreakextrapenalty,   500,
X    'R', 'V', "ASSIGNBREAKPENALTY",    (anyptr) &assignbreakpenalty,      5000,
X    'R', 'V', "ASSIGNBREAKEXTRAPENALTY",(anyptr)&assignbreakextrapenalty, 3000,
X    'R', 'V', "SPECIALARGBREAKPENALTY",(anyptr) &specialargbreakpenalty,   500,
X    'R', 'V', "OPBREAKPENALTY",        (anyptr) &opbreakpenalty,          2500,
X    'R', 'V', "OPBREAKEXTRAPENALTY",   (anyptr) &opbreakextrapenalty,     2000,
X    'R', 'V', "EXHYPHENPENALTY",       (anyptr) &exhyphenpenalty,         1000,
X    'R', 'V', "MOREBREAKPENALTY",      (anyptr) &morebreakpenalty,        -500,
X    'R', 'V', "MOREBREAKEXTRAPENALTY", (anyptr) &morebreakextrapenalty,   -300,
END_OF_FILE
if test 48347 -ne `wc -c <'src/trans.h.1'`; then
    echo shar: \"'src/trans.h.1'\" unpacked with wrong size!
fi
# end of 'src/trans.h.1'
fi
echo shar: End of archive 20 \(of 32\).
cp /dev/null ark20isdone
MISSING=""
for I in 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 ; do
    if test ! -f ark${I}isdone ; then
	MISSING="${MISSING} ${I}"
    fi
done
if test "${MISSING}" = "" ; then
    echo You have unpacked all 32 archives.
    echo "Now see PACKNOTES and the README"
    rm -f ark[1-9]isdone ark[1-9][0-9]isdone
else
    echo You still need to unpack the following archives:
    echo "        " ${MISSING}
fi
##  End of shell archive.
exit 0
-- 
Please send comp.sources.unix-related mail to rsalz at uunet.uu.net.
Use a domain-based address or give alternate paths, or you may lose out.



More information about the Comp.sources.unix mailing list