Display of "Modified Date" in workbook


Posted by Charlie Carroll on July 13, 2001 3:11 PM

I know Excel keeps "Created," "Modified," "Printed," and "Accessed" dates and would like to be able to display them in the workbook itself. Cannot find these as a function or field.

Posted by Russell on July 13, 2001 5:09 PM


Ok, this one is pretty long. I've combined some stuff that I've gathered from Chip Pearson's site and from the VBA Developer's Handbook by Ken Getz and Mike Gilbert. I'm going to paste in all the code you need (plus some you don't - sorry, but I didn't want to go through and delete the other functions). At the end, I'll show you what formula to put in your workbook to carry this off. Somebody please email me if I shouldn't be posting this. I think since I'm giving them credit it's ok? Also, there were 2 different modules from the VBA book, so you can either combine them or separate them -- it's easy to tell where by the second set of constants.

' From "VBA Developer's Handbook"
' by Ken Getz and Mike Gilbert
' Copyright 1997; Sybex, Inc. All rights reserved.

' Examples from Chapter 12

' Security attributes for CreateFile, but we don't use them
Type SECURITY_ATTRIBUTES
nLength As Long
lpSecurityDescriptor As Long
bInheritHandle As Boolean
End Type

' API CreateFile function creates and opens files
Private Declare Function CreateFile Lib "kernel32" _
Alias "CreateFileA" _
(ByVal lpFileName As String, _
ByVal dwDesiredAccess As Long, _
ByVal dwShareMode As Long, _
lpSecurityAttributes As Any, _
ByVal dwCreationDisposition As Long, _
ByVal dwFlagsAndAttributes As Long, _
ByVal hTemplateFile As Long) As Long

Declare Function dhapi_CloseHandle Lib "kernel32" _
Alias "CloseHandle" (ByVal hObject As Long) As Long

' File open mode constants
Public Const GENERIC_READ = &H80000000
Public Const GENERIC_WRITE = &H40000000
Public Const GENERIC_EXECUTE = &H20000000
Public Const GENERIC_ALL = &H10000000

Public Const FILE_SHARE_READ = &H1
Public Const FILE_SHARE_WRITE = &H2

' File attributes
Public Const FILE_ATTRIBUTE_READONLY = &H1
Public Const FILE_ATTRIBUTE_HIDDEN = &H2
Public Const FILE_ATTRIBUTE_SYSTEM = &H4
Public Const FILE_ATTRIBUTE_DIRECTORY = &H10
Public Const FILE_ATTRIBUTE_ARCHIVE = &H20
Public Const FILE_ATTRIBUTE_NORMAL = &H80
Public Const FILE_ATTRIBUTE_TEMPORARY = &H100
Public Const FILE_ATTRIBUTE_COMPRESSED = &H800

Public Const CREATE_NEW = 1
Public Const CREATE_ALWAYS = 2
Public Const OPEN_EXISTING = 3
Public Const OPEN_ALWAYS = 4
Public Const TRUNCATE_EXISTING = 5

Public Const FILE_BEGIN = 0
Public Const FILE_CURRENT = 1
Public Const FILE_END = 2

Public Const FILE_FLAG_WRITE_THROUGH = &H80000000
Public Const FILE_FLAG_OVERLAPPED = &H40000000
Public Const FILE_FLAG_NO_BUFFERING = &H20000000
Public Const FILE_FLAG_RANDOM_ACCESS = &H10000000
Public Const FILE_FLAG_SEQUENTIAL_SCAN = &H8000000
Public Const FILE_FLAG_DELETE_ON_CLOSE = &H4000000
Public Const FILE_FLAG_BACKUP_SEMANTICS = &H2000000
Public Const FILE_FLAG_POSIX_SEMANTICS = &H1000000


Function dhQuickOpenFile(strFile As String, _
Optional lngMode As Long = GENERIC_READ) As Long

' Returns a Windows API file handle for use in other
' API functions that require them.

' From "VBA Developer's Handbook"
' by Ken Getz and Mike Gilbert
' Copyright 1997; Sybex, Inc. All rights reserved.

' In:
' strFile
' Path to a file.
' lngMode (Optional, default = GENERIC_READ)
' Open mode. See constants in the declaration
' section.
' Out:
' Return Value:
' Value handle or -1 if error.
' Note:
' Make sure you close open files using the
' CloseHandle API function
' Example:
' Dim hFile As Long
'
' hFile = dhQuickOpenFile("C:\AUTOEXEC.BAT")
' If hFile > 0 Then
' Call dhapi_CloseHandle(hFile)
' End If

' Call CreateFile to open the file in
' read-only, shared mode unless the user
' has passed a different access method--
' return the resulting file handle
dhQuickOpenFile = CreateFile(strFile, lngMode, _
FILE_SHARE_READ Or FILE_SHARE_WRITE, _
ByVal 0&, OPEN_EXISTING, _
FILE_ATTRIBUTE_NORMAL Or _
FILE_FLAG_RANDOM_ACCESS, 0&)

End Function

Option Explicit

' From "VBA Developer's Handbook"
' by Ken Getz and Mike Gilbert
' Copyright 1997; Sybex, Inc. All rights reserved.

' Examples from Chapter 12

Type SYSTEMTIME
intYear As Integer
intMonth As Integer
intDayOfWeek As Integer
intDay As Integer
intHour As Integer
intMinute As Integer
intSecond As Integer
intMilliseconds As Integer
End Type

Type FILETIME
lngLowDateTime As Long
lngHighDateTime As Long
End Type

Type dhtypFileTimes
datCreated As Date
datAccessed As Date
datModified As Date
End Type

Type TIME_ZONE_INFORMATION
Bias As Long
StandardName(32) As Integer
StandardDate As SYSTEMTIME
StandardBias As Long
DaylightName(32) As Integer
DaylightDate As SYSTEMTIME
DaylightBias As Long
End Type

' Functions for system time
Private Declare Sub GetLocalTime Lib "kernel32" (lpSysTime As SYSTEMTIME)
Private Declare Sub GetSystemTime Lib "kernel32" (lpSysTime As SYSTEMTIME)

' Functions for time zone information
Private Declare Function GetTimeZoneInformation Lib "kernel32" (lpTimeZoneInformation As TIME_ZONE_INFORMATION) As Long
Private Declare Function SetTimeZoneInformation Lib "kernel32" (lpTimeZoneInformation As TIME_ZONE_INFORMATION) As Long

' Routines to convert back and forth
' between system time and file time
Private Declare Function SystemTimeToFileTime Lib "kernel32" (lpSystemTime As SYSTEMTIME, lpFileTime As FILETIME) As Long
Private Declare Function FileTimeToLocalFileTime Lib "kernel32" (lpFileTime As FILETIME, lpLocalFileTime As FILETIME) As Long
Private Declare Function LocalFileTimeToFileTime Lib "kernel32" (lpLocalFileTime As FILETIME, lpFileTime As FILETIME) As Long
Private Declare Function FileTimeToSystemTime Lib "kernel32" (lpFileTime As FILETIME, lpSystemTime As SYSTEMTIME) As Long

' Functions for getting/setting/comparing file times
Private Declare Function GetFileTime Lib "kernel32" _
(ByVal hFile As Long, lpCreationTime As FILETIME, _
lpLastAccessTime As FILETIME, _
lpLastWriteTime As FILETIME) As Long

Private Declare Function SetFileTime Lib "kernel32" _
(ByVal hFile As Long, lpCreationTime As FILETIME, _
lpLastAccessTime As FILETIME, _
lpLastWriteTime As FILETIME) As Long

Private Declare Function CompareFileTime Lib "kernel32" _
(lpFileTime1 As FILETIME, lpFileTime2 As FILETIME) As Long

' Our own time constants
Public Const dhcFileTimeCreated = 1
Public Const dhcFileTimeAccessed = 2
Public Const dhcFileTimeModified = 4

Sub VBATimeToSysTime(datTime As Date, stSysTime As SYSTEMTIME)

' Converts a VBA date/time to SYSTEMTIME.

' From "VBA Developer's Handbook"
' by Ken Getz and Mike Gilbert
' Copyright 1997; Sybex, Inc. All rights reserved.

' In:
' datTime
' VBA date/time value.
' stSysTime
' Pointer to SYSTEMTIME variable.
' Out:
' stSysTime
' Converted date/time.
' Return Value:
' n/a
' Example:
' Dim stCurrent As SYSTEMTIME
'
' Call VBATimeToSysTime(Now, stCurrent)

' Fill in the structure with date and time parts
With stSysTime
.intMonth = Month(datTime)
.intDay = Day(datTime)
.intYear = Year(datTime)

.intHour = Hour(datTime)
.intMinute = Minute(datTime)
.intSecond = Second(datTime)
End With
End Sub

Function FileTimeToVBATime(ftFileTime As FILETIME, _
Optional fLocal As Boolean = True) As Date

' Converts Windows FILETIME date/time value to VBA.

' From "VBA Developer's Handbook"
' by Ken Getz and Mike Gilbert
' Copyright 1997; Sybex, Inc. All rights reserved.

' In:
' ftFileTime
' Pointer to FILETIME variable.
' fLocal (Optional, default = True)
' If True, time is expressed in local time,
' otherwise time is expressed in GMT.
' Out:
' Return Value:
' VBA date/time value.
' Example:
' Dim ft As FILETIME
' Dim datTime as Date
'
' Call GetFileTime(ft, ft, ft)
'
' datTime = FileTimeToVBATime(ft)


Dim stSystem As SYSTEMTIME
Dim ftLocalFileTime As FILETIME

' If the user wants local time, convert the file
' time to local file time
If fLocal Then
Call FileTimeToLocalFileTime(ftFileTime, ftLocalFileTime)
ftFileTime = ftLocalFileTime
End If

' Convert the file time to system time then
' call our own function to convert to VBA time
If CBool(FileTimeToSystemTime(ftFileTime, stSystem)) Then
FileTimeToVBATime = SysTimeToVBATime(stSystem)
End If
End Function

Sub VBATimeToFileTime(datTime As Date, ftTime As FILETIME, _
Optional fLocal As Boolean = True)

' Converts VBA date/time value to FILETIME.

' From "VBA Developer's Handbook"
' by Ken Getz and Mike Gilbert
' Copyright 1997; Sybex, Inc. All rights reserved.

' In:
' datTime
' VBA date/time value.
' ftTime
' Pointer to FILETIME variable.
' fLocal (Optional, default = True)
' If True, time is expressed in local time,
' otherwise time is expressed in GMT.
' Out:
' ftTime
' Converted date/time information.
' Return Value:
' n/a
' Example:
' Dim ft As FILETIME
'
' Call VBATimeToFileTime(Now, ft)

Dim stSystem As SYSTEMTIME
Dim ftSystem As FILETIME

' Call our function to convert the VBA time to
' system time
Call VBATimeToSysTime(datTime, stSystem)

' Convert the system time to file time
If CBool(SystemTimeToFileTime(stSystem, ftTime)) Then

' If the VBA time was local time, convert the
' local file time to system file time
If fLocal Then
Call LocalFileTimeToFileTime(ftTime, ftSystem)
ftTime = ftSystem
End If
End If
End Sub

Function dhGetFileTimes(strFile As String, _
dftTimes As dhtypFileTimes) As Boolean

' Retrieves file times (created, modified,
' accessed) for a given file.

' From "VBA Developer's Handbook"
' by Ken Getz and Mike Gilbert
' Copyright 1997; Sybex, Inc. All rights reserved.

' In:
' strFile
' Path to an existing file.
' dftTimes
' Pointer to a dhtypFileTimes structure.
' Out:
' dftTimes
' All three file time values.
' Return Value:
' True if successful, False if not.
' Example:
' Dim dft As dhtypFileTimes
'
' Call dhGetFileTimes("C:\AUTOEXEC.BAT", dft)

Dim ftCreate As FILETIME
Dim ftAccess As FILETIME
Dim ftWrite As FILETIME
Dim hFile As Long
Dim lngRet As Long

' Open the file
hFile = dhQuickOpenFile(strFile)
If hFile > 0 Then

' Call GetFileTime to fetch time information
' into the local FILETIME structures
If CBool(GetFileTime(hFile, ftCreate, _
ftAccess, ftWrite)) Then

' If successful, convert the values to
' VBA Date format and return them in
' the passed dhtypFileTimes structure
With dftTimes
.datCreated = FileTimeToVBATime(ftCreate)
.datAccessed = FileTimeToVBATime(ftAccess)
.datModified = FileTimeToVBATime(ftWrite)
End With

' Return success
dhGetFileTimes = True
End If

' Close the file
Call dhapi_CloseHandle(hFile)
End If
End Function

Function dhGetFileTimesEx(strFile As String, _
Optional intTime As Integer = dhcFileTimeModified) _
As Date

' Retrieves a single file time value for a given file.

' From "VBA Developer's Handbook"
' by Ken Getz and Mike Gilbert
' Copyright 1997; Sybex, Inc. All rights reserved.

' In:
' strFile
' Path to an existing file.
' intTime (Optional, default = dhcFileTimeModified)
' Specifies which time value to retrieve. Value is
' one the following constants:
' dhcFileTimeCreated
' dhcFileTimeModified
' dhcFileTimeAccessed
' Out:
' Return Value:
' File time as a VBA date/time value.
' Example:
' Dim datTime As Date
'
' datTime = dhGetFileTimesEx("C:\AUTOEXEC.BAT", _
' dhcFileTimeCreated)

Dim ftCreate As FILETIME
Dim ftAccess As FILETIME
Dim ftWrite As FILETIME
Dim hFile As Long
Dim lngRet As Long

' Open the file
hFile = dhQuickOpenFile(strFile)
If hFile > 0 Then

' If successful, get the file times
If CBool(GetFileTime(hFile, ftCreate, _
ftAccess, ftWrite)) Then

' Return the requested time
Select Case intTime
Case dhcFileTimeCreated
dhGetFileTimesEx = _
FileTimeToVBATime(ftCreate)
Case dhcFileTimeAccessed
dhGetFileTimesEx = _
FileTimeToVBATime(ftAccess)
Case dhcFileTimeModified
dhGetFileTimesEx = _
FileTimeToVBATime(ftWrite)
End Select
End If

' Close the file
dhapi_CloseHandle hFile
End If
End Function

Function dhSetFileTimes(strFile As String, _
dftTimes As dhtypFileTimes) As Boolean

' Sets file times for a specified file.

' From "VBA Developer's Handbook"
' by Ken Getz and Mike Gilbert
' Copyright 1997; Sybex, Inc. All rights reserved.

' In:
' strFile
' Path to an existing file.
' dftTimes
' Pointer to dhtypFileTimes structure containing
' new file time information.
' Out:
' Return Value:
' True if successful, False if not.
' Example:
' Dim dft As dhtypFileTimes
'
' With dft
' .datCreated = #1/1/97#
' .datModified = #1/1/97#
' .datAccessed = #1/1/97#
' End With
'
' Call dhSetFileTimes("C:\AUTOEXEC.BAT", dft)

Dim ftCreated As FILETIME
Dim ftAccessed As FILETIME
Dim ftModified As FILETIME
Dim hFile As Long

' Open the file for write access
hFile = dhQuickOpenFile(strFile, GENERIC_WRITE)

' If successful then...
If hFile > 0 Then

' Convert the passed time to a FILETIME
With dftTimes
Call VBATimeToFileTime(.datCreated, ftCreated)
Call VBATimeToFileTime(.datAccessed, ftAccessed)
Call VBATimeToFileTime(.datModified, ftModified)
End With

' Set the times
If CBool(SetFileTime(hFile, ftCreated, _
ftAccessed, ftModified)) Then

' Return success
dhSetFileTimes = True
End If

' Close the file
Call dhapi_CloseHandle(hFile)
End If
End Function

Function dhSetFileTimesEx(strFile As String, _
datTime As Date, Optional intTimes As Integer = _
(dhcFileTimeAccessed Or dhcFileTimeModified)) As Boolean

' Sets one or more file time values to a given value.

' From "VBA Developer's Handbook"
' by Ken Getz and Mike Gilbert
' Copyright 1997; Sybex, Inc. All rights reserved.

' In:
' strFile
' Path to an existing file.
' datTime
' VBA date/time value.
' intTimes (Optional)
' Bitmask of flags specifying which file time value
' to change. Can be a combination of:
' dhcFileTimeCreated
' dhcFileTimeModified
' dhcFileTimeAccessed
' Out:
' Return Value:
' True if successful, False if not.
' Example:
' Call dhSetFileTimesEx("C:\AUTOEXEC.BAT", _
' #1/1/97#, dhcFileTimeCreated)

Dim ftIn As FILETIME
Dim ftCreated As FILETIME
Dim ftAccessed As FILETIME
Dim ftModified As FILETIME
Dim hFile As Long

' Open the file for write access
hFile = dhQuickOpenFile(strFile, GENERIC_WRITE)

' If successful then...
If hFile > 0 Then

' Convert the passed time to a FILETIME
Call VBATimeToFileTime(datTime, ftIn)

' Get current values
If CBool(GetFileTime(hFile, ftCreated, _
ftAccessed, ftModified)) Then

' Check the times-to-set flags
If (intTimes And dhcFileTimeCreated) <> 0 Then
ftCreated = ftIn
End If
If (intTimes And dhcFileTimeAccessed) <> 0 Then
ftAccessed = ftIn
End If
If (intTimes And dhcFileTimeModified) <> 0 Then
ftModified = ftIn
End If

' Set the times
If CBool(SetFileTime(hFile, ftCreated, _
ftAccessed, ftModified)) Then
dhSetFileTimesEx = True
End If

' Close the file
Call dhapi_CloseHandle(hFile)
End If
End If
End Function

Function dhCompareFileTime(strFile1 As String, _
strFile2 As String, Optional intTime As _
Integer = dhcFileTimeModified) As Long

' Compares a given file time for two files.

' From "VBA Developer's Handbook"
' by Ken Getz and Mike Gilbert
' Copyright 1997; Sybex, Inc. All rights reserved.

' In:
' strFile1
' Path of first file.
' strFile2
' Path fo second file.
' intTime (Optional, default = dhcFileTimeModified)
' File time value to compare. Can be one of:
' dhcFileTimeCreated
' dhcFileTimeModified
' dhcFileTimeAccessed
' Out:
' Return Value:
' Will be one of the following:
' -2: Error
' -1: File 1 time value < file 2 time value
' 0: File 1 time value = file 2 time value
' 1: File 1 time value > file 2 time value
' Example:
' Select Case dhCompareFileTime("C:\AUTOEXEC.BAT", _
' "C:\AUTOEXEC.BAK")
' Case -1
' MsgBox "AUTOEXEC.BAT is newer"
' Case 1
' MsgBox "AUTOEXEC.BAT is older"
' Case 0
' MsgBox "File dates are the same"
' Case Else
' MsgBox "Error"
' End Select

Dim ftCreate1 As FILETIME
Dim ftAccess1 As FILETIME
Dim ftWrite1 As FILETIME
Dim hFile1 As Long
Dim ftCreate2 As FILETIME
Dim ftAccess2 As FILETIME
Dim ftWrite2 As FILETIME
Dim hFile2 As Long

' Set a return value in case things go wrong
dhCompareFileTime = -2

' Open the first file
hFile1 = dhQuickOpenFile(strFile1)
If hFile1 > 0 Then

' Open the second file
hFile2 = dhQuickOpenFile(strFile2)
If hFile2 > 0 Then

' Get the file times
If CBool(GetFileTime(hFile1, ftCreate1, _
ftAccess1, ftWrite1)) Then
If CBool(GetFileTime(hFile2, ftCreate2, _
ftAccess2, ftWrite2)) Then

' Call CompareFileTime for the
' requested time and return the result
Select Case intTime
Case dhcFileTimeCreated
dhCompareFileTime = _
CompareFileTime(ftCreate1, ftCreate2)
Case dhcFileTimeAccessed
dhCompareFileTime = _
CompareFileTime(ftAccess1, ftAccess2)
Case dhcFileTimeModified
dhCompareFileTime = _
CompareFileTime(ftWrite1, ftWrite2)
End Select
End If
End If

' Close the second file
Call dhapi_CloseHandle(hFile2)
End If

' Close the first file
Call dhapi_CloseHandle(hFile1)
End If
End Function

' **************************
' Ok, here is a function that I adapted from
' Chip Pearson's site:

Public Function ThisSheetName() As String
Application.Volatile True
ThisSheetName = CStr(Application.Caller.Parent.Parent.Path) & "\" & _
CStr(Application.Caller.Parent.Parent.Name)
End Function

' *********************************

Now, in your workbook, type the following formula in the cell(s) you want the modified date (make sure you format your cell as a date):

=dhGetFileTimesEx(ThisSheetName())
*OR*
=dhGetFileTimesEx(ThisSheetName(),4) will do the same thing.

If you want to get the Creation Date:

=dhGetFileTimesEx(ThisSheetName(), 1)

And for Accessed:

=dhGetFileTimesEx(ThisSheetName(), 2)

(it seems like the accessed date gives only the date, and not the time).


Hope this helps,

Russell

Posted by Charlie Carroll on July 13, 2001 7:02 PM

hFile = dhQuickOpenFile("C:\AUTOEXEC.BAT") If hFile > 0 Then Call dhapi_CloseHandle(hFile) End If

Posted by Ivan F Moala on July 14, 2001 12:39 AM

Simplier method although the creation date may
be in error ??
Change as required....or repost.

Sub FileDates()
Dim x As Integer, sA

sA = Array("Created", "LastMod", "Printed")

For x = 1 To 3
MsgBox sA(x - 1) & ":=" & ActiveWorkbook.BuiltinDocumentProperties(x + 9)
Next

End sub

Ivan I know Excel keeps "Created," "Modified," "Printed," and "Accessed" dates and would like to be able to display them in the workbook itself. Cannot find these as a function or field.

Posted by Ivan F Moala on July 14, 2001 12:41 AM

String array error

Should be;
Sub FileDates()
Dim x As Integer, sA

sA = Array("Printed", "Created", "Modified")

For x = 1 To 3
MsgBox sA(x - 1) & ":=" & ActiveWorkbook.BuiltinDocumentProperties(x + 9)
Next
End Sub



Posted by Charlie Carroll on July 14, 2001 1:07 PM

Re: String array error

Ivan: Thanks. One interesting bit of information pointed out to me by Mr Excel Consulting is that Microsoft automatically updates the modified field when you open workbook (not taking into account that you may abandon changes or not even make any). A solution that he provided was to record (in a remote cell) the value of Now() when you know you are going to save the file and reference it where you want the display. I did this and it works. Here is the code he provided:

Private Sub Workbook_BeforeSave(ByVal SaveAsUI As Boolean, Cancel As Boolean)
' Update the Save Date
Worksheets("Tab_A").Range("Y1").Value = Now()
End Sub

The "Tab_A" obviously being my name for the worksheet. I appreciate your help and am going to use your solution to display other file properties within worksheets