<< Previous Article | Next Article >>
In my previous article Working with NT EventLog - Part 1 (Introduction, Event Source, Message Files) you learned how to create a Message file (*.Res file). In this article we will start actual implementation on CEventLog class. Some members of CEventLog class as below.
Properties
- EventCategoryString : Category Name of event
- EventComputerName : Local/Remote computer name from where event was generated
- EventDescription : Desctiption of event
- EventId : EventId of event which is defined in MessageFile
- EventRecordNum : Unique number of event
- EventSourceName : Source of event
- EventTimeCreated : Local machine time when event was generated
- EventType : Event type (i.e. Info, warning, error...)
- EventUserName : Username who logged this event
Methods
- CreateEventSource : This method Creates a new Event source
- DeleteEventSource : This method deletes an exsisting Event Source
- OpenLog : This method opens a specified log from a local/remote machine for processing. This is the first method you have to call before read/write to event log
- CloseLog : This method closes any previously openeded log.
- ClearLog : This method deletes all records from a specified Log file
- BackupLog : This method takes backup of entire Log.
- IsLogOpened : This method returns true if log is opened by current instance of CEventLog class.
- ReadEntry : Reads a single record specified by position number in the log file.
- LogNTEvent : Writes a single entry to the opened logfile.
- GetTotalRecords : returns total number of records in the opened log file
Lets start our class implementation with declaration section |
Click here to copy the following block | Private Const BASE_KEY = "System\CurrentControlSet\Services\EventLog"
Private Enum enumEventLogReadFlags EVENTLOG_SEQUENTIAL_READ = &H1& EVENTLOG_SEEK_READ = &H2& EVENTLOG_FORWARDS_READ = &H4& EVENTLOG_BACKWARDS_READ = &H8& End Enum
Enum enumLogEntryTypes EVENTLOG_SUCCESS = &H0& EVENTLOG_ERROR_TYPE = &H1& EVENTLOG_WARNING_TYPE = &H2& EVENTLOG_INFORMATION_TYPE = &H4& EVENTLOG_AUDIT_SUCCESS = &H8& EVENTLOG_AUDIT_FAILURE = &H10& End Enum
Private Enum enumEventLogWriteFlags EVENTLOG_START_PAIRED_EVENT = &H1& EVENTLOG_END_PAIRED_EVENT = &H2& EVENTLOG_END_ALL_PAIRED_EVENTS = &H4& EVENTLOG_PAIRED_EVENT_ACTIVE = &H8& EVENTLOG_PAIRED_EVENT_INACTIVE = &H10& End Enum
Private Type EVENTLOGRECORD length As Long Reserved As Long RecordNumber As Long TimeGenerated As Long TimeWritten As Long EventId As Long EventType As Integer NumStrings As Integer EventCategory As Integer ReservedFlags As Integer ClosingRecordNumber As Long StringOffset As Long UserSidLength As Long UserSidOffset As Long DataLength As Long DataOffset As Long End Type
Private Const ERROR_INSUFFICIENT_BUFFER = 122&
Private m_EventTimeWritten As Date Private m_EventTimeCreated As Date Private m_EventSourceName As String Private m_EventUserName As String Private m_EventUserSID As String Private m_EventComputerName As String Private m_EventType As String Private m_EventDescription As String Private m_EventCategoryString As String
Dim EventRecord As EVENTLOGRECORD
Private m_hEventLog As Long Private m_EventLogMachine As String Private m_EventLogName As String
Private colCategoryFileLib As New Collection Private colMessageFileLib As New Collection Private colParaMessageFileLib As New Collection
Private Enum LibType MessgeFileLib = 1 CategoryFileLib = 2 ParameterFileLib = 3 End Enum
Private Declare Function OpenEventLog Lib "advapi32.dll" Alias "OpenEventLogA" ( _ ByVal lpUNCServerName As String, ByVal lpSourceName As String) As Long
Private Declare Function CloseEventLog Lib "advapi32.dll" ( _ ByVal hEventLog As Long) As Long
Private Declare Function BackupEventLog Lib "advapi32.dll" Alias "BackupEventLogA" ( _ ByVal hEventLog As Long, ByVal lpBackupFileName As String) As Long
Private Declare Function ClearEventLog Lib "advapi32.dll" Alias "ClearEventLogA" ( _ ByVal hEventLog As Long, ByVal lpBackupFileName As String) As Long
Private Declare Function GetNumberOfEventLogRecords Lib "advapi32.dll" ( _ ByVal hEventLog As Long, NumberOfRecords As Long) As Long
Private Declare Function GetOldestEventLogRecord Lib "advapi32.dll" ( _ ByVal hEventLog As Long, OldestRecord As Long) As Long
Private Declare Function ReportEvent Lib "advapi32.dll" Alias _ "ReportEventA" ( _ ByVal hEventLog As Long, ByVal wType As Integer, _ ByVal wCategory As Integer, ByVal dwEventID As Long, _ ByVal lpUserSid As Any, ByVal wNumStrings As Integer, _ ByVal dwDataSize As Long, plpStrings As Long, _ lpRawData As Any) As Boolean
Private Declare Function ReadEventLog Lib "advapi32.dll" Alias "ReadEventLogA" ( _ ByVal hEventLog As Long, _ ByVal dwReadFlags As Long, _ ByVal dwRecordOffset As Long, _ lpBuffer As Any, _ ByVal nNumberOfBytesToRead As Long, _ pnBytesRead As Long, _ pnMinNumberOfBytesNeeded As Long) As Long
Private Declare Function RegisterEventSource Lib "advapi32.dll" Alias _ "RegisterEventSourceA" (ByVal lpUNCServerName As String, _ ByVal lpSourceName As String) As Long
Private Declare Function DeregisterEventSource Lib "advapi32.dll" ( _ ByVal hEventLog As Long) As Long
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" ( _ hpvDest As Any, hpvSource As Any, _ ByVal cbCopy As Long)
Private Declare Sub MoveMem Lib "kernel32" Alias "RtlMoveMemory" ( _ pTo As Any, _ uFrom As Any, _ ByVal lSize As Long)
Private Declare Function GlobalAlloc Lib "kernel32" ( _ ByVal wFlags As Long, _ ByVal dwBytes As Long) As Long
Private Declare Function GlobalFree Lib "kernel32" ( _ ByVal hMem As Long) As Long
Private Declare Function LookupAccountSid Lib "advapi32.dll" Alias "LookupAccountSidA" ( _ ByVal lpSystemName As String, _ Sid As Any, _ ByVal name As String, _ cbName As Long, _ ByVal ReferencedDomainName As String, _ cbReferencedDomainName As Long, _ peUse As Long) As Long
Private Declare Function MultiByteToWideChar Lib "kernel32" ( _ ByVal CodePage As Long, _ ByVal dwFlags As Long, _ lpMultiByteStr As Any, _ ByVal cchMultiByte As Long, _ lpWideCharStr As Any, _ ByVal cchWideChar As Long) As Long
Private Declare Function lstrlenA Lib "kernel32" ( _ lpString As Any) As Long
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 As String * 64 StandardDate As SYSTEMTIME StandardBias As Long DaylightName As String * 64 DaylightDate As SYSTEMTIME DaylightBias As Long End Type
Private Declare Function LoadLibraryEx Lib "kernel32" Alias "LoadLibraryExA" ( _ ByVal lpLibFileName As String, _ ByVal hFile As Long, _ ByVal dwFlags As Long) As Long
Private Declare Function FreeLibrary Lib "kernel32" ( _ ByVal hLibModule As Long) As Long
Private Declare Function ExpandEnvironmentStrings Lib "kernel32" Alias "ExpandEnvironmentStringsA" ( _ ByVal lpSrc As String, _ ByVal lpDst As String, _ ByVal nSize As Long) As Long
Private Const DONT_RESOLVE_DLL_REFERENCES As Long = 1& Private Const LOAD_LIBRARY_AS_DATAFILE As Long = 2& Private Const LOAD_WITH_ALTERED_SEARCH_PATH As Long = 8&
Private Declare Function RegOpenKeyEx Lib "advapi32" Alias "RegOpenKeyExA" ( _ ByVal hKey As Long, _ ByVal lpSubKey As String, _ ByVal ulOptions As Long, _ ByVal samDesired As Long, _ phkResult As Long) As Long
Private Declare Function RegCloseKey Lib "advapi32" (ByVal hKey As Long) As Long
Private Declare Function RegCreateKeyEx Lib "advapi32" Alias "RegCreateKeyExA" ( _ ByVal hKey As Long, _ ByVal lpSubKey As String, _ ByVal Reserved As Long, _ ByVal lpClass As String, _ ByVal dwOptions As Long, _ ByVal samDesired As Long, _ lpSecurityAttributes As SECURITY_ATTRIBUTES, _ phkResult As Long, _ lpdwDisposition As Long) As Long
Private Declare Function RegDeleteKey Lib "advapi32.dll" Alias "RegDeleteKeyA" ( _ ByVal hKey As Long, _ ByVal lpSubKey As String) As Long
Private Declare Function RegSetValueEx Lib "advapi32.dll" Alias "RegSetValueExA" ( _ ByVal hKey As Long, _ ByVal lpValueName As String, _ ByVal Reserved As Long, _ ByVal dwType As Long, _ lpData As Any, _ ByVal cbData As Long) As Long
Private Declare Function RegFlushKey Lib "advapi32.dll" (ByVal hKey As Long) As Long
Private Declare Function RegQueryValueEx Lib "advapi32.dll" Alias "RegQueryValueExA" ( _ ByVal hKey As Long, _ ByVal lpValueName As String, _ ByVal lpReserved As Long, _ lpType As Long, _ lpData As Any, _ lpcbData As Long) As Long
Private Type SECURITY_ATTRIBUTES length As Long SecurityDescriptor As Long InheritHandle As Long End Type
Private Const REG_NONE As Long = 0& Private Const REG_SZ As Long = 1& Private Const REG_EXPAND_SZ As Long = 2& Private Const REG_BINARY As Long = 3 Private Const REG_DWORD As Long = 4& Private Const REG_DWORD_LITTLE_ENDIAN As Long = 4& Private Const REG_DWORD_BIG_ENDIAN As Long = 5& Private Const REG_LINK As Long = 6& Private Const REG_MULTI_SZ As Long = 7& Private Const REG_RESOURCE_LIST As Long = 8& Private Const REG_FULL_RESOURCE_DESCRIPTOR As Long = 9& Private Const REG_RESOURCE_REQUIREMENTS_LIST As Long = 10
Private Const KEY_QUERY_VALUE As Long = &H1& Private Const KEY_SET_VALUE As Long = &H2& Private Const KEY_CREATE_SUB_KEY As Long = &H4& Private Const KEY_ENUMERATE_SUB_KEYS As Long = &H8& Private Const KEY_NOTIFY As Long = &H10& Private Const KEY_CREATE_LINK As Long = &H20& Private Const READ_CONTROL As Long = &H20000 Private Const WRITE_DAC As Long = &H40000 Private Const WRITE_OWNER As Long = &H80000 Private Const SYNCHRONIZE As Long = &H100000 Private Const STANDARD_RIGHTS_REQUIRED As Long = &HF0000 Private Const STANDARD_RIGHTS_READ As Long = READ_CONTROL Private Const STANDARD_RIGHTS_WRITE As Long = READ_CONTROL Private Const STANDARD_RIGHTS_EXECUTE As Long = READ_CONTROL Private Const KEY_READ As Long = STANDARD_RIGHTS_READ Or _ KEY_QUERY_VALUE Or _ KEY_ENUMERATE_SUB_KEYS Or _ KEY_NOTIFY Private Const KEY_WRITE As Long = STANDARD_RIGHTS_WRITE Or _ KEY_SET_VALUE Or _ KEY_CREATE_SUB_KEY Private Const KEY_EXECUTE As Long = KEY_READ
Private Const REG_OPTION_NON_VOLATILE As Long = 0& Private Const HKEY_LOCAL_MACHINE As Long = &H80000002
Private Const FORMAT_MESSAGE_ALLOCATE_BUFFER = &H100& Private Const FORMAT_MESSAGE_IGNORE_INSERTS = &H200& Private Const FORMAT_MESSAGE_FROM_STRING = &H400& Private Const FORMAT_MESSAGE_FROM_HMODULE = &H800 Private Const FORMAT_MESSAGE_ARGUMENT_ARRAY = &H2000
Private Declare Function FormatMessage Lib "kernel32" Alias "FormatMessageA" ( _ ByVal dwFlags As Long, _ lpSource As Any, _ ByVal dwMessageId As Long, _ ByVal dwLanguageId As Long, _ lpBuffer As Any, _ ByVal nSize As Long, _ Arguments As Long) As Long |
We will write our clean up code in Class_Terminate event as shown below |
Click here to copy the following block | Private Sub Class_Terminate() CloseLog End Sub
Public Function CloseLog() If IsLogOpened = True Then CloseEventLog m_hEventLog m_hEventLog = 0 End If End Function
Public Function IsLogOpened() As Boolean IsLogOpened = IIf(m_hEventLog = 0, False, True) End Function |
m_hEventLog is a handle to event log which is returned when you call OpenEventLog API
I have wrapped OpenEventLog API in a Public function as shown below. You have to call OpenEventLog before you call any other function except CreateEventSource and DeleteEventSource. |
Click here to copy the following block | Public Function OpenLog(Optional ByVal MachineName As String = "", Optional ByVal LogName As String = "Application") As Boolean On Error GoTo errHandler
Call CloseLog
m_EventLogMachine = MachineName m_hEventLog = OpenEventLog(m_EventLogMachine, LogName)
m_EventLogName = LogName
If IsLogOpened = True Then OpenLog = True
Exit Function errHandler: CloseLog End Function |
As you learned in previous article that you have to create your own Event Source before you start logging to EventLog. Creating Event Source requires few entries in registry. lets implement some registry function which we will use for CreateEventSource and DeleteEventSource. |
Click here to copy the following block |
Public Function CreateEventSource(Optional ByVal strMessageFile As String = "", _ Optional ByVal strCategoryFile As String = "", _ Optional ByVal strParaMsgFile As String = "", _ Optional ByVal strSourceName As String = "Binaryworld", _ Optional ByVal strLogName As String = "Application", _ Optional ByVal NumCategories As Long) As Boolean
Dim strSubKey As String Dim lngPtrValData As Long
If strMessageFile = "" Then strMessageFile = App.Path & IIf(Right(App.Path, 1) <> "\", "\", "") & App.EXEName & ".exe"
strSubKey = BASE_KEY & "\" & strLogName & "\" & strSourceName
CreateRegistryKey HKEY_LOCAL_MACHINE, strSubKey
If WriteToRegistry(strSubKey, "EventMessageFile", strMessageFile) = False Then Err.Raise Err.LastDllError, "CEventLog.CreateEventSource", "Error#" & Err.LastDllError End If
If strCategoryFile <> "" Then If WriteToRegistry(strSubKey, "CategoryMessageFile", strCategoryFile) = False Then Err.Raise Err.LastDllError, "CEventLog.CreateEventSource", "Error#" & Err.LastDllError End If End If
If strParaMsgFile <> "" Then If WriteToRegistry(strSubKey, "ParameterMessageFile", strParaMsgFile) = False Then Err.Raise Err.LastDllError, "CEventLog.CreateEventSource", "Error#" & Err.LastDllError End If End If
If WriteToRegistry(strSubKey, "CategoryCount", NumCategories, , REG_DWORD) = False Then Err.Raise Err.LastDllError, "CEventLog.CreateEventSource", "Error#" & Err.LastDllError End If
lngPtrValData = EVENTLOG_ERROR_TYPE Or _ EVENTLOG_WARNING_TYPE Or _ EVENTLOG_INFORMATION_TYPE
If WriteToRegistry(strSubKey, "TypesSupported", lngPtrValData, , REG_DWORD) = False Then Err.Raise Err.LastDllError, "CEventLog.CreateEventSource", "Error#" & Err.LastDllError End If CreateEventSource = True End Function
Public Function DeleteEventSource(Optional strSourceName As String = "Binaryworld", Optional strLogName As String = "Application") As Boolean Dim strSubKey As String, ret As Long strSubKey = BASE_KEY & "\" & strLogName & "\" & strSourceName ret = RegDeleteKey(HKEY_LOCAL_MACHINE, strSubKey) If ret = 0 Then DeleteEventSource = True End Function
Private Function CreateRegistryKey(Optional RootKey = HKEY_LOCAL_MACHINE, _ Optional strSubKey) As Boolean
On Error GoTo errHandler
Dim ret As Long, lngKeyHandle As Long, lngResKey As Long, lngDisposition As Long Dim typSecAttrib As SECURITY_ATTRIBUTES
ret = RegCreateKeyEx(hKey:=HKEY_LOCAL_MACHINE, _ lpSubKey:=strSubKey, _ Reserved:=0&, _ lpClass:="", _ dwOptions:=REG_OPTION_NON_VOLATILE, _ samDesired:=KEY_WRITE, _ lpSecurityAttributes:=typSecAttrib, _ phkResult:=lngResKey, _ lpdwDisposition:=lngDisposition)
If ret <> 0 Then ret = RegCloseKey(hKey:=lngResKey) Exit Function End If
ret = RegOpenKeyEx(hKey:=RootKey, _ lpSubKey:=strSubKey, _ ulOptions:=0&, _ samDesired:=KEY_WRITE, _ phkResult:=lngKeyHandle)
If ret <> 0 Then CreateRegistryKey = False Else CreateRegistryKey = True End If
ret = RegFlushKey(lngKeyHandle) ret = RegCloseKey(lngKeyHandle) Exit Function errHandler: End Function
Private Function WriteToRegistry(Optional strSubKey, Optional strValueName As String, Optional ValueData, _ Optional RootKey = HKEY_LOCAL_MACHINE, Optional DataType = REG_EXPAND_SZ) As Boolean
On Error GoTo errHandler Dim ret As Long, lngKeyHandle As Long
ret = RegOpenKeyEx(hKey:=RootKey, _ lpSubKey:=strSubKey, _ ulOptions:=0&, _ samDesired:=KEY_WRITE, _ phkResult:=lngKeyHandle)
If ret <> 0 Then ret = RegCloseKey(lngKeyHandle) Exit Function End If
If DataType = REG_EXPAND_SZ Or DataType = REG_SZ Or DataType = REG_MULTI_SZ Then ret = RegSetValueEx(lngKeyHandle, _ strValueName, _ 0, _ DataType, _ ByVal CStr(ValueData), _ Len(ValueData)) ElseIf DataType = REG_DWORD Then Dim lngValData As Long lngValData = CLng(ValueData) ret = RegSetValueEx(lngKeyHandle, _ strValueName, _ 0, _ DataType, _ lngValData, _ Len(lngValData)) Else ret = RegSetValueEx(lngKeyHandle, _ strValueName, _ 0, _ DataType, _ ValueData, _ Len(ValueData)) End If
If ret <> 0 Then WriteToRegistry = False Else WriteToRegistry = True End If ret = RegFlushKey(lngKeyHandle) ret = RegCloseKey(lngKeyHandle) Exit Function errHandler: End Function
Private Function ReadFromRegistry(ByVal RootKey As Long, ByVal strSubKey As String, ByVal strValueName As String) As String Dim hKey As Long Dim value As String Dim length As Long, value_type As Long
If RegOpenKeyEx(RootKey, strSubKey, 0&, KEY_QUERY_VALUE, hKey) <> 0 Then Exit Function End If
If RegQueryValueEx(hKey, strValueName, 0&, value_type, ByVal 0&, length) <> 0 Then Exit Function End If
value = Space$(length) If RegQueryValueEx(hKey, strValueName, 0&, value_type, ByVal value, length) <> 0 Then Exit Function Else ReadFromRegistry = Left$(value, length - 1) End If
RegCloseKey hKey End Function |
|