Setting Monitor Resolution


Posted by Damien on July 23, 2001 9:12 PM

Anyone know how to set the resolution of the users monitor in a macro or if it can be done ?

Posted by Ivan F Moala on July 23, 2001 11:31 PM

do this is via API.....

'**************************************
'Windows API/Global Declarations for
'Change Windows Display resolution
'**************************************
Public Const EWX_LOGOFF = 0
Public Const EWX_SHUTDOWN = 1
Public Const EWX_REBOOT = 2
Public Const EWX_FORCE = 4
Public Const CCDEVICENAME = 32
Public Const CCFORMNAME = 32
Public Const DM_BITSPERPEL = &H40000
Public Const DM_PELSWIDTH = &H80000
Public Const DM_PELSHEIGHT = &H100000
Public Const CDS_UPDATEREGISTRY = &H1
Public Const CDS_TEST = &H4
Public Const DISP_CHANGE_SUCCESSFUL = 0
Public Const DISP_CHANGE_RESTART = 1


Type typDevMODE
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


Declare Function EnumDisplaySettings Lib "user32" Alias "EnumDisplaySettingsA" _
(ByVal lpszDeviceName As Long, ByVal iModeNum As Long, lptypDevMode As Any) As Boolean


Declare Function ChangeDisplaySettings Lib "user32" Alias _
"ChangeDisplaySettingsA" (lptypDevMode As Any, ByVal dwFlags As Long) As Long


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

Sub ChangeScreen_Resol()
Dim typDevM As typDevMODE
Dim lngResult As Long
Dim intAns As Integer
' Retrieve info about the current graphics mode
' on the current display device.
lngResult = EnumDisplaySettings(0, 0, typDevM)
' Set the new resolution. Don't change the color
' depth so a restart is not necessary.

With typDevM
.dmFields = DM_PELSWIDTH Or DM_PELSHEIGHT
.dmPelsWidth = 800 'ScreenWidth (640,800,1024, etc)
.dmPelsHeight = 600 'ScreenHeight (480,600,768, etc)
End With
' Change the display settings to the specified graphics mode.
lngResult = ChangeDisplaySettings(typDevM, CDS_TEST)

Select Case lngResult
Case DISP_CHANGE_RESTART
intAns = MsgBox("You must restart your computer To apply these changes." & _
vbCrLf & vbCrLf & "Do you want To restart now?", _
vbYesNo + vbSystemModal, "Screen Resolution")
If intAns = vbYes Then Call ExitWindowsEx(EWX_REBOOT, 0)
Case DISP_CHANGE_SUCCESSFUL
Call ChangeDisplaySettings(typDevM, CDS_UPDATEREGISTRY)
MsgBox "Screen resolution changed", vbInformation, "Resolution Changed"
Case Else
MsgBox "Mode Not supported", vbSystemModal, "Error"
End Select


End Sub


Ivan



Posted by G-Man on July 23, 2001 11:37 PM

Damien,

Are you really trying to adjust the user's screen resolution? Or are you trying to adjust
your spreadsheet to display 'full screen' by reading the display resolution and adjusting
the 'zoom' setting automatically?

I use a function someone shared with me sometime back that returns the current display
resolution as '640', '800', '1024', etc. I coupled that with a macro that adjusts the zoom
setting based on reading the value of the display resolution. The macro is entered in the
Workbook_Open module and it automatically adjusts the screen when the workbook is opened.

Here is the complete function/macro:
_________________________________________________________________
Declare Function GetSystemMetrics Lib "user32" _
(ByVal nIndex As Long) As Long
Const SM_CYSCREEN As Long = 1
Const SM_CXSCREEN As Long = 0
_________________________________________________________________
Sub Set_Screen()
Dim lWidth As Long
Dim lHeight As Long
lWidth = GetSystemMetrics(SM_CXSCREEN)
lHeight = GetSystemMetrics(SM_CYSCREEN)

[af1] = lWidth 'cell AF1 is in a hidden column

If [af1] = 640 Then
ActiveWindow.Zoom = 100
ElseIf [af1] = 800 Then
ActiveWindow.Zoom = 125
ElseIf [af1] = 1024 Then
ActiveWindow.Zoom = 160
ElseIf [af1] = 1152 Then
ActiveWindow.Zoom = 180
ElseIf [af1] = 1280 Then
ActiveWindow.Zoom = 200
ElseIf [af1] = 1600 Then
ActiveWindow.Zoom = 250
Else
End If
End Sub

Of course, the adjustments could be done with a Select Case scenario, but this works well for me.
These zoom settings work properly for spreadsheets originally created in a 640x480 environment.
I have found that if the spreadsheet is created in an 800x600 display setting, the zoom settings
have to be adjusted to give the desired results.

Anyway, if this is not what you are getting at, I apologize for much ado about nothing....

G-Man