11Attribute VB_Name = "JsonConverter"
22''
3- ' VBA-JSON v1.0.0-rc.6
3+ ' VBA-JSON v1.0.0
44' (c) Tim Hall - https://github.com/VBA-tools/VBA-JSON
55'
66' JSON Converter for VBA
77'
8- ' Errors (513-65535 available) :
8+ ' Errors:
99' 10001 - JSON parse error
10- ' 10002 - ISO 8601 date conversion error
1110'
1211' @class JsonConverter
1312' @author tim.hall.engr@gmail.com
1413' @license MIT (http://www.opensource.org/licenses/mit-license.php)
15- ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
14+ '' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
1615'
1716' Based originally on vba-json (with extensive changes)
1817' BSD license included below
@@ -126,6 +125,7 @@ Private Declare Sub json_CopyMemory Lib "kernel32" Alias "RtlMoveMemory" _
126125' @method ParseJson
127126' @param {String} json_String
128127' @return {Object} (Dictionary or Collection)
128+ ' @throws 10001 - JSON parse error
129129''
130130Public Function ParseJson (ByVal json_String As String , Optional json_ConvertLargeNumbersToString As Boolean = True ) As Object
131131 Dim json_Index As Long
@@ -694,7 +694,7 @@ Private Function json_UnsignedAdd(json_Start As Long, json_Increment As Long) As
694694End Function
695695
696696''
697- ' VBA-UTC v1.0.0-rc.4
697+ ' VBA-UTC v1.0.0
698698' (c) Tim Hall - https://github.com/VBA-tools/VBA-UtcConverter
699699'
700700' UTC/ISO 8601 Converter for VBA
@@ -708,7 +708,7 @@ End Function
708708' @module UtcConverter
709709' @author tim.hall.engr@gmail.com
710710' @license MIT (http://www.opensource.org/licenses/mit-license.php)
711- ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
711+ '' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ '
712712
713713' (Declarations moved to top)
714714
@@ -722,6 +722,7 @@ End Function
722722' @method ParseUtc
723723' @param {Date} UtcDate
724724' @return {Date} Local date
725+ ' @throws 10011 - UTC parsing error
725726''
726727Public Function ParseUtc (utc_UtcDate As Date ) As Date
727728 On Error GoTo utc_ErrorHandling
@@ -750,6 +751,7 @@ End Function
750751' @method ConvertToUrc
751752' @param {Date} utc_LocalDate
752753' @return {Date} UTC date
754+ ' @throws 10012 - UTC conversion error
753755''
754756Public Function ConvertToUtc (utc_LocalDate As Date ) As Date
755757 On Error GoTo utc_ErrorHandling
@@ -778,6 +780,7 @@ End Function
778780' @method ParseIso
779781' @param {Date} utc_IsoString
780782' @return {Date} Local date
783+ ' @throws 10013 - ISO 8601 parsing error
781784''
782785Public Function ParseIso (utc_IsoString As String ) As Date
783786 On Error GoTo utc_ErrorHandling
@@ -853,6 +856,7 @@ End Function
853856' @method ConvertToIso
854857' @param {Date} utc_LocalDate
855858' @return {Date} ISO 8601 string
859+ ' @throws 10014 - ISO 8601 conversion error
856860''
857861Public Function ConvertToIso (utc_LocalDate As Date ) As String
858862 On Error GoTo utc_ErrorHandling
@@ -870,6 +874,7 @@ End Function
870874' ============================================= '
871875
872876#If Mac Then
877+
873878Private Function utc_ConvertDate (utc_Value As Date , Optional utc_ConvertToUtc As Boolean = False ) As Date
874879 Dim utc_ShellCommand As String
875880 Dim utc_Result As utc_ShellResult
@@ -900,6 +905,7 @@ Private Function utc_ConvertDate(utc_Value As Date, Optional utc_ConvertToUtc As
900905 TimeSerial(utc_TimeParts(0 ), utc_TimeParts(1 ), utc_TimeParts(2 ))
901906 End If
902907End Function
908+
903909Private Function utc_ExecuteInShell (utc_ShellCommand As String ) As utc_ShellResult
904910 Dim utc_File As Long
905911 Dim utc_Chunk As String
@@ -922,7 +928,9 @@ Private Function utc_ExecuteInShell(utc_ShellCommand As String) As utc_ShellResu
922928utc_ErrorHandling:
923929 utc_ExecuteInShell.utc_ExitCode = utc_pclose(utc_File)
924930End Function
931+
925932#Else
933+
926934Private Function utc_DateToSystemTime (utc_Value As Date ) As utc_SYSTEMTIME
927935 utc_DateToSystemTime.utc_wYear = VBA.Year(utc_Value)
928936 utc_DateToSystemTime.utc_wMonth = VBA.Month(utc_Value)
@@ -937,4 +945,5 @@ Private Function utc_SystemTimeToDate(utc_Value As utc_SYSTEMTIME) As Date
937945 utc_SystemTimeToDate = DateSerial(utc_Value.utc_wYear, utc_Value.utc_wMonth, utc_Value.utc_wDay) + _
938946 TimeSerial(utc_Value.utc_wHour, utc_Value.utc_wMinute, utc_Value.utc_wSecond)
939947End Function
948+
940949#End If
0 commit comments