Excel VBA 逆引き集 | 日付変換

Excel VBA
スポンサーリンク

日付変換

Excelのデータでは「文字列の日付」「シリアル値」「和暦や全角文字が混ざった日付」などが入りがちです。これを正しく 日付型に変換 して扱うのは、データ処理の基本です。初心者向けに、コード例とテンプレートをかみ砕いて説明します。


基本の考え方

  • IsDate関数: 値が日付かどうか判定。
  • CDate関数: 文字列や数値を日付型に変換。
  • Format関数: 日付を指定の書式に変換して表示。
  • シリアル値: Excelの日付は内部的に「1900年1月1日からの通算日数」で管理されている。

テンプレ1:文字列を日付に変換(CDate)

Sub Convert_CDate()
    Dim s As String
    s = "2025/12/11"

    If IsDate(s) Then
        Dim d As Date
        d = CDate(s)
        MsgBox "変換結果: " & d
    Else
        MsgBox "日付ではありません"
    End If
End Sub
VB
  • ポイント: "2025/12/11"2025/12/11 (日付型)。
  • IsDateで安全確認: 文字列が日付かどうかを判定してから変換。

テンプレ2:日付を指定フォーマットで表示(Format)

Sub Convert_Format()
    Dim d As Date
    d = Date ' 今日の日付

    MsgBox Format(d, "yyyy-mm-dd")   ' 2025-12-11
    MsgBox Format(d, "yyyy年m月d日") ' 2025年12月11日
    MsgBox Format(d, "mm/dd")        ' 12/11
End Sub
VB
  • ポイント: Formatで表示形式を自由に変えられる。
  • 用途: レポートやファイル名に日付を使うときに便利。

テンプレ3:シートの文字列日付を変換して書き戻す

Sub Convert_RangeDate()
    Dim ws As Worksheet: Set ws = Worksheets("Data")
    Dim lastRow As Long: lastRow = ws.Cells(ws.Rows.Count, "A").End(xlUp).Row

    Dim r As Long, v As Variant
    For r = 2 To lastRow
        v = ws.Cells(r, "A").Value
        If IsDate(v) Then
            ws.Cells(r, "A").Value = CDate(v) ' 日付型に変換
        End If
    Next r
End Sub
VB
  • ポイント: 「文字列として保存されている日付」を「日付型」に変換できる。
  • 効果: 並べ替えや計算が正しくできるようになる。

テンプレ4:日付の加算・減算

Sub Convert_DateMath()
    Dim d As Date
    d = CDate("2025/12/11")

    MsgBox "翌日: " & d + 1
    MsgBox "7日前: " & d - 7
End Sub
VB
  • ポイント: 日付はシリアル値なので「+1」で翌日、「-7」で7日前になる。

テンプレ5:文字列から安全に日付を取り出す関数

Function SafeToDate(ByVal s As Variant) As Date
    If IsDate(s) Then
        SafeToDate = CDate(s)
    Else
        SafeToDate = 0 ' 無効な場合は0(1900/1/0扱い)
    End If
End Function

Sub Convert_Safe()
    Dim arr As Variant
    arr = Array("2025/12/11", "12-11-2025", "ABC")

    Dim i As Long
    For i = LBound(arr) To UBound(arr)
        Debug.Print arr(i), "→", SafeToDate(arr(i))
    Next i
End Sub
VB
  • 結果:
    • "2025/12/11" → 2025/12/11
    • "12-11-2025" → 2025/12/11
    • "ABC" → 0(無効)

例題で練習

'例1:文字列を日付に変換
Sub Example_CDate()
    Convert_CDate
End Sub

'例2:日付を指定フォーマットで表示
Sub Example_Format()
    Convert_Format
End Sub

'例3:シートのA列を日付型に変換
Sub Example_Range()
    Convert_RangeDate
End Sub

'例4:日付の加算・減算
Sub Example_Math()
    Convert_DateMath
End Sub

'例5:SafeToDate関数で混在データを変換
Sub Example_Safe()
    Convert_Safe
End Sub
VB

初心者向けポイント

  • IsDateで安全確認: 文字列が日付かどうかを必ずチェック。
  • CDateで変換: 文字列や数値を日付型に変換。
  • Formatで表示: レポートやファイル名に便利。
  • 日付はシリアル値: 加算・減算で日付計算ができる。
  • 安全関数を作る: SafeToDate のようにまとめておくと再利用できる。
タイトルとURLをコピーしました