Rune - Change regsave burden for syscalls
[rune.git] / librune / parse2.c
1 /*
2  * PARSE2.C     - Misc parser support, including declarator handling
3  *
4  * (c)Copyright 1993-2018, Matthew Dillon, All Rights Reserved.  See the  
5  *    COPYRIGHT file at the base of the distribution.
6  */
7
8 #include "defs.h"
9
10 static int FinishDecl(Parse *p, int t, Declaration *d, Type *type);
11 static int ParseDeclarationList(Parse *p, int t, int scopeFlags,
12                         int idRequired, int dop);
13
14
15 /*
16  * Parse scope qualifiers.
17  *
18  * Locking scope flags are mutually exclusive and replace each other.
19  *
20  * XXX handle scope overrides
21  */
22 int
23 ParseScopeQual(Parse *p, int t, Scope *scope)
24 {
25         int mask;
26
27         scope->s_Flags = 0;
28         scope->s_AlignOverride = 0;
29
30         while (t & TOKF_SCOPE_QUAL) {
31                 mask = 1 << (t & TOKF_SCOPE_MASK);
32                 if (mask & SCOPE_LOCKING_MASK)
33                         scope->s_Flags &= ~SCOPE_LOCKING_MASK;
34                 scope->s_Flags |= mask;
35
36                 if (t == TOK_ALIGN) {
37                         t = LexToken(&p->p_Token);
38                         t = LexSkipToken(&p->p_Token, TOK_OPAREN);
39                         t = SimpleIntToken(&p->p_Token,
40                                            &scope->s_AlignOverride);
41                         t = LexSkipToken(&p->p_Token, TOK_INTEGER);
42                         t = LexSkipToken(&p->p_Token, TOK_CPAREN);
43                 } else {
44                         t = LexToken(&p->p_Token);
45                 }
46         }
47
48         /*
49          * Persistent storage is represented as an lvalue element
50          * Heap storage is represented as an lvalue element.
51          *
52          * lvalue elements are represented as an LValueStor structure
53          * which points to the object.  Even though this is physically a
54          * pointer, actions occur on the underlying object as if it were
55          * an lvalue.
56          */
57         if (scope->s_Flags & (SCOPE_PERSIST | SCOPE_HEAP))
58                 scope->s_Flags |= SCOPE_LVALUE;
59         return(t);
60 }
61
62 /*
63  * Locking storage qualifier flags are mutually exclusive and replace each
64  * other.
65  *
66  * XXX handle illegal storage qualifier combinations & overrides
67  */
68 int
69 ParseStorageQual(Parse *p, int t, int *pmask)
70 {
71         int res = 0;
72         int mask;
73
74         while (t & TOKF_STOR_QUAL) {
75                 mask = 1 << (t & TOKF_STOR_MASK);
76                 if (mask & SF_LOCKING_MASK)
77                         res &= ~SF_LOCKING_MASK;
78                 res |= mask;
79                 t = LexToken(&p->p_Token);
80         }
81         *pmask = res;
82
83         return(t);
84 }
85
86 /*
87  * declaration: type decl(idReq) [= exp]
88  *
89  * idRequired may be 0, 1, or 2.
90  *
91  *      0:      No identifier is required
92  *      1:      An identifier is required
93  *      2:      An identifier is required, a dotted identifier sequence is
94  *              optional, and global scope is implied if only a single
95  *              identifier is used.
96  *
97  * NOTE: We only handle the procedural reference portion of a procedure
98  *       definition here.  We do not handle the procedure body.  See
99  *       ParseDeclarationStmt().  We also handle aliases here.
100  *
101  * NOTE: TOK_ALIAS can be passed in and will handle alias declarations,
102  *       including converting the declaration to DOP_ALIAS.
103  */
104 int
105 ParseDeclaration(Parse *p, int t, Declaration **pd, int idRequired,
106                  int dop, Scope *scope)
107 {
108         Declaration *d;
109         int sqflags = 0;
110         int rqflags = 0;
111         int isAlias = 0;
112         int isCast = 0;
113         int isOper = 0;
114         int isMeth = 0;
115         string_t id = NULL;
116         string_t opid = NULL;
117         Type *type;
118         Scope tscope = *scope;
119
120         /*
121          * Handle alias declarations.
122          */
123         if (t == TOK_ALIAS) {
124                 isAlias = 1;
125                 t = LexToken(&p->p_Token);
126         }
127
128         /*
129          * Handle procedure-related special cases
130          */
131         switch(t) {
132         case TOK_CAST:
133                 t = LexToken(&p->p_Token);
134                 tscope.s_Flags |= SCOPE_CAST;
135                 isCast = 1;
136                 break;
137         case TOK_OPERATOR:
138                 t = LexToken(&p->p_Token);
139                 if (t != TOK_DSTRING) {
140                         t = LexError(&p->p_Token,
141                                      TOK_ERR_EXPECTED_QUOTED_OPERATOR);
142                 } else {
143                         /*
144                          * Add the operator to the operator hash.  Don't
145                          * hash the quotes, just the contents of the quotes.
146                          */
147                         opid = StrTableAlloc(p->p_Token.t_Ptr + 1,
148                                              p->p_Token.t_Len - 2, 0);
149                         t = LexToken(&p->p_Token);
150                 }
151                 isOper = 1;
152                 break;
153         case TOK_METHOD:
154                 t = LexToken(&p->p_Token);
155                 isMeth = 1;
156                 if (tscope.s_Flags & SCOPE_GLOBAL)
157                         rqflags |= SF_GMETHOD;
158                 else
159                         rqflags |= SF_METHOD;
160                 break;
161         }
162
163         /*
164          * Allow the LVALUE scope to be specified after the operator
165          * (to make operator declarations using lvalue look nicer).
166          *
167          * 'lvalue' is also a storage qualifier, and requires outer scoping.  
168          * e.g. if you have something like 'lvalue const int *x', lvalue
169          * applies to the declaration itself, the pointer, whereas const
170          * applies to what is being pointed to.
171          */
172         if (t == TOK_LVALUE) {
173                 tscope.s_Flags |= SCOPE_LVALUE;
174                 t = LexToken(&p->p_Token);
175         }
176
177         /*
178          * Translate certain scope flags into storage qualifier flags.
179          * In Rune it is convenient to parse certain storage qualifiers
180          * as scope.
181          */
182         if (tscope.s_Flags & SCOPE_LVALUE)
183                 rqflags |= SF_LVALUE;
184         if (tscope.s_Flags & SCOPE_CONSTANT)
185                 rqflags |= SF_CONST;
186
187         /*
188          * Transfer locking modes.  Locking modes are mutually exclusive.
189          */
190         if (tscope.s_Flags & SCOPE_UNTRACKED) {
191                 rqflags &= ~SF_LOCKING_MASK;
192                 rqflags |= SF_UNTRACKED;
193         }
194         if (tscope.s_Flags & SCOPE_UNLOCKED) {
195                 rqflags &= ~SF_LOCKING_MASK;
196                 rqflags |= SF_UNLOCKED;
197         }
198         if (tscope.s_Flags & SCOPE_SOFT) {
199                 rqflags &= ~SF_LOCKING_MASK;
200                 rqflags |= SF_SOFT;
201         }
202         if (tscope.s_Flags & SCOPE_HARD) {
203                 rqflags &= ~SF_LOCKING_MASK;
204                 rqflags |= SF_HARD;
205         }
206
207         /*
208          * Parse storage qualifiers and the base type
209          */
210         t = ParseStorageQual(p, t, &sqflags);
211         t = ParseType(p, t, &type, sqflags);
212
213         /*
214          * Parse the declarators and identifier(s).  Deal with implied global
215          * scope, and adjust 'dop' properly.
216          *
217          * Also set SCOPE_CONSTANT if SF_CONST is set (we've already handled
218          * setting SF_CONST if SCOPE_CONSTANT is set).
219          */
220         if (type) {
221                 SemGroup *sg = p->p_CurSemGroup;
222                 t = ParseDeclType(p, t, &type, &sg,
223                                   tscope.s_Flags & SCOPE_CLANG,
224                                   rqflags, &id, idRequired);
225                 if (type->ty_SQFlags & SF_CONST)
226                         tscope.s_Flags |= SCOPE_CONSTANT;
227                 if (idRequired == 2 && sg == p->p_CurSemGroup)
228                         tscope.s_Flags |= SCOPE_GLOBAL;
229                 if ((tscope.s_Flags & SCOPE_GLOBAL) && (dop & DOPF_STORAGE))
230                         dop = DOP_GLOBAL_STORAGE;
231                 if (isAlias)
232                         dop = DOP_ALIAS;
233                 d = AllocDeclaration(sg, dop, &tscope);
234                 t = FinishDecl(p, t, d, type);
235                 /* note: type installed in d->d_Type may be further qualified */
236
237                 if ((tscope.s_Flags & (SCOPE_SOFT | SCOPE_HARD)) &&
238                     d->d_Op != DOP_PROC && dop == DOP_GLOBAL_STORAGE) {
239                         t = LexError(&p->p_Token, TOK_ERR_ILLEGAL_LOCKED);
240                 }
241         } else {
242                 d = NULL;
243         }
244
245         /*
246          * Make sure procedural keywords are only used with procedures,
247          * and hash the operator id (if any).
248          */
249         if (d) {
250                 if (d->d_Op != DOP_PROC && (isCast || isOper || isMeth)) {
251                         t = LexError(&p->p_Token,
252                                      TOK_ERR_OPERATOR_NOT_PROCEDURE);
253                 } else if (opid) {
254                         HashOper(d, opid);
255                 }
256         }
257
258 #if 0
259         /*
260          * If this is a method procedure we have to add an argument called
261          * 'this' that represents an lvalue of the class the procedure resides
262          * in.  XXX not needed any more.
263          */
264         if (isMeth) {
265         }
266 #endif
267
268         /*
269          * Handle any assigned expression
270          */
271         if (t == TOK_ASS) {
272                 switch(d->d_Op) {
273                 case DOP_ALIAS:
274                         t = LexToken(&p->p_Token);
275                         t = ParseExp(p, t, &d->d_AliasDecl.ed_AssExp);
276                         break;
277                 case DOP_TYPEDEF:
278                         t = LexToken(&p->p_Token);
279                         t = ParseExp(p, t, &d->d_TypedefDecl.ed_AssExp);
280                         break;
281                 case DOP_ARGS_STORAGE:
282                 case DOP_STACK_STORAGE:
283                 case DOP_GLOBAL_STORAGE:
284                 case DOP_GROUP_STORAGE:
285                         t = LexToken(&p->p_Token);
286                         t = ParseExp(p, t, &d->d_StorDecl.ed_AssExp);
287                         break;
288                 }
289         } else if (isAlias) {
290                 /*
291                  * Assignment is required for aliases
292                  */
293                 t = LexError(&p->p_Token, TOK_ERR_SYNTAX);
294         }
295         if (t & TOKF_ERROR) {
296                 if (d) {
297                         FreeDeclaration(p, d);
298                         d = NULL;
299                 }
300                 if (id)
301                         RelStrTable(&id);
302         } else {
303                 if (id) {
304                         /*
305                          * NOTE: HashDecl() eats our reference on id.
306                          *
307                          * Allow overloading for operators.
308                          *
309                          * We currently do not support overloading of internal
310                          * identifiers or overload-qualified procedures (it
311                          * makes superclass refinement a nightmare).
312                          */
313                         if (HashDecl(d, id) > 0 &&
314                             /* (d->d_ScopeFlags & SCOPE_INTERNAL) == 0 && */
315                             /* (d->d_ScopeFlags & SCOPE_OVERLOAD) == 0 && */
316                             !(d->d_Op == DOP_PROC &&
317                               d->d_ProcDecl.ed_OperId != NULL))
318                         {
319                                 t = LexError(&p->p_Token, TOK_ERR_DUPLICATE_ID);
320                         }
321 #if 0
322                         if ((d->d_ScopeFlags & SCOPE_OVERLOAD) &&
323                             d->d_Op != DOP_PROC) {
324                                 t = LexError(&p->p_Token, TOK_ERR_DUPLICATE_ID);
325                         }
326 #endif
327                 }
328         }
329         if (pd)
330                 *pd = d;
331         return(t);
332 }
333
334 /*
335  * ( declaration [, declaration]* )
336  */
337 static int
338 ParseDeclarationList(Parse *p, int t, int scopeFlags, int idRequired, int dop)
339 {
340         t = LexSkipToken(&p->p_Token, TOK_OPAREN);
341         if (t != TOK_CPAREN) {
342                 for (;;) {
343                         Scope scope;
344
345                         if (t == TOK_DOT) {
346                                 if (p->p_CurSemGroup->sg_Type == SG_PROCARGS) {
347                                         t = LexSkipToken(&p->p_Token, TOK_DOT);
348                                         t = LexSkipToken(&p->p_Token, TOK_DOT);
349                                         t = LexSkipToken(&p->p_Token, TOK_DOT);
350                                         p->p_CurSemGroup->sg_Flags |= SGF_VARARGS;
351                                 } else {
352                                         t = LexError(&p->p_Token,
353                                                      TOK_ERR_SYNTAX);
354                                 }
355                                 break;
356                         }
357                         t = ParseScopeQual(p, t, &scope);
358                         scope.s_Flags |= scopeFlags;
359                         t = ParseDeclaration(p, t, NULL, idRequired, dop,
360                                              &scope);
361                         if (t != TOK_COMMA)
362                                 break;
363                         t = LexToken(&p->p_Token);
364                 }
365         }
366         t = LexSkipToken(&p->p_Token, TOK_CPAREN);
367         return(t);
368 }
369
370 /*
371  * type:
372  *      id [ . id ]*
373  *      ( declaration [, declaration]* )
374  */
375 int
376 ParseType(Parse *p, int t, Type **ptype, int sqflags)
377 {
378         *ptype = NULL;
379
380         if (t == TOK_STORAGE) {
381                 runesize_t bytes = 0;
382
383                 t = LexToken(&p->p_Token);
384                 t = LexSkipToken(&p->p_Token, TOK_OPAREN);
385                 t = SimpleRunesizeToken(&p->p_Token, &bytes);
386                 t = LexSkipToken(&p->p_Token, TOK_INTEGER);
387                 t = LexSkipToken(&p->p_Token, TOK_CPAREN);
388                 *ptype = AllocStorageType(bytes);
389                 if (sqflags) {
390                         *ptype = TypeToQualType(*ptype,
391                                                 NULL,
392                                                 (*ptype)->ty_SQFlags|sqflags,
393                                                 NULL);
394                 }
395                 return(t);
396         } 
397
398         if (t == TOK_OPAREN) {
399                 /*
400                  * parse a compound type.
401                  */
402                 p->p_CurSemGroup = AllocSemGroup(SG_COMPOUND, p,
403                                                  p->p_CurSemGroup, NULL);
404                 t = ParseDeclarationList(p, t, 0, 0, DOP_GROUP_STORAGE);
405                 if ((t & TOKF_ERROR) == 0) {
406                         *ptype = AllocCompoundType(p->p_CurSemGroup);
407                         if (sqflags) {
408                                 *ptype = TypeToQualType(*ptype, NULL,
409                                                         (*ptype)->ty_SQFlags |
410                                                          sqflags,
411                                                         NULL);
412                         }
413                 } else {
414                         t = LexError(&p->p_Token, TOK_ERR_EXPECTED_CPAREN);
415                         /* mark semgroup for free after pop */
416                 }
417                 p->p_CurSemGroup = p->p_CurSemGroup->sg_Parent;
418         } else if (t & TOKF_ID) {
419                 /*
420                  * parse a normal type, which is a semantic identifier path
421                  * like "a.b.c.d".
422                  */
423                 string_t *ary;
424                 int count;
425                 int lt;
426
427                 t = ParseDotIdAry(p, t, &ary, &count, &lt);
428                 if (lt != TOK_CLASSID)
429                         t = LexError(&p->p_Token, TOK_ERR_EXPECTED_CLASSID);
430                 if ((t & TOKF_ERROR) == 0) {
431                         *ptype = AllocUnresolvedType(
432                                 p->p_Import->st_ImportStmt.es_SemGroup,
433                                 p->p_CurSemGroup,
434                                 ary,
435                                 1);
436                 }
437                 /* XXX cleanup memory */
438         } else {
439                 t = LexError(&p->p_Token, TOK_ERR_EXPECTED_TYPE);
440         }
441         if ((t & TOKF_ERROR) == 0) {
442                 if (sqflags) {
443                         *ptype = TypeToQualType(*ptype, NULL,
444                                                 (*ptype)->ty_SQFlags | sqflags,
445                                                 NULL);
446                 }
447         }
448         return(t);
449 }
450
451 /*
452  * ParseDotIdAry() - parse a sequence of dot-separated identifiers.
453  */
454 int
455 ParseDotIdAry(Parse *p, int t, string_t **pary, int *pcount, int *ltp)
456 {
457         string_t *ary;
458         token_t save;
459         int count;
460
461         /*
462          * First token must be an identifier
463          */
464         if ((t & TOKF_ID) == 0)
465                 t = LexError(&p->p_Token, TOK_ERR_EXPECTED_ID);
466
467         /*
468          * First count the number of identifiers.
469          */
470         save = p->p_Token;
471         count = 0;
472         *ltp = 0;
473
474         while ((t & TOKF_ERROR) == 0) {
475                 ++count;                        /* count ID */
476                 *ltp = t;
477                 t = LexToken(&p->p_Token);      /* skip id */
478                 if (t != TOK_DOT)
479                         break;
480                 t = LexToken(&p->p_Token);      /* skip dot */
481                 if ((t & TOKF_ID) == 0)
482                         t = LexError(&p->p_Token, TOK_ERR_EXPECTED_ID);
483         }
484
485         /*
486          * If no error occured, allocate the array and load it with the
487          * identifiers.
488          */
489         if ((t & TOKF_ERROR) == 0) {
490                 int i;
491
492                 p->p_Token = save;
493                 t = save.t_Type;
494                 ary = zalloc(sizeof(string_t) * (count + 1));
495                 for (i = 0; i < count; ++i) {
496                         ary[i] = StrTableToken(&p->p_Token);
497                         t = LexToken(&p->p_Token);              /* skip id */
498                         if (i + 1 < count)
499                                 t = LexToken(&p->p_Token);      /* skip dot */
500                 }
501                 *pary = ary;
502                 *pcount = count;
503         } else {
504                 *pary = NULL;
505                 *pcount = 0;
506         }
507         return(t);
508 }
509
510 string_t *
511 DupDotIdAry(string_t *ary)
512 {
513         int i;
514         string_t *nary;
515
516         for (i = 0; ary[i]; ++i)
517                 ;
518         nary = zalloc(sizeof(string_t) * (i + 1));
519         for (i = 0; ary[i]; ++i)
520                 nary[i] = StrTableDup(ary[i]);
521         return(nary);
522 }
523
524 void
525 FreeDotIdAry(string_t *ary)
526 {
527         int i;
528
529         for (i = 0; ary[i]; ++i)
530                 RelStrTable(&ary[i]);
531         zfree(ary, sizeof(string_t) * (i + 1));
532 }
533
534 /*
535  * ParseDeclType() -    Parse declarators for declaration given base type
536  *
537  *      Parse the declarators for the specified base type, returning an
538  *      appropriate qualified type.  If an identifier is part of the 
539  *      declarator sequence the identifier will be returned.  If idRequired
540  *      is 1, an identifier is required.  If idRequired is 2, multiple
541  *      dot-separated identifiers are allowed (and the last is returned),
542  *      and psg will be set to the SemGroup representing the class they
543  *      reference.  For example, 'int FILE.setmode(int mode) { .. }'
544  *      will set *psg to FILE's SemGroup.  This eventually goes into
545  *      d_MyGroup, while d_OrigSemGroup retains the original semgroup.
546  *
547  *      Note that multi-identifiers have library scope only and must already
548  *      exist (not be forward referenced).
549  *
550  * declaration: type decl
551  *
552  * decl:        [ declarator ]*
553  *
554  * declarator:
555  *      id[.id]*                identifier(s) (if not already specified)
556  *      ( declaration_list)     procedure-returning
557  *      [ exp ]                 array of
558  *      *                       pointer to
559  *      [ storage_qual ]*       qualified with
560  *
561  * NOTE! Types are built up from left-to-right prior to the identifier or
562  * procedure args, then right-to-left.  For example:
563  *
564  *      const char * const a[2][10]     - an array 2 of an array 10 of
565  *                                        a constant pointer to a constant
566  *                                        character.
567  *
568  *      int func * (int, int)           - a pointer to a procedure taking
569  *                                        two arguments and returning an int.
570  *
571  * NOTE! Certain storage qualifiers in an underlying type will migrate to
572  *       an array type.
573  *
574  * NOTE! scopeFlags propogates SCOPE_CLANG, which effects pointers
575  *      (XXX and should effect alignment too??)
576  */
577 int
578 ParseDeclType(Parse *p, int t, Type **ptype, SemGroup **psg,
579               int scopeFlags, int rqflags, string_t *id,
580               int idRequired)
581 {
582         for (;;) {
583                 if (t == TOK_OPAREN) {
584                         /*
585                          * parse procedure argument-type, which is a compound
586                          * type.  Note that we leave our semantic linkages
587                          * intact to simplify the type resolver (see
588                          * resolve.c), but set the DOP to something we can
589                          * recognize later.  The nesting level will be fixed
590                          * up later.
591                          */
592                         p->p_CurSemGroup = AllocSemGroup(SG_PROCARGS,
593                                                          p,
594                                                          p->p_CurSemGroup,
595                                                          NULL);
596                         t = ParseDeclarationList(p, t, scopeFlags,
597                                                  0, DOP_ARGS_STORAGE);
598                         if (*id)
599                                 t = ParseDeclType(p, t, ptype,
600                                             NULL, scopeFlags, 0, id,
601                                             (idRequired > 1 ? 1 : idRequired));
602                         *ptype = TypeToProcType(*ptype,
603                                             AllocArgsType(p->p_CurSemGroup), 1);
604                         p->p_CurSemGroup = p->p_CurSemGroup->sg_Parent;
605
606                         /*
607                          * anything after proc args must be parsed as if
608                          * we had specified an identifier.
609                          */
610                         if (*id == NULL)
611                                 *id = StrTableAlloc("_dummy_", 7, 0);
612                 } else if (t == TOK_AT) {
613                         /*
614                          * A reference type (bound via a superclass)
615                          */
616                         t = LexToken(&p->p_Token);
617                         if (*id) {
618                                 t = ParseDeclType(p, t, ptype,
619                                                   psg, scopeFlags, 0, id,
620                                                   idRequired);
621                         }
622                         *ptype = TypeToRefType(*ptype);
623                 } else if (t == TOK_OPER && p->p_Token.t_Ptr[0] == '*') {
624                         /*
625                          * We have to deal with pointer-to declarators.
626                          * Regenerate the token using only the first character
627                          * if it is a '*'.
628                          */
629                         t = LexRedactToken(&p->p_Token, 1);
630                         t = LexToken(&p->p_Token);
631                         if (*id) {
632                                 t = ParseDeclType(p, t, ptype,
633                                                   psg, scopeFlags, 0, id,
634                                                   idRequired);
635                         }
636                         if (scopeFlags & SCOPE_CLANG)
637                                 *ptype = TypeToCPtrType(*ptype);
638                         else
639                                 *ptype = TypeToPtrType(*ptype);
640                 } else if (t == TOK_OBRACKET) {
641                         /*
642                          * Array
643                          */
644                         Exp *exp = NULL;
645
646                         t = LexToken(&p->p_Token);
647                         t = ParseExp(p, t, &exp);
648                         t = LexSkipToken(&p->p_Token, TOK_CBRACKET);
649                         if (*id) {
650                                 t = ParseDeclType(p, t, ptype,
651                                                   psg, scopeFlags, 0, id,
652                                                   idRequired);
653                         }
654                         *ptype = TypeToAryType(*ptype, exp, *psg);
655                 } else if (t & TOKF_SCOPE_QUAL) {
656                         t = LexError(&p->p_Token, TOK_ERR_SYNTAX);
657                 } else if (t & TOKF_STOR_QUAL) {
658                         int sqflags;
659
660                         t = ParseStorageQual(p, t, &sqflags);
661                         if (*id) {
662                                 t = ParseDeclType(p, t, ptype,
663                                                   psg, scopeFlags, 0, id,
664                                                   idRequired);
665                         }
666                         *ptype = TypeToQualType(*ptype,
667                                                 NULL,
668                                                 (*ptype)->ty_SQFlags | sqflags,
669                                                 NULL);
670                 } else if (t & TOKF_ID) {
671                         if (*id)        /* terminator */
672                                 break;
673                         *id = StrTableToken(&p->p_Token);
674                         t = LexToken(&p->p_Token);
675                         if (idRequired < 2 && t == TOK_DOT) {
676                                 t = LexError(&p->p_Token,
677                                              TOK_ERR_NO_DOTTED_ID_HERE);
678                         }
679                         while (t == TOK_DOT) {
680                                 /*
681                                  * Lookup *id based on the current psg.  This
682                                  * is about the only FindDeclPath() call that
683                                  * occurs during parse time.  All the rest
684                                  * occur at resolve time.  There is no
685                                  * skip-back SemGroup at parse time (i.e.
686                                  * first arg is NULL).
687                                  *
688                                  * At the moment we only allow private scope.
689                                  * This is because we need pre-resolution
690                                  * structural linkages to stay within their
691                                  * import paradigm, allowing us to save and
692                                  * restore/relocate the associated memory pool
693                                  * as an intermediate pre-parsed file format.
694                                  * It also allows us to resolve things
695                                  * incrementally and save/restore after those
696                                  * steps as well.
697                                  *
698                                  * At some future date I intend to allow
699                                  * library scope, (SCOPE_PRIVATE|SCOPE_LIBRARY),
700                                  * which will necessitate saving and restoring
701                                  * dependant files as a single entity.
702                                  * XXX
703                                  */
704                                 Declaration *d;
705                                 int vis = SCOPE_LIBRARY|SCOPE_PRIVATE;
706                                 int eno = TOK_ERR_PARSE_CLASS_NOT_FOUND;
707                                 string_t ary[] = { *id, NULL };
708
709                                 d = FindDeclPath(NULL, NULL, *psg,
710                                                  NULL, ary, 0, &vis, -1,
711                                                  &eno);
712                                 if (d) {
713                                         switch(d->d_Op) {
714                                         case DOP_CLASS:
715                                                 *psg =
716                                                     d->d_ClassDecl.ed_SemGroup;
717                                                 break;
718                                         case DOP_IMPORT:
719                                                 *psg =
720                                                     d->d_ImportDecl.ed_SemGroup;
721                                                 break;
722                                         default:
723                                                 t = LexError(&p->p_Token,
724                                                     TOK_ERR_PARSE_ID_NOT_CLASS);
725                                                 break;
726                                         }
727                                 } else {
728                                         t = LexError(&p->p_Token, eno);
729                                 }
730                                 if (t & TOKF_ERROR)
731                                         break;
732
733                                 /*
734                                  * Retrieve the next identifier
735                                  */
736                                 t = LexToken(&p->p_Token);
737                                 if ((t & TOKF_ID) == 0) {
738                                         t = LexError(&p->p_Token,
739                                                      TOK_ERR_EXPECTED_ID);
740                                         break;
741                                 }
742                                 ReplaceStrTable(id, StrTableToken(&p->p_Token));
743                                 t = LexToken(&p->p_Token);
744                         }
745                 } else if (
746                         t == TOK_CPAREN ||
747                         t == TOK_SEMI ||
748                         t == TOK_COMMA ||
749                         t == TOK_ASS ||
750                         t == TOK_OBRACE
751                 ) {
752                         break;          /* terminator */
753                 } else {
754                         t = LexError(&p->p_Token, TOK_ERR_EXPECTED_DECLARATOR);
755                 }
756                 if (t & TOKF_ERROR)
757                         break;
758         }
759
760         /*
761          * A Method procedure silently passes the lvalue object as the first
762          * argument to the procedure.  A global method procedure silently
763          * passes the type of the object as the first argument to the
764          * procedure (as a typedef).  The argument is called 'this'.  If the
765          * procedure declares a 'this' argument for the first argument, we
766          * assume that the programmer has constructed this special argument
767          * manually (which the programmer must do if he wants an lvalue
768          * pointer or reference to the object instead of the object itself).
769          *
770          * When constructing 'this' we inherit the locking mode from
771          * the procedure.
772          */
773         if (rqflags & (SF_METHOD|SF_GMETHOD)) {
774                 Type *type;
775                 Type *ctype;
776                 Stmt *st;
777                 SemGroup *sg;
778                 Declaration *nd;
779
780                 type = *ptype;
781                 dassert_parse(p, 0, type->ty_Op == TY_PROC);
782
783                 nd = RUNE_FIRST(&type->ty_ProcType.et_ArgsType->
784                                 ty_ArgsType.et_SemGroup->sg_DeclList);
785                 if (nd && nd->d_Id != String_This)
786                         nd = NULL;
787                 /*
788                  * XXX should really use TypeToProcType() or write a
789                  * ProcTypeToMethodProcType() call.
790                  */
791                 sg = *psg;
792                 st = sg->sg_Stmt;
793                 if (st->st_Op != ST_Class) {
794                         fprintf(stderr,
795                                 "Method calls must be placed in a class\n");
796                         dassert_parse(p, 0, st->st_Op == ST_Class);
797                 }
798
799                 ctype = AllocClassType(&sg->sg_ClassList,
800                                        st->st_ClassStmt.es_Super,
801                                        sg,
802                                        SCOPE_ALL_VISIBLE);
803
804                 if (rqflags & SF_METHOD) {
805                         type = TypeToQualType(type,
806                                               NULL,
807                                               type->ty_SQFlags | SF_METHOD,
808                                               NULL);
809                 } else {
810                         dassert(rqflags & SF_GMETHOD);
811                         type = TypeToQualType(type,
812                                               NULL,
813                                               type->ty_SQFlags | SF_GMETHOD,
814                                               NULL);
815                 }
816                 if (nd == NULL) {
817                         Scope tscope = INIT_SCOPE(SCOPE_ALL_VISIBLE);
818
819                         sg = type->ty_ProcType.et_ArgsType->
820                                 ty_ArgsType.et_SemGroup;
821                         nd = RUNE_FIRST(&sg->sg_DeclList);
822
823                         /*
824                          * Construct the method object, inherit the locking
825                          * mode from procedural scope if not overridden.
826                          * The default locking mode for the method object
827                          * is HARD.
828                          *
829                          * (Global methods do not)
830                          */
831                         if (rqflags & SF_METHOD) {
832                                 nd = AllocDeclaration(sg,
833                                                       DOP_ARGS_STORAGE,
834                                                       &tscope);
835                                 nd->d_StorDecl.ed_Type =
836                                         TypeToQualType(ctype, NULL,
837                                                        ctype->ty_SQFlags |
838                                                         SF_LVALUE,
839                                                        NULL);
840                                 nd->d_ScopeFlags |= SCOPE_LVALUE;
841                                 if (rqflags & SF_UNTRACKED)
842                                         nd->d_ScopeFlags |= SCOPE_UNTRACKED;
843                                 else if (rqflags & SF_UNLOCKED)
844                                         nd->d_ScopeFlags |= SCOPE_UNLOCKED;
845                                 else if (rqflags & SF_SOFT)
846                                         nd->d_ScopeFlags |= SCOPE_SOFT;
847                                 else if (rqflags & SF_HARD)
848                                         nd->d_ScopeFlags |= SCOPE_HARD;
849                                 else
850                                         nd->d_ScopeFlags |= SCOPE_HARD;
851                         } else {
852                                 nd = AllocDeclaration(sg, DOP_TYPEDEF, &tscope);
853                                 nd->d_TypedefDecl.ed_Type = ctype;
854                         }
855                         HashDecl(nd, StrTableDup(String_This));
856
857                         /*
858                          * We really want the declaration at the head, not
859                          * the tail.
860                          */
861                         RUNE_REMOVE(&sg->sg_DeclList, nd, d_Node);
862                         RUNE_INSERT_HEAD(&sg->sg_DeclList, nd, d_Node);
863                 } else {
864                         /*
865                          * Method object explicitly specified, inherit
866                          * locking mode from procedure scope if not
867                          * overridden.
868                          */
869                         if ((nd->d_ScopeFlags & SCOPE_LOCKING_MASK) == 0) {
870                                 if (rqflags & SF_UNTRACKED)
871                                         nd->d_ScopeFlags |= SCOPE_UNTRACKED;
872                                 else if (rqflags & SF_UNLOCKED)
873                                         nd->d_ScopeFlags |= SCOPE_UNLOCKED;
874                                 else if (rqflags & SF_SOFT)
875                                         nd->d_ScopeFlags |= SCOPE_SOFT;
876                                 else if (rqflags & SF_HARD)
877                                         nd->d_ScopeFlags |= SCOPE_HARD;
878                                 else
879                                         nd->d_ScopeFlags |= SCOPE_HARD;
880                         }
881                 }
882                 *ptype = type;
883                 rqflags &= ~(SF_METHOD | SF_GMETHOD);
884         }
885         if ((*ptype)->ty_Op == TY_PROC)
886                 rqflags &= ~SF_HARD;
887         if (rqflags) {
888                 Type *type = *ptype;
889                 if (type->ty_Op == TY_PROC) {
890                         type = type->ty_ProcType.et_RetType;
891                         (*ptype)->ty_ProcType.et_RetType =
892                                 TypeAdjustQList(TypeToQualType(type,
893                                                    NULL,
894                                                    type->ty_SQFlags | rqflags,
895                                                    NULL),
896                                                 (*ptype));
897                 } else {
898                         /*
899                          * Fixup compound argument and stack types too.
900                          */
901                         type = TypeFixupInheritedFlags(type, rqflags);
902                         *ptype = TypeToQualType(type,
903                                                 NULL,
904                                                 type->ty_SQFlags | rqflags,
905                                                 NULL);
906                 }
907         }
908         return(t);
909 }
910
911 static int
912 FinishDecl(Parse *p, int t, Declaration *d, Type *type)
913 {
914         /*
915          * The declaration's lock+refd scope is translated to type SQFlags
916          */
917         if (d->d_ScopeFlags & SCOPE_UNTRACKED) {
918                 type = TypeToQualType(type, NULL,
919                                       type->ty_SQFlags | SF_UNTRACKED, NULL);
920         } else if (d->d_ScopeFlags & SCOPE_UNLOCKED) {
921                 type = TypeToQualType(type, NULL,
922                                       type->ty_SQFlags | SF_UNLOCKED, NULL);
923         } else if (d->d_ScopeFlags & SCOPE_SOFT) {
924                 type = TypeToQualType(type, NULL,
925                                       type->ty_SQFlags | SF_SOFT, NULL);
926         } else if (d->d_ScopeFlags & SCOPE_HARD) {
927                 type = TypeToQualType(type, NULL,
928                                       type->ty_SQFlags | SF_HARD, NULL);
929         }
930
931         /*
932          * Install the type and adjust the declaration accordingly.
933          */
934         if (d->d_Op == DOP_ALIAS) {
935                 d->d_StorDecl.ed_Type = type;
936         } else if (d->d_Op == DOP_TYPEDEF) {
937                 if (type->ty_Op == TY_PROC)
938                         t = LexError(&p->p_Token, TOK_ERR_ILLEGAL_TYPEDEF);
939                 else
940                         d->d_TypedefDecl.ed_Type = type;
941         } else if (type->ty_Op == TY_PROC) {
942                 d->d_Op = DOP_PROC;
943                 d->d_ProcDecl.ed_Type = type;
944         } else {
945                 dassert_decl(d, d->d_Op & DOPF_STORAGE);
946                 d->d_StorDecl.ed_Type = type;
947         }
948
949         /*
950          * Install d_ImportSemGroup.
951          */
952         d->d_ImportSemGroup = p->p_Import->st_ImportStmt.es_SemGroup;
953
954         return(t);
955 }