VBcoders Guest



Don't have an account yet? Register
 


Forgot Password?



Change Desktop Resolution

by Punit Arora (1 Submission)
Category: Graphics
Compatability: VB 6.0
Difficulty: Unknown Difficulty
Originally Published: Tue 26th May 2009
Date Added: Mon 8th February 2021
Rating: (1 Votes)

Change Desktop Resolution

Rate Change Desktop Resolution




Dim bWindowsNT As Boolean
'
' Operating System Constants, Types and Declares
'
Const VER_PLATFORM_WIN32s = 0
Const VER_PLATFORM_WIN32_WINDOWS = 1
Const VER_PLATFORM_WIN32_NT = 2

Private Type OSVERSIONINFO
    dwOSVersionInfoSize As Long
    dwMajorVersion      As Long
    dwMinorVersion      As Long
    dwBuildNumber       As Long
    dwPlatformId        As Long
    szCSDVersion        As String * 128
End Type

Private Declare Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long
'
' Shutdown/change resolution Constants, Types and Declares
'
Const EWX_LOGOFF = 0
Const EWX_SHUTDOWN = 1
Const EWX_REBOOT = 2
'
' Using this option to shutdown windows does not send
' the WM_QUERYENDSESSION and WM_ENDSESSION messages to
' the open applications. Thus, those apps may loose
' any unsaved data.
'
Const EWX_FORCE = 4
Const CCDEVICENAME = 32
Const CCFORMNAME = 32
Const DM_BITSPERPEL = &H40000
Const DM_PELSWIDTH = &H80000
Const DM_PELSHEIGHT = &H100000
Const CDS_UPDATEREGISTRY = &H1
Const CDS_TEST = &H2
Const CDS_FULLSCREEN = &H4
Const DISP_CHANGE_SUCCESSFUL = 0
Const DISP_CHANGE_RESTART = 1
 
Const HWND_BROADCAST = &HFFFF&
Const WM_DISPLAYCHANGE = &H7E&
Const SPI_SETNONCLIENTMETRICS = 42

Private Type DEVMODE
    dmDeviceName       As String * CCDEVICENAME
    dmSpecVersion      As Integer
    dmDriverVersion    As Integer
    dmSize             As Integer
    dmDriverExtra      As Integer
    dmFields           As Long
    dmOrientation      As Integer
    dmPaperSize        As Integer
    dmPaperLength      As Integer
    dmPaperWidth       As Integer
    dmScale            As Integer
    dmCopies           As Integer
    dmDefaultSource    As Integer
    dmPrintQuality     As Integer
    dmColor            As Integer
    dmDuplex           As Integer
    dmYResolution      As Integer
    dmTTOption         As Integer
    dmCollate          As Integer
    dmFormName         As String * CCFORMNAME
    dmUnusedPadding    As Integer
    dmBitsPerPel       As Integer
    dmPelsWidth        As Long
    dmPelsHeight       As Long
    dmDisplayFlags     As Long
    dmDisplayFrequency As Long
End Type

Private Declare Function EnumDisplaySettings Lib "user32" Alias "EnumDisplaySettingsA" (ByVal lpszDeviceName As Long, ByVal iModeNum As Long, lpDevMode As Any) As Boolean
Private Declare Function ChangeDisplaySettings Lib "user32" Alias "ChangeDisplaySettingsA" (lpDevMode As Any, ByVal dwFlags As Long) As Long
Private Declare Function ExitWindowsEx Lib "user32" (ByVal uFlags As Long, ByVal dwReserved As Long) As Long
Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
'
' The following are required to shutdown NT.
'
Const ERROR_NOT_ALL_ASSIGNED = 1300
Const SE_PRIVILEGE_ENABLED = 2
Const TOKEN_QUERY = &H8
Const TOKEN_ADJUST_PRIVILEGES = &H20

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 As LUID_AND_ATTRIBUTES
End Type

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
Private Declare Function LookupPrivilegeValue Lib "advapi32.dll" Alias "LookupPrivilegeValueA" (ByVal lpSystemName As Any, ByVal lpName As String, lpUid As LUID) 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 GetCurrentProcess Lib "kernel32" () As Long

Private Sub cmdQuit_Click()
Unload Me
End Sub

Private Sub cmdChange_Click()
Dim DevM    As DEVMODE
Dim lResult As Long
Dim iAns    As Integer
'
' Retrieve info about the current graphics mode
' on the current display device.
'
lResult = EnumDisplaySettings(0, 0, DevM)
'
' Set the new resolution. Don't change the color
' depth so a restart is not necessary.
'
With DevM
    .dmFields = DM_PELSWIDTH Or DM_PELSHEIGHT 'Or DM_BITSPERPEL
    If optRes(0) Then
        .dmPelsWidth = 640  'ScreenWidth
        .dmPelsHeight = 480 'ScreenHeight
    ElseIf optRes(1) Then
        .dmPelsWidth = 800
        .dmPelsHeight = 600
    Else
        .dmPelsWidth = 1024
        .dmPelsHeight = 768
    End If
    '.dmBitsPerPel = 32 (could be 8, 16, 32 or even 4)
End With
'
' Change the display settings to the specified graphics mode.
'
lResult = ChangeDisplaySettings(DevM, CDS_FULLSCREEN)
Select Case lResult
    Case DISP_CHANGE_RESTART
        iAns = MsgBox("You must restart your computer to apply these changes." & _
            vbCrLf & vbCrLf & "Do you want to restart now?", _
            vbYesNo + vbSystemModal, "Screen Resolution")
        If iAns = vbYes Then Call ExitWindowsEx(EWX_REBOOT, 0)
    Case DISP_CHANGE_SUCCESSFUL
        Call ChangeDisplaySettings(DevM, CDS_UPDATEREGISTRY)
        Call SendMessage(HWND_BROADCAST, WM_DISPLAYCHANGE, SPI_SETNONCLIENTMETRICS, ByVal 0&)
        MsgBox "Screen resolution changed", vbInformation, "Resolution Changed"
    Case Else
        MsgBox "Mode not supported", vbSystemModal, "Error"
End Select



End Sub


Private Sub cmdReboot_Click()
Dim tLuid          As LUID
Dim tTokenPriv     As TOKEN_PRIVILEGES
Dim tPrevTokenPriv As TOKEN_PRIVILEGES
Dim lResult        As Long
Dim lToken         As Long
Dim lLenBuffer     As Long
Dim lMode As Long
'

'
If optShut(0) Then
    lMode = EWX_LOGOFF
ElseIf optShut(1) Then
    lMode = EWX_REBOOT
ElseIf optShut(2) Then
    lMode = EWX_SHUTDOWN
Else: lMode = EWX_FORCE
End If

If Not bWindowsNT Then
    Call ExitWindowsEx(lMode, 0)
Else
    '
    ' Get the access token of the current process.  Get it
    ' with the privileges of querying the access token and
    ' adjusting its privileges.
    '
    lResult = OpenProcessToken(GetCurrentProcess(), TOKEN_ADJUST_PRIVILEGES Or TOKEN_QUERY, lToken)
    If lResult = 0 Then
        Exit Sub 'Failed
    End If
    '
    ' Get the locally unique identifier (LUID) which
    ' represents the shutdown privilege.
    '
    lResult = LookupPrivilegeValue(0&, "SeShutdownPrivilege", tLuid)
    If lResult = 0 Then Exit Sub 'Failed
    '
    ' Populate the new TOKEN_PRIVILEGES values with the LUID
    ' and allow your current process to shutdown the computer.
    '
    With tTokenPriv
        .PrivilegeCount = 1
        .Privileges.Attributes = SE_PRIVILEGE_ENABLED
        .Privileges.pLuid = tLuid
    lResult = AdjustTokenPrivileges(lToken, False, tTokenPriv, Len(tPrevTokenPriv), tPrevTokenPriv, lLenBuffer)
    End With
    
    If lResult = 0 Then
        Exit Sub 'Failed
    Else
        If Err.LastDllError = ERROR_NOT_ALL_ASSIGNED Then Exit Sub 'Failed
    End If
    '
    '  Shutdown Windows.
    '
    Call ExitWindowsEx(lMode, 0)
End If
End Sub


Private Sub Command1_Click()
End Sub

Private Sub Form_Load()
Dim OSInfo As OSVERSIONINFO
'
' See if we are running Windows 9x or NT.
'
OSInfo.dwOSVersionInfoSize = Len(OSInfo)
Call GetVersionEx(OSInfo)
bWindowsNT = (OSInfo.dwPlatformId = VER_PLATFORM_WIN32_NT)
End Sub




Download this snippet    Add to My Saved Code

Change Desktop Resolution Comments

No comments have been posted about Change Desktop Resolution. Why not be the first to post a comment about Change Desktop Resolution.

Post your comment

Subject:
Message:
0/1000 characters