■ 指定したファイル名の Excel ファイルが使用中かチェックする
ExcelExcel ファイルを読み込む場合、すでにブック内に存在するかや、ファイルが他で使用されていないかをチェックする必要があります
別プロセスの Excel で操作している場合なども考慮して、追加書き込みによる処理が可能かどうかもチェックしています
この関数では Excel を読み取り専用で開いていますが、保存まで行う場合には ReadOnly:=true の指定は外します
Private Function CheckUseFile(ByVal st_path As String, ByVal bln_open As Boolean, Optional ByRef o_sheet As Worksheet) As Long

    Dim o_fso As Object                 '' FSO
    Dim o_file As Object                '' File
    Dim o_book As Workbook              '' 作業用ブック
    Dim st_filename As String           '' ファイル名
    Dim i_ret As Long                   '' 結果格納領域

    On Error Resume Next
    Set o_fso = CreateObject("Scripting.FileSystemObject")
    '' エラー時に処理を抜けるための無限ループ
    Do
        i_ret = 0
        '' Excel内で同時に開いているブック内での存在チェック
        st_path = LCase$(st_path)
        st_filename = o_fso.GetFileName(st_path)
        For Each o_book In Workbooks
            '' 同一パスのExcelを開いている場合
            If (LCase$(o_book.FullName) = st_path) Then
                i_ret = -1
                Set o_sheet = o_book.Worksheets(1)
                Exit Do
            End If
            '' 同一ファイル名のExcelを開いている場合
            If (LCase$(o_book.Name) = st_filename) Then
                i_ret = -2
                Set o_sheet = o_book.Worksheets(1)
                Exit Do
            End If
        Next o_book
        '' ファイルが保存できるかチェック
        If (o_fso.FileExists(st_path)) Then
            '' 使用中の場合は追加書き込みで開くとエラーになる
            Set o_file = o_fso.OpenTextFile(st_path, 8)
            i_ret = Err.Number
            o_file.Close
            Set o_file = Nothing
            If (i_ret <> 0) Then Exit Do
        End If
        '' ファイルを読み取り専用で開く
        If (bln_open) Then
            Set o_sheet = Workbooks.Open(Filename:=st_path, ReadOnly:=True).Worksheets(1)
            i_ret = Err.Number
            If (i_ret <> 0) Then Exit Do
        End If
        Exit Do
    Loop
    Set o_book = Nothing
    Set o_fso = Nothing
    CheckUseFile = i_ret

End Function