1 /* -*- Mode: C++; tab-width: 4; indent-tabs-mode: nil; c-basic-offset: 4 -*- */
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>
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
;
33 sal_uInt32 nChain
; // JUMP-Chain
40 void( SbiParser::*Func
)();
41 bool bMain
; // true: OK outside the SUB
42 bool bSubr
; // true: OK inside the SUB
50 const SbiStatement StmntTable
[] = {
51 { ATTRIBUTE
, &SbiParser::Attribute
, Y
, Y
, }, // ATTRIBUTE
52 { CALL
, &SbiParser::Call
, N
, Y
, }, // CALL
53 { CLOSE
, &SbiParser::Close
, N
, Y
, }, // CLOSE
54 { CONST_
, &SbiParser::Dim
, Y
, Y
, }, // CONST
55 { DECLARE
, &SbiParser::Declare
, Y
, N
, }, // DECLARE
56 { DEFBOOL
, &SbiParser::DefXXX
, Y
, N
, }, // DEFBOOL
57 { DEFCUR
, &SbiParser::DefXXX
, Y
, N
, }, // DEFCUR
58 { DEFDATE
, &SbiParser::DefXXX
, Y
, N
, }, // DEFDATE
59 { DEFDBL
, &SbiParser::DefXXX
, Y
, N
, }, // DEFDBL
60 { DEFERR
, &SbiParser::DefXXX
, Y
, N
, }, // DEFERR
61 { DEFINT
, &SbiParser::DefXXX
, Y
, N
, }, // DEFINT
62 { DEFLNG
, &SbiParser::DefXXX
, Y
, N
, }, // DEFLNG
63 { DEFOBJ
, &SbiParser::DefXXX
, Y
, N
, }, // DEFOBJ
64 { DEFSNG
, &SbiParser::DefXXX
, Y
, N
, }, // DEFSNG
65 { DEFSTR
, &SbiParser::DefXXX
, Y
, N
, }, // DEFSTR
66 { DEFVAR
, &SbiParser::DefXXX
, Y
, N
, }, // DEFVAR
67 { DIM
, &SbiParser::Dim
, Y
, Y
, }, // DIM
68 { DO
, &SbiParser::DoLoop
, N
, Y
, }, // DO
69 { ELSE
, &SbiParser::NoIf
, N
, Y
, }, // ELSE
70 { ELSEIF
, &SbiParser::NoIf
, N
, Y
, }, // ELSEIF
71 { ENDIF
, &SbiParser::NoIf
, N
, Y
, }, // ENDIF
72 { END
, &SbiParser::Stop
, N
, Y
, }, // END
73 { ENUM
, &SbiParser::Enum
, Y
, N
, }, // TYPE
74 { ERASE
, &SbiParser::Erase
, N
, Y
, }, // ERASE
75 { ERROR_
, &SbiParser::ErrorStmnt
, N
, Y
, }, // ERROR
76 { EXIT
, &SbiParser::Exit
, N
, Y
, }, // EXIT
77 { FOR
, &SbiParser::For
, N
, Y
, }, // FOR
78 { FUNCTION
, &SbiParser::SubFunc
, Y
, N
, }, // FUNCTION
79 { GOSUB
, &SbiParser::Goto
, N
, Y
, }, // GOSUB
80 { GLOBAL
, &SbiParser::Dim
, Y
, N
, }, // GLOBAL
81 { GOTO
, &SbiParser::Goto
, N
, Y
, }, // GOTO
82 { IF
, &SbiParser::If
, N
, Y
, }, // IF
83 { IMPLEMENTS
, &SbiParser::Implements
, Y
, N
, }, // IMPLEMENTS
84 { INPUT
, &SbiParser::Input
, N
, Y
, }, // INPUT
85 { LET
, &SbiParser::Assign
, N
, Y
, }, // LET
86 { LINE
, &SbiParser::Line
, N
, Y
, }, // LINE, -> LINE INPUT (#i92642)
87 { LINEINPUT
,&SbiParser::LineInput
, N
, Y
, }, // LINE INPUT
88 { LOOP
, &SbiParser::BadBlock
, N
, Y
, }, // LOOP
89 { LSET
, &SbiParser::LSet
, N
, Y
, }, // LSET
90 { NAME
, &SbiParser::Name
, N
, Y
, }, // NAME
91 { NEXT
, &SbiParser::BadBlock
, N
, Y
, }, // NEXT
92 { ON
, &SbiParser::On
, N
, Y
, }, // ON
93 { OPEN
, &SbiParser::Open
, N
, Y
, }, // OPEN
94 { OPTION
, &SbiParser::Option
, Y
, N
, }, // OPTION
95 { PRINT
, &SbiParser::Print
, N
, Y
, }, // PRINT
96 { PRIVATE
, &SbiParser::Dim
, Y
, N
, }, // PRIVATE
97 { PROPERTY
, &SbiParser::SubFunc
, Y
, N
, }, // FUNCTION
98 { PUBLIC
, &SbiParser::Dim
, Y
, N
, }, // PUBLIC
99 { REDIM
, &SbiParser::ReDim
, N
, Y
, }, // DIM
100 { RESUME
, &SbiParser::Resume
, N
, Y
, }, // RESUME
101 { RETURN
, &SbiParser::Return
, N
, Y
, }, // RETURN
102 { RSET
, &SbiParser::RSet
, N
, Y
, }, // RSET
103 { SELECT
, &SbiParser::Select
, N
, Y
, }, // SELECT
104 { SET
, &SbiParser::Set
, N
, Y
, }, // SET
105 { STATIC
, &SbiParser::Static
, Y
, Y
, }, // STATIC
106 { STOP
, &SbiParser::Stop
, N
, Y
, }, // STOP
107 { SUB
, &SbiParser::SubFunc
, Y
, N
, }, // SUB
108 { TYPE
, &SbiParser::Type
, Y
, N
, }, // TYPE
109 { UNTIL
, &SbiParser::BadBlock
, N
, Y
, }, // UNTIL
110 { WHILE
, &SbiParser::While
, N
, Y
, }, // WHILE
111 { WEND
, &SbiParser::BadBlock
, N
, Y
, }, // WEND
112 { WITH
, &SbiParser::With
, N
, Y
, }, // WITH
113 { WRITE
, &SbiParser::Write
, N
, Y
, }, // WRITE
115 { NIL
, nullptr, N
, N
}
119 SbiParser::SbiParser( StarBASIC
* pb
, SbModule
* pm
)
120 : SbiTokenizer( pm
->GetSource32(), pb
),
121 aGlobals( aGblStrings
, SbGLOBAL
, this ),
122 aPublics( aGblStrings
, SbPUBLIC
, this ),
123 aRtlSyms( aGblStrings
, SbRTL
, this ),
124 aGen( *pm
, this, 1024 )
136 bClassModule
= ( pm
->GetModuleType() == css::script::ModuleType::CLASS
);
138 for(SbxDataType
& eDefType
: eDefTypes
)
139 eDefType
= SbxVARIANT
; // no explicit default type
141 aPublics
.SetParent( &aGlobals
);
142 aGlobals
.SetParent( &aRtlSyms
);
145 nGblChain
= aGen
.Gen( SbiOpcode::JUMP_
, 0 );
147 rTypeArray
= new SbxArray
; // array for user defined types
148 rEnumArray
= new SbxArray
; // array for Enum types
149 bVBASupportOn
= pm
->IsVBACompat();
151 EnableCompatibility();
155 SbiParser::~SbiParser() { }
157 // part of the runtime-library?
158 SbiSymDef
* SbiParser::CheckRTLForSym(const OUString
& rSym
, SbxDataType eType
)
160 SbxVariable
* pVar
= GetBasic()->GetRtl()->Find(rSym
, SbxClassType::DontCare
);
164 if (SbxMethod
* pMethod
= dynamic_cast<SbxMethod
*>(pVar
))
166 SbiProcDef
* pProc_
= aRtlSyms
.AddProc( rSym
);
167 if (pMethod
->IsRuntimeFunction())
169 pProc_
->SetType( pMethod
->GetRuntimeFunctionReturnType() );
173 pProc_
->SetType( pVar
->GetType() );
179 SbiSymDef
* pDef
= aRtlSyms
.AddSym(rSym
);
180 pDef
->SetType(eType
);
184 // close global chain
186 bool SbiParser::HasGlobalCode()
188 if( bGblDefs
&& nGblChain
)
190 aGen
.BackChain( nGblChain
);
191 aGen
.Gen( SbiOpcode::LEAVE_
);
197 void SbiParser::OpenBlock( SbiToken eTok
, SbiExprNode
* pVar
)
199 SbiParseStack
* p
= new SbiParseStack
;
202 p
->pWithVar
= pWithVar
;
207 // #29955 service the for-loop level
212 void SbiParser::CloseBlock()
217 SbiParseStack
* p
= pStack
;
219 // #29955 service the for-loop level
220 if( p
->eExitTok
== FOR
)
223 aGen
.BackChain( p
->nChain
);
225 pWithVar
= p
->pWithVar
;
231 void SbiParser::Exit()
233 SbiToken eTok
= Next();
234 for( SbiParseStack
* p
= pStack
; p
; p
= p
->pNext
)
236 SbiToken eExitTok
= p
->eExitTok
;
237 if( eTok
== eExitTok
||
238 (eTok
== PROPERTY
&& (eExitTok
== GET
|| eExitTok
== LET
) ) ) // #i109051
240 p
->nChain
= aGen
.Gen( SbiOpcode::JUMP_
, p
->nChain
);
245 Error( ERRCODE_BASIC_EXPECTED
, pStack
->eExitTok
);
247 Error( ERRCODE_BASIC_BAD_EXIT
);
250 bool SbiParser::TestSymbol()
253 if( eCurTok
== SYMBOL
)
257 Error( ERRCODE_BASIC_SYMBOL_EXPECTED
);
262 bool SbiParser::TestToken( SbiToken t
)
270 Error( ERRCODE_BASIC_EXPECTED
, t
);
276 bool SbiParser::TestComma()
278 SbiToken eTok
= Peek();
284 else if( eTok
!= COMMA
)
286 Error( ERRCODE_BASIC_EXPECTED
, COMMA
);
294 void SbiParser::TestEoln()
296 if( !IsEoln( Next() ) )
298 Error( ERRCODE_BASIC_EXPECTED
, EOLN
);
299 while( !IsEoln( Next() ) ) {}
304 void SbiParser::StmntBlock( SbiToken eEnd
)
306 SbiToken xe
= eEndTok
;
308 while( !bAbort
&& Parse() ) {}
312 Error( ERRCODE_BASIC_BAD_BLOCK
, eEnd
);
317 void SbiParser::SetCodeCompleting( bool b
)
323 bool SbiParser::Parse()
325 if( bAbort
) return false;
329 bErrorIsSymbol
= false;
331 bErrorIsSymbol
= true;
335 // AB #33133: If no sub has been created before,
336 // the global chain must be closed here!
337 // AB #40689: Due to the new static-handling there
338 // can be another nGblChain, so ask for it before.
339 if( bNewGblDefs
&& nGblChain
== 0 )
340 nGblChain
= aGen
.Gen( SbiOpcode::JUMP_
, 0 );
345 if( IsEoln( eCurTok
) )
350 if( !bSingleLineIf
&& MayBeLabel( true ) )
354 Error( ERRCODE_BASIC_NOT_IN_MAIN
, aSym
);
356 pProc
->GetLabels().Define( aSym
);
359 if( IsEoln( eCurTok
) )
366 if( eCurTok
== eEndTok
||
367 ( bVBASupportOn
&& // #i109075
368 (eCurTok
== ENDFUNC
|| eCurTok
== ENDPROPERTY
|| eCurTok
== ENDSUB
) &&
369 (eEndTok
== ENDFUNC
|| eEndTok
== ENDPROPERTY
|| eEndTok
== ENDSUB
) ) )
383 // In vba it's possible to do Error.foobar ( even if it results in
385 if ( eCurTok
== ERROR_
&& IsVBASupportOn() ) // we probably need to define a subset of keywords where this madness applies e.g. if ( IsVBASupportOn() && SymbolCanBeRedined( eCurTok ) )
387 SbiTokenizer
tokens( *this );
389 if ( tokens
.Peek() == DOT
)
395 // if there's a symbol, it's either a variable (LET)
396 // or a SUB-procedure (CALL without brackets)
397 // DOT for assignments in the WITH-block: .A=5
398 if( eCurTok
== SYMBOL
|| eCurTok
== DOT
)
401 Error( ERRCODE_BASIC_EXPECTED
, SUB
);
404 // for correct line and column...
417 const SbiStatement
* p
;
418 for( p
= StmntTable
; p
->eTok
!= NIL
; p
++ )
419 if( p
->eTok
== eCurTok
)
423 if( !pProc
&& !p
->bMain
)
424 Error( ERRCODE_BASIC_NOT_IN_MAIN
, eCurTok
);
425 else if( pProc
&& !p
->bSubr
)
426 Error( ERRCODE_BASIC_NOT_IN_SUBR
, eCurTok
);
429 // AB #41606/#40689: Due to the new static-handling there
430 // can be another nGblChain, so ask for it before.
431 if( bNewGblDefs
&& nGblChain
== 0 &&
432 ( eCurTok
== SUB
|| eCurTok
== FUNCTION
|| eCurTok
== PROPERTY
) )
434 nGblChain
= aGen
.Gen( SbiOpcode::JUMP_
, 0 );
437 // statement-opcode at the beginning of a sub, too, please
438 if( ( p
->bSubr
&& (eCurTok
!= STATIC
|| Peek() == SUB
|| Peek() == FUNCTION
) ) ||
439 eCurTok
== SUB
|| eCurTok
== FUNCTION
)
441 (this->*( p
->Func
) )();
442 ErrCode nSbxErr
= SbxBase::GetError();
445 SbxBase::ResetError();
451 Error( ERRCODE_BASIC_UNEXPECTED
, eCurTok
);
454 // test for the statement's end -
455 // might also be an ELSE, as there must not necessary be a : before the ELSE!
460 if( !IsEos() && eCurTok
!= ELSE
)
462 // if the parsing has been aborted, jump over to the ":"
463 Error( ERRCODE_BASIC_UNEXPECTED
, eCurTok
);
464 while( !IsEos() ) Next();
467 // The parser aborts at the end, the
468 // next token has not been fetched yet!
473 SbiExprNode
* SbiParser::GetWithVar()
478 SbiParseStack
* p
= pStack
;
481 // LoopVar can at the moment only be for with
490 // assignment or subroutine call
492 void SbiParser::Symbol( const KeywordSymbolInfo
* pKeywordSymbolInfo
)
494 SbiExprMode eMode
= bVBASupportOn
? EXPRMODE_STANDALONE
: EXPRMODE_STANDARD
;
495 SbiExpression
aVar( this, SbSYMBOL
, eMode
, pKeywordSymbolInfo
);
497 bool bEQ
= ( Peek() == EQ
);
498 if( !bEQ
&& bVBASupportOn
&& aVar
.IsBracket() )
499 Error( ERRCODE_BASIC_EXPECTED
, "=" );
501 RecursiveMode eRecMode
= ( bEQ
? PREVENT_CALL
: FORCE_CALL
);
502 bool bSpecialMidHandling
= false;
503 SbiSymDef
* pDef
= aVar
.GetRealVar();
504 if( bEQ
&& pDef
&& pDef
->GetScope() == SbRTL
)
506 OUString aRtlName
= pDef
->GetName();
507 if( aRtlName
.equalsIgnoreAsciiCase("Mid") )
509 SbiExprNode
* pExprNode
= aVar
.GetExprNode();
510 if( pExprNode
&& pExprNode
->GetNodeType() == SbxVARVAL
)
512 SbiExprList
* pPar
= pExprNode
->GetParameters();
513 short nParCount
= pPar
? pPar
->GetSize() : 0;
514 if( nParCount
== 2 || nParCount
== 3 )
517 pPar
->addExpression( std::make_unique
<SbiExpression
>( this, -1, SbxLONG
) );
520 pPar
->addExpression( std::make_unique
<SbiExpression
>( this ) );
522 bSpecialMidHandling
= true;
527 aVar
.Gen( eRecMode
);
528 if( bSpecialMidHandling
)
533 aGen
.Gen( SbiOpcode::GET_
);
537 // so it must be an assignment!
538 if( !aVar
.IsLvalue() )
539 Error( ERRCODE_BASIC_LVALUE_EXPECTED
);
541 SbiExpression
aExpr( this );
543 SbiOpcode eOp
= SbiOpcode::PUT_
;
546 if( pDef
->GetConstDef() )
547 Error( ERRCODE_BASIC_DUPLICATE_DEF
, pDef
->GetName() );
548 if( pDef
->GetType() == SbxOBJECT
)
550 eOp
= SbiOpcode::SET_
;
551 if( pDef
->GetTypeId() )
553 aGen
.Gen( SbiOpcode::SETCLASS_
, pDef
->GetTypeId() );
563 void SbiParser::Assign()
565 SbiExpression
aLvalue( this, SbLVALUE
);
567 SbiExpression
aExpr( this );
571 SbiSymDef
* pDef
= aLvalue
.GetRealVar();
573 if( pDef
->GetConstDef() )
574 Error( ERRCODE_BASIC_DUPLICATE_DEF
, pDef
->GetName() );
575 nLen
= aLvalue
.GetRealVar()->GetLen();
578 aGen
.Gen( SbiOpcode::PAD_
, nLen
);
579 aGen
.Gen( SbiOpcode::PUT_
);
582 // assignments of an object-variable
584 void SbiParser::Set()
586 SbiExpression
aLvalue( this, SbLVALUE
);
587 SbxDataType eType
= aLvalue
.GetType();
588 if( eType
!= SbxOBJECT
&& eType
!= SbxEMPTY
&& eType
!= SbxVARIANT
)
589 Error( ERRCODE_BASIC_INVALID_OBJECT
);
591 SbiSymDef
* pDef
= aLvalue
.GetRealVar();
592 if( pDef
->GetConstDef() )
593 Error( ERRCODE_BASIC_DUPLICATE_DEF
, pDef
->GetName() );
595 SbiToken eTok
= Peek();
599 auto pTypeDef
= std::make_unique
<SbiSymDef
>( OUString() );
600 TypeDecl( *pTypeDef
, true );
603 aGen
.Gen( SbiOpcode::CREATE_
, pDef
->GetId(), pTypeDef
->GetTypeId() );
604 aGen
.Gen( SbiOpcode::SETCLASS_
, pDef
->GetTypeId() );
608 SbiExpression
aExpr( this );
611 // It's a good idea to distinguish between
612 // set something = another &
613 // something = another
614 // ( it's necessary for vba objects where set is object
615 // specific and also doesn't involve processing default params )
616 if( pDef
->GetTypeId() )
619 aGen
.Gen( SbiOpcode::VBASETCLASS_
, pDef
->GetTypeId() );
621 aGen
.Gen( SbiOpcode::SETCLASS_
, pDef
->GetTypeId() );
626 aGen
.Gen( SbiOpcode::VBASET_
);
628 aGen
.Gen( SbiOpcode::SET_
);
634 void SbiParser::LSet()
636 SbiExpression
aLvalue( this, SbLVALUE
);
637 if( aLvalue
.GetType() != SbxSTRING
)
639 Error( ERRCODE_BASIC_INVALID_OBJECT
);
642 SbiSymDef
* pDef
= aLvalue
.GetRealVar();
643 if( pDef
&& pDef
->GetConstDef() )
645 Error( ERRCODE_BASIC_DUPLICATE_DEF
, pDef
->GetName() );
647 SbiExpression
aExpr( this );
650 aGen
.Gen( SbiOpcode::LSET_
);
654 void SbiParser::RSet()
656 SbiExpression
aLvalue( this, SbLVALUE
);
657 if( aLvalue
.GetType() != SbxSTRING
)
659 Error( ERRCODE_BASIC_INVALID_OBJECT
);
662 SbiSymDef
* pDef
= aLvalue
.GetRealVar();
663 if( pDef
&& pDef
->GetConstDef() )
664 Error( ERRCODE_BASIC_DUPLICATE_DEF
, pDef
->GetName() );
665 SbiExpression
aExpr( this );
668 aGen
.Gen( SbiOpcode::RSET_
);
671 // DEFINT, DEFLNG, DEFSNG, DEFDBL, DEFSTR and so on
673 void SbiParser::DefXXX()
675 sal_Unicode ch1
, ch2
;
676 SbxDataType t
= SbxDataType( eCurTok
- DEFINT
+ SbxINTEGER
);
680 if( Next() != SYMBOL
) break;
681 ch1
= rtl::toAsciiUpperCase(aSym
[0]);
683 if( Peek() == MINUS
)
686 if( Next() != SYMBOL
) Error( ERRCODE_BASIC_SYMBOL_EXPECTED
);
689 ch2
= rtl::toAsciiUpperCase(aSym
[0]);
692 Error( ERRCODE_BASIC_SYNTAX
);
698 ch1
-= 'A'; ch2
-= 'A';
699 for (; ch1
<= ch2
; ch1
++) eDefTypes
[ ch1
] = t
;
700 if( !TestComma() ) break;
706 void SbiParser::Stop()
708 aGen
.Gen( SbiOpcode::STOP_
);
709 Peek(); // #35694: only Peek(), so that EOL is recognized in Single-Line-If
714 void SbiParser::Implements()
718 Error( ERRCODE_BASIC_UNEXPECTED
, IMPLEMENTS
);
723 if( eCurTok
!= SYMBOL
)
725 Error( ERRCODE_BASIC_SYMBOL_EXPECTED
);
729 OUString aImplementedIface
= aSym
;
733 OUString
aDotStr( '.' );
734 while( Peek() == DOT
)
736 aImplementedIface
+= aDotStr
;
738 SbiToken ePeekTok
= Peek();
739 if( ePeekTok
== SYMBOL
|| IsKwd( ePeekTok
) )
742 aImplementedIface
+= aSym
;
747 Error( ERRCODE_BASIC_SYMBOL_EXPECTED
);
752 aIfaceVector
.push_back( aImplementedIface
);
755 void SbiParser::EnableCompatibility()
764 void SbiParser::Option()
769 bExplicit
= true; break;
771 if( Next() == NUMBER
&& ( nVal
== 0 || nVal
== 1 ) )
773 nBase
= static_cast<short>(nVal
);
776 Error( ERRCODE_BASIC_EXPECTED
, "0/1" );
780 OUString aString
= SbiTokenizer::Symbol(Next());
781 if( !aString
.equalsIgnoreAsciiCase("Module") )
783 Error( ERRCODE_BASIC_EXPECTED
, "Module" );
789 SbiToken eTok
= Next();
793 else if( eTok
== SYMBOL
&& GetSym().equalsIgnoreAsciiCase("text") )
798 Error( ERRCODE_BASIC_EXPECTED
, "Text/Binary" );
803 EnableCompatibility();
808 aGen
.GetModule().SetModuleType( css::script::ModuleType::CLASS
);
810 case VBASUPPORT
: // Option VBASupport used to override the module mode ( in fact this must reset the mode
811 if( Next() == NUMBER
)
813 if ( nVal
== 1 || nVal
== 0 )
815 bVBASupportOn
= ( nVal
== 1 );
818 EnableCompatibility();
820 // if the module setting is different
821 // reset it to what the Option tells us
822 if ( bVBASupportOn
!= aGen
.GetModule().IsVBACompat() )
824 aGen
.GetModule().SetVBACompat( bVBASupportOn
);
829 Error( ERRCODE_BASIC_EXPECTED
, "0/1" );
832 Error( ERRCODE_BASIC_BAD_OPTION
, eCurTok
);
836 static void addStringConst( SbiSymPool
& rPool
, const OUString
& pSym
, const OUString
& rStr
)
838 SbiConstDef
* pConst
= new SbiConstDef( pSym
);
839 pConst
->SetType( SbxSTRING
);
844 void SbiParser::AddConstants()
846 // #113063 Create constant RTL symbols
847 addStringConst( aPublics
, "vbCr", "\x0D" );
848 addStringConst( aPublics
, "vbCrLf", "\x0D\x0A" );
849 addStringConst( aPublics
, "vbFormFeed", "\x0C" );
850 addStringConst( aPublics
, "vbLf", "\x0A" );
852 addStringConst( aPublics
, "vbNewLine", "\x0D\x0A" );
854 addStringConst( aPublics
, "vbNewLine", "\x0A" );
856 addStringConst( aPublics
, "vbNullString", "" );
857 addStringConst( aPublics
, "vbTab", "\x09" );
858 addStringConst( aPublics
, "vbVerticalTab", "\x0B" );
860 addStringConst( aPublics
, "vbNullChar", OUString(u
'\0') );
865 void SbiParser::ErrorStmnt()
867 SbiExpression
aPar( this );
869 aGen
.Gen( SbiOpcode::ERROR_
);
872 /* vim:set shiftwidth=4 softtabstop=4 expandtab: */