Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations Mike Lewis on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

My full-featured Access Forms resizing class module

Status
Not open for further replies.

ESquared

Programmer
Dec 23, 2003
6,129
0
0
US
I've been working on this for a while and now it's nearly ready to hand out to people. I have a few questions I'd like some collaboration help from, first.

- Resizing events in subforms can be handled from the subform's class module with no help from the main form... except when maximizing the main form. In that case, the subform does not receive a resize event so the controls in it stay the same size/position as they were before the maximize. Does anyone have any suggestions/ideas/comments on this? I was hoping to avoid the need to make the main form's resize module aware of subforms.

- Resizing properly for a form that has page header/footer or form header/footer can be a pain. How many people have forms with these elements that you would like to resize? I can make my code work with these elements, but I haven't done it yet. Do you want this?

- I'd like to assess the demand for multiple resizable areas of a form, that is, splitter bars that can change the width/height of sub-areas, requiring special resizing. Is this something you need? Is there a control out there that handles this already?

- What kind of resizing do you want for listboxes? My module as it is can proportionally resize the columns in a listbox. Would you want to specify some columns as fixed-width and others as resizable? (Note: this is not resizing individual columns by a mouse movement but simply making the columns fit proportionally into the listbox as it is sized with the whole form in a resize event.)

- Speaking of listboxes, do you have interest in code to handle resizing of specific columns, sorting by different columns, and detecting a click on a specific column in the header? Is there an explorer-style listbox control out there that you can suggest which does all these things for me so I don't have to write all this stuff for Access 97? (That is, resizing columns, dragging columns to change order, auto-resize to a column's visible values or full list with a double-click on divider, adding/removing columns with a right-click or other means, etc.)

Once I am satisfied with my class module I'll be happy to share it with everyone. You would not believe how much work it was to find out the correct constants and math to determine the current Windows size settings on form borders and elements.

Usage info:
- One form-class-module global object to point to the resize control.
- Instantiate the class with custom "border" space or let the control choose the space based on the position of your topmost and leftmost controls.
- ResizeToMinimum feature: No more laborious painstaking adjusting your forms to get them just the right size. Resize the form in Design Mode all you want and let the resize control do the job at form load.
- Resizing is now as easy as [tt]MyResizingClass.Resize[/tt],voilá!
- Easy to add new controls. Just place a value in the Tag of a control telling the class how to resize the control. Add one or more values below to get the behavior you want:
1 - move left
2 - move top
4 - resize width
8 - resize height
16 - resize listbox columnwidths
For example, for a button in the lower right corner, the value 3 (1+2) will make it stay in the lower right corner.
Note: some combinations don't make sense.

The values 1, 2, 4, 8 for each behavior are arbitrary... suggestions are welcome. The Tag is the only place I know to easily store a value for each control—if you are already using the tag you'll need to make modifications to your code and mine to allow for both to be stored in the tag. Again, suggestions are welcome.

-E²
 
Is no one interested in resizing their forms easily...?

:-(
 
That was a complete flop.

I guess I'll look somewhere else for people who would appreciate it.
 
hi!

I'm very interested in making my forms all the
same size and loading in the same position,
top/width/height, everything. I haven't been
able to find a way to set the top? I would love
to see your module, or any code you have that
would help me make my forms consistent.

Thanks,
Christy.
 
Whoaa,

Don't go. I'm a little late, and am very interested in your code! Still there?

Jeremy
 
Hi Jeremy,

Should I just post it all here (it's long) or do you want me to email it to you?
 
ESquared, one of the goals of this site is sharing, so, please, don't consider private emailing, but posting instead.
 
My suggestion is that if you're going to share it, then post it here for everyone. Plus you're more likely to receive feedback from your item list with lots of eyes able to review.

Good Luck
--------------
As a circle of light increases so does the circumference of darkness around it. - Albert Einstein
 
I was just concerned about the length... but here goes. I am going to make separate posts for each module so you can tell them apart.

I am not really developing this now, but people are using my program in the company so I am interested in fixing my bugs and creating improvements.

[tt]Class Module claControlResizer
-------------------------------

Option Compare Database
Option Explicit

'MS Access 97 Form Resizer Class Module
'by Erik Eckhardt
'(c) 2004
'
'You may use this code freely with the following conditions:
' 1) Above credits and these conditions must remain with the source.
' 2) If you use this code in a business environment,
' - I must be given credit in the About box of your final application ("thanks to Erik Eckhardt" will do)
' - You must send an email to test@test.com saying you used my code. If you are comfortable with it,
' a brief description or even a copy of your program would be nice.
' 3) If you redistribute this code,
' - My name must remain as the source author.
' 4) And if you modify the code,
' - Before you redistribute it, please contact me at test@test.com
' - At the very least, make note that some of the code is your own.
' 5) Enjoy yourself!
'
'Uses claFormWindow, mdlSystemMetrics
'This module handles the job of resizing controls (and windows) for you. To use it, do the following:
'
'Place values in the Tag of each control you want to resize. To use multiple resize methods, add the values together:
' 1 - Move control left and right
' 2 - Move control up and down
' 4 - Adjust width of control
' 8 - Adjust height of control
' 16 - Adjust proportional width of a combobox or listbox's columns (must be used with 4)
' - For example, if you have a button in the lower right of your form that you want to keep in the corner
' when the form is resized, you would place the value 3 in the form's tag.
' Note: If you try to use incompatible resize methods together, you will get an error.
' - For example, if you choose the value 6, to move the top of a control as well as adjust its height,
' the resizer could attempt to resize the control's height to a negative number.
'
'In the class module of the form you want to resize, put the following code:
'
'Dim crResizer as claControlResizer
'Private Sub Form_Load()
' Set crSizer = New claControlResizer
' crSizer.Initialize Me
' crSizer.Resize ResizeToMinimum:=True 'only if you don't want to choose the size yourself at design time.
'End Sub
'Private Sub Form_Resize()
' If Not crSizer Is Nothing Then 'Maximized forms trigger resize *after* Form_Unload, so object could be already destroyed
' crSizer.Resize
' End If
'End Sub
'Private Sub Form_Unload(Cancel As Integer)
' Set crSizer = Nothing
'End Sub
'
'Further notes:
'This class makes some basic allowance for Form Headers and Form Footers, however, you cannot use any vertical options for
' controls in these sections. This is because when a form is resized, only the detail section resizes vertically automatically.
' If you need a control to move or resize vertically, put it in the Detail section.
'Does not handle Page Headers or Page Footers

'To Do: Handle resize bars inside form, with user-defined "sections"
'To Do: Allow two objects to resize but share the space, e.g., each gets half or a proportionate amount
'To Do: Allow for width of Record Selectors on a form

'Known Bugs:
'Subforms on maximized main forms do not resize properly.
'Some bug exists that can move a window partly or completely out of the visible screen area, I think it's some
' conjunction of maximized windows + reading saved window positions from the registry.
'Dragging windows off the edge of the screen can cause weird (cascading?) behavior I haven't yet identified.
'Some of these bugs may be due to the fact that Access maximizes all forms and windows together as a unit... you can't have
' a maximized form and a normal-window form at the same time.
'Then again, they could be all my fault! :)

'Known Programming Kluges:
'There are all sorts of features of VB6 and Office 2000 VBA that Access 97 can't use, such as Split.
'So, some of my code isn't so pretty as I make a workaround. Plus, I spent more time on the main module than on the
' supporting modules.


Const STANDARD_BORDER = 4
Const X_OFS = 0
Const Y_OFS = 0

Const APPNAME = "Your Application Name Here"

'I can't do Enums (Access 97?), like:
'Private Enum SizingType
' szLeft = 1
' szTop = 2
' szWidth = 4
' szHeight = 8
' szColumns = 16
'End Enum

'so I guess I use constants
Const szLeft = 1
Const szTop = 2
Const szWidth = 4
Const szHeight = 8
Const szColumns = 16

Private Type ControlInfo
Ctl As Control
CtlType As Long
x As Long 'pixels
y As Long 'pixels
Width As Long 'twips just because it's easier for this one
Widths() As Long 'twips
End Type

Private ctlArray() As ControlInfo

Private frmForm As Form
Private lngMinX As Long 'minimum window width in pixels
Private lngMinY As Long 'minimum window height in pixels

Private lngPreviousWindowState As Long

Private bolDontResize As Boolean

Public Sub Initialize(TheForm As Form, Optional XBorderSize As Variant, Optional YBorderSize As Variant)
'border size in pixels (distance from bottom and right controls).
If TheForm Is Nothing Then Exit Sub
Set frmForm = TheForm
ReadControlPositions XBorderSize, YBorderSize 'figure out control positions for resizing
bolDontResize = False
End Sub

Private Sub Class_Terminate()
Set frmForm = Nothing
End Sub

Private Sub ReadControlPositions(Optional XBorderSize As Variant, Optional YBorderSize As Variant)
ReDim ctlArray(0)
Dim ctlCtl As Control

Dim ControlRightMax As Long 'twips
Dim ControlBottomMax As Long 'twips
Dim ControlLeftMin As Long 'twips
Dim ControlTopMin As Long 'twips

Dim lngTokenCount As Long
Dim lngCntr As Long
Dim lngOffset As Long

ControlLeftMin = 9999999
ControlTopMin = 9999999

For Each ctlCtl In frmForm.Controls 'find the min and max positions of controls on the form
'must add offsets for controls in sections below the top one
'because the Top property is measured from the top of a control's own section
Select Case ctlCtl.Section
Case acHeader
lngOffset = 0 'no offset
Case acDetail
'If frmForm.Section(acHeader).Visible Then lngOffset = frmForm.Section(acHeader).Height
Case acFooter
If frmForm.Section(acHeader).Visible Then lngOffset = frmForm.Section(acHeader).Height
If frmForm.Section(acDetail).Visible Then lngOffset = frmForm.Section(acDetail).Height
End Select
ControlRightMax = LongMax(ctlCtl.Left + ctlCtl.Width, ControlRightMax)
ControlBottomMax = LongMax(ctlCtl.Top + ctlCtl.Height + lngOffset, ControlBottomMax)
ControlLeftMin = LongMin(ctlCtl.Left, ControlLeftMin)
ControlTopMin = LongMin(ctlCtl.Top + lngOffset, ControlTopMin)
Next
ControlRightMax = ControlRightMax \ TwipsPerPixelX
ControlBottomMax = ControlBottomMax \ TwipsPerPixelY
ControlLeftMin = ControlLeftMin \ TwipsPerPixelX
ControlTopMin = ControlTopMin \ TwipsPerPixelY
Select Case frmForm.BorderStyle 'account for widths of borders and menus
Case 0 ' None
Case 1, 3 'Thin, Dialog
lngMinX = lngMinX + GetSystemMetrics(SM_CXFIXEDFRAME) * 2
lngMinY = lngMinY + GetSystemMetrics(SM_CYFIXEDFRAME) * 2 + GetSystemMetrics(SM_CYCAPTION)
Case 2 'Sizable
lngMinX = lngMinX + (GetSystemMetrics(SM_CXSIZEFRAME) + GetSystemMetrics(SM_CXEDGE)) * 2
lngMinY = lngMinY + ((GetSystemMetrics(SM_CYSIZEFRAME) + GetSystemMetrics(SM_CYEDGE)) * 2) + GetSystemMetrics(SM_CYCAPTION)
End Select
If frmForm.ScrollBars And 1 Then lngMinX = lngMinX + GetSystemMetrics(SM_CXVSCROLL)
If frmForm.ScrollBars And 2 Then lngMinY = lngMinY + GetSystemMetrics(SM_CYVSCROLL)

If IsMissing(YBorderSize) Then
If IsMissing(XBorderSize) Then
XBorderSize = ControlLeftMin
YBorderSize = ControlTopMin
Else
YBorderSize = XBorderSize
End If
End If
lngMinX = lngMinX + XBorderSize + ControlRightMax 'minimum form sizes: all controls on the form, + borders
lngMinY = lngMinY + YBorderSize + ControlBottomMax

For Each ctlCtl In frmForm.Controls
If ctlCtl.Tag <> "" Then
ReDim Preserve ctlArray(UBound(ctlArray()) + 1)
With ctlArray(UBound(ctlArray()))
Set .Ctl = ctlCtl
.CtlType = Val(ctlCtl.Tag)
If .CtlType And szLeft Then
.x = lngMinX - (ctlCtl.Left \ TwipsPerPixelX)
ElseIf .CtlType And szWidth Then
.x = lngMinX - (ctlCtl.Width \ TwipsPerPixelX)
End If
If .CtlType And szTop Then
.y = lngMinY - (ctlCtl.Top \ TwipsPerPixelY)
ElseIf .CtlType And szHeight Then
.y = lngMinY - (ctlCtl.Height \ TwipsPerPixelY)
End If
If .CtlType And szColumns Then
ReDim .Widths(ctlCtl.ColumnCount - 1)
.Width = ctlCtl.Width
lngTokenCount = SplitTokensIntoLongs(ctlCtl.ColumnWidths, .Widths)
For lngCntr = lngTokenCount To ctlCtl.ColumnCount - 1 'in case not all column widths are specified
.Widths(lngCntr) = -1 'mark them as unspecified
Next
End If
End With
End If
Next
End Sub

Public Sub Resize(Optional ResizeToMinimum As Boolean = False, Optional SmartWindowState As Boolean = False)
If frmForm Is Nothing Then Exit Sub
If bolDontResize = True Then Exit Sub 'prevent cascading events
bolDontResize = True
Dim lngCntr As Long
Dim lngWindowState As Long
Dim fwForm As New claFormWindow

fwForm.hWnd = frmForm.hWnd
lngWindowState = fwForm.WindowState
If ResizeToMinimum And lngWindowState <> 2 Then
fwForm.Width = lngMinX
fwForm.Height = lngMinY
Else
If SmartWindowState Then 'currently using registry... should I use another way?

SavePosition OnlyWindowState:=(lngPreviousWindowState <> 0) Or (lngWindowState <> 0)
If lngWindowState = 0 And lngPreviousWindowState <> 0 Then RestorePosition NotWindowState:=True
End If

If lngCntr <> 2 Then 'don't size on minimized form
If fwForm.Width < lngMinX Then fwForm.Width = lngMinX
If fwForm.Height < lngMinY Then fwForm.Height = lngMinY
For lngCntr = 1 To UBound(ctlArray())
With ctlArray(lngCntr)
If .CtlType And szLeft Then .Ctl.Left = (fwForm.Width - .x) * TwipsPerPixelX
If .CtlType And szTop Then .Ctl.Top = (fwForm.Height - .y) * TwipsPerPixelY
If .CtlType And szWidth Then .Ctl.Width = (fwForm.Width - .x) * TwipsPerPixelX
If .CtlType And szHeight Then .Ctl.Height = (fwForm.Height - .y) * TwipsPerPixelY
If .CtlType And szColumns And .Ctl.ControlType = acListBox Then
Dim strWidths As String
Dim lngCntr2 As Long

For lngCntr2 = 0 To .Ctl.ColumnCount - 1
If .Widths(lngCntr2) <> -1 Then
strWidths = strWidths & CStr(.Widths(lngCntr2) / .Width * .Ctl.Width)
End If
strWidths = strWidths & ";"
Next
.Ctl.ColumnWidths = Left(strWidths, Len(strWidths) - 1)
End If
End With
Next
End If
End If
lngPreviousWindowState = lngWindowState
Set fwForm = Nothing
bolDontResize = False
End Sub

Public Sub SavePosition(Optional OnlyWindowState As Boolean = False)
If frmForm Is Nothing Then Exit Sub
Dim fwForm As New claFormWindow
fwForm.hWnd = frmForm.hWnd
With fwForm
If (Not OnlyWindowState) And .WindowState = 0 Then
SaveSetting APPNAME, "Settings", frmForm.Name & "Top", .Top
SaveSetting APPNAME, "Settings", frmForm.Name & "Left", .Left
SaveSetting APPNAME, "Settings", frmForm.Name & "Height", .Height
SaveSetting APPNAME, "Settings", frmForm.Name & "Width", .Width
End If
SaveSetting APPNAME, "Settings", frmForm.Name & "WindowState", .WindowState
End With
Set fwForm = Nothing
End Sub

Public Sub RestorePosition(Optional SizeToMinimum As Boolean = False, Optional NotWindowState As Boolean = False)
If frmForm Is Nothing Then Exit Sub

Dim fwTheForm As New claFormWindow
Dim lngValue As Long
Dim lngWindowState As Long
Dim lngRestoreState As Long
bolDontResize = True

fwTheForm.hWnd = frmForm.hWnd

lngWindowState = fwTheForm.WindowState
lngRestoreState = GetSetting(APPNAME, "Settings", frmForm.Name & "WindowState", 0)
If Not NotWindowState And (lngRestoreState <> lngWindowState) Then
Select Case lngRestoreState
Case 0
DoCmd.Restore
Case 1
DoCmd.Maximize
Case 2
DoCmd.Minimize
Case Else
'????
End Select
lngWindowState = lngRestoreState
End If
If lngWindowState = 0 Then 'current state is restored: get top, left, width, height
If SizeToMinimum Then
fwTheForm.Width = lngMinX \ TwipsPerPixelX
fwTheForm.Height = lngMinY \ TwipsPerPixelY
Else
lngValue = GetSetting(APPNAME, "Settings", frmForm.Name & "Top", 0)
If lngValue > 0 Then 'use the registry settings if they exist
With fwTheForm
.Top = lngValue
.Left = GetSetting(APPNAME, "Settings", frmForm.Name & "Left")
If Not SizeToMinimum Then
.Height = GetSetting(APPNAME, "Settings", frmForm.Name & "Height")
.Width = GetSetting(APPNAME, "Settings", frmForm.Name & "Width")
End If
End With
Else 'otherwise center the form in the parent window without resizing
Dim fwTheParent As New claFormWindow
fwTheParent.hWnd = Application.hWndAccessApp
With fwTheParent
fwTheForm.Top = .Top + Int((.Height - fwTheForm.Height) / 2)
fwTheForm.Left = .Left + Int((.Width - fwTheForm.Width) / 2)
End With
Set fwTheParent = Nothing
End If
End If
End If
Set fwTheForm = Nothing
bolDontResize = False
End Sub

Private Function LongMax(Value1 As Long, Value2 As Long) As Long
If Value1 > Value2 Then LongMax = Value1 Else LongMax = Value2
End Function

Private Function LongMin(Value1 As Long, Value2 As Long) As Long
If Value1 < Value2 Then LongMin = Value1 Else LongMin = Value2
End Function[/tt]
 
This module was made by someone else, I used it with gratitude. Unfortunately, I don't know where it's from as the author didn't put his name in the module itself.

I was thinking about modifying this module to accept a Top, Left, Width, and Height in one call for efficiency, or perhaps even removing this class module entirely and putting the code in the Resizer module. The problem is that each separate call creates a new resize event and this is slow and can cause cascade problems.




[tt]Class Module claFormWindow
-----------------------------

Option Compare Database
Option Explicit



'*************************************************************
' Class module: claFormWindow *
'*************************************************************
' Moves and resizes a window in the coordinate system *
' of its parent window. *
' N.B.: This class was developed for use on Access forms *
' and has not been tested for use with other window *
' types. *
'*************************************************************

Const fwMinimized = 2
Const fwMaximized = 1
Const fwNormal = 0

'*************************************************************
' Type declarations
'*************************************************************

Private Type RECT 'RECT structure used for API calls.
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type

Private Type POINTAPI 'POINTAPI structure used for API calls.
x As Long
y As Long
End Type


'*************************************************************
' Member variables
'*************************************************************

Private m_hWnd As Long 'Handle of the window.
Private m_rctWindow As RECT 'Rectangle describing the sides of the last polled location of the window.


'*************************************************************
' Private error constants for use with RaiseError procedure
'*************************************************************

Private Const m_ERR_INVALIDHWND = 1
Private Const m_ERR_NOPARENTWINDOW = 2



'*************************************************************
' API function declarations
'*************************************************************

Private Declare Function apiIsWindow Lib "user32" Alias "IsWindow" ( _
ByVal hWnd As Long) As Long

Private Declare Function apiMoveWindow Lib "user32" Alias "MoveWindow" ( _
ByVal hWnd As Long, _
ByVal x As Long, _
ByVal y As Long, _
ByVal nWidth As Long, _
ByVal nHeight As Long, _
ByVal bRepaint As Long) As Long
'Moves and resizes a window in the coordinate system of its parent window.

Private Declare Function apiGetWindowRect Lib "user32" Alias "GetWindowRect" ( _
ByVal hWnd As Long, _
lpRect As RECT) As Long
'After calling, the lpRect parameter contains the RECT structure describing the sides of the window in screen coordinates.

Private Declare Function apiScreenToClient Lib "user32" Alias "ScreenToClient" ( _
ByVal hWnd As Long, _
lpPoint As POINTAPI) As Long
'Converts lpPoint from screen coordinates to the coordinate system of the specified client window.

Private Declare Function apiGetParent Lib "user32" Alias "GetParent" ( _
ByVal hWnd As Long) As Long
'Returns the handle of the parent window of the specified window.

Private Declare Function IsZoomed Lib "user32" ( _
ByVal hWnd As Long) As Integer
Private Declare Function IsIconic Lib "user32" ( _
ByVal hWnd As Long) As Integer

'*************************************************************
' Private procedures
'*************************************************************

Private Sub RaiseError(ByVal lngErrNumber As Long, ByVal strErrDesc As String)
'Raises a user-defined error to the calling procedure.

Err.Raise vbObjectError + lngErrNumber, "claFormWindow", strErrDesc
End Sub

Private Sub UpdateWindowRect()
'Places the current window rectangle position (in pixels, in coordinate system of parent window) in m_rctWindow.

Dim ptCorner As POINTAPI

If m_hWnd = 0 Or apiIsWindow(m_hWnd) Then
apiGetWindowRect m_hWnd, m_rctWindow 'm_rctWindow now holds window coordinates in screen coordinates.

If Not Me.Parent Is Nothing Then
'If there is a parent window, convert top, left of window from screen coordinates to parent window coordinates.
With ptCorner
.x = m_rctWindow.Left
.y = m_rctWindow.Top
End With

apiScreenToClient Me.Parent.hWnd, ptCorner

With m_rctWindow
.Left = ptCorner.x
.Top = ptCorner.y
End With

'If there is a parent window, convert bottom, right of window from screen coordinates to parent window coordinates.
With ptCorner
.x = m_rctWindow.Right
.y = m_rctWindow.Bottom
End With

apiScreenToClient Me.Parent.hWnd, ptCorner

With m_rctWindow
.Right = ptCorner.x
.Bottom = ptCorner.y
End With
End If
Else
RaiseError m_ERR_INVALIDHWND, "The window handle " & m_hWnd & " is no longer valid."
End If

End Sub




'*************************************************************
' Public read-write properties
'*************************************************************

Public Property Get hWnd() As Long
'Returns the value the user has specified for the window's handle.

If m_hWnd = 0 Or apiIsWindow(m_hWnd) Then
hWnd = m_hWnd
Else
RaiseError m_ERR_INVALIDHWND, "The window handle " & m_hWnd & " is no longer valid."
End If

End Property


Public Property Let hWnd(ByVal lngNewValue As Long)
'Sets the window to use by specifying its handle.
'Only accepts valid window handles.

If lngNewValue = 0 Or apiIsWindow(lngNewValue) Then
m_hWnd = lngNewValue
Else
RaiseError m_ERR_INVALIDHWND, "The value passed to the hWnd property is not a valid window handle."
End If

End Property

'----------------------------------------------------

Public Property Get Left() As Long
'Returns the current position (in pixels) of the left edge of the window in the coordinate system of its parent window.

If m_hWnd = 0 Or apiIsWindow(m_hWnd) Then
UpdateWindowRect
Left = m_rctWindow.Left
Else
RaiseError m_ERR_INVALIDHWND, "The window handle " & m_hWnd & " is no longer valid."
End If

End Property


Public Property Let Left(ByVal lngNewValue As Long)
'Moves the window such that its left edge falls at the position indicated
'(measured in pixels, in the coordinate system of its parent window).

If m_hWnd = 0 Or apiIsWindow(m_hWnd) Then
UpdateWindowRect
With m_rctWindow
apiMoveWindow m_hWnd, lngNewValue, .Top, .Right - .Left, .Bottom - .Top, True
End With
Else
RaiseError m_ERR_INVALIDHWND, "The window handle " & m_hWnd & " is no longer valid."
End If

End Property

'----------------------------------------------------

Public Property Get Top() As Long
'Returns the current position (in pixels) of the top edge of the window in the coordinate system of its parent window.

If m_hWnd = 0 Or apiIsWindow(m_hWnd) Then
UpdateWindowRect
Top = m_rctWindow.Top
Else
RaiseError m_ERR_INVALIDHWND, "The window handle " & m_hWnd & " is no longer valid."
End If

End Property


Public Property Let Top(ByVal lngNewValue As Long)
'Moves the window such that its top edge falls at the position indicated
'(measured in pixels, in the coordinate system of its parent window).

If m_hWnd = 0 Or apiIsWindow(m_hWnd) Then
UpdateWindowRect
With m_rctWindow
apiMoveWindow m_hWnd, .Left, lngNewValue, .Right - .Left, .Bottom - .Top, True
End With
Else
RaiseError m_ERR_INVALIDHWND, "The window handle " & m_hWnd & " is no longer valid."
End If

End Property

'----------------------------------------------------

Public Property Get Width() As Long
'Returns the current width (in pixels) of the window.

If m_hWnd = 0 Or apiIsWindow(m_hWnd) Then
UpdateWindowRect
With m_rctWindow
Width = .Right - .Left
End With
Else
RaiseError m_ERR_INVALIDHWND, "The window handle " & m_hWnd & " is no longer valid."
End If

End Property


Public Property Let Width(ByVal lngNewValue As Long)
'Changes the width of the window to the value provided (in pixels).

If m_hWnd = 0 Or apiIsWindow(m_hWnd) Then
UpdateWindowRect
With m_rctWindow
apiMoveWindow m_hWnd, .Left, .Top, lngNewValue, .Bottom - .Top, True
End With
Else
RaiseError m_ERR_INVALIDHWND, "The window handle " & m_hWnd & " is no longer valid."
End If

End Property

'----------------------------------------------------

Public Property Get Height() As Long
'Returns the current height (in pixels) of the window.

If m_hWnd = 0 Or apiIsWindow(m_hWnd) Then
UpdateWindowRect
With m_rctWindow
Height = .Bottom - .Top
End With
Else
RaiseError m_ERR_INVALIDHWND, "The window handle " & m_hWnd & " is no longer valid."
End If

End Property


Public Property Let Height(ByVal lngNewValue As Long)
'Changes the height of the window to the value provided (in pixels).

If m_hWnd = 0 Or apiIsWindow(m_hWnd) Then
UpdateWindowRect
With m_rctWindow
apiMoveWindow m_hWnd, .Left, .Top, .Right - .Left, lngNewValue, True
End With
Else
RaiseError m_ERR_INVALIDHWND, "The window handle " & m_hWnd & " is no longer valid."
End If

End Property



'*************************************************************
' Public read-only properties
'*************************************************************

Public Property Get Parent() As claFormWindow
'Returns the parent window as a claFormWindow object.
'For forms, this should be the Access MDI window.

Dim fwParent As New claFormWindow
Dim lngHWnd As Long

If m_hWnd = 0 Then
Set Parent = Nothing
ElseIf apiIsWindow(m_hWnd) Then
lngHWnd = apiGetParent(m_hWnd)
fwParent.hWnd = lngHWnd
Set Parent = fwParent
Else
RaiseError m_ERR_INVALIDHWND, "The window handle " & m_hWnd & " is no longer valid."
End If

Set fwParent = Nothing
End Property

Public Property Get WindowState() As Long
'Returns the state of the window
'0=normal,1=maximized, 2=minimized
Dim lngState

If m_hWnd = 0 Then
RaiseError m_ERR_INVALIDHWND, "The window handle " & m_hWnd & " is no longer valid."
End If
If IsIconic(m_hWnd) Then 'minimized
WindowState = 2
ElseIf IsZoomed(m_hWnd) Then 'maximized
WindowState = 1
Else
WindowState = 0 'restored
End If
End Property[/tt]
 

This started out as someone else's module, but I did a ton of research to fill in all the missing constants and get better descriptions. A lot is straight from MSDN but even that was missing at least one that I think I ended up using.

[tt]Relar module mdlSystemMetrics:
-----------------------------------

Option Compare Database
Option Explicit

Public Const SM_CXSCREEN = 0 'Width and height of the screen of the primary display monitor, in pixels. _
These are the same values obtained by calling GetDeviceCaps(hdcPrimaryMonitor, HORZRES/VERTRES).
Public Const SM_CYSCREEN = 1 'Width and height of the screen of the primary display monitor, in pixels. _
These are the same values obtained by calling GetDeviceCaps(hdcPrimaryMonitor, HORZRES/VERTRES).
Public Const SM_CXVSCROLL = 2 'Width of a vertical scroll bar, in pixels; and height of the arrow bitmap on a _
vertical scroll bar, in pixels.
Public Const SM_CYHSCROLL = 3 'Width of the arrow bitmap on a horizontal scroll bar, in pixels; and height of a _
horizontal scroll bar, in pixels.
Public Const SM_CYCAPTION = 4 'Height of a caption area, in pixels.
Public Const SM_CXBORDER = 5 'Width and height of a window border, in pixels. This is equivalent to the SM_CXEDGE _
value for windows with the 3-D look.
Public Const SM_CYBORDER = 6 'Width and height of a window border, in pixels. This is equivalent to the SM_CXEDGE _
value for windows with the 3-D look.
Public Const SM_CXDLGFRAME = 7 'Same as SM_CXFIXEDFRAME and SM_CYFIXEDFRAME.
Public Const SM_CXFIXEDFRAME = 7 'Thickness of the frame around the perimeter of a window that has a caption but is _
not sizable, in pixels. SM_CXFIXEDFRAME is the height of the horizontal border and SM_CYFIXEDFRAME is the width _
of the vertical border. Same as SM_CXDLGFRAME and SM_CYDLGFRAME.
Public Const SM_CYDLGFRAME = 8 'Same as SM_CXFIXEDFRAME and SM_CYFIXEDFRAME.
Public Const SM_CYFIXEDFRAME = 8 'Thickness of the frame around the perimeter of a window that has a caption but is _
not sizable, in pixels. SM_CXFIXEDFRAME is the height of the horizontal border and SM_CYFIXEDFRAME is the width _
of the vertical border. Same as SM_CXDLGFRAME and SM_CYDLGFRAME.
Public Const SM_CYVTHUMB = 9 'Height of the thumb box in a vertical scroll bar, in pixels.
Public Const SM_CXHTHUMB = 10 'Width of the thumb box in a horizontal scroll bar, in pixels.
Public Const SM_CXICON = 11 'Default width and height of an icon, in pixels. The LoadIcon function can load only _
icons of these dimensions.
Public Const SM_CYICON = 12 'Default width and height of an icon, in pixels. The LoadIcon function can load only _
icons of these dimensions.
Public Const SM_CXCURSOR = 13 'Width and height of a cursor, in pixels. The system cannot create cursors of other sizes.
Public Const SM_CYCURSOR = 14 'Width and height of a cursor, in pixels. The system cannot create cursors of other sizes.
Public Const SM_CYMENU = 15 'Height of a single-line menu bar, in pixels.
Public Const SM_CXFULLSCREEN = 16 'Width and height of the client area for a full-screen window on the primary display _
monitor, in pixels. To get the coordinates of the portion of the screen not obscured by the system taskbar or by _
application desktop toolbars, call the SystemParametersInfo function with the SPI_GETWORKAREA value.
Public Const SM_CYFULLSCREEN = 17 'Width and height of the client area for a full-screen window on the primary display _
monitor, in pixels. To get the coordinates of the portion of the screen not obscured by the system taskbar or by _
application desktop toolbars, call the SystemParametersInfo function with the SPI_GETWORKAREA value.
Public Const SM_CYKANJIWINDOW = 18 'For double byte character set versions of the system, this is the height of the _
Kanji window at the bottom of the screen, in pixels.
Public Const SM_MOUSEPRESENT = 19 'Nonzero if a mouse is installed; zero otherwise.
Public Const SM_CYVSCROLL = 20 'Width of a vertical scroll bar, in pixels; and height of the arrow bitmap on a _
vertical scroll bar, in pixels.
Public Const SM_CXHSCROLL = 21 'Width of the arrow bitmap on a horizontal scroll bar, in pixels; and height of a _
horizontal scroll bar, in pixels.
Public Const SM_DEBUG = 22 'Nonzero if the debug version of User.exe is installed; zero otherwise.
Public Const SM_SWAPBUTTON = 23 'Nonzero if the meanings of the left and right mouse buttons are swapped; zero _
otherwise.
Public Const SM_CXMIN = 28 'Minimum width and height of a window, in pixels.
Public Const SM_CYMIN = 29 'Minimum width and height of a window, in pixels.
Public Const SM_CXSIZE = 30 'Width and height of a button in a window's caption or title bar, in pixels.
Public Const SM_CXSMSIZE = 30 'Dimensions of small caption buttons, in pixels.
Public Const SM_CYSIZE = 31 'Width and height of a button in a window's caption or title bar, in pixels.
Public Const SM_CYSMSIZE = 31 'Dimensions of small caption buttons, in pixels.
Public Const SM_CXFRAME = 32 'Same as SM_CXSIZEFRAME and SM_CYSIZEFRAME.
Public Const SM_CXSIZEFRAME = 32 'Thickness of the sizing border around the perimeter of a window that can be _
resized, in pixels. SM_CXSIZEFRAME is the width of the horizontal border, and SM_CYSIZEFRAME is the height _
of the vertical border. Same as SM_CXFRAME and SM_CYFRAME.
Public Const SM_CYFRAME = 33 'Same as SM_CXSIZEFRAME and SM_CYSIZEFRAME.
Public Const SM_CYSIZEFRAME = 33 'Thickness of the sizing border around the perimeter of a window that can be _
resized, in pixels. SM_CXSIZEFRAME is the width of the horizontal border, and SM_CYSIZEFRAME is the height _
of the vertical border. Same as SM_CXFRAME and SM_CYFRAME.
Public Const SM_CXMINTRACK = 34 'Minimum tracking width and height of a window, in pixels. The user cannot drag _
the window frame to a size smaller than these dimensions. A window can override these values by processing _
the WM_GETMINMAXINFO message.
Public Const SM_CYMINTRACK = 35 'Minimum tracking width and height of a window, in pixels. The user cannot drag _
the window frame to a size smaller than these dimensions. A window can override these values by processing _
the WM_GETMINMAXINFO message.
Public Const SM_CXDOUBLECLK = 36 'Width and height of the rectangle around the location of a first click in a _
double-click sequence, in pixels. The second click must occur within this rectangle for the system to consider _
the two clicks a double-click. (The two clicks must also occur within a specified time.) To set the width and _
height of the double-click rectangle, call SystemParametersInfo with the SPI_SETDOUBLECLKHEIGHT and _
SPI_SETDOUBLECLKWIDTH flags.
Public Const SM_CYDOUBLECLK = 37 'Width and height of the rectangle around the location of a first click in a _
double-click sequence, in pixels. The second click must occur within this rectangle for the system to consider _
the two clicks a double-click. (The two clicks must also occur within a specified time.) To set the width and _
height of the double-click rectangle, call SystemParametersInfo with the SPI_SETDOUBLECLKHEIGHT and _
SPI_SETDOUBLECLKWIDTH flags.
Public Const SM_CXICONSPACING = 38 'Dimensions of a grid cell for items in large icon view, in pixels. Each item _
fits into a rectangle of this size when arranged. These values are always greater than or equal to SM_CXICON _
and SM_CYICON.
Public Const SM_CYICONSPACING = 39 'Dimensions of a grid cell for items in large icon view, in pixels. Each item _
fits into a rectangle of this size when arranged. These values are always greater than or equal to SM_CXICON _
and SM_CYICON.
Public Const SM_MENUDROPALIGNMENT = 40 'Nonzero if drop-down menus are right-aligned with the corresponding _
menu-bar item; zero if the menus are left-aligned.
Public Const SM_PENWINDOWS = 41 'Nonzero if the Microsoft Windows for Pen computing extensions are installed; _
zero otherwise.
Public Const SM_DBCSENABLED = 42 'Nonzero if User32.dll supports DBCS; zero otherwise. Windows Me/98/95: Nonzero _
if the double-byte character-set (DBCS) version of User.exe is installed; zero otherwise."
Public Const SM_CMOUSEBUTTONS = 43 'Number of buttons on mouse, or zero if no mouse is installed.
Public Const SM_SECURE = 44 'Nonzero if security is present; zero otherwise.
Public Const SM_CXEDGE = 45 'Dimensions of a 3-D border, in pixels. These are the 3-D counterparts of SM_CXBORDER _
and SM_CYBORDER.
Public Const SM_CYEDGE = 46 'Dimensions of a 3-D border, in pixels. These are the 3-D counterparts of SM_CXBORDER _
and SM_CYBORDER.
Public Const SM_CXMINSPACING = 47 'Dimensions of a grid cell for a minimized window, in pixels. Each minimized _
window fits into a rectangle this size when arranged. These values are always greater than or equal to _
SM_CXMINIMIZED and SM_CYMINIMIZED.
Public Const SM_CYMINSPACING = 48 'Dimensions of a grid cell for a minimized window, in pixels. Each minimized _
window fits into a rectangle this size when arranged. These values are always greater than or equal to _
SM_CXMINIMIZED and SM_CYMINIMIZED.
Public Const SM_CXSMICON = 49 'Recommended dimensions of a small icon, in pixels. Small icons typically appear _
in window captions and in small icon view.
Public Const SM_CYSMICON = 50 'Recommended dimensions of a small icon, in pixels. Small icons typically appear _
in window captions and in small icon view.
Public Const SM_CYSMCAPTION = 51 'Height of a small caption, in pixels.
Public Const SM_CXMENUSIZE = 54 'Dimensions of menu bar buttons, such as the child window close button used in _
the multiple document interface, in pixels.
Public Const SM_CYMENUSIZE = 55 'Dimensions of menu bar buttons, such as the child window close button used in _
the multiple document interface, in pixels.
Public Const SM_ARRANGE = 56 'Flags specifying how the system arranged minimized windows. For more information _
about minimized windows, see the following Remarks section.
Public Const SM_CXMINIMIZED = 57 'Dimensions of a minimized window, in pixels.
Public Const SM_CYMINIMIZED = 58 'Dimensions of a minimized window, in pixels.
Public Const SM_CXMAXTRACK = 59 'Default maximum dimensions of a window that has a caption and sizing borders, _
in pixels. This metric refers to the entire desktop. The user cannot drag the window frame to a size larger _
than these dimensions. A window can override these values by processing the WM_GETMINMAXINFO message.
Public Const SM_CYMAXTRACK = 60 'Default maximum dimensions of a window that has a caption and sizing borders, _
in pixels. This metric refers to the entire desktop. The user cannot drag the window frame to a size larger _
than these dimensions. A window can override these values by processing the WM_GETMINMAXINFO message.
Public Const SM_CXMAXIMIZED = 61 'Default dimensions, in pixels, of a maximized top-level window on the primary _
display monitor.
Public Const SM_CYMAXIMIZED = 62 'Default dimensions, in pixels, of a maximized top-level window on the primary _
display monitor.
Public Const SM_NETWORK = 63 'Least significant bit is set if a network is present; otherwise, it is cleared. The _
other bits are reserved for future use.
Public Const SM_CLEANBOOT = 67 'Value that specifies how the system was started: _
0 NORMAL boot _
1 Fail-safe boot _
2 Fail-safe with network boot _
Fail-safe boot (also called SafeBoot, Safe Mode, or Clean Boot) bypasses the user's startup files.
Public Const SM_CXDRAG = 68 'Width and height of a rectangle centered on a drag point to allow for limited movement _
of the mouse pointer before a drag operation begins. These values are in pixels. It allows the user to click _
and release the mouse button easily without unintentionally starting a drag operation.
Public Const SM_CYDRAG = 69 'Width and height of a rectangle centered on a drag point to allow for limited movement _
of the mouse pointer before a drag operation begins. These values are in pixels. It allows the user to click _
and release the mouse button easily without unintentionally starting a drag operation.
Public Const SM_SHOWSOUNDS = 70 'Nonzero if the user requires an application to present information visually in _
situations where it would otherwise present the information only in audible form; zero otherwise.
Public Const SM_CXMENUCHECK = 71 'Dimensions of the default menu check-mark bitmap, in pixels.
Public Const SM_CYMENUCHECK = 72 'Dimensions of the default menu check-mark bitmap, in pixels.
Public Const SM_SLOWMACHINE = 73 'Nonzero if the computer has a low-end (slow) processor; zero otherwise.
Public Const SM_MIDEASTENABLED = 74 'Nonzero if the system is enabled for Hebrew and Arabic languages, zero if not.
Public Const SM_MOUSEWHEELPRESENT = 75 'Nonzero if a mouse with a wheel is installed; zero otherwise. _
Windows 3.51 and earlier, Windows 95:  This value is not supported.
Public Const SM_XVIRTUALSCREEN = 76 'Coordinates for the left side and the top of the virtual screen. The virtual _
screen is the bounding rectangle of all display monitors. The SM_CXVIRTUALSCREEN, SM_CYVIRTUALSCREEN metrics _
are the width and height of the virtual screen. Windows NT, Windows 95:  This value is not supported.
Public Const SM_YVIRTUALSCREEN = 77 'Coordinates for the left side and the top of the virtual screen. The virtual _
screen is the bounding rectangle of all display monitors. The SM_CXVIRTUALSCREEN, SM_CYVIRTUALSCREEN metrics _
are the width and height of the virtual screen. Windows NT, Windows 95:  This value is not supported.
Public Const SM_CXVIRTUALSCREEN = 78 'Width and height of the virtual screen, in pixels. The virtual screen is the _
bounding rectangle of all display monitors. The SM_XVIRTUALSCREEN, SM_YVIRTUALSCREEN metrics are the _
coordinates of the top-left corner of the virtual screen. Windows NT, Windows 95:  This value is not supported.
Public Const SM_CYVIRTUALSCREEN = 79 'Width and height of the virtual screen, in pixels. The virtual screen is the _
bounding rectangle of all display monitors. The SM_XVIRTUALSCREEN, SM_YVIRTUALSCREEN metrics are the _
coordinates of the top-left corner of the virtual screen. Windows NT, Windows 95:  This value is not supported.
Public Const SM_CMONITORS = 80 'Number of display monitors on the desktop. See Remarks for more information. _
Windows NT, Windows 95:  This value is not supported.
Public Const SM_SAMEDISPLAYFORMAT = 81 'Nonzero if all the display monitors have the same color format, zero _
otherwise. Note that two displays can have the same bit depth, but different color formats. For example, _
the red, green, and blue pixels can be encoded with different numbers of bits, or those bits can be located _
in different places in a pixel's color value. Windows NT, Windows 95:  This value is not supported.
Public Const SM_IMMENABLED = 82 'Nonzero if Input Method Manager/Input Method Editor features are enabled; zero _
otherwise. Windows NT, Windows Me/98/95:  This value is not supported. _
SM_IMMENABLED indicates whether the system is ready to use a Unicode-based IME on a Unicode application. _
To ensure that a language-dependent IME works, check SM_DBCSENABLED and the system ANSI code
Public Const SM_CXFOCUSBORDER = 83 'Width of the left and right edges and the height of the top and bottom _
edges of the focus rectangle drawn by DrawFocusRect. These values are in pixels. _
Windows 2000/NT, Windows Me/98/95:  This value is not supported.
Public Const SM_CYFOCUSBORDER = 84 'Width of the left and right edges and the height of the top and bottom _
edges of the focus rectangle drawn by DrawFocusRect. These values are in pixels. _
Windows 2000/NT, Windows Me/98/95:  This value is not supported.
Public Const SM_TABLETPC = 86 'Nonzero if the current operating system is the Windows XP Tablet PC edition, _
zero if not.
Public Const SM_MEDIACENTER = 87 'Nonzero if the current operating system is the Windows XP, Media Center _
Edition, zero if not.
Public Const SM_REMOTESESSION = 4096 'This system metric is used in a Terminal Services environment. If the _
calling process is associated with a Terminal Services client session, the return value is nonzero. If the _
calling process is associated with the Terminal Server console session, the return value is zero. _
Windows NT 4.0 SP3 and earlier, Windows Me/98/95:  This value is not supported.
Public Const SM_SHUTTINGDOWN = 8192 'Nonzero if the current session is shutting down; zero otherwise. _
Windows 2000/NT, Windows Me/98/95:  This value is not supported.
Public Const SM_REMOTECONTROL = 8193 'This system metric is used in a Terminal Services environment. Its value _
is nonzero if the current session is remotely controlled; zero otherwise. _
Windows 2000/NT, Windows Me/98/95:  This value is not supported.

Private Const LOGPIXELSX = 88 'Pixels per logical inch in X
Private Const LOGPIXELSY = 90 'Pixels per logical inch in Y

Public Declare Function GetSystemMetrics Lib "user32" ( _
ByVal nIndex As Long) As Long

Private Declare Function GetDeviceCaps Lib "gdi32" ( _
ByVal hdc As Long, _
ByVal nIndex As Long) As Long

Private Declare Function GetDesktopWindow Lib "user32" () As Long

Private Declare Function GetDC Lib "user32" ( _
ByVal hWnd As Long) As Long

Private Declare Function ReleaseDC Lib "user32" ( _
ByVal hWnd As Long, _
ByVal hdc As Long) As Long

Sub GetAllMetrics()
Dim lngCntr As Long
For lngCntr = 0 To 74
Debug.Print CStr(lngCntr) & vbTab & CStr(GetSystemMetrics(lngCntr))
Next
End Sub

Public Function TwipsPerPixelX() As Long 'Twips per pixel for screen in X
Static lngX As Long
If lngX = 0 Then ' no need to repeatedly get this value from system when we can put it in a static variable
Dim lgDC As Long
Dim lgHwnd As Long
lgHwnd = GetDesktopWindow
lgDC = GetDC(lgHwnd)
TwipsPerPixelX = 1440 / GetDeviceCaps(lgDC, LOGPIXELSX)
ReleaseDC lgHwnd, lgDC
Else
TwipsPerPixelX = lngX
End If
End Function

Public Function TwipsPerPixelY() As Long 'Twips per pixel for screen in Y
Static lngY As Long
If lngY = 0 Then
Dim lgDC As Long
Dim lgHwnd As Long
lgHwnd = GetDesktopWindow
lgDC = GetDC(lgHwnd)
TwipsPerPixelY = 1440 / GetDeviceCaps(lgDC, LOGPIXELSY)
ReleaseDC lgHwnd, lgDC
Else
TwipsPerPixelY = lngY
End If
End Function[/tt]
 
Procedures I put in a module called mdlUtilities because I use them elsewhere:

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

Public Function SplitTokensIntoLongs(TheString As String, TheValues() As Long, Optional Delimiter As String = ";") As Long
Dim lngCntr As Long
Dim strStrings() As String
ReDim strStrings(UBound(TheValues) - LBound(TheValues) + 1)

SplitTokensIntoLongs = SplitTokens(TheString, strStrings(), Delimiter)
For lngCntr = 0 To SplitTokensIntoLongs - 1
TheValues(lngCntr) = Val(strStrings(lngCntr))
Next
End Function


Public Function SplitTokens(TheString As String, TheStrings() As String, Optional Delimiter As String = ";", Optional IgnoreQuotes As Boolean = False) As Long
Dim lngFoundPos As Long
Dim lngValueNum As Long
Dim lngStartPos As Long

Dim lngPos As Long
Dim bolInQuotes As Boolean

If Len(TheString) = 0 Then
SplitTokens = 0
Exit Function
End If
If IgnoreQuotes Then
lngStartPos = 1
lngFoundPos = InStr(lngStartPos, TheString & Delimiter, Delimiter)
Do Until lngFoundPos = 0
TheStrings(lngValueNum) = Mid(TheString, lngStartPos, lngFoundPos - lngStartPos)
lngStartPos = lngFoundPos + 1
lngValueNum = lngValueNum + 1
lngFoundPos = InStr(lngStartPos, TheString & Delimiter, Delimiter)
Loop
Else
bolInQuotes = False
lngStartPos = 1
For lngPos = 1 To Len(TheString) + 1
Select Case Mid(TheString & ";", lngPos, 1)
Case """"
bolInQuotes = Not bolInQuotes
Case ";"
If Not bolInQuotes Then
TheStrings(lngValueNum) = Mid(TheString, lngStartPos, lngPos - lngStartPos)
lngStartPos = lngPos + 1
lngValueNum = lngValueNum + 1
End If
Case Else
End Select
Next
End If
SplitTokens = lngValueNum
End Function
 
Now, last of all:

I see I put some features in that I didn't document, such as SmartWindowState in my Resize event. Feel free to ask any questions, and I'll try to document stuff in the meantime. SmartWindowState is about saving the last 'restored' window position in the registry so when you maximize, the values aren't lost. Then you can restore later and get your favorite window position.

This code was working as is in my production database, but when I moved just the pieces above to a new database and a new form, there's some sort of problem. So, I'm resolving that now and will post any fixes or additional gotchas in a bit...



 
Aha! The trick is that you have to resize the form's inner width & height to their maximums. If the resize class tries to move a control outside of these invisible boundaries, an error occurs. That is, the form itself can be dragged to any size

The width is in the property sheet as Width, The height is set per section and I don't remember how to easily get this(Form Header, Page Header, Detail, Page Footer, Form Footer).

I suppose I need to add code to prevent the form from being resized past these values so they can be used as maximums, I just didn't need this in my application. Does anyone want it?
 
Well, first I put a real email address in... then I realized it was going to be seen by spambots eventually, so I asked an admin to fix it for me. Instead of fixing it, the admin broke it--now test@test.com--and seems to like it that way.

So, if you do copy the code from my claControlResizer, please replace test@test.com with esquared@ecxhardts.com

... and replace the x in the domain name with a k.

Regards,

 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top