merge the formfield patch from ooo-build
[ooovba.git] / testautomation / writer / optional / includes / option / wh_o_3.inc
blob29709b3cab3faad533cf7c5c9ad6b89e7c86766b
1 'encoding UTF-8  Do not remove or change this line!
2 '**************************************************************************
3 '* DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
4 '* 
5 '* Copyright 2008 by Sun Microsystems, Inc.
6 '*
7 '* OpenOffice.org - a multi-platform office productivity suite
8 '*
9 '* $RCSfile: wh_o_3.inc,v $
11 '* $Revision: 1.2 $
13 '* last change: $Author: vg $ $Date: 2008-08-18 12:32:30 $
15 '* This file is part of OpenOffice.org.
17 '* OpenOffice.org is free software: you can redistribute it and/or modify
18 '* it under the terms of the GNU Lesser General Public License version 3
19 '* only, as published by the Free Software Foundation.
21 '* OpenOffice.org is distributed in the hope that it will be useful,
22 '* but WITHOUT ANY WARRANTY; without even the implied warranty of
23 '* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
24 '* GNU Lesser General Public License version 3 for more details
25 '* (a copy is included in the LICENSE file that accompanied this code).
27 '* You should have received a copy of the GNU Lesser General Public License
28 '* version 3 along with OpenOffice.org.  If not, see
29 '* <http://www.openoffice.org/license.html>
30 '* for a copy of the LGPLv3 License.
32 '/************************************************************************
34 '* owner : helge.delfs@sun.com
36 '* short description : Funcitonal-Test for Tools -Options - HTML - Cursor.
38 '\***********************************************************************
40 sub wh_o_3
41    Call tToolsOptionsHTMLInsert
43 ' on view2 with ex content
44    Call tToolsOptionsHTMLCursor
45 end sub
47 '------------------------------------------------------------------------------
48 testcase tToolsOptionsHTMLInsert
50 '/ Insert                     ///'
51 '/ ------                     ///'
52 '/ tToolsOptionsHTMLInsert    ///'
53 '/ normal                         ///'
54 '/ Function:  ///'
55 '/ Function:  not yet: Tables ///'
56 '/                                ///'
58    dim irgendwas(8) as boolean    ' Checkbox states
60 '(1) = Automatisch
62 '(2) = Ueberschrift
63 '(3) = Wiederholen                       depends on Ueberschrift
64 '(4) = NichtTrennen
65 '(5) = Umrandung
67 '(6) = AutomatischeZahlenerkennung
68 '(7) = Zahlenformaterkennung             depends on AutomatischeZahlenerkennung
69 '(8) = AutomatischeAusrichtung           depends on AutomatischeZahlenerkennung
71    call hNewDocument
72     printlog "'///- Tools/Options/HTML: Insert ///"
74     printlog ("'/// - save states ///")
75     ToolsOptions
76     hToolsOptions ("HTML","Table")
78     irgendwas(2) = Ueberschrift.IsChecked
79     irgendwas(3) = Wiederholen.IsChecked
80     irgendwas(5) = Umrandung.IsChecked
82     irgendwas(6) = AutomatischeZahlenerkennung.IsChecked
83     irgendwas(7) = Zahlenformaterkennung.IsChecked
84     irgendwas(8) = AutomatischeAusrichtung.IsChecked
86     printlog ("'/// - all states inverting ///")
88 '      if irgendwas(2) Then Ueberschrift.UnCheck                Else Ueberschrift.Check
89     Ueberschrift.Check
90     if irgendwas(3) Then Wiederholen.UnCheck                 Else Wiederholen.Check
91     if irgendwas(5) Then Umrandung.UnCheck                   Else Umrandung.Check
93 '      if irgendwas(6) Then AutomatischeZahlenerkennung.UnCheck Else AutomatischeZahlenerkennung.Check
94     AutomatischeZahlenerkennung.Check
95     if irgendwas(7) Then Zahlenformaterkennung.UnCheck       Else Zahlenformaterkennung.Check
96     if irgendwas(8) Then AutomatischeAusrichtung.UnCheck     Else AutomatischeAusrichtung.Check
98     Kontext "ExtrasOptionenDlg"
99     ExtrasOptionenDlg.OK
101     printlog ("'/// - SO quit - start ///")
103     call wOfficeRestart
105     printlog ("'/// - checking states ///")
106     ToolsOptions
107     hToolsOptions ( "HTML" , "Table" )
109 '      If ( irgendwas(2) = Ueberschrift.IsChecked                ) Then WarnLog "Ueberschrift state changed"
110       If ( Ueberschrift.IsChecked                = False ) Then WarnLog "Ueberschrift state changed"
111       If ( irgendwas(3) = Wiederholen.IsChecked                 ) Then WarnLog "Wiederholen state changed"
112       If ( irgendwas(5) = Umrandung.IsChecked                   ) Then WarnLog "Umrandung state changed"
114 '      If ( irgendwas(6) = AutomatischeZahlenerkennung.IsChecked ) Then WarnLog "AutomatischeZahlenerkennung state changed"
115       If ( AutomatischeZahlenerkennung.IsChecked = False ) Then WarnLog "AutomatischeZahlenerkennung state changed"
116       If ( irgendwas(7) = Zahlenformaterkennung.IsChecked       ) Then WarnLog "Zahlenformaterkennung state changed"
117       If ( irgendwas(8) = AutomatischeAusrichtung.IsChecked     ) Then WarnLog "AutomatischeAusrichtung state changed"
119     Kontext "ExtrasOptionenDlg"
120     ExtrasOptionenDlg.OK
122     printlog ("'/// - all UnCheck -> o ///")
123     ToolsOptions
124     hToolsOptions ( "HTML" , "Table" )
126     Ueberschrift.UnCheck
127 '      Wiederholen.UnCheck
128     Umrandung.UnCheck
130     AutomatischeZahlenerkennung.UnCheck
131 '      Zahlenformaterkennung.UnCheck
132 '      AutomatischeAusrichtung.UnCheck
134     Kontext "ExtrasOptionenDlg"
135     ExtrasOptionenDlg.OK
137 'These Options also have another location
139 '/// 2.Location of Options: InsertTableWriter get's checked too ///'
141   Printlog "'///    - check in InsertTableHTML ///"
142    Call hNewDocument
143    InsertTableWriter
144    Kontext "TabelleEinfuegenWriter"
146       If ( Ueberschrift.IsChecked          ) Then WarnLog "Ueberschrift x"
147 '      If ( UeberschriftWiederholen.IsChecked ) Then WarnLog "Wiederholen x"
148       If ( Umrandung.IsChecked           ) Then WarnLog "Umrandung x"
150    TabelleEinfuegenWriter.OK
152 '/// Function: Input in tables ///'
154    Kontext "DocumentWriter"
156     DocumentWriter.TypeKeys "<Down>1<Tab><Left>"
158     FormatParagraph
160     Kontext
161    Active.SetPage TabAusrichtungAbsatz
162    Kontext "TabAusrichtungAbsatz"
163    if NOT Links.IsChecked then Warnlog "Die automatische Ausrichtung der Zahl wurde trotzdem durchgeführt!"
165     TabAusrichtungAbsatz.Cancel
168    FormatNumberFormat
170     Kontext "Zahlenformat"
171    If Kategorie.GetSelIndex <> 11 then Warnlog "Das Zahlenformat ist nicht Text geblieben!"
173     Zahlenformat.Cancel
176    Call hCloseDocument
178 '.................
180   printlog ("'/// - check if all UnChecked ///")
182   ' Workaround issue i48383 Slot get's executed on backing window
183   Kontext "DocumentWriter"
184   DocumentWriter.typekeys ("a")
186     ToolsOptions
187    hToolsOptions ( "HTML" , "Table" )
189       If Ueberschrift.IsChecked                Then WarnLog "Ueberschrift x"
190 '      If Wiederholen.IsChecked                 Then WarnLog "Wiederholen x"
191       If Umrandung.IsChecked                   Then WarnLog "Umrandung x"
193       If AutomatischeZahlenerkennung.IsChecked Then WarnLog "AutomatischeZahlenerkennung x"
194 '      If Zahlenformaterkennung.IsChecked       Then WarnLog "Zahlenformaterkennung x"
195 '      If AutomatischeAusrichtung.IsChecked     Then WarnLog "AutomatischeAusrichtung x"
197       Printlog ("'/// - all Check -> x ///")
199       Ueberschrift.Check
200       Wiederholen.Check
201       Umrandung.Check
203       AutomatischeZahlenerkennung.Check
204       Zahlenformaterkennung.Check
205       AutomatischeAusrichtung.Check
207     Kontext "ExtrasOptionenDlg"
208     ExtrasOptionenDlg.OK
210 'These Options also have another location
212   Printlog "'///    - check in InsertTableWriter ///"
213    hNewDocument
214    InsertTableWriter
215    Kontext "TabelleEinfuegenWriter"
217       If ( Ueberschrift.IsChecked                = FALSE ) Then WarnLog "Ueberschrift o"
218       If ( UeberschriftWiederholen.IsChecked                 = FALSE ) Then WarnLog "Wiederholen o"
219       If ( Umrandung.IsChecked                   = FALSE ) Then WarnLog "Umrandung o"
221    TabelleEinfuegenWriter.Ok
223    Kontext "DocumentWriter"
224    DocumentWriter.TypeKeys "<Down>1<Tab><Left>"
225    FormatParagraph
226    Kontext
227    Active.SetPage TabAusrichtungAbsatz
228    Kontext "TabAusrichtungAbsatz"
229    if NOT Rechts.IsChecked then Warnlog "Alignment of number didn't change to: right!"
230    TabAusrichtungAbsatz.Cancel
232    FormatNumberFormat
233    Kontext "Zahlenformat"
234    If Kategorie.GetSelIndex <> 3 then Warnlog "numberformat didn't get changed!"
235    Zahlenformat.Cancel
237    Call hCloseDocument
239 '.......................
241   printlog ("'/// - check if all Checked ///")
243   ' Workaround issue i48383 Slot get's executed on backing window
244   Kontext "DocumentWriter"
245   DocumentWriter.typekeys ("a")
246   
247     ToolsOptions
248     hToolsOptions ( "HTML" , "Table" )
250       If ( Ueberschrift.IsChecked                = FALSE ) Then WarnLog "Ueberschrift o"
251       If ( Wiederholen.IsChecked                 = FALSE ) Then WarnLog "Wiederholen o"
252       If ( Umrandung.IsChecked                   = FALSE ) Then WarnLog "Umrandung o"
254       If ( AutomatischeZahlenerkennung.IsChecked = FALSE ) Then WarnLog "AutomatischeZahlenerkennung o"
255       If ( Zahlenformaterkennung.IsChecked       = FALSE ) Then WarnLog "Zahlenformaterkennung o"
256       If ( AutomatischeAusrichtung.IsChecked     = FALSE ) Then WarnLog "AutomatischeAusrichtung o"
258   printlog ("'/// - restore states ///")
260       If ( irgendwas(2) = TRUE ) Then Ueberschrift.Check                Else Ueberschrift.UnCheck
261       If ( irgendwas(3) = TRUE ) Then Wiederholen.Check                 Else _
262       if Ueberschrift.IsChecked Then Wiederholen.UnCheck
263       If ( irgendwas(5) = TRUE ) Then Umrandung.Check                   Else Umrandung.UnCheck
265       AutomatischeZahlenerkennung.Check
266     if AutomatischeZahlenerkennung.IsChecked then
267         if ( irgendwas(7) = TRUE ) Then Zahlenformaterkennung.Check
268         if ( irgendwas(8) = TRUE ) Then AutomatischeAusrichtung.Check
269     end if
270     if ( irgendwas(6) = TRUE ) Then AutomatischeAusrichtung.Check
272     Kontext "ExtrasOptionenDlg"
273     ExtrasOptionenDlg.OK
275     Do Until GetDocumentCount = 0
276         Call hCloseDocument
277     Loop
278 endcase
280 '------------------------------------------------------------------------------------------------------------------------
282 testcase tToolsOptionsHTMLCursor
284    dim irgendwas(17) as boolean    ' Checkbox states
286 '(10) = Absatzenden
287 '(11) = WeicheTrenner
288 '(12) = Leerzeichen
289 '(13) = GeschLeerzeichen
290 '(14) = Tabulatoren
291 '(15) = Umbrueche
292 '(16) = VersteckterText
293 '(17) = VersteckteAbsatze
295    hNewDocument
296   printlog "'///- Tools/Options/Writer: View 2 ///"
298   printlog ("'/// - save states ///")
299     ToolsOptions
300     hToolsOptions ("HTML","FORMATTINGAIDS")
302       irgendwas(10) = Absatzenden.IsChecked
303       irgendwas(11) = WeicheTrenner.IsChecked
304       irgendwas(12) = Leerzeichen.IsChecked
305       irgendwas(13) = GeschLeerzeichen.IsChecked
306       irgendwas(15) = Umbrueche.IsChecked
308       printlog ("'/// - all states inverting ///")
310       if irgendwas(10) Then Absatzenden.UnCheck Else Absatzenden.Check
311       if irgendwas(11) Then WeicheTrenner.UnCheck Else WeicheTrenner.Check
312       if irgendwas(12) Then Leerzeichen.UnCheck Else Leerzeichen.Check
313       if irgendwas(13) Then GeschLeerzeichen.UnCheck Else GeschLeerzeichen.Check
314       if irgendwas(15) Then Umbrueche.UnCheck Else Umbrueche.Check
316     Kontext "ExtrasOptionenDlg"
317     ExtrasOptionenDlg.OK
319     printlog ("'/// - SO quit - start ///")
321     call wOfficeRestart
323     printlog ("'/// - checking states ///")
324     ToolsOptions
325     hToolsOptions ( "HTML" , "FORMATTINGAIDS" )
327       If ( irgendwas(10) = Absatzenden.IsChecked  ) Then  WarnLog "Absatzenden state changed"
328       If ( irgendwas(11) = WeicheTrenner.IsChecked  ) Then  WarnLog "WeicheTrenner state changed"
329       If ( irgendwas(12) = Leerzeichen.IsChecked  ) Then  WarnLog "Leerzeichen state changed"
330       If ( irgendwas(13) = GeschLeerzeichen.IsChecked  ) Then  WarnLog "GeschLeerzeichen state changed (Bug#99202)"
331       If ( irgendwas(15) = Umbrueche.IsChecked  ) Then  WarnLog "Umbrueche state changed (Bug#99202)"
333     Kontext "ExtrasOptionenDlg"
334     ExtrasOptionenDlg.OK
336     printlog ("'/// - all UnCheck -> o ///")
337     ToolsOptions
338     hToolsOptions ( "HTML" , "FORMATTINGAIDS" )
340       Absatzenden.UnCheck
341       WeicheTrenner.UnCheck
342       Leerzeichen.UnCheck
343       GeschLeerzeichen.UnCheck
344       Umbrueche.UnCheck
346     Kontext "ExtrasOptionenDlg"
347     ExtrasOptionenDlg.OK
349   printlog ("'/// - check if all UnChecked ///")
350     ToolsOptions
351     hToolsOptions ( "HTML" , "FORMATTINGAIDS" )
353       If Absatzenden.IsChecked Then  WarnLog "Absatzenden x"
354       If WeicheTrenner.IsChecked Then  WarnLog "WeicheTrenner x"
355       If Leerzeichen.IsChecked Then  WarnLog "Leerzeichen x"
356       If GeschLeerzeichen.IsChecked Then  WarnLog "GeschLeerzeichen x"
357       If Umbrueche.IsChecked Then  WarnLog "Umbrueche x"
359       Printlog ("'/// - all Check -> x ///")
361       Absatzenden.Check
362       WeicheTrenner.Check
363       Leerzeichen.Check
364       GeschLeerzeichen.Check
365       Umbrueche.Check
367     Kontext "ExtrasOptionenDlg"
368     ExtrasOptionenDlg.OK
370   printlog ("'/// - check if all Checked ///")
371     ToolsOptions
372     hToolsOptions ( "HTML" , "FORMATTINGAIDS" )
374       If True <> Absatzenden.IsChecked Then  WarnLog "Absatzenden o BugID: 82942 OS"
375       If True <> WeicheTrenner.IsChecked Then  WarnLog "WeicheTrenner o"
376       If True <> Leerzeichen.IsChecked Then  WarnLog "Leerzeichen o"
377       If True <> GeschLeerzeichen.IsChecked Then  WarnLog "GeschLeerzeichen o"
378       If True <> Umbrueche.IsChecked Then  WarnLog "Umbrueche o"
380   printlog ("'/// - restore states ///")
382       If ( irgendwas(10) = TRUE ) Then  Absatzenden.Check Else Absatzenden.UnCheck
383       If ( irgendwas(11) = TRUE ) Then  WeicheTrenner.Check Else WeicheTrenner.UnCheck
384       If ( irgendwas(12) = TRUE ) Then  Leerzeichen.Check Else Leerzeichen.UnCheck
385       If ( irgendwas(13) = TRUE ) Then  GeschLeerzeichen.Check Else GeschLeerzeichen.UnCheck
386       If ( irgendwas(15) = TRUE ) Then  Umbrueche.Check Else Umbrueche.UnCheck
388     Kontext "ExtrasOptionenDlg"
389     ExtrasOptionenDlg.OK
391     Do Until GetDocumentCount = 0
392         Call hCloseDocument
393     Loop
394 endcase