登录  
 加关注
   显示下一条  |  关闭
温馨提示!由于新浪微博认证机制调整,您的新浪微博帐号绑定已过期,请重新绑定!立即重新绑定新浪微博》  |  关闭

凡人视界

灌水天地 软件修改

 
 
 

日志

 
 

VB创建SYSTEM用户进程  

2007-06-07 00:11:21|  分类: vb编程 |  标签: |举报 |字号 订阅

  下载LOFTER 我的照片书  |

Option Explicit
'chenhui530
'VB创建SYSTEM用户进程
'2007-5-29
Private Const PROCESS_CREATE_THREAD = &H2
Private Const PROCESS_QUERY_INFORMATION = &H400
Private Const PROCESS_VM_WRITE = &H20
Private Const PROCESS_VM_OPERATION = &H8
Private Const PROCESS_VM_READ = &H10
Private Const PROCESS_TERMINATE = 1
Private Const READ_CONTROL = &H20000
Private Const WRITE_DAC = &H40000
Private Const MEM_COMMIT = &H1000
Private Const MEM_RELEASE = &H8000
Private Const PAGE_READWRITE = &H4
Private Const INFINITE = &HFFFFFFFF
Private Const STANDARD_RIGHTS_REQUIRED = &HF0000
Private Const TOKEN_ASSIGN_PRIMARY = &H1
Private Const TOKEN_DUPLICATE = (&H2)
Private Const TOKEN_IMPERSONATE = (&H4)
Private Const TOKEN_QUERY = (&H8)
Private Const TOKEN_QUERY_SOURCE = (&H10)
Private Const TOKEN_ADJUST_PRIVILEGES = (&H20)
Private Const TOKEN_ADJUST_GROUPS = (&H40)
Private Const TOKEN_ADJUST_DEFAULT = (&H80)
'Private Const TOKEN_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or TOKEN_ASSIGN_PRIMARY Or _
'TOKEN_DUPLICATE Or TOKEN_IMPERSONATE Or TOKEN_QUERY Or TOKEN_QUERY_SOURCE Or _
'TOKEN_ADJUST_PRIVILEGES Or TOKEN_ADJUST_GROUPS Or TOKEN_ADJUST_DEFAULT)
Private Const TOKEN_ALL_ACCESS = 983551
Private Const SE_PRIVILEGE_ENABLED = &H2
Private Const ANYSIZE_ARRAY = 1
Private Const SE_DEBUG_NAME = "SeDebugPrivilege"

Private Const DACL_SECURITY_INFORMATION = &H4

Private Const GRANT_ACCESS = 1

Private Type LUID
     lowpart As Long
     highpart As Long
End Type

Private Type LUID_AND_ATTRIBUTES
     pLuid As LUID
     Attributes As Long
End Type

Private Type TOKEN_PRIVILEGES
     PrivilegeCount As Long
     Privileges(ANYSIZE_ARRAY) As LUID_AND_ATTRIBUTES
End Type

Private Type TRUSTEE
     pMultipleTrustee As Long
     MultipleTrusteeOperation As Long
     TrusteeForm As Long
     TrusteeType As Long
     ptstrName As String
End Type

Private Type EXPLICIT_ACCESS
     grfAccessPermissions As Long
     grfAccessMode As Long
     grfInheritance As Long
     pTRUSTEE As TRUSTEE
End Type

Private Declare Sub BuildExplicitAccessWithName Lib "advapi32.dll" Alias _
     "BuildExplicitAccessWithNameA" _
     (ea As Any, _
     ByVal TrusteeName As String, _
     ByVal AccessPermissions As Long, _
     ByVal AccessMode As Integer, _
     ByVal Inheritance As Long)
    
Private Declare Function SetEntriesInAcl Lib "advapi32.dll" Alias "SetEntriesInAclA" (ByVal CountofExplicitEntries As Long, ea As Any, ByVal OldAcl As Long, NewAcl As Long) As Long

Private Declare Function GetNamedSecurityInfo Lib "advapi32.dll" Alias _
     "GetNamedSecurityInfoA" _
     (ByVal ObjName As String, _
     ByVal SE_OBJECT_TYPE As Long, _
     ByVal SecInfo As Long, _
     ByVal pSid As Long, _
     ByVal pSidGroup As Long, _
     pDacl As Long, _
     ByVal pSacl As Long, _
     pSecurityDescriptor As Long) As Long
    
Private Declare Function SetNamedSecurityInfo Lib "advapi32.dll" Alias _
     "SetNamedSecurityInfoA" _
     (ByVal ObjName As String, _
     ByVal SE_OBJECT As Long, _
     ByVal SecInfo As Long, _
     ByVal pSid As Long, _
     ByVal pSidGroup As Long, _
     ByVal pDacl As Long, _
     ByVal pSacl As Long) As Long
    
Private Declare Function GetKernelObjectSecurity Lib "advapi32.dll" (ByVal Handle As Long, ByVal RequestedInformation As Long, pSecurityDescriptor As Long, ByVal nLength As Long, lpnLengthNeeded As Long) As Long


Private Declare Function LocalFree Lib "kernel32" (ByVal hMem As Long) As Long

Private Declare Function OpenProcessToken Lib "advapi32.dll" (ByVal ProcessHandle As Long, ByVal DesiredAccess As Long, TokenHandle As Long) As Long
Private Declare Function AdjustTokenPrivileges Lib "advapi32.dll" (ByVal TokenHandle As Long, ByVal DisableAllPriv As Long, NewState As TOKEN_PRIVILEGES, ByVal BufferLength As Long, PreviousState As TOKEN_PRIVILEGES, ReturnLength As Long) As Long                 'Used to adjust your program's security privileges, can't restore without it!
Private Declare Function LookupPrivilegeValue Lib "advapi32.dll" Alias "LookupPrivilegeValueA" (ByVal lpSystemName As Any, ByVal lpName As String, lpLuid As LUID) As Long
Private Declare Function GetCurrentProcess Lib "kernel32" () As Long '获取当前进程句柄
Private Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Private Declare Function EnumProcesses Lib "psapi.dll" (ByRef lpidProcess As Long, ByVal cb As Long, ByRef cbNeeded As Long) As Long
Private Declare Function GetModuleFileNameExA Lib "psapi.dll" (ByVal hProcess As Long, ByVal hModule As Long, ByVal ModuleName As String, ByVal nSize As Long) As Long
Private Declare Function EnumProcessModules Lib "psapi.dll" (ByVal hProcess As Long, ByRef lphModule As Long, ByVal cb As Long, ByRef cbNeeded As Long) As Long
Private Declare Function GetLastError Lib "kernel32" () As Long
Private Declare Function HeapAlloc Lib "kernel32" (ByVal hHeap As Long, ByVal dwFlags As Long, ByVal dwBytes As Long) As Long
Private Declare Function GetProcessHeap Lib "kernel32" () As Long

Private Declare Function MakeAbsoluteSD Lib "advapi32.dll" (ByVal pSelfRelativeSecurityDescriptor As Long, ByVal pAbsoluteSecurityDescriptor As Long, lpdwAbsoluteSecurityDescriptorSize As Long, ByVal pDacl As Long, lpdwDaclSize As Long, ByVal pSacl As Long, lpdwSaclSize As Long, ByVal pOwner As Long, lpdwOwnerSize As Long, ByVal pPrimaryGroup As Long, lpdwPrimaryGroupSize As Long) As Long

  
   chenhui530(陈辉) ( ) 信誉:100     Blog    加为好友   2007-5-29 22:24:45   得分: 0  


   
'Private Declare Function SetSecurityDescriptorDacl Lib "advapi32.dll" (pSecurityDescriptor As Long, ByVal bDaclPresent As Long, pDacl As ACL, ByVal bDaclDefaulted As Long) As Long
Private Declare Function SetSecurityDescriptorDacl Lib "advapi32.dll" (ByVal pSecurityDescriptor As Long, ByVal bDaclPresent As Long, ByVal pDacl As Long, ByVal bDaclDefaulted As Long) As Long

Private Declare Function SetKernelObjectSecurity Lib "advapi32.dll" (ByVal Handle As Long, ByVal SecurityInformation As Long, ByVal SecurityDescriptor As Long) As Long
Private Declare Function ImpersonateLoggedOnUser Lib "advapi32" (ByVal hToken As Long) As Long
'Private Declare Function DuplicateTokenEx Lib "advapi32" (ByVal hExistingToken As Long, ByVal dwDesiredAcces As Long, lpTokenAttribute As Long, ImpersonatonLevel As SECURITY_IMPERSONATION_LEVEL, ByVal tokenType As TOKEN_TYPE, Phandle As Long) As Long
Private Declare Function DuplicateTokenEx Lib "advapi32" (ByVal hExistingToken As Long, ByVal dwDesiredAcces As Long, lpTokenAttribute As Long, ImpersonatonLevel As SECURITY_IMPERSONATION_LEVEL, ByVal tokenType As TOKEN_TYPE, Phandle As Long) As Long
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)

'Private Declare Function GetSecurityDescriptorDacl Lib "advapi32.dll" (pSecurityDescriptor As Long, lpbDaclPresent As Long, pDacl As ACL, lpbDaclDefaulted As Long) As Long
Private Declare Function GetSecurityDescriptorDacl Lib "advapi32.dll" (ByVal pSecurityDescriptor As Long, lpbDaclPresent As Long, pDacl As Long, lpbDaclDefaulted As Long) As Long
'Private Declare Function CreateProcessAsUser Lib "advapi32.dll" Alias "CreateProcessAsUserA" (ByVal hToken As Long, ByVal lpApplicationName As String, ByVal lpCommandLine As String, lpProcessAttributes As SECURITY_ATTRIBUTES, lpThreadAttributes As SECURITY_ATTRIBUTES, ByVal bInheritHandles As Long, ByVal dwCreationFlags As Long, ByVal lpEnvironment As String, ByVal lpCurrentDirectory As String, lpStartupInfo As STARTUPINFO, lpProcessInformation As PROCESS_INFORMATION) As Long
'Private Declare Function CreateProcessAsUser Lib "advapi32.dll" Alias "CreateProcessAsUserA" (ByVal hToken As Long, ByVal lpApplicationName As String, ByVal lpCommandLine As String, ByVal lpProcessAttributes As SECURITY_ATTRIBUTES, ByVal lpThreadAttributes As SECURITY_ATTRIBUTES, ByVal bInheritHandles As Long, ByVal dwCreationFlags As Long, ByVal lpEnvironment As String, ByVal lpCurrentDirectory As String, ByVal lpStartupInfo As STARTUPINFO, ByVal lpProcessInformation As PROCESS_INFORMATION) As Long
Private Declare Function CreateProcessAsUser Lib "advapi32.dll" Alias "CreateProcessAsUserA" (ByVal hToken As Long, ByVal lpApplicationName As String, ByVal lpCommandLine As String, lpProcessAttributes As Long, lpThreadAttributes As Long, ByVal bInheritHandles As Long, ByVal dwCreationFlags As Long, ByVal lpEnvironment As String, ByVal lpCurrentDirectory As String, lpStartupInfo As STARTUPINFO, lpProcessInformation As PROCESS_INFORMATION) As Long
Private Declare Function HeapFree Lib "kernel32" (ByVal hHeap As Long, ByVal dwFlags As Long, lpMem As Any) As Long
Private Const ERROR_INSUFFICIENT_BUFFER = 122
Private Const HEAP_ZERO_MEMORY As Long = &H8
Private Const ERROR_SUCCESS = 0&

Private Type SID_IDENTIFIER_AUTHORITY
     Value(6) As Byte
End Type

Private Type SID
     Revision As Byte
     SubAuthorityCount As Byte
     IdentifierAuthority As SID_IDENTIFIER_AUTHORITY
     '#if MIDL_PASS
     '[size_is(SubAuthorityCount)] DWORD SubAuthority;
     '#else // MIDL_PASS
     SubAuthority(0) As Integer
     '#endif // MIDL_PASS
End Type

Private Enum SECURITY_IMPERSONATION_LEVEL
     SecurityAnonymous
     SecurityIdentification
     SecurityImpersonation
     SecurityDelegation
End Enum

Private Enum TOKEN_TYPE
     TokenPrimary = 1
     TokenImpersonation
End Enum

Private Type SECURITY_ATTRIBUTES
     nLength As Long
     lpSecurityDescriptor As Long
     bInheritHandle As Long
End Type

Private Type ACL
     AclRevision As Byte
     Sbz1 As Byte
     AclSize As Integer
     AceCount As Integer
     Sbz2 As Integer
End Type

Private Type SECURITY_DESCRIPTOR
     Revision As Byte
     Sbz1 As Byte
     Control As Long
     Owner As Long
     Group As Long
     Sacl As ACL
     Dacl As ACL
End Type

Private Type STARTUPINFO
     cb As Long
     lpReserved As String
     lpDesktop As String
     lpTitle As String
     dwX As Long
     dwY As Long
     dwXSize As Long
     dwYSize As Long
     dwXCountChars As Long
     dwYCountChars As Long
     dwFillAttribute As Long
     dwFlags As Long
     wShowWindow As Integer
     cbReserved2 As Integer
     lpReserved2 As Long
     hStdInput As Long
     hStdOutput As Long
     hStdError As Long
End Type

Private Type PROCESS_INFORMATION
     hProcess As Long
     hThread As Long
     dwProcessId As Long
     dwThreadId As Long
End Type


'提升进程为Debug权限
Public Function EnablePrivilege() As Boolean
     Dim hdlProcessHandle As Long
     Dim hdlTokenHandle As Long
     Dim tmpLuid As LUID
     Dim tkp As TOKEN_PRIVILEGES
     Dim tkpNewButIgnored As TOKEN_PRIVILEGES
     Dim lBufferNeeded As Long
     Dim lp As Long
     hdlProcessHandle = GetCurrentProcess()
     lp = OpenProcessToken(hdlProcessHandle, TOKEN_ADJUST_PRIVILEGES Or TOKEN_QUERY, hdlTokenHandle)
     Debug.Print "TOKENS: " & CStr(TOKEN_ADJUST_PRIVILEGES Or TOKEN_QUERY)
     Debug.Print "TOKEN: " & hdlTokenHandle
     lp = LookupPrivilegeValue(vbNullString, "SeDebugPrivilege", tmpLuid)
     tkp.PrivilegeCount = 1
     tkp.Privileges(0).pLuid = tmpLuid
     tkp.Privileges(0).Attributes = SE_PRIVILEGE_ENABLED
     EnablePrivilege = AdjustTokenPrivileges(hdlTokenHandle, False, tkp, Len(tkp), tkpNewButIgnored, lBufferNeeded)
End Function

Public Function CreateSystemProcess(ByVal szProcessName As String) As Boolean
     Dim hProcess As Long, dwPid As Long, hToken As Long, hNewToken As Long, pOrigSd As SECURITY_DESCRIPTOR, pNewSd As SECURITY_DESCRIPTOR, dwSDLen As Long, bDAcl As Long, pOldDAcl As ACL, bDefDAcl As Long
     Dim dwRet As Long, pNewDAcl As ACL, pSacl As ACL, dwSidOwnLen As Long, dwSidPrimLen As Long, si As STARTUPINFO, pi As PROCESS_INFORMATION, bError As Boolean
     Dim ea As EXPLICIT_ACCESS, hOrigSd As Long, hOldDAcl As Long, hNewDAcl As Long, dwAclSize As Long, dwSaclSize As Long
     Dim hSacl As Long, hSidOwner As Long, hSidPrimary As Long, hNewSd As Long, lngErr As Long
     Dim hea As Long, hToken1 As Long, pSidOwner As SID, pSidPrimary As SID, ct As SECURITY_DESCRIPTOR
     Dim hSacl1 As Long, hSidOwner1 As Long, hSidPrimary1 As Long
     '提高进程权限为Debug权限
     If Not EnablePrivilege Then
         bError = True
         GoTo Cleanup
     End If
     '得到winlogon的进程ID
     dwPid = GetSystemProcessID
     If dwPid = 0 Then
         bError = True
         GoTo Cleanup
     End If
     '得到句柄
     hProcess = OpenProcess(PROCESS_QUERY_INFORMATION, False, dwPid)
     If hProcess = 0 Then
         bError = True
         GoTo Cleanup
     End If


  

Top  
chenhui530(陈辉) ( ) 信誉:100     Blog    加为好友   2007-5-29 22:24:53   得分: 0  


   
'得到hToken
     If OpenProcessToken(hProcess, READ_CONTROL Or WRITE_DAC, hToken) = 0 Then
         bError = True
         GoTo Cleanup
     End If
     '设置 ACE 具有所有访问权限
     BuildExplicitAccessWithName ea, "Everyone", TOKEN_ALL_ACCESS, GRANT_ACCESS, 0
     Debug.Print ea.grfAccessMode
     '第一次调用肯定错误,目的是为了得到dwSDLen的值
     If GetKernelObjectSecurity(ByVal hToken, DACL_SECURITY_INFORMATION, ByVal hOrigSd, ByVal 0, dwSDLen) = 0 Then
         lngErr = GetLastError()
         Debug.Print "GetLastError: " & lngErr
         Debug.Print "dwSDLen值为: " & dwSDLen
'         If lngErr = ERROR_INSUFFICIENT_BUFFER Then
             hOrigSd = HeapAlloc(GetProcessHeap, HEAP_ZERO_MEMORY, dwSDLen)
             '再次调用取得正确得到安全描述符hOrigSd
             If GetKernelObjectSecurity(ByVal hToken, DACL_SECURITY_INFORMATION, ByVal hOrigSd, ByVal dwSDLen, dwSDLen) = 0 Then
                 bError = True
                 GoTo Cleanup
             End If
'         Else
'             bError = True
'             GoTo Cleanup
'         End If
     Else
         bError = True
         GoTo Cleanup
     End If
     '得到原安全描述符的访问控制列表 ACL
     If GetSecurityDescriptorDacl(ByVal hOrigSd, bDAcl, hOldDAcl, bDefDAcl) = 0 Then
         bError = True
         GoTo Cleanup
     End If

     '生成新 ACE 权限的访问控制列表 ACL
     dwRet = SetEntriesInAcl(ByVal 1, ea, hOldDAcl, hNewDAcl)
     If dwRet <> ERROR_SUCCESS Then
         hNewDAcl = 0
         bError = True
         GoTo Cleanup
     End If
     '第一次调用给出的参数肯定返回这个错误,这样做的目的是为了创建新的安全描述符 hNewSd 而得到各项的长度
     If MakeAbsoluteSD(ByVal hOrigSd, ByVal hNewSd, dwSDLen, ByVal hOldDAcl, dwAclSize, ByVal hSacl, dwSaclSize, ByVal hSidOwner, dwSidOwnLen, ByVal hSidPrimary, dwSidPrimLen) = 0 Then
         lngErr = GetLastError()
         Debug.Print "GetLastError: " & lngErr
         Debug.Print "hNewSd: " & hNewSd
         Debug.Print "hNewDAcl: " & hNewDAcl
         'If lngErr = ERROR_INSUFFICIENT_BUFFER Then
             hOldDAcl = HeapAlloc(GetProcessHeap, HEAP_ZERO_MEMORY, ByVal dwAclSize)
             hSacl = HeapAlloc(GetProcessHeap, HEAP_ZERO_MEMORY, ByVal dwSaclSize)
             hSidOwner = HeapAlloc(GetProcessHeap, HEAP_ZERO_MEMORY, ByVal dwSidOwnLen)
             hSidPrimary = HeapAlloc(GetProcessHeap, HEAP_ZERO_MEMORY, ByVal dwSidPrimLen)
             hNewSd = HeapAlloc(GetProcessHeap, HEAP_ZERO_MEMORY, ByVal dwSDLen)
             Debug.Print "调用MakeAbsoluteSD成功之后dwSDLen值为: " & dwSDLen
             '再次调用才可以成功创建新的安全描述符 hNewSd但新的安全描述符仍然是原访问控制列表 ACL
             If MakeAbsoluteSD(ByVal hOrigSd, ByVal hNewSd, dwSDLen, ByVal hOldDAcl, dwAclSize, ByVal hSacl, dwSaclSize, ByVal hSidOwner, dwSidOwnLen, ByVal hSidPrimary, dwSidPrimLen) = 0 Then
                 bError = True
                 GoTo Cleanup
             End If
             Debug.Print "hNewSd: " & hNewSd
             Debug.Print "hNewDAcl: " & hNewDAcl
'         Else
'             bError = True
'             GoTo Cleanup
'         End If
     End If

     '将具有所有访问权限的访问控制列表 hNewDAcl 加入到新的hNewSd中
     If SetSecurityDescriptorDacl(hNewSd, bDAcl, hNewDAcl, bDefDAcl) = 0 Then
         bError = True
         GoTo Cleanup
     End If

     '将新的安全描述符加到 TOKEN 中
     If SetKernelObjectSecurity(hToken, DACL_SECURITY_INFORMATION, ByVal hNewSd) = 0 Then
         bError = True
         GoTo Cleanup
     End If
     '以所有权限方式再次打开winlogon.exe为复制权限作准备
     If OpenProcessToken(ByVal hProcess, TOKEN_ALL_ACCESS, hToken) = 0 Then
         bError = True
         GoTo Cleanup
     End If
     '复制一份具有相同访问权限的 TOKEN
     If DuplicateTokenEx(hToken, TOKEN_ALL_ACCESS, ByVal 0, ByVal SecurityImpersonation, ByVal TokenPrimary, hNewToken) = 0 Then
         bError = True
         GoTo Cleanup
     End If
     '不虚拟登陆用户的话,创建新进程会提示1314 客户没有所需的特权错误
     Call ImpersonateLoggedOnUser(hNewToken)
     '利用具有所有权限的 TOKEN,创建高权限进程
     If CreateProcessAsUser(hNewToken, vbNullString, szProcessName, ByVal 0&, ByVal 0, False, ByVal 0&, vbNullString, vbNullString, si, pi) = 0 Then
         bError = True
         GoTo Cleanup
     End If
     bError = False
Cleanup:
'     On Error Resume Next
     If hOrigSd Then HeapFree GetProcessHeap, 0, hOrigSd
     If hNewSd Then HeapFree GetProcessHeap, 0, hNewSd
     If hSidPrimary Then HeapFree GetProcessHeap, 0, hSidPrimary
     If hSidOwner Then HeapFree GetProcessHeap, 0, hSidOwner
     If hSacl Then Call HeapFree(GetProcessHeap, 0, hSacl)
     If hOldDAcl Then Call HeapFree(GetProcessHeap, 0, hOldDAcl)
     Call CloseHandle(pi.hProcess)
     Call CloseHandle(pi.hThread)
     Call CloseHandle(hToken)
     Call CloseHandle(hNewToken)
     Call CloseHandle(hProcess)
     If (bError) Then
         CreateSystemProcess = False
     Else
         CreateSystemProcess = True
     End If
End Function

Private Function GetSystemProcessID() As Long
     Dim cb As Long
     Dim cbNeeded As Long
     Dim NumElements As Long
     Dim ProcessIDs() As Long
     Dim cbNeeded2 As Long
     Dim NumElements2 As Long
     Dim Modules(1 To 255) As Long
     Dim lRet As Long
     Dim ModuleName As String, Str As String
     Dim nSize As Long
     Dim hProcess As Long
     Dim i As Long, j As Integer
     ReDim ProcessIDs(1024)
     lRet = EnumProcesses(ProcessIDs(0), 4 * 1024, cbNeeded)
     NumElements = cbNeeded / 4
     ReDim Preserve ProcessIDs(NumElements - 1)
     '遍历进程
     For i = 0 To NumElements - 1
         hProcess = OpenProcess(PROCESS_QUERY_INFORMATION _
         Or PROCESS_VM_READ Or PROCESS_TERMINATE, False, ProcessIDs(i))
         If hProcess <> 0 Then
             lRet = EnumProcessModules(hProcess, Modules(1), 255, cbNeeded2)
             If lRet <> 0 Then
                 ModuleName = Space(255)
                 nSize = 255
                 lRet = GetModuleFileNameExA(hProcess, Modules(1), ModuleName, 255)
                 ModuleName = Left(ModuleName, lRet)
                 If InStr(LCase(ModuleName), "system32\winlogon.exe") Then '"system32\services.exe") Then
                     GetSystemProcessID = ProcessIDs(i)
                     Exit Function
                 End If
             End If
         End If
     Next
End Function

Private Sub cmdRun_Click()
     If CreateSystemProcess(txtPath.Text) Then
         'MsgBox "创建成功!!"
         Unload Me
     End If
End Sub

Private Sub Form_Load()
     Dim strCmdLine As String, strAgs As String
     strCmdLine = Command
     If strCmdLine <> "" Then
         Me.Hide
         strAgs = Mid(strCmdLine, InStr(strCmdLine, "/") + 1, Len(strCmdLine) - InStr(strCmdLine, "/"))
         CreateSystemProcess strAgs
         Unload Me
     End If
End Sub

  评论这张
 
阅读(186)| 评论(0)

历史上的今天

评论

<#--最新日志,群博日志--> <#--推荐日志--> <#--引用记录--> <#--博主推荐--> <#--随机阅读--> <#--首页推荐--> <#--历史上的今天--> <#--被推荐日志--> <#--上一篇,下一篇--> <#-- 热度 --> <#-- 网易新闻广告 --> <#--右边模块结构--> <#--评论模块结构--> <#--引用模块结构--> <#--博主发起的投票-->
 
 
 
 
 
 
 
 
 
 
 
 
 
 

页脚

网易公司版权所有 ©1997-2018