xref: /trunk/main/basic/source/comp/parser.cxx (revision b63233d868a9af170b0457a7aa0c5809011cc2c1)
1 /**************************************************************
2  *
3  * Licensed to the Apache Software Foundation (ASF) under one
4  * or more contributor license agreements.  See the NOTICE file
5  * distributed with this work for additional information
6  * regarding copyright ownership.  The ASF licenses this file
7  * to you under the Apache License, Version 2.0 (the
8  * "License"); you may not use this file except in compliance
9  * with the License.  You may obtain a copy of the License at
10  *
11  *   http://www.apache.org/licenses/LICENSE-2.0
12  *
13  * Unless required by applicable law or agreed to in writing,
14  * software distributed under the License is distributed on an
15  * "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY
16  * KIND, either express or implied.  See the License for the
17  * specific language governing permissions and limitations
18  * under the License.
19  *
20  *************************************************************/
21 
22 
23 
24 // MARKER(update_precomp.py): autogen include statement, do not remove
25 #include "precompiled_basic.hxx"
26 #include <basic/sbx.hxx>
27 #include "sbcomp.hxx"
28 #include <com/sun/star/script/ModuleType.hpp>
29 
30 struct SbiParseStack {              // "Stack" fuer Statement-Blocks
31     SbiParseStack* pNext;           // Chain
32     SbiExprNode* pWithVar;          // Variable fuer WITH
33     SbiToken eExitTok;              // Exit-Token
34     sal_uInt32  nChain;                 // JUMP-Chain
35 };
36 
37 struct SbiStatement {
38     SbiToken eTok;
39     void( SbiParser::*Func )();     // Verarbeitungsroutine
40     sal_Bool  bMain;                    // sal_True: ausserhalb SUBs OK
41     sal_Bool  bSubr;                    // sal_True: in SUBs OK
42 };
43 
44 #define Y   sal_True
45 #define N   sal_False
46 
47 static SbiStatement StmntTable [] = {
48 { CALL,     &SbiParser::Call,       N, Y, }, // CALL
49 { CLOSE,    &SbiParser::Close,      N, Y, }, // CLOSE
50 { _CONST_,  &SbiParser::Dim,        Y, Y, }, // CONST
51 { DECLARE,  &SbiParser::Declare,    Y, N, }, // DECLARE
52 { DEFBOOL,  &SbiParser::DefXXX,     Y, N, }, // DEFBOOL
53 { DEFCUR,   &SbiParser::DefXXX,     Y, N, }, // DEFCUR
54 { DEFDATE,  &SbiParser::DefXXX,     Y, N, }, // DEFDATE
55 { DEFDBL,   &SbiParser::DefXXX,     Y, N, }, // DEFDBL
56 { DEFERR,   &SbiParser::DefXXX,     Y, N, }, // DEFERR
57 { DEFINT,   &SbiParser::DefXXX,     Y, N, }, // DEFINT
58 { DEFLNG,   &SbiParser::DefXXX,     Y, N, }, // DEFLNG
59 { DEFOBJ,   &SbiParser::DefXXX,     Y, N, }, // DEFOBJ
60 { DEFSNG,   &SbiParser::DefXXX,     Y, N, }, // DEFSNG
61 { DEFSTR,   &SbiParser::DefXXX,     Y, N, }, // DEFSTR
62 { DEFVAR,   &SbiParser::DefXXX,     Y, N, }, // DEFVAR
63 { DIM,      &SbiParser::Dim,        Y, Y, }, // DIM
64 { DO,       &SbiParser::DoLoop,     N, Y, }, // DO
65 { ELSE,     &SbiParser::NoIf,       N, Y, }, // ELSE
66 { ELSEIF,   &SbiParser::NoIf,       N, Y, }, // ELSEIF
67 { ENDIF,    &SbiParser::NoIf,       N, Y, }, // ENDIF
68 { END,      &SbiParser::Stop,       N, Y, }, // END
69 { ENUM,     &SbiParser::Enum,       Y, N, }, // TYPE
70 { ERASE,    &SbiParser::Erase,      N, Y, }, // ERASE
71 { _ERROR_,  &SbiParser::ErrorStmnt, N, Y, }, // ERROR
72 { EXIT,     &SbiParser::Exit,       N, Y, }, // EXIT
73 { FOR,      &SbiParser::For,        N, Y, }, // FOR
74 { FUNCTION, &SbiParser::SubFunc,    Y, N, }, // FUNCTION
75 { GOSUB,    &SbiParser::Goto,       N, Y, }, // GOSUB
76 { GLOBAL,   &SbiParser::Dim,        Y, N, }, // GLOBAL
77 { GOTO,     &SbiParser::Goto,       N, Y, }, // GOTO
78 { IF,       &SbiParser::If,         N, Y, }, // IF
79 { IMPLEMENTS, &SbiParser::Implements, Y, N, }, // IMPLEMENTS
80 { INPUT,    &SbiParser::Input,      N, Y, }, // INPUT
81 { LET,      &SbiParser::Assign,     N, Y, }, // LET
82 { LINE,     &SbiParser::Line,       N, Y, }, // LINE, -> LINE INPUT (#i92642)
83 { LINEINPUT,&SbiParser::LineInput,  N, Y, }, // LINE INPUT
84 { LOOP,     &SbiParser::BadBlock,   N, Y, }, // LOOP
85 { LSET,     &SbiParser::LSet,       N, Y, }, // LSET
86 { NAME,     &SbiParser::Name,       N, Y, }, // NAME
87 { NEXT,     &SbiParser::BadBlock,   N, Y, }, // NEXT
88 { ON,       &SbiParser::On,         N, Y, }, // ON
89 { OPEN,     &SbiParser::Open,       N, Y, }, // OPEN
90 { OPTION,   &SbiParser::Option,     Y, N, }, // OPTION
91 { PRINT,    &SbiParser::Print,      N, Y, }, // PRINT
92 { PRIVATE,  &SbiParser::Dim,        Y, N, }, // PRIVATE
93 { PROPERTY, &SbiParser::SubFunc,    Y, N, }, // FUNCTION
94 { PUBLIC,   &SbiParser::Dim,        Y, N, }, // PUBLIC
95 { REDIM,    &SbiParser::ReDim,      N, Y, }, // DIM
96 { RESUME,   &SbiParser::Resume,     N, Y, }, // RESUME
97 { RETURN,   &SbiParser::Return,     N, Y, }, // RETURN
98 { RSET,     &SbiParser::RSet,       N, Y, }, // RSET
99 { SELECT,   &SbiParser::Select,     N, Y, }, // SELECT
100 { SET,      &SbiParser::Set,        N, Y, }, // SET
101 { STATIC,   &SbiParser::Static,     Y, Y, }, // STATIC
102 { STOP,     &SbiParser::Stop,       N, Y, }, // STOP
103 { SUB,      &SbiParser::SubFunc,    Y, N, }, // SUB
104 { TYPE,     &SbiParser::Type,       Y, N, }, // TYPE
105 { UNTIL,    &SbiParser::BadBlock,   N, Y, }, // UNTIL
106 { WHILE,    &SbiParser::While,      N, Y, }, // WHILE
107 { WEND,     &SbiParser::BadBlock,   N, Y, }, // WEND
108 { WITH,     &SbiParser::With,       N, Y, }, // WITH
109 { WRITE,    &SbiParser::Write,      N, Y, }, // WRITE
110 
111 { NIL, NULL, N, N }
112 };
113 
114 
115 #ifdef _MSC_VER
116 // 'this' : used in base member initializer list
117 #pragma warning( disable: 4355 )
118 #endif
119 
120 SbiParser::SbiParser( StarBASIC* pb, SbModule* pm )
121         : SbiTokenizer( pm->GetSource32(), pb ),
122           aGblStrings( this ),
123           aLclStrings( this ),
124           aGlobals( aGblStrings, SbGLOBAL ),
125           aPublics( aGblStrings, SbPUBLIC ),
126           aRtlSyms( aGblStrings, SbRTL ),
127           aGen( *pm, this, 1024 )
128 {
129     pBasic   = pb;
130     eCurExpr = SbSYMBOL;
131     eEndTok  = NIL;
132     pProc    = NULL;
133     pStack   = NULL;
134     pWithVar = NULL;
135     nBase    = 0;
136     bText    =
137     bGblDefs =
138     bNewGblDefs =
139     bSingleLineIf =
140     bExplicit = sal_False;
141     bClassModule = ( pm->GetModuleType() == com::sun::star::script::ModuleType::CLASS );
142     OSL_TRACE("Parser - %s, bClassModule %d", rtl::OUStringToOString( pm->GetName(), RTL_TEXTENCODING_UTF8 ).getStr(), bClassModule );
143     pPool    = &aPublics;
144     for( short i = 0; i < 26; i++ )
145         eDefTypes[ i ] = SbxVARIANT;    // Kein expliziter Defaulttyp
146 
147     aPublics.SetParent( &aGlobals );
148     aGlobals.SetParent( &aRtlSyms );
149 
150     // Die globale Chainkette faengt bei Adresse 0 an:
151     nGblChain = aGen.Gen( _JUMP, 0 );
152 
153     rTypeArray = new SbxArray; // Array fuer Benutzerdefinierte Typen
154     rEnumArray = new SbxArray; // Array for Enum types
155     bVBASupportOn = pm->IsVBACompat();
156     if ( bVBASupportOn )
157         EnableCompatibility();
158 
159 }
160 
161 
162 // Ist  Teil der Runtime-Library?
163 SbiSymDef* SbiParser::CheckRTLForSym( const String& rSym, SbxDataType eType )
164 {
165     SbxVariable* pVar = GetBasic()->GetRtl()->Find( rSym, SbxCLASS_DONTCARE );
166     SbiSymDef* pDef = NULL;
167     if( pVar )
168     {
169         if( pVar->IsA( TYPE(SbxMethod) ) )
170         {
171             SbiProcDef* pProc_ = aRtlSyms.AddProc( rSym );
172             SbxMethod* pMethod = (SbxMethod*) pVar;
173             if ( pMethod && pMethod->IsRuntimeFunction() )
174             {
175                 pProc_->SetType( pMethod->GetRuntimeFunctionReturnType() );
176             }
177             else
178             {
179                 pProc_->SetType( pVar->GetType() );
180             }
181             pDef = pProc_;
182         }
183         else
184         {
185             pDef = aRtlSyms.AddSym( rSym );
186             pDef->SetType( eType );
187         }
188     }
189     return pDef;
190 }
191 
192 // Globale Chainkette schliessen
193 
194 sal_Bool SbiParser::HasGlobalCode()
195 {
196     if( bGblDefs && nGblChain )
197     {
198         aGen.BackChain( nGblChain );
199         aGen.Gen( _LEAVE );
200         // aGen.Gen( _STOP );
201         nGblChain = 0;
202     }
203     return bGblDefs;
204 }
205 
206 void SbiParser::OpenBlock( SbiToken eTok, SbiExprNode* pVar )
207 {
208     SbiParseStack* p = new SbiParseStack;
209     p->eExitTok = eTok;
210     p->nChain   = 0;
211     p->pWithVar = pWithVar;
212     p->pNext    = pStack;
213     pStack      = p;
214     pWithVar    = pVar;
215 
216     // #29955 for-Schleifen-Ebene pflegen
217     if( eTok == FOR )
218         aGen.IncForLevel();
219 }
220 
221 void SbiParser::CloseBlock()
222 {
223     if( pStack )
224     {
225         SbiParseStack* p = pStack;
226 
227         // #29955 for-Schleifen-Ebene pflegen
228         if( p->eExitTok == FOR )
229             aGen.DecForLevel();
230 
231         aGen.BackChain( p->nChain );
232         pStack = p->pNext;
233         pWithVar = p->pWithVar;
234         delete p;
235     }
236 }
237 
238 // EXIT ...
239 
240 void SbiParser::Exit()
241 {
242     SbiToken eTok = Next();
243     for( SbiParseStack* p = pStack; p; p = p->pNext )
244     {
245         SbiToken eExitTok = p->eExitTok;
246         if( eTok == eExitTok ||
247             (eTok == PROPERTY && (eExitTok == GET || eExitTok == LET) ) )   // #i109051
248         {
249             p->nChain = aGen.Gen( _JUMP, p->nChain );
250             return;
251         }
252     }
253     if( pStack )
254         Error( SbERR_EXPECTED, pStack->eExitTok );
255     else
256         Error( SbERR_BAD_EXIT );
257 }
258 
259 sal_Bool SbiParser::TestSymbol( sal_Bool bKwdOk )
260 {
261     Peek();
262     if( eCurTok == SYMBOL || ( bKwdOk && IsKwd( eCurTok ) ) )
263     {
264         Next(); return sal_True;
265     }
266     Error( SbERR_SYMBOL_EXPECTED );
267     return sal_False;
268 }
269 
270 // Testen auf ein bestimmtes Token
271 
272 sal_Bool SbiParser::TestToken( SbiToken t )
273 {
274     if( Peek() == t )
275     {
276         Next(); return sal_True;
277     }
278     else
279     {
280         Error( SbERR_EXPECTED, t );
281         return sal_False;
282     }
283 }
284 
285 // Testen auf Komma oder EOLN
286 
287 sal_Bool SbiParser::TestComma()
288 {
289     SbiToken eTok = Peek();
290     if( IsEoln( eTok ) )
291     {
292         Next();
293         return sal_False;
294     }
295     else if( eTok != COMMA )
296     {
297         Error( SbERR_EXPECTED, COMMA );
298         return sal_False;
299     }
300     Next();
301     return sal_True;
302 }
303 
304 // Testen, ob EOLN vorliegt
305 
306 void SbiParser::TestEoln()
307 {
308     if( !IsEoln( Next() ) )
309     {
310         Error( SbERR_EXPECTED, EOLN );
311         while( !IsEoln( Next() ) ) {}
312     }
313 }
314 
315 // Parsing eines Statement-Blocks
316 // Das Parsing laeuft bis zum Ende-Token.
317 
318 void SbiParser::StmntBlock( SbiToken eEnd )
319 {
320     SbiToken xe = eEndTok;
321     eEndTok = eEnd;
322     while( !bAbort && Parse() ) {}
323     eEndTok = xe;
324     if( IsEof() )
325     {
326         Error( SbERR_BAD_BLOCK, eEnd );
327         bAbort = sal_True;
328     }
329 }
330 
331 // Die Hauptroutine. Durch wiederholten Aufrufs dieser Routine wird
332 // die Quelle geparst. Returnwert sal_False bei Ende/Fehlern.
333 
334 sal_Bool SbiParser::Parse()
335 {
336     if( bAbort ) return sal_False;
337 
338     EnableErrors();
339 
340     bErrorIsSymbol = false;
341     Peek();
342     bErrorIsSymbol = true;
343     // Dateiende?
344     if( IsEof() )
345     {
346         // AB #33133: Falls keine Sub angelegt wurde, muss hier
347         // der globale Chain abgeschlossen werden!
348         // AB #40689: Durch die neue static-Behandlung kann noch
349         // ein nGblChain vorhanden sein, daher vorher abfragen
350         if( bNewGblDefs && nGblChain == 0 )
351             nGblChain = aGen.Gen( _JUMP, 0 );
352         return sal_False;
353     }
354 
355     // Leerstatement?
356     if( IsEoln( eCurTok ) )
357     {
358         Next(); return sal_True;
359     }
360 
361     if( !bSingleLineIf && MayBeLabel( sal_True ) )
362     {
363         // Ist ein Label
364         if( !pProc )
365             Error( SbERR_NOT_IN_MAIN, aSym );
366         else
367             pProc->GetLabels().Define( aSym );
368         Next(); Peek();
369         // Leerstatement?
370         if( IsEoln( eCurTok ) )
371         {
372             Next(); return sal_True;
373         }
374     }
375 
376     // Ende des Parsings?
377     if( eCurTok == eEndTok ||
378         ( bVBASupportOn &&      // #i109075
379           (eCurTok == ENDFUNC || eCurTok == ENDPROPERTY || eCurTok == ENDSUB) &&
380           (eEndTok == ENDFUNC || eEndTok == ENDPROPERTY || eEndTok == ENDSUB) ) )
381     {
382         Next();
383         if( eCurTok != NIL )
384             aGen.Statement();
385         return sal_False;
386     }
387 
388     // Kommentar?
389     if( eCurTok == REM )
390     {
391         Next(); return sal_True;
392     }
393 
394     // Kommt ein Symbol, ist es entweder eine Variable( LET )
395     // oder eine SUB-Prozedur( CALL ohne Klammern )
396     // DOT fuer Zuweisungen im WITH-Block: .A=5
397     if( eCurTok == SYMBOL || eCurTok == DOT )
398     {
399         if( !pProc )
400             Error( SbERR_EXPECTED, SUB );
401         else
402         {
403             // Damit Zeile & Spalte stimmen...
404             Next();
405             Push( eCurTok );
406             aGen.Statement();
407                 Symbol();
408         }
409     }
410     else
411     {
412         Next();
413 
414         // Hier folgen nun die Statement-Parser.
415 
416         SbiStatement* p;
417         for( p = StmntTable; p->eTok != NIL; p++ )
418             if( p->eTok == eCurTok )
419                 break;
420         if( p->eTok != NIL )
421         {
422             if( !pProc && !p->bMain )
423                 Error( SbERR_NOT_IN_MAIN, eCurTok );
424             else if( pProc && !p->bSubr )
425                 Error( SbERR_NOT_IN_SUBR, eCurTok );
426             else
427             {
428                 // globalen Chain pflegen
429                 // AB #41606/#40689: Durch die neue static-Behandlung kann noch
430                 // ein nGblChain vorhanden sein, daher vorher abfragen
431                 if( bNewGblDefs && nGblChain == 0 &&
432                     ( eCurTok == SUB || eCurTok == FUNCTION || eCurTok == PROPERTY ) )
433                 {
434                     nGblChain = aGen.Gen( _JUMP, 0 );
435                     bNewGblDefs = sal_False;
436                 }
437                 // Statement-Opcode bitte auch am Anfang einer Sub
438                 if( ( p->bSubr && (eCurTok != STATIC || Peek() == SUB || Peek() == FUNCTION ) ) ||
439                         eCurTok == SUB || eCurTok == FUNCTION )
440                     aGen.Statement();
441                 (this->*( p->Func ) )();
442                 SbxError nSbxErr = SbxBase::GetError();
443                 if( nSbxErr )
444                     SbxBase::ResetError(), Error( (SbError)nSbxErr );
445             }
446         }
447         else
448             Error( SbERR_UNEXPECTED, eCurTok );
449     }
450 
451     // Test auf Ende des Statements:
452     // Kann auch ein ELSE sein, da vor dem ELSE kein : stehen muss!
453 
454     if( !IsEos() )
455     {
456         Peek();
457         if( !IsEos() && eCurTok != ELSE )
458         {
459             // falls das Parsing abgebrochen wurde, bis zum ":" vorgehen:
460             Error( SbERR_UNEXPECTED, eCurTok );
461             while( !IsEos() ) Next();
462         }
463     }
464     // Der Parser bricht am Ende ab, das naechste Token ist noch nicht
465     // geholt!
466     return sal_True;
467 }
468 
469 // Innerste With-Variable liefern
470 SbiExprNode* SbiParser::GetWithVar()
471 {
472     if( pWithVar )
473         return pWithVar;
474 
475     // Sonst im Stack suchen
476     SbiParseStack* p = pStack;
477     while( p )
478     {
479         // LoopVar kann zur Zeit nur fuer with sein
480         if( p->pWithVar )
481             return p->pWithVar;
482         p = p->pNext;
483     }
484     return NULL;
485 }
486 
487 
488 // Zuweisung oder Subroutine Call
489 
490 void SbiParser::Symbol( const KeywordSymbolInfo* pKeywordSymbolInfo )
491 {
492     SbiExprMode eMode = bVBASupportOn ? EXPRMODE_STANDALONE : EXPRMODE_STANDARD;
493     SbiExpression aVar( this, SbSYMBOL, eMode, pKeywordSymbolInfo );
494 
495     bool bEQ = ( Peek() == EQ );
496     if( !bEQ && bVBASupportOn && aVar.IsBracket() )
497         Error( SbERR_EXPECTED, "=" );
498 
499     RecursiveMode eRecMode = ( bEQ ? PREVENT_CALL : FORCE_CALL );
500     bool bSpecialMidHandling = false;
501     SbiSymDef* pDef = aVar.GetRealVar();
502     if( bEQ && pDef && pDef->GetScope() == SbRTL )
503     {
504         String aRtlName = pDef->GetName();
505         if( aRtlName.EqualsIgnoreCaseAscii("Mid") )
506         {
507             SbiExprNode* pExprNode = aVar.GetExprNode();
508             // SbiNodeType eNodeType;
509             if( pExprNode && pExprNode->GetNodeType() == SbxVARVAL )
510             {
511                 SbiExprList* pPar = pExprNode->GetParameters();
512                 short nParCount = pPar ? pPar->GetSize() : 0;
513                 if( nParCount == 2 || nParCount == 3 )
514                 {
515                     if( nParCount == 2 )
516                         pPar->addExpression( new SbiExpression( this, -1, SbxLONG ) );
517 
518                     TestToken( EQ );
519                     pPar->addExpression( new SbiExpression( this ) );
520 
521                     bSpecialMidHandling = true;
522                 }
523             }
524         }
525     }
526     aVar.Gen( eRecMode );
527     if( !bSpecialMidHandling )
528     {
529         if( !bEQ )
530         {
531             aGen.Gen( _GET );
532         }
533         else
534         {
535             // Dann muss es eine Zuweisung sein. Was anderes gibts nicht!
536             if( !aVar.IsLvalue() )
537                 Error( SbERR_LVALUE_EXPECTED );
538             TestToken( EQ );
539             SbiExpression aExpr( this );
540             aExpr.Gen();
541             SbiOpcode eOp = _PUT;
542             // SbiSymDef* pDef = aVar.GetRealVar();
543             if( pDef )
544             {
545                 if( pDef->GetConstDef() )
546                     Error( SbERR_DUPLICATE_DEF, pDef->GetName() );
547                 if( pDef->GetType() == SbxOBJECT )
548                 {
549                     eOp = _SET;
550                     if( pDef->GetTypeId() )
551                     {
552                         aGen.Gen( _SETCLASS, pDef->GetTypeId() );
553                         return;
554                     }
555                 }
556             }
557             aGen.Gen( eOp );
558         }
559     }
560 }
561 
562 // Zuweisungen
563 
564 void SbiParser::Assign()
565 {
566     SbiExpression aLvalue( this, SbLVALUE );
567     TestToken( EQ );
568     SbiExpression aExpr( this );
569     aLvalue.Gen();
570     aExpr.Gen();
571     sal_uInt16 nLen = 0;
572     SbiSymDef* pDef = aLvalue.GetRealVar();
573     {
574         if( pDef->GetConstDef() )
575             Error( SbERR_DUPLICATE_DEF, pDef->GetName() );
576         nLen = aLvalue.GetRealVar()->GetLen();
577     }
578     if( nLen )
579         aGen.Gen( _PAD, nLen );
580     aGen.Gen( _PUT );
581 }
582 
583 // Zuweisungen einer Objektvariablen
584 
585 void SbiParser::Set()
586 {
587     SbiExpression aLvalue( this, SbLVALUE );
588     SbxDataType eType = aLvalue.GetType();
589     if( eType != SbxOBJECT && eType != SbxEMPTY && eType != SbxVARIANT )
590         Error( SbERR_INVALID_OBJECT );
591     TestToken( EQ );
592     SbiSymDef* pDef = aLvalue.GetRealVar();
593     if( pDef && pDef->GetConstDef() )
594         Error( SbERR_DUPLICATE_DEF, pDef->GetName() );
595 
596     SbiToken eTok = Peek();
597     if( eTok == NEW )
598     {
599         Next();
600         String aStr;
601         SbiSymDef* pTypeDef = new SbiSymDef( aStr );
602         TypeDecl( *pTypeDef, sal_True );
603 
604         aLvalue.Gen();
605         // aGen.Gen( _CLASS, pDef->GetTypeId() | 0x8000 );
606         aGen.Gen( _CREATE, pDef->GetId(), pTypeDef->GetTypeId() );
607         aGen.Gen( _SETCLASS, pDef->GetTypeId() );
608     }
609     else
610     {
611         SbiExpression aExpr( this );
612         aLvalue.Gen();
613         aExpr.Gen();
614         // Its a good idea to distinguish between
615         // set someting = another &
616         // someting = another
617         // ( its necessary for vba objects where set is object
618         // specific and also doesn't involve processing default params )
619         if( pDef->GetTypeId() )
620         {
621             if ( bVBASupportOn )
622                 aGen.Gen( _VBASETCLASS, pDef->GetTypeId() );
623             else
624                 aGen.Gen( _SETCLASS, pDef->GetTypeId() );
625         }
626         else
627         {
628             if ( bVBASupportOn )
629                 aGen.Gen( _VBASET );
630             else
631                 aGen.Gen( _SET );
632         }
633     }
634     // aGen.Gen( _SET );
635 }
636 
637 // JSM 07.10.95
638 void SbiParser::LSet()
639 {
640     SbiExpression aLvalue( this, SbLVALUE );
641     if( aLvalue.GetType() != SbxSTRING )
642         Error( SbERR_INVALID_OBJECT );
643     TestToken( EQ );
644     SbiSymDef* pDef = aLvalue.GetRealVar();
645     if( pDef && pDef->GetConstDef() )
646         Error( SbERR_DUPLICATE_DEF, pDef->GetName() );
647     SbiExpression aExpr( this );
648     aLvalue.Gen();
649     aExpr.Gen();
650     aGen.Gen( _LSET );
651 }
652 
653 // JSM 07.10.95
654 void SbiParser::RSet()
655 {
656     SbiExpression aLvalue( this, SbLVALUE );
657     if( aLvalue.GetType() != SbxSTRING )
658         Error( SbERR_INVALID_OBJECT );
659     TestToken( EQ );
660     SbiSymDef* pDef = aLvalue.GetRealVar();
661     if( pDef && pDef->GetConstDef() )
662         Error( SbERR_DUPLICATE_DEF, pDef->GetName() );
663     SbiExpression aExpr( this );
664     aLvalue.Gen();
665     aExpr.Gen();
666     aGen.Gen( _RSET );
667 }
668 
669 // DEFINT, DEFLNG, DEFSNG, DEFDBL, DEFSTR und so weiter
670 
671 void SbiParser::DefXXX()
672 {
673     sal_Unicode ch1, ch2;
674     SbxDataType t = SbxDataType( eCurTok - DEFINT + SbxINTEGER );
675 
676     while( !bAbort )
677     {
678         if( Next() != SYMBOL ) break;
679         ch1 = aSym.ToUpperAscii().GetBuffer()[0];
680         ch2 = 0;
681         if( Peek() == MINUS )
682         {
683             Next();
684             if( Next() != SYMBOL ) Error( SbERR_SYMBOL_EXPECTED );
685             else
686             {
687                 ch2 = aSym.ToUpperAscii().GetBuffer()[0];
688                 //ch2 = aSym.Upper();
689                 if( ch2 < ch1 ) Error( SbERR_SYNTAX ), ch2 = 0;
690             }
691         }
692         if (!ch2) ch2 = ch1;
693         ch1 -= 'A'; ch2 -= 'A';
694         for (; ch1 <= ch2; ch1++) eDefTypes[ ch1 ] = t;
695         if( !TestComma() ) break;
696     }
697 }
698 
699 // STOP/SYSTEM
700 
701 void SbiParser::Stop()
702 {
703     aGen.Gen( _STOP );
704     Peek();     // #35694: Nur Peek(), damit EOL in Single-Line-If erkannt wird
705 }
706 
707 // IMPLEMENTS
708 
709 void SbiParser::Implements()
710 {
711     if( !bClassModule )
712     {
713         Error( SbERR_UNEXPECTED, IMPLEMENTS );
714         return;
715     }
716 
717     Peek();
718     if( eCurTok != SYMBOL )
719     {
720         Error( SbERR_SYMBOL_EXPECTED );
721         return;
722     }
723 
724     String aImplementedIface = aSym;
725     Next();
726     if( Peek() == DOT )
727     {
728         String aDotStr( '.' );
729         while( Peek() == DOT )
730         {
731             aImplementedIface += aDotStr;
732             Next();
733             SbiToken ePeekTok = Peek();
734             if( ePeekTok == SYMBOL || IsKwd( ePeekTok ) )
735             {
736                 Next();
737                 aImplementedIface += aSym;
738             }
739             else
740             {
741                 Next();
742                 Error( SbERR_SYMBOL_EXPECTED );
743                 break;
744             }
745         }
746     }
747     aIfaceVector.push_back( aImplementedIface );
748 }
749 
750 void SbiParser::EnableCompatibility()
751 {
752     if( !bCompatible )
753         AddConstants();
754     bCompatible = sal_True;
755 }
756 
757 // OPTION
758 
759 void SbiParser::Option()
760 {
761     switch( Next() )
762     {
763         case BASIC_EXPLICIT:
764             bExplicit = sal_True; break;
765         case BASE:
766             if( Next() == NUMBER )
767             {
768                 if( nVal == 0 || nVal == 1 )
769                 {
770                     nBase = (short) nVal;
771                     break;
772                 }
773             }
774             Error( SbERR_EXPECTED, "0/1" );
775             break;
776         case PRIVATE:
777         {
778             String aString = SbiTokenizer::Symbol(Next());
779             if( !aString.EqualsIgnoreCaseAscii("Module") )
780                 Error( SbERR_EXPECTED, "Module" );
781             break;
782         }
783         case COMPARE:
784         {
785             SbiToken eTok = Next();
786             if( eTok == BINARY )
787                 bText = sal_False;
788             else if( eTok == SYMBOL && GetSym().EqualsIgnoreCaseAscii("text") )
789                 bText = sal_True;
790             else
791                 Error( SbERR_EXPECTED, "Text/Binary" );
792             break;
793         }
794         case COMPATIBLE:
795             EnableCompatibility();
796             break;
797 
798         case CLASSMODULE:
799             bClassModule = sal_True;
800             aGen.GetModule().SetModuleType( com::sun::star::script::ModuleType::CLASS );
801             break;
802         case VBASUPPORT:
803             if( Next() == NUMBER )
804             {
805                 if ( nVal == 1 || nVal == 0 )
806                 {
807                     bVBASupportOn = ( nVal == 1 );
808                     if ( bVBASupportOn )
809                         EnableCompatibility();
810                     // if the module setting is different
811                     // reset it to what the Option tells us
812                     if ( bVBASupportOn != aGen.GetModule().IsVBACompat() )
813                         aGen.GetModule().SetVBACompat( bVBASupportOn );
814                     break;
815                 }
816             }
817             Error( SbERR_EXPECTED, "0/1" );
818             break;
819         default:
820             Error( SbERR_BAD_OPTION, eCurTok );
821     }
822 }
823 
824 void addStringConst( SbiSymPool& rPool, const char* pSym, const String& rStr )
825 {
826     SbiConstDef* pConst = new SbiConstDef( String::CreateFromAscii( pSym ) );
827     pConst->SetType( SbxSTRING );
828     pConst->Set( rStr );
829     rPool.Add( pConst );
830 }
831 
832 inline void addStringConst( SbiSymPool& rPool, const char* pSym, const char* pStr )
833 {
834     addStringConst( rPool, pSym, String::CreateFromAscii( pStr ) );
835 }
836 
837 void SbiParser::AddConstants( void )
838 {
839     // #113063 Create constant RTL symbols
840     addStringConst( aPublics, "vbCr", "\x0D" );
841     addStringConst( aPublics, "vbCrLf", "\x0D\x0A" );
842     addStringConst( aPublics, "vbFormFeed", "\x0C" );
843     addStringConst( aPublics, "vbLf", "\x0A" );
844 #if defined(UNX)
845     addStringConst( aPublics, "vbNewLine", "\x0A" );
846 #else
847     addStringConst( aPublics, "vbNewLine", "\x0D\x0A" );
848 #endif
849     addStringConst( aPublics, "vbNullString", "" );
850     addStringConst( aPublics, "vbTab", "\x09" );
851     addStringConst( aPublics, "vbVerticalTab", "\x0B" );
852 
853     // Force length 1 and make char 0 afterwards
854     String aNullCharStr( String::CreateFromAscii( " " ) );
855     aNullCharStr.SetChar( 0, 0 );
856     addStringConst( aPublics, "vbNullChar", aNullCharStr );
857 }
858 
859 // ERROR n
860 
861 void SbiParser::ErrorStmnt()
862 {
863     SbiExpression aPar( this );
864     aPar.Gen();
865     aGen.Gen( _ERROR );
866 }
867 
868