FreeBASIC  0.91.0
parser-proccall.bas
Go to the documentation of this file.
1 '' proc calls (CALL or foo[(...)]) and function result assignments (function=expr)
2 ''
3 '' chng: sep/2004 written [v1ctor]
4 
5 
6 #include once "fb.bi"
7 #include once "fbint.bi"
8 #include once "parser.bi"
9 #include once "rtl.bi"
10 #include once "ast.bi"
11 
12 declare sub hCtorChain( )
13 declare sub hBaseInit( )
14 declare function hBaseMemberAccess( ) as integer
15 declare function hForwardCall( ) as integer
16 
17 function cBydescArrayArgParens( byval arg as ASTNODE ptr ) as FB_PARAMMODE
18  function = INVALID
19  if( lexGetToken( ) = CHAR_LPRNT ) then
20  if( lexGetLookAhead( 1 ) = CHAR_RPRNT ) then
21  if( astGetSymbol( arg ) <> NULL ) then
22  if( symbIsArray( astGetSymbol( arg ) ) ) then
23  lexSkipToken( )
24  lexSkipToken( )
25  function = FB_PARAMMODE_BYDESC
26  end if
27  end if
28  end if
29  end if
30 end function
31 
32 function cAssignFunctResult( byval is_return as integer ) as integer
33  dim as FBSYMBOL ptr res = any, subtype = any
34  dim as ASTNODE ptr rhs = any, expr = any
35  dim as integer has_ctor = any, has_defctor = any
36 
37  function = FALSE
38 
39  res = symbGetProcResult( parser.currproc )
40  if( res = NULL ) then
41  errReport( FB_ERRMSG_SYNTAXERROR )
42  '' error recovery: skip stmt, return
43  hSkipStmt( )
44  return TRUE
45  end if
46 
47  has_ctor = symbHasCtor( parser.currproc )
48  has_defctor = symbHasDefCtor( parser.currproc )
49 
50  '' RETURN?
51  if( is_return ) then
52  if( symbGetProcStatAssignUsed( parser.currproc ) ) then
53  if( has_defctor ) then
54  errReport( FB_ERRMSG_RETURNMIXEDWITHASSIGN )
55  end if
56  end if
57 
58  symbSetProcStatReturnUsed( parser.currproc )
59  else
60  if( symbGetProcStatReturnUsed( parser.currproc ) ) then
61  if( has_defctor ) then
62  errReport( FB_ERRMSG_ASSIGNMIXEDWITHRETURN )
63  end if
64  end if
65 
66  symbSetProcStatAssignUsed( parser.currproc )
67  end if
68 
69  '' set the context symbol to allow taking the address of overloaded
70  '' procs and also to allow anonymous UDT's
71  parser.ctxsym = symbGetSubType( parser.currproc )
72  parser.ctx_dtype = symbGetType( parser.currproc )
73 
74  '' Expression
75  ''
76  '' Any Expression is allowed in "FUNCTION = expr" or "RETURN expr",
77  '' as long as the type matches, unless the function returns BYREF,
78  '' then it must be a variable/deref (since we do an implicit ADDROF).
79  '' However if BYVAL is explicitly given then any pointer expression
80  '' is allowed, no implicit ADDROF is done, just like with BYREF params.
81 
82  '' Returning BYREF and no explicit BYVAL given?
83  if( symbProcReturnsByref( parser.currproc ) and (not hMatch( FB_TK_BYVAL )) ) then
84  '' BYREF return, must be able to do addrof on the expression
85  '' (this disallows expressions like constants, BOPs, @ UOP, ...)
86  rhs = cVarOrDeref( FB_VAREXPROPT_ISEXPR )
87 
88  if( rhs ) then
89  if( astIsAccessToLocal( rhs ) ) then
90  errReport( FB_ERRMSG_INVALIDREFERENCETOLOCAL )
91  end if
92 
93  '' BYREF AS STRING and expression is a string literal?
94  if( (symbGetType( parser.currproc ) = FB_DATATYPE_STRING) and _
95  (astGetStrLitSymbol( rhs ) <> NULL) ) then
96  '' Cannot be allowed, since a string literal is not
97  '' an FBSTRING descriptor...
98  errReport( FB_ERRMSG_INVALIDDATATYPES )
99  astDelTree( rhs )
100  rhs = NULL
101  else
102  '' Implicit addrof due to BYREF
103  rhs = astNewADDROF( rhs )
104  end if
105  end if
106  else
107  rhs = cExpression( )
108  end if
109 
110  parser.ctxsym = NULL
111  parser.ctx_dtype = FB_DATATYPE_INVALID
112 
113  if( rhs = NULL ) then
114  errReport( FB_ERRMSG_EXPECTEDEXPRESSION )
115  '' error recovery: skip stmt, return
116  hSkipStmt( )
117  return TRUE
118  end if
119 
120  '' set accessed flag here, as proc will be ended before AST is flushed
121  symbSetIsAccessed( res )
122 
123  '' RETURN and has ctor? try to initialize..
124  if( is_return and has_ctor ) then
125  dim as integer is_ctorcall = any
126  rhs = astBuildImplicitCtorCallEx( res, rhs, cBydescArrayArgParens( rhs ), is_ctorcall )
127  if( rhs = NULL ) then
128  exit function
129  end if
130 
131  if( is_ctorcall ) then
132  astAdd( astPatchCtorCall( rhs, astBuildProcResultVar( parser.currproc, res ) ) )
133  return TRUE
134  end if
135  end if
136 
137  '' do the assignment
138  expr = astNewASSIGN( astBuildProcResultVar( parser.currproc, res ), rhs )
139  if( expr = NULL ) then
140  astDelTree( rhs )
141  errReport( FB_ERRMSG_ILLEGALASSIGNMENT )
142  else
143  astAdd( expr )
144  end if
145 
146  function = TRUE
147 end function
148 
150  ( _
151  byval proc as FBSYMBOL ptr, _
152  byval thisexpr as ASTNODE ptr, _
153  byval arg_list as FB_CALL_ARG_LIST ptr, _
154  byval options as FB_PARSEROPT ptr _
155  )
156 
157  '' Only for method calls
158  if( thisexpr = NULL ) then
159  return
160  end if
161 
162  '' The proc given here can be a method with THIS pointer or a static
163  '' member proc, depending on which was declared/found first, but it's
164  '' not known yet whether the exact overload that's going to be called
165  '' will be static or not. So the thisexpr needs to be preserved here,
166  '' the rest is done after the args were parsed.
167 
168  dim as FB_CALL_ARG ptr arg = symbAllocOvlCallArg( @parser.ovlarglist, arg_list, FALSE )
169 
170  dim as FBSYMBOL ptr parent = symbGetParent( proc )
171  if( astGetSubtype( thisexpr ) <> parent ) then
172  thisexpr = astNewCONV( symbGetType( parent ), parent, thisexpr )
173  end if
174 
175  arg->expr = thisexpr
176  arg->mode = hGetInstPtrMode( thisexpr )
177 
178  *options or= FB_PARSEROPT_HASINSTPTR
179 
180 end sub
181 
182 '':::::
183 function cProcCall _
184  ( _
185  byval base_parent as FBSYMBOL ptr, _
186  byval sym as FBSYMBOL ptr, _
187  byval ptrexpr as ASTNODE ptr, _
188  byval thisexpr as ASTNODE ptr, _
189  byval checkprnts as integer, _
190  byval options as FB_PARSEROPT _
191  ) as ASTNODE ptr
192 
193  dim as integer dtype = any, is_propset = FALSE
194  dim as ASTNODE ptr procexpr = any
195  dim as FB_CALL_ARG_LIST arg_list = ( 0, NULL, NULL )
196 
197  function = NULL
198 
199  hMethodCallAddInstPtrOvlArg( sym, thisexpr, @arg_list, @options )
200 
201  '' property?
202  if( symbIsProperty( sym ) ) then
203 
204  dim as integer is_indexed = FALSE
205 
206  '' '('? indexed..
207  if( lexGetToken( ) = CHAR_LPRNT ) then
208  is_indexed = TRUE
209 
210  lexSkipToken( )
211 
212  '' index expr
213  dim as ASTNODE ptr expr = cExpression( )
214  if( expr = NULL ) then
215  errReport( FB_ERRMSG_EXPECTEDEXPRESSION )
216  '' error recovery: fake an expr
217  expr = astNewCONSTi( 0 )
218  end if
219 
220  dim as FB_CALL_ARG ptr arg = symbAllocOvlCallArg( @parser.ovlarglist, @arg_list, FALSE )
221  arg->expr = expr
222  arg->mode = INVALID
223 
224  '' ')'
225  if( lexGetToken( ) <> CHAR_RPRNT ) then
226  errReport( FB_ERRMSG_EXPECTEDRPRNT )
227  '' error recovery: skip until next ')'
228  hSkipUntil( CHAR_RPRNT, TRUE )
229  else
230  lexSkipToken( )
231  end if
232  end if
233 
234  '' '='?
235  if( hIsAssignToken( ) ) then
236  if( is_indexed ) then
237  if( symbGetUDTHasIdxSetProp( symbGetParent( sym ) ) = FALSE ) then
238  errReport( FB_ERRMSG_PROPERTYHASNOIDXSETMETHOD, TRUE )
239  exit function
240  end if
241  else
242  if( symbGetUDTHasSetProp( symbGetParent( sym ) ) = FALSE ) then
243  errReport( FB_ERRMSG_PROPERTYHASNOSETMETHOD )
244  exit function
245  end if
246  end if
247 
248  lexSkipToken( )
249  is_propset = TRUE
250 
251  '' the value arg is the lhs expression
252 
253  else
254  options or= FB_PARSEROPT_ISPROPGET
255 
256  if( is_indexed ) then
257  if( symbGetUDTHasIdxGetProp( symbGetParent( sym ) ) = FALSE ) then
258  errReport( FB_ERRMSG_PROPERTYHASNOIDXGETMETHOD, TRUE )
259  exit function
260  end if
261  else
262  if( symbGetUDTHasGetProp( symbGetParent( sym ) ) = FALSE ) then
263  errReport( FB_ERRMSG_PROPERTYHASNOGETMETHOD )
264  exit function
265  end if
266  end if
267 
268  '' it's a property get call being deref'd or discarded
269  end if
270 
271  checkprnts = FALSE
272 
273  '' anything else..
274  else
275  if( checkprnts = TRUE ) then
276  '' if the sub has no args, prnts are optional
277  if( symbGetProcParams( sym ) = 0 ) then
278  checkprnts = FALSE
279  end if
280 
281  '' if it's a function pointer, prnts are obligatory
282  elseif( ptrexpr <> NULL ) then
283  checkprnts = TRUE
284 
285  end if
286  end if
287 
288  if( checkprnts ) then
289  '' '('
290  if( hMatch( CHAR_LPRNT ) = FALSE ) then
291  errReport( FB_ERRMSG_EXPECTEDLPRNT )
292  end if
293  end if
294 
295  parser.prntcnt = 0
296  fbSetPrntOptional( not checkprnts )
297 
298  '' ProcArgList
299  procexpr = cProcArgList( base_parent, sym, ptrexpr, @arg_list, options )
300  if( procexpr = NULL ) then
301  hSkipUntil( CHAR_RPRNT )
302  exit function
303  end if
304 
305  '' ')'
306  if( (checkprnts) or (parser.prntcnt > 0) ) then
307  '' --parent cnt
308  parser.prntcnt -= 1
309 
310  if( hMatch( CHAR_RPRNT ) = FALSE ) then
311  errReport( FB_ERRMSG_EXPECTEDRPRNT )
312  '' error recovery: skip until next ')'
313  hSkipUntil( CHAR_RPRNT, TRUE )
314  elseif( parser.prntcnt > 0 ) then
315  '' error recovery: skip until all ')'s are found
316  do while( parser.prntcnt > 0 )
317  hSkipUntil( CHAR_RPRNT, TRUE )
318  parser.prntcnt -= 1
319  loop
320  end if
321  end if
322 
323  fbSetPrntOptional( FALSE )
324 
325  if( is_propset = FALSE ) then
326  '' Take care of functions returning BYREF
327  procexpr = astBuildByrefResultDeref( procexpr )
328 
329  '' StrIdxOrMemberDeref?
330  procexpr = cStrIdxOrMemberDeref( procexpr )
331 
332  '' if it's a SUB, the expr will be NULL
333  if( procexpr = NULL ) then
334  exit function
335  end if
336  end if
337 
338  '' not a function? (because StrIdxOrMemberDeref())
339  if( astIsCALL( procexpr ) = FALSE ) then
340  '' And not a DEREF( CALL( function-with-byref-result ) ) either?
341  if( astIsByrefResultDeref( procexpr ) = FALSE ) then
342  '' Cannot ignore this
343  return procexpr
344  end if
345 
346  select case( lexGetToken( ) )
347  case FB_TK_STMTSEP, FB_TK_EOL, FB_TK_EOF, _
348  FB_TK_COMMENT, FB_TK_REM
349  '' It seems like the result is being ignored,
350  '' i.e. no assignment following
351 
352  case else
353  return procexpr
354  end select
355 
356  '' Remove the DEREF and turn it into a plain CALL,
357  '' whose result can be ignored.
358  procexpr = astRemoveByrefResultDeref( procexpr )
359  end if
360 
361  dtype = astGetDataType( procexpr )
362 
363  '' can proc's result be skipped?
364  if( dtype <> FB_DATATYPE_VOID ) then
365  if( typeGetClass( dtype ) <> FB_DATACLASS_INTEGER ) then
366  errReport( FB_ERRMSG_VARIABLEREQUIRED )
367  '' error recovery: skip
368  astDelTree( procexpr )
369  exit function
370 
371  '' CHAR and WCHAR literals are also from the INTEGER class
372  else
373  select case as const dtype
374  case FB_DATATYPE_CHAR, FB_DATATYPE_WCHAR
375  errReport( FB_ERRMSG_VARIABLEREQUIRED )
376  '' error recovery: skip
377  astDelTree( procexpr )
378  exit function
379  end select
380  end if
381  end if
382 
383  '' check error?
384  sym = astGetSymbol( procexpr )
385  if( sym <> NULL ) then
386  if( symbGetIsThrowable( sym ) ) then
387  astAdd( rtlErrorCheck( procexpr ) )
388  exit function
389  end if
390  end if
391 
392  '' tell the emitter to not allocate a result
393  astSetType( procexpr, FB_DATATYPE_VOID, NULL )
394 
395  astAdd( procexpr )
396 
397  function = NULL
398 
399 end function
400 
401 function hProcSymbol _
402  ( _
403  byval base_parent as FBSYMBOL ptr, _
404  byval sym as FBSYMBOL ptr, _
405  byval iscall as integer, _
406  byval options as FB_PARSEROPT = 0 _
407  ) as integer
408 
409  dim as integer do_call = any
410 
411  function = FALSE
412 
413  if( cCompStmtIsAllowed( FB_CMPSTMT_MASK_CODE ) = FALSE ) then
414  hSkipStmt( )
415  return TRUE
416  end if
417 
418  lexSkipToken( )
419 
420  '' '='?
421  do_call = not hIsAssignToken( )
422 
423  if( do_call = FALSE ) then
424  '' special case: property
425  if( symbIsProperty( sym ) ) then
426  do_call = TRUE
427 
428  '' unless it's inside a PROPERTY GET block
429  if( symbIsProperty( parser.currproc ) ) then
430  if( symbGetProcParams( parser.currproc ) = 1 ) then
431  if( symbIsProcOverloadOf( parser.currproc, sym ) ) then
432  do_call = FALSE
433  end if
434  end if
435  end if
436  end if
437  end if
438 
439  '' ID ProcParamList?
440  if( do_call ) then
441  dim as ASTNODE ptr expr = any
442  expr = cProcCall( base_parent, sym, NULL, NULL, FALSE, options )
443 
444  '' assignment of a function deref?
445  if( expr <> NULL ) then
446  cAssignment( expr )
447  end if
448 
449  return TRUE
450  end if
451 
452  '' ID '=' Expression
453 
454  '' CALL?
455  if( iscall ) then
456  errReport( FB_ERRMSG_SYNTAXERROR )
457  '' error recovery: skip stmt, return
458  hSkipStmt( )
459  return TRUE
460  end if
461 
462  '' check if name is valid (or if overloaded)
463  if( symbIsProcOverloadOf( parser.currproc, sym ) = FALSE ) then
464  errReport( FB_ERRMSG_ILLEGALOUTSIDEAPROC )
465  '' error recovery: skip stmt, return
466  hSkipStmt( )
467  return TRUE
468  end if
469 
470  '' skip the '='
471  lexSkipToken( )
472 
473  function = cAssignFunctResult( FALSE )
474 end function
475 
476 '':::::
477 function hVarSymbol _
478  ( _
479  byval sym as FBSYMBOL ptr, _
480  byval iscall as integer _
481  ) as integer
482 
483  dim as ASTNODE ptr expr = any
484 
485  function = FALSE
486 
487  '' must process variables here, multiple calls to
488  '' Identifier() will fail if a namespace was explicitly
489  '' given, because the next call will return an inner symbol
490  expr = cVariableEx( sym, TRUE )
491  if( expr = NULL ) then
492  exit function
493  end if
494 
495  '' CALL?
496  if( iscall ) then
497  '' not a ptr call?
498  if( astIsCALL( expr ) = FALSE ) then
499  astDelTree( expr )
500  errReport( FB_ERRMSG_SYNTAXERROR )
501  '' error recovery: skip stmt, return
502  hSkipStmt( )
503  return TRUE
504  end if
505  end if
506 
507  function = cAssignmentOrPtrCallEx( expr )
508 
509 end function
510 
511 ''::::
512 function hAssignOrCall_QB _
513  ( _
514  byval chain_ as FBSYMCHAIN ptr, _
515  byval iscall as integer _
516  ) as integer
517 
518  function = FALSE
519 
520  dim as zstring ptr id = lexGetText( )
521  dim as integer suffix = lexGetType( )
522  dim as integer defdtype = symbGetDefType( id )
523 
524  do while( chain_ <> NULL )
525 
526  dim as FBSYMBOL ptr sym = chain_->sym
527  dim as FBSYMBOL ptr var_sym = NULL
528 
529  '' no suffix?
530  if( suffix = FB_DATATYPE_INVALID ) then
531  do
532  dim as integer is_match = TRUE
533  '' is the original symbol suffixed?
534  if( symbIsSuffixed( sym ) ) then
535  '' if it's a VAR, lookup the default type (last DEF###) in
536  '' the case symbol could not be found..
537  if( symbGetClass( sym ) = FB_SYMBCLASS_VAR ) then
538  if( defdtype = FB_DATATYPE_STRING ) then
539  select case as const symbGetType( sym )
540  case FB_DATATYPE_STRING, FB_DATATYPE_FIXSTR, FB_DATATYPE_CHAR
541 
542  case else
543  is_match = FALSE
544  end select
545  else
546  is_match = (symbGetType( sym ) = defdtype)
547  end if
548  end if
549  end if
550 
551  if( is_match ) then
552  select case as const symbGetClass( sym )
553  '' proc?
554  case FB_SYMBCLASS_PROC
555  '' if it's a RTL func, the suffix is obligatory
556  if( symbGetIsRTL( sym ) ) then
557  is_match = (symbIsSuffixed( sym ) = FALSE)
558  end if
559 
560  if( is_match ) then
561  return hProcSymbol( NULL, sym, iscall )
562  end if
563 
564  '' variable?
565  case FB_SYMBCLASS_VAR
566  if( var_sym = NULL ) then
567  if( symbVarCheckAccess( sym ) ) then
568  var_sym = sym
569  end if
570  end if
571 
572  '' quirk-keyword?
573  case FB_SYMBCLASS_KEYWORD
574  '' only if not suffixed
575  if( symbIsSuffixed( sym ) = FALSE ) then
576  return cQuirkStmt( sym->key.id )
577  end if
578 
579  end select
580  end if
581 
582  sym = sym->hash.next
583  loop while( sym <> NULL )
584 
585  '' suffix..
586  else
587  do
588  dim as integer is_match = any
589  if( suffix = FB_DATATYPE_STRING ) then
590  select case as const symbGetType( sym )
591  case FB_DATATYPE_STRING, FB_DATATYPE_FIXSTR, FB_DATATYPE_CHAR
592  is_match = TRUE
593  case else
594  is_match = FALSE
595  end select
596  else
597  is_match = (symbGetType( sym ) = suffix)
598  end if
599 
600  if( is_match ) then
601  select case as const symbGetClass( sym )
602  '' proc?
603  case FB_SYMBCLASS_PROC
604  return hProcSymbol( NULL, sym, iscall )
605 
606  '' variable?
607  case FB_SYMBCLASS_VAR
608  if( symbVarCheckAccess( sym ) ) then
609  var_sym = sym
610  end if
611 
612  '' quirk-keyword?
613  case FB_SYMBCLASS_KEYWORD
614  return cQuirkStmt( sym->key.id )
615 
616  end select
617  end if
618 
619  sym = sym->hash.next
620  loop while( sym <> NULL )
621  end if
622 
623  '' vars have the less priority than keywords and rtl procs
624  if( var_sym <> NULL ) then
625  return hVarSymbol( var_sym, iscall )
626  end if
627 
628  chain_ = symbChainGetNext( chain_ )
629  loop
630 
631 end function
632 
633 function hAssignOrPtrCall _
634  ( _
635  byval expr as ASTNODE ptr, _
636  byval iscall as integer _
637  ) as integer
638 
639  if( expr = NULL ) then
640  exit function
641  end if
642 
643  '' CALL?
644  if( iscall ) then
645  '' not a ptr call?
646  if( astIsCALL( expr ) = FALSE ) then
647  astDelTree( expr )
648  errReport( FB_ERRMSG_SYNTAXERROR )
649  '' error recovery: skip stmt, return
650  hSkipStmt( )
651  return TRUE
652  end if
653  end if
654 
655  function = cAssignmentOrPtrCallEx( expr )
656 end function
657 
658 ''::::
659 function hAssignOrCall _
660  ( _
661  byval base_parent as FBSYMBOL ptr, _
662  byval chain_ as FBSYMCHAIN ptr, _
663  byval iscall as integer, _
664  byval options as FB_PARSEROPT = 0 _
665  ) as integer
666 
667  function = FALSE
668 
669  do while( chain_ <> NULL )
670 
671  dim as FBSYMBOL ptr sym = chain_->sym
672  do
673  select case as const symbGetClass( sym )
674  '' proc?
675  case FB_SYMBCLASS_PROC
676  return hProcSymbol( base_parent, sym, iscall, options )
677 
678  case FB_SYMBCLASS_VAR
679  '' must process variables here, multiple calls to
680  '' cIdentifier() will fail if a namespace was explicitly
681  '' given, because the next call will return an inner symbol
682  return hAssignOrPtrCall( cVariableEx( chain_, TRUE ), iscall )
683 
684  case FB_SYMBCLASS_FIELD
685  return hAssignOrPtrCall( cImplicitDataMember( base_parent, chain_, TRUE, options ), iscall )
686 
687  case FB_SYMBCLASS_CONST
688  '' This covers misuse of constants as "statements",
689  '' or on the lhs of assignments:
690  '' ns.someconst
691  '' ns.someconst = 123
692  '' both isn't allowed; so we finish parsing the constant,
693  '' then let cAssignment() show & handle the error.
694  return hAssignOrPtrCall( cConstant( sym ), iscall )
695 
696  '' quirk-keyword?
697  case FB_SYMBCLASS_KEYWORD
698  return cQuirkStmt( sym->key.id )
699 
700  end select
701 
702  sym = sym->hash.next
703  loop while( sym <> NULL )
704 
705  chain_ = symbChainGetNext( chain_ )
706  loop
707 
708 end function
709 
710 function hProcCallOrAssign_QB( ) as integer
711  function = FALSE
712 
713  select case as const lexGetClass( )
714  case FB_TKCLASS_IDENTIFIER, FB_TKCLASS_QUIRKWD, FB_TKCLASS_OPERATOR
715 
716  return hAssignOrCall_QB( lexGetSymChain( ), FALSE )
717 
718  case FB_TKCLASS_KEYWORD
719 
720  if( lexGetToken( ) <> FB_TK_CALL ) then
721  return hAssignOrCall_QB( lexGetSymChain( ), FALSE )
722  end if
723 
724  if( cCompStmtIsAllowed( FB_CMPSTMT_MASK_CODE ) = FALSE ) then
725  hSkipStmt( )
726  exit function
727  end if
728 
729  lexSkipToken( )
730 
731  if( lexGetSymChain( ) = NULL ) then
732  return hForwardCall( )
733  else
734  return hAssignOrCall_QB( lexGetSymChain( ), TRUE )
735  end if
736 
737  end select
738 
739 end function
740 
741 '':::::
742 ''ProcCallOrAssign= CALL ID ('(' ProcParamList ')')?
743 '' | ID ProcParamList?
744 '' | (ID | FUNCTION | OPERATOR | PROPERTY) '=' Expression .
745 ''
746 function cProcCallOrAssign _
747  ( _
748  ) as integer
749 
750  dim as FBSYMCHAIN ptr chain_ = any
751  dim as FBSYMBOL ptr base_parent = any
752  dim as ASTNODE ptr expr = any
753 
754  function = FALSE
755 
756  '' QB mode?
757  if( env.clopt.lang = FB_LANG_QB ) then
758  return hProcCallOrAssign_QB( )
759  end if
760 
761  select case as const lexGetClass( )
762  case FB_TKCLASS_IDENTIFIER, FB_TKCLASS_QUIRKWD
763 
764  chain_ = cIdentifier( base_parent, FB_IDOPT_DEFAULT or FB_IDOPT_ALLOWSTRUCT )
765 
766  return hAssignOrCall( base_parent, chain_, FALSE )
767 
768  case FB_TKCLASS_KEYWORD
769 
770  select case as const lexGetToken( )
771  '' FUNCTION?
772  case FB_TK_FUNCTION
773 
774  '' no need to check for '=', that was done already by Declaration()
775 
776  if( fbIsModLevel( ) ) then
777  errReport( FB_ERRMSG_ILLEGALOUTSIDEAFUNCTION )
778  '' error recovery: skip stmt, return
779  hSkipStmt( )
780  return TRUE
781  end if
782 
783  '' useless check.. don't allow FUNCTION inside OPERATOR or PROPERTY
784  if( symbIsOperator( parser.currproc ) ) then
785  errReport( FB_ERRMSG_EXPECTEDOPERATOR )
786  elseif( symbIsProperty( parser.currproc ) ) then
787  errReport( FB_ERRMSG_EXPECTEDPROPERTY )
788  end if
789 
790  lexSkipToken( )
791  lexSkipToken( )
792 
793  return cAssignFunctResult( FALSE )
794 
795  '' OPERATOR?
796  case FB_TK_OPERATOR
797 
798  '' not inside an OPERATOR function?
799  if( symbIsOperator( parser.currproc ) = FALSE ) then
800  errReport( FB_ERRMSG_ILLEGALOUTSIDEANOPERATOR )
801  '' error recovery: skip stmt, return
802  hSkipStmt( )
803  return TRUE
804  end if
805 
806  lexSkipToken( )
807  lexSkipToken( )
808 
809  return cAssignFunctResult( FALSE )
810 
811  '' PROPERTY?
812  case FB_TK_PROPERTY
813 
814  '' no need to check for '=', that was done already by Declaration()
815 
816  if( fbIsModLevel( ) ) then
817  errReport( FB_ERRMSG_ILLEGALOUTSIDEANPROPERTY )
818  '' error recovery: skip stmt, return
819  hSkipStmt( )
820  return TRUE
821  else
822  if( symbIsProperty( parser.currproc ) = FALSE ) then
823  errReport( FB_ERRMSG_ILLEGALOUTSIDEANPROPERTY )
824  end if
825  end if
826 
827  lexSkipToken( )
828  lexSkipToken( )
829 
830  return cAssignFunctResult( FALSE )
831 
832  '' CONSTRUCTOR?
833  case FB_TK_CONSTRUCTOR
834  hCtorChain( )
835  return TRUE
836 
837  '' BASE?
838  case FB_TK_BASE
839 
840  '' accessing a base member?
841  if( lexGetLookAhead( 1 ) = CHAR_DOT ) then
842  return hBaseMemberAccess( )
843  else
844  hBaseInit( )
845  return TRUE
846  end if
847 
848  '' CALL?
849  case FB_TK_CALL
850 
851  if( fbLangOptIsSet( FB_LANG_OPT_CALL ) = FALSE ) then
852  errReportNotAllowed( FB_LANG_OPT_CALL )
853  '' error recovery: skip stmt
854  hSkipStmt( )
855  return TRUE
856  end if
857 
858  if( cCompStmtIsAllowed( FB_CMPSTMT_MASK_CODE ) = FALSE ) then
859  hSkipStmt( )
860  return TRUE
861  end if
862 
863  lexSkipToken( )
864 
866  if( chain_ <> NULL ) then
867  return hAssignOrCall( base_parent, chain_, TRUE )
868  end if
869 
870  errReport( FB_ERRMSG_EXPECTEDIDENTIFIER )
871  return TRUE
872 
873  end select
874 
875  case FB_TKCLASS_OPERATOR
876  if( lexGetToken( ) = FB_TK_DELETE ) then
877  cOperatorDelete( )
878  return TRUE
879  end if
880 
881  case FB_TKCLASS_DELIMITER
882 
883  '' '.'?
884  if( lexGetToken( ) = CHAR_DOT ) then
885  '' inside a WITH block?
886  if( parser.stmt.with.sym <> NULL ) then
887  '' not '..'?
888  if( lexGetLookAhead( 1, LEXCHECK_NOPERIOD ) <> CHAR_DOT ) then
889  expr = cWithVariable( fbGetCheckArray( ) )
890  if( expr = NULL ) then
891  exit function
892  end if
893 
894  return cAssignmentOrPtrCallEx( expr )
895  end if
896  end if
897 
898  '' global namespace access..
899  chain_ = cIdentifier( base_parent, FB_IDOPT_DEFAULT or FB_IDOPT_ALLOWSTRUCT )
900  if( chain_ <> NULL ) then
901  return hAssignOrCall( base_parent, chain_, FALSE )
902  end if
903  end if
904 
905  end select
906 
907 end function
908 
910  dim as FBSYMBOL ptr proc = any, parent = any, this_ = any, ctor_head = any
911  dim as ASTNODE ptr this_expr = any
912 
913  '' CONSTRUCTOR() chaining is only allowed inside constructors.
914  if( symbIsConstructor( parser.currproc ) = FALSE ) then
915  errReport( FB_ERRMSG_ILLEGALOUTSIDEACTOR )
916  '' error recovery: skip stmt, return
917  hSkipStmt( )
918  exit sub
919  end if
920 
921  parent = symbGetNamespace( parser.currproc )
922 
923  '' A CONSTRUCTOR() chain call replaces a constructor's initialization
924  '' code, so it's only allowed at the top. Is there already another
925  '' statement (including CONSTRUCTOR()), or maybe a BASE() initializer?
926  '' (BASE() is pointless combined with CONSTRUCTOR() chaining, since
927  '' it will be unused)
928  if( (astFindFirstCode( ast.proc.curr ) <> NULL) or _
929  (parser.currproc->proc.ext->base_initree <> NULL) ) then
930  errReport( FB_ERRMSG_CTORCHAINMUSTBEFIRST )
931  end if
932 
933  '' Tell astProcEnd() to omit the default init code at the top of ctors
934  symbSetIsCtorInited( parser.currproc )
935 
936  '' CONSTRUCTOR
937  lexSkipToken( )
938 
939  cProcCall( NULL, symbGetCompCtorHead( parent ), NULL, _
940  astBuildInstPtr( symbGetParamVar( symbGetProcHeadParam( parser.currproc ) ) ) )
941 end sub
942 
943 '' BaseInit = BASE (CtorCall | Initializer)
944 sub hBaseInit( )
945  dim as FBSYMBOL ptr parent = any, base_ = any, subtype = any
946  dim as ASTNODE ptr initree = any, ctorcall = any
947 
948  '' BASE() is only allowed inside constructors...
949  if( symbIsConstructor( parser.currproc ) = FALSE ) then
950  errReport( FB_ERRMSG_ILLEGALOUTSIDEACTOR )
951  '' error recovery: skip stmt, return
952  hSkipStmt( )
953  exit sub
954  end if
955 
956  '' ...and only if there even is a base UDT.
957  base_ = symbGetNamespace( parser.currproc )->udt.base
958  if( base_ = NULL ) then
959  errReport( FB_ERRMSG_CLASSNOTDERIVED )
960  '' error recovery: skip stmt, return
961  hSkipStmt( )
962  exit sub
963  end if
964 
965  '' We expect BASE() to appear as the first statement. The base ctor
966  '' cannot be called in the same place where BASE() was given, anyways --
967  '' it must be inserted above the other implicit ctorinit code at the
968  '' top of the constructor, to ensure the vtbl pointer is initialized in
969  '' the proper order.
970 
971  '' Is there another statement already (including CONSTRUCTOR()), or
972  '' another BASE()?
973  if( (astFindFirstCode( ast.proc.curr ) <> NULL) or _
974  (parser.currproc->proc.ext->base_initree <> NULL) ) then
975  errReport( FB_ERRMSG_BASEINITMUSTBEFIRST )
976  '' error recovery: skip stmt, return
977  hSkipStmt( )
978  exit sub
979  end if
980 
981  '' BASE
982  lexSkipToken( )
983 
984  subtype = symbGetSubtype( base_ )
985  initree = NULL
986 
987  '' Has a ctor?
988  if( symbGetCompCtorHead( subtype ) ) then
989  '' CtorCall
990  ctorcall = cCtorCall( subtype )
991  if( ctorcall ) then
992  '' Will be a CTORCALL except in case of error recovery
993  if( astIsCALLCTOR( ctorcall ) ) then
994  '' cCtorCall() created a temporary object to
995  '' call the constructor on, we delete it though:
996  ctorcall = astCALLCTORToCALL( ctorcall )
997 
998  '' Turn the ctorcall into an initree
999  initree = astTypeIniBegin( FB_DATATYPE_STRUCT, subtype, TRUE )
1000  astTypeIniAddCtorCall( initree, base_, ctorcall )
1001  astTypeIniEnd( initree, TRUE )
1002  else
1003  astDelTree( ctorcall )
1004  ctorcall = NULL
1005  end if
1006  end if
1007  else
1008  '' Initializer
1009  initree = cInitializer( base_, FB_INIOPT_ISINI )
1010  end if
1011 
1012  parser.currproc->proc.ext->base_initree = initree
1013 end sub
1014 
1015 '' BaseMemberAccess = (BASE '.')+ ID
1016 function hBaseMemberAccess( ) as integer
1017  var proc = parser.currproc
1018 
1019  '' not inside a method?
1020  if( symbIsMethod( proc ) = FALSE ) then
1021  errReport( FB_ERRMSG_ILLEGALOUTSIDEAMETHOD )
1022  '' error recovery: skip stmt, return
1023  hSkipStmt( )
1024  return TRUE
1025  end if
1026 
1027  var parent = symbGetNamespace( proc )
1028 
1029  '' is class derived?
1030  var base_ = parent->udt.base
1031 
1032  do
1033  if( base_ = NULL ) then
1034  errReport( FB_ERRMSG_CLASSNOTDERIVED )
1035  '' error recovery: skip stmt, return
1036  hSkipStmt( )
1037  return TRUE
1038  end if
1039 
1040  '' skip BASE
1041  lexSkipToken( LEXCHECK_NOPERIOD )
1042 
1043  '' skip '.'
1044  lexSkipToken()
1045 
1046  '' (BASE '.')?
1047  if( lexGetToken() <> FB_TK_BASE ) then
1048  exit do
1049  end if
1050 
1051  '' '.'
1052  if( lexGetLookAhead( 1 ) <> CHAR_DOT ) then
1053  errReport( FB_ERRMSG_EXPECTEDPERIOD )
1054  '' error recovery: skip stmt, return
1055  hSkipStmt( )
1056  return TRUE
1057  end if
1058 
1059  base_ = symbGetSubtype( base_ )->udt.base
1060  loop
1061 
1062  dim as FBSYMCHAIN chain_ = (base_, NULL, FALSE)
1063  function = hAssignOrCall( symbGetSubType( base_ ), @chain_, FALSE, FB_PARSEROPT_EXPLICITBASE )
1064 end function
1065 
1066 function hForwardCall( ) as integer
1067  function = FALSE
1068 
1069  select case lexGetClass( )
1070  case FB_TKCLASS_IDENTIFIER
1071  if( fbLangOptIsSet( FB_LANG_OPT_PERIODS ) ) then
1072  '' if inside a namespace, symbols can't contain periods (.)'s
1073  if( symbIsGlobalNamespc( ) = FALSE ) then
1074  if( lexGetPeriodPos( ) > 0 ) then
1075  errReport( FB_ERRMSG_CANTINCLUDEPERIODS )
1076  end if
1077  end if
1078  end if
1079 
1080  case else
1081  errReport( FB_ERRMSG_EXPECTEDIDENTIFIER )
1082  '' error recovery: skip until next '('
1083  hSkipUntil( CHAR_LPRNT )
1084  exit function
1085  end select
1086 
1087  dim as string id = *lexGetText( )
1088 
1089  if( lexGetType( ) <> FB_DATATYPE_INVALID ) then
1090  errReport( FB_ERRMSG_SYNTAXERROR )
1091  end if
1092 
1093  lexSkipToken( )
1094 
1095  dim as FBSYMBOL ptr proc = symbPreAddProc( id )
1096 
1097  '' '('?
1098  dim as integer check_prnt = FALSE
1099  if( lexGetToken( ) = CHAR_LPRNT ) then
1100  lexSkipToken( )
1101  check_prnt = TRUE
1102  end if
1103 
1104  dim as FB_CALL_ARG_LIST arg_list = ( 0, NULL, NULL )
1105 
1106  do
1107  dim as ASTNODE ptr expr = cExpression( )
1108  if( expr = NULL ) then
1109  exit do
1110  end if
1111 
1112  dim as FB_PARAMMODE mode = FB_PARAMMODE_BYREF
1113 
1114  '' ('('')')?
1115  if( lexGetToken( ) = CHAR_LPRNT ) then
1116  if( lexGetLookAhead( 1 ) = CHAR_RPRNT ) then
1117  lexSkipToken( )
1118  lexSkipToken( )
1119  mode = FB_PARAMMODE_BYDESC
1120  end if
1121  end if
1122 
1123  ''
1124  dim as integer dtype = FB_DATATYPE_VOID
1125  select case astGetDataType( expr )
1126  case FB_DATATYPE_STRING, FB_DATATYPE_FIXSTR, _
1127  FB_DATATYPE_CHAR, FB_DATATYPE_WCHAR
1128  dtype = FB_DATATYPE_STRING
1129  end select
1130 
1131  if( symbAddProcParam( proc, NULL, dtype, NULL, mode, 0 ) = NULL ) then
1132  exit do
1133  end if
1134 
1135  dim as FB_CALL_ARG ptr arg = symbAllocOvlCallArg( @parser.ovlarglist, @arg_list, FALSE )
1136  arg->expr = expr
1137  arg->mode = INVALID
1138 
1139  '' ','
1140  if( lexGetToken( ) <> CHAR_COMMA ) then
1141  exit do
1142  end if
1143 
1144  lexSkipToken( )
1145  loop
1146 
1147  '' ')'?
1148  if( check_prnt ) then
1149  if( lexGetToken( ) <> CHAR_RPRNT ) then
1150  errReport( FB_ERRMSG_EXPECTEDRPRNT )
1151  '' error recovery: skip until ')'
1152  hSkipUntil( CHAR_RPRNT, TRUE )
1153  else
1154  lexSkipToken( )
1155  end if
1156  end if
1157 
1158  proc = symbAddProc( proc, id, NULL, FB_DATATYPE_VOID, NULL, 0, env.target.fbcall, FB_SYMBOPT_NONE )
1159  if( proc = NULL ) then
1160  errReport( FB_ERRMSG_DUPDEFINITION, TRUE )
1161  exit function
1162  end if
1163 
1164  ''
1165  dim as ASTNODE ptr procexpr = cProcArgList( NULL, _
1166  proc, _
1167  NULL, _
1168  @arg_list, _
1169  FB_PARSEROPT_OPTONLY )
1170  if( procexpr <> NULL ) then
1171  astAdd( procexpr )
1172  end if
1173 
1174  function = TRUE
1175 
1176 end function
1177