Showing posts with label access. Show all posts
Showing posts with label access. Show all posts

Wednesday, 4 December 2013

VBA Modules: Access: accUtils v2.00

Read this for full information on these modules

Kudos to a number of different people who've found similar solutions...

v1.00: acU_RelinkTables
Does a find & replace in linked tablesCross-posted.  Not sure why it took me so long to find the answer to this problem, but it did.... so after 5 years of manually updating linked tables I finally got the answer.
v1.01 improved messaging, case sensitivity bugfix

v2.00: acU_ChangeQueryPaths
Does a find & replace in SQL in all queries.


'accUtils
'v2.00 2014-01-16 13:46

'===========================================================================
' HELP CONTACT
'===========================================================================
' Code is provided without warranty and can be stolen and amended as required.
'   Tom Parish
'   TJP@tomparish.me.uk
'   http://baldywrittencod.blogspot.com / www.baldmosher.com
'   DGF Help Contact: see BPMHelpContact module
'=========================================================================

'===========================================================================
' accUtils
'===========================================================================
'   Various time-saving utilities for Access databases
'

'===========================================================================
' Additional modules required:
'===========================================================================
'   None
'

'=========================================================================
' VERSION HISTORY
'=========================================================================
'v2.00 2014-01-16 13:46 - added acU_ChangeQueryPaths (does a find & replace in all queries)
'v1.02 2013-12-05 14:18 - acU_RelinkTables, added Debug.Print for missing tables
'v1.01 2013-12-04 15:06 - acU_RelinkTables, bugfix for case sensitivity, added t count, improved msgboxes
'v1.00 2013-12-04 14:31 - added acU_RelinkTables (does a find & replace in linked tables)

Option Compare Database

Public Sub acU_RelinkTables(ByVal OldBasePath As String, ByVal NewBasePath As String _
    , Optional ByVal AlsoChangeQueries As Boolean = True)
'v1.02 2013-12-05 14:18 - added Debug.Print for missing tables
'v1.01 2013-12-04 15:06 - bugfix for case sensitivity, added t count, improved msgboxes
'v1.00 2013-12-04 14:31 - original version
'pass old & new path to update all linked tables
'and it will go through all the tables in your database and link them to the new location
'Original source: Written by John Hawkins 20/9/99 www.fabalou.com
'via http://database.ittoolbox.com/groups/technical-functional/access-l/how-to-programme-the-linked-table-manager-using-vba-in-ms-access-5185870
'Syntax:
'  acU_RelinkTables("\\OldShare\FolderName\", "\\NewShare\FolderName\)

Dim Dbs As Database
Dim Tdf As TableDef
Dim Tdfs As TableDefs
Dim TdfCurrentPath As String
Dim t As Integer, u As Integer  'NB: practical limit of 65536 linked tables
Dim pp As String, tt As String  'for msgboxes

Set Dbs = CurrentDb
Set Tdfs = Dbs.TableDefs

Screen.MousePointer = 11  'shows as "working"
'Loop through the tables collection
For Each Tdf In Tdfs
    If Tdf.SourceTableName <> "" Then 'If the table source is other than a base table
        TdfCurrentPath = Tdf.Connect
        If InStr(UCase(TdfCurrentPath), UCase(OldBasePath)) > 0 Then  'If the current path needs to be changed
            t = t + 1   'count tables processed
On Error Resume Next
            Tdf.RefreshLink 'Refresh the link
            If Err = 3011 Then GoTo OriginalTdfError    'bypasses change if current linked table isn't found
            Tdf.Connect = Replace(TdfCurrentPath, OldBasePath, NewBasePath)   'Set the new source
            Tdf.RefreshLink 'Refresh the link
            If Err = 3011 Then GoTo EscapeOnError    'likely means error in new path - could be critical
            u = u + 1   'count tables updated
On Error GoTo 0
        End If
    End If
OriginalTdfError:
If Err = 3011 Then Debug.Print "Error 3011:  " & Tdf.Name & vbLf & TdfCurrentPath
Next 'Goto next table

pp = u & " tables have been relinked from " & OldBasePath & " to " & NewBasePath
If t > u Then pp = pp & vbLf & vbLf & "(" & t - u & " were not updated successfully because the original table was missing)"
tt = "Tables Relinked"

Screen.MousePointer = 0
MsgBox pp, vbInformation, tt

Exit Sub
EscapeOnError:
pp = "Possible major error: please ensure OldBasePath and NewBasePath are correct - you will now be returned to Debug"
tt = "WARNING"
MsgBox pp, vbExclamation, tt
On Error GoTo 0
Tdf.Connect = TdfCurrentPath 'return to original
Tdf.RefreshLink 'Refresh the link - errors here means the table was missing before... this needs to be resolved
'NB: to continue from where you left off, drag arrow up to Next
End Sub

Public Sub acU_ChangeQueryPaths(ByVal OldBasePath As String, ByVal NewBasePath As String)
'v2.00 2014-01-16 13:46 - original version
'pass old & new path to update all queries
'Original source: acU_RelinkTables
'Syntax:
'  acU_ChangeQueryPaths("\\OldShare\FolderName\", "\\NewShare\FolderName\)

Dim Dbs As Database
Dim Qdf As QueryDef
Dim Qdfs As QueryDefs
Dim QdfOldSQL As String, QdfNewSQL As String
Dim q As Integer 'NB: practical limit of 65536 queries
Dim pp As String, tt As String  'for msgboxes

If Right(OldBasePath, 1) = "\" And Right(NewBasePath, 1) = "\" Then
    pp = "This will Find & Replace in all queries.  There is no validation for this.  Use with caution.  To Undo, simply re-run to correct the error." _
        & vbLf & vbLf & "find:          " & OldBasePath & vbLf & "replace:    " & NewBasePath
    tt = "WARNING"
    If MsgBox(pp, vbExclamation Or vbOKCancel, tt) = vbCancel Then Exit Sub
Else
    pp = "Your old and new paths must end with ""\"".  Otherwise, errors may occur.  Will now Exit." _
        & vbLf & vbLf & "find:          " & OldBasePath & vbLf & "replace:    " & NewBasePath
    tt = "CRITICAL WARNING"
    MsgBox pp, vbCritical, tt
    Exit Sub
End If

Set Dbs = CurrentDb
Set Qdfs = Dbs.QueryDefs

Screen.MousePointer = 11  'shows as "working"
For Each Qdf In Qdfs
    QdfOldSQL = Qdf.SQL
    QdfNewSQL = Replace(QdfOldSQL, OldBasePath, NewBasePath)
    If QdfOldSQL <> QdfNewSQL Then
        q = q + 1
        Qdf.SQL = QdfNewSQL
    End If
Next 'Goto next query

pp = q & " queries have been updated from " & OldBasePath & " to " & NewBasePath
tt = "Queries Updated"

Screen.MousePointer = 0
MsgBox pp, vbInformation, tt

End Sub

Friday, 29 November 2013

VBA Modules: Access: accPostCodes v1.03

Read this for full information on these modules


I wrote this module to help me out processing and extracting GB post codes, which can have a number of combinations:

A1 2BC
A12 3BC
AB1 2CD
AB12 3CD
AB1C 2DE

accPostCodeExtract is probably the most useful function here, as it will extract the post code from the end of a long address string.  There are options to work with most source string formats.  By default, the result will be padded with spaces to length = 8, e.g. "AB1  2CD"

accPostCodePrefix extracts the post code "town", e.g. "AB" from "AB1 2CD"
accPostCodePrefixWithNumber extracts the full post code prefix, e.g. "AB1" from "AB1 2CD"


'accPostCodes
'v1.03 2013-11-29 13:03

'===========================================================================
' HELP CONTACT
'===========================================================================
' Code is provided without warranty and can be stolen and amended as required.
'   Tom Parish
'   TJP@tomparish.me.uk
'   http://baldywrittencod.blogspot.com/2013/11/vba-modules-access-accpostcodes.html
'   DGF Help Contact: see BPMHelpContact module
'=========================================================================

'   v1.03   accPostCodeExtract: bugfix where original post code already padded to len=8
'   v1.02   accPostCodeExtract: added bPadResult option, bugfix where string is just post code
'   v1.01   added accPostCodeExtract
'   v1.00   original version

Option Explicit
Option Compare Database

Function accPostCode(ByRef PCode, Optional ByVal FWSrcSys) As String
'v1.00 2013-11-29 11:53

Dim sPCode As String, sFWsys As String
On Error Resume Next
sPCode = PCode
sFWsys = FWSrcSys
On Error GoTo 0

If sFWsys = "LO" Then Exit Function

'extract "GB/" from start of NFE PCode
Dim b As Byte
b = InStr(sPCode, "/")
sPCode = Mid(sPCode, b + 1, Len(sPCode))

If sPCode = "" Or sPCode = "0" Or sPCode = "." Or sPCode = "#" Then Exit Function

accPostCode = sPCode

End Function

Function accPostCodePrefix(ByRef PCode, Optional ByVal FWSrcSys) As String
'v1.00 2013-11-29 11:53
'checks first 1-2 characters for alpha prefix

Dim sPCode As String, sFWsys As String
On Error Resume Next
sPCode = PCode
sFWsys = FWSrcSys
On Error GoTo 0

If sFWsys = "LO" Then Exit Function

Dim s As String
sPCode = accPostCode(sPCode)
If sPCode = "" Then Exit Function
s = Left(sPCode, 1)
If IsNumeric(s) Then Exit Function Else accPostCodePrefix = s
s = Mid(sPCode, 2, 1)
If IsNumeric(s) Then Exit Function Else accPostCodePrefix = accPostCodePrefix & s

End Function

Function accPostCodePrefixWithNumber(ByVal PCode, Optional ByVal FWSrcSys) As String
'v1.00 2013-11-29 11:53
'checks first 2 characters for alpha prefix then checks following 2-3 chars for numeric

Dim sPCode As String, sFWsys As String
On Error Resume Next
sPCode = PCode
sFWsys = FWSrcSys
On Error GoTo 0

If sFWsys = "LO" Then Exit Function

Dim b As Byte, APfx As String, ANPfx As String
APfx = accPostCodePrefix(sPCode)
If APfx = "" Then Exit Function
b = InStr(sPCode, " ")
If b > 0 Then
'just use characters before space
    ANPfx = Left(sPCode, b - 1)
Else
'no space, deduce logically
'e.g. for AB123CD need AB12, take APfx plus all except last following numeric character
    ANPfx = APfx & Mid(sPCode, Len(APfx) + 1, 3)
    'e.g. AB123 or AB12C or AB1C2
    If ANPfx = sPCode Then
    'e.g. AB12[] so only prefix anyway
    ElseIf IsNumeric(Mid(ANPfx, Len(ANPfx), 1)) Then
    'e.g. AB123[CD] so AB12 3CD
        ANPfx = Left(ANPfx, Len(ANPfx) - 1)
    ElseIf IsNumeric(Mid(ANPfx, Len(ANPfx) - 1, 1)) Then
    'e.g. AB12C[D] so AB1 2CD
        ANPfx = Left(ANPfx, Len(ANPfx) - 2)
    ElseIf IsNumeric(Mid(ANPfx, 3, 1)) And Not IsNumeric(Mid(ANPfx, 4, 1)) Then
    'e.g. AB1C2[DE] so AB1C 2DE
        ANPfx = Left(ANPfx, Len(ANPfx) - 1)
    Else
    'cannot identify
        ANPfx = ""
    End If
End If

accPostCodePrefixWithNumber = ANPfx

End Function

Function accPostCodeExtract(ByVal FullAddressString, Optional ByVal bPostCodeNoSpace As Boolean = False _
    , Optional ByVal bCommaSeparated As Boolean = False, Optional bPadResult As Boolean = True) As String
'v1.03 2013-11-29 13:03
'extracts the post code from the end of a long address string (after the last-but-one space [or comma])
'e.g. "CITY, County, AB12 3CD" becomes "AB12 3CD"
'NB: with "AB123CD" post code formats, use bPostCodeNoSpace = True
'NB: with "City,County,AB12 3CD" format strings, use bCommaSeparated = True
'NB: to pad result to fixed 8 characters, use bPadResult = True

On Error Resume Next

Dim FullString As String
FullString = FullAddressString
If FullString = "" Then Exit Function

Dim sSearchString As String, sCount As Byte
If bCommaSeparated Then
    sSearchString = ","
    sCount = 1
Else
    sSearchString = " "
    If bPostCodeNoSpace Then sCount = 1 Else sCount = 2
    While InStr(FullString, "  ") > 0
        FullString = Replace(FullString, "  ", " ")
    Wend
End If

Dim findspaces() As Integer, f As Integer, fCount As Byte
fCount = 1
While InStr(f + 1, FullString, sSearchString) > 0
ReDim Preserve findspaces(1 To fCount) As Integer
f = InStr(f + 1, FullString, sSearchString)
findspaces(fCount) = f
fCount = fCount + 1
Wend
accPostCodeExtract = Mid(FullString, findspaces(fCount - sCount) + 1, Len(FullString))
If accPostCodeExtract = "" Then accPostCodeExtract = FullString
If bPostCodeNoSpace Then accPostCodeExtract = Left(accPostCodeExtract, Len(accPostCodeExtract) - 3) & " " & Right(accPostCodeExtract, 3)
If bPadResult Then
    While Len(accPostCodeExtract) < 8
        accPostCodeExtract = Left(accPostCodeExtract, Len(accPostCodeExtract) - 3) & " " & Right(accPostCodeExtract, 3)
    Wend
End If

End Function

Tuesday, 8 October 2013

VBA Modules: Access: accCompactRepair v2.03

Read this for full information on these modules

This nifty little module performs a compact & repair on an Access database, or for all Access databases under a specified path. 

accSweepForDatabases runs acCompactRepair on all *.accdb and *.mdb files within [and beneath] the specified folder. (NB: you'll need to comment out the line for .accdb if you only have Access 2003 installed because it won't open those files.)

Syntax to auto-compact all databases under a path:

Access 2007/2010:
accSweepForDatabases "C:\Folder\", True, False, False

Access 2003:

accSweepForDatabases "C:\Folder\", True, False, True


acCompactRepair launches Access, opens the database, sets the "Compact on Close" option to "True", then quits.

Syntax to auto-compact:
acCompactRepair "C:\Folder\Database.accdb", True

I tend to use it after running a Delete query or removing a single table object from a database.

Syntax to return to default* afterwards:
acCompactRepair "C:\Folder\Database.accdb", False

*not necessary, but if your back end database is >1GB this can be rather annoying when you go into it directly and it then takes >2 minutes to quit.

'accCompactRepair
'v2.03 2013-11-28 17:43

'===========================================================================
' HELP CONTACT
'===========================================================================
' Code is provided without warranty and can be stolen and amended as required.
'   Tom Parish
'   TJP@tomparish.me.uk
'   http://baldywrittencod.blogspot.com/2013/10/vba-modules-access-compact-repair.html
'   DGF Help Contact: see BPMHelpContact module
'=========================================================================

'includes code from
'http://www.ammara.com/access_image_faq/recursive_folder_search.html
'tweaked slightly for improved error handling

'   v2.03   added option for Access 2003 users
'           improved code annotation
'   v2.02   bugfix preventing Compact when bAutoCompact set to False
'           bugfix with "OLE waiting for another application" msgbox
'           added "MB" to start & end sizes of message box at end
'   v2.01   added size reduction to message box
'   v2.00   added recurse
'   v1.00   original version

Option Explicit

Function accSweepForDatabases(ByVal strFolder As String, Optional ByVal bIncludeSubfolders As Boolean = True _
    , Optional bAutoCompact As Boolean = False, Optional bOnlyAccess2003 As Boolean) As String
'v2.03 2013-11-28 17:43
'sweeps path for .accdb and .mdb files, compacts and repairs all that it finds
'NB: leaves AutoCompact on Close as False unless specified, then leaves as True

'syntax:
'   accSweepForDatabases "path", [False], [True]

'code for ActiveX CommandButton on sheet module named "admin" with two named ranges "vPath" and "vRecurse":
'   accSweepForDatabases admin.Range("vPath"), admin.Range("vRecurse") [, admin.Range("vLeaveAutoCompact")]

Application.DisplayAlerts = False

Dim colFiles As New Collection, vFile As Variant, i As Integer, j As Integer, sFails As String, t As Single
Dim SizeBefore As Long, SizeAfter As Long
t = Timer

'scan path for any .mdb and .accdb files
    If bOnlyAccess2003 = False Then RecursiveDir colFiles, strFolder, "*.accdb", True
    RecursiveDir colFiles, strFolder, "*.mdb", True

'now compact & repair the list of databases
    For Each vFile In colFiles
        'Debug.Print vFile
        SizeBefore = SizeBefore + (FileLen(vFile) / 1048576)
On Error GoTo CompactFailed
    If InStr(vFile, "Geographical Configuration.accdb") > 0 Then MsgBox "yes"
        acCompactRepair vFile, bAutoCompact
        i = i + 1  'counts successes
        GoTo NextCompact
CompactFailed:
On Error GoTo 0
        j = j + 1   'counts failures
        sFails = sFails & vFile & vbLf  'records failure
NextCompact:
On Error GoTo 0
        SizeAfter = SizeAfter + (FileLen(vFile) / 1048576)

    Next vFile

Application.DisplayAlerts = True

'display message box, mark end of process
    accSweepForDatabases = i & " databases compacted successfully, taking " & CInt(Timer - t) & " seconds, and reducing storage overheads by " & Int(SizeBefore - SizeAfter) & "MB" & vbLf & vbLf & "Size Before: " & Int(SizeBefore) & "MB" & vbLf & "Size After: " & Int(SizeAfter) & "MB"
    If j > 0 Then accSweepForDatabases = accSweepForDatabases & vbLf & j & " failures:" & vbLf & vbLf & sFails
    MsgBox accSweepForDatabases, vbInformation, "accSweepForDatabases"

End Function

Function acCompactRepair(ByVal pthfn As String, Optional doEnable As Boolean = True) As Boolean
'v2.02 2013-11-28 16:22
'if doEnable = True will compact and repair pthfn
'if doEnable = False will then disable auto compact on pthfn

On Error GoTo CompactFailed

Dim A As Object
Set A = CreateObject("Access.Application")
With A
    .OpenCurrentDatabase pthfn
    .SetOption "Auto compact", True
    .CloseCurrentDatabase
    If doEnable = False Then
        .OpenCurrentDatabase pthfn
        .SetOption "Auto compact", doEnable
    End If
    .Quit
End With
Set A = Nothing
acCompactRepair = True
Exit Function
CompactFailed:
End Function


'source: http://www.ammara.com/access_image_faq/recursive_folder_search.html
'tweaked slightly for error handling

Private Function RecursiveDir(colFiles As Collection, _
                             strFolder As String, _
                             strFileSpec As String, _
                             bIncludeSubfolders As Boolean)

    Dim strTemp As String
    Dim colFolders As New Collection
    Dim vFolderName As Variant

    'Add files in strFolder matching strFileSpec to colFiles
    strFolder = TrailingSlash(strFolder)
On Error Resume Next
    strTemp = ""
    strTemp = Dir(strFolder & strFileSpec)
On Error GoTo 0
    Do While strTemp <> vbNullString
        colFiles.Add strFolder & strTemp
        strTemp = Dir
    Loop

    If bIncludeSubfolders Then
        'Fill colFolders with list of subdirectories of strFolder
On Error Resume Next
        strTemp = ""
        strTemp = Dir(strFolder, vbDirectory)
On Error GoTo 0
        Do While strTemp <> vbNullString
            If (strTemp <> ".") And (strTemp <> "..") Then
                If (GetAttr(strFolder & strTemp) And vbDirectory) <> 0 Then
                    colFolders.Add strTemp
                End If
            End If
            strTemp = Dir
        Loop

        'Call RecursiveDir for each subfolder in colFolders
        For Each vFolderName In colFolders
            Call RecursiveDir(colFiles, strFolder & vFolderName, strFileSpec, True)
        Next vFolderName
    End If

End Function

Private Function TrailingSlash(strFolder As String) As String
    If Len(strFolder) > 0 Then
        If Right(strFolder, 1) = "\" Then
            TrailingSlash = strFolder
        Else
            TrailingSlash = strFolder & "\"
        End If
    End If
End Function

Monday, 2 September 2013

VBA Modules: Outlook/Access/Excel: modProcedures v2.14

Read this for full information on these modules

One major down side of the OL_BPMProcess and modAppsFirefox routines was that they locked up the Outlook session while they're running.  This module came about because I was fed up of losing Outlook for an entire Monday while it was busy waiting to download huge CSV files, particularly as the routines would invariably get stuck somewhere random and unexpected and I'd have to set them going again on Monday morning.  Storing the URL and other variables from the email triggers allows me to move on, and pick up those routines where they left off, much later on, when it's more convenient for me.

A few tweaks to the other modules have allowed me to force all downloads to complete during weekends and evenings (my routines usually run on Sundays), but to never wait for too long during business hours (in case something got stuck and I have to fix an issue on Monday).  Manually running the procedures doesn't invoke the same protections, so I can still consciously forego Outlook during the day if I want to run these saved procedures, or I can just wait until I leave the office at night or go on lunch.

Firefox (for me) will only download a maximum of 6 simultaneous streams so there are protections built into modFirefox for that too.  Rather than start downloading the file, store the Excel or Access procedure and pick those up later when the file has downloaded, it just stores the Download procedure for triggering later on.

When the procedure is running it updates the worksheet to "In Progress" then to "OK" when completed.  (You can choose to rerun Failed procedures, but it's not really recommended, owing to the way the routines are stored and will run -- if it fails once it'll usually fail again.  I usually delete all the procedures from the file once a week just for good housekeeping.)

This module should be added to an Excel workbook with sheets named Excel, Access, and Download with the appropriate column headings in place:

Excel:
mpTimestamp mpURL mpDownloadingFile mpMoveToFile mpPathFile mpMacro rResult rTimestamp
Access:
mpTimestamp mpURL mpDownloadingFile mpMoveToFile mpPathFile mpMacro rResult rTimestamp
Download:
mpTimestamp mpURL mpApp mpMoveToFile mpPathFile mpMacro rResult rTimestamp

'modProcedures
'v2.14 2013-12-02 13:05

'===========================================================================
' HELP CONTACT
'===========================================================================
' Code is provided without warranty and can be stolen and amended as required.
'   Tom Parish
'   TJP@tomparish.me.uk
'   http://baldywrittencod.blogspot.com
'   DGF Help Contact: see BPMHelpContact module
'=========================================================================

'===========================================================================
' modProcedures
'===========================================================================
'   mp_Procedure_Store: stores list of procedures to be run later, prevents
'   indefinite hangs when downloading large files from Outlook.
'
'   mp_Run_Procedures: runs stored list of procedures sequentially (or just one)

'===========================================================================
' Additional modules required:
'===========================================================================
'   modAppsOffice
'
'  [automation requires modAppsFireFox v3.00 and OL_BPMprocess v6.00, but not used here]

'===========================================================================
' Additional References required:
'===========================================================================
'   Microsoft Excel Object Library

'===========================================================================
' External applications required:
'===========================================================================
'   Microsoft Outlook   (for automation)
'   Microsoft Access    (for Access functions)
'   Microsoft Excel     (for Excel functions)

'=========================================================================
' VERSION HISTORY
'=========================================================================
'   v2.14   mpDefaultStoreWorkbook changed to C:\SHARES\ as more robust than UNC
'   v2.13   mp_Run_Procedures: recalcs after each item is run
'   v2.12   mp_Run_Procedures: bugfix, resets mpApp on Downloads sheet
'   v2.11   mp_Run_Procedures: bugfix, doesn't run Excel/Access if nothing to do
'   v2.10   mpXLapp, prevents conflict with modAppsOffice
'   v2.09   mp_Run_Procedures: bugfix prevents WB.Open Read-Only
'   v2.08   mp_Procedure_Store: bugfix prevents WB.Open Read-Only
'   v2.07   mp_Procedure_Store: bugfix prevents looping for Download proc
'   v2.06   mp_Procedure: bugfixes
'   v2.05   mp_Procedure_Store: bugfix for Downloads store
'   v2.04   mp_Run_Procedures: will Download then run relevant App procedure
'   v2.03   mp_Procedure: bugfix if mpDownloadedFile not found
'   v2.02   mp_Procedure_Store: bugfix
'   v2.01   mp_Procedure_Store: bugfix
'   v2.00   mp_Procedure_Store now stores URL and allows queued Downloads
'   v1.01   errorhandlers, bugfix in mp_run_Procedures
'   v1.00   mp_Procedure_Store, mp_Run_Procedures, mp_Procedure

Option Explicit

Private mpXLapp As Excel.Application  '2.10 bugfix prevents issues with modAppsOffice XLapp

Private Const mpDefaultStoreWorkbook As String = "C:\SHARES\VS\ProcStore.xlsb"  'v2.13
'can specify a different WB when storing procedures

Public Enum mpApps
'v2.00 2013-08-27 13:05
'sheet number matched to each application type
    mpExcel = 1
    mpAccess = 2
    mpDownload = 3  'v2.00
End Enum

Function mp_Procedure_Store(ByVal mpURL As String, ByVal mpDownloadingFile As String, ByVal mpMoveToFile As String _
    , ByVal mpApp As mpApps, ByRef mpPathFile As String, Optional ByVal mpMacro As String _
    , Optional ByVal mpProceduresWorkbook As String = mpDefaultStoreWorkbook) As Boolean
'v2.08 2013-09-16 13:05
'runs Excel, opens mpProceduresWorkbook, records downloading filename and procedure details for later

'SYNTAX
' Store Excel procedure:
'   mp_Procedure_Store "http://url.com", "C:\Users\bpmgb\Downloads\downloadingfile.xls", "C:\Users\bpmgb\Downloads\Downloaded File.xls", mpExcel, "C:\Users\bpmgb\Downloads\", "runtest.xlsm", ""
' Store Access procedure:
'   mp_Procedure_Store "http://url.com", "C:\Users\bpmgb\Downloads\downloadingfile.xls", "C:\Users\bpmgb\Downloads\Downloaded File.csv", mpAccess, "C:\Users\bpmgb\Downloads\", "runtest.accdb", "runtest"
' Store Download procedure:  mpDownloadingFile = "" qualifies
'   mp_Procedure_Store "http://url.com", "", "C:\Users\bpmgb\Downloads\Downloaded File.xls", mpExcel, "C:\Users\bpmgb\Downloads\", "runtest.xlsm", ""

mp_Procedure_Store = True

Dim WB As Excel.Workbook, pwSheet As Excel.Worksheet, pwRow As Excel.Range
Dim rTimestamp As Excel.Range, rDownloadingFile As Excel.Range, rMoveToFile As Excel.Range _
    , rPathFile As Excel.Range, rMacro As Excel.Range, rDLfiles As Excel.Range _
    , rURL As Excel.Range, rApp As Excel.Range, a As Byte

'run Excel (or use this Excel session for testing)
Dim mpNative As Boolean
On Error Resume Next
If UCase(ThisWorkbook.FullName) <> UCase(mpProceduresWorkbook) Then  'v2.08 stops looping
    Set mpXLapp = XLlaunch(True, False)
Else
    Set mpXLapp = Application
End If
On Error GoTo 0

With mpXLapp
    .DisplayAlerts = False

'open WB (if not open), store details for processing later
    If mpXLapp <> Application Then
        Set WB = .Workbooks.Open(mpProceduresWorkbook)
    Else
    If UCase(ThisWorkbook.FullName) = UCase(mpProceduresWorkbook) _
    Then Set WB = ThisWorkbook _
    Else: Set WB = .Workbooks.Open(mpProceduresWorkbook)
    End If
  
    With WB
        If mpApp <> mpDownload And mpDownloadingFile <> "" Then  'v2.07 bugfix, doesn't loop
        'check this file is not already being downloaded on Excel and Access sheets
            For a = mpApps.mpExcel To mpApps.mpAccess
                Set pwSheet = .Sheets(a)
                With pwSheet
                    Set rDLfiles = .Columns(mpXLapp.Match("mpDownloadingFile", .Rows(1), 0))  'v2.01
                    If mpXLapp.CountIf(rDLfiles, mpDownloadingFile) > 0 Then
                    'error: this mpDownloadingFile file is already being used for another procedure?
                    'store this procedure to try downloading it again later from source URL
                        mp_Procedure_Store mpURL, "", mpMoveToFile, mpApp, mpPathFile, mpMacro, mpProceduresWorkbook
                        GoTo CleanUp
                    End If
                End With
            Next a
        End If
        'this is a new file being downloaded / to be downloaded
        If mpDownloadingFile = "" Then Set pwSheet = .Sheets(3) Else Set pwSheet = .Sheets(mpApp)  'v2.05
        With pwSheet
            Set pwRow = .Rows(mpXLapp.CountA(.Columns(1)) + 1)
            Set rTimestamp = pwRow.Columns(mpXLapp.Match("mpTimestamp", .Rows(1), 0))
                rTimestamp.Value = Now()
            Set rURL = pwRow.Columns(mpXLapp.Match("mpURL", .Rows(1), 0))
                rURL.Value = mpURL
        If mpDownloadingFile = "" Then   'v2.05 'store app, only for Download sheet
            Set rApp = pwRow.Columns(mpXLapp.Match("mpApp", .Rows(1), 0))
                rApp.Value = mpApp
        Else  'store downloading file name, not for Download sheet
            Set rDownloadingFile = pwRow.Columns(mpXLapp.Match("mpDownloadingFile", .Rows(1), 0))
                rDownloadingFile.Value = mpDownloadingFile
        End If
            Set rMoveToFile = pwRow.Columns(mpXLapp.Match("mpMoveToFile", .Rows(1), 0))
                rMoveToFile.Value = mpMoveToFile
            Set rPathFile = pwRow.Columns(mpXLapp.Match("mpPathFile", .Rows(1), 0))
                rPathFile.Value = mpPathFile
            Set rMacro = pwRow.Columns(mpXLapp.Match("mpMacro", .Rows(1), 0))
                rMacro.Value = mpMacro
        End With
CleanUp:
On Error Resume Next
        If mpNative = False Then .Close SaveChanges:=True Else .Save
        Set pwSheet = Nothing
        Set WB = Nothing
    End With
    If mpNative = False Then .Quit
    Set mpXLapp = Nothing
End With

End Function

Sub mp_Run_Procedures(ByRef mpApp As mpApps, ByVal bRerun As Boolean _
    , Optional ByVal mpProceduresWorkbook As String = mpDefaultStoreWorkbook)
'v2.13 2013-11-26 16:00
'runs all Procedures that have not yet been completed OK
'[and reruns all failed Procedures if bRerun = True]
'SYNTAX:  mp_Run_Procedures mpExcel, False

Dim WB As Excel.Workbook, pwSheet As Excel.Worksheet, pwRow As Excel.Range, pwRows() As Long
Dim rURL As Range, rApp As Range, rDownloadingFile As Excel.Range, rMoveToFile As Excel.Range _
    , rPathFile As Excel.Range, rMacro As Excel.Range _
    , rResult As Excel.Range, rTimestamp As Excel.Range, rTimestamps As Excel.Range
Dim mpDownloadingFile As String, mpMoveToFile As String _
    , mpPathFile As String, mpMacro As String, mpFileExt As String, mpFileName As String, r As Long
Dim b As Integer, c As Integer, d As Integer

Const rOK As String = "OK"
Const rFail As String = "Fail"
Const rIP As String = "In Progress"

'run Excel (use this WB preferably)  'v2.09
Dim mpNative As Boolean
If UCase(ThisWorkbook.FullName) = UCase(mpProceduresWorkbook) Then
'NB: differences in path e.g. UNC vs Local will cause to open again Read-Only
    Set mpXLapp = Application
    mpNative = True
Else
    Set mpXLapp = XLlaunch(True, False)
End If

With mpXLapp
    .DisplayAlerts = False

'open WB, store details for processing later
    If mpNative = True Then 'v2.09
        Set WB = ThisWorkbook
    Else
        Set WB = .Workbooks.Open(mpProceduresWorkbook)
    End If
  
    With WB
        Set pwSheet = .Sheets(mpApp)
        With pwSheet
            Set rTimestamps = .Cells(1, 1)
            Set rTimestamps = .Range(rTimestamps, rTimestamps.End(xlDown))
            r = rTimestamps.Cells.Count  'total rows (timestamps) in table incl. header
            Set rTimestamps = .Columns(mpXLapp.Match("rTimestamp", .Rows(1), 0))  'in/complete rows
            Set rResult = .Columns(mpXLapp.Match("rResult", .Rows(1), 0))   'result (allows rerun)
            Set rURL = .Columns(mpXLapp.Match("mpURL", .Rows(1), 0))  'v2.04 URL for download or in case need to download again
            If mpApp = mpApps.mpDownload Then 'v2.04
                Set rApp = .Columns(mpXLapp.Match("mpApp", .Rows(1), 0))
                Set rDownloadingFile = .Columns(mpXLapp.Match("mpMoveToFile", .Rows(1), 0))  'v2.12 bugfix in Downloads process
            Else
                Set rDownloadingFile = .Columns(mpXLapp.Match("mpDownloadingFile", .Rows(1), 0))
            End If
            Set rMoveToFile = .Columns(mpXLapp.Match("mpMoveToFile", .Rows(1), 0))
            Set rPathFile = .Columns(mpXLapp.Match("mpPathFile", .Rows(1), 0))
            Set rMacro = .Columns(mpXLapp.Match("mpMacro", .Rows(1), 0))
            For r = 2 To r  'all reports, ignore header row
                If rTimestamps.Cells(r) = "" Then
                    If (bRerun = True And rResult.Cells(r) <> "OK") Or rResult.Cells(r) <> "Fail" Then 'v2.04
                    'run this procedure
                        mpMoveToFile = rMoveToFile.Cells(r).Value
                        b = InStr(mpMoveToFile, ".")
                        Do While b > 0
                            c = b
                            b = InStr(c + 1, mpMoveToFile, ".")
                        Loop
                        If c > 0 Then mpFileExt = Mid(mpMoveToFile, c, 8)
                        b = InStr(mpMoveToFile, "\")
                        Do While b > 0
                            d = b
                            b = InStr(d + 1, mpMoveToFile, "\")
                        Loop
                        If d > 0 Then mpFileName = Mid(mpMoveToFile, d + 1, Len(mpMoveToFile) - d)
                        mpPathFile = rPathFile.Cells(r).Value
                        mpMacro = rMacro.Cells(r).Value
                        rResult.Cells(r).Value = "In Progress"
                        If mpApp = mpApps.mpDownload Then
                        'Downloads: mp_Procedure will use URL to download file, then run procedure in relevant App
                            mpApp = rApp.Cells(r).Value
                            mpDownloadingFile = rURL.Cells(r).Value  'starts with "http://" or "https://"
                        Else
                        'Apps: mp_Procedure will check if downloading file is finished yet, then run procedure in relevant App
                            mpDownloadingFile = rDownloadingFile.Cells(r).Value
                        End If
                        If mp_Procedure(mpApp, mpDownloadingFile, mpMoveToFile, mpPathFile, mpMacro) = True _
                        Then rResult.Cells(r).Value = "OK" _
                        Else: rResult.Cells(r).Value = "Fail"
                        rTimestamps.Cells(r).Value = Now()
                        mpApp = .Index  'v2.12 bugfix, resets mpApp
                    End If
                End If
                Application.Calculate  'v2.13, updates admin sheet counts
            Next r
        End With
        If mpNative = False Then .Close SaveChanges:=True Else .Save
        Set pwSheet = Nothing
        Set WB = Nothing
    End With
    If mpNative = False Then .Quit
    Set mpXLapp = Nothing
End With

End Sub

Private Function mp_Procedure(ByRef mpApp As mpApps, ByRef mpDownloadingFile As String, ByRef mpMoveToFile As String _
    , ByVal mpPathFile As String, ByVal mpMacro As String) As Boolean
'v2.11 2013-09-23 11:18
'only run from mp_Run_Procedures

On Error GoTo ErrorHandler  'mp_Procedure = False

Dim mp_DownloadedFile As String, mp_FileExt As String, b As Byte, c As Byte

'v2.04 if URL is specified, download file then change variables and run relevant procedure
'       NB: mpApp is never 3 at this point
If Left(mpDownloadingFile, 7) = "http://" Or Left(mpDownloadingFile, 8) = "https://" Then  'v2.05 handles https
    b = InStr(mpMoveToFile, ".")  'check end of string for file ext
    Do Until b = 0
        mp_FileExt = Mid(mpMoveToFile, b, 1 + Len(mpMoveToFile) - b)  '".csv"
        c = b
        b = InStr(b + 1, mpMoveToFile, ".") 'check end of string for file ext
    Loop
    mpDownloadingFile = modAppsFirefox.ff_GetDownload(mpDownloadingFile, mp_FileExt, mpMoveToFile, True)  'True always waits for completion
End If

'original code from modFireFox, second part is changed for this procedure
'whilst downloading, file.ext placeholder will exist with 0 bytes, file.ext.part is temporary downloading file
'on completion, file.ext wil be deleted, then file.ext.part will be renamed, so file.ext will be >0 bytes
    Dim f1 As Double
On Error Resume Next
    If Dir(mpDownloadingFile) = "" Then GoTo ErrorHandler
    f1 = FileLen(mpDownloadingFile)
    Do While f1 = 0
    'when download completes, mpDownloadingFile is deleted (i.e. error) then reappears with f1 > 0
        f1 = FileLen(mpDownloadingFile)
    Loop
On Error GoTo 0

On Error GoTo ErrorHandler  'mp_Procedure = False

'rename downloaded file if specified
'NB: renaming .csv to .xls will cause you problems!
    If mpMoveToFile <> "" Then
    'use specified filename
        mp_DownloadedFile = mpMoveToFile
    Else
    'use default download filename
        Const cDefaultFilename As String = "Downloaded Web Server Report."  ' & mp_FileExt
        Const cPrd As String = "."
        mp_FileExt = Replace(LCase(mp_FileExt), cPrd, "")
        mp_DownloadedFile = cDefaultFilename & mp_FileExt
    End If
'before moving/renaming download file, kill target file
    If mpDownloadingFile <> mp_DownloadedFile Then 'v2.06 not necessary where filenames the same
        If Dir(mpDownloadingFile) <> "" And Dir(mp_DownloadedFile) <> "" Then Kill mp_DownloadedFile  'v2.06 stops deletion where files not found
    'rename/move downloaded file
        Name mpDownloadingFile As mp_DownloadedFile
    End If
  
'validity check to confirm download completed
    If Dir(mp_DownloadedFile) = "" Then
    'downloaded file doesn't exist, something went wrong
        MsgBox "Downloaded file not found", vbCritical, "Error in mp_DownloadedFile"
        GoTo ErrorHandler
    End If

'run relevant application (only if required)  'v2.11
    If mpPathFile <> "" Then
        If mpApp = 1 Then run_Excel "", mpPathFile, mpMacro, False
        If mpApp = 2 Then run_Access "", mpPathFile, mpMacro
    End If
  
mp_Procedure = True
Exit Function
ErrorHandler:
End Function

Monday, 5 August 2013

VBA Modules: modAppsOffice v4.08

Read this for full information on these modules

modAppsOffice is a module I use all the time.  It has a few simple but endlessly useful functions for launching Access and Excel, and running SQL/Access macros/queries.  I probably haven't developed this one as much as I could have, but my needs are fairly simple!  I prefer to handle more complicated requirements within Excel using the Workbook_Open event to launch other custom macros.

This makes use of modKeyState by Chip Pearson - included within the module as of v4.

'modAppsOffice
'v4.08 2013-11-06 13:26

'===========================================================================
' HELP CONTACT
'===========================================================================
' Code is provided without warranty and can be stolen and amended as required.
'   Tom Parish
'   TJP@tomparish.me.uk
'   http://baldywrittencod.blogspot.com
'   DGF Help Contact: see BPMHelpContact module
'=========================================================================

'*************************************************************
' NOTE: all prior versions MUST be upgraded to v3.14 or later
'*************************************************************

'********************************************
'****  two settings to be changed below  ****
'********************************************

'===========================================================================
' modAppsOffice
'===========================================================================
'   Routines for launching MS Office applications, opening files, running
'   macros, etc.  Requires application reference libraries to be enabled
'   via Tools > References ONLY if you are running from a different Office
'   application (e.g. launching Excel from Access).  Enabling unnecessary
'   libraries will cause no harm.

'===========================================================================
' Additional modules required:
'===========================================================================
'   None

'===========================================================================
' Additional References required:
'===========================================================================
'   None

'===========================================================================
' External applications required:
'===========================================================================
'   Microsoft Outlook   (for Outlook functions)
'   Microsoft Access    (for Access functions)
'   Microsoft Excel     (for Excel functions)

'=========================================================================
' VERSION HISTORY
'=========================================================================
'   v4.08   run_Excel: bugfix in error handler
'   v4.07   run_Excel: added bForceVisibility (defaults to maoVisibleByDefault)
'           run_Excel: added bForceVisibility
'           XL_launch: changed XLvisible to bForceVisibility
'   v4.06   mao_fix_path bugfix when pth includes fn
'   v4.05   run_Access: permits use of VB "function()" as DBmacro
'                       strQuery variable relabelled as SQLcommand
'   v4.04   run_Access/run_Excel: persistence bugfix
'   v4.03   run_Excel: RunNative bugfix
'   v4.02   run_Access/run_Excel error handlers (Not DBapp/XLapp Is Nothing)
'   v4.01   retired runOutlook_SendMail, use modEmail instead
'   v4.00   added optional SharePoint domain to check when opening XL_WB
'   v3.18   maoVisibleByDefault set Public for use with other modules
'           XLlaunch: visibility bugfix
'   v3.17   run_Excel: can specify Read-Only (rxlOpenReadOnly)
'   v3.16   run_Excel: determine Read-Only/Editable from iShare/not
'   v3.15   late bound references
'   v3.14   changed Access.Application to Object, fixes Debug issue for
'           users without MS Access installed - OL and XL still required
'*************************************************************
'   v3.13   minor bugfix in run_Excel (just saves a little time)
'   v3.12   MAJOR BUGFIX in XLlaunch
'*************************************************************
'!! v3.11   fixed persistent DBapp and XLapp issue (Objects set Public)
'           moved to GBMNCWSA050, annotations changed
'   v3.10a  MAJOR BUGFIX mao_fix_path
'*************************************************************
'!! v3.10   FAULTY mao_fix_path adds the last slash to paths
'*************************************************************
'   v3.09   annotations improved, no functional change
'   v3.08   run_AppName application objects changed to AppName.Application
'           runOutlook_SendMail tested in 2010
'           ** DOESN'T WORK IN OFFICE 2003 **
'   v3.07   run_Access changed to function (so XLapp, DBapp not required)
'   v3.03   runOutlook_SendMail sSubject, sRecipient, sBodyText, [DisplayFirst], [sAttach_pthfn1], [sAttach_pthfn2]
'   v2.xx   run_Excel XLpth, XLfn, [XLmacro], [RunNative], [LeaveOpenWhenDone](v2.09), [OpenOnly](v3.03)
'   v1.xx   run_Access DBpath, DBfn, [DBmacro], [DBquery], [strQuery], [LeaveOpenWhenDone](v2.09), [OpenOnly](v3.03)

Option Explicit
'References must be enabled via Tools > References
'Public prevents app always closing when macro ends
'--> must Set XXapp = Nothing to clean up
Public DBapp As Object 'Access.Application  'requires Access object library
Public OLapp As Object 'Outlook.Application 'requires Outlook object library
Public XLapp As Object 'Excel.Application   'requires Excel object library

'********************************************
'****  two settings to be changed below  ****
'********************************************

Public Const maoVisibleByDefault As Boolean = True  'v3.18 set public for use with other modules
    'set this to False for background-only operations

Private Const SP_domain As String = "ishare.dhl.com"
    'SharePoint domain, optional, "" if not required

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

Function run_Access(ByVal DBpath As String, ByVal DBfn As String _
    , Optional ByVal DBmacro As String _
    , Optional ByVal DBquery As String _
    , Optional ByVal SQLcommand As String _
    , Optional ByVal LeaveOpenWhenDone As Boolean _
    , Optional ByVal OpenOnly As Boolean _
    , Optional ByVal bForceVisibility As Boolean = maoVisibleByDefault) _
    As Object 'v3.14 was Access.Application  'v3.08 requires Microsoft Access object library via Tools > References
'v4.07 2013-11-04 14:04
'runs Access and opens DB [then runs Query OR Macro OR SQL command]

'DBpath   = "C:\JBA\"
DBpath = mao_fix_path(DBpath)  'v3.10
'DBfn   = "JBA G7 Detail.mdb"
'DBmacro  = "macro name 1"
'DBquery  = "query name 1"
'SQLcommand = "SELECT stuff FROM table WHERE this"

Set DBapp = Nothing  'v4.04

Dim strcount As Byte, pp As String, tt As String
Dim InXL As Boolean 'v3.07, v3.11
If InStr(Application.Name, "Excel") > 0 Then InXL = True
If InXL = True Then
    Set XLapp = Application  'v3.07
    XLapp.DisplayAlerts = False  'v3.07
End If

strcount = 0
tt = "FATAL ERROR"
pp = "Warning: can only process DBmacro OR DBquery OR SQLcommand." & vbLf
If DBmacro <> "" Then
    strcount = strcount + 1
    pp = pp & " - specified DBmacro " & DBmacro & vbLf
End If
If DBquery <> "" Then
    strcount = strcount + 1
    pp = pp & " - specified DBquery " & DBquery & vbLf
End If
If SQLcommand <> "" Then
    strcount = strcount + 1
    pp = pp & " - specified SQLcommand " & SQLcommand & vbLf
End If
If (strcount = 0 And OpenOnly = False) _
Or strcount > 1 Then
    MsgBox pp, , tt
    Exit Function
End If

Set run_Access = CreateObject("Access.Application")

On Error GoTo ErrorHandler  'leaves DBapp <> Nothing on error

With run_Access
    .Visible = bForceVisibility
'errors here means DBpath or DBfn is wrong
    .OpenCurrentDatabase DBpath & DBfn
'errors here could mean Excel Connection is not Read-Only
'solution here:   http://social.msdn.microsoft.com/Forums/en/sqlintegrationservices/thread/d03e4b1a-6be0-4b3c-8b31-42d6fc79bf39
    If OpenOnly = False Then
        If DBmacro <> "" Then
        'OL macro fails here doing Append macro - works when rerun - add a 2 second delay?
        'Application.Wait Val(Now() + TimeSerial(0, 0, 5))
            If Right(DBmacro, 2) = "()" Then  'v4.05 runs VB function or DB macro as required
            'DBmacro ends with "()", run VB function
                DBmacro = Left(DBmacro, Len(DBmacro) - 2)  'remove "()" from function name
                run_Access.Run DBmacro
            Else
            'run DB macro
                .DoCmd.RunMacro DBmacro
            End If
        ElseIf DBquery <> "" Then
            .DoCmd.OpenQuery DBquery
        ElseIf SQLcommand <> "" Then
            .DoCmd.RunSQL SQLcommand
        End If
    End If
    If maoVisibleByDefault = False Then
        .Visible = OpenOnly
    End If
    If OpenOnly = False And LeaveOpenWhenDone = False Then
        .CloseCurrentDatabase
        .Quit
        Set run_Access = Nothing
    Else
        If DBapp Is Nothing Then Set DBapp = run_Access 'Else MsgBox "Cannot persist >1 instance of Access"  'v3.11
        Set run_Access = Nothing
        .Visible = True
        Set XLapp = Nothing
        Exit Function  'v4.04 stops Access quitting
    End If
End With

ErrorHandler:   'leaves DBapp <> Nothing

Set DBapp = run_Access

If InXL = True Then
    XLapp.DisplayAlerts = True  'v3.07
End If

Set XLapp = Nothing

End Function

Function run_Excel(ByVal XLpth As String, ByVal XLfn As String _
    , Optional ByVal XLmacro As String _
    , Optional ByVal RunNative As Boolean _
    , Optional ByVal LeaveOpenWhenDone As Boolean _
    , Optional ByVal rxlOpenReadOnly As Boolean = False _
    , Optional ByVal bForceVisibility As Boolean = maoVisibleByDefault) _
    As Object
'v4.08 2013-11-06 13:26
'simply runs Excel and opens WB  [then runs macro] --> will run XLmacro when opened, if optional macro name specified
'WB should normally have macros that run on Workbook.Open
'v3.16 uses xlSharePoint, such files are ALWAYS opened Read-Only to allow automation and bypass message boxes
'otherwise use IsShiftKeyDown=True and Application.Wait to allow users to bypass any autoroutines

If RunNative = False Then Set XLapp = Nothing  'v4.04

On Error GoTo ErrorHandler  'leaves XLapp <> Nothing on error

If XLpth <> "" Then XLpth = mao_fix_path(XLpth)  'v3.13

Dim WB As Object  'Excel.Workbook  v3.15
Set run_Excel = XLlaunch(LeaveOpenWhenDone, RunNative) 'v4.03

With run_Excel
    .Visible = bForceVisibility  'v4.07
    .DisplayAlerts = False
    If XLmacro <> vbNullString Then
    'open WB, run macro
        Set WB = .Workbooks.Open(XLpth & XLfn)
        .Run XLmacro
    On Error Resume Next  'prevents errors where ThisWorbook closes automatically
        If LeaveOpenWhenDone = False Then .Close SaveChanges:=True
    On Error GoTo 0
    Else
    'macro(s) will autorun on Workbook.Open
        If SP_domain <> "" And (InStr(XLpth, SP_domain) > 0 Or InStr(XLfn, SP_domain) > 0) Then
        'always open RO from SharePoint (prevents issues with CheckIn and can dictate automation when opened Read-Only)
            .Workbooks.Open FileName:=XLpth & XLfn, ReadOnly:=True
        Else
        'always open writeable from shared drive (unless rxlOpenReadOnly is specified)
            .Workbooks.Open FileName:=XLpth & XLfn, ReadOnly:=rxlOpenReadOnly
        End If
    On Error Resume Next  'prevents errors where ThisWorbook closes automatically
        If LeaveOpenWhenDone = True Then .ActiveWorkbook.Close SaveChanges:=True
    On Error GoTo 0
    End If
    .DisplayAlerts = False
    On Error Resume Next  'prevents errors where Excel closes automatically
        If LeaveOpenWhenDone = False Then
            .Quit
            Set run_Excel = Nothing
        Else
            .Visible = True
        End If
    On Error GoTo 0
End With
Exit Function 'v4.08

ErrorHandler:
On Error Resume Next  'v4.08
run_Excel.Visible = True  'v4.07
Set XLapp = run_Excel

End Function

Function XLlaunch(Optional ByVal bForceVisibility As Boolean = maoVisibleByDefault _
    , Optional RunNative As Boolean = False) _
    As Object
'v4.07 2013-11-04 14:04

Dim InXL As Boolean
If InStr(Application.Name, "Excel") > 0 Then InXL = True 'v3.12

If RunNative = True And InXL = True Then
    Set XLlaunch = Application
Else
    Set XLlaunch = CreateObject("Excel.Application")
    XLlaunch.Visible = bForceVisibility
End If

End Function

Function mao_fix_path(ByVal pth As String) As String
'v4.06 2013-10-31 11:32
'adds the relevant last slash to the path, if missing, and if not including .accdb/.mdb/.xl

Const cBsl As String = "\"
Const cFsl As String = "/"

If InStr(pth, ".xl") > 0 Or InStr(pth, ".accdb") > 0 Or InStr(pth, ".mdb") > 0 Then
    mao_fix_path = pth
ElseIf InStr(pth, cBsl) > 0 And Right(pth, 1) <> cBsl Then
    mao_fix_path = pth & cBsl
ElseIf InStr(pth, cFsl) > 0 And Right(pth, 1) <> cFsl Then
    mao_fix_path = pth & cFsl
Else
    mao_fix_path = pth
End If

End Function



'Sub runOutlook_SendMail(sSubject As String, sRecipient As String _
'    , sBodyText As String, DisplayFirst As Boolean _
'    , Optional sAttach_pthfn1 As String _
'    , Optional sAttach_pthfn2 As String)
'retired v4.01 2013-08-21 16:27
'
'legacy code:
'modEmail.SendEmail sRecipient, "", "", sSubject, sBodyText, DisplayFirst, sAttach_pthfn1
'
''v3.15 2013-07-10 12:25
''*** DOESN'T WORK IN OFFICE 2003? *** tested OK in 2010
'' - haven't bypassed Outlook virus protection so will ask for permission?
'' - can only attach max 2 files, need to change this to allow more
'
''Syntax:
''  SendMail "My email with attachment", "name@host.com", "Here is an email", False, "c:\test.txt"
''source: http://www.vbaexpress.com/kb/getarticle.php?kb_id=758
'
'    Dim olMail As Object  'Outlook.MailItem
'    Dim blRunning As Boolean
'
'     'get application
'    blRunning = True
'    On Error Resume Next
'    Set OLapp = GetObject(, "Outlook.Application")
'    If OLapp Is Nothing Then
'        Set OLapp = CreateObject("Outlook.Application")
'        blRunning = False
'    End If
'    On Error GoTo 0
'
'    Set olMail = OLapp.CreateItem(0)  '0=olMailItem, see http://www.ozgrid.com/forum/showthread.php?t=148735
'    With olMail
'         'Specify the email subject
'        .Subject = sSubject
'         'Specify who it should be sent to
'         'Repeat this line to add further recipients
'        .Recipients.Add sRecipient
'         'specify the file to attach
'         'repeat this line to add further attachments
'        If sAttach_pthfn1 <> vbNullString Then
'            .Attachments.Add sAttach_pthfn1
'            If sAttach_pthfn2 <> vbNullString Then
'                .Attachments.Add sAttach_pthfn2
'            End If
'        End If
'         'specify the text to appear in the email
'        .Body = sBodyText
'         'Choose which of the following 2 lines to have commented out
'        If DisplayFirst = True Then
'            .Display 'This will display the message for you to check and send yourself
'        Else
'            .Send ' This will send the message straight away
'        End If
'    End With
'
'    If Not blRunning Then OLapp.Quit
'
'    Set OLapp = Nothing
'    Set olMail = Nothing
'
'End Sub