Sluk computeren med Windows XP

Tags:    visual-basic

Hvordan slukker men computeren fra Windows XP (Med kodning)?



4 svar postet i denne tråd vises herunder
1 indlæg har modtaget i alt 1 karma
Sorter efter stemmer Sorter efter dato
<quote>
har du prøvet med at se om koden til at slukke i tips og tricks virker, hvis du ikke gør skal du prøve med en kode til nt da windows xp og nt er nået de sammen, pricipet er nemlig netværk.

-Thomas


Har du koden til NT?</quote>
virker svarende i mit tidliger indlæg ikke så prøv denne




Exit Windows from VB
--------------------------------------------------------------------------------

Author: Jess Kjellmann (Kim Pedersen)
Subject: System
Updated: 25/11/1999
See also: Forcing a local or remote Windows NT system to reboot

--------------------------------------------------------------------------------

This tips shows you how to exit Windows from within VB. The tip uses the ExitWindowsEx API and it's great for enhancing an application that needs to restart Windows because it has made some changes to the system. This is slightly edited by me.




Add this code to a Module:

Option Explicit

Declare Function ExitWindowsEx lib "user32" (ByVal uFlags As Long, _
ByVal dwReserved As Long) As Long

Const EWX_LOGOFF As Long = 0
Const EWX_SHUTDOWN As Long = 1
Const EWX_REBOOT = 2
Const EWX_FORCE As Long = 4
Const EWX_POWEROFF As Long = 8
'-- End --'


To use the code add this line where you wish to shut down Windows:

Dim sPar As Long
sPar = ExitWindowEx(command, &H0)
The command parameter can be any of the following (From the win32 SDK):

command Description
EWX_SHUTDOWN Shuts down the system to a point at which it is safe to turn off the power. All file buffers have been flushed to disk, and all running processes have stopped.
EWX_LOGOFF Shuts down all processes running in the security context of the process that called the ExitWindowsEx function. Then it logs the user off.
EWX_POWEROFF Shuts down the system and turns off the power. The system must support the power-off feature.
EWX_REBOOT Shuts down the system and then restarts the system.

--------------------------------------------------------------------------------

EWX_FORCE (ADVANCED) Forces processes to terminate. When this flag is set, the system does not send the WM_QUERYENDSESSION and WM_ENDSESSION messages. This can cause the applications to lose data. Therefore, you should only use this flag in an emergency.

When ExitWindowsEx has been executed the focus returns to your application. Remeber to save your work before executing this code. Otherwise all your work might be lost.

If the shutdown is succesful a non-zero value will be returned in sPar. 0 will be returned if shutdown was unsuccesful. Use this for error trapping.




**************************
eller denne
***********


Forcing a local or remote Windows NT system to reboot
--------------------------------------------------------------------------------

Author: Steve McMahon
Subject: System
Updated: 13/06/1999

--------------------------------------------------------------------------------

Under Windows NT, you can force a timed system shutdown on either the local machine or a remote network machine. This code tip shows how to do it. You can specifiy how long it will be before the machine will be shutdown in seconds (a zero value shuts down immediately), how remorseless the shutdown process should be (whether it allows any unsaved work to be saved) and whether the machine will be rebooted.

Start a new project in VB. Add a new module to the project.




Add this code to a Module:

Option Explicit

' To Determine if we are running NT or not:
Private Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * 128 ' Maintenance string for PSS usage
End Type

Private Declare Function GetVersionEx Lib "kernel32" Alias _
"GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Private Const VER_PLATFORM_WIN32_NT = 2
Private Const VER_PLATFORM_WIN32_WINDOWS = 1
Private Const VER_PLATFORM_WIN32s = 0

' To Report API errors:
Private Const FORMAT_MESSAGE_ALLOCATE_BUFFER = &H100
Private Const FORMAT_MESSAGE_ARGUMENT_ARRAY = &H2000
Private Const FORMAT_MESSAGE_FROM_HMODULE = &H800
Private Const FORMAT_MESSAGE_FROM_STRING = &H400
Private Const FORMAT_MESSAGE_FROM_SYSTEM = &H1000
Private Const FORMAT_MESSAGE_IGNORE_INSERTS = &H200
Private Const FORMAT_MESSAGE_MAX_WIDTH_MASK = &HFF
Private Declare Function FormatMessage Lib "kernel32" Alias _
"FormatMessageA" (ByVal dwFlags As Long, lpSource As Any, _
ByVal dwMessageId As Long, ByVal dwLanguageId As Long, _
ByVal lpBuffer As String, ByVal nSize As Long, _
Arguments As Long) As Long

' Win NT Only

Private Type LARGE_INTEGER
LowPart As Long
HighPart As Long
End Type

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(0 To 0) As LUID_AND_ATTRIBUTES
End Type

Private Declare Function GetCurrentProcess Lib "kernel32" () 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 CloseHandle Lib "kernel32" _
(ByVal hObject As Long) As Long

Private Declare Function GetTokenInformation Lib "advapi32.dll" _
(ByVal TokenHandle As Long, TokenInformationClass As Integer, _
TokenInformation As Any, ByVal TokenInformationLength As Long, _
ReturnLength As Long) As Long

Private Declare Function AdjustTokenPrivileges Lib "advapi32.dll" _
(ByVal TokenHandle As Long, ByVal DisableAllPrivileges As Long, _
NewState As TOKEN_PRIVILEGES, ByVal BufferLength As Long, _
PreviousState As TOKEN_PRIVILEGES, ReturnLength As Long) As Long

Private Declare Function LookupPrivilegeValue Lib "advapi32.dll" _
Alias "LookupPrivilegeValueA" (ByVal lpSystemName As String, _
ByVal lpName As String, lpLuid As LUID) As Long

Private Const SE_SHUTDOWN_NAME = "SeShutdownPrivilege"
Private Const SE_PRIVILEGE_ENABLED = &H2

Private Const READ_CONTROL = &H20000
Private Const STANDARD_RIGHTS_ALL = &H1F0000
Private Const STANDARD_RIGHTS_EXECUTE = (READ_CONTROL)
Private Const STANDARD_RIGHTS_READ = (READ_CONTROL)
Private Const STANDARD_RIGHTS_REQUIRED = &HF0000
Private Const STANDARD_RIGHTS_WRITE = (READ_CONTROL)

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_READ = (STANDARD_RIGHTS_READ Or _
TOKEN_QUERY)

Private Const TOKEN_WRITE = (STANDARD_RIGHTS_WRITE Or _
TOKEN_ADJUST_PRIVILEGES Or _
TOKEN_ADJUST_GROUPS Or _
TOKEN_ADJUST_DEFAULT)

Private Const TOKEN_EXECUTE = (STANDARD_RIGHTS_EXECUTE)

Private Const TokenDefaultDacl = 6
Private Const TokenGroups = 2
Private Const TokenImpersonationLevel = 9
Private Const TokenOwner = 4
Private Const TokenPrimaryGroup = 5
Private Const TokenPrivileges = 3
Private Const TokenSource = 7
Private Const TokenStatistics = 10
Private Const TokenType = 8
Private Const TokenUser = 1

Private Declare Function InitiateSystemShutdown Lib "advapi32.dll" _
Alias "InitiateSystemShutdownA" (ByVal lpMachineName As String, _
ByVal lpMessage As String, ByVal dwTimeout As Long, _
ByVal bForceAppsClosed As Long, _
ByVal bRebootAfterShutdown As Long) As Long

Private Declare Function AbortSystemShutdown Lib "advapi32.dll" _
Alias "AbortSystemShutdownA" (ByVal lpMachineName As String) _
As Long

Public Function WinError(ByVal lLastDLLError As Long) As String

Dim sBuff As String
Dim lCount As Long

' Return the error message associated with LastDLLError:
sBuff = String$(256, 0)
lCount = FormatMessage(FORMAT_MESSAGE_FROM_SYSTEM Or _
FORMAT_MESSAGE_IGNORE_INSERTS, 0, lLastDLLError, 0&, _
sBuff, Len(sBuff), ByVal 0)

If lCount Then
WinError = Left$(sBuff, lCount)
End If

End Function

Public Function IsNT() As Boolean

Static bOnce As Boolean
Static bValue As Boolean

' Return whether the system is running NT or not:
If Not (bOnce) Then
Dim tVI As OSVERSIONINFO
tVI.dwOSVersionInfoSize = Len(tVI)
If (GetVersionEx(tVI) <> 0) Then
bValue = (tVI.dwPlatformId = VER_PLATFORM_WIN32_NT)
bOnce = True
End If
End If
IsNT = bValue

End Function

Private Function NTEnableShutDown(ByRef sMsg As String) As Boolean

Dim tLUID As LUID
Dim hProcess As Long
Dim hToken As Long
Dim tTP As TOKEN_PRIVILEGES, tTPOld As TOKEN_PRIVILEGES
Dim lTpOld As Long
Dim lR As Long
' Under NT we must enable the SE_SHUTDOWN_NAME privilege in the
' process we're trying to shutdown from, otherwise a call to
' try to shutdown has no effect!

' Find the LUID of the Shutdown privilege token:
lR = LookupPrivilegeValue(vbNullString, SE_SHUTDOWN_NAME, tLUID)

' If we get it:
If (lR <> 0) Then
' Get the current process handle:
hProcess = GetCurrentProcess()
If (hProcess <> 0) Then
' Open the token for adjusting and querying (if
' we can - user may not have rights):
lR = OpenProcessToken(hProcess, TOKEN_ADJUST_PRIVILEGES _
Or TOKEN_QUERY, hToken)
If (lR <> 0) Then
' Ok we can now adjust the
' shutdown priviledges:
With tTP
.PrivilegeCount = 1
With .Privileges(0)
.Attributes = SE_PRIVILEGE_ENABLED
.pLuid.HighPart = tLUID.HighPart
.pLuid.LowPart = tLUID.LowPart
End With
End With

' Now allow this process to shutdown the system:
lR = AdjustTokenPrivileges(hToken, 0, tTP, Len(tTP), _
tTPOld, lTpOld)
If (lR <> 0) Then
NTEnableShutDown = True
Else
Err.Raise eeSSDErrorBase + 6, App.EXEName & ".mShutDown", _
"Can't enable shutdown: You do not have the _
privileges to shutdown this system. _
[" & WinError(Err.LastDllError) & "]"
End If

' Remember to close the handle when finished with it:
CloseHandle hToken
Else
Err.Raise eeSSDErrorBase + 6, App.EXEName & ".mShutDown", _
"Can't enable shutdown: You do not have the _
privileges to shutdown this system. [" & _
WinError(Err.LastDllError) & "]"
End If
Else
Err.Raise eeSSDErrorBase + 5, App.EXEName & ".mShutDown", _
"Can't enable shutdown: Can't determine the current _
process. [" & WinError(Err.LastDllError) & "]"

End If
Else
Err.Raise eeSSDErrorBase + 4, App.EXEName & ".mShutDown", _
"Can't enable shutdown: Can't find the SE_SHUTDOWN_NAME _
privilege value. [" & WinError(Err.LastDllError) & "]"
End If

End Function

Public Function NTForceTimedShutdown _
(Optional ByVal lTimeOut As Long = -1, _
Optional ByVal sMsg As String = "", _
Optional ByVal sMachineNetworkName As String = vbNullString, _
Optional ByVal bForceAppsToClose As Boolean = False, _
Optional ByVal bReboot As Boolean = False) As Boolean

Dim lR As Long
If IsNT Then
' Make sure we have enabled the privilege to shutdown
' for this process if we're running NT:
If Not (NTEnableShutDown(sMsg)) Then
Exit Function
End If

' This is the code to do a timed shutdown:
lR = InitiateSystemShutdown(sMachineNetworkName, sMsg, _
lTimeOut, bForceAppsToClose, bReboot)
If (lR = 0) Then
Err.Raise eeSSDErrorBase + 2, App.EXEName & ".mShutDown", _
"InitiateSystemShutdown failed: " & _
WinError(Err.LastDllError)
End If
Else
Err.Raise eeSSDErrorBase + 1, App.EXEName & ".mShutDown", _
"Function only available under Windows NT."
End If

End Function

Public Function NTAbortTimedShutdown(Optional ByVal sMachineNetworkName _
As String = vbNullString)

AbortSystemShutdown sMachineNetworkName

End Function

'-- End --'


To try out a shutdown, add two Command buttons and a Text box to the project's form and then paste in the following code:
Note you should save your work before running it, because the shutdown will kill VB without asking you to save any changes!

Then put the following code under the Command Buttons' click event:

Private Sub Command1_Click()

If (MsgBox("Are you sure you want to initiate a forced, _
timed shutdown?", vbYesNo Or vbQuestion) = vbYes) Then

NTForceTimedShutdown CLng(Text1.Text), _
"You're gonna get shutdown in " & Text1.Text & " s..."
End If

End Sub

Private Sub Command2_Click()
NTAbortTimedShutdown
End Sub

Private Sub Form_Load()
Text1.Text = 60
End Sub
'-- End --'


Clicking on the first Command button will initiate a shutdown, with a timeout value set to the number of seconds entered into the text box. To stop the shutdown, click the second Command button.

**************
som jeg fand på vbcodemagian!

-Thomas



<quote>Hvordan slukker men computeren fra Windows XP (Med kodning)?</quote>
har du prøvet med at se om kode ntil at slukke i tips og tricks virker, hvis du ikke gør sakl du prøve med en kode til nt da windows xp og nt er nået de sammen, pricipet er nemlig netværk.

-Thomas




<quote>
har du prøvet med at se om koden til at slukke i tips og tricks virker, hvis du ikke gør skal du prøve med en kode til nt da windows xp og nt er nået de sammen, pricipet er nemlig netværk.

-Thomas
</quote>

Har du koden til NT?



<quote>
har du prøvet med at se om koden til at slukke i tips og tricks virker, hvis du ikke gør skal du prøve med en kode til nt da windows xp og nt er nået de sammen, pricipet er nemlig netværk.

-Thomas


Har du koden til NT?</quote>

prøv med nogle af følgende eksempler

*********************************'

'1 eksempel 1

'Øverste del skal i "General" og resten til en knap


Option Explicit

#If Win32 Then
Private Declare Function ShutdownWindows _
Lib "user32" Alias _
"ExitWindowsEx" (ByVal uFlags As Long, _
ByVal dwReserved As Long) As Long
#Else
Private Declare Function ShutdownWindows _
Lib "user" Alias _
"ExitWindows" (ByVal wReturnCode As Integer, _
ByVal dwReserved As Integer) As Integer
#End If
Private Const EWX_LOGOFF = 0
Private Const EWX_SHUTDOWN = 1
Private Const EWX_REBOOT = 2
Private Const EWX_FORCE = 4

'---------------------------------------------
Private Sub Command1_Click()
ShutdownWindows EWX_SHUTDOWN, 1
End Sub

'***********'
*****************************************
'2

'declaration

Private Const EWX_SHUTDOWN As Long = 1
Private Declare Function ExitWindowsEx Lib "user32" (ByVal dwOptions As Long, ByVal dwReserved As Long) As Long


'code

'shut down the computer
lngResult = ExitWindowsEx(EWX_SHUTDOWN, 0&)

********************************************
'3
'decleration

Private Const EWX_LogOff As Long = 0
Private Declare Function ExitWindowsEx Lib "user32" (ByVal dwOptions As Long, ByVal dwReserved As Long) As Long


'code
'close all programs and log on as a different user
lngResult = ExitWindowsEx(EWX_LogOff, 0&)



*********************************************



jeg søgte på følgende web sider

http://users.cybercity.dk/~cfs4636/
http://www.mobilixnet.dk/~mob83058/vbtext/
http://sitelevel.whatuseek.com/query.go
http://www.vbcodemagician.dk/
http://www.vbcode.com/




t