Search code examples
excelvbaif-statementepochnested-if

How to convert epoch dates across years, including DST


I have a spreadsheet that includes a "Last Modified Date" in epoch format in column C, such as:

1486841495 (earliest date in 2017) 1574478516 (latest date in 2019)

Column C has 6,003 rows. What I want to do is have a script take what's in column C and convert it to the following format in column E: MM/DD/YY HH:MM:SS AM/PM. I have the result cells formatted correctly so that's showing up right. I'm in Central time zone.

I have very little exposure to writing code and I've been trying to piece something together for hours.

This is the closest I've been able to get, but it only runs on one cell and I need it to run on the entire column C. Can anyone help?

Sub CalcDate()

'2017

If Range("C2").Value > 1483250400 And Range("C2").Value < 1489298520 Then
Range("E2:E10").Value = ((Range("C2:E10") - 21600) / 86400) + 25569

ElseIf Range("C2").Value > 1489298520 And Range("C2").Value < 1509858120 Then
Range("E2").Value = ((Range("C2") - 18000) / 86400) + 25569

ElseIf Range("C2").Value > 1509858120 And Range("C2").Value < 1514743199 Then
Range("E2").Value = ((Range("C2") - 21600) / 86400) + 25569

'2018

ElseIf Range("C2").Value > 1514786400 And Range("C2").Value < 1520755200 Then
Range("E2:E10").Value = ((Range("C2:E10") - 21600) / 86400) + 25569

ElseIf Range("C2").Value > 1520755200 And Range("C2").Value < 1541318400 Then
Range("E2").Value = ((Range("C2") - 18000) / 86400) + 25569

ElseIf Range("C2").Value > 1541318400 And Range("C2").Value < 1546279199 Then
Range("E2").Value = ((Range("C2") - 21600) / 86400) + 25569

'2019

 ElseIf Range("C2").Value > 1546322400 And Range("C2").Value < 1552204800 Then
    Range("E2:E10").Value = ((Range("C2:E10") - 21600) / 86400) + 25569

    ElseIf Range("C2").Value > 1552204800 And Range("C2").Value < 1572768000 Then
    Range("E2").Value = ((Range("C2") - 18000) / 86400) + 25569

    ElseIf Range("C2").Value > 1572768000 And Range("C2").Value < 1577815199 Then
    Range("E2").Value = ((Range("C2") - 21600) / 86400) + 25569


End If
End Sub

Solution

  • I think the "=fromUnix(C2)" formula suggested by Tim Williams in the question's comments may be the most straightforward way to resolve the conversion of all the epoch values to UTC. But, if the intent is to learn how to do it with VBA alone, including the conversion to local time, the code below will hopefully be of some help to someone.

    NB: An advantage to having a VBA macro is that it can write out all the results in one fell swoop and avoids the need to add 6,000 new formulas in the workbook. The disadvantage is that the conversion is not dynamic, so any changes in the epoch values will require running the macro again.

    Tactic

    We would need a procedure that reads in the epoch values from one column into an array, converts each value in the array from epoch to local time, and then prints that array to a different column. To perform the conversion of each individual epoch value, we must first convert it to UTC, and from UTC to local time.

    To do the 2nd conversion, we will need to rely on some code adapted from an answer posted by ashleedawg at Convert UTC time to local. The nice thing about that code is that it takes into account the DST status at the time of the UTC value, as opposed to the current DST status at the time of the calculation. This was not the case in the Chip Pearson code (at this link) that I had previously suggested for this answer.

    Code modules to add

    We would need to create a new VBA code module with the following adaptation of ashleedawg's code:

    Option Explicit
    'Adapted from ashleedawg's answer at
    '  https://stackoverflow.com/questions/23903872/convert-utc-time-to-local#50452663
    'That answer, in turn, was adapted from code by Tim Hall at
    '  https://github.com/VBA-tools/VBA-UTC
    
    'PUBLIC FUNCTIONS:
    '    - UTCtoLocal(utc_UtcDate As Date) As Date     converts UTC datetimes to local
    '    - LocalToUTC(utc_LocalDate As Date) As Date   converts local DateTime to UTC
    'Accuracy confirmed for several variations of time zones & DST rules. (ashleedawg)
    '===============================================================================
    
    Private Type utc_SYSTEMTIME
        utc_wYear As Integer: utc_wMonth As Integer: utc_wDayOfWeek As Integer: utc_wDay As Integer
        utc_wHour As Integer: utc_wMinute As Integer: utc_wSecond As Integer: utc_wMilliseconds As Integer
    End Type
    
    Private Type utc_TIME_ZONE_INFORMATION
        utc_Bias As Long: utc_StandardName(0 To 31) As Integer: utc_StandardDate As utc_SYSTEMTIME: utc_StandardBias As Long
        utc_DaylightName(0 To 31) As Integer: utc_DaylightDate As utc_SYSTEMTIME: utc_DaylightBias As Long
    End Type
    
    'http://msdn.microsoft.com/library/windows/desktop/ms724421.aspx /ms724949.aspx /ms725485.aspx
    #If VBA7 Then
    Private Declare PtrSafe Function utc_GetTimeZoneInformation Lib "kernel32" Alias "GetTimeZoneInformation" _
        (utc_lpTimeZoneInformation As utc_TIME_ZONE_INFORMATION) As Long
    Private Declare PtrSafe Function utc_SystemTimeToTzSpecificLocalTime Lib "kernel32" Alias "SystemTimeToTzSpecificLocalTime" _
        (utc_lpTimeZoneInformation As utc_TIME_ZONE_INFORMATION, utc_lpUniversalTime As utc_SYSTEMTIME, utc_lpLocalTime As utc_SYSTEMTIME) As Long
    Private Declare PtrSafe Function utc_TzSpecificLocalTimeToSystemTime Lib "kernel32" Alias "TzSpecificLocalTimeToSystemTime" _
        (utc_lpTimeZoneInformation As utc_TIME_ZONE_INFORMATION, utc_lpLocalTime As utc_SYSTEMTIME, utc_lpUniversalTime As utc_SYSTEMTIME) As Long
    #Else
    Private Declare Function utc_GetTimeZoneInformation Lib "kernel32" Alias "GetTimeZoneInformation" _
        (utc_lpTimeZoneInformation As utc_TIME_ZONE_INFORMATION) As Long
    Private Declare Function utc_SystemTimeToTzSpecificLocalTime Lib "kernel32" Alias "SystemTimeToTzSpecificLocalTime" _
        (utc_lpTimeZoneInformation As utc_TIME_ZONE_INFORMATION, utc_lpUniversalTime As utc_SYSTEMTIME, utc_lpLocalTime As utc_SYSTEMTIME) As Long
    Private Declare Function utc_TzSpecificLocalTimeToSystemTime Lib "kernel32" Alias "TzSpecificLocalTimeToSystemTime" _
        (utc_lpTimeZoneInformation As utc_TIME_ZONE_INFORMATION, utc_lpLocalTime As utc_SYSTEMTIME, utc_lpUniversalTime As utc_SYSTEMTIME) As Long
    #End If
    
    Private Function utc_DateToSystemTime(utc_Value As Date) As utc_SYSTEMTIME ' "Helper Function" for Public subs (below)
        With utc_DateToSystemTime
            .utc_wYear = Year(utc_Value): .utc_wMonth = Month(utc_Value): .utc_wDay = Day(utc_Value)
            .utc_wHour = Hour(utc_Value): .utc_wMinute = Minute(utc_Value): .utc_wSecond = Second(utc_Value): .utc_wMilliseconds = 0
        End With
    End Function
    
    Private Function utc_SystemTimeToDate(utc_Value As utc_SYSTEMTIME) As Date ' "Helper Function" for Public Functions (below)
        utc_SystemTimeToDate = DateSerial(utc_Value.utc_wYear, utc_Value.utc_wMonth, utc_Value.utc_wDay) + _
            TimeSerial(utc_Value.utc_wHour, utc_Value.utc_wMinute, utc_Value.utc_wSecond)
    End Function
    
    '===============================================================================
    
    Public Function UTCtoLocal(utc_UtcDate As Date) As Date
        On Error GoTo errorUTC
        Dim utc_TimeZoneInfo As utc_TIME_ZONE_INFORMATION, utc_LocalDate As utc_SYSTEMTIME
        utc_GetTimeZoneInformation utc_TimeZoneInfo
        utc_SystemTimeToTzSpecificLocalTime utc_TimeZoneInfo, utc_DateToSystemTime(utc_UtcDate), utc_LocalDate
        UTCtoLocal = utc_SystemTimeToDate(utc_LocalDate)
        Exit Function
    errorUTC:
        Debug.Print "UTC parsing error: " & Err.Number & " - " & Err.Description: Stop
    End Function
    
    Public Function LocalToUTC(utc_LocalDate As Date) As Date
        On Error GoTo errorUTC
        Dim utc_TimeZoneInfo As utc_TIME_ZONE_INFORMATION, utc_UtcDate As utc_SYSTEMTIME
        utc_GetTimeZoneInformation utc_TimeZoneInfo
        utc_TzSpecificLocalTimeToSystemTime utc_TimeZoneInfo, utc_DateToSystemTime(utc_LocalDate), utc_UtcDate
        LocalToUTC = utc_SystemTimeToDate(utc_UtcDate)
        Exit Function
    errorUTC:
        Debug.Print "UTC conversion error: " & Err.Number & " - " & Err.Description: Stop
    End Function
    

    After that, we can create a second module with the following code to convert from epoch seconds to local time:

    Option Explicit
    
    Function EpochToLocal(ByVal unixSecs As Variant) As Variant
      EpochToLocal = "" 'Default value returned in case the conversion is not possible
      On Error Resume Next
      If IsNumeric(unixSecs & "") Then EpochToLocal = UTCtoLocal(EpochToUTC(CLng(unixSecs)))
      'UTCtoLocal is adapted from the answer posted by ashleedawg at
      '  https://stackoverflow.com/questions/23903872/convert-utc-time-to-local#50452663
    End Function
    
    Function EpochToUTC(ByVal unixSecs As Long)
      EpochToUTC = DateAdd("s", unixSecs, #1/1/1970#) 
    End Function
    

    Then, we can create a third VBA module and paste the following macro to do the actual conversion:

    Option Explicit
    
    Sub ConvertAllUnixTimestamps()
      'This range must be set to the 1-column block of cells with all the epoch-seconds values;
      '  to simplify the code, this method assumes that this range has at least 2 rows
      'The range is being hard-coded here, but it could be passed as a parameter in future
      Dim epochColumn As Range: Set epochColumn = Range("C2:C6003")
    
      'This range must be set to the first cell where the local times must be written
      'The cell is being hard-coded here, but it could be passed as a parameter in future
      Dim localFirstCell As Range: Set localFirstCell = Range("E2")
    
      'Read in all the epoch values into a 2-dimensional array (assuming the range has 2+ rows)
      Dim epochArr As Variant: epochArr = epochColumn.value
    
      'Get the lower and upper bounds of the array's 1st dimension with the epoch values
      Dim epochLb As Long: epochLb = LBound(epochArr, 1)
      Dim epochUb As Long: epochUb = UBound(epochArr, 1)
      'Get the lower bound of the array's 2nd dimension;
      '  since we only care about the 1st column of values, the 2nd dim's upper bound is not used
      Dim index2 As Long: index2 = LBound(epochArr, 2)
      'Get the number of epoch values to process
      Dim epochCount As Long: epochCount = epochUb - epochLb + 1
    
      'Convert all the values in the array from epoch seconds to local times
      Dim i As Long
      For i = epochLb To epochUb
        epochArr(i, index2) = EpochToLocal(epochArr(i, index2))
      Next
    
      'Create a range that goes from the first cell and goes down [epochCount] rows,
      '  and then write the converted array to it
      localFirstCell.Resize(epochCount).value = epochArr
    End Sub
    

    Subtracting leap seconds for a more exact UTC conversion

    I believe that, for most cases, the above code would do. However, the Adrian Monk's of the world may disagree. This is because the number of seconds in epoch values are not necessarily aligned with UTC. As explained on Wikipedia, epoch timestamps may not take into account the pesky "leap seconds" that are occasionally inserted into UTC time to account for astronomical variations delaying the earth's rotation. If those precious seconds need to be accounted for, the second module mentioned above, the one with the EpochToLocal function, would need to be replaced with something like the code below:

    NB: If the epoch values being converted are from a clock that is counting the actual seconds since 1 Jan 1970 (e.g. a TAI-based clock), then adding the leap seconds during the conversion is theoretically necessary. However, if the epoch values are a mere "formatting" of UTC times that simply subtracted 1 Jan 1970 from the UTC time, then leap seconds should not be removed because they have already been accounted for.

    Option Explicit
    
    Dim LeapSecDates() As Variant 'Array to store all the dates when leap secs. were added to the UTC
    Dim LeapSecLb As Long, LeapSecUb As Long 'Bounds of the leap-seconds array
    Dim LeapSecDatesLoaded As Boolean 'Indicates whether the leap-seconds array has been loaded yet
    
    Function EpochToLocal(ByVal unixSecs As Variant) As Variant
      EpochToLocal = "" 'Default value returned in case the conversion is not possible
      On Error Resume Next
      If IsNumeric(unixSecs & "") Then EpochToLocal = UTCtoLocal(EpochToUTC(CLng(unixSecs)))
      'UTCtoLocal is adapted from the answer posted by ashleedawg at
      '  https://stackoverflow.com/questions/23903872/convert-utc-time-to-local#50452663
    End Function
    
    Function EpochToUTC(ByVal unixSecs As Long)
      Dim dte As Date
      dte = DateAdd("s", unixSecs, #1/1/1970#) 'This takes us to UTC, but w/ extra leap secs.
      dte = DateAdd("s", -LeapSecondsFor(dte), dte) 'Removing the extra leap seconds
    
      EpochToUTC = dte
    End Function
    
    Private Function LeapSecondsFor(ByVal dte As Date)
      Dim i As Long
    
      If Not LeapSecDatesLoaded Then 'To save time, the leap-seconds array is only loaded once
        'Based on table at https://en.wikipedia.org/wiki/Leap_second#Insertion_of_leap_seconds
        '  as of Dec 2019; the dates must be in ascending order
        LeapSecDates = Array(#6/30/1972#, #12/31/1972#, #12/31/1973#, #12/31/1974# _
          , #12/31/1975#, #12/31/1976#, #12/31/1977#, #12/31/1978#, #12/31/1979# _
          , #6/30/1981#, #6/30/1982#, #6/30/1983#, #6/30/1985#, #12/31/1987#, #12/31/1989# _
          , #12/31/1990#, #6/30/1992#, #6/30/1993#, #6/30/1994#, #12/31/1995# _
          , #6/30/1997#, #12/31/1998#, #12/31/2005#, #12/31/2008#, #7/31/2012# _
          , #6/30/2015#, #12/31/2016#) 'This array needs to be manually updated as new dates emerge
        LeapSecLb = LBound(LeapSecDates)
        LeapSecUb = UBound(LeapSecDates)
    
        'Move the time to midnight of the next day for each date in the array
        For i = LeapSecLb To LeapSecUb
          LeapSecDates(i) = DateAdd("d", 1, LeapSecDates(i))
        Next
    
        LeapSecDatesLoaded = True
      End If
    
      'Get the number of leap-second dates that have elapsed up until the date [dte];
      '  e.g. if [dte] - 23 secs. is > the last 24 dates in the array, then 24 leap seconds
      '       must be removed
      Dim leap As Long: leap = 0
      Dim previousLeapSecs As Long
      For i = LeapSecUb To LeapSecLb Step -1
        previousLeapSecs = i - LeapSecLb
        If DateAdd("s", -previousLeapSecs, dte) > LeapSecDates(i) Then
          LeapSecondsFor = previousLeapSecs + 1
          Exit Function
        End If
      Next
    
      'If we are here, no leap seconds were added before [dte]
      LeapSecondsFor = 0
    End Function
    

    Do bear in mind that the modules above have many extra comments that make the code look lengthier than it really is. If you do not need all the play-by-play, you can delete many of the comments to get a better sense of what the code tries to do.