FreeBASIC  0.91.0
ast-node-scope.bas
Go to the documentation of this file.
1 '' AST scope and break nodes
2 '' scope: l = NULL; r = NULL
3 '' break: l = branch (used as reference, not loaded)
4 ''
5 '' chng: mar/2006 written [v1ctor]
6 
7 
8 #include once "fb.bi"
9 #include once "fbint.bi"
10 #include once "lex.bi"
11 #include once "parser.bi"
12 #include once "ast.bi"
13 #include once "ir.bi"
14 
15 declare function hCheckBranch _
16  ( _
17  byval proc as ASTNODE ptr, _
18  byval n as ASTNODE ptr _
19  ) as integer
20 
21 declare sub hDelLocals _
22  ( _
23  byval n as ASTNODE ptr, _
24  byval check_backward as integer _
25  )
26 
27 function astScopeBegin( ) as ASTNODE ptr
28  dim as ASTNODE ptr n = any
29  dim as FBSYMBOL ptr s = any
30 
31  if( parser.scope >= FB_MAXSCOPEDEPTH ) then
32  return NULL
33  end if
34 
35  n = astNewNode( AST_NODECLASS_SCOPEBEGIN, FB_DATATYPE_INVALID )
36 
37  '' Assuming the astAdd() adds the SCOPEBEGIN without reallocating it
38  '' or similar, because it's still referenced afterwards!
39  '' astAdd() could theoretically LINK it with other statements though,
40  '' that's why we can't use "n = astAdd( n )".
41  astAdd( n )
42 
43  s = symbAddScope( n )
44 
45  '' change to scope's symbol tb
46  n->sym = s
47  n->block.parent = ast.currblock
48  n->block.inistmt = parser.stmt.cnt
49 
50  '' must update the stmt count or any internal label
51  '' allocated/emitted previously will lie in the same stmt
52  parser.stmt.cnt += 1
53 
54  ''
55  parser.scope += 1
56  parser.currblock = s
57  ast.currblock = n
58 
59  symbSetCurrentSymTb( @s->scp.symtb )
60 
61  ''
62  irScopeBegin( s )
63 
64  ''
65  astAdd( astNewDBG( AST_OP_DBG_SCOPEINI, cint( s ) ) )
66 
67  function = n
68 end function
69 
70 sub hAddToBreakList _
71  ( _
72  byval list as AST_BREAKLIST ptr, _
73  byval node as ASTNODE ptr _
74  )
75 
76  if( list->tail <> NULL ) then
77  list->tail->next = node
78  else
79  list->head = node
80  end if
81 
82  node->prev = list->tail
83  node->next = NULL
84  list->tail = node
85 
86 end sub
87 
88 sub astScopeBreak( byval target as FBSYMBOL ptr )
89  dim as ASTNODE ptr n = any
90 
91  n = astNewNode( AST_NODECLASS_SCOPE_BREAK, FB_DATATYPE_INVALID, NULL )
92 
93  n->sym = target
94  n->break.parent = ast.currblock
95  n->break.scope = parser.scope
96  n->break.linenum = lexLineNum( )
97  n->break.stmtnum = parser.stmt.cnt
98 
99  '' the branch node is added, not the break itself, any
100  '' destructor will be added before this node when
101  '' processing the proc's branch list
102  '' Same concerns apply as for the astAdd() of SCOPEBEGIN above
103  n->l = astNewBRANCH( AST_OP_JMP, target )
104  astAdd( n->l )
105 
106  hAddToBreakList( @ast.proc.curr->block.breaklist, n )
107 end sub
108 
109 sub astScopeEnd( byval n as ASTNODE ptr )
110  dim as FBSYMBOL ptr s = any
111 
112  assert( n->class = AST_NODECLASS_SCOPEBEGIN )
113 
114  s = n->sym
115 
116  '' must update the stmt count or any internal label
117  '' allocated/emitted previously will lie in the same stmt
118  parser.stmt.cnt += 1
119 
120  n->block.endstmt = parser.stmt.cnt
121 
122  astScopeDestroyVars(symbGetScopeSymbTb(s).tail)
123 
124  '' remove symbols from hash table
125  symbDelScopeTb( s )
126 
127  irScopeEnd( s )
128 
129  '' back to preview symbol tb
130  symbSetCurrentSymTb( s->symtb )
131 
132  ast.currblock = n->block.parent
133  parser.currblock = ast.currblock->sym
134  parser.scope -= 1
135 
136  astAdd( astNewDBG( AST_OP_DBG_SCOPEEND, cint( s ) ) )
137 
138  n = astNewNode( AST_NODECLASS_SCOPEEND, FB_DATATYPE_INVALID )
139 
140  '' Same concerns apply as for the astAdd() of SCOPEBEGIN above
141  astAdd( n )
142 
143  n->sym = s
144 end sub
145 
146 function astScopeUpdBreakList( byval proc as ASTNODE ptr ) as integer
147  dim as ASTNODE ptr n = any
148 
149  function = FALSE
150 
151  '' for each break in this proc..
152  n = proc->block.breaklist.head
153  do while( n <> NULL )
154 
155  '' EXIT SUB | FUNCTION?
156  if( n->sym = proc->block.exitlabel ) then
157  '' special case due the non implicit scope block, that
158  '' can't be created for procs because the implicit
159  '' main() function
160  hDelLocals( n, FALSE )
161 
162  else
163  if( hCheckBranch( proc, n ) = FALSE ) then
164  exit function
165  end if
166  end if
167 
168  '' next
169  n = n->next
170  loop
171 
172  function = TRUE
173 end function
174 
175 '':::::
176 sub hBranchError _
177  ( _
178  byval errnum as integer, _
179  byval n as ASTNODE ptr, _
180  byval s as FBSYMBOL ptr = NULL _
181  ) static
182 
183  dim as integer showerror
184  dim as string msg
185 
186  showerror = env.clopt.showerror
187  env.clopt.showerror = FALSE
188 
189  if( symbGetName( n->sym ) <> NULL ) then
190  msg = "to label: " + *symbGetName( n->sym )
191  if( s <> NULL ) then
192  msg += ", "
193  end if
194  end if
195 
196  if( s <> NULL ) then
197  msg += "local "
198  if( symbGetType( s ) = FB_DATATYPE_STRING ) then
199  msg += "string: "
200  elseif( symbGetArrayDimensions( s ) <> 0 ) then
201  msg += "array: "
202  else
203  msg += "object: "
204  end if
205 
206  msg += *symbGetName( s )
207  end if
208 
209  errReportEx( errnum, msg, n->break.linenum )
210 
211  env.clopt.showerror = showerror
212 end sub
213 
214 '':::::
215 sub hBranchWarning _
216  ( _
217  byval errnum as integer, _
218  byval n as ASTNODE ptr, _
219  byval s as FBSYMBOL ptr = NULL _
220  ) static
221 
222  dim as integer showerror
223  dim as string msg
224 
225  showerror = env.clopt.showerror
226  env.clopt.showerror = FALSE
227 
228  if( symbGetName( n->sym ) <> NULL ) then
229  msg = "to label: " + *symbGetName( n->sym )
230  if( s <> NULL ) then
231  msg += ", "
232  end if
233  end if
234 
235  if( s <> NULL ) then
236  msg += "variable: "
237  msg += *symbGetName( s )
238  end if
239 
240  errReportWarnEx( errnum, msg, n->break.linenum )
241 
242  env.clopt.showerror = showerror
243 
244 end sub
245 
246 '':::::
247 function hFindCommonParent _
248  ( _
249  byval branch_parent as ASTNODE ptr, _
250  byval label_parent_sym as FBSYMBOL ptr _
251  ) as FBSYMBOL ptr
252 
253  dim as ASTNODE ptr label_parent = label_parent_sym->scp.backnode
254 
255  dim as integer branch_scope = symbGetScope( branch_parent->sym )
256  dim as integer label_scope = symbGetScope( label_parent_sym )
257 
258  if( branch_scope > label_scope ) then
259  do
260  branch_parent = branch_parent->block.parent
261  branch_scope = symbGetScope( branch_parent->sym )
262  loop until( branch_scope = label_scope )
263 
264  elseif( branch_scope < label_scope ) then
265  do
266  label_parent = label_parent->block.parent
267  label_scope = symbGetScope( label_parent->sym )
268  loop until( label_scope = branch_scope )
269  end if
270 
271  do until( branch_parent = label_parent )
272  branch_parent = branch_parent->block.parent
273  label_parent = label_parent->block.parent
274  loop
275 
276  function = branch_parent->sym
277 
278 end function
279 
280 sub hCheckCrossing _
281  ( _
282  byval n as ASTNODE ptr, _
283  byval blk as FBSYMBOL ptr, _
284  byval top_stmt as integer, _
285  byval bot_stmt as integer _
286  )
287 
288  dim as FBSYMBOL ptr s = any
289  dim as integer stmt = any
290 
291  '' search for:
292  '' goto label
293  '' redim array(...) as type | dim obj as object() | dim str as string
294  '' label:
295 
296  if( symbIsScope( blk ) ) then
297  s = symbGetScopeSymbtb( blk ).head
298  else
299  s = symbGetProcSymbtb( blk ).head
300  end if
301 
302  do while( s <> NULL )
303  if( symbIsVar( s ) ) then
304  stmt = symbGetVarStmt( s )
305  if( stmt > top_stmt ) then
306  if( stmt < bot_stmt ) then
307  if( symbGetVarHasCtor( s ) ) then
308  hBranchError( FB_ERRMSG_BRANCHCROSSINGDYNDATADEF, n, s )
309 
310  else
311  '' not static, shared or temp?
312  if( (s->attrib and (FB_SYMBATTRIB_STATIC or _
313  FB_SYMBATTRIB_SHARED or _
314  FB_SYMBATTRIB_TEMP)) = 0 ) then
315  '' must be cleaned?
316  if( symbGetDontInit( s ) = FALSE ) then
317  hBranchWarning( FB_WARNINGMSG_BRANCHCROSSINGLOCALVAR, n, s )
318  end if
319  end if
320  end if
321  end if
322  end if
323  end if
324 
325  s = s->next
326  loop
327 end sub
328 
329 sub hCheckScopeLocals _
330  ( _
331  byval n as ASTNODE ptr, _
332  byval top_parent as FBSYMBOL ptr = NULL _
333  )
334 
335  dim as FBSYMBOL ptr label = any, blk = any
336  dim as integer label_stmt = any, branch_stmt = any
337 
338  if( top_parent = NULL ) then
339  top_parent = n->break.parent->sym
340  end if
341 
342  branch_stmt = n->break.stmtnum
343 
344  label = n->sym
345  label_stmt = symbGetLabelStmt( label )
346 
347  blk = symbGetLabelParent( label )
348  do
349  '' check for any var allocated between the block's
350  '' beginning and the branch
351  hCheckCrossing( n, blk, 0, label_stmt )
352 
353  if( symbGetSymbtb( blk ) = NULL ) then
354  exit do
355  end if
356 
357  blk = symbGetParent( blk )
358 
359  '' same parent?
360  if( blk = top_parent ) then
361  '' forward?
362  if( label_stmt > branch_stmt ) then
363  hCheckCrossing( n, blk, branch_stmt, label_stmt )
364  end if
365  exit do
366  end if
367  loop
368 end sub
369 
370 '':::::
372  ( _
373  byval blk as FBSYMBOL ptr, _
374  byval top_stmt as integer, _
375  byval bot_stmt as integer, _
376  byval base_expr as ASTNODE ptr _ '' the node before the branch, not itself!
377  )
378 
379  dim as FBSYMBOL ptr s = any
380  dim as ASTNODE ptr expr = any
381  dim as integer stmt = any
382 
383  '' for each now (in reverse order)
384  if( symbIsScope( blk ) ) then
385  s = symbGetScopeSymbTb( blk ).tail
386  else
387  s = symbGetProcSymbTb( blk ).tail
388  end if
389 
390  do while( s <> NULL )
391  if( symbIsVar( s ) ) then
392  stmt = symbGetVarStmt( s )
393  if( stmt > top_stmt ) then
394  if( stmt < bot_stmt ) then
395  '' has a dtor?
396  if( symbGetVarHasDtor( s ) ) then
397  '' call it..
398  expr = astBuildVarDtorCall( s, TRUE )
399  if( expr <> NULL ) then
400  base_expr = astAddAfter( expr, base_expr )
401  end if
402  end if
403  end if
404  end if
405  end if
406 
407  s = s->prev
408  loop
409 
410 end sub
411 
412 '':::::
413 sub hDelBackwardLocals _
414  ( _
415  byval n as ASTNODE ptr _
416  )
417 
418  '' free any dyn var allocated between the block's
419  '' beginning and the branch
420  hDestroyBlockLocals( n->break.parent->sym, _
421  symbGetLabelStmt( n->sym ), _
422  n->break.stmtnum, _
423  astGetPrev( n->l ) )
424 
425 end sub
426 
427 
428 #define hisInside( blk, lbl_stmt ) _
429  ( (lbl_stmt) >= (blk)->block.inistmt andalso (lbl_stmt) < (blk)->block.endstmt)
430 
431 
432 '':::::
433 sub hDelLocals _
434  ( _
435  byval n as ASTNODE ptr, _
436  byval check_backward as integer _
437  )
438 
439  dim as FBSYMBOL ptr s = any
440  dim as integer label_stmt = any, branch_stmt = any
441  dim as ASTNODE ptr blk = any
442 
443  label_stmt = symbGetLabelStmt( n->sym )
444  branch_stmt = n->break.stmtnum
445 
446  '' for each parent (starting from the branch ones)
447  blk = n->break.parent
448  do
449  '' destroy any var created between the beginning of
450  '' the block and the branch
451  hDestroyBlockLocals( blk->sym, _
452  0, _
453  branch_stmt, _
454  astGetPrev( n->l ) ) '' prev node will change
455 
456  blk = blk->block.parent
457  if( blk = NULL ) then
458  exit do
459  end if
460 
461  '' target label found?
462  if( hIsInside( blk, label_stmt ) ) then
463  if( check_backward ) then
464  '' if backward, free any dyn var allocated
465  '' between the target label and the branch
466  if( label_stmt <= branch_stmt ) then
467  hDestroyBlockLocals( blk->sym, _
468  label_stmt, _
469  branch_stmt, _
470  astGetPrev( n->l ) )
471  end if
472  end if
473 
474  exit do
475  end if
476  loop
477 
478 end sub
479 
480 '':::::
481 function hIsTargetOutside _
482  ( _
483  byval proc as FBSYMBOL ptr, _
484  byval label as FBSYMBOL ptr _
485  ) as integer
486 
487  '' main?
488  if( (proc->stats and (FB_SYMBSTATS_MAINPROC or _
489  FB_SYMBSTATS_MODLEVELPROC)) <> 0 ) then
490 
491  function = symbGetParent( label ) <> @symbGetGlobalNamespc( )
492 
493  else
494  function = symbGetParent( label ) <> proc
495  end if
496 
497 end function
498 
499 '':::::
500 function hCheckBranch _
501  ( _
502  byval proc as ASTNODE ptr, _
503  byval n as ASTNODE ptr _
504  ) as integer
505 
506  dim as ASTNODE ptr branch_parent = any
507  dim as FBSYMBOL ptr label = any, label_parent = any
508  dim as integer branch_scope = any, label_scope = any
509  dim as integer branch_stmt = any, label_stmt = any, isparent = any
510 
511  function = FALSE
512 
513  label = n->sym
514 
515  '' not declared?
516  if( symbGetLabelIsDeclared( label ) = FALSE ) then
517  hBranchError( FB_ERRMSG_BRANCHTARGETOUTSIDECURRPROC, n )
518  exit function
519  end if
520 
521  '' branching to other procs or mod-level?
522  if( hIsTargetOutside( proc->sym, label ) ) then
523  hBranchError( FB_ERRMSG_BRANCHTARGETOUTSIDECURRPROC, n )
524  exit function
525  end if
526 
527  ''
528  label_scope = symbGetScope( label )
529  label_parent = symbGetLabelParent( label )
530  label_stmt = symbGetLabelStmt( label )
531 
532  branch_scope = n->break.scope
533  branch_parent = n->break.parent
534  branch_stmt = n->break.stmtnum
535 
536  '' inside parent?
537  if( hIsInside( branch_parent, label_stmt ) ) then
538  '' jumping to a child block?
539  if( label_scope > branch_scope ) then
540  '' any locals?
541  hCheckScopeLocals( n )
542 
543  '' backward?
544  if( label_stmt <= branch_stmt ) then
545  hDelBackwardLocals( n )
546  end if
547 
548  '' same level..
549  else
550  '' backward?
551  if( label_stmt <= branch_stmt ) then
552  hDelBackwardLocals( n )
553 
554  '' forward..
555  else
556  '' crossing any declaration?
557  hCheckCrossing( n, label_parent, branch_stmt, label_stmt )
558  end if
559  end if
560 
561  return TRUE
562  end if
563 
564  '' outside..
565 
566  '' jumping to a scope block?
567  if( symbIsScope( label_parent ) ) then
568  isparent = (label_parent->scp.backnode->block.inistmt <= _
569  branch_parent->block.inistmt) and _
570  (label_parent->scp.backnode->block.endstmt >= _
571  branch_parent->block.endstmt)
572 
573  '' not a parent block?
574  if( isparent = FALSE ) then
575  '' any locals?
576  hCheckScopeLocals( n, hFindCommonParent( branch_parent, label_parent ) )
577  end if
578 
579  '' proc level..
580  else
581  isparent = TRUE
582  end if
583 
584  if( isparent ) then
585  '' forward?
586  if( label_stmt > branch_stmt ) then
587  '' crossing any declaration?
588  hCheckCrossing( n, label_parent, branch_stmt, label_stmt )
589  end if
590  end if
591 
592  '' jumping out, free any dyn var already allocated
593  '' until the target block if reached
594  hDelLocals( n, TRUE )
595 
596  function = TRUE
597 
598 end function
599 
600 sub astScopeDestroyVars( byval symtbtail as FBSYMBOL ptr )
601  dim as FBSYMBOL ptr s = any
602 
603  '' For each symbol declared inside the block (in reverse order)
604  s = symtbtail
605  while( s )
606  '' variable?
607  if( symbIsVar( s ) ) then
608  '' has a dtor?
609  if( symbGetVarHasDtor( s ) ) then
610  astAdd( astBuildVarDtorCall( s, TRUE ) )
611  end if
612  end if
613  s = s->prev
614  wend
615 end sub
616 
617 sub astScopeAllocLocals( byval symtbhead as FBSYMBOL ptr )
618  dim as FBSYMBOL ptr s = any
619 
620  '' Emit/allocate variables local to a procedure or scope block
621  assert( ast.doemit )
622 
623  s = symtbhead
624  if( env.clopt.backend = FB_BACKEND_GCC ) then
625  ''
626  '' C backend: Most locals (including statics) are emitted from
627  '' astLoadDECL(), assuming they have DECL nodes, so they will
628  '' start shadowing variables from parent scopes not earlier
629  '' than they should.
630  ''
631  '' Behind the scenes, statics with dtors are actually emitted
632  '' during irProcAllocStaticVars() because they're special:
633  '' They're emitted as globals so the dtor wrappers can see them.
634  ''
635  '' The only cases of locals that don't have DECL nodes seem to
636  '' be temp vars. Since their names are unique, there's no
637  '' problem with var shadowing and we can emit them all at the
638  '' top of the scope from here.
639  ''
640  while( s )
641  '' temp var?
642  if( symbIsVar( s ) and symbIsTemp( s ) ) then
643  assert( (symbIsShared( s ) = FALSE) and (symbIsParam( s ) = FALSE) )
644  '' Fake a DECL to emit the variable declaration
645  irEmitDECL( s )
646  end if
647  s = s->next
648  wend
649  else
650  ''
651  '' ASM backend: All locals except statics or shared vars
652  '' are allocated from here (i.e. the backend reserves the stack
653  '' space for them). Parameters are allocated from here too.
654  ''
655  '' statics are handled by irProcAllocStaticVars() later.
656  ''
657  while( s )
658  '' non-shared/static variable?
659  if( symbIsVar( s ) and ((symbGetAttrib( s ) and (FB_SYMBATTRIB_SHARED or FB_SYMBATTRIB_STATIC)) = 0) ) then
660  '' Procedure parameter?
661  if( symbIsParam( s ) ) then
662  irProcAllocArg( parser.currproc, s )
663  else
664  irProcAllocLocal( parser.currproc, s )
665  end if
666  symbSetVarIsAllocated( s )
667  end if
668  s = s->next
669  wend
670  end if
671 end sub
672 
673 function astLoadSCOPEBEGIN( byval n as ASTNODE ptr ) as IRVREG ptr
674  dim as FBSYMBOL ptr s = any
675 
676  s = n->sym
677 
678  s->scp.emit.baseofs = symbGetProcLocalOfs( parser.currproc )
679 
680  if( ast.doemit ) then
681  irEmitSCOPEBEGIN( s )
682  astScopeAllocLocals( symbGetScopeSymbTbHead( s ) )
683  end if
684 
685  function = NULL
686 end function
687 
688 function astLoadSCOPEEND( byval n as ASTNODE ptr ) as IRVREG ptr
689  dim as FBSYMBOL ptr s = any
690 
691  s = n->sym
692 
693  if( ast.doemit ) then
694  irEmitSCOPEEND( s )
695  end if
696 
697  symbSetProcLocalOfs( parser.currproc, s->scp.emit.baseofs )
698 
699  function = NULL
700 end function
701 
702 ''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
703 '' Temporary scopes used by TYPEINIs to capture any temp symbols, so that they
704 '' can be duplicated into other scope contexts
705 '' (needed for field/parameter/global var initializer expressions)
706 
707 function astTempScopeBegin _
708  ( _
709  byref lastscp as FBSYMBOL ptr, _
710  byval backnode as ASTNODE ptr _
711  ) as FBSYMBOL ptr
712 
713  dim as FBSYMBOL ptr scp = any
714 
715  scp = symbAddScope( backnode )
716 
717  lastscp = parser.currblock
718 
719  parser.scope += 1
720  parser.currblock = scp
721 
722  symbSetCurrentSymTb( @scp->scp.symtb )
723 
724  function = scp
725 end function
726 
727 sub astTempScopeEnd _
728  ( _
729  byval scp as FBSYMBOL ptr, _
730  byval lastscp as FBSYMBOL ptr _
731  )
732 
733  dim as FBSYMBOL ptr sym = any
734 
735  '' remove symbols from hash table
736  symbDelScopeTb( scp )
737 
738  '' back to previous symbol tb
739  symbSetCurrentSymTb( scp->symtb )
740 
742 
743  parser.currblock = lastscp
744  parser.scope -= 1
745 
746  '' Unregister any temp var dtor calls
747  '' (astTempScopeClone() will re-add them in the new context)
748  sym = symbGetScopeSymbTbHead( scp )
749  while( sym )
750  if( symbIsVar( sym ) ) then
751  astDtorListDel( sym )
752  end if
753  sym = sym->next
754  wend
755 
756 end sub
757 
758 sub astTempScopeClone _
759  ( _
760  byval scp as FBSYMBOL ptr, _
761  byval clonetree as ASTNODE ptr _
762  )
763 
764  dim as FBSYMBOL ptr sym = any, clonesym = any
765 
766  '' Duplicate any symbols from the temp scope into the current context
767  sym = symbGetScopeSymbTbHead( scp )
768  while( sym )
769  clonesym = symbCloneSymbol( sym )
770 
771  '' Update the corresponding expression tree
772  astReplaceSymbolOnTree( clonetree, sym, clonesym )
773 
774  '' Re-register temp var dtors in the current context
775  if( symbIsVar( clonesym ) ) then
776  astDtorListAdd( clonesym )
777  end if
778 
779  sym = sym->next
780  wend
781 
782 end sub
783 
784 sub astTempScopeDelete( byval scp as FBSYMBOL ptr )
785  dim as FBSYMBOL ptr sym = any, nxt = any
786 
787  sym = symbGetScopeSymbTbHead( scp )
788  while( sym )
789  nxt = sym->next
791  sym = nxt
792  wend
793 
795 end sub
796