Skip to content

Commit 3927286

Browse files
authored
Add 64-bit Mac support (#278)
* Add 64-bit Mac support * Update VBA-JSON to v2.2.3 - Apply PR 279 - Update VBA-JSON to v2.2.3
1 parent f80e870 commit 3927286

File tree

1 file changed

+65
-15
lines changed

1 file changed

+65
-15
lines changed

src/WebHelpers.bas

Lines changed: 65 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -144,10 +144,31 @@ Const AUTOPROXY_DETECT_TYPE_DNS = 2
144144
' === VBA-UTC Headers
145145
#If Mac Then
146146

147-
Private Declare Function utc_popen Lib "libc.dylib" Alias "popen" (ByVal utc_Command As String, ByVal utc_Mode As String) As Long
148-
Private Declare Function utc_pclose Lib "libc.dylib" Alias "pclose" (ByVal utc_File As Long) As Long
149-
Private Declare Function utc_fread Lib "libc.dylib" Alias "fread" (ByVal utc_Buffer As String, ByVal utc_Size As Long, ByVal utc_Number As Long, ByVal utc_File As Long) As Long
150-
Private Declare Function utc_feof Lib "libc.dylib" Alias "feof" (ByVal utc_File As Long) As Long
147+
#If VBA7 Then
148+
149+
' 64-bit Mac (2016)
150+
Private Declare PtrSafe Function utc_popen Lib "libc.dylib" Alias "popen" _
151+
(ByVal utc_Command As String, ByVal utc_Mode As String) As LongPtr
152+
Private Declare PtrSafe Function utc_pclose Lib "libc.dylib" Alias "pclose" _
153+
(ByVal utc_File As Long) As LongPtr
154+
Private Declare PtrSafe Function utc_fread Lib "libc.dylib" Alias "fread" _
155+
(ByVal utc_Buffer As String, ByVal utc_Size As LongPtr, ByVal utc_Number As LongPtr, ByVal utc_File As LongPtr) As LongPtr
156+
Private Declare PtrSafe Function utc_feof Lib "libc.dylib" Alias "feof" _
157+
(ByVal utc_File As LongPtr) As LongPtr
158+
159+
#Else
160+
161+
' 32-bit Mac
162+
Private Declare Function utc_popen Lib "libc.dylib" Alias "popen" _
163+
(ByVal utc_Command As String, ByVal utc_Mode As String) As Long
164+
Private Declare Function utc_pclose Lib "libc.dylib" Alias "pclose" _
165+
(ByVal utc_File As Long) As Long
166+
Private Declare Function utc_fread Lib "libc.dylib" Alias "fread" _
167+
(ByVal utc_Buffer As String, ByVal utc_Size As Long, ByVal utc_Number As Long, ByVal utc_File As Long) As Long
168+
Private Declare Function utc_feof Lib "libc.dylib" Alias "feof" _
169+
(ByVal utc_File As Long) As Long
170+
171+
#End If
151172

152173
#ElseIf VBA7 Then
153174

@@ -174,11 +195,21 @@ Private Declare Function utc_TzSpecificLocalTimeToSystemTime Lib "kernel32" Alia
174195

175196
#If Mac Then
176197

198+
#If VBA7 Then
199+
Private Type utc_ShellResult
200+
utc_Output As String
201+
utc_ExitCode As LongPtr
202+
End Type
203+
204+
#Else
205+
177206
Private Type utc_ShellResult
178207
utc_Output As String
179208
utc_ExitCode As Long
180209
End Type
181210

211+
#End If
212+
182213
#Else
183214

184215
Private Type utc_SYSTEMTIME
@@ -237,10 +268,17 @@ Public JsonOptions As json_Options
237268
' === End VBA-JSON
238269

239270
#If Mac Then
240-
Private Declare Function web_popen Lib "libc.dylib" Alias "popen" (ByVal Command As String, ByVal mode As String) As Long
241-
Private Declare Function web_pclose Lib "libc.dylib" Alias "pclose" (ByVal File As Long) As Long
242-
Private Declare Function web_fread Lib "libc.dylib" Alias "fread" (ByVal outStr As String, ByVal size As Long, ByVal Items As Long, ByVal stream As Long) As Long
243-
Private Declare Function web_feof Lib "libc.dylib" Alias "feof" (ByVal File As Long) As Long
271+
#If VBA7 Then
272+
Private Declare PtrSafe Function web_popen Lib "libc.dylib" Alias "popen" (ByVal web_Command As String, ByVal web_Mode As String) As LongPtr
273+
Private Declare PtrSafe Function web_pclose Lib "libc.dylib" Alias "pclose" (ByVal web_File As LongPtr) As LongPtr
274+
Private Declare PtrSafe Function web_fread Lib "libc.dylib" Alias "fread" (ByVal web_OutStr As String, ByVal web_Size As LongPtr, ByVal web_Items As LongPtr, ByVal web_Stream As LongPtr) As LongPtr
275+
Private Declare PtrSafe Function web_feof Lib "libc.dylib" Alias "feof" (ByVal web_File As LongPtr) As LongPtr
276+
#Else
277+
Private Declare Function web_popen Lib "libc.dylib" Alias "popen" (ByVal web_Command As String, ByVal web_Mode As String) As Long
278+
Private Declare Function web_pclose Lib "libc.dylib" Alias "pclose" (ByVal web_File As Long) As Long
279+
Private Declare Function web_fread Lib "libc.dylib" Alias "fread" (ByVal web_OutStr As String, ByVal web_Size As Long, ByVal web_Items As Long, ByVal web_Stream As Long) As Long
280+
Private Declare Function web_feof Lib "libc.dylib" Alias "feof" (ByVal web_File As Long) As Long
281+
#End If
244282
#End If
245283

246284
Public Const WebUserAgent As String = "VBA-Web v4.1.1 (https://github.com/VBA-tools/VBA-Web)"
@@ -1592,7 +1630,12 @@ End Sub
15921630
''
15931631
Public Function ExecuteInShell(web_Command As String) As ShellResult
15941632
#If Mac Then
1633+
#If VBA7 Then
1634+
Dim web_File As LongPtr
1635+
#Else
15951636
Dim web_File As Long
1637+
#End If
1638+
15961639
Dim web_Chunk As String
15971640
Dim web_Read As Long
15981641

@@ -1607,7 +1650,7 @@ Public Function ExecuteInShell(web_Command As String) As ShellResult
16071650

16081651
Do While web_feof(web_File) = 0
16091652
web_Chunk = VBA.Space$(50)
1610-
web_Read = web_fread(web_Chunk, 1, Len(web_Chunk) - 1, web_File)
1653+
web_Read = CLng(web_fread(web_Chunk, 1, Len(web_Chunk) - 1, web_File))
16111654
If web_Read > 0 Then
16121655
web_Chunk = VBA.Left$(web_Chunk, web_Read)
16131656
ExecuteInShell.Output = ExecuteInShell.Output & web_Chunk
@@ -1616,7 +1659,7 @@ Public Function ExecuteInShell(web_Command As String) As ShellResult
16161659

16171660
web_Cleanup:
16181661

1619-
ExecuteInShell.ExitCode = web_pclose(web_File)
1662+
ExecuteInShell.ExitCode = CLng(web_pclose(web_File))
16201663
#End If
16211664
End Function
16221665

@@ -1910,7 +1953,7 @@ Private Function web_GetUrlEncodedKeyValue(Key As Variant, Value As Variant, Opt
19101953
End Function
19111954

19121955
''
1913-
' VBA-JSON v2.2.2
1956+
' VBA-JSON v2.2.3
19141957
' (c) Tim Hall - https://github.com/VBA-tools/VBA-JSON
19151958
'
19161959
' JSON Converter for VBA
@@ -2694,7 +2737,7 @@ Private Function json_UnsignedAdd(json_Start As Long, json_Increment As Long) As
26942737
End Function
26952738

26962739
''
2697-
' VBA-UTC v1.0.2
2740+
' VBA-UTC v1.0.3
26982741
' (c) Tim Hall - https://github.com/VBA-tools/VBA-UtcConverter
26992742
'
27002743
' UTC/ISO 8601 Converter for VBA
@@ -2909,9 +2952,15 @@ Private Function utc_ConvertDate(utc_Value As Date, Optional utc_ConvertToUtc As
29092952
End Function
29102953

29112954
Private Function utc_ExecuteInShell(utc_ShellCommand As String) As utc_ShellResult
2955+
#If VBA7 Then
2956+
Dim utc_File As LongPtr
2957+
Dim utc_Read As LongPtr
2958+
#Else
29122959
Dim utc_File As Long
2913-
Dim utc_Chunk As String
29142960
Dim utc_Read As Long
2961+
#End If
2962+
2963+
Dim utc_Chunk As String
29152964

29162965
On Error GoTo utc_ErrorHandling
29172966
utc_File = utc_popen(utc_ShellCommand, "r")
@@ -2920,15 +2969,16 @@ Private Function utc_ExecuteInShell(utc_ShellCommand As String) As utc_ShellResu
29202969

29212970
Do While utc_feof(utc_File) = 0
29222971
utc_Chunk = VBA.Space$(50)
2923-
utc_Read = utc_fread(utc_Chunk, 1, Len(utc_Chunk) - 1, utc_File)
2972+
utc_Read = CLng(utc_fread(utc_Chunk, 1, Len(utc_Chunk) - 1, utc_File))
29242973
If utc_Read > 0 Then
29252974
utc_Chunk = VBA.Left$(utc_Chunk, utc_Read)
29262975
utc_ExecuteInShell.utc_Output = utc_ExecuteInShell.utc_Output & utc_Chunk
29272976
End If
29282977
Loop
29292978

29302979
utc_ErrorHandling:
2931-
utc_ExecuteInShell.utc_ExitCode = utc_pclose(utc_File)
2980+
utc_ExecuteInShell.utc_ExitCode = CLng(utc_pclose(utc_File))
2981+
#End If
29322982
End Function
29332983

29342984
#Else

0 commit comments

Comments
 (0)