help-smalltalk
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

[Help-smalltalk] HTTP clients


From: Mike Anderson
Subject: [Help-smalltalk] HTTP clients
Date: Sun, 04 Sep 2005 18:48:58 +0000
User-agent: Mozilla Thunderbird 0.7.3 (X11/20040803)


Hello,

For responses with a content-length, the pre-read bytes threw out the count for the body, causing it to expect more bytes than there were.

For other responses, it didn't handle chunked encoding at all.

It's not 100% clear to me what the protocol is meant to be, but I think that the client of HTTPClient>>#get:requestHeaders:into: will be expecting it to have had transfer encoding removed, so that's what I've done, and I remove the chunked transfer-encoding header to match.

It also seems to me that HTTPClient>>#head:requestHeaders:into: should be removed in favour of #head:requestHeaders:, since it doesn't do anything with the stream parameter.

Mike
--- arch/kernel/Character.st    2005-08-24 20:28:34.000000000 +0000
+++ mod/kernel/Character.st     2005-09-04 18:43:48.000000000 +0000
@@ -267,8 +267,13 @@
     char = $o ifTrue: [ ^true ].    
     char = $u ifTrue: [ ^true ].    
     ^false
-! !
+! 
 
+isHexDigit
+       "We don't accept lowercase letters, for compatibility with #digitValue."
+       ^self isDigit or: [ 'ABCDEF' includes: self ].
+!
+!
 
 
 !Character methodsFor: 'coercion methods'!
--- arch/net/HTTP.st    2005-08-24 20:28:36.000000000 +0000
+++ mod/net/HTTP.st     2005-09-04 18:43:37.000000000 +0000
@@ -110,8 +110,8 @@
 getText: urlString
     ^self clientPI decode: (self getBinary: urlString)!
 
-head: urlString requestHeaders: requestHeaders into: aStream
-    ^self clientPI head: urlString requestHeaders: requestHeaders into: 
aStream!
+head: urlString requestHeaders: requestHeaders
+    ^self clientPI head: urlString requestHeaders: requestHeaders!
 
 post: urlString type: type data: data binary: binary requestHeaders: 
requestHeaders into: aStream
     ^self clientPI
@@ -137,41 +137,90 @@
     ^self readResponseInto: aStream
 !
 
+readResponseStream: aResponseStream into: aStream length: aContentLength
+       | remaining |
+       remaining := aContentLength.
+       [ remaining = 0 ]
+               whileFalse:
+               [ | data |
+               data := aResponseStream next: (4096 min: remaining).
+               remaining := remaining - data size.
+               self reporter readByte: data size.
+               aStream nextPutAll: data ].
+!
+
+readChunkedResponseStream: aResponseStream into: aStream
+       | cr lf |
+       "Happily, aResponseStream should be buffered."
+       cr := Character cr.
+       lf := Character lf.
+       [       | chunkSize chunkExt i remaining s |
+               aResponseStream peek asUppercase isHexDigit ifFalse: 
+                       [ self error: 'Expecting chunk-size, but found ', 
aResponseStream peek printString, '.' ].
+               chunkSize := Integer readHexFrom: aResponseStream.
+               "Technically, a chunk-extension should start with $;, but we'll
+                ignore everything to the CRLF for simplicity (we don't 
understand
+                any chunk extensions, so we have to ignore them)."
+               [ aResponseStream next = cr
+                       and: [ aResponseStream next = lf ] ] 
+                       whileFalse.
+
+               "Possibly we should just read it all?"
+               self readResponseStream: aResponseStream into: aStream length: 
chunkSize.
+               
+               s := aResponseStream next: 2.
+               ( (cr = (s at: 1)) and: [ lf = (s at: 2) ] ) ifFalse: 
+                       [ self error: ('Expected CRLF but found: ', s 
printString).
+                       "We could try to recover by reading to the next CRLF, I 
suppose..." ].
+       
+               chunkSize = 0 ]
+               whileFalse.             
+       "There shouldn't be a trailer as we didn't say it was acceptable in the 
request."
+       "FIXME - We should read in the final CRLF even though we don't check 
it. It
+        is not always sent, however..."
+!
+
 readResponseInto: aStream
     | response totalByte readStream |
     response := self getResponse.
     self checkResponse: response.
 
     totalByte := response fieldAt: 'Content-Length' ifAbsent: [nil].
-    totalByte notNil ifTrue: [
-       totalByte := totalByte value trimSeparators asInteger.
-       self reporter totalByte: totalByte ].
+    totalByte notNil 
+               ifTrue: 
+                       [ "#asInteger strips 'Content-Length' from the front of 
the string."
+                       totalByte := totalByte value trimSeparators asInteger.
+                       self reporter totalByte: totalByte. ].
     self reporter startTransfer.
     response preReadBytes isEmpty ifFalse:
-       [self reporter readByte: response preReadBytes size.
-       aStream nextPutAll: response preReadBytes].
+       [ self reporter readByte: response preReadBytes size. ].
 
     readStream := connectionStream stream.
-    [totalByte isNil
-       ifTrue: [readStream atEnd]
-       ifFalse: [totalByte = 0]
-
-    ]  whileFalse:
-               [| data |
-               data := totalByte notNil 
-                   ifTrue: [ readStream next: (4096 min: totalByte) ]
-                   ifFalse: [ readStream nextHunk ].
-
-               totalByte notNil
-                   ifTrue: [ totalByte := totalByte - data size ].
-               self reporter readByte: data size.
-               aStream nextPutAll: data ].
-
-    self reporter endTransfer.
+       response preReadBytes notEmpty ifTrue:
+               [ readStream := ConcatenatedStream 
+                       with: response preReadBytes readStream 
+                       with: readStream ].
+
+       totalByte notNil 
+               ifTrue:
+                       [ self readResponseStream: readStream into: aStream 
length: totalByte ]
+               ifFalse:
+                       [ | te |
+                       self readChunkedResponseStream: readStream into: 
aStream.
+                       "Remove 'chunked' from transfer-encoding header"
+                       te := response fieldAt: 'transfer-encoding' ifAbsent: [ 
nil ].
+                       te notNil ifTrue:
+                               [ | i s | 
+                               s := te value.
+                               (s indexOf: 'chunked' matchCase: false 
startingAt: 1) ifNotNil:
+                                       [ :i | 
+                                       te value: (s copyFrom: 1 to: i first - 
1), (s copyFrom: i last + 1) ] ]. ].
+       self reporter endTransfer.
     response keepAlive ifFalse: [ self close ]. 
-    ^response!
+    ^response
+!
 
-head: urlString requestHeaders: requestHeaders into: aStream
+head: urlString requestHeaders: requestHeaders
     | response |
     self connectIfClosed.
     self reporter startTransfer.
--- arch/kernel/Integer.st      2005-08-24 20:28:34.000000000 +0000
+++ mod/kernel/Integer.st       2005-09-04 18:43:42.000000000 +0000
@@ -51,7 +51,19 @@
 coerce: aNumber
     "Answer aNumber converted to a kind of Integer"
     ^aNumber truncated
-! !
+! 
+
+readHexFrom: aStream
+    | value ch |
+    value := 0.
+    [  (ch := aStream peek) notNil and: 
+                       [ (ch := ch asUppercase) isHexDigit ] ] 
+               whileTrue: 
+               [ value := (value * 16) + ch digitValue.
+               aStream next. ].
+       ^self coerce: value
+!
+!
 
 
 !Integer methodsFor: 'basic'!

reply via email to

[Prev in Thread] Current Thread [Next in Thread]