ArchiveFilter.StartTime



StartTime() As Long
ED
not used
RT
avaliable

Remarks

Gets or sets the start time of the filter as long.

Every data that is within the range of the "StartTime" and "EndTime" properties, will not be filtered out and therefore returned.

ATTENTION: zenOn uses UTC time internally, hence the desired start time has to be converted from the local time zone into UTC.

Time conversion

The following macro should be used to set the time correctly. Follow the instructions inside the macro header.

'##############################################################################
'## Name	 : clsTimeConvert											##
'## Description: Macro to convert from local time into UTC and vice versa	##
'##																		##
'## Instructions															 ##
'## 1. Copy the macro into a textfile and save it under "clsTimeConvert.cls" ##
'## 2. Import the file into the VBA project								##
'##	 >> File -> Import file...											##
'##	 >> Shortcut CTRL + M												 ##
'## 3. Declare a variable as "clsTimeConvert" within the VBA project		 ##
'##	 e.g. Dim zTimeConversion as clsTimeConvert						 ##
'## 4. Convert from local time into UTC									##
'##	 e.g. zTimeConvert.System2zenOn(CDbl(CDate("30.07.2007 14:00:00")))   ##
'##############################################################################
Option Explicit
Private Declare Function GetTimeZoneInformation _
		Lib "kernel32" (lpTimeZoneInformation As TIME_ZONE_INFORMATION) As Long
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 TIME_ZONE_INFORMATION
  Bias As Long
  StandardName(1 To 64) As Byte
  StandardDate As SYSTEMTIME
  StandardBias As Long
  DaylightName(1 To 64) As Byte
  DaylightDate As SYSTEMTIME
  DaylightBias As Long
End Type
Const TIME_ZONE_ID_UNKNOWN = &H0
Const TIME_ZONE_ID_STANDARD = &H1
Const TIME_ZONE_ID_DAYLIGHT = &H2
Dim SommerZeit As Boolean
Dim SommerZeitDate As Date
Dim SommerZeitName$
Dim SommerZeitGMT&
Dim NormalZeitDate As Date
Dim NormalZeitName$
Dim NormalZeitGMT

Public Function zenOn2System(dTime As Double) As Double
'Converts zenOn (GMT) time to system time format...
	zenOn2System = (dTime - GetTimeZone) / 86400 + 25569
End Function

Public Function System2zenOn(lTime As Double) As Double
'Converts system time to zenOn time (GMT) format...
	System2zenOn = (lTime - 25569) * 86400 + GetTimeZone
End Function

Private Function GetTimeZone() As Long
Dim TZI As TIME_ZONE_INFORMATION
Dim Result&, ErrFlag As Boolean
	Result = GetTimeZoneInformation(TZI)
	Select Case Result
		Case TIME_ZONE_ID_UNKNOWN
			SommerZeit = False
		Case TIME_ZONE_ID_STANDARD
			SommerZeit = False
		Case TIME_ZONE_ID_DAYLIGHT
			SommerZeit = True
		Case Else
			Exit Function
	End Select
	If SommerZeit = True Then
		GetTimeZone = (60 * TZI.Bias) + (60 * TZI.DaylightBias)
	Else
		GetTimeZone = (60 * TZI.Bias) + (60 * TZI.StandardBias)
	End If
End Function

See Also

ArchiveFilter