Skip to content

Commit

Permalink
pdSpinner: when receiving focus via tab key, activate the edit box...
Browse files Browse the repository at this point in the history
...NOT the spin control.  This behavior is far more intuitive.

(Relates to #277; thank you to @schneis for pointing this out.)
  • Loading branch information
tannerhelland committed Jul 30, 2019
1 parent dc297ce commit d92c059
Show file tree
Hide file tree
Showing 5 changed files with 161 additions and 111 deletions.
3 changes: 2 additions & 1 deletion Classes/pdEditBoxW.cls
Original file line number Diff line number Diff line change
Expand Up @@ -581,10 +581,11 @@ End Sub

'This function actually does two things: makes the edit box the foreground window, then assigns it keyboard focus.
' By design, all non-multiline edit boxes in PD select all their own text upon an initial click.
Friend Sub SetFocusToEditBox()
Friend Sub SetFocusToEditBox(Optional ByVal selectTextToo As Boolean = False)
If (m_EditBoxHwnd <> 0) Then
SetForegroundWindow m_EditBoxHwnd
SetFocus m_EditBoxHwnd
If selectTextToo Then Me.SelectAll
End If
End Sub

Expand Down
240 changes: 131 additions & 109 deletions Classes/pdObjectList.cls
Original file line number Diff line number Diff line change
Expand Up @@ -159,134 +159,156 @@ End Sub
'Tab keypresses only require an incoming hWnd; we'll figure out the rest.
Friend Sub NotifyTabKey(ByVal srcHwnd As Long, ByVal shiftTabPressed As Boolean)

'First thing we need to do is make a list of all visible/enabled controls on the form.
' (Invisible/disabled controls can't receive focus, obviously!)
ReDim m_ControlsSort(0 To m_numOfControls) As PD_ControlSort
m_numOfControlsSort = 0

'We also need the width of the current screen, so we can sort coordinates one-dimensionally.
Dim screenWidth As Long
screenWidth = g_Displays.GetDesktopWidth()

Dim currentControlIndex As Long
currentControlIndex = -1
'Before doing anything else, ask the source control if it wants to specify a custom tab-key target.
' If it does, we'll use its suggestion instead of determining our own.
Dim newTargetHwnd As Long: newTargetHwnd = 0
If shiftTabPressed Then
UserControls.PostPDMessage WM_PD_SHIFT_TAB_KEY_TARGET, srcHwnd, VarPtr(newTargetHwnd)
Else
UserControls.PostPDMessage WM_PD_TAB_KEY_TARGET, srcHwnd, VarPtr(newTargetHwnd)
End If

Dim i As Long, tmpRect As winRect
For i = 0 To m_numOfControls - 1
If (newTargetHwnd = 0) Then

'Only visible + enabled controls are eligible for receiving focus
If (IsWindowVisible(m_Controls(i).hWnd) <> 0) And (IsWindowEnabled(m_Controls(i).hWnd)) Then

'The command bar (and mini command bar) are a special case. They are managed by this class,
' because we need to detect them for OK/Cancel purposes, but we don't want them receiving
' focus during KeyPress events. (Instead, focus should go to one of their child controls.)
If (m_Controls(i).ctlType <> pdct_CommandBar) And (m_Controls(i).ctlType <> pdct_CommandBarMini) Then

'This control is visible, enabled, and interactive, making it a candidate for receiving focus.
' Retrieve its coordinates.
g_WindowManager.GetWindowRect_API m_Controls(i).hWnd, tmpRect

'I haven't decided if it is worthwhile to map coordinates to a new coordinate space prior to
' determining order. (I don't think it matters, but it's possible I haven't fully considered the math!)

'For now, convert the top-left corner of the rect into a single-dimension variable
With m_ControlsSort(m_numOfControlsSort)
.hWnd = m_Controls(i).hWnd
.x = tmpRect.x1
.y = tmpRect.y1
.sortKey = GetSortKeyFromRect(tmpRect, screenWidth)
End With
'First thing we need to do is make a list of all visible/enabled controls on the form.
' (Invisible/disabled controls can't receive focus, obviously!)
ReDim m_ControlsSort(0 To m_numOfControls) As PD_ControlSort
m_numOfControlsSort = 0

'We also need the width of the current screen, so we can sort coordinates one-dimensionally.
Dim screenWidth As Long
screenWidth = g_Displays.GetDesktopWidth()

Dim currentControlIndex As Long
currentControlIndex = -1

Dim i As Long, tmpRect As winRect
For i = 0 To m_numOfControls - 1

'Only visible + enabled controls are eligible for receiving focus
If (IsWindowVisible(m_Controls(i).hWnd) <> 0) And (IsWindowEnabled(m_Controls(i).hWnd)) Then

'If this control is the one that supplied the tabkey, note it now
If (srcHwnd = m_Controls(i).hWnd) Then currentControlIndex = m_numOfControlsSort
'The command bar (and mini command bar) are a special case. They are managed by this class,
' because we need to detect them for OK/Cancel purposes, but we don't want them receiving
' focus during KeyPress events. (Instead, focus should go to one of their child controls.)
If (m_Controls(i).ctlType <> pdct_CommandBar) And (m_Controls(i).ctlType <> pdct_CommandBarMini) Then

m_numOfControlsSort = m_numOfControlsSort + 1
'This control is visible, enabled, and interactive, making it a candidate for receiving focus.
' Retrieve its coordinates.
g_WindowManager.GetWindowRect_API m_Controls(i).hWnd, tmpRect

'I haven't decided if it is worthwhile to map coordinates to a new coordinate space prior to
' determining order. (I don't think it matters, but it's possible I haven't fully considered the math!)

'For now, convert the top-left corner of the rect into a single-dimension variable
With m_ControlsSort(m_numOfControlsSort)
.hWnd = m_Controls(i).hWnd
.x = tmpRect.x1
.y = tmpRect.y1
.sortKey = GetSortKeyFromRect(tmpRect, screenWidth)
End With

'If this control is the one that supplied the tabkey, note it now
If (srcHwnd = m_Controls(i).hWnd) Then currentControlIndex = m_numOfControlsSort

m_numOfControlsSort = m_numOfControlsSort + 1

End If

End If
Next i

'We now have a list of all valid tab recipients on this form. Hopefully our source control was included;
' if it wasn't (for whatever reason), retrieve its last-known position and use that instead.
If (currentControlIndex = -1) Then

g_WindowManager.GetWindowRect_API srcHwnd, tmpRect

With m_ControlsSort(m_numOfControlsSort)
.hWnd = srcHwnd
.x = tmpRect.x1
.y = tmpRect.y1
.sortKey = GetSortKeyFromRect(tmpRect, screenWidth)
End With

m_numOfControlsSort = m_numOfControlsSort + 1

End If
Next i

'We now have a list of all valid tab recipients on this form. Hopefully our source control was included;
' if it wasn't (for whatever reason), retrieve its last-known position and use that instead.
If (currentControlIndex = -1) Then

g_WindowManager.GetWindowRect_API srcHwnd, tmpRect
'Our list of "valid" window targets is now guaranteed to include the source window that triggered this tab press
' in the first place! (We need it in the list, obviously, so we know which control(s) surround it in the tab order.)

With m_ControlsSort(m_numOfControlsSort)
.hWnd = srcHwnd
.x = tmpRect.x1
.y = tmpRect.y1
.sortKey = GetSortKeyFromRect(tmpRect, screenWidth)
End With
'Next, we need to sort the list by its sortKey property. This list is guaranteed to be small, so we shouldn't
' need a fancy sort. An in-place insertion sort (as used elsewhere in the project) should be more than sufficient.
If (m_numOfControlsSort > 1) Then

m_numOfControlsSort = m_numOfControlsSort + 1
Dim j As Long, loopBound As Long, tmpRef As PD_ControlSort
loopBound = m_numOfControlsSort - 1

'Loop through all entries in the stack, sorting them as we go
For i = 0 To loopBound
For j = 0 To loopBound
If (m_ControlsSort(i).sortKey < m_ControlsSort(j).sortKey) Then
tmpRef = m_ControlsSort(i)
m_ControlsSort(i) = m_ControlsSort(j)
m_ControlsSort(j) = tmpRef
End If
Next j
Next i

'If there is only one (or zero) valid tab key recipient(s) on this dialog, skip the sort step, obviously.
Else

End If

'Our list of "valid" window targets is now guaranteed to include the source window that triggered this tab press
' in the first place! (We need it in the list, obviously, so we know which control(s) surround it in the tab order.)

'Next, we need to sort the list by its sortKey property. This list is guaranteed to be small, so we shouldn't
' need a fancy sort. An in-place insertion sort (as used elsewhere in the project) should be more than sufficient.
If (m_numOfControlsSort > 1) Then

Dim j As Long, loopBound As Long, tmpRef As PD_ControlSort
loopBound = m_numOfControlsSort - 1
End If

'Loop through all entries in the stack, sorting them as we go
For i = 0 To loopBound
For j = 0 To loopBound
If (m_ControlsSort(i).sortKey < m_ControlsSort(j).sortKey) Then
tmpRef = m_ControlsSort(i)
m_ControlsSort(i) = m_ControlsSort(j)
m_ControlsSort(j) = tmpRef
End If
Next j
'Now that our list is sorted, we need to once again find the source window's hWnd.
For i = 0 To m_numOfControlsSort - 1
If (m_ControlsSort(i).hWnd = srcHwnd) Then
currentControlIndex = i
Exit For
End If
Next i

'If there is only one (or zero) valid tab key recipient(s) on this dialog, skip the sort step, obviously.
Else

End If

'Now that our list is sorted, we need to once again find the source window's hWnd.
For i = 0 To m_numOfControlsSort - 1
If (m_ControlsSort(i).hWnd = srcHwnd) Then
currentControlIndex = i
Exit For
'With a sorted list of controls, finding the next/previous control is easy!
Dim targetIndex As Long

If shiftTabPressed Then
targetIndex = currentControlIndex - 1
If (targetIndex < 0) Then targetIndex = m_numOfControlsSort - 1
Else
targetIndex = currentControlIndex + 1
If (targetIndex >= m_numOfControlsSort) Then targetIndex = 0
End If
Next i

'With a sorted list of controls, finding the next/previous control is easy!
Dim targetIndex As Long

If shiftTabPressed Then
targetIndex = currentControlIndex - 1
If (targetIndex < 0) Then targetIndex = m_numOfControlsSort - 1
Else
targetIndex = currentControlIndex + 1
If (targetIndex >= m_numOfControlsSort) Then targetIndex = 0

'During debug sessions, it can be helpful to print window details to the immediate window
If DISPLAY_DEBUG_TABORDER_DATA Then
Debug.Print "---------"
For i = 0 To m_numOfControlsSort - 1
If (i = targetIndex) Then
Debug.Print "> " & GetControlNameFromHWnd(m_ControlsSort(i).hWnd), m_ControlsSort(i).sortKey
ElseIf (i = currentControlIndex) Then
Debug.Print "* " & GetControlNameFromHWnd(m_ControlsSort(i).hWnd), m_ControlsSort(i).sortKey
Else
Debug.Print GetControlNameFromHWnd(m_ControlsSort(i).hWnd), m_ControlsSort(i).sortKey
End If
Next i
Debug.Print "FYI, target control is " & GetControlNameFromHWnd(m_ControlsSort(targetIndex).hWnd)
End If

newTargetHwnd = m_ControlsSort(targetIndex).hWnd

End If

'Some controls require special focus notifications (e.g. spinners, which default to
' the edit box receiving focus via tab key - NOT the spin control). Check for this now.
Dim useSpecialFocusEvent As Long: useSpecialFocusEvent = 0
UserControls.PostPDMessage WM_PD_FOCUS_FROM_TAB_KEY, newTargetHwnd, VarPtr(useSpecialFocusEvent)

'During debug sessions, it can be helpful to print window details to the immediate window
If DISPLAY_DEBUG_TABORDER_DATA Then
Debug.Print "---------"
For i = 0 To m_numOfControlsSort - 1
If (i = targetIndex) Then
Debug.Print "> " & GetControlNameFromHWnd(m_ControlsSort(i).hWnd), m_ControlsSort(i).sortKey
ElseIf (i = currentControlIndex) Then
Debug.Print "* " & GetControlNameFromHWnd(m_ControlsSort(i).hWnd), m_ControlsSort(i).sortKey
Else
Debug.Print GetControlNameFromHWnd(m_ControlsSort(i).hWnd), m_ControlsSort(i).sortKey
End If
Next i
Debug.Print "FYI, target control is " & GetControlNameFromHWnd(m_ControlsSort(targetIndex).hWnd)
End If
'Finally, apply the focus change! (If the previous step succeeded, the caller must set
' useSpecialFocusEvent to a non-zero value - this means they handled the focus event
' internally, so we don't need to handle it for them.)
If (useSpecialFocusEvent = 0) Then g_WindowManager.SetFocusAPI newTargetHwnd

'Finally, apply the focus change!
g_WindowManager.SetFocusAPI m_ControlsSort(targetIndex).hWnd

End Sub

'Return a sort key for a given control's window rectangle (e.g. the control's coordinates and dimensions,
Expand Down
24 changes: 24 additions & 0 deletions Controls/pdSpinner.ctl
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,7 @@ Public Event ResetClick()
Public Event Resize()
Public Event GotFocusAPI()
Public Event LostFocusAPI()
Public Event SetCustomTabTarget(ByVal shiftTabWasPressed As Boolean, ByRef newTargetHwnd As Long)

'The actual common control edit box is handled by a dedicated class
Private WithEvents m_EditBox As pdEditBoxW
Expand Down Expand Up @@ -448,6 +449,21 @@ Private Sub ucSupport_ClickCustom(ByVal Button As PDMouseButtonConstants, ByVal
End If
End Sub

Private Sub ucSupport_CustomMessage(ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long, bHandled As Boolean, lReturn As Long)

'If this control is about to receive focus via the tab key, manually set focus to the edit box.
If (wMsg = WM_PD_FOCUS_FROM_TAB_KEY) And (wParam = Me.hWnd) Then

'Set focus to the edit box
m_EditBox.SetFocusToEditBox True

'Set the lParam flag to a non-zero value (see NavKey.NotifyNavKeyPress for details)
PutMem4 lParam, 1&

End If

End Sub

Private Sub ucSupport_GotFocusAPI()
m_FocusCount = m_FocusCount + 1
EvaluateFocusCount
Expand Down Expand Up @@ -732,6 +748,10 @@ Private Sub ucSupport_RepaintRequired(ByVal updateLayoutToo As Boolean)
If updateLayoutToo And (Not m_InternalResizeState) Then UpdateControlLayout Else RedrawBackBuffer
End Sub

Private Sub ucSupport_SetCustomTabTarget(ByVal shiftTabWasPressed As Boolean, newTargetHwnd As Long)
RaiseEvent SetCustomTabTarget(shiftTabWasPressed, newTargetHwnd)
End Sub

Private Sub ucSupport_VisibilityChange(ByVal newVisibility As Boolean)
If (Not m_EditBox Is Nothing) Then m_EditBox.Visible = newVisibility
End Sub
Expand All @@ -758,6 +778,10 @@ Private Sub UserControl_Initialize()
ucSupport.RequestExtraFunctionality True, True
ucSupport.SpecifyRequiredKeys VK_UP, VK_RIGHT, VK_DOWN, VK_LEFT, vbKeyAdd, vbKeySubtract

'We also want to be notified when focus changes via tab-key; when this occurs, we want to
' set focus to the edit box - NOT the spin control.
ucSupport.SubclassCustomMessage WM_PD_FOCUS_FROM_TAB_KEY, True

'Prep the color manager and load default colors
Set m_Colors = New pdThemeColors
Dim colorCount As PDSPINNER_COLOR_LIST: colorCount = [_Count]
Expand Down
3 changes: 3 additions & 0 deletions Modules/PublicConstants.bas
Original file line number Diff line number Diff line change
Expand Up @@ -115,6 +115,9 @@ Public Const WM_PD_PRIMARY_COLOR_CHANGE As Long = (WM_APP + 16&)
Public Const WM_PD_COLOR_MANAGEMENT_CHANGE As Long = (WM_APP + 17&)
Public Const WM_PD_DIALOG_NAVKEY As Long = (WM_APP + 18&)
Public Const WM_PD_PRIMARY_COLOR_APPLIED As Long = (WM_APP + 19&)
Public Const WM_PD_FOCUS_FROM_TAB_KEY As Long = (WM_APP + 20&)
Public Const WM_PD_TAB_KEY_TARGET As Long = (WM_APP + 21&)
Public Const WM_PD_SHIFT_TAB_KEY_TARGET As Long = (WM_APP + 22&)

'Inside the IDE, we can't rely on PD's central themer for color decisions (as it won't be initialized).
' A few constants are used instead.
Expand Down
2 changes: 1 addition & 1 deletion Modules/UserControl_Support.bas
Original file line number Diff line number Diff line change
Expand Up @@ -437,7 +437,7 @@ Public Sub RemoveMessageRecipient(ByVal targetHWnd As Long)
'Rather then condensing the list, we simply set all corresponding window entries to zero.
Dim i As Long
For i = 0 To m_windowMsgCount - 1
If m_windowList(i) = targetHWnd Then
If (m_windowList(i) = targetHWnd) Then
m_windowList(i) = 0
m_wMsgList(i) = 0
End If
Expand Down

0 comments on commit d92c059

Please sign in to comment.