VBA-tools / VBA-Web

VBA-Web: Connect VBA, Excel, Access, and Office for Windows and Mac to web services and the web
http://vba-tools.github.io/VBA-Web/
MIT License
2.01k stars 494 forks source link

POST fails on Mac but succeeds on Windows #125

Closed mmustala closed 9 years ago

mmustala commented 9 years ago

Hi,

I'm using VBA-Web to post sheet in csv and images as base64 encoded strings to my web server. The server responds with an empty JSON with status 200. When using the macro in Windows Excel 2003 it works ok but on Mac Excel 2011 I get an error

Run-time error '-2147210493 (80042b03)': 
Method 'Execute' of object 'WebClient' failed

The debug is highlighting the row with

Set response = expClient.Execute(expRequest)

The macro code looks like this

Sub test()

    Dim token As String
    Dim i As Long
    Dim requestBody As String
    Dim imageString As String

    Application.StatusBar = "Sending csv data..."

    Dim expClient As New WebClient
    expClient.BaseUrl = ApiBaseUrl()
    Dim expRequest As New WebRequest
    expRequest.Resource = "/excel_data"
    expRequest.Method = WebMethod.HttpPost
    expRequest.RequestFormat = WebFormat.PlainText
    expRequest.ResponseFormat = WebFormat.json
    expRequest.AddHeader "X-Api-Access-Token", Range("L1")

    requestBody = Join2d(Worksheets("Sheet1").Range("A1:I37").Value, vbCrLf, ",")
    expRequest.Body = requestBody

    Dim response As WebResponse
    Set response = expClient.Execute(expRequest)
    If response.StatusCode = WebStatusCode.ok Then
        token = response.Data("token")
        i = 1
        For Each img In Worksheets("Sheet1").Shapes
            Application.StatusBar = "Sending image " & i

            imageString = readImageToString(img)
            requestBody = Encode64(imageString)
            Set expRequest = New WebRequest
            expRequest.Resource = "/image_data"
            expRequest.Method = WebMethod.HttpPost
            expRequest.RequestFormat = WebFormat.PlainText
            expRequest.ResponseFormat = WebFormat.json
            expRequest.AddHeader "X-Api-Access-Token", Range("L1")
            expRequest.AddHeader "X-Token", token
            expRequest.AddHeader "X-Image-Name", "test.jpg"
            expRequest.Body = requestBody

            Set response = expClient.Execute(expRequest)
            If response.StatusCode <> WebStatusCode.ok Then
                MsgBox ("Sending data error:" & vbCrLf & response.Content)
                Exit Sub
            End If

            i = i + 1
        Next img

    Else
        MsgBox ("Sending data error:" & vbCrLf & response.Content)
        Exit Sub
   End If

End Sub

Do you have ideas about why this is happening? Any workarounds?

timhall commented 9 years ago

I've had some issues with Excel for Mac eating the detailed error messages and reported that generic one. To get the full error, open the Immediate Window from the VBA Editor and that should contain the full error message. If you could post that, I'll try to figure out what's happening.

mmustala commented 9 years ago

Here is the error message from the immediate window.

ERROR - WebResponse.CreateFromCurl: -2147210473 (11031 / 80042b17), An error occurred while creating response from cURL
9: Subscript out of range
ERROR - WebClient.Execute: -2147210493 (11011 / 80042b03), An error occurred during execute
-2147210473 (80042b17): Method 'CreateFromCurl' of object 'WebResponse' failed
timhall commented 9 years ago

Hmm, can you put a breakpoint in WebResponse:171 and look at the raw response (Immediate Window > "? Result") and then see which step (Status Code/Description, Content, Body, Headers/Cookies) is throwing the error? I'm thinking it's something with the StatusCode so seeing the raw response would be helpful.

mmustala commented 9 years ago

I added some debug prints to the code. The code looks like this now:

Public Sub CreateFromCurl(Client As WebClient, Request As WebRequest, Result As String)
    On Error GoTo web_ErrorHandling

    Dim web_Lines() As String
    Debug.Print "BEGIN RESULT"
    Debug.Print Result
    Debug.Print "END RESULT"
    web_Lines = VBA.Split(Result, vbCrLf)

    Me.StatusCode = web_ExtractStatusFromCurlResponse(web_Lines)
    Debug.Print "BEGIN STATUS CODE"
    Debug.Print Me.StatusCode
    Debug.Print "END STATUS CODE"
    Me.StatusDescription = web_ExtractStatusTextFromCurlResponse(web_Lines)
    Debug.Print "BEGIN STATUS DESCRIPTION"
    Debug.Print Me.StatusDescription
    Debug.Print "END STATUS DESCRIPTION"
    Me.Content = web_ExtractResponseTextFromCurlResponse(web_Lines)
    Debug.Print "BEGIN CONTENT"
    Debug.Print Me.Content
    Debug.Print "END CONTENT"
    Me.Body = WebHelpers.StringToAnsiBytes(Me.Content)
    Debug.Print "BEGIN BODY"
    Debug.Print Me.Body
    Debug.Print "END BODY"

    web_LoadValues web_ExtractHeadersFromCurlResponse(web_Lines), Me.Content, Me.Body, Request

    Exit Sub

web_ErrorHandling:

    Dim web_ErrorDescription As String
    web_ErrorDescription = "An error occurred while creating response from cURL" & vbNewLine & _
        Err.Number & VBA.IIf(Err.Number < 0, " (" & VBA.LCase$(VBA.Hex$(Err.Number)) & ")", "") & ": " & Err.Description

    WebHelpers.LogError web_ErrorDescription, "WebResponse.CreateFromCurl", 11031 + vbObjectError
    Err.Raise 11031 + vbObjectError, "WebResponse.CreateFromCurl", web_ErrorDescription
End Sub

And it produced a log below. There is first a successful post for sending the sheet in csv format and then the failed post for sending the image.

BEGIN RESULT
HTTP/1.1 200 OK
Date: Tue, 16 Jun 2015 06:56:15 GMT
X-Frame-Options: SAMEORIGIN
X-XSS-Protection: 1; mode=block
X-Content-Type-Options: nosniff
Content-Type: application/json; charset=utf-8
ETag: "47228861fa3c107b8170e828cb6b39f8"
Cache-Control: max-age=0, private, must-revalidate
X-Request-Id: 84c230a0-54f7-43be-b45a-e3dbb2b25cc6
X-Runtime: 0.087000
Set-Cookie: request_method=POST; path=/
Transfer-Encoding: chunked

{"token":"GB5"}
END RESULT
BEGIN STATUS CODE
 200 
END STATUS CODE
BEGIN STATUS DESCRIPTION
OK
END STATUS DESCRIPTION
BEGIN CONTENT
{"token":"GB5"}
END CONTENT
BEGIN BODY
_______
END BODY
BEGIN RESULT
HTTP/1.1 100 Continue

HTTP/1.1 200 OK
Date: Tue, 16 Jun 2015 06:56:16 GMT
X-Frame-Options: SAMEORIGIN
X-XSS-Protection: 1; mode=block
X-Content-Type-Options: nosniff
Content-Type: application/json; charset=utf-8
ETag: "99914b932bd37a50b983c5e7c90ae93b"
Cache-Control: max-age=0, private, must-revalidate
X-Request-Id: 4f113e34-7d05-4f85-9cfc-2f4424c7ca64
X-Runtime: 0.183000
Set-Cookie: request_method=POST; path=/
Transfer-Encoding: chunked

{}
END RESULT
BEGIN STATUS CODE
 100 
END STATUS CODE
BEGIN STATUS DESCRIPTION
Continue
END STATUS DESCRIPTION
BEGIN CONTENT
HTTP/1.1 200 OK
Date: Tue, 16 Jun 2015 06:56:16 GMT
X-Frame-Options: SAMEORIGIN
X-XSS-Protection: 1; mode=block
X-Content-Type-Options: nosniff
Content-Type: application/json; charset=utf-8
ETag: "99914b932bd37a50b983c5e7c90ae93b"
Cache-Control: max-age=0, private, must-revalidate
X-Request-Id: 4f113e34-7d05-4f85-9cfc-2f4424c7ca64
X-Runtime: 0.183000
Set-Cookie: request_method=POST; path=/
Transfer-Encoding: chunked

{}
END CONTENT
BEGIN BODY
_____________________________________________________________________›______________________________›__________________________________________________›__________________________________________________________________
END BODY
ERROR - WebResponse.CreateFromCurl: -2147210473 (11031 / 80042b17), An error occurred while creating response from cURL
9: Subscript out of range
ERROR - WebClient.Execute: -2147210493 (11011 / 80042b03), An error occurred during execute
-2147210473 (80042b17): Method 'CreateFromCurl' of object 'WebResponse' failed

So it looks like parsing the content fails because the response has a blank line after the HTTP/1.1 100 Continue line and the code expects the first blank line to be after all the headers.

timhall commented 9 years ago

Thanks for including all of the debugging. Strange, so it includes both 100 and 200 in the same response? (I've never worked with status code 100 before, but didn't think that was normal) I'll look into a way to handle this case.

mmustala commented 9 years ago

It looks like others have had similar issues with cURL and 100 Continue responses. http://stackoverflow.com/questions/2964687/how-to-handle-100-continue-http-message

Maybe just remove the Continue lines if they exist?

timhall commented 9 years ago

Good find, that looks like that's the issue and glad to see it's cURL's default (even though it doesn't really make sense) so that I can work around it consistently. Will fix shortly.