Editor's Choice: This article has been selected by our editors as an exceptional contribution.

Time Zones, Windows, and VBA - Part 1

Gustav BrockMVP
CERTIFIED EXPERT
Published:
Updated:
Edited by: Andrew Leniart
Obtaining and using time zones in Windows is not simple. It involves API calls and reading the Registry. Some information is localised, and some is not. Here you will find a complete set of functions that wraps the difficult steps, eases common tasks, and helps when designing user interfaces.

This is the first article about maximising the usage of time zones in Windows with Microsoft Access and Excel.
The second covers how to store, present, and select time zones:
Time Zones, Windows, and Microsoft Office - Part 2


Time Zones are not science


Even though time zones as such origin from the astronomical fact, that the Earth is spinning, time zones are not purely defined by science, math, or coordinates but are often a result of political decisions. Take, for example, daylight saving time or the date line that zigzags its way down the Pacific Ocean because some small countries adjacent the true date line have decided to belong to another time zone to "stay ahead" of the other countries. In 1940, Spain decided to move to the Central European Time time zone even though the country lines up with the United Kingdom.


It would be nice and convenient if the time zone of a location could be calculated directly from its coordinates. That is not so and, even worse, the time zone may change over time. Therefore, it is necessary to track the changes and record these to be able to obtain the time zone of a location at a given time. 

For the IT industry, this is taken care of by IANA, which maintains a database, IANA Time Zone Database, holding all information about past and planned future changes of time zones and their locations. Due to its nature, however, this database is not just a set of tables you can look up; to query this vast database, special tools are needed. 


This will be discussed in a later article. Here, in these two articles, we will focus on maximising the information you can retrieve directly from Windows.


Time Zones in Windows


To be honest, time zones in Windows is a mess. Some information requires API calls, most are located in the Registry, and some of this is localised, while some are not.

This is caused by the evolution of Windows. In DOS and the first Windows versions, no one had time zones in mind. Later, the demand grew and, little by little, Windows' support for time zones improved. Currently, Windows knows about all time zones and their current settings for Daylight Saving Time. Historical and future information is, however, minimal and inconsistent.


Nevertheless, as the major demand for time zone information regards the current date and time around the globe, the information ready at hand in Windows is often exactly what is needed for many applications.

However - and partly because of the mentioned drawbacks - the published code related to time zones in Windows is fragmented or focused on a single task or just the necessary.


Thus, it is relevant to walk through how the complete information can be retrieved and utilised in a simple, fast, and consistent way.


The basics


At first, a set of UDTs (User Defined Type) are needed to transport the convoluted information about the time zones:


' User defined types.
'
    Public 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


    Public Type RegTziFormat
        Bias                            As Long
        StandardBias                    As Long
        DaylightBias                    As Long
        StandardDate                    As SystemTime
        DaylightDate                    As SystemTime
    End Type
   
    Public Type TimezoneEntry
        Mui                             As Integer
        MuiDaylight                     As Integer
        MuiStandard                     As Integer
        Bias                            As Integer
        Name                            As String
        Utc                             As String
        Locations                       As String
        ZoneDaylight                    As String
        ZoneStandard                    As String
        FirstEntry                      As Variant
        LastEntry                       As Variant
        Tzi                             As RegTziFormat
    End Type

    ' TimezoneInformation holds information about a timezone.
    ' The two arrays are null-terminated strings, where each element
    ' holds the byte code for a character, and the last element is a
    ' null value, ASCII code 0.
    Public Type TimezoneInformation
        Bias                            As Long
        StandardName(0 To (32 * 2 - 1)) As Byte     ' Unicode.
        StandardDate                    As SystemTime
        StandardBias                    As Long
        DaylightName(0 To (32 * 2 - 1)) As Byte     ' Unicode.
        DaylightDate                    As SystemTime
        DaylightBias                    As Long
    End Type

Second, two API calls are available for very basic usage:


' Declarations.

' Returns the current UTC time.
Private Declare PtrSafe Sub GetSystemTime Lib "kernel32" ( _
    ByRef lpSystemTime As SystemTime)
   
' Retrieves the current timezone settings from Windows.
Private Declare PtrSafe Function GetTimezoneInformation Lib "Kernel32.dll" Alias "GetTimeZoneInformation" ( _
    ByRef lpTimezoneInformation As TimezoneInformation) _
    As Long

Having these, we can retrieve some basic information. 


The first API call is used here to return the UTC time - the time zone all time zones relate to. All variations are covered - date, time, and now (date and time combined) - as they each have their usages:


' Retrieves the current date from the local computer as UTC.
' Resolution is one day to mimic Date().
'
' 2016-06-09. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function UtcDate() As Date

    Dim SysTime     As SystemTime
    Dim Datetime    As Date
   
    ' Retrieve current UTC date.
    GetSystemTime SysTime
   
    Datetime = DateSerial(SysTime.wYear, SysTime.wMonth, SysTime.wDay)
   
    UtcDate = Datetime
   
End Function


' Retrieves the current time from the local computer as UTC.
' By cutting off the milliseconds, the resolution is one second to mimic Time().
'
' 2016-06-09. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function UtcTime() As Date

    Dim SysTime     As SystemTime
    Dim Datetime    As Date
   
    ' Retrieve current UTC time.
    GetSystemTime SysTime
   
    Datetime = TimeSerial(SysTime.wHour, SysTime.wMinute, SysTime.wSecond)
   
    UtcTime = Datetime
   
End Function


' Retrieves the current date and time from the local computer as UTC.
' By cutting off the milliseconds, the resolution is one second to mimic Now().
'
' 2016-06-09. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function UtcNow() As Date

    Dim SysTime     As SystemTime
    Dim Datetime    As Date
   
    ' Retrieve current UTC date/time.
    GetSystemTime SysTime
   
    Datetime = _
        DateSerial(SysTime.wYear, SysTime.wMonth, SysTime.wDay) + _
        TimeSerial(SysTime.wHour, SysTime.wMinute, SysTime.wSecond)
   
    UtcNow = Datetime
   
End Function

The second API returns the current properties of the local time zone.

One of these is the Windows labelling of the local time zone:


' Returns the localised friendly description of the current timezone.
'
' 2016-06-09. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function LocalTimezoneDescription() As String

    Dim TzInfo      As TimezoneInformation
    Dim Description As String
   
    Select Case GetTimezoneInformation(TzInfo)
        Case TimezoneId.Unknown
            Description = "Cannot determine current timezone"
        Case TimezoneId.Standard
            Description = TzInfo.StandardName
        Case TimezoneId.Daylight
            Description = TzInfo.DaylightName
        Case TimezoneId.Invalid
            Description = "Invalid current timezone"
    End Select
   
    LocalTimezoneDescription = Split(Description, vbNullChar)(0)
   
End Function

The output will be like: Rom, normaltid

You might have hoped this to be the widely used abbreviations - like CET, EST, etc. - but that is not the case. This kind (or level) of information is not stored in Windows.


Of more practical use, are the parameters for the bias, which can be defined like this:

The difference in minutes between UTC time and local time.
The calculation method is: UTC time = local time + Bias

What's important here, is, that the parameters don't define the current bias (Daylight Saving Time or Standard Time) but how this is to be calculated for some date.

So, for this date, the first step is to find out if this falls within the range of Daylight Saving Time. The function IsCurrentDaylightSavingTime and its helper function DateWeekdayInMonth will do that:


' Returns True if the passed date/time value is within the local Daylight Saving Time
' period as defined by the rules for the current year.
'
' Note:
' For a value of the transition interval from daylight time back to standard time,
' where the value could belong to either of these, daylight time is assumed.
' This means that a standard time of the transition interval will return True.
'
' Limitation:
' For dates outside the current year, the same rules as for the current year are used,
' thus the returned result will follow a rule that could be true only for recent or
' near future years relative to the current year.
'
' 2016-06-09. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function IsCurrentDaylightSavingTime( _
    Optional ByVal Date1 As Date) _
    As Boolean
   
    Dim TzInfo          As TimezoneInformation
    Dim Dst             As Boolean
    Dim TzId            As TimezoneId
    Dim DaylightDate    As Date
    Dim StandardDate    As Date
    Dim Year            As Integer
   
    TzId = GetTimezoneInformation(TzInfo)
    If Date1 = ZeroDateValue Or Date1 = Date Then
        ' GetTimezoneInformation returns the timezone ID for the current date.
        Dst = (TzId = TimezoneId.Daylight)
    Else
        ' Calculate DaylightDate starting date and standard starting date for Year.
        ' wDay is the occurrence of the weekday in the month. 5 is the last occurrence.
        Year = VBA.Year(Date1)
        DaylightDate = _
            DateWeekdayInMonth(DateSerial(Year, TzInfo.DaylightDate.wMonth, 1), TzInfo.DaylightDate.wDay, vbSunday) + _
            TimeSerial(TzInfo.DaylightDate.wHour, TzInfo.DaylightDate.wMinute, TzInfo.DaylightDate.wSecond)
        StandardDate = _
            DateWeekdayInMonth(DateSerial(Year, TzInfo.StandardDate.wMonth, 1), TzInfo.StandardDate.wDay, vbSunday) + _
            TimeSerial(TzInfo.StandardDate.wHour, TzInfo.StandardDate.wMinute, TzInfo.StandardDate.wSecond)
           
        ' Check if Date1 falls within the period of Daylight Saving Time for Year.
        If DaylightDate < StandardDate Then
            ' Northern hemisphere.
            If DateDiff("s", DaylightDate, Date1) >= 0 And DateDiff("s", Date1, StandardDate) > 0 Then
                Dst = True
            End If
        Else
            ' Southern hemisphere.
            If DateDiff("s", StandardDate, Date1) >= 0 And DateDiff("s", Date1, DaylightDate) > 0 Then
                Dst = True
            End If
        End If
    End If
   
    IsCurrentDaylightSavingTime = Dst
 
End Function



' Calculates the date of the occurrence of Weekday in the month of DateInMonth.
'
' If Occurrence is 0 or negative, the first occurrence of Weekday in the month is assumed.
' If Occurrence is 5 or larger, the last occurrence of Weekday in the month is assumed.
'
' If Weekday is invalid or not specified, the weekday of DateInMonth is used.
'
' 2019-12-08. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function DateWeekdayInMonth( _
    ByVal DateInMonth As Date, _
    Optional ByVal Occurrence As Integer, _
    Optional ByVal Weekday As VbDayOfWeek = vbUseSystemDayOfWeek) _
    As Date
   
    Dim Offset          As Integer
    Dim Month           As Integer
    Dim Year            As Integer
    Dim ResultDate      As Date
   
    ' Validate Weekday.
    Select Case Weekday
        Case _
            vbMonday, _
            vbTuesday, _
            vbWednesday, _
            vbThursday, _
            vbFriday, _
            vbSaturday, _
            vbSunday
        Case Else
            ' vbUseSystemDayOfWeek, zero, none or invalid value for VbDayOfWeek.
            Weekday = VBA.Weekday(DateInMonth)
    End Select
   
    ' Validate Occurence.
    If Occurrence < 1 Then
        ' Find first occurrence.
        Occurrence = 1
    ElseIf Occurrence > MaxWeekdayCountInMonth Then
        ' Find last occurrence.
        Occurrence = MaxWeekdayCountInMonth
    End If
   
    ' Start date.
    Month = VBA.Month(DateInMonth)
    Year = VBA.Year(DateInMonth)
    ResultDate = DateSerial(Year, Month, 1)
   
    ' Find offset of Weekday from first day of month.
    Offset = DaysPerWeek * (Occurrence - 1) + (Weekday - VBA.Weekday(ResultDate) + DaysPerWeek) Mod DaysPerWeek
    ' Calculate result date.
    ResultDate = DateAdd("d", Offset, ResultDate)
   
    If Occurrence = MaxWeekdayCountInMonth Then
        ' The latest occurrency of Weekday is requested.
        ' Check if there really is a fifth occurrence of Weekday in this month.
        If VBA.Month(ResultDate) <> Month Then
            ' There are only four occurrencies of Weekday in this month.
            ' Return the fourth as the latest.
            ResultDate = DateAdd("d", -DaysPerWeek, ResultDate)
        End If
    End If
   
    DateWeekdayInMonth = ResultDate
 
End Function

The next step - to determine the bias of the date - now becomes easy:


' Returns the timezone bias of the current date or, using the current rules,
' for another present date.
' If IgnoreDaylightSetting is True, the returned bias will not include a local
' daylight saving time bias.
'
' 2016-06-09. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function LocalBiasTimezonePresent( _
    ByVal Date1 As Date, _
    Optional ByVal IgnoreDaylightSetting As Boolean) _
    As Long

    Dim TzInfo  As TimezoneInformation
    Dim TzId    As TimezoneId
    Dim Bias    As Long
   
    TzId = GetTimezoneInformation(TzInfo)
   
    Select Case TzId
        Case TimezoneId.Standard, TimezoneId.Daylight
            Bias = TzInfo.Bias
            If IgnoreDaylightSetting = False Then
                If IsCurrentDaylightSavingTime(Date1) = True Then
                    Bias = Bias + TzInfo.DaylightBias
                End If
            End If
    End Select
   
    LocalBiasTimezonePresent = Bias
     
End Function

So, to find the local bias of today in Copenhagen if the date is in February or early October:


Bias = LocalBiasTimezonePresent(#2020-02-10#)
Bias -> -60

Bias = LocalBiasTimezonePresent(#2020-10-02#)
Bias -> -120

What's important here is, that - for any historical date passed - the bias will be calculated using the current parameters, not the parameters that were in force at that date and might be different from the current parameters. Likewise, the bias of a future date may change as the parameters may be changed before that date is reached.


To summarize - this function fits well for current business use, but will be less and less reliable the more decades older the passed date is.


Time Zones of the World


So far we have no information about time zones other than the local. To obtain information about other time zones, the Registry must be queried, which is not an easy task, as the data is distributed in layers of keys and subkeys.


To streamline the task, one core function, GetRegistryTimezoneItems, is used to retrieve all information for one year in one go. 

This is a bit of a "parsing exercise" as you will see. It has been made Private, as it on its own isn't very useful, as it returns an array of time zone items which also holds arrays. Because of this, it is supported by several wrapping functions that, for all practical purposes, will return what is useful in typical scenarios where you need data about time zones.

Notice the in-line comments that explain the many steps:


' Required references:
'   Windows Script Host Object Model
'
' 2019-12-14. Gustav Brock, Cactus Data ApS, CPH.
'
Private Function GetRegistryTimezoneItems( _
    Optional ByRef DynamicDstYear As Integer) _
    As TimezoneEntry()

    Const Component     As String = "winmgmts:{impersonationLevel=impersonate}!\\.\root\default:StdRegProv"
    Const DefKey        As Long = HKeyLocalMachine
    Const HKey          As String = "HKLM"
    Const SubKeyPath    As String = "SOFTWARE\Microsoft\Windows NT\CurrentVersion\Time Zones"
    Const DstPath       As String = "Dynamic DST"

    Const DisplayKey    As String = "Display"
    Const DaylightKey   As String = "Dlt"
    Const StandardKey   As String = "Std"
    Const MuiDisplayKey As String = "MUI_Display"
    Const MuiDltKey     As String = "MUI_Dlt"
    Const MuiStdKey     As String = "MUI_Std"
    Const TziKey        As String = "TZI"
    Const FirstEntryKey As String = "FirstEntry"
    Const LastEntryKey  As String = "LastEntry"
   
    Dim SWbemServices   As Object
    Dim WshShell        As WshShell
   
    Dim SubKey          As Variant
    Dim Names           As Variant
    Dim NameKeys        As Variant
   
    Dim Display         As String
    Dim DisplayUtc      As String
    Dim Name            As Variant
    Dim DstEntry        As Variant
    Dim Mui             As Integer
    Dim BiasLabel       As String
    Dim Bias            As Long
    Dim Locations       As String
    Dim TziDetails      As Variant
    Dim TzItems()       As TimezoneEntry
    Dim TzItem          As TimezoneEntry
    Dim Index           As Long
    Dim SubIndex        As Long
    Dim Value           As String
    Dim LBoundItems     As Long
    Dim UBoundItems     As Long
   
    Dim TziInformation  As RegTziFormat

    ' The call is either for another year, or
    ' more than one day has passed since the last call.
    Set SWbemServices = GetObject(Component)
    Set WshShell = New WshShell

    SWbemServices.EnumKey DefKey, SubKeyPath, Names
    ' Retrieve all timezones' base data.
    LBoundItems = LBound(Names)
    UBoundItems = UBound(Names)
    ReDim TzItems(LBoundItems To UBoundItems)
   
    For Index = LBound(Names) To UBound(Names)
        ' Assemble paths and look up key values.
        SubKey = Names(Index)
       
        ' Invariant name of timezone.
        TzItem.Name = SubKey
       
        ' MUI of the timezone.
        Name = Join(Array(HKey, SubKeyPath, SubKey, MuiDisplayKey), "\")
        Value = WshShell.RegRead(Name)
        Mui = Val(Split(Value, ",")(1))
        TzItem.Mui = Mui
        ' MUI of the standard timezone.
        Name = Join(Array(HKey, SubKeyPath, SubKey, MuiStdKey), "\")
        Value = WshShell.RegRead(Name)
        Mui = Val(Split(Value, ",")(1))
        TzItem.MuiStandard = Mui
        ' MUI of the DST timezone.
        Name = Join(Array(HKey, SubKeyPath, SubKey, MuiDltKey), "\")
        Value = WshShell.RegRead(Name)
        Mui = Val(Split(Value, ",")(1))
        TzItem.MuiDaylight = Mui
       
        ' Localised description of the timezone.
        Name = Join(Array(HKey, SubKeyPath, SubKey, DisplayKey), "\")
        Display = WshShell.RegRead(Name)
        ' Extract the first part, cleaned like "UTC+08:30".
        DisplayUtc = Mid(Split(Display, ")", 2)(0) & "+00:00", 2, 9)
        ' Extract the offset part of first part, like "+08:30".
        BiasLabel = Mid(Split(Display, ")", 2)(0) & "+00:00", 5, 6)
        ' Convert the offset part of the first part to a bias value (signed integer minutes).
        Bias = -Val(Left(BiasLabel, 1) & Str(CDbl(CDate(Mid(BiasLabel, 2))) * 24 * 60))
        ' Extract the last part, holding the location(s).
        Locations = Split(Display, " ", 2)(1)
        TzItem.Bias = Bias
        TzItem.Utc = DisplayUtc
        TzItem.Locations = Locations
       
        ' Localised name of the standard timezone.
        Name = Join(Array(HKey, SubKeyPath, SubKey, StandardKey), "\")
        TzItem.ZoneStandard = WshShell.RegRead(Name)
        ' Localised name of the DST timezone.
        Name = Join(Array(HKey, SubKeyPath, SubKey, DaylightKey), "\")
        TzItem.ZoneDaylight = WshShell.RegRead(Name)
       
        ' TZI details.
        SWbemServices.GetBinaryValue DefKey, Join(Array(SubKeyPath, SubKey), "\"), TziKey, TziDetails
        FillRegTziFormat TziDetails, TziInformation
        TzItem.Tzi = TziInformation
        ' Default Dynamic DST range.
        TzItem.FirstEntry = Null
        TzItem.LastEntry = Null
       
        ' Check for Dynamic DST info.
        SWbemServices.EnumKey DefKey, Join(Array(SubKeyPath, SubKey), "\"), NameKeys
        If IsArray(NameKeys) Then
            ' This timezone has subkeys. Check if Dynamic DST is present.
            For SubIndex = LBound(NameKeys) To UBound(NameKeys)
                If NameKeys(SubIndex) = DstPath Then
                    ' Dynamic DST details found.
                    ' Record first and last entry.
                    DstEntry = Join(Array(HKey, SubKeyPath, SubKey, DstPath, FirstEntryKey), "\")
                    Value = WshShell.RegRead(DstEntry)
                    TzItem.FirstEntry = Value
                    DstEntry = Join(Array(HKey, SubKeyPath, SubKey, DstPath, LastEntryKey), "\")
                    Value = WshShell.RegRead(DstEntry)
                    TzItem.LastEntry = Value
                   
                    If DynamicDstYear >= TzItems(Index).FirstEntry And _
                        DynamicDstYear <= TzItems(Index).LastEntry Then
                        ' Replace default TZI details with those from the dynamic DST.
                        DstEntry = Join(Array(SubKeyPath, SubKey, DstPath), "\")
                        SWbemServices.GetBinaryValue DefKey, Join(Array(SubKeyPath, SubKey), "\"), , CStr(DynamicDstYear), TziDetails
                        FillRegTziFormat TziDetails, TziInformation
                        TzItem.Tzi = TziInformation
                    Else
                        ' Dynamic DST year was not found.
                        ' Return current year.
                        DynamicDstYear = Year(Date)
                    End If
                    Exit For
                End If
            Next
        End If
        TzItems(Index) = TzItem
    Next
   
    GetRegistryTimezoneItems = TzItems
   
End Function

You will note yet a Private function, FillRegTziFormat, that converts between two of the custom data structures used. It is trivial, so I won't post it here - please study it in the attached code.


Caching the time zones

Retrieval of the list of time zones is not fast - about half a second. That is acceptable for single calls, but for repeated calls - for example in a query - it will in many scenarios throttle execution. 

To avoid this, a function, RegistryTime zoneItems, is included which will cache repeated calls for a day and be slightly faster if only one time zone is queried, and this is the Public function to retrieve these data:


' 2019-12-14. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function RegistryTimezoneItems( _
    Optional ByVal TimezoneName As String, _
    Optional ByRef DynamicDstYear As Integer) _
    As TimezoneEntry()

    Static TzAllItems() As TimezoneEntry
    Static LastCall     As Date
    Static LastYear     As Integer
       
    Dim TzItems()       As TimezoneEntry
    Dim TzItem          As TimezoneEntry
    Dim Index           As Long
    Dim Continue        As Boolean
   
    If LastYear <> DynamicDstYear Or DateDiff("d", LastCall, Date) <> 0 Then
        ' Save 0.5 second for each call by caching the retrieved timezones.
        TzAllItems() = GetRegistryTimezoneItems(DynamicDstYear)
        LastYear = DynamicDstYear
        LastCall = Date
    End If

    If TimezoneName = "" Then
        ' Retrieve all timezones' base data.
        TzItems() = TzAllItems()
    Else
        ' Retrieve one timezone's base data.
        ReDim TzItems(0)
   
        For Index = LBound(TzAllItems) To UBound(TzAllItems)
            TzItem = TzAllItems(Index)
            Continue = Not CBool(StrComp(TzItem.Name, TimezoneName, vbTextCompare))
            If Continue = False Then
                ' Check, if stripping the trailing "Standard Time" form Name will result in a match.
                Continue = Not CBool(StrComp(Replace(TzItem.Name, StandardTimeLabel, ""), TimezoneName, vbTextCompare))
            End If
           
            If Continue = True Then
                TzItems(0) = TzItem
                Exit For
            End If
        Next
    End If
   
    RegistryTimezoneItems = TzItems
   
End Function

A direct usage of the function is demonstrated in the function, ListAllTimezones. 

This will list the names of the time zones and their bias. Also, an "MUI" is found; it is probably a Microsoft Unique Identifier but, strangely, this is not a key, only a numeric identifier. Do remember:

The name of the timezone is the key of the timezone. 


Thus, it is not localised:


' List all timezones from the Windows Registry.
' They will be ordered by their names (keys).
'
' 2018-11-11. Gustav Brock. Cactus Data ApS, CPH.
'
Public Sub ListAllTimezones()
   
    Dim Entries()   As TimezoneEntry
   
    Dim Entry       As TimezoneEntry
    Dim Index       As Integer
   
    Entries = RegistryTimezoneItems()
   
    For Index = LBound(Entries) To UBound(Entries)
        Entry = Entries(Index)
        Debug.Print "Mui: " & Entry.Mui, "Bias: " & Str(Entry.Bias), "Name: " & Entry.Name
    Next
   
End Sub

To retrieve the localised names (the descriptions) of the time zones, replace Entry.Name with Entry.ZoneStandard or Entry.ZoneDaylight, like:


        Debug.Print "Mui: " & Entry.Mui, "Bias: " & Str(Entry.Bias), "Name: " & Entry.ZoneStandard

The output will be very close to this list:


Mui: -460     Bias: -270    Name: Afghanistan Standard Time
Mui: -220     Bias:  540    Name: Alaskan Standard Time
Mui: -2390    Bias:  600    Name: Aleutian Standard Time
Mui: -2160    Bias: -420    Name: Altai Standard Time
Mui: -390     Bias: -180    Name: Arab Standard Time
Mui: -440     Bias: -240    Name: Arabian Standard Time
Mui: -400     Bias: -180    Name: Arabic Standard Time
Mui: -2080    Bias:  180    Name: Argentina Standard Time
Mui: -2180    Bias: -240    Name: Astrakhan Standard Time
Mui: -80      Bias:  240    Name: Atlantic Standard Time
Mui: -650     Bias: -570    Name: AUS Central Standard Time
Mui: -2490    Bias: -525    Name: Aus Central W. Standard Time
Mui: -670     Bias: -600    Name: AUS Eastern Standard Time
Mui: -447     Bias: -240    Name: Azerbaijan Standard Time
Mui: -10      Bias:  60     Name: Azores Standard Time
Mui: -1660    Bias:  180    Name: Bahia Standard Time
Mui: -1020    Bias: -360    Name: Bangladesh Standard Time
Mui: -1970    Bias: -180    Name: Belarus Standard Time
Mui: -2610    Bias: -660    Name: Bougainville Standard Time
Mui: -140     Bias:  360    Name: Canada Central Standard Time
Mui: -2000    Bias:  60     Name: Cape Verde Standard Time
Mui: -450     Bias: -240    Name: Caucasus Standard Time
Mui: -660     Bias: -570    Name: Cen. Australia Standard Time
Mui: -150     Bias:  360    Name: Central America Standard Time
Mui: -1010    Bias: -360    Name: Central Asia Standard Time
Mui: -1120    Bias:  240    Name: Central Brazilian Standard Time
Mui: -280     Bias: -60     Name: Central Europe Standard Time
Mui: -290     Bias: -60     Name: Central European Standard Time
Mui: -1460    Bias: -660    Name: Central Pacific Standard Time
Mui: -160     Bias:  360    Name: Central Standard Time
Mui: -170     Bias:  360    Name: Central Standard Time (Mexico)
Mui: -2530    Bias: -765    Name: Chatham Islands Standard Time
Mui: -570     Bias: -480    Name: China Standard Time
Mui: -2430    Bias:  300    Name: Cuba Standard Time
Mui: -250     Bias:  720    Name: Dateline Standard Time
Mui: -410     Bias: -180    Name: E. Africa Standard Time
Mui: -680     Bias: -600    Name: E. Australia Standard Time
Mui: -2710    Bias: -120    Name: E. Europe Standard Time
Mui: -40      Bias:  180    Name: E. South America Standard Time
Mui: -2370    Bias:  360    Name: Easter Island Standard Time
Mui: -110     Bias:  300    Name: Eastern Standard Time
Mui: -2040    Bias:  300    Name: Eastern Standard Time (Mexico)
Mui: -340     Bias: -120    Name: Egypt Standard Time
Mui: -2190    Bias: -300    Name: Ekaterinburg Standard Time
Mui: -1140    Bias: -720    Name: Fiji Standard Time
Mui: -350     Bias: -120    Name: FLE Standard Time
Mui: -1070    Bias: -240    Name: Georgian Standard Time
Mui: -2670    Bias:  0      Name: GMT Standard Time
Mui: -50      Bias:  180    Name: Greenland Standard Time
Mui: -2690    Bias:  0      Name: Greenwich Standard Time
Mui: -1490    Bias: -120    Name: GTB Standard Time
Mui: -2340    Bias:  300    Name: Haiti Standard Time
Mui: -230     Bias:  600    Name: Hawaiian Standard Time
Mui: -490     Bias: -330    Name: India Standard Time
Mui: -430     Bias: -210    Name: Iran Standard Time
Mui: -370     Bias: -120    Name: Israel Standard Time
Mui: -333     Bias: -120    Name: Jordan Standard Time
Mui: -2200    Bias: -120    Name: Kaliningrad Standard Time
Mui: -1420    Bias: -720    Name: Kamchatka Standard Time
Mui: -620     Bias: -540    Name: Korea Standard Time
Mui: -1780    Bias: -120    Name: Libya Standard Time
Mui: -1800    Bias: -840    Name: Line Islands Standard Time
Mui: -2510    Bias: -630    Name: Lord Howe Standard Time
Mui: -1470    Bias: -660    Name: Magadan Standard Time
Mui: -2870    Bias:  180    Name: Magallanes Standard Time
Mui: -2410    Bias:  570    Name: Marquesas Standard Time
Mui: -910     Bias: -240    Name: Mauritius Standard Time
Mui: -1760    Bias:  120    Name: Mid-Atlantic Standard Time
Mui: -363     Bias: -120    Name: Middle East Standard Time
Mui: -770     Bias:  180    Name: Montevideo Standard Time
Mui: -3010    Bias: -60     Name: Morocco Standard Time
Mui: -190     Bias:  420    Name: Mountain Standard Time
Mui: -180     Bias:  420    Name: Mountain Standard Time (Mexico)
Mui: -540     Bias: -390    Name: Myanmar Standard Time
Mui: -2790    Bias: -420    Name: N. Central Asia Standard Time
Mui: -383     Bias: -120    Name: Namibia Standard Time
Mui: -500     Bias: -345    Name: Nepal Standard Time
Mui: -740     Bias: -720    Name: New Zealand Standard Time
Mui: -70      Bias:  210    Name: Newfoundland Standard Time
Mui: -2630    Bias: -660    Name: Norfolk Standard Time
Mui: -2230    Bias: -480    Name: North Asia East Standard Time
Mui: -2240    Bias: -420    Name: North Asia Standard Time
Mui: -2960    Bias: -540    Name: North Korea Standard Time
Mui: -2770    Bias: -360    Name: Omsk Standard Time
Mui: -90      Bias:  240    Name: Pacific SA Standard Time
Mui: -210     Bias:  480    Name: Pacific Standard Time
Mui: -1100    Bias:  480    Name: Pacific Standard Time (Mexico)
Mui: -870     Bias: -300    Name: Pakistan Standard Time
Mui: -960     Bias:  240    Name: Paraguay Standard Time
Mui: -3050    Bias: -300    Name: Qyzylorda Standard Time
Mui: -300     Bias: -60     Name: Romance Standard Time
Mui: -2250    Bias: -660    Name: Russia Time Zone 10
Mui: -2260    Bias: -720    Name: Russia Time Zone 11
Mui: -2270    Bias: -240    Name: Russia Time Zone 3
Mui: -2980    Bias: -180    Name: Russian Standard Time
Mui: -1110    Bias:  180    Name: SA Eastern Standard Time
Mui: -120     Bias:  300    Name: SA Pacific Standard Time
Mui: -1130    Bias:  240    Name: SA Western Standard Time
Mui: -2450    Bias:  180    Name: Saint Pierre Standard Time
Mui: -2320    Bias: -660    Name: Sakhalin Standard Time
Mui: -1640    Bias: -780    Name: Samoa Standard Time
Mui: -3030    Bias:  0      Name: Sao Tome Standard Time
Mui: -2840    Bias: -240    Name: Saratov Standard Time
Mui: -560     Bias: -420    Name: SE Asia Standard Time
Mui: -590     Bias: -480    Name: Singapore Standard Time
Mui: -380     Bias: -120    Name: South Africa Standard Time
Mui: -530     Bias: -330    Name: Sri Lanka Standard Time
Mui: -2890    Bias: -120    Name: Sudan Standard Time
Mui: -1410    Bias: -120    Name: Syria Standard Time
Mui: -600     Bias: -480    Name: Taipei Standard Time
Mui: -690     Bias: -600    Name: Tasmania Standard Time
Mui: -2590    Bias:  180    Name: Tocantins Standard Time
Mui: -630     Bias: -540    Name: Tokyo Standard Time
Mui: -2750    Bias: -420    Name: Tomsk Standard Time
Mui: -750     Bias: -780    Name: Tonga Standard Time
Mui: -2140    Bias: -540    Name: Transbaikal Standard Time
Mui: -2810    Bias: -180    Name: Turkey Standard Time
Mui: -2910    Bias:  300    Name: Turks And Caicos Standard Time
Mui: -1040    Bias: -480    Name: Ulaanbaatar Standard Time
Mui: -130     Bias:  300    Name: US Eastern Standard Time
Mui: -200     Bias:  420    Name: US Mountain Standard Time
Mui: -930     Bias:  0      Name: UTC
Mui: -1380    Bias: -720    Name: UTC+12
Mui: -1390    Bias: -780    Name: UTC+13
Mui: -1160    Bias:  120    Name: UTC-02
Mui: -1220    Bias:  480    Name: UTC-08
Mui: -1230    Bias:  540    Name: UTC-09
Mui: -1250    Bias:  660    Name: UTC-11
Mui: -2730    Bias:  240    Name: Venezuela Standard Time
Mui: -2120    Bias: -600    Name: Vladivostok Standard Time
Mui: -2990    Bias: -240    Name: Volgograd Standard Time
Mui: -610     Bias: -480    Name: W. Australia Standard Time
Mui: -310     Bias: -60     Name: W. Central Africa Standard Time
Mui: -320     Bias: -60     Name: W. Europe Standard Time
Mui: -2550    Bias: -420    Name: W. Mongolia Standard Time
Mui: -1740    Bias: -300    Name: West Asia Standard Time
Mui: -2470    Bias: -120    Name: West Bank Standard Time
Mui: -710     Bias: -600    Name: West Pacific Standard Time
Mui: -2290    Bias: -540    Name: Yakutsk Standard Time

Now, having the names, the complete information of a single time zone can be listed:


' List one timezone from the Windows Registry by its name.
' If no name is passed, information for timezone UTC is read.
' If a non-existing name is passed, no information is listed.
'
' Example:
'   ? ListOneTimezone("central europe standard time")
'   ' or:
'   ? ListOneTimezone("central europe")
'   Name:         Central Europe Standard Time
'   UTC Zone:     UTC+01:00
'   Bias:         -60
'   MUI:          -280
'   MUI Std:      -282
'   MUI Dlt:      -281
'   Std:          Centraleuropa , normaltid
'   Dlt:          Centraleuropa , sommertid
'   Bias Std:      0
'   Bias Dlt:     -60
'   Date Std:     2019-10-27 03:00:00
'   Date Dlt:     2019-03-31 02:00:00
'   Locations:    Beograd , Bratislava, Budapest, Ljubljana, Prag
'   True
'
' 2018-11-11. Gustav Brock. Cactus Data ApS, CPH.
'
Public Function ListOneTimezone( _
    ByVal Name As String) _
    As Boolean

    Const UtcName   As String = "UTC"
   
    Dim Entries()   As TimezoneEntry
   
    Dim Entry       As TimezoneEntry
    Dim Result      As Boolean
   
    If Name = "" Then
        ' Use default name.
        Name = UtcName
    End If
   
    Entries = RegistryTimezoneItems(Name)
    ' Only one entry is expected.
    Entry = Entries(LBound(Entries))
   
    ' If the name is not found, no name is returned.
    Result = CBool(Len(Entry.Name))
   
    If Result = True Then
        ' List information for the found timezone.
        Debug.Print "Name:", Entry.Name
        Debug.Print "UTC Zone:", Entry.Utc
        Debug.Print "Bias:", Entry.Bias
        Debug.Print "MUI:", Entry.Mui
        Debug.Print "MUI Std:", Entry.MuiStandard
        Debug.Print "MUI Dlt:", Entry.MuiDaylight
        Debug.Print "Std:", Entry.ZoneStandard
        Debug.Print "Dlt:", Entry.ZoneDaylight
        Debug.Print "Bias Std:", Entry.Tzi.StandardBias
        Debug.Print "Bias Dlt:", Entry.Tzi.DaylightBias
        Debug.Print "Date Std:", Format(DateSystemTime(Entry.Tzi.StandardDate), "yyyy-mm-dd hh:nn:ss")
        Debug.Print "Date Dlt:", Format(DateSystemTime(Entry.Tzi.DaylightDate), "yyyy-mm-dd hh:nn:ss")
        Debug.Print "Locations:", Entry.Locations
    End If
   
    ListOneTimezone = Result

End Function

A helper function is called for - to convert the SystemTime type to a normal VBA Date value, as this is more convoluted than one might think initially:


' Converts a SystemTime structure to its date/time value.
'
' If SysTime.wYear is zero, SysTime is expected to hold the special set of data
' used for calculation of the beginning or the end of the Daylight Saving Time
' period of the current year.
'
' A value for SystemTime.wMilliseconds will be ignored.
'
' 2018-06-15. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function DateSystemTime( _
    ByRef SysTime As SystemTime) _
    As Date
   
    Const FirstDay  As Integer = 1

    Dim DateInMonth As Date
    Dim Occurrence  As Integer
    Dim Weekday     As VBA.VbDayOfWeek
    Dim DateValue   As Date
    Dim TimeValue   As Date
    Dim Value       As Date

    With SysTime
        If .wYear <> 0 Then
            ' Calculate actual date from structure data.
            DateValue = DateSerial(.wYear, .wMonth, .wDay)
        Else
            ' Calculate from a set of data for Daylight Saving Time.
            DateInMonth = DateSerial(Year(Date), .wMonth, FirstDay)
            Occurrence = .wDay
            Weekday = WeekdayFromDayOfWeek(.wDayOfWeek)
            DateValue = DateWeekdayInMonth(DateInMonth, Occurrence, Weekday)
        End If
        TimeValue = TimeSerial(.wHour, .wMinute, .wSecond)
       
        If CDbl(DateValue) >= 0 Then
            Value = DateValue + TimeValue
        Else
            Value = DateValue - TimeValue
        End If
    End With
 
    DateSystemTime = Value

End Function

For completeness, the reverse function is also available:


' Converts a date/time value to a SystemTime structure.
' Optionally, a value for milliseconds can be passed.
'
' 2016-06-09. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function CSystemTime( _
    ByVal Date1 As Date, _
    Optional ByVal Milliseconds As Integer) _
    As SystemTime

    Dim SysTime As SystemTime

    ' Limit milliseconds.
    If Milliseconds < 0 Or Milliseconds > 999 Then
        Milliseconds = 0
    End If
   
    ' Split the date/time value into its components.
    With SysTime
        .wYear = DatePart("yyyy", Date1)
        .wMonth = DatePart("m", Date1)
        .wDay = DatePart("d", Date1)
        .wHour = DatePart("h", Date1)
        .wMinute = DatePart("n", Date1)
        .wSecond = DatePart("s", Date1)
        .wMilliseconds = Milliseconds
        .wDayOfWeek = WeekdayToDayOfWeek(Weekday(Date1))
    End With
 
    CSystemTime = SysTime

End Function

Again, because of the mismatch between VBA and the SystemTime type, helper functions are needed, here to convert weekdays back and forth:


' Converts a value of wDayOfWeek from a SystemTime structure to a VBA weekday value.
' An error is raised for invalid input.
'
' Example where Wednesday is the first day of the week:
'   DayOfWeek     Weekday
'   0 Sunday      5
'   1             6
'   2             7
'   3             1 Wednesday
'   4             2
'   5             3
'   6             4
'
' 2019-12-08. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function WeekdayFromDayOfWeek( _
    ByVal DayOfWeek As Integer, _
    Optional ByVal FirstDayOfWeek As VbDayOfWeek = vbSunday) _
    As VbDayOfWeek

    Dim Weekday         As VbDayOfWeek
   
    If DayOfWeek < 0 Or DayOfWeek > 6 Then
        ' Raise error.
        Err.Raise DtError.dtInvalidProcedureCallOrArgument, "WeekdayFromDayOfWeek"
        Exit Function
    End If

    Weekday = (DayOfWeek + 1 - FirstDayOfWeek + DaysPerWeek) Mod DaysPerWeek + 1
   
    WeekdayFromDayOfWeek = Weekday

End Function



' Converts a VBA weekday value to the value of wDayOfWeek for a SystemTime structure.
' An error is raised for invalid input.
'
' Example where Wednesday is the first day of the week:
'   Weekday       DayOfWeek
'   1 Wednesday   3
'   2             4
'   3             5
'   4             6
'   5             0 Sunday
'   6             1
'   7             2
'
' 2019-12-07. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function WeekdayToDayOfWeek( _
    ByVal Weekday As VbDayOfWeek, _
    Optional ByVal FirstDayOfWeek As VbDayOfWeek = vbSunday) _
    As Integer
   
    Dim DayOfWeek       As Integer

    ' Validate FirstDayOfWeek.
    Select Case FirstDayOfWeek
        Case _
            vbMonday, _
            vbTuesday, _
            vbWednesday, _
            vbThursday, _
            vbFriday, _
            vbSaturday, _
            vbSunday
        Case Else
            FirstDayOfWeek = vbSunday
    End Select
   
    ' Validate Weekday and calculate DayOfWeek.
    Select Case Weekday
        Case _
            vbMonday, _
            vbTuesday, _
            vbWednesday, _
            vbThursday, _
            vbFriday, _
            vbSaturday, _
            vbSunday
                DayOfWeek = (Weekday + FirstDayOfWeek - 2) Mod DaysPerWeek
        Case Else
            ' Raise error.
            Err.Raise DtError.dtInvalidProcedureCallOrArgument, "WeekdayToDayOfWeek"
            Exit Function
    End Select

    WeekdayToDayOfWeek = DayOfWeek

End Function


Lookup and search

Having an array of the time zones, a lot of options for fast searching and lookup is possible:


  • The MUI of a time zone
  • The time zone from its description
  • The time zone from its MUI
  • The time zone from a location


These will not be detailed here. Please study the attached demo.


Finally, and what's it all about, the bias of a time zone can be found for Standard Time as well as Daylight Saving Time:


' Returns the timezone bias as specified in Windows from
' the name (key) of a timezone entry in the Registry.
' Accepts values without the common trailing "Standard Time".
'
' If Dst is true, and the current date is within daylight saving time,
' bias for daylight saving time is returned.
' If Date1 is specified, the bias of that date is returned.
'
' Returns a bias of zero if a timezone is not found.
'
' Examples:
'   Bias = BiasWindowsTimezone("Argentina")
'   Bias -> 180     ' Found
'
'   Bias = BiasWindowsTimezone("Argentina Standard Time")
'   Bias -> 180     ' Found.
'
'   Bias = BiasWindowsTimezone("Germany")
'   Bias -> 0       ' Not found.
'
'   Bias = BiasWindowsTimezone("Western Europe")
'   Bias -> 0       ' Not found.
'
'   Bias = BiasWindowsTimezone("W. Europe")
'   Bias -> -60     ' Found.
'
'   Bias = BiasWindowsTimezone("Paraguay", True, #2018-07-07#)
'   Bias -> 240     ' Found.
'
'   Bias = BiasWindowsTimezone("Paraguay", True, #2018-02-11#)
'   Bias -> 180     ' Found. DST.
'
'   Bias = BiasWindowsTimezone("Paraguay", False, #2018-02-11#)
'   Bias -> 240     ' Found.
'
' 2018-11-16. Gustav Brock. Cactus Data ApS, CPH.
'
Public Function BiasWindowsTimezone( _
    ByVal TimezoneName As String, _
    Optional Dst As Boolean, _
    Optional Date1 As Date) _
    As Long
   
    Static Entries()    As TimezoneEntry
    Static LastName     As String
    Static LastYear     As Integer
   
    Static Entry        As TimezoneEntry
    Dim ThisName        As String
    Dim ThisYear        As Integer
    Dim StandardDate    As Date
    Dim DaylightDate    As Date
    Dim DeltaBias       As Long
    Dim Bias            As Long
   
    If Trim(TimezoneName) = "" Then
        ' Nothing to look up.
        Exit Function
    Else
        ThisName = Trim(TimezoneName)
        ThisYear = Year(Date1)
        If LastName = ThisName And LastYear = ThisYear Then
            ' Use cached data.
        Else
            ' Retrieve the single entry or - if not found - an empty entry.
            Entries = RegistryTimezoneItems(ThisName, (ThisYear))
            Entry = Entries(LBound(Entries))
            LastName = ThisName
            LastYear = ThisYear
        End If
        If _
            StrComp(Entry.Name, TimezoneName, vbTextCompare) = 0 Or _
            StrComp(Replace(Entry.Name, StandardTimeLabel, ""), TimezoneName, vbTextCompare) = 0 Then
            ' Windows timezone found.
           
            ' Default is standard bias.
            DeltaBias = Entry.Tzi.StandardBias
            If Dst = True Then
                ' Return daylight bias if Date1 is of daylight saving time.
                StandardDate = DateSystemTime(Entry.Tzi.StandardDate)
                DaylightDate = DateSystemTime(Entry.Tzi.DaylightDate)
               
                If DaylightDate < StandardDate Then
                    ' Northern Hemisphere.
                    If DateDiff("s", DaylightDate, Date1) >= 0 And DateDiff("s", Date1, StandardDate) > 0 Then
                        ' Daylight time.
                        DeltaBias = Entry.Tzi.DaylightBias
                    Else
                        ' Standard time.
                    End If
                Else
                    ' Southern Hemisphere.
                    If DateDiff("s", DaylightDate, Date1) >= 0 Or DateDiff("s", Date1, StandardDate) > 0 Then
                        ' Daylight time.
                        DeltaBias = Entry.Tzi.DaylightBias
                    Else
                        ' Standard time.
                    End If
                End If
               
            End If
            ' Calculate total bias.
            Bias = Entry.Bias + DeltaBias
        End If
    End If

    BiasWindowsTimezone = Bias

End Function

See the in-line comments for typical usage.


Applying bias


The two most common tasks are to convert a local time to a remote time and vice-versa.

For this, the local bias and the remote bias must be known. Having these, the task is easy with the functions DateLocalBias and DateRemoteBias and a tiny helper function, BiasDiff:


' Calculates the date/time of LocalDate in a remote timezone.
' Adds the difference in minutes between the local timezone bias and
' the remote timezone bias, where both bias values are relative to UTC.
'
' Examples:
'
'   RemoteDate = DateRemoteBias(Now(), 60, -600)
'   will return RemoteDate as eleven hours ahead of local time.
'
'   RemoteDate = DateRemoteBias(Now(), -600, 60)
'   will return RemoteDate as eleven hours behind local time.
'
' 2016-06-09. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function DateRemoteBias( _
    ByVal LocalDate As Date, _
    ByVal LocalBias As Long, _
    ByVal RemoteBias As Long) _
    As Date
 
    Dim RemoteDate  As Date
    Dim Bias        As Long
   
    ' Find difference (in minutes) between timezone bias.
    Bias = BiasDiff(LocalBias, RemoteBias)
    ' Calculate remote date/time.
    RemoteDate = DateAdd("n", Bias, LocalDate)
   
    DateRemoteBias = RemoteDate
 
End Function



' Calculates the date/time of RemoteDate in a local timezone.
' Adds the difference in minutes between the remote timezone bias and
' the local timezone bias, where both bias values are relative to UTC.
'
' Examples:
'
'   LocalDate = DateLocalBias(Now(), 60, -600)
'   will return LocalDate as eleven hours ahead of remote time.
'
'   LocalDate = DateLocalBias(Now(), -600, 60)
'   will return LocalDate as eleven hours behind remote time.
'
' 2016-06-09. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function DateLocalBias( _
    ByVal RemoteDate As Date, _
    ByVal RemoteBias As Long, _
    ByVal LocalBias As Long) _
    As Date
 
    Dim LocalDate   As Date
    Dim Bias        As Long
   
    ' Find difference (in minutes) between timezone bias.
    Bias = BiasDiff(RemoteBias, LocalBias)
    ' Calculate local date/time.
    LocalDate = DateAdd("n", Bias, RemoteDate)
   
    DateLocalBias = LocalDate
 
End Function



' Calculates the difference in bias (minutes) between two timezones, 
' typically from the local timezone to the remote timezone. 
' Both timezones must be expressed by their bias relative to 
' UTC (Coordinated Universal Time) which is measured in minutes. 
' 
' 2019-11-12. Gustav Brock, Cactus Data ApS, CPH. 
' 
Public Function BiasDiff( _ 
    ByVal LocalBias As Long, _ 
    ByVal RemoteBias As Long) _ 
    As Long 
   
    Dim Bias    As Long 
     
    ' Calculate difference in timezone bias. 
    Bias = LocalBias - RemoteBias 
     
    BiasDiff = Bias 
 
End Function 

Armed with these and several of the functions mentioned above, it is also a simple task to convert a local time to UTC and a UTC time to local time with the functions DateFromUtc and DateToUtc:


' Converts a present UtcDate from Coordinated Universal Time (UTC) to local time.
' If IgnoreDaylightSetting is True, returned time will always be standard time.
'
' For dates not within the current year, use the function DateFromDistantUtc.
'
' 2017-11-27. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function DateFromUtc( _
    ByVal UtcDate As Date, _
    Optional ByVal IgnoreDaylightSetting As Boolean) _
    As Date

    Dim LocalBias   As Long
    Dim LocalDate   As Date
 
    ' Find the local time using standard bias.
    LocalBias = LocalBiasTimezonePresent(UtcDate, True)
    LocalDate = DateRemoteBias(UtcDate, UtcBias, LocalBias)
    If IgnoreDaylightSetting = False Then
        ' The local time should be returned as daylight time.
        If IsCurrentDaylightSavingTime(LocalDate) Then
            ' The local time is daylight time.
            ' Find bias for daylight time.
            LocalBias = LocalBiasTimezonePresent(LocalDate, IgnoreDaylightSetting)
            ' Find the local time using daylight bias.
            LocalDate = DateRemoteBias(UtcDate, UtcBias, LocalBias)
        End If
    End If
   
    DateFromUtc = LocalDate

End Function



' Converts a present LocalDate from local time to Coordinated Universal Time (UTC).
' If IgnoreDaylightSetting is True, LocalDate is considered standard time.
'
' For dates not within the current year, it is preferable to use the function
' ZoneCore.DateToDistantUtc.
'
' Note:
' For a value of the transition interval from daylight time back to standard time,
' where the value could belong to either of these, daylight time is assumed.
' This means that a standard time of the transition interval will return an UTC
' time off by the daylight saving bias.
' Thus, for obtaining the current time in UTC, always use the function UtcNow.
'
' 2017-11-27. Gustav Brock, Cactus Data ApS, CPH.
'
Public Function DateToUtc( _
    ByVal LocalDate As Date, _
    Optional ByVal IgnoreDaylightSetting As Boolean) _
    As Date

    Dim LocalBias   As Long
    Dim UtcDate     As Date
 
    LocalBias = LocalBiasTimezonePresent(LocalDate, IgnoreDaylightSetting)
    UtcDate = DateRemoteBias(LocalDate, LocalBias, UtcBias)

    DateToUtc = UtcDate

End Function

Please note, that DateToUtc is intended for converting recent time only. For converting the current time, use UtcNow (or UtcDate or UtcTime). Also, be careful converting time more than a decade from now, as the information in Windows may not cover this. Exactly how many years, is dependant on your local time zone.


Format the bias


In code, the bias is normally fine as is - a count of minutes. But for presentation, it may not be enough, as the typical way to present a time zone is by showing its difference from UTC in hours and minutes.

But there is not a standard format, not even a de facto standard, so the formatting options should be flexible. As a bare minimum, it should be able to build a list that mimics that of Windows 10:



It's a bit special, as no bias is presented for UTC, which makes sense, while other locations in that time zone do have the bias specified as +00:00, which also makes sense.


The function FormatBias was created to return this format - and more. Please browse the in-line comments for a lot of examples:


' Formats for display a bias value as a UTC offset.
'
' If argument Name is passed as "UTC", no offet is displayed.
'
' Examples:
'   FormatBias(300)                         -> -05:00
'   FormatBias(300, True)                   -> UTC-05:00
'   FormatBias(300, True, True)             -> (UTC-05:00)
'   FormatBias(0, True)                     -> UTC+00:00
'   FormatBias(0, True, True)               -> (UTC+00:00)
'   FormatBias(0, True, True, "Sao Tome")   -> (UTC+00:00)
'   FormatBias(0, True, True, "UTC")        -> (UTC)
'   FormatBias(0, False, True, "UTC")       -> ()
'   FormatBias(0, False, False, "UTC")      ->
'   FormatBias(-60)                         -> +10:00
'   FormatBias(-60, True)                   -> UTC+10:00
'   FormatBias(-60, True, True)             -> (UTC+10:00)
'
' 2019-12-08. Gustav Brock. Cactus Data ApS, CPH.
'
Public Function FormatBias( _
    ByVal Bias As Integer, _
    Optional PrefixUtc As Boolean, _
    Optional OuterParenthesis As Boolean, _
    Optional Name As String) _
    As String
   
    Const UtcPrefix     As String = "UTC"
    Const OffsetMask    As String = "({0})"
   
    Dim Offset          As Date
    Dim Prefix          As String
    Dim Result          As String
   
    Offset = TimeBias(Bias)
   
    If PrefixUtc = True Then
        Prefix = UtcPrefix
    End If
    If Name = UtcPrefix Then
        Result = Prefix
    Else
        Result = Prefix & FormatSign(Offset, True) & Format(Offset, "hh\:nn")
    End If
   
    If OuterParenthesis = True Then
        Result = Replace(OffsetMask, "{0}", Result)
    End If
   
    FormatBias = Result
   
End Function

If you paid attention to the details, you might have noticed, that the format reverses the sign of the bias. This is because - by convention - it is not the bias but the offset from UTC that is displayed.



Until now, all code has been equally well suited for Excel as well as Access.

When it comes to presentation at the user level, however, the code separates completely.

Read on in part two of the article: Time Zones, Windows, and Microsoft Office - Part 2


Conclusion


With the collection of functions described, it has been shown how to retrieve each and every information about time zones stored in the Windows Registry without any third-party tools or need for supplemental information.

Also, it has been demonstrated how to use this information to perform all usual - and some unusual - tasks where time zone information is expected or needed.

Finally, the core functions will provide a solid foundation for any Access or Excel application that will require custom higher-level time zone related functions for special purposes.


Code and download


The full code and demo is attached for Microsoft Access 365 and Microsoft Excel 365.

    Microsoft Access: TimezoneWin.accdb

    Microsoft Excel: TimezoneWin.xlsm


At any time, full and updated code is available on GitHub: VBA.Timezone-Windows


I hope you found this article useful. You are encouraged to ask questions, report any bugs or make any other comments about it below.

 

Note: If you need further "Support" about this topic, please consider using the Ask a Question feature of Experts Exchange. I monitor questions asked and would be pleased to provide any additional support required in questions asked in this manner, along with other EE experts.

 

Please do not forget to press the "Thumbs Up" button if you think this article was helpful and valuable for EE members.



3
6,173 Views
Gustav BrockMVP
CERTIFIED EXPERT

Comments (0)

Have a question about something in this article? You can receive help directly from the article author. Sign up for a free trial to get started.