1 {
2     Copyright (c) 1998-2002 by Florian Klaempfl
3 
4     Does parsing of expression for Free Pascal
5 
6     This program is free software; you can redistribute it and/or modify
7     it under the terms of the GNU General Public License as published by
8     the Free Software Foundation; either version 2 of the License, or
9     (at your option) any later version.
10 
11     This program is distributed in the hope that it will be useful,
12     but WITHOUT ANY WARRANTY; without even the implied warranty of
13     MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14     GNU General Public License for more details.
15 
16     You should have received a copy of the GNU General Public License
17     along with this program; if not, write to the Free Software
18     Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
19 
20  ****************************************************************************
21 }
22 unit pexpr;
23 
24 {$i fpcdefs.inc}
25 
26 interface
27 
28     uses
29       symtype,symdef,symbase,
30       node,ncal,compinnr,
31       tokens,globtype,globals,constexp,
32       pgentype;
33 
34     type
35       texprflag = (
36         ef_accept_equal,
37         ef_type_only,
38         ef_had_specialize
39       );
40       texprflags = set of texprflag;
41 
42     { reads a whole expression }
exprnull43     function expr(dotypecheck:boolean) : tnode;
44 
45     { reads an expression without assignements and .. }
comp_exprnull46     function comp_expr(flags:texprflags):tnode;
47 
48     { reads a single factor }
factornull49     function factor(getaddr:boolean;flags:texprflags) : tnode;
50 
51     procedure string_dec(var def: tdef; allowtypedef: boolean);
52 
parse_parasnull53     function parse_paras(__colon,__namedpara : boolean;end_of_paras : ttoken) : tnode;
54 
55     { the ID token has to be consumed before calling this function }
56     procedure do_member_read(structh:tabstractrecorddef;getaddr:boolean;sym:tsym;var p1:tnode;var again:boolean;callflags:tcallnodeflags;spezcontext:tspecializationcontext);
57 
get_intconstnull58     function get_intconst:TConstExprInt;
get_stringconstnull59     function get_stringconst:string;
60 
61     { Does some postprocessing for a generic type (especially when nested types
62       of the specialization are used) }
63     procedure post_comp_expr_gendef(var def: tdef);
64 
65 implementation
66 
67     uses
68        { common }
69        cutils,cclasses,
70        { global }
71        verbose,
72        systems,widestr,
73        { symtable }
74        symconst,symtable,symsym,symcpu,defutil,defcmp,
75        { module }
76        fmodule,ppu,
77        { pass 1 }
78        pass_1,
79        nmat,nadd,nmem,nset,ncnv,ninl,ncon,nld,nflw,nbas,nutils,
80        { parser }
81        scanner,
82        pbase,pinline,ptype,pgenutil,procinfo,cpuinfo
83        ;
84 
85     function sub_expr(pred_level:Toperator_precedence;flags:texprflags;factornode:tnode):tnode;forward;
86 
87     const
88        { true, if the inherited call is anonymous }
89        anon_inherited : boolean = false;
90        { last def found, only used by anon. inherited calls to insert proper type casts }
91        srdef : tdef = nil;
92 
93     procedure string_dec(var def:tdef; allowtypedef: boolean);
94     { reads a string type with optional length }
95     { and returns a pointer to the string      }
96     { definition                               }
97       var
98          p : tnode;
99       begin
100          def:=cshortstringtype;
101          consume(_STRING);
102          if token=_LECKKLAMMER then
103            begin
104              if not(allowtypedef) then
105                Message(parser_e_no_local_para_def);
106              consume(_LECKKLAMMER);
107              p:=comp_expr([ef_accept_equal]);
108              if not is_constintnode(p) then
109                begin
110                  Message(parser_e_illegal_expression);
111                  { error recovery }
112                  consume(_RECKKLAMMER);
113                end
114              else
115                begin
116                 if (tordconstnode(p).value<=0) then
117                   begin
118                      Message(parser_e_invalid_string_size);
119                      tordconstnode(p).value:=255;
120                   end;
121                 if tordconstnode(p).value>255 then
122                   begin
123                     { longstring is currently unsupported (CEC)! }
124 {                    t:=cstringdef.createlong(tordconstnode(p).value))}
125                     Message(parser_e_invalid_string_size);
126                     tordconstnode(p).value:=255;
127                     def:=cstringdef.createshort(int64(tordconstnode(p).value),true);
128                   end
129                 else
130                   if tordconstnode(p).value<>255 then
131                     def:=cstringdef.createshort(int64(tordconstnode(p).value),true);
132                 consume(_RECKKLAMMER);
133               end;
134              p.free;
135            end
136           else
137             begin
138               if cs_refcountedstrings in current_settings.localswitches then
139                 begin
140                   if m_default_unicodestring in current_settings.modeswitches then
141                     def:=cunicodestringtype
142                   else
143                     def:=cansistringtype
144                 end
145               else
146                 def:=cshortstringtype;
147             end;
148        end;
149 
150 
parse_parasnull151     function parse_paras(__colon,__namedpara : boolean;end_of_paras : ttoken) : tnode;
152       var
153          p1,p2,argname : tnode;
154          prev_in_args,
155          old_named_args_allowed : boolean;
156       begin
157          if token=end_of_paras then
158            begin
159               parse_paras:=nil;
160               exit;
161            end;
162          { save old values }
163          prev_in_args:=in_args;
164          old_named_args_allowed:=named_args_allowed;
165          { set para parsing values }
166          in_args:=true;
167          named_args_allowed:=false;
168          p2:=nil;
169          repeat
170            if __namedpara then
171              begin
172                if token=_COMMA then
173                  begin
174                    { empty parameter }
175                    p2:=ccallparanode.create(cnothingnode.create,p2);
176                  end
177                else
178                  begin
179                    named_args_allowed:=true;
180                    p1:=comp_expr([ef_accept_equal]);
181                    named_args_allowed:=false;
182                    if found_arg_name then
183                      begin
184                        argname:=p1;
185                        p1:=comp_expr([ef_accept_equal]);
186                        p2:=ccallparanode.create(p1,p2);
187                        tcallparanode(p2).parametername:=argname;
188                      end
189                    else
190                      p2:=ccallparanode.create(p1,p2);
191                    found_arg_name:=false;
192                  end;
193              end
194            else
195              begin
196                p1:=comp_expr([ef_accept_equal]);
197                p2:=ccallparanode.create(p1,p2);
198              end;
199            { it's for the str(l:5,s); }
200            if __colon and (token=_COLON) then
201              begin
202                consume(_COLON);
203                p1:=comp_expr([ef_accept_equal]);
204                p2:=ccallparanode.create(p1,p2);
205                include(tcallparanode(p2).callparaflags,cpf_is_colon_para);
206                if try_to_consume(_COLON) then
207                  begin
208                    p1:=comp_expr([ef_accept_equal]);
209                    p2:=ccallparanode.create(p1,p2);
210                    include(tcallparanode(p2).callparaflags,cpf_is_colon_para);
211                  end
212              end;
213          until not try_to_consume(_COMMA);
214          in_args:=prev_in_args;
215          named_args_allowed:=old_named_args_allowed;
216          parse_paras:=p2;
217       end;
218 
219 
gen_c_style_operatornull220      function gen_c_style_operator(ntyp:tnodetype;p1,p2:tnode) : tnode;
221        var
222          hp    : tnode;
223          hdef  : tdef;
224          temp  : ttempcreatenode;
225          newstatement : tstatementnode;
226        begin
227          { Properties are not allowed, because the write can
228            be different from the read }
229          if (nf_isproperty in p1.flags) then
230            begin
231              Message(type_e_variable_id_expected);
232              { We can continue with the loading,
233                it'll not create errors. Only the expected
234                result can be wrong }
235            end;
236 
237          hp:=p1;
238          while assigned(hp) and
239                (hp.nodetype in [derefn,subscriptn,vecn,typeconvn]) do
240            hp:=tunarynode(hp).left;
241          if not assigned(hp) then
242            internalerror(200410121);
243          if (hp.nodetype=calln) then
244            begin
245              typecheckpass(p1);
246              result:=internalstatements(newstatement);
247              hdef:=cpointerdef.getreusable(p1.resultdef);
248              temp:=ctempcreatenode.create(hdef,sizeof(pint),tt_persistent,false);
249              addstatement(newstatement,temp);
250              addstatement(newstatement,cassignmentnode.create(ctemprefnode.create(temp),caddrnode.create_internal(p1)));
251              addstatement(newstatement,cassignmentnode.create(
252                  cderefnode.create(ctemprefnode.create(temp)),
253                  caddnode.create(ntyp,
254                      cderefnode.create(ctemprefnode.create(temp)),
255                      p2)));
256              addstatement(newstatement,ctempdeletenode.create(temp));
257            end
258          else
259            result:=cassignmentnode.create(p1,caddnode.create(ntyp,p1.getcopy,p2));
260        end;
261 
262 
statement_syssymnull263      function statement_syssym(l : tinlinenumber) : tnode;
264       var
265         p1,p2,paras  : tnode;
266         err,
267         prev_in_args : boolean;
268         def : tdef;
269         exit_procinfo: tprocinfo;
270       begin
271         prev_in_args:=in_args;
272         case l of
273 
274           in_new_x :
275             begin
276               if afterassignment or in_args then
277                statement_syssym:=new_function
elsenull278               else
279                statement_syssym:=new_dispose_statement(true);
280             end;
281 
282           in_dispose_x :
283             begin
284               statement_syssym:=new_dispose_statement(false);
285             end;
286 
287           in_ord_x :
288             begin
289               consume(_LKLAMMER);
290               in_args:=true;
291               p1:=comp_expr([ef_accept_equal]);
292               consume(_RKLAMMER);
293               p1:=geninlinenode(in_ord_x,false,p1);
294               statement_syssym := p1;
295             end;
296 
297           in_exit :
298             begin
299               statement_syssym:=nil;
300               if try_to_consume(_LKLAMMER) then
301                 begin
302                   if not (m_mac in current_settings.modeswitches) then
303                     begin
304                       if not(try_to_consume(_RKLAMMER)) then
305                         begin
306                           p1:=comp_expr([ef_accept_equal]);
307                           consume(_RKLAMMER);
308                           if not assigned(current_procinfo) or
309                              (current_procinfo.procdef.proctypeoption in [potype_constructor,potype_destructor]) or
310                              is_void(current_procinfo.procdef.returndef) then
311                             begin
312                               Message(parser_e_void_function);
313                               { recovery }
314                               p1.free;
315                               p1:=nil;
316                             end;
317                         end
318                       else
319                         p1:=nil;
320                     end
321                   else
322                     begin
323                       { non local exit ? }
324                       if current_procinfo.procdef.procsym.name<>pattern then
325                         begin
326                           exit_procinfo:=current_procinfo.parent;
327                           while assigned(exit_procinfo) do
328                             begin
329                               if exit_procinfo.procdef.procsym.name=pattern then
330                                 break;
331                               exit_procinfo:=exit_procinfo.parent;
332                             end;
333                           if assigned(exit_procinfo) then
334                             begin
335                               if not(assigned(exit_procinfo.nestedexitlabel)) then
336                                 begin
337                                   include(current_procinfo.flags,pi_has_nested_exit);
338                                   exclude(current_procinfo.procdef.procoptions,po_inline);
339 
340                                   exit_procinfo.nestedexitlabel:=clabelsym.create('$nestedexit');
341 
342                                   { the compiler is responsible to define this label }
343                                   exit_procinfo.nestedexitlabel.defined:=true;
344                                   exit_procinfo.nestedexitlabel.used:=true;
345 
346                                   exit_procinfo.nestedexitlabel.jumpbuf:=clocalvarsym.create('LABEL$_'+exit_procinfo.nestedexitlabel.name,vs_value,rec_jmp_buf,[]);
347                                   exit_procinfo.procdef.localst.insert(exit_procinfo.nestedexitlabel);
348                                   exit_procinfo.procdef.localst.insert(exit_procinfo.nestedexitlabel.jumpbuf);
349                                 end;
350 
351                               statement_syssym:=cgotonode.create(exit_procinfo.nestedexitlabel);
352                               tgotonode(statement_syssym).labelsym:=exit_procinfo.nestedexitlabel;
353                             end
354                           else
355                             Message(parser_e_macpas_exit_wrong_param);
356                         end;
357                       consume(_ID);
358                       consume(_RKLAMMER);
359                       p1:=nil;
360                     end
361                 end
362               else
363                 p1:=nil;
364               if not assigned(statement_syssym) then
365                 statement_syssym:=cexitnode.create(p1);
366             end;
367 
368           in_break :
369             begin
370               statement_syssym:=cbreaknode.create
371             end;
372 
373           in_continue :
374             begin
375               statement_syssym:=ccontinuenode.create
376             end;
377 
378           in_leave :
379             begin
380               if m_mac in current_settings.modeswitches then
381                 statement_syssym:=cbreaknode.create
382               else
383                 begin
384                   Message1(sym_e_id_not_found, orgpattern);
385                   statement_syssym:=cerrornode.create;
386                 end;
387             end;
388 
389           in_cycle :
390             begin
391               if m_mac in current_settings.modeswitches then
392                 statement_syssym:=ccontinuenode.create
393               else
394                 begin
395                   Message1(sym_e_id_not_found, orgpattern);
396                   statement_syssym:=cerrornode.create;
397                 end;
398             end;
399 
400           in_typeof_x :
401             begin
402               consume(_LKLAMMER);
403               in_args:=true;
404               p1:=comp_expr([ef_accept_equal]);
405               consume(_RKLAMMER);
406               if p1.nodetype=typen then
407                 ttypenode(p1).allowed:=true;
408               { Allow classrefdef, which is required for
409                 Typeof(self) in static class methods }
410               if not(is_objc_class_or_protocol(p1.resultdef)) and
411                  not(is_java_class_or_interface(p1.resultdef)) and
412                  ((p1.resultdef.typ = objectdef) or
413                   (assigned(current_procinfo) and
414                    ((po_classmethod in current_procinfo.procdef.procoptions) or
415                     (po_staticmethod in current_procinfo.procdef.procoptions)) and
416                    (p1.resultdef.typ=classrefdef))) then
417                statement_syssym:=geninlinenode(in_typeof_x,false,p1)
418               else
419                begin
420                  Message(parser_e_class_id_expected);
421                  p1.destroy;
422                  statement_syssym:=cerrornode.create;
423                end;
424             end;
425 
426           in_sizeof_x,
427           in_bitsizeof_x :
428             begin
429               consume(_LKLAMMER);
430               in_args:=true;
431               p1:=comp_expr([ef_accept_equal]);
432               consume(_RKLAMMER);
433               if ((p1.nodetype<>typen) and
434 
435                  (
436                   (is_object(p1.resultdef) and
437                    (oo_has_constructor in tobjectdef(p1.resultdef).objectoptions)) or
438                   is_open_array(p1.resultdef) or
439                   is_array_of_const(p1.resultdef) or
440                   is_open_string(p1.resultdef)
441                  )) or
442                  { keep the function call if it is a type parameter to avoid arithmetic errors due to constant folding }
443                  is_typeparam(p1.resultdef) then
444                 begin
445                   statement_syssym:=geninlinenode(in_sizeof_x,false,p1);
446                   { no packed bit support for these things }
447                   if l=in_bitsizeof_x then
448                     statement_syssym:=caddnode.create(muln,statement_syssym,cordconstnode.create(8,sizesinttype,true));
449                 end
450               else
451                begin
452                  { allow helpers for SizeOf and BitSizeOf }
453                  if p1.nodetype=typen then
454                    ttypenode(p1).helperallowed:=true;
455                  if (p1.resultdef.typ=forwarddef) then
456                    Message1(type_e_type_is_not_completly_defined,tforwarddef(p1.resultdef).tosymname^);
457                  if (l = in_sizeof_x) or
458                     (not((p1.nodetype = vecn) and
459                          is_packed_array(tvecnode(p1).left.resultdef)) and
460                      not((p1.nodetype = subscriptn) and
461                          is_packed_record_or_object(tsubscriptnode(p1).left.resultdef))) then
462                    begin
463                      statement_syssym:=cordconstnode.create(p1.resultdef.size,sizesinttype,true);
464                      if (l = in_bitsizeof_x) then
465                        statement_syssym:=caddnode.create(muln,statement_syssym,cordconstnode.create(8,sizesinttype,true));
466                    end
467                  else
468                    statement_syssym:=cordconstnode.create(p1.resultdef.packedbitsize,sizesinttype,true);
469                  { p1 not needed !}
470                  p1.destroy;
471                end;
472             end;
473 
474           in_typeinfo_x,
475           in_objc_encode_x,
476           in_gettypekind_x,
477           in_ismanagedtype_x:
478             begin
479               if (l in [in_typeinfo_x,in_gettypekind_x,in_ismanagedtype_x]) or
480                  (m_objectivec1 in current_settings.modeswitches) then
481                 begin
482                   consume(_LKLAMMER);
483                   in_args:=true;
484                   p1:=comp_expr([ef_accept_equal]);
485                   { When reading a class type it is parsed as loadvmtaddrn,
486                     typeinfo only needs the type so we remove the loadvmtaddrn }
487                   if p1.nodetype=loadvmtaddrn then
488                     begin
489                       p2:=tloadvmtaddrnode(p1).left;
490                       tloadvmtaddrnode(p1).left:=nil;
491                       p1.free;
492                       p1:=p2;
493                     end;
494                   if p1.nodetype=typen then
495                   begin
496                     ttypenode(p1).allowed:=true;
497                     { allow helpers for TypeInfo }
498                     if l in [in_typeinfo_x,in_gettypekind_x,in_ismanagedtype_x] then
499                       ttypenode(p1).helperallowed:=true;
500                   end;
501     {              else
502                     begin
503                        p1.destroy;
504                        p1:=cerrornode.create;
505                        Message(parser_e_illegal_parameter_list);
506                     end;}
507                   consume(_RKLAMMER);
508                   p2:=geninlinenode(l,false,p1);
509                   statement_syssym:=p2;
510                 end
511               else
512                 begin
513                   Message1(sym_e_id_not_found, orgpattern);
514                   statement_syssym:=cerrornode.create;
515                 end;
516             end;
517 
518           in_aligned_x,
519           in_unaligned_x :
520             begin
521               err:=false;
522               consume(_LKLAMMER);
523               in_args:=true;
524               p1:=comp_expr([ef_accept_equal]);
525               p2:=ccallparanode.create(p1,nil);
526               p2:=geninlinenode(l,false,p2);
527               consume(_RKLAMMER);
528               statement_syssym:=p2;
529             end;
530 
531           in_assigned_x :
532             begin
533               err:=false;
534               consume(_LKLAMMER);
535               in_args:=true;
536               p1:=comp_expr([ef_accept_equal]);
537               { When reading a class type it is parsed as loadvmtaddrn,
538                 typeinfo only needs the type so we remove the loadvmtaddrn }
539               if p1.nodetype=loadvmtaddrn then
540                 begin
541                   p2:=tloadvmtaddrnode(p1).left;
542                   tloadvmtaddrnode(p1).left:=nil;
543                   p1.free;
544                   p1:=p2;
545                 end;
546               if not codegenerror then
547                begin
548                  case p1.resultdef.typ of
549                    procdef, { procvar }
550                    pointerdef,
551                    procvardef,
552                    classrefdef : ;
553                    objectdef :
554                      if not is_implicit_pointer_object_type(p1.resultdef) then
555                        begin
556                          Message(parser_e_illegal_parameter_list);
557                          err:=true;
558                        end;
559                    arraydef :
560                      if not is_dynamic_array(p1.resultdef) then
561                        begin
562                          Message(parser_e_illegal_parameter_list);
563                          err:=true;
564                        end;
565                    else
566                      if p1.resultdef.typ<>undefineddef then
567                        begin
568                          Message(parser_e_illegal_parameter_list);
569                          err:=true;
570                        end;
571                  end;
572                end
573               else
574                err:=true;
575               if not err then
576                begin
577                  p2:=ccallparanode.create(p1,nil);
578                  p2:=geninlinenode(in_assigned_x,false,p2);
579                end
580               else
581                begin
582                  p1.free;
583                  p2:=cerrornode.create;
584                end;
585               consume(_RKLAMMER);
586               statement_syssym:=p2;
587             end;
588 
589           in_addr_x :
590             begin
591               consume(_LKLAMMER);
592               got_addrn:=true;
593               p1:=factor(true,[]);
594               { inside parentheses a full expression is allowed, see also tests\webtbs\tb27517.pp }
595               if token<>_RKLAMMER then
596                 p1:=sub_expr(opcompare,[ef_accept_equal],p1);
597               p1:=caddrnode.create(p1);
598               got_addrn:=false;
599               consume(_RKLAMMER);
600               statement_syssym:=p1;
601             end;
602 
603 {$ifdef i8086}
604           in_faraddr_x :
605             begin
606               consume(_LKLAMMER);
607               got_addrn:=true;
608               p1:=factor(true,[]);
609               { inside parentheses a full expression is allowed, see also tests\webtbs\tb27517.pp }
610               if token<>_RKLAMMER then
611                 p1:=sub_expr(opcompare,[ef_accept_equal],p1);
612               p1:=geninlinenode(in_faraddr_x,false,p1);
613               got_addrn:=false;
614               consume(_RKLAMMER);
615               statement_syssym:=p1;
616             end;
617 {$endif i8086}
618 
619           in_ofs_x :
620             begin
621               if target_info.system in systems_managed_vm then
622                 message(parser_e_feature_unsupported_for_vm);
623               consume(_LKLAMMER);
624               got_addrn:=true;
625               p1:=factor(true,[]);
626               { inside parentheses a full expression is allowed, see also tests\webtbs\tb27517.pp }
627               if token<>_RKLAMMER then
628                 p1:=sub_expr(opcompare,[ef_accept_equal],p1);
629               p1:=caddrnode.create(p1);
630               include(taddrnode(p1).addrnodeflags,anf_ofs);
631               got_addrn:=false;
632               { Ofs() returns a cardinal/qword, not a pointer }
633               inserttypeconv_internal(p1,uinttype);
634               consume(_RKLAMMER);
635               statement_syssym:=p1;
636             end;
637 
638           in_seg_x :
639             begin
640               consume(_LKLAMMER);
641               got_addrn:=true;
642               p1:=factor(true,[]);
643               { inside parentheses a full expression is allowed, see also tests\webtbs\tb27517.pp }
644               if token<>_RKLAMMER then
645                 p1:=sub_expr(opcompare,[ef_accept_equal],p1);
646               p1:=geninlinenode(in_seg_x,false,p1);
647               got_addrn:=false;
648               consume(_RKLAMMER);
649               statement_syssym:=p1;
650             end;
651 
652           in_high_x,
653           in_low_x :
654             begin
655               consume(_LKLAMMER);
656               in_args:=true;
657               p1:=comp_expr([ef_accept_equal]);
658               p2:=geninlinenode(l,false,p1);
659               consume(_RKLAMMER);
660               statement_syssym:=p2;
661             end;
662 
663           in_succ_x,
664           in_pred_x :
665             begin
666               consume(_LKLAMMER);
667               in_args:=true;
668               p1:=comp_expr([ef_accept_equal]);
669               p2:=geninlinenode(l,false,p1);
670               consume(_RKLAMMER);
671               statement_syssym:=p2;
672             end;
673 
674           in_inc_x,
675           in_dec_x :
676             begin
677               consume(_LKLAMMER);
678               in_args:=true;
679               p1:=comp_expr([ef_accept_equal]);
680               if try_to_consume(_COMMA) then
681                 p2:=ccallparanode.create(comp_expr([ef_accept_equal]),nil)
682               else
683                 p2:=nil;
684               p2:=ccallparanode.create(p1,p2);
685               statement_syssym:=geninlinenode(l,false,p2);
686               consume(_RKLAMMER);
687             end;
688 
689           in_slice_x:
690             begin
691               if not(in_args) then
692                 begin
693                   message(parser_e_illegal_slice);
694                   consume(_LKLAMMER);
695                   in_args:=true;
696                   comp_expr([ef_accept_equal]).free;
697                   if try_to_consume(_COMMA) then
698                     comp_expr([ef_accept_equal]).free;
699                   statement_syssym:=cerrornode.create;
700                   consume(_RKLAMMER);
701                 end
702               else
703                 begin
704                   consume(_LKLAMMER);
705                   in_args:=true;
706                   p1:=comp_expr([ef_accept_equal]);
707                   Consume(_COMMA);
708                   if not(codegenerror) then
709                     p2:=ccallparanode.create(comp_expr([ef_accept_equal]),nil)
710                   else
711                     p2:=cerrornode.create;
712                   p2:=ccallparanode.create(p1,p2);
713                   statement_syssym:=geninlinenode(l,false,p2);
714                   consume(_RKLAMMER);
715                 end;
716             end;
717 
718           in_initialize_x:
719             begin
720               statement_syssym:=inline_initialize;
721             end;
722 
723           in_finalize_x:
724             begin
725               statement_syssym:=inline_finalize;
726             end;
727 
728           in_copy_x:
729             begin
730               statement_syssym:=inline_copy;
731             end;
732 
733           in_concat_x :
734             begin
735               statement_syssym:=inline_concat;
736             end;
737 
738           in_read_x,
739           in_readln_x,
740           in_readstr_x:
741             begin
742               if try_to_consume(_LKLAMMER) then
743                begin
744                  paras:=parse_paras(false,false,_RKLAMMER);
745                  consume(_RKLAMMER);
746                end
747               else
748                paras:=nil;
749               p1:=geninlinenode(l,false,paras);
750               statement_syssym := p1;
751             end;
752 
753           in_setlength_x:
754             begin
755               statement_syssym := inline_setlength;
756             end;
757 
758           in_objc_selector_x:
759             begin
760               if (m_objectivec1 in current_settings.modeswitches) then
761                 begin
762                   consume(_LKLAMMER);
763                   in_args:=true;
764                   { don't turn procsyms into calls (getaddr = true) }
765                   p1:=factor(true,[]);
766                   p2:=geninlinenode(l,false,p1);
767                   consume(_RKLAMMER);
768                   statement_syssym:=p2;
769                 end
770               else
771                 begin
772                   Message1(sym_e_id_not_found, orgpattern);
773                   statement_syssym:=cerrornode.create;
774                 end;
775             end;
776 
777           in_length_x:
778             begin
779               consume(_LKLAMMER);
780               in_args:=true;
781               p1:=comp_expr([ef_accept_equal]);
782               p2:=geninlinenode(l,false,p1);
783               consume(_RKLAMMER);
784               statement_syssym:=p2;
785             end;
786 
787           in_write_x,
788           in_writeln_x,
789           in_writestr_x :
790             begin
791               if try_to_consume(_LKLAMMER) then
792                begin
793                  paras:=parse_paras(true,false,_RKLAMMER);
794                  consume(_RKLAMMER);
795                end
796               else
797                paras:=nil;
798               p1 := geninlinenode(l,false,paras);
799               statement_syssym := p1;
800             end;
801 
802           in_str_x_string :
803             begin
804               consume(_LKLAMMER);
805               paras:=parse_paras(true,false,_RKLAMMER);
806               consume(_RKLAMMER);
807               p1 := geninlinenode(l,false,paras);
808               statement_syssym := p1;
809             end;
810 
811           in_val_x:
812             Begin
813               consume(_LKLAMMER);
814               in_args := true;
815               p1:= ccallparanode.create(comp_expr([ef_accept_equal]), nil);
816               consume(_COMMA);
817               p2 := ccallparanode.create(comp_expr([ef_accept_equal]),p1);
818               if try_to_consume(_COMMA) then
819                 p2 := ccallparanode.create(comp_expr([ef_accept_equal]),p2);
820               consume(_RKLAMMER);
821               p2 := geninlinenode(l,false,p2);
822               statement_syssym := p2;
823             End;
824 
825           in_include_x_y,
826           in_exclude_x_y :
827             begin
828               consume(_LKLAMMER);
829               in_args:=true;
830               p1:=comp_expr([ef_accept_equal]);
831               consume(_COMMA);
832               p2:=comp_expr([ef_accept_equal]);
833               statement_syssym:=geninlinenode(l,false,ccallparanode.create(p1,ccallparanode.create(p2,nil)));
834               consume(_RKLAMMER);
835             end;
836 
837           in_pack_x_y_z,
838           in_unpack_x_y_z :
839             begin
840               consume(_LKLAMMER);
841               in_args:=true;
842               p1:=comp_expr([ef_accept_equal]);
843               consume(_COMMA);
844               p2:=comp_expr([ef_accept_equal]);
845               consume(_COMMA);
846               paras:=comp_expr([ef_accept_equal]);
847               statement_syssym:=geninlinenode(l,false,ccallparanode.create(p1,ccallparanode.create(p2,ccallparanode.create(paras,nil))));
848               consume(_RKLAMMER);
849             end;
850 
851           in_assert_x_y :
852             begin
853               consume(_LKLAMMER);
854               in_args:=true;
855               p1:=comp_expr([ef_accept_equal]);
856               if try_to_consume(_COMMA) then
857                  p2:=comp_expr([ef_accept_equal])
858               else
859                begin
860                  { then insert an empty string }
861                  p2:=cstringconstnode.createstr('');
862                end;
863               statement_syssym:=geninlinenode(l,false,ccallparanode.create(p1,ccallparanode.create(p2,nil)));
864               consume(_RKLAMMER);
865             end;
866           in_get_frame:
867             begin
868               statement_syssym:=geninlinenode(l,false,nil);
869             end;
870 (*
871           in_get_caller_frame:
872             begin
873               if try_to_consume(_LKLAMMER) then
874                 begin
875                   {You used to call get_caller_frame as get_caller_frame(get_frame),
876                    however, as a stack frame may not exist, it does more harm than
877                    good, so ignore it.}
878                   in_args:=true;
879                   p1:=comp_expr([ef_accept_equal]);
880                   p1.destroy;
881                   consume(_RKLAMMER);
882                 end;
883               statement_syssym:=geninlinenode(l,false,nil);
884             end;
885 *)
886           in_default_x:
887             begin
888               consume(_LKLAMMER);
889               in_args:=true;
890               def:=nil;
891               single_type(def,[stoAllowSpecialization]);
892               statement_syssym:=cerrornode.create;
893               if def<>generrordef then
894                 { "type expected" error is already done by single_type }
895                 if def.typ=forwarddef then
896                   Message1(type_e_type_is_not_completly_defined,tforwarddef(def).tosymname^)
897                 else
898                   begin
899                     statement_syssym.free;
900                     statement_syssym:=geninlinenode(in_default_x,false,ctypenode.create(def));
901                   end;
902               { consume the right bracket here for a nicer error position }
903               consume(_RKLAMMER);
904             end;
905 
906           in_setstring_x_y_z:
907             begin
908               statement_syssym := inline_setstring;
909             end;
910 
911           in_delete_x_y_z:
912             begin
913               statement_syssym:=inline_delete;
914             end;
915 
916           in_insert_x_y_z:
917             begin
918               statement_syssym:=inline_insert;
919             end;
920           else
921             internalerror(15);
922 
923         end;
924         in_args:=prev_in_args;
925       end;
926 
927 
maybe_load_methodpointernull928     function maybe_load_methodpointer(st:TSymtable;var p1:tnode):boolean;
929       var
930         pd: tprocdef;
931       begin
932         maybe_load_methodpointer:=false;
933         if not assigned(p1) then
934          begin
935            case st.symtabletype of
936              withsymtable :
937                begin
938                  if (st.defowner.typ=objectdef) then
939                    p1:=tnode(twithsymtable(st).withrefnode).getcopy;
940                end;
941              ObjectSymtable,
942              recordsymtable:
943                begin
944                  { Escape nested procedures }
945                  if assigned(current_procinfo) then
946                    begin
947                      pd:=current_procinfo.get_normal_proc.procdef;
948                      { We are calling from the static class method which has no self node }
949                      if assigned(pd) and pd.no_self_node then
950                        if st.symtabletype=recordsymtable then
951                          p1:=ctypenode.create(pd.struct)
952                        else
953                          p1:=cloadvmtaddrnode.create(ctypenode.create(pd.struct))
954                      else
955                        p1:=load_self_node;
956                    end
957                  else
958                    p1:=load_self_node;
959                  { We are calling a member }
960                  maybe_load_methodpointer:=true;
961                end;
962            end;
963          end;
964       end;
965 
966 
967     { reads the parameter for a subroutine call }
968     procedure do_proc_call(sym:tsym;st:TSymtable;obj:tabstractrecorddef;getaddr:boolean;var again : boolean;var p1:tnode;callflags:tcallnodeflags;spezcontext:tspecializationcontext);
969       var
970          membercall,
971          prevafterassn : boolean;
972          i        : integer;
973          para,p2  : tnode;
974          currpara : tparavarsym;
975          aprocdef : tprocdef;
976       begin
977          prevafterassn:=afterassignment;
978          afterassignment:=false;
979          membercall:=false;
980          aprocdef:=nil;
981 
982          { when it is a call to a member we need to load the
983            methodpointer first
984          }
985          membercall:=maybe_load_methodpointer(st,p1);
986 
987          { When we are expecting a procvar we also need
988            to get the address in some cases }
989          if assigned(getprocvardef) then
990           begin
991             if (block_type=bt_const) or
992                getaddr then
993              begin
994                aprocdef:=Tprocsym(sym).Find_procdef_byprocvardef(getprocvardef);
995                getaddr:=true;
996              end
997             else
998              if ((m_tp_procvar in current_settings.modeswitches) or
999                  (m_mac_procvar in current_settings.modeswitches)) and
1000                 not(token in [_CARET,_POINT,_LKLAMMER]) then
1001               begin
1002                 aprocdef:=Tprocsym(sym).Find_procdef_byprocvardef(getprocvardef);
1003                 if assigned(aprocdef) then
1004                  getaddr:=true;
1005               end;
1006           end;
1007 
1008          { only need to get the address of the procedure? Check token because
1009            in the case of opening parenthesis is possible to get pointer to
1010            function result (lack of checking for token was the reason of
1011            tw10933.pp test failure) }
1012          if getaddr and (token<>_LKLAMMER) then
1013            begin
1014              { for now we don't support pointers to generic functions, but since
1015                this is only temporary we use a non translated message }
1016              if assigned(spezcontext) then
1017                begin
1018                  comment(v_error, 'Pointers to generics functions not implemented');
1019                  p1:=cerrornode.create;
1020                  spezcontext.free;
1021                  exit;
1022                end;
1023 
1024              { Retrieve info which procvar to call. For tp_procvar the
1025                aprocdef is already loaded above so we can reuse it }
1026              if not assigned(aprocdef) and
1027                 assigned(getprocvardef) then
1028                aprocdef:=Tprocsym(sym).Find_procdef_byprocvardef(getprocvardef);
1029 
1030              { generate a methodcallnode or proccallnode }
1031              { we shouldn't convert things like @tcollection.load }
1032              p2:=cloadnode.create_procvar(sym,aprocdef,st);
1033              if assigned(p1) then
1034               begin
1035                 { for loading methodpointer of an inherited function
1036                   we use self as instance and load the address of
1037                   the function directly and not through the vmt (PFV) }
1038                 if (cnf_inherited in callflags) then
1039                   begin
1040                     include(tloadnode(p2).loadnodeflags,loadnf_inherited);
1041                     p1.free;
1042                     p1:=load_self_node;
1043                   end;
1044                 if (p1.nodetype<>typen) then
1045                   tloadnode(p2).set_mp(p1)
1046                 else
1047                   begin
1048                     typecheckpass(p1);
1049                     if (p1.resultdef.typ=objectdef) then
1050                       { so we can create the correct  method pointer again in case
1051                         this is a "objectprocvar:=@classname.method" expression }
1052                       tloadnode(p2).symtable:=tobjectdef(p1.resultdef).symtable
1053                     else
1054                       p1.free;
1055                   end;
1056               end;
1057              p1:=p2;
1058 
1059              { no postfix operators }
1060              again:=false;
1061            end
1062          else
1063            begin
1064              para:=nil;
1065              if anon_inherited then
1066               begin
1067                 if not assigned(current_procinfo) then
1068                   internalerror(200305054);
1069                 for i:=0 to current_procinfo.procdef.paras.count-1 do
1070                   begin
1071                     currpara:=tparavarsym(current_procinfo.procdef.paras[i]);
1072                     if not(vo_is_hidden_para in currpara.varoptions) then
1073                       begin
1074                         { inheritance by msgint? }
1075                         if assigned(srdef) then
1076                           { anonymous inherited via msgid calls only require a var parameter for
1077                             both methods, so we need some type casting here }
1078                           para:=ccallparanode.create(ctypeconvnode.create_internal(ctypeconvnode.create_internal(
1079                             cloadnode.create(currpara,currpara.owner),cformaltype),tparavarsym(tprocdef(srdef).paras[i]).vardef),
1080                           para)
1081                         else
1082                           para:=ccallparanode.create(cloadnode.create(currpara,currpara.owner),para);
1083                       end;
1084                  end;
1085               end
1086              else
1087               begin
1088                 if try_to_consume(_LKLAMMER) then
1089                  begin
1090                    para:=parse_paras(false,false,_RKLAMMER);
1091                    consume(_RKLAMMER);
1092                  end;
1093               end;
1094              { indicate if this call was generated by a member and
1095                no explicit self is used, this is needed to determine
1096                how to handle a destructor call (PFV) }
1097              if membercall then
1098                include(callflags,cnf_member_call);
1099              if assigned(obj) then
1100                begin
1101                  if not (st.symtabletype in [ObjectSymtable,recordsymtable]) then
1102                    internalerror(200310031);
1103                  p1:=ccallnode.create(para,tprocsym(sym),obj.symtable,p1,callflags,spezcontext);
1104                end
1105              else
1106                p1:=ccallnode.create(para,tprocsym(sym),st,p1,callflags,spezcontext);
1107            end;
1108          afterassignment:=prevafterassn;
1109       end;
1110 
1111 
1112     procedure handle_procvar(pv : tprocvardef;var p2 : tnode);
1113       var
1114         hp,hp2 : tnode;
1115         hpp    : ^tnode;
1116         currprocdef : tprocdef;
1117       begin
1118         if not assigned(pv) then
1119          internalerror(200301121);
1120         if (m_tp_procvar in current_settings.modeswitches) or
1121            (m_mac_procvar in current_settings.modeswitches) then
1122          begin
1123            hp:=p2;
1124            hpp:=@p2;
1125            while assigned(hp) and
1126                  (hp.nodetype=typeconvn) do
1127             begin
1128               hp:=ttypeconvnode(hp).left;
1129               { save orignal address of the old tree so we can replace the node }
1130               hpp:=@hp;
1131             end;
1132            if (hp.nodetype=calln) and
1133               { a procvar can't have parameters! }
1134               not assigned(tcallnode(hp).left) then
1135             begin
1136               currprocdef:=tcallnode(hp).symtableprocentry.Find_procdef_byprocvardef(pv);
1137               if assigned(currprocdef) then
1138                begin
1139                  hp2:=cloadnode.create_procvar(tprocsym(tcallnode(hp).symtableprocentry),currprocdef,tcallnode(hp).symtableproc);
1140                  if (po_methodpointer in pv.procoptions) then
1141                    tloadnode(hp2).set_mp(tcallnode(hp).methodpointer.getcopy);
1142                  hp.destroy;
1143                  { replace the old callnode with the new loadnode }
1144                  hpp^:=hp2;
1145                end;
1146             end;
1147          end;
1148       end;
1149 
1150 
1151     { the following procedure handles the access to a property symbol }
1152     procedure handle_propertysym(propsym : tpropertysym;st : TSymtable;var p1 : tnode);
1153       var
1154          paras : tnode;
1155          p2    : tnode;
1156          membercall : boolean;
1157          callflags  : tcallnodeflags;
1158          propaccesslist : tpropaccesslist;
1159          sym: tsym;
1160       begin
1161          { property parameters? read them only if the property really }
1162          { has parameters                                             }
1163          paras:=nil;
1164          if (ppo_hasparameters in propsym.propoptions) then
1165            begin
1166              if try_to_consume(_LECKKLAMMER) then
1167                begin
1168                  paras:=parse_paras(false,false,_RECKKLAMMER);
1169                  consume(_RECKKLAMMER);
1170                end;
1171            end;
1172          { indexed property }
1173          if (ppo_indexed in propsym.propoptions) then
1174            begin
1175              p2:=cordconstnode.create(propsym.index,propsym.indexdef,true);
1176              paras:=ccallparanode.create(p2,paras);
1177            end;
1178          { we need only a write property if a := follows }
1179          { if not(afterassignment) and not(in_args) then }
1180          if token=_ASSIGNMENT then
1181            begin
1182               if propsym.getpropaccesslist(palt_write,propaccesslist) then
1183                 begin
1184                    sym:=propaccesslist.firstsym^.sym;
1185                    case sym.typ of
1186                      procsym :
1187                        begin
1188                          callflags:=[];
1189                          { generate the method call }
1190                          membercall:=maybe_load_methodpointer(st,p1);
1191                          if membercall then
1192                            include(callflags,cnf_member_call);
1193                          p1:=ccallnode.create(paras,tprocsym(sym),st,p1,callflags,nil);
1194                          addsymref(sym);
1195                          paras:=nil;
1196                          consume(_ASSIGNMENT);
1197                          { read the expression }
1198                          if propsym.propdef.typ=procvardef then
1199                            getprocvardef:=tprocvardef(propsym.propdef);
1200                          p2:=comp_expr([ef_accept_equal]);
1201                          if assigned(getprocvardef) then
1202                            handle_procvar(getprocvardef,p2);
1203                          tcallnode(p1).left:=ccallparanode.create(p2,tcallnode(p1).left);
1204                          { mark as property, both the tcallnode and the real call block }
1205                          include(p1.flags,nf_isproperty);
1206                          getprocvardef:=nil;
1207                        end;
1208                      fieldvarsym :
1209                        begin
1210                          { generate access code }
1211                          if not handle_staticfield_access(sym,p1) then
1212                            propaccesslist_to_node(p1,st,propaccesslist);
1213                          include(p1.flags,nf_isproperty);
1214                          consume(_ASSIGNMENT);
1215                          { read the expression }
1216                          p2:=comp_expr([ef_accept_equal]);
1217                          p1:=cassignmentnode.create(p1,p2);
1218                       end
1219                     else
1220                       begin
1221                         p1:=cerrornode.create;
1222                         Message(parser_e_no_procedure_to_access_property);
1223                       end;
1224                   end;
1225                 end
1226               else
1227                 begin
1228                    p1:=cerrornode.create;
1229                    Message(parser_e_no_procedure_to_access_property);
1230                 end;
1231            end
1232          else
1233            begin
1234               if propsym.getpropaccesslist(palt_read,propaccesslist) then
1235                 begin
1236                    sym := propaccesslist.firstsym^.sym;
1237                    case sym.typ of
1238                      fieldvarsym :
1239                        begin
1240                          { generate access code }
1241                          if not handle_staticfield_access(sym,p1) then
1242                            propaccesslist_to_node(p1,st,propaccesslist);
1243                          include(p1.flags,nf_isproperty);
1244                          { catch expressions like "(propx):=1;" }
1245                          include(p1.flags,nf_no_lvalue);
1246                        end;
1247                      procsym :
1248                        begin
1249                           callflags:=[];
1250                           { generate the method call }
1251                           membercall:=maybe_load_methodpointer(st,p1);
1252                           if membercall then
1253                             include(callflags,cnf_member_call);
1254                           p1:=ccallnode.create(paras,tprocsym(sym),st,p1,callflags,nil);
1255                           paras:=nil;
1256                           include(p1.flags,nf_isproperty);
1257                           include(p1.flags,nf_no_lvalue);
1258                        end
1259                      else
1260                        begin
1261                           p1:=cerrornode.create;
1262                           Message(type_e_mismatch);
1263                        end;
1264                   end;
1265                 end
1266               else
1267                 begin
1268                    { error, no function to read property }
1269                    p1:=cerrornode.create;
1270                    Message(parser_e_no_procedure_to_access_property);
1271                 end;
1272            end;
1273         { release paras if not used }
1274         if assigned(paras) then
1275          paras.free;
1276       end;
1277 
1278 
1279     { the ID token has to be consumed before calling this function }
1280     procedure do_member_read(structh:tabstractrecorddef;getaddr:boolean;sym:tsym;var p1:tnode;var again:boolean;callflags:tcallnodeflags;spezcontext:tspecializationcontext);
1281       var
1282         isclassref:boolean;
1283         isrecordtype:boolean;
1284         isobjecttype:boolean;
1285       begin
1286          if sym=nil then
1287            begin
1288               { pattern is still valid unless
1289               there is another ID just after the ID of sym }
1290               Message1(sym_e_id_no_member,orgpattern);
1291               p1.free;
1292               p1:=cerrornode.create;
1293               { try to clean up }
1294               spezcontext.free;
1295               again:=false;
1296            end
1297          else
1298            begin
1299               if assigned(p1) then
1300                begin
1301                  if not assigned(p1.resultdef) then
1302                    do_typecheckpass(p1);
1303                  isclassref:=(p1.resultdef.typ=classrefdef);
1304                  isrecordtype:=(p1.nodetype=typen) and (p1.resultdef.typ=recorddef);
1305                  isobjecttype:=(p1.nodetype=typen) and is_object(p1.resultdef);
1306                end
1307               else
1308                 begin
1309                   isclassref:=false;
1310                   isrecordtype:=false;
1311                   isobjecttype:=false;
1312                 end;
1313 
1314               if assigned(spezcontext) and not (sym.typ=procsym) then
1315                 internalerror(2015091801);
1316 
1317               { we assume, that only procsyms and varsyms are in an object }
1318               { symbol table, for classes, properties are allowed          }
1319               case sym.typ of
1320                  procsym:
1321                    begin
1322                       do_proc_call(sym,sym.owner,structh,
1323                                    (getaddr and not(token in [_CARET,_POINT])),
1324                                    again,p1,callflags,spezcontext);
1325                       { we need to know which procedure is called }
1326                       do_typecheckpass(p1);
1327                       { calling using classref? }
1328                       if (
1329                             isclassref or
1330                             (
1331                               (isobjecttype or
1332                                isrecordtype) and
1333                               not (cnf_inherited in callflags)
1334                             )
1335                           ) and
1336                          (p1.nodetype=calln) and
1337                          assigned(tcallnode(p1).procdefinition) then
1338                         begin
1339                           if not isobjecttype then
1340                             begin
1341                               if not(po_classmethod in tcallnode(p1).procdefinition.procoptions) and
1342                                  not(tcallnode(p1).procdefinition.proctypeoption=potype_constructor) then
1343                                 Message(parser_e_only_class_members_via_class_ref);
1344                             end
1345                           else
1346                             begin
1347                               { with objects, you can also do this:
1348                                   type
1349                                     tparent = object
1350                                       procedure test;
1351                                     end;
1352 
1353                                     tchild = object(tchild)
1354                                       procedure test;
1355                                     end;
1356 
1357                                     procedure tparent.test;
1358                                       begin
1359                                       end;
1360 
1361                                     procedure tchild.test;
1362                                       begin
1363                                         tparent.test;
1364                                       end;
1365                               }
1366                               if (tcallnode(p1).procdefinition.proctypeoption<>potype_constructor) and
1367                                  not(po_staticmethod in tcallnode(p1).procdefinition.procoptions) and
1368                                  (not assigned(current_structdef) or
1369                                   not def_is_related(current_structdef,structh)) then
1370                                 Message(parser_e_only_static_members_via_object_type);
1371                             end;
1372                           { in Java, constructors are not automatically inherited
1373                             -> calling a constructor from a parent type will create
1374                                an instance of that parent type! }
1375                           if is_javaclass(structh) and
1376                              (tcallnode(p1).procdefinition.proctypeoption=potype_constructor) and
1377                              (tcallnode(p1).procdefinition.owner.defowner<>find_real_class_definition(tobjectdef(structh),false)) then
1378                             Message(parser_e_java_no_inherited_constructor);
1379                           { Provide a warning if we try to create an instance of a
1380                             abstract class using the type name of that class. We
1381                             must not provide a warning if we use a "class of"
1382                             variable of that type though as we don't know the
1383                             type of the class }
1384                           if (tcallnode(p1).procdefinition.proctypeoption=potype_constructor) and
1385                               (oo_is_abstract in structh.objectoptions) and
1386                               assigned(tcallnode(p1).methodpointer) and
1387                               (tcallnode(p1).methodpointer.nodetype=loadvmtaddrn) then
1388                             Message1(type_w_instance_abstract_class,structh.RttiName);
1389                         end
1390                    end;
1391                  fieldvarsym:
1392                    begin
1393                       if not handle_staticfield_access(sym,p1) then
1394                         begin
1395                           if isclassref then
1396                             if assigned(p1) and
1397                               (
1398                                 is_self_node(p1) or
1399                                 (assigned(current_procinfo) and (current_procinfo.get_normal_proc.procdef.no_self_node) and
1400                                 (current_procinfo.procdef.struct=structh))) then
1401                               Message(parser_e_only_class_members)
1402                             else
1403                               Message(parser_e_only_class_members_via_class_ref);
1404                           p1:=csubscriptnode.create(sym,p1);
1405                         end;
1406                    end;
1407                  propertysym:
1408                    begin
1409                       if isclassref and not (sp_static in sym.symoptions) then
1410                         Message(parser_e_only_class_members_via_class_ref);
1411                       handle_propertysym(tpropertysym(sym),sym.owner,p1);
1412                    end;
1413                  typesym:
1414                    begin
1415                      p1.free;
1416                      if try_to_consume(_LKLAMMER) then
1417                       begin
1418                         p1:=comp_expr([ef_accept_equal]);
1419                         consume(_RKLAMMER);
1420                         p1:=ctypeconvnode.create_explicit(p1,ttypesym(sym).typedef);
1421                       end
1422                      else
1423                        begin
1424                          p1:=ctypenode.create(ttypesym(sym).typedef);
1425                          if (is_class(ttypesym(sym).typedef) or
1426                              is_objcclass(ttypesym(sym).typedef) or
1427                              is_javaclass(ttypesym(sym).typedef)) and
1428                             not(block_type in [bt_type,bt_const_type,bt_var_type]) then
1429                            p1:=cloadvmtaddrnode.create(p1);
1430                        end;
1431                    end;
1432                  constsym:
1433                    begin
1434                      p1.free;
1435                      p1:=genconstsymtree(tconstsym(sym));
1436                    end;
1437                  staticvarsym:
1438                    begin
1439                      { typed constant is a staticvarsym
1440                        now they are absolutevarsym }
1441                      p1.free;
1442                      p1:=cloadnode.create(sym,sym.Owner);
1443                    end;
1444                  absolutevarsym:
1445                    begin
1446                      p1.free;
1447                      p1:=nil;
1448                      { typed constants are absolutebarsyms now to handle storage properly }
1449                      propaccesslist_to_node(p1,nil,tabsolutevarsym(sym).ref);
1450                    end
1451                  else
1452                    internalerror(16);
1453               end;
1454            end;
1455       end;
1456 
1457 
handle_specialize_inline_specializationnull1458     function handle_specialize_inline_specialization(var srsym:tsym;out srsymtable:tsymtable;out spezcontext:tspecializationcontext):boolean;
1459       var
1460         spezdef : tdef;
1461         symname : tsymstr;
1462       begin
1463         result:=false;
1464         spezcontext:=nil;
1465         srsymtable:=nil;
1466         if not assigned(srsym) then
1467           message1(sym_e_id_no_member,orgpattern)
1468         else
1469           if not (srsym.typ in [typesym,procsym]) then
1470             message(type_e_type_id_expected)
1471           else
1472             begin
1473               if srsym.typ=typesym then
1474                 spezdef:=ttypesym(srsym).typedef
1475               else
1476                 spezdef:=tdef(tprocsym(srsym).procdeflist[0]);
1477               if (spezdef.typ=errordef) and (sp_generic_dummy in srsym.symoptions) then
1478                 symname:=srsym.RealName
1479               else
1480                 symname:='';
1481               spezdef:=generate_specialization_phase1(spezcontext,spezdef,symname);
1482               case spezdef.typ of
1483                 errordef:
1484                   begin
1485                     spezcontext.free;
1486                     spezcontext:=nil;
1487                     srsym:=generrorsym;
1488                   end;
1489                 procdef:
1490                   begin
1491                     if block_type<>bt_body then
1492                       begin
1493                         message(parser_e_illegal_expression);
1494                         spezcontext.free;
1495                         spezcontext:=nil;
1496                         srsym:=generrorsym;
1497                       end
1498                     else
1499                       begin
1500                         srsym:=tprocdef(spezdef).procsym;
1501                         srsymtable:=srsym.owner;
1502                         result:=true;
1503                       end;
1504                   end;
1505                 objectdef,
1506                 recorddef,
1507                 arraydef,
1508                 procvardef:
1509                   begin
1510                     spezdef:=generate_specialization_phase2(spezcontext,tstoreddef(spezdef),false,'');
1511                     spezcontext.free;
1512                     spezcontext:=nil;
1513                     if spezdef<>generrordef then
1514                       begin
1515                         srsym:=spezdef.typesym;
1516                         srsymtable:=srsym.owner;
1517                         check_hints(srsym,srsym.symoptions,srsym.deprecatedmsg);
1518                         result:=true;
1519                       end;
1520                   end;
1521                 else
1522                   internalerror(2015070302);
1523               end;
1524             end;
1525       end;
1526 
1527 
handle_factor_typenodenull1528     function handle_factor_typenode(hdef:tdef;getaddr:boolean;var again:boolean;sym:tsym;typeonly:boolean):tnode;
1529       var
1530         srsym : tsym;
1531         srsymtable : tsymtable;
1532         erroroutresult,
1533         isspecialize : boolean;
1534         spezcontext : tspecializationcontext;
1535         savedfilepos : tfileposinfo;
1536       begin
1537          spezcontext:=nil;
1538          if sym=nil then
1539            sym:=hdef.typesym;
1540          { allow Ordinal(Value) for type declarations since it
1541            can be an enummeration declaration or a set lke:
1542            (OrdinalType(const1)..OrdinalType(const2) }
1543          if (not typeonly or is_ordinal(hdef)) and
1544             try_to_consume(_LKLAMMER) then
1545           begin
1546             result:=comp_expr([ef_accept_equal]);
1547             consume(_RKLAMMER);
1548             { type casts to class helpers aren't allowed }
1549             if is_objectpascal_helper(hdef) then
1550               Message(parser_e_no_category_as_types)
1551               { recovery by not creating a conversion node }
1552             else
1553               result:=ctypeconvnode.create_explicit(result,hdef);
1554           end
1555          { not LKLAMMER }
1556          else if (token=_POINT) and
1557             (is_object(hdef) or is_record(hdef)) then
1558            begin
1559              consume(_POINT);
1560              { handles calling methods declared in parent objects
1561                using "parentobject.methodname()" }
1562              if assigned(current_structdef) and
1563                 not(getaddr) and
1564                 def_is_related(current_structdef,hdef) then
1565                begin
1566                  result:=ctypenode.create(hdef);
1567                  ttypenode(result).typesym:=sym;
1568                  if not (m_delphi in current_settings.modeswitches) and
1569                      (block_type in inline_specialization_block_types) and
1570                      (token=_ID) and
1571                      (idtoken=_SPECIALIZE) then
1572                    begin
1573                      consume(_ID);
1574                      if token<>_ID then
1575                        message(type_e_type_id_expected);
1576                      isspecialize:=true;
1577                    end
1578                  else
1579                    isspecialize:=false;
1580                  { search also in inherited methods }
1581                  searchsym_in_class(tobjectdef(hdef),tobjectdef(current_structdef),pattern,srsym,srsymtable,[ssf_search_helper]);
1582                  if isspecialize then
1583                    begin
1584                      consume(_ID);
1585                      if not handle_specialize_inline_specialization(srsym,srsymtable,spezcontext) then
1586                        begin
1587                          result.free;
1588                          result:=cerrornode.create;
1589                        end;
1590                    end
1591                  else
1592                    begin
1593                      if assigned(srsym) then
1594                        check_hints(srsym,srsym.symoptions,srsym.deprecatedmsg);
1595                      consume(_ID);
1596                    end;
1597                  if result.nodetype<>errorn then
1598                    do_member_read(tabstractrecorddef(hdef),false,srsym,result,again,[],spezcontext)
1599                  else
1600                    spezcontext.free;
1601                end
1602              else
1603               begin
1604                 { handles:
1605                     * @TObject.Load
1606                     * static methods and variables }
1607                 result:=ctypenode.create(hdef);
1608                 ttypenode(result).typesym:=sym;
1609                 if not (m_delphi in current_settings.modeswitches) and
1610                     (block_type in inline_specialization_block_types) and
1611                     (token=_ID) and
1612                     (idtoken=_SPECIALIZE) then
1613                   begin
1614                     consume(_ID);
1615                     if token<>_ID then
1616                       message(type_e_type_id_expected);
1617                     isspecialize:=true;
1618                   end
1619                 else
1620                   isspecialize:=false;
1621                 erroroutresult:=true;
1622                 { TP allows also @TMenu.Load if Load is only }
1623                 { defined in an anchestor class              }
1624                 srsym:=search_struct_member(tabstractrecorddef(hdef),pattern);
1625                 if isspecialize and assigned(srsym) then
1626                   begin
1627                     consume(_ID);
1628                     if handle_specialize_inline_specialization(srsym,srsymtable,spezcontext) then
1629                       erroroutresult:=false;
1630                   end
1631                 else
1632                   begin
1633                     if assigned(srsym) then
1634                       begin
1635                         savedfilepos:=current_filepos;
1636                         consume(_ID);
1637                         if not (sp_generic_dummy in srsym.symoptions) or
1638                             not (token in [_LT,_LSHARPBRACKET]) then
1639                           check_hints(srsym,srsym.symoptions,srsym.deprecatedmsg,savedfilepos)
1640                         else
1641                           result:=cspecializenode.create(result,getaddr,srsym);
1642                         erroroutresult:=false;
1643                       end
1644                     else
1645                       Message1(sym_e_id_no_member,orgpattern);
1646                   end;
1647                 if erroroutresult then
1648                   begin
1649                     result.free;
1650                     result:=cerrornode.create;
1651                   end
1652                 else
1653                   if result.nodetype<>specializen then
1654                     do_member_read(tabstractrecorddef(hdef),getaddr,srsym,result,again,[],spezcontext);
1655               end;
1656            end
1657          else
1658           begin
1659             { Normally here would be the check against the usage
1660               of "TClassHelper.Something", but as that might be
1661               used inside of system symbols like sizeof and
1662               typeinfo this check is put into ttypenode.pass_1
1663               (for "TClassHelper" alone) and tcallnode.pass_1
1664               (for "TClassHelper.Something") }
1665             { class reference ? }
1666             if is_class(hdef) or
1667                is_objcclass(hdef) or
1668                { Java interfaces also can have loadvmtaddrnodes,
1669                  e.g. for expressions such as JLClass(intftype) }
1670                is_java_class_or_interface(hdef) then
1671              begin
1672                if getaddr and (token=_POINT) and
1673                   not is_javainterface(hdef) then
1674                 begin
1675                   consume(_POINT);
1676                   { allows @Object.Method }
1677                   { also allows static methods and variables }
1678                   result:=ctypenode.create(hdef);
1679                   ttypenode(result).typesym:=sym;
1680                   { TP allows also @TMenu.Load if Load is only }
1681                   { defined in an anchestor class              }
1682                   srsym:=search_struct_member(tobjectdef(hdef),pattern);
1683                   if assigned(srsym) then
1684                    begin
1685                      check_hints(srsym,srsym.symoptions,srsym.deprecatedmsg);
1686                      consume(_ID);
1687                      { in case of @Object.Method1.Method2, we have to call
1688                        Method1 -> create a loadvmtaddr node as self instead of
1689                        a typen (the typenode would be changed to self of the
1690                        current method in case Method1 is a constructor, see
1691                        mantis #24844) }
1692                      if not(block_type in [bt_type,bt_const_type,bt_var_type]) and
1693                         (srsym.typ=procsym) and
1694                         (token in [_CARET,_POINT]) then
1695                        result:=cloadvmtaddrnode.create(result);
1696                      do_member_read(tabstractrecorddef(hdef),getaddr,srsym,result,again,[],nil);
1697                    end
1698                   else
1699                    begin
1700                      Message1(sym_e_id_no_member,orgpattern);
1701                      consume(_ID);
1702                    end;
1703                 end
1704                else
1705                 begin
1706                   result:=ctypenode.create(hdef);
1707                   ttypenode(result).typesym:=sym;
1708                   { For a type block we simply return only
1709                     the type. For all other blocks we return
1710                     a loadvmt node }
1711                   if not(block_type in [bt_type,bt_const_type,bt_var_type]) then
1712                     result:=cloadvmtaddrnode.create(result);
1713                 end;
1714              end
1715             else
1716               begin
1717                 result:=ctypenode.create(hdef);
1718                 ttypenode(result).typesym:=sym;
1719               end;
1720           end;
1721       end;
1722 
1723 {****************************************************************************
1724                                Factor
1725 ****************************************************************************}
1726 
1727 
real_const_node_from_patternnull1728     function real_const_node_from_pattern(s:string):tnode;
1729       var
1730         d : bestreal;
1731         code : integer;
1732         cur : currency;
1733       begin
1734         val(s,d,code);
1735         if code<>0 then
1736          begin
1737            Message(parser_e_error_in_real);
1738            d:=1.0;
1739          end;
1740         if current_settings.fputype=fpu_none then
1741           begin
1742             Message(parser_e_unsupported_real);
1743             result:=cerrornode.create;
1744             exit;
1745           end;
1746         if (current_settings.minfpconstprec=s32real) and
1747            (d = single(d)) then
1748           result:=crealconstnode.create(d,s32floattype)
1749         else if (current_settings.minfpconstprec=s64real) and
1750                 (d = double(d)) then
1751           result:=crealconstnode.create(d,s64floattype)
1752         else
1753           result:=crealconstnode.create(d,pbestrealtype^);
1754         val(pattern,cur,code);
1755         if code=0 then
1756           trealconstnode(result).value_currency:=cur;
1757       end;
1758 
1759 {---------------------------------------------
1760                PostFixOperators
1761 ---------------------------------------------}
1762 
1763     { returns whether or not p1 has been changed }
postfixoperatorsnull1764     function postfixoperators(var p1:tnode;var again:boolean;getaddr:boolean): boolean;
1765 
1766       { tries to avoid syntax errors after invalid qualifiers }
1767       procedure recoverconsume_postfixops;
1768        begin
1769          repeat
1770            if not try_to_consume(_CARET) then
1771              if try_to_consume(_POINT) then
1772                try_to_consume(_ID)
1773              else if try_to_consume(_LECKKLAMMER) then
1774                begin
1775                  repeat
1776                    comp_expr([ef_accept_equal]);
1777                  until not try_to_consume(_COMMA);
1778                  consume(_RECKKLAMMER);
1779                end
1780              else if try_to_consume(_LKLAMMER) then
1781                begin
1782                  repeat
1783                    comp_expr([ef_accept_equal]);
1784                  until not try_to_consume(_COMMA);
1785                  consume(_RKLAMMER);
1786                end
1787              else
1788                break;
1789          until false;
1790        end;
1791 
1792 
1793       procedure handle_variantarray;
1794        var
1795          p4 : tnode;
1796          newstatement : tstatementnode;
1797          tempresultvariant,
1798          temp    : ttempcreatenode;
1799          paras : tcallparanode;
1800          newblock : tnode;
1801          countindices : longint;
1802          elements: tfplist;
1803          arraydef: tdef;
1804        begin
1805          { create statements with call initialize the arguments and
1806            call fpc_dynarr_setlength }
1807          newblock:=internalstatements(newstatement);
1808 
1809          { store all indices in a temporary array }
1810          countindices:=0;
1811          elements:=tfplist.Create;
1812          repeat
1813            p4:=comp_expr([ef_accept_equal]);
1814            elements.add(p4);
1815          until not try_to_consume(_COMMA);
1816 
1817          arraydef:=carraydef.getreusable(s32inttype,elements.count);
1818          temp:=ctempcreatenode.create(arraydef,arraydef.size,tt_persistent,false);
1819          addstatement(newstatement,temp);
1820          for countindices:=0 to elements.count-1 do
1821            begin
1822              addstatement(newstatement,
1823                cassignmentnode.create(
1824                  cvecnode.create(
1825                    ctemprefnode.create(temp),
1826                    genintconstnode(countindices)
1827                  ),
1828                  tnode(elements[countindices])
1829                )
1830              );
1831            end;
1832          countindices:=elements.count;
1833          elements.free;
1834 
1835          consume(_RECKKLAMMER);
1836 
1837          { we need only a write access if a := follows }
1838          if token=_ASSIGNMENT then
1839            begin
1840              consume(_ASSIGNMENT);
1841              p4:=comp_expr([ef_accept_equal]);
1842 
1843              { create call to fpc_vararray_put }
1844              paras:=ccallparanode.create(cordconstnode.create
1845                    (countindices,s32inttype,true),
1846                 ccallparanode.create(caddrnode.create_internal
1847                (cvecnode.create(ctemprefnode.create(temp),genintconstnode(0))),
1848                 ccallparanode.create(ctypeconvnode.create_internal(p4,cvarianttype),
1849                 ccallparanode.create(ctypeconvnode.create_internal(p1,cvarianttype)
1850                   ,nil))));
1851 
1852              addstatement(newstatement,ccallnode.createintern('fpc_vararray_put',paras));
1853              addstatement(newstatement,ctempdeletenode.create(temp));
1854            end
1855          else
1856            begin
1857              { create temp for result }
1858              tempresultvariant:=ctempcreatenode.create(cvarianttype,cvarianttype.size,tt_persistent,true);
1859              addstatement(newstatement,tempresultvariant);
1860 
1861              { create call to fpc_vararray_get }
1862              paras:=ccallparanode.create(cordconstnode.create
1863                    (countindices,s32inttype,true),
1864                 ccallparanode.create(caddrnode.create_internal
1865                (ctemprefnode.create(temp)),
1866                 ccallparanode.create(p1,
1867                 ccallparanode.create(
1868                     ctemprefnode.create(tempresultvariant)
1869                   ,nil))));
1870 
1871              addstatement(newstatement,ccallnode.createintern('fpc_vararray_get',paras));
1872              addstatement(newstatement,ctempdeletenode.create(temp));
1873              { the last statement should return the value as
1874                location and type, this is done be referencing the
1875                temp and converting it first from a persistent temp to
1876                normal temp }
1877              addstatement(newstatement,ctempdeletenode.create_normal_temp(tempresultvariant));
1878              addstatement(newstatement,ctemprefnode.create(tempresultvariant));
1879            end;
1880          p1:=newblock;
1881        end;
1882 
parse_array_constructornull1883       function parse_array_constructor(arrdef:tarraydef): tnode;
1884         var
1885           newstatement,assstatement:tstatementnode;
1886           arrnode:ttempcreatenode;
1887           temp2:ttempcreatenode;
1888           assnode:tnode;
1889           paracount:integer;
1890         begin
1891           result:=internalstatements(newstatement);
1892           { create temp for result }
1893           arrnode:=ctempcreatenode.create(arrdef,arrdef.size,tt_persistent,true);
1894           addstatement(newstatement,arrnode);
1895 
1896           paracount:=0;
1897           { check arguments and create an assignment calls }
1898           if try_to_consume(_LKLAMMER) then
1899             begin
1900               assnode:=internalstatements(assstatement);
1901               repeat
1902                 { arr[i] := param_i }
1903                 addstatement(assstatement,
1904                   cassignmentnode.create(
1905                     cvecnode.create(
1906                       ctemprefnode.create(arrnode),
1907                       cordconstnode.create(paracount,arrdef.rangedef,false)),
1908                     comp_expr([ef_accept_equal])));
1909                 inc(paracount);
1910               until not try_to_consume(_COMMA);
1911               consume(_RKLAMMER);
1912             end
1913           else
1914             assnode:=nil;
1915 
1916           { get temp for array of lengths }
1917           temp2:=ctempcreatenode.create(sinttype,sinttype.size,tt_persistent,false);
1918           addstatement(newstatement,temp2);
1919 
1920           { one dimensional }
1921           addstatement(newstatement,cassignmentnode.create(
1922               ctemprefnode.create(temp2),
1923               cordconstnode.create
1924                  (paracount,s32inttype,true)));
1925           { create call to fpc_dynarr_setlength }
1926           addstatement(newstatement,ccallnode.createintern('fpc_dynarray_setlength',
1927               ccallparanode.create(caddrnode.create_internal
1928                     (ctemprefnode.create(temp2)),
1929                  ccallparanode.create(cordconstnode.create
1930                     (1,s32inttype,true),
1931                  ccallparanode.create(caddrnode.create_internal
1932                     (crttinode.create(tstoreddef(arrdef),initrtti,rdt_normal)),
1933                  ccallparanode.create(
1934                    ctypeconvnode.create_internal(
1935                      ctemprefnode.create(arrnode),voidpointertype),
1936                    nil))))
1937 
1938             ));
1939           { add assignment statememnts }
1940           addstatement(newstatement,ctempdeletenode.create(temp2));
1941           if assigned(assnode) then
1942             addstatement(newstatement,assnode);
1943           { the last statement should return the value as
1944             location and type, this is done be referencing the
1945             temp and converting it first from a persistent temp to
1946             normal temp }
1947           addstatement(newstatement,ctempdeletenode.create_normal_temp(arrnode));
1948           addstatement(newstatement,ctemprefnode.create(arrnode));
1949         end;
1950 
try_type_helpernull1951       function try_type_helper(var node:tnode;def:tdef):boolean;
1952         var
1953           srsym : tsym;
1954           srsymtable : tsymtable;
1955           n : tnode;
1956           newstatement : tstatementnode;
1957           temp : ttempcreatenode;
1958           extdef : tdef;
1959         begin
1960           result:=false;
1961           if (token=_ID) and (block_type in [bt_body,bt_general,bt_except,bt_const]) then
1962             begin
1963               if not assigned(def) then
1964                 if node.nodetype=addrn then
1965                   { always use the pointer type for addr nodes as otherwise
1966                     we'll have an anonymous pointertype with no name }
1967                   def:=voidpointertype
1968                 else
1969                   def:=node.resultdef;
1970               result:=search_objectpascal_helper(def,nil,pattern,srsym,srsymtable);
1971               if result then
1972                 begin
1973                   if not (srsymtable.symtabletype=objectsymtable) or
1974                       not is_objectpascal_helper(tdef(srsymtable.defowner)) then
1975                     internalerror(2013011401);
1976                   { convert const node to temp node of the extended type }
1977                   if node.nodetype in (nodetype_const+[addrn]) then
1978                     begin
1979                       extdef:=tobjectdef(srsymtable.defowner).extendeddef;
1980                       newstatement:=nil;
1981                       n:=internalstatements(newstatement);
1982                       temp:=ctempcreatenode.create(extdef,extdef.size,tt_persistent,false);
1983                       addstatement(newstatement,temp);
1984                       addstatement(newstatement,cassignmentnode.create(ctemprefnode.create(temp),node));
1985                       addstatement(newstatement,ctempdeletenode.create_normal_temp(temp));
1986                       addstatement(newstatement,ctemprefnode.create(temp));
1987                       node:=n;
1988                       do_typecheckpass(node)
1989                     end;
1990                   check_hints(srsym,srsym.symoptions,srsym.deprecatedmsg);
1991                   consume(_ID);
1992                   do_member_read(nil,getaddr,srsym,node,again,[],nil);
1993                 end;
1994             end;
1995         end;
1996 
1997     var
1998      protsym  : tpropertysym;
1999      p2,p3  : tnode;
2000      srsym  : tsym;
2001      srsymtable : TSymtable;
2002      structh    : tabstractrecorddef;
2003      { shouldn't be used that often, so the extra overhead is ok to save
2004        stack space }
2005      dispatchstring : ansistring;
2006      autoderef,
2007      erroroutp1,
2008      allowspecialize,
2009      isspecialize,
2010      found,
2011      haderror,
2012      nodechanged    : boolean;
2013      calltype: tdispcalltype;
2014      valstr,expstr : string;
2015      intval : qword;
2016      code : integer;
2017      strdef : tdef;
2018      spezcontext : tspecializationcontext;
2019      old_current_filepos : tfileposinfo;
2020     label
2021      skipreckklammercheck,
2022      skippointdefcheck;
2023     begin
2024      result:=false;
2025      again:=true;
2026      while again do
2027       begin
2028         spezcontext:=nil;
2029         { we need the resultdef }
2030         do_typecheckpass_changed(p1,nodechanged);
2031         result:=result or nodechanged;
2032 
2033         if codegenerror then
2034          begin
2035            recoverconsume_postfixops;
2036            exit;
2037          end;
2038         { handle token }
2039         case token of
2040           _CARET:
2041              begin
2042                consume(_CARET);
2043 
2044                { support tp/mac procvar^ if the procvar returns a
2045                  pointer type }
2046                if ((m_tp_procvar in current_settings.modeswitches) or
2047                    (m_mac_procvar in current_settings.modeswitches)) and
2048                   (p1.resultdef.typ=procvardef) and
2049                   (tprocvardef(p1.resultdef).returndef.typ=pointerdef) then
2050                  begin
2051                    p1:=ccallnode.create_procvar(nil,p1);
2052                    typecheckpass(p1);
2053                  end;
2054 
2055                { iso file buf access? }
2056                if (m_isolike_io in current_settings.modeswitches) and
2057                  (p1.resultdef.typ=filedef) then
2058                  begin
2059                    case tfiledef(p1.resultdef).filetyp of
2060                      ft_text:
2061                        begin
2062                          p1:=cderefnode.create(ccallnode.createintern('fpc_getbuf_text',ccallparanode.create(p1,nil)));
2063                          typecheckpass(p1);
2064                        end;
2065                      ft_typed:
2066                        begin
2067                          p1:=cderefnode.create(ctypeconvnode.create_internal(ccallnode.createintern('fpc_getbuf_typedfile',ccallparanode.create(p1,nil)),
2068                            cpointerdef.getreusable(tfiledef(p1.resultdef).typedfiledef)));
2069                          typecheckpass(p1);
2070                        end;
2071                    end;
2072                  end
2073                else if not(p1.resultdef.typ in [pointerdef,undefineddef]) then
2074                  begin
2075                     { ^ as binary operator is a problem!!!! (FK) }
2076                     again:=false;
2077                     Message(parser_e_invalid_qualifier);
2078                     recoverconsume_postfixops;
2079                     p1.destroy;
2080                     p1:=cerrornode.create;
2081                  end
2082                else
2083                  p1:=cderefnode.create(p1);
2084              end;
2085 
2086           _LECKKLAMMER:
2087              begin
2088                if is_class_or_interface_or_object(p1.resultdef) or
2089                   is_dispinterface(p1.resultdef) or
2090                   is_record(p1.resultdef) or
2091                   is_javaclass(p1.resultdef) then
2092                  begin
2093                    { default property }
2094                    protsym:=search_default_property(tabstractrecorddef(p1.resultdef));
2095                    if not(assigned(protsym)) then
2096                      begin
2097                         p1.destroy;
2098                         p1:=cerrornode.create;
2099                         again:=false;
2100                         message(parser_e_no_default_property_available);
2101                      end
2102                    else
2103                      begin
2104                        { The property symbol is referenced indirect }
2105                        protsym.IncRefCount;
2106                        handle_propertysym(protsym,protsym.owner,p1);
2107                      end;
2108                  end
2109                else
2110                  begin
2111                    consume(_LECKKLAMMER);
2112                    repeat
2113                      { in all of the cases below, p1 is changed }
2114                      case p1.resultdef.typ of
2115                        pointerdef:
2116                          begin
2117                             { support delphi autoderef }
2118                             if (tpointerdef(p1.resultdef).pointeddef.typ=arraydef) and
2119                                (m_autoderef in current_settings.modeswitches) then
2120                               p1:=cderefnode.create(p1);
2121                             p2:=comp_expr([ef_accept_equal]);
2122                             { Support Pbytevar[0..9] which returns array [0..9].}
2123                             if try_to_consume(_POINTPOINT) then
2124                               p2:=crangenode.create(p2,comp_expr([ef_accept_equal]));
2125                             p1:=cvecnode.create(p1,p2);
2126                          end;
2127                        variantdef:
2128                          begin
2129                            handle_variantarray;
2130                            { the RECKKLAMMER is already read }
2131                            goto skipreckklammercheck;
2132                          end;
2133                        stringdef :
2134                          begin
2135                            p2:=comp_expr([ef_accept_equal]);
2136                            { Support string[0..9] which returns array [0..9] of char.}
2137                            if try_to_consume(_POINTPOINT) then
2138                              p2:=crangenode.create(p2,comp_expr([ef_accept_equal]));
2139                            p1:=cvecnode.create(p1,p2);
2140                          end;
2141                        arraydef:
2142                          begin
2143                            p2:=comp_expr([ef_accept_equal]);
2144                            { support SEG:OFS for go32v2/msdos Mem[] }
2145                            if (target_info.system in [system_i386_go32v2,system_i386_watcom,system_i8086_msdos,system_i8086_win16,system_i8086_embedded]) and
2146                               (p1.nodetype=loadn) and
2147                               assigned(tloadnode(p1).symtableentry) and
2148                               assigned(tloadnode(p1).symtableentry.owner.name) and
2149                               (tloadnode(p1).symtableentry.owner.name^='SYSTEM') and
2150                               ((tloadnode(p1).symtableentry.name='MEM') or
2151                                (tloadnode(p1).symtableentry.name='MEMW') or
2152                                (tloadnode(p1).symtableentry.name='MEML')) then
2153                              begin
2154 {$if defined(i8086)}
2155                                consume(_COLON);
2156                                inserttypeconv(p2,u16inttype);
2157                                inserttypeconv_internal(p2,u32inttype);
2158                                p3:=cshlshrnode.create(shln,p2,cordconstnode.create($10,s16inttype,false));
2159                                p2:=comp_expr([ef_accept_equal]);
2160                                inserttypeconv(p2,u16inttype);
2161                                inserttypeconv_internal(p2,u32inttype);
2162                                p2:=caddnode.create(addn,p2,p3);
2163                                case tloadnode(p1).symtableentry.name of
2164                                  'MEM': p2:=ctypeconvnode.create_internal(p2,bytefarpointertype);
2165                                  'MEMW': p2:=ctypeconvnode.create_internal(p2,wordfarpointertype);
2166                                  'MEML': p2:=ctypeconvnode.create_internal(p2,longintfarpointertype);
2167                                  else
2168                                    internalerror(2013053102);
2169                                end;
2170                                p1:=cderefnode.create(p2);
2171 {$elseif defined(i386)}
2172                                if try_to_consume(_COLON) then
2173                                 begin
2174                                   p3:=caddnode.create(muln,cordconstnode.create($10,s32inttype,false),p2);
2175                                   p2:=comp_expr([ef_accept_equal]);
2176                                   p2:=caddnode.create(addn,p2,p3);
2177                                   if try_to_consume(_POINTPOINT) then
2178                                     { Support mem[$a000:$0000..$07ff] which returns array [0..$7ff] of memtype.}
2179                                     p2:=crangenode.create(p2,caddnode.create(addn,comp_expr([ef_accept_equal]),p3.getcopy));
2180                                   p1:=cvecnode.create(p1,p2);
2181                                   include(tvecnode(p1).flags,nf_memseg);
2182                                   include(tvecnode(p1).flags,nf_memindex);
2183                                 end
2184                                else
2185                                 begin
2186                                   if try_to_consume(_POINTPOINT) then
2187                                     { Support mem[$80000000..$80000002] which returns array [0..2] of memtype.}
2188                                     p2:=crangenode.create(p2,comp_expr([ef_accept_equal]));
2189                                   p1:=cvecnode.create(p1,p2);
2190                                   include(tvecnode(p1).flags,nf_memindex);
2191                                 end;
2192 {$else}
2193                                internalerror(2013053101);
2194 {$endif}
2195                              end
2196                            else
2197                              begin
2198                                if try_to_consume(_POINTPOINT) then
2199                                  { Support arrayvar[0..9] which returns array [0..9] of arraytype.}
2200                                  p2:=crangenode.create(p2,comp_expr([ef_accept_equal]));
2201                                p1:=cvecnode.create(p1,p2);
2202                              end;
2203                          end;
2204                        else
2205                          begin
2206                            if p1.resultdef.typ<>undefineddef then
2207                              Message(parser_e_invalid_qualifier);
2208                            p1.destroy;
2209                            p1:=cerrornode.create;
2210                            comp_expr([ef_accept_equal]);
2211                            again:=false;
2212                          end;
2213                      end;
2214                      do_typecheckpass(p1);
2215                    until not try_to_consume(_COMMA);
2216                    consume(_RECKKLAMMER);
2217                    { handle_variantarray eats the RECKKLAMMER and jumps here }
2218                  skipreckklammercheck:
2219                  end;
2220              end;
2221 
2222           _POINT :
2223              begin
2224                consume(_POINT);
2225                allowspecialize:=not (m_delphi in current_settings.modeswitches) and (block_type in inline_specialization_block_types);
2226                if allowspecialize and (token=_ID) and (idtoken=_SPECIALIZE) then
2227                  begin
2228                    //consume(_ID);
2229                    isspecialize:=true;
2230                  end
2231                else
2232                  isspecialize:=false;
2233                autoderef:=false;
2234                if (p1.resultdef.typ=pointerdef) and
2235                   (m_autoderef in current_settings.modeswitches) and
2236                   { don't auto-deref objc.id, because then the code
2237                     below for supporting id.anyobjcmethod isn't triggered }
2238                   (p1.resultdef<>objc_idtype) then
2239                  begin
2240                    p1:=cderefnode.create(p1);
2241                    do_typecheckpass(p1);
2242                    autoderef:=true;
2243                  end;
2244                { procvar.<something> can never mean anything so always
2245                  try to call it in case it returns a record/object/... }
2246                maybe_call_procvar(p1,false);
2247 
2248                if (p1.nodetype=ordconstn) and
2249                    not is_boolean(p1.resultdef) and
2250                    not is_enum(p1.resultdef) then
2251                  begin
2252                    { type helpers are checked first }
2253                    if (token=_ID) and try_type_helper(p1,nil) then
2254                      goto skippointdefcheck;
2255                    { only an "e" or "E" can follow an intconst with a ".", the
2256                      other case (another intconst) is handled by the scanner }
2257                    if (token=_ID) and (pattern[1]='E') then
2258                      begin
2259                        haderror:=false;
2260                        if length(pattern)>1 then
2261                          begin
2262                            expstr:=copy(pattern,2,length(pattern)-1);
2263                            val(expstr,intval,code);
2264                            if code<>0 then
2265                              begin
2266                                haderror:=true;
2267                                intval:=intval; // Hackfix the "var assigned but never used" note.
2268                              end;
2269                          end
2270                        else
2271                          expstr:='';
2272                        consume(token);
2273                        if tordconstnode(p1).value.signed then
2274                          str(tordconstnode(p1).value.svalue,valstr)
2275                        else
2276                          str(tordconstnode(p1).value.uvalue,valstr);
2277                        valstr:=valstr+'.0E';
2278                        if expstr='' then
2279                          case token of
2280                            _MINUS:
2281                              begin
2282                                consume(token);
2283                                if token=_INTCONST then
2284                                  begin
2285                                    valstr:=valstr+'-'+pattern;
2286                                    consume(token);
2287                                  end
2288                                else
2289                                  haderror:=true;
2290                              end;
2291                            _PLUS:
2292                              begin
2293                                consume(token);
2294                                if token=_INTCONST then
2295                                  begin
2296                                    valstr:=valstr+pattern;
2297                                    consume(token);
2298                                  end
2299                                else
2300                                  haderror:=true;
2301                              end;
2302                            _INTCONST:
2303                              begin
2304                                valstr:=valstr+pattern;
2305                                consume(_INTCONST);
2306                              end;
2307                            else
2308                              haderror:=true;
2309                          end
2310                        else
2311                          valstr:=valstr+expstr;
2312                        if haderror then
2313                          begin
2314                            Message(parser_e_error_in_real);
2315                            p2:=cerrornode.create;
2316                          end
2317                        else
2318                          p2:=real_const_node_from_pattern(valstr);
2319                        p1.free;
2320                        p1:=p2;
2321                        again:=false;
2322                        goto skippointdefcheck;
2323                      end
2324                    else
2325                      begin
2326                        { just convert the ordconst to a realconst }
2327                        p2:=crealconstnode.create(tordconstnode(p1).value,pbestrealtype^);
2328                        p1.free;
2329                        p1:=p2;
2330                        again:=false;
2331                        goto skippointdefcheck;
2332                      end;
2333                  end;
2334 
2335                if (p1.nodetype=stringconstn) and (token=_ID) then
2336                  begin
2337                    { the def of a string const is an array }
2338                    case tstringconstnode(p1).cst_type of
2339                      cst_conststring:
2340                        if cs_refcountedstrings in current_settings.localswitches then
2341                          if m_default_unicodestring in current_settings.modeswitches then
2342                            strdef:=cunicodestringtype
2343                          else
2344                            strdef:=cansistringtype
2345                        else
2346                          strdef:=cshortstringtype;
2347                      cst_shortstring:
2348                        strdef:=cshortstringtype;
2349                      cst_ansistring:
2350                        { use getansistringdef? }
2351                        strdef:=cansistringtype;
2352                      cst_widestring:
2353                        strdef:=cwidestringtype;
2354                      cst_unicodestring:
2355                        strdef:=cunicodestringtype;
2356                      cst_longstring:
2357                        { let's see when someone stumbles upon this...}
2358                        internalerror(201301111);
2359                      else
2360                        internalerror(2013112903);
2361                    end;
2362                    if try_type_helper(p1,strdef) then
2363                      goto skippointdefcheck;
2364                  end;
2365 
2366                { this is skipped if label skippointdefcheck is used }
2367                case p1.resultdef.typ of
2368                  recorddef:
2369                    begin
2370                      if isspecialize or (token=_ID) then
2371                        begin
2372                          erroroutp1:=true;
2373                          srsym:=nil;
2374                          structh:=tabstractrecorddef(p1.resultdef);
2375                          if isspecialize then
2376                            begin
2377                              { consume the specialize }
2378                              consume(_ID);
2379                              if token<>_ID then
2380                                consume(_ID)
2381                              else
2382                                begin
2383                                  searchsym_in_record(structh,pattern,srsym,srsymtable);
2384                                  consume(_ID);
2385                                  if handle_specialize_inline_specialization(srsym,srsymtable,spezcontext) then
2386                                    erroroutp1:=false;
2387                                end;
2388                            end
2389                          else
2390                            begin
2391                              searchsym_in_record(structh,pattern,srsym,srsymtable);
2392                              if assigned(srsym) then
2393                                begin
2394                                  old_current_filepos:=current_filepos;
2395                                  consume(_ID);
2396                                  if not (sp_generic_dummy in srsym.symoptions) or
2397                                      not (token in [_LT,_LSHARPBRACKET]) then
2398                                    check_hints(srsym,srsym.symoptions,srsym.deprecatedmsg,old_current_filepos)
2399                                  else
2400                                    p1:=cspecializenode.create(p1,getaddr,srsym);
2401                                  erroroutp1:=false;
2402                                end
2403                              else
2404                                begin
2405                                  Message1(sym_e_id_no_member,orgpattern);
2406                                  { try to clean up }
2407                                  consume(_ID);
2408                                end;
2409                            end;
2410                          if erroroutp1 then
2411                            begin
2412                              p1.free;
2413                              p1:=cerrornode.create;
2414                            end
2415                          else
2416                            if p1.nodetype<>specializen then
2417                              do_member_read(structh,getaddr,srsym,p1,again,[],spezcontext);
2418                        end
2419                      else
2420                      consume(_ID);
2421                    end;
2422                  enumdef:
2423                    begin
2424                      if token=_ID then
2425                        begin
2426                          srsym:=tsym(tenumdef(p1.resultdef).symtable.Find(pattern));
2427                          if assigned(srsym) and (srsym.typ=enumsym) and (p1.nodetype=typen) then
2428                            begin
2429                              p1.destroy;
2430                              check_hints(srsym,srsym.symoptions,srsym.deprecatedmsg);
2431                              p1:=genenumnode(tenumsym(srsym));
2432                              consume(_ID);
2433                            end
2434                          else
2435                            if not try_type_helper(p1,nil) then
2436                              begin
2437                                p1.destroy;
2438                                Message1(sym_e_id_no_member,orgpattern);
2439                                p1:=cerrornode.create;
2440                                consume(_ID);
2441                              end;
2442                        end;
2443                    end;
2444                  arraydef:
2445                    begin
2446                      if is_dynamic_array(p1.resultdef) then
2447                        begin
2448                          if token=_ID then
2449                            begin
2450                              if not try_type_helper(p1,nil) then
2451                                begin
2452                                  if p1.nodetype=typen then
2453                                    begin
2454                                      if pattern='CREATE' then
2455                                        begin
2456                                          consume(_ID);
2457                                          p2:=parse_array_constructor(tarraydef(p1.resultdef));
2458                                          p1.destroy;
2459                                          p1:=p2;
2460                                        end
2461                                      else
2462                                        begin
2463                                          Message2(scan_f_syn_expected,'CREATE',pattern);
2464                                          p1.destroy;
2465                                          p1:=cerrornode.create;
2466                                          consume(_ID);
2467                                        end;
2468                                    end
2469                                  else
2470                                    begin
2471                                      Message(parser_e_invalid_qualifier);
2472                                      p1.destroy;
2473                                      p1:=cerrornode.create;
2474                                      consume(_ID);
2475                                    end;
2476                                end;
2477                            end
2478                          else
2479                            begin
2480                              Message(parser_e_invalid_qualifier);
2481                              p1.destroy;
2482                              p1:=cerrornode.create;
2483                              consume(_ID);
2484                            end;
2485                        end
2486                      else
2487                        if (token<>_ID) or not try_type_helper(p1,nil) then
2488                          begin
2489                            Message(parser_e_invalid_qualifier);
2490                            p1.destroy;
2491                            p1:=cerrornode.create;
2492                            consume(_ID);
2493                          end;
2494                    end;
2495                   variantdef:
2496                     begin
2497                       { dispatch call? }
2498                       { lhs := v.ident[parameters] -> property get
2499                         lhs := v.ident(parameters) -> method call
2500                         v.ident[parameters] := rhs -> property put
2501                         v.ident(parameters) := rhs -> also property put }
2502                       if token=_ID then
2503                         begin
2504                           if not try_type_helper(p1,nil) then
2505                             begin
2506                               dispatchstring:=orgpattern;
2507                               consume(_ID);
2508                               calltype:=dct_method;
2509                               if try_to_consume(_LKLAMMER) then
2510                                 begin
2511                                   p2:=parse_paras(false,true,_RKLAMMER);
2512                                   consume(_RKLAMMER);
2513                                 end
2514                               else if try_to_consume(_LECKKLAMMER) then
2515                                 begin
2516                                   p2:=parse_paras(false,true,_RECKKLAMMER);
2517                                   consume(_RECKKLAMMER);
2518                                   calltype:=dct_propget;
2519                                 end
2520                               else
2521                                 p2:=nil;
2522                               { property setter? }
2523                               if (token=_ASSIGNMENT) and not(afterassignment) then
2524                                 begin
2525                                   consume(_ASSIGNMENT);
2526                                   { read the expression }
2527                                   p3:=comp_expr([ef_accept_equal]);
2528                                   { concat value parameter too }
2529                                   p2:=ccallparanode.create(p3,p2);
2530                                   p1:=translate_disp_call(p1,p2,dct_propput,dispatchstring,0,voidtype);
2531                                 end
2532                               else
2533                               { this is only an approximation
2534                                 setting useresult if not necessary is only a waste of time, no more, no less (FK) }
2535                               if afterassignment or in_args or (token<>_SEMICOLON) then
2536                                 p1:=translate_disp_call(p1,p2,calltype,dispatchstring,0,cvarianttype)
2537                               else
2538                                 p1:=translate_disp_call(p1,p2,calltype,dispatchstring,0,voidtype);
2539                             end;
2540                         end
2541                       else { Error }
2542                         Consume(_ID);
2543                      end;
2544                   classrefdef:
2545                     begin
2546                       erroroutp1:=true;
2547                       if token=_ID then
2548                         begin
2549                           srsym:=nil;
2550                           structh:=tobjectdef(tclassrefdef(p1.resultdef).pointeddef);
2551                           if isspecialize then
2552                             begin
2553                               { consume the specialize }
2554                               consume(_ID);
2555                               if token<>_ID then
2556                                 consume(_ID)
2557                               else
2558                                 begin
2559                                   searchsym_in_class(tobjectdef(structh),tobjectdef(structh),pattern,srsym,srsymtable,[ssf_search_helper]);
2560                                   consume(_ID);
2561                                   if handle_specialize_inline_specialization(srsym,srsymtable,spezcontext) then
2562                                     erroroutp1:=false;
2563                                 end;
2564                             end
2565                           else
2566                             begin
2567                               searchsym_in_class(tobjectdef(structh),tobjectdef(structh),pattern,srsym,srsymtable,[ssf_search_helper]);
2568                               if assigned(srsym) then
2569                                 begin
2570                                   old_current_filepos:=current_filepos;
2571                                   consume(_ID);
2572                                   if not (sp_generic_dummy in srsym.symoptions) or
2573                                       not (token in [_LT,_LSHARPBRACKET]) then
2574                                     check_hints(srsym,srsym.symoptions,srsym.deprecatedmsg,old_current_filepos)
2575                                   else
2576                                     p1:=cspecializenode.create(p1,getaddr,srsym);
2577                                   erroroutp1:=false;
2578                                 end
2579                               else
2580                                 begin
2581                                   Message1(sym_e_id_no_member,orgpattern);
2582                                   { try to clean up }
2583                                   consume(_ID);
2584                                 end;
2585                             end;
2586                           if erroroutp1 then
2587                             begin
2588                               p1.free;
2589                               p1:=cerrornode.create;
2590                             end
2591                           else
2592                             if p1.nodetype<>specializen then
2593                               do_member_read(structh,getaddr,srsym,p1,again,[],spezcontext);
2594                         end
2595                       else { Error }
2596                         Consume(_ID);
2597                     end;
2598                   objectdef:
2599                     begin
2600                       if isspecialize or (token=_ID) then
2601                         begin
2602                           erroroutp1:=true;
2603                           srsym:=nil;
2604                           structh:=tobjectdef(p1.resultdef);
2605                           if isspecialize then
2606                             begin
2607                               { consume the "specialize" }
2608                               consume(_ID);
2609                               if token<>_ID then
2610                                 consume(_ID)
2611                               else
2612                                 begin
2613                                   searchsym_in_class(tobjectdef(structh),tobjectdef(structh),pattern,srsym,srsymtable,[ssf_search_helper]);
2614                                   consume(_ID);
2615                                   if handle_specialize_inline_specialization(srsym,srsymtable,spezcontext) then
2616                                     erroroutp1:=false;
2617                                 end;
2618                             end
2619                           else
2620                             begin
2621                               searchsym_in_class(tobjectdef(structh),tobjectdef(structh),pattern,srsym,srsymtable,[ssf_search_helper]);
2622                               if assigned(srsym) then
2623                                 begin
2624                                    old_current_filepos:=current_filepos;
2625                                    consume(_ID);
2626                                    if not (sp_generic_dummy in srsym.symoptions) or
2627                                        not (token in [_LT,_LSHARPBRACKET]) then
2628                                      check_hints(srsym,srsym.symoptions,srsym.deprecatedmsg,old_current_filepos)
2629                                    else
2630                                      p1:=cspecializenode.create(p1,getaddr,srsym);
2631                                    erroroutp1:=false;
2632                                 end
2633                               else
2634                                 begin
2635                                    Message1(sym_e_id_no_member,orgpattern);
2636                                    { try to clean up }
2637                                    consume(_ID);
2638                                 end;
2639                             end;
2640                           if erroroutp1 then
2641                             begin
2642                               p1.free;
2643                               p1:=cerrornode.create;
2644                             end
2645                           else
2646                             if p1.nodetype<>specializen then
2647                               do_member_read(structh,getaddr,srsym,p1,again,[],spezcontext);
2648                         end
2649                       else { Error }
2650                         Consume(_ID);
2651                     end;
2652                   pointerdef:
2653                     begin
2654                       if (p1.resultdef=objc_idtype) then
2655                         begin
2656                           { objc's id type can be used to call any
2657                             Objective-C method of any Objective-C class
2658                             type that's currently in scope }
2659                           if search_objc_method(pattern,srsym,srsymtable) then
2660                             begin
2661                               consume(_ID);
2662                               do_proc_call(srsym,srsymtable,nil,
2663                                 (getaddr and not(token in [_CARET,_POINT])),
2664                                 again,p1,[cnf_objc_id_call],nil);
2665                               { we need to know which procedure is called }
2666                               do_typecheckpass(p1);
2667                             end
2668                           else
2669                             begin
2670                               consume(_ID);
2671                               Message(parser_e_methode_id_expected);
2672                             end;
2673                         end
2674                       else
2675                         begin
2676                           if not try_type_helper(p1,nil) then
2677                             begin
2678                               Message(parser_e_invalid_qualifier);
2679                               if tpointerdef(p1.resultdef).pointeddef.typ in [recorddef,objectdef,classrefdef] then
2680                                 Message(parser_h_maybe_deref_caret_missing);
2681                             end;
2682                         end
2683                     end;
2684                   else
2685                     begin
2686                       if autoderef then
2687                         begin
2688                           { always try with the not dereferenced node }
2689                           p2:=tderefnode(p1).left;
2690                           found:=try_type_helper(p2,nil);
2691                           if found then
2692                             begin
2693                               tderefnode(p1).left:=nil;
2694                               p1.destroy;
2695                               p1:=p2;
2696                             end;
2697                         end
2698                       else
2699                         found:=try_type_helper(p1,nil);
2700                       if not found then
2701                         begin
2702                           if p1.resultdef.typ<>undefineddef then
2703                             Message(parser_e_invalid_qualifier);
2704                           p1.destroy;
2705                           p1:=cerrornode.create;
2706                           { Error }
2707                           consume(_ID);
2708                         end;
2709                     end;
2710                end;
2711                { processing an ordconstnode avoids the resultdef check }
2712                skippointdefcheck:
2713              end;
2714 
2715           else
2716             begin
2717               { is this a procedure variable ? }
2718               if assigned(p1.resultdef) and
2719                  (p1.resultdef.typ=procvardef) then
2720                 begin
2721                   { Typenode for typecasting or expecting a procvar }
2722                   if (p1.nodetype=typen) or
2723                      (
2724                       assigned(getprocvardef) and
2725                       equal_defs(p1.resultdef,getprocvardef)
2726                      ) then
2727                     begin
2728                       if try_to_consume(_LKLAMMER) then
2729                         begin
2730                           p1:=comp_expr([ef_accept_equal]);
2731                           consume(_RKLAMMER);
2732                           p1:=ctypeconvnode.create_explicit(p1,p1.resultdef);
2733                         end
2734                       else
2735                         again:=false
2736                     end
2737                   else
2738                     begin
2739                       if try_to_consume(_LKLAMMER) then
2740                         begin
2741                           p2:=parse_paras(false,false,_RKLAMMER);
2742                           consume(_RKLAMMER);
2743                           p1:=ccallnode.create_procvar(p2,p1);
2744                           { proc():= is never possible }
2745                           if token=_ASSIGNMENT then
2746                             begin
2747                               Message(parser_e_illegal_expression);
2748                               p1.free;
2749                               p1:=cerrornode.create;
2750                               again:=false;
2751                             end;
2752                         end
2753                       else
2754                         again:=false;
2755                     end;
2756                 end
2757               else
2758                 again:=false;
2759              end;
2760         end;
2761 
2762         { we only try again if p1 was changed }
2763         if again or
2764            (p1.nodetype=errorn) then
2765           result:=true;
2766       end; { while again }
2767     end;
2768 
is_member_readnull2769     function is_member_read(sym: tsym; st: tsymtable; var p1: tnode;
2770                             out memberparentdef: tdef): boolean;
2771       var
2772         hdef : tdef;
2773       begin
2774         result:=true;
2775         memberparentdef:=nil;
2776 
2777         case st.symtabletype of
2778           ObjectSymtable,
2779           recordsymtable:
2780             begin
2781               memberparentdef:=tdef(st.defowner);
2782               exit;
2783             end;
2784           WithSymtable:
2785             begin
2786               if assigned(p1) then
2787                internalerror(2007012002);
2788 
2789               hdef:=tnode(twithsymtable(st).withrefnode).resultdef;
2790               p1:=tnode(twithsymtable(st).withrefnode).getcopy;
2791 
2792               if not(hdef.typ in [objectdef,classrefdef]) then
2793                 exit;
2794 
2795               if (hdef.typ=classrefdef) then
2796                 hdef:=tclassrefdef(hdef).pointeddef;
2797               memberparentdef:=hdef;
2798             end;
2799           else
2800             result:=false;
2801         end;
2802       end;
2803 
2804   {$maxfpuregisters 0}
2805 
factornull2806     function factor(getaddr:boolean;flags:texprflags) : tnode;
2807 
2808          {---------------------------------------------
2809                          Factor_read_id
2810          ---------------------------------------------}
2811 
2812        procedure factor_read_id(out p1:tnode;out again:boolean);
2813 
findwithsymtablenull2814          function findwithsymtable : boolean;
2815            var
2816              hp : psymtablestackitem;
2817            begin
2818              result:=true;
2819              hp:=symtablestack.stack;
2820              while assigned(hp) do
2821                begin
2822                  if hp^.symtable.symtabletype=withsymtable then
2823                    exit;
2824                  hp:=hp^.next;
2825                end;
2826              result:=false;
2827            end;
2828 
2829          var
2830            srsym: tsym;
2831            srsymtable: TSymtable;
2832            hdef: tdef;
2833            pd: tprocdef;
2834            orgstoredpattern,
2835            storedpattern: string;
2836            callflags: tcallnodeflags;
2837            t : ttoken;
2838            wasgenericdummy,
2839            allowspecialize,
2840            isspecialize,
2841            unit_found, tmpgetaddr: boolean;
2842            dummypos,
2843            tokenpos: tfileposinfo;
2844            spezcontext : tspecializationcontext;
2845          begin
2846            { allow post fix operators }
2847            again:=true;
2848 
2849            { preinitalize tokenpos }
2850            tokenpos:=current_filepos;
2851            p1:=nil;
2852            spezcontext:=nil;
2853 
2854            { avoid warning }
2855            fillchar(dummypos,sizeof(dummypos),0);
2856 
2857            allowspecialize:=not (m_delphi in current_settings.modeswitches) and
2858                             not (ef_had_specialize in flags) and
2859                             (block_type in inline_specialization_block_types);
2860            if allowspecialize and (token=_ID) and (idtoken=_SPECIALIZE) then
2861              begin
2862                consume(_ID);
2863                isspecialize:=true;
2864              end
2865            else
2866              isspecialize:=ef_had_specialize in flags;
2867 
2868            { first check for identifier }
2869            if token<>_ID then
2870              begin
2871                srsym:=generrorsym;
2872                srsymtable:=nil;
2873                consume(_ID);
2874                unit_found:=false;
2875              end
2876            else
2877              begin
2878                if ef_type_only in flags then
2879                  searchsym_type(pattern,srsym,srsymtable)
2880                else
2881                  searchsym(pattern,srsym,srsymtable);
2882                { handle unit specification like System.Writeln }
2883                if not isspecialize then
2884                  unit_found:=try_consume_unitsym(srsym,srsymtable,t,true,allowspecialize,isspecialize,pattern)
2885                else
2886                  begin
2887                    unit_found:=false;
2888                    t:=_ID;
2889                  end;
2890                storedpattern:=pattern;
2891                orgstoredpattern:=orgpattern;
2892                { store the position of the token before consuming it }
2893                tokenpos:=current_filepos;
2894                consume(t);
2895                { named parameter support }
2896                found_arg_name:=false;
2897 
2898                if not(unit_found) and
2899                    not isspecialize and
2900                   named_args_allowed and
2901                   (token=_ASSIGNMENT) then
2902                   begin
2903                     found_arg_name:=true;
2904                     p1:=cstringconstnode.createstr(storedpattern);
2905                     consume(_ASSIGNMENT);
2906                     exit;
2907                   end;
2908 
2909                if isspecialize then
2910                  begin
2911                    if not assigned(srsym) then
2912                      begin
2913                        identifier_not_found(orgstoredpattern,tokenpos);
2914                        srsym:=generrorsym;
2915                        srsymtable:=nil;
2916                      end
2917                    else
2918                      begin
2919                        {$push}
2920                        {$warn 5036 off}
2921                        hdef:=generate_specialization_phase1(spezcontext,nil,nil,orgstoredpattern,dummypos);
2922                        {$pop}
2923                        if hdef=generrordef then
2924                          begin
2925                            spezcontext.free;
2926                            spezcontext:=nil;
2927                            srsym:=generrorsym;
2928                            srsymtable:=nil;
2929                          end
2930                        else
2931                          begin
2932                            if hdef.typ in [objectdef,recorddef,procvardef,arraydef] then
2933                              begin
2934                                hdef:=generate_specialization_phase2(spezcontext,tstoreddef(hdef),false,'');
2935                                spezcontext.free;
2936                                spezcontext:=nil;
2937                                if hdef<>generrordef then
2938                                  begin
2939                                    srsym:=hdef.typesym;
2940                                    srsymtable:=srsym.owner;
2941                                  end
2942                                else
2943                                  begin
2944                                    srsym:=generrorsym;
2945                                    srsymtable:=nil;
2946                                  end;
2947                              end
2948                            else
2949                              if hdef.typ=procdef then
2950                                begin
2951                                  if block_type<>bt_body then
2952                                    begin
2953                                      message(parser_e_illegal_expression);
2954                                      srsym:=generrorsym;
2955                                      srsymtable:=nil;
2956                                    end
2957                                  else
2958                                    begin
2959                                      srsym:=tprocdef(hdef).procsym;
2960                                      if assigned(spezcontext.symtable) then
2961                                        srsymtable:=spezcontext.symtable
2962                                      else
2963                                        srsymtable:=srsym.owner;
2964                                    end;
2965                                end
2966                              else
2967                                internalerror(2015061204);
2968                          end;
2969                      end;
2970                  end;
2971 
2972                wasgenericdummy:=false;
2973                if assigned(srsym) and
2974                    (sp_generic_dummy in srsym.symoptions) and
2975                    (srsym.typ=typesym) and
2976                    (
2977                      (
2978                        (m_delphi in current_settings.modeswitches) and
2979                        not (token in [_LT, _LSHARPBRACKET]) and
2980                        (ttypesym(srsym).typedef.typ=undefineddef)
2981                      )
2982                      or
2983                      (
2984                        not (m_delphi in current_settings.modeswitches) and
2985                        not isspecialize and
2986                        (
2987                          not parse_generic or
2988                          not (
2989                            assigned(current_structdef) and
2990                            assigned(get_generic_in_hierarchy_by_name(srsym,current_structdef))
2991                          )
2992                        )
2993                      )
2994                    ) then
2995                  begin
2996                    srsym:=resolve_generic_dummysym(srsym.name);
2997                    if assigned(srsym) then
2998                      srsymtable:=srsym.owner
2999                    else
3000                      begin
3001                        srsymtable:=nil;
3002                        wasgenericdummy:=true;
3003                      end;
3004                  end;
3005 
3006                { check hints, but only if it isn't a potential generic symbol;
3007                  that is checked in sub_expr if it isn't a generic }
3008                if assigned(srsym) and
3009                    not (
3010                      (srsym.typ=typesym) and
3011                      (
3012                        (ttypesym(srsym).typedef.typ in [recorddef,objectdef,arraydef,procvardef,undefineddef]) or
3013                        (
3014                          (ttypesym(srsym).typedef.typ=errordef) and
3015                          (sp_generic_dummy in srsym.symoptions)
3016                        )
3017                      ) and
3018                      not (sp_generic_para in srsym.symoptions) and
3019                      (token in [_LT, _LSHARPBRACKET])
3020                    ) then
3021                  check_hints(srsym,srsym.symoptions,srsym.deprecatedmsg);
3022 
3023                { if nothing found give error and return errorsym }
3024                if not assigned(srsym) or
3025                    { is this a generic dummy symbol? }
3026                    ((srsym.typ=typesym) and
3027                    assigned(ttypesym(srsym).typedef) and
3028                    (ttypesym(srsym).typedef.typ=undefineddef) and
3029                    not (sp_generic_para in srsym.symoptions) and
3030                    not (token in [_LT, _LSHARPBRACKET]) and
3031                    not (
3032                      { in non-Delphi modes the generic class' name without a
3033                        "specialization" or "<T>" may be used to identify the
3034                        current class }
3035                      (sp_generic_dummy in srsym.symoptions) and
3036                      assigned(current_structdef) and
3037                      (df_generic in current_structdef.defoptions) and
3038                      not (m_delphi in current_settings.modeswitches) and
3039                      assigned(get_generic_in_hierarchy_by_name(srsym,current_structdef))
3040                    )) and
3041                    { it could be a rename of a generic para }
3042                    { Note: if this generates false positives we'll need to
3043                            include a "basesym" to tsym to track the original
3044                            symbol }
3045                    not (sp_explicitrename in srsym.symoptions) then
3046                  begin
3047                    { if a generic is parsed and when we are inside an with block,
3048                      a symbol might not be defined }
3049                    if assigned(current_procinfo) and (df_generic in current_procinfo.procdef.defoptions) and
3050                       findwithsymtable then
3051                      begin
3052                        { create dummy symbol, it will be freed later on }
3053                        srsym:=tstoredsym.create(undefinedsym,'$undefinedsym');
3054                        srsymtable:=nil;
3055                      end
3056                    else
3057                      begin
3058                        if wasgenericdummy then
3059                          messagepos(tokenpos,parser_e_no_generics_as_types)
3060                        else
3061                          identifier_not_found(orgstoredpattern,tokenpos);
3062                        srsym:=generrorsym;
3063                        srsymtable:=nil;
3064                      end;
3065                  end;
3066              end;
3067 
3068            { Access to funcret or need to call the function? }
3069            if (srsym.typ in [absolutevarsym,localvarsym,paravarsym]) and
3070               (vo_is_funcret in tabstractvarsym(srsym).varoptions) and
3071               { result(x) is not allowed }
3072               not(vo_is_result in tabstractvarsym(srsym).varoptions) and
3073               (
3074                (token=_LKLAMMER) or
3075                (
3076                 (([m_tp7,m_delphi,m_mac,m_iso,m_extpas] * current_settings.modeswitches) <> []) and
3077                 (afterassignment or in_args)
3078                )
3079               ) then
3080             begin
3081               hdef:=tdef(srsym.owner.defowner);
3082               if assigned(hdef) and
3083                  (hdef.typ=procdef) then
3084                 srsym:=tprocdef(hdef).procsym
3085               else
3086                 begin
3087                   Message(parser_e_illegal_expression);
3088                   srsym:=generrorsym;
3089                 end;
3090               srsymtable:=srsym.owner;
3091             end;
3092 
3093             begin
3094               case srsym.typ of
3095                 absolutevarsym :
3096                   begin
3097                     if (tabsolutevarsym(srsym).abstyp=tovar) then
3098                       begin
3099                         p1:=nil;
3100                         propaccesslist_to_node(p1,nil,tabsolutevarsym(srsym).ref);
3101                         p1:=ctypeconvnode.create(p1,tabsolutevarsym(srsym).vardef);
3102                         include(p1.flags,nf_absolute);
3103                       end
3104                     else
3105                       p1:=cloadnode.create(srsym,srsymtable);
3106                   end;
3107 
3108                 staticvarsym,
3109                 localvarsym,
3110                 paravarsym,
3111                 fieldvarsym :
3112                   begin
3113                     { check if we are reading a field of an object/class/   }
3114                     { record. is_member_read() will deal with withsymtables }
3115                     { if needed.                                            }
3116                     p1:=nil;
3117                     if is_member_read(srsym,srsymtable,p1,hdef) then
3118                       begin
3119                         { if the field was originally found in an     }
3120                         { objectsymtable, it means it's part of self  }
3121                         { if only method from which it was called is  }
3122                         { not class static                            }
3123                         if (srsymtable.symtabletype in [ObjectSymtable,recordsymtable]) then
3124                           { if we are accessing a owner procsym from the nested }
3125                           { class we need to call it as a class member          }
3126                           if assigned(current_structdef) and
3127                               (((current_structdef<>hdef) and is_owned_by(current_structdef,hdef)) or
3128                                (sp_static in srsym.symoptions)) then
3129                             if srsymtable.symtabletype=recordsymtable then
3130                               p1:=ctypenode.create(hdef)
3131                             else
3132                               p1:=cloadvmtaddrnode.create(ctypenode.create(hdef))
3133                           else
3134                             begin
3135                               if assigned(current_procinfo) then
3136                                 begin
3137                                   pd:=current_procinfo.get_normal_proc.procdef;
3138                                   if assigned(pd) and pd.no_self_node then
3139                                     p1:=cloadvmtaddrnode.create(ctypenode.create(pd.struct))
3140                                   else
3141                                     p1:=load_self_node;
3142                                 end
3143                               else
3144                                 p1:=load_self_node;
3145                             end;
3146                         { now, if the field itself is part of an objectsymtab }
3147                         { (it can be even if it was found in a withsymtable,  }
3148                         {  e.g., "with classinstance do field := 5"), then    }
3149                         { let do_member_read handle it                        }
3150                         if (srsym.owner.symtabletype in [ObjectSymtable,recordsymtable]) then
3151                           do_member_read(tabstractrecorddef(hdef),getaddr,srsym,p1,again,[],nil)
3152                         else
3153                           { otherwise it's a regular record subscript }
3154                           p1:=csubscriptnode.create(srsym,p1);
3155                       end
3156                     else
3157                       { regular non-field load }
3158                       p1:=cloadnode.create(srsym,srsymtable);
3159                   end;
3160 
3161                 syssym :
3162                   begin
3163                     p1:=statement_syssym(tsyssym(srsym).number);
3164                   end;
3165 
3166                 typesym :
3167                   begin
3168                     hdef:=ttypesym(srsym).typedef;
3169                     if not assigned(hdef) then
3170                      begin
3171                        again:=false;
3172                      end
3173                     else
3174                      begin
3175                        if (m_delphi in current_settings.modeswitches) and
3176                            (sp_generic_dummy in srsym.symoptions) and
3177                            (token in [_LT,_LSHARPBRACKET]) then
3178                          begin
3179                            if block_type in [bt_type,bt_const_type,bt_var_type] then
3180                              begin
3181                                if not handle_specialize_inline_specialization(srsym,srsymtable,spezcontext) or (srsym.typ=procsym) then
3182                                  begin
3183                                    spezcontext.free;
3184                                    p1:=cerrornode.create;
3185                                    if try_to_consume(_LKLAMMER) then
3186                                     begin
3187                                       parse_paras(false,false,_RKLAMMER);
3188                                       consume(_RKLAMMER);
3189                                     end;
3190                                  end
3191                                else
3192                                  begin
3193                                    if srsym.typ<>typesym then
3194                                      internalerror(2015071705);
3195                                    hdef:=ttypesym(srsym).typedef;
3196                                    p1:=handle_factor_typenode(hdef,getaddr,again,srsym,ef_type_only in flags);
3197                                  end;
3198                              end
3199                            else
3200                              p1:=cspecializenode.create(nil,getaddr,srsym)
3201                          end
3202                        else
3203                          begin
3204                            { We need to know if this unit uses Variants }
3205                            if ((hdef=cvarianttype) or (hdef=colevarianttype)) and
3206                               not(cs_compilesystem in current_settings.moduleswitches) then
3207                              current_module.flags:=current_module.flags or uf_uses_variants;
3208                            p1:=handle_factor_typenode(hdef,getaddr,again,srsym,ef_type_only in flags);
3209                          end;
3210                      end;
3211                   end;
3212 
3213                 enumsym :
3214                   begin
3215                     p1:=genenumnode(tenumsym(srsym));
3216                   end;
3217 
3218                 constsym :
3219                   begin
3220                     if tconstsym(srsym).consttyp=constresourcestring then
3221                       begin
3222                         p1:=cloadnode.create(srsym,srsymtable);
3223                         do_typecheckpass(p1);
3224                         p1.resultdef:=getansistringdef;
3225                       end
3226                     else
3227                       p1:=genconstsymtree(tconstsym(srsym));
3228                   end;
3229 
3230                 procsym :
3231                   begin
3232                     p1:=nil;
3233                     { check if it's a method/class method }
3234                     if is_member_read(srsym,srsymtable,p1,hdef) then
3235                       begin
3236                         { if we are accessing a owner procsym from the nested }
3237                         { class we need to call it as a class member          }
3238                         if (srsymtable.symtabletype in [ObjectSymtable,recordsymtable]) and
3239                           assigned(current_structdef) and (current_structdef<>hdef) and is_owned_by(current_structdef,hdef) then
3240                           p1:=cloadvmtaddrnode.create(ctypenode.create(hdef));
3241                         { not srsymtable.symtabletype since that can be }
3242                         { withsymtable as well                          }
3243                         if (srsym.owner.symtabletype in [ObjectSymtable,recordsymtable]) then
3244                           begin
3245                             do_member_read(tabstractrecorddef(hdef),getaddr,srsym,p1,again,[],spezcontext);
3246                             spezcontext:=nil;
3247                           end
3248                         else
3249                           { no procsyms in records (yet) }
3250                           internalerror(2007012006);
3251                       end
3252                     else
3253                       begin
3254                         { regular procedure/function call }
3255                         if not unit_found then
3256                           callflags:=[]
3257                         else
3258                           callflags:=[cnf_unit_specified];
3259                         { TP7 uglyness: @proc^ is parsed as (@proc)^,
3260                           but @notproc^ is parsed as @(notproc^) }
3261                         if m_tp_procvar in current_settings.modeswitches then
3262                           tmpgetaddr:=getaddr and not(token in [_POINT,_LECKKLAMMER])
3263                         else
3264                           tmpgetaddr:=getaddr and not(token in [_CARET,_POINT,_LECKKLAMMER]);
3265                         do_proc_call(srsym,srsymtable,nil,tmpgetaddr,
3266                                      again,p1,callflags,spezcontext);
3267                         spezcontext:=nil;
3268                       end;
3269                   end;
3270 
3271                 propertysym :
3272                   begin
3273                     p1:=nil;
3274                     { property of a class/object? }
3275                     if is_member_read(srsym,srsymtable,p1,hdef) then
3276                       begin
3277                         if (srsymtable.symtabletype in [ObjectSymtable,recordsymtable]) then
3278                           { if we are accessing a owner procsym from the nested }
3279                           { class or from a static class method we need to call }
3280                           { it as a class member                                }
3281                           if (assigned(current_structdef) and (current_structdef<>hdef) and is_owned_by(current_structdef,hdef)) or
3282                              (assigned(current_procinfo) and current_procinfo.get_normal_proc.procdef.no_self_node) then
3283                             begin
3284                               p1:=ctypenode.create(hdef);
3285                               if not is_record(hdef) then
3286                                 p1:=cloadvmtaddrnode.create(p1);
3287                             end
3288                           else
3289                             p1:=load_self_node;
3290                         { not srsymtable.symtabletype since that can be }
3291                         { withsymtable as well                          }
3292                         if (srsym.owner.symtabletype in [ObjectSymtable,recordsymtable]) then
3293                           do_member_read(tabstractrecorddef(hdef),getaddr,srsym,p1,again,[],nil)
3294                         else
3295                           { no propertysyms in records (yet) }
3296                           internalerror(2009111510);
3297                       end
3298                     else
3299                     { no method pointer }
3300                       begin
3301                         handle_propertysym(tpropertysym(srsym),srsymtable,p1);
3302                       end;
3303                   end;
3304 
3305                 labelsym :
3306                   begin
3307                     { Support @label }
3308                     if getaddr then
3309                       begin
3310                         if srsym.owner<>current_procinfo.procdef.localst then
3311                           CGMessage(parser_e_label_outside_proc);
3312                         p1:=cloadnode.create(srsym,srsym.owner)
3313                       end
3314                     else
3315                       begin
3316                         consume(_COLON);
3317                         if tlabelsym(srsym).defined then
3318                           Message(sym_e_label_already_defined);
3319                         if symtablestack.top.symtablelevel<>srsymtable.symtablelevel then
3320                           begin
3321                             tlabelsym(srsym).nonlocal:=true;
3322                             exclude(current_procinfo.procdef.procoptions,po_inline);
3323                           end;
3324                         if tlabelsym(srsym).nonlocal and
3325                           (current_procinfo.procdef.proctypeoption in [potype_unitinit,potype_unitfinalize]) then
3326                           Message(sym_e_interprocgoto_into_init_final_code_not_allowed);
3327                         tlabelsym(srsym).defined:=true;
3328                         p1:=clabelnode.create(nil,tlabelsym(srsym));
3329                         tlabelsym(srsym).code:=p1;
3330                       end;
3331                   end;
3332 
3333                 undefinedsym :
3334                   begin
3335                     p1:=cnothingnode.Create;
3336                     p1.resultdef:=cundefineddef.create(true);
3337                     { clean up previously created dummy symbol }
3338                     srsym.free;
3339                   end;
3340 
3341                 errorsym :
3342                   begin
3343                     p1:=cerrornode.create;
3344                     if try_to_consume(_LKLAMMER) then
3345                      begin
3346                        parse_paras(false,false,_RKLAMMER);
3347                        consume(_RKLAMMER);
3348                      end;
3349                   end;
3350 
3351                 else
3352                   begin
3353                     p1:=cerrornode.create;
3354                     Message(parser_e_illegal_expression);
3355                   end;
3356               end; { end case }
3357 
3358               if assigned(spezcontext) then
3359                 internalerror(2015061207);
3360 
3361               if assigned(p1) and (p1.nodetype<>errorn) then
3362                 p1.fileinfo:=tokenpos;
3363             end;
3364          end;
3365 
3366          {---------------------------------------------
3367                          Factor_Read_Set
3368          ---------------------------------------------}
3369 
3370          { Read a set between [] }
factor_read_setnull3371          function factor_read_set:tnode;
3372          var
3373            p1,p2 : tnode;
3374            lastp,
3375            buildp : tarrayconstructornode;
3376          begin
3377            buildp:=nil;
3378            lastp:=nil;
3379          { be sure that a least one arrayconstructn is used, also for an
3380            empty [] }
3381            if token=_RECKKLAMMER then
3382              buildp:=carrayconstructornode.create(nil,buildp)
3383            else
3384             repeat
3385               p1:=comp_expr([ef_accept_equal]);
3386               if try_to_consume(_POINTPOINT) then
3387                 begin
3388                   p2:=comp_expr([ef_accept_equal]);
3389                   p1:=carrayconstructorrangenode.create(p1,p2);
3390                 end;
3391                { insert at the end of the tree, to get the correct order }
3392              if not assigned(buildp) then
3393                begin
3394                  buildp:=carrayconstructornode.create(p1,nil);
3395                  lastp:=buildp;
3396                end
3397              else
3398                begin
3399                  lastp.right:=carrayconstructornode.create(p1,nil);
3400                  lastp:=tarrayconstructornode(lastp.right);
3401                end;
3402            { there could be more elements }
3403            until not try_to_consume(_COMMA);
3404            buildp.allow_array_constructor:=block_type in [bt_body,bt_except];
3405            factor_read_set:=buildp;
3406          end;
3407 
can_load_self_nodenull3408          function can_load_self_node: boolean;
3409          begin
3410            result:=false;
3411            if (block_type in [bt_const,bt_type,bt_const_type,bt_var_type]) or
3412               not assigned(current_structdef) or
3413               not assigned(current_procinfo) then
3414              exit;
3415            result:=not current_procinfo.get_normal_proc.procdef.no_self_node;
3416          end;
3417 
3418 
3419       {---------------------------------------------
3420                       Factor (Main)
3421       ---------------------------------------------}
3422 
3423       var
3424          l          : longint;
3425          ic         : int64;
3426          qc         : qword;
3427          p1         : tnode;
3428          code       : integer;
3429          srsym      : tsym;
3430          srsymtable : TSymtable;
3431          pd         : tprocdef;
3432          hclassdef  : tobjectdef;
3433          d          : bestreal;
3434          hs,hsorg   : string;
3435          hdef       : tdef;
3436          filepos    : tfileposinfo;
3437          callflags  : tcallnodeflags;
3438          idstr      : tidstring;
3439          spezcontext : tspecializationcontext;
3440          isspecialize,
3441          mightbegeneric,
3442          useself,
3443          dopostfix,
3444          again,
3445          updatefpos,
3446          nodechanged  : boolean;
3447       begin
3448         { can't keep a copy of p1 and compare pointers afterwards, because
3449           p1 may be freed and reallocated in the same place!  }
3450         dopostfix:=true;
3451         updatefpos:=false;
3452         p1:=nil;
3453         filepos:=current_tokenpos;
3454         again:=false;
3455         pd:=nil;
3456         isspecialize:=false;
3457         if token=_ID then
3458          begin
3459            again:=true;
3460            { Handle references to self }
3461            if (idtoken=_SELF) and can_load_self_node then
3462              begin
3463                p1:=load_self_node;
3464                consume(_ID);
3465                again:=true;
3466              end
3467            else
3468              factor_read_id(p1,again);
3469 
3470            if assigned(p1) then
3471             begin
3472               { factor_read_id will set the filepos to after the id,
3473                 and in case of _SELF the filepos will already be the
3474                 same as filepos (so setting it again doesn't hurt).  }
3475               p1.fileinfo:=filepos;
3476               filepos:=current_tokenpos;
3477             end;
3478            { handle post fix operators }
3479            if (p1.nodetype=specializen) then
3480              { post fix operators are handled after specialization }
3481              dopostfix:=false
3482            else
3483              if (m_delphi in current_settings.modeswitches) and
3484                  (block_type=bt_body) and
3485                  (token in [_LT,_LSHARPBRACKET]) then
3486                begin
3487                  if p1.nodetype=typen then
3488                    idstr:=ttypenode(p1).typesym.name
3489                  else
3490                    if (p1.nodetype=loadvmtaddrn) and
3491                        (tloadvmtaddrnode(p1).left.nodetype=typen) then
3492                      idstr:=ttypenode(tloadvmtaddrnode(p1).left).typesym.name
3493                    else
3494                      if (p1.nodetype=loadn) then
3495                        idstr:=tloadnode(p1).symtableentry.name
3496                      else
3497                        idstr:='';
3498                  { if this is the case then the postfix handling is done in
3499                    sub_expr if necessary }
3500                  dopostfix:=not could_be_generic(idstr);
3501                end;
3502            { TP7 uglyness: @proc^ is parsed as (@proc)^, but @notproc^ is parsed
3503              as @(notproc^) }
3504            if (m_tp_procvar in current_settings.modeswitches) and (token=_CARET) and
3505               getaddr and (p1.nodetype=loadn) and (tloadnode(p1).symtableentry.typ=procsym) then
3506              dopostfix:=false;
3507            { maybe an additional parameter instead of misusing hadspezialize? }
3508            if dopostfix and not (ef_had_specialize in flags) then
3509              updatefpos:=postfixoperators(p1,again,getaddr);
3510          end
3511         else
3512          begin
3513            updatefpos:=true;
3514            case token of
3515              _RETURN :
3516                 begin
3517                   consume(_RETURN);
3518                   p1:=nil;
3519                   if not(token in [_SEMICOLON,_ELSE,_END]) then
3520                     begin
3521                       p1:=comp_expr([ef_accept_equal]);
3522                       if not assigned(current_procinfo) or
3523                          (current_procinfo.procdef.proctypeoption in [potype_constructor,potype_destructor]) or
3524                          is_void(current_procinfo.procdef.returndef) then
3525                         begin
3526                           Message(parser_e_void_function);
3527                           { recovery }
3528                           p1.free;
3529                           p1:=nil;
3530                         end;
3531                     end;
3532                   p1 := cexitnode.create(p1);
3533                 end;
3534              _INHERITED :
3535                begin
3536                  again:=true;
3537                  consume(_INHERITED);
3538                  if assigned(current_procinfo) and
3539                     assigned(current_structdef) and
3540                     ((current_structdef.typ=objectdef) or
3541                      ((target_info.system in systems_jvm) and
3542                       (current_structdef.typ=recorddef)))then
3543                   begin
3544                     { for record helpers in mode Delphi "inherited" is not
3545                       allowed }
3546                     if is_objectpascal_helper(current_structdef) and
3547                         (m_delphi in current_settings.modeswitches) and
3548                         (tobjectdef(current_structdef).helpertype=ht_record) then
3549                       Message(parser_e_inherited_not_in_record);
3550                     if (current_structdef.typ=objectdef) then
3551                       begin
3552                         hclassdef:=tobjectdef(current_structdef).childof;
3553                         { Objective-C categories *replace* methods in the class
3554                           they extend, or add methods to it. So calling an
3555                           inherited method always calls the method inherited from
3556                           the parent of the extended class }
3557                         if is_objccategory(current_structdef) then
3558                           hclassdef:=hclassdef.childof;
3559                       end
3560                     else if target_info.system in systems_jvm then
3561                       hclassdef:=java_fpcbaserecordtype
3562                     else
3563                       internalerror(2012012401);
3564                     spezcontext:=nil;
3565                     { if inherited; only then we need the method with
3566                       the same name }
3567                     if token <> _ID then
3568                      begin
3569                        hs:=current_procinfo.procdef.procsym.name;
3570                        hsorg:=current_procinfo.procdef.procsym.realname;
3571                        anon_inherited:=true;
3572                        { For message methods we need to search using the message
3573                          number or string }
3574                        pd:=tprocdef(tprocsym(current_procinfo.procdef.procsym).ProcdefList[0]);
3575                        srdef:=nil;
3576                        if (po_msgint in pd.procoptions) then
3577                          searchsym_in_class_by_msgint(hclassdef,pd.messageinf.i,srdef,srsym,srsymtable)
3578                        else
3579                         if (po_msgstr in pd.procoptions) then
3580                           searchsym_in_class_by_msgstr(hclassdef,pd.messageinf.str^,srsym,srsymtable)
3581                        else
3582                        { helpers have their own ways of dealing with inherited }
3583                        if is_objectpascal_helper(current_structdef) then
3584                          searchsym_in_helper(tobjectdef(current_structdef),tobjectdef(current_structdef),hs,srsym,srsymtable,[ssf_has_inherited])
3585                        else
3586                          searchsym_in_class(hclassdef,current_structdef,hs,srsym,srsymtable,[ssf_search_helper]);
3587                      end
3588                     else
3589                      begin
3590                        if not (m_delphi in current_settings.modeswitches) and
3591                            (block_type in inline_specialization_block_types) and
3592                            (token=_ID) and
3593                            (idtoken=_SPECIALIZE) then
3594                          begin
3595                            consume(_ID);
3596                            if token<>_ID then
3597                              message(parser_e_methode_id_expected);
3598                            isspecialize:=true;
3599                          end
3600                        else
3601                          isspecialize:=false;
3602                        hs:=pattern;
3603                        hsorg:=orgpattern;
3604                        consume(_ID);
3605                        anon_inherited:=false;
3606                        { helpers have their own ways of dealing with inherited }
3607                        if is_objectpascal_helper(current_structdef) then
3608                          searchsym_in_helper(tobjectdef(current_structdef),tobjectdef(current_structdef),hs,srsym,srsymtable,[ssf_has_inherited])
3609                        else
3610                          searchsym_in_class(hclassdef,current_structdef,hs,srsym,srsymtable,[ssf_search_helper]);
3611                        if isspecialize and assigned(srsym) then
3612                          begin
3613                            if not handle_specialize_inline_specialization(srsym,srsymtable,spezcontext) then
3614                              srsym:=nil;
3615                          end;
3616                      end;
3617                     if assigned(srsym) then
3618                      begin
3619                        mightbegeneric:=(m_delphi in current_settings.modeswitches) and
3620                                          (token in [_LT,_LSHARPBRACKET]) and
3621                                          (sp_generic_dummy in srsym.symoptions);
3622                        { load the procdef from the inherited class and
3623                          not from self }
3624                        case srsym.typ of
3625                          typesym,
3626                          procsym:
3627                            begin
3628                              { typesym is only a valid choice if we're dealing
3629                                with a potential generic }
3630                              if (srsym.typ=typesym) and not mightbegeneric then
3631                                begin
3632                                  Message(parser_e_methode_id_expected);
3633                                  p1:=cerrornode.create;
3634                                end
3635                              else
3636                                begin
3637                                  useself:=false;
3638                                  if is_objectpascal_helper(current_structdef) then
3639                                    begin
3640                                      { for a helper load the procdef either from the
3641                                        extended type, from the parent helper or from
3642                                        the extended type of the parent helper
3643                                        depending on the def the found symbol belongs
3644                                        to }
3645                                      if (srsym.Owner.defowner.typ=objectdef) and
3646                                          is_objectpascal_helper(tobjectdef(srsym.Owner.defowner)) then
3647                                        if def_is_related(current_structdef,tdef(srsym.Owner.defowner)) and
3648                                            assigned(tobjectdef(current_structdef).childof) then
3649                                          hdef:=tobjectdef(current_structdef).childof
3650                                        else
3651                                          begin
3652                                            hdef:=tobjectdef(srsym.Owner.defowner).extendeddef;
3653                                            useself:=true;
3654                                          end
3655                                      else
3656                                        begin
3657                                          hdef:=tdef(srsym.Owner.defowner);
3658                                          useself:=true;
3659                                        end;
3660                                    end
3661                                  else
3662                                    hdef:=hclassdef;
3663                                  if (po_classmethod in current_procinfo.procdef.procoptions) or
3664                                     (po_staticmethod in current_procinfo.procdef.procoptions) then
3665                                    hdef:=cclassrefdef.create(hdef);
3666                                  if useself then
3667                                    begin
3668                                      p1:=ctypeconvnode.create_internal(load_self_node,hdef);
3669                                    end
3670                                  else
3671                                    begin
3672                                      p1:=ctypenode.create(hdef);
3673                                      { we need to allow helpers here }
3674                                      ttypenode(p1).helperallowed:=true;
3675                                    end;
3676                                end;
3677                            end;
3678                          propertysym:
3679                            ;
3680                          else
3681                            begin
3682                              Message(parser_e_methode_id_expected);
3683                              p1:=cerrornode.create;
3684                            end;
3685                        end;
3686                        if mightbegeneric then
3687                          begin
3688                            p1:=cspecializenode.create_inherited(p1,getaddr,srsym,hclassdef);
3689                          end
3690                        else
3691                          begin
3692                            if not isspecialize then
3693                              check_hints(srsym,srsym.symoptions,srsym.deprecatedmsg);
3694                            callflags:=[cnf_inherited];
3695                            include(current_procinfo.flags,pi_has_inherited);
3696                            if anon_inherited then
3697                              include(callflags,cnf_anon_inherited);
3698                            do_member_read(hclassdef,getaddr,srsym,p1,again,callflags,spezcontext);
3699                          end;
3700                        if p1.nodetype=errorn then
3701                          spezcontext.free;
3702                      end
3703                     else
3704                      begin
3705                        if anon_inherited then
3706                         begin
3707                           { For message methods we need to call DefaultHandler }
3708                           if (po_msgint in pd.procoptions) or
3709                              (po_msgstr in pd.procoptions) then
3710                             begin
3711                               searchsym_in_class(hclassdef,hclassdef,'DEFAULTHANDLER',srsym,srsymtable,[ssf_search_helper]);
3712                               if not assigned(srsym) or
3713                                  (srsym.typ<>procsym) then
3714                                 internalerror(200303171);
3715                               p1:=nil;
3716                               do_proc_call(srsym,srsym.owner,hclassdef,false,again,p1,[],nil);
3717                             end
3718                           else
3719                             begin
3720                               { we need to ignore the inherited; }
3721                               p1:=cnothingnode.create;
3722                             end;
3723                         end
3724                        else
3725                         begin
3726                           Message1(sym_e_id_no_member,hsorg);
3727                           p1:=cerrornode.create;
3728                         end;
3729                        again:=false;
3730                      end;
3731                     { turn auto inheriting off }
3732                     anon_inherited:=false;
3733                   end
3734                  else
3735                    begin
3736                      { in case of records we use a more clear error message }
3737                      if assigned(current_structdef) and
3738                          (current_structdef.typ=recorddef) then
3739                        Message(parser_e_inherited_not_in_record)
3740                      else
3741                        Message(parser_e_generic_methods_only_in_methods);
3742                      again:=false;
3743                      p1:=cerrornode.create;
3744                    end;
3745                  if p1.nodetype<>specializen then
3746                    postfixoperators(p1,again,getaddr);
3747                end;
3748 
3749              _INTCONST :
3750                begin
3751                  {Try first wether the value fits in an int64.}
3752                  val(pattern,ic,code);
3753                  if code=0 then
3754                    begin
3755                       consume(_INTCONST);
3756                       int_to_type(ic,hdef);
3757                       p1:=cordconstnode.create(ic,hdef,true);
3758                    end
3759                  else
3760                    begin
3761                      { try qword next }
3762                      val(pattern,qc,code);
3763                      if code=0 then
3764                        begin
3765                           consume(_INTCONST);
3766                           int_to_type(qc,hdef);
3767                           p1:=cordconstnode.create(qc,hdef,true);
3768                        end;
3769                    end;
3770                  if code<>0 then
3771                    begin
3772                      { finally float }
3773                      val(pattern,d,code);
3774                      if code<>0 then
3775                        begin
3776                           Message(parser_e_invalid_integer);
3777                           consume(_INTCONST);
3778                           l:=1;
3779                           p1:=cordconstnode.create(l,sinttype,true);
3780                        end
3781                      else
3782                        begin
3783                           consume(_INTCONST);
3784                           p1:=crealconstnode.create(d,pbestrealtype^);
3785                        end;
3786                    end
3787                  else
3788                    { the necessary range checking has already been done by val }
3789                    tordconstnode(p1).rangecheck:=false;
3790                  if token=_POINT then
3791                    begin
3792                      again:=true;
3793                      postfixoperators(p1,again,getaddr);
3794                    end;
3795                end;
3796 
3797              _REALNUMBER :
3798                begin
3799                  p1:=real_const_node_from_pattern(pattern);
3800                  consume(_REALNUMBER);
3801                  if token=_POINT then
3802                    begin
3803                      again:=true;
3804                      postfixoperators(p1,again,getaddr);
3805                    end;
3806                end;
3807 
3808              _STRING :
3809                begin
3810                  string_dec(hdef,true);
3811                  { STRING can be also a type cast }
3812                  if try_to_consume(_LKLAMMER) then
3813                   begin
3814                     p1:=comp_expr([ef_accept_equal]);
3815                     consume(_RKLAMMER);
3816                     p1:=ctypeconvnode.create_explicit(p1,hdef);
3817                     { handle postfix operators here e.g. string(a)[10] }
3818                     again:=true;
3819                     postfixoperators(p1,again,getaddr);
3820                   end
3821                  else
3822                    begin
3823                      p1:=ctypenode.create(hdef);
3824                      if token=_POINT then
3825                        begin
3826                          again:=true;
3827                          { handle type helpers here }
3828                          postfixoperators(p1,again,getaddr);
3829                        end;
3830                    end;
3831                end;
3832 
3833              _FILE :
3834                begin
3835                  hdef:=cfiletype;
3836                  consume(_FILE);
3837                  { FILE can be also a type cast }
3838                  if try_to_consume(_LKLAMMER) then
3839                   begin
3840                     p1:=comp_expr([ef_accept_equal]);
3841                     consume(_RKLAMMER);
3842                     p1:=ctypeconvnode.create_explicit(p1,hdef);
3843                     { handle postfix operators here e.g. string(a)[10] }
3844                     again:=true;
3845                     postfixoperators(p1,again,getaddr);
3846                   end
3847                  else
3848                   begin
3849                     p1:=ctypenode.create(hdef);
3850                   end;
3851                end;
3852 
3853              _CSTRING :
3854                begin
3855                  p1:=cstringconstnode.createpchar(ansistring2pchar(cstringpattern),length(cstringpattern),nil);
3856                  consume(_CSTRING);
3857                  if token in postfixoperator_tokens then
3858                    begin
3859                      again:=true;
3860                      postfixoperators(p1,again,getaddr);
3861                    end;
3862                end;
3863 
3864              _CCHAR :
3865                begin
3866                  p1:=cordconstnode.create(ord(pattern[1]),cansichartype,true);
3867                  consume(_CCHAR);
3868                  if token=_POINT then
3869                    begin
3870                      again:=true;
3871                      postfixoperators(p1,again,getaddr);
3872                    end;
3873                end;
3874 
3875              _CWSTRING:
3876                begin
3877                  if getlengthwidestring(patternw)=1 then
3878                    p1:=cordconstnode.create(ord(getcharwidestring(patternw,0)),cwidechartype,true)
3879                  else
3880                    p1:=cstringconstnode.createunistr(patternw);
3881                  consume(_CWSTRING);
3882                  if token in postfixoperator_tokens then
3883                    begin
3884                      again:=true;
3885                      postfixoperators(p1,again,getaddr);
3886                    end;
3887                end;
3888 
3889              _CWCHAR:
3890                begin
3891                  p1:=cordconstnode.create(ord(getcharwidestring(patternw,0)),cwidechartype,true);
3892                  consume(_CWCHAR);
3893                  if token=_POINT then
3894                    begin
3895                      again:=true;
3896                      postfixoperators(p1,again,getaddr);
3897                    end;
3898                end;
3899 
3900              _KLAMMERAFFE :
3901                begin
3902                  consume(_KLAMMERAFFE);
3903                  got_addrn:=true;
3904                  { support both @<x> and @(<x>) }
3905                  if try_to_consume(_LKLAMMER) then
3906                   begin
3907                     p1:=factor(true,[]);
3908                     { inside parentheses a full expression is allowed, see also tests\webtbs\tb27517.pp }
3909                     if token<>_RKLAMMER then
3910                       p1:=sub_expr(opcompare,[ef_accept_equal],p1);
3911                     consume(_RKLAMMER);
3912                   end
3913                  else
3914                   p1:=factor(true,[]);
3915                  if (token in postfixoperator_tokens) and
3916                    { TP7 uglyness: @proc^ is parsed as (@proc)^, but @notproc^
3917                      is parsed as @(notproc^) }
3918                     not
3919                     (
3920                      (m_tp_procvar in current_settings.modeswitches) and
3921                      (token=_CARET) and (p1.nodetype=loadn) and (tloadnode(p1).symtableentry.typ=procsym)
3922                     )
3923                    then
3924                   begin
3925                     again:=true;
3926                     postfixoperators(p1,again,getaddr);
3927                   end;
3928                  got_addrn:=false;
3929                  p1:=caddrnode.create(p1);
3930                  p1.fileinfo:=filepos;
3931                  if cs_typed_addresses in current_settings.localswitches then
3932                    include(taddrnode(p1).addrnodeflags,anf_typedaddr);
3933                  { Store the procvar that we are expecting, the
3934                    addrn will use the information to find the correct
3935                    procdef or it will return an error }
3936                  if assigned(getprocvardef) and
3937                     (taddrnode(p1).left.nodetype = loadn) then
3938                    taddrnode(p1).getprocvardef:=getprocvardef;
3939                  if (token in postfixoperator_tokens) then
3940                   begin
3941                     again:=true;
3942                     postfixoperators(p1,again,getaddr);
3943                   end;
3944                end;
3945 
3946              _LKLAMMER :
3947                begin
3948                  consume(_LKLAMMER);
3949                  p1:=comp_expr([ef_accept_equal]);
3950                  consume(_RKLAMMER);
3951                  { it's not a good solution
3952                    but (a+b)^ makes some problems  }
3953                  if token in postfixoperator_tokens then
3954                   begin
3955                     again:=true;
3956                     postfixoperators(p1,again,getaddr);
3957                   end;
3958                end;
3959 
3960              _LECKKLAMMER :
3961                begin
3962                  consume(_LECKKLAMMER);
3963                  p1:=factor_read_set;
3964                  consume(_RECKKLAMMER);
3965                end;
3966 
3967              _PLUS :
3968                begin
3969                  consume(_PLUS);
3970                  p1:=factor(false,[]);
3971                  p1:=cunaryplusnode.create(p1);
3972                end;
3973 
3974              _MINUS :
3975                begin
3976                  consume(_MINUS);
3977                  if (token = _INTCONST) and not(m_isolike_unary_minus in current_settings.modeswitches) then
3978                     begin
3979                       { ugly hack, but necessary to be able to parse }
3980                       { -9223372036854775808 as int64 (JM)           }
3981                       pattern := '-'+pattern;
3982                       p1:=sub_expr(oppower,[],nil);
3983                       {  -1 ** 4 should be - (1 ** 4) and not
3984                          (-1) ** 4
3985                          This was the reason of tw0869.pp test failure PM }
3986                       if p1.nodetype=starstarn then
3987                         begin
3988                           if tbinarynode(p1).left.nodetype=ordconstn then
3989                             begin
3990                               tordconstnode(tbinarynode(p1).left).value:=-tordconstnode(tbinarynode(p1).left).value;
3991                               p1:=cunaryminusnode.create(p1);
3992                             end
3993                           else if tbinarynode(p1).left.nodetype=realconstn then
3994                             begin
3995                               trealconstnode(tbinarynode(p1).left).value_real:=-trealconstnode(tbinarynode(p1).left).value_real;
3996                               trealconstnode(tbinarynode(p1).left).value_currency:=-trealconstnode(tbinarynode(p1).left).value_currency;
3997                               p1:=cunaryminusnode.create(p1);
3998                             end
3999                           else
4000                             internalerror(20021029);
4001                         end;
4002                     end
4003                  else
4004                    begin
4005                      if m_isolike_unary_minus in current_settings.modeswitches then
4006                        p1:=sub_expr(opmultiply,[],nil)
4007                      else
4008                        p1:=sub_expr(oppower,[],nil);
4009 
4010                      p1:=cunaryminusnode.create(p1);
4011                    end;
4012                end;
4013 
4014              _OP_NOT :
4015                begin
4016                  consume(_OP_NOT);
4017                  p1:=factor(false,[]);
4018                  p1:=cnotnode.create(p1);
4019                end;
4020 
4021              _NIL :
4022                begin
4023                  consume(_NIL);
4024                  p1:=cnilnode.create;
4025                  { It's really ugly code nil^, but delphi allows it }
4026                  if token in [_CARET,_POINT] then
4027                   begin
4028                     again:=true;
4029                     postfixoperators(p1,again,getaddr);
4030                   end;
4031                end;
4032              _OBJCPROTOCOL:
4033                begin
4034                  { The @protocol keyword is used in two ways in Objective-C:
4035                      1) to declare protocols (~ Object Pascal interfaces)
4036                      2) to obtain the metaclass (~ Object Pascal) "class of")
4037                         of a declared protocol
4038                    This code is for handling the second case. Because of 1),
4039                    we cannot simply use a system unit symbol.
4040                  }
4041                  consume(_OBJCPROTOCOL);
4042                  consume(_LKLAMMER);
4043                  p1:=factor(false,[]);
4044                  consume(_RKLAMMER);
4045                  p1:=cinlinenode.create(in_objc_protocol_x,false,p1);
4046                end;
4047 
4048              else
4049                begin
4050                  Message(parser_e_illegal_expression);
4051                  p1:=cerrornode.create;
4052                  { recover }
4053                  consume(token);
4054                end;
4055            end;
4056         end;
4057 
4058         { generate error node if no node is created }
4059         if not assigned(p1) then
4060          begin
4061 {$ifdef EXTDEBUG}
4062            Comment(V_Warning,'factor: p1=nil');
4063 {$endif}
4064            p1:=cerrornode.create;
4065            updatefpos:=true;
4066          end;
4067 
4068         { get the resultdef for the node if nothing stops us }
4069         if (not assigned(p1.resultdef)) and dopostfix then
4070           begin
4071             do_typecheckpass_changed(p1,nodechanged);
4072             updatefpos:=updatefpos or nodechanged;
4073           end;
4074 
4075         if assigned(p1) and
4076            updatefpos then
4077           p1.fileinfo:=filepos;
4078         factor:=p1;
4079       end;
4080   {$maxfpuregisters default}
4081 
4082     procedure post_comp_expr_gendef(var def: tdef);
4083       var
4084         p1 : tnode;
4085         again : boolean;
4086       begin
4087         if not assigned(def) then
4088           internalerror(2011053001);
4089         again:=false;
4090         { handle potential typecasts, etc }
4091         p1:=handle_factor_typenode(def,false,again,nil,false);
4092         { parse postfix operators }
4093         postfixoperators(p1,again,false);
4094         if assigned(p1) and (p1.nodetype=typen) then
4095           def:=ttypenode(p1).typedef
4096         else
4097           def:=generrordef;
4098       end;
4099 
4100 {****************************************************************************
4101                              Sub_Expr
4102 ****************************************************************************}
sub_exprnull4103     function sub_expr(pred_level:Toperator_precedence;flags:texprflags;factornode:tnode):tnode;
4104     {Reads a subexpression while the operators are of the current precedence
4105      level, or any higher level. Replaces the old term, simpl_expr and
4106      simpl2_expr.}
4107 
istypenodenull4108       function istypenode(n:tnode):boolean;inline;
4109       { Checks whether the given node is a type node or a VMT node containing a
4110         typenode. This is used in the code for inline specializations in the
4111         _LT branch below }
4112         begin
4113           result:=assigned(n) and
4114                     (
4115                       (n.nodetype=typen) or
4116                       (
4117                         (n.nodetype=loadvmtaddrn) and
4118                         (tloadvmtaddrnode(n).left.nodetype=typen)
4119                       )
4120                     );
4121         end;
4122 
gettypedefnull4123       function gettypedef(n:tnode):tdef;inline;
4124       { This returns the typedef that belongs to the given typenode or
4125         loadvmtaddrnode. n must not be Nil! }
4126         begin
4127           if n.nodetype=typen then
4128             result:=ttypenode(n).typedef
4129           else
4130             result:=ttypenode(tloadvmtaddrnode(n).left).typedef;
4131         end;
4132 
gettypedefnull4133       function gettypedef(sym:tsym):tdef;inline;
4134         begin
4135           result:=nil;
4136           case sym.typ of
4137             typesym:
4138               result:=ttypesym(sym).typedef;
4139             procsym:
4140               result:=tdef(tprocsym(sym).procdeflist[0]);
4141             else
4142               internalerror(2015092701);
4143           end;
4144         end;
4145 
getgenericsymnull4146       function getgenericsym(n:tnode;out srsym:tsym):boolean;
4147         var
4148           srsymtable : tsymtable;
4149         begin
4150           srsym:=nil;
4151           case n.nodetype of
4152             typen:
4153               srsym:=ttypenode(n).typedef.typesym;
4154             loadvmtaddrn:
4155               srsym:=ttypenode(tloadvmtaddrnode(n).left).typedef.typesym;
4156             loadn:
4157               if not searchsym_with_symoption(tloadnode(n).symtableentry.Name,srsym,srsymtable,sp_generic_dummy) then
4158                 srsym:=nil;
4159             specializen:
4160               srsym:=tspecializenode(n).sym;
4161             { TODO : handle const nodes }
4162           end;
4163           result:=assigned(srsym);
4164         end;
4165 
generate_inline_specializationnull4166       function generate_inline_specialization(gendef:tdef;n:tnode;filepos:tfileposinfo;parseddef:tdef;gensym:tsym;p2:tnode):tnode;
4167         var
4168           again,
4169           getaddr : boolean;
4170           pload : tnode;
4171           spezcontext : tspecializationcontext;
4172           structdef,
4173           inheriteddef : tabstractrecorddef;
4174           callflags : tcallnodeflags;
4175         begin
4176           if n.nodetype=specializen then
4177             begin
4178               getaddr:=tspecializenode(n).getaddr;
4179               pload:=tspecializenode(n).left;
4180               inheriteddef:=tabstractrecorddef(tspecializenode(n).inheriteddef);
4181               tspecializenode(n).left:=nil;
4182             end
4183           else
4184             begin
4185               getaddr:=false;
4186               pload:=nil;
4187               inheriteddef:=nil;
4188             end;
4189 
4190           if assigned(parseddef) and assigned(gensym) and assigned(p2) then
4191             gendef:=generate_specialization_phase1(spezcontext,gendef,parseddef,gensym.realname,p2.fileinfo)
4192           else
4193             gendef:=generate_specialization_phase1(spezcontext,gendef);
4194           case gendef.typ of
4195             errordef:
4196               begin
4197                 spezcontext.free;
4198                 spezcontext:=nil;
4199                 gensym:=generrorsym;
4200               end;
4201             objectdef,
4202             recorddef,
4203             procvardef,
4204             arraydef:
4205               begin
4206                 gendef:=generate_specialization_phase2(spezcontext,tstoreddef(gendef),false,'');
4207                 spezcontext.free;
4208                 spezcontext:=nil;
4209                 gensym:=gendef.typesym;
4210               end;
4211             procdef:
4212               begin
4213                 if block_type<>bt_body then
4214                   begin
4215                     message(parser_e_illegal_expression);
4216                     gensym:=generrorsym;
4217                   end
4218                 else
4219                   begin
4220                     gensym:=tprocdef(gendef).procsym;
4221                   end;
4222               end;
4223             else
4224               internalerror(2015092702);
4225           end;
4226 
4227           { in case of a class or a record the specialized generic
4228             is always a classrefdef }
4229           again:=false;
4230 
4231           if assigned(pload) then
4232             begin
4233               result:=pload;
4234               typecheckpass(result);
4235               structdef:=inheriteddef;
4236               if not assigned(structdef) then
4237                 case result.resultdef.typ of
4238                   objectdef,
4239                   recorddef:
4240                     begin
4241                       structdef:=tabstractrecorddef(result.resultdef);
4242                     end;
4243                   classrefdef:
4244                     begin
4245                       structdef:=tabstractrecorddef(tclassrefdef(result.resultdef).pointeddef);
4246                     end;
4247                   else
4248                     internalerror(2015092703);
4249                 end;
4250               if not (structdef.typ in [recorddef,objectdef]) then
4251                 internalerror(2018092101);
4252               if assigned(inheriteddef) then
4253                 begin
4254                   callflags:=[cnf_inherited];
4255                   include(current_procinfo.flags,pi_has_inherited);
4256                 end
4257               else
4258                 callflags:=[];
4259               do_member_read(structdef,getaddr,gensym,result,again,callflags,spezcontext);
4260               spezcontext:=nil;
4261             end
4262           else
4263             begin
4264               if gensym.typ=procsym then
4265                 begin
4266                   result:=nil;
4267                   { check if it's a method/class method }
4268                   if is_member_read(gensym,gensym.owner,result,parseddef) then
4269                     begin
4270                       { if we are accessing a owner procsym from the nested }
4271                       { class we need to call it as a class member }
4272                       if (gensym.owner.symtabletype in [ObjectSymtable,recordsymtable]) and
4273                           assigned(current_structdef) and (current_structdef<>parseddef) and is_owned_by(current_structdef,parseddef) then
4274                         result:=cloadvmtaddrnode.create(ctypenode.create(parseddef));
4275                       { not srsymtable.symtabletype since that can be }
4276                       { withsymtable as well                          }
4277                       if (gensym.owner.symtabletype in [ObjectSymtable,recordsymtable]) then
4278                         begin
4279                           do_member_read(tabstractrecorddef(parseddef),getaddr,gensym,result,again,[],spezcontext);
4280                           spezcontext:=nil;
4281                         end
4282                       else
4283                         { no procsyms in records (yet) }
4284                         internalerror(2015092704);
4285                     end
4286                   else
4287                     begin
4288                       { regular procedure/function call }
4289                       do_proc_call(gensym,gensym.owner,nil,
4290                                    (getaddr and not(token in [_CARET,_POINT,_LECKKLAMMER])),
4291                                    again,result,[],spezcontext);
4292                       spezcontext:=nil;
4293                     end;
4294                   end
4295                 else
4296                   { handle potential typecasts, etc }
4297                   result:=handle_factor_typenode(gendef,false,again,nil,false);
4298             end;
4299 
4300           { parse postfix operators }
4301           if postfixoperators(result,again,false) then
4302             if assigned(result) then
4303               result.fileinfo:=filepos
4304             else
4305               result:=cerrornode.create;
4306 
4307           spezcontext.free;
4308         end;
4309 
4310       label
4311         SubExprStart;
4312       var
4313         p1,p2,ptmp : tnode;
4314         oldt    : Ttoken;
4315         filepos : tfileposinfo;
4316         gendef,parseddef : tdef;
4317         gensym : tsym;
4318       begin
4319         SubExprStart:
4320         if pred_level=highest_precedence then
4321           begin
4322             if factornode=nil then
4323               p1:=factor(false,flags)
4324             else
4325               p1:=factornode;
4326           end
4327         else
4328           p1:=sub_expr(succ(pred_level),flags+[ef_accept_equal],factornode);
4329         repeat
4330           if (token in [NOTOKEN..last_operator]) and
4331              (token in operator_levels[pred_level]) and
4332              ((token<>_EQ) or (ef_accept_equal in flags)) then
4333            begin
4334              oldt:=token;
4335              filepos:=current_tokenpos;
4336              consume(token);
4337              if pred_level=highest_precedence then
4338                p2:=factor(false,[])
4339              else
4340                p2:=sub_expr(succ(pred_level),flags+[ef_accept_equal],nil);
4341              case oldt of
4342                _PLUS :
4343                  p1:=caddnode.create(addn,p1,p2);
4344                _MINUS :
4345                  p1:=caddnode.create(subn,p1,p2);
4346                _STAR :
4347                  p1:=caddnode.create(muln,p1,p2);
4348                _SLASH :
4349                  p1:=caddnode.create(slashn,p1,p2);
4350                _EQ:
4351                  p1:=caddnode.create(equaln,p1,p2);
4352                _GT :
4353                  p1:=caddnode.create(gtn,p1,p2);
4354                _LT :
4355                  begin
4356                    { we need to decice whether we have an inline specialization
4357                      (type nodes to the left and right of "<", mode Delphi and
4358                      ">" or "," following) or a normal "<" comparison }
4359                    { TODO : p1 could be a non type if e.g. a variable with the
4360                             same name is defined in the same unit where the
4361                             generic is defined (though "same unit" is not
4362                             necessarily needed) }
4363                    if getgenericsym(p1,gensym) and
4364                       { Attention: when nested specializations are supported
4365                                    p2 could be a loadn if a "<" follows }
4366                       istypenode(p2) and
4367                        (m_delphi in current_settings.modeswitches) and
4368                        { TODO : add _LT, _LSHARPBRACKET for nested specializations }
4369                        (token in [_GT,_RSHARPBRACKET,_COMMA]) then
4370                      begin
4371                        { this is an inline specialization }
4372 
4373                        { retrieve the defs of two nodes }
4374                        if p1.nodetype=specializen then
4375                          gendef:=gettypedef(tspecializenode(p1).sym)
4376                        else
4377                          gendef:=nil;
4378                        parseddef:=gettypedef(p2);
4379 
4380                        { check the hints for parseddef }
4381                        check_hints(parseddef.typesym,parseddef.typesym.symoptions,parseddef.typesym.deprecatedmsg,p1.fileinfo);
4382 
4383                        ptmp:=generate_inline_specialization(gendef,p1,filepos,parseddef,gensym,p2);
4384 
4385                        { we don't need these nodes anymore }
4386                        p1.free;
4387                        p2.free;
4388 
4389                        p1:=ptmp;
4390 
4391                        { with p1 now set we are in reality directly behind the
4392                          call to "factor" thus we need to call down to that
4393                          again }
4394                        { This is disabled until specializations on the right
4395                          hand side work as well, because
4396                          "not working expressions" is better than "half working
4397                          expressions" }
4398                        {factornode:=p1;
4399                        goto SubExprStart;}
4400                      end
4401                    else
4402                      begin
4403                        { this is a normal "<" comparison }
4404 
4405                        { potential generic types that are followed by a "<": }
4406 
4407                        { a) might not have their resultdef set }
4408                        if not assigned(p1.resultdef) then
4409                          do_typecheckpass(p1);
4410 
4411                        { b) are not checked whether they are an undefined def,
4412                             but not a generic parameter }
4413                        if (p1.nodetype=typen) and
4414                            (ttypenode(p1).typedef.typ=undefineddef) and
4415                            assigned(ttypenode(p1).typedef.typesym) and
4416                            not (sp_generic_para in ttypenode(p1).typedef.typesym.symoptions) then
4417                          begin
4418                            identifier_not_found(ttypenode(p1).typedef.typesym.RealName);
4419                            p1.Free;
4420                            p1:=cerrornode.create;
4421                          end;
4422 
4423                        { c) don't have their hints checked }
4424                        if istypenode(p1) then
4425                          begin
4426                            gendef:=gettypedef(p1);
4427                            if gendef.typ in [objectdef,recorddef,arraydef,procvardef] then
4428                              check_hints(gendef.typesym,gendef.typesym.symoptions,gendef.typesym.deprecatedmsg);
4429                          end;
4430 
4431                        { Note: the second part of the expression will be needed
4432                                for nested specializations }
4433                        if istypenode(p2) {and
4434                            not (token in [_LT, _LSHARPBRACKET])} then
4435                          begin
4436                            gendef:=gettypedef(p2);
4437                            if gendef.typ in [objectdef,recorddef,arraydef,procvardef] then
4438                              check_hints(gendef.typesym,gendef.typesym.symoptions,gendef.typesym.deprecatedmsg);
4439                          end;
4440 
4441                        { create the comparison node for "<" }
4442                        p1:=caddnode.create(ltn,p1,p2)
4443                      end;
4444                  end;
4445                _GTE :
4446                  p1:=caddnode.create(gten,p1,p2);
4447                _LTE :
4448                  p1:=caddnode.create(lten,p1,p2);
4449                _SYMDIF :
4450                  p1:=caddnode.create(symdifn,p1,p2);
4451                _STARSTAR :
4452                  p1:=caddnode.create(starstarn,p1,p2);
4453                _OP_AS,
4454                _OP_IS :
4455                  begin
4456                    if (m_delphi in current_settings.modeswitches) and
4457                        (token in [_LT, _LSHARPBRACKET]) and
4458                        getgenericsym(p2,gensym) then
4459                      begin
4460                        { for now we're handling this as a generic declaration;
4461                          there could be cases though (because of operator
4462                          overloading) where this is the wrong decision... }
4463                        if gensym.typ=typesym then
4464                          gendef:=ttypesym(gensym).typedef
4465                        else
4466                          if gensym.typ=procsym then
4467                            gendef:=tdef(tprocsym(gensym).procdeflist[0])
4468                          else
4469                            internalerror(2015072401);
4470 
4471                        ptmp:=generate_inline_specialization(gendef,p2,filepos,nil,nil,nil);
4472 
4473                        { we don't need the old p2 anymore }
4474                        p2.Free;
4475 
4476                        p2:=ptmp;
4477 
4478                        { here we don't need to call back down to "factor", thus
4479                          no "goto" }
4480                      end;
4481 
4482                    { now generate the "is" or "as" node }
4483                    case oldt of
4484                      _OP_AS:
4485                        p1:=casnode.create(p1,p2);
4486                      _OP_IS:
4487                        p1:=cisnode.create(p1,p2);
4488                    end;
4489                  end;
4490                _OP_IN :
4491                  p1:=cinnode.create(p1,p2);
4492                _OP_OR,
4493                _PIPE {macpas only} :
4494                  begin
4495                    p1:=caddnode.create(orn,p1,p2);
4496                    if (oldt = _PIPE) then
4497                      include(p1.flags,nf_short_bool);
4498                  end;
4499                _OP_AND,
4500                _AMPERSAND {macpas only} :
4501                  begin
4502                    p1:=caddnode.create(andn,p1,p2);
4503                    if (oldt = _AMPERSAND) then
4504                      include(p1.flags,nf_short_bool);
4505                  end;
4506                _OP_DIV :
4507                  p1:=cmoddivnode.create(divn,p1,p2);
4508                _OP_NOT :
4509                  p1:=cnotnode.create(p1);
4510                _OP_MOD :
4511                  begin
4512                    p1:=cmoddivnode.create(modn,p1,p2);
4513                    if m_isolike_mod in current_settings.modeswitches then
4514                      include(p1.flags,nf_isomod);
4515                  end;
4516                _OP_SHL :
4517                  p1:=cshlshrnode.create(shln,p1,p2);
4518                _OP_SHR :
4519                  p1:=cshlshrnode.create(shrn,p1,p2);
4520                _OP_XOR :
4521                  p1:=caddnode.create(xorn,p1,p2);
4522                _ASSIGNMENT :
4523                  p1:=cassignmentnode.create(p1,p2);
4524                _NE :
4525                  p1:=caddnode.create(unequaln,p1,p2);
4526              end;
4527              p1.fileinfo:=filepos;
4528            end
4529           else
4530            break;
4531         until false;
4532         sub_expr:=p1;
4533       end;
4534 
4535 
comp_exprnull4536     function comp_expr(flags:texprflags):tnode;
4537       var
4538          oldafterassignment : boolean;
4539          p1 : tnode;
4540       begin
4541          oldafterassignment:=afterassignment;
4542          afterassignment:=true;
4543          p1:=sub_expr(opcompare,flags,nil);
4544          { get the resultdef for this expression }
4545          if not assigned(p1.resultdef) then
4546           do_typecheckpass(p1);
4547          afterassignment:=oldafterassignment;
4548          comp_expr:=p1;
4549       end;
4550 
4551 
exprnull4552     function expr(dotypecheck : boolean) : tnode;
4553 
4554       var
4555          p1,p2 : tnode;
4556          filepos : tfileposinfo;
4557          oldafterassignment,
4558          updatefpos          : boolean;
4559 
4560       begin
4561          oldafterassignment:=afterassignment;
4562          p1:=sub_expr(opcompare,[ef_accept_equal],nil);
4563          { get the resultdef for this expression }
4564          if not assigned(p1.resultdef) and
4565             dotypecheck then
4566           do_typecheckpass(p1);
4567          filepos:=current_tokenpos;
4568          if token in [_ASSIGNMENT,_PLUSASN,_MINUSASN,_STARASN,_SLASHASN] then
4569            afterassignment:=true;
4570          updatefpos:=true;
4571          case token of
4572            _POINTPOINT :
4573              begin
4574                 consume(_POINTPOINT);
4575                 p2:=sub_expr(opcompare,[ef_accept_equal],nil);
4576                 p1:=crangenode.create(p1,p2);
4577              end;
4578            _ASSIGNMENT :
4579              begin
4580                 consume(_ASSIGNMENT);
4581                 if assigned(p1.resultdef) and (p1.resultdef.typ=procvardef) then
4582                   getprocvardef:=tprocvardef(p1.resultdef);
4583                 p2:=sub_expr(opcompare,[ef_accept_equal],nil);
4584                 if assigned(getprocvardef) then
4585                   handle_procvar(getprocvardef,p2);
4586                 getprocvardef:=nil;
4587                 p1:=cassignmentnode.create(p1,p2);
4588              end;
4589            _PLUSASN :
4590              begin
4591                consume(_PLUSASN);
4592                p2:=sub_expr(opcompare,[ef_accept_equal],nil);
4593                p1:=gen_c_style_operator(addn,p1,p2);
4594             end;
4595           _MINUSASN :
4596             begin
4597                consume(_MINUSASN);
4598                p2:=sub_expr(opcompare,[ef_accept_equal],nil);
4599                p1:=gen_c_style_operator(subn,p1,p2);
4600             end;
4601           _STARASN :
4602             begin
4603                consume(_STARASN  );
4604                p2:=sub_expr(opcompare,[ef_accept_equal],nil);
4605                p1:=gen_c_style_operator(muln,p1,p2);
4606             end;
4607           _SLASHASN :
4608             begin
4609                consume(_SLASHASN  );
4610                p2:=sub_expr(opcompare,[ef_accept_equal],nil);
4611                p1:=gen_c_style_operator(slashn,p1,p2);
4612             end;
4613           else
4614             updatefpos:=false;
4615          end;
4616          { get the resultdef for this expression }
4617          if not assigned(p1.resultdef) and
4618             dotypecheck then
4619           do_typecheckpass(p1);
4620          afterassignment:=oldafterassignment;
4621          if updatefpos then
4622            p1.fileinfo:=filepos;
4623          expr:=p1;
4624       end;
4625 
get_intconstnull4626     function get_intconst:TConstExprInt;
4627     {Reads an expression, tries to evalute it and check if it is an integer
4628      constant. Then the constant is returned.}
4629     var
4630       p:tnode;
4631     begin
4632       result:=0;
4633       p:=comp_expr([ef_accept_equal]);
4634       if not codegenerror then
4635        begin
4636          if (p.nodetype<>ordconstn) or
4637             not(is_integer(p.resultdef)) then
4638           Message(parser_e_illegal_expression)
4639          else
4640           result:=tordconstnode(p).value;
4641        end;
4642       p.free;
4643     end;
4644 
4645 
get_stringconstnull4646     function get_stringconst:string;
4647     {Reads an expression, tries to evaluate it and checks if it is a string
4648      constant. Then the constant is returned.}
4649     var
4650       p:tnode;
4651     begin
4652       get_stringconst:='';
4653       p:=comp_expr([ef_accept_equal]);
4654       if p.nodetype<>stringconstn then
4655         begin
4656           if (p.nodetype=ordconstn) and is_char(p.resultdef) then
4657             get_stringconst:=char(int64(tordconstnode(p).value))
4658           else
4659             Message(parser_e_illegal_expression);
4660         end
4661       else
4662         get_stringconst:=strpas(tstringconstnode(p).value_str);
4663       p.free;
4664     end;
4665 
4666 end.
4667