ファイル名に関連付けられている実行可能ファイルの名前を取得
Option Explicit
Declare Function FindExecutable Lib "shell32.dll" Alias "FindExecutableA" _
(ByVal lpFile As String, _
ByVal lpDirectory As String, _
ByVal lpResult As String) As Long
Dim vbNullChar
Sub run()
Dim RetVal As Long
Dim strWorkDir As String
Dim strDstFile As String
Dim strBuffer As String
Dim mypos As Long
Dim lngReturnCode As Long
Dim wexe As String
Dim wrun As String
vbNullChar = Chr(0)
strWorkDir = "c:\"
strDstFile = "test.txt"
If Dir$(strWorkDir & strDstFile) = "" Then
MsgBox "ファイルが存在しません 事前に" & strWorkDir & strDstFile & "を作成してください。"
Exit Sub
End If
strBuffer = String$(516, vbNullChar)
'指定されたファイル名に関連付けられている実行可能 (.EXE) ファイルの名前を取得
lngReturnCode = FindExecutable(strWorkDir & strDstFile, _
strWorkDir, _
strBuffer)
Call ReplaceNullChar(strBuffer)
If Left$(strBuffer, 1) = " " Then
GoTo abend
End If
mypos = InStr(1, strBuffer, ".exe", vbTextCompare)
If mypos = 0 Then
GoTo abend
End If
wexe = Left$(strBuffer, mypos + 3)
wrun = wexe & " " & """" & strWorkDir & strDstFile & """"
RetVal = Shell(wrun, 1)
Exit Sub
abend:
MsgBox "指定されたファイル名に関連付けられている" + Chr(13) + Chr(10) + "実行可能プログラムが存在しません。"
End Sub
Sub ReplaceNullChar(Str As String)
Dim lonLoopCount As Long

For lonLoopCount = 1 To Len(Str)
If Mid$(Str, lonLoopCount, 1) = vbNullChar Then
Mid$(Str, lonLoopCount, 1) = " "
End If
Next lonLoopCount
End Sub