Home
       cc1.h - scc - simple c99 compiler
  HTML git clone git://git.simple-cc.org/scc
   DIR Log
   DIR Files
   DIR Refs
   DIR Submodules
   DIR README
   DIR LICENSE
       ---
       cc1.h (10143B)
       ---
            1 #include <stdint.h>
            2 
            3 #define INPUTSIZ LINESIZ
            4 
            5 #define GLOBALCTX 0
            6 #define PARAMCTX  1
            7 
            8 #define NR_USWITCHES 20
            9 
           10 #define FAIL   1
           11 #define NOFAIL 0
           12 
           13 #define EQUAL  0
           14 #define EQUIV  1
           15 
           16 /*
           17  * Definition of enumerations
           18  */
           19 enum {
           20         NOALLOC,
           21         ALLOC
           22 };
           23 
           24 enum typeprops {
           25         TDEFINED = 1 << 0,    /* type defined */
           26         TSIGNED  = 1 << 1,    /* signedness of the type */
           27         TINTEGER = 1 << 2,    /* the type is INT of enum */
           28         TARITH   = 1 << 3,    /* the type is INT, ENUM or FLOAT */
           29         TAGGREG  = 1 << 4,    /* the type is struct or union */
           30         TK_R     = 1 << 5,    /* this is a K&R-function */
           31         TELLIPSIS= 1 << 6,    /* this function has an ellipsis par */
           32         TFUNDEF  = 1 << 7,    /* function definition */
           33 };
           34 
           35 enum inputtype {
           36         IMACRO = 1 << 0,      /* macro expansion type */
           37         IFILE  = 1 << 1,      /* input file type */
           38         ISTDIN = 1 << 2,      /* stdin type */
           39         IPARAM = 1 << 3,      /* macro param expansion */
           40         IEOF   = 1 << 4,      /* EOF mark */
           41         ITYPE  = IMACRO | IFILE | ISTDIN | IPARAM,
           42 };
           43 
           44 /* data type letters */
           45 enum ns {
           46         L_INT8      = 'C',
           47         L_INT16     = 'I',
           48         L_INT32     = 'W',
           49         L_INT64     = 'Q',
           50         L_UINT8     = 'K',
           51         L_UINT16    = 'N',
           52         L_UINT32    = 'Z',
           53         L_UINT64    = 'O',
           54         L_BOOL      = 'B',
           55 
           56         L_FLOAT     = 'J',
           57         L_DOUBLE    = 'D',
           58         L_LDOUBLE   = 'H',
           59 
           60         L_ELLIPSIS  = 'E',
           61         L_VOID      = '0',
           62         L_POINTER   = 'P',
           63         L_FUNCTION  = 'F',
           64         L_ARRAY     = 'V',
           65         L_UNION     = 'U',
           66         L_STRUCT    = 'S',
           67         L_VA_ARG    = '1',
           68 };
           69 
           70 /* recovery points */
           71 enum {
           72         END_DECL,
           73         END_LDECL,
           74         END_COMP,
           75         END_COND
           76 };
           77 
           78 /* type constructors */
           79 enum typeop {
           80         FTN = 1,
           81         PTR,
           82         ARY,
           83         KRFTN
           84 };
           85 
           86 /* namespaces */
           87 enum namespaces {
           88         NS_DUMMY,
           89         NS_IDEN,
           90         NS_TAG,
           91         NS_LABEL,
           92         NS_CPP,
           93         NS_KEYWORD,
           94         NS_CPPCLAUSES,
           95         NS_STRUCTS
           96 };
           97 
           98 /* symbol flags */
           99 enum {
          100         SAUTO     = 1 << 0,
          101         SREGISTER = 1 << 1,
          102         SDECLARED = 1 << 2,
          103         SFIELD    = 1 << 3,
          104         SEXTERN   = 1 << 4,
          105         SUSED     = 1 << 5,
          106         SCONSTANT = 1 << 6,
          107         SGLOBAL   = 1 << 7,
          108         SPRIVATE  = 1 << 8,
          109         SLOCAL    = 1 << 9,
          110         SEMITTED  = 1 << 10,
          111         SDEFINED  = 1 << 11,
          112         SSTRING   = 1 << 12,
          113         STYPEDEF  = 1 << 13,
          114         SINITLST  = 1 << 14,
          115         SHASINIT  = 1 << 15
          116 };
          117 
          118 /* node flags */
          119 enum {
          120         NLVAL   = 1 << 0,
          121         NCONST  = 1 << 1,
          122         NEFFECT = 1 << 2,
          123         NDECAY  = 1 << 3,
          124 };
          125 
          126 /* lexer mode, compiler or preprocessor directive */
          127 enum {
          128         CCMODE,
          129         CPPMODE
          130 };
          131 
          132 /* input tokens */
          133 enum tokens {
          134         CONST      = 1 << 0,      /* type qualifier tokens are used as flags */
          135         RESTRICT   = 1 << 1,
          136         VOLATILE   = 1 << 2,
          137         INLINE     = 1 << 3,
          138         TQUALIFIER = 1 << 7,
          139         MACROPAR   = 17,
          140         CONCAT     = 18,
          141         STRINGIZE  = 19,
          142         TYPE       = 129,
          143         IDEN,
          144         SCLASS,
          145         CONSTANT,
          146         STRING,
          147         SIZEOF,
          148         INDIR,
          149         INC,
          150         DEC,
          151         SHL,
          152         SHR,
          153         LE,
          154         GE,
          155         EQ,
          156         NE,
          157         AND,
          158         OR,
          159         MUL_EQ,
          160         DIV_EQ,
          161         MOD_EQ,
          162         ADD_EQ,
          163         SUB_EQ,
          164         AND_EQ,
          165         XOR_EQ,
          166         OR_EQ,
          167         SHL_EQ,
          168         SHR_EQ,
          169         ELLIPSIS,
          170         CASE,
          171         DEFAULT,
          172         IF,
          173         ELSE,
          174         SWITCH,
          175         WHILE,
          176         DO,
          177         FOR,
          178         GOTO,
          179         VOID,
          180         FLOAT,
          181         INT,
          182         BOOL,
          183         VA_LIST,
          184         STRUCT,
          185         UNION,
          186         CHAR,
          187         DOUBLE,
          188         SHORT,
          189         LONG,
          190         LLONG,
          191         COMPLEX,
          192         TYPEDEF,
          193         EXTERN,
          194         STATIC,
          195         AUTO,
          196         REGISTER,
          197         ENUM,
          198         TYPEIDEN,
          199         UNSIGNED,
          200         SIGNED,
          201         CONTINUE,
          202         BREAK,
          203         RETURN,
          204         DEFINE,
          205         DEFINED,
          206         INCLUDE,
          207         LINE,
          208         PRAGMA,
          209         ERROR,
          210         IFDEF,
          211         ELIF,
          212         IFNDEF,
          213         UNDEF,
          214         ENDIF,
          215         BUILTIN,
          216         EOFTOK
          217 };
          218 
          219 /* operations */
          220 enum op {
          221         OADD,
          222         OMUL,
          223         OSUB,
          224         OINC,
          225         ODEC,
          226         ODIV,
          227         OMOD,
          228         OSHL,
          229         OSHR,
          230         OBAND,
          231         OBXOR,
          232         OBOR,
          233         OSNEG,
          234         ONEG,
          235         OCPL,
          236         OAND,
          237         OOR,
          238         OEQ,
          239         ONE,
          240         OLT,
          241         OGE,
          242         OLE,
          243         OGT,
          244         OASSIGN,
          245         OA_MUL,
          246         OA_DIV,
          247         OA_MOD,
          248         OA_ADD,
          249         OA_SUB,
          250         OA_SHL,
          251         OA_SHR,
          252         OA_AND,
          253         OA_XOR,
          254         OA_OR,
          255         OADDR,
          256         OCOMMA,
          257         OCAST,
          258         OPTR,
          259         OSYM,
          260         OASK,
          261         OCOLON,
          262         OFIELD,
          263         OLABEL,
          264         ODEFAULT,
          265         OCASE,
          266         OJUMP,
          267         OBRANCH,
          268         OEXPR,
          269         OEFUN,
          270         OELOOP,
          271         OBLOOP,
          272         OFUN,
          273         OPAR,
          274         OCALL,
          275         OCALLE,
          276         ORET,
          277         ODECL,
          278         OBSWITCH,
          279         OESWITCH,
          280         OINIT,
          281         OBUILTIN,
          282         OTYP,
          283 };
          284 
          285 /*
          286  * Definition of structures
          287  */
          288 typedef struct type Type;
          289 typedef struct symbol Symbol;
          290 typedef struct swtch Switch;
          291 typedef struct node Node;
          292 typedef struct macro Macro;
          293 typedef struct input Input;
          294 typedef struct arch Arch;
          295 typedef uint32_t Rune;
          296 
          297 struct limits {
          298         union {
          299                 TUINT i;
          300                 TFLOAT f;
          301         } max;
          302         union {
          303                 TUINT i;
          304                 TFLOAT f;
          305         } min;
          306 };
          307 
          308 struct builtin {
          309         char *str;
          310         Node *(*fun)(Symbol *);
          311 };
          312 
          313 struct type {
          314         unsigned char op;           /* type builder operator */
          315         unsigned char ns;           /* namespace for struct members */
          316         short id;                   /* type id, used in dcls */
          317         char letter;                /* letter of the type */
          318         unsigned char prop;         /* type properties */
          319         unsigned char align;        /* align of the type */
          320         unsigned long size;         /* sizeof the type */
          321         Type *type;                 /* base type */
          322         Symbol *tag;                /* symbol of the strug tag */
          323         union {
          324                 Type **pars;            /* Function type parameters */
          325                 Symbol **fields;        /* fields of aggregate type */
          326         } p;
          327         union {
          328                 unsigned char rank;     /* convertion rank */
          329                 TINT elem;              /* number of type parameters */
          330         } n;
          331         Type *next;                 /* local list pointer */
          332         Type *h_next;               /* hash collision list */
          333 };
          334 
          335 struct symbol {
          336         unsigned char ctx;
          337         unsigned char hide;
          338         char ns;
          339         unsigned short id;
          340         unsigned short flags;
          341         char *name;
          342         Type *type;
          343         unsigned char token;
          344         union {
          345                 TINT i;
          346                 TUINT u;
          347                 TFLOAT f;
          348                 char *s;
          349                 unsigned char token;
          350                 Node **init;
          351                 Symbol **pars;
          352                 Node *(*fun)(Symbol *);
          353         } u;
          354         struct symbol *next;
          355         struct symbol *hash;
          356 };
          357 
          358 struct node {
          359         unsigned char op;
          360         unsigned char flags;
          361         Type *type;
          362         Symbol *sym;
          363         struct node *left, *right;
          364 };
          365 
          366 struct swtch {
          367         short nr;
          368         char hasdef;
          369 };
          370 
          371 struct arch {
          372         Type voidtype;
          373         Type pvoidtype;
          374         Type booltype;
          375         Type schartype;
          376         Type uchartype;
          377         Type chartype;
          378         Type ushorttype;
          379         Type shorttype;
          380         Type uinttype;
          381         Type inttype;
          382         Type longtype;
          383         Type ulongtype;
          384         Type ullongtype;
          385         Type llongtype;
          386         Type floattype;
          387         Type doubletype;
          388         Type ldoubletype;
          389         Type sizettype;
          390         Type pdifftype;
          391         Type ellipsistype;
          392         Type va_type;
          393         Type va_list_type;
          394         Type wchartype;
          395 
          396         int (*valid_va_list)(Type *tp);
          397 };
          398 
          399 struct yystype {
          400         Symbol *sym;
          401         unsigned char token;
          402 };
          403 
          404 #ifdef NR_MACROARG
          405 struct macro {
          406         Symbol *sym;
          407         char *fname;
          408         char **arglist;
          409         char *buffer;
          410         char *def;
          411         char *arg;
          412         int bufsiz;
          413         int argsiz;
          414         int npars;
          415         Symbol *hideset[NR_MACROARG];
          416 };
          417 #endif
          418 
          419 #ifdef stdin
          420 struct input {
          421         char flags;
          422         unsigned lineno;
          423         char *filenam;
          424         FILE *fp;
          425         Macro *macro;
          426         char *line, *begin, *p;
          427         struct input *next;
          428 };
          429 #endif
          430 
          431 /* error.c */
          432 extern void error(char *fmt, ...);
          433 extern void warn(char *fmt, ...);
          434 extern void unexpected(void);
          435 extern void errorp(char *fmt, ...);
          436 extern void cpperror(char *fmt, ...);
          437 extern Type *deftype(Type *tp);
          438 
          439 /* types.c */
          440 extern int eqtype(Type *tp1, Type *tp2, int eqflag);
          441 extern Type *ctype(int type, int sign, int size);
          442 extern Type *mktype(Type *tp, int op, TINT nelem, Type *data[]);
          443 extern Type *duptype(Type *base);
          444 extern struct limits *getlimits(Type *tp);
          445 extern void typesize(Type *tp);
          446 extern void flushtypes(void);
          447 
          448 /* symbol.c */
          449 extern void dumpstab(Symbol **tbl, char *msg);
          450 extern Symbol *lookup(int ns, char *name, int alloc);
          451 extern Symbol *nextsym(Symbol *sym, int ns);
          452 extern Symbol *install(int ns, Symbol *sym);
          453 extern Symbol *newsym(int ns, char *name);
          454 extern void pushctx(void), popctx(void);
          455 extern void killsym(Symbol *sym);
          456 extern Symbol *newlabel(void);
          457 extern void builtins(struct builtin *builts);
          458 extern Symbol *newstring(char *s, size_t len);
          459 extern unsigned newid(void);
          460 extern void isyms(void);
          461 
          462 /* stmt.c */
          463 extern void compound(Symbol *lbreak, Symbol *lcont, Switch *sw);
          464 
          465 /* decl.c */
          466 extern Type *typename(void);
          467 extern void decl(void);
          468 
          469 /* lex.c */
          470 extern int ahead(void);
          471 extern int next(void);
          472 extern void expect(int tok);
          473 extern void discard(void);
          474 extern int addinput(int, void *, int);
          475 extern void delinput(void);
          476 extern void setsafe(int type);
          477 extern void setloc(char *fname, unsigned line);
          478 #define accept(t) ((yytoken == (t)) ? next() : 0)
          479 
          480 /* code.c */
          481 extern Node *prtree(char *s, Node *np);
          482 extern void emit(int, void *);
          483 extern Node *node(int op, Type *tp, Node *left, Node *rigth);
          484 extern Node *varnode(Symbol *sym);
          485 extern Node *constnode(Symbol *sym);
          486 extern Node *sizeofnode(Type *tp);
          487 extern Node *offsetnode(Symbol *,  Type *);
          488 extern void freetree(Node *np);
          489 extern void icode(void);
          490 #define BTYPE(np) ((np)->type->op)
          491 
          492 /* fold.c */
          493 extern Node *simplify(Node *np);
          494 extern TUINT ones(int nbytes);
          495 
          496 /* expr.c */
          497 extern Node *decay(Node *), *negate(Node *np), *assign(void);
          498 extern Node *convert(Node *np, Type *tp1, int iscast);
          499 extern Node *constexpr(void), *condexpr(int neg), *expr(void);
          500 extern int isnodecmp(int op);
          501 extern int negop(int op);
          502 extern int cmpnode(Node *np, TUINT val);
          503 extern int power2node(Node *, int *);
          504 
          505 /* init.c */
          506 extern void initializer(Symbol *sym, Type *tp);
          507 extern Node *initlist(Type *tp);
          508 
          509 /* cpp.c */
          510 extern void icpp(void);
          511 extern int cpp(void);
          512 extern int expand(Symbol *);
          513 extern void incdir(char *dir);
          514 extern void outcpp(void);
          515 extern void defdefine(char *macro, char *val, char *source);
          516 extern void undefmacro(char *s);
          517 extern void ppragmaln(void);
          518 extern void delmacro(Macro *);
          519 extern Macro *newmacro(Symbol *);
          520 extern Node *defined(void);
          521 
          522 
          523 /* builtin.c */
          524 extern void ibuilts(void);
          525 
          526 /* arch.c */
          527 extern void iarch(void);
          528 extern int valid_va_list(Type *tp);
          529 
          530 /* architectures */
          531 extern Arch *amd64_sysv(void);
          532 extern Arch *z80_scc(void);
          533 extern Arch *arm64_sysv(void);
          534 extern Arch *i386_sysv(void);
          535 
          536 /*
          537  * Definition of global variables
          538  */
          539 extern struct yystype yylval;
          540 extern char yytext[];
          541 extern int yytoken;
          542 extern unsigned short yylen;
          543 extern int disexpand, disescape;
          544 extern unsigned cppctx;
          545 extern Input *input;
          546 extern int lexmode, namespace;
          547 extern int onlycpp, onlyheader;
          548 extern unsigned curctx;
          549 extern Symbol *curfun, *zero, *one;
          550 extern unsigned lineno;
          551 extern char filenam[];
          552 extern char *architecture;
          553 
          554 extern Type *voidtype, *pvoidtype, *booltype,
          555             *uchartype,   *chartype, *schartype,
          556             *uinttype,    *inttype,
          557             *sizettype, *pdifftype,
          558             *ushorttype,   *shorttype,
          559             *longtype,    *ulongtype,
          560             *ullongtype,  *llongtype,
          561             *floattype,   *doubletype,  *ldoubletype,
          562             *ellipsistype, *va_list_type, *va_type,
          563             *wchartype;