日付関数

にメンテナンス済み

VBA で業務システムを開発する際、日付の計算は避けて通れない重要なスキルです。納期計算、期限管理、勤怠処理、レポート生成など、様々な場面で日付を加算・減算・比較する必要があります。

この記事では、VBA で頻繁に使用される日付関数について、基本的な使い方から実践的な活用例まで詳しく解説します。

日付操作が必要となるシチュエーション

実務では、以下のような場面で日付操作が必要になります:

  • 納期計算: 受注日から営業日ベースで納期を算出
  • 期限管理: 契約日から ○ ヶ月後の更新日を計算
  • 勤怠処理: 勤務日数や残業時間の集計
  • レポート生成: 月初・月末・四半期末などの日付取得
  • 年齢計算: 生年月日から現在の年齢を算出
  • スケジュール管理: 定期イベントの次回実施日を計算

これらの処理を効率的に行うために、VBA には強力な日付関数が用意されています。

主要な日付関数一覧

VBA で使用できる主な日付関数を紹介します:

関数用途戻り値
Date現在の日付を取得Date
Now現在の日付と時刻を取得Date
Time現在の時刻を取得Date
Year日付から年を取得Integer
Month日付から月を取得Integer
Day日付から日を取得Integer
Weekday日付から曜日を取得Integer
DateAdd日付に期間を加算Date
DateDiff2 つの日付の差を計算Long
DateSerial年月日から日付を作成Date
DateValue文字列を日付に変換Date
IsDate日付として有効か判定Boolean
Format日付を書式設定して文字列に変換String

それでは、各関数について詳しく見ていきましょう。

現在の日付・時刻を取得する

Date 関数:現在の日付

date_function.bas
Sub GetCurrentDate()
    Dim today As Date
    today = Date

    Debug.Print "今日の日付: " & today
    ' 出力例: 今日の日付: 2025/12/02
End Sub

Now 関数:現在の日付と時刻

now_function.bas
Sub GetCurrentDateTime()
    Dim currentDateTime As Date
    currentDateTime = Now

    Debug.Print "現在日時: " & currentDateTime
    ' 出力例: 現在日時: 2025/12/02 14:30:25
End Sub

Time 関数:現在の時刻

time_function.bas
Sub GetCurrentTime()
    Dim currentTime As Date
    currentTime = Time

    Debug.Print "現在時刻: " & currentTime
    ' 出力例: 現在時刻: 14:30:25
End Sub

日付から年月日を取得する

Year、Month、Day 関数

日付から年・月・日をそれぞれ整数として取得できます。

year_month_day.bas
Sub ExtractDateParts()
    Dim targetDate As Date
    targetDate = #12/25/2025#

    Debug.Print "年: " & Year(targetDate)   ' => 2025
    Debug.Print "月: " & Month(targetDate)  ' => 12
    Debug.Print "日: " & Day(targetDate)    ' => 25
End Sub

実用例:月初と月末の取得

month_start_end.bas
Sub GetMonthStartAndEnd()
    Dim targetDate As Date
    Dim monthStart As Date
    Dim monthEnd As Date

    targetDate = Date  ' 今日の日付

    ' 月初日を取得(当月の1日)
    monthStart = DateSerial(Year(targetDate), Month(targetDate), 1)

    ' 月末日を取得(翌月の1日の前日)
    monthEnd = DateSerial(Year(targetDate), Month(targetDate) + 1, 0)

    Debug.Print "対象日: " & targetDate
    Debug.Print "月初日: " & monthStart
    Debug.Print "月末日: " & monthEnd
End Sub
チェック

DateSerial 関数で日に 0 を指定すると、前月の末日が取得できます。これを利用して「翌月の0日=当月の末日」という計算ができます。

Weekday 関数:曜日を取得する

基本構文

Weekday(日付, [週の開始曜日])

Weekday 関数は、日付から曜日を 1〜7 の数値で返します。

曜日の数値対応

戻り値曜日定数
1日曜日vbSunday
2月曜日vbMonday
3火曜日vbTuesday
4水曜日vbWednesday
5木曜日vbThursday
6金曜日vbFriday
7土曜日vbSaturday

基本的な使い方

weekday_basic.bas
Sub GetWeekday()
    Dim targetDate As Date
    Dim dayOfWeek As Integer

    targetDate = #12/2/2025#  ' 2025年12月2日
    dayOfWeek = Weekday(targetDate)

    Debug.Print "曜日番号: " & dayOfWeek  ' => 3(火曜日)

    ' 曜日名を取得
    Debug.Print "曜日名: " & WeekdayName(dayOfWeek)  ' => 火曜日
End Sub

実用例:土日判定

weekend_check.bas
Function IsWeekend(targetDate As Date) As Boolean
    Dim dayOfWeek As Integer
    dayOfWeek = Weekday(targetDate)

    ' 日曜日(1)または土曜日(7)ならTrue
    IsWeekend = (dayOfWeek = vbSunday Or dayOfWeek = vbSaturday)
End Function

Sub TestWeekend()
    Debug.Print IsWeekend(#12/6/2025#)  ' => True(土曜日)
    Debug.Print IsWeekend(#12/8/2025#)  ' => False(月曜日)
End Sub

DateAdd 関数:日付に期間を加算する

基本構文

DateAdd(加算単位, 加算数, 日付)

DateAdd 関数は、日付に指定した期間を加算(または減算)した新しい日付を返します。

加算単位(interval)一覧

単位意味
yyyy1 年後、2 年前
q四半期1 四半期後(3 ヶ月後)
m3 ヶ月後、6 ヶ月前
y年間通算日日数加算(“d”と同じ)
d7 日後、30 日前
w平日日数加算(“d”と同じ)
ww2 週間後、1 週間前
h時間3 時間後
n30 分後
s10 秒後

基本的な使い方

dateadd_basic.bas
Sub DateAddExamples()
    Dim baseDate As Date
    baseDate = #12/2/2025#

    ' 7日後
    Debug.Print "7日後: " & DateAdd("d", 7, baseDate)
    ' => 2025/12/09

    ' 3ヶ月後
    Debug.Print "3ヶ月後: " & DateAdd("m", 3, baseDate)
    ' => 2026/03/02

    ' 1年後
    Debug.Print "1年後: " & DateAdd("yyyy", 1, baseDate)
    ' => 2026/12/02

    ' 2週間後
    Debug.Print "2週間後: " & DateAdd("ww", 2, baseDate)
    ' => 2025/12/16

    ' 30日前(負の値で減算)
    Debug.Print "30日前: " & DateAdd("d", -30, baseDate)
    ' => 2025/11/02
End Sub

実用例:納期計算

delivery_date.bas
Function CalculateDeliveryDate(orderDate As Date, leadDays As Long) As Date
    ' 受注日から営業日ベースで納期を計算
    Dim deliveryDate As Date
    Dim addedDays As Long

    deliveryDate = orderDate
    addedDays = 0

    Do While addedDays < leadDays
        deliveryDate = DateAdd("d", 1, deliveryDate)
        ' 土日をスキップ
        If Weekday(deliveryDate) <> vbSunday And _
           Weekday(deliveryDate) <> vbSaturday Then
            addedDays = addedDays + 1
        End If
    Loop

    CalculateDeliveryDate = deliveryDate
End Function

Sub TestDeliveryDate()
    Dim orderDate As Date
    orderDate = #12/2/2025#  ' 火曜日

    ' 5営業日後の納期
    Debug.Print "納期: " & CalculateDeliveryDate(orderDate, 5)
    ' => 2025/12/09(火曜日)
End Sub
チェック

負の数を指定すると減算になります。例えば DateAdd("m", -3, Date) は3ヶ月前の日付を返します。

DateDiff 関数:日付の差を計算する

基本構文

DateDiff(比較単位, 開始日, 終了日, [週の開始曜日], [年の開始週])

DateDiff 関数は、2 つの日付の間の期間を指定した単位で返します。

基本的な使い方

datediff_basic.bas
Sub DateDiffExamples()
    Dim startDate As Date
    Dim endDate As Date

    startDate = #1/1/2025#
    endDate = #12/31/2025#

    ' 日数の差
    Debug.Print "日数: " & DateDiff("d", startDate, endDate)
    ' => 364

    ' 月数の差
    Debug.Print "月数: " & DateDiff("m", startDate, endDate)
    ' => 11

    ' 週数の差
    Debug.Print "週数: " & DateDiff("ww", startDate, endDate)
    ' => 52

    ' 年数の差
    Debug.Print "年数: " & DateDiff("yyyy", startDate, endDate)
    ' => 0(同じ年なので)
End Sub

実用例:年齢計算

age_calculation.bas
Function CalculateAge(birthDate As Date, Optional baseDate As Date) As Long
    ' 基準日が省略された場合は今日の日付を使用
    If baseDate = 0 Then baseDate = Date

    Dim age As Long

    ' 年の差を計算
    age = DateDiff("yyyy", birthDate, baseDate)

    ' 今年の誕生日がまだ来ていない場合は1を引く
    If DateSerial(Year(baseDate), Month(birthDate), Day(birthDate)) > baseDate Then
        age = age - 1
    End If

    CalculateAge = age
End Function

Sub TestAge()
    ' 1990年5月15日生まれの人の年齢
    Debug.Print "年齢: " & CalculateAge(#5/15/1990#) & "歳"
End Sub

実用例:経過日数と残り日数

days_calculation.bas
Sub ProjectProgress()
    Dim projectStart As Date
    Dim projectEnd As Date
    Dim today As Date
    Dim elapsed As Long
    Dim remaining As Long

    projectStart = #10/1/2025#
    projectEnd = #3/31/2026#
    today = Date

    ' 経過日数
    elapsed = DateDiff("d", projectStart, today)

    ' 残り日数
    remaining = DateDiff("d", today, projectEnd)

    Debug.Print "プロジェクト開始: " & projectStart
    Debug.Print "プロジェクト終了: " & projectEnd
    Debug.Print "経過日数: " & elapsed & "日"
    Debug.Print "残り日数: " & remaining & "日"
End Sub
チェック

DateDiff で月数を計算する場合、単純に月の差を返すだけで、日数は考慮されません。例えば、1月31日から2月1日の月数差は1となります。正確な「経過月数」が必要な場合は、日付も考慮したロジックが必要です。

DateSerial 関数:年月日から日付を作成する

基本構文

DateSerial(年, 月, 日)

DateSerial 関数は、年・月・日の数値から Date 型の値を作成します。

基本的な使い方

dateserial_basic.bas
Sub DateSerialExamples()
    Dim newDate As Date

    ' 2025年12月25日を作成
    newDate = DateSerial(2025, 12, 25)
    Debug.Print newDate  ' => 2025/12/25

    ' 年の下2桁でも作成可能(ただし非推奨)
    newDate = DateSerial(25, 12, 25)
    Debug.Print newDate  ' => 2025/12/25
End Sub

日付の自動調整機能

DateSerial は、範囲外の値を自動的に調整します。

dateserial_overflow.bas
Sub DateSerialOverflow()
    ' 13月は翌年の1月に調整される
    Debug.Print DateSerial(2025, 13, 1)
    ' => 2026/01/01

    ' 32日は翌月に繰り越される
    Debug.Print DateSerial(2025, 1, 32)
    ' => 2025/02/01

    ' 0日は前月の末日になる
    Debug.Print DateSerial(2025, 3, 0)
    ' => 2025/02/28

    ' 負の日数も使える
    Debug.Print DateSerial(2025, 3, -1)
    ' => 2025/02/27
End Sub

実用例:四半期の開始日と終了日

quarter_dates.bas
Function GetQuarterStart(targetDate As Date) As Date
    Dim quarter As Integer
    quarter = (Month(targetDate) - 1) \ 3 + 1

    GetQuarterStart = DateSerial(Year(targetDate), (quarter - 1) * 3 + 1, 1)
End Function

Function GetQuarterEnd(targetDate As Date) As Date
    Dim quarter As Integer
    quarter = (Month(targetDate) - 1) \ 3 + 1

    GetQuarterEnd = DateSerial(Year(targetDate), quarter * 3 + 1, 0)
End Function

Sub TestQuarter()
    Dim testDate As Date
    testDate = #11/15/2025#

    Debug.Print "対象日: " & testDate
    Debug.Print "四半期開始: " & GetQuarterStart(testDate)  ' => 2025/10/01
    Debug.Print "四半期終了: " & GetQuarterEnd(testDate)    ' => 2025/12/31
End Sub

DateValue 関数:文字列を日付に変換する

基本構文

DateValue(文字列)

DateValue 関数は、日付を表す文字列を Date 型に変換します。

基本的な使い方

datevalue_basic.bas
Sub DateValueExamples()
    ' 様々な形式の文字列を変換
    Debug.Print DateValue("2025/12/25")      ' => 2025/12/25
    Debug.Print DateValue("2025-12-25")      ' => 2025/12/25
    Debug.Print DateValue("December 25, 2025")  ' => 2025/12/25
    Debug.Print DateValue("25-Dec-2025")     ' => 2025/12/25
End Sub

IsDate 関数と組み合わせた安全な変換

safe_date_conversion.bas
Function SafeDateConvert(dateString As String) As Variant
    ' 日付として有効かチェックしてから変換
    If IsDate(dateString) Then
        SafeDateConvert = DateValue(dateString)
    Else
        SafeDateConvert = Null
    End If
End Function

Sub TestSafeConvert()
    Debug.Print SafeDateConvert("2025/12/25")  ' => 2025/12/25
    Debug.Print SafeDateConvert("invalid")     ' => Null
    Debug.Print IsNull(SafeDateConvert("abc")) ' => True
End Sub
チェック

DateValue は無効な日付文字列を渡すとエラーになります。ユーザー入力など不確実なデータを扱う場合は、必ず IsDate でチェックするか、エラーハンドリングを行いましょう。

Format 関数:日付を書式設定する

基本構文

Format(日付, 書式文字列)

Format 関数を使うと、日付を様々な形式の文字列に変換できます。

主な書式指定文字

書式説明出力例
yyyy4 桁の年2025
yy2 桁の年25
mm2 桁の月01〜12
m月(0 埋めなし)1〜12
dd2 桁の日01〜31
d日(0 埋めなし)1〜31
ddd曜日(短縮)Mon〜Sun
dddd曜日(完全)Monday
aaa曜日(日本語短縮)月〜日
aaaa曜日(日本語)月曜日

基本的な使い方

format_date.bas
Sub FormatDateExamples()
    Dim targetDate As Date
    targetDate = #12/2/2025#

    ' 様々な形式で出力
    Debug.Print Format(targetDate, "yyyy/mm/dd")
    ' => 2025/12/02

    Debug.Print Format(targetDate, "yyyy年mm月dd日")
    ' => 2025年12月02日

    Debug.Print Format(targetDate, "yyyy-mm-dd")
    ' => 2025-12-02

    Debug.Print Format(targetDate, "yyyymmdd")
    ' => 20251202

    Debug.Print Format(targetDate, "yyyy/mm/dd (aaa)")
    ' => 2025/12/02 (火)

    Debug.Print Format(targetDate, "yyyy年m月d日 aaaa")
    ' => 2025年12月2日 火曜日
End Sub

実用例:ファイル名に日付を含める

filename_with_date.bas
Function GenerateFileName(baseName As String) As String
    ' 日付付きのファイル名を生成
    ' 例: レポート_20251202.xlsx
    GenerateFileName = baseName & "_" & Format(Date, "yyyymmdd") & ".xlsx"
End Function

Sub TestFileName()
    Debug.Print GenerateFileName("売上レポート")
    ' => 売上レポート_20251202.xlsx

    Debug.Print GenerateFileName("月次報告")
    ' => 月次報告_20251202.xlsx
End Sub

実践的な活用例

例 1:月末締め処理

month_end_processing.bas
Sub MonthEndProcessing()
    Dim processDate As Date
    Dim monthEndDate As Date
    Dim isMonthEnd As Boolean

    processDate = Date
    monthEndDate = DateSerial(Year(processDate), Month(processDate) + 1, 0)

    isMonthEnd = (processDate = monthEndDate)

    If isMonthEnd Then
        Debug.Print "本日は月末です。締め処理を実行します。"
        ' 締め処理のコード
    Else
        Debug.Print "本日は月末ではありません。"
        Debug.Print "月末日: " & monthEndDate
        Debug.Print "残り日数: " & DateDiff("d", processDate, monthEndDate) & "日"
    End If
End Sub

例 2:契約更新日の計算

contract_renewal.bas
Function GetNextRenewalDate(contractStartDate As Date, _
                           renewalIntervalMonths As Integer) As Date
    ' 契約開始日から次回更新日を計算
    Dim today As Date
    Dim nextRenewal As Date

    today = Date
    nextRenewal = contractStartDate

    ' 今日より後の更新日になるまでループ
    Do While nextRenewal <= today
        nextRenewal = DateAdd("m", renewalIntervalMonths, nextRenewal)
    Loop

    GetNextRenewalDate = nextRenewal
End Function

Sub TestRenewal()
    Dim contractStart As Date
    contractStart = #4/1/2023#

    Debug.Print "契約開始日: " & contractStart
    Debug.Print "次回更新日(年次): " & GetNextRenewalDate(contractStart, 12)
    Debug.Print "次回更新日(半期): " & GetNextRenewalDate(contractStart, 6)
End Sub

例 3:営業日計算(祝日対応)

business_days.bas
' 祝日リストをシートに持っていると仮定
Function IsHoliday(targetDate As Date) As Boolean
    ' この例では簡略化のため、祝日リストはハードコード
    ' 実際の運用では、シートやデータベースから取得することを推奨
    Dim holidays As Variant
    holidays = Array(#1/1/2025#, #1/13/2025#, #2/11/2025#, _
                     #2/23/2025#, #3/20/2025#, #4/29/2025#, _
                     #5/3/2025#, #5/4/2025#, #5/5/2025#, _
                     #5/6/2025#, #7/21/2025#, #8/11/2025#)

    Dim i As Long
    For i = LBound(holidays) To UBound(holidays)
        If targetDate = holidays(i) Then
            IsHoliday = True
            Exit Function
        End If
    Next i

    IsHoliday = False
End Function

Function IsBusinessDay(targetDate As Date) As Boolean
    ' 土日と祝日以外は営業日
    If Weekday(targetDate) = vbSunday Then
        IsBusinessDay = False
    ElseIf Weekday(targetDate) = vbSaturday Then
        IsBusinessDay = False
    ElseIf IsHoliday(targetDate) Then
        IsBusinessDay = False
    Else
        IsBusinessDay = True
    End If
End Function

Function AddBusinessDays(startDate As Date, businessDays As Long) As Date
    Dim result As Date
    Dim addedDays As Long

    result = startDate
    addedDays = 0

    Do While addedDays < businessDays
        result = DateAdd("d", 1, result)
        If IsBusinessDay(result) Then
            addedDays = addedDays + 1
        End If
    Loop

    AddBusinessDays = result
End Function

Sub TestBusinessDays()
    Dim startDate As Date
    startDate = #12/2/2025#

    Debug.Print "開始日: " & startDate
    Debug.Print "5営業日後: " & AddBusinessDays(startDate, 5)
    Debug.Print "10営業日後: " & AddBusinessDays(startDate, 10)
End Sub

練習問題

問題1:DateAdd関数の結果

DateAdd("m", 3, #1/31/2025#) の結果は何になりますか?

DateAdd で月を加算する場合、元の日付の日が加算後の月に存在しない場合は、その月の末日に調整されます。1月31日の3ヶ月後は4月31日となりますが、4月は30日までなので、4月30日が返されます。

問題2:月末日の取得

2025 年 2 月の末日を取得するための正しいコードはどれですか?

DateSerial で日に0を指定すると、前月の末日が返されます。よって DateSerial(2025, 3, 0) は2025年2月28日を返します。選択肢4の DateAdd を使う方法も正しいですが、より簡潔なのは DateSerial を使う方法です。

問題3:Weekday関数の戻り値

Weekday(#12/25/2025#) の戻り値は何ですか?(2025 年 12 月 25 日は木曜日です)

Weekday関数はデフォルトで日曜日を1として数値を返します。木曜日は5となります(日=1, 月=2, 火=3, 水=4, 木=5, 金=6, 土=7)。曜日名を取得するには WeekdayName 関数を使用します。

まとめ

この記事では、VBA の主要な日付関数について解説しました。

関数主な用途
Date/Now現在の日付・時刻を取得
Year/Month/Day日付から年月日を分解
Weekday曜日を数値で取得
DateAdd日付に期間を加算・減算
DateDiff2 つの日付の差を計算
DateSerial年月日から日付を作成
DateValue文字列を日付に変換
Format日付を指定形式の文字列に変換

これらの関数を組み合わせることで、納期計算、年齢計算、営業日計算など、実務で必要となる様々な日付処理を実現できます。

チェック

日付処理でよくあるミスは、月末日の扱いと閏年の考慮です。DateSerial や DateAdd は自動調整機能があるため、これらの関数を活用することでバグを減らせます。

#VBA #日付関数 #DateAdd #DateDiff #DateSerial