The Recordset Object Open Method

Applies to: Access 2013 | Access 2016

In this article Source and Options Arguments ActiveConnection Argument CursorType Argument LockType Argument Retrieving Multiple Recordsets

Everything you need to open an ADO Recordset is built into the Open method. Use it without explicitly creating any other objects. The syntax of this method is as follows:

recordset .OpenSource, ActiveConnection, CursorType, LockType, Options

All arguments are optional because the information they pass can be communicated to ADO in other ways. However, understanding each argument will help you to understand many important ADO concepts. The following topics will examine each argument of this method in more detail.

Source and Options Arguments

The Source and Options arguments appear in the same topic because they are closely related.

recordset .Open Source, ActiveConnection, CursorType, LockType, Options

The Source argument is a Variant that evaluates to a valid Command object, a text command (e.g., a SQL statement), a table name, a stored procedure call, a URL, or the name of a file or Stream object containing a persistently stored Recordset. If Source is a file path name, it can be a full path ("C:\dir\file.rst"), a relative path ("..\file.rst"), or a URL ("https://files/file.rst"). You can also specify this information in the Recordset object Source property and leave the Source argument blank.

The Options argument is a Long value that indicates either or both of the following:

  • How the provider should evaluate the Source argument if it represents something other than a Command object.
  • That the Recordset should be restored from a file where it was previously saved.

This argument can contain a bitmask of CommandTypeEnum or ExecuteOptionEnum values. A CommandTypeEnum passed in the Options argument sets the CommandType property of the Recordset.

Note

The ExecuteOpenEnum values of adExecuteNoRecords and adExecuteStream cannot be used with Open.

If the CommandType property value equals adCmdUnknown (the default value), you might experience diminished performance, because ADO must make calls to the provider to determine whether the CommandText property is a SQL statement, a stored procedure, or a table name. If you know what type of command you are using, setting the CommandType property instructs ADO to go directly to the relevant code. If the CommandType property does not match the type of command in the CommandText property, an error occurs when you call the Open method.

For more information about using these enumerated constants for Options and with other ADO methods and properties, see CommandTypeEnum and ExecuteOptionEnum.

ActiveConnection Argument

You can pass in either a Connection object or a connection string as the ActiveConnection argument.

recordset .Open Source, ActiveConnection, CursorType, LockType, Options

The ActiveConnection argument corresponds to the ActiveConnection property and specifies in which connection to open the Recordset object. If you pass a connection definition for this argument, ADO opens a new connection using the specified parameters. After opening the Recordset with a client-side cursor ( CursorLocation = adUseClient ), you can change the value of this property to send updates to another provider. Or you can set this property to Nothing (in Microsoft Visual Basic) or NULL to disconnect the Recordset from any provider. Changing ActiveConnection for a server-side cursor generates an error, however.

If you pass a Command object in the Source argument and also pass an ActiveConnection argument, an error occurs because the ActiveConnection property of the Command object must already be set to a valid Connection object or connection string.

CursorType Argument

recordset .Open Source, ActiveConnection, CursorType, LockType, Options

As discussed in The Significance of Cursor Location, the type of cursor that your application uses will determine which capabilities are available to the resultant Recordset (if any). For a detailed examination of cursor types, see Chapter 8: Understanding Cursors and Locks.

The CursorType argument can accept any of the CursorTypeEnum values.

LockType Argument

recordset .Open Source, ActiveConnection, CursorType, LockType, Options

Set the LockType argument to specify what type of locking the provider should use when opening the Recordset. The different types of locking are discussed in Chapter 8: Understanding Cursors and Locks.

The LockType argument can accept any of the LockTypeEnum values.

Retrieving Multiple Recordsets

You might occasionally need to execute a command that will return more than one result set. A common example is a stored procedure that runs against a SQL Server database, as in the following example. The stored procedure contains a COMPUTE clause to return the average price of all products in the table. The definition of the stored procedure is as follows:

CREATE PROCEDURE ProductsWithAvgPrice  
AS 
SELECT ProductID, ProductName, UnitPrice  
  FROM PRODUCTS  
  COMPUTE AVG(UnitPrice) 

The Microsoft OLE DB Provider for SQL Server returns multiple result sets to ADO when the command contains a COMPUTE clause. Therefore, the ADO code must use the NextRecordset method to access the data in the second result set, as shown here:

 
'BeginNextRs 
    On Error GoTo ErrHandler: 
     
    Dim objConn As New ADODB.Connection 
    Dim objCmd As New ADODB.Command 
    Dim objRs As New ADODB.Recordset 
 
    Set objConn = GetNewConnection 
    objCmd.ActiveConnection = objConn 
     
    objCmd.CommandText = "ProductsWithAvgPrice" 
    objCmd.CommandType = adCmdStoredProc 
     
    Set objRs = objCmd.Execute 
     
    Do While Not objRs.EOF 
        Debug.Print objRs(0) & vbTab & objRs(1) & vbTab & _ 
                    objRs(2) 
        objRs.MoveNext 
    Loop 
     
    Set objRs = objRs.NextRecordset 
     
    Debug.Print "AVG. PRICE = $ " & objRs(0) 
 
    'clean up 
    objRs.Close 
    objConn.Close 
    Set objRs = Nothing 
    Set objConn = Nothing 
    Set objCmd = Nothing 
    Exit Sub 
     
ErrHandler: 
    'clean up 
    If objRs.State = adStateOpen Then 
        objRs.Close 
    End If 
     
    If objConn.State = adStateOpen Then 
        objConn.Close 
    End If 
     
    Set objRs = Nothing 
    Set objConn = Nothing 
    Set objCmd = Nothing 
     
    If Err <> 0 Then 
        MsgBox Err.Source & "-->" & Err.Description, , "Error" 
    End If 
'EndNextRs 

For more information, see NextRecordset.

See also

Support and feedback

Have questions or feedback about Office VBA or this documentation? Please see Office VBA support and feedback for guidance about the ways you can receive support and provide feedback.