Visual Basic Locale/Regionalization Routines
Identifying Time Zones Using the Time Zone Bias
     
Posted:   Monday July 08, 2002
Updated:   Monday December 26, 2011
     
Applies to:   VB4-32, VB5, VB6
Developed with:   VB6, Windows XP Pro
OS restrictions:   None
Author:   VBnet - Randy Birch
     

Related:  

WM_TIMECHANGE: Detect System Changes to the Date/Time
RegQueryValueEx: Determine Windows Last Shutdown Date and Time
RegQueryValueEx: Identify Time Zones by Time Zone Bias
EnumDateFormats: Regional Locale Date Settings
EnumTimeFormats: Regional Locale Time Settings
GetLocaleInfo: Regional Locale Date Settings
     
 Prerequisites
None.

I received an interesting request for time zone information. The code at SetSystemTime: Date and Time Synchronization to a Remote Server shows how to retrieve a remote server's TIME_OF_DAY_INFO, and how to synchronize machines to a remote server. One member of the TIME_OF_DAY_INFO structure is tod_timezone ... the Bias from GMT for the remote server. The request was for a means to take this time and determine what the actual time zone was for the server.

After scanning the MSDN there appeared no direct way to pass a Bias and have the system return the zones currently represented by that bias. So using a few registry reads, a custom UDT for the data, and a simple UDT array lookup loop I was able to construct the code that would (somewhat) satisfy the request.

The primary issue that can not be resolved with just the GMT bias is that of multiple time zones each having the same Bias. As the demo shows, for a Bias of 240 minutes during daylight saving time there are three different time zones that satisfy the Bias ... Eastern Standard Time, SA Pacific Standard Time and US Eastern Standard Time.

The code is straight forward: the initial routine checks the operating system version and in order to determine the correct registry key to read. It then checks and sets a flag indicating whether, according to the settings of the local machine, the machine is currently in "Daylight Saving Time mode".  This information is used because on the local machine, the Bias minutes returned from the registry in the REG_TIME_ZONE_INFORMATION's Bias member represents the Standard Time bias from GMT, yet the data returned from the synchronization TIME_OF_DAY_INFO always reflects the current system Bias which changes depending on whether Standard or Daylight time is currently in force. For example, if a local machine in England is in standard time and a machine in Ontario was queried using the code from SetSystemTime: Date and Time Synchronization to a Remote Server, the Bias returned as tod_timezone for the Ontario machine would be 300 (5 hours). This is the same data returned as the REG_TIME_ZONE_INFORMATION's Bias member in this demo. But, when the local machine is in Daylight Saving Time, the remote Ontario machine returns 240 (4 hours). Thus attempting to compare the tod_timezone with the Bias member without taking DST into account would return the wrong set of time zones when DST was in force. Therefore, the demo determines if the local machine is running on DST, and if so applies the REG_TIME_ZONE_INFORMATION's DaylightBias to the base Bias. Thus the 240 minute Bias for Ontario during DST is correctly  reflected as the registry's Eastern Standard Time member. However, there is a caveat. Depending on the location of the machine on the WAN, the local machine's Standard/Daylight changeover dates may not necessarily be the same as the distant WAN server (ie someone reported that Australia changeover dates are a week different than North America's). Therefore, although this code can provide the correct time zone when both the local and remote machine's are both in either Standard or Daylight times, judicious use of the method is required to ensure the code is not used during the period one machine has changed over and the other has not.

You may also notice that, even though the current time setting was Daylight Saving Time when this demo was created, the names returned from the code below are all stating Standard Time. If it is DST in Ontario, one would think the string returned from the registry should be "Eastern Daylight Saving Time", not "Eastern Standard Time" as shown. This naming anomaly is due to the way the strings are stored in the registry ... all registry time zone primary keys - the ones enumerated and listed above - contain the phrase "Standard Time" (look in the registry under HKEY_LOCAL_MACHINE and the keys listed as constants in the code below). Under each set of time zone keys is a DLT subkey which contains the actual name of the Daylight Saving time for each time zone.

I had initially thought of leaving the end user to apply a simple Replace() call when the IsDaylightSavingTime flag was set, to change "Standard" to "Daylight", but on examination of a few registry keys I found at least one "Daylight Saving" name that did not parallel the "Standard Time" name. While "Eastern Standard Time" becomes "Eastern Daylight Time", interestingly (according to the registry) "Israel Standard Time" becomes "Jerusalem Daylight Time". Now, if Israelis could live with "Israel Daylight Time", then performing a Replace() easily takes care of assuring the names reflect DST if required. But where precision is the order of the day, I leave to you, the user, the task of retrieving the proper Daylight Time string from the registry should it actually be required.

 BAS Module Code
None.

 Form Code
Add a label (Label1) to hold the return value representing the Bias time, a command button (Command1) a text box (Text1)  and two lists (List1, List2) to a form. Other labels are optional. Add the following code:

Option Explicit
''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
' Copyright ©1996-2011 VBnet/Randy Birch, All Rights Reserved.
' Some pages may also contain other copyrights by the author.
''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
' Distribution: You can freely use this code in your own
'               applications, but you may not reproduce 
'               or publish this code on any web site,
'               online service, or distribute as source 
'               on any media without express permission.
''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
'IsDaylightSavingTime flag
Private BiasAdjust As Boolean

' results UDT
Private Type TZ_LOOKUP_DATA
   TimeZoneName As String
   Bias As Long
   IsDST As Boolean
End Type

Private tzinfo() As TZ_LOOKUP_DATA

'holds the correct key for the OS version
Private sTzKey As String

'windows constants and declares
Private Const TIME_ZONE_ID_UNKNOWN As Long = 1
Private Const TIME_ZONE_ID_STANDARD As Long = 1
Private Const TIME_ZONE_ID_DAYLIGHT As Long = 2
Private Const TIME_ZONE_ID_INVALID As Long = &HFFFFFFFF
Private Const VER_PLATFORM_WIN32_NT = 2
Private Const VER_PLATFORM_WIN32_WINDOWS = 1

'registry constants
Private Const SKEY_NT = "SOFTWARE\Microsoft\Windows NT\CurrentVersion\Time Zones"
Private Const SKEY_9X = "SOFTWARE\Microsoft\Windows\CurrentVersion\Time Zones"
Private Const HKEY_LOCAL_MACHINE = &H80000002
Private Const ERROR_SUCCESS = 0
Private Const REG_SZ As Long = 1
Private Const REG_BINARY = 3
Private Const REG_DWORD As Long = 4
Private Const STANDARD_RIGHTS_READ As Long = &H20000
Private Const KEY_QUERY_VALUE As Long = &H1
Private Const KEY_ENUMERATE_SUB_KEYS As Long = &H8
Private Const KEY_NOTIFY As Long = &H10
Private Const SYNCHRONIZE As Long = &H100000
Private Const KEY_READ As Long = ((STANDARD_RIGHTS_READ Or _
                                   KEY_QUERY_VALUE Or _
                                   KEY_ENUMERATE_SUB_KEYS Or _
                                   KEY_NOTIFY) And _
                                   (Not SYNCHRONIZE))

Private Type SYSTEMTIME
   wYear As Integer
   wMonth As Integer
   wDayOfWeek As Integer
   wDay As Integer
   wHour As Integer
   wMinute As Integer
   wSecond As Integer
   wMilliseconds As Integer
End Type

Private Type FILETIME 
   dwLowDateTime As Long
   dwHighDateTime As Long
End Type

Private Type REG_TIME_ZONE_INFORMATION
   Bias As Long
   StandardBias As Long
   DaylightBias As Long
   StandardDate As SYSTEMTIME
   DaylightDate As SYSTEMTIME
End Type

Private Type TIME_ZONE_INFORMATION
   Bias As Long
   StandardName(0 To 63) As Byte
   StandardDate As SYSTEMTIME
   StandardBias As Long
   DaylightName(0 To 63) As Byte
   DaylightDate As SYSTEMTIME
   DaylightBias As Long
End Type

Private Type OSVERSIONINFO
   OSVSize As Long
   dwVerMajor As Long
   dwVerMinor As Long
   dwBuildNumber As Long
   PlatformID As Long
   szCSDVersion As String * 128
End Type

Private Declare Function GetVersionEx Lib "kernel32" _
   Alias "GetVersionExA" _
  (lpVersionInformation As OSVERSIONINFO) As Long

Private Declare Function GetTimeZoneInformation Lib "kernel32" _
   (lpTimeZoneInformation As TIME_ZONE_INFORMATION) As Long

Private Declare Function RegOpenKeyEx Lib "advapi32.dll" _
   Alias "RegOpenKeyExA" _
  (ByVal hKey As Long, _
   ByVal lpsSubKey As String, _
   ByVal ulOptions As Long, _
   ByVal samDesired As Long, _
   phkResult As Long) As Long

Private Declare Function RegQueryValueEx Lib "advapi32.dll" _
   Alias "RegQueryValueExA" _
  (ByVal hKey As Long, _
   ByVal lpszValueName As String, _
   ByVal lpdwReserved As Long, _
   lpdwType As Long, _
   lpData As Any, _
   lpcbData As Long) As Long

Private Declare Function RegQueryInfoKey Lib "advapi32.dll" _
   Alias "RegQueryInfoKeyA" _
  (ByVal hKey As Long, _
   ByVal lpClass As String, _
   lpcbClass As Long, _
   ByVal lpReserved As Long, _
   lpcsSubKeys As Long, _
   lpcbMaxsSubKeyLen As Long, _
   lpcbMaxClassLen As Long, _
   lpcValues As Long, _
   lpcbMaxValueNameLen As Long, _
   lpcbMaxValueLen As Long, _
   lpcbSecurityDescriptor As Long, _
   lpftLastWriteTime As FILETIME) As Long
   
Private Declare Function RegQueryValueExString Lib "advapi32.dll" _
   Alias "RegQueryValueExA" _
  (ByVal hKey As Long, _
   ByVal lpValueName As String, _
   ByVal lpReserved As Long, _
   lpType As Long, _
   ByVal lpData As String, _
   lpcbData As Long) As Long

Private Declare Function RegEnumKey Lib "advapi32.dll" _
   Alias "RegEnumKeyA" _
  (ByVal hKey As Long, _
   ByVal dwIndex As Long, _
   ByVal lpName As String, _
   ByVal cbName As Long) As Long

Private Declare Function RegCloseKey Lib "advapi32.dll" _
  (ByVal hKey As Long) As Long

Private Declare Function lstrlenW Lib "kernel32" _
  (ByVal lpString As Long) As Long



Private Sub Form_Load()

   With Command1
      .Caption = "Load TZ Array"
      .Enabled = True
   End With
   
   With Command2
      .Caption = "Lookup Time Zone"
      .Enabled = False
   End With
   
   With Text1
      .Text = -120
   End With
   
   BiasAdjust = IsDaylightSavingTime()
   
   With Label1
      
      If BiasAdjust Then
         .Caption = "(Bias shown is for Daylight Saving Time)"
      Else
         .Caption = "(Bias shown is for Standard Time)"
      End If
   
   End With
   
End Sub


Private Sub Command1_Click()

  'enable the lookup key if
  'results returned 
   Command2.Enabled = GetTimeZoneArray()

End Sub


Private Sub Command2_Click()

   Dim cnt As Long
   
  'do a lookup for the Bias entered 
   With List2
      .Clear
      
      For cnt = LBound(tzinfo) To UBound(tzinfo)
      
         If tzinfo(cnt).Bias = Text1.Text Then
            
            .AddItem tzinfo(cnt).TimeZoneName
            Debug.Print tzinfo(cnt).TimeZoneName
         End If
         
      Next
      
   End With
End Sub


Private Sub List1_Click()

   Dim pos As Long
   
  'on a list click, show the Bias in the 
  'textbox to make lookups easier
   If List1.ListIndex > -1 Then
   
      pos = InStr(List1.List(List1.ListIndex), vbTab)
      Text1.Text = Left$(List1.List(List1.ListIndex), pos - 1)
   
   End If
   
End Sub


Private Function GetTimeZoneArray() As Boolean

   Dim success As Long
   Dim dwIndex As Long
   Dim cbName As Long
   Dim hKey As Long
   Dim sName As String
   Dim dwSubKeys As Long
   Dim dwMaxSubKeyLen As Long
   Dim ft As FILETIME

  'Win9x and WinNT have a slightly
  'different registry structure.
  'Determine the operating system and
  'set a module variable to the
  'correct key.
  
  'assume OS is win9x
   sTzKey = SKEY_9X
   
  'see if OS is NT, and if so,
  'use assign the correct key
   If IsWinNTPlus Then sTzKey = SKEY_NT
   
  'BiasAdjust is used when calculating the
  'bias values retrieved from the registry.
  'If True, the reg value retrieved represents
  'the location's bias with the bias for
  'daylight saving time added. If false, the
  'location's bias is returned with the
  'standard bias adjustment applied (this
  'is usually 0). Doing this allows us to
  'use the bias returned from a TIME_OF_DAY_INFO
  'call as the correct lookup value dependant
  'on whether the world is currently on
  'daylight saving time or not. For those
  'countries not recognizing daylight saving
  'time, the registry daylight bias will be 0,
  'therefore proper lookup will not be affected.
  'Not considered (nor can such be coded) are those
  'special areas within a given country that do
  'not recognize daylight saving time, even
  'when the rest of the country does (like
  'Saskatchewan in Canada).
   BiasAdjust = IsDaylightSavingTime()

  'open the timezone registry key
   hKey = OpenRegKey(HKEY_LOCAL_MACHINE, sTzKey)
   
   If hKey <> 0 Then
   
     'query registry for the number of
     'entries under that key
      If RegQueryInfoKey(hKey, _
                         0&, _
                         0&, _
                         0, _
                         dwSubKeys, _
                         dwMaxSubKeyLen&, _
                         0&, _
                         0&, _
                         0&, _
                         0&, _
                         0&, _
                         ft) = ERROR_SUCCESS Then
   
   
        'create a UDT array for the time zone info
         ReDim tzinfo(0 To dwSubKeys - 1) As TZ_LOOKUP_DATA
         
         dwIndex = 0
         cbName = 32
   
         Do
         
           'pad a string for the returned value
            sName = Space$(cbName)
            success = RegEnumKey(hKey, dwIndex, sName, cbName)
            
            If success = ERROR_SUCCESS Then
            
              'add the data to the appropriate
              'tzinfo UDT array members
               With tzinfo(dwIndex)
               
                  .TimeZoneName = TrimNull(sName)
                  .Bias = GetTZBiasByName(.TimeZoneName)
                  .IsDST = BiasAdjust
                  
                 'for demo purposes only, the data
                 'is also added to a list                 
                  List1.AddItem .Bias & vbTab & .TimeZoneName
                  
               End With
               
            End If
   
           'increment the loop...
            dwIndex = dwIndex + 1
            
        '...and continue while the reg
        'call returns success.
         Loop While success = ERROR_SUCCESS

        'clean up
         RegCloseKey hKey
         
        'return success if, well, successful
         GetTimeZoneArray = dwIndex > 0

      End If  'If RegQueryInfoKey
   
   Else
      
     'could not open reg key
      GetTimeZoneArray = False
   
   End If  'If hKey

End Function


Private Function IsDaylightSavingTime() As Boolean

   Dim tzi As TIME_ZONE_INFORMATION

   IsDaylightSavingTime = GetTimeZoneInformation(tzi) = TIME_ZONE_ID_DAYLIGHT

End Function


Private Function GetTZBiasByName(sTimeZone As String) As Long

   Dim rtzi As REG_TIME_ZONE_INFORMATION
   Dim hKey As Long

  'open the passed time zone key 
   hKey = OpenRegKey(HKEY_LOCAL_MACHINE, sTzKey & "\" & sTimeZone)
   
   If hKey <> 0 Then
   
     'obtain the data from the TZI member 
      If RegQueryValueEx(hKey, _
                         "TZI", _
                         0&, _
                         ByVal 0&, _
                         rtzi, _
                         Len(rtzi)) = ERROR_SUCCESS Then

        'tweak the Bias when in Daylight Saving time 
         If BiasAdjust Then
            GetTZBiasByName = (rtzi.Bias + rtzi.DaylightBias)
         Else
            GetTZBiasByName = (rtzi.Bias + rtzi.StandardBias) 'StandardBias is usually 0
         End If

      End If

      RegCloseKey hKey
      
   End If
   
End Function


Private Function TrimNull(startstr As String) As String

   TrimNull = Left$(startstr, lstrlenW(StrPtr(startstr)))
   
End Function


Private Function OpenRegKey(ByVal hKey As Long, _
                            ByVal lpSubKey As String) As Long

  Dim hSubKey As Long

  If RegOpenKeyEx(hKey, _
                  lpSubKey, _
                  0, _
                  KEY_READ, _
                  hSubKey) = ERROR_SUCCESS Then

      OpenRegKey = hSubKey

  End If

End Function


Private Function IsWinNTPlus() As Boolean

   'returns True if running WinNT or better
   #If Win32 Then
  
      Dim OSV As OSVERSIONINFO
   
      OSV.OSVSize = Len(OSV)
   
      If GetVersionEx(OSV) = 1 Then
   
         IsWinNTPlus = (OSV.PlatformID = VER_PLATFORM_WIN32_NT)
         
      End If

   #End If

End Function

 
 

PayPal Link
Make payments with PayPal - it's fast, free and secure!

 
 
 
 

Copyright ©1996-2011 VBnet and Randy Birch. All Rights Reserved.
Terms of Use  |  Your Privacy

 

Hit Counter