We will use VBA to develop an Excel user-defined function (UDF) capable of returning certain dimensional information about your computer’s display screen, including the screen size. In particular, it will determine the zoom factor for Excel and other Office applications to display items actual-size (as when printed). If your computer is configured with multiple monitors, this UDF’s return value will apply to the screen currently displaying Excel’s ActiveWindow. Although this discussion is focused on Excel, the results apply generally to all Windows applications.
Dots/Inch, Pixels/Inch, and Points
Microsoft Windows normally assumes a logical value of 96 dots per inch for desktop and laptop computer display screens. (Tablet computers like Surface Pro might have a different logical value.) But your screen’s display density depends on its physical dimensions (inches) and the video controller’s resolution (pixels). We will use the term pixels per inch (ppi) when referring to display screens and dots per inch (dpi) when referring to the logical value assumed by Windows.
Windows also measures certain items using points. There are 72 standard points per inch. Using 96 dpi, Windows assumes each point requires 1.333… dots for display (or 4 dots for every 3 points).
When in Normal view, Excel sets row height in terms of points. (Logical pixels, which are actually dots in our terminology, might also be indicated.) But have you ever set a row height of 72 points (96 dots) and measured with a ruler? If so, you might find it measures more or less than an inch, depending on your monitor and Excel’s zoom factor (in the View ribbon).
Excel in Normal view also sets column width in points, but this is simply confusing. A column width of N “points” actually means N zero characters (0) will fit in the column when it is formatted with the Normal style font (see the Home ribbon). For example, my Normal style uses Calibri (Body) Regular size 11 font; therefore, setting a column width of 8 “points” will fit 8 zeros (00000000) of Calibri Regular size 11. Excel calls this 8 “point” width equivalent to 61 logical pixels (or dots) assuming 96 dpi, so this 8 “point” width is actually 61x72/96=45.75 points (0.635 inch).
Switching to Page Layout view (on the View ribbon), Excel uses inches instead of points for row height and column width. However, the column width seems to change when the view is changed. In my example above, the 8 “point” column changed to 0.69 inch (66 logical pixels instead of 61). If you can explain why, please post a Comment below. Horizontal and vertical rulers are displayed in Page Layout view. As mentioned before, your ruler might not match Excel’s ruler depending on your monitor and the zoom factor.
The Screen Function Module
Now let’s find out how to get dimensional information about a computer’s actual display screen. The complete VBA code for our Screen UDF module is listed below. Further discussion follows the listing.
' This module includes Private declarations for certain Windows API functions
' plus code for Public Function Screen, which returns metrics for the screen displaying ActiveWindow
' This module requires VBA7 (Office 2010 or later)
' DEVELOPER: J. Woolley (for wellsr.com)
Private Declare PtrSafe Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As Long
Private Declare PtrSafe Function GetDeviceCaps Lib "gdi32" (ByVal hDC As LongPtr, ByVal nIndex As Long) As Long
Private Declare PtrSafe Function GetDC Lib "user32" (ByVal hWnd As LongPtr) As LongPtr
Private Declare PtrSafe Function ReleaseDC Lib "user32" (ByVal hWnd As LongPtr, ByVal hDC As LongPtr) As Long
Private Declare PtrSafe Function GetActiveWindow Lib "user32" () As LongPtr
Private Declare PtrSafe Function MonitorFromWindow Lib "user32" _
(ByVal hWnd As LongPtr, ByVal dwFlags As Long) As LongPtr
Private Declare PtrSafe Function GetMonitorInfo Lib "user32" Alias "GetMonitorInfoA" _
(ByVal hMonitor As LongPtr, ByRef lpMI As MONITORINFOEX) As Boolean
Private Declare PtrSafe Function CreateDC Lib "gdi32" Alias "CreateDCA" _
(ByVal lpDriverName As String, ByVal lpDeviceName As String, ByVal lpOutput As String, lpInitData As LongPtr) As LongPtr
Private Declare PtrSafe Function DeleteDC Lib "gdi32" (ByVal hDC As LongPtr) As Long
Private Const SM_CMONITORS As Long = 80 ' number of display monitors
Private Const MONITOR_CCHDEVICENAME As Long = 32 ' device name fixed length
Private Const MONITOR_PRIMARY As Long = 1
Private Const MONITOR_DEFAULTTONULL As Long = 0
Private Const MONITOR_DEFAULTTOPRIMARY As Long = 1
Private Const MONITOR_DEFAULTTONEAREST As Long = 2
Private Type RECT
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type
Private Type MONITORINFOEX
cbSize As Long
rcMonitor As RECT
rcWork As RECT
dwFlags As Long
szDevice As String * MONITOR_CCHDEVICENAME
End Type
Private Enum DevCap ' GetDeviceCaps nIndex (video displays)
HORZSIZE = 4 ' width in millimeters
VERTSIZE = 6 ' height in millimeters
HORZRES = 8 ' width in pixels
VERTRES = 10 ' height in pixels
BITSPIXEL = 12 ' color bits per pixel
LOGPIXELSX = 88 ' horizontal DPI (assumed by Windows)
LOGPIXELSY = 90 ' vertical DPI (assumed by Windows)
COLORRES = 108 ' actual color resolution (bits per pixel)
VREFRESH = 116 ' vertical refresh rate (Hz)
End Enum
Public Function Screen(Item As String) As Variant
' Return display screen Item for monitor displaying ActiveWindow
' Patterned after Excel's built-in information functions CELL and INFO
' Supported Item values (each must be a string, but alphabetic case is ignored):
' HorizontalResolution or pixelsX
' VerticalResolution or pixelsY
' WidthInches or inchesX
' HeightInches or inchesY
' DiagonalInches or inchesDiag
' PixelsPerInchX or ppiX
' PixelsPerInchY or ppiY
' PixelsPerInch or ppiDiag
' WinDotsPerInchX or dpiX
' WinDotsPerInchY or dpiY
' WinDotsPerInch or dpiWin ' DPI assumed by Windows
' AdjustmentFactor or zoomFac ' adjustment to match actual size (ppiDiag/dpiWin)
' IsPrimary ' True if primary display
' DisplayName ' name recognized by CreateDC
' Update ' update cells referencing this UDF and return date/time
' Help ' display all recognized Item string values
' EXAMPLE: =Screen("pixelsX")
' Function Returns #VALUE! for invalid Item
Dim xHSizeSq As Double, xVSizeSq As Double, xPix As Double, xDot As Double
Dim hWnd As LongPtr, hDC As LongPtr, hMonitor As LongPtr
Dim tMonitorInfo As MONITORINFOEX
Dim nMonitors As Integer
Dim vResult As Variant
Dim sItem As String
Application.Volatile
nMonitors = GetSystemMetrics(SM_CMONITORS)
If nMonitors < 2 Then
nMonitors = 1 ' in case GetSystemMetrics failed
hWnd = 0
Else
hWnd = GetActiveWindow()
hMonitor = MonitorFromWindow(hWnd, MONITOR_DEFAULTTONULL)
If hMonitor = 0 Then
Debug.Print "ActiveWindow does not intersect a monitor"
hWnd = 0
Else
tMonitorInfo.cbSize = Len(tMonitorInfo)
If GetMonitorInfo(hMonitor, tMonitorInfo) = False Then
Debug.Print "GetMonitorInfo failed"
hWnd = 0
Else
hDC = CreateDC(tMonitorInfo.szDevice, 0, 0, 0)
If hDC = 0 Then
Debug.Print "CreateDC failed"
hWnd = 0
End If
End If
End If
End If
If hWnd = 0 Then
hDC = GetDC(hWnd)
tMonitorInfo.dwFlags = MONITOR_PRIMARY
tMonitorInfo.szDevice = "PRIMARY" & vbNullChar
End If
sItem = Trim(LCase(Item))
Select Case sItem
Case "horizontalresolution", "pixelsx" ' HorizontalResolution (pixelsX)
vResult = GetDeviceCaps(hDC, DevCap.HORZRES)
Case "verticalresolution", "pixelsy" ' VerticalResolution (pixelsY)
vResult = GetDeviceCaps(hDC, DevCap.VERTRES)
Case "widthinches", "inchesx" ' WidthInches (inchesX)
vResult = GetDeviceCaps(hDC, DevCap.HORZSIZE) / 25.4
Case "heightinches", "inchesy" ' HeightInches (inchesY)
vResult = GetDeviceCaps(hDC, DevCap.VERTSIZE) / 25.4
Case "diagonalinches", "inchesdiag" ' DiagonalInches (inchesDiag)
vResult = Sqr(GetDeviceCaps(hDC, DevCap.HORZSIZE) ^ 2 + GetDeviceCaps(hDC, DevCap.VERTSIZE) ^ 2) / 25.4
Case "pixelsperinchx", "ppix" ' PixelsPerInchX (ppiX)
vResult = 25.4 * GetDeviceCaps(hDC, DevCap.HORZRES) / GetDeviceCaps(hDC, DevCap.HORZSIZE)
Case "pixelsperinchy", "ppiy" ' PixelsPerInchY (ppiY)
vResult = 25.4 * GetDeviceCaps(hDC, DevCap.VERTRES) / GetDeviceCaps(hDC, DevCap.VERTSIZE)
Case "pixelsperinch", "ppidiag" ' PixelsPerInch (ppiDiag)
xHSizeSq = GetDeviceCaps(hDC, DevCap.HORZSIZE) ^ 2
xVSizeSq = GetDeviceCaps(hDC, DevCap.VERTSIZE) ^ 2
xPix = GetDeviceCaps(hDC, DevCap.HORZRES) ^ 2 + GetDeviceCaps(hDC, DevCap.VERTRES) ^ 2
vResult = 25.4 * Sqr(xPix / (xHSizeSq + xVSizeSq))
Case "windotsperinchx", "dpix" ' WinDotsPerInchX (dpiX)
vResult = GetDeviceCaps(hDC, DevCap.LOGPIXELSX)
Case "windotsperinchy", "dpiy" ' WinDotsPerInchY (dpiY)
vResult = GetDeviceCaps(hDC, DevCap.LOGPIXELSY)
Case "windotsperinch", "dpiwin" ' WinDotsPerInch (dpiWin)
xHSizeSq = GetDeviceCaps(hDC, DevCap.HORZSIZE) ^ 2
xVSizeSq = GetDeviceCaps(hDC, DevCap.VERTSIZE) ^ 2
xDot = GetDeviceCaps(hDC, DevCap.LOGPIXELSX) ^ 2 * xHSizeSq + GetDeviceCaps(hDC, DevCap.LOGPIXELSY) ^ 2 * xVSizeSq
vResult = Sqr(xDot / (xHSizeSq + xVSizeSq))
Case "adjustmentfactor", "zoomfac" ' AdjustmentFactor (zoomFac)
xHSizeSq = GetDeviceCaps(hDC, DevCap.HORZSIZE) ^ 2
xVSizeSq = GetDeviceCaps(hDC, DevCap.VERTSIZE) ^ 2
xPix = GetDeviceCaps(hDC, DevCap.HORZRES) ^ 2 + GetDeviceCaps(hDC, DevCap.VERTRES) ^ 2
xDot = GetDeviceCaps(hDC, DevCap.LOGPIXELSX) ^ 2 * xHSizeSq + GetDeviceCaps(hDC, DevCap.LOGPIXELSY) ^ 2 * xVSizeSq
vResult = 25.4 * Sqr(xPix / xDot)
Case "isprimary" ' IsPrimary
vResult = CBool(tMonitorInfo.dwFlags And MONITOR_PRIMARY)
Case "displayname" ' DisplayName
vResult = tMonitorInfo.szDevice & vbNullChar
vResult = Left(vResult, (InStr(1, vResult, vbNullChar) - 1))
Case "update" ' Update
vResult = Now
Case "help" ' Help
vResult = "HorizontalResolution (pixelsX), VerticalResolution (pixelsY), " _
& "WidthInches (inchesX), HeightInches (inchesY), DiagonalInches (inchesDiag), " _
& "PixelsPerInchX (ppiX), PixelsPerInchY (ppiY), PixelsPerInch (ppiDiag), " _
& "WinDotsPerInchX (dpiX), WinDotsPerInchY (dpiY), WinDotsPerInch (dpiWin), " _
& "AdjustmentFactor (zoomFac), IsPrimary, DisplayName, Update, Help"
Case Else ' Else
vResult = CVErr(xlErrValue) ' return #VALUE! error (2015)
End Select
If hWnd = 0 Then
ReleaseDC hWnd, hDC
Else
DeleteDC hDC
End If
Screen = vResult
End Function
Make powerful macros with our free VBA Developer Kit Tutorials like this can be complicated. That’s why we created our free VBA Developer Kit and our Big Book of Excel VBA Macros to supplement this tutorial. Grab them below and you’ll be writing powerful macros in no time.
Notice everything in our VBAProject’s module is declared Private
except Function Screen
; only that UDF may be accessed outside the module. There are 9 Declare
statements for Windows API functions; 5 of these are included to support multi-monitor configurations. The Windows API functions require several Const
statements, 2 Type
statements, and 1 Enum
statement.
This module requires VBA7, which was introduced with Office 2010. If VBA7 is not available, the UDF will probably work correctly if the following changes are made to all Declare
statements: Delete all PtrSafe
and change all LongPtr
to Long
.
The Screen function takes one text argument named Variant
result representing that
=Screen("pixelsX") =Screen(" PiXeLsX ")
The following cell formula will return a comma-separated list of all recognized
=Screen("Help")
Here is that formula’s result:
HorizontalResolution (pixelsX), VerticalResolution (pixelsY), WidthInches (inchesX), HeightInches (inchesY), DiagonalInches (inchesDiag), PixelsPerInchX (ppiX), PixelsPerInchY (ppiY), PixelsPerInch (ppiDiag), WinDotsPerInchX (dpiX), WinDotsPerInchY (dpiY), WinDotsPerInch (dpiWin), AdjustmentFactor (zoomFac), IsPrimary, DisplayName, Update, Help.
The Application.Volatile statement is included to ensure all cells referencing the Screen function are updated when the Workbook is opened or when such a cell is recalculated. If Excel’s ActiveWindow is moved from one screen to another in a multi-monitor configuration, it will probably be necessary to force an update by pressing function key
The purpose of the code related to
Finally, a Select Case statement is used to resolve the result requested by
You might wonder about the following two statements associated with DisplayName:
vResult = tMonitorInfo.szDevice & vbNullChar
vResult = Left(vResult, (InStr(1, vResult, vbNullChar) - 1))
This is necessary when Type
) vbNullChar
. Another vbNullChar
is added in the first statement to insure InStr
does not return zero.
Screen Function Results
The following two screen shots illustrate results for two single-monitor configurations. The first is a desktop computer with a 25” monitor. The second is a laptop computer purported to have a 15.6” display (actually 15.5”). The results were created by entering the following formula into cell A2
=Screen(A1)
then copying that formula across row 2 (range B2:O2). Notice the different zoom factors necessary to display Windows applications actual-size. By setting your zoom to this size, the size displayed on your screen should match the “real” size of the application.
The following screen shots represent a multi-monitor configuration with two equivalent 23” monitors that are almost perfectly matched to Windows’ assumed 96 dpi. Notice DISPLAY1 is primary and DISPLAY2 is not.
We have only been able to test the Screen function with a few computer configurations. If you observe unsatisfactory results with your configuration, please describe the details including VBA version and Windows version in a Comment below.
Final Thought
The Screen UDF is patterned after Excel’s built-in information functions CELL and INFO, which return a single result requested by a text argument. Screen could be made shorter and more efficient if converted to a Sub
procedure with no argument and run as a Macro. In this case, the full set of results could be reported in a new Worksheet added to ActiveWorkbook. Or the Macro could be made independent of Excel by reporting results in a MsgBox
or a UserForm
or an output file. (See our list of UserForm tutorials and File Input/Output tutorials.)
That’s all for this tutorial. If you’re serious about writing macros, subscribe for more VBA tips. Simply fill out the form below and we’ll share our best time-saving VBA tips.