Showing posts with label VBA. Show all posts
Showing posts with label VBA. Show all posts

10/1/12

Sending mail from Excel with CDO

What is CDO doing

The example code is using CDOSYS (CDO for Windows 2000).
It does not depend on MAPI or CDO and hence is dialog free
and does not use your mail program to send email.


Briefly to explain, this code builds the message and drops it
in the pickup directory, and SMTP service running on the machine
picks it up and send it out to the internet.


Why using CDO code instead of Outlook automation or SendMail in VBA.

1: It doesn't matter what Mail program you are using (It only use the SMTP server).
2: It doesn't matter what Office version you are using (97…2007)
3: You can send a range/sheet in the body of the mail (some mail programs can’t do this)
4: You can send any file you like (Word, PDF, PowerPoint, TXT files,….)
5: No Security warnings anymore, really great if you are sending a lot of mail in a loop.


Read this!!!

This code will not work in Win 98 and ME.
You must be connected to the internet when you run a example.

It is possible that you get a Send error when you use one of the examples.
AFAIK : This will happen if you haven't setup an account in Outlook Express or Windows Mail.
In that case the system doesn't know the name of your SMTP server.
If this happens you can use the commented green lines in each example.
Don't forget to fill in the SMTP server name in each code sample where
it says "Fill in your SMTP server here"

When you also get the Authentication Required Error you can add this three lines.
.Item("http://schemas.microsoft.com/cdo/configuration/smtpauthenticate") = 1
.Item("http://schemas.microsoft.com/cdo/configuration/sendusername") = "username"
.Item("http://schemas.microsoft.com/cdo/configuration/sendpassword") = "password"


Don't remove the TextBody line in the code. If you do you can't open the attachment (bug in CDO).
If you don't want to have text in the body use this then .TextBody = ""

Note: It is always possible that your firewall block the code (Check your firewall settings)


Can you use CDO on your machine?

Let's try a basic example first.

The code below will send four text lines in the body of the mail to the person in this line
.To = "ron@debruin.nl"

Change ron@debruin.nl to your own mail address before you test the code.
If you read the information above you know that if you have a account in Outlook Express or
Windows Mail you can Run the code below after changing the mail address.
But if you not have a account in Outlook Express or Windows Mail you also need the commented
green lines in the code. Remove every ' before every green line and fill in the name of your SMTP server
where it says "Fill in your SMTP server here"

1) Open a new workbook
2) Alt F11 (to open the VBA editor)
3) Insert>Module
4) Paste the code in this module
5) Make your changes
6) Alt q to go back to Excel

When you use Alt F8 you can select the macro and press Run.
Now wait a moment and see if you receive the mail in your inbox.
Sub CDO_Mail_Small_Text()
    Dim iMsg As Object
    Dim iConf As Object
    Dim strbody As String
    '    Dim Flds As Variant

    Set iMsg = CreateObject("CDO.Message")
    Set iConf = CreateObject("CDO.Configuration")

    '    iConf.Load -1    ' CDO Source Defaults
    '    Set Flds = iConf.Fields
    '    With Flds
    '        .Item("http://schemas.microsoft.com/cdo/configuration/sendusing") = 2
    '        .Item("http://schemas.microsoft.com/cdo/configuration/smtpserver") _
    '                       = "Fill in your SMTP server here"
    '        .Item("http://schemas.microsoft.com/cdo/configuration/smtpserverport") = 25
    '        .Update
    '    End With

    strbody = "Hi there" & vbNewLine & vbNewLine & _
              "This is line 1" & vbNewLine & _
              "This is line 2" & vbNewLine & _
              "This is line 3" & vbNewLine & _
              "This is line 4"

    With iMsg
        Set .Configuration = iConf
        .To = "ron@debruin.nl"
        .CC = ""
        .BCC = ""
        .From = """Ron"" "
        .Subject = "New figures"
        .TextBody = strbody
        .Send
    End With

End Sub

Note: If you get this error : The transport failed to connect to the server
then try to change the SMTP port from 25 to 465



Use the GMail SMTP server from Google.
http://gmail.google.com

You can find the code in the workbook with examples that you can download below.
There is more information about the code in the workbook.
Note: You must have a Gmail account to try this example.




Download workbook with more examples

You can download a example workbook with eighth examples.
Download Example workbook with all the code

Attachment examples:
Module file1 = Workbook
Module file2 = One worksheet or more
Module file3 = Every sheet with a mail address in cell A1

Body examples:
Module body1 = Selection/Range or whole worksheet
Module body2 = Personalized Mail
Module body3 = Every sheet with a mail address in cell A1
Module body4 = Small text and text from a txt file

Note: the body examples in the workbook are using the function RangetoHTML in
the "bodyfunction" module of the workbook.

Gmail example:
Module gmail = Use the smtp.gmail.com server from Gmail to send mail



Tips and links


CDO sheet template

Check out this sheet template if you want to send every sheet to a different person.
Or want to send one or more sheets to one or more recipient.
http://www.rondebruin.nl/mail/templates.htm



Set importance/priority and request read receipt

For importance/priority and read receipt you can add this in the With iMsg part of the macro before .Send

' Set importance or Priority to high
.Fields("urn:schemas:httpmail:importance") = 2
.Fields("urn:schemas:mailheader:X-Priority") = 1

' Request read receipt
.Fields("urn:schemas:mailheader:return-receipt-to") = "ron@debruin.nl"
.Fields("urn:schemas:mailheader:disposition-notification-to") = "ron@debruin.nl"

' Update fields
.Fields.Update


Changing the To line

If you want to mail to all E-mail addresses in a range then use this code
instead of .To = "ron@debruin.nl"

The example below will use the cells from sheets("Sheet1") in ThisWorkbook (workbook with the code)
It is possible that you must use ActiveWorkbook or something else in your code to use it.
    Dim cell As Range
    Dim strto As String
    On Error Resume Next
    For Each cell In ThisWorkbook.Sheets("Sheet1") _
        .Range("A1:A10").Cells.SpecialCells(xlCellTypeConstants)
        If cell.Value Like "?*@?*.?*" Then
            strto = strto & cell.Value & ";"
        End If
    Next cell
    On Error GoTo 0
    If Len(strto) > 0 Then strto = Left(strto, Len(strto) - 1)

Change the To line to .To = strto


Or to more people
.To = "Jon@something.com;ron@something.com"

Or you can use a address in a cell like this
.To = Sheets("Sheet1").Range("C1").Value



Change the Body line


Plain text :

Note: see also the example in the workbook to send all text from a txt file (Module body4)

If you want to add more text to the body then you can use the code below.
Instead of .TextBody = "This is the body text" use .TextBody = strbody then.

Dim strbody As String
strbody = "Hi there" & vbNewLine & vbNewLine & _
    "This is line 1" & vbNewLine & _
    "This is line 2" & vbNewLine & _
    "This is line 3" & vbNewLine & _
    "This is line 4"


Or use this if you want to use cell values

Dim cell As Range
Dim strbody As String
For Each cell In Sheets("Sheet1").Range("C1:C20")
    strbody = strbody & cell.Value & vbNewLine
Next


Or this one

Dim strbody As String
With Sheets("Sheet1")
    strbody = "Hi there" & vbNewLine & vbNewLine & _
        .Range("A1") & vbNewLine & _
        .Range("A2") & vbNewLine & _
        .Range("A3") & vbNewLine & _
        .Range("A4")
End With




Links

.TextBody = "file://Yourcomputer/YourFolder/Week2.xls"

'If there are spaces use %20
.TextBody = "file://Yourcomputer/YourFolder/Week%202.xls"

'Example for a file on a website
.TextBody = "http://www.rondebruin.nl/files/EasyFilter.zip"



HTML text :

If you want to create emails that are formatted you can use HTMLBody (Office 2000 and up) instead of TextBody. You can find a lot of WebPages on the internet with more HTML tags examples.

.HTMLBody = "

Dear Ron de Bruin

" & _
"Please visit this website to download an update.
" & _
"Ron's Excel Page"



Tip: Or send a complete webpage, instead of HTMLBody or TextBody use

.CreateMHTMLBody "http://www.rondebruin.nl/copy1.htm"

Or file on your computer
.CreateMHTMLBody "file://C:/test.htm"



Copy the cells as values

If you want to paste as values the sheet must be unprotected!!!!!
Or Unprotect and Protect the sheet in the Sub also.

See this page for example code that you can use
http://www.rondebruin.nl/values.htm



Test if you are online

You can use code like this in your subroutine to avoid errors if you run the code
when you are not online (example below is for a dial up connection)

For checking other connections check out this great website.
http://vbnet.mvps.org/

Public Declare Function InternetGetConnectedState _
                         Lib "wininet.dll" (lpdwFlags As Long, _
                                            ByVal dwReserved As Long) As Boolean

Function IsConnected() As Boolean
    Dim Stat As Long
    IsConnected = (InternetGetConnectedState(Stat, 0&) <> 0)
End Function

Sub Test()
' Randy Birch
    If IsConnected = True Then
        MsgBox "Copy your mail code here"
    Else
        MsgBox "You can't use this subroutine because you are not online"
    End If
End Sub


Links to more information about CDO for windows 2000


MSDN
Search for "CDO for Windows 2000" on MSDN

Paul R. Sadowski
http://www.paulsadowski.com/WSH/cdo.htm

www.aspfaq.com
http://www.aspfaq.com/show.asp?id=2026

http://www.rondebruin.nl/cdo.htm

1/24/11

Holiday Functions

Often it is useful to return the date of a holiday for a given year, perhaps for a schedule application. Neither Excel nor VBA have any built in functions for working with holidays -- you have to create your own. Holidays can be thought of as being either Fixed or Floating. Fixed holidays are those that occur on the same day each year, such as Christmas. Floating holidays are those which occur on different days in different years. For example, Thanksgiving (in the US) occurs on the fourth Thursday of November. Therefore, we need a function that will calculate the fourth Thursday. We'll generalize that function, in both VBA and worksheet function form, to return the Nth day-of-week for any month and year.

Other floating holidays are a bit harder to calculate. For example, in the US, Memorial Day occurs on the last Monday of May. Depending on the year, this may be either the 4th or 5th Monday. So we need a function to calculate the number of Mondays in May. We'll generalize this to compute the number of any day-of-week in any month and year.

Finally, there is Easter, whose actual date is some bizarre result of the phases of the moon. I don't claim credit for the formulas for calculating Easter shown below, nor do I claim to understand why the work, but they do.



Fixed Holidays
For fixed holidays, such as Christmas, this is simple since the date of the holiday does not change from year to year. For example, use the following to return the date of Christmas in the current year:

=DATE(YEAR(NOW()),12,25)


Floating Holidays
Other holidays, however, are not assigned to a specific date. For example, Thanksgiving Day is defined to be the 4th Thursday of November. Therefore its exact date will change from year to year. For Thanksgiving, we have an explicit VBA function:

Public Function ThanksgivingDate(Yr As Integer) As Date
ThanksgivingDate = DateSerial(Yr, 11, 29 - _
WeekDay(DateSerial(Yr, 11, 1), vbFriday))
End Function

We can generalize this to holidays that are defined as the Nth Day of some month, such as Martin Luther King's birthday, celebrated on the 3rd Monday of January. The following function will return the Nth DayOfWeek for a given month and year:

Public Function NDow(Y As Integer, M As Integer, _
N As Integer, DOW As Integer) As Date

NDow = DateSerial(Y, M, (8 - WeekDay(DateSerial(Y, M, 1), _
(DOW + 1) Mod 8)) + ((N - 1) * 7))
End Function

To return the date of the 3rd Monday in January of 1998, use
=NDow (1998, 1, 3, 2)


The NDow function can also be written as a worksheet formula:
=DATE(Yr,Mon,1+((Nth-(DoW>=WEEKDAY(DATE(Yr,Mon,1))))*7)
+(DoW-WEEKDAY(DATE(Yr,Mon,1))))

Where Yr,Mon, and DoW are cell references or values indicating Year, Month, Nth, and Day-Of-Week.


This will work fine for most floating holidays. However, Memorial Day is celebrated on the Last Monday of May. To compute this date, we first need a function to tell us how many Mondays there are in the month.

Public Function DOWsInMonth(Yr As Integer, M As Integer, _
DOW As Integer) As Integer

On Error GoTo EndFunction

Dim I As Integer
Dim Lim As Integer
Lim = Day(DateSerial(Yr, M + 1, 0))
DOWsInMonth = 0
For I = 1 To Lim
If WeekDay(DateSerial(Yr, M, I)) = DOW Then
DOWsInMonth = DOWsInMonth + 1
End If
Next I

Exit Function
EndFunction:
DOWsInMonth = 0
End Function


Calling this function will tell us how many Mondays there are in May, 1998.
=DOWsInMonth(1998, 5, 2)

The DOWsInMonth can also be written as a worksheet function with the following array formula. Note that it will not work properly unless you press CTRL+SHIFT+ENTER instead of just ENTER when you first enter the formula and whenever you edit it later. If you do this properly, Excel will display the formula in the formula bar enclosed in curly braces {}.


=SUM((WEEKDAY(DATE(B3,C3,(ROW(INDIRECT
("1:"&DAY(DATE(B3,C3+1,0)))))))=D3)*1)

where B3 is the year, C3 is the month, and D3 is the day of week (1=Sunday, 2=Monday, ..., 7=Saturday)

There are 4 Mondays in May, 1998. The we can pass this into the NDOW function, to return 25-May-1998, the date of Memorial Day. Therefore, the formula to return the date of Memorial Day in 1999 would be

=NDow(1999,5,DowsInMonth(1999,5,2),2)

Many organizations recognize holiday dates on dates different than those of the actual date. Typically, this is done when the day of week of the holiday falls on a weekend and holidays are observed to make a three-day weekend. The general rule is that if the holiday falls on a Saturday, it is observed on the Friday before the holiday. If the holiday falls on a Sunday, it is observed on the following Monday. The following formula will return a Friday if the holiday falls on a Saturday, a Monday if the holiday falls on a Sunday, or the date itself if it falls on a weekday.=IF(WEEKDAY(A2, 1)=1,A2+1,IF(WEEKDAY(A2,1)=7,A2-1,A2)) where A2 is the date of the holiday. In VBA, you can use the following function:

Function Observed(TheDate As Date) As Date
If Weekday(TheDate, vbSunday) = 1 Then
Observed = TheDate + 1
ElseIf Weekday(TheDate, vbSunday) = 7 Then
Observed = TheDate - 1
Else
Observed = TheDate
End If
End Function

where TheDate is the date if the holiday.


Easter

Worksheet Formula For Easter
You can calculate the date of Easter with formula below. It is accurate for the years from 1900 to 2368. The formula is:

=FLOOR("5/"&DAY(MINUTE(YYYY/38)/2+56)&"/"&YYYY,7)-34

where YYYY is a four digit year between 1900 and 2368. The formula returns an incorrect for some years past 2369.


VBA Function For Easter
The date of Easter can be computed in VBA. The algorithm below is from the United States Naval Observatory, at Computing The Date Of Easter.

Public Function EasterUSNO(YYYY As Long) As Long
Dim C As Long
Dim N As Long
Dim K As Long
Dim I As Long
Dim J As Long
Dim L As Long
Dim M As Long
Dim D As Long

C = YYYY \ 100
N = YYYY - 19 * (YYYY \ 19)
K = (C - 17) \ 25
I = C - C \ 4 - (C - K) \ 3 + 19 * N + 15
I = I - 30 * (I \ 30)
I = I - (I \ 28) * (1 - (I \ 28) * (29 \ (I + 1)) * ((21 - N) \ 11))
J = YYYY + YYYY \ 4 + I + 2 - C + C \ 4
J = J - 7 * (J \ 7)
L = I - J
M = 3 + (L + 40) \ 44
D = L + 28 - 31 * (M \ 4)
EasterUSNO = DateSerial(YYYY, M, D)
End Function
You can call this from a worksheet cell with a formula like

=EasterUSNO(YYYY)

where YYYY is a four digit year.

http://www.cpearson.com/excel/holidays.htm
http://www.cpearson.com/excel/Easter.aspx

1/17/11

Delete Duplicate Records

Sub DeleteDuplicateRecords(strTableName As String)
' Deletes exact duplicates from the specified table.
' No user confirmation is required. Use with caution.
Dim rst As DAO.Recordset
Dim rst2 As DAO.Recordset
Dim tdf As DAO.TableDef
Dim fld As DAO.Field
Dim strSQL As String
Dim varBookmark As Variant

Set tdf = DBEngine(0)(0).TableDefs(strTableName)
strSQL = "SELECT * FROM " & strTableName & " ORDER BY "
' Build a sort string to make sure duplicate records are
' adjacent. Can't sort on OLE or Memo fields,though.
For Each fld In tdf.Fields
If (fld.Type <> dbMemo) And (fld.Type <> dbLongBinary) Then
strSQL = strSQL & fld.Name & ", "
End If
Next fld
' Remove the extra comma and space from the SQL
strSQL = Left(strSQL, Len(strSQL) - 2)
Set tdf = Nothing

Set rst = CurrentDb.OpenRecordset(strSQL)
Set rst2 = rst.Clone
rst.MoveNext
Do Until rst.EOF
varBookmark = rst.Bookmark
For Each fld In rst.Fields
If fld.Value <> rst2.Fields(fld.Name).Value Then
GoTo NextRecord
End If
Next fld
MsgBox "delete"
rst.Delete
GoTo SkipBookmark
NextRecord:
rst2.Bookmark = varBookmark
SkipBookmark:
rst.MoveNext
Loop
End Sub

http://www.databasejournal.com/features/msaccess/article.php/3077791/Delete-Duplicate-Records-From-Access-Tables.htm

Mouse Pointer Hover Function

These are the standard Access cursors and can be set in code. The problem with this is once set the cursor remains this way until reset to another value

Screen.MousePointer = 1 'Standard Cursor
Screen.MousePointer = 3 ' I Beam
Screen.MousePointer = 7 'Double Arrow Vertical
Screen.MousePointer = 9 'Double Arrow Horizontal
Screen.MousePointer = 11 'Hour Glass

The function below allows you to change a cursor only when it hovers over a label or command button. It resets th e cursor when it leaves the control. Goto Modules in the Objects Dialog box and click on NEW. Then enter this code:


‘*********************** Code Starts Here **********************************
Declare Function SetClassLong Lib "user32" Alias "SetClassLongA" (ByVal hWnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long

'=====================================================================
' Globals for cursor handling
Global Const GCL_HCURSOR = (-12)
Global hSwapCursor As Long
Global hAniCursor As Long

'=====================================================================

Public Const IDC_ARROW = 32512&
Public Const IDC_IBEAM = 32513&
Public Const IDC_WAIT = 32514&
Public Const IDC_CROSS = 32515&
Public Const IDC_UPARROW = 32516&
Public Const IDC_ICON = 32641&
Public Const IDC_SIZENWSE = 32642&
Public Const IDC_SIZENESW = 32643&
Public Const IDC_SIZEWE = 32644&
Public Const IDC_SIZENS = 32645&
Public Const IDC_SIZEALL = 32646&
Public Const IDC_NO = 32648&
Public Const IDC_HAND = 32649&
Public Const IDC_APPSTARTING = 32650&

Declare Function LoadCursorBynum Lib "user32" Alias "LoadCursorA" _
(ByVal hInstance As Long, ByVal lpCursorName As Long) As Long

Declare Function LoadCursorFromFile Lib "user32" Alias _
"LoadCursorFromFileA" (ByVal lpFileName As String) As Long

Declare Function SetCursor Lib "user32" _
(ByVal hCursor As Long) As Long
'
Public Function Arrow_Pointer()
Screen.MousePointer = 1
End Function

Function ChangeCursor(strPathToCursor As String)

On Error GoTo Error_On_ChangeCursor

' Example :
' ChangeCursor ("C:\Program Files\Microsoft Office\Office\Hand.cur")

If Dir(strPathToCursor) <> "" Then
Dim lngRet As Long
lngRet = LoadCursorFromFile(strPathToCursor)
lngRet = SetCursor(lngRet)
End If

Exit_ChangeCursor:

Exit Function

Error_On_ChangeCursor:

Resume Exit_ChangeCursor

End Function

Public Function Default_Pointer()
Screen.MousePointer = 0
End Function

Public Function IBeam_Pointer()
Screen.MousePointer = 3
End Function

Function MouseCursor(CursorType As Long)

' Example: =MouseCursor(32512) ' using Public Constants from above

Dim lngRet As Long
lngRet = LoadCursorBynum(0&, CursorType)
lngRet = SetCursor(lngRet)
End Function

Public Function Replace_Cursor(PathToFile As String)

' Return handle from animated cursor

' Original - hAniCursor = LoadCursorFromFile("C:\WINDOWS\CURSORS\GLOBE.ANI")

hAniCursor = LoadCursorFromFile(PathToFile)
' Swap current mouse pointer with new animated cursor :
hSwapCursor = SetClassLong(Screen.ActiveForm.hWnd, GCL_HCURSOR, hAniCursor)


End Function

Public Function Restore_Cursor()

' Remove animated cursorand replace with saved index :

hSwapCursor = SetClassLong(Screen.ActiveForm.hWnd, GCL_HCURSOR, hSwapCursor)

End Function
‘*********************** Code End Here **********************************

When Prompted name the module modMousePointers

To change a pointer when the cursor moves over a control, goto the control’s

Properties – Events – On Mouse Move and in the MouseMove Property enter

=MouseCursor(xxxxx)

where xxxxx is the number without the ampersand

Public Const IDC_ARROW = 32512&
Public Const IDC_IBEAM = 32513&
Public Const IDC_WAIT = 32514&
Public Const IDC_CROSS = 32515&
Public Const IDC_UPARROW = 32516&
Public Const IDC_ICON = 32641&
Public Const IDC_SIZENWSE = 32642&
Public Const IDC_SIZENESW = 32643&
Public Const IDC_SIZEWE = 32644&
Public Const IDC_SIZENS = 32645&
Public Const IDC_SIZEALL = 32646&
Public Const IDC_NO = 32648&
Public Const IDC_HAND = 32649&
Public Const IDC_APPSTARTING = 32650&


http://bytes.com/topic/access/answers/662035-changing-mouse-cursor

7/7/10

Carriage return

When creating long text strings in VBA and you use Chr(13) you will see that this "Carriage return Character" is represented by a small square in forms or on reports. To avoid this you should use the following structure.

& Chr(13) & Chr(10)

NOTE: They must be used in the displayed order.
13 is a Carriage return
10 is a Line Feed

Also you may use the following
vbCr is a Carriage Return
vbCrLf is a Carriage Return and Line Feed
vbLf is a Line Feed
vbNewLine Is a new Line

VBA Function to get text driving directions from XML web page

Reference Needed: Microsoft XML, V6.0

Function TextDirectionsXML(StartAddress As String, EndAddress As String) As String
On Error GoTo ErrMsg
dteStartTime = Now()
'populate addresses
strStartAddress = StartAddress
strEndAddress = EndAddress

' check google.com using xml
Dim xSite As XMLHTTP60
Set xSite = New XMLHTTP60
xSite.Open "GET", "http://maps.google.com/maps?q=from+" & strStartAddress & "+to+" & strEndAddress & "&output=kml", False
xSite.Send
Do Until xSite.readyState = 4
Loop

'MsgBox xSite.getAllResponseHeaders
'MsgBox xSite.getResponseHeader("Last-Modified")
'MsgBox "Status Text: " & xSite.statusText & vbCr & vbCr & "Status: " & xSite.Status
'MsgBox xSite.responseText


Dim xml_doc As New DOMDocument
Dim nde_Placemark As IXMLDOMNode
'Dim nde_Dividend As IXMLDOMNode
xml_doc.loadXML (xSite.responseText) ' response text is the xml file being returned

i = 1
DriveDirection = ""

'Looop through node
For Each nde_Placemark In xml_doc.selectNodes("//Placemark")

str_Phrase = nde_Placemark.childNodes(0).Text
str_DistanceTime = nde_Placemark.childNodes(1).Text
If str_Phrase = "Route" Then
str_Phrase = ""
If InStr(str_DistanceTime, "&") <> 0 Then
If InStr(str_DistanceTime, "hour") > 1 Then
'time is at least 1 hour
pos1 = InStr(str_DistanceTime, "about")
pos2 = InStr(str_DistanceTime, "hours")
intHours = Mid(str_DistanceTime, pos1 + 6, pos2 - pos1 - 7)
pos1 = InStr(str_DistanceTime, "hours")
pos2 = InStr(str_DistanceTime, "mins")
intMinutes = Mid(str_DistanceTime, pos1 + 6, pos2 - pos1 - 7)
IntTotalMinutes = intHours * 60 + intMinutes
Else
'time is less than 1 hour
intHours = 0
pos1 = InStr(str_DistanceTime, "about")
pos2 = InStr(str_DistanceTime, "mins")
intMinutes = Mid(str_DistanceTime, pos1 + 6, pos2 - pos1 - 7)
IntTotalMinutes = intHours * 60 + intMinutes
End If

intDistanceValue = Mid(str_DistanceTime, 11, InStr(str_DistanceTime, "&") - 11)
intDistanceUnit = Mid(str_DistanceTime, InStr(str_DistanceTime, ";") + 1, 2)
strTotalMiles = intDistanceValue & intDistanceUnit
intSpeed = (intDistanceValue / IntTotalMinutes) * 60
Else
MilesUnits = ""
End If

Else
If InStr(str_DistanceTime, "&") <> 0 Then
intDistanceValue = Mid(str_DistanceTime, 4, InStr(str_DistanceTime, "&") - 4)
intDistanceUnit = Mid(str_DistanceTime, InStr(str_DistanceTime, ";") + 1, Len(str_DistanceTime))
strTotalMiles = " (Go " & intDistanceValue & intDistanceUnit & ")"
Else
MilesUnits = ""
End If

End If

If i = 1 Then Str_AddressBeg = nde_Placemark.childNodes(2).Text

If str_Phrase <> "" Then
If Left(str_Phrase, 6) = "Arrive" Then
Str_AddressEnd = nde_Placemark.childNodes(1).Text
DriveDirection = DriveDirection & i & "." & str_Phrase & vbCrLf
Else
DriveDirection = DriveDirection & i & "." & str_Phrase & strTotalMiles & vbCrLf
End If

Else
DriveDirection = DriveDirection
End If

i = i + 1
Next

dteEndTime = Now()
dteRunTime = "(" & Format(dteEndTime - dteStartTime, "s") & " Second(s))"
Header = "Retreived: " & Format(Now(), "m/d/yy, h:mma/p")
TextDirectionsXML = DriveDirection & vbCrLf & _
"Distance: " & strTotalMiles & vbCrLf & _
"Travel Time: " & intHours & ":" & intMinutes & vbCrLf & _
"Speed: " & Format(intSpeed, "#,##0.0 mph") & vbCrLf & _
"Est Time To Deliver: " & Format(TimeValue(TimeSerial(0, i * 1 + (IntTotalMinutes * 2) + 15, 0)), "h:mm") & vbCrLf & _
Str_AddressBeg & vbCrLf & _
Str_AddressEnd & vbCrLf


' Header & " " & dteRunTime & vbCrLf & _
' "ettd: " & i * 1 + (IntTotalMinutes * 2) + 15


Exit Function
ErrMsg:

TextDirectionsXML = ""
Exit Function

End Function

http://www.tek-tips.com/viewthread.cfm?qid=1444524&page=8
http://groups.google.com/group/Google-Maps-API/msg/4dc2fad4f74e3314

7/6/10

Median Function for Access

Function DMedian(FieldName As String, _
TableName As String, _
Optional WhereClause As String = "" _
) As Single

Dim dbMedian As DAO.Database
Dim rsMedian As DAO.Recordset
Dim lngLoop As Long
Dim lngOffSet As Long
Dim lngRecCount As Long
Dim dblTemp1 As Double
Dim dblTemp2 As Double
Dim strSQL As String

Set dbMedian = CurrentDb()
strSQL = "SELECT [" & FieldName & _
"] FROM [" & TableName & "] "
' NOTE: To ignore nulls when calculating the median value, use
' the following 4 lines:
' strSQL = strSQL & "WHERE [" & FieldName & "] IS NOT NULL "
' If Len(WhereClause) > 0 Then
' strSQL = strSQL & "AND (" & WhereClause & ") "
' End If
' NOTE: The following 3 lines will include nulls. Remove them
' (and use the 4 lines above) if you want to ignore nulls.
If Len(WhereClause) > 0 Then
strSQL = strSQL & "WHERE " & WhereClause & " "
End If
strSQL = strSQL & "ORDER BY [" & FieldName & "]"
Set rsMedian = dbMedian.OpenRecordset(strSQL)
If rsMedian.EOF = False Then
rsMedian.MoveLast
lngRecCount = rsMedian.RecordCount
If lngRecCount Mod 2 <> 0 Then
lngOffSet = ((lngRecCount + 1) / 2) - 2
For lngLoop = 0 To lngOffSet
rsMedian.MovePrevious
Next lngLoop
DMedian = rsMedian(FieldName)
Else
lngOffSet = (lngRecCount / 2) - 2
For lngLoop = 0 To lngOffSet
rsMedian.MovePrevious
Next lngLoop
dblTemp1 = rsMedian(FieldName)
rsMedian.MovePrevious
dblTemp2 = rsMedian(FieldName)
DMedian = (dblTemp1 + dblTemp2) / 2
End If
End If

End_DMedian:
On Error Resume Next
rsMedian.Close
dbMedian.Close
Set dbMedian = Nothing
Exit Function

Err_DMedian:
Err.Raise Err.Number, "DMedian", Err.Description
Resume End_DMedian

End Function

7/5/10

Sort Data by Double Clicking a Control

Private Sub CUSTNAME_Label_DblClick(Cancel As Integer)
If Me.OrderBy = "CUSTNAME DESC" Then
Me.OrderBy = "CUSTNAME"
Me.OrderByOn = True
Else
Me.OrderBy = "CUSTNAME DESC"
Me.OrderByOn = True
End If
End Sub

Recordsets Collection and Recordset Object

The Recordset object is the primary object used to manipulate data in Access databases (and other databases as well, via ODBC connections). Although there is a Recordsets collection (the collection of all open Recordset objects in a database), it is not much use, except to list the open recordsets and their SQL statements, as in the following code sample:

Private Sub cmdListRecordsets_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim intCount As Integer   Dim strTable As String      strTable = "Orders"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   intCount = dbs.Recordsets.Count   Debug.Print intCount & _         " recordsets in current database (before opening a recordset)"   Set rst = dbs.OpenRecordset(strTable, dbOpenTable)   intCount = dbs.Recordsets.Count   Debug.Print intCount & _         " recordsets in current database (after opening a recordset)"      For Each rst In dbs.Recordsets      Debug.Print "Open recordset: " & rst.Name   Next rst   End Sub

A new Recordset object is automatically added to the Recordsets collection when you open the recordset, and it is automatically removed when you close it. Note that when you first count the recordsets in the preceding code, the count is 0; after setting a recordset variable, it is 1. The position of the Recordsets collection in the DAO object model is shown in Figure 8-1.

Figure 8-1. The Recordsets collection in the DAO object model

You can create as many recordset variables as you want, and different recordsets can access the same tables, queries, or fields without causing a problem. You can even open two recordsets from the same data source, and this is not a problem, so long as you refer to the recordsets by the variables used to assign them, not by their names.

TIP:

See the Name property section later in this chapter for a discussion of why it is unwise to use the Name property to reference a recordset.

There are five types of recordsets: Table-type, Dynaset, Snapshot, Forward-only, and Dynamic. (See the Type property section for a discussion of recordset types.) Each Recordset object contains a collection of Fields that represents the fields in the underlying table(s). You can list the field names and values, but you will just get the values in the current record, unless you first go to a particular record. For example, the following code moves to the last record in a recordset and lists the field names and values for that record:

Private Sub cmdListFields_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String   Dim fld As Field      strTable = "Categories"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenTable)   With rst      .MoveLast      For Each fld In .Fields         Debug.Print fld.Name & " value: " & fld.Value      Next fld      .Close   End With   End Sub

Although you can reference a Recordset object in the Recordsets collection by any of the following syntax variants, it is advisable to use its variable instead to avoid possible ambiguity.

Recordsets(0)Recordsets("name")Recordsets![name]

The Recordsets collection has two properties and one method, which are shown in Table 8-1.

Table 8-1: Members of the Recordsets Collection

Type

Name

Description

Property

Count

Indicates the number of Recordset objects in the Recordsets
collection

Property

Item

Retrieves a Recordset object either by its index in the collection or by its name

Method

Refresh

A nonfunctional method

The Recordset object has 32 properties (shown in Table 8-2) and 24 methods (listed in Table 8-3). It also has two collections: the Fields collection, a collection of the individual fields in the recordset; and the Properties collection, a collection of the individual properties supported by the Recordset object.

Table 8-2: Recordset Object Properties

Property

Description

AbsolutePosition

The relative position of the current record

BatchCollisionCount

Number of records that did not complete the last batch update

BatchCollisions

Array of bookmarks representing rows that had a collision during the last batch update

BatchSize

For batch updates, the number of statements to send back to the server in each batch

BOF

Flag indicating whether the record pointer is at the beginning of the file

Bookmark

Value that uniquely identifies a particular record in the recordset

Bookmarkable

Indicates whether a recordset supports bookmarks

CacheSize

Determines the number of records from an ODBC data source that will be cached locally

CacheStart

The bookmark of the first record to be cached locally

Connection

The Connection object that owns the recordset

DateCreated

Date and time the recordset was created

EditMode

Indicates the recordset's editing state

EOF

Flag indicating whether the record pointer is at the end of the file

Filter

Expression that filters records from the recordset

Index

Name of the current index

LastModified

Bookmark indicating the most recently modified record

LastUpdated

Date and time the recordset was last updated

LockEdits

The type of locking in effect when editing

Name

The name of the Recordset object

NoMatch

Flag indicating whether a search was successful

PercentPosition

Relative position of the current record in the recordset

RecordCount

Number of records in the recordset

RecordStatus

The update status of the current record in the next batch update

Restartable

Indicates whether a recordset supports the Requery method

Sort

Expression defining the sort order of records

StillExecuting

Indicates whether an asynchronous operation has finished executing

Transactions

Indicates whether the recordset supports transactions

Type

The recordset (or cursor) type

Updatable

Indicates whether the recordset can be updated

UpdateOptions

Indicates how the SQL WHERE clause is constructed for each record during a batch update and whether the update should use an UPDATE statement or a DELETE followed by an INSERT

ValidationRule

Defines a validation rule used to validate data as it is changed

ValidationText

Text displayed when a record fails to meet the validation criteria

Table 8-3: Recordset Object Methods

Method

Description

AddNew

Adds a new record to an updatable recordset

Cancel

Cancels execution of a pending asynchronous method call

CancelUpdate

Cancels any pending updates

Clone

Creates a duplicate Recordset object

Close

Closes the recordset

CopyQueryDef

Returns a copy of the QueryDef object originally used to create the recordset

Delete

Deletes the current record

Edit

Prepares a record for editing

FillCache

Fills all or part of a recordset's local cache

FindFirst

Finds the first record that meets designated criteria

FindLast

Finds the last record that meets designated criteria

FindNext

Finds the next record that meets designated criteria

FindPrevious

Finds the previous record that meets designated criteria

GetRows

Retrieves rows into a two-dimensional array

Move

Moves the record pointer either forward or backward

MoveFirst

Moves to the first record of the recordset

MoveLast

Moves to the last record of the recordset

MoveNext

Moves to the next record of the recordset

MovePrevious

Moves to the previous record of the recordset

NextRecordset

Retrieves the next set of records returned by a multipart SELECT query

OpenRecordset

Creates a new recordset

Requery

Reissues the query that created the recordset

Seek

Locates a record that meets the criteria based on the current index

Update

Saves changes to a record

Access to the Recordset Object

Creatable
No

Returned by
The OpenRecordset method of the Connection object
The Recordsets property of the Connection object
The OpenRecordset method of the Database object
The Recordsets property of the Database object
The Clone method of the Recordset object
The OpenRecordset method of the Recordset object
The OpenRecordset method of the TableDef object

Recordsets Collection Properties

Count

Data Type

Integer

Description

Indicates the number of recordsets in the Recordsets collection. See the code sample in the introduction to this chapter for an example of its usage. As far as I can see, there is little (if any) practical use for this property.

Item

Recordsets.Item(Index)

Argument

Data Type

Description

Index

Integer

The ordinal position of the Recordset object in the Recordsets collection, or a string containing the name of the Recordset object to be retrieved from the collection

Data Type

Recordset object

Description

Retrieves a particular Recordset object from the Recordsets collection. A Recordset object can be retrieved either based on its ordinal position in the collection or based on its name. (But see the Name section later in this chapter for the reasons why it is unwise to reference a recordset based on its name.) Mostly, recordsets are manipulated by means of the variable used to set them, since this is the best way to assure that you are working with the correct recordset.

Recordsets Collection Methods

Refresh
Recordsets.Refresh

Although the documentation lists Refresh as a method of the Recordsets object in Help and the Object Browser, actually this method is inapplicable to the Recordset object, since Refresh applies only to persistent objects. (Since recordsets exist only in memory, the Recordsets collection is not a collection of persistent objects.) Calling the method, however, does not generate an error; it simply has no effect.

Recordset Object Properties

Table 8-4 summarizes which properties apply to each type of Recordset object and whether the property setting is read/write (RW) or read-only (RO) for Jet ( J) and ODBCDirect (O) databases, or for both Jet and ODBCDirect workspaces ( JO). A blank cell indicates that the property does not apply to either type of workspace. In cases where the property is always read-only with a value of False, that is indicated by an F in the cell.

Table 8-4: Recordset Property Summary

Property

Table

Dynaset

Snapshot

Forward-Only

Dynamic

AbsolutePosition

RW

RW

RW

JO

JO

O

BatchCollisionCount

RO

RO

RO

RO

O

O

O

O

BatchCollisions

RO

RO

RO

RO

O

O

O

O

BatchSize

RW

RW

RW

RW

O

O

O

O

BOF

RO

RO

RO

RO

RO

J

JO

JO

JO

O

Bookmark

RW

RW

RW

RW

J

JO

JO

O

Bookmarkable

RO

RO

RO

RO

J

JO

JO

O

CacheSize

RW/RO

RO

RO

J/O

O

O

CacheStart

RW

J

Connection

RW

RW

RW

RW

O

O

O

O

DateCreated

RO

J

EditMode

RO

RO

RO

RO

RO

J

JO

JO

JO

O

EOF

RO

RO

RO

RO

RO

J

JO

JO

JO

O

Filter

RW

RW

RW

J

J

J

Index

RW

J

LastModified

RO

RO

RO

RO

J

JO

O[1]

O

LastUpdated

RO

J

LockEdits

RW

RW/RO

RW/RO

RW

RO

J

J/O

J/O

J

O

Name

RO

RO

RO

RO

RO

J

JO

JO

JO

O

NoMatch

RO

RO

RO

J

J

J

PercentPosition

RW

RW

RW

RW

J

JO

JO

O

RecordCount

RO

RO

RO

RO

RO

J

JO

JO

JO

O

RecordStatus

RO

RO

RO

RO

O

O

O

O

Restartable

F

RO

RO

RO

RO

J

JO

JO

JO

O

Sort

RW

RW

J

J

StillExecuting

RO

RO

RO

RO

O

O

O

O

Transactions

RO

RO

RO (F)

RO (F)

J

J

J

J

Type

RO

RO

RO

RO

RO

J

JO

JO

JO

O

Updatable

RO

RO

F/RO

F/RO

RO

J

JO

J/Oa

J/Oa

O

UpdateOptions

RW

RW

RW

RW

O

O

O

O

ValidationRule

RO

RO

RO

RO

J

J

J

J

ValidationText

RO

RO

RO

RO

J

J

J

J

AbsolutePosition



Data Type

Long

Description

This misleadingly named property sets or returns the relative record number of a recordset's current record. It is a zero-based number corresponding to the ordinal position of the current record in the recordset, ranging from zero to one less than the record count. If there is no current record (for example, for an empty recordset), AbsolutePosition returns -1.

TIP:

Despite the "Absolute" in the property name, this property is not stable and certainly is not a record number. It changes every time records are added to or deleted from a recordset. Use the Bookmark property to set a variable you can use to return to a particular record after moving the record pointer by a search or requerying.

VBA Code

This code displays the ordinal number of the record in a recordset while iterating through it:

Private Sub cmdAbsolutePosition_Click()    Dim dbs As Database   Dim strDBName As String   Dim rst As Recordset      strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset("Employees", dbOpenSnapshot)   With rst      .MoveFirst      Do While Not .EOF         Debug.Print !LastName & " record--No. " & .AbsolutePosition + 1         .MoveNext      Loop      .Close   End With   dbs.Close End Sub 
BatchCollisionCount

Data Type

Long

Description

For ODBCDirect workspaces only, this property returns the number of records that did not complete in the last batch update. It corresponds to the number of Bookmarks in the BatchCollisions property.

BatchCollisions

Data Type

Variant Array

Description

For ODBCDirect workspaces only, this property returns a variant containing an array of bookmarks, representing rows that had a collision during the last batch Update call. The number of elements in the array can be determined by retrieving the value of the BatchCollisionCount property.

BatchSize

Data Type

Long

Description

For ODBCDirect workspaces only, this property sets or returns the number of statements sent back to the server in each batch. The default value is 15. Setting BatchSize to 1 causes each statement to be sent separately; you might do this when working with those database servers that don't support batch updates.

BOF

Data Type

Boolean

Description

The BOF property (the name is derived from "Beginning of File") indicates that the current record position is before the first record in a recordset. It is useful for determining whether you have gone beyond the beginning of the records in a recordset when moving backward. In a recordset with no objects, this property is True. However, if you delete the last remaining record in a recordset, BOF may remain False until you attempt to reposition the record pointer. See Table 8-5 for a summary of what happens when you use the Move methods with different combinations of the BOF and EOF properties.

Table 8-5: The Move Methods with BOF and EOF

BOF/EOF

MoveFirst,
MoveLast

MovePrevious,
Move <>

Move 0

MoveNext,
Move > 0

BOF=True, EOF=False

Allowed

Error

Error

Allowed

BOF=False, EOF=True

Allowed

Allowed

Error

Error

Both True

Error

Error

Error

Error

Both False

Allowed

Allowed

Allowed

Allowed

Table 8-6 shows what happens to the BOF and EOF properties after using Move methods that don't find a record.

Table 8-6: When Move Methods Don't Find a Record

BOF

EOF

MoveFirst, MoveLast

True

True

Move 0

No change

No change

MovePrevious, Move <>

True

No change

MoveNext, Move > 0

No change

True

VBA Code

This code uses the BOF marker to prevent going beyond the first record when iterating backward through a recordset:

Private Sub cmdBOF_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String   Dim fld As Field      strTable = "Categories"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenTable)   With rst      .MoveLast      Do While Not .BOF         Debug.Print !CategoryName         .MovePrevious      Loop      .Close   End With   End Sub
Bookmark

Data Type

Variant array of Byte data

Description

Uniquely identifies the current record in a recordset. By retrieving the value of a record's Bookmark property, you can later return the record pointer to that record. It is the closest thing Access has to a record number. You can use bookmarks on recordsets whose Bookmarkable property is True, which is always the case for recordsets based entirely on Jet tables. For recordsets based on other databases, Bookmarkable may not be True, in which case you can't use bookmarks.

VBA Code

See the code sample in the Requery section for an example of using the Bookmark property to return to the same record after requerying; the following code sample shows another way the Bookmark property can be useful in returning to the previous record after a failed search:

Private Sub cmdBookmark_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String   Dim varBookmark As Variant      strTable = "Categories"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenTable)   With rst      If .Bookmarkable = False Then         MsgBox "This recordset is not bookmarkable -- exiting!"         Exit Sub      Else         MsgBox "This recordset is bookmarkable -- continuing!"      End If      varBookmark = .Bookmark      .Index = "PrimaryKey"      .Seek "=", 5      If .NoMatch Then .Bookmark = varBookmark      Debug.Print !CategoryName      .Close   End With End Sub
Bookmarkable

Data Type

Boolean

Description

The Bookmarkable property indicates whether you can use bookmarks in a recordset. If you are not sure that the tables underlying a recordset are all Jet tables, you can check this property before attempting to use bookmarks. See the Bookmark section for an example of its usage.

CacheSize

Data Type

Long

Description

Sets or returns the number of records retrieved from an ODBC data source that will be cached locally. The value must be between 5 and 1200, but it can't be greater than available memory permits. Setting CacheSize to 0 turns off caching. Using a cache can improve performance, since retrieving data from a local cache is faster than retrieving it from the server.

CacheStart

Data Type

String

Description

The CacheStart property (used in conjunction with CacheSize and FillCache) sets or returns a value that specifies the bookmark of the first record in a dynaset-type recordset containing the data to be locally cached from an ODBC data source in a Jet workspace.

Connection

Data Type

Connection Object

Description

Sets or returns the Connection object that owns the recordset, for ODBCDirect workspaces only.

DateCreated

Data Type

Date/Time

Description

Returns the date and time the recordset was created. Note that this is usually different than the date the underlying table was created.

VBA Code

Private Sub cmdDateCreated_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String      strTable = "Categories"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenTable)   Debug.Print rst.Name & " recordset created on " & rst.DateCreated   End Sub
EditMode

Data Type

Long

Description

Indicates the state of editing, as listed in Table 8-7.

Table 8-7: The EditMode Property Settings

Named Constant

Value

Description

dbEditNone

0

No editing operation is in progress.

dbEditInProgress

1

The Edit method has been invoked, and the current record is in the copy buffer.

dbEditAdd

2

The AddNew method has been invoked, and the current record in the copy buffer is a new record that hasn't been saved in the database.

The value of the EditMode property can be useful in determining whether you should use the Update or CancelUpdate method when editing is interrupted. The following code sample shows the EditMode value for various stages of editing records.

VBA Code

Private Sub cmdEditMode_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String      strTable = "Categories"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenTable)      With rst      .Move 3      Debug.Print "EditMode before editing: " & .EditMode      .Edit      Debug.Print "EditMode after Edit : " & .EditMode      !Description = "New description of this category"      .Update      Debug.Print "EditMode after updating: " & .EditMode      .AddNew      Debug.Print "EditMode after AddNew: " & .EditMode      .CancelUpdate      Debug.Print "EditMode after canceling editing: " & .EditMode      .Close   End With End Sub 
EOF

Data Type

Boolean

Description

The EOF property (derived from "End of File") indicates that the current record position is after the last record in a recordset. It is useful for determining whether you have gone beyond the end of the records in a recordset when moving forward. In a recordset with no objects, this property is True. However, if you delete the last remaining record in a recordset, EOF may remain False until you attempt to reposition the record. See Table 8-5 in the BOF section for a summary of what happens when you use the Move methods with different combinations of the BOF and EOF properties, and Table 8-6 for a listing of what happens to the BOF and EOF properties after using Move methods that don't find a record.

VBA Code

This code uses the EOF marker to prevent going beyond the last record when iterating through a recordset:

Private Sub cmdEOF_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String   Dim fld As Field      strTable = "Categories"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenTable)   With rst      Do While Not .EOF         Debug.Print !CategoryName         .MoveNext      Loop      .Close   End With   End Sub
Filter

Data Type

String

Description

Sets or returns a value that filters the records in a recordset (for Jet workspaces only). Basically, it is the WHERE clause of a SQL statement without the word WHERE. You can use Filter with dynaset-, snapshot-, or forward-only-type recordsets.

TIP:

After using the Filter property with a recordset, you don't see the results of filtering immediately--you must open another recordset from the filtered recordset to see the results.

VBA Code

This code sample illustrates using the Filter property to filter records by country, opening a second recordset of UK employees based on the original, unfiltered recordset:

Private Sub cmdFilter_Click()    Dim dbs As Database   Dim strDBName As String   Dim rstEmployees As Recordset   Dim rstUKEmployees As Recordset   Dim strSearch As String      strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rstEmployees = dbs.OpenRecordset("Employees", dbOpenDynaset)      'Create a filtered recordset based on the first recordset   rstEmployees.Filter = "Country = 'UK'"   Set rstUKEmployees = rstEmployees.OpenRecordset()    With rstUKEmployees      Debug.Print vbCrLf & "Filtered recordset:"      Do While Not .EOF         Debug.Print "Name: " & !LastName & ", country: " & !Country         .MoveNext      Loop   End With End Sub

TIP:

Using the Filter property on a recordset is generally less efficient than just applying a filter to a recordset and opening it in one step, using a SQL statement with a WHERE clause.

Index



Data Type

String

Description

Sets or returns the name of the index to use for a table-type recordset in a Jet workspace. It must be the name of an existing index in the Indexes collection of the TableDef object that is the data source of the Recordset object. The Index property is used with the Seek method for locating records in an indexed recordset. See the Seek section later in this chapter for an example of usage.

LastModified

Data Type

Variant array of Byte data

Description

Returns a bookmark indicating which record in a recordset was most recently added or modified. It applies to table-type or dynaset-type recordsets only. The primary use of this property is to return to the record that was most recently modified in code by setting the Bookmark property equal to LastModified.

TIP:

The value of LastModified only reflects changes made to the recordset itself; if a record was changed in the interface or directly in the table, this change is not reflected in the LastModified property.

VBA Code

This code loops through tblCustomers (a copy of the Northwind Customers table), modifying records that meet a criterion, and then returns to the last modified record. I'm using the RecordCount property (-1) to avoid being at the EOF marker after looping; otherwise, there would be an error on the first Debug.Print line:

Private Sub cmdLastModified_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strTable As String   Dim intCount As Integer   Dim i As Integer      strTable = "tblCustomers"   Set dbs = CurrentDb   Set rst = dbs.OpenRecordset(strTable, dbOpenTable)   intCount = rst.RecordCount - 1      With rst      For i = 1 To intCount         If !Country = "UK" Then            .Edit            !Country = "United Kingdom"            .Update            Debug.Print "Changed " & !CompanyName & " record"         End If         .MoveNext      Next i            Debug.Print "After looping, at " & !CompanyName & " record"      'Go to most recently modified record      .Bookmark = .LastModified      Debug.Print "Last record modified: " & !CompanyName & " record"      .Close   End With End Sub
LastUpdated

Data Type

Date/Time

Description

Returns the date and time the recordset was last updated--in other words, when the data in the base table(s) was last changed. The changes can be made either in the interface or in code (unlike the LastModified property).

VBA Code

Private Sub cmdLastUpdated_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String      strTable = "Categories"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenTable)   Debug.Print "Date Created: " & rst.DateCreated   Debug.Print "Last Updated: " & rst.LastUpdated End Sub
LockEdits

Data Type

Boolean

Description

For updatable recordsets the LockEdits property sets or returns a value indicating the type of locking in effect while editing, as shown in Table 8-8. Pessimistic locking (True) means that the page containing the record being edited is unavailable to other users until you are through editing and use the Update method to save the record. Optimistic locking (False) means that other users can access the same record you are working on, except just briefly while you are actually updating the record. Optimistic locking is more risky (two users can simultaneously change a record), but pessimistic locking may cause delays while records are unnecessarily locked.

Table 8-8: The LockEdits Values/Settings

Named Constant

Value

Description

True

-1

(Default) Pessimistic locking is in effect. The 2K page containing the record you're editing is locked as soon as you call the Edit method.

False

0

Optimistic locking is in effect for editing. The 2K page containing the record is not locked until the Update method is executed.

TIP:

The LockEdits value can be preset by setting the lockedit argument of the OpenRecordset method; setting the lockedit argument to dbPessimistic sets the LockEdits property to True, and setting it to any other value sets LockEdits to False. When working with ODBC data sources, LockEdits is always set to False, allowing only optimistic locking.

Name

Data Type

String

Description

For recordsets, the Name property is either the name of the underlying table or query, or, if the recordset is based on a SQL statement, the first 256 characters of the SQL statement. This makes the Name property unreliable as a means of referencing a particular recordset. To reference a recordset, just use the variable it was set with.

VBA Code

The code lists the names of several recordsets created based on a table, a query, and a SQL statement:

Private Sub cmdName_Click()    Dim dbs As Database   Dim rstTable As Recordset   Dim rstQuery As Recordset   Dim rstSQL As Recordset   Dim rst As Recordset   Dim strDBName As String   Dim intCount As Integer   Dim strTable As String   Dim strQuery As String   Dim strSQL As String    strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   strTable = "Orders"   strQuery = "Ten Most Expensive Products"   strSQL = "SELECT * FROM Customers"   Set rstTable = dbs.OpenRecordset(strTable, dbOpenTable)   Set rstSQL = dbs.OpenRecordset(strSQL, dbOpenSnapshot)   Set rstQuery = dbs.OpenRecordset(strQuery, dbOpenSnapshot)      For Each rst In dbs.Recordsets      Debug.Print rst.Name   Next rst End Sub
NoMatch

Data Type

Boolean

Description

Indicates whether a search was successful. It applies to searches done with the Seek method or one of the Find methods.

If a search is unsuccessful (NoMatch = True), the current record will no longer be valid. To avoid problems, save the record's bookmark to a variable so you can return to it after an unsuccessful search, as in the code sample in the Seek section.

PercentPosition

Data Type

Single

Description

Sets or returns a value between 0 and 100, representing the position of the current record in a recordset. For dynaset- or snapshot-type recordsets, move to the last record before using this method to ensure an accurate record count. The following code prints the percent position to the Debug window after each successful find of a record meeting a search criterion.

TIP:

You can use Percent Position with a scroll bar control on a form or text box to indicate the position of the current record in a recordset.

VBA Code

Private Sub cmdPercentPosition_Click()    Dim dbs As Database   Dim strDBName As String   Dim rst As Recordset   Dim strSearch As String      strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset("Employees", dbOpenSnapshot)   strSearch = "[Title] = 'Sales Rep'"      'MoveLast to ensure an accurate count of records.   With rst      .MoveLast      .MoveFirst      .FindFirst strSearch      Debug.Print !LastName & " record -- " & .PercentPosition & "%"      .FindNext strSearch      Debug.Print !LastName & " record -- " & .PercentPosition & "%"      .Close   End With   dbs.Close End Sub
RecordCount

Data Type

Long

Description

Returns the number of records in a recordset. In case of dynaset-, snapshot-, or forward-only-type recordsets, you need to access all the records in the recordset before getting an accurate count of the records. See the following code sample for an example of usage of RecordCount for this purpose. This is not necessary for table-type recordsets.

VBA Code

Private Sub cmdRecordCount_Click()    Dim dbs As Database   Dim strDBName As String   Dim rst As Recordset   Dim intCount As Integer      strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset("Employees", dbOpenSnapshot)      Debug.Print "Record count before traversing recordset: " & _               rst.RecordCount      'MoveLast to ensure an accurate count of records.   rst.MoveLast      Debug.Print "Record count after traversing recordset: " & _               rst.RecordCount   rst.Close   dbs.Close End Sub
RecordStatus

Data Type

Long

Description

Indicates the update status of the current record, if it is part of a batch update (for ODBCDirect workspaces only). The value returned indicates whether (and how) the current record will be involved in the next optimistic batch update. See Table 8-9 for a listing of the constants that may be returned.

Table 8-9: The RecordStatus Return Value Intrinsic Constants

Named Constant

Value

Description

dbRecordUnmodified

0

(Default) The record has not been modified or has been updated successfully.

dbRecordModified

1

The record has been modified and not updated in the database.

dbRecordNew

2

The record has been inserted locally with the AddNew method, but not yet inserted into the database.

dbRecordDeleted

3

The record has been deleted locally, but not yet deleted in the database.

dbRecordDBDeleted

4

The record has been deleted locally and in the database.

Restartable

Data Type

Boolean

Description

Indicates whether a recordset supports the Requery method. If the value is True, Requery can be used to re-execute the query on which the recordset is based; if it is False, the query can't be re-executed.

VBA Code

The following code opens three different types of recordsets, examines the Restartable property of each, and requeries those that are restartable:

Private Sub cmdRestartable_Click()    Dim dbs As Database   Dim rstTable As Recordset   Dim rstQuery As Recordset   Dim rstSQL As Recordset   Dim rst As Recordset   Dim strDBName As String   Dim intCount As Integer   Dim strTable As String   Dim strQuery As String   Dim strSQL As String    strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   strTable = "Orders"   strQuery = "Ten Most Expensive Products"   strSQL = "SELECT * FROM Customers"   Set rstTable = dbs.OpenRecordset(strTable, dbOpenTable)   Set rstSQL = dbs.OpenRecordset(strSQL, dbOpenSnapshot)   Set rstQuery = dbs.OpenRecordset(strQuery, dbOpenSnapshot)      'Determine whether each recordset is restartable,   'and requery it if so.   For Each rst In dbs.Recordsets      Debug.Print rst.Name & " restartable? " & rst.Restartable      If rst.Restartable = True Then rst.Requery   Next rst   End Sub
Sort

Data Type

String

Description

Sets or returns the sort order for records in a recordset (for Jet workspaces only). Basically, it is the ORDER BY clause of a SQL statement without the phrase ORDER BY. You can use Sort with dynaset- and snapshot-type recordsets only. As with the Filter property, the Sort property only takes effect when a new recordset is created from the sorted recordset. The Sort property overrides any sort order that might be specified for a QueryDef on which a recordset is based.

TIP:

Using the Sort property on a recordset is generally less efficient than just applying a sort order to a recordset and opening it in one step, using a SQL statement with an ORDER BY clause.

VBA Code

The following code applies a Sort order to a recordset and then opens a second recordset based on the sorted original recordset:

Private Sub cmdSort_Click()    Dim dbs As Database   Dim strDBName As String   Dim rst As Recordset   Dim rstSort As Recordset      strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset("Employees", dbOpenDynaset)   rst.Sort = "Region"   Set rstSort = rst.OpenRecordset      With rstSort       Do Until .EOF           Debug.Print "State: " & !Region & " for "; !LastName           .MoveNext       Loop   End With End Sub
StillExecuting

Data Type

Boolean

Description

For ODBCDirect workspaces only, indicates whether an asynchronous operation (one called with the dbRunAsync option) has finished executing. The return value is True if the query is still executing and False if it has finished executing. The Cancel method can be called to cancel execution if the value is True.

Transactions

Data Type

Boolean

Description

This property is True if the recordset supports transactions, and False if it does not. For ODBC workspaces the Transactions property indicates whether the ODBC driver supports transactions. The property can be used for dynaset- or table-type recordsets in Jet workspaces; for snapshot- and forward-only-type recordsets in Jet workspaces, it is always False. For dynaset- or table-type recordsets in Jet workspaces, the Transactions property is always True, indicating that you can use transactions.

TIP:

You should always check the Transactions property and make sure it returns True before working with transactions using the BeginTrans, CommitTrans, and Rollback methods.

VBA Code

This code creates a recordset from the QueryDefs in Northwind and lists the Transactions value for each one:

Private Sub cmdTransactions_Click()    Dim dbs As Database   Dim strDBName As String   Dim qdf As QueryDef   Dim rst As Recordset      strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)      Debug.Print "QueryDefs in " & dbs.Name   For Each qdf In dbs.QueryDefs      On Error Resume Next      Set rst = dbs.OpenRecordset(qdf.Name)      Debug.Print "Recordset name and type: " & rst.Name & vbTab & _                  rst.Type      Debug.Print "Transactions possible?: " & rst.Transactions   Next qdf   dbs.Close  End Sub
Type

Data Type

Integer

Description

Indicates the recordset type of a Recordset object. The possible values are listed in Table 8-10.

Table 8-10: The Type Setting Return Values Intrinsic Constants

Named Constant

Value

Description

dbOpenTable

1

Table ( Jet workspaces only)

dbOpenDynamic

16

Dynamic (ODBC workspaces only)

dbOpenDynaset

2

Dynaset

dbOpenSnapshot

4

Snapshot

dbOpenForwardOnly

96

Forward-only

Using the Type property on recordsets can be useful when you don't know what type the recordset is. Note that the recordset type is not the same as the QueryDef type. There are many more QueryDef type constants than Recordset constants, and the available constants are different for the two types of objects.

VBA Code

The following code sample lists the recordset type of recordsets based on all the queries in Northwind:

Private Sub cmdType_Click()    Dim dbs As Database   Dim strDBName As String   Dim qdf As QueryDef   Dim rst As Recordset      strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)      Debug.Print "QueryDefs in " & dbs.Name   For Each qdf In dbs.QueryDefs      Debug.Print "Query name and type: " & qdf.Name & vbTab & qdf.Type      Set rst = dbs.OpenRecordset(qdf.Name)      Debug.Print "Recordset name and type: " & rst.Name & vbTab & _                  rst.Type   Next qdf   dbs.Close End Sub
Updatable

Data Type

Boolean

Description

Indicates whether a recordset can be changed or updated. If it is True, the recordset can be updated; if it is False, it can't be updated.

VBA Code

This code creates recordsets from all the Northwind queries and reports on whether they are updatable:

Private Sub cmdUpdatable_Click()    Dim dbs As Database   Dim strDBName As String   Dim qdf As QueryDef   Dim rst As Recordset      strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)      Debug.Print "QueryDefs in " & dbs.Name   For Each qdf In dbs.QueryDefs      On Error Resume Next      Set rst = dbs.OpenRecordset(qdf.Name)      Debug.Print "Recordset name and type: " & rst.Name & vbTab & _                  rst.Type      Debug.Print "Recordset updatable?: " & rst.Updatable   Next qdf   dbs.Close   End Sub
UpdateOptions

Data Type

Long

Description

Indicates how the WHERE clause is constructed for each record during a batch update and whether the update should use an UPDATE statement or a DELETE followed by an INSERT (for ODBCDirect workspaces only). The UpdateOptions value can be any of the constants in Table 8-11.

Table 8-11: The UpdateOptions Return Value/Settings Intrinsic Constants

Named Constant

Value

Description

dbCriteriaKey

1

(Default) Uses just the key column(s) in the where clause.

dbCriteriaModValues

2

Uses the key column(s) and all updated columns in the where clause.

dbCriteriaAllCols

4

Uses the key column(s) and all the columns in the where clause.

dbCriteriaTimeStamp

8

Uses just the timestamp column if available (will generate a run-time error if no timestamp column is in the result set).

dbCriteriaDeleteInsert

16

Uses a set of DELETE and INSERT statements for each modified row.

dbCriteriaUpdate

32

(Default) Uses an UPDATE statement for each modified row.

ValidationRule

Data Type

String

Description

Returns a value used to validate data as it is being changed or added to a field in a recordset's underlying data source table. It only applies to Jet workspaces. The ValidationRule phrase describes a comparison in the form of a SQL WHERE clause without the WHERE keyword. If the data does not meet the validation criteria, a trappable run-time error is generated, and the error message contains the text of the ValidationText property, if specified, or else the text of the expression specified by the ValidationRule property. See the ValidationRule section in Chapter 10, TableDefs Collection and TableDef Object, for more information on this property.

TIP:

ValidationRule comparison strings are limited to referencing the field; they can't contain references to user-defined functions or queries.

VBA Code

This code lists the fields in the Northwind Customers table and their validation rules and validation text, if any:

Private Sub cmdValidationRule_Click()      Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String   Dim fld As Field      strTable = "Employees"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenTable)   With rst      .MoveLast      For Each fld In .Fields         Debug.Print fld.Name         If fld.ValidationRule <> "" Then            Debug.Print "Validation Rule: " & fld.ValidationRule            Debug.Print "Validation Text: " & fld.ValidationText         End If      Next fld      .Close   End With End Sub
ValidationText

Data Type

String

Description

The ValidationText property returns a value specifying the text of the message that appears when data for a field fails the validation rule specified by the ValidationRule property. It applies only to Jet workspaces. See the ValidationText section in Chapter 10 for more information on this property. See the code sample in the ValidationRule section for an example of usage of this property.

Recordset Object Methods

Table 8-12 summarizes the Recordset type supported by each method and whether it applies to Jet ( J) or ODBCDirect (O) workspaces, or both ( JO). A blank cell indicates that the property does not apply to either type of workspace.

Table 8-12: Recordset Method Summary

Method

Table

Dynaset

Snapshot

Forward-Only

Dynamic

AddNew

J

JO

O[2]

O

O

Cancel

O

O

O

O

CancelUpdate

J

JO

Oa

O

O

Clone

J

J

J

Close

J

JO

JO

JO

O

CopyQueryDef

J

J

J

Delete

J

JO

Oa

O

O

Edit

J

JO

Oa

O

O

FillCache

J

FindFirst

J

J

FindLast

J

J

FindNext

J

J

FindPrevious

J

J

GetRows

J

JO

JO

JO

O

Move

J

JO

JO

[3]

O

MoveFirst

J

JO

JO

O

MoveLast

J

JO

JO

O

MoveNext

J

JO

JO

JO

O

MovePrevious

J

JO

JO

O

NextRecordset

O

O

O

O

OpenRecordset

J

J

J

Requery

JO

JO

JO

O

Seek

J

Update

J

JO

Oa

O

O

The recordset types and their uses are listed in Table 8-13.

Table 8-13: Recordset Types and Their Uses

Recordset Type

Usage

Table

Represents a single base table. Supports the AddNew, Delete, and Seek methods, but not the Find* methods. ( Jet only.)

Dynamic

Represents one or more base tables. Supports the AddNew and Delete methods, but not the Find* or Seek methods.

Dynaset

Represents a table or an updatable query. Supports the AddNew, Delete, and Find* methods, but not the Seek method.

Snapshot

A read-only recordset; useful for finding data or printing. Does not allow updating, except in the case of an updatable Snapshot in an ODBCDirect workspace. Supports the Find* methods.

Forward-only

Similar to a snapshot, but only allows forward movement. Useful when you only need to make a single pass through a recordset. Does not support the Find* methods.

AddNew


recordset.AddNew

Adds a new record to an updatable recordset (table-type or dynaset recordsets only). For dynasets the new records are added at the end of the recordset. For indexed dynasets, the new record is placed in indexed order; if the dynaset is not indexed, the new record is added to the end of the recordset.

TIP:

Don't confuse AddNew and Append. The DAO AddNew method is the equivalent of Append in other database languages, such as dBASE, while the Append method in DAO is used to add new members to collections.

After adding a new record with the AddNew method, you need to use the Update method to save the new record, as in the following code sample. If you omit the Update, you won't get a warning, and the new record will be lost when you move to another record or close the recordset.

Note that in VBA code, you should use the dot (.) operator for recordset methods and properties, and the bang (!) operator for fields. In VBS code use the dot operator for methods, properties, and fields.

TIP:

If you get an "Item not found in this collection" error message when updating a recordset, it is probably the result of a misspelled field name (fields are members of the Fields collection within the recordset).

VBA Code

This code first lists the categories in the Northwind Categories table, then adds a new record, then lists the categories again, showing the newly added one:

Private Sub cmdAddNew_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String    strTable = "Categories"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenTable)    'List categories before adding new record   Debug.Print "Categories before adding new record:" & vbCrLf   rst.MoveFirst   Do Until rst.EOF      Debug.Print rst!CategoryName      rst.MoveNext   Loop      'Add new category   With rst      .AddNew      !CategoryName = "Dried Foods"      !Description = _         "Freeze-dried and sun-dried fruits, vegetables, and meats"      .Update   End With      'List categories after adding new record   Debug.Print vbCrLf & "Categories after adding new record:" & vbCrLf   rst.MoveFirst   Do Until rst.EOF      Debug.Print rst!CategoryName      rst.MoveNext   Loop   rst.Close End Sub
Cancel
recordset.Cancel

Cancels execution of a pending asynchronous method call. It only applies to recordsets in ODBCDirect workspaces since it requires use of the dbRunAsync value for the MoveLast method's Options argument. See the StillExecuting section for an example that uses this method.

CancelUpdate
recordset.CancelUpdate updatetype

Argument

Data Type

Description

recordset

Recordset object

The Recordset object for which you are canceling pending updates

updatetype

Integer

A named constant or Integer value (see Table 8-14)

Cancels any pending updates for a Recordset object, such as would result from use of the Edit or AddNew methods. Before using the CancelUpdate method, you should check the EditMode property of the recordset to find out if there is a pending operation that can be canceled.

Table 8-14: The UpdateType Intrinsic Constants

Named Constant

Value

Description

dbUpdateRegular

1

(Default) Cancels pending changes that aren't cached

dbUpdateBatch

4

Cancels pending changes in the update cache

TIP:

The type argument settings in Table 8-14 can only be used if batch updating is enabled. In an ODBCDirect workspace (only), this is done by setting the DefaultCursorDriver property to dbUseClientBatchCursor when the connection is opened, and the recordset must be opened using OpenRecordset with the locktype argument set to dbOptimisticBatch .

VBA Code

This code illustrates the use of CancelUpdate to allow a user to confirm adding a new record to the Categories table in the Northwind database:

Private Sub cmdCancelUpdate_Click()    Dim dbs As Database   Dim strDBName As String   Dim rst As Recordset   Dim intReturn As Integer   Dim strCategory As String   Dim strDescription As String      strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset("Categories")   With rst      .AddNew      strCategory = "Test"      strDescription = "Test new food category"      !CategoryName = strCategory      !Description = strDescription      intReturn = MsgBox("Add " & strCategory & " -- " & _         strDescription & " as a food category?", vbYesNo)      If intReturn = VbYes Then         .Update         MsgBox strCategory & " -- " & strDescription & _            " added as a food category"      Else         .CancelUpdate         MsgBox strCategory & " -- " & strDescription & _            " not added as a food category"      End If   End With End Sub

Clone


Set duplicate = original.Clone

Argument

Data Type

Description

duplicate

Recordset object

The duplicate Recordset object being created

original

Recordset object

The original Recordset object being duplicated

Creates a duplicate Recordset object that references the original Recordset object. The original and duplicate recordsets can have different current records. (Note, though, that after the cloning operation, the duplicate recordset initially has no current record.) Using the Clone method allows you to share bookmarks between Recordset objects, since their bookmarks are interchangeable.

VBA Code

This code sets up a recordset based on the Northwind Categories table, then clones it, and moves to different records in the original and duplicate recordsets:

Private Sub cmdClone_Click()    Dim dbs As Database   Dim strDBName As String   Dim rstO As Recordset   Dim rstD As Recordset   Dim strSearch As String   Dim strText As String      strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rstO = dbs.OpenRecordset("Categories", dbOpenDynaset)   Set rstD = rstO.Clone   strText = "Dried Food"   strSearch = "[CategoryID] = 2"   rstO.FindFirst strSearch   strSearch = "[CategoryID] = 8"   rstD.FindFirst strSearch    'Report on where pointer is in the two recordsets.   Debug.Print "At "; rstO!CategoryName & " record in original recordset"   Debug.Print "At "; rstD!CategoryName & _               " record in duplicate recordset"   rstO.Close   rstD.Close   dbs.Close End Sub

Close


recordset.Close

Closes a recordset. You should always use this method to close a recordset before closing a database, because otherwise your pending edits and updates will be canceled.

TIP:

If you try to close a recordset that has already been closed, run-time error 3420, "Object invalid or no longer set," occurs.

See the code sample in the Clone section for an example of usage.

CopyQueryDef


Set querydef = recordset.CopyQueryDef

Argument

Data Type

Description

querydef

QueryDef object

The QueryDef object you want to create

recordset

Recordset object

The Recordset object you are creating

Returns a QueryDef object that is a copy of the QueryDef object originally used to create the Recordset object. A recordset must be created using the OpenRecordset method before using the CopyQueryDef method. This method can only be used in Jet workspaces. CopyQueryDef can be useful when you need to recreate a QueryDef from a recordset passed to a procedure.

WARNING:

An error occurs if you use this method on a recordset that was not based on a QueryDef.

VBA Code

The cmdCopyQueryDef_Click event procedure calls the CreateRecordset function, which sets a recordset variable, rst. (Note that the rst recordset variable is declared in the Declarations section of the module to make it public in scope.) When control returns to the event procedure, the CopyQueryDef method is used to recreate the QueryDef. The contents of one of the QueryDef's fields are then listed to the Debug window:

Private Function CreateRecordset()    Dim dbs As Database   Dim strDBName As String   Dim qdf As QueryDef      strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set qdf = dbs.QueryDefs("Sales by Category")   Set rst = qdf.OpenRecordset   End Function Private Sub cmdCopyQueryDef_Click()    Dim qdf As QueryDef   Call CreateRecordset   Set qdf = rst.CopyQueryDef      With rst      Do While Not .EOF         Debug.Print !CategoryName         .MoveNext      Loop      .Close   End With   End Sub

Delete


recordset.Delete

Deletes the current record from an updatable recordset. If the deleted record is in the primary table in a relationship set to permit cascading deletes, one or more records in the related table may also be deleted. The deleted record remains current (although it can't be edited or used) until you move to another record. It is not necessary to use Update after calling the Delete method.

TIP:

If you want to be able to undo deletions, you can use transactions and the Rollback method. Transactions are covered in Chapter 4, Workspaces Collection and Workspace Object .

VBA Code

This code goes to the last record in a recordset and deletes it:

Private Sub cmdDelete_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String   Dim intCount As Integer      strTable = "Categories"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenTable)   intCount = rst.RecordCount   Debug.Print intCount & " records in recordset"      With rst      .MoveLast      .Delete      intCount = .RecordCount      .Close   End With         Debug.Print intCount & " records in recordset (after delete)"   End Sub

Edit


recordset.Edit

The Edit method prepares a record in an updatable recordset for editing by placing it in a temporary copy buffer. Generally, you must use the Edit method before making any changes to a record; however, the AddNew and Delete methods are exceptions (no need to use Edit before using either of them). After making changes to a record, you need to use the Update method to save the record.

TIP:

You must have a current record in order to use the Edit method.

WARNING:

If you edit a record and don't use the Update method to save the changes, they will be lost without warning or an error message when you close the recordset or move to another record.

VBA Code

Private Sub cmdEdit_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String      strTable = "Categories"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenTable)      With rst      .MoveLast      Debug.Print "Description value before editing: " & !Description      .Edit      !Description = "New description of this category"      .Update      Debug.Print "Description value after editing: " & !Description      .Close   End With      End Sub

FillCache


recordset.FillCache rows, startbookmark

Argument

Data Type

Description

recordset

Recordset object

A Recordset object created from an ODBC data source, such as a TableDef representing a linked table.

rows

Integer

The number of rows to store in the cache (if omitted, the CacheSize property value is used).

startbookmark

String

The Bookmark specifying the record from which the cache is filled (if omitted, the CacheStart property setting is used).

For Jet-connected ODBC data sources only, this method fills all or part of a recordset's local cache. Caching can improve performance, as data can be retrieved faster from the local cache than from the remote data source.

VBA Code

The following VBA code compares the performance when iterating through a recordset based on a linked table, with or without caching. According to Help, performance should be better with caching, but when I ran this code with a table linked to Northwind, the time was actually slightly longer with caching.

Private Sub cmdFillCache_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strTable As String   Dim sngStart As Single   Dim sngEnd As Single   Dim sngNoCache As Single   Dim sngCache As Single   Dim intCount As Integer   Dim strTemp As String      'Set up a recordset based on a linked table.   strTable = "tblContacts"   Set dbs = CurrentDb   Set rst = dbs.OpenRecordset(strTable, dbOpenDynaset)         'Iterate through recordset and time the operation.   With rst      .MoveFirst      Do While Not .EOF         sngStart = Timer         strTemp = !LastName         .MoveNext      Loop         sngEnd = Timer      sngNoCache = sngEnd         'Display performance results.      Debug.Print "Without cache: " & Format(sngNoCache, "##0,000.000") _                  & " seconds"            'Cache the first 100 records and time the operation again.      intCount = 0      .MoveFirst      .CacheSize = 100      .FillCache      sngStart = Timer      .MoveFirst      Do While Not .EOF         strTemp = !LastName         intCount = intCount + 1         .MoveNext         If intCount Mod 100 = 0 Then            On Error Resume Next            .CacheStart = .Bookmark            .FillCache         End If      Loop         sngEnd = Timer      sngCache = sngEnd         'Display performance results.      Debug.Print "With cache: " & Format(sngCache, "##0,000.000") _                  & " seconds"      .Close   End With   End Sub

FindFirst


recordset.FindFirst criteria

Argument

Data Type

Description

recordset

Recordset object

An existing dynaset-type or snapshot-type Recordset object

criteria

String

A search string used to locate a record, similar to the WHERE clause in a SQL statement, but without the word WHERE

For Jet workspaces only, the FindFirst method locates the first record in a dynaset or snapshot-type recordset that meets the specified criteria and makes that record the current record. If no matching record is found, the NoMatch property is set to True, making this property useful in determining the success or failure of the FindFirst method, as shown in the following code sample.

TIP:

To locate a record in a table-type recordset, use the Seek method instead of the FindFirst method.

VBA Code

Private Sub cmdFindFirst_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String   Dim strSearch As String   Dim strName As String      strTable = "Employees"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenDynaset)   strName = Chr(39) & "Smith" & Chr(39)   strSearch = "[LastName] = " & strName   With rst      .FindFirst strSearch      Debug.Print strName & " found? " & Not .NoMatch      .Close   End With   End Sub

FindLast


recordset.FindLast criteria

Argument

Data Type

Description

recordset

Recordset object

An existing dynaset-type or snapshot-type Recordset object

criteria

String

A search string used to locate a record, similar to the WHERE clause in a SQL statement, but without the word WHERE

Similar to the FindFirst method, for Jet workspaces only, the FindLast method locates the last record in a dynaset or snapshot-type recordset that meets the specified criteria and makes that record the current record. If no matching record is found, the NoMatch property is set to True.

VBA Code

Private Sub cmdFindLast_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String   Dim strSearch As String   Dim strName As String      strTable = "Employees"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenDynaset)   strName = Chr(39) & "Davolio" & Chr(39)   strSearch = "[LastName] = " & strName   With rst      .FindLast strSearch      Debug.Print strName & " found? " & Not .NoMatch      .Close   End With   End Sub

FindNext


recordset.FindNext criteria

Argument

Data Type

Description

recordset

Recordset object

An existing dynaset-type or snapshot-type Recordset object

criteria

String

A search string used to locate a record, similar to the WHERE clause in a SQL statement, but without the word WHERE

For Jet workspaces only, the FindNext method locates the next record in a dynaset or snapshot-type recordset that meets the specified criteria and makes that record the current record. If no matching record is found, the NoMatch property is set to True, so you can use this property to tell whether the method was successful in locating another match, as shown in the following code sample.

VBA Code

Private Sub cmdFindNext_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String   Dim strSearch As String   Dim strTitle As String      strTable = "Employees"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenDynaset)   strTitle = Chr(39) & "Sales Representative" & Chr(39)   strSearch = "[Title] = " & strTitle   With rst      .FindFirst strSearch      If .NoMatch = False Then         Debug.Print "Found a match for " & strTitle & " -- name: " & _                     !LastName      End If      .FindNext strSearch      If .NoMatch = False Then         Debug.Print "Found another match for " & strTitle & "--name: " _                     & !LastName      End If      .Close   End With End Sub

FindPrevious


recordset.FindPrevious criteria

Argument

Data Type

Description

recordset

Recordset object

An existing dynaset-type or snapshot-type Recordset object

criteria

String

A search string used to locate a record, similar to the WHERE clause in a SQL statement, but without the word WHERE

FindPrevious works much like FindNext, except that it moves backward through the recordset instead of forward.

VBA Code

Private Sub cmdFindPrevious_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String   Dim strSearch As String   Dim strTitle As String      strTable = "Employees"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenDynaset)   strTitle = Chr(39) & "Sales Representative" & Chr(39)   strSearch = "[Title] = " & strTitle   With rst      .FindFirst strSearch      If .NoMatch = False Then         Debug.Print "Found a match for " & strTitle & " -- name: " _                     & !LastName      End If      .FindNext strSearch      If .NoMatch = False Then         Debug.Print "Found another match for " & strTitle & "--name: " _                     & !LastName      End If      .FindPrevious strSearch      If .NoMatch = False Then         Debug.Print "Went back to last match for " & strTitle & _                     " -- name: " & !LastName      End If      .Close   End With End Sub

GetRows


Set varArray = recordset.GetRows(numrows)

Argument

Data Type

Description

varArray

Variant

An array that stores the retrieved rows of data

recordset

Recordset object

A Recordset object

numrows

Variant

The number of rows to retrieve (if left blank, all available rows are retrieved)

Retrieves multiple rows from a Recordset object into a two-dimensional array. It is very useful for filling list boxes and combo boxes on Outlook forms or Office UserForms from Access tables since they can't be bound to tables or recordsets, unlike Access controls. See the VBS code sample and the second VBA sample for examples of this usage. If you want to retrieve just one field value from the array, you can specify the array element, as in the first VBA code sample (bear in mind that the array numbering is zero-based).

Access VBA Code

Private Sub cmdGetRows_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strTable As String   Dim strFieldValue As String   Dim varRecords As Variant   Dim intRecord As Integer   Dim intField As Integer      strTable = "Employees"   Set dbs = CurrentDb   Set rst = dbs.OpenRecordset(strTable, dbOpenSnapshot)   varRecords = rst.GetRows(10)   Debug.Print "Fourth field in fifth record: " & varRecords(5, 6)   End Sub

Outlook VBS Code

Sub cmdFillListBox_Click    Dim rst   Dim dao   Dim wks   Dim dbs   Dim strAccessDir   Dim objAccess   Dim CustomerArray(99, 2)    'Pick up path to Access database directory from Access SysCmd function.   Set objAccess = Item.Application.CreateObject("Access.Application")   strAccessDir = objAccess.SysCmd(9)   strDBName = strAccessDir & "Samples\Northwind.mdb"   objAccess.Quit    'Set up reference to Access database.   Set dao = Application.CreateObject("DAO.DBEngine.35")   Set wks = dao.Workspaces(0)   Set dbs = wks.OpenDatabase(strDBName)    'Retrieve Customer information from table.   Set rst = dbs.OpenRecordset("Customers")   Set ctl = Item.GetInspector.ModifiedFormPages("Message").Controls("lstCustomers")    ctl.ColumnCount = 3   ctl.ColumnWidths = "50; 150 pt; 75 pt"    'Assign Access data to an array of 3 columns and 100 rows.   CustomerArray(99, 2) = rst.GetRows(100)    ctl.Column() = CustomerArray(99, 2) End Sub

VBA Code Behind an Office UserForm

This code runs from the Initialize event of an Office UserForm, so that the lstCustomers listbox is filled with data from Northwind when the form is run. The UserForm could be run from Word 97 or 2000, Excel 97 or 2000, or Outlook 2000:

Private Sub UserForm_Initialize()    Dim dao As Object   Dim rst As Recordset   Dim wks As Workspace   Dim dbs As Database   Dim strDBName As String   Dim strAccessDir As String   Dim objAccess As New Access.Application   Dim CustomerArray(99, 2)   Dim ctl As ListBox      'Pick up path to Access database directory from Access SysCmd function.   strAccessDir = objAccess.SysCmd(9)   strDBName = strAccessDir & "Samples\Northwind.mdb"   objAccess.Quit    'Set up reference to Access database.   Set dao = CreateObject("DAO.DBEngine.35")   Set wks = dao.Workspaces(0)   Set dbs = wks.OpenDatabase(strDBName)    'Retrieve Customer information from table.   Set rst = dbs.OpenRecordset("Customers")   Set ctl = lstCustomers    ctl.ColumnCount = 3   ctl.ColumnWidths = "50; 150 pt; 75 pt"    'Assign Access data to an array of 3 columns and 100 rows.   CustomerArray(99, 2) = rst.GetRows(100)    ctl.Column() = CustomerArray(99, 2) End Sub

Move


recordset.Move rows, startbookmark

Argument

Data Type

Description

recordset

Recordset object

The Recordset object whose current record position is being moved.

rows

Long

The number of rows to move. If rows is greater than zero, the movement is forward; if it is negative, the movement is backward.

startbookmark

String

The Bookmark of the record to start movement from. If omitted, Move begins from the current record.

Moves the current position in a recordset, either forward or backward. If you are at the BOF marker and move backward or at the EOF marker and move forward, you will get an error. You will also get a run-time error if you try to use the Move method when either the BOF or EOF property is True. (See the BOF and EOF property sections for an explanation of these properties.)

VBA Code

This VBA code moves to the last record in a recordset, then back three records:

Private Sub cmdMove_Click()    Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String      strTable = "Employees"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenDynaset)   With rst      .MoveLast      .Move -3      Debug.Print "On " & !LastName & " record"      .Close   End With End Sub

MoveFirst


recordset.MoveFirst

Moves to the first record in a recordset and makes it the current record. It is often used before a loop that iterates through the records in a recordset to ensure that the loop starts with the first record, as in the code sample in the FillCache section.

WARNING:

If you have edited the current record, before moving to another record, be sure to save the changes with the Update method; otherwise, the changes will be lost with no warning.

MoveLast


recordset.MoveLast

Moves to the last record in a recordset and makes it the current record.

TIP:

For dynaset- or snapshot-type recordsets, you need to use the MoveLast method before counting the number of records in a recordset in order to get an accurate count.

VBA Code

Private Sub cmdMoveLast_Click()      Dim dbs As Database   Dim rst As Recordset   Dim strDBName As String   Dim strTable As String   Dim intCount As Integer      strTable = "Categories"   strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset(strTable, dbOpenDynaset)   intCount = rst.RecordCount   Debug.Print intCount & " records in recordset (before MoveLast)"         With rst      .MoveLast      intCount = .RecordCount      .Close   End With         Debug.Print intCount & " records in recordset (after MoveLast)" End Sub

MoveNext


recordset.MoveNext

Moves to the next record in a recordset and makes it the current record. It is often used in looping structures in code. See the FillCache section for an example of usage.

MovePrevious


recordset.MovePrevious

Moves to the previous record in a recordset and makes it the current record. Usage is similar to MoveNext, except for the direction of movement.

NextRecordset


Set boolean = recordset.NextRecordset

Argument

Data Type

Description

boolean

Boolean

True indicates that the next set of records is available in recordset; False indicates that there are no more records, and recordset is empty.

recordset

Recordset object

An existing Recordset object variable to which you want to return pending records.

This method gets the next set of records (if any) returned by a multipart select query in an OpenRecordset call. It returns a Boolean value indicating whether there are any more additional records pending. The method only applies to ODBCDirect workspaces.

OpenRecordset


Set recordset = object.OpenRecordset(name, type, options, lockedit)
Set recordset = object.OpenRecordset(type, options, lockedit)

Argument

Data Type

Description

recordset

Recordset object

The Recordset object to be opened.

object

Connection, Database, Recordset, QueryDef, or
TableDef object

The object from which the recordset is to be created.

source

String

The record source for the new Recordset object. May be a table name, a query name, or a SQL statement. For table-type Jet recordsets, only table names are allowable.

name

Integer

A named constant or Integer value defining the type of recordset to open (see Table 8-15).

options

Long

A named constant or Long value (see Table 8-16).

lockedit

Integer

A named constant or Integer value (see Table 8-17).

WARNING:

A saved query or SQL statement used for the source argument must be a query that returns records, not an action query. If you specify an action query, an "Invalid Operation" error occurs.

Table 8-15: The Type Intrinsic Constants

Named Constant

Value

Description

dbOpenTable

1

Opens a table-type Recordset object ( Jet workspaces only)

dbOpenDynamic

16

Opens a dynamic-type Recordset object, similar to an ODBC dynamic cursor (ODBCDirect workspaces only)

dbOpenDynaset

2

Opens a dynaset-type Recordset object, similar to an ODBC keyset cursor

dbOpenSnapshot

4

Opens a snapshot-type Recordset object similar to an ODBC static cursor

dbOpenForwardOnly

8

Opens a forward-only-type Recordset object

Table 8-16: The Options Intrinsic Constants

Named Constant

Value

Description

dbAppendOnly

8

Allows users to append new records to the Recordset, but prevents them from editing or deleting existing records ( Jet dynaset-type Recordset only).

dbSQLPassThrough

64

Passes a SQL statement to a Jet-connected ODBC data source for processing ( Jet snapshot-type Recordset only).

dbSeeChanges

512

Generates a run-time error if one user is changing data that another user is editing ( Jet dynaset-type Recordset only). This setting is useful in applications where multiple users have simultaneous read/write access to the same data.

dbDenyWrite

1

Prevents other users from modifying or adding records ( Jet Recordset objects only).

dbDenyRead

2

Prevents other users from reading data in a table ( Jet table-type Recordset only).

dbForwardOnly

256

Creates a forward-only Recordset ( Jet snapshot-type Recordset only). It is provided only for backward compatibility, and you should use the dbOpenForwardOnly constant in the type argument instead of using this option.

dbReadOnly

4

Prevents users from making changes to the Recordset
( Jet only). The dbReadOnly constant in the lockedit argument replaces this option, which is provided only for backward compatibility.

dbRunAsync

1024

Runs an asynchronous query (ODBCDirect workspaces only).

dbExecDirect

2048

Runs a query by skipping SQLPrepare and directly calling SQLExecDirect (ODBCDirect workspaces only). Use this option only when you're not opening a Recordset based on a parameter query.

dbInconsistent

16

Allows inconsistent updates ( Jet dynaset-type and
snapshot-type Recordset objects only).

dbConsistent

32

Allows only consistent updates ( Jet dynaset-type and snapshot-type Recordset objects only).

Table 8-17: The LockEdit Intrinsic Constants

Named Constant

Value

Description

dbReadOnly

4

Prevents users from making changes to the Recordset (default for ODBCDirect workspaces). You can use dbReadOnly in either the options argument or the lockedit argument, but not both. If you use it for both arguments, a run-time error occurs.

dbPessimistic

2

Uses pessimistic locking to determine how changes are made to the Recordset in a multiuser environment. The page containing the record you're editing is locked as soon as you use the Edit method (default for Jet workspaces).

dbOptimistic

3

Uses optimistic locking to determine how changes are made to the Recordset in a multiuser environment. The page containing the record is not locked until the Update method is executed.

dbOptimisticValue

1

Uses optimistic concurrency based on row values (ODBCDirect workspaces only).

dbOptimisticBatch

5

Enables batch optimistic updating (ODBCDirect workspaces only).

The OpenRecordset method creates a new recordset and automatically appends it to the Recordsets collection. The first syntax variant for the OpenRecordset method call applies to Connection and Database objects, and the second variant applies to QueryDef, Recordset, and TableDef objects. See the OpenRecordset section in Chapter 5, Databases Collection and Database Object, for a number of code samples illustrating use of this method with Database objects in Access VBA, Word VBA, Excel VBA, and Outlook VBS code.

VBA Code

This code opens a filtered recordset based on another recordset and displays the results to the Debug window:

Private Sub cmdOpenRecordset_Click()    Dim dbs As Database   Dim strDBName As String   Dim rstEmployees As Recordset   Dim rstWAEmployees As Recordset   Dim strSearch As String      strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rstEmployees = dbs.OpenRecordset("Employees", dbOpenDynaset)      With rstEmployees      Debug.Print vbCrLf & "Unfiltered recordset:"      Do While Not .EOF         Debug.Print "Name: " & !LastName & ", state: " & !Region         .MoveNext      Loop   End With      'Create a second, filtered recordset based on the first recordset.   rstEmployees.Filter = "Region = 'WA'"   Set rstWAEmployees = rstEmployees.OpenRecordset()    With rstWAEmployees      Debug.Print vbCrLf & "Filtered recordset:"      Do While Not .EOF         Debug.Print "Name: " & !LastName & ", state: " & !Region         .MoveNext      Loop   End With   End Sub

Requery


recordset.Requery newquerydef

Argument

Data Type

Description

recordset

Recordset object

An existing Jet dynaset-, snapshot-, or forward-only Recordset object, or an ODBCDirect Recordset object

newquerydef

Variant

(Optional) The Name property of a QueryDef object ( Jet workspaces only)

The Requery method updates the data in a recordset by re-executing the query on which it is based. The newquerydef argument can be used to specify a new query for the recordset.

WARNING:

When you use the Requery method, the first record in the recordset becomes the current record, which can be a problem on forms. To avoid losing the user's place on a form after requerying, you can set a search string before requerying so you can return to the record you were on, as in the following code sample.

VBA Code

This code runs from a command button on an Access form; it calls a function (Calcinome, not reproduced here) that modifies data in the form's record source, so that the form needs requerying:

Private Sub cmdRequery_Click()    Dim strSearch As String   Dim strContract As String      'Create search string for current record.   strContract = Me![ContractNo]   strSearch = "[ContractNo] = " & strContract      'Call a function that needs requerying.   Call Calcincome   Me.Requery      'Find the record that matches the control.   Debug.Print "Search string: " & strSearch   Me.RecordsetClone.FindFirst strSearch   Me.Bookmark = Me.RecordsetClone.Bookmark End Sub

Seek


recordset.Seek comparison, key1, key2...key13

Argument

Data Type

Description

recordset

Recordset object

An existing table-type Recordset object with an index specified by the Recordset object's Index property

comparison

String

One of the following expressions: <, <=, =, >=, or >

key1, key2..., key13

One or more values (up to 13 in number) corresponding to fields in the Recordset object's current index, as specified by its Index property

For indexed table-type recordsets in Jet workspaces, the Seek method locates a record that meets the criteria for the current index and makes it the current record. You must set the Index property to the index you want to use before using Seek. (You can also determine if the index you want is active by retrieving its value beforehand.) If the index identifies a nonunique key field, Seek locates the first record that satisfies the criteria.

For =, >=, and > comparisons, Seek starts at the beginning of the index and seeks forward; for <>

You must specify values for all fields defined in the index in order to use Seek.

The key1 argument must be of the same field data type as the corresponding field in the current index.

Seek can be used even if there is no current record. You can't use Seek on a linked table, because you can't create a table-type recordset on a linked table.

See the Index property section for more information about indexes.

VBA Code

Private Sub cmdSeek_Click()    Dim dbs As Database   Dim strDBName As String   Dim rst As Recordset   Dim varBookmark As Variant   Dim intEmployee As Integer      strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset("Employees", dbOpenTable)   With rst      .Index = "PrimaryKey"            'Bookmark current record so we can return to it later.      varBookmark = .Bookmark      intEmployee = InputBox("Enter an Employee ID:")      .Seek "=", intEmployee            'Return to current record if Seek fails.      If .NoMatch Then         MsgBox "ID " & intEmployee & " not found"         .Bookmark = varBookmark      Else         MsgBox "Found ID at " & !LastName & " record"      End If      .Close   End With   End Sub 

Update


recordset.Update(updatetype, force)

Argument

Data Type

Description

recordset

Recordset object

An open, updatable Recordset object.

updatetype

Integer

A named constant or Integer value (see Table 8-18) (for ODBCDirect workspaces only).

force

Boolean

(Optional) If True, force changes regardless of whether another user has made any changes. If False (default), the update fails if another user has made changes while the update is pending.

Table 8-18: The UpdateType Intrinsic Constants

Named Constant

Value

Description

dbUpdateBatch

4

All pending changes in the update cache are written to disk

dbUpdateCurrentRecord

2

Only the current record's pending changes are written to disk

dbUpdateRegular

1

(Default) Pending changes aren't cached and are written to disk immediately

The Update method is crucial to saving your edits; it must be used for all edits done to a record, after creating a new record with AddNew, or calling the Edit method to edit an existing record. One exception is that you don't need to use Update after deleting a record with Delete. If you don't use Update after making a change (other than a Delete), the changes will be lost in any of the following situations:

  • You use Edit or AddNew and move to another record without using Update.

  • You use Edit or AddNew then use Edit or AddNew again without first using Update.

  • You set the Bookmark property to another record.

  • You close the recordset without first using Update.

  • You cancel editing by using CancelUpdate.

VBA Code

This example code illustrates a standard use of the Update method after using the Edit method and making some changes to a record, in a looping structure that iterates through an entire recordset:

Private Sub cmdUpdate_Click()    Dim dbs As Database   Dim strDBName As String   Dim rst As Recordset      strDBName = "D:\Documents\Northwind.mdb"   Set dbs = OpenDatabase(strDBName)   Set rst = dbs.OpenRecordset("Employees", dbOpenTable)   With rst      .MoveFirst      Do While Not .EOF         .Edit         If !Title = "Sales Representative" Then !Title = "Sales Rep"         .Update         .MoveNext      Loop      .Close   End With   dbs.Close   End Sub


1. In an ODBCDirect workspace a snapshot-type Recordset may be updatable, depending on the ODBC driver. The LastModified property is available and the Updatable property is True only on ODBCDirect snapshot-type Recordset objects if the ODBC driver supports updatable snapshots.

2. In an ODBCDirect workspace, a snapshot-type recordset may be updatable, depending on the ODBC driver. The AddNew, Edit, Delete, Update, and CancelUpdate methods are only available on ODBCDirect snapshot-type Recordset objects if the ODBC driver supports updatable snapshots.

3. Only with forward moves that don't use a bookmark offset.

http://oreilly.com/catalog/progacdao/chapter/ch08.html