]> git.xonotic.org Git - xonotic/gmqcc.git/blobdiff - parser.c
util_memory_r with byte=0 will now call util_memory_d and return NULL
[xonotic/gmqcc.git] / parser.c
index 5b06b9f612f9922cbcda2ff8677245cb3f5794b6..2a5ba76d20528815293d378417f9424ed4f99fcc 100644 (file)
--- a/parser.c
+++ b/parser.c
@@ -23,6 +23,9 @@ typedef struct {
     ast_value *imm_float_zero;
     ast_value *imm_vector_zero;
 
+    size_t crc_globals;
+    size_t crc_fields;
+
     ast_function *function;
     MEM_VECTOR_MAKE(varentry_t, locals);
     size_t blocklocal;
@@ -59,7 +62,7 @@ static void parseerror(parser_t *parser, const char *fmt, ...)
        parser->errors++;
 
        va_start(ap, fmt);
-    vprintmsg(LVL_ERROR, parser->lex->tok->ctx.file, parser->lex->tok->ctx.line, "parse error", fmt, ap);
+    vprintmsg(LVL_ERROR, parser->lex->tok.ctx.file, parser->lex->tok.ctx.line, "parse error", fmt, ap);
        va_end(ap);
 }
 
@@ -78,7 +81,7 @@ static bool GMQCC_WARN parsewarning(parser_t *parser, int warntype, const char *
        }
 
        va_start(ap, fmt);
-    vprintmsg(lvl, parser->lex->tok->ctx.file, parser->lex->tok->ctx.line, "warning", fmt, ap);
+    vprintmsg(lvl, parser->lex->tok.ctx.file, parser->lex->tok.ctx.line, "warning", fmt, ap);
        va_end(ap);
 
        return opts_werror;
@@ -155,17 +158,9 @@ bool parser_next(parser_t *parser)
     return true;
 }
 
-/* lift a token out of the parser so it's not destroyed by parser_next */
-token *parser_lift(parser_t *parser)
-{
-    token *tok = parser->lex->tok;
-    parser->lex->tok = NULL;
-    return tok;
-}
-
-#define parser_tokval(p) (p->lex->tok->value)
-#define parser_token(p)  (p->lex->tok)
-#define parser_ctx(p)    (p->lex->tok->ctx)
+#define parser_tokval(p) ((p)->lex->tok.value)
+#define parser_token(p)  (&((p)->lex->tok))
+#define parser_ctx(p)    ((p)->lex->tok.ctx)
 
 static ast_value* parser_const_float(parser_t *parser, double d)
 {
@@ -420,6 +415,9 @@ static ast_value *parse_type(parser_t *parser, int basetype, bool *isfunc)
             goto on_error;
     }
 
+    if (params.p_count > 8)
+        parseerror(parser, "more than 8 parameters are currently not supported");
+
     var = ast_value_new(ctx, "<unnamed>", vtype);
     if (!var)
         goto on_error;
@@ -453,6 +451,7 @@ MEM_VEC_FUNCTIONS(shunt, sy_elem, ops)
 static sy_elem syexp(lex_ctx ctx, ast_expression *v) {
     sy_elem e;
     e.etype = 0;
+    e.off   = 0;
     e.out   = v;
     e.block = NULL;
     e.ctx   = ctx;
@@ -463,6 +462,7 @@ static sy_elem syexp(lex_ctx ctx, ast_expression *v) {
 static sy_elem syblock(lex_ctx ctx, ast_block *v) {
     sy_elem e;
     e.etype = 0;
+    e.off   = 0;
     e.out   = (ast_expression*)v;
     e.block = v;
     e.ctx   = ctx;
@@ -473,6 +473,7 @@ static sy_elem syblock(lex_ctx ctx, ast_block *v) {
 static sy_elem syop(lex_ctx ctx, const oper_info *op) {
     sy_elem e;
     e.etype = 1 + (op - operators);
+    e.off   = 0;
     e.out   = NULL;
     e.block = NULL;
     e.ctx   = ctx;
@@ -869,10 +870,50 @@ static bool parser_sy_pop(parser_t *parser, shunt *sy)
             break;
 
         case opid1('='):
-            if (ast_istype(exprs[0], ast_entfield))
+            if (ast_istype(exprs[0], ast_entfield)) {
+                ast_expression *field = ((ast_entfield*)exprs[0])->field;
                 assignop = type_storep_instr[exprs[0]->expression.vtype];
+                if (!ast_compare_type(field->expression.next, exprs[1])) {
+                    char ty1[1024];
+                    char ty2[1024];
+                    ast_type_to_string(field->expression.next, ty1, sizeof(ty1));
+                    ast_type_to_string(exprs[1], ty2, sizeof(ty2));
+                    if (opts_standard == COMPILER_QCC &&
+                        field->expression.next->expression.vtype == TYPE_FUNCTION &&
+                        exprs[1]->expression.vtype == TYPE_FUNCTION)
+                    {
+                        if (parsewarning(parser, WARN_ASSIGN_FUNCTION_TYPES,
+                                         "invalid types in assignment: cannot assign %s to %s", ty2, ty1))
+                        {
+                            parser->errors++;
+                        }
+                    }
+                    else
+                        parseerror(parser, "invalid types in assignment: cannot assign %s to %s", ty2, ty1);
+                }
+            }
             else
+            {
                 assignop = type_store_instr[exprs[0]->expression.vtype];
+                if (!ast_compare_type(exprs[0], exprs[1])) {
+                    char ty1[1024];
+                    char ty2[1024];
+                    ast_type_to_string(exprs[0], ty1, sizeof(ty1));
+                    ast_type_to_string(exprs[1], ty2, sizeof(ty2));
+                    if (opts_standard == COMPILER_QCC &&
+                        exprs[0]->expression.vtype == TYPE_FUNCTION &&
+                        exprs[1]->expression.vtype == TYPE_FUNCTION)
+                    {
+                        if (parsewarning(parser, WARN_ASSIGN_FUNCTION_TYPES,
+                                         "invalid types in assignment: cannot assign %s to %s", ty2, ty1))
+                        {
+                            parser->errors++;
+                        }
+                    }
+                    else
+                        parseerror(parser, "invalid types in assignment: cannot assign %s to %s", ty2, ty1);
+                }
+            }
             out = (ast_expression*)ast_store_new(ctx, assignop, exprs[0], exprs[1]);
             break;
         case opid2('+','='):
@@ -972,6 +1013,8 @@ static bool parser_close_call(parser_t *parser, shunt *sy)
             MEM_VECTOR_MOVE(params, exprs, call, params);
             ast_delete(params);
         }
+        if (!ast_call_check_types(call))
+            parser->errors++;
     } else {
         parseerror(parser, "invalid function call");
         return false;
@@ -1820,7 +1863,7 @@ static bool parse_block_into(parser_t *parser, ast_block *block, bool warnreturn
             break;
 
         if (!parse_statement(parser, block, &expr)) {
-            parseerror(parser, "parse error");
+            /* parseerror(parser, "parse error"); */
             block = NULL;
             goto cleanup;
         }
@@ -1910,26 +1953,366 @@ static bool create_vector_members(parser_t *parser, ast_value *var, varentry_t *
         --i;
         mem_d(ve[i].name);
         ast_delete(ve[i].var);
+        ve[i].name = NULL;
+        ve[i].var  = NULL;
     } while (i);
     return false;
 }
 
+static bool parse_function_body(parser_t *parser, ast_value *var)
+{
+    ast_block      *block = NULL;
+    ast_function   *func;
+    ast_function   *old;
+    size_t          parami;
+
+    ast_expression *framenum  = NULL;
+    ast_expression *nextthink = NULL;
+    /* None of the following have to be deleted */
+    ast_expression *fld_think = NULL, *fld_nextthink = NULL, *fld_frame = NULL;
+    ast_expression *gbl_time = NULL, *gbl_self = NULL;
+    bool            has_frame_think;
+
+    bool retval = true;
+
+    has_frame_think = false;
+    old = parser->function;
+
+    if (var->expression.variadic) {
+        if (parsewarning(parser, WARN_VARIADIC_FUNCTION,
+                         "variadic function with implementation will not be able to access additional parameters"))
+        {
+            return false;
+        }
+    }
+
+    if (parser->tok == '[') {
+        /* got a frame definition: [ framenum, nextthink ]
+         * this translates to:
+         * self.frame = framenum;
+         * self.nextthink = time + 0.1;
+         * self.think = nextthink;
+         */
+        nextthink = NULL;
+
+        fld_think     = parser_find_field(parser, "think");
+        fld_nextthink = parser_find_field(parser, "nextthink");
+        fld_frame     = parser_find_field(parser, "frame");
+        if (!fld_think || !fld_nextthink || !fld_frame) {
+            parseerror(parser, "cannot use [frame,think] notation without the required fields");
+            parseerror(parser, "please declare the following entityfields: `frame`, `think`, `nextthink`");
+            return false;
+        }
+        gbl_time      = parser_find_global(parser, "time");
+        gbl_self      = parser_find_global(parser, "self");
+        if (!gbl_time || !gbl_self) {
+            parseerror(parser, "cannot use [frame,think] notation without the required globals");
+            parseerror(parser, "please declare the following globals: `time`, `self`");
+            return false;
+        }
+
+        if (!parser_next(parser))
+            return false;
+
+        framenum = parse_expression_leave(parser, true);
+        if (!framenum) {
+            parseerror(parser, "expected a framenumber constant in[frame,think] notation");
+            return false;
+        }
+        if (!ast_istype(framenum, ast_value) || !( (ast_value*)framenum )->isconst) {
+            ast_unref(framenum);
+            parseerror(parser, "framenumber in [frame,think] notation must be a constant");
+            return false;
+        }
+
+        if (parser->tok != ',') {
+            ast_unref(framenum);
+            parseerror(parser, "expected comma after frame number in [frame,think] notation");
+            parseerror(parser, "Got a %i\n", parser->tok);
+            return false;
+        }
+
+        if (!parser_next(parser)) {
+            ast_unref(framenum);
+            return false;
+        }
+
+        if (parser->tok == TOKEN_IDENT && !parser_find_var(parser, parser_tokval(parser)))
+        {
+            /* qc allows the use of not-yet-declared functions here
+             * - this automatically creates a prototype */
+            varentry_t      varent;
+            ast_value      *thinkfunc;
+            ast_expression *functype = fld_think->expression.next;
+
+            thinkfunc = ast_value_new(parser_ctx(parser), parser_tokval(parser), functype->expression.vtype);
+            if (!thinkfunc || !ast_type_adopt(thinkfunc, functype)) {
+                ast_unref(framenum);
+                parseerror(parser, "failed to create implicit prototype for `%s`", parser_tokval(parser));
+                return false;
+            }
+
+            if (!parser_next(parser)) {
+                ast_unref(framenum);
+                ast_delete(thinkfunc);
+                return false;
+            }
+
+            varent.var = (ast_expression*)thinkfunc;
+            varent.name = util_strdup(thinkfunc->name);
+            if (!parser_t_globals_add(parser, varent)) {
+                ast_unref(framenum);
+                ast_delete(thinkfunc);
+                return false;
+            }
+            nextthink = (ast_expression*)thinkfunc;
+
+        } else {
+            nextthink = parse_expression_leave(parser, true);
+            if (!nextthink) {
+                ast_unref(framenum);
+                parseerror(parser, "expected a think-function in [frame,think] notation");
+                return false;
+            }
+        }
+
+        if (!ast_istype(nextthink, ast_value)) {
+            parseerror(parser, "think-function in [frame,think] notation must be a constant");
+            retval = false;
+        }
+
+        if (retval && parser->tok != ']') {
+            parseerror(parser, "expected closing `]` for [frame,think] notation");
+            retval = false;
+        }
+
+        if (retval && !parser_next(parser)) {
+            retval = false;
+        }
+
+        if (retval && parser->tok != '{') {
+            parseerror(parser, "a function body has to be declared after a [frame,think] declaration");
+            retval = false;
+        }
+
+        if (!retval) {
+            ast_unref(nextthink);
+            ast_unref(framenum);
+            return false;
+        }
+
+        has_frame_think = true;
+    }
+
+    block = ast_block_new(parser_ctx(parser));
+    if (!block) {
+        parseerror(parser, "failed to allocate block");
+        if (has_frame_think) {
+            ast_unref(nextthink);
+            ast_unref(framenum);
+        }
+        return false;
+    }
+
+    if (has_frame_think) {
+        lex_ctx ctx;
+        ast_expression *self_frame;
+        ast_expression *self_nextthink;
+        ast_expression *self_think;
+        ast_expression *time_plus_1;
+        ast_store *store_frame;
+        ast_store *store_nextthink;
+        ast_store *store_think;
+
+        ctx = parser_ctx(parser);
+        self_frame     = (ast_expression*)ast_entfield_new(ctx, gbl_self, fld_frame);
+        self_nextthink = (ast_expression*)ast_entfield_new(ctx, gbl_self, fld_nextthink);
+        self_think     = (ast_expression*)ast_entfield_new(ctx, gbl_self, fld_think);
+
+        time_plus_1    = (ast_expression*)ast_binary_new(ctx, INSTR_ADD_F,
+                         gbl_time, (ast_expression*)parser_const_float(parser, 0.1));
+
+        if (!self_frame || !self_nextthink || !self_think || !time_plus_1) {
+            if (self_frame)     ast_delete(self_frame);
+            if (self_nextthink) ast_delete(self_nextthink);
+            if (self_think)     ast_delete(self_think);
+            if (time_plus_1)    ast_delete(time_plus_1);
+            retval = false;
+        }
+
+        if (retval)
+        {
+            store_frame     = ast_store_new(ctx, INSTR_STOREP_F,   self_frame,     framenum);
+            store_nextthink = ast_store_new(ctx, INSTR_STOREP_F,   self_nextthink, time_plus_1);
+            store_think     = ast_store_new(ctx, INSTR_STOREP_FNC, self_think,     nextthink);
+
+            if (!store_frame) {
+                ast_delete(self_frame);
+                retval = false;
+            }
+            if (!store_nextthink) {
+                ast_delete(self_nextthink);
+                retval = false;
+            }
+            if (!store_think) {
+                ast_delete(self_think);
+                retval = false;
+            }
+            if (!retval) {
+                if (store_frame)     ast_delete(store_frame);
+                if (store_nextthink) ast_delete(store_nextthink);
+                if (store_think)     ast_delete(store_think);
+                retval = false;
+            }
+            if (retval && !ast_block_exprs_add(block, (ast_expression*)store_frame)) {
+                ast_delete(store_frame);
+                ast_delete(store_nextthink);
+                ast_delete(store_think);
+                retval = false;
+            }
+
+            if (retval && !ast_block_exprs_add(block, (ast_expression*)store_nextthink)) {
+                ast_delete(store_nextthink);
+                ast_delete(store_think);
+                retval = false;
+            }
+
+            if (retval && !ast_block_exprs_add(block, (ast_expression*)store_think) )
+            {
+                ast_delete(store_think);
+                retval = false;
+            }
+        }
+
+        if (!retval) {
+            parseerror(parser, "failed to generate code for [frame,think]");
+            ast_unref(nextthink);
+            ast_unref(framenum);
+            ast_delete(block);
+            return false;
+        }
+    }
+
+    for (parami = 0; parami < var->expression.params_count; ++parami) {
+        size_t     e;
+        varentry_t ve[3];
+        ast_value *param = var->expression.params[parami];
+
+        if (param->expression.vtype != TYPE_VECTOR &&
+            (param->expression.vtype != TYPE_FIELD ||
+             param->expression.next->expression.vtype != TYPE_VECTOR))
+        {
+            continue;
+        }
+
+        if (!create_vector_members(parser, param, ve)) {
+            ast_block_delete(block);
+            return false;
+        }
+
+        for (e = 0; e < 3; ++e) {
+            if (!parser_t_locals_add(parser, ve[e]))
+                break;
+            if (!ast_block_collect(block, ve[e].var)) {
+                parser->locals_count--;
+                break;
+            }
+            ve[e].var = NULL; /* collected */
+        }
+        if (e != e) {
+            parser->locals -= e;
+            do {
+                mem_d(ve[e].name);
+                --e;
+            } while (e);
+            ast_block_delete(block);
+            return false;
+        }
+    }
+
+    func = ast_function_new(ast_ctx(var), var->name, var);
+    if (!func) {
+        parseerror(parser, "failed to allocate function for `%s`", var->name);
+        ast_block_delete(block);
+        goto enderr;
+    }
+    if (!parser_t_functions_add(parser, func)) {
+        parseerror(parser, "failed to allocate slot for function `%s`", var->name);
+        ast_block_delete(block);
+        goto enderrfn;
+    }
+
+    parser->function = func;
+    if (!parse_block_into(parser, block, true)) {
+        ast_block_delete(block);
+        goto enderrfn2;
+    }
+
+    if (!ast_function_blocks_add(func, block)) {
+        ast_block_delete(block);
+        goto enderrfn2;
+    }
+
+    parser->function = old;
+    while (parser->locals_count)
+        retval = retval && parser_pop_local(parser);
+
+    if (parser->tok == ';')
+        return parser_next(parser);
+    else if (opts_standard == COMPILER_QCC)
+        parseerror(parser, "missing semicolon after function body (mandatory with -std=qcc)");
+    return retval;
+
+enderrfn2:
+    parser->functions_count--;
+enderrfn:
+    ast_function_delete(func);
+    var->constval.vfunc = NULL;
+
+enderr:
+    while (parser->locals_count) {
+        parser->locals_count--;
+        mem_d(parser->locals[parser->locals_count].name);
+    }
+    parser->function = old;
+    return false;
+}
+
 static bool parse_variable(parser_t *parser, ast_block *localblock)
 {
-    bool          isfunc = false;
-    lex_ctx       ctx;
-    ast_value    *var;
-    varentry_t    varent;
+    bool            isfunc = false;
+    lex_ctx         ctx;
+
+    ast_value      *var = NULL;
+    ast_value      *fld = NULL;
+    bool cleanvar = false;
+
+    varentry_t      varent;
+    varentry_t      ve[3];
+
     ast_expression *olddecl;
 
-    ast_value    *typevar;
+    ast_value      *typevar;
 
     bool hadproto;
     bool isparam;
 
     bool retval = true;
+    bool isfield = false;
+
+    /* go */
+
+    int basetype;
+
+    if (parser->tok == '.') {
+        isfield = true;
+        if (!parser_next(parser)) {
+            parseerror(parser, "expected typename for field definition");
+            return false;
+        }
+    }
 
-    int basetype = parser_token(parser)->constval.t;
+    basetype = parser_token(parser)->constval.t;
 
     if (!parser_next(parser)) {
         parseerror(parser, "expected variable definition");
@@ -1942,95 +2325,56 @@ static bool parse_variable(parser_t *parser, ast_block *localblock)
 
     while (true)
     {
-        hadproto = false;
-        olddecl = NULL;
-        isparam = false;
+        hadproto    = false;
+        olddecl     = NULL;
+        isparam     = false;
+        varent.name = NULL;
+
+        ve[0].name = ve[1].name = ve[2].name = NULL;
+        ve[0].var  = ve[1].var  = ve[2].var  = NULL;
 
         ctx = parser_ctx(parser);
         var = ast_value_copy(typevar);
+        cleanvar = true;
 
         if (!var) {
-            ast_delete(typevar);
             parseerror(parser, "failed to create variable");
-            return false;
+            retval = false;
+            goto cleanup;
         }
 
         if (parser->tok != TOKEN_IDENT) {
             parseerror(parser, "expected variable name");
-            ast_value_delete(typevar);
-            ast_value_delete(var);
-            return false;
+            retval = false;
+            goto cleanup;
         }
 
-        if (!isfunc) {
-            if (!localblock && (olddecl = parser_find_global(parser, parser_tokval(parser)))) {
-                ast_value_delete(typevar);
-                ast_value_delete(var);
-                parseerror(parser, "global `%s` already declared here: %s:%i",
-                           parser_tokval(parser), ast_ctx(olddecl).file, (int)ast_ctx(olddecl).line);
-                return false;
+        if (!localblock) {
+            bool was_end = false;
+            if      (!strcmp(parser_tokval(parser), "end_sys_globals")) {
+                parser->crc_globals = parser->globals_count;
+                was_end = true;
             }
-
-            if (localblock) {
-                olddecl = parser_find_local(parser, parser_tokval(parser), parser->blocklocal, &isparam);
-                if (opts_standard == COMPILER_GMQCC)
-                {
-                    if (olddecl)
-                    {
-                        if (!isparam) {
-                            ast_value_delete(typevar);
-                            ast_value_delete(var);
-                            parseerror(parser, "local `%s` already declared here: %s:%i",
-                                       parser_tokval(parser), ast_ctx(olddecl).file, (int)ast_ctx(olddecl).line);
-                            return false;
-                        }
-                    }
-
-                    if( (!isparam && olddecl) || (olddecl = parser_find_local(parser, parser_tokval(parser), 0, &isparam)) )
-                    {
-                        if (parsewarning(parser, WARN_LOCAL_SHADOWS,
-                                         "local `%s` is shadowing a parameter", parser_tokval(parser)))
-                        {
-                            ast_value_delete(typevar);
-                            ast_value_delete(var);
-                            parseerror(parser, "local `%s` already declared here: %s:%i",
-                                       parser_tokval(parser), ast_ctx(olddecl).file, (int)ast_ctx(olddecl).line);
-                            return false;
-                        }
-                    }
-                }
-                else
+            else if (!strcmp(parser_tokval(parser), "end_sys_fields")) {
+                parser->crc_fields = parser->fields_count;
+                was_end = true;
+            }
+            if (isfield && was_end) {
+                if (parsewarning(parser, WARN_END_SYS_FIELDS,
+                                 "global '%s' hint should not be a field",
+                                 parser_tokval(parser)))
                 {
-                    if (olddecl)
-                    {
-                        ast_value_delete(var);
-                        if (isparam &&
-                            parsewarning(parser, WARN_LOCAL_SHADOWS,
-                                         "a parameter is shadowing local `%s`", parser_tokval(parser)))
-                        {
-                            ast_value_delete(typevar);
-                            ast_value_delete(var);
-                            return false;
-                        }
-                        else if (!isparam)
-                        {
-                            parseerror(parser, "local `%s` already declared here: %s:%i",
-                                       parser_tokval(parser), ast_ctx(olddecl).file, (int)ast_ctx(olddecl).line);
-                            ast_value_delete(typevar);
-                            ast_value_delete(var);
-                            return false;
-                        }
-                        goto nextvar;
-                    }
+                    retval = false;
+                    goto cleanup;
                 }
+
             }
         }
 
         if (!ast_value_set_name(var, parser_tokval(parser))) {
             parseerror(parser, "failed to set variable name\n");
-            ast_value_delete(typevar);
-            ast_value_delete(var);
-            return false;
+            retval = false;
+            goto cleanup;
         }
 
         if (isfunc) {
@@ -2047,16 +2391,13 @@ static bool parse_variable(parser_t *parser, ast_block *localblock)
             if (olddecl) {
                 /* we had a prototype */
                 if (!ast_istype(olddecl, ast_value)) {
-                    /* theoretically not possible you think?
-                     * well:
-                     * vector v;
+                    /* vector v;
                      * void() v_x = {}
-                     * got it?
                      */
                     parseerror(parser, "cannot declare a function with the same name as a vector's member: %s",
                                parser_tokval(parser));
-                    ast_value_delete(var);
-                    return false;
+                    retval = false;
+                    goto cleanup;
                 }
 
                 proto = (ast_value*)olddecl;
@@ -2067,15 +2408,14 @@ static bool parse_variable(parser_t *parser, ast_block *localblock)
              */
             fval = ast_value_new(ctx, var->name, TYPE_FUNCTION);
             if (!fval) {
-                ast_value_delete(var);
-                ast_value_delete(typevar);
-                if (fval) ast_value_delete(fval);
-                return false;
+                retval = false;
+                goto cleanup;
             }
 
             fval->expression.next = (ast_expression*)var;
             MEM_VECTOR_MOVE(&var->expression, params, &fval->expression, params);
             fval->expression.variadic = var->expression.variadic;
+            var = NULL;
 
             /* we compare the type late here, but it's easier than
              * messing with the parameter-vector etc. earlier
@@ -2087,8 +2427,8 @@ static bool parse_variable(parser_t *parser, ast_block *localblock)
                                proto->name,
                                ast_ctx(proto).file, ast_ctx(proto).line);
                     ast_value_delete(fval);
-                    ast_value_delete(typevar);
-                    return false;
+                    retval = false;
+                    goto cleanup;
                 }
                 /* copy over the parameter names */
                 for (param = 0; param < fval->expression.params_count; ++param)
@@ -2105,85 +2445,222 @@ static bool parse_variable(parser_t *parser, ast_block *localblock)
             var = fval;
         }
 
-        if (!hadproto) {
-            varent.name = util_strdup(var->name);
-            varent.var = (ast_expression*)var;
-            if (var->expression.vtype == TYPE_VECTOR)
+        if (isfield) {
+            ast_value *tmp;
+            fld = ast_value_new(ctx, var->name, TYPE_FIELD);
+            fld->expression.next = (ast_expression*)var;
+            tmp = var;
+            var = fld;
+            fld = tmp;
+        }
+        else
+            fld = var;
+
+        if (!isfunc) {
+            if (!localblock)
             {
-                varentry_t ve[3];
-                if (!create_vector_members(parser, var, ve)) {
-                    ast_delete(var);
-                    ast_value_delete(typevar);
-                    return false;
+                olddecl = parser_find_global(parser, var->name);
+                if (olddecl) {
+                    if (!isfield) {
+                        parseerror(parser, "global `%s` already declared here: %s:%i",
+                                   var->name, ast_ctx(olddecl).file, (int)ast_ctx(olddecl).line);
+                        retval = false;
+                        goto cleanup;
+                    }
+                    else if (opts_standard == COMPILER_QCC) {
+                        parseerror(parser, "cannot declare a field and a global of the same name with -std=qcc");
+                        parseerror(parser, "global `%s` already declared here: %s:%i",
+                                   var->name, ast_ctx(olddecl).file, (int)ast_ctx(olddecl).line);
+                        retval = false;
+                        goto cleanup;
+                    }
                 }
-
-                if (!localblock) {
-                    (void)!parser_t_globals_add(parser, varent);
-                    (void)!parser_t_globals_add(parser, ve[0]);
-                    (void)!parser_t_globals_add(parser, ve[1]);
-                    (void)!parser_t_globals_add(parser, ve[2]);
-                } else {
-                    (void)!parser_t_locals_add(parser, varent);
-                    (void)!parser_t_locals_add(parser, ve[0]);
-                    (void)!parser_t_locals_add(parser, ve[1]);
-                    (void)!parser_t_locals_add(parser, ve[2]);
-                    if (!ast_block_locals_add(localblock, var) ||
-                        !ast_block_collect(localblock, ve[0].var) ||
-                        !ast_block_collect(localblock, ve[1].var) ||
-                        !ast_block_collect(localblock, ve[2].var))
+                olddecl = parser_find_field(parser, var->name);
+                if (olddecl && opts_standard == COMPILER_QCC) {
+                    if (!isfield) {
+                        parseerror(parser, "cannot declare a field and a global of the same name with -std=qcc");
+                        parseerror(parser, "field `%s` already declared here: %s:%i",
+                                   var->name, ast_ctx(olddecl).file, (int)ast_ctx(olddecl).line);
+                        retval = false;
+                        goto cleanup;
+                    }
+                    else
                     {
-                        (void)!parser_pop_local(parser);
-                        (void)!parser_pop_local(parser);
-                        (void)!parser_pop_local(parser);
-                        (void)!parser_pop_local(parser);
-                        ast_value_delete(var);
-                        ast_value_delete(typevar);
-                        return false;
+                        if (parsewarning(parser, WARN_FIELD_REDECLARED, "field `%s` already declared here: %s:%i",
+                                         var->name, ast_ctx(olddecl).file, (int)ast_ctx(olddecl).line))
+                        {
+                            retval = false;
+                            goto cleanup;
+                        }
+                        if (!ast_compare_type(olddecl, (ast_expression*)var)) {
+                            parseerror(parser, "field %s has previously been declared with a different type here: %s:%i",
+                                       var->name, ast_ctx(olddecl).file, (int)ast_ctx(olddecl).line);
+                            retval = false;
+                            goto cleanup;
+                        }
+                        ast_delete(var);
+                        var = NULL;
+                        goto nextvar;
                     }
                 }
+                else if (olddecl) {
+                    parseerror(parser, "field `%s` already declared here: %s:%i",
+                               var->name, ast_ctx(olddecl).file, (int)ast_ctx(olddecl).line);
+                    retval = false;
+                    goto cleanup;
+                }
             }
-            else
+            else /* if it's a local: */
             {
-                if ( (!localblock && !parser_t_globals_add(parser, varent)) ||
-                     ( localblock && !parser_t_locals_add(parser, varent)) )
+                olddecl = parser_find_local(parser, var->name, parser->blocklocal, &isparam);
+                if (opts_standard == COMPILER_GMQCC)
                 {
-                    ast_value_delete(var);
-                    ast_value_delete(typevar);
-                    return false;
+                    if (olddecl)
+                    {
+                        if (!isparam) {
+                            parseerror(parser, "local `%s` already declared here: %s:%i",
+                                       var->name, ast_ctx(olddecl).file, (int)ast_ctx(olddecl).line);
+                            retval = false;
+                            goto cleanup;
+                        }
+                    }
+
+                    if( (!isparam && olddecl) ||
+                        (olddecl = parser_find_local(parser, var->name, 0, &isparam))
+                      )
+                    {
+                        if (parsewarning(parser, WARN_LOCAL_SHADOWS,
+                                         "local `%s` is shadowing a parameter", var->name))
+                        {
+                            parseerror(parser, "local `%s` already declared here: %s:%i",
+                                       var->name, ast_ctx(olddecl).file, (int)ast_ctx(olddecl).line);
+                            retval = false;
+                            goto cleanup;
+                        }
+                    }
                 }
-                if (localblock && !ast_block_locals_add(localblock, var))
+                else
                 {
-                    (void)!parser_pop_local(parser);
-                    ast_value_delete(var);
-                    ast_value_delete(typevar);
-                    return false;
-                }
-            }
+                    if (olddecl)
+                    {
+                        if (isparam &&
+                            parsewarning(parser, WARN_LOCAL_SHADOWS,
+                                         "a parameter is shadowing local `%s`", var->name))
+                        {
+                            ast_value_delete(var);
+                            var = NULL;
+                            retval = false;
+                            goto cleanup;
+                        }
+                        else if (!isparam)
+                        {
+                            parseerror(parser, "local `%s` already declared here: %s:%i",
+                                       var->name, ast_ctx(olddecl).file, (int)ast_ctx(olddecl).line);
+                            ast_value_delete(var);
+                            var = NULL;
+                            retval = false;
+                            goto cleanup;
+                        }
+                        ast_value_delete(var);
+                        var = NULL;
+                        goto nextvar;
+                    }
+                }
+            }
         }
 
-nextvar:
-        if (!parser_next(parser)) {
-            ast_value_delete(typevar);
-            ast_value_delete(var);
-            return false;
+
+        if (!hadproto) {
+            varent.name = util_strdup(var->name);
+            varent.var = (ast_expression*)var;
+
+            if (!localblock) {
+                if (!isfield) {
+                    if (!(retval = parser_t_globals_add(parser, varent)))
+                        goto cleanup;
+                }
+                else {
+                    if (!(retval = parser_t_fields_add(parser, varent)))
+                        goto cleanup;
+                }
+            } else {
+                if (!(retval = parser_t_locals_add(parser, varent)))
+                    goto cleanup;
+                if (!(retval = ast_block_locals_add(localblock, var))) {
+                    parser->locals_count--;
+                    goto cleanup;
+                }
+            }
+
+            if (fld->expression.vtype == TYPE_VECTOR)
+            {
+                size_t e;
+                if (!create_vector_members(parser, var, ve)) {
+                    retval = false;
+                    goto cleanup;
+                }
+
+                if (!localblock) {
+                    for (e = 0; e < 3; ++e) {
+                        if (!isfield) {
+                            if (!(retval = parser_t_globals_add(parser, ve[e])))
+                                break;
+                        }
+                        else {
+                            if (!(retval = parser_t_fields_add(parser, ve[e])))
+                                break;
+                        }
+                    }
+                    if (!retval) {
+                        parser->globals_count -= e+1;
+                        goto cleanup;
+                    }
+                } else {
+                    for (e = 0; e < 3; ++e) {
+                        if (!(retval = parser_t_locals_add(parser, ve[e])))
+                            break;
+                        if (!(retval = ast_block_collect(localblock, ve[e].var)))
+                            break;
+                        ve[e].var = NULL; /* from here it's being collected in the block */
+                    }
+                    if (!retval) {
+                        parser->locals_count -= e+1;
+                        localblock->locals_count--;
+                        goto cleanup;
+                    }
+                }
+                ve[0].name = ve[1].name = ve[2].name = NULL;
+                ve[0].var  = ve[1].var  = ve[2].var  = NULL;
+            }
+            cleanvar = false;
+            varent.name = NULL;
         }
 
+nextvar:
+        if (!(retval = parser_next(parser)))
+            goto cleanup;
+
         if (parser->tok == ';') {
             ast_value_delete(typevar);
-            if (!parser_next(parser))
-                return false;
-            return true;
+            return parser_next(parser);
         }
 
         if (parser->tok == ',') {
             /* another var */
-            if (!parser_next(parser)) {
-                ast_delete(typevar);
-                return false;
-            }
+            if (!(retval = parser_next(parser)))
+                goto cleanup;
             continue;
         }
 
+        if (!localblock && isfield) {
+            parseerror(parser, "missing semicolon");
+            ast_value_delete(typevar);
+            return false;
+        }
+
+        /* NOTE: only 'typevar' needs to be deleted from here on, so 'cleanup' won't be used
+         * to avoid having too many gotos
+         */
         if (localblock && opts_standard == COMPILER_QCC) {
             if (parsewarning(parser, WARN_LOCAL_CONSTANTS,
                              "initializing expression turns variable `%s` into a constant in this standard",
@@ -2195,8 +2672,11 @@ nextvar:
         }
 
         if (parser->tok != '=') {
+            if (opts_standard == COMPILER_QCC)
+                parseerror(parser, "missing semicolon");
+            else
+                parseerror(parser, "missing semicolon or initializer");
             ast_value_delete(typevar);
-            parseerror(parser, "expected '=' or ';'");
             return false;
         }
 
@@ -2254,283 +2734,19 @@ nextvar:
                 ast_value_delete(typevar);
                 return false;
             }
-        } else if (parser->tok == '{' || parser->tok == '[') {
-            /* function body */
-            ast_function *func;
-            ast_function *old;
-            ast_block *block;
-            size_t     parami;
-
-            ast_expression *fld_think, *fld_nextthink, *fld_frame;
-            ast_expression *gbl_time, *gbl_self;
-            ast_expression *framenum, *nextthink;
-            bool            has_frame_think;
-
-            has_frame_think = false;
-            old = parser->function;
-
-            if (var->expression.variadic) {
-                if (parsewarning(parser, WARN_VARIADIC_FUNCTION,
-                                 "variadic function with implementation will not be able to access additional parameters"))
-                {
-                    ast_value_delete(typevar);
-                    return false;
-                }
-            }
-
+        }
+        else if (parser->tok == '{' || parser->tok == '[')
+        {
+            ast_value_delete(typevar);
             if (localblock) {
                 parseerror(parser, "cannot declare functions within functions");
-                ast_value_delete(typevar);
-                return false;
-            }
-
-            if (parser->tok == '[') {
-                /* got a frame definition: [ framenum, nextthink ]
-                 * this translates to:
-                 * self.frame = framenum;
-                 * self.nextthink = time + 0.1;
-                 * self.think = nextthink;
-                 */
-                nextthink = NULL;
-
-                fld_think     = parser_find_field(parser, "think");
-                fld_nextthink = parser_find_field(parser, "nextthink");
-                fld_frame     = parser_find_field(parser, "frame");
-                if (!fld_think || !fld_nextthink || !fld_frame) {
-                    parseerror(parser, "cannot use [frame,think] notation without the required fields");
-                    parseerror(parser, "please declare the following entityfields: `frame`, `think`, `nextthink`");
-                    ast_value_delete(typevar);
-                    return false;
-                }
-                gbl_time      = parser_find_global(parser, "time");
-                gbl_self      = parser_find_global(parser, "self");
-                if (!gbl_time || !gbl_self) {
-                    parseerror(parser, "cannot use [frame,think] notation without the required globals");
-                    parseerror(parser, "please declare the following globals: `time`, `self`");
-                    ast_value_delete(typevar);
-                    return false;
-                }
-
-                if (!parser_next(parser)) {
-                    ast_value_delete(typevar);
-                    return false;
-                }
-
-                framenum = parse_expression_leave(parser, true);
-                if (!framenum) {
-                    parseerror(parser, "expected a framenumber constant in[frame,think] notation");
-                    ast_value_delete(typevar);
-                    return false;
-                }
-                if (!ast_istype(framenum, ast_value) || !( (ast_value*)framenum )->isconst) {
-                    ast_unref(framenum);
-                    parseerror(parser, "framenumber in [frame,think] notation must be a constant");
-                }
-
-                if (parser->tok != ',') {
-                    ast_unref(framenum);
-                    parseerror(parser, "expected comma after frame number in [frame,think] notation");
-                    parseerror(parser, "Got a %i\n", parser->tok);
-                    ast_value_delete(typevar);
-                    return false;
-                }
-
-                if (!parser_next(parser)) {
-                    ast_unref(framenum);
-                    ast_value_delete(typevar);
-                    return false;
-                }
-
-                if (parser->tok == TOKEN_IDENT && !parser_find_var(parser, parser_tokval(parser)))
-                {
-                    /* qc allows the use of not-yet-declared functions here
-                     * - this automatically creates a prototype */
-                    varentry_t      varent;
-                    ast_value      *thinkfunc;
-                    ast_expression *functype = fld_think->expression.next;
-
-                    thinkfunc = ast_value_new(parser_ctx(parser), parser_tokval(parser), functype->expression.vtype);
-                    if (!thinkfunc || !ast_type_adopt(thinkfunc, functype)) {
-                        ast_unref(framenum);
-                        parseerror(parser, "failed to create implicit prototype for `%s`", parser_tokval(parser));
-                        ast_value_delete(typevar);
-                        return false;
-                    }
-
-                    if (!parser_next(parser)) {
-                        ast_unref(framenum);
-                        ast_value_delete(typevar);
-                        return false;
-                    }
-
-                    varent.var = (ast_expression*)thinkfunc;
-                    varent.name = util_strdup(thinkfunc->name);
-                    (void)!parser_t_globals_add(parser, varent);
-                    nextthink = (ast_expression*)thinkfunc;
-
-                } else {
-                    nextthink = parse_expression_leave(parser, true);
-                    if (!nextthink) {
-                        ast_unref(framenum);
-                        parseerror(parser, "expected a think-function in [frame,think] notation");
-                        ast_value_delete(typevar);
-                        return false;
-                    }
-                }
-
-                if (!ast_istype(nextthink, ast_value)) {
-                    ast_unref(nextthink);
-                    ast_unref(framenum);
-                    parseerror(parser, "think-function in [frame,think] notation must be a constant");
-                }
-
-                if (parser->tok != ']') {
-                    parseerror(parser, "expected closing `]` for [frame,think] notation");
-                    ast_unref(nextthink);
-                    ast_unref(framenum);
-                    ast_value_delete(typevar);
-                    return false;
-                }
-
-                if (!parser_next(parser)) {
-                    ast_unref(nextthink);
-                    ast_unref(framenum);
-                    ast_value_delete(typevar);
-                    return false;
-                }
-
-                if (parser->tok != '{') {
-                    parseerror(parser, "a function body has to be declared after a [frame,think] declaration");
-                    ast_unref(nextthink);
-                    ast_unref(framenum);
-                    ast_value_delete(typevar);
-                    return false;
-                }
-
-                has_frame_think = true;
-            }
-
-            block = ast_block_new(parser_ctx(parser));
-            if (!block) {
-                parseerror(parser, "failed to allocate block");
-                ast_value_delete(typevar);
-                return false;
-            }
-
-            if (has_frame_think) {
-                lex_ctx ctx;
-                ast_expression *self_frame;
-                ast_expression *self_nextthink;
-                ast_expression *self_think;
-                ast_expression *time_plus_1;
-                ast_store *store_frame;
-                ast_store *store_nextthink;
-                ast_store *store_think;
-
-                ctx = parser_ctx(parser);
-                self_frame     = (ast_expression*)ast_entfield_new(ctx, gbl_self, fld_frame);
-                self_nextthink = (ast_expression*)ast_entfield_new(ctx, gbl_self, fld_nextthink);
-                self_think     = (ast_expression*)ast_entfield_new(ctx, gbl_self, fld_think);
-
-                time_plus_1    = (ast_expression*)ast_binary_new(ctx, INSTR_ADD_F,
-                                 gbl_time, (ast_expression*)parser_const_float(parser, 0.1));
-
-                store_frame     = ast_store_new(ctx, INSTR_STOREP_F,   self_frame,     framenum);
-                store_nextthink = ast_store_new(ctx, INSTR_STOREP_F,   self_nextthink, time_plus_1);
-                store_think     = ast_store_new(ctx, INSTR_STOREP_FNC, self_think,     nextthink);
-
-                if (!ast_block_exprs_add(block, (ast_expression*)store_frame)     ||
-                    !ast_block_exprs_add(block, (ast_expression*)store_nextthink) ||
-                    !ast_block_exprs_add(block, (ast_expression*)store_think) )
-                {
-                    parseerror(parser, "failed to generate code for [frame,think]");
-                    ast_block_delete(block);
-                    ast_value_delete(typevar);
-                    return false;
-                }
-            }
-
-            for (parami = 0; parami < var->expression.params_count; ++parami) {
-                ast_value *param = var->expression.params[parami];
-                varentry_t ve[3];
-
-                if (param->expression.vtype != TYPE_VECTOR &&
-                    (param->expression.vtype != TYPE_FIELD ||
-                     param->expression.next->expression.vtype != TYPE_VECTOR))
-                {
-                    continue;
-                }
-
-                if (!create_vector_members(parser, param, ve)) {
-                    ast_block_delete(block);
-                    ast_value_delete(typevar);
-                    return false;
-                }
-
-                (void)!parser_t_locals_add(parser, ve[0]);
-                (void)!parser_t_locals_add(parser, ve[1]);
-                (void)!parser_t_locals_add(parser, ve[2]);
-                if (!ast_block_collect(block, ve[0].var) ||
-                    !ast_block_collect(block, ve[1].var) ||
-                    !ast_block_collect(block, ve[2].var) )
-                {
-                    (void)!parser_pop_local(parser);
-                    (void)!parser_pop_local(parser);
-                    (void)!parser_pop_local(parser);
-                    ast_block_delete(block);
-                    ast_value_delete(typevar);
-                    return false;
-                }
-            }
-
-            func = ast_function_new(ast_ctx(var), var->name, var);
-            if (!func) {
-                parseerror(parser, "failed to allocate function for `%s`", var->name);
-                ast_block_delete(block);
-                parser->function = old;
-                ast_value_delete(typevar);
-                return false;
-            }
-            if (!parser_t_functions_add(parser, func)) {
-                parseerror(parser, "failed to allocate slot for function `%s`", var->name);
-                ast_function_delete(func);
-                var->constval.vfunc = NULL;
-                ast_value_delete(typevar);
-                ast_block_delete(block);
-                parser->function = old;
-                return false;
-            }
-
-            parser->function = func;
-            if (!parse_block_into(parser, block, true)) {
-                ast_block_delete(block);
-                parser->function = old;
-                ast_value_delete(typevar);
                 return false;
             }
-            parser->function = old;
-            while (parser->locals_count)
-                retval = retval && parser_pop_local(parser);
 
-            if (!block) {
-                ast_value_delete(typevar);
+            if (!parse_function_body(parser, var)) {
                 return false;
             }
-
-            if (!ast_function_blocks_add(func, block)) {
-                ast_block_delete(block);
-                ast_value_delete(typevar);
-                return false;
-            }
-
-            if (parser->tok == ';') {
-                ast_value_delete(typevar);
-                return parser_next(parser) || parser->tok == TOKEN_EOF;
-            }
-            else if (opts_standard == COMPILER_QCC)
-                parseerror(parser, "missing semicolon after function body (mandatory with -std=qcc)");
-            ast_value_delete(typevar);
-            return retval;
+            return true;
         } else {
             ast_expression *cexp;
             ast_value      *cval;
@@ -2571,11 +2787,24 @@ nextvar:
         ast_value_delete(typevar);
         return true;
     }
+
+cleanup:
+    ast_delete(typevar);
+    if (var && cleanvar) ast_delete(var);
+    if (varent.name) mem_d(varent.name);
+    if (ve[0].name)  mem_d(ve[0].name);
+    if (ve[1].name)  mem_d(ve[1].name);
+    if (ve[2].name)  mem_d(ve[2].name);
+    if (ve[0].var)   mem_d(ve[0].var);
+    if (ve[1].var)   mem_d(ve[1].var);
+    if (ve[2].var)   mem_d(ve[2].var);
+
+    return retval;
 }
 
 static bool parser_global_statement(parser_t *parser)
 {
-    if (parser->tok == TOKEN_TYPENAME)
+    if (parser->tok == TOKEN_TYPENAME || parser->tok == '.')
     {
         return parse_variable(parser, NULL);
     }
@@ -2584,144 +2813,6 @@ static bool parser_global_statement(parser_t *parser)
         /* handle 'var' and 'const' */
         return false;
     }
-    else if (parser->tok == '.')
-    {
-        ast_value *var;
-        ast_value *typevar;
-        ast_value *fld;
-        ast_expression *oldex;
-        bool       isfunc = false;
-        int        basetype;
-        lex_ctx    ctx = parser_ctx(parser);
-        varentry_t varent;
-
-        /* entity-member declaration */
-        if (!parser_next(parser) || parser->tok != TOKEN_TYPENAME) {
-            parseerror(parser, "expected member variable definition");
-            return false;
-        }
-
-        /* remember the base/return type */
-        basetype = parser_token(parser)->constval.t;
-
-        /* parse into the declaration */
-        if (!parser_next(parser)) {
-            parseerror(parser, "expected field definition");
-            return false;
-        }
-
-        /* parse the field type fully */
-        typevar = var = parse_type(parser, basetype, &isfunc);
-        if (!var)
-            return false;
-
-        while (true) {
-            var = ast_value_copy(typevar);
-            /* now the field name */
-            if (parser->tok != TOKEN_IDENT) {
-                parseerror(parser, "expected field name");
-                ast_delete(var);
-                return false;
-            }
-
-            /* check for an existing field
-             * in original qc we also have to check for an existing
-             * global named like the field
-             */
-            if (opts_standard == COMPILER_QCC) {
-                if (parser_find_global(parser, parser_tokval(parser))) {
-                    parseerror(parser, "cannot declare a field and a global of the same name with -std=qcc");
-                    ast_delete(var);
-                    return false;
-                }
-            }
-
-            if (isfunc) {
-                ast_value *fval;
-                fval = ast_value_new(ctx, var->name, TYPE_FUNCTION);
-                if (!fval) {
-                    ast_value_delete(var);
-                    return false;
-                }
-                fval->expression.next = (ast_expression*)var;
-                MEM_VECTOR_MOVE(&var->expression, params, &fval->expression, params);
-                fval->expression.variadic = var->expression.variadic;
-                var = fval;
-            }
-
-            /* turn it into a field */
-            fld = ast_value_new(ctx, parser_tokval(parser), TYPE_FIELD);
-            fld->expression.next = (ast_expression*)var;
-
-            if ( (oldex = parser_find_field(parser, parser_tokval(parser)))) {
-                if (ast_istype(oldex, ast_member)) {
-                    parseerror(parser, "cannot declare a field with the same name as a vector component, component %s has been declared here: %s:%i",
-                               parser_tokval(parser), ast_ctx(oldex).file, (int)ast_ctx(oldex).line);
-                    ast_delete(fld);
-                    return false;
-                }
-                if (!ast_istype(oldex, ast_value)) {
-                    /* not possible / sanity check */
-                    parseerror(parser, "internal error: %s is not an ast_value", parser_tokval(parser));
-                    ast_delete(fld);
-                    return false;
-                }
-
-                if (!ast_compare_type(oldex, (ast_expression*)fld)) {
-                    parseerror(parser, "field %s has previously been declared with a different type here: %s:%i",
-                               parser_tokval(parser), ast_ctx(oldex).file, (int)ast_ctx(oldex).line);
-                    ast_delete(fld);
-                    return false;
-                } else {
-                    if (parsewarning(parser, WARN_FIELD_REDECLARED, "field `%s` has already been declared here: %s:%i",
-                                     parser_tokval(parser), ast_ctx(oldex).file, (int)ast_ctx(oldex).line))
-                    {
-                        ast_delete(fld);
-                        return false;
-                    }
-                }
-
-                ast_delete(fld);
-                goto nextfield;
-            }
-
-            varent.var = (ast_expression*)fld;
-            varent.name = util_strdup(fld->name);
-            (void)!parser_t_fields_add(parser, varent);
-
-            if (var->expression.vtype == TYPE_VECTOR)
-            {
-                /* create _x, _y and _z fields as well */
-                varentry_t ve[3];
-                if (!create_vector_members(parser, fld, ve)) {
-                    ast_delete(fld);
-                    return false;
-                }
-                (void)!parser_t_fields_add(parser, ve[0]);
-                (void)!parser_t_fields_add(parser, ve[1]);
-                (void)!parser_t_fields_add(parser, ve[2]);
-            }
-
-nextfield:
-            if (!parser_next(parser)) {
-                parseerror(parser, "expected semicolon or another field name");
-                return false;
-            }
-            if (parser->tok == ';')
-                break;
-            if (parser->tok != ',' || !parser_next(parser)) {
-                parseerror(parser, "expected semicolon or another field name");
-                return false;
-            }
-        }
-        ast_delete(typevar);
-
-        /* skip the semicolon */
-        if (!parser_next(parser))
-            return parser->tok == TOKEN_EOF;
-
-        return true;
-    }
     else if (parser->tok == '$')
     {
         if (!parser_next(parser)) {
@@ -2731,7 +2822,7 @@ nextfield:
     }
     else
     {
-        parseerror(parser, "unexpected token: %s", parser->lex->tok->value);
+        parseerror(parser, "unexpected token: %s", parser->lex->tok.value);
         return false;
     }
     return true;
@@ -2768,7 +2859,7 @@ bool parser_compile(const char *filename)
                 if (parser->tok == TOKEN_EOF)
                     parseerror(parser, "unexpected eof");
                 else if (!parser->errors)
-                    parseerror(parser, "parse error");
+                    parseerror(parser, "there have been errors, bailing out");
                 lex_close(parser->lex);
                 parser->lex = NULL;
                 return false;
@@ -2821,6 +2912,78 @@ void parser_cleanup()
     mem_d(parser);
 }
 
+static uint16_t progdefs_crc_sum(uint16_t old, const char *str)
+{
+    return util_crc16(old, str, strlen(str));
+}
+
+static void progdefs_crc_file(const char *str)
+{
+    /* write to progdefs.h here */
+}
+
+static uint16_t progdefs_crc_both(uint16_t old, const char *str)
+{
+    old = progdefs_crc_sum(old, str);
+    progdefs_crc_file(str);
+    return old;
+}
+
+static void generate_checksum(parser_t *parser)
+{
+    uint16_t crc = 0xFFFF;
+    size_t i;
+
+       crc = progdefs_crc_both(crc, "\n/* file generated by qcc, do not modify */\n\ntypedef struct\n{");
+       crc = progdefs_crc_sum(crc, "\tint\tpad[28];\n");
+       /*
+       progdefs_crc_file("\tint\tpad;\n");
+       progdefs_crc_file("\tint\tofs_return[3];\n");
+       progdefs_crc_file("\tint\tofs_parm0[3];\n");
+       progdefs_crc_file("\tint\tofs_parm1[3];\n");
+       progdefs_crc_file("\tint\tofs_parm2[3];\n");
+       progdefs_crc_file("\tint\tofs_parm3[3];\n");
+       progdefs_crc_file("\tint\tofs_parm4[3];\n");
+       progdefs_crc_file("\tint\tofs_parm5[3];\n");
+       progdefs_crc_file("\tint\tofs_parm6[3];\n");
+       progdefs_crc_file("\tint\tofs_parm7[3];\n");
+       */
+       for (i = 0; i < parser->crc_globals; ++i) {
+           if (!ast_istype(parser->globals[i].var, ast_value))
+               continue;
+           switch (parser->globals[i].var->expression.vtype) {
+               case TYPE_FLOAT:    crc = progdefs_crc_both(crc, "\tfloat\t"); break;
+               case TYPE_VECTOR:   crc = progdefs_crc_both(crc, "\tvec3_t\t"); break;
+               case TYPE_STRING:   crc = progdefs_crc_both(crc, "\tstring_t\t"); break;
+               case TYPE_FUNCTION: crc = progdefs_crc_both(crc, "\tfunc_t\t"); break;
+               default:
+                   crc = progdefs_crc_both(crc, "\tint\t");
+                   break;
+           }
+           crc = progdefs_crc_both(crc, parser->globals[i].name);
+           crc = progdefs_crc_both(crc, ";\n");
+       }
+       crc = progdefs_crc_both(crc, "} globalvars_t;\n\ntypedef struct\n{\n");
+       for (i = 0; i < parser->crc_fields; ++i) {
+           if (!ast_istype(parser->fields[i].var, ast_value))
+               continue;
+           switch (parser->fields[i].var->expression.next->expression.vtype) {
+               case TYPE_FLOAT:    crc = progdefs_crc_both(crc, "\tfloat\t"); break;
+               case TYPE_VECTOR:   crc = progdefs_crc_both(crc, "\tvec3_t\t"); break;
+               case TYPE_STRING:   crc = progdefs_crc_both(crc, "\tstring_t\t"); break;
+               case TYPE_FUNCTION: crc = progdefs_crc_both(crc, "\tfunc_t\t"); break;
+               default:
+                   crc = progdefs_crc_both(crc, "\tint\t");
+                   break;
+           }
+           crc = progdefs_crc_both(crc, parser->fields[i].name);
+           crc = progdefs_crc_both(crc, ";\n");
+       }
+       crc = progdefs_crc_both(crc, "} entvars_t;\n\n");
+
+       code_crc = crc;
+}
+
 bool parser_finish(const char *output)
 {
     size_t i;
@@ -2867,8 +3030,12 @@ bool parser_finish(const char *output)
                 continue;
             asvalue = (ast_value*)(parser->globals[i].var);
             if (!asvalue->uses && !asvalue->isconst && asvalue->expression.vtype != TYPE_FUNCTION) {
-                retval = retval && !genwarning(ast_ctx(asvalue), WARN_UNUSED_VARIABLE,
-                                               "unused global: `%s`", asvalue->name);
+                if (strcmp(asvalue->name, "end_sys_globals") &&
+                    strcmp(asvalue->name, "end_sys_fields"))
+                {
+                    retval = retval && !genwarning(ast_ctx(asvalue), WARN_UNUSED_VARIABLE,
+                                                   "unused global: `%s`", asvalue->name);
+                }
             }
             if (!ast_global_codegen(asvalue, ir)) {
                 printf("failed to generate global %s\n", parser->globals[i].name);
@@ -2914,6 +3081,8 @@ bool parser_finish(const char *output)
             if (opts_dump)
                 ir_builder_dump(ir, printf);
 
+            generate_checksum(parser);
+
             if (!ir_builder_generate(ir, output)) {
                 printf("*** failed to generate output file\n");
                 ir_builder_delete(ir);