Underc0de

Programación General => Visual Basic => Códigos Fuentes => Mensaje iniciado por: ANTRAX en Julio 26, 2010, 11:24:30 AM

Título: Como apagar, reiniciar o salir del sistema
Publicado por: ANTRAX en Julio 26, 2010, 11:24:30 AM
usa la API ExitWindowsEx

Copia todo este codigo en un modulo, despues en tu formulario, o donde lo necesites unicamente llama a las funciones necesarias:

Código (vb) [Seleccionar]
Option Explicit

Public Const TOKEN_ADJUST_PRIVILEGES As Long = &H20
Public Const TOKEN_QUERY As Long = &H8
Public Const SE_PRIVILEGE_ENABLED As Long = &H2

Public Const EWX_LOGOFF As Long = &H0
Public Const EWX_SHUTDOWN As Long = &H1
Public Const EWX_REBOOT As Long = &H2
Public Const EWX_FORCE As Long = &H4
Public Const EWX_POWEROFF As Long = &H8
Public Const EWX_FORCEIFHUNG As Long = &H10 '2000/XP only

Public Const VER_PLATFORM_WIN32_NT As Long = 2
Public uflags As Long
Public success As Long

'TIPO DE DATOS PARA LAS APIS
Public Type OSVERSIONINFO
  OSVSize         As Long
  dwVerMajor      As Long
  dwVerMinor      As Long
  dwBuildNumber   As Long
  PlatformID      As Long
  szCSDVersion    As String * 128
End Type

Public Type LUID
   dwLowPart As Long
   dwHighPart As Long
End Type

Public Type LUID_AND_ATTRIBUTES
   udtLUID As LUID
   dwAttributes As Long
End Type

Public Type TOKEN_PRIVILEGES
   PrivilegeCount As Long
   laa As LUID_AND_ATTRIBUTES
End Type

'DECLARACION DE LAS APIS A USAR
Public Declare Function ExitWindowsEx Lib "user32" (ByVal dwOptions As Long, ByVal dwReserved As Long) As Long
Public Declare Function GetCurrentProcess Lib "kernel32" () As Long
Public Declare Function OpenProcessToken Lib "advapi32" (ByVal ProcessHandle As Long, ByVal DesiredAccess As Long, TokenHandle As Long) As Long
Public Declare Function LookupPrivilegeValue Lib "advapi32" Alias "LookupPrivilegeValueA" (ByVal lpSystemName As String, ByVal lpName As String, lpLuid As LUID) As Long
Public Declare Function AdjustTokenPrivileges Lib "advapi32" (ByVal TokenHandle As Long, ByVal DisableAllPrivileges As Long, NewState As TOKEN_PRIVILEGES, ByVal BufferLength As Long, PreviousState As Any, ReturnLength As Long) As Long
Public Declare Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

'FUNCION PARA SABER QUE SISTEMA OPERATIVO CORRE
'returns True if running Windows NT,
'Windows 2000, Windows XP, or .net server
Public Function IsWinNTPlus() As Boolean
   #If Win32 Then
      Dim OSV As OSVERSIONINFO
      OSV.OSVSize = Len(OSV)
      If GetVersionEx(OSV) = 1 Then
         IsWinNTPlus = (OSV.PlatformID = VER_PLATFORM_WIN32_NT) And (OSV.dwVerMajor >= 4)
      End If
   #End If
End Function

'FUNCION PARA DAR LOS PERMISOS NECESARIOS
Public Function EnableShutdownPrivledges() As Boolean
   Dim hProcessHandle As Long
   Dim hTokenHandle As Long
   Dim lpv_la As LUID
   Dim token As TOKEN_PRIVILEGES
   
   hProcessHandle = GetCurrentProcess()
   
   If hProcessHandle <> 0 Then
   
     'open the access token associated
     'with the current process. hTokenHandle
     'returns a handle identifying the
     'newly-opened access token
      If OpenProcessToken(hProcessHandle, _
                        (TOKEN_ADJUST_PRIVILEGES Or TOKEN_QUERY), _
                         hTokenHandle) <> 0 Then
   
        'obtain the locally unique identifier
        '(LUID) used on the specified system
        'to locally represent the specified
        'privilege name. Passing vbNullString
        'causes the api to attempt to find
        'the privilege name on the local system.
         If LookupPrivilegeValue(vbNullString, _
                                 "SeShutdownPrivilege", _
                                 lpv_la) <> 0 Then
         
           'TOKEN_PRIVILEGES contains info about
           'a set of privileges for an access token.
           'Prepare the TOKEN_PRIVILEGES structure
           'by enabling one privilege.
            With token
               .PrivilegeCount = 1
               .laa.udtLUID = lpv_la
               .laa.dwAttributes = SE_PRIVILEGE_ENABLED
            End With
   
           'Enable the shutdown privilege in
           'the access token of this process.
           'hTokenHandle: access token containing the
           '  privileges to be modified
           'DisableAllPrivileges: if True the function
           '  disables all privileges and ignores the
           '  NewState parameter. If FALSE, the
           '  function modifies privileges based on
           '  the information pointed to by NewState.
           'token: TOKEN_PRIVILEGES structure specifying
           '  an array of privileges and their attributes.
           '
           'Since were just adjusting to shut down,
           'BufferLength, PreviousState and ReturnLength
           'can be passed as null.
            If AdjustTokenPrivileges(hTokenHandle, _
                                     False, _
                                     token, _
                                     ByVal 0&, _
                                     ByVal 0&, _
                                     ByVal 0&) <> 0 Then
                                     
              'success, so return True
               EnableShutdownPrivledges = True
   
            End If  'AdjustTokenPrivileges
         End If  'LookupPrivilegeValue
      End If  'OpenProcessToken
   End If  'hProcessHandle
End Function

'FUNCION PARA REINICIAR EL SISTEMA
Public Sub ReiniciarPc()
    uflags = EWX_REBOOT Or EWX_FORCE
    If IsWinNTPlus() Then
        success = EnableShutdownPrivledges()
        If success Then Call ExitWindowsEx(uflags, 0&)
    Else
        '9x system, so just do it
        Call ExitWindowsEx(uflags, 0&)
    End If
End Sub


'FUNCIONA PARA APAGAR EL SISTEMA
Public Sub ApagarPc()
    uflags = EWX_POWEROFF Or EWX_FORCE
    If IsWinNTPlus() Then
        success = EnableShutdownPrivledges()
        If success Then Call ExitWindowsEx(uflags, 0&)
        'Shell "shutdown -r -t 0"
    Else
        '9x system, so just do it
        Call ExitWindowsEx(uflags, 0&)
    End If
End Sub

'FUNCION PARA SALIR DEL SISTEMA
Public Sub SalirSistema()
    uflags = EWX_LOGOFF Or EWX_FORCE
    If IsWinNTPlus() Then
        success = EnableShutdownPrivledges()
        If success Then Call ExitWindowsEx(uflags, 0&)
        'Shell "shutdown -r -t 0"
    Else
        '9x system, so just do it
        Call ExitWindowsEx(uflags, 0&)
    End If
End Sub


y para usarlas nomas asi:

Código (vb) [Seleccionar]
'PARA REINICIAR EL SISTEMA
Call ReiniciarPc

'PARA APAGAR EL ORDENADOR
Call ApagarPc