User Tools

Site Tools


vba:functions:isnothing

This is an old revision of the document!


[VBA] isNothing()

Prüft ob allgemein etwas in einer Variable ist.

Die folgenden Variableninhalte geben TRUE zurück

  • Null
  • Empty
  • Nothing
  • Leerer String (getrimmt)
  • leerer Array/Collection/Dictionary
  • Nicht initializierter Array

Definition

boolean = isNothing(object)
boolean = isNothing(vaule)
Public Function isNothing(ByRef iValue As Variant) As Boolean
  • iValue Variable die geprüft werden soll
Beispiele
?isNothing(123)
False
 
?isNothing(array())
True
 
?isNothing(array(1,2,3))
False
 
?isNothing("    ")
True
 
?isNothing(new Collection)
True
Code
udf_isNothing.bas
'-------------------------------------------------------------------------------
'File         : udf_isNothing.bas
'               Copyright mpl by ERB software
'               All rights reserved
'               http://wiki.yaslaw.info/dokuwiki/doku.php/vba/cast/strtodate
'Environment  : VBA 2007 +
'Version      : 1.0.1
'Name         : _isNothing
'Author       : Stefan Erb (ERS)
'History      : 30.04.2014 - ERS - Creation
'-------------------------------------------------------------------------------
Option Explicit
 
'/**
' * Prüft, ob eine Variable Null, Empty, Nothing, Leerstring, leerer Array etc ist
' *
' *     boolean = isNothing(object)
' *     boolean = isNothing(vaule)
' *
' * @param  Variant     Variable die geprüft werden soll
' * @return Boolean
' */
Public Function isNothing(ByRef iValue As Variant) As Boolean
    isNothing = True
    Select Case TypeName(iValue)
        Case "Nothing", "Empty", "Null":    Exit Function
        Case "Collection", "Dictionary":    If iValue.count = 0 Then Exit Function
        Case "String":                      If Len(Trim(iValue)) = 0 Then Exit Function
        Case "Iterator":                    If Not iValue.isInitialized Then Exit Function
        '//TODO: weitere Spezialfälle
        Case Else:
            If IsArray(iValue) Then
                On Error Resume Next
                Dim dummy As Variant: dummy = iValue(LBound(iValue))
                If Err.Number <> 0 Then Exit Function
            End If
    End Select
    isNothing = False
End Function
vba/functions/isnothing.1404823055.txt.gz · Last modified: 08.07.2014 14:37:35 by yaslaw