Dynamic field lists in an Access ADP report

C

CSDunn

Hello,
I have a situation with MS Access 2000 in which I need to display report
data in spreadsheet orientation (much like a datasheet view for a form). If
you think of the report in terms of what a spreadsheet might show, the
column names will actually be dynamic, based on data from a SQL Server 2000
database. The row data will also come from the same database. So in this
case, I will have a main report and a subreport. I've already tried this
arrangement for the data I will be presenting, and I get the results I
expect. so everything seems to work okay. The main report displays a single
'row' of data that make up the column headings, and the sub report displays
many rows that make up the main records.

The thing I need to figure out is how to make the physical number of
displayed 'column names' in the main report and associated 'data fields' in
the sub report change based on the report data I need to show. Right now, I
just have static fields in the main and sub report to show the data, but not
all of the fields are populated between the variations of returned data.

The Record Source for the main report is a stored procedure that takes a
@TestShortName parameter. The Record Source for the subreport is also a
stored procedure. The query for the stored procedure of the sub report is
slightly different, but it still takes an @TestShortName parameter. This
@TestShortName parameter equates to the TestID of a Student Test for both
procedures. Each student test has a different number of questions. The main
report is designed to display a questionID (QID) based on the @TestShortName
parameter. So for an @TestShortName of 'SFM2' there would be QID's 1 through
10. But for an @TestShortName of 'HMLM', there would be seventeen total
QID's of A1 through B7. SFM2 would require that there be ten fields in the
main report to show all ten QID's, but HMLM would require that there be
seventeen fields in the main report. The sub report would require the
different number of fields between the two @TestShortName parameters, ten
for SFM2, and seventeen for HMLM. However, the sub report shows question
answers for a given @TestShortName, not QID's. So given different
@TestshortNames, the data returned would look like this:

@TestShortName = 'SFM2':

1 2 3 4 5 6 7 8
9 10 (QID's in the main report)
(studentID) (sName) C I I C I C C C I I
(corresponding question answers in the sub report)

**********************************************
@TestShortName = 'HMLM'

A1 A2 A3 A4 A5 A6 A7
A8 A9 A10 B1 B2 B3 B4 B5 B6 B7 (QID's)
(studentID) (sName) C I I I C C C C
I I C C C I C C C (answers)


I know that I'll need to have the report set up in Landscape to accomodate
the varying results in the main and sub reports, but how do I set up both
reports so that I only have the required number of main and sub report
fields as required by the @TestShortName parameter? It seems like there
should be some sort of Loop structure that could count the number of
distinct QID's given a particular @TestShortName, and then display each
value in a label or text box. Maybe the same for the sub report for question
answers.

The stored procedures are set up to create 75 fields for any @TestShortName.
If an @TestShortName in the main report results in only the first ten QID's
having values, then the other 65 QID's will be NULL. The same would hold
true for the child records in the sub report. So the Loop would have to
ignore NULL values for the main and sub report. Also, for a given
@TestShortName, there can also be NULL values for the first ten QID's, then
the remaining 65 QID's could have values. The child records in the sub
report would match this as well.

I haven't done very much with coding as far as Access Reports are concerned,
and I need my 'hand held' with this one, so here are some questions:

1. How do I handle the communication between the Access ADP report and the
SQL Server Stored Procedures in the main and sub report? The procedures are
called 'MMQuestionDetailsMain_sp' and 'MMQuestionDetailsSub_sp' and both
take @TestShortName nvarchar(8). I don't suppose I would need to set up a
seperate ADO connection since I already have an OLE DB connection through
the ADP file.

2. Once I have established communication with the Stored Procedure, and have
established how I will send the parameter value for @TestShortName to the
SP, how do I handle the data that comes back from the procedure for the main
report so that the data values become the label or field names in the
report, and that any NULL values are ignored? Would I use an Object Array?
It has been suggested to me that one way to handle the NULL values would be
to use FindFirst. How might I otherwise handle the NULL values?

3. Once I have handled the data back from the SP, how do I set up the
dynamic action I need for the labels/fields in the main and sub report?


Please let me know if you have any ideas on this.

Thanks for your help!

CSDunn
 
L

Lyle Fairfield

The thing I need to figure out is how to make the physical number of
displayed 'column names' in the main report and associated 'data fields'
in the sub report change based on the report data I need to show.

It's likely that you will have to design the report in code at run time.
This may require many lines of code. This is an example. It calls a few
functions in a GeneralFunctions Module and so is not a closed system as
shown:

Option Compare Database
Option Explicit

Const ReportName As String = "rptSchoolOrganizations"
Const ReportCaption As String = "School Organizations (right click for
menu)"
Const Spacing As Long = 57
Const StartField As Long = 6
Const Width As Long = 567

Private ClassStructure As ADODB.Recordset
Private OrganizationType As String

Public Sub ViewSchoolOrganizationsReportofActualClasses()
Dim Cancel As Integer
VerifyLogin Cancel
If Cancel = 1 Then Exit Sub
OrganizationType = "Actual"
ShowStatusMessage "Updating Actual Grade Split-Grade Designations"
UpDateGrade_SplitGradeDesignations ("tblActualClasses")
ViewSchoolOrganizationsReport
End Sub

Public Sub ViewSchoolOrganizationsReportofTheoreticalClasses()
Dim Cancel As Integer
VerifyLogin Cancel
If Cancel = 1 Then Exit Sub
OrganizationType = "Theoretical"
ShowStatusMessage "Updating Theoretical Grade Split-Grade Designations"
UpDateGrade_SplitGradeDesignations ("tblTheoreticalClasses")
ViewSchoolOrganizationsReport
End Sub

Sub ViewSchoolOrganizationsReport()
Dim Control As Control
Dim FieldName As String
Dim Height As Long
Dim Label As Label
Dim Left As Long
Dim Line As Line
Dim NewReportName As String
Dim NextTop As Long
Dim sql As String
Dim Report As Report
Dim TextBox As TextBox
Dim ReportWidth As Long
Dim z As Long

' -------------------------
' if the report is open
' ask that it be closed
' and exit
' -------------------------
If SysCmd(acSysCmdGetObjectState, acReport, ReportName) <> 0 Then
MsgBox "Please, close all reports and try again.", vbExclamation Or
vbOKOnly, "FFDBA"
GoTo ViewSchoolOrganizationsReportExit
End If

' -------------------------
' delete the report, is if exists
' -------------------------
On Error Resume Next
DoCmd.DeleteObject acReport, ReportName
On Error GoTo 0
' -------------------------
' set error handling
' -------------------------
On Error GoTo ViewSchoolOrganizationsReportErr

' -------------------------
' stop screen updating
' -------------------------
Application.Echo 0

' -------------------------
' get class structure
' -------------------------
GetClassStructure

' -------------------------
' create the report
' -------------------------
ShowStatusMessage "Creating School Organization Report"

Set Report = Application.CreateReport
With Report
.Caption = "School Organizations"
End With

' -------------------------
' create groupings
' -------------------------
Application.CreateGroupLevel Report.Name, "fldSchoolName", True, True
Application.CreateGroupLevel Report.Name, "fldProgramName", True, True
With Report.GroupLevel(0)
.KeepTogether = 1
End With
With Report.GroupLevel(1)
.KeepTogether = 1
End With

' -------------------------
' create the textbox fields that access the data in the table
' -------------------------
With ClassStructure
For z = StartField To .Fields.Count - 1
FieldName = .Fields(z).Name
Set TextBox = Application.CreateReportControl(Report.Name,
acTextBox, acDetail, , FieldName)
With TextBox
.Format = "#0;=#0;" & Chr$(34) & Chr$(34)
.Left = Left
.Name = "txt" & FieldName
.TextAlign = 3
.Width = Width
End With
Left = Left + Width
Next z
End With

' -------------------------
' set some report dimensions
' -------------------------
ReportWidth = Left
Report.Width = ReportWidth
Report.Section(acDetail).Height = TextBox.Height

' -------------------------
' design the page header
' -------------------------
Set Line = Application.CreateReportControl( _
Report.Name, acLine, acPageHeader, , , 0, _
Spacing, ReportWidth)
With Line
.BorderWidth = 0
.Name = "Line1"
NextTop = .Top + .Height + Spacing
End With

Set Label = Application.CreateReportControl( _
Report.Name, acLabel, acPageHeader, , , 0, NextTop)
With Label
.BorderStyle = 0
.Caption = "Halton District School Board"
.Name = "lblDistrictName"
.SizeToFit
.Width = ReportWidth
NextTop = .Top + .Height + Spacing
End With

Set Label = Application.CreateReportControl( _
Report.Name, acLabel, acPageHeader, , , 0, NextTop)
With Label
.BorderStyle = 0
.Caption = "School Organizations"
.Name = "lblSchoolOrganizations"
.SizeToFit
.Width = ReportWidth
NextTop = .Top + .Height + Spacing
End With

Set Line = Application.CreateReportControl( _
Report.Name, acLine, acPageHeader, , , 0, _
NextTop, ReportWidth)
With Line
.BorderWidth = 0
.Name = "Line2"
NextTop = .Top + .Height + Spacing
End With

Report.Section(acPageHeader).Height = NextTop

' -------------------------
' design the school grouping header
' -------------------------
Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel1Header, , , 0, _
Spacing, ReportWidth)
With Line
.BorderWidth = 3
.Name = "Line3"
NextTop = .Top + .Height + Spacing
End With

Set TextBox = Application.CreateReportControl( _
Report.Name, acTextBox, acGroupLevel1Header, , , 0, NextTop)
With TextBox
.BorderStyle = 0
.ControlSource = "fldSchoolName"
.Name = "txtSchoolName"
.SizeToFit
.Width = ReportWidth
NextTop = .Top + .Height + Spacing * 2
End With

Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel1Header, , , 0, _
NextTop, ReportWidth)
With Line
.BorderWidth = 3
.Name = "Line4"
NextTop = .Top + .Height + Spacing
End With

Report.Section(acGroupLevel1Header).Height = NextTop

' -------------------------
' design the school grouping footer
' -------------------------
Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel1Footer, , , 0, _
Spacing, ReportWidth)
With Line
.BorderWidth = 3
.Name = "Line5"
NextTop = .Top + .Height + Spacing
End With

Set TextBox = Application.CreateReportControl( _
Report.Name, acTextBox, acGroupLevel1Footer, , , 0, NextTop)
With TextBox
.BorderStyle = 0
.ControlSource = "= fldSchoolName & " & Chr(34) & " Totals" & Chr
(34)
.Name = "txtSumSchool"
.SizeToFit
.Width = ReportWidth
NextTop = .Top + .Height + Spacing
End With

Left = 0

With ClassStructure
For z = StartField To .Fields.Count - 1
FieldName = .Fields(z).Name
Set TextBox = Application.CreateReportControl(Report.Name,
acTextBox, acGroupLevel1Footer)
With TextBox
.ControlSource = "=Sum(" & FieldName & ")"
.Left = Left
.Name = "txt" & FieldName & "SumSchool"
.TextAlign = 3
.Top = NextTop
.Width = Width
Height = .Top + .Height
End With
Left = Left + Width
Next z
End With

NextTop = Height + Spacing

Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel1Footer, , , 0, _
NextTop, ReportWidth)
With Line
.BorderWidth = 3
.Name = "Line6"
NextTop = .Top + .Height + Spacing
End With

Report.Section(acGroupLevel1Footer).Height = NextTop

' -------------------------
' design the program grouping header
' -------------------------
Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel2Header, , , 0, _
Spacing, ReportWidth)
With Line
.BorderWidth = 0
.Name = "Line7"
NextTop = .Top + .Height + Spacing
End With

Set TextBox = Application.CreateReportControl( _
Report.Name, acTextBox, acGroupLevel2Header, , , 0, NextTop)
With TextBox
.BorderStyle = 0
.ControlSource = "fldProgramName"
.Name = "txtProgramName"
.SizeToFit
.Width = ReportWidth
NextTop = .Top + .Height + Spacing
End With

Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel2Header, , , 0, _
NextTop, ReportWidth)
With Line
.BorderWidth = 0
.Name = "Line8"
NextTop = .Top + .Height + Spacing
End With

Left = 0
With ClassStructure
For z = StartField To .Fields.Count - 1
FieldName = .Fields(z).Name
Set Label = Application.CreateReportControl(Report.Name,
acLabel, acGroupLevel2Header, , Replace(FieldName, "fld", ""))
With Label
.Left = Left
.Name = "lbl" & .Caption
.TextAlign = 3
.Top = NextTop
.Width = Width
Left = Left + Width
End With
Next z
End With

Report.Section(acGroupLevel2Header).Height = Height

' -------------------------
' design the program grouping footer
' -------------------------
Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel2Footer, , , 0, _
Spacing, ReportWidth)
With Line
.BorderWidth = 0
.Name = "Line9"
NextTop = .Top + .Height + Spacing
End With

Set TextBox = Application.CreateReportControl( _
Report.Name, acTextBox, acGroupLevel2Footer, , , 0, NextTop)
With TextBox
.BorderStyle = 0
.ControlSource = "= fldProgramName & " & Chr(34) & " Totals" & Chr
(34)
.Name = "txtSumProgram"
.SizeToFit
.Width = ReportWidth
NextTop = .Top + .Height + Spacing
End With

Left = 0

With ClassStructure
For z = StartField To .Fields.Count - 1
FieldName = .Fields(z).Name
Set TextBox = Application.CreateReportControl(Report.Name,
acTextBox, acGroupLevel2Footer)
With TextBox
.ControlSource = "=Sum(" & FieldName & ")"
.Left = Left
.Name = "txt" & FieldName & "SumProgram"
.TextAlign = 3
.Top = NextTop
.Width = Width
Height = .Top + .Height
End With
Left = Left + Width
Next z
End With

NextTop = Height + Spacing

Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel2Footer, , , 0, _
NextTop, ReportWidth)
With Line
.BorderWidth = 0
.Name = "Line10"
NextTop = .Top + .Height + Spacing
End With

Report.Section(acGroupLevel2Footer).Height = NextTop

' -------------------------
' set page footer grouping properties
' -------------------------
Set TextBox = Application.CreateReportControl(Report.Name, acTextBox,
acPageFooter, , , 0, Spacing * 2)
With TextBox
.ControlSource = "= " & Chr$(34) & "Page " & Chr$(34) & " & [Page]
& " & Chr$(34) & " of " & Chr$(34) & " & [Pages]"
.Name = "txtPage"
.TextAlign = 1
.Width = ReportWidth
NextTop = .Top + .Height + Spacing
End With
Set TextBox = Application.CreateReportControl(Report.Name, acTextBox,
acPageFooter, , , 0, NextTop + Spacing * 2)
With TextBox
.ControlSource = "= Now()"
.Format = "YYYY-MM-DD HH:NN"
.Name = "txtNow"
.TextAlign = 1
.Width = ReportWidth
NextTop = .Top + .Height + Spacing
End With

' -------------------------
' set some more report properties
' -------------------------
With Report
.Section(acPageFooter).Height = NextTop
.Caption = ReportCaption
.ShortcutMenuBar = "Report Preview"
.Width = ReportWidth
.RecordSource = "dbo.SpSchoolOrganizationReport"
.InputParameters = "@SchoolID int = " & Form_frmLogin.Login.Collect
(2)

NewReportName = .Name

End With

' -------------------------
' close and save the report
' -------------------------

DoCmd.Close acReport, Report.Name, acSaveYes

' -------------------------
' Rename the report
' -------------------------
DoCmd.Rename ReportName, acReport, NewReportName
' -------------------------
' View the report
' -------------------------
Application.Echo 1
ShowStatusMessage ReportCaption
With DoCmd
.OpenReport ReportName, acViewPreview
.ShowToolbar "Print Preview", acToolbarNo
.Maximize
End With
Reports(ReportName).ZoomControl = 0

ViewSchoolOrganizationsReportExit:
ShowStatusMessage
Exit Sub
ViewSchoolOrganizationsReportErr:
MsgBox Err.Description, vbCritical, "Number " & Err.Number
DoCmd.Close acReport, Report.Name, acSaveNo
Application.Echo 1
Resume ViewSchoolOrganizationsReportExit
End Sub

Private Sub GetClassStructure()
If Not ClassStructure Is Nothing Then Exit Sub
If OrganizationType = "Actual" Then
CreateRecordSet ClassStructure, "SpGetEmptyActualClassRecordet", ,
True
ElseIf OrganizationType = "Theoretical" Then
CreateRecordSet ClassStructure,
"SpGetEmptyTheoreticalClassRecordet", , True
End If
End Sub
 
C

CSDunn

Thanks for your help!
CSDunn

Lyle Fairfield said:
The thing I need to figure out is how to make the physical number of
displayed 'column names' in the main report and associated 'data fields'
in the sub report change based on the report data I need to show.

It's likely that you will have to design the report in code at run time.
This may require many lines of code. This is an example. It calls a few
functions in a GeneralFunctions Module and so is not a closed system as
shown:

Option Compare Database
Option Explicit

Const ReportName As String = "rptSchoolOrganizations"
Const ReportCaption As String = "School Organizations (right click for
menu)"
Const Spacing As Long = 57
Const StartField As Long = 6
Const Width As Long = 567

Private ClassStructure As ADODB.Recordset
Private OrganizationType As String

Public Sub ViewSchoolOrganizationsReportofActualClasses()
Dim Cancel As Integer
VerifyLogin Cancel
If Cancel = 1 Then Exit Sub
OrganizationType = "Actual"
ShowStatusMessage "Updating Actual Grade Split-Grade Designations"
UpDateGrade_SplitGradeDesignations ("tblActualClasses")
ViewSchoolOrganizationsReport
End Sub

Public Sub ViewSchoolOrganizationsReportofTheoreticalClasses()
Dim Cancel As Integer
VerifyLogin Cancel
If Cancel = 1 Then Exit Sub
OrganizationType = "Theoretical"
ShowStatusMessage "Updating Theoretical Grade Split-Grade Designations"
UpDateGrade_SplitGradeDesignations ("tblTheoreticalClasses")
ViewSchoolOrganizationsReport
End Sub

Sub ViewSchoolOrganizationsReport()
Dim Control As Control
Dim FieldName As String
Dim Height As Long
Dim Label As Label
Dim Left As Long
Dim Line As Line
Dim NewReportName As String
Dim NextTop As Long
Dim sql As String
Dim Report As Report
Dim TextBox As TextBox
Dim ReportWidth As Long
Dim z As Long

' -------------------------
' if the report is open
' ask that it be closed
' and exit
' -------------------------
If SysCmd(acSysCmdGetObjectState, acReport, ReportName) <> 0 Then
MsgBox "Please, close all reports and try again.", vbExclamation Or
vbOKOnly, "FFDBA"
GoTo ViewSchoolOrganizationsReportExit
End If

' -------------------------
' delete the report, is if exists
' -------------------------
On Error Resume Next
DoCmd.DeleteObject acReport, ReportName
On Error GoTo 0
' -------------------------
' set error handling
' -------------------------
On Error GoTo ViewSchoolOrganizationsReportErr

' -------------------------
' stop screen updating
' -------------------------
Application.Echo 0

' -------------------------
' get class structure
' -------------------------
GetClassStructure

' -------------------------
' create the report
' -------------------------
ShowStatusMessage "Creating School Organization Report"

Set Report = Application.CreateReport
With Report
.Caption = "School Organizations"
End With

' -------------------------
' create groupings
' -------------------------
Application.CreateGroupLevel Report.Name, "fldSchoolName", True, True
Application.CreateGroupLevel Report.Name, "fldProgramName", True, True
With Report.GroupLevel(0)
.KeepTogether = 1
End With
With Report.GroupLevel(1)
.KeepTogether = 1
End With

' -------------------------
' create the textbox fields that access the data in the table
' -------------------------
With ClassStructure
For z = StartField To .Fields.Count - 1
FieldName = .Fields(z).Name
Set TextBox = Application.CreateReportControl(Report.Name,
acTextBox, acDetail, , FieldName)
With TextBox
.Format = "#0;=#0;" & Chr$(34) & Chr$(34)
.Left = Left
.Name = "txt" & FieldName
.TextAlign = 3
.Width = Width
End With
Left = Left + Width
Next z
End With

' -------------------------
' set some report dimensions
' -------------------------
ReportWidth = Left
Report.Width = ReportWidth
Report.Section(acDetail).Height = TextBox.Height

' -------------------------
' design the page header
' -------------------------
Set Line = Application.CreateReportControl( _
Report.Name, acLine, acPageHeader, , , 0, _
Spacing, ReportWidth)
With Line
.BorderWidth = 0
.Name = "Line1"
NextTop = .Top + .Height + Spacing
End With

Set Label = Application.CreateReportControl( _
Report.Name, acLabel, acPageHeader, , , 0, NextTop)
With Label
.BorderStyle = 0
.Caption = "Halton District School Board"
.Name = "lblDistrictName"
.SizeToFit
.Width = ReportWidth
NextTop = .Top + .Height + Spacing
End With

Set Label = Application.CreateReportControl( _
Report.Name, acLabel, acPageHeader, , , 0, NextTop)
With Label
.BorderStyle = 0
.Caption = "School Organizations"
.Name = "lblSchoolOrganizations"
.SizeToFit
.Width = ReportWidth
NextTop = .Top + .Height + Spacing
End With

Set Line = Application.CreateReportControl( _
Report.Name, acLine, acPageHeader, , , 0, _
NextTop, ReportWidth)
With Line
.BorderWidth = 0
.Name = "Line2"
NextTop = .Top + .Height + Spacing
End With

Report.Section(acPageHeader).Height = NextTop

' -------------------------
' design the school grouping header
' -------------------------
Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel1Header, , , 0, _
Spacing, ReportWidth)
With Line
.BorderWidth = 3
.Name = "Line3"
NextTop = .Top + .Height + Spacing
End With

Set TextBox = Application.CreateReportControl( _
Report.Name, acTextBox, acGroupLevel1Header, , , 0, NextTop)
With TextBox
.BorderStyle = 0
.ControlSource = "fldSchoolName"
.Name = "txtSchoolName"
.SizeToFit
.Width = ReportWidth
NextTop = .Top + .Height + Spacing * 2
End With

Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel1Header, , , 0, _
NextTop, ReportWidth)
With Line
.BorderWidth = 3
.Name = "Line4"
NextTop = .Top + .Height + Spacing
End With

Report.Section(acGroupLevel1Header).Height = NextTop

' -------------------------
' design the school grouping footer
' -------------------------
Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel1Footer, , , 0, _
Spacing, ReportWidth)
With Line
.BorderWidth = 3
.Name = "Line5"
NextTop = .Top + .Height + Spacing
End With

Set TextBox = Application.CreateReportControl( _
Report.Name, acTextBox, acGroupLevel1Footer, , , 0, NextTop)
With TextBox
.BorderStyle = 0
.ControlSource = "= fldSchoolName & " & Chr(34) & " Totals" & Chr
(34)
.Name = "txtSumSchool"
.SizeToFit
.Width = ReportWidth
NextTop = .Top + .Height + Spacing
End With

Left = 0

With ClassStructure
For z = StartField To .Fields.Count - 1
FieldName = .Fields(z).Name
Set TextBox = Application.CreateReportControl(Report.Name,
acTextBox, acGroupLevel1Footer)
With TextBox
.ControlSource = "=Sum(" & FieldName & ")"
.Left = Left
.Name = "txt" & FieldName & "SumSchool"
.TextAlign = 3
.Top = NextTop
.Width = Width
Height = .Top + .Height
End With
Left = Left + Width
Next z
End With

NextTop = Height + Spacing

Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel1Footer, , , 0, _
NextTop, ReportWidth)
With Line
.BorderWidth = 3
.Name = "Line6"
NextTop = .Top + .Height + Spacing
End With

Report.Section(acGroupLevel1Footer).Height = NextTop

' -------------------------
' design the program grouping header
' -------------------------
Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel2Header, , , 0, _
Spacing, ReportWidth)
With Line
.BorderWidth = 0
.Name = "Line7"
NextTop = .Top + .Height + Spacing
End With

Set TextBox = Application.CreateReportControl( _
Report.Name, acTextBox, acGroupLevel2Header, , , 0, NextTop)
With TextBox
.BorderStyle = 0
.ControlSource = "fldProgramName"
.Name = "txtProgramName"
.SizeToFit
.Width = ReportWidth
NextTop = .Top + .Height + Spacing
End With

Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel2Header, , , 0, _
NextTop, ReportWidth)
With Line
.BorderWidth = 0
.Name = "Line8"
NextTop = .Top + .Height + Spacing
End With

Left = 0
With ClassStructure
For z = StartField To .Fields.Count - 1
FieldName = .Fields(z).Name
Set Label = Application.CreateReportControl(Report.Name,
acLabel, acGroupLevel2Header, , Replace(FieldName, "fld", ""))
With Label
.Left = Left
.Name = "lbl" & .Caption
.TextAlign = 3
.Top = NextTop
.Width = Width
Left = Left + Width
End With
Next z
End With

Report.Section(acGroupLevel2Header).Height = Height

' -------------------------
' design the program grouping footer
' -------------------------
Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel2Footer, , , 0, _
Spacing, ReportWidth)
With Line
.BorderWidth = 0
.Name = "Line9"
NextTop = .Top + .Height + Spacing
End With

Set TextBox = Application.CreateReportControl( _
Report.Name, acTextBox, acGroupLevel2Footer, , , 0, NextTop)
With TextBox
.BorderStyle = 0
.ControlSource = "= fldProgramName & " & Chr(34) & " Totals" & Chr
(34)
.Name = "txtSumProgram"
.SizeToFit
.Width = ReportWidth
NextTop = .Top + .Height + Spacing
End With

Left = 0

With ClassStructure
For z = StartField To .Fields.Count - 1
FieldName = .Fields(z).Name
Set TextBox = Application.CreateReportControl(Report.Name,
acTextBox, acGroupLevel2Footer)
With TextBox
.ControlSource = "=Sum(" & FieldName & ")"
.Left = Left
.Name = "txt" & FieldName & "SumProgram"
.TextAlign = 3
.Top = NextTop
.Width = Width
Height = .Top + .Height
End With
Left = Left + Width
Next z
End With

NextTop = Height + Spacing

Set Line = Application.CreateReportControl( _
Report.Name, acLine, acGroupLevel2Footer, , , 0, _
NextTop, ReportWidth)
With Line
.BorderWidth = 0
.Name = "Line10"
NextTop = .Top + .Height + Spacing
End With

Report.Section(acGroupLevel2Footer).Height = NextTop

' -------------------------
' set page footer grouping properties
' -------------------------
Set TextBox = Application.CreateReportControl(Report.Name, acTextBox,
acPageFooter, , , 0, Spacing * 2)
With TextBox
.ControlSource = "= " & Chr$(34) & "Page " & Chr$(34) & " & [Page]
& " & Chr$(34) & " of " & Chr$(34) & " & [Pages]"
.Name = "txtPage"
.TextAlign = 1
.Width = ReportWidth
NextTop = .Top + .Height + Spacing
End With
Set TextBox = Application.CreateReportControl(Report.Name, acTextBox,
acPageFooter, , , 0, NextTop + Spacing * 2)
With TextBox
.ControlSource = "= Now()"
.Format = "YYYY-MM-DD HH:NN"
.Name = "txtNow"
.TextAlign = 1
.Width = ReportWidth
NextTop = .Top + .Height + Spacing
End With

' -------------------------
' set some more report properties
' -------------------------
With Report
.Section(acPageFooter).Height = NextTop
.Caption = ReportCaption
.ShortcutMenuBar = "Report Preview"
.Width = ReportWidth
.RecordSource = "dbo.SpSchoolOrganizationReport"
.InputParameters = "@SchoolID int = " & Form_frmLogin.Login.Collect
(2)

NewReportName = .Name

End With

' -------------------------
' close and save the report
' -------------------------

DoCmd.Close acReport, Report.Name, acSaveYes

' -------------------------
' Rename the report
' -------------------------
DoCmd.Rename ReportName, acReport, NewReportName
' -------------------------
' View the report
' -------------------------
Application.Echo 1
ShowStatusMessage ReportCaption
With DoCmd
.OpenReport ReportName, acViewPreview
.ShowToolbar "Print Preview", acToolbarNo
.Maximize
End With
Reports(ReportName).ZoomControl = 0

ViewSchoolOrganizationsReportExit:
ShowStatusMessage
Exit Sub
ViewSchoolOrganizationsReportErr:
MsgBox Err.Description, vbCritical, "Number " & Err.Number
DoCmd.Close acReport, Report.Name, acSaveNo
Application.Echo 1
Resume ViewSchoolOrganizationsReportExit
End Sub

Private Sub GetClassStructure()
If Not ClassStructure Is Nothing Then Exit Sub
If OrganizationType = "Actual" Then
CreateRecordSet ClassStructure, "SpGetEmptyActualClassRecordet", ,
True
ElseIf OrganizationType = "Theoretical" Then
CreateRecordSet ClassStructure,
"SpGetEmptyTheoreticalClassRecordet", , True
End If
End Sub
 

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