Print Search Listbox Results in Report Filter Preview ... HELP!!!

A

arzadoch05

Hello all,

I have a list box in a Search Form "frmSearch" that is capable of
displaying the records in my database. User can type in a search
criteria and it will display all the rusults of that search in the list
box. I want to print/export these list box results in a report? So
far, I have three buttons on the form:
1. "Preview" invidual record when user hi-lights a record in the list
box and clicks Preview button.
2. "View Results" button
3. "Preview Results" button

Button 2 and 3 is currently unassigned and ultimately, I want to set up
command buttons for 2 and 3 to print/export/filter these list box
results in a report? My report name is "rptPatentResultPage".

Check out my code in the form "frmSearch" nd please advise. Thanks in
advance.

____________________________________________________________________________
Option Compare Database
Option Explicit

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

Private Type OPENFILENAME
lStructSize As Long
hwnd As Long
hInstance As Long
lpstrFilter As String
lpstrCustomFilter As String
nMaxCustFilter As Long
nFilterIndex As Long
lpstrFile As String
nMaxFile As Long
lpstrFileTitle As String
nMaxFileTitle As Long
lpstrInitialDir As String
lpstrTitle As String
Flags As Long
nFileOffset As Integer
nFileExtension As Integer
lpstrDefExt As String
lCustData As Long
lpfnHook As Long
lpTemplateName As String
End Type

Private Declare Function GetOpenFileName _
Lib "comdlg32.dll" Alias "GetOpenFileNameA" _
(pOpenfilename As OPENFILENAME) As Long

Private Declare Function GetSaveFileName Lib "comdlg32.dll" Alias
"GetSaveFileNameA" (pOpenfilename As OPENFILENAME) As Long

Private Const OFN_FILEMUSTEXIST = &H1000
Private Const OFN_HIDEREADONLY = &H4
Private Const OFN_OVERWRITEPROMPT = &H2
Private Const OFN_PATHMUSTEXIST = &H800
Private Const OFN_SAVE = 0
Private Const OFN_OPEN = 1



Private Type CTLInf
Name As String
Enabled As Boolean
End Type
Private Declare Function apiSortStringArray Lib "msaccess.exe" _
Alias "#81" _
(astrStringArray() As String) _
As Long

Private arrCtls() As CTLInf
Private mvarOriginalFields As Variant
Private Const mconQ = """"

Private Sub chkEditSQL_Click()
With Me
.txtSQL.Enabled = (.chkEditSQL = True)
.txtSQL.Locked = Not ((.chkEditSQL = True))
.txtSQL.BackColor = IIf(.chkEditSQL = True, vbWhite, _
-2147483633)
End With
End Sub

Private Sub cmdExport_Click()
On Error GoTo ErrHandler
Dim arrCtl As Control
Dim intUbound As Integer
Dim intLbound As Integer
Dim intCount As Integer
Select Case cmdExport.Tag
Case "Choose"
intCount = -1
For Each arrCtl In Me.Controls
Select Case arrCtl.ControlType
Case acTextBox, acComboBox, acCheckBox, acListBox,
acCommandButton
If arrCtl.Name <> "cmdExport" And arrCtl.Name <> "lstResult"
Then
intCount = intCount + 1
ReDim Preserve arrCtls(0 To intCount)
With arrCtls(intCount)
.Name = arrCtl.Name
.Enabled = arrCtl.Enabled
End With
arrCtl.Enabled = False
End If
End Select
Next

With lstResult
.ColumnCount = 4
.ColumnWidths = "0,0,0"
.RowSourceType = "Value List"
.RowSource = "-1,-1,-1,Export Type," _
& "0,0,.xls,Excel 3," _
& "0,6,.xls,Excel 4," _
& "0,5,.xls,Excel 5," _
& "0,5,.xls,Excel 7," _
& "0,8,.xls,Excel 97," _
& "0,2,.wk1,Lotus WK1," _
& "0,3,.wk3,Lotus WK3," _
& "0,7,.wk4,Lotus WK4," _
& "0,4,.wj2,Lotus WJ2 (Japanese)," _
& "1,2,.txt,Delimited Text," _
& "1,8,.html,HTML"
'& "1,3,.txt,Fixed Length Text,"
.selected(1) = True
End With
Label16.Caption = "Select ..."
cmdExport.Tag = "Export"
Case "Export"
If MsgBox("Are you sure you want to export this query", vbYesNo +
vbQuestion) <> vbNo Then
Call ExportRoutine
End If
intLbound = LBound(arrCtls)
intUbound = UBound(arrCtls)
For intCount = intLbound To intUbound
With arrCtls(intCount)
Me(.Name).Enabled = .Enabled
End With
Next
Label16.Caption = "Search Results"
cmdExport.Tag = "Choose"
lstResult.ColumnWidths = ""
If Me.chkAutoBuildSQL = True Then Call sBuildSQL
End Select
ExitHere:
Exit Sub
ErrHandler:
If Err = 2448 Then Resume Next
Resume ExitHere
End Sub

Private Sub cmdPreview_Click()
DoCmd.OpenReport "rptPatentResultPage", acViewPreview, ,
"(RawPatentNo = '" & Me!lstResult.Column(0) & "')"
End Sub

Private Sub Command52_Click()

DoCmd.OpenTable ("SearchHelp")

End Sub

Private Sub Command91_Click()
DoCmd.Maximize
End Sub

Private Sub Form_Load()
cmdExport.Tag = "Choose"
End Sub

Private Sub Label95_Click()
DoCmd.Close
End Sub

Private Sub lstResult_DblClick(Cancel As Integer)
If Len(Me.lstResult & "") > 0 Then
DoCmd.OpenForm "PatentRecords", acNormal, , _
"[RawPatentNo] = '" & Me.lstResult & "'"
End If
End Sub


Private Sub PrintInvoice_Click()
' This code created by Command Button Wizard.
On Error GoTo Err_PrintInvoice_Click

Dim strDocName As String

strDocName = "rptPatentResultPage"
' Print Invoice report, using Invoices Filter query to print
' invoice for current order.
DoCmd.OpenReport strDocName, acViewNormal, "rptPatentResultPage"

Exit_PrintInvoice_Click:
Exit Sub

Err_PrintInvoice_Click:
' If action was cancelled by the user, don't display an error
message.
Const conErrDoCmdCancelled = 2501
If (Err = conErrDoCmdCancelled) Then
Resume Exit_PrintInvoice_Click
Else
MsgBox Err.Description
Resume Exit_PrintInvoice_Click
End If


End Sub




Private Sub txtSQL_AfterUpdate()
'build the SQL with what we have
Call sBuildSQL
End Sub

Private Sub cmdBuildSQL_Click()
'build the SQL with what we have
Call sBuildSQL
End Sub

Private Sub cmdClear_Click()
'Clear out and disable appropriate controls on the form
Dim ctl As Control
On Error Resume Next
For Each ctl In Me.Controls
Select Case ctl.ControlType
Case acTextBox:
ctl = Null
ctl.Enabled = False
ctl.BackColor = -2147483633
Case acCommandButton:
'only disable the CopySQL or CreateQDF command buttons
If ctl.Name = "cmdCopySQL" Or ctl.Name = "cmdCreateQDF"
Then
ctl.Enabled = False
End If
Case acOptionGroup, acListBox:
If Not Screen.ActiveControl.ControlType = acListBox Then _
ctl = Null
Case acCheckBox:
If ctl.Name = "chkEditSQL" Then
ctl = Null
ctl.Enabled = False
End If
Case Else:
ctl = Null
ctl.Enabled = False
End Select
If ctl.Name <> "cmdExport" Then ctl.Tag = vbNullString
Next
With Me.lstResult
.Enabled = False
.ColumnCount = 1
.ColumnHeads = False
.RowSource = vbNullString
End With
mvarOriginalFields = Null
Me.txtSQL.Enabled = True
Me.cmdClear.Enabled = True
'Me.lstTables = Null
End Sub

Private Sub cmdCopySQL_Click()
'Copy the SQL to the clipboard
On Error Resume Next
With Me
.txtSQL.SetFocus
'.txtSQL.SelText = .txtSQL.SelLength
DoCmd.RunCommand acCmdCopy
Screen.PreviousControl.SetFocus
End With
End Sub

Private Sub cmdCreateQDF_Click()
On Error GoTo ErrHandler
Dim Db As DAO.Database
Dim qdf As DAO.QueryDef
Dim strName As String
'first get a unique name for the querydef object
strName = Application.Run("acwzmain.wlib_stUniquedocname", "Query1",
acQuery)
strName = InputBox("Please specify a query name", "Save As",
strName)
If Not strName = vbNullString Then
'only create the querydef if user really wants to.
Set Db = CurrentDb
Set qdf = Db.CreateQueryDef(strName, Me.txtSQL)
qdf.Close
Else
'ok, so they don't want to
MsgBox "The save operation was cancelled." & vbCrLf & _
"Please try again.", vbExclamation + vbOKOnly, "Cancelled"
End If
ExitHere:
On Error Resume Next
qdf.Close
Set qdf = Nothing
Db.QueryDefs.Refresh
Set Db = Nothing
Exit Sub
ErrHandler:
Resume ExitHere
End Sub

Private Sub cmdUndo0_Click()
Call sDisableControls(0)
End Sub

Private Sub cmdUndo1_Click()
Call sDisableControls(1)
End Sub

Private Sub cmdUndo2_Click()
Call sDisableControls(2)
End Sub

Private Sub cmdUndo3_Click()
Call sDisableControls(3)
End Sub

Private Sub cmdUndo4_Click()
Call sDisableControls(4)
End Sub

Private Sub Command87_Click()
Me.lstTables.Requery
Call cmdClear_Click
End Sub

Private Sub lstTables_AfterUpdate()
'Try and enable the next control only if the the Clear
'button has been clicked (ctl.Tag = vbNullString)
'Otherwise just requery the field's info
'
Call cmdClear_Click
If Me.lstTables.Tag = vbNullString Then Call fEnableNextInTab
Me.cbxFld0.Requery
End Sub

Private Sub cmdExit_Click()
DoCmd.Close acForm, Me.Name
DoCmd.OpenForm ("Switchboard")
End Sub







Private Sub sDisableControls(intIndex As Integer)
'Undo/disable the field combo, criteria textbox,
' and the Or/And option
'
On Error Resume Next
With Me
.Controls("cbxFld" & intIndex) = Null
.Controls("opgClauseType" & intIndex) = Null
.Controls("txtVal" & intIndex) = Null
End With
If Not intIndex = 0 Then
'if the user wants to clear out the first combo,
'don't disable, just clear out the controls
With Me
.Controls("cbxFld" & intIndex).Enabled = False
.Controls("txtVal" & intIndex).Enabled = False
End With
End If
'Build the SQL automatically only if the user specified so
If Me.chkAutoBuildSQL = True Then Call sBuildSQL
End Sub

Private Sub sFillCombo(intTargetIndex As Integer)
'Fills the Rowsource for a combo
'
On Error GoTo ErrHandler
Dim i As Long
Dim j As Integer
Dim strOut As String
Dim ctlTarget As Control

'Which one to fill?
Set ctlTarget = Me("cbxFld" & intTargetIndex)
For i = LBound(mvarOriginalFields) To UBound(mvarOriginalFields)
strOut = strOut & mvarOriginalFields(i) & ";"
Next
With ctlTarget
.RowSourceType = "Value List"
.RowSource = strOut
End With
ExitHere:
Set ctlTarget = Nothing
Exit Sub
ErrHandler:
Resume ExitHere
End Sub

Sub sBuildSQL()
' Take what's currently selected on the form
' and create a dynamic SQL statement for the
' lstResults listbox.
'
On Error GoTo ErrHandler
Dim strSQL As String
Dim strWhere As String
Dim strJoinType As String
Dim i As Integer
Dim j As Integer
Dim Db As DAO.Database
Dim rs As DAO.Recordset
Dim tdf As TableDef
Dim qdf As DAO.QueryDef
Dim rsQdf As DAO.Recordset
Dim fld As DAO.Field
Const conMAXCONTROLS = 5

Set Db = DBEngine(0)(0)
strSQL = "Select * "
'Right now we have five combo/textbox sets
'so set up the master loop to go through these controls
For i = 0 To conMAXCONTROLS - 1
strJoinType = vbNullString
'there might be some unused sets, so don't bother
'going through the disabled controls
If Me("cbxFld" & i).Enabled Then
'The Or/And set starts with the second combo/textbox set
'so if there's only one criteria specified, don't need to
'concatenate additional stuff.
If i > 0 Then
If Me("opgClauseType" & i) = 1 Then
strJoinType = " OR "
Else
strJoinType = " AND "
End If
End If
'Get the a reference to the field in the table/Query as
'we'll need it for BuildCriteria later on
If Me.lstTables.Column(1) = "Table" Then
Set tdf = Db.TableDefs(Me.lstTables.Column(0))
Set fld = tdf.Fields(Me("cbxFld" & i))
Else
Set rsQdf = Db.OpenRecordset( _
"Select * from [" & Me.lstTables.Column(0) & "] Where
1=2", dbOpenSnapshot)
Set fld = rsQdf.Fields(Me("cbxFld" & i))
End If

'Only build a criteria if something's typed in the textbox
'otherwise assume all records
If Not IsNull(Me("txtVal" & i)) Then
strWhere = strWhere & strJoinType &
Application.BuildCriteria( _
"[" & Me("cbxFld" & i)
& "]", _
fld.Type, Me("txtVal" & i)
& "")
Else
strWhere = strWhere & strJoinType & "[" & Me("cbxFld" & i)
& "] like '*'"
End If

End If
Next
'The final all important SQL statement
strSQL = strSQL & " from [" & Me.lstTables & "] Where " & strWhere

'If the user has modified the SQL directly, take what they've typed
in
If Nz(Me.chkEditSQL, False) = False Then
'"save" it in the textbox
Me.txtSQL = strSQL
End If

With Me.lstResult
Set rs = Db.OpenRecordset(Me.txtSQL)
'assign the SQL to the lstResult only if
' (a) it's valid (Set rs will generate an error otherwise)
' (b) if the recordset actually returned any records.
If rs.RecordCount > 0 Then
Me.cmdCopySQL.Enabled = True
Me.cmdCreateQDF.Enabled = True
Me.cmdExport.Enabled = True
.RowSourceType = "Table/Query"
.RowSource = Me.txtSQL
.Enabled = True
'display * fields
.ColumnCount = CInt(Me.lstTables.Tag)
.ColumnHeads = True
Me.chkEditSQL.Enabled = True
Else
'Thanks for trying, better luck next time!!
Me.cmdCopySQL.Enabled = False
Me.cmdCreateQDF.Enabled = False
Me.cmdExport.Enabled = False
.ColumnCount = 1
.RowSourceType = "Value List"
.RowSource = "No records found."
End If
End With
ExitHere:
Set rsQdf = Nothing
Set rs = Nothing
Set tdf = Nothing
Set Db = Nothing
Exit Sub
ErrHandler:
Select Case Err.Number
'we're trying to open a parameter query
Case 3061:
MsgBox "The " & mconQ & Me.lstTables & mconQ & " query you've
selected " _
& " is a Parameter Query." & vbCrLf & Err.Description,
vbExclamation + vbOKOnly, _
"Missing parameters"
Case Else:
'Either invalid SQL or some other error
End Select
Me.cmdCopySQL.Enabled = False
Me.cmdCreateQDF.Enabled = False
With Me.lstResult
.RowSourceType = "Value List"
.RowSource = "Invalid SQL statement."
.ColumnHeads = False
.ColumnCount = 1
.Enabled = False
End With
Resume ExitHere
End Sub

Function fListFill(ctl As Control, varID As Variant, lngRow As Long, _
lngCol As Long, intCode As Integer) As Variant
'The callback function for the first combo
' sFillCombo takes care of the rest of 'em.
On Error GoTo ErrHandler
Static sastrObjSource() As String
Static sastrFields() As String
Static slngCount As Long
Static sdb As DAO.Database
Dim i As Long
Dim j As Long
Dim tdf As TableDef
Dim rsQdf As DAO.Recordset
Dim fld As DAO.Field
Dim varRet As Variant
Dim strObjectType As String
Dim varItem As Variant

Select Case intCode
Case acLBInitialize
If sdb Is Nothing Then Set sdb = CurrentDb
With Me
ReDim sastrObjSource(0)
'Are we looking for a table or a query
sastrObjSource(0) = .lstTables.Column(0)
strObjectType = .lstTables.Column(1)
j = -1
If strObjectType = "Table" Then
Set tdf = sdb.TableDefs(sastrObjSource(0))
Me.lstTables.Tag = tdf.Fields.Count
'Get a list of all the fields
For Each fld In tdf.Fields
j = j + 1
ReDim Preserve sastrFields(j)
sastrFields(j) = fld.Name
Next
j = UBound(sastrFields)
Else
'Since the fieldnames can be changed, safest way is to
'open a recordset and go through it's Fields collection
Set rsQdf = sdb.OpenRecordset( _
"Select * from [" & sastrObjSource(0) & "] Where
1=2", _
dbOpenSnapshot)
Me.lstTables.Tag = rsQdf.Fields.Count
For Each fld In rsQdf.Fields
j = j + 1
ReDim Preserve sastrFields(j)
sastrFields(j) = fld.Name
Next
j = UBound(sastrFields)
End If
'sort the string
' Call apiSortStringArray(sastrFields)
slngCount = UBound(sastrFields) + 1
'create a module level variant array for other combos
mvarOriginalFields = sastrFields
End With
varRet = True

Case acLBOpen
varRet = Timer

Case acLBGetRowCount
varRet = slngCount

Case acLBGetValue
varRet = sastrFields(lngRow)

Case acLBEnd
Set rsQdf = Nothing
Set tdf = Nothing
Set sdb = Nothing
Erase sastrFields
Erase sastrObjSource
End Select
fListFill = varRet
ExitHere:
Exit Function
ErrHandler:
Resume ExitHere
End Function

Function fEnableNextInTab()
'Enable and Setfocus to the next control
'in the form's TabIndex.
Dim ctlNew As Control, intTab As Integer
Dim ctlOld As Control, intNewTab As Integer

On Error Resume Next
'Since we're calling this function from AfterUpdate,
'what's the current control's position in TabIndex
Set ctlOld = Screen.ActiveControl
'we want the next one
intNewTab = ctlOld.TabIndex + 1

For Each ctlNew In Me.Controls
intTab = ctlNew.TabIndex
If Not Err And (intTab = intNewTab) Then
'if no error occurred and the tab index is same as
'what we're looking for, then enable it
With ctlNew
'Store the control's name for later use
'but exclude the listbox since the tag there
'contains the number of fields in the object select
If Not ctlOld.ControlType = acListBox Then _
ctlOld.Tag = .Name
Select Case .ControlType
Case acListBox:
Case acComboBox:
'If the control found is a combo, fill it's rowsource
Call sFillCombo(Right(.Name, 1))
Case Else:

End Select
.Enabled = True
.Locked = False
.BackColor = vbWhite
.SetFocus
Exit For
End With
End If
Next
Set ctlOld = Nothing
Set ctlNew = Nothing
'Build the SQL automatically only if the user specified so
If Me.chkAutoBuildSQL = True Then Call sBuildSQL
End Function

Private Function fGetDocObjectProperty(strObjectName As String, _
strObjectType As String, _
strPropertyName As String) _
As Variant
'?fGetDocObjectProperty("Module33","Modules","DateLastUpdated")
'
On Error GoTo ErrHandler
Dim Db As DAO.Database
Dim doc As Document
Dim ctr As Container

Set Db = CurrentDb
Set ctr = Db.Containers(strObjectType)
Set doc = ctr.Documents(strObjectName)

fGetDocObjectProperty = doc.Properties(strPropertyName)
ExitHere:
Set doc = Nothing
Set ctr = Nothing
Set Db = Nothing
Exit Function
ErrHandler:
fGetDocObjectProperty = Null
Resume ExitHere
End Function

Private Function fSetDocObjectProperty(strObjectName As String, _
strObjectType As String, _
strPropertyName As String, _
varPropertyValue As Variant, _
Optional varPropertyType As Variant =
dbText) _
As Boolean
'?fSetDocObjectProperty("Module33","Modules","DateLastUpdated",Now)
'
On Error GoTo ErrHandler
Dim Db As DAO.Database
Dim doc As Document
Dim ctr As Container
Dim prop As Property

Set Db = CurrentDb
Set ctr = Db.Containers(strObjectType)
Set doc = ctr.Documents(strObjectName)

doc.Properties(strPropertyName).Value = varPropertyValue
fSetDocObjectProperty = True
ExitHere:
Set prop = Nothing
Set doc = Nothing
Set ctr = Nothing
Set Db = Nothing
Exit Function
ErrHandler:
Select Case Err.Number
Case 3270:
Set prop = doc.CreateProperty(strPropertyName, _
varPropertyType, varPropertyValue)
doc.Properties.Append prop
Resume Next
Case Else:
fSetDocObjectProperty = False
Resume ExitHere
End Select
Resume ExitHere
End Function

Private Function ExportRoutine()
Dim Db As DAO.Database
Dim qdf As DAO.QueryDef
Dim lorst As DAO.Recordset
Dim strName As String
Dim strFile As String
Const strSpecName = "~~TempSpec~~"
On Error GoTo ExportRoutine_err
With Me.lstResult
strFile = DialogFile(OFN_SAVE, "Save file", "", .Column(3) & " (" &
..Column(2) & ")|" & .Column(2), CurDir, .Column(2))
End With
If Len(strFile) > 0 Then
'first get a unique name for the querydef object
strName = Application.Run("acwzmain.wlib_stUniquedocname",
"Query1", acQuery)
Set Db = CurrentDb
Set qdf = Db.CreateQueryDef(strName, Me.txtSQL)
qdf.Close
With lstResult
Select Case .Column(0)
Case 0 'Transferspreadsheet
DoCmd.TransferSpreadsheet acExport, .Column(1), strName,
strFile, True
Case 1 'Transfertext
If .Column(1) = acExportFixed Then
'Considerations
'Do MsysImexColumns and MsysImexSpecs exist
'Need to create if not
'Can use Max Length on each field in query to get lengths for
MsysImexSpecs

' Set lorst = db.OpenRecordset(strName)
'Do loads of other stuff in here ...
' DoCmd.TransferText .Column(1), , strName, strFile, True
Else
DoCmd.TransferText .Column(1), , strName, strFile, True
End If
End Select
End With
End If
ExportRoutine_end:
On Error Resume Next
DoCmd.DeleteObject acQuery, strName
qdf.Close
Set qdf = Nothing
Db.QueryDefs.Refresh
Set Db = Nothing
Exit Function
ExportRoutine_err:
Resume ExportRoutine_end
End Function
Public Function DialogFile(wMode As Integer, szDialogTitle As String,
szFileName As String, szFilter As String, szDefDir As String, szDefExt
As String) As String
Dim x As Long, OFN As OPENFILENAME, szFile As String, szFileTitle As
String
With OFN
.lStructSize = Len(OFN)
.hwnd = hWndAccessApp
.lpstrTitle = szDialogTitle
.lpstrFile = szFileName & String$(250 - Len(szFileName), 0)
.nMaxFile = 255
.lpstrFileTitle = String$(255, 0)
.nMaxFileTitle = 255
.lpstrFilter = NullSepString(szFilter)
.nFilterIndex = 2
.lpstrInitialDir = szDefDir
.lpstrDefExt = szDefExt
If wMode = 1 Then
OFN.Flags = OFN_HIDEREADONLY Or OFN_PATHMUSTEXIST Or
OFN_FILEMUSTEXIST
x = GetOpenFileName(OFN)
Else
OFN.Flags = OFN_HIDEREADONLY Or OFN_OVERWRITEPROMPT Or
OFN_PATHMUSTEXIST
x = GetSaveFileName(OFN)
End If
If x <> 0 Then
If InStr(.lpstrFile, Chr$(0)) > 0 Then
szFile = Left$(.lpstrFile, InStr(.lpstrFile, Chr$(0)) - 1)
End If
DialogFile = szFile
Else
DialogFile = ""
End If
End With
End Function

'Pass a "|" separated string and returns a Null separated string
Private Function NullSepString(ByVal CommaString As String) As String
Dim intInstr As Integer
Const vbBar = "|"
Do
intInstr = InStr(CommaString, vbBar)
If intInstr > 0 Then Mid$(CommaString, intInstr, 1) = vbNullChar
Loop While intInstr > 0
NullSepString = CommaString
End Function
___________________________________________________________________________
 

Ask a Question

Want to reply to this thread or ask your own question?

You'll need to choose a username for the site, which only take a couple of moments. After that, you can post your question and our members will help you out.

Ask a Question

Top