xref: /AOO41X/main/migrationanalysis/src/wizard/Utilities.bas (revision cdf0e10c4e3984b49a9502b011690b615761d4a3)
1*cdf0e10cSrcweirAttribute VB_Name = "Utilities"
2*cdf0e10cSrcweir'/*************************************************************************
3*cdf0e10cSrcweir' *
4*cdf0e10cSrcweir' DO NOT ALTER OR REMOVE COPYRIGHT NOTICES OR THIS FILE HEADER.
5*cdf0e10cSrcweir'
6*cdf0e10cSrcweir' Copyright 2000, 2010 Oracle and/or its affiliates.
7*cdf0e10cSrcweir'
8*cdf0e10cSrcweir' OpenOffice.org - a multi-platform office productivity suite
9*cdf0e10cSrcweir'
10*cdf0e10cSrcweir' This file is part of OpenOffice.org.
11*cdf0e10cSrcweir'
12*cdf0e10cSrcweir' OpenOffice.org is free software: you can redistribute it and/or modify
13*cdf0e10cSrcweir' it under the terms of the GNU Lesser General Public License version 3
14*cdf0e10cSrcweir' only, as published by the Free Software Foundation.
15*cdf0e10cSrcweir'
16*cdf0e10cSrcweir' OpenOffice.org is distributed in the hope that it will be useful,
17*cdf0e10cSrcweir' but WITHOUT ANY WARRANTY; without even the implied warranty of
18*cdf0e10cSrcweir' MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
19*cdf0e10cSrcweir' GNU Lesser General Public License version 3 for more details
20*cdf0e10cSrcweir' (a copy is included in the LICENSE file that accompanied this code).
21*cdf0e10cSrcweir'
22*cdf0e10cSrcweir' You should have received a copy of the GNU Lesser General Public License
23*cdf0e10cSrcweir' version 3 along with OpenOffice.org.  If not, see
24*cdf0e10cSrcweir' <http://www.openoffice.org/license.html>
25*cdf0e10cSrcweir' for a copy of the LGPLv3 License.
26*cdf0e10cSrcweir'
27*cdf0e10cSrcweir' ************************************************************************/
28*cdf0e10cSrcweirOption Explicit
29*cdf0e10cSrcweir
30*cdf0e10cSrcweirPublic Const LOCALE_ILANGUAGE             As Long = &H1    'language id
31*cdf0e10cSrcweirPublic Const LOCALE_SLANGUAGE             As Long = &H2    'localized name of lang
32*cdf0e10cSrcweirPublic Const LOCALE_SENGLANGUAGE          As Long = &H1001 'English name of lang
33*cdf0e10cSrcweirPublic Const LOCALE_SABBREVLANGNAME       As Long = &H3    'abbreviated lang name
34*cdf0e10cSrcweirPublic Const LOCALE_SNATIVELANGNAME       As Long = &H4    'native name of lang
35*cdf0e10cSrcweirPublic Const LOCALE_ICOUNTRY              As Long = &H5    'country code
36*cdf0e10cSrcweirPublic Const LOCALE_SCOUNTRY              As Long = &H6    'localized name of country
37*cdf0e10cSrcweirPublic Const LOCALE_SENGCOUNTRY           As Long = &H1002 'English name of country
38*cdf0e10cSrcweirPublic Const LOCALE_SABBREVCTRYNAME       As Long = &H7    'abbreviated country name
39*cdf0e10cSrcweirPublic Const LOCALE_SNATIVECTRYNAME       As Long = &H8    'native name of country
40*cdf0e10cSrcweirPublic Const LOCALE_SINTLSYMBOL           As Long = &H15   'intl monetary symbol
41*cdf0e10cSrcweirPublic Const LOCALE_IDEFAULTLANGUAGE      As Long = &H9    'def language id
42*cdf0e10cSrcweirPublic Const LOCALE_IDEFAULTCOUNTRY       As Long = &HA    'def country code
43*cdf0e10cSrcweirPublic Const LOCALE_IDEFAULTCODEPAGE      As Long = &HB    'def oem code page
44*cdf0e10cSrcweirPublic Const LOCALE_IDEFAULTANSICODEPAGE  As Long = &H1004 'def ansi code page
45*cdf0e10cSrcweirPublic Const LOCALE_IDEFAULTMACCODEPAGE   As Long = &H1011 'def mac code page
46*cdf0e10cSrcweir
47*cdf0e10cSrcweirPublic Const LOCALE_IMEASURE              As Long = &HD     '0 = metric, 1 = US
48*cdf0e10cSrcweirPublic Const LOCALE_SSHORTDATE            As Long = &H1F    'short date format string
49*cdf0e10cSrcweir
50*cdf0e10cSrcweir'#if(WINVER >=  &H0400)
51*cdf0e10cSrcweirPublic Const LOCALE_SISO639LANGNAME       As Long = &H59   'ISO abbreviated language name
52*cdf0e10cSrcweirPublic Const LOCALE_SISO3166CTRYNAME      As Long = &H5A   'ISO abbreviated country name
53*cdf0e10cSrcweir'#endif /* WINVER >= as long = &H0400 */
54*cdf0e10cSrcweir
55*cdf0e10cSrcweir'#if(WINVER >=  &H0500)
56*cdf0e10cSrcweirPublic Const LOCALE_SNATIVECURRNAME        As Long = &H1008 'native name of currency
57*cdf0e10cSrcweirPublic Const LOCALE_IDEFAULTEBCDICCODEPAGE As Long = &H1012 'default ebcdic code page
58*cdf0e10cSrcweirPublic Const LOCALE_SSORTNAME              As Long = &H1013 'sort name
59*cdf0e10cSrcweir'#endif /* WINVER >=  &H0500 */
60*cdf0e10cSrcweir
61*cdf0e10cSrcweirPublic Const CSTR_LOG_FILE_NAME = "analysis.log"
62*cdf0e10cSrcweir
63*cdf0e10cSrcweirPublic Declare Function GetThreadLocale Lib "kernel32" () As Long
64*cdf0e10cSrcweir
65*cdf0e10cSrcweirPublic Declare Function GetSystemDefaultLCID Lib "kernel32" () As Long
66*cdf0e10cSrcweirPublic Declare Function GetUserDefaultLCID Lib "kernel32" () As Long
67*cdf0e10cSrcweirPublic Declare Function GetUserDefaultLangID Lib "kernel32" () As Long
68*cdf0e10cSrcweirPublic Declare Function GetSystemDefaultLangID Lib "kernel32" () As Long
69*cdf0e10cSrcweir
70*cdf0e10cSrcweirPublic Declare Function GetLocaleInfo Lib "kernel32" _
71*cdf0e10cSrcweir   Alias "GetLocaleInfoA" _
72*cdf0e10cSrcweir  (ByVal Locale As Long, _
73*cdf0e10cSrcweir   ByVal LCType As Long, _
74*cdf0e10cSrcweir   ByVal lpLCData As String, _
75*cdf0e10cSrcweir   ByVal cchData As Long) As Long
76*cdf0e10cSrcweir
77*cdf0e10cSrcweirPrivate Const VER_PLATFORM_WIN32s = 0
78*cdf0e10cSrcweirPrivate Const VER_PLATFORM_WIN32_WINDOWS = 1
79*cdf0e10cSrcweirPrivate Const VER_PLATFORM_WIN32_NT = 2
80*cdf0e10cSrcweir
81*cdf0e10cSrcweirPrivate Type OSVERSIONINFO
82*cdf0e10cSrcweir  OSVSize         As Long         'size, in bytes, of this data structure
83*cdf0e10cSrcweir  dwVerMajor      As Long         'ie NT 3.51, dwVerMajor = 3; NT 4.0, dwVerMajor = 4.
84*cdf0e10cSrcweir  dwVerMinor      As Long         'ie NT 3.51, dwVerMinor = 51; NT 4.0, dwVerMinor= 0.
85*cdf0e10cSrcweir  dwBuildNumber   As Long         'NT: build number of the OS
86*cdf0e10cSrcweir                                  'Win9x: build number of the OS in low-order word.
87*cdf0e10cSrcweir                                  '       High-order word contains major & minor ver nos.
88*cdf0e10cSrcweir  PlatformID      As Long         'Identifies the operating system platform.
89*cdf0e10cSrcweir  szCSDVersion    As String * 128 'NT: string, such as "Service Pack 3"
90*cdf0e10cSrcweir                                  'Win9x: string providing arbitrary additional information
91*cdf0e10cSrcweirEnd Type
92*cdf0e10cSrcweir
93*cdf0e10cSrcweirPublic Type RGB_WINVER
94*cdf0e10cSrcweir  PlatformID      As Long
95*cdf0e10cSrcweir  VersionName     As String
96*cdf0e10cSrcweir  VersionNo       As String
97*cdf0e10cSrcweir  ServicePack     As String
98*cdf0e10cSrcweir  BuildNo         As String
99*cdf0e10cSrcweirEnd Type
100*cdf0e10cSrcweir
101*cdf0e10cSrcweir'defined As Any to support OSVERSIONINFO and OSVERSIONINFOEX
102*cdf0e10cSrcweirPrivate Declare Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" _
103*cdf0e10cSrcweir  (lpVersionInformation As Any) As Long
104*cdf0e10cSrcweir
105*cdf0e10cSrcweirPrivate Declare Function GetDesktopWindow Lib "user32" () As Long
106*cdf0e10cSrcweir
107*cdf0e10cSrcweirPrivate Declare Function ShellExecute Lib "shell32" _
108*cdf0e10cSrcweir    Alias "ShellExecuteA" _
109*cdf0e10cSrcweir   (ByVal hWnd As Long, _
110*cdf0e10cSrcweir    ByVal lpOperation As String, _
111*cdf0e10cSrcweir    ByVal lpFile As String, _
112*cdf0e10cSrcweir    ByVal lpParameters As String, _
113*cdf0e10cSrcweir    ByVal lpDirectory As String, _
114*cdf0e10cSrcweir    ByVal nShowCmd As Long) As Long
115*cdf0e10cSrcweir
116*cdf0e10cSrcweirPublic Const SW_SHOWNORMAL As Long = 1
117*cdf0e10cSrcweirPublic Const SW_SHOWMAXIMIZED As Long = 3
118*cdf0e10cSrcweirPublic Const SW_SHOWDEFAULT As Long = 10
119*cdf0e10cSrcweirPublic Const SE_ERR_NOASSOC As Long = 31
120*cdf0e10cSrcweir
121*cdf0e10cSrcweirPublic Const CNO_OPTIONAL_PARAM = "_NoOptionalParam_"
122*cdf0e10cSrcweirPrivate Declare Function WritePrivateProfileString Lib "kernel32" _
123*cdf0e10cSrcweir   Alias "WritePrivateProfileStringA" _
124*cdf0e10cSrcweir  (ByVal lpSectionName As String, _
125*cdf0e10cSrcweir   ByVal lpKeyName As Any, _
126*cdf0e10cSrcweir   ByVal lpString As Any, _
127*cdf0e10cSrcweir   ByVal lpFileName As String) As Long
128*cdf0e10cSrcweir
129*cdf0e10cSrcweir
130*cdf0e10cSrcweirPublic Const HKEY_LOCAL_MACHINE  As Long = &H80000002
131*cdf0e10cSrcweirPublic Const HKEY_CLASSES_ROOT = &H80000000
132*cdf0e10cSrcweirPrivate Const ERROR_MORE_DATA = 234
133*cdf0e10cSrcweirPrivate Const ERROR_SUCCESS As Long = 0
134*cdf0e10cSrcweirPrivate Const KEY_QUERY_VALUE As Long = &H1
135*cdf0e10cSrcweirPrivate Const KEY_ENUMERATE_SUB_KEYS As Long = &H8
136*cdf0e10cSrcweirPrivate Const KEY_NOTIFY As Long = &H10
137*cdf0e10cSrcweirPrivate Const STANDARD_RIGHTS_READ As Long = &H20000
138*cdf0e10cSrcweirPrivate Const SYNCHRONIZE As Long = &H100000
139*cdf0e10cSrcweirPrivate Const KEY_READ As Long = ((STANDARD_RIGHTS_READ Or _
140*cdf0e10cSrcweir                                   KEY_QUERY_VALUE Or _
141*cdf0e10cSrcweir                                   KEY_ENUMERATE_SUB_KEYS Or _
142*cdf0e10cSrcweir                                   KEY_NOTIFY) And _
143*cdf0e10cSrcweir                                   (Not SYNCHRONIZE))
144*cdf0e10cSrcweir
145*cdf0e10cSrcweirPrivate Declare Function RegOpenKeyEx Lib "advapi32.dll" _
146*cdf0e10cSrcweir   Alias "RegOpenKeyExA" _
147*cdf0e10cSrcweir  (ByVal hKey As Long, _
148*cdf0e10cSrcweir   ByVal lpSubKey As String, _
149*cdf0e10cSrcweir   ByVal ulOptions As Long, _
150*cdf0e10cSrcweir   ByVal samDesired As Long, _
151*cdf0e10cSrcweir   phkResult As Long) As Long
152*cdf0e10cSrcweir
153*cdf0e10cSrcweirPrivate Declare Function RegQueryValueEx Lib "advapi32.dll" _
154*cdf0e10cSrcweir   Alias "RegQueryValueExA" _
155*cdf0e10cSrcweir  (ByVal hKey As Long, _
156*cdf0e10cSrcweir   ByVal lpValueName As String, _
157*cdf0e10cSrcweir   ByVal lpReserved As Long, _
158*cdf0e10cSrcweir   lpType As Long, _
159*cdf0e10cSrcweir   lpData As Any, _
160*cdf0e10cSrcweir   lpcbData As Long) As Long
161*cdf0e10cSrcweir
162*cdf0e10cSrcweirPrivate Declare Function RegCloseKey Lib "advapi32.dll" _
163*cdf0e10cSrcweir  (ByVal hKey As Long) As Long
164*cdf0e10cSrcweir
165*cdf0e10cSrcweirPrivate Declare Function lstrlenW Lib "kernel32" _
166*cdf0e10cSrcweir  (ByVal lpString As Long) As Long
167*cdf0e10cSrcweir
168*cdf0e10cSrcweirPrivate Type ShortItemId
169*cdf0e10cSrcweir   cb As Long
170*cdf0e10cSrcweir   abID As Byte
171*cdf0e10cSrcweirEnd Type
172*cdf0e10cSrcweir
173*cdf0e10cSrcweirPrivate Type ITEMIDLIST
174*cdf0e10cSrcweir   mkid As ShortItemId
175*cdf0e10cSrcweirEnd Type
176*cdf0e10cSrcweir
177*cdf0e10cSrcweirPrivate Declare Function SHGetPathFromIDList Lib "shell32.dll" _
178*cdf0e10cSrcweir   (ByVal pidl As Long, ByVal pszPath As String) As Long
179*cdf0e10cSrcweir
180*cdf0e10cSrcweirPrivate Declare Function SHGetSpecialFolderLocation Lib _
181*cdf0e10cSrcweir   "shell32.dll" (ByVal hWndOwner As Long, ByVal nFolder _
182*cdf0e10cSrcweir   As Long, pidl As ITEMIDLIST) As Long
183*cdf0e10cSrcweir
184*cdf0e10cSrcweir
185*cdf0e10cSrcweirPublic Function IsWin98Plus() As Boolean
186*cdf0e10cSrcweir    'returns True if running Windows 2000 or later
187*cdf0e10cSrcweir    Dim osv As OSVERSIONINFO
188*cdf0e10cSrcweir
189*cdf0e10cSrcweir    osv.OSVSize = Len(osv)
190*cdf0e10cSrcweir
191*cdf0e10cSrcweir    If GetVersionEx(osv) = 1 Then
192*cdf0e10cSrcweir
193*cdf0e10cSrcweir       Select Case osv.PlatformID 'win 32
194*cdf0e10cSrcweir            Case VER_PLATFORM_WIN32s:
195*cdf0e10cSrcweir                IsWin98Plus = False
196*cdf0e10cSrcweir                Exit Function
197*cdf0e10cSrcweir            Case VER_PLATFORM_WIN32_NT: 'win nt, 2000, xp
198*cdf0e10cSrcweir                IsWin98Plus = True
199*cdf0e10cSrcweir                Exit Function
200*cdf0e10cSrcweir            Case VER_PLATFORM_WIN32_WINDOWS:
201*cdf0e10cSrcweir                Select Case osv.dwVerMinor
202*cdf0e10cSrcweir                    Case 0: 'win95
203*cdf0e10cSrcweir                        IsWin98Plus = False
204*cdf0e10cSrcweir                        Exit Function
205*cdf0e10cSrcweir                    Case 90:   'Windows ME
206*cdf0e10cSrcweir                        IsWin98Plus = True
207*cdf0e10cSrcweir                        Exit Function
208*cdf0e10cSrcweir                    Case 10:   ' Windows 98
209*cdf0e10cSrcweir                        If osv.dwBuildNumber >= 2222 Then 'second edition
210*cdf0e10cSrcweir                            IsWin98Plus = True
211*cdf0e10cSrcweir                            Exit Function
212*cdf0e10cSrcweir                        Else
213*cdf0e10cSrcweir                            IsWin98Plus = False
214*cdf0e10cSrcweir                            Exit Function
215*cdf0e10cSrcweir                        End If
216*cdf0e10cSrcweir                End Select
217*cdf0e10cSrcweir            Case Else
218*cdf0e10cSrcweir                IsWin98Plus = False
219*cdf0e10cSrcweir                Exit Function
220*cdf0e10cSrcweir      End Select
221*cdf0e10cSrcweir
222*cdf0e10cSrcweir    End If
223*cdf0e10cSrcweir
224*cdf0e10cSrcweirEnd Function
225*cdf0e10cSrcweir
226*cdf0e10cSrcweirPublic Function GetWinVersion(WIN As RGB_WINVER) As String
227*cdf0e10cSrcweir
228*cdf0e10cSrcweir'returns a structure (RGB_WINVER)
229*cdf0e10cSrcweir'filled with OS information
230*cdf0e10cSrcweir
231*cdf0e10cSrcweir  #If Win32 Then
232*cdf0e10cSrcweir
233*cdf0e10cSrcweir   Dim osv As OSVERSIONINFO
234*cdf0e10cSrcweir   Dim pos As Integer
235*cdf0e10cSrcweir   Dim sVer As String
236*cdf0e10cSrcweir   Dim sBuild As String
237*cdf0e10cSrcweir
238*cdf0e10cSrcweir   osv.OSVSize = Len(osv)
239*cdf0e10cSrcweir
240*cdf0e10cSrcweir   If GetVersionEx(osv) = 1 Then
241*cdf0e10cSrcweir
242*cdf0e10cSrcweir     'PlatformId contains a value representing the OS
243*cdf0e10cSrcweir      WIN.PlatformID = osv.PlatformID
244*cdf0e10cSrcweir
245*cdf0e10cSrcweir      Select Case osv.PlatformID
246*cdf0e10cSrcweir         Case VER_PLATFORM_WIN32s:   WIN.VersionName = "Win32s"
247*cdf0e10cSrcweir         Case VER_PLATFORM_WIN32_NT: WIN.VersionName = "Windows NT"
248*cdf0e10cSrcweir
249*cdf0e10cSrcweir         Select Case osv.dwVerMajor
250*cdf0e10cSrcweir            Case 4:  WIN.VersionName = "Windows NT"
251*cdf0e10cSrcweir            Case 5:
252*cdf0e10cSrcweir            Select Case osv.dwVerMinor
253*cdf0e10cSrcweir               Case 0:  WIN.VersionName = "Windows 2000"
254*cdf0e10cSrcweir               Case 1:  WIN.VersionName = "Windows XP"
255*cdf0e10cSrcweir            End Select
256*cdf0e10cSrcweir        End Select
257*cdf0e10cSrcweir
258*cdf0e10cSrcweir         Case VER_PLATFORM_WIN32_WINDOWS:
259*cdf0e10cSrcweir
260*cdf0e10cSrcweir          'The dwVerMinor bit tells if its 95 or 98.
261*cdf0e10cSrcweir            Select Case osv.dwVerMinor
262*cdf0e10cSrcweir               Case 0:    WIN.VersionName = "Windows 95"
263*cdf0e10cSrcweir               Case 90:   WIN.VersionName = "Windows ME"
264*cdf0e10cSrcweir               Case Else: WIN.VersionName = "Windows 98"
265*cdf0e10cSrcweir            End Select
266*cdf0e10cSrcweir
267*cdf0e10cSrcweir      End Select
268*cdf0e10cSrcweir
269*cdf0e10cSrcweir
270*cdf0e10cSrcweir     'Get the version number
271*cdf0e10cSrcweir      WIN.VersionNo = osv.dwVerMajor & "." & osv.dwVerMinor
272*cdf0e10cSrcweir
273*cdf0e10cSrcweir     'Get the build
274*cdf0e10cSrcweir      WIN.BuildNo = (osv.dwBuildNumber And &HFFFF&)
275*cdf0e10cSrcweir
276*cdf0e10cSrcweir     'Any additional info. In Win9x, this can be
277*cdf0e10cSrcweir     '"any arbitrary string" provided by the
278*cdf0e10cSrcweir     'manufacturer. In NT, this is the service pack.
279*cdf0e10cSrcweir      pos = InStr(osv.szCSDVersion, Chr$(0))
280*cdf0e10cSrcweir      If pos Then
281*cdf0e10cSrcweir         WIN.ServicePack = Left$(osv.szCSDVersion, pos - 1)
282*cdf0e10cSrcweir      End If
283*cdf0e10cSrcweir
284*cdf0e10cSrcweir   End If
285*cdf0e10cSrcweir
286*cdf0e10cSrcweir  #Else
287*cdf0e10cSrcweir
288*cdf0e10cSrcweir    'can only return that this does not
289*cdf0e10cSrcweir    'support the 32 bit call, so must be Win3x
290*cdf0e10cSrcweir     WIN.VersionName = "Windows 3.x"
291*cdf0e10cSrcweir  #End If
292*cdf0e10cSrcweir  GetWinVersion = WIN.VersionName
293*cdf0e10cSrcweir
294*cdf0e10cSrcweirEnd Function
295*cdf0e10cSrcweir
296*cdf0e10cSrcweirPublic Sub RunShellExecute(sTopic As String, _
297*cdf0e10cSrcweir                           sFile As Variant, _
298*cdf0e10cSrcweir                           sParams As Variant, _
299*cdf0e10cSrcweir                           sDirectory As Variant, _
300*cdf0e10cSrcweir                           nShowCmd As Long)
301*cdf0e10cSrcweir
302*cdf0e10cSrcweir   Dim hWndDesk As Long
303*cdf0e10cSrcweir   Dim success As Long
304*cdf0e10cSrcweir
305*cdf0e10cSrcweir  'the desktop will be the
306*cdf0e10cSrcweir  'default for error messages
307*cdf0e10cSrcweir   hWndDesk = GetDesktopWindow()
308*cdf0e10cSrcweir
309*cdf0e10cSrcweir  'execute the passed operation
310*cdf0e10cSrcweir   success = ShellExecute(hWndDesk, sTopic, sFile, sParams, sDirectory, nShowCmd)
311*cdf0e10cSrcweir
312*cdf0e10cSrcweir  'This is optional. Uncomment the three lines
313*cdf0e10cSrcweir  'below to have the "Open With.." dialog appear
314*cdf0e10cSrcweir  'when the ShellExecute API call fails
315*cdf0e10cSrcweir  If success = SE_ERR_NOASSOC Then
316*cdf0e10cSrcweir     Call Shell("rundll32.exe shell32.dll,OpenAs_RunDLL " & sFile, vbNormalFocus)
317*cdf0e10cSrcweir  End If
318*cdf0e10cSrcweir
319*cdf0e10cSrcweirEnd Sub
320*cdf0e10cSrcweir
321*cdf0e10cSrcweirPublic Sub WriteToLog(key As String, value As String, _
322*cdf0e10cSrcweir    Optional path As String = CNO_OPTIONAL_PARAM, _
323*cdf0e10cSrcweir    Optional section As String = WIZARD_NAME)
324*cdf0e10cSrcweir
325*cdf0e10cSrcweir    Static logFile As String
326*cdf0e10cSrcweir
327*cdf0e10cSrcweir    If logFile = "" Then
328*cdf0e10cSrcweir        logFile = GetLogFilePath
329*cdf0e10cSrcweir    End If
330*cdf0e10cSrcweir
331*cdf0e10cSrcweir    If path = "" Then
332*cdf0e10cSrcweir        Exit Sub
333*cdf0e10cSrcweir    End If
334*cdf0e10cSrcweir
335*cdf0e10cSrcweir    If path = CNO_OPTIONAL_PARAM Then
336*cdf0e10cSrcweir        path = logFile
337*cdf0e10cSrcweir    End If
338*cdf0e10cSrcweir    Call WritePrivateProfileString(section, key, value, path)
339*cdf0e10cSrcweirEnd Sub
340*cdf0e10cSrcweir
341*cdf0e10cSrcweirPublic Sub WriteDebug(value As String)
342*cdf0e10cSrcweir    Static ErrCount As Long
343*cdf0e10cSrcweir    Static logFile As String
344*cdf0e10cSrcweir    Static debugLevel As Long
345*cdf0e10cSrcweir
346*cdf0e10cSrcweir    If logFile = "" Then
347*cdf0e10cSrcweir        logFile = GetLogFilePath
348*cdf0e10cSrcweir    End If
349*cdf0e10cSrcweir
350*cdf0e10cSrcweir    Dim sSection As String
351*cdf0e10cSrcweir    sSection = WIZARD_NAME & "Debug"
352*cdf0e10cSrcweir
353*cdf0e10cSrcweir    Call WritePrivateProfileString(sSection, "Analysis" & "_debug" & ErrCount, _
354*cdf0e10cSrcweir        value, logFile)
355*cdf0e10cSrcweir    ErrCount = ErrCount + 1
356*cdf0e10cSrcweirEnd Sub
357*cdf0e10cSrcweir
358*cdf0e10cSrcweirPublic Function GetDebug(section As String, key As String) As String
359*cdf0e10cSrcweir    Static logFile As String
360*cdf0e10cSrcweir
361*cdf0e10cSrcweir    If logFile = "" Then
362*cdf0e10cSrcweir        logFile = GetLogFilePath
363*cdf0e10cSrcweir    End If
364*cdf0e10cSrcweir
365*cdf0e10cSrcweir    GetDebug = ProfileGetItem(section, key, "", logFile)
366*cdf0e10cSrcweirEnd Function
367*cdf0e10cSrcweir
368*cdf0e10cSrcweirPublic Function GetUserLocaleInfo(ByVal dwLocaleID As Long, ByVal dwLCType As Long) As String
369*cdf0e10cSrcweir
370*cdf0e10cSrcweir   Dim sReturn As String
371*cdf0e10cSrcweir   Dim r As Long
372*cdf0e10cSrcweir
373*cdf0e10cSrcweir  'call the function passing the Locale type
374*cdf0e10cSrcweir  'variable to retrieve the required size of
375*cdf0e10cSrcweir  'the string buffer needed
376*cdf0e10cSrcweir   r = GetLocaleInfo(dwLocaleID, dwLCType, sReturn, Len(sReturn))
377*cdf0e10cSrcweir
378*cdf0e10cSrcweir  'if successful..
379*cdf0e10cSrcweir   If r Then
380*cdf0e10cSrcweir
381*cdf0e10cSrcweir     'pad the buffer with spaces
382*cdf0e10cSrcweir      sReturn = Space$(r)
383*cdf0e10cSrcweir
384*cdf0e10cSrcweir     'and call again passing the buffer
385*cdf0e10cSrcweir      r = GetLocaleInfo(dwLocaleID, dwLCType, sReturn, Len(sReturn))
386*cdf0e10cSrcweir
387*cdf0e10cSrcweir     'if successful (r > 0)
388*cdf0e10cSrcweir      If r Then
389*cdf0e10cSrcweir
390*cdf0e10cSrcweir        'r holds the size of the string
391*cdf0e10cSrcweir        'including the terminating null
392*cdf0e10cSrcweir         GetUserLocaleInfo = Left$(sReturn, r - 1)
393*cdf0e10cSrcweir
394*cdf0e10cSrcweir      End If
395*cdf0e10cSrcweir
396*cdf0e10cSrcweir   End If
397*cdf0e10cSrcweir
398*cdf0e10cSrcweirEnd Function
399*cdf0e10cSrcweir
400*cdf0e10cSrcweirPublic Function GetRegistryInfo(sHive As String, sSubKey As String, sKey As String) As String
401*cdf0e10cSrcweir    GetRegistryInfo = ""
402*cdf0e10cSrcweir    Dim hKey As Long
403*cdf0e10cSrcweir
404*cdf0e10cSrcweir    hKey = OpenRegKey(sHive, sSubKey)
405*cdf0e10cSrcweir
406*cdf0e10cSrcweir    If hKey <> 0 Then
407*cdf0e10cSrcweir       GetRegistryInfo = GetRegValue(hKey, sKey)
408*cdf0e10cSrcweir
409*cdf0e10cSrcweir      'the opened key must be closed
410*cdf0e10cSrcweir       Call RegCloseKey(hKey)
411*cdf0e10cSrcweir    End If
412*cdf0e10cSrcweirEnd Function
413*cdf0e10cSrcweir
414*cdf0e10cSrcweir
415*cdf0e10cSrcweirPrivate Function GetRegValue(hSubKey As Long, sKeyName As String) As String
416*cdf0e10cSrcweir
417*cdf0e10cSrcweir   Dim lpValue As String   'value retrieved
418*cdf0e10cSrcweir   Dim lpcbData As Long    'length of retrieved string
419*cdf0e10cSrcweir
420*cdf0e10cSrcweir  'if valid
421*cdf0e10cSrcweir   If hSubKey <> 0 Then
422*cdf0e10cSrcweir
423*cdf0e10cSrcweir     'Pass an zero-length string to
424*cdf0e10cSrcweir     'obtain the required buffer size
425*cdf0e10cSrcweir     'required to return the result.
426*cdf0e10cSrcweir     'If the key passed exists, the call
427*cdf0e10cSrcweir     'will return error 234 (more data)
428*cdf0e10cSrcweir     'and lpcbData will indicate the
429*cdf0e10cSrcweir     'required buffer size (including
430*cdf0e10cSrcweir     'the terminating null).
431*cdf0e10cSrcweir      lpValue = ""
432*cdf0e10cSrcweir      lpcbData = 0
433*cdf0e10cSrcweir      If RegQueryValueEx(hSubKey, _
434*cdf0e10cSrcweir                         sKeyName, _
435*cdf0e10cSrcweir                         0&, _
436*cdf0e10cSrcweir                         0&, _
437*cdf0e10cSrcweir                         ByVal lpValue, _
438*cdf0e10cSrcweir                         lpcbData) = ERROR_MORE_DATA Then
439*cdf0e10cSrcweir
440*cdf0e10cSrcweir         lpValue = Space$(lpcbData)
441*cdf0e10cSrcweir
442*cdf0e10cSrcweir        'retrieve the desired value
443*cdf0e10cSrcweir         If RegQueryValueEx(hSubKey, _
444*cdf0e10cSrcweir                            sKeyName, _
445*cdf0e10cSrcweir                            0&, _
446*cdf0e10cSrcweir                            0&, _
447*cdf0e10cSrcweir                            ByVal lpValue, _
448*cdf0e10cSrcweir                            lpcbData) = ERROR_SUCCESS Then
449*cdf0e10cSrcweir
450*cdf0e10cSrcweir            GetRegValue = TrimNull(lpValue)
451*cdf0e10cSrcweir
452*cdf0e10cSrcweir         End If  'If RegQueryValueEx (second call)
453*cdf0e10cSrcweir      End If  'If RegQueryValueEx (first call)
454*cdf0e10cSrcweir   End If  'If hSubKey
455*cdf0e10cSrcweir
456*cdf0e10cSrcweirEnd Function
457*cdf0e10cSrcweir
458*cdf0e10cSrcweirPrivate Function OpenRegKey(ByVal hKey As Long, _
459*cdf0e10cSrcweir                            ByVal lpSubKey As String) As Long
460*cdf0e10cSrcweir    Dim hSubKey As Long
461*cdf0e10cSrcweir    Dim retval As Long
462*cdf0e10cSrcweir
463*cdf0e10cSrcweir    retval = RegOpenKeyEx(hKey, lpSubKey, _
464*cdf0e10cSrcweir                          0, KEY_READ, hSubKey)
465*cdf0e10cSrcweir
466*cdf0e10cSrcweir    If retval = ERROR_SUCCESS Then
467*cdf0e10cSrcweir        OpenRegKey = hSubKey
468*cdf0e10cSrcweir    End If
469*cdf0e10cSrcweirEnd Function
470*cdf0e10cSrcweir
471*cdf0e10cSrcweir
472*cdf0e10cSrcweirPrivate Function TrimNull(startstr As String) As String
473*cdf0e10cSrcweir
474*cdf0e10cSrcweir   TrimNull = Left$(startstr, lstrlenW(StrPtr(startstr)))
475*cdf0e10cSrcweir
476*cdf0e10cSrcweirEnd Function
477*cdf0e10cSrcweir
478*cdf0e10cSrcweirFunction GetLogFilePath() As String
479*cdf0e10cSrcweir
480*cdf0e10cSrcweir    Dim fso As New FileSystemObject
481*cdf0e10cSrcweir    Dim TempPath As String
482*cdf0e10cSrcweir
483*cdf0e10cSrcweir    TempPath = fso.GetSpecialFolder(TemporaryFolder).path
484*cdf0e10cSrcweir
485*cdf0e10cSrcweir    If (TempPath = "") Then
486*cdf0e10cSrcweir        TempPath = "."
487*cdf0e10cSrcweir    End If
488*cdf0e10cSrcweir
489*cdf0e10cSrcweir    GetLogFilePath = fso.GetAbsolutePathName(TempPath & "\" & CSTR_LOG_FILE_NAME)
490*cdf0e10cSrcweirEnd Function
491*cdf0e10cSrcweir
492*cdf0e10cSrcweirFunction GetIniFilePath() As String
493*cdf0e10cSrcweir
494*cdf0e10cSrcweir    Dim fso As New FileSystemObject
495*cdf0e10cSrcweir    Dim AppDataDir As String
496*cdf0e10cSrcweir
497*cdf0e10cSrcweir    AppDataDir = GetAppDataFolder
498*cdf0e10cSrcweir    If (AppDataDir = "") Then
499*cdf0e10cSrcweir        AppDataDir = CBASE_RESOURCE_DIR
500*cdf0e10cSrcweir    Else
501*cdf0e10cSrcweir        If Not fso.FolderExists(AppDataDir) Then
502*cdf0e10cSrcweir            fso.CreateFolder (AppDataDir)
503*cdf0e10cSrcweir        End If
504*cdf0e10cSrcweir        AppDataDir = AppDataDir & "\Sun"
505*cdf0e10cSrcweir        If Not fso.FolderExists(AppDataDir) Then
506*cdf0e10cSrcweir            fso.CreateFolder (AppDataDir)
507*cdf0e10cSrcweir        End If
508*cdf0e10cSrcweir        AppDataDir = AppDataDir & "\AnalysisWizard"
509*cdf0e10cSrcweir        If Not fso.FolderExists(AppDataDir) Then
510*cdf0e10cSrcweir            fso.CreateFolder (AppDataDir)
511*cdf0e10cSrcweir        End If
512*cdf0e10cSrcweir    End If
513*cdf0e10cSrcweir
514*cdf0e10cSrcweir    GetIniFilePath = fso.GetAbsolutePathName(AppDataDir & "\" & CANALYSIS_INI_FILE)
515*cdf0e10cSrcweirEnd Function
516*cdf0e10cSrcweir
517*cdf0e10cSrcweir' This function returns the Application Data Folder Path
518*cdf0e10cSrcweirFunction GetAppDataFolder() As String
519*cdf0e10cSrcweir   Dim idlstr As Long
520*cdf0e10cSrcweir   Dim sPath As String
521*cdf0e10cSrcweir   Dim IDL As ITEMIDLIST
522*cdf0e10cSrcweir   Const NOERROR = 0
523*cdf0e10cSrcweir   Const MAX_LENGTH = 260
524*cdf0e10cSrcweir   Const CSIDL_APPDATA = &H1A
525*cdf0e10cSrcweir
526*cdf0e10cSrcweir   On Error GoTo Err_GetFolder
527*cdf0e10cSrcweir
528*cdf0e10cSrcweir   ' Fill the idl structure with the specified folder item.
529*cdf0e10cSrcweir   idlstr = SHGetSpecialFolderLocation(0, CSIDL_APPDATA, IDL)
530*cdf0e10cSrcweir
531*cdf0e10cSrcweir   If idlstr = NOERROR Then
532*cdf0e10cSrcweir       ' Get the path from the idl list, and return
533*cdf0e10cSrcweir       ' the folder with a slash at the end.
534*cdf0e10cSrcweir       sPath = Space$(MAX_LENGTH)
535*cdf0e10cSrcweir       idlstr = SHGetPathFromIDList(ByVal IDL.mkid.cb, ByVal sPath)
536*cdf0e10cSrcweir       If idlstr Then
537*cdf0e10cSrcweir           GetAppDataFolder = Left$(sPath, InStr(sPath, Chr$(0)) - 1)
538*cdf0e10cSrcweir       End If
539*cdf0e10cSrcweir   End If
540*cdf0e10cSrcweir
541*cdf0e10cSrcweirExit_GetFolder:
542*cdf0e10cSrcweir    Exit Function
543*cdf0e10cSrcweir
544*cdf0e10cSrcweirErr_GetFolder:
545*cdf0e10cSrcweir   MsgBox "An Error was Encountered" & Chr(13) & Err.Description, _
546*cdf0e10cSrcweir      vbCritical Or vbOKOnly
547*cdf0e10cSrcweir   Resume Exit_GetFolder
548*cdf0e10cSrcweir
549*cdf0e10cSrcweirEnd Function
550*cdf0e10cSrcweir
551*cdf0e10cSrcweir
552*cdf0e10cSrcweir
553