FreeBASIC  0.91.0
error.bas
Go to the documentation of this file.
1 '' error reporting module
2 ''
3 ''
4 
5 #include once "fb.bi"
6 #include once "fbint.bi"
7 #include once "ir.bi"
8 #include once "lex.bi"
9 #include once "parser.bi"
10 #include once "hash.bi"
11 
13  '' While an argument location is pushed,
14  '' errors will be reported "at parameter N of F()"
15  proc as FBSYMBOL ptr
16  tk as integer
17  paramnum as integer
18  paramid as zstring ptr
19 end type
20 
22  inited as integer
23  cnt as integer
25  lastline as integer
26  laststmt as integer
27  undefhash as THASH '' undefined symbols
28  paramlocations as TLIST '' ERRPARAMLOCATION's
29 end type
30 
32  level as integer
33  text as const zstring ptr
34 end type
35 
36 declare function hMakeParamDesc _
37  ( _
38  byval msgex as const zstring ptr _
39  ) as const zstring ptr
40 
41 ''globals
42  dim shared errctx as FB_ERRCTX
43 
44  dim shared warningMsgs( 1 to FB_WARNINGMSGS-1 ) as FBWARNING = _
45  { _
46  ( 1, @"Passing scalar as pointer" ), _
47  ( 1, @"Passing pointer to scalar" ), _
48  ( 1, @"Passing different pointer types" ), _
49  ( 1, @"Suspicious pointer assignment" ), _
50  ( 0, @"Implicit conversion" ), _
51  ( 1, @"Cannot export symbol without -export option" ), _
52  ( 1, @"Identifier's name too big, truncated" ), _
53  ( 1, @"Literal number too big, truncated" ), _
54  ( 1, @"Literal string too big, truncated" ), _
55  ( 0, @"UDT with pointer or var-len string fields" ), _
56  ( 0, @"Implicit variable allocation" ), _
57  ( 0, @"Missing closing quote in literal string" ), _
58  ( 0, @"Function result was not explicitly set" ), _
59  ( 1, @"Branch crossing local variable definition" ), _
60  ( 0, @"No explicit BYREF or BYVAL" ), _
61  ( 0, @"Possible escape sequence found in" ), _
62  ( 0, @"The type length is too large, consider passing BYREF" ), _
63  ( 1, @"The length of the parameters list is too large, consider passing UDT's BYREF" ), _
64  ( 1, @"The ANY initializer has no effect on UDT's with default constructors" ), _
65  ( 2, @"Object files or libraries with mixed multithreading (-mt) options" ), _
66  ( 2, @"Object files or libraries with mixed language (-lang) options" ), _
67  ( 0, @"Deleting ANY pointers is undefined" ), _
68  ( 2, @"Array too large for stack, consider making it var-len or SHARED" ), _
69  ( 2, @"Variable too large for stack, consider making it SHARED" ), _
70  ( 0, @"Overflow in constant conversion" ), _
71  ( 0, @"Variable following NEXT is meaningless" ), _
72  ( 0, @"Cast to non-pointer" ), _
73  ( 0, @"Return method mismatch" ), _
74  ( 0, @"Passing Pointer" ), _
75  ( 0, @"Command line option overrides directive" ), _
76  ( 0, @"Directive ignored after first pass" ), _
77  ( 0, @"'IF' statement found directly after multi-line 'ELSE'" ), _
78  ( 0, @"Shift value greater than or equal to number of bits in data type" ), _
79  ( 0, @"'BYVAL AS STRING' actually behaves like 'BYREF AS ZSTRING' (this is hoped to change in future releases)" ), _
80  ( 0, @"'=' parsed as equality operator in function argument, not assignment to BYREF function result" ), _
81  ( 0, @"Mixing signed/unsigned operands" ), _
82  ( 0, @"Mismatching parameter initializer" ) _
83  }
84 
85  dim shared errorMsgs( 1 to FB_ERRMSGS-1 ) as const zstring ptr => _
86  { _
87  @"Argument count mismatch", _
88  @"Expected End-of-File", _
89  @"Expected End-of-Line", _
90  @"Duplicated definition", _
91  @"Expected 'AS'", _
92  @"Expected '('", _
93  @"Expected ')'", _
94  @"Undefined symbol", _
95  @"Expected expression", _
96  @"Expected '='", _
97  @"Expected constant", _
98  @"Expected 'TO'", _
99  @"Expected 'NEXT'", _
100  @"Expected identifier", _
101  @"Expected '-'", _
102  @"Expected ','", _
103  @"Syntax error", _
104  @"Element not defined", _
105  @"Expected 'END TYPE' or 'END UNION'", _
106  @"Type mismatch", _
107  @"Internal!", _
108  @"Parameter type mismatch", _
109  @"File not found", _
110  @"Invalid data types", _
111  @"Invalid character", _
112  @"File access error", _
113  @"Recursion level too deep", _
114  @"Expected pointer", _
115  @"Expected 'LOOP'", _
116  @"Expected 'WEND'", _
117  @"Expected 'THEN'", _
118  @"Expected 'END IF'", _
119  @"Illegal 'END'", _
120  @"Expected 'CASE'", _
121  @"Expected 'END SELECT'", _
122  @"Wrong number of dimensions", _
123  @"Array boundaries do not match the original EXTERN declaration", _
124  @"'SUB' or 'FUNCTION' without 'END SUB' or 'END FUNCTION'", _
125  @"Expected 'END SUB' or 'END FUNCTION'", _
126  @"Illegal parameter specification", _
127  @"Variable not declared", _
128  @"Variable required", _
129  @"Illegal outside a compound statement", _
130  @"Expected 'END ASM'", _
131  @"Function not declared", _
132  @"Expected ';'", _
133  @"Undefined label", _
134  @"Too many array dimensions", _
135  @"Array too big", _
136  @"User Defined Type too big", _
137  @"Expected scalar counter", _
138  @"Illegal outside a CONSTRUCTOR, DESTRUCTOR, FUNCTION, OPERATOR, PROPERTY or SUB block", _
139  @"Expected var-len array", _
140  @"Fixed-len strings cannot be returned from functions", _
141  @"Array already dimensioned", _
142  @"Illegal without the -ex option", _
143  @"Type mismatch", _
144  @"Illegal specification", _
145  @"Expected 'END WITH'", _
146  @"Illegal inside functions", _
147  @"Statement in between SELECT and first CASE", _
148  @"Expected array", _
149  @"Expected '{'", _
150  @"Expected '}'", _
151  @"Expected ']'", _
152  @"Too many expressions", _
153  @"Expected explicit result type", _
154  @"Range too large", _
155  @"Forward references not allowed", _
156  @"Incomplete type", _
157  @"Array not dimensioned", _
158  @"Array access, index expected", _
159  @"Expected 'END ENUM'", _
160  @"Var-len arrays cannot be initialized", _
161  @"Invalid bitfield", _
162  @"Too many parameters", _
163  @"Macro text too long", _
164  @"Invalid command-line option", _
165  @"Selected non-x86 CPU when compiling for DOS", _
166  @"Selected -gen gas ASM backend for non-x86 CPU", _
167  @"-asm att used for -gen gas, but -gen gas only supports -asm intel", _
168  @"Var-len strings cannot be initialized", _
169  @"Recursive TYPE or UNION not allowed", _
170  @"Recursive DEFINE not allowed", _
171  @"Array fields cannot be redimensioned", _
172  @"Identifier cannot include periods", _
173  @"Executable not found", _
174  @"Array out-of-bounds", _
175  @"Missing command-line option for", _
176  @"Expected 'ANY'", _
177  @"Expected 'END SCOPE'", _
178  @"Illegal inside a compound statement or scoped block", _
179  @"UDT function results cannot be passed by reference", _
180  @"Ambiguous call to overloaded function", _
181  @"No matching overloaded function", _
182  @"Division by zero", _
183  @"Cannot pop stack, underflow", _
184  @"UDT's containing var-len string fields cannot be initialized", _
185  @"Branching to scope block containing local variables", _
186  @"Branching to other functions or to module-level", _
187  @"Branch crossing local array, var-len string or object definition", _
188  @"LOOP without DO", _
189  @"NEXT without FOR", _
190  @"WEND without WHILE", _
191  @"END WITH without WITH", _
192  @"END IF without IF", _
193  @"END SELECT without SELECT", _
194  @"END SUB or FUNCTION without SUB or FUNCTION",_
195  @"END SCOPE without SCOPE", _
196  @"END NAMESPACE without NAMESPACE", _
197  @"END EXTERN without EXTERN", _
198  @"ELSEIF without IF", _
199  @"ELSE without IF", _
200  @"CASE without SELECT", _
201  @"Cannot modify a constant", _
202  @"Expected period ('.')", _
203  @"Expected 'END NAMESPACE'", _
204  @"Illegal inside a NAMESPACE block", _
205  @"Symbols defined inside namespaces cannot be removed", _
206  @"Expected 'END EXTERN'", _
207  @"Expected 'END SUB'", _
208  @"Expected 'END FUNCTION'", _
209  @"Expected 'END CONSTRUCTOR'", _
210  @"Expected 'END DESTRUCTOR'", _
211  @"Expected 'END OPERATOR'", _
212  @"Expected 'END PROPERTY'", _
213  @"Declaration outside the original namespace", _
214  @"No end of multi-line comment, expected ""'/""", _
215  @"Too many errors, exiting", _
216  @"Expected 'ENDMACRO'", _
217  @"EXTERN or COMMON variables cannot be initialized", _
218  @"At least one parameter must be a user-defined type", _
219  @"Parameter or result must be a user-defined type", _
220  @"Both parameters can't be of the same type", _
221  @"Parameter and result can't be of the same type", _
222  @"Invalid result type for this operator", _
223  @"Invalid parameter type, it must be the same as the parent TYPE/CLASS", _
224  @"Vararg parameters are not allowed in overloaded functions", _
225  @"Illegal outside an OPERATOR block", _
226  @"Parameter cannot be optional", _
227  @"Only valid in -lang", _
228  @"Default types or suffixes are only valid in -lang", _
229  @"Suffixes are only valid in -lang", _
230  @"Implicit variables are only valid in -lang", _
231  @"Auto variables are only valid in -lang", _
232  @"Invalid array index", _
233  @"Operator must be a member function", _
234  @"Operator cannot be a member function", _
235  @"Method declared in anonymous UDT", _
236  @"Constant declared in anonymous UDT", _
237  @"Static variable declared in anonymous UDT", _
238  @"Expected operator", _
239  @"Declaration outside the original namespace or class", _
240  @"A destructor should not have any parameters", _
241  @"Expected class or UDT identifier", _
242  @"Var-len strings cannot be part of UNION's or nested TYPE's", _
243  @"Fields with constructors cannot be part of UNION's or nested TYPE's", _
244  @"Fields with destructors cannot be part of UNION's or nested TYPE's", _
245  @"Illegal outside a CONSTRUCTOR block", _
246  @"Illegal outside a DESTRUCTOR block", _
247  @"UDT's with methods must have unique names", _
248  @"Parent is not a class or UDT", _
249  @"CONSTRUCTOR() chain call not at top of constructor", _
250  @"BASE() initializer not at top of constructor", _
251  @"REDIM on UDT with non-CDECL constructor", _
252  @"REDIM on UDT with non-CDECL destructor", _
253  @"REDIM on UDT with non-parameterless default constructor", _
254  @"ERASE on UDT with non-CDECL constructor", _
255  @"ERASE on UDT with non-CDECL destructor", _
256  @"ERASE on UDT with non-parameterless default constructor", _
257  @"This symbol cannot be undefined", _
258  @"RETURN mixed with 'FUNCTION =' or EXIT FUNCTION (using both styles together is unsupported when returning objects with constructors)", _
259  @"'FUNCTION =' or EXIT FUNCTION mixed with RETURN (using both styles together is unsupported when returning objects with constructors)", _
260  @"Missing RETURN to copy-construct function result", _
261  @"Invalid assignment/conversion", _
262  @"Invalid array subscript", _
263  @"TYPE or CLASS has no default constructor", _
264  @"Function result TYPE has no default constructor", _
265  @"Base UDT without default constructor; missing BASE() initializer", _
266  @"Base UDT without default constructor; missing default constructor implementation in derived UDT", _
267  @"Base UDT without default constructor; missing copy constructor implementation in derived UDT", _
268  @"Invalid priority attribute", _
269  @"PROPERTY GET should have no parameter, or just one if indexed", _
270  @"PROPERTY SET should have one parameter, or just two if indexed", _
271  @"Expected 'PROPERTY'", _
272  @"Illegal outside a PROPERTY block", _
273  @"PROPERTY has no GET method/accessor", _
274  @"PROPERTY has no SET method/accessor", _
275  @"PROPERTY has no indexed GET method/accessor", _
276  @"PROPERTY has no indexed SET method/accessor", _
277  @"Missing overloaded operator: ", _
278  @"The NEW[] operator does not allow explicit calls to constructors", _
279  @"The NEW[] operator only supports the { ANY } initialization", _
280  @"The NEW operator cannot be used with strings", _
281  @"Illegal member access", _
282  @"Expected ':'", _
283  @"The default constructor has no public access", _
284  @"Constructor has no public access", _
285  @"Destructor has no public access", _
286  @"Accessing base UDT's private default constructor", _
287  @"Accessing base UDT's private destructor", _
288  @"Illegal non-static member access", _
289  @"Constructor declared ABSTRACT", _
290  @"Constructor declared VIRTUAL", _
291  @"Destructor declared ABSTRACT", _
292  @"Member cannot be static", _
293  @"Member isn't static", _
294  @"Only static members can be accessed from static functions", _
295  @"The PRIVATE and PUBLIC attributes are not allowed with REDIM, COMMON or EXTERN", _
296  @"STATIC used here, but not the in the DECLARE statement", _
297  @"CONST used here, but not the in the DECLARE statement", _
298  @"VIRTUAL used here, but not the in the DECLARE statement", _
299  @"ABSTRACT used here, but not the in the DECLARE statement", _
300  @"Method declared VIRTUAL, but UDT does not extend OBJECT", _
301  @"Method declared ABSTRACT, but UDT does not extend OBJECT", _
302  @"Not overriding any virtual method", _
303  @"Implemented body for an ABSTRACT method", _
304  @"Override has different return type than overridden method", _
305  @"Override has different calling convention than overridden method", _
306  @"Implicit destructor override would have different calling convention", _
307  @"Implicit LET operator override would have different calling convention", _
308  @"Override has different parameters than overridden method", _
309  @"This operator cannot be STATIC", _
310  @"Parameter must be an integer", _
311  @"Parameter must be a pointer", _
312  @"Expected initializer", _
313  @"Fields cannot be named as keywords in TYPE's that contain member functions or in CLASS'es", _
314  @"Illegal outside a FOR compound statement", _
315  @"Illegal outside a DO compound statement", _
316  @"Illegal outside a WHILE compound statement", _
317  @"Illegal outside a SELECT compound statement", _
318  @"Expected 'FOR'", _
319  @"Expected 'DO'", _
320  @"Expected 'WHILE'", _
321  @"Expected 'SELECT'", _
322  @"No outer FOR compound statement found", _
323  @"No outer DO compound statement found", _
324  @"No outer WHILE compound statement found", _
325  @"No outer SELECT compound statement found", _
326  @"Expected 'CONSTRUCTOR', 'DESTRUCTOR', 'DO', 'FOR', 'FUNCTION', 'OPERATOR', 'PROPERTY', 'SELECT', 'SUB' or 'WHILE'", _
327  @"Expected 'DO', 'FOR' or 'WHILE'", _
328  @"Illegal outside a SUB block", _
329  @"Illegal outside a FUNCTION block", _
330  @"Ambiguous symbol access, explicit scope resolution required", _
331  @"An ENUM, TYPE or UNION cannot be empty", _
332  @"STATIC used on non-member procedure", _
333  @"CONST used on non-member procedure", _
334  @"ABSTRACT used on non-member procedure", _
335  @"VIRTUAL used on non-member procedure", _
336  @"Invalid initializer", _
337  @"Objects with default [con|de]structors or methods are only allowed in the module level", _
338  @"Symbol not a CLASS, ENUM, TYPE or UNION type", _
339  @"Too many elements", _
340  @"Only data members supported", _
341  @"UNIONs are not allowed", _
342  @"Arrays are not allowed", _
343  @"COMMON variables cannot be object instances of CLASS/TYPE's with cons/destructors", _
344  @"Cloning operators (LET, Copy constructors) can't take a byval arg of the parent's type", _
345  @"Local symbols can't be referenced", _
346  @"Expected 'PTR' or 'POINTER'", _
347  @"Too many levels of pointer indirection", _
348  @"Dynamic arrays can't be const", _
349  @"Const UDT cannot invoke non-const method", _
350  @"Elements must be empty for strings and arrays", _
351  @"GOSUB disabled, use 'OPTION GOSUB' to enable", _
352  @"Invalid -lang", _
353  @"Can't use ANY as initializer in array with ellipsis bound", _
354  @"Must have initializer with array with ellipsis bound", _
355  @"Can't use ... as lower bound", _
356  @"FOR/NEXT variable name mismatch", _
357  @"Selected option requires an SSE FPU mode", _
358  @"Expected relational operator ( =, >, <, <>, <=, >= )", _
359  @"Unsupported statement in -gen gcc mode", _
360  @"Too many labels", _
361  @"Unsupported function", _
362  @"Expected sub", _
363  @"Expected '#ENDIF'", _
364  @"Resource file given for target system that does not support them", _
365  @"-o <file> option without corresponding input file", _
366  @"Not extending a TYPE/UNION (a TYPE/UNION can only extend other TYPEs/UNIONs)", _
367  @"Illegal outside a CLASS, TYPE or UNION method", _
368  @"CLASS, TYPE or UNION not derived", _
369  @"CLASS, TYPE or UNION has no constructor", _
370  @"Symbol type has no Run-Time Type Info (RTTI)", _
371  @"Types have no hierarchical relation", _
372  @"Expected a CLASS, TYPE or UNION symbol type", _
373  @"Casting derived UDT pointer from incompatible pointer type", _
374  @"Casting derived UDT pointer from unrelated UDT pointer type", _
375  @"Casting derived UDT pointer to incompatible pointer type", _
376  @"Casting derived UDT pointer to unrelated UDT pointer type", _
377  @"ALIAS name string is empty", _
378  @"LIB name string is empty", _
379  @"UDT has unimplemented abstract methods", _
380  @"Non-virtual call to ABSTRACT method", _
381  @"#ASSERT condition failed", _
382  @"Expected '>'", _
383  @"Invalid size", _
384  @"ALIAS name here is different from ALIAS given in DECLARE prototype", _
385  @"vararg parameters are only allowed in CDECL procedures", _
386  @"the first parameter in a procedure may not be vararg", _
387  @"CONST used on constructor (not needed)", _
388  @"CONST used on destructor (not needed)" _
389  }
390 
391 
392 sub errInit( )
393  '' fbc.bas will call err*() even before errInit() or after errEnd()
394  errctx.inited += 1
395 
396  errctx.cnt = 0
398  errctx.lastline = -1
399  errctx.laststmt = -1
400 
401  '' alloc the undefined symbols tb, used to not report them more than once
402  hashInit( @errctx.undefhash, 64, TRUE )
403 
405 end sub
406 
407 sub errEnd( )
410 
411  errctx.inited -= 1
412 end sub
413 
416 end sub
417 
418 function errGetCount( ) as integer
419  return errctx.cnt
420 end function
421 
423  ( _
424  byval proc as FBSYMBOL ptr, _
425  byval tk as integer, _
426  byval paramnum as integer, _
427  byval paramid as zstring ptr _
428  )
429 
430  dim as ERRPARAMLOCATION ptr l = any
431 
432  if( proc ) then
433  '' don't count the instance pointer
434  if( symbIsMethod( proc ) ) then
435  if( paramnum > 1 ) then
436  paramnum -= 1
437  end if
438  end if
439  end if
440 
442  l->proc = proc
443  l->tk = tk
444  l->paramnum = paramnum
445  l->paramid = paramid
446 end sub
447 
449  assert( listGetTail( @errctx.paramlocations ) )
451 end sub
452 
453 function errHaveParamLocation( ) as integer
454  function = (listGetTail( @errctx.paramlocations ) <> NULL)
455 end function
456 
457 '':::::
458 sub hPrintErrMsg _
459  ( _
460  byval errnum as integer, _
461  byval msgex as const zstring ptr, _
462  byval options as FB_ERRMSGOPT, _
463  byval linenum as integer, _
464  byval showerror as integer = TRUE, _
465  byval customText as const zstring ptr = 0 _
466  ) static
467 
468  dim as const zstring ptr msg
469  dim as string token_pos
470 
471  if( (errnum < 1) or (errnum >= FB_ERRMSGS) ) then
472  msg = NULL
473  else
474  msg = errorMsgs(errnum)
475  end if
476 
477  if( msgex = NULL ) then
478  msgex = @""
479  end if
480 
481  if( len( env.inf.name ) > 0 ) then
482  print env.inf.name; "(";
483  if( linenum > 0 ) then
484  print str( linenum );
485  end if
486  print ") ";
487  end if
488 
489  print "error";
490 
491  if( errnum >= 0 ) then
492  print " " & errnum & ": " & *msg;
493  if( customText ) then
494  print *customText;
495  end if
496 
497  if( showerror ) then
498  showerror = (linenum > 0)
499  end if
500 
501  if( len( *msgex ) > 0 ) then
502  if( (options and FB_ERRMSGOPT_ADDCOMMA) <> 0 ) then
503  print ", ";
504  elseif( (options and FB_ERRMSGOPT_ADDCOLON) <> 0 ) then
505  print ": ";
506  else
507  print " ";
508  end if
509 
510  if( (options and FB_ERRMSGOPT_ADDQUOTES) <> 0 ) then
511  print QUOTE;
512  end if
513 
514  print *msgex;
515 
516  if( (options and FB_ERRMSGOPT_ADDQUOTES) <> 0 ) then
517  print QUOTE;
518  end if
519  end if
520 
521  if( showerror ) then
522  dim as string ln
523  ln = lexPeekCurrentLine( token_pos, fbLangOptIsSet( FB_LANG_OPT_SINGERRLINE ) )
524 
525  if( len( ln ) > 0 ) then
526  if( fbLangOptIsSet( FB_LANG_OPT_SINGERRLINE ) ) then
527  print " in '" & ln & "'"
528  else
529  print
530  print lexPeekCurrentLine( token_pos, FALSE )
531  print token_pos
532  end if
533  else
534  print
535  end if
536  else
537  print
538  end if
539 
540  else
541  print ": "; *msgex
542  end if
543 
544 end sub
545 
546 '':::::
547 sub errReportEx _
548  ( _
549  byval errnum as integer, _
550  byval msgex as const zstring ptr, _
551  byval linenum as integer, _
552  byval options as FB_ERRMSGOPT, _
553  byval customText as const zstring ptr _
554  )
555 
556  '' Don't show if already too many errors displayed
557  if( errctx.hide_further_messages ) then
558  exit sub
559  end if
560 
561  if( errctx.inited > 0 ) then
562  msgex = hMakeParamDesc( msgex )
563  end if
564 
565  if( linenum = 0 ) then
566  '' only one error per stmt
567  if( parser.stmt.cnt = errctx.laststmt ) then
568  exit sub
569  end if
570 
571  if( lex.ctx <> NULL ) then
572  linenum = lexLineNum( )
573  end if
574 
575  errctx.lastline = linenum
576  errctx.laststmt = parser.stmt.cnt
577  end if
578 
579  hPrintErrMsg( errnum, msgex, options, linenum, env.clopt.showerror, customText )
580 
581  errctx.cnt += 1
582 
583  if( errctx.cnt >= env.clopt.maxerrors ) then
584  hPrintErrMsg( FB_ERRMSG_TOOMANYERRORS, NULL, 0, linenum, FALSE )
586  end if
587 end sub
588 
589 function hAddToken _
590  ( _
591  byval isbefore as integer, _
592  byval addcomma as integer, _
593  byval msgex as zstring ptr = NULL _
594  ) as const zstring ptr
595 
596  static as string res, token
597 
598  res = ""
599 
600  if( msgex = NULL ) then
601  token = *lexGetText( )
602  else
603  token = *msgex
604  end if
605 
606  if( len( token ) > 0 ) then
607  '' don't print control chars
608  select case lexGetToken( )
609  case is <= CHAR_SPACE, FB_TK_EOL, FB_TK_EOF
610 
611  case else
612  if( addcomma ) then
613  res += ", "
614  end if
615 
616  if( isbefore ) then
617  res += "before '"
618  else
619  res += "found '"
620  end if
621 
622  res += token + "'"
623  end select
624  end if
625 
626  function = strptr( res )
627 end function
628 
629 '':::::
630 sub errReport _
631  ( _
632  byval errnum as integer, _
633  byval isbefore as integer = FALSE, _
634  byval customText as const zstring ptr _
635  )
636 
637  dim as const zstring ptr msgex = any
638 
639  if( errHaveParamLocation( ) ) then
640  msgex = NULL
641  else
642  msgex = hAddToken( isbefore, FALSE )
643  end if
644 
645  errReportEx( errnum, msgex, , , customText )
646 
647 end sub
648 
649 '':::::
650 sub errReportWarnEx _
651  ( _
652  byval msgnum as integer, _
653  byval msgex as const zstring ptr, _
654  byval linenum as integer, _
655  byval options as FB_ERRMSGOPT _
656  )
657 
658  if( (msgnum < 1) or (msgnum >= FB_WARNINGMSGS) ) then
659  exit sub
660  end if
661 
662  if( warningMsgs(msgnum).level < env.clopt.warninglevel ) then
663  exit sub
664  end if
665 
666  if( errctx.hide_further_messages ) then
667  exit sub
668  end if
669 
670  if( errctx.inited > 0 ) then
671  msgex = hMakeParamDesc( msgex )
672  end if
673 
674  if( len( env.inf.name ) > 0 ) then
675  print env.inf.name;
676  else
677  if( msgex <> NULL ) then
678  print *msgex;
679  msgex = NULL
680  end if
681  end if
682 
683  if( linenum > 0 ) then
684  print "(" & linenum & ")";
685  else
686  print "()";
687  end if
688 
689  print " warning " & msgnum & "(" & warningMsgs(msgnum).level & "): ";
690  print *warningMsgs(msgnum).text;
691 
692  if( msgex <> NULL ) then
693  if( (options and FB_ERRMSGOPT_ADDCOMMA) <> 0 ) then
694  print ", ";
695  elseif( (options and FB_ERRMSGOPT_ADDCOLON) <> 0 ) then
696  print ": ";
697  else
698  print " ";
699  end if
700 
701  if( (options and FB_ERRMSGOPT_ADDQUOTES) <> 0 ) then
702  print QUOTE;
703  end if
704 
705  print *msgex;
706 
707  if( (options and FB_ERRMSGOPT_ADDQUOTES) <> 0 ) then
708  print QUOTE;
709  end if
710  end if
711 
712  print
713 
714 end sub
715 
716 '':::::
717 sub errReportWarn _
718  ( _
719  byval msgnum as integer, _
720  byval msgex as const zstring ptr, _
721  byval options as FB_ERRMSGOPT _
722  )
723 
724  errReportWarnEx( msgnum, msgex, lexLineNum( ), options )
725 
726 end sub
727 
728 '':::::
730  ( _
731  byval opt as FB_LANG_OPT, _
732  byval errnum as integer, _
733  byval msgex as zstring ptr _
734  )
735 
736  dim as string msg = ""
737  dim as integer i, langs
738 
739  langs = 0
740  for i = 0 to FB_LANGS-1
741  if( (fbGetLangOptions( i ) and opt) <> 0 ) then
742  if( langs > 0 ) then
743  msg += " or "
744  end if
745  msg += fbGetLangName( i )
746  langs += 1
747  end if
748  next
749 
750  msg += *hAddToken( FALSE, langs > 0, msgex )
751 
752  errReportEx( errnum, msg, , FB_ERRMSGOPT_NONE )
753 
754 end sub
755 
756 function hMakeParamDesc _
757  ( _
758  byval msgex as const zstring ptr _
759  ) as const zstring ptr
760 
761  static as string desc
762  dim as ERRPARAMLOCATION ptr paramloc = any
763  dim as FBSYMBOL ptr proc = any
764  dim as zstring ptr pname = any, pid = any
765  dim as integer pnum = any, addprnts = any
766 
767  paramloc = listGetTail( @errctx.paramlocations )
768  if( paramloc = NULL ) then
769  return msgex
770  end if
771 
772  proc = paramloc->proc
773  pnum = paramloc->paramnum
774  pid = paramloc->paramid
775  desc = ""
776  if( msgex ) then
777  desc = *msgex + " "
778  end if
779 
780  if( pnum > 0 ) then
781  desc += "at parameter " + str( pnum )
782  if( pid = NULL ) then
783  if( proc <> NULL ) then
784  dim as FBSYMBOL ptr param = symbGetProcHeadParam( proc )
785  dim as integer cnt = iif( symbIsMethod( proc ), 0, 1 )
786 
787  do while( param <> NULL )
788  if( cnt = pnum ) then
789  exit do
790  end if
791  cnt += 1
792  param = param->next
793  loop
794 
795  if( param <> NULL ) then
796  pid = symbGetName( param )
797  end if
798  end if
799  end if
800 
801  if( pid <> NULL ) then
802  if( len(*pid) > 0 ) then
803  desc += " ("
804  desc += *pid
805  desc += ")"
806  end if
807  end if
808  end if
809 
810  if( proc <> NULL ) then
811  dim as integer showname = TRUE
812 
813  '' part of the rtlib?
814  pname = NULL
815  if( symbGetIsRTL( proc ) ) then
816  '' any name set?
817  if( symbGetName( proc ) <> NULL ) then
818  '' starts with "FB_"?
819  if( left( *symbGetName( proc ), 3 ) = "FB_" ) then
820  showname = FALSE
821  end if
822  else
823  showname = FALSE
824  end if
825  else
826  static s as string
827 
828  '' function pointer?
829  if( symbGetIsFuncPtr( proc ) ) then
830  s = symbProcPtrToStr( proc )
831  pname = strptr( s )
832  '' method?
833  elseif( (symbGetAttrib( proc ) and (FB_SYMBATTRIB_CONSTRUCTOR or _
834  FB_SYMBATTRIB_DESTRUCTOR or _
835  FB_SYMBATTRIB_OPERATOR)) <> 0 ) then
836  s = symbMethodToStr( proc )
837  pname = strptr( s )
838  end if
839  end if
840 
841  if( showname ) then
842  if( pname = NULL ) then
843  addprnts = TRUE
844  pname = symbGetName( proc )
845  if( pname <> NULL ) then
846  if( len( *pname ) = 0 ) then
847  pname = symbGetMangledName( proc )
848  end if
849  end if
850  else
851  addprnts = FALSE
852  end if
853 
854  if( pname <> NULL ) then
855  if( pnum > 0 ) then
856  desc += " of "
857  end if
858  desc += *pname
859  if( addprnts ) then
860  desc += "()"
861  end if
862  end if
863  end if
864  else
865  if( pnum > 0 ) then
866  desc += " of "
867  end if
868  desc += *symbKeywordGetText( paramloc->tk )
869  end if
870 
871  function = strptr( desc )
872 end function
873 
874 sub errReportParam _
875  ( _
876  byval proc as FBSYMBOL ptr, _
877  byval paramnum as integer, _
878  byval paramid as zstring ptr, _
879  byval msgnum as integer _
880  )
881 
883  errReportEx( msgnum, NULL )
885 
886 end sub
887 
888 sub errReportParamWarn _
889  ( _
890  byval proc as FBSYMBOL ptr, _
891  byval paramnum as integer, _
892  byval paramid as zstring ptr, _
893  byval msgnum as integer _
894  )
895 
897  errReportWarn( msgnum, NULL )
899 
900 end sub
901 
902 '':::::
903 sub errReportUndef _
904  ( _
905  byval errnum as integer, _
906  byval id as zstring ptr _
907  )
908 
909  dim as uinteger hash
910  dim as zstring ptr id_cpy
911 
912  '' already reported?
913  hash = hashHash( id )
914  if( hashLookupEx( @errctx.undefhash, id, hash ) <> NULL ) then
915  exit sub
916  end if
917 
918  '' add to hash and report the error
919  id_cpy = NULL
920  ZStrAssign( @id_cpy, id )
921 
922  hashAdd( @errctx.undefhash, id_cpy, id_cpy, hash )
923 
924  errReportEx( errnum, id )
925 
926 end sub
927