xref: /AOO41X/main/testtools/source/bridgetest/cli/cli_vb_bridgetest.vb (revision cdf0e10c4e3984b49a9502b011690b615761d4a3)
1*cdf0e10cSrcweir'*************************************************************************
2*cdf0e10cSrcweir'
3*cdf0e10cSrcweir' DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
4*cdf0e10cSrcweir'
5*cdf0e10cSrcweir' Copyright 2000, 2010 Oracle and/or its affiliates.
6*cdf0e10cSrcweir'
7*cdf0e10cSrcweir' OpenOffice.org - a multi-platform office productivity suite
8*cdf0e10cSrcweir'
9*cdf0e10cSrcweir' This file is part of OpenOffice.org.
10*cdf0e10cSrcweir'
11*cdf0e10cSrcweir' OpenOffice.org is free software: you can redistribute it and/or modify
12*cdf0e10cSrcweir' it under the terms of the GNU Lesser General Public License version 3
13*cdf0e10cSrcweir' only, as published by the Free Software Foundation.
14*cdf0e10cSrcweir'
15*cdf0e10cSrcweir' OpenOffice.org is distributed in the hope that it will be useful,
16*cdf0e10cSrcweir' but WITHOUT ANY WARRANTY; without even the implied warranty of
17*cdf0e10cSrcweir' MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18*cdf0e10cSrcweir' GNU Lesser General Public License version 3 for more details
19*cdf0e10cSrcweir' (a copy is included in the LICENSE file that accompanied this code).
20*cdf0e10cSrcweir'
21*cdf0e10cSrcweir' You should have received a copy of the GNU Lesser General Public License
22*cdf0e10cSrcweir' version 3 along with OpenOffice.org.  If not, see
23*cdf0e10cSrcweir' <http://www.openoffice.org/license.html>
24*cdf0e10cSrcweir' for a copy of the LGPLv3 License.
25*cdf0e10cSrcweir'
26*cdf0e10cSrcweir'*************************************************************************
27*cdf0e10cSrcweir
28*cdf0e10cSrcweir
29*cdf0e10cSrcweir
30*cdf0e10cSrcweirOption Explicit On
31*cdf0e10cSrcweirOption Strict On
32*cdf0e10cSrcweir
33*cdf0e10cSrcweirimports System
34*cdf0e10cSrcweirimports uno
35*cdf0e10cSrcweirimports uno.util
36*cdf0e10cSrcweirimports unoidl.com.sun.star.lang
37*cdf0e10cSrcweirimports unoidl.com.sun.star.uno
38*cdf0e10cSrcweir'imports unoidl.com.sun.star.test.bridge
39*cdf0e10cSrcweirimports unoidl.test.testtools.bridgetest
40*cdf0e10cSrcweirimports System.Windows.Forms
41*cdf0e10cSrcweirimports System.Diagnostics
42*cdf0e10cSrcweirimports System.Reflection
43*cdf0e10cSrcweir
44*cdf0e10cSrcweirClass CONSTANTS
45*cdf0e10cSrcweirFriend Shared STRING_TEST_CONSTANT As String  = """ paco\' chorizo\\\' ""\'"
46*cdf0e10cSrcweirEnd Class
47*cdf0e10cSrcweir
48*cdf0e10cSrcweirNamespace foo
49*cdf0e10cSrcweir
50*cdf0e10cSrcweir    Public Interface MyInterface
51*cdf0e10cSrcweir    End Interface
52*cdf0e10cSrcweirEnd Namespace
53*cdf0e10cSrcweir
54*cdf0e10cSrcweirNamespace vb_bridetest
55*cdf0e10cSrcweirClass ORecursiveCall
56*cdf0e10cSrcweir    Inherits WeakBase
57*cdf0e10cSrcweir    Implements XRecursiveCall
58*cdf0e10cSrcweir
59*cdf0e10cSrcweir    Overridable Sub callRecursivly(xCall As XRecursiveCall, nToCall As Integer) _
60*cdf0e10cSrcweir    Implements XRecursiveCall.callRecursivly
61*cdf0e10cSrcweir		SyncLock Me
62*cdf0e10cSrcweir            If nToCall > 0
63*cdf0e10cSrcweir                nToCall = nToCall - 1
64*cdf0e10cSrcweir                xCall.callRecursivly(Me, nToCall)
65*cdf0e10cSrcweir            End If
66*cdf0e10cSrcweir       End SyncLock
67*cdf0e10cSrcweir    End Sub
68*cdf0e10cSrcweirEnd Class
69*cdf0e10cSrcweir
70*cdf0e10cSrcweir
71*cdf0e10cSrcweir
72*cdf0e10cSrcweir
73*cdf0e10cSrcweirPublic Class BridgeTest
74*cdf0e10cSrcweir       Inherits uno.util.WeakBase
75*cdf0e10cSrcweir       Implements XMain
76*cdf0e10cSrcweir
77*cdf0e10cSrcweir    Private m_xContext As XComponentContext
78*cdf0e10cSrcweir
79*cdf0e10cSrcweir    Public Sub New( xContext As unoidl.com.sun.star.uno.XComponentContext )
80*cdf0e10cSrcweir        mybase.New()
81*cdf0e10cSrcweir        m_xContext = xContext
82*cdf0e10cSrcweir    End Sub
83*cdf0e10cSrcweir
84*cdf0e10cSrcweir    Private Shared Function check( b As Boolean , message As String  ) As Boolean
85*cdf0e10cSrcweir        If Not b
86*cdf0e10cSrcweir            Console.WriteLine("{0} failed\n" , message)
87*cdf0e10cSrcweir        End If
88*cdf0e10cSrcweir        Return b
89*cdf0e10cSrcweir    End Function
90*cdf0e10cSrcweir
91*cdf0e10cSrcweir    Private Shared Sub assign( rData As TestElement, bBool As Boolean, _
92*cdf0e10cSrcweir			aChar As Char, nByte As Byte, nShort As Short, nUShort As UInt16, _
93*cdf0e10cSrcweir					nLong As Integer, nULong As UInt32, nHyper As Long, _
94*cdf0e10cSrcweir                    nUHyper As UInt64, fFloat As Single, fDouble As Double, _
95*cdf0e10cSrcweir					eEnum As TestEnum, rStr As String, xTest As Object, _
96*cdf0e10cSrcweir					rAny As Any)
97*cdf0e10cSrcweir
98*cdf0e10cSrcweir    	rData.Bool = bBool
99*cdf0e10cSrcweir	    rData.Char = aChar
100*cdf0e10cSrcweir	    rData.Byte = nByte
101*cdf0e10cSrcweir	    rData.Short = nShort
102*cdf0e10cSrcweir	    rData.UShort = nUShort
103*cdf0e10cSrcweir	    rData.Long = nLong
104*cdf0e10cSrcweir	    rData.ULong = nULong
105*cdf0e10cSrcweir	    rData.Hyper = nHyper
106*cdf0e10cSrcweir	    rData.UHyper = nUHyper
107*cdf0e10cSrcweir	    rData.Float = fFloat
108*cdf0e10cSrcweir	    rData.Double = fDouble
109*cdf0e10cSrcweir	    rData.Enum = eEnum
110*cdf0e10cSrcweir	    rData.String = rStr
111*cdf0e10cSrcweir	    rData.Interface = xTest
112*cdf0e10cSrcweir	    rData.Any = rAny
113*cdf0e10cSrcweir    End Sub
114*cdf0e10cSrcweir
115*cdf0e10cSrcweir    Private Shared Sub assign( rData As TestDataElements, bBool As Boolean, _
116*cdf0e10cSrcweir            aChar As Char, nByte As Byte, nShort As Short, nUShort As UInt16, _
117*cdf0e10cSrcweir			nLong As Integer, nULong As UInt32, nHyper As Long, _
118*cdf0e10cSrcweir            nUHyper As UInt64, fFloat As Single, fDouble As Double, _
119*cdf0e10cSrcweir    		eEnum As TestEnum, rStr As String, xTest As Object, _
120*cdf0e10cSrcweir			rAny As Any, rSequence() As TestElement)
121*cdf0e10cSrcweir
122*cdf0e10cSrcweir    	assign( DirectCast( rData,TestElement), _
123*cdf0e10cSrcweir			bBool, aChar, nByte, nShort, nUShort, nLong, nULong, nHyper, _
124*cdf0e10cSrcweir            nUHyper, fFloat, fDouble, eEnum, rStr, xTest, rAny )
125*cdf0e10cSrcweir	    rData.Sequence = rSequence
126*cdf0e10cSrcweir    End Sub
127*cdf0e10cSrcweir
128*cdf0e10cSrcweir	Private Shared Function compareData(val1 As Object, val2 As Object) As Boolean
129*cdf0e10cSrcweir		If val1 Is Nothing And val2 Is Nothing OrElse _
130*cdf0e10cSrcweir            val1 Is val2
131*cdf0e10cSrcweir			Return True
132*cdf0e10cSrcweir        End If
133*cdf0e10cSrcweir		If  val1 Is Nothing And Not(val2 Is Nothing)  OrElse _
134*cdf0e10cSrcweir		    Not (val1 Is Nothing) And val2 Is Nothing OrElse _
135*cdf0e10cSrcweir            Not val1.GetType().Equals( val2.GetType())
136*cdf0e10cSrcweir			Return False
137*cdf0e10cSrcweir		End If
138*cdf0e10cSrcweir
139*cdf0e10cSrcweir		Dim ret As Boolean = False
140*cdf0e10cSrcweir		Dim t1 As Type = val1.GetType()
141*cdf0e10cSrcweir        'Sequence
142*cdf0e10cSrcweir		If t1.IsArray()
143*cdf0e10cSrcweir			ret = compareSequence(DirectCast( val1, Array), _
144*cdf0e10cSrcweir                  DirectCast( val2, Array))
145*cdf0e10cSrcweir		'String
146*cdf0e10cSrcweir		ElseIf TypeOf val1 Is String
147*cdf0e10cSrcweir			ret = DirectCast( val1, string) = DirectCast( val2, string)
148*cdf0e10cSrcweir		' Interface implementation
149*cdf0e10cSrcweir		ElseIf t1.GetInterfaces().Length > 0 And Not t1.IsValueType
150*cdf0e10cSrcweir			ret = val1 Is val2
151*cdf0e10cSrcweir		' Struct
152*cdf0e10cSrcweir		ElseIf  Not t1.IsValueType
153*cdf0e10cSrcweir			ret = compareStruct(val1, val2)
154*cdf0e10cSrcweir		ElseIf TypeOf val1 Is Any
155*cdf0e10cSrcweir			Dim a1 As Any = DirectCast( val1, Any)
156*cdf0e10cSrcweir			Dim a2 As Any = DirectCast( val2, Any)
157*cdf0e10cSrcweir			ret = a1.Type.Equals( a2.Type ) And compareData( a1.Value, a2.Value )
158*cdf0e10cSrcweir		ElseIf t1.IsValueType
159*cdf0e10cSrcweir			'Any, enum, int, bool char, float, double etc.
160*cdf0e10cSrcweir			ret = val1.Equals(val2)
161*cdf0e10cSrcweir		Else
162*cdf0e10cSrcweir			Debug.Assert(False)
163*cdf0e10cSrcweir		End If
164*cdf0e10cSrcweir		Return ret
165*cdf0e10cSrcweir	End Function
166*cdf0e10cSrcweir
167*cdf0e10cSrcweir	' Arrays have only one dimension
168*cdf0e10cSrcweir	Private Shared Function compareSequence( ar1 As Array, ar2 As Array) As Boolean
169*cdf0e10cSrcweir		Debug.Assert( Not (ar1 Is Nothing) And Not (ar2 Is Nothing) )
170*cdf0e10cSrcweir		Dim t1 As Type  = ar1.GetType()
171*cdf0e10cSrcweir		Dim t2 As Type  = ar2.GetType()
172*cdf0e10cSrcweir
173*cdf0e10cSrcweir		if ( Not(ar1.Rank = 1 And ar2.Rank = 1 _
174*cdf0e10cSrcweir			And ar1.Length = ar2.Length And t1.GetElementType().Equals(t2.GetElementType())))
175*cdf0e10cSrcweir			return False
176*cdf0e10cSrcweir        End If
177*cdf0e10cSrcweir		'arrays have same rank and size and element type.
178*cdf0e10cSrcweir		Dim len As Integer  = ar1.Length
179*cdf0e10cSrcweir		Dim elemType As Type = t1.GetElementType()
180*cdf0e10cSrcweir		Dim ret As Boolean = True
181*cdf0e10cSrcweir        Dim i As Integer
182*cdf0e10cSrcweir		For i = 0 To len - 1
183*cdf0e10cSrcweir			If (compareData(ar1.GetValue(i), ar2.GetValue(i)) = False)
184*cdf0e10cSrcweir				ret = False
185*cdf0e10cSrcweir				Exit For
186*cdf0e10cSrcweir			End If
187*cdf0e10cSrcweir		Next i
188*cdf0e10cSrcweir
189*cdf0e10cSrcweir        Return ret
190*cdf0e10cSrcweir	End Function
191*cdf0e10cSrcweir
192*cdf0e10cSrcweir	Private Shared Function compareStruct( val1 As Object, val2 As Object) As Boolean
193*cdf0e10cSrcweir		Debug.Assert( Not(val1 Is Nothing) And Not(val2 Is Nothing))
194*cdf0e10cSrcweir		Dim t1 As Type = val1.GetType()
195*cdf0e10cSrcweir		Dim t2 As Type = val2.GetType()
196*cdf0e10cSrcweir		If Not t1.Equals(t2)
197*cdf0e10cSrcweir			Return False
198*cdf0e10cSrcweir        End If
199*cdf0e10cSrcweir		Dim fields() As FieldInfo = t1.GetFields()
200*cdf0e10cSrcweir		Dim cFields As Integer = fields.Length
201*cdf0e10cSrcweir		Dim ret As Boolean = True
202*cdf0e10cSrcweir        Dim i As Integer
203*cdf0e10cSrcweir		For i = 0 To cFields - 1
204*cdf0e10cSrcweir			Dim fieldVal1 As Object = fields(i).GetValue(val1)
205*cdf0e10cSrcweir			Dim fieldVal2 As Object = fields(i).GetValue(val2)
206*cdf0e10cSrcweir			If Not compareData(fieldVal1, fieldVal2)
207*cdf0e10cSrcweir				ret = False
208*cdf0e10cSrcweir				Exit For
209*cdf0e10cSrcweir			End If
210*cdf0e10cSrcweir		Next i
211*cdf0e10cSrcweir		Return ret
212*cdf0e10cSrcweir	End Function
213*cdf0e10cSrcweir
214*cdf0e10cSrcweir
215*cdf0e10cSrcweir    Private Shared Function performSequenceTest(xBT As XBridgeTest) As Boolean
216*cdf0e10cSrcweir        Dim bRet As Boolean = True
217*cdf0e10cSrcweir        'Automati cast ?? like with COM objects
218*cdf0e10cSrcweir        Dim xBT2 As XBridgeTest2
219*cdf0e10cSrcweir        Try
220*cdf0e10cSrcweir            xBT2 = DirectCast(xBT,XBridgeTest2)
221*cdf0e10cSrcweir        Catch e As InvalidCastException
222*cdf0e10cSrcweir            Return False
223*cdf0e10cSrcweir        End Try
224*cdf0e10cSrcweir
225*cdf0e10cSrcweir        ' perform sequence tests (XBridgeTest2)
226*cdf0e10cSrcweir        'create the sequence which are compared with the results
227*cdf0e10cSrcweir        Dim arBool() As Boolean = {True, False, True}
228*cdf0e10cSrcweir        Dim arChar() As Char = {"A"C,"B"C,"C"C}
229*cdf0e10cSrcweir        Dim arByte() As Byte = { 1,  2,  &Hff}
230*cdf0e10cSrcweir        Dim arShort() As Short = {Int16.MinValue, 1,  Int16.MaxValue}
231*cdf0e10cSrcweir        Dim arUShort() As UInt16 = {Convert.ToUInt16(0), Convert.ToUInt16(1), _
232*cdf0e10cSrcweir                                    Convert.ToUInt16(&Hffff)}
233*cdf0e10cSrcweir        Dim arLong() As Integer = {Int32.MinValue, 1, Int32.MaxValue}
234*cdf0e10cSrcweir        Dim arULong() As UInt32 = {Convert.ToUInt32(0), Convert.ToUInt32(1), _
235*cdf0e10cSrcweir                                   Convert.ToUInt32(&HffffffffL)}
236*cdf0e10cSrcweir        Dim arHyper() As Long = {Int64.MinValue, 1, Int64.MaxValue}
237*cdf0e10cSrcweir        Dim arUHyper() As UInt64 = {Convert.ToUInt64(0), Convert.ToUInt64(1), _
238*cdf0e10cSrcweir                                    Convert.ToUInt64(&Hffffffff5L)}
239*cdf0e10cSrcweir        Dim arFloat() As Single = {1.1f, 2.2f, 3.3f}
240*cdf0e10cSrcweir        Dim arDouble() As Double = {1.11, 2.22, 3.33}
241*cdf0e10cSrcweir        Dim arString() As String = {"String 1", "String 2", "String 3"}
242*cdf0e10cSrcweir
243*cdf0e10cSrcweir        Dim arAny() As Any = {New Any(True), New Any(11111), New Any(3.14)}
244*cdf0e10cSrcweir        Dim arObject() As Object = {New WeakBase(), New WeakBase(), New WeakBase()}
245*cdf0e10cSrcweir        Dim arEnum() As TestEnum = {TestEnum.ONE, TestEnum.TWO, TestEnum.CHECK}
246*cdf0e10cSrcweir
247*cdf0e10cSrcweir        Dim arStruct() As TestElement = {New TestElement(), New TestElement(), _
248*cdf0e10cSrcweir                               New TestElement()}
249*cdf0e10cSrcweir        assign( arStruct(0), True, "@"C, 17, &H1234, Convert.ToUInt16(&Hfedc), _
250*cdf0e10cSrcweir            &H12345678, Convert.ToUInt32(&H123456), &H123456789abcdef0, _
251*cdf0e10cSrcweir            Convert.ToUInt64(123456788), 17.0815F, 3.1415926359, _
252*cdf0e10cSrcweir            TestEnum.LOLA, CONSTANTS.STRING_TEST_CONSTANT, arObject(0), _
253*cdf0e10cSrcweir            New Any(GetType(System.Object), arObject(0)))
254*cdf0e10cSrcweir        assign( arStruct(1), True, "A"C, 17, &H1234, Convert.ToUInt16(&Hfedc), _
255*cdf0e10cSrcweir            &H12345678, Convert.ToUInt32(&H123456), &H123456789abcdef0, _
256*cdf0e10cSrcweir            Convert.ToUInt64(12345678), 17.0815F, 3.1415926359, _
257*cdf0e10cSrcweir            TestEnum.TWO, CONSTANTS.STRING_TEST_CONSTANT, arObject(1), _
258*cdf0e10cSrcweir            New Any(GetType(System.Object), arObject(1)) )
259*cdf0e10cSrcweir        assign( arStruct(2), True, "B"C, 17, &H1234, Convert.ToUInt16(&Hfedc), _
260*cdf0e10cSrcweir            &H12345678, Convert.ToUInt32(654321), &H123456789abcdef0, _
261*cdf0e10cSrcweir            Convert.ToUInt64(87654321), 17.0815F, 3.1415926359, _
262*cdf0e10cSrcweir            TestEnum.CHECK, Constants.STRING_TEST_CONSTANT, arObject(2), _
263*cdf0e10cSrcweir            New Any(GetType(System.Object), arObject(2)))
264*cdf0e10cSrcweir
265*cdf0e10cSrcweir
266*cdf0e10cSrcweir        Dim arLong3()()() As Integer = New Integer()()() { _
267*cdf0e10cSrcweir        New Integer()(){New Integer(){1,2,3},New Integer(){4,5,6}, New Integer(){7,8,9} }, _
268*cdf0e10cSrcweir        New Integer ()(){New Integer(){1,2,3},New Integer(){4,5,6}, New Integer(){7,8,9}}, _
269*cdf0e10cSrcweir        New Integer()(){New Integer(){1,2,3},New Integer(){4,5,6}, New Integer(){7,8,9}}}
270*cdf0e10cSrcweir
271*cdf0e10cSrcweir        Dim seqSeqRet()() As Integer = xBT2.setDim2(arLong3(0))
272*cdf0e10cSrcweir        bRet = check( compareData(seqSeqRet, arLong3(0)), "sequence test") _
273*cdf0e10cSrcweir               And bRet
274*cdf0e10cSrcweir        Dim seqSeqRet2()()() As Integer = xBT2.setDim3(arLong3)
275*cdf0e10cSrcweir        bRet = check( compareData(seqSeqRet2, arLong3), "sequence test") _
276*cdf0e10cSrcweir               And bRet
277*cdf0e10cSrcweir        Dim seqAnyRet() As Any = xBT2.setSequenceAny(arAny)
278*cdf0e10cSrcweir        bRet = check( compareData(seqAnyRet, arAny), "sequence test") And bRet
279*cdf0e10cSrcweir        Dim seqBoolRet() As Boolean = xBT2.setSequenceBool(arBool)
280*cdf0e10cSrcweir        bRet = check( compareData(seqBoolRet, arBool), "sequence test") _
281*cdf0e10cSrcweir               And bRet
282*cdf0e10cSrcweir        Dim seqByteRet() As Byte = xBT2.setSequenceByte(arByte)
283*cdf0e10cSrcweir        bRet = check( compareData(seqByteRet, arByte), "sequence test") _
284*cdf0e10cSrcweir               And bRet
285*cdf0e10cSrcweir        Dim seqCharRet() As Char = xBT2.setSequenceChar(arChar)
286*cdf0e10cSrcweir        bRet = check( compareData(seqCharRet, arChar), "sequence test") _
287*cdf0e10cSrcweir                   And bRet
288*cdf0e10cSrcweir        Dim seqShortRet() As Short = xBT2.setSequenceShort(arShort)
289*cdf0e10cSrcweir        bRet = check( compareData(seqShortRet, arShort), "sequence test") _
290*cdf0e10cSrcweir               And bRet
291*cdf0e10cSrcweir        Dim seqLongRet() As Integer = xBT2.setSequenceLong(arLong)
292*cdf0e10cSrcweir        bRet = check( compareData(seqLongRet, arLong), "sequence test") _
293*cdf0e10cSrcweir                   And bRet
294*cdf0e10cSrcweir        Dim seqHyperRet() As Long = xBT2.setSequenceHyper(arHyper)
295*cdf0e10cSrcweir        bRet = check( compareData(seqHyperRet,arHyper), "sequence test") _
296*cdf0e10cSrcweir               And bRet
297*cdf0e10cSrcweir        Dim seqFloatRet() As Single = xBT2.setSequenceFloat(arFloat)
298*cdf0e10cSrcweir        bRet = check( compareData(seqFloatRet, arFloat), "sequence test") _
299*cdf0e10cSrcweir               And bRet
300*cdf0e10cSrcweir        Dim seqDoubleRet() As Double= xBT2.setSequenceDouble(arDouble)
301*cdf0e10cSrcweir        bRet = check( compareData(seqDoubleRet, arDouble), "sequence test") _
302*cdf0e10cSrcweir               And bRet
303*cdf0e10cSrcweir        Dim seqEnumRet() As TestEnum = xBT2.setSequenceEnum(arEnum)
304*cdf0e10cSrcweir        bRet = check( compareData(seqEnumRet, arEnum), "sequence test") _
305*cdf0e10cSrcweir               And bRet
306*cdf0e10cSrcweir        Dim seqUShortRet() As UInt16 = xBT2.setSequenceUShort(arUShort)
307*cdf0e10cSrcweir        bRet = check( compareData(seqUShortRet, arUShort), "sequence test") _
308*cdf0e10cSrcweir               And bRet
309*cdf0e10cSrcweir        Dim seqULongRet() As UInt32 = xBT2.setSequenceULong(arULong)
310*cdf0e10cSrcweir        bRet = check( compareData(seqULongRet, arULong), "sequence test") _
311*cdf0e10cSrcweir               And bRet
312*cdf0e10cSrcweir        Dim seqUHyperRet() As UInt64 = xBT2.setSequenceUHyper(arUHyper)
313*cdf0e10cSrcweir        bRet = check( compareData(seqUHyperRet, arUHyper), "sequence test") _
314*cdf0e10cSrcweir               And bRet
315*cdf0e10cSrcweir        Dim seqObjectRet() As Object = xBT2.setSequenceXInterface(arObject)
316*cdf0e10cSrcweir        bRet = check( compareData(seqObjectRet, arObject), "sequence test") _
317*cdf0e10cSrcweir               And bRet
318*cdf0e10cSrcweir        Dim seqStringRet() As String = xBT2.setSequenceString(arString)
319*cdf0e10cSrcweir        bRet = check( compareData(seqStringRet, arString), "sequence test") _
320*cdf0e10cSrcweir               And bRet
321*cdf0e10cSrcweir        Dim seqStructRet() As TestElement = xBT2.setSequenceStruct(arStruct)
322*cdf0e10cSrcweir        bRet = check( compareData(seqStructRet, arStruct), "sequence test") _
323*cdf0e10cSrcweir               And bRet
324*cdf0e10cSrcweir
325*cdf0e10cSrcweir
326*cdf0e10cSrcweir        Dim arBoolTemp() As Boolean = DirectCast(arBool.Clone(), Boolean())
327*cdf0e10cSrcweir        Dim arCharTemp() As Char = DirectCast(arChar.Clone(), Char())
328*cdf0e10cSrcweir        Dim arByteTemp() As Byte = DirectCast(arByte.Clone(), Byte())
329*cdf0e10cSrcweir        Dim arShortTemp() As Short = DirectCast(arShort.Clone(), Short())
330*cdf0e10cSrcweir        Dim arUShortTemp() As UInt16 = DirectCast(arUShort.Clone(), UInt16())
331*cdf0e10cSrcweir        Dim arLongTemp() As Integer= DirectCast(arLong.Clone(), Integer())
332*cdf0e10cSrcweir        Dim arULongTemp() As UInt32 =  DirectCast(arULong.Clone(), UInt32())
333*cdf0e10cSrcweir        Dim arHyperTemp() As Long = DirectCast(arHyper.Clone(), Long())
334*cdf0e10cSrcweir        Dim arUHyperTemp() As UInt64 = DirectCast(arUHyper.Clone(), UInt64())
335*cdf0e10cSrcweir        Dim arFloatTemp() As Single = DirectCast(arFloat.Clone(), Single())
336*cdf0e10cSrcweir        Dim arDoubleTemp() As Double = DirectCast(arDouble.Clone(), Double())
337*cdf0e10cSrcweir        Dim arEnumTemp() As TestEnum = DirectCast(arEnum.Clone(), TestEnum())
338*cdf0e10cSrcweir        Dim arStringTemp() As String = DirectCast(arString.Clone(), String())
339*cdf0e10cSrcweir        Dim arObjectTemp() As Object = DirectCast(arObject.Clone(), Object())
340*cdf0e10cSrcweir        Dim arAnyTemp() As Any = DirectCast(arAny.Clone(), Any())
341*cdf0e10cSrcweir        ' make sure this are has the same contents as arLong3(0)
342*cdf0e10cSrcweir        Dim arLong2Temp()() As Integer = New Integer()(){New Integer(){1,2,3}, _
343*cdf0e10cSrcweir                                         New Integer(){4,5,6}, New Integer(){7,8,9} }
344*cdf0e10cSrcweir        ' make sure this are has the same contents as arLong3
345*cdf0e10cSrcweir        Dim arLong3Temp()()() As Integer = New Integer()()(){ _
346*cdf0e10cSrcweir            New Integer()(){New Integer(){1,2,3},New Integer(){4,5,6}, New Integer(){7,8,9} }, _
347*cdf0e10cSrcweir            New Integer ()(){New Integer(){1,2,3},New Integer(){4,5,6}, New Integer(){7,8,9}}, _
348*cdf0e10cSrcweir            New Integer()(){New Integer(){1,2,3},New Integer(){4,5,6}, New Integer(){7,8,9}}}
349*cdf0e10cSrcweir
350*cdf0e10cSrcweir        xBT2.setSequencesInOut( arBoolTemp, arCharTemp,  arByteTemp, _
351*cdf0e10cSrcweir                            arShortTemp,  arUShortTemp,  arLongTemp, _
352*cdf0e10cSrcweir                            arULongTemp, arHyperTemp,  arUHyperTemp, _
353*cdf0e10cSrcweir                            arFloatTemp, arDoubleTemp,  arEnumTemp, _
354*cdf0e10cSrcweir                            arStringTemp,   arObjectTemp, _
355*cdf0e10cSrcweir                             arAnyTemp,  arLong2Temp,  arLong3Temp)
356*cdf0e10cSrcweir        bRet = check( _
357*cdf0e10cSrcweir            compareData(arBoolTemp, arBool) And _
358*cdf0e10cSrcweir            compareData(arCharTemp , arChar) And _
359*cdf0e10cSrcweir            compareData(arByteTemp , arByte) And _
360*cdf0e10cSrcweir            compareData(arShortTemp , arShort) And _
361*cdf0e10cSrcweir            compareData(arUShortTemp , arUShort) And _
362*cdf0e10cSrcweir            compareData(arLongTemp , arLong) And _
363*cdf0e10cSrcweir            compareData(arULongTemp , arULong) And _
364*cdf0e10cSrcweir            compareData(arHyperTemp , arHyper) And _
365*cdf0e10cSrcweir            compareData(arUHyperTemp , arUHyper) And _
366*cdf0e10cSrcweir            compareData(arFloatTemp , arFloat) And _
367*cdf0e10cSrcweir            compareData(arDoubleTemp , arDouble) And _
368*cdf0e10cSrcweir            compareData(arEnumTemp , arEnum) And _
369*cdf0e10cSrcweir            compareData(arStringTemp , arString) And _
370*cdf0e10cSrcweir            compareData(arObjectTemp , arObject) And _
371*cdf0e10cSrcweir            compareData(arAnyTemp , arAny) And _
372*cdf0e10cSrcweir            compareData(arLong2Temp , arLong3(0)) And _
373*cdf0e10cSrcweir            compareData(arLong3Temp , arLong3), "sequence test") And bRet
374*cdf0e10cSrcweir
375*cdf0e10cSrcweir        Dim arBoolOut() As Boolean
376*cdf0e10cSrcweir        Dim arCharOut() As Char
377*cdf0e10cSrcweir        Dim arByteOut() As Byte
378*cdf0e10cSrcweir        Dim arShortOut() As Short
379*cdf0e10cSrcweir        Dim arUShortOut() As UInt16
380*cdf0e10cSrcweir        Dim arLongOut() As Integer
381*cdf0e10cSrcweir        Dim arULongOut() As UInt32
382*cdf0e10cSrcweir        Dim arHyperOut() As Long
383*cdf0e10cSrcweir        Dim arUHyperOut() As UInt64
384*cdf0e10cSrcweir        Dim arFloatOut() As Single
385*cdf0e10cSrcweir        Dim arDoubleOut() As Double
386*cdf0e10cSrcweir        Dim arEnumOut() As TestEnum
387*cdf0e10cSrcweir        Dim arStringOut() As String
388*cdf0e10cSrcweir        Dim arObjectOut() As Object
389*cdf0e10cSrcweir        Dim arAnyOut() As Any
390*cdf0e10cSrcweir        Dim arLong2Out()() As Integer
391*cdf0e10cSrcweir        Dim arLong3Out()()() As Integer
392*cdf0e10cSrcweir
393*cdf0e10cSrcweir        xBT2.setSequencesOut( arBoolOut,  arCharOut,  arByteOut, _
394*cdf0e10cSrcweir                             arShortOut,  arUShortOut,  arLongOut, _
395*cdf0e10cSrcweir                             arULongOut,  arHyperOut,  arUHyperOut, _
396*cdf0e10cSrcweir                             arFloatOut,  arDoubleOut,  arEnumOut, _
397*cdf0e10cSrcweir                             arStringOut,  arObjectOut,  arAnyOut, _
398*cdf0e10cSrcweir                             arLong2Out,  arLong3Out)
399*cdf0e10cSrcweir        bRet = check( _
400*cdf0e10cSrcweir            compareData(arBoolOut, arBool) And _
401*cdf0e10cSrcweir            compareData(arCharOut, arChar) And _
402*cdf0e10cSrcweir            compareData(arByteOut, arByte) And _
403*cdf0e10cSrcweir            compareData(arShortOut, arShort) And _
404*cdf0e10cSrcweir            compareData(arUShortOut, arUShort) And _
405*cdf0e10cSrcweir            compareData(arLongOut, arLong) And _
406*cdf0e10cSrcweir            compareData(arULongOut, arULong) And _
407*cdf0e10cSrcweir            compareData(arHyperOut, arHyper) And _
408*cdf0e10cSrcweir            compareData(arUHyperOut, arUHyper) And _
409*cdf0e10cSrcweir            compareData(arFloatOut, arFloat) And _
410*cdf0e10cSrcweir            compareData(arDoubleOut, arDouble) And _
411*cdf0e10cSrcweir            compareData(arEnumOut, arEnum) And _
412*cdf0e10cSrcweir            compareData(arStringOut, arString) And _
413*cdf0e10cSrcweir            compareData(arObjectOut, arObject) And _
414*cdf0e10cSrcweir            compareData(arAnyOut, arAny) And _
415*cdf0e10cSrcweir            compareData(arLong2Out, arLong3(0)) And _
416*cdf0e10cSrcweir            compareData(arLong3Out, arLong3), "sequence test") And bRet
417*cdf0e10cSrcweir
418*cdf0e10cSrcweir
419*cdf0e10cSrcweir        'test with empty sequences
420*cdf0e10cSrcweir        Dim _arLong2()() As Integer = New Integer()(){}
421*cdf0e10cSrcweir        seqSeqRet = xBT2.setDim2(_arLong2)
422*cdf0e10cSrcweir        bRet = check( compareData(seqSeqRet, _arLong2), "sequence test") And bRet
423*cdf0e10cSrcweir        Dim _arLong3()()() As Integer = New Integer()()(){}
424*cdf0e10cSrcweir        seqSeqRet2 = xBT2.setDim3(_arLong3)
425*cdf0e10cSrcweir        bRet = check( compareData(seqSeqRet2, _arLong3), "sequence test") And bRet
426*cdf0e10cSrcweir        Dim _arAny() As Any = New Any(){}
427*cdf0e10cSrcweir        seqAnyRet = xBT2.setSequenceAny(_arAny)
428*cdf0e10cSrcweir        bRet = check( compareData(seqAnyRet, _arAny), "sequence test") And bRet
429*cdf0e10cSrcweir        Dim _arBool() As Boolean = New Boolean() {}
430*cdf0e10cSrcweir        seqBoolRet = xBT2.setSequenceBool(_arBool)
431*cdf0e10cSrcweir        bRet = check( compareData(seqBoolRet, _arBool), "sequence test") And bRet
432*cdf0e10cSrcweir        Dim _arByte() As Byte = New Byte() {}
433*cdf0e10cSrcweir        seqByteRet = xBT2.setSequenceByte(_arByte)
434*cdf0e10cSrcweir        bRet = check( compareData(seqByteRet, _arByte), "sequence test") And bRet
435*cdf0e10cSrcweir        Dim _arChar() As Char = New Char() {}
436*cdf0e10cSrcweir        seqCharRet  = xBT2.setSequenceChar(_arChar)
437*cdf0e10cSrcweir        bRet = check( compareData(seqCharRet, _arChar), "sequence test") And bRet
438*cdf0e10cSrcweir        Dim _arShort() As Short = New Short() {}
439*cdf0e10cSrcweir        seqShortRet = xBT2.setSequenceShort(_arShort)
440*cdf0e10cSrcweir        bRet = check( compareData(seqShortRet, _arShort), "sequence test") And bRet
441*cdf0e10cSrcweir        Dim _arLong() As Integer = New Integer() {}
442*cdf0e10cSrcweir        seqLongRet = xBT2.setSequenceLong(_arLong)
443*cdf0e10cSrcweir        bRet = check( compareData(seqLongRet, _arLong), "sequence test") And bRet
444*cdf0e10cSrcweir        Dim _arHyper() As Long = New Long(){}
445*cdf0e10cSrcweir        seqHyperRet = xBT2.setSequenceHyper(_arHyper)
446*cdf0e10cSrcweir        bRet = check( compareData(seqHyperRet, _arHyper), "sequence test") And bRet
447*cdf0e10cSrcweir        Dim _arFloat() As Single = New Single(){}
448*cdf0e10cSrcweir        seqFloatRet = xBT2.setSequenceFloat(_arFloat)
449*cdf0e10cSrcweir        bRet = check( compareData(seqFloatRet, _arFloat), "sequence test") And bRet
450*cdf0e10cSrcweir        Dim _arDouble() As Double = New Double(){}
451*cdf0e10cSrcweir        seqDoubleRet = xBT2.setSequenceDouble(_arDouble)
452*cdf0e10cSrcweir        bRet = check( compareData(seqDoubleRet, _arDouble), "sequence test") And bRet
453*cdf0e10cSrcweir        Dim _arEnum() As TestEnum = New TestEnum(){}
454*cdf0e10cSrcweir        seqEnumRet = xBT2.setSequenceEnum(_arEnum)
455*cdf0e10cSrcweir        bRet = check( compareData(seqEnumRet, _arEnum), "sequence test") And bRet
456*cdf0e10cSrcweir        Dim  _arUShort() As UInt16 = New UInt16(){}
457*cdf0e10cSrcweir        seqUShortRet = xBT2.setSequenceUShort(_arUShort)
458*cdf0e10cSrcweir        bRet = check( compareData(seqUShortRet, _arUShort), "sequence test") And bRet
459*cdf0e10cSrcweir        Dim _arULong() As UInt32 = New UInt32(){}
460*cdf0e10cSrcweir        seqULongRet = xBT2.setSequenceULong(_arULong)
461*cdf0e10cSrcweir        bRet = check( compareData(seqULongRet, _arULong), "sequence test") And bRet
462*cdf0e10cSrcweir        Dim  _arUHyper() As UInt64 = New UInt64(){}
463*cdf0e10cSrcweir        seqUHyperRet = xBT2.setSequenceUHyper(_arUHyper)
464*cdf0e10cSrcweir        bRet = check( compareData(seqUHyperRet, _arUHyper), "sequence test") And bRet
465*cdf0e10cSrcweir        Dim _arObject() As Object = New Object(){}
466*cdf0e10cSrcweir        seqObjectRet = xBT2.setSequenceXInterface(_arObject)
467*cdf0e10cSrcweir        bRet = check( compareData(seqObjectRet, _arObject), "sequence test") And bRet
468*cdf0e10cSrcweir        Dim _arString() As String = New String(){}
469*cdf0e10cSrcweir        seqStringRet = xBT2.setSequenceString(_arString)
470*cdf0e10cSrcweir        bRet = check( compareData(seqStringRet, _arString), "sequence test") And bRet
471*cdf0e10cSrcweir        Dim _arStruct() As TestElement = New TestElement(){}
472*cdf0e10cSrcweir        seqStructRet = xBT2.setSequenceStruct(_arStruct)
473*cdf0e10cSrcweir        bRet = check( compareData(seqStructRet, _arStruct), "sequence test") And bRet
474*cdf0e10cSrcweir        Return bRet
475*cdf0e10cSrcweir    End Function
476*cdf0e10cSrcweir
477*cdf0e10cSrcweir    Private Shared Function testAny(typ As Type, value As  Object, _
478*cdf0e10cSrcweir                                    xLBT As  XBridgeTest ) As Boolean
479*cdf0e10cSrcweir
480*cdf0e10cSrcweir	    Dim any As Any
481*cdf0e10cSrcweir	    If (typ Is Nothing)
482*cdf0e10cSrcweir		    any = New Any(value.GetType(), value)
483*cdf0e10cSrcweir	    Else
484*cdf0e10cSrcweir		    any = New Any(typ, value)
485*cdf0e10cSrcweir        End If
486*cdf0e10cSrcweir
487*cdf0e10cSrcweir	    Dim any2 As Any = xLBT.transportAny(any)
488*cdf0e10cSrcweir	    Dim ret As Boolean = compareData(any, any2)
489*cdf0e10cSrcweir	    If ret = False
490*cdf0e10cSrcweir            Console.WriteLine("any is different after roundtrip: in {0}, " _
491*cdf0e10cSrcweir                              & "out {1}\n", _
492*cdf0e10cSrcweir                            any.Type.FullName, any2.Type.FullName)
493*cdf0e10cSrcweir        End If
494*cdf0e10cSrcweir	    Return ret
495*cdf0e10cSrcweir    End Function
496*cdf0e10cSrcweir
497*cdf0e10cSrcweir    Private Shared Function performAnyTest(xLBT As XBridgeTest, _
498*cdf0e10cSrcweir                                           data As TestDataElements) As Boolean
499*cdf0e10cSrcweir        Dim bReturn As Boolean = True
500*cdf0e10cSrcweir	    bReturn = testAny( Nothing, data.Byte ,xLBT ) And bReturn
501*cdf0e10cSrcweir	    bReturn = testAny( Nothing, data.Short,xLBT ) And bReturn
502*cdf0e10cSrcweir	    bReturn = testAny(  Nothing, data.UShort,xLBT ) And bReturn
503*cdf0e10cSrcweir	    bReturn = testAny(  Nothing, data.Long,xLBT ) And bReturn
504*cdf0e10cSrcweir	    bReturn = testAny(  Nothing, data.ULong,xLBT ) And bReturn
505*cdf0e10cSrcweir	    bReturn = testAny(  Nothing, data.Hyper,xLBT ) And bReturn
506*cdf0e10cSrcweir	    bReturn = testAny(  Nothing,data.UHyper,xLBT ) And bReturn
507*cdf0e10cSrcweir	    bReturn = testAny( Nothing, data.Float,xLBT ) And bReturn
508*cdf0e10cSrcweir	    bReturn = testAny( Nothing, data.Double,xLBT ) And bReturn
509*cdf0e10cSrcweir	    bReturn = testAny( Nothing, data.Enum,xLBT ) And bReturn
510*cdf0e10cSrcweir	    bReturn = testAny( Nothing, data.String,xLBT ) And bReturn
511*cdf0e10cSrcweir	    bReturn = testAny(GetType(unoidl.com.sun.star.uno.XWeak), _
512*cdf0e10cSrcweir                     data.Interface,xLBT ) And bReturn
513*cdf0e10cSrcweir	    bReturn = testAny(Nothing, data, xLBT ) And bReturn
514*cdf0e10cSrcweir
515*cdf0e10cSrcweir        Dim a1 As Any = New Any(True)
516*cdf0e10cSrcweir        Dim a2 As Any = xLBT.transportAny( a1 )
517*cdf0e10cSrcweir	    bReturn = compareData(a2, a1) And bReturn
518*cdf0e10cSrcweir
519*cdf0e10cSrcweir        Dim a3 As Any = New Any("A"C)
520*cdf0e10cSrcweir	    Dim a4 As Any = xLBT.transportAny(a3)
521*cdf0e10cSrcweir	    bReturn = compareData(a4, a3) And bReturn
522*cdf0e10cSrcweir
523*cdf0e10cSrcweir	    Return bReturn
524*cdf0e10cSrcweir    End Function
525*cdf0e10cSrcweir
526*cdf0e10cSrcweir    Private Shared Function performSequenceOfCallTest(xLBT As XBridgeTest) As Boolean
527*cdf0e10cSrcweir
528*cdf0e10cSrcweir	    Dim i, nRounds As Integer
529*cdf0e10cSrcweir	    Dim nGlobalIndex As Integer = 0
530*cdf0e10cSrcweir	    const nWaitTimeSpanMUSec As Integer = 10000
531*cdf0e10cSrcweir	    For nRounds = 0 To 9
532*cdf0e10cSrcweir		    For i = 0 To  nRounds - 1
533*cdf0e10cSrcweir			    ' fire oneways
534*cdf0e10cSrcweir			    xLBT.callOneway(nGlobalIndex, nWaitTimeSpanMUSec)
535*cdf0e10cSrcweir			    nGlobalIndex = nGlobalIndex + 1
536*cdf0e10cSrcweir		    Next
537*cdf0e10cSrcweir
538*cdf0e10cSrcweir		    ' call synchron
539*cdf0e10cSrcweir		    xLBT.call(nGlobalIndex, nWaitTimeSpanMUSec)
540*cdf0e10cSrcweir		    nGlobalIndex = nGlobalIndex + 1
541*cdf0e10cSrcweir	    Next
542*cdf0e10cSrcweir 	    Return xLBT.sequenceOfCallTestPassed()
543*cdf0e10cSrcweir    End Function
544*cdf0e10cSrcweir
545*cdf0e10cSrcweir    Private Shared Function performRecursiveCallTest(xLBT As XBridgeTest) As Boolean
546*cdf0e10cSrcweir	    xLBT.startRecursiveCall(new ORecursiveCall(), 50)
547*cdf0e10cSrcweir	    ' on failure, the test would lock up or crash
548*cdf0e10cSrcweir	    Return True
549*cdf0e10cSrcweir    End Function
550*cdf0e10cSrcweir
551*cdf0e10cSrcweir
552*cdf0e10cSrcweir    Private Shared Function performTest(xLBT As XBridgeTest) As Boolean
553*cdf0e10cSrcweir	    check( Not xLBT Is Nothing, "### no test interface!" )
554*cdf0e10cSrcweir        Dim bRet As Boolean = True
555*cdf0e10cSrcweir	    If xLBT Is Nothing
556*cdf0e10cSrcweir            Return False
557*cdf0e10cSrcweir        End If
558*cdf0e10cSrcweir		'this data is never ever granted access to by calls other than equals(), assign()!
559*cdf0e10cSrcweir		Dim aData As New TestDataElements' test against this data
560*cdf0e10cSrcweir		Dim xI As New WeakBase
561*cdf0e10cSrcweir
562*cdf0e10cSrcweir        Dim aAny As New Any(GetType(System.Object), xI)
563*cdf0e10cSrcweir		assign( DirectCast(aData, TestElement), _
564*cdf0e10cSrcweir			True, "@"C, 17, &H1234, Convert.ToUInt16(&HdcS), &H12345678, _
565*cdf0e10cSrcweir            Convert.ToUInt32(4294967294), _
566*cdf0e10cSrcweir			&H123456789abcdef0, Convert.ToUInt64(14294967294), _
567*cdf0e10cSrcweir			17.0815f, 3.1415926359, TestEnum.LOLA, _
568*cdf0e10cSrcweir			CONSTANTS.STRING_TEST_CONSTANT, xI, _
569*cdf0e10cSrcweir			aAny)
570*cdf0e10cSrcweir
571*cdf0e10cSrcweir		bRet = check( aData.Any.Value Is xI, "### unexpected any!" ) And bRet
572*cdf0e10cSrcweir
573*cdf0e10cSrcweir		aData.Sequence = New TestElement(1){}
574*cdf0e10cSrcweir        aData.Sequence(0) = New TestElement( _
575*cdf0e10cSrcweir			aData.Bool, aData.Char, aData.Byte, aData.Short, _
576*cdf0e10cSrcweir			aData.UShort, aData.Long, aData.ULong, _
577*cdf0e10cSrcweir			aData.Hyper, aData.UHyper, aData.Float, _
578*cdf0e10cSrcweir			aData.Double, aData.Enum, aData.String, _
579*cdf0e10cSrcweir			aData.Interface, aData.Any)
580*cdf0e10cSrcweir        aData.Sequence(1) = New TestElement 'is empty
581*cdf0e10cSrcweir
582*cdf0e10cSrcweir		' aData complete
583*cdf0e10cSrcweir		'
584*cdf0e10cSrcweir		' this is a manually copy of aData for first setting...
585*cdf0e10cSrcweir		Dim aSetData As New TestDataElements
586*cdf0e10cSrcweir		Dim aAnySet As New Any(GetType(System.Object), xI)
587*cdf0e10cSrcweir		assign( DirectCast(aSetData, TestElement), _
588*cdf0e10cSrcweir				aData.Bool, aData.Char, aData.Byte, aData.Short, aData.UShort, _
589*cdf0e10cSrcweir				aData.Long, aData.ULong, aData.Hyper, aData.UHyper, aData.Float, _
590*cdf0e10cSrcweir                aData.Double, aData.Enum, aData.String, xI, aAnySet)
591*cdf0e10cSrcweir
592*cdf0e10cSrcweir		aSetData.Sequence = New TestElement(1){}
593*cdf0e10cSrcweir        aSetData.Sequence(0) = New TestElement( _
594*cdf0e10cSrcweir			aSetData.Bool, aSetData.Char, aSetData.Byte, aSetData.Short, _
595*cdf0e10cSrcweir			aSetData.UShort, aSetData.Long, aSetData.ULong, _
596*cdf0e10cSrcweir			aSetData.Hyper, aSetData.UHyper, aSetData.Float, _
597*cdf0e10cSrcweir			aSetData.Double, aSetData.Enum, aSetData.String, _
598*cdf0e10cSrcweir			aSetData.Interface, aSetData.Any)
599*cdf0e10cSrcweir        aSetData.Sequence(1) = New TestElement ' empty struct
600*cdf0e10cSrcweir
601*cdf0e10cSrcweir		xLBT.setValues( _
602*cdf0e10cSrcweir				aSetData.Bool, aSetData.Char, aSetData.Byte, aSetData.Short, _
603*cdf0e10cSrcweir                aSetData.UShort, aSetData.Long, aSetData.ULong, _
604*cdf0e10cSrcweir                aSetData.Hyper, aSetData.UHyper, aSetData.Float, _
605*cdf0e10cSrcweir                aSetData.Double, aSetData.Enum, aSetData.String, _
606*cdf0e10cSrcweir                aSetData.Interface, aSetData.Any, aSetData.Sequence, _
607*cdf0e10cSrcweir                aSetData )
608*cdf0e10cSrcweir
609*cdf0e10cSrcweir
610*cdf0e10cSrcweir		Dim aRet As New TestDataElements
611*cdf0e10cSrcweir        Dim aRet2 As New TestDataElements
612*cdf0e10cSrcweir		xLBT.getValues( _
613*cdf0e10cSrcweir			aRet.Bool, aRet.Char, aRet.Byte, aRet.Short, _
614*cdf0e10cSrcweir            aRet.UShort, aRet.Long, aRet.ULong, _
615*cdf0e10cSrcweir            aRet.Hyper, aRet.UHyper, aRet.Float, _
616*cdf0e10cSrcweir            aRet.Double, aRet.Enum, aRet.String, _
617*cdf0e10cSrcweir            aRet.Interface, aRet.Any, aRet.Sequence, _
618*cdf0e10cSrcweir            aRet2 )
619*cdf0e10cSrcweir
620*cdf0e10cSrcweir		bRet = check( compareData( aData, aRet ) And _
621*cdf0e10cSrcweir                      compareData( aData, aRet2 ) , "getValues test") And bRet
622*cdf0e10cSrcweir
623*cdf0e10cSrcweir		' set last retrieved values
624*cdf0e10cSrcweir		Dim  aSV2ret As TestDataElements= xLBT.setValues2( _
625*cdf0e10cSrcweir			aRet.Bool, aRet.Char, aRet.Byte, _
626*cdf0e10cSrcweir            aRet.Short, aRet.UShort, aRet.Long, _
627*cdf0e10cSrcweir            aRet.ULong, aRet.Hyper, aRet.UHyper, _
628*cdf0e10cSrcweir            aRet.Float, aRet.Double, aRet.Enum, _
629*cdf0e10cSrcweir            aRet.String, aRet.Interface, aRet.Any, _
630*cdf0e10cSrcweir            aRet.Sequence, aRet2 )
631*cdf0e10cSrcweir
632*cdf0e10cSrcweir        ' check inout sequence order
633*cdf0e10cSrcweir        ' => inout sequence parameter was switched by test objects
634*cdf0e10cSrcweir		Dim temp As TestElement = aRet.Sequence( 0 )
635*cdf0e10cSrcweir        aRet.Sequence( 0 ) = aRet.Sequence( 1 )
636*cdf0e10cSrcweir        aRet.Sequence( 1 ) = temp
637*cdf0e10cSrcweir
638*cdf0e10cSrcweir		bRet = check( _
639*cdf0e10cSrcweir            compareData( aData, aSV2ret ) And compareData( aData, aRet2 ), _
640*cdf0e10cSrcweir            "getValues2 test") And bRet
641*cdf0e10cSrcweir
642*cdf0e10cSrcweir
643*cdf0e10cSrcweir		aRet = New TestDataElements
644*cdf0e10cSrcweir        aRet2 = New TestDataElements
645*cdf0e10cSrcweir		Dim  aGVret As TestDataElements= xLBT.getValues( _
646*cdf0e10cSrcweir			aRet.Bool, aRet.Char, aRet.Byte, _
647*cdf0e10cSrcweir            aRet.Short, aRet.UShort, aRet.Long, _
648*cdf0e10cSrcweir            aRet.ULong, aRet.Hyper, aRet.UHyper, _
649*cdf0e10cSrcweir            aRet.Float, aRet.Double, aRet.Enum, _
650*cdf0e10cSrcweir            aRet.String, aRet.Interface, aRet.Any, _
651*cdf0e10cSrcweir            aRet.Sequence, aRet2 )
652*cdf0e10cSrcweir
653*cdf0e10cSrcweir		bRet = check( compareData( aData, aRet ) And _
654*cdf0e10cSrcweir                      compareData( aData, aRet2 ) And _
655*cdf0e10cSrcweir                      compareData( aData, aGVret ), "getValues test" ) And bRet
656*cdf0e10cSrcweir
657*cdf0e10cSrcweir		' set last retrieved values
658*cdf0e10cSrcweir		xLBT.Bool = aRet.Bool
659*cdf0e10cSrcweir		xLBT.Char = aRet.Char
660*cdf0e10cSrcweir		xLBT.Byte = aRet.Byte
661*cdf0e10cSrcweir		xLBT.Short = aRet.Short
662*cdf0e10cSrcweir		xLBT.UShort = aRet.UShort
663*cdf0e10cSrcweir        xLBT.Long = aRet.Long
664*cdf0e10cSrcweir		xLBT.ULong = aRet.ULong
665*cdf0e10cSrcweir		xLBT.Hyper = aRet.Hyper
666*cdf0e10cSrcweir		xLBT.UHyper = aRet.UHyper
667*cdf0e10cSrcweir		xLBT.Float = aRet.Float
668*cdf0e10cSrcweir		xLBT.Double = aRet.Double
669*cdf0e10cSrcweir		xLBT.Enum = aRet.Enum
670*cdf0e10cSrcweir		xLBT.String = aRet.String
671*cdf0e10cSrcweir		xLBT.Interface = aRet.Interface
672*cdf0e10cSrcweir		xLBT.Any = aRet.Any
673*cdf0e10cSrcweir		xLBT.Sequence = aRet.Sequence
674*cdf0e10cSrcweir		xLBT.Struct = aRet2
675*cdf0e10cSrcweir
676*cdf0e10cSrcweir
677*cdf0e10cSrcweir		aRet = New TestDataElements
678*cdf0e10cSrcweir        aRet2 = New TestDataElements
679*cdf0e10cSrcweir		aRet.Hyper = xLBT.Hyper
680*cdf0e10cSrcweir		aRet.UHyper = xLBT.UHyper
681*cdf0e10cSrcweir		aRet.Float = xLBT.Float
682*cdf0e10cSrcweir		aRet.Double = xLBT.Double
683*cdf0e10cSrcweir		aRet.Byte = xLBT.Byte
684*cdf0e10cSrcweir		aRet.Char = xLBT.Char
685*cdf0e10cSrcweir		aRet.Bool = xLBT.Bool
686*cdf0e10cSrcweir		aRet.Short = xLBT.Short
687*cdf0e10cSrcweir		aRet.UShort = xLBT.UShort
688*cdf0e10cSrcweir		aRet.Long = xLBT.Long
689*cdf0e10cSrcweir		aRet.ULong = xLBT.ULong
690*cdf0e10cSrcweir		aRet.Enum = xLBT.Enum
691*cdf0e10cSrcweir		aRet.String = xLBT.String
692*cdf0e10cSrcweir		aRet.Interface = xLBT.Interface
693*cdf0e10cSrcweir		aRet.Any = xLBT.Any
694*cdf0e10cSrcweir		aRet.Sequence = xLBT.Sequence
695*cdf0e10cSrcweir		aRet2 = xLBT.Struct
696*cdf0e10cSrcweir
697*cdf0e10cSrcweir		bRet = check( compareData( aData, aRet ) And _
698*cdf0e10cSrcweir                      compareData( aData, aRet2 ) , "struct comparison test") _
699*cdf0e10cSrcweir                     And bRet
700*cdf0e10cSrcweir
701*cdf0e10cSrcweir		bRet = check(performSequenceTest(xLBT), "sequence test") And bRet
702*cdf0e10cSrcweir
703*cdf0e10cSrcweir		' any test
704*cdf0e10cSrcweir		bRet = check( performAnyTest( xLBT , aData ) , "any test" ) And bRet
705*cdf0e10cSrcweir
706*cdf0e10cSrcweir		'sequence of call test
707*cdf0e10cSrcweir		bRet = check( performSequenceOfCallTest( xLBT ) , _
708*cdf0e10cSrcweir                      "sequence of call test" ) And bRet
709*cdf0e10cSrcweir
710*cdf0e10cSrcweir		' recursive call test
711*cdf0e10cSrcweir		bRet = check( performRecursiveCallTest( xLBT ) , "recursive test" ) _
712*cdf0e10cSrcweir                And bRet
713*cdf0e10cSrcweir
714*cdf0e10cSrcweir		bRet = (compareData( aData, aRet ) And compareData( aData, aRet2 )) _
715*cdf0e10cSrcweir                And bRet
716*cdf0e10cSrcweir
717*cdf0e10cSrcweir        ' check setting of null reference
718*cdf0e10cSrcweir        xLBT.Interface = Nothing
719*cdf0e10cSrcweir        aRet.Interface = xLBT.Interface
720*cdf0e10cSrcweir        bRet = (aRet.Interface Is Nothing) And bRet
721*cdf0e10cSrcweir
722*cdf0e10cSrcweir        Return bRet
723*cdf0e10cSrcweir    End Function
724*cdf0e10cSrcweir
725*cdf0e10cSrcweir    Private Shared Function raiseException(xLBT As XBridgeTest) As Boolean
726*cdf0e10cSrcweir	    Dim nCount As Integer = 0
727*cdf0e10cSrcweir	    Try
728*cdf0e10cSrcweir		    Try
729*cdf0e10cSrcweir			    Try
730*cdf0e10cSrcweir				    Dim aRet As TestDataElements = New TestDataElements
731*cdf0e10cSrcweir                    Dim aRet2 As TestDataElements = New TestDataElements
732*cdf0e10cSrcweir				    xLBT.raiseException( _
733*cdf0e10cSrcweir					    5, CONSTANTS.STRING_TEST_CONSTANT, xLBT.Interface )
734*cdf0e10cSrcweir			    Catch  rExc As unoidl.com.sun.star.lang.IllegalArgumentException
735*cdf0e10cSrcweir				    If rExc.ArgumentPosition = 5 And _
736*cdf0e10cSrcweir                        rExc.Context Is xLBT.Interface
737*cdf0e10cSrcweir					    nCount = nCount + 1
738*cdf0e10cSrcweir				    Else
739*cdf0e10cSrcweir					    check( False, "### unexpected exception content!" )
740*cdf0e10cSrcweir				    End If
741*cdf0e10cSrcweir
742*cdf0e10cSrcweir				    'it is certain, that the RuntimeException testing will fail,
743*cdf0e10cSrcweir                    '    if no
744*cdf0e10cSrcweir				    xLBT.RuntimeException = 0
745*cdf0e10cSrcweir			    End Try
746*cdf0e10cSrcweir		    Catch rExc As unoidl.com.sun.star.uno.RuntimeException
747*cdf0e10cSrcweir			    If rExc.Context Is xLBT.Interface
748*cdf0e10cSrcweir			       nCount = nCount + 1
749*cdf0e10cSrcweir			    Else
750*cdf0e10cSrcweir				    check( False, "### unexpected exception content!" )
751*cdf0e10cSrcweir			    End If
752*cdf0e10cSrcweir                xLBT.RuntimeException = CType(&Hcafebabe, Integer)
753*cdf0e10cSrcweir    	    End Try
754*cdf0e10cSrcweir	    Catch rExc As unoidl.com.sun.star.uno.Exception
755*cdf0e10cSrcweir		    If rExc.Context Is xLBT.Interface
756*cdf0e10cSrcweir		        nCount = nCount + 1
757*cdf0e10cSrcweir		    Else
758*cdf0e10cSrcweir			    check( False, "### unexpected exception content!" )
759*cdf0e10cSrcweir            End If
760*cdf0e10cSrcweir		    Return nCount = 3
761*cdf0e10cSrcweir	    End Try
762*cdf0e10cSrcweir        Return False
763*cdf0e10cSrcweir    End Function
764*cdf0e10cSrcweir
765*cdf0e10cSrcweir    Private Shared Function raiseOnewayException(xLBT As XBridgeTest) As Boolean
766*cdf0e10cSrcweir        Dim bReturn As Boolean= True
767*cdf0e10cSrcweir	    Dim sCompare As String = CONSTANTS.STRING_TEST_CONSTANT
768*cdf0e10cSrcweir	    Try
769*cdf0e10cSrcweir		    ' Note : the exception may fly or not (e.g. remote scenario).
770*cdf0e10cSrcweir		    '        When it flies, it must contain the correct elements.
771*cdf0e10cSrcweir		    xLBT.raiseRuntimeExceptionOneway(sCompare, xLBT.Interface )
772*cdf0e10cSrcweir	    Catch e As RuntimeException
773*cdf0e10cSrcweir		    bReturn =  xLBT.Interface Is e.Context
774*cdf0e10cSrcweir	    End Try
775*cdf0e10cSrcweir        Return bReturn
776*cdf0e10cSrcweir    End Function
777*cdf0e10cSrcweir
778*cdf0e10cSrcweir    'Test the System::Object method on the proxy object
779*cdf0e10cSrcweir    '
780*cdf0e10cSrcweir    Private Shared Function testObjectMethodsImplemention(xLBT As XBridgeTest) As Boolean
781*cdf0e10cSrcweir        Dim ret As Boolean = False
782*cdf0e10cSrcweir        Dim obj As Object = New Object
783*cdf0e10cSrcweir	    Dim xInt As Object = DirectCast(xLBT, Object)
784*cdf0e10cSrcweir	    Dim xBase As XBridgeTestBase = DirectCast(xLBT, XBridgeTestBase)
785*cdf0e10cSrcweir	    ' Object.Equals
786*cdf0e10cSrcweir	    ret = DirectCast(xLBT, Object).Equals(obj) = False
787*cdf0e10cSrcweir	    ret = DirectCast(xLBT, Object).Equals(xLBT) And ret
788*cdf0e10cSrcweir	    ret = Object.Equals(obj, obj) And ret
789*cdf0e10cSrcweir	    ret = Object.Equals(xLBT, xBase) And ret
790*cdf0e10cSrcweir	    'Object.GetHashCode
791*cdf0e10cSrcweir	    ' Don't know how to verify this. Currently it is not possible to get the object id from a proxy
792*cdf0e10cSrcweir	    Dim nHash As Integer = DirectCast(xLBT, Object).GetHashCode()
793*cdf0e10cSrcweir	    ret = nHash = DirectCast(xBase, Object).GetHashCode() And ret
794*cdf0e10cSrcweir
795*cdf0e10cSrcweir	    'Object.ToString
796*cdf0e10cSrcweir        ' Don't know how to verify this automatically.
797*cdf0e10cSrcweir	    Dim s As String = DirectCast(xLBT, Object).ToString()
798*cdf0e10cSrcweir        ret = (s.Length > 0) And ret
799*cdf0e10cSrcweir        Return ret
800*cdf0e10cSrcweir    End Function
801*cdf0e10cSrcweir
802*cdf0e10cSrcweir    Private Shared Function performQueryForUnknownType(xLBT As XBridgeTest) As Boolean
803*cdf0e10cSrcweir        Dim bRet As Boolean = False
804*cdf0e10cSrcweir        ' test queryInterface for an unknown type
805*cdf0e10cSrcweir        Try
806*cdf0e10cSrcweir            Dim a As foo.MyInterface = DirectCast(xLBT, foo.MyInterface)
807*cdf0e10cSrcweir        Catch e As System.InvalidCastException
808*cdf0e10cSrcweir            bRet = True
809*cdf0e10cSrcweir        End Try
810*cdf0e10cSrcweir
811*cdf0e10cSrcweir        Return bRet
812*cdf0e10cSrcweir    End Function
813*cdf0e10cSrcweir
814*cdf0e10cSrcweir
815*cdf0e10cSrcweir    Private Shared Sub perform_test( xLBT As XBridgeTest)
816*cdf0e10cSrcweir        Dim bRet As Boolean = True
817*cdf0e10cSrcweir        bRet = check( performTest( xLBT ), "standard test" ) And bRet
818*cdf0e10cSrcweir        bRet = check( raiseException( xLBT ) , "exception test" ) And bRet
819*cdf0e10cSrcweir        bRet = check( raiseOnewayException( xLBT ), "oneway exception test" ) _
820*cdf0e10cSrcweir               And bRet
821*cdf0e10cSrcweir        bRet = check( testObjectMethodsImplemention(xLBT), _
822*cdf0e10cSrcweir               "object methods test") And bRet
823*cdf0e10cSrcweir        bRet = performQueryForUnknownType( xLBT ) And bRet
824*cdf0e10cSrcweir        If  Not bRet
825*cdf0e10cSrcweir            Throw New unoidl.com.sun.star.uno.RuntimeException( "error: test failed!", Nothing)
826*cdf0e10cSrcweir        End If
827*cdf0e10cSrcweir    End Sub
828*cdf0e10cSrcweir
829*cdf0e10cSrcweir
830*cdf0e10cSrcweir
831*cdf0e10cSrcweir    Public Overridable Function run(args() As String) As Integer _
832*cdf0e10cSrcweir	   Implements XMain.run
833*cdf0e10cSrcweir        Try
834*cdf0e10cSrcweir            If (args.Length < 1)
835*cdf0e10cSrcweir                Throw New RuntimeException( _
836*cdf0e10cSrcweir                    "missing argument for bridgetest!", Me )
837*cdf0e10cSrcweir            End If
838*cdf0e10cSrcweir
839*cdf0e10cSrcweir            Dim test_obj As Object = _
840*cdf0e10cSrcweir                m_xContext.getServiceManager().createInstanceWithContext( _
841*cdf0e10cSrcweir                    args( 0 ), m_xContext )
842*cdf0e10cSrcweir
843*cdf0e10cSrcweir            Debug.WriteLine( _
844*cdf0e10cSrcweir                "cli target bridgetest obj: {0}", test_obj.ToString() )
845*cdf0e10cSrcweir            Dim xTest As XBridgeTest = DirectCast(test_obj, XBridgeTest)
846*cdf0e10cSrcweir            perform_test( xTest )
847*cdf0e10cSrcweir            Console.WriteLine("### cli_uno VB bridgetest succeeded.")
848*cdf0e10cSrcweir            return 0
849*cdf0e10cSrcweir	Catch e as unoidl.com.sun.star.uno.RuntimeException
850*cdf0e10cSrcweir	     Throw
851*cdf0e10cSrcweir        Catch e as System.Exception
852*cdf0e10cSrcweir	      Throw New unoidl.com.sun.star.uno.RuntimeException( _
853*cdf0e10cSrcweir		    "cli_vb_bridgetest.vb: unexpected exception occured in XMain::run. " _
854*cdf0e10cSrcweir		    & "Original exception: " + e.GetType().Name + "\n Message: " _
855*cdf0e10cSrcweir		    & e.Message , Nothing)
856*cdf0e10cSrcweir
857*cdf0e10cSrcweir        End Try
858*cdf0e10cSrcweir    End Function
859*cdf0e10cSrcweir
860*cdf0e10cSrcweirEnd Class
861*cdf0e10cSrcweir
862*cdf0e10cSrcweirEnd Namespace
863