Mid関数
にメンテナンス済み
Mid 関数は、文字列の指定した位置から指定した文字数の部分文字列を抽出する VBA の関数です。固定長データの解析、日付の分解、特定位置のデータ取得などに非常に便利です。
基本構文
Mid(文字列, 開始位置, [文字数])
引数
引数 | 型 | 必須 | 説明 |
---|---|---|---|
文字列 | String | ○ | 対象の文字列 |
開始位置 | Long | ○ | 抽出開始位置(1 から始まる) |
文字数 | Long | × | 抽出する文字数(省略時は末尾まで) |
戻り値
抽出された部分文字列(String 型)
チェック
Mid関数の開始位置は1から始まります(0ではありません)。文字数を省略すると、開始位置から文字列の末尾までを取得します。
基本的な使い方
シンプルな抽出
mid_basic.bas
Sub MidBasicExample()
Dim text As String
Dim result As String
text = "Hello World"
' 7文字目から5文字を抽出
result = Mid(text, 7, 5)
Debug.Print result ' World
' 1文字目から5文字を抽出
result = Mid(text, 1, 5)
Debug.Print result ' Hello
' 3文字目から3文字を抽出
result = Mid(text, 3, 3)
Debug.Print result ' llo
End Sub
文字数の省略
mid_omit_length.bas
Sub MidOmitLength()
Dim text As String
Dim result As String
text = "2025-10-20"
' 6文字目から末尾まで取得
result = Mid(text, 6)
Debug.Print result ' 10-20
' 1文字目から末尾まで(全体を取得)
result = Mid(text, 1)
Debug.Print result ' 2025-10-20
End Sub
チェック
文字数を省略すると、開始位置から文字列の末尾まですべて取得できます。この機能を使うと、特定位置以降のすべてのデータを簡単に取得できます。
日付文字列の分解
基本的な日付の分解
mid_date_parse.bas
Sub ParseDateWithMid()
Dim dateText As String
Dim year As String
Dim month As String
Dim day As String
dateText = "2025-10-20"
' 年を抽出(1文字目から4文字)
year = Mid(dateText, 1, 4)
Debug.Print "年: " & year ' 2025
' 月を抽出(6文字目から2文字)
month = Mid(dateText, 6, 2)
Debug.Print "月: " & month ' 10
' 日を抽出(9文字目から2文字)
day = Mid(dateText, 9, 2)
Debug.Print "日: " & day ' 20
' Date型に変換
Dim actualDate As Date
actualDate = DateSerial(CInt(year), CInt(month), CInt(day))
Debug.Print Format(actualDate, "yyyy年mm月dd日")
End Sub
様々な日付形式の処理
mid_date_formats.bas
Sub ParseVariousDateFormats()
Dim dateText As String
Dim year As String
Dim month As String
Dim day As String
' 形式1: yyyymmdd
dateText = "20251020"
year = Mid(dateText, 1, 4)
month = Mid(dateText, 5, 2)
day = Mid(dateText, 7, 2)
Debug.Print year & "年" & month & "月" & day & "日"
' 形式2: yyyy/mm/dd
dateText = "2025/10/20"
year = Mid(dateText, 1, 4)
month = Mid(dateText, 6, 2)
day = Mid(dateText, 9, 2)
Debug.Print year & "年" & month & "月" & day & "日"
' 形式3: dd-mm-yyyy
dateText = "20-10-2025"
day = Mid(dateText, 1, 2)
month = Mid(dateText, 4, 2)
year = Mid(dateText, 7, 4)
Debug.Print year & "年" & month & "月" & day & "日"
End Sub
固定長データの読み込み
固定長レコードの解析
mid_fixed_length.bas
Sub ParseFixedLengthData()
Dim record As String
Dim id As String
Dim name As String
Dim age As String
Dim address As String
' 固定長レコード(ID:5桁、名前:10文字、年齢:3桁、住所:20文字)
record = "00001山田太郎 030東京都新宿区西新宿 "
' データを抽出
id = Mid(record, 1, 5) ' 1-5文字目
name = Trim(Mid(record, 6, 10)) ' 6-15文字目
age = Mid(record, 16, 3) ' 16-18文字目
address = Trim(Mid(record, 19, 20)) ' 19-38文字目
' 結果表示
Debug.Print "ID: " & id
Debug.Print "名前: " & name
Debug.Print "年齢: " & age
Debug.Print "住所: " & address
End Sub
複数行の固定長データ処理
mid_multiple_records.bas
Sub ProcessMultipleFixedLengthRecords()
Dim records() As Variant
Dim record As Variant
Dim ws As Worksheet
Dim row As Long
Set ws = ActiveSheet
row = 2
' 複数の固定長レコード
records = Array( _
"00001山田太郎 030東京都新宿区 ", _
"00002鈴木花子 025大阪府大阪市 ", _
"00003佐藤次郎 035福岡県福岡市 " _
)
' ヘッダー行
ws.Cells(1, 1).Value = "ID"
ws.Cells(1, 2).Value = "名前"
ws.Cells(1, 3).Value = "年齢"
ws.Cells(1, 4).Value = "住所"
' 各レコードを処理
For Each record In records
ws.Cells(row, 1).Value = Mid(record, 1, 5)
ws.Cells(row, 2).Value = Trim(Mid(record, 6, 10))
ws.Cells(row, 3).Value = CInt(Mid(record, 16, 3))
ws.Cells(row, 4).Value = Trim(Mid(record, 19))
row = row + 1
Next record
End Sub
実践的な活用例
クレジットカード番号のマスキング
mid_mask_credit_card.bas
Function MaskCreditCard(cardNumber As String) As String
Dim masked As String
Dim lastFour As String
' 空白やハイフンを除去
cardNumber = Replace(cardNumber, " ", "")
cardNumber = Replace(cardNumber, "-", "")
If Len(cardNumber) >= 4 Then
' 最後の4桁を取得
lastFour = Mid(cardNumber, Len(cardNumber) - 3, 4)
' 最初の桁以外をマスク
masked = String(Len(cardNumber) - 4, "*") & lastFour
' 4桁ごとにスペースを挿入
Dim i As Long
Dim formatted As String
For i = 1 To Len(masked)
formatted = formatted & Mid(masked, i, 1)
If i Mod 4 = 0 And i < Len(masked) Then
formatted = formatted & " "
End If
Next i
MaskCreditCard = formatted
Else
MaskCreditCard = cardNumber
End If
End Function
Sub TestMaskCreditCard()
Debug.Print MaskCreditCard("1234567890123456")
' 出力: **** **** **** 3456
End Sub
IP アドレスの分解
mid_parse_ip.bas
Sub ParseIPAddress()
Dim ipAddress As String
Dim positions(3) As Long
Dim octets(3) As String
Dim i As Long
ipAddress = "192.168.1.100"
' ドットの位置を検索
positions(0) = 0
positions(1) = InStr(ipAddress, ".")
positions(2) = InStr(positions(1) + 1, ipAddress, ".")
positions(3) = InStr(positions(2) + 1, ipAddress, ".")
' 各オクテットを抽出
octets(0) = Mid(ipAddress, 1, positions(1) - 1)
octets(1) = Mid(ipAddress, positions(1) + 1, positions(2) - positions(1) - 1)
octets(2) = Mid(ipAddress, positions(2) + 1, positions(3) - positions(2) - 1)
octets(3) = Mid(ipAddress, positions(3) + 1)
' 結果表示
For i = 0 To 3
Debug.Print "オクテット" & (i + 1) & ": " & octets(i)
Next i
End Sub
電話番号のフォーマット変換
mid_format_phone.bas
Function FormatPhoneNumber(phone As String) As String
' ハイフンやスペースを除去
phone = Replace(phone, "-", "")
phone = Replace(phone, " ", "")
phone = Replace(phone, "(", "")
phone = Replace(phone, ")", "")
If Len(phone) = 10 Then
' 10桁の場合: 090-1234-5678
FormatPhoneNumber = Mid(phone, 1, 3) & "-" & _
Mid(phone, 4, 4) & "-" & _
Mid(phone, 8, 4)
ElseIf Len(phone) = 11 Then
' 11桁の場合: 090-1234-5678
FormatPhoneNumber = Mid(phone, 1, 3) & "-" & _
Mid(phone, 4, 4) & "-" & _
Mid(phone, 8, 4)
Else
FormatPhoneNumber = phone
End If
End Function
Sub TestFormatPhone()
Debug.Print FormatPhoneNumber("09012345678")
' 出力: 090-1234-5678
Debug.Print FormatPhoneNumber("0312345678")
' 出力: 03-1234-5678
End Sub
商品コードの分解
mid_product_code.bas
Sub ParseProductCode()
Dim productCode As String
Dim category As String
Dim subCategory As String
Dim serialNumber As String
Dim checkDigit As String
' 商品コード形式: AA-BB-CCCC-D
' AA: カテゴリ、BB: サブカテゴリ、CCCC: シリアル番号、D: チェックデジット
productCode = "AB12WXYZ9"
category = Mid(productCode, 1, 2)
subCategory = Mid(productCode, 3, 2)
serialNumber = Mid(productCode, 5, 4)
checkDigit = Mid(productCode, 9, 1)
Debug.Print "カテゴリ: " & category
Debug.Print "サブカテゴリ: " & subCategory
Debug.Print "シリアル番号: " & serialNumber
Debug.Print "チェックデジット: " & checkDigit
End Sub
InStr との組み合わせ
動的な位置からの抽出
mid_with_instr.bas
Sub MidWithInStr()
Dim text As String
Dim startPos As Long
Dim endPos As Long
Dim extracted As String
text = "価格: 1,980円(税込)"
' 「: 」の後から「円」の前までを抽出
startPos = InStr(text, ": ")
endPos = InStr(text, "円")
If startPos > 0 And endPos > 0 Then
extracted = Mid(text, startPos + 2, endPos - startPos - 2)
Debug.Print "価格: " & extracted ' 1,980
' カンマを除去して数値に変換
Dim price As Long
price = CLng(Replace(extracted, ",", ""))
Debug.Print "数値: " & price ' 1980
End If
End Sub
ファイルパスから拡張子を取得
mid_get_extension.bas
Function GetExtension(filePath As String) As String
Dim dotPos As Long
' 末尾から最初の.を検索
dotPos = InStrRev(filePath, ".")
If dotPos > 0 Then
' .の後から末尾まで抽出
GetExtension = Mid(filePath, dotPos + 1)
Else
GetExtension = ""
End If
End Function
Sub TestGetExtension()
Debug.Print GetExtension("report.xlsx") ' xlsx
Debug.Print GetExtension("data.backup.csv") ' csv
Debug.Print GetExtension("C:\folder\file.txt") ' txt
End Sub
注意点と Tips
範囲外の位置指定
mid_out_of_range.bas
Sub MidOutOfRange()
Dim text As String
Dim result As String
text = "Hello"
' 開始位置が文字列の長さを超える場合
result = Mid(text, 10, 5)
Debug.Print "結果: [" & result & "]" ' 空文字列
' 文字数が残りの文字数を超える場合
result = Mid(text, 3, 100)
Debug.Print "結果: [" & result & "]" ' llo(残りすべて)
End Sub
チェック
開始位置が文字列の長さを超える場合、Mid関数は空文字列を返します。指定した文字数が残りの文字数を超える場合は、残りすべてが返されます。
全角・半角の処理
mid_fullwidth_halfwidth.bas
Sub MidFullwidthHalfwidth()
Dim text As String
Dim result As String
' 全角文字も1文字としてカウント
text = "こんにちは世界"
result = Mid(text, 6, 2)
Debug.Print result ' 世界
' 全角と半角が混在
text = "VBA入門"
result = Mid(text, 1, 3)
Debug.Print result ' VBA
End Sub
チェック
Mid関数は、全角文字も半角文字も同じく1文字としてカウントします。バイト単位で処理したい場合は、MidB関数を使用します。
まとめ
Mid 関数は、文字列の指定位置から部分文字列を抽出する基本的かつ重要な関数です。
重要なポイント:
- 開始位置は 1 から始まる
- 文字数を省略すると末尾までを取得
- 固定長データの解析に最適
- InStr 関数と組み合わせて動的な抽出が可能
- 全角・半角を区別せず 1 文字としてカウント
関連関数:
- Left/Right関数VBAのLeft関数とRight関数を使って、文字列の先頭や末尾から指定した文字数を抽出する方法を詳しく解説します。ファイル拡張子の取得、プレフィックスの処理などに便利です。:先頭・末尾からの抽出
- InStr関数VBAのInStr関数とInStrRev関数を使って、文字列内で特定の文字列を検索し、その位置を取得する方法を詳しく解説します。文字列の検証やデータ抽出に必須の関数です。:文字列の検索
- Len関数VBAのLen関数を使って、文字列の文字数を取得する方法を詳しく解説します。入力チェック、データ検証、固定長フォーマットの処理に必須の関数です。:文字列の長さ
Mid 関数をマスターすることで、様々な文字列抽出処理が効率的に行えるようになります。
#VBA
#Mid
#文字列操作
#抽出