IN THE SPOTLIGHT: MDE to MDB Conversion Service
(also supports: ACCDE to ACCDB, ADE to ADP, etc)
IN THE SPOTLIGHT: Access Database Repair Service
An in-depth repair service for corrupt Microsoft Access files
IN THE SPOTLIGHT: vbWatchdog
VBA error handling just got easier...
" vbWatchdog is off the chart. It solves a long standing problem of how to consolidate error handling into one global location and avoid repetitious code within applications. "
- Joe Anderson,
Microsoft Access MVP
Meet Shady, the vbWatchdog mascot watching over your VBA code →
(courtesy of Crystal Long, Microsoft Access MVP)
IN THE SPOTLIGHT: vbMAPI
An Outlook / MAPI code library for VBA, .NET and C# projects
Get emails out to your customers reliably, and without hassle, every single time.
Use vbMAPI alongside Microsoft Outlook to add professional emailing capabilities to your projects.
IN THE SPOTLIGHT: Code Protector
Standard compilation to MDE/ACCDE format is flawed and reversible.
Provided by Allen Browne, January 2008
Copy the function below into a standard module in your database. You can then call it from anywhere in your database to insert characters into the active control, at the cursor position.
If any characters are selected at the time you run this code, those characters are overwritten. That is in keeping with what normally happens in Windows programs.
Here are some examples of how the function could be used.
In Access, the Tab key does not insert a tab character as it does in Word. To simulate this, you could insert 4 spaces when the user presses the Tab key.
Use the KeyDown event procedure of your text box, like this:
Private Sub txtMemo_KeyDown(KeyCode As Integer, Shift As Integer) If (KeyCode = vbKeyTab) And (Shift = 0) Then If InsertAtCursor(" ") Then KeyCode = 0 End If End If End Sub
This example inserts preset paragraphs at the cursor as the user presses Alt+1, Alt+2, etc.
Private Sub Text0_KeyDown(KeyCode As Integer, Shift As Integer)
Dim strMsg As String
Dim strText As String
If Shift = acAltMask Then
Select Case KeyCode
Case vbKey1
strText = "Paragraph 1" & vbCrLf
Case vbKey2
strText = "Paragraph 2" & vbCrLf
Case vbKey3
strText = "Paragraph 3" & vbCrLf
'etc for other paragraphs.
End Select
If InsertAtCursor(strText, strMsg) Then
KeyCode = 0
ElseIf strMsg <> vbNullString Then
MsgBox strMsg, vbExclamation, "Problem inserting boilerplate text"
End If
End If
End Sub
For a variation on the above, you could create a buttons on a custom toolbar/ribbon that insert the paragraphs. You could allow the user to define their own paragraphs (stored in a table), and use DLookup() to retrieve the values to insert.
Note that you cannot use a command button on the form to do this: when its Click event runs, it has focus, and the attempt to insert text into the command button cannot succeed.
In a memo field, you may want to insert a new line and today's date when Alt+D is pressed
Private Sub Text5_KeyDown(KeyCode As Integer, Shift As Integer) If (Shift = acAltMask) And KeyCode = vbKeyD Then Call InsertAtCursor(vbCrLf & Date) End If End Sub
Here is the code to copy into a standard module in your database:
Public Function InsertAtCursor(strChars As String, Optional strErrMsg As String) As Boolean On Error GoTo Err_Handler 'Purpose: Insert the characters at the cursor in the active control. 'Return: True if characters were inserted. 'Arguments: strChars = the character(s) you want inserted at the cursor. ' strErrMsg = string to append any error messages to. 'Note: Control must have focus. Dim strPrior As String 'Text before the cursor. Dim strAfter As String 'Text after the cursor. Dim lngLen As Long 'Number of characters Dim iSelStart As Integer 'Where cursor is. If strChars <> vbNullString Then With Screen.ActiveControl If .Enabled And Not .Locked Then lngLen = Len(.Text) 'SelStart can't cope with more than 32k characters. If lngLen <= 32767& - Len(strChars) Then 'Remember characters before cursor. iSelStart = .SelStart If iSelStart > 1 Then strPrior = Left$(.Text, iSelStart) End If 'Remember characters after selection. If iSelStart + .SelLength < lngLen Then strAfter = Mid$(.Text, iSelStart + .SelLength + 1) End If 'Assign prior characters, new ones, and later ones. .Value = strPrior & strChars & strAfter 'Put the cursor back where it as, after the new ones. .SelStart = iSelStart + Len(strChars) 'Return True on success InsertAtCursor = True End If End If End With End If Exit_Handler: Exit Function Err_Handler: Debug.Print Err.Number, Err.Description Select Case Err.Number Case 438&, 2135&, 2144& 'Object doesn't support this property. Property is read-only. Wrong data type. strErrMsg = strErrMsg & "You cannot insert text here." & vbCrLf Case 2474&, 2185& 'No active control. Control doesn't have focus. strErrMsg = strErrMsg & "Cannot determine which control to insert the characters into." & vbCrLf Case Else strErrMsg = strErrMsg & "Error " & Err.Number & ": " & Err.Description & vbCrLf End Select Resume Exit_Handler End Function
Home | Index of tips | Top |
Rate this article:
This is a cached tutorial, reproduced with permission.
iTech Masters | VAT: GB202994606 | Terms | Sitemap | Newsletter