User Tools

Site Tools


vba:functions:isnothing

Differences

This shows you the differences between two versions of the page.

Link to this comparison view

Next revision
Previous revision
vba:functions:isnothing [08.07.2014 14:37:35]
yaslaw created
vba:functions:isnothing [05.02.2021 14:21:58] (current)
yaslaw
Line 1: Line 1:
 +<​const>​
 +    version=1.0.3
 +    vdate=03.09.2018
 +    fname=udf_isnothing.bas
 +    ns=%NAMESPACE%
 +    fpath=/​vba/​functions
 +</​const>​
 ====== [VBA] isNothing() ====== ====== [VBA] isNothing() ======
-Prüft ob allgemein etwas in einer Variable ist.+Prüft ob allgemein etwas in einer Variable ist. Fast also mehrere mögliche Leerprüfungen zusammen
  
 Die folgenden Variableninhalte geben TRUE zurück Die folgenden Variableninhalte geben TRUE zurück
Line 9: Line 16:
   *leerer Array/​Collection/​Dictionary   *leerer Array/​Collection/​Dictionary
   *Nicht initializierter Array   *Nicht initializierter Array
 +
 +==Version %%version%% %%vdate%%==
 +{{%%fname%%|Download %%fname%% (V-%%version%%)}}
  
 ===== Definition ===== ===== Definition =====
Line 16: Line 26:
   ***iValue** ​ Variable die geprüft werden soll   ***iValue** ​ Variable die geprüft werden soll
  
-== Beispiele ===+=== Beispiele ​====
 <code vb>?​isNothing(123) <code vb>?​isNothing(123)
 False False
Line 32: Line 42:
 True</​code>​ True</​code>​
  
-== Code == +===== Code ===== 
-<code vb udf_isNothing.bas>'​------------------------------------------------------------------------------- +<source '​%%fpath%%/%%fname%%'​ vb>
-'​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</code>+
vba/functions/isnothing.1404823055.txt.gz · Last modified: 08.07.2014 14:37:35 by yaslaw