Len関数
にメンテナンス済み
Len 関数は、文字列の長さ(文字数)を取得する VBA の基本的な関数です。入力チェック、データ検証、固定長フォーマットの処理など、あらゆる文字列操作で使用されます。
基本構文
Len(文字列)
引数
引数 | 型 | 必須 | 説明 |
---|---|---|---|
文字列 | String/Variant | ○ | 長さを取得する文字列 |
戻り値
文字列の長さ(Long 型)
チェック
Len関数は、全角文字も半角文字も同じく1文字としてカウントします。バイト数を取得したい場合は、LenB関数を使用します。
基本的な使い方
シンプルな文字数取得
len_basic.bas
Sub LenBasicExample()
Dim text As String
Dim length As Long
text = "Hello World"
length = Len(text)
Debug.Print length ' 11
text = "VBA"
length = Len(text)
Debug.Print length ' 3
' 空文字列
text = ""
length = Len(text)
Debug.Print length ' 0
End Sub
全角・半角の文字数
len_fullwidth.bas
Sub LenFullwidthHalfwidth()
Dim text As String
Dim length As Long
' 半角のみ
text = "Hello"
length = Len(text)
Debug.Print text & ": " & length & "文字" ' Hello: 5文字
' 全角のみ
text = "こんにちは"
length = Len(text)
Debug.Print text & ": " & length & "文字" ' こんにちは: 5文字
' 混在
text = "VBA入門"
length = Len(text)
Debug.Print text & ": " & length & "文字" ' VBA入門: 5文字
End Sub
チェック
Len関数は、全角文字も半角文字も同じく1文字としてカウントします。全角の「あ」も半角の「a」も、どちらも長さは1です。
入力検証
文字数チェック
len_validation.bas
Function ValidatePassword(password As String) As Boolean
Dim length As Long
length = Len(password)
' 8文字以上32文字以下
If length < 8 Then
MsgBox "パスワードは8文字以上で入力してください"
ValidatePassword = False
ElseIf length > 32 Then
MsgBox "パスワードは32文字以内で入力してください"
ValidatePassword = False
Else
ValidatePassword = True
End If
End Function
Sub TestValidatePassword()
Debug.Print ValidatePassword("abc") ' False(短すぎ)
Debug.Print ValidatePassword("abcd1234") ' True
Debug.Print ValidatePassword(String(40, "x")) ' False(長すぎ)
End Sub
必須入力チェック
len_required.bas
Function IsNotEmpty(value As String) As Boolean
IsNotEmpty = (Len(Trim(value)) > 0)
End Function
Sub TestRequired()
Dim name As String
name = InputBox("名前を入力してください")
If Not IsNotEmpty(name) Then
MsgBox "名前は必須です"
Else
MsgBox "ようこそ、" & name & "さん"
End If
End Sub
郵便番号の形式チェック
len_zipcode.bas
Function IsValidZipCode(zipCode As String) As Boolean
' ハイフンを除去
Dim cleaned As String
cleaned = Replace(zipCode, "-", "")
' 7桁の数字かチェック
If Len(cleaned) = 7 And IsNumeric(cleaned) Then
IsValidZipCode = True
Else
IsValidZipCode = False
End If
End Function
Sub TestZipCode()
Debug.Print IsValidZipCode("123-4567") ' True
Debug.Print IsValidZipCode("1234567") ' True
Debug.Print IsValidZipCode("12-3456") ' False(7桁でない)
Debug.Print IsValidZipCode("abc-defg") ' False(数字でない)
End Sub
電話番号の形式チェック
len_phone.bas
Function IsValidPhoneNumber(phone As String) As Boolean
Dim cleaned As String
' ハイフン、スペース、括弧を除去
cleaned = Replace(phone, "-", "")
cleaned = Replace(cleaned, " ", "")
cleaned = Replace(cleaned, "(", "")
cleaned = Replace(cleaned, ")", "")
' 10桁または11桁の数字
If (Len(cleaned) = 10 Or Len(cleaned) = 11) And IsNumeric(cleaned) Then
IsValidPhoneNumber = True
Else
IsValidPhoneNumber = False
End If
End Function
Sub TestPhoneNumber()
Debug.Print IsValidPhoneNumber("090-1234-5678") ' True
Debug.Print IsValidPhoneNumber("03-1234-5678") ' True
Debug.Print IsValidPhoneNumber("12-3456") ' False
End Sub
固定長データの処理
固定長文字列の生成
len_fixed_length.bas
Function ToFixedLength(text As String, length As Long, padChar As String) As String
Dim currentLen As Long
currentLen = Len(text)
If currentLen > length Then
' 長すぎる場合は切り詰め
ToFixedLength = Left(text, length)
ElseIf currentLen < length Then
' 短い場合はパディング
ToFixedLength = text & String(length - currentLen, padChar)
Else
ToFixedLength = text
End If
End Function
Sub TestFixedLength()
Debug.Print "[" & ToFixedLength("ABC", 10, " ") & "]"
' 出力: [ABC ](10文字)
Debug.Print "[" & ToFixedLength("1234567890ABCDE", 10, " ") & "]"
' 出力: [1234567890](切り詰め)
End Sub
固定長レコードの検証
len_validate_record.bas
Function ValidateFixedLengthRecord(record As String) As Boolean
Const EXPECTED_LENGTH As Long = 50
If Len(record) = EXPECTED_LENGTH Then
ValidateFixedLengthRecord = True
Else
Debug.Print "エラー: 長さが" & Len(record) & "文字です(期待値: " & EXPECTED_LENGTH & "文字)"
ValidateFixedLengthRecord = False
End If
End Function
右詰めパディング
len_right_pad.bas
Function RightPad(text As String, totalLength As Long) As String
Dim currentLen As Long
currentLen = Len(text)
If currentLen < totalLength Then
RightPad = text & Space(totalLength - currentLen)
Else
RightPad = Left(text, totalLength)
End If
End Function
Sub TestRightPad()
Debug.Print "[" & RightPad("山田", 10) & "]"
' 出力: [山田 ]
End Sub
左詰めパディング
len_left_pad.bas
Function LeftPad(text As String, totalLength As Long, Optional padChar As String = " ") As String
Dim currentLen As Long
currentLen = Len(text)
If currentLen < totalLength Then
LeftPad = String(totalLength - currentLen, padChar) & text
Else
LeftPad = Right(text, totalLength)
End If
End Function
Sub TestLeftPad()
Debug.Print "[" & LeftPad("123", 10, "0") & "]"
' 出力: [0000000123]
Debug.Print "[" & LeftPad("5", 5, "0") & "]"
' 出力: [00005]
End Sub
文字列の切り詰め
最大長での切り詰め
len_truncate.bas
Function Truncate(text As String, maxLength As Long, Optional suffix As String = "...") As String
If Len(text) <= maxLength Then
Truncate = text
Else
Truncate = Left(text, maxLength - Len(suffix)) & suffix
End If
End Function
Sub TestTruncate()
Dim longText As String
longText = "これは非常に長いテキストで、表示しきれない可能性があります"
Debug.Print Truncate(longText, 20)
' 出力: これは非常に長いテキスト...
Debug.Print Truncate("短いテキスト", 20)
' 出力: 短いテキスト
End Sub
セル幅に合わせた切り詰め
len_truncate_cell.bas
Sub TruncateCellValues()
Dim ws As Worksheet
Dim lastRow As Long
Dim i As Long
Dim maxLength As Long
Set ws = ActiveSheet
lastRow = ws.Cells(ws.Rows.Count, 1).End(xlUp).Row
maxLength = 30 ' 最大30文字
For i = 1 To lastRow
If Len(ws.Cells(i, 1).Value) > maxLength Then
ws.Cells(i, 1).Value = Truncate(ws.Cells(i, 1).Value, maxLength)
End If
Next i
End Sub
LenB との比較
バイト数の取得
len_lenb_compare.bas
Sub CompareLenAndLenB()
Dim text As String
' 半角のみ
text = "Hello"
Debug.Print "文字数: " & Len(text) ' 5
Debug.Print "バイト数: " & LenB(text) ' 10(Unicode: 2バイト/文字)
' 全角のみ
text = "こんにちは"
Debug.Print "文字数: " & Len(text) ' 5
Debug.Print "バイト数: " & LenB(text) ' 10(Unicode: 2バイト/文字)
End Sub
チェック
LenB関数は、VBAの内部文字コード(Unicode)でのバイト数を返します。Shift_JISやUTF-8でのバイト数とは異なる場合があります。
実践的な活用例
ファイルサイズの概算表示
len_file_size.bas
Function EstimateFileSize(text As String) As String
Dim bytes As Long
' 概算(UTF-8エンコーディングを想定)
bytes = Len(text) * 3 ' 日本語は平均3バイト
If bytes < 1024 Then
EstimateFileSize = bytes & " バイト"
ElseIf bytes < 1048576 Then
EstimateFileSize = Format(bytes / 1024, "0.0") & " KB"
Else
EstimateFileSize = Format(bytes / 1048576, "0.0") & " MB"
End If
End Function
文字数カウンター
len_counter.bas
Sub CharacterCounter()
Dim text As String
Dim charCount As Long
Dim spaceCount As Long
Dim i As Long
text = ActiveCell.Value
charCount = Len(text)
' スペースの数をカウント
For i = 1 To Len(text)
If Mid(text, i, 1) = " " Then
spaceCount = spaceCount + 1
End If
Next i
MsgBox "文字数: " & charCount & vbCrLf & _
"スペースを除く: " & (charCount - spaceCount) & vbCrLf & _
"スペース: " & spaceCount
End Sub
進捗バーの表示
len_progress.bas
Function CreateProgressBar(current As Long, total As Long, barLength As Long) As String
Dim percentage As Double
Dim filledLength As Long
Dim bar As String
percentage = current / total
filledLength = Int(barLength * percentage)
bar = String(filledLength, "■") & String(barLength - filledLength, "□")
CreateProgressBar = bar & " " & Format(percentage, "0%")
End Function
Sub TestProgressBar()
Debug.Print CreateProgressBar(25, 100, 20)
' 出力: ■■■■■□□□□□□□□□□□□□□□ 25%
Debug.Print CreateProgressBar(75, 100, 20)
' 出力: ■■■■■■■■■■■■■■■□□□□□ 75%
End Sub
パスワード強度チェック
len_password_strength.bas
Function GetPasswordStrength(password As String) As String
Dim length As Long
Dim strength As String
length = Len(password)
If length < 6 Then
strength = "弱い"
ElseIf length < 10 Then
strength = "普通"
ElseIf length < 15 Then
strength = "強い"
Else
strength = "非常に強い"
End If
GetPasswordStrength = strength & "(" & length & "文字)"
End Function
Sub TestPasswordStrength()
Debug.Print GetPasswordStrength("abc") ' 弱い(3文字)
Debug.Print GetPasswordStrength("abcd1234") ' 普通(8文字)
Debug.Print GetPasswordStrength("P@ssw0rd123") ' 強い(11文字)
End Sub
注意点とエラー処理
Null 値の処理
len_null.bas
Function SafeLen(value As Variant) As Long
On Error Resume Next
If IsNull(value) Then
SafeLen = 0
ElseIf IsEmpty(value) Then
SafeLen = 0
Else
SafeLen = Len(value)
End If
On Error GoTo 0
End Function
Sub TestSafeLen()
Debug.Print SafeLen("Hello") ' 5
Debug.Print SafeLen(Empty) ' 0
Debug.Print SafeLen(Null) ' 0
End Sub
数値の文字列長
len_numeric.bas
Sub LenNumeric()
Dim num As Long
Dim text As String
num = 12345
' 数値をそのままLenに渡すとエラー(文字列変換が必要)
text = CStr(num)
Debug.Print "数値 " & num & " の桁数: " & Len(text) ' 5
' より簡潔に
Debug.Print Len(CStr(num)) ' 5
End Sub
チェック
Len関数に数値を直接渡すとエラーが発生します。必ずCStr関数で文字列に変換してから使用してください。
まとめ
Len 関数は、文字列の長さを取得する最も基本的な関数です。
重要なポイント:
- 文字列の文字数を取得(全角も半角も 1 文字)
- 入力検証、データ検証に必須
- 固定長フォーマットの処理に活用
- LenB 関数はバイト数を取得(Unicode 基準)
- Null 値や数値には注意が必要
主な用途:
- 入力チェック:パスワード、郵便番号、電話番号
- 固定長処理:パディング、切り詰め
- データ検証:必須チェック、最大長チェック
- 表示制御:文字数制限、プログレスバー
関連関数:
- Left/Right関数VBAのLeft関数とRight関数を使って、文字列の先頭や末尾から指定した文字数を抽出する方法を詳しく解説します。ファイル拡張子の取得、プレフィックスの処理などに便利です。:先頭・末尾からの抽出
- Mid関数VBAのMid関数を使って、文字列の指定した位置から指定した文字数の部分文字列を抽出する方法を詳しく解説します。固定長データの解析やデータの切り出しに便利です。:任意の位置からの抽出
- Trim関数VBAのTrim、LTrim、RTrim関数を使って、文字列の先頭や末尾の空白を削除する方法を詳しく解説します。データクレンジングやCSV処理に必須の関数です。:空白の削除
Len 関数を適切に使うことで、堅牢な文字列処理とデータ検証が実現できます。
#VBA
#Len
#文字列操作
#長さ
#検証