Version 6.4.0.3, tag libreoffice-6.4.0.3
[LibreOffice.git] / basic / source / comp / parser.cxx
blob1de38c9c854136d6a33491a2aa652f2ea348e637
1 /* -*- Mode: C++; tab-width: 4; indent-tabs-mode: nil; c-basic-offset: 4 -*- */
2 /*
3 * This file is part of the LibreOffice project.
5 * This Source Code Form is subject to the terms of the Mozilla Public
6 * License, v. 2.0. If a copy of the MPL was not distributed with this
7 * file, You can obtain one at http://mozilla.org/MPL/2.0/.
9 * This file incorporates work covered by the following license notice:
11 * Licensed to the Apache Software Foundation (ASF) under one or more
12 * contributor license agreements. See the NOTICE file distributed
13 * with this work for additional information regarding copyright
14 * ownership. The ASF licenses this file to you under the Apache
15 * License, Version 2.0 (the "License"); you may not use this file
16 * except in compliance with the License. You may obtain a copy of
17 * the License at http://www.apache.org/licenses/LICENSE-2.0 .
20 #include <basic/sberrors.hxx>
21 #include <basic/sbxmeth.hxx>
22 #include <basic/sbmod.hxx>
23 #include <basic/sbstar.hxx>
24 #include <basic/sbx.hxx>
25 #include <parser.hxx>
26 #include <com/sun/star/script/ModuleType.hpp>
27 #include <rtl/character.hxx>
29 struct SbiParseStack { // "Stack" for statement-blocks
30 SbiParseStack* pNext; // Chain
31 SbiExprNode* pWithVar;
32 SbiToken eExitTok;
33 sal_uInt32 nChain; // JUMP-Chain
36 struct SbiStatement {
37 SbiToken eTok;
38 void( SbiParser::*Func )();
39 bool bMain; // true: OK outside the SUB
40 bool bSubr; // true: OK inside the SUB
43 #define Y true
44 #define N false
46 static const SbiStatement StmntTable [] = {
47 { ATTRIBUTE, &SbiParser::Attribute, Y, Y, }, // ATTRIBUTE
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
111 { NIL, nullptr, N, N }
115 SbiParser::SbiParser( StarBASIC* pb, SbModule* pm )
116 : SbiTokenizer( pm->GetSource32(), pb ),
117 aGlobals( aGblStrings, SbGLOBAL, this ),
118 aPublics( aGblStrings, SbPUBLIC, this ),
119 aRtlSyms( aGblStrings, SbRTL, this ),
120 aGen( *pm, this, 1024 )
122 eEndTok = NIL;
123 pProc = nullptr;
124 pStack = nullptr;
125 pWithVar = nullptr;
126 nBase = 0;
127 bGblDefs =
128 bNewGblDefs =
129 bSingleLineIf =
130 bCodeCompleting =
131 bExplicit = false;
132 bClassModule = ( pm->GetModuleType() == css::script::ModuleType::CLASS );
133 pPool = &aPublics;
134 for(SbxDataType & eDefType : eDefTypes)
135 eDefType = SbxVARIANT; // no explicit default type
137 aPublics.SetParent( &aGlobals );
138 aGlobals.SetParent( &aRtlSyms );
141 nGblChain = aGen.Gen( SbiOpcode::JUMP_, 0 );
143 rTypeArray = new SbxArray; // array for user defined types
144 rEnumArray = new SbxArray; // array for Enum types
145 bVBASupportOn = pm->IsVBACompat();
146 if ( bVBASupportOn )
147 EnableCompatibility();
151 SbiParser::~SbiParser() { }
153 // part of the runtime-library?
154 SbiSymDef* SbiParser::CheckRTLForSym(const OUString& rSym, SbxDataType eType)
156 SbxVariable* pVar = GetBasic()->GetRtl()->Find(rSym, SbxClassType::DontCare);
157 if (!pVar)
158 return nullptr;
160 if (SbxMethod* pMethod = dynamic_cast<SbxMethod*>(pVar))
162 SbiProcDef* pProc_ = aRtlSyms.AddProc( rSym );
163 if (pMethod->IsRuntimeFunction())
165 pProc_->SetType( pMethod->GetRuntimeFunctionReturnType() );
167 else
169 pProc_->SetType( pVar->GetType() );
171 return pProc_;
175 SbiSymDef* pDef = aRtlSyms.AddSym(rSym);
176 pDef->SetType(eType);
177 return pDef;
180 // close global chain
182 bool SbiParser::HasGlobalCode()
184 if( bGblDefs && nGblChain )
186 aGen.BackChain( nGblChain );
187 aGen.Gen( SbiOpcode::LEAVE_ );
188 nGblChain = 0;
190 return bGblDefs;
193 void SbiParser::OpenBlock( SbiToken eTok, SbiExprNode* pVar )
195 SbiParseStack* p = new SbiParseStack;
196 p->eExitTok = eTok;
197 p->nChain = 0;
198 p->pWithVar = pWithVar;
199 p->pNext = pStack;
200 pStack = p;
201 pWithVar = pVar;
203 // #29955 service the for-loop level
204 if( eTok == FOR )
205 aGen.IncForLevel();
208 void SbiParser::CloseBlock()
210 if( pStack )
212 SbiParseStack* p = pStack;
214 // #29955 service the for-loop level
215 if( p->eExitTok == FOR )
216 aGen.DecForLevel();
218 aGen.BackChain( p->nChain );
219 pStack = p->pNext;
220 pWithVar = p->pWithVar;
221 delete p;
225 // EXIT ...
227 void SbiParser::Exit()
229 SbiToken eTok = Next();
230 for( SbiParseStack* p = pStack; p; p = p->pNext )
232 SbiToken eExitTok = p->eExitTok;
233 if( eTok == eExitTok ||
234 (eTok == PROPERTY && (eExitTok == GET || eExitTok == LET) ) ) // #i109051
236 p->nChain = aGen.Gen( SbiOpcode::JUMP_, p->nChain );
237 return;
240 if( pStack )
241 Error( ERRCODE_BASIC_EXPECTED, pStack->eExitTok );
242 else
243 Error( ERRCODE_BASIC_BAD_EXIT );
246 bool SbiParser::TestSymbol()
248 Peek();
249 if( eCurTok == SYMBOL )
251 Next(); return true;
253 Error( ERRCODE_BASIC_SYMBOL_EXPECTED );
254 return false;
258 bool SbiParser::TestToken( SbiToken t )
260 if( Peek() == t )
262 Next(); return true;
264 else
266 Error( ERRCODE_BASIC_EXPECTED, t );
267 return false;
272 bool SbiParser::TestComma()
274 SbiToken eTok = Peek();
275 if( IsEoln( eTok ) )
277 Next();
278 return false;
280 else if( eTok != COMMA )
282 Error( ERRCODE_BASIC_EXPECTED, COMMA );
283 return false;
285 Next();
286 return true;
290 void SbiParser::TestEoln()
292 if( !IsEoln( Next() ) )
294 Error( ERRCODE_BASIC_EXPECTED, EOLN );
295 while( !IsEoln( Next() ) ) {}
300 void SbiParser::StmntBlock( SbiToken eEnd )
302 SbiToken xe = eEndTok;
303 eEndTok = eEnd;
304 while( !bAbort && Parse() ) {}
305 eEndTok = xe;
306 if( IsEof() )
308 Error( ERRCODE_BASIC_BAD_BLOCK, eEnd );
309 bAbort = true;
313 void SbiParser::SetCodeCompleting( bool b )
315 bCodeCompleting = b;
319 bool SbiParser::Parse()
321 if( bAbort ) return false;
323 EnableErrors();
325 bErrorIsSymbol = false;
326 Peek();
327 bErrorIsSymbol = true;
329 if( IsEof() )
331 // AB #33133: If no sub has been created before,
332 // the global chain must be closed here!
333 // AB #40689: Due to the new static-handling there
334 // can be another nGblChain, so ask for it before.
335 if( bNewGblDefs && nGblChain == 0 )
336 nGblChain = aGen.Gen( SbiOpcode::JUMP_, 0 );
337 return false;
341 if( IsEoln( eCurTok ) )
343 Next(); return true;
346 if( !bSingleLineIf && MayBeLabel( true ) )
348 // is a label
349 if( !pProc )
350 Error( ERRCODE_BASIC_NOT_IN_MAIN, aSym );
351 else
352 pProc->GetLabels().Define( aSym );
353 Next(); Peek();
355 if( IsEoln( eCurTok ) )
357 Next(); return true;
361 // end of parsing?
362 if( eCurTok == eEndTok ||
363 ( bVBASupportOn && // #i109075
364 (eCurTok == ENDFUNC || eCurTok == ENDPROPERTY || eCurTok == ENDSUB) &&
365 (eEndTok == ENDFUNC || eEndTok == ENDPROPERTY || eEndTok == ENDSUB) ) )
367 Next();
368 if( eCurTok != NIL )
369 aGen.Statement();
370 return false;
373 // comment?
374 if( eCurTok == REM )
376 Next(); return true;
379 // In vba it's possible to do Error.foobar ( even if it results in
380 // a runtime error
381 if ( eCurTok == ERROR_ && IsVBASupportOn() ) // we probably need to define a subset of keywords where this madness applies e.g. if ( IsVBASupportOn() && SymbolCanBeRedined( eCurTok ) )
383 SbiTokenizer tokens( *this );
384 tokens.Next();
385 if ( tokens.Peek() == DOT )
387 eCurTok = SYMBOL;
388 ePush = eCurTok;
391 // if there's a symbol, it's either a variable (LET)
392 // or a SUB-procedure (CALL without brackets)
393 // DOT for assignments in the WITH-block: .A=5
394 if( eCurTok == SYMBOL || eCurTok == DOT )
396 if( !pProc )
397 Error( ERRCODE_BASIC_EXPECTED, SUB );
398 else
400 // for correct line and column...
401 Next();
402 Push( eCurTok );
403 aGen.Statement();
404 Symbol(nullptr);
407 else
409 Next();
411 // statement parsers
413 const SbiStatement* p;
414 for( p = StmntTable; p->eTok != NIL; p++ )
415 if( p->eTok == eCurTok )
416 break;
417 if( p->eTok != NIL )
419 if( !pProc && !p->bMain )
420 Error( ERRCODE_BASIC_NOT_IN_MAIN, eCurTok );
421 else if( pProc && !p->bSubr )
422 Error( ERRCODE_BASIC_NOT_IN_SUBR, eCurTok );
423 else
425 // AB #41606/#40689: Due to the new static-handling there
426 // can be another nGblChain, so ask for it before.
427 if( bNewGblDefs && nGblChain == 0 &&
428 ( eCurTok == SUB || eCurTok == FUNCTION || eCurTok == PROPERTY ) )
430 nGblChain = aGen.Gen( SbiOpcode::JUMP_, 0 );
431 bNewGblDefs = false;
433 // statement-opcode at the beginning of a sub, too, please
434 if( ( p->bSubr && (eCurTok != STATIC || Peek() == SUB || Peek() == FUNCTION ) ) ||
435 eCurTok == SUB || eCurTok == FUNCTION )
436 aGen.Statement();
437 (this->*( p->Func ) )();
438 ErrCode nSbxErr = SbxBase::GetError();
439 if( nSbxErr )
441 SbxBase::ResetError();
442 Error( nSbxErr );
446 else
447 Error( ERRCODE_BASIC_UNEXPECTED, eCurTok );
450 // test for the statement's end -
451 // might also be an ELSE, as there must not necessary be a : before the ELSE!
453 if( !IsEos() )
455 Peek();
456 if( !IsEos() && eCurTok != ELSE )
458 // if the parsing has been aborted, jump over to the ":"
459 Error( ERRCODE_BASIC_UNEXPECTED, eCurTok );
460 while( !IsEos() ) Next();
463 // The parser aborts at the end, the
464 // next token has not been fetched yet!
465 return true;
469 SbiExprNode* SbiParser::GetWithVar()
471 if( pWithVar )
472 return pWithVar;
474 SbiParseStack* p = pStack;
475 while( p )
477 // LoopVar can at the moment only be for with
478 if( p->pWithVar )
479 return p->pWithVar;
480 p = p->pNext;
482 return nullptr;
486 // assignment or subroutine call
488 void SbiParser::Symbol( const KeywordSymbolInfo* pKeywordSymbolInfo )
490 SbiExprMode eMode = bVBASupportOn ? EXPRMODE_STANDALONE : EXPRMODE_STANDARD;
491 SbiExpression aVar( this, SbSYMBOL, eMode, pKeywordSymbolInfo );
493 bool bEQ = ( Peek() == EQ );
494 if( !bEQ && bVBASupportOn && aVar.IsBracket() )
495 Error( ERRCODE_BASIC_EXPECTED, "=" );
497 RecursiveMode eRecMode = ( bEQ ? PREVENT_CALL : FORCE_CALL );
498 bool bSpecialMidHandling = false;
499 SbiSymDef* pDef = aVar.GetRealVar();
500 if( bEQ && pDef && pDef->GetScope() == SbRTL )
502 OUString aRtlName = pDef->GetName();
503 if( aRtlName.equalsIgnoreAsciiCase("Mid") )
505 SbiExprNode* pExprNode = aVar.GetExprNode();
506 if( pExprNode && pExprNode->GetNodeType() == SbxVARVAL )
508 SbiExprList* pPar = pExprNode->GetParameters();
509 short nParCount = pPar ? pPar->GetSize() : 0;
510 if( nParCount == 2 || nParCount == 3 )
512 if( nParCount == 2 )
513 pPar->addExpression( std::make_unique<SbiExpression>( this, -1, SbxLONG ) );
515 TestToken( EQ );
516 pPar->addExpression( std::make_unique<SbiExpression>( this ) );
518 bSpecialMidHandling = true;
523 aVar.Gen( eRecMode );
524 if( !bSpecialMidHandling )
526 if( !bEQ )
528 aGen.Gen( SbiOpcode::GET_ );
530 else
532 // so it must be an assignment!
533 if( !aVar.IsLvalue() )
534 Error( ERRCODE_BASIC_LVALUE_EXPECTED );
535 TestToken( EQ );
536 SbiExpression aExpr( this );
537 aExpr.Gen();
538 SbiOpcode eOp = SbiOpcode::PUT_;
539 if( pDef )
541 if( pDef->GetConstDef() )
542 Error( ERRCODE_BASIC_DUPLICATE_DEF, pDef->GetName() );
543 if( pDef->GetType() == SbxOBJECT )
545 eOp = SbiOpcode::SET_;
546 if( pDef->GetTypeId() )
548 aGen.Gen( SbiOpcode::SETCLASS_, pDef->GetTypeId() );
549 return;
553 aGen.Gen( eOp );
559 void SbiParser::Assign()
561 SbiExpression aLvalue( this, SbLVALUE );
562 TestToken( EQ );
563 SbiExpression aExpr( this );
564 aLvalue.Gen();
565 aExpr.Gen();
566 sal_uInt16 nLen = 0;
567 SbiSymDef* pDef = aLvalue.GetRealVar();
569 if( pDef->GetConstDef() )
570 Error( ERRCODE_BASIC_DUPLICATE_DEF, pDef->GetName() );
571 nLen = aLvalue.GetRealVar()->GetLen();
573 if( nLen )
574 aGen.Gen( SbiOpcode::PAD_, nLen );
575 aGen.Gen( SbiOpcode::PUT_ );
578 // assignments of an object-variable
580 void SbiParser::Set()
582 SbiExpression aLvalue( this, SbLVALUE );
583 SbxDataType eType = aLvalue.GetType();
584 if( eType != SbxOBJECT && eType != SbxEMPTY && eType != SbxVARIANT )
585 Error( ERRCODE_BASIC_INVALID_OBJECT );
586 TestToken( EQ );
587 SbiSymDef* pDef = aLvalue.GetRealVar();
588 if( pDef->GetConstDef() )
589 Error( ERRCODE_BASIC_DUPLICATE_DEF, pDef->GetName() );
591 SbiToken eTok = Peek();
592 if( eTok == NEW )
594 Next();
595 SbiSymDef* pTypeDef = new SbiSymDef( OUString() );
596 TypeDecl( *pTypeDef, true );
598 aLvalue.Gen();
599 aGen.Gen( SbiOpcode::CREATE_, pDef->GetId(), pTypeDef->GetTypeId() );
600 aGen.Gen( SbiOpcode::SETCLASS_, pDef->GetTypeId() );
602 else
604 SbiExpression aExpr( this );
605 aLvalue.Gen();
606 aExpr.Gen();
607 // It's a good idea to distinguish between
608 // set something = another &
609 // something = another
610 // ( it's necessary for vba objects where set is object
611 // specific and also doesn't involve processing default params )
612 if( pDef->GetTypeId() )
614 if ( bVBASupportOn )
615 aGen.Gen( SbiOpcode::VBASETCLASS_, pDef->GetTypeId() );
616 else
617 aGen.Gen( SbiOpcode::SETCLASS_, pDef->GetTypeId() );
619 else
621 if ( bVBASupportOn )
622 aGen.Gen( SbiOpcode::VBASET_ );
623 else
624 aGen.Gen( SbiOpcode::SET_ );
629 // JSM 07.10.95
630 void SbiParser::LSet()
632 SbiExpression aLvalue( this, SbLVALUE );
633 if( aLvalue.GetType() != SbxSTRING )
635 Error( ERRCODE_BASIC_INVALID_OBJECT );
637 TestToken( EQ );
638 SbiSymDef* pDef = aLvalue.GetRealVar();
639 if( pDef && pDef->GetConstDef() )
641 Error( ERRCODE_BASIC_DUPLICATE_DEF, pDef->GetName() );
643 SbiExpression aExpr( this );
644 aLvalue.Gen();
645 aExpr.Gen();
646 aGen.Gen( SbiOpcode::LSET_ );
649 // JSM 07.10.95
650 void SbiParser::RSet()
652 SbiExpression aLvalue( this, SbLVALUE );
653 if( aLvalue.GetType() != SbxSTRING )
655 Error( ERRCODE_BASIC_INVALID_OBJECT );
657 TestToken( EQ );
658 SbiSymDef* pDef = aLvalue.GetRealVar();
659 if( pDef && pDef->GetConstDef() )
660 Error( ERRCODE_BASIC_DUPLICATE_DEF, pDef->GetName() );
661 SbiExpression aExpr( this );
662 aLvalue.Gen();
663 aExpr.Gen();
664 aGen.Gen( SbiOpcode::RSET_ );
667 // DEFINT, DEFLNG, DEFSNG, DEFDBL, DEFSTR and so on
669 void SbiParser::DefXXX()
671 sal_Unicode ch1, ch2;
672 SbxDataType t = SbxDataType( eCurTok - DEFINT + SbxINTEGER );
674 while( !bAbort )
676 if( Next() != SYMBOL ) break;
677 ch1 = rtl::toAsciiUpperCase(aSym[0]);
678 ch2 = 0;
679 if( Peek() == MINUS )
681 Next();
682 if( Next() != SYMBOL ) Error( ERRCODE_BASIC_SYMBOL_EXPECTED );
683 else
685 ch2 = rtl::toAsciiUpperCase(aSym[0]);
686 if( ch2 < ch1 )
688 Error( ERRCODE_BASIC_SYNTAX );
689 ch2 = 0;
693 if (!ch2) ch2 = ch1;
694 ch1 -= 'A'; ch2 -= 'A';
695 for (; ch1 <= ch2; ch1++) eDefTypes[ ch1 ] = t;
696 if( !TestComma() ) break;
700 // STOP/SYSTEM
702 void SbiParser::Stop()
704 aGen.Gen( SbiOpcode::STOP_ );
705 Peek(); // #35694: only Peek(), so that EOL is recognized in Single-Line-If
708 // IMPLEMENTS
710 void SbiParser::Implements()
712 if( !bClassModule )
714 Error( ERRCODE_BASIC_UNEXPECTED, IMPLEMENTS );
715 return;
718 Peek();
719 if( eCurTok != SYMBOL )
721 Error( ERRCODE_BASIC_SYMBOL_EXPECTED );
722 return;
725 OUString aImplementedIface = aSym;
726 Next();
727 if( Peek() == DOT )
729 OUString aDotStr( '.' );
730 while( Peek() == DOT )
732 aImplementedIface += aDotStr;
733 Next();
734 SbiToken ePeekTok = Peek();
735 if( ePeekTok == SYMBOL || IsKwd( ePeekTok ) )
737 Next();
738 aImplementedIface += aSym;
740 else
742 Next();
743 Error( ERRCODE_BASIC_SYMBOL_EXPECTED );
744 break;
748 aIfaceVector.push_back( aImplementedIface );
751 void SbiParser::EnableCompatibility()
753 if( !bCompatible )
754 AddConstants();
755 bCompatible = true;
758 // OPTION
760 void SbiParser::Option()
762 switch( Next() )
764 case BASIC_EXPLICIT:
765 bExplicit = true; break;
766 case BASE:
767 if( Next() == NUMBER && ( nVal == 0 || nVal == 1 ) )
769 nBase = static_cast<short>(nVal);
770 break;
772 Error( ERRCODE_BASIC_EXPECTED, "0/1" );
773 break;
774 case PRIVATE:
776 OUString aString = SbiTokenizer::Symbol(Next());
777 if( !aString.equalsIgnoreAsciiCase("Module") )
779 Error( ERRCODE_BASIC_EXPECTED, "Module" );
781 break;
783 case COMPARE:
785 SbiToken eTok = Next();
786 if( eTok == BINARY )
789 else if( eTok == SYMBOL && GetSym().equalsIgnoreAsciiCase("text") )
792 else
794 Error( ERRCODE_BASIC_EXPECTED, "Text/Binary" );
796 break;
798 case COMPATIBLE:
799 EnableCompatibility();
800 break;
802 case CLASSMODULE:
803 bClassModule = true;
804 aGen.GetModule().SetModuleType( css::script::ModuleType::CLASS );
805 break;
806 case VBASUPPORT: // Option VBASupport used to override the module mode ( in fact this must reset the mode
807 if( Next() == NUMBER )
809 if ( nVal == 1 || nVal == 0 )
811 bVBASupportOn = ( nVal == 1 );
812 if ( bVBASupportOn )
814 EnableCompatibility();
816 // if the module setting is different
817 // reset it to what the Option tells us
818 if ( bVBASupportOn != aGen.GetModule().IsVBACompat() )
820 aGen.GetModule().SetVBACompat( bVBASupportOn );
822 break;
825 Error( ERRCODE_BASIC_EXPECTED, "0/1" );
826 break;
827 default:
828 Error( ERRCODE_BASIC_BAD_OPTION, eCurTok );
832 static void addStringConst( SbiSymPool& rPool, const OUString& pSym, const OUString& rStr )
834 SbiConstDef* pConst = new SbiConstDef( pSym );
835 pConst->SetType( SbxSTRING );
836 pConst->Set( rStr );
837 rPool.Add( pConst );
840 void SbiParser::AddConstants()
842 // #113063 Create constant RTL symbols
843 addStringConst( aPublics, "vbCr", "\x0D" );
844 addStringConst( aPublics, "vbCrLf", "\x0D\x0A" );
845 addStringConst( aPublics, "vbFormFeed", "\x0C" );
846 addStringConst( aPublics, "vbLf", "\x0A" );
847 #ifdef _WIN32
848 addStringConst( aPublics, "vbNewLine", "\x0D\x0A" );
849 #else
850 addStringConst( aPublics, "vbNewLine", "\x0A" );
851 #endif
852 addStringConst( aPublics, "vbNullString", "" );
853 addStringConst( aPublics, "vbTab", "\x09" );
854 addStringConst( aPublics, "vbVerticalTab", "\x0B" );
856 // Force length 1 and make char 0 afterwards
857 OUString aNullCharStr(u'\0');
858 addStringConst( aPublics, "vbNullChar", aNullCharStr );
861 // ERROR n
863 void SbiParser::ErrorStmnt()
865 SbiExpression aPar( this );
866 aPar.Gen();
867 aGen.Gen( SbiOpcode::ERROR_ );
870 /* vim:set shiftwidth=4 softtabstop=4 expandtab: */