User Tools

Site Tools


vba:cast:cvalue

Differences

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

Link to this comparison view

Both sides previous revision Previous revision
Next revision
Previous revision
Last revision Both sides next revision
vba:cast:cvalue [19.11.2014 15:28:09]
yaslaw
vba:cast:cvalue [19.10.2015 12:37:18]
yaslaw
Line 1: Line 1:
 <​const>​ <​const>​
-    version=1.0.0 +    version=1.3.0 
-    vdate=19.11.2014+    vdate=19.10.2015
     fname=cast_cvalue.bas     fname=cast_cvalue.bas
     ns=%NAMESPACE%     ns=%NAMESPACE%
Line 8: Line 8:
 {{keywords>​vba,​castfunction}} {{keywords>​vba,​castfunction}}
  
-====== [VBA] cValue() ======+====== [VBA] cValue(), cV() ====== 
 +//cValue versucht einen String in ein Nativetyp zu casten.// 
 ==Version %%version%% - %%vdate%%== ==Version %%version%% - %%vdate%%==
- +Die Funktion wird zum Beispiel ​in [[vba:​cast:​cdict]] verwendet.
-cValue versucht einen String ​in ein Nativetyp zu casten.+
  
 {{%%fname%%|Download %%fname%% (V-%%version%%)}} {{%%fname%%|Download %%fname%% (V-%%version%%)}}
  
-===== Definition ​=====+Ich habe 2 Versionen. cValue() ist ein ausführlicher,​ lesbarer Code der sich gut eignet um als eigenständige Funktion verwendet zu werden. 
 +\\ cV() ist auf das nötigste gekürzt und gestutzt. Sie hat die gleiche Funktionalität wir cValue(), ist jedoch vom Code her viel kompakter. Ich verwende vV() in verschiedenen anderen Funktionen. 
 + 
 +===== cValue() ​===== 
 +==== Definition ​====
 <​code>​Variant = cValue(String [,​cvHandling])</​code>​ <​code>​Variant = cValue(String [,​cvHandling])</​code>​
 <code vb>​Public Function cValue( <code vb>​Public Function cValue(
Line 27: Line 32:
 End Enum</​code>​ End Enum</​code>​
  
-===== Beispiel ​=====+==== Beispiel ====
 > Für die Ausgabe der Resultate verwendete ich die Funktion [[:​vba:​functions:​print_r:​]]. > Für die Ausgabe der Resultate verwendete ich die Funktion [[:​vba:​functions:​print_r:​]].
  
-==== Zahlen ​====+=== Zahlen ===
 <code vb> <code vb>
 'Ein Integer asl Text -> Integer 'Ein Integer asl Text -> Integer
Line 52: Line 57:
 </​code>​ </​code>​
  
-==== Datum ====+=== Datum ===
 Es wird mit cDate geparst. Dieses kann sich Systemabhängig anders verhalten Es wird mit cDate geparst. Dieses kann sich Systemabhängig anders verhalten
 <code vb> <code vb>
Line 65: Line 70:
  
  
-==== Strings ​====+=== Strings ===
 <code vb> <code vb>
 'Ein Text ohne Delemiter 'Ein Text ohne Delemiter
Line 76: Line 81:
 </​code>​ </​code>​
  
-=== Thematik NULL ===+== Thematik NULL ==
 <code vb> <code vb>
 '​Leerer Text '​Leerer Text
Line 97: Line 102:
 d cValue("'​Null'",​ cvhNullTextAsNull) d cValue("'​Null'",​ cvhNullTextAsNull)
 <​String>​ '​Null'</​code>​ <​String>​ '​Null'</​code>​
 +
 +===== cV() =====
 +==== Definition ====
 +<​code>​Variant = cV(Variant [,​flags])</​code>​
 +<code vb>​Public Function cV(
 +    ByVal iValue As Variant, ​
 +    Optional ByVal iFlags As String
 +) As Variant</​code>​
 +
 +**iFLags** ist ein String, der das Verhalten cV() steuert. Die Flags sind3 Buchstaben de kombiniert werden können.
 +  ***s** Der Text Null ohne Delemiter wird als Wert Null intepretiert
 +  ***e** Ein leerer String wird als Null intepretiert
 +  ***b** Boolean-Text wird als Boolean intepretiert
 +  ***d** Bei Delemited Strings den Delemiter entfernen. ' oder " gelten als Delemiter
 +==== Beispiel ====
 +> Für die Ausgabe der Resultate verwendete ich die Funktion [[:​vba:​functions:​print_r:​]].
 +
 +<code vb>'​String zu Zahl
 +d cV("​1234.5"​)
 +<​Date>​ 01.05.1234
 +
 +'Text Null
 +d cV("​NULL"​)
 +<​String>​ '​NULL'​
 +
 +'Text Null intepretieren
 +d cV("​NULL",​ "​n"​)
 +<​Null> ​
 +
 +'​Leerer String
 +d cV(""​)
 +<​Empty> ​
 +
 +'Empty als Null zurückgeben
 +d cV("",​ "​e"​)
 +<​Null> ​
 +
 +'​Boolean als Wert
 +d cV("​TRUE"​)
 +<​String>​ '​TRUE'​
 +
 +'​Boolean parsen
 +d cV("​TRUE",​ "​b"​)
 +<​Boolean>​ True
 +
 +'​Kombioniert. Nicht alle Flags kommen unbedigt zum tragen
 +' Der String ist mit ' Als Deleimiter mitgeliefert
 +d cV("'​NULL'",​ "​nd"​)
 +<​String>​ '​NULL'​
 +</​code>​
  
 ===== Code ===== ===== Code =====
 +==== Ganzes Modul ====
 <source '​%%fpath%%/​%%fname%%'​ vb> <source '​%%fpath%%/​%%fname%%'​ vb>
 +
 +==== Nur Kurzversion cV ====
 +<code vb>'/​**
 +' * Dies ist die Minimalversion von cValue (V1.0.0): http://​wiki.yaslaw.info/​dokuwiki/​doku.php/​vba/​cast/​cvalue
 +' * Der 2te Paramtersteuert das Null-Verhalten('​seb'​):​
 +' *     n: Der Text Null ohne Delemiter wird als Wert Null intepretiert,​
 +' *     e: Ein leerer String wird als Null intepretiert,​
 +' *     b: Boolean-Text wird als Boolean intepretiert
 +' *     d: Bei Delemited Strings den Delemiter entfernen. ' oder " gelten als Delemiter
 +' */
 +Public Function cV(ByVal iValue As Variant, Optional ByVal iFlags As String) As Variant
 +    On Error Resume Next: If IsNull(iValue) Then cV = Null: Exit Function
 +    Static rxDa As Object, rsDs As Object: Dim sm As Object, str As String, flg As String: ​ str = CStr(iValue):​ flg = UCase(iFlags)
 +    If UCase(str) = "​NULL"​ And InStr(flg, "​N"​) Then cV = Null: Exit Function
 +    If iValue = Empty And CBool(InStr(flg,​ "​E"​)) Then cV = Null: Exit Function
 +    If IsDate(str) Then cV = CDate(str): Exit Function
 +    cV = CByte(str): ​   If cV = str Then Exit Function
 +    cV = CInt(str): ​    If cV = str Then Exit Function
 +    cV = CLng(str): ​    If cV = str Then Exit Function
 +    cV = CDbl(str): ​    If cV = str Then Exit Function
 +    cV = CDec(str): ​    If cV = str Then Exit Function
 +    Err.Clear: If InStr(flg, "​B"​) Then cV = CBool(str): ​  If Err.Number = 0 Then Exit Function
 +    If rxDa Is Nothing Then Set rxDa = CreateObject("​VBScript.RegExp"​):​ rxDa.pattern = "​^#​(.*)#​$"​
 +    If rxDa.Test(str) Then cV = CDate(rxDa.execute(str)(0).subMatches(0)): ​ Exit Function
 +    If InStr(flg, "​D"​) Then
 +        If rsDs Is Nothing Then Set rsDs = CreateObject("​VBScript.RegExp"​):​ rsDs.pattern = "​^([""'​])(.*)\1$"​
 +        If rsDs.Test(str) Then Set sm = rsDs.execute(str)(0).subMatches:​ cV = Replace(sm(1),​ "​\"​ & sm(0), sm(0)): ​ Exit Function
 +    End If
 +    cV = iValue
 +End Function
 +</​code>​
vba/cast/cvalue.txt · Last modified: 19.10.2015 12:37:48 by yaslaw