1 /*************************************************************************
3 * DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
5 * Copyright 2008 by Sun Microsystems, Inc.
7 * OpenOffice.org - a multi-platform office productivity suite
9 * $RCSfile: parser.cxx,v $
12 * This file is part of OpenOffice.org.
14 * OpenOffice.org is free software: you can redistribute it and/or modify
15 * it under the terms of the GNU Lesser General Public License version 3
16 * only, as published by the Free Software Foundation.
18 * OpenOffice.org is distributed in the hope that it will be useful,
19 * but WITHOUT ANY WARRANTY; without even the implied warranty of
20 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
21 * GNU Lesser General Public License version 3 for more details
22 * (a copy is included in the LICENSE file that accompanied this code).
24 * You should have received a copy of the GNU Lesser General Public License
25 * version 3 along with OpenOffice.org. If not, see
26 * <http://www.openoffice.org/license.html>
27 * for a copy of the LGPLv3 License.
29 ************************************************************************/
31 // MARKER(update_precomp.py): autogen include statement, do not remove
32 #include "precompiled_basic.hxx"
33 #include <basic/sbx.hxx>
36 struct SbiParseStack
{ // "Stack" fuer Statement-Blocks
37 SbiParseStack
* pNext
; // Chain
38 SbiExprNode
* pWithVar
; // Variable fuer WITH
39 SbiToken eExitTok
; // Exit-Token
40 UINT32 nChain
; // JUMP-Chain
45 void( SbiParser::*Func
)(); // Verarbeitungsroutine
46 BOOL bMain
; // TRUE: ausserhalb SUBs OK
47 BOOL bSubr
; // TRUE: in SUBs OK
53 static SbiStatement StmntTable
[] = {
54 { ATTRIBUTE
, &SbiParser::Attribute
, Y
, Y
, }, // ATTRIBUTE
55 { CALL
, &SbiParser::Call
, N
, Y
, }, // CALL
56 { CLOSE
, &SbiParser::Close
, N
, Y
, }, // CLOSE
57 { _CONST_
, &SbiParser::Dim
, Y
, Y
, }, // CONST
58 { DECLARE
, &SbiParser::Declare
, Y
, N
, }, // DECLARE
59 { DEFBOOL
, &SbiParser::DefXXX
, Y
, N
, }, // DEFBOOL
60 { DEFCUR
, &SbiParser::DefXXX
, Y
, N
, }, // DEFCUR
61 { DEFDATE
, &SbiParser::DefXXX
, Y
, N
, }, // DEFDATE
62 { DEFDBL
, &SbiParser::DefXXX
, Y
, N
, }, // DEFDBL
63 { DEFERR
, &SbiParser::DefXXX
, Y
, N
, }, // DEFERR
64 { DEFINT
, &SbiParser::DefXXX
, Y
, N
, }, // DEFINT
65 { DEFLNG
, &SbiParser::DefXXX
, Y
, N
, }, // DEFLNG
66 { DEFOBJ
, &SbiParser::DefXXX
, Y
, N
, }, // DEFOBJ
67 { DEFSNG
, &SbiParser::DefXXX
, Y
, N
, }, // DEFSNG
68 { DEFSTR
, &SbiParser::DefXXX
, Y
, N
, }, // DEFSTR
69 { DEFVAR
, &SbiParser::DefXXX
, Y
, N
, }, // DEFVAR
70 { DIM
, &SbiParser::Dim
, Y
, Y
, }, // DIM
71 { DO
, &SbiParser::DoLoop
, N
, Y
, }, // DO
72 { ELSE
, &SbiParser::NoIf
, N
, Y
, }, // ELSE
73 { ELSEIF
, &SbiParser::NoIf
, N
, Y
, }, // ELSEIF
74 { ENDIF
, &SbiParser::NoIf
, N
, Y
, }, // ENDIF
75 { END
, &SbiParser::Stop
, N
, Y
, }, // END
76 { ENUM
, &SbiParser::Enum
, Y
, N
, }, // TYPE
77 { ERASE
, &SbiParser::Erase
, N
, Y
, }, // ERASE
78 { _ERROR_
, &SbiParser::ErrorStmnt
, N
, Y
, }, // ERROR
79 { EXIT
, &SbiParser::Exit
, N
, Y
, }, // EXIT
80 { FOR
, &SbiParser::For
, N
, Y
, }, // FOR
81 { FUNCTION
, &SbiParser::SubFunc
, Y
, N
, }, // FUNCTION
82 { GOSUB
, &SbiParser::Goto
, N
, Y
, }, // GOSUB
83 { GLOBAL
, &SbiParser::Dim
, Y
, N
, }, // GLOBAL
84 { GOTO
, &SbiParser::Goto
, N
, Y
, }, // GOTO
85 { IF
, &SbiParser::If
, N
, Y
, }, // IF
86 { IMPLEMENTS
, &SbiParser::Implements
, Y
, N
, }, // IMPLEMENTS
87 { INPUT
, &SbiParser::Input
, N
, Y
, }, // INPUT
88 { LET
, &SbiParser::Assign
, N
, Y
, }, // LET
89 { LINEINPUT
,&SbiParser::LineInput
, N
, Y
, }, // LINE INPUT
90 { LOOP
, &SbiParser::BadBlock
, N
, Y
, }, // LOOP
91 { LSET
, &SbiParser::LSet
, N
, Y
, }, // LSET
92 { NAME
, &SbiParser::Name
, N
, Y
, }, // NAME
93 { NEXT
, &SbiParser::BadBlock
, N
, Y
, }, // NEXT
94 { ON
, &SbiParser::On
, N
, Y
, }, // ON
95 { OPEN
, &SbiParser::Open
, N
, Y
, }, // OPEN
96 { OPTION
, &SbiParser::Option
, Y
, N
, }, // OPTION
97 { PRINT
, &SbiParser::Print
, N
, Y
, }, // PRINT
98 { PRIVATE
, &SbiParser::Dim
, Y
, N
, }, // PRIVATE
99 { PROPERTY
, &SbiParser::SubFunc
, Y
, N
, }, // FUNCTION
100 { PUBLIC
, &SbiParser::Dim
, Y
, N
, }, // PUBLIC
101 { REDIM
, &SbiParser::ReDim
, N
, Y
, }, // DIM
102 { RESUME
, &SbiParser::Resume
, N
, Y
, }, // RESUME
103 { RETURN
, &SbiParser::Return
, N
, Y
, }, // RETURN
104 { RSET
, &SbiParser::RSet
, N
, Y
, }, // RSET
105 { SELECT
, &SbiParser::Select
, N
, Y
, }, // SELECT
106 { SET
, &SbiParser::Set
, N
, Y
, }, // SET
107 { STATIC
, &SbiParser::Static
, Y
, Y
, }, // STATIC
108 { STOP
, &SbiParser::Stop
, N
, Y
, }, // STOP
109 { SUB
, &SbiParser::SubFunc
, Y
, N
, }, // SUB
110 { TYPE
, &SbiParser::Type
, Y
, N
, }, // TYPE
111 { UNTIL
, &SbiParser::BadBlock
, N
, Y
, }, // UNTIL
112 { WHILE
, &SbiParser::While
, N
, Y
, }, // WHILE
113 { WEND
, &SbiParser::BadBlock
, N
, Y
, }, // WEND
114 { WITH
, &SbiParser::With
, N
, Y
, }, // WITH
115 { WRITE
, &SbiParser::Write
, N
, Y
, }, // WRITE
122 // 'this' : used in base member initializer list
123 #pragma warning( disable: 4355 )
126 SbiParser::SbiParser( StarBASIC
* pb
, SbModule
* pm
)
127 : SbiTokenizer( pm
->GetSource32(), pb
),
130 aGlobals( aGblStrings
, SbGLOBAL
),
131 aPublics( aGblStrings
, SbPUBLIC
),
132 aRtlSyms( aGblStrings
, SbRTL
),
133 aGen( *pm
, this, 1024 )
148 bClassModule
= ( pm
->GetModuleType() == com::sun::star::script::ModuleType::Class
);
149 OSL_TRACE("Parser - %s, bClassModule %d", rtl::OUStringToOString( pm
->GetName(), RTL_TEXTENCODING_UTF8
).getStr(), bClassModule
);
151 for( short i
= 0; i
< 26; i
++ )
152 eDefTypes
[ i
] = SbxVARIANT
; // Kein expliziter Defaulttyp
154 aPublics
.SetParent( &aGlobals
);
155 aGlobals
.SetParent( &aRtlSyms
);
157 // Die globale Chainkette faengt bei Adresse 0 an:
158 nGblChain
= aGen
.Gen( _JUMP
, 0 );
160 rTypeArray
= new SbxArray
; // Array fuer Benutzerdefinierte Typen
161 rEnumArray
= new SbxArray
; // Array for Enum types
162 bVBASupportOn
= pm
->IsVBACompat();
164 EnableCompatibility();
169 // Ist Teil der Runtime-Library?
170 SbiSymDef
* SbiParser::CheckRTLForSym( const String
& rSym
, SbxDataType eType
)
172 SbxVariable
* pVar
= GetBasic()->GetRtl()->Find( rSym
, SbxCLASS_DONTCARE
);
173 SbiSymDef
* pDef
= NULL
;
176 if( pVar
->IsA( TYPE(SbxMethod
) ) )
178 SbiProcDef
* pProc_
= aRtlSyms
.AddProc( rSym
);
179 pProc_
->SetType( pVar
->GetType() );
184 pDef
= aRtlSyms
.AddSym( rSym
);
185 pDef
->SetType( eType
);
191 // Globale Chainkette schliessen
193 BOOL
SbiParser::HasGlobalCode()
195 if( bGblDefs
&& nGblChain
)
197 aGen
.BackChain( nGblChain
);
199 // aGen.Gen( _STOP );
205 void SbiParser::OpenBlock( SbiToken eTok
, SbiExprNode
* pVar
)
207 SbiParseStack
* p
= new SbiParseStack
;
210 p
->pWithVar
= pWithVar
;
215 // #29955 for-Schleifen-Ebene pflegen
220 void SbiParser::CloseBlock()
224 SbiParseStack
* p
= pStack
;
226 // #29955 for-Schleifen-Ebene pflegen
227 if( p
->eExitTok
== FOR
)
230 aGen
.BackChain( p
->nChain
);
232 pWithVar
= p
->pWithVar
;
239 void SbiParser::Exit()
241 SbiToken eTok
= Next();
242 for( SbiParseStack
* p
= pStack
; p
; p
= p
->pNext
)
244 if( eTok
== p
->eExitTok
)
246 p
->nChain
= aGen
.Gen( _JUMP
, p
->nChain
);
251 Error( SbERR_EXPECTED
, pStack
->eExitTok
);
253 Error( SbERR_BAD_EXIT
);
256 BOOL
SbiParser::TestSymbol( BOOL bKwdOk
)
259 if( eCurTok
== SYMBOL
|| ( bKwdOk
&& IsKwd( eCurTok
) ) )
263 Error( SbERR_SYMBOL_EXPECTED
);
267 // Testen auf ein bestimmtes Token
269 BOOL
SbiParser::TestToken( SbiToken t
)
277 Error( SbERR_EXPECTED
, t
);
282 // Testen auf Komma oder EOLN
284 BOOL
SbiParser::TestComma()
286 SbiToken eTok
= Peek();
292 else if( eTok
!= COMMA
)
294 Error( SbERR_EXPECTED
, COMMA
);
301 // Testen, ob EOLN vorliegt
303 void SbiParser::TestEoln()
305 if( !IsEoln( Next() ) )
307 Error( SbERR_EXPECTED
, EOLN
);
308 while( !IsEoln( Next() ) ) {}
312 // If some keywords e.g. Name have been dim as a variable,
313 // they should be treated as symbol
314 BOOL
SbiParser::IsSymbol( SbiToken t
)
316 // FIXME: if "name" is a argument in a subroutine like "Sub Test( name as String )".
317 if( IsVBASupportOn() && ( t
== NAME
|| t
== LINE
|| t
== TEXT
))
319 if( pCurStat
&& ( pCurStat
->eTok
== DIM
|| pCurStat
->eTok
== PUBLIC
||
320 pCurStat
->eTok
== PRIVATE
|| pCurStat
->eTok
== GLOBAL
))
324 if( pPool
->Find(aSym
) )
332 // Parsing eines Statement-Blocks
333 // Das Parsing laeuft bis zum Ende-Token.
335 void SbiParser::StmntBlock( SbiToken eEnd
)
337 SbiToken xe
= eEndTok
;
339 while( !bAbort
&& Parse() ) {}
343 Error( SbERR_BAD_BLOCK
, eEnd
);
348 // Die Hauptroutine. Durch wiederholten Aufrufs dieser Routine wird
349 // die Quelle geparst. Returnwert FALSE bei Ende/Fehlern.
351 BOOL
SbiParser::Parse()
353 if( bAbort
) return FALSE
;
357 bErrorIsSymbol
= false;
359 bErrorIsSymbol
= true;
363 // AB #33133: Falls keine Sub angelegt wurde, muss hier
364 // der globale Chain abgeschlossen werden!
365 // AB #40689: Durch die neue static-Behandlung kann noch
366 // ein nGblChain vorhanden sein, daher vorher abfragen
367 if( bNewGblDefs
&& nGblChain
== 0 )
368 nGblChain
= aGen
.Gen( _JUMP
, 0 );
373 if( IsEoln( eCurTok
) )
378 if( !bSingleLineIf
&& MayBeLabel( TRUE
) )
382 Error( SbERR_NOT_IN_MAIN
, aSym
);
384 pProc
->GetLabels().Define( aSym
);
387 if( IsEoln( eCurTok
) )
393 // Ende des Parsings?
394 if( eCurTok
== eEndTok
)
408 // In vba it's possible to do Error.foobar ( even if it results in
410 if ( eCurTok
== _ERROR_
&& IsVBASupportOn() ) // we probably need to define a subset of keywords where this madness applies e.g. if ( IsVBASupportOn() && SymbolCanBeRedined( eCurTok ) )
412 SbiTokenizer
tokens( *(SbiTokenizer
*)this );
414 if ( tokens
.Peek() == DOT
)
420 // Kommt ein Symbol, ist es entweder eine Variable( LET )
421 // oder eine SUB-Prozedur( CALL ohne Klammern )
422 // DOT fuer Zuweisungen im WITH-Block: .A=5
423 if( eCurTok
== SYMBOL
|| eCurTok
== DOT
)
426 Error( SbERR_EXPECTED
, SUB
);
429 // Damit Zeile & Spalte stimmen...
440 // Hier folgen nun die Statement-Parser.
443 for( p
= StmntTable
; p
->eTok
!= NIL
; p
++ )
444 if( p
->eTok
== eCurTok
)
448 if( !pProc
&& !p
->bMain
)
449 Error( SbERR_NOT_IN_MAIN
, eCurTok
);
450 else if( pProc
&& !p
->bSubr
)
451 Error( SbERR_NOT_IN_SUBR
, eCurTok
);
454 // globalen Chain pflegen
455 // AB #41606/#40689: Durch die neue static-Behandlung kann noch
456 // ein nGblChain vorhanden sein, daher vorher abfragen
457 if( bNewGblDefs
&& nGblChain
== 0 &&
458 ( eCurTok
== SUB
|| eCurTok
== FUNCTION
|| eCurTok
== PROPERTY
) )
460 nGblChain
= aGen
.Gen( _JUMP
, 0 );
463 // Statement-Opcode bitte auch am Anfang einer Sub
464 if( ( p
->bSubr
&& (eCurTok
!= STATIC
|| Peek() == SUB
|| Peek() == FUNCTION
) ) ||
465 eCurTok
== SUB
|| eCurTok
== FUNCTION
)
468 (this->*( p
->Func
) )();
470 SbxError nSbxErr
= SbxBase::GetError();
472 SbxBase::ResetError(), Error( (SbError
)nSbxErr
);
476 Error( SbERR_UNEXPECTED
, eCurTok
);
479 // Test auf Ende des Statements:
480 // Kann auch ein ELSE sein, da vor dem ELSE kein : stehen muss!
485 if( !IsEos() && eCurTok
!= ELSE
)
487 // falls das Parsing abgebrochen wurde, bis zum ":" vorgehen:
488 Error( SbERR_UNEXPECTED
, eCurTok
);
489 while( !IsEos() ) Next();
492 // Der Parser bricht am Ende ab, das naechste Token ist noch nicht
497 // Innerste With-Variable liefern
498 SbiExprNode
* SbiParser::GetWithVar()
503 // Sonst im Stack suchen
504 SbiParseStack
* p
= pStack
;
507 // LoopVar kann zur Zeit nur fuer with sein
516 // Zuweisung oder Subroutine Call
518 void SbiParser::Symbol()
520 SbiExprMode eMode
= bVBASupportOn
? EXPRMODE_STANDALONE
: EXPRMODE_STANDARD
;
521 SbiExpression
aVar( this, SbSYMBOL
, eMode
);
523 bool bEQ
= ( Peek() == EQ
);
524 if( !bEQ
&& bVBASupportOn
&& aVar
.IsBracket() )
525 Error( SbERR_EXPECTED
, "=" );
527 RecursiveMode eRecMode
= ( bEQ
? PREVENT_CALL
: FORCE_CALL
);
528 bool bSpecialMidHandling
= false;
529 SbiSymDef
* pDef
= aVar
.GetRealVar();
530 if( bEQ
&& pDef
&& pDef
->GetScope() == SbRTL
)
532 String aRtlName
= pDef
->GetName();
533 if( aRtlName
.EqualsIgnoreCaseAscii("Mid") )
535 SbiExprNode
* pExprNode
= aVar
.GetExprNode();
536 // SbiNodeType eNodeType;
537 if( pExprNode
&& pExprNode
->GetNodeType() == SbxVARVAL
)
539 SbiExprList
* pPar
= pExprNode
->GetParameters();
540 short nParCount
= pPar
? pPar
->GetSize() : 0;
541 if( nParCount
== 2 || nParCount
== 3 )
544 pPar
->addExpression( new SbiExpression( this, -1, SbxLONG
) );
547 pPar
->addExpression( new SbiExpression( this ) );
549 bSpecialMidHandling
= true;
554 aVar
.Gen( eRecMode
);
555 if( !bSpecialMidHandling
)
563 // Dann muss es eine Zuweisung sein. Was anderes gibts nicht!
564 if( !aVar
.IsLvalue() )
565 Error( SbERR_LVALUE_EXPECTED
);
567 SbiExpression
aExpr( this );
569 SbiOpcode eOp
= _PUT
;
570 // SbiSymDef* pDef = aVar.GetRealVar();
573 if( pDef
->GetConstDef() )
574 Error( SbERR_DUPLICATE_DEF
, pDef
->GetName() );
575 if( pDef
->GetType() == SbxOBJECT
)
578 if( pDef
->GetTypeId() )
580 aGen
.Gen( _SETCLASS
, pDef
->GetTypeId() );
592 void SbiParser::Assign()
594 SbiExpression
aLvalue( this, SbLVALUE
);
596 SbiExpression
aExpr( this );
600 SbiSymDef
* pDef
= aLvalue
.GetRealVar();
602 if( pDef
->GetConstDef() )
603 Error( SbERR_DUPLICATE_DEF
, pDef
->GetName() );
604 nLen
= aLvalue
.GetRealVar()->GetLen();
607 aGen
.Gen( _PAD
, nLen
);
611 // Zuweisungen einer Objektvariablen
613 void SbiParser::Set()
615 SbiExpression
aLvalue( this, SbLVALUE
);
616 SbxDataType eType
= aLvalue
.GetType();
617 if( eType
!= SbxOBJECT
&& eType
!= SbxEMPTY
&& eType
!= SbxVARIANT
)
618 Error( SbERR_INVALID_OBJECT
);
620 SbiSymDef
* pDef
= aLvalue
.GetRealVar();
621 if( pDef
&& pDef
->GetConstDef() )
622 Error( SbERR_DUPLICATE_DEF
, pDef
->GetName() );
624 SbiToken eTok
= Peek();
629 SbiSymDef
* pTypeDef
= new SbiSymDef( aStr
);
630 TypeDecl( *pTypeDef
, TRUE
);
633 // aGen.Gen( _CLASS, pDef->GetTypeId() | 0x8000 );
634 aGen
.Gen( _CREATE
, pDef
->GetId(), pTypeDef
->GetTypeId() );
635 aGen
.Gen( _SETCLASS
, pDef
->GetTypeId() );
639 SbiExpression
aExpr( this );
642 // Its a good idea to distinguish between
643 // set someting = another &
644 // someting = another
645 // ( its necessary for vba objects where set is object
646 // specific and also doesn't involve processing default params )
647 if( pDef
->GetTypeId() )
650 aGen
.Gen( _VBASETCLASS
, pDef
->GetTypeId() );
652 aGen
.Gen( _SETCLASS
, pDef
->GetTypeId() );
666 void SbiParser::LSet()
668 SbiExpression
aLvalue( this, SbLVALUE
);
669 if( aLvalue
.GetType() != SbxSTRING
)
670 Error( SbERR_INVALID_OBJECT
);
672 SbiSymDef
* pDef
= aLvalue
.GetRealVar();
673 if( pDef
&& pDef
->GetConstDef() )
674 Error( SbERR_DUPLICATE_DEF
, pDef
->GetName() );
675 SbiExpression
aExpr( this );
682 void SbiParser::RSet()
684 SbiExpression
aLvalue( this, SbLVALUE
);
685 if( aLvalue
.GetType() != SbxSTRING
)
686 Error( SbERR_INVALID_OBJECT
);
688 SbiSymDef
* pDef
= aLvalue
.GetRealVar();
689 if( pDef
&& pDef
->GetConstDef() )
690 Error( SbERR_DUPLICATE_DEF
, pDef
->GetName() );
691 SbiExpression
aExpr( this );
697 // DEFINT, DEFLNG, DEFSNG, DEFDBL, DEFSTR und so weiter
699 void SbiParser::DefXXX()
701 sal_Unicode ch1
, ch2
;
702 SbxDataType t
= SbxDataType( eCurTok
- DEFINT
+ SbxINTEGER
);
706 if( Next() != SYMBOL
) break;
707 ch1
= aSym
.ToUpperAscii().GetBuffer()[0];
709 if( Peek() == MINUS
)
712 if( Next() != SYMBOL
) Error( SbERR_SYMBOL_EXPECTED
);
715 ch2
= aSym
.ToUpperAscii().GetBuffer()[0];
716 //ch2 = aSym.Upper();
717 if( ch2
< ch1
) Error( SbERR_SYNTAX
), ch2
= 0;
721 ch1
-= 'A'; ch2
-= 'A';
722 for (; ch1
<= ch2
; ch1
++) eDefTypes
[ ch1
] = t
;
723 if( !TestComma() ) break;
729 void SbiParser::Stop()
732 Peek(); // #35694: Nur Peek(), damit EOL in Single-Line-If erkannt wird
737 void SbiParser::Implements()
741 Error( SbERR_UNEXPECTED
, IMPLEMENTS
);
747 String aImplementedIface
= GetSym();
748 aIfaceVector
.push_back( aImplementedIface
);
752 void SbiParser::EnableCompatibility()
761 void SbiParser::Option()
766 bExplicit
= TRUE
; break;
768 if( Next() == NUMBER
)
770 if( nVal
== 0 || nVal
== 1 )
772 nBase
= (short) nVal
;
776 Error( SbERR_EXPECTED
, "0/1" );
780 String aString
= SbiTokenizer::Symbol(Next());
781 if( !aString
.EqualsIgnoreCaseAscii("Module") )
782 Error( SbERR_EXPECTED
, "Module" );
788 case TEXT
: bText
= TRUE
; return;
789 case BINARY
: bText
= FALSE
; return;
793 EnableCompatibility();
798 aGen
.GetModule().SetModuleType( com::sun::star::script::ModuleType::Class
);
800 case VBASUPPORT
: // Option VBASupport used to override the module mode ( in fact this must reset the mode
801 if( Next() == NUMBER
)
803 if ( nVal
== 1 || nVal
== 0 )
805 bVBASupportOn
= ( nVal
== 1 );
807 EnableCompatibility();
808 // if the module setting is different
809 // reset it to what the Option tells us
810 if ( bVBASupportOn
!= aGen
.GetModule().IsVBACompat() )
811 aGen
.GetModule().SetVBACompat( bVBASupportOn
);
815 Error( SbERR_EXPECTED
, "0/1" );
818 Error( SbERR_BAD_OPTION
, eCurTok
);
822 void addStringConst( SbiSymPool
& rPool
, const char* pSym
, const String
& rStr
)
824 SbiConstDef
* pConst
= new SbiConstDef( String::CreateFromAscii( pSym
) );
825 pConst
->SetType( SbxSTRING
);
830 inline void addStringConst( SbiSymPool
& rPool
, const char* pSym
, const char* pStr
)
832 addStringConst( rPool
, pSym
, String::CreateFromAscii( pStr
) );
835 void SbiParser::AddConstants( void )
837 // #113063 Create constant RTL symbols
838 addStringConst( aPublics
, "vbCr", "\x0D" );
839 addStringConst( aPublics
, "vbCrLf", "\x0D\x0A" );
840 addStringConst( aPublics
, "vbFormFeed", "\x0C" );
841 addStringConst( aPublics
, "vbLf", "\x0A" );
843 addStringConst( aPublics
, "vbNewLine", "\x0A" );
845 addStringConst( aPublics
, "vbNewLine", "\x0D\x0A" );
847 addStringConst( aPublics
, "vbNullString", "" );
848 addStringConst( aPublics
, "vbTab", "\x09" );
849 addStringConst( aPublics
, "vbVerticalTab", "\x0B" );
851 // Force length 1 and make char 0 afterwards
852 String
aNullCharStr( String::CreateFromAscii( " " ) );
853 aNullCharStr
.SetChar( 0, 0 );
854 addStringConst( aPublics
, "vbNullChar", aNullCharStr
);
859 void SbiParser::ErrorStmnt()
861 SbiExpression
aPar( this );