文章探索:   分类:    关键字:  
  + 栏目导航
  + 相关文章
文本框中光标位置的获得
用VB导入导出你的IE收藏夹
VB应用程序访问SQL Server方法探讨
VB访问SQL Server数据库技术全揭密
自动上网抓数据的机器人
自己的IE——用VB制作浏览器
VB中如何保存Webbrowser中的整个页面..
在VB中该如何控制其它程序的弹出窗口..
保存webbrowser中的HTML内容
破译动网验证码的简单方法
轻松获取QQ密码
VB.NET获取硬盘序列号的方法
WEBBROWSER 技巧一(收藏)
VB自动登陆网络站点详解(二):Inet..
获取webbrowser控件网页的源码
WebBrowser控件说明
关于用VB做更漂亮的窗体的思考
VB中访问存储过程的几种办法
VB6中改变屏幕的分辨率和刷新频率
VB编写一个能显示百分比的自定义进度..
公农历转换VB类
VB.NET窗口渐淡关闭
使用VB实现邮箱自动注册(二):修改..
VB.NET轻松实现任务栏程序
VB.NET启动外部程序
利用vb实现图片上传
VB实现局域网内的文件传输
VB 一个Function传回多个值
在VB中实现多线程
VB 手机号码编码程序


技术教程 -> VB教程 ->  
VB控制文件系统
来源:转载   人气:1049   录入时间:2007-11-8
     磁盘
    获得分区信息并判断是否有CD
   声明:
   Declare Function GetVolumeInformation Lib _
   "kernel32" Alias "GetVolumeInformationA" _
   (ByVal lpRootPathName As String, _
   ByVal lpVolumeNameBuffer As String, _
   ByVal nVolumeNameSize As Long, _
   lpVolumeSerialNumber As Long, _
   lpMaximumComponentLength As Long, _
   lpFileSystemFlags As Long, _
   ByVal lpFileSystemNameBuffer As String, _
   ByVal nFileSystemNameSize As Long) As Long
   
   Declare Function GetDriveType Lib "kernel32" _
   Alias "GetDriveTypeA" (ByVal nDrive As String) As Long
   
   Public Const DRIVE_CDROM = 5
   使用:
   Dim VolName As String, FSys As String, erg As Long
   Dim VolNumber As Long, MCM As Long, FSF As Long
   Dim Drive As String, DriveType As Long
   VolName = Space(127)
   FSys = Space(127)
   Drive = "F:\" 'Enter the driverletter you want
   DriveType& = GetDriveType(Drive$)
   erg& = GetVolumeInformation(Drive$, VolName$, 127&, _
   VolNumber&, MCM&, FSF&, FSys$, 127&)
   Print "分区名称:" & vbTab & VolName$
   Print "序列号:" & vbTab & VolNumber&
   Print "最大文件名称长:" & vbTab & vbTab & MCM&
   Print "文件系统标志:" & vbTab & vbTab & FSF&
   Print "文件系统名称:" & vbTab & FSys$
   Print "类型:" & vbTab & DriveType&;
   'Is the drive a CDROM, if so, check for a CD
   If DriveType& = DRIVE_CDROM Then
   Print " (CDROM, ";
   If erg& = 0 Then
   Print "没有 CD )"
   Else
   Print "有 CD )"
   End If
   Else
   Print " (非 CDROM)" '
   End If
   
   打开和关闭CD-ROM 驱动器
   声明:
   Declare Function mciSendString Lib "winmm.dll" Alias _
   "mciSendStringA" (ByVal lpstrCommand As String, ByVal _
   lpstrReturnString As String, ByVal uReturnLength As Long, _
   ByVal hwndCallback As Long) As Long
   使用:
   '打开
   retvalue = mcisendstring("set CDAudio door open", returnstring, 127, 0)
   '关闭
   retvalue = mcisendstring("set CDAudio door closed", returnstring, 127, 0)
   
   判断驱动器类型
   利用 API 可以判断一个驱动器的类型。
   声明:
   Declare Function GetDriveType Lib "kernel32" Alias "GetDriveTypeA" (ByVal nDrive As String) As Long
   调用:
   ret = GetDriveType ( "D:\")
   如果 ret =2 软盘,=3 硬盘,=4 网络映射盘,=5 光驱,=6 RAM DISK
   
   取得磁盘序列号、卷标和文件系统类型
   磁盘序列号在每次软盘或硬盘格式化后都重新生成,并且不回重复。许多程序员用此加密。其实也可以修改该函数,可以得到磁盘卷标和文件系统类型信息。
   
   声明:
   Private Declare Function GetVolumeInformation Lib "kernel32.dll" Alias "GetVolumeInformationA" (ByVal lpRootPathName As String, ByVal lpVolumeNameBuffer As String, ByVal nVolumeNameSize As Integer, lpVolumeSerialNumber As Long, lpMaximumComponentLength As Long, lpFileSystemFlags As Long, ByVal lpFileSystemNameBuffer As String, ByVal nFileSystemNameSize As Long) As Long
   
   代码:
   
   Function GetSerialNumber(sRoot As String) As Long
    Dim lSerialNum As Long
    Dim R As Long
    Dim sTemp1 As String, sTemp2 As String
    strLabel = String$(255, Chr$(0))
    ' 磁盘卷标
    strType = String$(255, Chr$(0))
    ' 文件系统类型 一般为 FAT
    R = GetVolumeInformation(sRoot, strLabel, Len(strLabel), lSerialNum, 0, 0, strType, Len(strType))
    GetSerialNumber = lSerialNum
    '在 strLabel 中为 磁盘卷标
    '在 strType 中为 文件系统类型
   End Function
   
   用法:
   
   当驱动器不存在时,函数返回 0。如果是个非根目录,也将返回 0:
   
   lSerial = GetSerialNumber("c:\")
   
   格式化磁盘
   在Drive的参数中 "A:" = 0,类推。
   
   Private Const SHFMT_ID_DEFAULT = &HFFFF&
   'Currently the only fmtID supported.
   
   Private Declare Function SHFormatDrive Lib "shell32.dll" (ByVal hWnd As Long, ByVal Drive As Long, fmtID As Long, Options As Long) As Long
   
   Private Sub Command1_Click()
   Dim lret As Long
   lret = SHFormatDrive(Me.hWnd, 0, SHFMT_ID_DEFAULT, 0)
   Select Case lret
   Case -2
   MsgBox "OK !"
   Case -3
   MsgBox "Cannot format a read only drive !"
   End Select
   End Sub
   
   文件
   自动出现动画、进度和确认的文件操作
   使用以下的 API , 得到与资源管理器相同的感觉!
   Private Type SHFILEOPSTRUCT
   hwnd As Long
   wFunc As Long
   pFrom As String
   pTo As String
   fFlags As Integer
   fAnyOperationsAborted As Long
   hNameMappings As Long
   lpszProgressTitle As String '只有在 FOF_SIMPLEPROGRESS 时用
   End Type
   
   Private Declare Function SHFileOperation Lib _
   "shell32.dll" Alias "SHFileOperationA" (lpFileOp _
   As SHFILEOPSTRUCT) As Long
   
   'wFunc 常数
   'FO_COPY 把 pFrom 文件拷贝到 pTo。
   Const FO_COPY = &H2
   'FO_DELETE 删除 pFrom 中的文件(pTo 忽略)。
   Const FO_DELETE = &H3
   'FO_MOVE 把 pFrom 文件移动到 pTo。
   Const FO_MOVE = &H1
   
   'fFlag 常数
   'FOF_ALLOWUNDO 允许 Undo 。
   Const FOF_ALLOWUNDO = &H40
   'FOF_NOCONFIRMATION 不显示系统确认对话框。
   Const FOF_NOCONFIRMATION = &H10
   'FOF_NOCONFIRMMKDIR 不提示是否新建目录。
   Const FOF_NOCONFIRMMKDIR = &H200
   'FOF_SILENT 不显示进度对话框
   Const FOF_SILENT = &H4
   
   例子:
   Dim SHFileOp As SHFILEOPSTRUCT
   ' 删除
   SHFileOp.wFunc = FO_DELETE
   SHFileOp.pFrom = "c:\config.old" + Chr(0)
   SHFileOp.fFlags = FOF_ALLOWUNDO + FOF_NOCONFIRMATION
   Call SHFileOperation(SHFileOp)
   ' 删除多个文件
   SHFileOp.wFunc = FO_DELETE
   SHFileOp.pFrom = "c:\config.old" +Chr(0) + "c:\autoexec.old"+Chr(0)
   SHFileOp.fFlags = FOF_ALLOWUNDO
   Call SHFileOperation(SHFileOp)
   ' 拷贝
   SHFileOp.wFunc = FO_COPY
   SHFileOp.pFrom = "c:\t\*.*"
   SHFileOp.pTo = "d:\t\*.*"
   SHFileOp.fFlags = FOF_ALLOWUNDO + FOF_NOCONFIRMMKDIR
   Call SHFileOperation(SHFileOp)
   ' 移动
   SHFileOp.wFunc = FO_MOVE
   SHFileOp.pFrom = "c:\config.old" + Chr(0)
   SHFileOp.pTo = "d:\t"
   SHFileOp.fFlags = FOF_ALLOWUNDO + FOF_NOCONFIRMATION
   Call SHFileOperation(SHFileOp) 参见 FB016
   
    快速建立目录
   声明:
   Private Type SECURITY_ATTRIBUTES
   nLength As Long
   lpSecurityDescriptor As Long
   bInheritHandle As Long
   End Type
   Private Declare Function CreateDirectory Lib "kernel32" _
   Alias "CreateDirectoryA" (ByVal lpPathName As String, _
   lpSecurityAttributes As SECURITY_ATTRIBUTES) As Long
   函数:
   'Call CreateNewDirectory("c:\test\directory\vb\tips\")
   Public Sub CreateNewDirectory(NewDirectory As String)
   Dim sDirTest As String
   Dim SecAttrib As SECURITY_ATTRIBUTES
   Dim bSuccess As Boolean
   Dim sPath As String
   Dim iCounter As Integer
   Dim sTempDir As String
   iFlag = 0
   sPath = NewDirectory
   If Right(sPath, Len(sPath)) <> "\" Then
   sPath = sPath & "\"
   End If
   iCounter = 1
   Do Until InStr(iCounter, sPath, "\") = 0
   iCounter = InStr(iCounter, sPath, "\")
   sTempDir = Left(sPath, iCounter)
   sDirTest = Dir(sTempDir)
   iCounter = iCounter + 1
   'create directory
   SecAttrib.lpSecurityDescriptor = &O0
   SecAttrib.bInheritHandle = False
   SecAttrib.nLength = Len(SecAttrib)
   bSuccess = CreateDirectory(sTempDir, SecAttrib)
   Loop
   End Sub
   
   开启文件属性窗口
   声明:
   Type SHELLEXECUTEINFO
   cbSize As Long
   fMask As Long
   hwnd As Long
   lpVerb As String
   lpFile As String
   lpParameters As String
   lpDirectory As String
   nShow As Long
   hInstApp As Long
   lpIDList As Long
   lpClass As String
   hkeyClass As Long
   dwHotKey As Long
   hIcon As Long
   hProcess As Long
   End Type
   
   Public Const SEE_MASK_INVOKEIDLIST = &HC
   Public Const SEE_MASK_NOCLOSEPROCESS = &H40
   Public Const SEE_MASK_FLAG_NO_UI = &H400
   
   Declare Function ShellExecuteEX Lib "shell32.dll" Alias _
   "ShellExecuteEx" (SEI As SHELLEXECUTEINFO) As Long
   
   代码:
   ' 使用: ShowProps("c:\command.com",Me.hWnd)
   Public Sub ShowProps(FileName As String, OwnerhWnd As Long)
   Dim SEI As SHELLEXECUTEINFO
   Dim r As Long
   With SEI
   .cbSize = Len(SEI)
   .fMask = SEE_MASK_NOCLOSEPROCESS Or _
   SEE_MASK_INVOKEIDLIST Or SEE_MASK_FLAG_NO_UI
   .hwnd = OwnerhWnd
   .lpVerb = "properties"
   .lpFile = FileName
   .lpParameters = vbNullChar
   .lpDirectory = vbNullChar
   .nShow = 0
   .hInstApp = 0
   .lpIDList = 0
   End With
   r = ShellExecuteEX(SEI)
   End Sub
   
   使用 WIN95 的选择目录对话框
   声明:
   Private Type BrowseInfo
   hWndOwner As Long
   pIDLRoot As Long
   pszDisplayName As Long
   lpszTitle As Long
   ulFlags As Long
   lpfnCallback As Long
   lParam As Long
   iImage As Long
   End Type
   
   Private Const BIF_RETURNONLYFSDIRS = 1
   Private Const MAX_PATH = 260
   
   Private Declare Sub CoTaskMemFree Lib "ole32.dll" (ByVal hMem As Long)
   Private Declare Function lstrcat Lib "kernel32" Alias "lstrcatA" _
   (ByVal lpString1 As String, ByVal lpString2 As String) As Long
   Private Declare Function SHBrowseForFolder Lib "shell32" _
   (lpbi As BrowseInfo) As Long
   Private Declare Function SHGetPathFromIDList Lib "shell32" _
   (ByVal pidList As Long, ByVal lpBuffer As String) As Long
   函数:
   Public Function BrowseForFolder(hWndOwner As Long, sPrompt As String) As String
   
   Dim iNull As Integer
   Dim lpIDList As Long
   Dim lResult As Long
   Dim sPath As String
   Dim udtBI As BrowseInfo
   
   With udtBI
   .hWndOwner = hWndOwner
   .lpszTitle = lstrcat(sPrompt, "")
   .ulFlags = BIF_RETURNONLYFSDIRS
   End With
   
   lpIDList = SHBrowseForFolder(udtBI)
   If lpIDList Then
   sPath = String$(MAX_PATH, 0)
   lResult = SHGetPathFromIDList(lpIDList, sPath)
   Call CoTaskMemFree(lpIDList)
   iNull = InStr(sPath, vbNullChar)
   If iNull Then
   sPath = Left$(sPath, iNull - 1)
   End If
   End If
   
   BrowseForFolder = sPath
   
   End Function
   
   移动文件到回收站
   声明:
   Public Type SHFILEOPSTRUCT
   hwnd As Long
   wFunc As Long
   pFrom As String
   pTo As String
   fFlags As Integer
   fAnyOperationsAborted As Long
   hNameMappings As Long
   lpszProgressTitle As Long
   End Type
   
   Public Declare Function SHFileOperation Lib _
   "shell32.dll" Alias "SHFileOperationA" (lpFileOp _
   As SHFILEOPSTRUCT) As Long
   
   Public Const FO_DELETE = &H3
   Public Const FOF_ALLOWUNDO = &H40
   代码:
   Dim SHop As SHFILEOPSTRUCT
   Dim strFile as string
   
   With SHop
   .wFunc = FO_DELETE
   .pFrom = strFile + Chr(0)
   .fFlags = FOF_ALLOWUNDO
   End With
   
   SHFileOperation SHop
   
   比较两个文件
   Function CompFile(F1 as string, F2 as string) as boolean
   Dim issame as boolean
   Open F1 For Binary As #1
   Open F2 For Binary As #2
   
   issame = True
   If LOF(1) <> LOF(2) Then
   issame = False
   Else
   whole& = LOF(1) \ 10000 'number of whole 10,000 byte chunks
   part& = LOF(1) Mod 10000 'remaining bytes at end of file
   buffer1$ = String$(10000, 0)
   buffer2$ = String$(10000, 0)
   start& = 1
   For x& = 1 To whole& 'this for-next loop will get 10,000
   Get #1, start&, buffer1$ 'byte chunks at a time.
   Get #2, start&, buffer2$
   If buffer1$ <> buffer2$ Then
   issame = False
   Exit For
   End If
   start& = start& + 10000
   Next
   buffer1$ = String$(part&, 0)
   buffer2$ = String$(part&, 0)
   Get #1, start&, buffer1$ 'get the remaining bytes at the end
   Get #2, start&, buffer2$ 'get the remaining bytes at the end
   If buffer1$ <> buffer2$ Then
   issame = False
   End If
   Close
   CompFile = issame
   End Function
   
   取得临时文件名
   声明:
   Public Const MAX_PATH = 260
   
   Public Declare Function GetTempFileName Lib "kernel32" Alias "GetTempFileNameA" (ByVal lpszPath As String, ByVal lpPrefixString As String, ByVal wUnique As Long, ByVal lpTempFileName As String) As Long
   Public Declare Function GetTempPath Lib "kernel32" Alias "GetTempPathA" (ByVal nBufferLength As Long, ByVal lpBuffer As String) As Long
   
   代码:
   Public Function GetTempFile() As String
   Dim lngRet As Long
   Dim strBuffer As String, strTempPath As String
   
   '初始化 buffer
   strBuffer = String$(MAX_PATH, 0)
   
   '取得临时路径
   lngRet = GetTempPath(Len(strBuffer), strBuffer)
   
   '0 错误
   If lngRet = 0 Then Exit Function
   
   '去掉尾中的 null
   strTempPath = Left$(strBuffer, lngRet)
   
   '初始化 buffer
   strBuffer = String$(MAX_PATH, 0)
   
   '取得临时文件名
   lngRet = GetTempFileName(strTempPath, "tmp", 0&, strBuffer)
   
   If lngRet = 0 Then Exit Function
   
   lngRet = InStr(1, strBuffer, Chr(0))
   If lngRet > 0 Then
   GetTempFile = Left$(strBuffer, lngRet - 1)
   Else
   GetTempFile = strBuffer
   End If
   End Function
   
   确定是 WINDOWS 的可执行文件
   在文件的第 24 字节,如果为40h,就是 Windows 的可执行文件。
   
   Function WinExe (ByVal Exe As String) As Integer
   Dim fh As Integer
   Dim t As String * 1
   fh = FreeFile
   Open Exe For Binary As #fh
   Get fh, 25, t
   Close #fh
   WinExe = (Asc(t) = &H40&)
   End Function
   
   建立多级目录
   Sub CreateLongDir(sDrive As String, sDir As String)
   Dim sBuild As String
   
   While InStr(2, sDir, "\") > 1
   sBuild = sBuild & left(sDir, InStr(2, sDir, "\") - 1)
   sDir = Mid(sDir, InStr(2, sDir, "\"))
   If Dir(sDrive & sBuild, 16) = "" Then
   MkDir sDrive & sBuild
   End If
   Wend
   End Sub
   
   取得文件的扩展名
   Function GetExtension(Filename As String)
   Dim PthPos, ExtPos As Integer
   
   For i = Len(Filename) To 1 Step -1 ' Go from the Length of the filename, to the first character by 1.
   If Mid(Filename, i, 1) = "." Then ' If the current position is '.' then...
   ExtPos = i ' ...Change the ExtPos to the number.
   For j = Len(Filename) To 1 Step -1 ' Do the Same...
   If Mid(Filename, j, 1) = "\" Then ' ...but for '\'.
   PthPos = j ' Change the PthPos to the number.
   Exit For ' Since we found it, don't search any more.
   End If
   Next j
   Exit For ' Since we found it, don't search any more.
   End If
   Next i
   
   If PthPos > ExtPos Then
   Exit Function ' No extension.
   Else
   If ExtPos = 0 Then Exit Function ' If there is not extension, then exit sub.
   GetExtension = Mid(Filename, ExtPos + 1, Len(Filename) - ExtPos) 'Messagebox the Extension
   End If
   
   End Function
   使用:
   FileExt = GetExtension("c:\windows\vb\vb.exe")
   
   从全路径名中提取文件名
   Function StripPath(T$) As String
   Dim x%, ct%
   StripPath$ = T$
   x% = InStr(T$, "\")
   Do While x%
   ct% = x%
   x% = InStr(ct% + 1, T$, "\")
   Loop
   If ct% > 0 Then StripPath$ = Mid$(T$, ct% + 1)
   End Function
   例子:
   File = StripPath("c:\windows\hello.txt")
   
   把文件置入到Text或RichText中
   dim sFile as string
   'Set sFile equal to your filename
   dim i as long
   
   i = freefile()
   
   open sFile for input as #i
   txtMain.text = input$(i,LOF(i))
   close #1
   
   检测文件是否存在
   Function FileExists(FileName As String) As Boolean
    On Error Resume Next
    FileExists = Dir$(FileName) <> ""
    If Err.Number <> 0 Then
    FileExists = False
    End If
    On Error GoTo 0
   End Function
   
   
   增加快捷方式到 启动 组
   利用 DDE 可方便地建立快捷方式:(Text1 为表单中的 Textbox)
    Text1.LinkTopic = "Progman|Progman"
    Text1.LinkMode = 2
    Text1.LinkExecute "[ShowGroup(启动, 4)]"
    Text1.LinkExecute "[AddItem(c:\vb5\myprog.exe, 我的程序)]"
   
   
   目录所占的字节数
   该函数返回目录使用的字节数:
   
   Function DirUsedBytes(ByVal dirName As String) As Long
   Dim FileName As String
   Dim FileSize As Currency
   If Right$(dirName, 1) <> "\" Then
    dirName = dirName & "\"
   Endif
   FileSize = 0
   FileName = Dir$(dirName & "*.*")
   Do While FileName <> ""
    FileSize = FileSize + _
    FileLen(dirName & FileName)
    FileName = Dir$
   Loop
   DirUsedBytes = FileSize
   使用:
   MsgBox DirUsedBytes("C:\Windows")
   
   打开 Win95 的创建快捷方式窗口
   以下的代码演示了如何利用 Win95 的 Wizard 在指定的目录中建立快捷方式。
   
   Dim X As Integer
   X = Shell("C:\WINDOWS\rundll32.exe AppWiz.Cpl,NewLinkHere " & App.Path & "\", 1)
   
   取得短文件名
   如果要传递文件到老的不支持长文件名的应用,以下的函数可以派上用场:
   Declare Function GetShortPathName Lib "kernel32" Alias "GetShortPathNameA" (ByVal lpszLongPath As String, ByVal lpszShortPath As String, ByVal cchBuffer As Long) As Long
   
   Function ShortName(LongPath As String) As String
    Dim ShortPath As String
    Const MAX_PATH = 260
    Dim ret&
    ShortPath = Space$(MAX_PATH)
    ret& = GetShortPathName(LongPath, ShortPath, MAX_PATH)
    If ret& Then
    ShortName = Left$(ShortPath, ret&)
    End If
   End Function
   
   显示盘中所有的目录
   以下的代码把盘中所有的目录都显示在 Listbox 中。需要一个 DriveListBox 和一个 DirListBox。如果 DirListBox 隐藏的话,处理可以快一些。
   
   Dim iLevel As Integer, iMaxSize As Integer
   Dim i As Integer, j As Integer
   ReDim iDirCount(22) As Integer
   '最大 22 级目录
   ReDim sdirs(22, 1) As String
   'drive1 是 DriveListBox 控件
   'dir1 是 DirListBox 控件
   iLevel = 1
   iDirCount(iLevel) = 1
   iMaxSize = 1
   sdirs(iLevel, iDirCount(iLevel)) = Left$(drive1.Drive, 2) & "\"
   Do
   iLevel = iLevel + 1
   iDirCount(iLevel) = 0
   For j = 1 To iDirCount(iLevel - 1)
    dir1.Path = sdirs(iLevel - 1, j)
    dir1.Refresh
    If iMaxSize < (iDirCount(iLevel) + dir1.ListCount) Then
    ReDim Preserve sdirs(22, iMaxSize + dir1.ListCount + 1) As String
    iMaxSize = dir1.ListCount + iDirCount(iLevel) + 1
    End If
    For i = 0 To dir1.ListCount - 1
    iDirCount(iLevel) = _
    iDirCount(iLevel) + 1 '子目录记数
    sdirs(iLevel, iDirCount(iLevel)) = dir1.List(i)
    Next i
   Next j
   '所有名称放到 List1 中
   list1.Clear
   If iDirCount(iLevel) = 0 Then
   '如果无自目录
    For i = 1 To iLevel
    For j = 1 To iDirCount(i)
    list1.AddItem sdirs(i, j)
    Next j
    Next i
    Exit Do
   End If
   Loop
   
    取得长文件名
   Public Function GetLongFilename (ByVal sShortName As String) As String
   
   Dim sLongName As String
   Dim sTemp As String
   Dim iSlashPos As Integer
   
   'Add \ to short name to prevent Instr from failing
   sShortName = sShortName & "\"
   
   'Start from 4 to ignore the "[Drive Letter]:\" characters
   iSlashPos = InStr(4, sShortName, "\")
   
   'Pull out each string between \ character for conversion
   While iSlashPos
   sTemp = Dir(Left$(sShortName, iSlashPos - 1), _
   vbNormal + vbHidden + vbSystem + vbDirectory)
   If sTemp = "" Then
   'Error 52 - Bad File Name or Number
   GetLongFilename = ""
   Exit Function
   End If
   sLongName = sLongName & "\" & sTemp
   iSlashPos = InStr(iSlashPos + 1, sShortName, "\")
   Wend
   
   'Prefix with the drive letter
   GetLongFilename = Left$(sShortName, 2) & sLongName
   
   End Function
   
   建立快捷方式
   Private Declare Function fCreateShellLink Lib "vb5stkit.DLL" (ByVal _
   lpstrFolderName As String, ByVal lpstrLinkName As String, ByVal _
   lpstrLinkPath As String, ByVal lpstrLinkArgs As String) As Long
   
   Private Sub MakeShortCuts()
   
   Dim lReturn As Long
   Dim MyPath As String
   Dim MyName As String
   MyPath = App.Path
   MyName = App.EXEName
   '增加到桌面
   lReturn = fCreateShellLink("..\..\Desktop", _
   "Shortcut to Net Timer", MyPath & "\" & MyName, "")
   '增加到启动组
   lReturn = fCreateShellLink("\启动", "Shortcut to Net Timer", _
   MyPath & "\" & MyName, "")
   
   End Sub
   




Copyright(C)2007-2024 广州市佳沛数码科技有限公司 版权所有
公司地址: 广州市荔湾区东漖北路560号511室
电话:020-81803473 传真:020-81544987