home *** CD-ROM | disk | FTP | other *** search
/ Chip 1999 May / Chip_1999-05_cd.bin / zkuste / vbasic / Data / Priklady / basFile.bas next >
BASIC Source File  |  1998-06-29  |  13KB  |  458 lines

  1. Attribute VB_Name = "basFile"
  2. Option Explicit
  3.  
  4. Private Const MAX_FILENAME_LEN = 256
  5.  
  6. ' File and Disk functions.
  7. Public Const DRIVE_CDROM = 5
  8. Public Const DRIVE_FIXED = 3
  9. Public Const DRIVE_RAMDISK = 6
  10. Public Const DRIVE_REMOTE = 4
  11. Public Const DRIVE_REMOVABLE = 2
  12. Public Const DRIVE_UNKNOWN = 0    'Unknown, or unable to be determined.
  13.  
  14. Private Declare Function GetDriveTypeA Lib "kernel32" (ByVal nDrive As String) As Long
  15. Private Declare Function GetVolumeInformation& Lib "kernel32" Alias "GetVolumeInformationA" (ByVal lpRootPathName As String, ByVal pVolumeNameBuffer As String, ByVal nVolumeNameSize As Long, lpVolumeSerialNumber As Long, lpMaximumComponentLength As Long, lpFileSystemFlags As Long, ByVal lpFileSystemNameBuffer As String, ByVal nFileSystemNameSize As Long)
  16. Private Declare Function GetWindowsDirectoryA Lib "kernel32" (ByVal lpBuffer As String, ByVal nSize As Long) As Long
  17. Private Declare Function GetTempPathA Lib "kernel32" (ByVal nBufferLength As Long, ByVal lpBuffer As String) As Long
  18.  
  19. Private Const UNIQUE_NAME = &H0
  20.  
  21. Private Declare Function GetTempFileNameA Lib "kernel32" (ByVal lpszPath As String, ByVal lpPrefixString As String, ByVal wUnique As Long, ByVal lpTempFileName As String) As Long   
  22. Private Declare Function GetSystemDirectoryA Lib "kernel32" (ByVal lpBuffer As String, ByVal nSize As Long) As Long
  23. Private Declare Function ShellExecute Lib "shell32.dll" Alias "ShellExecuteA" (ByVal hwnd As Long, ByVal lpOperation As String, ByVal lpFile As String, ByVal lpParameters As String, ByVal lpdirectory As String, ByVal nShowCmd As Long) As Long
  24.    
  25. Private Const SW_HIDE = 0             ' = vbHide
  26. Private Const SW_SHOWNORMAL = 1       ' = vbNormal
  27. Private Const SW_SHOWMINIMIZED = 2    ' = vbMinimizeFocus
  28. Private Const SW_SHOWMAXIMIZED = 3    ' = vbMaximizedFocus
  29. Private Const SW_SHOWNOACTIVATE = 4   ' = vbNormalNoFocus
  30. Private Const SW_MINIMIZE = 6         ' = vbMinimizedNofocus
  31.  
  32. Private Declare Function GetShortPathNameA Lib "kernel32" (ByVal lpszLongPath As String, ByVal lpszShortPath As String, ByVal cchBuffer As Long) As Long
  33.    
  34. Private Type SHFILEOPSTRUCT
  35.         hwnd As Long
  36.         wFunc As Long
  37.         pFrom As String
  38.         pTo As String
  39.         fFlags As Integer
  40.         fAborted As Boolean
  41.         hNameMaps As Long
  42.         sProgress As String
  43. End Type
  44.  
  45. Private Const FO_DELETE = &H3
  46. Private Const FOF_ALLOWUNDO = &H40
  47. Private Const FOF_SILENT = &H4
  48. Private Const FOF_NOCONFIRMATION = &H10
  49.  
  50. Private Declare Function SHFileOperation Lib "shell32.dll" Alias "SHFileOperationA" (lpFileOp As SHFILEOPSTRUCT) As Long
  51.  
  52. Private Type STARTUPINFO
  53.     cb As Long
  54.     lpReserved As String
  55.     lpDesktop As String
  56.     lpTitle As String
  57.     dwX As Long
  58.     dwY As Long
  59.     dwXSize As Long
  60.     dwYSize As Long
  61.     dwXCountChars As Long
  62.     dwYCountChars As Long
  63.     dwFillAttribute As Long
  64.     dwFlags As Long
  65.     wShowWindow As Integer
  66.     cbReserved2 As Integer
  67.     lpReserved2 As Long
  68.     hStdInput As Long
  69.     hStdOutput As Long
  70.     hStdError As Long
  71. End Type
  72.  
  73. Private Type PROCESS_INFORMATION
  74.     hProcess As Long
  75.     hThread As Long
  76.     dwProcessId As Long
  77.     dwThreadID As Long
  78. End Type
  79.  
  80. Private Const NORMAL_PRIORITY_CLASS = &H20&
  81. Private Const INFINITE = -1&
  82. Private Const SYNCHRONIZE = &H100000
  83.  
  84. Private Declare Function CloseHandle Lib "kernel32" (hObject As Long) As Boolean
  85. Private Declare Function WaitForSingleObject Lib "kernel32" (ByVal hHandle As Long, ByVal dwMilliseconds As Long) As Long    
  86. Private Declare Function CreateProcessA Lib "kernel32" (ByVal lpApplicationName As Long, ByVal lpCommandLine As String, ByVal lpProcessAttributes As Long, ByVal lpThreadAttributes As Long, ByVal bInheritHandles As Long, ByVal dwCreationFlags As Long, ByVal lpEnvironment As Long, ByVal lpCurrentDirectory As Long, lpStartupInfo As STARTUPINFO, lpProcessInformation As PROCESS_INFORMATION) As Long
  87. Private Declare Function FindExecutableA Lib "shell32.dll" (ByVal lpFile As String, ByVal lpdirectory As String, ByVal lpResult As String) As Long
  88. Private Declare Function SetVolumeLabelA Lib "kernel32" (ByVal lpRootPathName As String, ByVal lpVolumeName As String) As Long
  89.  
  90. '  Finds the executable associated with a file
  91. '
  92. '  Returns "" if no file is found.
  93. '
  94. Public Function FindExecutable(s As String) As String
  95.    Dim i As Integer
  96.    Dim s2 As String
  97.    
  98.    s2 = String(MAX_FILENAME_LEN, 32) & Chr$(0)
  99.    
  100.    i = FindExecutableA(s & Chr$(0), vbNullString, s2)
  101.    
  102.    If i > 32 Then
  103.       FindExecutable = Left$(s2, InStr(s2, Chr$(0)) - 1)
  104.    Else
  105.       FindExecutable = ""
  106.    End If
  107.    
  108. End Function
  109.  
  110.  
  111. '
  112. '  Deletes a single file, or an array of files to the trashcan.
  113. '
  114. Public Function ShellDelete(ParamArray vntFileName() As Variant) As Boolean
  115.    Dim i As Integer
  116.    Dim sFileNames As String
  117.    Dim SHFileOp As SHFILEOPSTRUCT
  118.  
  119.    For i = LBound(vntFileName) To UBound(vntFileName)
  120.       sFileNames = sFileNames & vntFileName(i) & vbNullChar
  121.    Next
  122.         
  123.    sFileNames = sFileNames & vbNullChar
  124.  
  125.    With SHFileOp
  126.       .wFunc = FO_DELETE
  127.       .pFrom = sFileNames
  128.       .fFlags = FOF_ALLOWUNDO + FOF_SILENT + FOF_NOCONFIRMATION
  129.    End With
  130.  
  131.    i = SHFileOperation(SHFileOp)
  132.    
  133.    If i = 0 Then
  134.       ShellDelete = True
  135.    Else
  136.       ShellDelete = False
  137.    End If
  138. End Function
  139. '
  140. '  Runs a command as the Shell command does but waits for the command
  141. '  to finish before returning.  Note: The full path and filename extention
  142. '  is required.
  143. '  You might want to use Environ$("COMSPEC") & " /c " & command
  144. '  if you wish to run it under the command shell (and thus it)
  145. '  will search the path etc...
  146. '
  147. '  returns false if the shell failed
  148. '
  149. Public Function ShellWait(cCommandLine As String) As Boolean
  150.     Dim NameOfProc As PROCESS_INFORMATION
  151.     Dim NameStart As STARTUPINFO
  152.     Dim i As Long
  153.  
  154.     NameStart.cb = Len(NameStart)
  155.     i = CreateProcessA(0&, cCommandLine, 0&, 0&, 1&, _
  156.         NORMAL_PRIORITY_CLASS, 0&, 0&, NameStart, NameOfProc)
  157.    
  158.     If i <> 0 Then
  159.        Call WaitForSingleObject(NameOfProc.hProcess, INFINITE)
  160.        Call CloseHandle(NameOfProc.hProcess)
  161.        ShellWait = True
  162.     Else
  163.        ShellWait = False
  164.     End If
  165.     
  166. End Function
  167.  
  168. '
  169. '  As the Execute function but waits for the process to finish before
  170. '  returning
  171. '
  172. '  returns true on success.
  173.  
  174. Public Function ExecuteWait(s As String, Optional param As Variant) As Boolean
  175.    Dim s2 As String
  176.    
  177.    s2 = FindExecutable(s)
  178.    
  179.    If s2 <> "" Then
  180.       ExecuteWait = ShellWait(s2 & _
  181.          IIf(IsMissing(param), " ", " " & CStr(param) & " ") & s)
  182.    Else
  183.       ExecuteWait = False
  184.    End If
  185. End Function
  186. '
  187. '  Adds a backslash if the string doesn't have one already.
  188. '
  189. Public Function AddBackslash(s As String) As String
  190.    If Len(s) > 0 Then
  191.       If Right$(s, 1) <> "\" Then
  192.          AddBackslash = s + "\"
  193.       Else
  194.          AddBackslash = s
  195.       End If
  196.    Else
  197.       AddBackslash = "\"
  198.    End If
  199. End Function
  200.  
  201. '
  202. ' Executes a file with it's associated program.
  203. '    windowstyle uses the same constants as the Shell function:
  204. '       vbHide   0
  205. '       vbNormalFocus  1
  206. '       vbMinimizedFocus  2
  207. '       vbMaximizedFocus  3
  208. '       vbNormalNoFocus   4
  209. '       vbMinimizedNoFocus   6
  210. '
  211. '   returns true on success
  212. Public Function Execute(ByVal hwnd As Integer, s As String, Optional param As Variant, Optional windowstyle As Variant) As Boolean
  213.    Dim i As Long
  214.    
  215.    If IsMissing(windowstyle) Then
  216.       windowstyle = vbNormalFocus
  217.    End If
  218.    
  219.    i = ShellExecute(hwnd, vbNullString, s, IIf(IsMissing(param) Or (param = ""), vbNullString, CStr(param)), GetPath(s), CLng(windowstyle))
  220.    If i > 32 Then
  221.       Execute = True
  222.    Else
  223.       Execute = False
  224.    End If
  225. End Function
  226.  
  227. '
  228. '  Returns the file portion of a file + pathname
  229. '
  230. Public Function GetFile(s As String) As String
  231.    Dim i As Integer
  232.    Dim j As Integer
  233.    
  234.    i = 0
  235.    j = 0
  236.    
  237.    i = InStr(s, "\")
  238.    Do While i <> 0
  239.       j = i
  240.       i = InStr(j + 1, s, "\")
  241.    Loop
  242.    
  243.    If j = 0 Then
  244.       GetFile = ""
  245.    Else
  246.       GetFile = Right$(s, Len(s) - j)
  247.    End If
  248. End Function
  249.  
  250. '
  251. '  Returns the path portion of a file + pathname
  252. '
  253. Public Function GetPath(s As String) As String
  254.    Dim i As Integer
  255.    Dim j As Integer
  256.    
  257.    i = 0
  258.    j = 0
  259.    
  260.    i = InStr(s, "\")
  261.    Do While i <> 0
  262.       j = i
  263.       i = InStr(j + 1, s, "\")
  264.    Loop
  265.    
  266.    If j = 0 Then
  267.       GetPath = ""
  268.    Else
  269.       GetPath = Left$(s, j)
  270.    End If
  271. End Function
  272. '
  273. '  Returns a volume's serial number
  274. '
  275. Public Function GetSerialNumber(sDrive As String) As Long
  276.    Dim ser As Long
  277.    Dim s As String * MAX_FILENAME_LEN
  278.    Dim s2 As String * MAX_FILENAME_LEN
  279.    Dim i As Long
  280.    Dim j As Long
  281.    
  282.    Call GetVolumeInformation(sDrive + ":\" & Chr$(0), s, MAX_FILENAME_LEN, ser, i, j, s2, MAX_FILENAME_LEN)
  283.    GetSerialNumber = ser
  284. End Function
  285.  
  286.  
  287. Public Function GetShortPathName(longpath As String) As String
  288.    Dim s As String
  289.    Dim i As Long
  290.    
  291.    i = Len(longpath) + 1
  292.    s = String(i, 0)
  293.    GetShortPathNameA longpath, s, i
  294.    
  295.    GetShortPathName = Left$(s, InStr(s, Chr$(0)) - 1)
  296. End Function
  297.  
  298. Public Function GetVolumeName(sDrive As String) As String
  299.    Dim ser As Long
  300.    Dim s As String * MAX_FILENAME_LEN
  301.    Dim s2 As String * MAX_FILENAME_LEN
  302.    Dim i As Long
  303.    Dim j As Long
  304.    
  305.    Call GetVolumeInformation(sDrive + ":\" & Chr$(0), s, MAX_FILENAME_LEN, ser, i, j, s2, MAX_FILENAME_LEN)
  306.    GetVolumeName = Left$(s, InStr(s, Chr$(0)) - 1)
  307. End Function
  308. '
  309. '  Sets the volume name.  Returns true on success, false on failure.
  310. '
  311. Public Function SetVolumeName(sDrive As String, n As String) As Boolean
  312.    Dim i As Long
  313.    
  314.    i = SetVolumeLabelA(sDrive + ":\" & Chr$(0), n & Chr$(0))
  315.    
  316.    SetVolumeName = IIf(i = 0, False, True)
  317. End Function
  318. '
  319. '  Returns the system directory.
  320. '
  321. Public Function GetSystemDirectory() As String
  322.    Dim s As String
  323.    Dim i As Integer
  324.    i = GetSystemDirectoryA("", 0)
  325.    s = Space(i)
  326.    Call GetSystemDirectoryA(s, i)
  327.    GetSystemDirectory = AddBackslash(Left$(s, i - 1))
  328. End Function
  329.  
  330. '
  331. '  Returns a unique tempfile name.
  332. '
  333. Public Function GetTempFileName() As String
  334.    Dim s As String
  335.    Dim s2 As String
  336.    
  337.    s2 = GetTempPath
  338.    s = Space(Len(s2) + MAX_FILENAME_LEN)
  339.    Call GetTempFileNameA(s2, App.EXEName, UNIQUE_NAME, s)
  340.    GetTempFileName = Left$(s, InStr(s, Chr$(0)) - 1)
  341. End Function
  342.  
  343. '
  344. '  Returns the path to the temp directory.
  345. '
  346. Public Function GetTempPath() As String
  347.    Dim s As String
  348.    Dim i As Integer
  349.    i = GetTempPathA(0, "")
  350.    s = Space(i)
  351.    Call GetTempPathA(i, s)
  352.    GetTempPath = AddBackslash(Left$(s, i - 1))
  353. End Function
  354.  
  355. '
  356. '  Returns the windows directory.
  357. '
  358. Public Function GetWindowsDirectory() As String
  359.    Dim s As String
  360.    Dim i As Integer
  361.    i = GetWindowsDirectoryA("", 0)
  362.    s = Space(i)
  363.    Call GetWindowsDirectoryA(s, i)
  364.    GetWindowsDirectory = AddBackslash(Left$(s, i - 1))
  365. End Function
  366.  
  367. '
  368. '  Removes the backslash from the string if it has one.
  369. '
  370. Public Function RemoveBackslash(s As String) As String
  371.    Dim i As Integer
  372.    i = Len(s)
  373.    If i <> 0 Then
  374.       If Right$(s, 1) = "\" Then
  375.          RemoveBackslash = Left$(s, i - 1)
  376.       Else
  377.          RemoveBackslash = s
  378.       End If
  379.    Else
  380.       RemoveBackslash = ""
  381.    End If
  382. End Function
  383.  
  384. '
  385. ' Returns the drive type if possible.
  386. '
  387. Public Function sDriveType(sDrive As String) As String
  388. Dim lRet As Long
  389.  
  390.     lRet = GetDriveTypeA(sDrive & ":\")
  391.     Select Case lRet
  392.         Case 0
  393.             'sDriveType = "Cannot be determined!"
  394.             sDriveType = "Unknown"
  395.             
  396.         Case 1
  397.             'sDriveType = "The root directory does not exist!"
  398.             sDriveType = "Unknown"
  399.         Case DRIVE_CDROM:
  400.             sDriveType = "CD-ROM Drive"
  401.             
  402.         Case DRIVE_REMOVABLE:
  403.             sDriveType = "Removable Drive"
  404.             
  405.         Case DRIVE_FIXED:
  406.             sDriveType = "Fixed Drive"
  407.             
  408.         Case DRIVE_REMOTE:
  409.             sDriveType = "Remote Drive"
  410.         End Select
  411. End Function
  412.  
  413. Public Function GetDriveType(sDrive As String) As Long
  414.   Dim lRet As Long
  415.   lRet = GetDriveTypeA(sDrive & ":\")
  416.   
  417.   If lRet = 1 Then
  418.      lRet = 0
  419.   End If
  420.  
  421.   GetDriveType = lRet
  422. End Function
  423. '-----------------------------------------------------------
  424. ' FUNCTION: FileExists
  425. ' Determines whether the specified file exists
  426. '
  427. ' IN: [strPathName] - file to check for
  428. '
  429. ' Returns: True if file exists, False otherwise
  430. '-----------------------------------------------------------
  431. '
  432. Public Function FileExists(ByVal strPathName As String) As Integer
  433.     Dim intFileNum As Integer
  434.  
  435.     On Error Resume Next
  436.  
  437.     '
  438.     'Remove any trailing directory separator character
  439.     '
  440.     If Right$(strPathName, 1) = "\" Then
  441.         strPathName = Left$(strPathName, Len(strPathName) - 1)
  442.     End If
  443.  
  444.     '
  445.     'Attempt to open the file, return value of this function is False
  446.     'if an error occurs on open, True otherwise
  447.     '
  448.     intFileNum = FreeFile
  449.     Open strPathName For Input As intFileNum
  450.  
  451.     FileExists = IIf(Err, False, True)
  452.  
  453.     Close intFileNum
  454.  
  455.     Err = 0
  456. End Function
  457.  
  458.