Macrotized – Intelligent Office Automation https://macrotized.com An Intelligent Automation Platform for Office developers and professionals Tue, 01 Jun 2021 10:32:21 +0000 en-US hourly 1 https://wordpress.org/?v=6.7.1 https://i0.wp.com/macrotized.com/wp-content/uploads/2021/04/AutomationIcon.jpg?fit=32%2C32&ssl=1 Macrotized – Intelligent Office Automation https://macrotized.com 32 32 193501958 How to list out all the procedures that exist in an MS Access Module Using VBA https://macrotized.com/how-to-list-out-all-the-procedures-that-exist-in-an-ms-access-module-using-vba/ https://macrotized.com/how-to-list-out-all-the-procedures-that-exist-in-an-ms-access-module-using-vba/#comments Tue, 01 Jun 2021 10:31:46 +0000 https://macrotized.com/?p=401 This function will list out all the procedures and functions that exist in an MS Access module.

Public Function AllProcsInThisModule(ByVal strModulename As String, acc As Access.Application)
 
 Dim mdl As Module
 Dim lngCount As Long
 Dim lngCountDecl As Long
 Dim lngI As Long
 Dim strProcname As String
 Dim astrProcNames() As String
 Dim intI As Integer
 Dim strMsg As String
 Dim lngR As Long
 
 ' Open specified Module object.
 'acc.DoCmd.OpenModule strModuleName
 
 ' Return reference to Module object.
 Set mdl = acc.Modules(strModulename)
 
 ' Count lines in module.
 lngCount = mdl.CountOfLines
 
 ' Count lines in Declaration section in module.
 lngCountDecl = mdl.CountOfDeclarationLines
 
 ' Determine name of first procedure.
 strProcname = mdl.ProcOfLine(lngCountDecl + 1, lngR)
 
 ' Initialize counter variable.
 intI = 0
 
 ' Redimension array.
 ReDim Preserve astrProcNames(intI)
 
 ' Store name of first procedure in array.
 astrProcNames(intI) = strProcname
 
 ' Determine procedure name for each line after declarations.
 For lngI = lngCountDecl + 1 To lngCount
 ' Compare procedure name with ProcOfLine property value.
 If strProcname <> mdl.ProcOfLine(lngI, lngR) Then
 ' Increment counter.
 intI = intI + 1
 strProcname = mdl.ProcOfLine(lngI, lngR)
 ReDim Preserve astrProcNames(intI)
 ' Assign unique procedure names to array.
 astrProcNames(intI) = strProcname
 End If
 Next lngI
 
 'strMsg = "Procedures in module '" & strModuleName & "': " & vbCrLf & vbCrLf
 For intI = 0 To UBound(astrProcNames)
 strMsg = strMsg & intI + 1 & ". " & astrProcNames(intI) & vbCrLf
 Next intI
 
 ' Message box listing all procedures in module.
 AllProcsInThisModule = strMsg
End Function

This is a complimentary article written by the MAARS team for the MAARS user community. Code in this article drives the operation of MAARS (MS Access Application wRiting Software). MAARS is an intelligent automation program that speeds up MS Access Application Development by 10x, 20x or 100x times. To learn more about MAARS, click here.

Disclaimer:

Some information included in this article may have been sourced from other publicly available websites and blogs. In such cases, credit goes to those authors for the original ideas and thoughts, but we do take credit for putting valuable information together and improve the efficiency of other office developers.

]]>
https://macrotized.com/how-to-list-out-all-the-procedures-that-exist-in-an-ms-access-module-using-vba/feed/ 9 401
How to find all the Queries in an MS Access Database using VBA https://macrotized.com/how-to-find-all-the-queries-in-an-ms-access-database-using-vba/ https://macrotized.com/how-to-find-all-the-queries-in-an-ms-access-database-using-vba/#respond Tue, 01 Jun 2021 10:16:02 +0000 https://macrotized.com/?p=399 This procedure finds all the Queries in an MS Access Database. This prints out the name of each query plus the SQL behind each query.

Public Sub AllQueryDefs()
    Dim obj As QueryDef, dbs As DAO.Database
    Set dbs = CurrentDb
    For Each obj In dbs.QueryDefs
        
            If InStr(obj.Name, "~") = 0 Then
                Debug.Print obj.Name & " SQL - " & obj.SQL & vbNewLine & " ----------- " & vbNewLine
            End If
            

    Next obj
End Sub

This is a complimentary article written by the MAARS team for the MAARS user community. Code in this article drives the operation of MAARS (MS Access Application wRiting Software). MAARS is an intelligent automation program that speeds up MS Access Application Development by 10x, 20x or 100x times. To learn more about MAARS, click here.

Disclaimer:

Some information included in this article may have been sourced from other publicly available websites and blogs. In such cases, credit goes to those authors for the original ideas and thoughts, but we do take credit for putting valuable information together and improve the efficiency of other office developers.

]]>
https://macrotized.com/how-to-find-all-the-queries-in-an-ms-access-database-using-vba/feed/ 0 399
How to find all the Reports in an MS Access Database Using VBA https://macrotized.com/how-to-find-all-the-reports-in-an-ms-access-database-using-vba/ https://macrotized.com/how-to-find-all-the-reports-in-an-ms-access-database-using-vba/#respond Tue, 01 Jun 2021 10:06:43 +0000 https://macrotized.com/?p=396 This procedure finds all the Reports in an MS Access Database. This shows how many reports are in the database and prints out the source of each report. In order to print the source of each report, the report is opened in design mode.

Public Sub AllReports()
    Dim obj As AccessObject, dbs As Object
    Set dbs = Application.CurrentProject
    ' Search for open AccessObject objects in AllForms collection.
    MsgBox dbs.AllReports.Count
    For Each obj In dbs.AllReports
        'If obj.IsLoaded = True Then
            ' Print name of obj.
           ' Debug.Print obj.name & vbNewLine & "--------------"
           ' For Each prop In obj.Properties
            '    Debug.Print vbTab & prp.name & " = " & prp.Value
           ' Next
           DoCmd.OpenReport obj.Name, acViewDesign
            Debug.Print obj.Name & " RecordSource -" & Reports(obj.Name).RecordSource
           DoCmd.Close acReport, obj.Name
        'End If
    Next obj
End Sub

This is a complimentary article written by the MAARS team for the MAARS user community. Code in this article drives the operation of MAARS (MS Access Application wRiting Software). MAARS is an intelligent automation program that speeds up MS Access Application Development by 10x, 20x or 100x times. To learn more about MAARS, click here.

Disclaimer:

Some information included in this article may have been sourced from other publicly available websites and blogs. In such cases, credit goes to those authors for the original ideas and thoughts, but we do take credit for putting valuable information together and improve the efficiency of other office developers.

]]>
https://macrotized.com/how-to-find-all-the-reports-in-an-ms-access-database-using-vba/feed/ 0 396
How to find all the Modules in an MS Access databases using VBA https://macrotized.com/how-to-find-all-the-modules-in-an-ms-access-databases-using-vba/ https://macrotized.com/how-to-find-all-the-modules-in-an-ms-access-databases-using-vba/#respond Tue, 01 Jun 2021 09:59:38 +0000 https://macrotized.com/?p=394 This procedure finds all the modules in an MS Access Database. This shows how many modules are in the database and prints out the number of lines of code the module has as well as the code in that module.

Public Sub AllModules()
    Dim obj As AccessObject, dbs As Object, mdl As Module
    Set dbs = Application.CurrentProject
    ' Search for open AccessObject objects in AllModules collection.
    MsgBox dbs.AllModules.Count
    For Each obj In dbs.AllModules
        Set mdl = Modules(obj.Name)
            Debug.Print obj.Name & mdl.CountOfLines & vbNewLine & mdl.Lines(1, mdl.CountOfLines)
           
    Next obj
End Sub

This is a complimentary article written by the MAARS team for the MAARS user community. Code in this article drives the operation of MAARS (MS Access Application wRiting Software). MAARS is an intelligent automation program that speeds up MS Access Application Development by 10x, 20x or 100x times. To learn more about MAARS, click here.

Disclaimer:

Some information included in this article may have been sourced from other publicly available websites and blogs. In such cases, credit goes to those authors for the original ideas and thoughts, but we do take credit for putting valuable information together and improve the efficiency of other office developers.

]]>
https://macrotized.com/how-to-find-all-the-modules-in-an-ms-access-databases-using-vba/feed/ 0 394
How to find all the forms in an MS Access Database using VBA https://macrotized.com/how-to-find-all-the-forms-in-an-ms-access-database/ https://macrotized.com/how-to-find-all-the-forms-in-an-ms-access-database/#respond Tue, 01 Jun 2021 09:51:49 +0000 https://macrotized.com/?p=392 This procedure finds all the forms in an MS Access Database. This shows how many forms are in the database and prints out the source of each form. In order to print the source of each form, the form should be opened in design mode.

Public Sub AllForms()
    Dim obj As AccessObject, dbs As Object
    Set dbs = Application.CurrentProject
    ' Search for open AccessObject objects in AllForms collection.
    MsgBox dbs.AllForms.Count
    For Each obj In dbs.AllForms
        'If obj.IsLoaded = True Then
            ' Print name of obj.
           ' Debug.Print obj.name & vbNewLine & "--------------"
           ' For Each prop In obj.Properties
            '    Debug.Print vbTab & prp.name & " = " & prp.Value
           ' Next
           DoCmd.OpenForm obj.Name
            Debug.Print obj.Name & " RecordSource -" & Forms(obj.Name).RecordSource
           DoCmd.Close acForm, obj.Name
        'End If
    Next obj
End Sub

This is a complimentary article written by the MAARS team for the MAARS user community. Code in this article drives the operation of MAARS (MS Access Application wRiting Software). MAARS is an intelligent automation program that speeds up MS Access Application Development by 10x, 20x or 100x times. To learn more about MAARS, click here.

Disclaimer:

Some information included in this article may have been sourced from other publicly available websites and blogs. In such cases, credit goes to those authors for the original ideas and thoughts, but we do take credit for putting valuable information together and improve the efficiency of other office developers.

]]>
https://macrotized.com/how-to-find-all-the-forms-in-an-ms-access-database/feed/ 0 392
How to add controls to an MS Access Report programmatically using VBA https://macrotized.com/how-to-add-controls-to-an-ms-access-report-programmatically-using-vba/ https://macrotized.com/how-to-add-controls-to-an-ms-access-report-programmatically-using-vba/#respond Fri, 28 May 2021 10:55:26 +0000 https://macrotized.com/?p=390 This procedure (sub) will add all the fields (text boxes) found in the underlying source table to the report programmatically using VBA. This also adds the proper buttons to the report output.

Sub AddControlsToTheReportOfThisTable(tblName As String, P_L As String)
Dim rpt As Report, ctl As Control, ctlLabel As Control, ctlLabelHeader As Control, ctrlName As String, ctrlSource As String
Dim rptName As String, mdl As Module, fldCounter As Integer, colCounter As Integer
Dim shortButtonL As Integer, LongButtonL As Integer, startPoscontrols As Integer, buttonH As Integer, buttonT As Integer
Dim numFields As Integer, paperWidthInInch As Integer, hH As Integer, fH As Integer, drHeight As Integer, fldsPerRow As Integer

startPoscontrols = 100 'twips
shortButtonL = 400
LongButtonL = 2000
buttonH = 420
buttonT = 50
paperWidthInInch = 10
hH = 400
fH = 360
drHeight = 400
fldsPerRow = 7
'Name    Value   Description
'acViewDesign    1   Design view
'acViewLayout    6   Layout view
'acViewNormal    0   (Default) Normal view
'acViewPivotChart    4   PivotChart view
'acViewPivotTable    3   PivotTable view
'acViewPreview   2   Print Preview
'acViewReport    5   Report view


'None    0   (Default) The current section (the section for which you're setting the property) is printed on the current page.
'Before Section  1   The current section is printed at the top of a new page.
'After Section   2   The section immediately following the current section is printed at the top of a new page.
'Before & After  3   The current section is printed at the top of a new page, and the next section is printed at the top of a new page.

'Name    Value   Description
'acDetail    0   (Default) Detail section
'acFooter    2   Form or report footer
'acGroupLevel1Footer 6   Group-level 1 footer (reports only)
'acGroupLevel1Header 5   Group-level 1 header (reports only)
'acGroupLevel2Footer 8   Group-level 2 footer (reports only)
'acGroupLevel2Header 7   Group-level 2 header (reports only)
'acHeader    1   Form or report header
'acPageFooter    4   Page footer
'acPageHeader    3   Page header




'Dim tblName$
Dim rs As DAO.Recordset
Dim list$, n%
Dim msg$
Dim procHeader As String, SQLHeader As String, SQLData As String
Dim iType%

Set rs = CurrentDb.OpenRecordset(tblName)
' Check how many fields are in the table
With rs
    numFields = .Fields.Count
End With

rptName = "rpt" & tblName & P_L
DoCmd.OpenReport ReportName:=rptName, View:=acDesign
Set rpt = Reports(rptName)

colCounter = 1
leftPos = rpt.WindowLeft + 1440 / 2
toppos = rpt.WindowTop + 100
Set mdl = rpt.Module

With rpt
    


  .Section(1).Height = hH
  .Section(2).Height = fH
  
    'Place the labels in the header section
    If ControlExistsInReport("lblReportHeader", rptName) = False Then
         Set ctlLabel = CreateReportControl(rptName, acLabel, Section:=acHeader, Width:=rpt.Width / 2, _
            Height:=(hH * 0.9), Left:=rpt.Width / 3, Top:=0)
            ctlLabel.Name = "lblReportHeader"
            ctlLabel.Caption = StrConv(Replace(tblName, "tbl", ""), vbProperCase) & " Report"
            ctlLabel.ControlTipText = "Double Click to See Print Preview of the Report"
            ctlLabel.FontSize = 18
            Call mdl.InsertLines(3, "Dim vCounter as Integer, gRecordsToPrintPerPage as Integer")
            
            lngReturn = mdl.CreateEventProc("DblClick", ctlLabel.Name)
            mdl.InsertLines lngReturn + 1, vbTab & "gRecordsToPrintPerPage = CInt(InputBox(""How many records to print per page?"", ""Enter Records"", 2))"
            mdl.InsertLines lngReturn + 2, vbTab & "DoCmd.OpenReport Me.name, acViewPreview"
        
    End If
    
 
  
    
    .Section(1).BackColor = RGB(140, 60, 80)
    .Section(2).BackColor = RGB(140, 60, 80)
    'MsgBox .Section(2).Height
    .Section(2).Height = 500
    
End With

Set rs = CurrentDb.OpenRecordset([tblName])

With rs
   ' MsgBox "There are " & .Fields.Count & " columns in " & tblName
    numFields = .Fields.Count

For n% = 0 To .Fields.Count - 1
fldCounter = fldCounter + 1
    list$ = list$ & .Fields(n%).Name & Chr(44) & dmwFieldType(.Fields(n%).Type) & vbNewLine
    iType% = .Fields(n%).Type
    'For Each prpLoop In .Fields(n%).Properties
     '   MsgBox .Fields(n%).Size
    
    Select Case iType%
    Case 1
        fldType$ = "Boolean"
    Case 2
        fldType$ = "Byte"
    Case 3
        fldType$ = "Integer"
    Case 4
        fldType$ = "Long"
    Case 5
        fldType$ = "Currency"
    Case 6
        fldType$ = "Single"
    Case 7
        fldType$ = "Double"
    Case 8
        fldType$ = "Date" '"Date/Time"
    Case 9
        fldType$ = "Binary"
    Case 10
        fldType$ = "String" '"Short Text"
    Case 11
        fldType$ = "Long Binary"
    Case 12
        fldType$ = "String" '"Long Text"
    Case 15
        fldType$ = "GUID"
    Case 16
        fldType$ = "Double" '"Large Number"
    Case 101
        fldType$ = "Attachment"
    Case Else
        fldType$ = "NOT RECOGNISED"
    End Select
    
    ctrlName = fldType$ & .Fields(n%).Name
    ctrlSource = .Fields(n%).Name
    
    If ControlExistsInReport(ctrlName, rptName) = False Then
        
    If .Fields.Count <= 20 Then
        'Place the data entry fields in the detail section
        w = ((rpt.Width) - 1 * 1440) / (fldsPerRow) '(numFields)
        Set ctl = CreateReportControl(ReportName:=rptName, ControlType:=acTextBox, ColumnName:=ctrlSource, _
        Left:=leftPos, Top:=toppos, Width:=w, Height:=drHeight)
        ctl.Name = ctrlName
                    
        'Place the labels in the header section
         Set ctlLabel = CreateReportControl(rptName, acLabel, Section:=acPageHeader, Width:=w, _
            Height:=drHeight, Left:=leftPos, Top:=toppos)
            ctlLabel.Name = ctrlSource
            ctlLabel.Caption = ctrlSource
 
            leftPos = leftPos + w 'rpt.Width / (numFields + 1) '+ 30
            
            If (fldCounter Mod 7) = 0 Then
                leftPos = rpt.WindowLeft + 1440 / 2
                toppos = toppos + drHeight
            End If
            
    Else ' More then 7 columns in the table, so create a single record Report
            
            'Place the labels first in the detail section
            lblWidth = rpt.Width / numFields
            w = ((rpt.Width) - 1 * 1440) / (fldsPerRow)
            Set ctlLabel = CreateReportControl(rptName, acLabel, Section:=acDetail, Width:=w, _
            Height:=420, Left:=leftPos, Top:=toppos)
            ctlLabel.Name = ctrlSource
            ctlLabel.Caption = fldCounter & ". " & ctrlSource
            
            'Place the data entry field next to the label in the detail section
            Set ctl = CreateReportControl(ReportName:=rptName, ControlType:=acTextBox, ColumnName:=ctrlSource, _
            Left:=leftPos + w, Top:=toppos, Width:=w, Height:=420)
            ctl.Name = ctrlName
                    
            
            toppos = toppos + 420
                       
           'leftPos = leftPos + w 'rpt.Width / (numFields + 1) '+ 30
            
            If fldCounter Mod 25 = 0 Then
                colCounter = colCounter + 1
                leftPos = leftPos + (w * 2) + 100
                toppos = rpt.WindowTop + 100
            End If
            
    End If
    
    Else
        MsgBox "Control " & ctrlName & " already exists in Report " & rptName
    End If
    
   

Next n%
End With

rpt.Caption = "Auto Created Report - " & StrConv(tblName, vbProperCase)

If fldCounter <= 7 Then
    rpt.DefaultView = 1 ' Continuous Report
Else
    rpt.DefaultView = 0 ' Single Report
End If

'Add Procedures to the Report Module
    'MsgBox mdl.CountOfLines
    
    Dim startline As Integer
    Dim strProc As String, strProcBody As String
    strProc = "Detail_Format"
    If ProcedureExistsInModule(strProc, "Report_" & rptName) Then ' First Parameter - Procedure name, second parameter - module name
        
        startline = mdl.ProcStartLine(strProc, vbext_pk_Proc)
        totalLinesInModule = mdl.CountOfLines
        totalLinesInProc = mdl.ProcCountLines(strProc, vbext_pk_Proc)
        MsgBox strProc & " Proc already exists. Starts at line " & startline & ", contains " & totalLinesInProc & " lines"
    Else
        lngReturn = mdl.CreateEventProc("Format", "Detail") '  "format" is the event, Detail is the name of the control
        ' Insert text into body of procedure.
        'mdl.InsertLines lngReturn + 1, vbTab & "MsgBox ""Way so cool!"""
        strProcBody = "If vCounter = gRecordsToPrintPerPage Then" & vbCrLf & vbTab & "Me.Section(acDetail).ForceNewPage = 1"
        strProcBody = strProcBody & vbCrLf & vbTab & "vCounter = 0 " & vbCrLf & "Else " & vbCrLf & vbTab & "Me.Section(acDetail).ForceNewPage = 0"
        strProcBody = strProcBody & vbCrLf & "End if " & vbCrLf & vbTab & "vCounter = vCounter + 1"

        mdl.InsertLines lngReturn + 2, strProcBody
        'rpt.Section(acReportHeader).Visible = True
    End If
    
   ' MsgBox mdl.CountOfLines
    strProc = "Report_Open"
   If ProcedureExistsInModule(strProc, "Report_" & rptName) Then
       ' MsgBox "Report_Open Proc already exists"
        
        startline = mdl.ProcStartLine(strProc, vbext_pk_Proc)
        totalLinesInModule = mdl.CountOfLines
        totalLinesInProc = mdl.ProcCountLines(strProc, vbext_pk_Proc)
        MsgBox strProc & " Proc already exists. Starts at line " & startline & ", contains " & totalLinesInProc & " lines"
    Else
        lngReturn = mdl.CreateEventProc("Open", "Report")
        ' Insert text into body of procedure.
        'mdl.InsertLines lngReturn + 1, vbTab & "MsgBox ""Way so cool!"""
        mdl.InsertLines lngReturn + 1, vbTab & " vCounter=1 "
        'rpt.Section(acReportHeader).Visible = True
    End If
    
    'MsgBox mdl.CountOfLines
    

    DoCmd.Save acReport, rptName
    DoCmd.Close acReport, rptName, acSaveYes
    DoCmd.Restore
    'DoCmd.OpenReport rptName, acViewPreview
    DoCmd.OpenReport rptName, acViewDesign
    DoCmd.Close acReport, rptName, acSaveYes
End Sub

This is a complimentary article written by the MAARS team for the MAARS user community. Code in this article drives the operation of MAARS (MS Access Application wRiting Software). MAARS is an intelligent automation program that speeds up MS Access Application Development by 10x, 20x or 100x times. To learn more about MAARS, click here.

Disclaimer:

Some information included in this article may have been sourced from other publicly available websites and blogs. In such cases, credit goes to those authors for the original ideas and thoughts, but we do take credit for putting valuable information together and improve the efficiency of other office developers.

]]>
https://macrotized.com/how-to-add-controls-to-an-ms-access-report-programmatically-using-vba/feed/ 0 390
How to create a new report for an MS Access table programmatically using VBA https://macrotized.com/how-to-create-a-new-report-for-an-ms-access-table-programmatically-using-vba/ https://macrotized.com/how-to-create-a-new-report-for-an-ms-access-table-programmatically-using-vba/#respond Fri, 28 May 2021 10:34:00 +0000 https://macrotized.com/?p=387 This procedure (sub) will create a report for the given table dynamically by adding all the fields found in the table. If “_P” is passed to the 2nd parameter, it will create report in portrait report, if “_L” is passed, it will create a landscape report.

Public Sub CreateNewReportForThisTable(tblName As String, P_L As String)
 Dim rpt As Report, rptNameJustCreated As String, rptNameFinal As String
 rptNameFinal = "rpt" & StrConv(tblName, vbProperCase) & P_L
 
 If reportExistsInTheDatabase(rptNameFinal) Then
    MsgBox rptNameFinal & " already exists in the database"
    'DoCmd.DeleteObject acForm, rptNameJustCreated
 Else
    Set rpt = CreateReport(, "rptBlankReport")
    rptNameJustCreated = rpt.Name
    'MsgBox rptNameJustCreated
    
    With rpt
        .RecordSource = tblName
        .Section(0).Height = 400 ' Form Detail
        .Section(1).Visible = True  ' Form Header
        .Section(1).Height = 400 ' Form Header
        '.Section(1).DisplayWhen = 0  ' Form Header
        '.Section(2).Height = 100 ' Form Footer
        If P_L = "_L" Then
            .Printer.Orientation = acPRORLandscape
            .Width = 10 * 1440 ' 10 Inch, Leave 1 Inch for Margins
        Else
            .Printer.Orientation = acPRORPortrait
            .Width = 7.5 * 1440 ' 7.5 Inch, Leave 1 Inch for Margins
        End If
        
    End With
    
    DoCmd.Save acReport, rptNameJustCreated
    DoCmd.Close acReport, rptNameJustCreated
    DoCmd.Restore
    DoCmd.Rename rptNameFinal, acReport, rptNameJustCreated
    
    'Add Controls to the Report that was just created
    Call AddControlsToTheReportOfThisTable(tblName, P_L)
 'This procedure does most of the work
    
 End If
 
End Sub

This is a complimentary article written by the MAARS team for the MAARS user community. Code in this article drives the operation of MAARS (MS Access Application wRiting Software). MAARS is an intelligent automation program that speeds up MS Access Application Development by 10x, 20x or 100x times. To learn more about MAARS, click here.

Disclaimer:

Some information included in this article may have been sourced from other publicly available websites and blogs. In such cases, credit goes to those authors for the original ideas and thoughts, but we do take credit for putting valuable information together and improve the efficiency of other office developers.

]]>
https://macrotized.com/how-to-create-a-new-report-for-an-ms-access-table-programmatically-using-vba/feed/ 0 387
How MAARS creates the Dashboard Form programmatically using VBA https://macrotized.com/how-maars-creates-the-dashboard-form-programmatically-using-vba/ https://macrotized.com/how-maars-creates-the-dashboard-form-programmatically-using-vba/#respond Fri, 28 May 2021 10:21:49 +0000 https://macrotized.com/?p=385 This function will ask the user to provide a name for the application dashboard and it will create the form, set the height to 4 inches tall. It only creates the form by using another form called “frmBlankForm” as a template and does not add any controls to the dashboard form.

Public Function CreateDashboardForm() As String
' Purpose: This function creates a new MS Access Form to be used as the Dashboard in MAARS, using VBA by copying another form
 ' Change the data source fo the new created form to the given table in tblName
 
 Dim frm As Form, frmNameJustCreated As String, frmNameFinal As String
 'Ask the user for the name of the dashboard form
 
 tblName = InputBox("Please enter the name of your new dashboard form", "Create New Generic Form", "Dashboard")

 frmNameFinal = "frm" & tblName
 
 If tblName = "" Then ' If the user did not give a name, exit the function
    CreateNewGenericForm = ""
    Exit Function
 Else
 
 If formExistsInTheDatabase(frmNameFinal) Then ' Another form already exists with the given name, so just inform the user
    MsgBox frmNameFinal & " already exists in the database"
    'DoCmd.DeleteObject acForm, frmNameJustCreated
 Else
    Set frm = CreateForm(, "frmBlankForm")
    frmNameJustCreated = frm.Name ' Create the new form as Form1 or Form2 etc.
    'MsgBox frmNameJustCreated
    
    With frm
        '.RecordSource = tblName
        .Width = 1440 * 11
        .Section(0).Height = 1440 * 4 ' Form Detail - set the height to 4 inch
        .Section(1).Visible = True  ' Form Header
        .Section(1).Height = 400 ' Form Header
        '.Section(1).DisplayWhen = 0  ' Form Header
        '.Section(2).Height = 100 ' Form Footer
        
    End With
    
    DoCmd.Save acForm, frmNameJustCreated
    DoCmd.Close acForm, frmNameJustCreated
    DoCmd.Restore
    DoCmd.Rename frmNameFinal, acForm, frmNameJustCreated
    CreateDashboardForm = frmNameFinal
    
 End If
 
 End If
 
End Function

This is a complimentary article written by the MAARS team for the MAARS user community. Code in this article drives the operation of MAARS (MS Access Application wRiting Software). MAARS is an intelligent automation program that speeds up MS Access Application Development by 10x, 20x or 100x times. To learn more about MAARS, click here.

Disclaimer:

Some information included in this article may have been sourced from other publicly available websites and blogs. In such cases, credit goes to those authors for the original ideas and thoughts, but we do take credit for putting valuable information together and improve the efficiency of other office developers.

]]>
https://macrotized.com/how-maars-creates-the-dashboard-form-programmatically-using-vba/feed/ 0 385
How to transfer a table (definition plus data) from one Access database to another using VBA https://macrotized.com/how-to-transfer-a-table-structure-definition-from-one-access-database-to-another-using-vba/ https://macrotized.com/how-to-transfer-a-table-structure-definition-from-one-access-database-to-another-using-vba/#comments Sat, 15 May 2021 11:44:04 +0000 https://macrotized.com/?p=171 This procedure will transfer a table definition plus data from one database to another. Manually copying objects such as tables, forms, reports, modules etc from one database to another database is simple but unnecessary and time consuming. This can be achieved quickly with these few lines of code. This code is used in MAARS implementation. Feel to free use it in your own program, however, please give proper credit to the MAARS team.

Public Sub TransferATableStructureAndDataToAnotherDB(srcTableName As String, destTableName As String, _
destDbFullPath As String)
   'Export only the table definition to the destination database
   If Dir(destDbFullPath) <> "" Then
    DoCmd.TransferDatabase acExport, "Microsoft Access", destDbFullPath, acTable, srcTableName, destTableName, False
   End If

End Sub

This is a complimentary article written by the MAARS team for the MAARS user community. Code in this article drives the operation of MAARS (MS Access Application wRiting Software). MAARS is an intelligent automation program that speeds up MS Access Application Development by 10x, 20x or 100x times. To learn more about MAARS, click here.

Disclaimer:

Some information included in this article may have been sourced from other publicly available websites and blogs. In such cases, credit goes to those authors for the original ideas and thoughts, but we do take credit for putting valuable information together and improve the efficiency of other office developers.

]]>
https://macrotized.com/how-to-transfer-a-table-structure-definition-from-one-access-database-to-another-using-vba/feed/ 27 171
How to transfer a Report from one Access database to another Access database using VBA https://macrotized.com/how-to-transfer-a-report-from-one-access-database-to-another-access-database-using-vba/ https://macrotized.com/how-to-transfer-a-report-from-one-access-database-to-another-access-database-using-vba/#respond Sat, 15 May 2021 11:31:14 +0000 https://macrotized.com/?p=168 This procedure will transfer an entire module from one database to another. Manually copying objects such as tables, forms, reports, modules etc. from one database to another database is simple but unnecessary and time consuming. This can be achieved quickly with these few lines of code. This code is used in MAARS implementation. Feel to free use it in your own program, however, please give proper credit to the MAARS team.

Public Sub TransferAReportToAnotherDB(srcReportName As String, destReportName As String, destDbFullPath As String)
   'Export only the Report definition to new database, given in  destDbFullPath parameter
   If Dir(destDbFullPath) <> "" Then
    DoCmd.TransferDatabase acExport, "Microsoft Access", destDbFullPath, acReport, srcReportName, destReportName, True
   End If
   
End Sub

This is a complimentary article written by the MAARS team for the MAARS user community. Code in this article drives the operation of MAARS (MS Access Application wRiting Software). MAARS is an intelligent automation program that speeds up MS Access Application Development by 10x, 20x or 100x times. To learn more about MAARS, click here.

Disclaimer: Some information included in this article may have been sourced from other publicly available websites and blogs. In such cases, credit goes to those authors for the original ideas and thoughts, but we do take credit for putting valuable information together and improve the efficiency of other office developers.

]]>
https://macrotized.com/how-to-transfer-a-report-from-one-access-database-to-another-access-database-using-vba/feed/ 0 168