Ciao, se ti può servire, questo è un esempio completo per avere informazioni dettagliate di un qualsiasi file.
nel progetto bisogna inserire un CommandButton, un CommonDialog e una ListBox

codice:
 Option Explicit
Private Declare Function GetFileInformationByHandle Lib "kernel32" (ByVal hFile As Long, lpFileInformation As BY_HANDLE_FILE_INFORMATION) As Long
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
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Private Declare Function FileTimeToSystemTime Lib "kernel32" (lpFileTime As FILETIME, lpSystemTime As SYSTEMTIME) As Long
Private Declare Function FileTimeToLocalFileTime Lib "kernel32" (lpFileTime As FILETIME, lpLocalFileTime As FILETIME) As Long

Const FILE_ATTRIBUTE_ARCHIVE = &H20 'Un file di archivio
Const FILE_ATTRIBUTE_COMPRESSED = &H800 'Un file in un drive o in una directori compressa.
Const FILE_ATTRIBUTE_DIRECTORY = &H10 'Una directory invece di un file.
Const FILE_ATTRIBUTE_HIDDEN = &H2 'File nascosto.
Const FILE_ATTRIBUTE_NORMAL = &H80 'File senza attributi.
Const FILE_ATTRIBUTE_READONLY = &H1 'File di sola lettura.
Const FILE_ATTRIBUTE_SYSTEM = &H4 'File di sistema
Const FILE_ATTRIBUTE_TEMPORARY = &H100

Const MAXDWORD = &HFFFF
Const OPEN_EXISTING = 3
Const GENERIC_READ = &H80000000

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 FILETIME
    dwLowDateTime As Long
    dwHighDateTime As Long
End Type

Private Type BY_HANDLE_FILE_INFORMATION
    dwFileAttributes As Long
    ftCreationTime As FILETIME
    ftLastAccessTime As FILETIME
    ftLastWriteTime As FILETIME
    dwVolumeSerialNumber As Long
    nFileSizeHigh As Long
    nFileSizeLow As Long
    nNumberOfLinks As Long
    nFileIndexHigh As Long
    nFileIndexLow As Long
End Type

Private Function AttribFile(attrib As Long) As String
   Dim strAttrib As String
   strAttrib = ""
   If (attrib And FILE_ATTRIBUTE_ARCHIVE) <> 0 Then
      strAttrib = "ARCHIVE/"
   End If
   If (attrib And FILE_ATTRIBUTE_COMPRESSED) <> 0 Then
      strAttrib = strAttrib & "COMPRESSED/"
   End If
   If (attrib And FILE_ATTRIBUTE_DIRECTORY) <> 0 Then
      strAttrib = strAttrib & "DIRECTORY/"
   End If
   If (attrib And FILE_ATTRIBUTE_HIDDEN) <> 0 Then
      strAttrib = strAttrib & "HIDDEN/"
   End If
   If (attrib And FILE_ATTRIBUTE_NORMAL) <> 0 Then
      strAttrib = strAttrib & "NORMAL/"
   End If
   If (attrib And FILE_ATTRIBUTE_READONLY) <> 0 Then
      strAttrib = strAttrib & "READONLY/"
   End If
   If (attrib And FILE_ATTRIBUTE_SYSTEM) <> 0 Then
      strAttrib = strAttrib & "SYSTEM/"
   End If
   If (attrib And FILE_ATTRIBUTE_TEMPORARY) <> 0 Then
      strAttrib = strAttrib & "TEMPORARY"
   End If
   AttribFile = strAttrib
End Function

Private Function DataOraFile(FT As FILETIME) As String
   Dim strData As String
   Dim strOra As String
   Dim sysTime As SYSTEMTIME
   Dim tmpFT As FILETIME
   'Convert the file time to the local file time
   FileTimeToLocalFileTime FT, tmpFT
    
   'Convert the file time to system file time
   FileTimeToSystemTime tmpFT, sysTime
   strData = CStr(sysTime.wDay) & "/" & CStr(sysTime.wMonth) & "/" & CStr(sysTime.wYear)
   strOra = CStr(sysTime.wHour) & "." & CStr(sysTime.wMinute) & "." & CStr(sysTime.wSecond)
   DataOraFile = strData & " - " & strOra
End Function

Private Function SommaValori(H As Long, L As Long) As Long
   SommaValori = (H * MAXDWORD) + L
End Function

Private Sub InfoFile(nFile As String)
    Dim hFile As Long
    Dim FileInfo As BY_HANDLE_FILE_INFORMATION
    
    If Len(Trim$(nFile)) > 0 Then
       'Recupera l'handle del file..
       hFile = CreateFile(nFile, GENERIC_READ, 0, ByVal 0&, OPEN_EXISTING, 0, ByVal 0&)
       
       'recupera le informazioni del file
       GetFileInformationByHandle hFile, FileInfo
       
       'chiude il file
       CloseHandle hFile
   
      List1.AddItem "ATTRIBUTI: " & AttribFile(FileInfo.dwFileAttributes)
      List1.AddItem "CREATION TIME: " & DataOraFile(FileInfo.ftCreationTime)
      List1.AddItem "LAST ACCESS TIME: " & DataOraFile(FileInfo.ftLastAccessTime)
      List1.AddItem "LAST WRITE TIME: " & DataOraFile(FileInfo.ftLastWriteTime)
      List1.AddItem "VOLUME SERIAL NUMBER: " & FileInfo.dwVolumeSerialNumber
      List1.AddItem "FILE SIZE: " & FormatNumber(SommaValori(FileInfo.nFileSizeHigh, FileInfo.nFileSizeLow), 0) & " bytes"
      List1.AddItem "NUMBER OF LINKS: " & FileInfo.nNumberOfLinks
      List1.AddItem "FILE INDEX: " & SommaValori(FileInfo.nFileIndexHigh, FileInfo.nFileIndexLow)
   Else
      MsgBox "Non è stato selezionato nessun file"
   End If
End Sub

Private Sub Command1_Click()
   On Error GoTo myerr
   CommonDialog1.DialogTitle = "Scegli un file..."
   CommonDialog1.CancelError = True
   CommonDialog1.ShowOpen
   
   InfoFile CommonDialog1.FileName
myerr:
   
End Sub