Page 1 Page 2 Page 4


Version 3.94                     First Published 10 Mar 2019                              Last Updated 26 Apr 2023                           Difficulty level:     Moderate

Section Links (this page):
        How Does the Code Work?
        Zoom Form Code
        Datasheet Code
        Report Resizing Code
        Other Code
        Downloads
        YouTube Videos
        Summary/Review
        Feedback


In the first part of this article, I discussed the benefits of automatic form resizing (AFR) compared to using layout guides and anchoring.

In the second section, I showed how the resizing code can add an adjustable zoom feature to your forms together with the use of AFR with datasheet, split & navigation forms. Some potential issues were discussed together with possible solutions for each of these.

The third part of this article explains how the code works and provides tips for using the code most effectively in your own applications.

The fourth part of the article will explain all the latest features added in version 3.90



1.   How Does the Code Work?                                                   Return To Top

All the code used in the automatic form resizing process is contained in the module modResizeForm.
The code works in both 32-bit and 64-bit versions of Access

No additional VBA references are required

There are a number of procedures used of which the following are the most important.

First of all, the declarations section of the module modResizeForm includes the following lines:

'-----------------------------MODULE CONSTANTS & VARIABLES------------------------------

'CHANGE THE VALUE BELOW TO THE HORIZONTAL 'BASE' RESOLUTION USED TO DESIGN YOUR FORM e.g. 800 x 600 -> 800
'Other possible values could include 3840, 1920, 1680, 1440, 1366, 1280, 1024 '800
Private Const DESIGN_HORZRES As Long = 800

'CHANGE THE VALUE BELOW TO THE VERTICAL 'BASE' RESOLUTION USED TO DESIGN YOUR FORM e.g. 800 x 600 -> 600
'Other possible values could include 1080, 1050, 900, 768
Private Const DESIGN_VERTRES As Long = 600
'NOTE: THE VALUE IS ONLY USED AS A CHECK in the GetCurrentFactor procedure

'CHANGE THE VALUE BELOW TO THE DPI SETTING USED TO DESIGN YOUR FORM
'Do NOT alter the DESIGN_PIXELS setting UNLESS you are ABSOLUTELY sure
Private Const DESIGN_PIXELS As Long = 96



The first line is the default or baseline horizontal resolution - in this case 800
You can adjust this to any other suitable minimum value such as 1024 or 1280 if you prefer

The next line is the baseline vertical resolution - 600
This is currently only used in the GetCurrentFactor procedure and can also be amended to suit

The third line is the pixels per inch setting which is normally 96 for 100%
NOTE: if the screen scaling is magnified to e.g. 125% this value becomes 120 ppi. The code still works perfectly.

Based on this information, the GetCurrentFactor function calculates the multiplying factor based on screen size & resolution:
NOTE: GetCurrentFactoris a new function which replaces the old GetFactor function in use up to version 3.75

Public Function GetCurrentFactor() As Single

'---------------------------------------------------------------------------------------
' Procedure :                 GetCurrentFactor
' DateTime :                 18/11/2022
' Authors :                     Colin Riddington
' Purpose :                    Function returns the value that the form's/control's height, width, top
'                                       and left should be multiplied by to fit the current screen resolution.

'NEW CODE v3.78     Replaces older GetFactor (now removed)
'---------------------------------------------------------------------------------------

Dim sngFactorP As Single, intWidth As Integer, intHeight As Integer

On Error Resume Next

      If GetCurrentScreen("dpiwin") <> 96 Then
            sngFactorP = DESIGN_PIXELS / GetCurrentScreen("dpiwin")
      Else
            sngFactorP = 1 'error with dpi reported so assume 96 dpi
      End If

      '============================================================
      'NOTE: After further tests, this section can hopefully be simplified to Case "Widesceen" & Case Else
      Select Case FormFactor

      Case "4:3"       '1.33
            GetCurrentFactor = (lngH / DESIGN_HORZRES) * sngFactorP

      Case "5:4"       '1.25
            GetCurrentFactor = (lngH / DESIGN_HORZRES) * sngFactorP

      Case "Widescreen"       'e.g. 16:10 = 1.66 or 16:9 = 1.78
            GetCurrentFactor = (GetBaseFormFactor * lngV / DESIGN_HORZRES) * sngFactorP

            'Modified by Colin Riddington v3.6 23/11/2021
            'This fixes very rare issue where value of GetCurrentFactor < 1 causes forms to shrink not grow!
            'NOT WIDELY TESTED AS YET AS VERY RARE!
            If GetCurrentFactor < 1 Then GetCurrentFactor = (lngH / DESIGN_HORZRES) * sngFactorP

      '======ADDED Portrait v3.80=============
      Case "Portrait"      'e.g. 1080x1920
           GetCurrentFactor = (lngH / DESIGN_HORZRES) * sngFactorP
            ' GetCurrentFactor = (lngV / DESIGN_HORZRES) * sngFactorP

      Case "Other"       'e.g. split screen @1720x1440
            GetCurrentFactor = (lngH / DESIGN_HORZRES) * sngFactorP

      End Select
      '============================================================

End Function



HINT:
If all the screens on which your application will be displayed are known to have the same form factor e.g. widescreen, you should set your default form size/shape accordingly to match that.

The Resize procedure then uses the GetFactor value to adjust the height and width of the form together with the size and position of each control on the form.

Public Sub Resize(sngFactor As Single, frm As Access.Form)

'---------------------------------------------------------------------------------------
' Procedure :                   Resize
' DateTime :                     27/01/2003 with many updates by Colin Riddington
' Authors :                       Jamie Czernik / Colin Riddington
' Purpose :                       Routine re-scales the form sections and controls.

' Modifications by Colin Riddington:
'04/03/2019 :                Fixed issue with font size issue on some controls
'02/10/2021 :                Updated code to handle acNavigationControl & acNavigationButton
'09/11/2022 :                Added check to ensure resized form width doesn't exceed integer limit - needed for high resolution monitors
'18/11/2022 :                 No further changes needed for new code in v3.78
'---------------------------------------------------------------------------------------

Dim ctl As Access.Control, sngNCW As Single

On Error Resume Next

      With frm
            'First check resized form doesn't exceed maximum form width (32767 twips) to prevent display issues
            'Set limit to 32000 to allow some leeway - then if necessary adjust scaling factor so it fits
            If .Width * sngFactor > 32000 Then sngFactor = 32000 / .Width

            'Now resize width/height for each section:
            .Width = .Width * sngFactor
            .Section(Access.acHeader).Height = .Section(Access.acHeader).Height * sngFactor
            .Section(Access.acDetail).Height = .Section(Access.acDetail).Height * sngFactor
            .Section(Access.acFooter).Height = .Section(Access.acFooter).Height * sngFactor
      End With

      'Resize and locate each control:
      For Each ctl In frm.Controls
            If ctl.ControlType <> acPage Then       'Ignore pages in TAB controls
                  With ctl
                        .Left = .Left * sngFactor
                        .Top = .Top * sngFactor
                        .Height = .Height * sngFactor

                        'CR 02/10/2021 - updated 09/11/2022 to exclude A2007
                        If GetAccessVersion > 12 Then 'A2010 or later
                              If .ControlType = acNavigationControl Then       'still errors in A2007 as control from 2010 onwards
                                    .Width = .Width * sngFactor
                                    sngNCW = .Width 'save value
                              ElseIf .ControlType = acNavigationButton Then
                                    'do NOT use AFR scaling code for acNavigationButton (it would be MUCH too wide)
                                    .Width = sngNCW 'make width equal to navigation control
                                    'increase font size proportionately
                                    .FontSize = .FontSize * sngFactor
                              Else
                                    .Width = .Width * sngFactor
                              End If
                        End If

                        '----------Enhancement by Myke Myers (NOT Austin Powers!) & Colin Riddington------------
                        'Fix certain combo box, list box and tab control properties:
                        'CR - 02/10/2021 - added acNavigationButton

                        Select Case .ControlType

                        Case acLabel, acCommandButton, acTextBox, acToggleButton 'acNavigationButton now handled above
                              'increase font size proportionately
                              .FontSize = .FontSize * sngFactor

                        Case acListBox
                              'as above & increase width of each column proportionately
                              .FontSize = .FontSize * sngFactor
                              .ColumnWidths = AdjustColumnWidths(.ColumnWidths, sngFactor)

                        Case acComboBox
                              'as above & increase list width proportionately
                              .FontSize = .FontSize * sngFactor
                              .ColumnWidths = AdjustColumnWidths(.ColumnWidths, sngFactor)
                              .ListWidth = .ListWidth * sngFactor

                        Case acTabCtl
                              'as for textbox & increase width/height of each tab proportionately
                              .FontSize = .FontSize * sngFactor
                              .TabFixedWidth = .TabFixedWidth * sngFactor
                              .TabFixedHeight = .TabFixedHeight * sngFactor

                        Case Else
                              'no code needed for other control types
                              'acRectangle, acCheckBox, acImage, acLine, acPageBreak, acSubform
                              'acOptionButton, acOptionGroup, acObjectFrame, acBoundObjectFrame, acNavigationControl

                        End Select

                        '------------ End enhancement by Myke Myers / Colin Riddington ------------------
                  End With

            End If

      Next ctl

End Sub


The Resize procedure gives 'special treatment' to selected controls – list boxes, combo boxes and tab controls - to manage their individual features.

Tab control pages are excluded as are the contents of subforms (the subform container is resized automatically)

As previously stated, the code line ResizeForm Me needs to be added to the Form_Load event of each form being resized.
This code line means the ResizeForm procedure is applied to the loaded form (Me)

To scale up the subform control positions / sizes, add the line ResizeForm Me to the Form_Load event of the subform.
Alternatively, add a line like ReSizeForm subFormName.Form to the Form_Load event of the main form.

NOTE: DO NOT DO BOTH METHODS or the subform will be scaled up twice!!

Public Sub ReSizeForm(frm As Access.Form)

'---------------------------------------------------------------------------------------
' Procedure :                   ReSizeForm
' DateTime :                     27/01/2003 with many updates by Colin Riddington
' Authors :                       Jamie Czernik / Colin Riddington
' Purpose :                       Routine should be called on a form's onOpen or onLoad event.

'Significantly modified by Colin Riddington 2006-2022
'---------------------------------------------------------------------------------------

Dim rectWindow As tRect, sngFactor As Single
Dim lngWidth As Long, lngHeight As Long

On Error Resume Next

      'NEW CODE v3.78
      CheckMonitorInfo 'check current monitor in use
      SetStatusBarText
      GetCurrentResolution 'get resolution info for current monitor

      sngFactor = GetCurrentFactor 'get scaling factor for current monitor

      'lngH = horizontal resolution ; DESIGN_HORZRES = base resolution set in declarations section
      If lngH <> DESIGN_HORZRES Then 'resize necessary
            Resize sngFactor, frm 'local procedure
            'END OF NEW CODE

            'the following code controls the positioning of pop-up forms
            'but only if the form tag is null. This allows more control where it causes a problem
            If IsZoomed(frm.hWnd) = 0 Then       'Don't change window settings for maximised form.
                  Access.DoCmd.RunCommand acCmdAppMaximize       'maximize Access Window
                  Call GetWindowRect(frm.hWnd, rectWindow)
                  With rectWindow
                        lngWidth = .Right - .Left
                        lngHeight = .Bottom - .Top
                  End With

                  If Nz(frm.Tag, 1) <> 1 Then
                        'NEW CODE v3.78
                        Call MoveWindow(frm.hWnd, ((lngH - _
                              (sngFactor * lngWidth)) / 2) - GetLeftOffset, _
                              ((lngV - (sngFactor * lngHeight)) / 2) - GetTopOffset, _
                              lngWidth * sngFactor, lngHeight * sngFactor, 1)
                  End If

            End If
      End If

'Modification by Colin Riddington 13/03/2019
'UseMDIMode property =1 (overlapping windows) or = 0 (tabbed documents)
'next section fixes display issue for users of tabbed documents (MDIMode=0)
If CurrentDb.Properties("UseMDIMode") = 0 Then
MaximizeNavigationPane
DoEvents
MinimizeNavigationPane
End If

End Sub



The code first checks whether resizing is required then uses the Resize procedure above

Following that two adjustments may be made:
a) For popup forms an adjustment is made to the code to fix possible positioning issues. However this can be disabled if necessary by setting the form Tag value = 1
b) Where the display option is set to tabbed documents (UseMDIMode=0), the navigation pane is first maximised and then minimised again.
    This again fixes positioning issues.

HINT:
If you have a form that is sometimes used as a subform, you can conditionally apply resizing code when used as a standalone form.
To do so, use the IsSubform function in the Form_Load event of the subform.

Private Sub Form_Load()

      'resize form if used as a standalone form but not if its a subform
      If Not IsSubform(Me) Then ReSizeForm Me

End Sub


The above code is calling the IsSubform function from modResizeForm

Public Function IsSubform(frm As Access.Form) As Boolean

      Dim bHasParent As Boolean

      On Error GoTo NotASubform

      ' If opened not as a subform, accessing the Parent property raises an error:
      bHasParent = Not (Me.Parent Is Nothing)

      IsSubform = True

      Exit Function

NotASubform:
      IsSubform = False

End Function



The UnResizeForm procedure can be used to fix issues when forms become 'over-enlarged'.
This reverses the form resizing code and effectively 'shrinks' the form again.

Public Sub UnReSizeForm(frm As Access.Form)

'---------------------------------------------------------------------------------------
' Procedure :                UnReSizeForm
' DateTime :                 27/01/2003 with many updates
' Authors :                     Jamie Czernik / Colin Riddington
' Purpose :                    Used to unresize forms where needed e.g. before changing zoom
' Modifications:           Jeff Blumson / Colin Riddington

'Significantly modified by Colin Riddington 2006-2022
'---------------------------------------------------------------------------------------

Dim rectWindow As tRect
Dim lngWidth As Long
Dim lngHeight As Long
Dim sngFactor As Single

On Error Resume Next

      'NEW CODE v3.78
      GetCurrentResolution
      sngFactor = 1 / GetCurrentFactor 'scaling factor
      'lngH = horizontal resolution ; DESIGN_HORZRES = base resolution set in declarations section
      If lngH <> DESIGN_HORZRES Then 'resize necessary
            'END OF NEW CODE
            Resize sngFactor, frm 'local procedure
            If IsZoomed(frm.hWnd) = 0 Then 'Don't change window settings for maximized form.
                  Access.DoCmd.RunCommand acCmdAppMaximize 'Max Access Window
                  Call GetWindowRect(frm.hWnd, rectWindow)
                  With rectWindow
                        lngWidth = .Right - .Left
                        lngHeight = .Bottom - .Top
                  End With

                  'NEW CODE v3.78
                  Call MoveWindow(frm.hWnd, ((lngH - _
                        (sngFactor * lngWidth)) / 2) - GetLeftOffset, _
                        ((lngV - (sngFactor * lngHeight)) / 2) - GetTopOffset, _
                        lngWidth * sngFactor, lngHeight * sngFactor, 1)
            End If
      End If

End Sub



This code is used in both the frmFormUnresizer form and the FixFormSize procedure:

Sub FixFormSize()

'---------------------------------------------------------------------------------------
' Procedure :                 FixFormSize
' DateTime :                 23/09/2015
' Authors :                     Colin Riddington
' Purpose :                    Can be used to restore size of forms which have become 'over-sized'
'                                       Or just use frmFormUnresizer (no need to open in design view first)
'---------------------------------------------------------------------------------------

On Error GoTo Err_Handler
'Make sure the form you need to un-resize is open in design view before running this process
Dim frm As Access.Form
Set frm = Forms!frmColoursCont 'modify form name as necessary

UnReSizeForm frm
'ReSizeForm frm

Exit_Handler:
Exit Sub

Err_Handler:
MsgBox "Error " & Err.Number & " in FixFormSize procedure : " & Err.Description
Resume Exit_Handler

End Sub



Very occasionally, you may experience a form that does not automatically revert to its correct size on closing.
In such cases, try adding the line UnresizeForm Me in the Form_Close event.
I also do this where conditional resizing code is applied to subforms (as above)



2.   Zoom Form Code                                                                           Return To Top

The new ZoomForm procedure is a modified version of the original ResizeForm code.

NOTE: The code was completely rewritten for version 3.90 of the example application

Public Sub ZoomForm(frm As Access.Form)

'---------------------------------------------------------------------------------------
' Procedure :                 ZoomForm
' DateTime :                 10/03/2019 (Original version)
' Authors :                     Colin Riddington
' Purpose :                    Zoom form in/out by a specified multiplier sngZoom
'                                       Routine should be called after the form has been resized e.g. using a combo or slider control
' Modifications:           Completely rewritten for v3.78 21/11/2022
'---------------------------------------------------------------------------------------

Dim rectWindow As tRect, sngFactor As Single
Dim lngWidth As Long, lngHeight As Long

On Error Resume Next

     'NEW CODE v3.78
      CheckMonitorInfo 'check current monitor in use
      SetStatusBarText
      GetCurrentResolution 'get resolution info for current monitor

      sngFactor = sngZoom / sngOldZoom

     'lngH = horizontal resolution ; DESIGN_HORZRES = base resolution set in declarations section
      If lngH <> DESIGN_HORZRES Then 'resize necessary
            Resize sngFactor, frm 'local procedure
            'END OF NEW CODE

            'the following code controls the positioning of pop-up forms
            'but only if the form tag is null. This allows more control where it causes a problem
            If IsZoomed(frm.hWnd) = 0 Then       'Don't change window settings for maximised form.
                  Access.DoCmd.RunCommand acCmdAppMaximize       'maximize Access Window
                  Call GetWindowRect(frm.hWnd, rectWindow)
                  With rectWindow
                        lngWidth = .Right - .Left
                        lngHeight = .Bottom - .Top
                  End With

                  If Nz(frm.Tag, 1) <> 1 Then
                        'NEW CODE v3.78
                        Call MoveWindow(frm.hWnd, ((lngH - _
                              (sngFactor * lngWidth)) / 2) - GetLeftOffset, _
                              ((lngV - (sngFactor * lngHeight)) / 2) - GetTopOffset, _
                              lngWidth * sngFactor, lngHeight * sngFactor, 1)
                  End If

            End If
      End If

      'Modification by Colin Riddington 13/03/2019
      'UseMDIMode property =1 (overlapping windows) or = 0 (tabbed documents)
      'next section fixes display issue for users of tabbed documents (MDIMode=0)
      If CurrentDb.Properties("UseMDIMode") = 0 Then
            MaximizeNavigationPane
            DoEvents
            MinimizeNavigationPane
      End If

End Sub



Additional code is used in the form being zoomed.
First of all the form is 'unresized' then resized by an additional amount based on the sngZoom multiplier
Adjustments are made to the form width and section heights to ensure the form dimensions remain in proportion.
This is done by comparing with the sizes of four hidden lines placed on each section of the form

PopupZoomDesign

Private Sub UpdateFormZoom()

      Application.Echo False

      sngZoom = (Me.cboZoom / 100)

      If sngZoom <> sngOldZoom Then
            CentreForm Me
            ZoomForm Me
      End If

      'reset form section dimensions
      Me.Width = Me.LineFW.Width
      Me.FormHeader.Height = Me.LineHH.Height
      Me.Detail.Height = Me.LineDH.Height
      Me.FormFooter.Height = Me.LineFH.Height

      Select Case Me.cboZoom

      Case Is > 100
            Me.ScrollBars = 3       'both scrollbars

      Case 100
            Me.ScrollBars = 0       'no scrollbars

      Case Else
            Me.ScrollBars = 0       'no scrollbars

      End Select

      Application.Echo True

      'store zoom value for future reference
      sngOldZoom = Me.cboZoom / 100

End Sub





3.   Datasheet Code                                                                           Return To Top

Standard resizing code does not work for datasheets. Instead the code first multiplies the font height by the GetFactor function value.
Next the code loops through each column and adjusts the widths of each automatically.

NOTE: The code is limited to the control types found in datasheets to prevent the occurrence of error 438 (Object doesn't support this property or method)

Private Sub cmdResizeDS_Click()

On Error GoTo Err_Handler

      Me.cboZoom = 100
      cboZoom_AfterUpdate

      If Me.cmdResizeDS.Caption = "Resize Datasheet" Then
            Me.cmdResizeDS.Caption = "UnResize Datasheet"
            Me.fsubControlTypesDS.Form.DatasheetFontHeight = Me.fsubControlTypesDS.Form.DatasheetFontHeight * GetCurrentFactor
      Else
            Me.cmdResizeDS.Caption = "Resize Datasheet"
            Me.fsubControlTypesDS.Form.DatasheetFontHeight = Me.fsubControlTypesDS.Form.DatasheetFontHeight / GetCurrentFactor
      End If

      'CR v3.72 18/02/2022 - updated code to prevent error 438 with unsupported control types
      For Each ctrl In Me.fsubControlTypesDS.Form.Controls 'set widths automatically
            'loop through controls and adjust column widths automatically
            Select Case ctrl.ControlType

            Case acTextBox, acCheckBox, acComboBox 'limit to prevent error 438
                  ctrl.ColumnWidth = -2

            End Select
      Next

Exit_Handler:
      Exit Sub

Err_Handler:
      MsgBox "Error " & Err.Number & " in cmdResizeDS_Click procedure : " & Err.Description
      Resume Exit_Handler

End Sub



The datasheet zoom code is very similar. Firstly the font height is further adjusted up/down by the zoom factor
Next the code loops through each column and adjusts the widths of each automatically.
The code is again limited to the control types found in datasheets to prevent the occurrence of error 438

Private Sub cboZoom_AfterUpdate()

On Error GoTo Err_Handler

      If Me.cmdResizeDS.Caption = "Resize Datasheet" Then
            Me.fsubControlTypesDS.Form.DatasheetFontHeight = intFontSize * cboZoom / 100
      Else
            Me.fsubControlTypesDS.Form.DatasheetFontHeight = intFontSize * GetCurrentFactor * cboZoom / 100
      End If

      'CR v3.72 18/02/2022 - updated code to prevent error 438 with unsupported control types
      For Each ctrl In Me.fsubControlTypesDS.Form.Controls
            'loop through controls and adjust column widths automatically
            Select Case ctrl.ControlType

            Case acTextBox, acCheckBox, acComboBox 'limit to prevent error 438
                  ctrl.ColumnWidth = -2

            End Select
      Next

Exit_Handler:
      Exit Sub

Err_Handler:
      MsgBox "Error " & Err.Number & " in cboZoom_AfterUpdate procedure: " & vbCrLf & Err.Description
      Resume Exit_Handler

End Sub




4.   Report Resize Code                                                                                     Return To Top

The ReportResize code is used when a report is used as a subform in a form using AFR.
It is a simplified version of the Resize procedure used in the form itself

Public Sub ReportResize(rpt As Access.Report)

'---------------------------------------------------------------------------------------
' Procedure :                   ReportResize
' DateTime :                   18/02/2022
' Author :                         Colin Riddington
' Purpose :                       Allows resizing of report opened as a subform
' Last Updated :             18/11/2022 - Rewritten to use GetCurrentFactor
'---------------------------------------------------------------------------------------

Dim ctl As Access.Control

On Error Resume Next

      With rpt
            .Width = .Width * GetCurrentFactor
            .Section(Access.acHeader).Height = .Section(Access.acHeader).Height * GetCurrentFactor
            .Section(Access.acDetail).Height = .Section(Access.acDetail).Height * GetCurrentFactor
            .Section(Access.acFooter).Height = .Section(Access.acFooter).Height * GetCurrentFactor
      End With

      'Resize and locate each control:
      For Each ctl In rpt.Controls
            If ctl.ControlType <> acPage Then       'Ignore pages in TAB controls
                  With ctl
                        .Left = .Left * GetCurrentFactor
                        .Top = .Top * GetCurrentFactor
                        .Height = .Height * GetCurrentFactor
                        .Width = .Width * GetCurrentFactor
                                    sngNCW = .Width 'save value

                        'Several of the control types below are unlikely to be used in reports
                        'Fix certain combo box, list box and tab control properties:
                        Select Case .ControlType

                        Case acLabel, acCommandButton, acTextBox, acToggleButton
                              'increase font size proportionately
                              .FontSize = .FontSize * GetCurrentFactor

                        Case acListBox
                              'as above & increase width of each column proportionately
                              .FontSize = .FontSize * GetCurrentFactor
                              .ColumnWidths = AdjustColumnWidths(.ColumnWidths, GetCurrentFactor)

                        Case acComboBox
                              'as above & increase list width proportionately
                              .FontSize = .FontSize * GetCurrentFactor
                              .ColumnWidths = AdjustColumnWidths(.ColumnWidths, GetCurrentFactor)
                              .ListWidth = .ListWidth * GetCurrentFactor

                        Case acTabCtl
                              'as for textbox & increase width/height of each tab proportionately
                              .FontSize = .FontSize * GetCurrentFactor
                              .TabFixedWidth = .TabFixedWidth * GetCurrentFactor
                              .TabFixedHeight = .TabFixedHeight * GetCurrentFactor

                        Case Else
                              'no code needed for other control types
                              'acRectangle, acCheckBox, acImage, acLine, acPageBreak, acSubform
                              'acOptionButton, acOptionGroup, acObjectFrame, acBoundObjectFrame

                        End Select
                  End With
            End If
      Next ctl

End Sub




5.   Other Code                                                                                     Return To Top

Several other procedures are also included in module modResizeForm including:

a)   GetCurrentResolution / GetResolution / GetHorizontalResolution / GetVerticalResolution / GetScreenShape - all used to detect resolution / form factor

b)   GetTopOffset / GetLeftOffset - used to centre forms on screen

c)   IsMainMonitor / SetStatusBarText - used to display monitor resolution info on status bar

d)   AdjustColumnWidths - used in Resize procedure to adjust combo boxes & list boxes during resizing

e)   GetOrigWindow - used to note the original form dimensions before resizing

f)   RestoreWindow - can be used in the Form_Close event to restore the original form dimensions

In addition, the following procedures are also used in the resizing code:

g)   CentreForm - in module modFormInfo - used to centre forms after form zoom code is used

h)   MinimizeNavigationPane / MaximizeNavigationPane - in module modNavPaneTaskbar - used toggle nav pane width to fix issue with tabbed documents display



6.   Downloads                                                                                                                                       Return To Top

Click the links to download various items related to this topic:

1.   The example application referenced in this article - ResizeFormExample_v3.94.zip     (ACCDB file zipped)

2.   An earlier version of the example application if you don't need any of the new features - ResizeFormExample_v3.75.zip     (ACCDB file zipped)

3.   The original auto form resize utility by Jamie Czernik from 2003 - afr2003jc.zip     (MDB zipped)



7.   YouTube Videos                                                                                                                         Return To Top

1.   I ran a session on Automatic Form Resizing for the US Lunchtime Access User Group on 28 Sept 2021.
      The video is available on You Tube at: https://youtu.be/-mgIvCosYtU or you can click on the video below.

       

      Many thanks to Crystal Long (MVP) for the considerable time she spent expertly editing the video recording of this session.

2.  Since then, I have done updated versions of the same presentation for the UK Access User Group on 8 Feb 2022 and again for the Denver Area Access
      User Group on 17 Feb 2022. The updated presentation also included the use of AFR with datasheet forms and navigation forms

      The video of the Denver Area AUG session is also available on You Tube at: https://youtu.be/dzk9rM5A9zU or you can click on the video below.

       



8.   Summary / Review                                                                                                                    Return To Top

The first part of this article compared the use of automatic form resizing (AFR) with the built in layout guides and anchoring.

The second part discussed the many features available in the example app as well as potential issues you may experience and possible solutions for each.

This article explained how the resizing code works and how to use it effectively in your own applications.

The fourth part of the article will explain all the latest features added in version 3.90



9.   Feedback                                                                                                                                           Return To Top

I would be grateful for any feedback on this article including details of any errors or omissions

If you have any comments or questions, please contact me using the feedback form below or send me an email



Colin Riddington               Mendip Data Systems               Last Updated 26 Apr 2023



Return to Access Articles Page 3 of 4 1 2 3 4 Return To Top