web-dev-qa-db-ja.com

IsDate関数が予期しない結果を返します

なぜIsDate("13.50")Trueを返しますが、IsDate("12.25.2010")Falseを返しますか?

28
mwolfe02

最近、この小さな「機能」につまずいたので、VBとVBAのIsDate関数を取り巻く問題のいくつかの認識を高めたいと思いました。

シンプルなケース

ご想像のとおり、IsDateは、Dateデータ型が渡されたときにTrueを返し、Stringsを除く他のすべてのデータ型に対してはFalseを返します。文字列の場合、IsDateは、文字列の内容に基づいてTrueまたはFalseを返します。

_IsDate(CDate("1/1/1980"))  --> True
IsDate(#12/31/2000#)       --> True
IsDate(12/24)              --> False  '12/24 evaluates to a Double: 0.5'
IsDate("Foo")              --> False
IsDate("12/24")            --> True
_

IsDateTime?

IsDateは、時刻としてフォーマットされた文字列に対してIsDateTimeを返すため、より正確にTrueという名前にする必要があります。

_IsDate("10:55 AM")   --> True
IsDate("23:30")      --> True  'CDate("23:30")   --> 11:30:00 PM'
IsDate("1:30:59")    --> True  'CDate("1:30:59") --> 1:30:59 AM'
IsDate("13:55 AM")   --> True  'CDate("13:55 AM")--> 1:55:00 PM'
IsDate("13:55 PM")   --> True  'CDate("13:55 PM")--> 1:55:00 PM'
_

上記の最後の2つの例から、IsDateは完全なvalidatorではないことに注意してください。

落とし穴!

IsDateは時間を受け入れるだけでなく、多くの形式の時間を受け入れます。 1つは、区切り文字としてピリオド(_._)を使用します。これは、期間を日付区切り記号としてではなく時間区切り記号として使用できるため、混乱を招きます。

_IsDate("13.50")     --> True  'CDate("13.50")    --> 1:50:00 PM'
IsDate("12.25")     --> True  'CDate("12.25")    --> 12:25:00 PM'
IsDate("12.25.10")  --> True  'CDate("12.25.10") --> 12:25:10 PM'
IsDate("12.25.2010")--> False '2010 > 59 (number of seconds in a minute - 1)'
IsDate("24.12")     --> False '24 > 23 (number of hours in a day - 1)'
IsDate("0.12")      --> True  'CDate("0.12")     --> 12:12:00 AM
_

文字列を解析し、その見かけ上の型に基づいて操作している場合、これは問題になる可能性があります。例えば:

_Function Bar(Var As Variant)
    If IsDate(Var) Then
        Bar = "This is a date"
    ElseIf IsNumeric(Var) Then
        Bar = "This is numeric"
    Else
        Bar = "This is something else"
    End If
End Function

?Bar("12.75")   --> This is numeric
?Bar("12.50")   --> This is a date
_

回避策

基になるデータ型のバリアントをテストする場合は、TypeName(Var) = "Date"ではなくIsDate(Var)を使用する必要があります。

_TypeName(#12/25/2010#)  --> Date
TypeName("12/25/2010")  --> String

Function Bar(Var As Variant)
    Select Case TypeName(Var)
    Case "Date"
        Bar = "This is a date type"
    Case "Long", "Double", "Single", "Integer", "Currency", "Decimal", "Byte"
        Bar = "This is a numeric type"
    Case "String"
        Bar = "This is a string type"
    Case "Boolean"
        Bar = "This is a boolean type"
    Case Else
        Bar = "This is some other type"
    End Select
End Function

?Bar("12.25")   --> This is a string type
?Bar(#12/25#)   --> This is a date type
?Bar(12.25)     --> This is a numeric type
_

ただし、日付または数値の文字列を扱う場合(テキストファイルの解析など)、日付かどうかを確認する前に、数値かどうかを確認する必要があります。

_Function Bar(Var As Variant)
    If IsNumeric(Var) Then
        Bar = "This is numeric"
    ElseIf IsDate(Var) Then
        Bar = "This is a date"
    Else
        Bar = "This is something else"
    End If
End Function

?Bar("12.75")   --> This is numeric
?Bar("12.50")   --> This is numeric
?Bar("12:50")   --> This is a date
_

日付であるかどうかだけが重要な場合でも、数字ではないことを確認する必要があります。

_Function Bar(Var As Variant)
    If IsDate(Var) And Not IsNumeric(Var) Then
        Bar = "This is a date"
    Else
        Bar = "This is something else"
    End If
End Function

?Bar("12:50")   --> This is a date
?Bar("12.50")   --> This is something else
_

CDateの特性

@Deannaが以下のコメントで指摘したように、CDate()の動作も同様に信頼できません。結果は、文字列または数値のどちらを渡されるかによって異なります。

_?CDate(0.5)     -->  12:00:00 PM
?CDate("0.5")   -->  12:05:00 AM
_

末尾のand数字が文字列として渡される場合、先頭のゼロは重要です:

_?CDate(".5")    -->  12:00:00 PM 
?CDate("0.5")   -->  12:05:00 AM 
?CDate("0.50")  -->  12:50:00 AM 
?CDate("0.500") -->  12:00:00 PM 
_

文字列の小数部分が60分マークに近づくと、動作も変わります。

_?CDate("0.59")  -->  12:59:00 AM 
?CDate("0.60")  -->   2:24:00 PM 
_

一番下の行は、文字列を日付/時刻に変換する必要がある場合は、文字列の形式を認識し、CDate()に依存して変換する前に適切に再フォーマットする必要があるということです。

64
mwolfe02

ここでゲームに遅れました(mwolfe02は1年前にこれに答えました!)が、問題はまだ現実的で、調査する価値のある代替アプローチがあり、StackOverflowはそれらを見つける場所です。

私は数年前にこの問題でVBA.IsDate()につまずき、VBA.IsDate()が不適切に処理するケースをカバーする拡張機能をコーディングしました。最悪なのは、日付シリアルがDouble(DateTimeの場合)およびLong Integer(日付の場合)として頻繁に渡される場合でも、浮動小数点数と整数がIsDateからFALSEを返すことです。

注意点:実装には、配列バリアントをチェックする機能が必要ない場合があります。そうでない場合は、Else ' Comment this out if you don't need to check array variantsに続くインデントされたブロックのコードを自由に削除してください。ただし、一部のサードパーティシステム(リアルタイムマーケットデータクライアントを含む)は、単一のデータポイントでさえ、配列でデータを返すことに注意してください。

詳細については、コードのコメントをご覧ください。

コードはこちら:

Public Function IsDateEx(TestDate As Variant, Optional LimitPastDays As Long = 7305, Optional LimitFutureDays As Long = 7305, Optional FirstColumnOnly As Boolean = False) As Boolean
'Attribute IsDateEx.VB_Description = "Returns TRUE if TestDate is a date, and is within ± 20 years of the system date.
'Attribute IsDateEx.VB_ProcData.VB_Invoke_Func = "w\n9"
Application.Volatile False
On Error Resume Next

' Returns TRUE if TestDate is a date, and is within ± 20 years of the system date.

' This extends VBA.IsDate(), which returns FALSE for floating-point numbers and integers
' even though the VBA Serial Date is a Double. IsDateEx() returns TRUE for variants that
' can be parsed into string dates, and numeric values with equivalent date serials.  All
' values must still be ±20 years from SysDate. Note: locale and language settings affect
' the validity of day- and month names; and partial date strings (eg: '01 January') will
' be parsed with the missing components filled-in with system defaults.

' Optional parameters LimitPastDays/LimitFutureDays vary the default ± 20 years boundary

' Note that an array variant is an acceptable input parameter: IsDateEx will return TRUE
' if all the values in the array are valid dates: set  FirstColumnOnly:=TRUE if you only
' need to check the leftmost column of a 2-dimensional array.


' *     THIS CODE IS IN THE PUBLIC DOMAIN
' *
' *     Author: Nigel Heffernan, May 2005
' *     http://excellerando.blogspot.com/
' *
' *
' *     *********************************

Dim i As Long
Dim j As Long
Dim k As Long

Dim jStart As Long
Dim jEnd   As Long

Dim dateFirst As Date
Dim dateLast As Date

Dim varDate As Variant

dateFirst = VBA.Date - LimitPastDays
dateLast = VBA.Date + LimitFutureDays

IsDateEx = False

If TypeOf TestDate Is Excel.Range Then
    TestDate = TestDate.Value2
End If

If VarType(TestDate) < vbArray Then

    If IsDate(TestDate) Or IsNumeric(TestDate) Then
        If (dateLast > TestDate) And (TestDate > dateFirst) Then
            IsDateEx = True
        End If
    End If

Else   ' Comment this out if you don't need to check array variants

    k = ArrayDimensions(TestDate)
    Select Case k
    Case 1

        IsDateEx = True
        For i = LBound(TestDate) To UBound(TestDate)
            If IsDate(TestDate(i)) Or IsNumeric(TestDate(i)) Then
                If Not ((dateLast > CVDate(TestDate(i))) And (CVDate(TestDate(i)) > dateFirst)) Then
                    IsDateEx = False
                    Exit For
                End If
            Else
                IsDateEx = False
                Exit For
            End If
        Next i

    Case 2

        IsDateEx = True
        jStart = LBound(TestDate, 2)

        If FirstColumnOnly Then
            jEnd = LBound(TestDate, 2)
        Else
            jEnd = UBound(TestDate, 2)
        End If

        For i = LBound(TestDate, 1) To UBound(TestDate, 1)
            For j = jStart To jEnd
                If IsDate(TestDate(i, j)) Or IsNumeric(TestDate(i, j)) Then
                    If Not ((dateLast > CVDate(TestDate(i, j))) And (CVDate(TestDate(i, j)) > dateFirst)) Then
                        IsDateEx = False
                        Exit For
                    End If
                Else
                    IsDateEx = False
                    Exit For
                End If
            Next j
        Next i

    Case Is > 2

        ' Warning: For... Each enumerations are SLOW
        For Each varDate In TestDate

            If IsDate(varDate) Or IsNumeric(varDate) Then
                If Not ((dateLast > CVDate(varDate)) And (CVDate(varDate) > dateFirst)) Then
                    IsDateEx = False
                    Exit For
                End If
            Else
                IsDateEx = False
                Exit For
            End If

        Next varDate

    End Select

End If

End Function

まだExcel 2003を使用しているユーザー向けのヒント:

ユーザー(またはユーザー)がワークシートからIsDateEx()を呼び出す場合、エクスポートされた.basファイルでテキストエディターを使用して、関数ヘッダーのすぐ下に、これらの2行を入れ、 VB属性は便利ですが、ExcelのVBA IDEのコードエディターからアクセスできないため、ファイルを再インポートします

Attribute IsDateEx.VB_Description = "Returns TRUE if TestDate is a date, and is within ± 20 years of the system date.\r\nChange the defaulte default ± 20 years boundaries by setting values for LimitPastDays and LimitFutureDays\r\nIf you are checking an array of dates, ALL the values will be tested: set FirstColumnOnly TRUE to check the leftmost column only."

それはすべて1行です。ブラウザによって挿入された改行に注意してください! ...この行は、isDateEXをISNUMBER()、ISER()、ISTEXT()などとともに、「情報」カテゴリの関数Wizard)に入れます。

Attribute IsDateEx.VB_ProcData.VB_Invoke_Func = "w\n9"

日付と時刻の関数で表示したい場合は、「w\n2」を使用します。独自のコードの「Used Defined」関数と、人々が開発したすべてのサードパーティのアドインの泥沼でそれを失うことはありません時々ユーザーを助けるのに十分なquiteをしない人.

これがOffice 2010でまだ機能するかどうかはわかりません。

また、ArrayDimensionsのソースが必要になる場合があります。

このAPI宣言はモジュールヘッダーで必要です。

Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" _
                   (Destination As Any, _
                    Source As Any, _
                    ByVal Length As Long)

…そして、関数自体は次のとおりです。

Private Function ArrayDimensions(arr As Variant) As Integer
  '-----------------------------------------------------------------
  ' will return:
  ' -1 if not an array
  ' 0  if an un-dimmed array
  ' 1  or more indicating the number of dimensions of a dimmed array
  '-----------------------------------------------------------------


  ' Retrieved from Chris Rae's VBA Code Archive - http://chrisrae.com/vba
  ' Code written by Chris Rae, 25/5/00

  ' Originally published by R. B. Smissaert.
  ' Additional credits to Bob Phillips, Rick Rothstein, and Thomas Eyde on VB2TheMax

  Dim ptr As Long
  Dim vType As Integer

  Const VT_BYREF = &H4000&

  'get the real VarType of the argument
  'this is similar to VarType(), but returns also the VT_BYREF bit
  CopyMemory vType, arr, 2

  'exit if not an array
  If (vType And vbArray) = 0 Then
    ArrayDimensions = -1
    Exit Function
  End If

  'get the address of the SAFEARRAY descriptor
  'this is stored in the second half of the
  'Variant parameter that has received the array
  CopyMemory ptr, ByVal VarPtr(arr) + 8, 4

  'see whether the routine was passed a Variant
  'that contains an array, rather than directly an array
  'in the former case ptr already points to the SA structure.
  'Thanks to Monte Hansen for this fix

  If (vType And VT_BYREF) Then
    ' ptr is a pointer to a pointer
    CopyMemory ptr, ByVal ptr, 4
  End If

  'get the address of the SAFEARRAY structure
  'this is stored in the descriptor

  'get the first Word of the SAFEARRAY structure
  'which holds the number of dimensions
  '...but first check that saAddr is non-zero, otherwise
  'this routine bombs when the array is uninitialized

  If ptr Then
    CopyMemory ArrayDimensions, ByVal ptr, 2
  End If

End Function

ソースコードに謝辞を保管してください。開発者としてのキャリアが進むにつれて、認められたあなた自身の貢献に感謝するようになります。

また、その宣言を非公開にしておくことをお勧めします。別のモジュールでパブリックSubにする必要がある場合は、モジュールヘッダーにOption Private Moduleステートメントを挿入します。 CopyMemoryoperationsとポインター演算を使用してユーザーが関数を呼び出すことは本当に望ましくありません。

7
Nigel Heffernan