smalltalk
/
osmo-st-sip
Archived
1
0
Fork 0

callagent: Use a Base64 encoding to avoid spec issues

The branch may not contain '=' and the easiest is to
rename the code.
This commit is contained in:
Holger Hans Peter Freyther 2011-06-13 15:53:04 +02:00
parent c9362c643e
commit 67a44dd341
2 changed files with 9 additions and 9 deletions

View File

@ -64,7 +64,7 @@ Object subclass: MimeConverter [
MimeConverter subclass: Base64MimeConverter [
MimeConverter subclass: Base64LikeConverter [
| data |
<comment: 'This class encodes and decodes data in Base64 format. This is MIME encoding. We translate a whole stream at once, taking a Stream as input and giving one as output. Returns a whole stream for the caller to use. 0 A 17 R 34 i 51 z 1 B 18 S 35 j 52 0 2 C 19 T 36 k 53 1 3 D 20 U 37 l 54 2 4 E 21 V 38 m 55 3 5 F 22 W 39 n 56 4 6 G 23 X 40 o 57 5 7 H 24 Y 41 p 58 6 8 I 25 Z 42 q 59 7 9 J 26 a 43 r 60 8 10 K 27 b 44 s 61 9 11 L 28 c 45 t 62 + 12 M 29 d 46 u 63 / 13 N 30 e 47 v 14 O 31 f 48 w (pad) = 15 P 32 g 49 x 16 Q 33 h 50 y Outbound: bytes are broken into 6 bit chunks, and the 0-63 value is converted to a character. 3 data bytes go into 4 characters. Inbound: Characters are translated in to 0-63 values and shifted into 8 bit bytes. (See: N. Borenstein, Bellcore, N. Freed, Innosoft, Network Working Group, Request for Comments: RFC 1521, September 1993, MIME (Multipurpose Internet Mail Extensions) Part One: Mechanisms for Specifying and Describing the Format of Internet Message Bodies. Sec 6.2) By Ted Kaehler, based on Tim Olson''s Base64Filter.'>
@ -73,7 +73,7 @@ MimeConverter subclass: Base64MimeConverter [
FromCharTable := nil.
ToCharTable := nil.
Base64MimeConverter class >> initialize [
Base64LikeConverter class >> initialize [
FromCharTable := Array new: 256. "nils"
ToCharTable := Array new: 64.
($A asciiValue to: $Z asciiValue) doWithIndex:
@ -94,7 +94,7 @@ MimeConverter subclass: Base64MimeConverter [
ToCharTable at: 64 put: $/
]
Base64MimeConverter class >> mimeDecodeToBytes: aStream [
Base64LikeConverter class >> mimeDecodeToBytes: aStream [
"Return a RWBinaryOrTextStream of the original ByteArray. aStream has only 65 innocuous character values. aStream is not binary. (See class comment). 4 bytes in aStream goes to 3 bytes in output."
| me |
@ -107,7 +107,7 @@ MimeConverter subclass: Base64MimeConverter [
^me dataStream
]
Base64MimeConverter class >> mimeEncode: aStream [
Base64LikeConverter class >> mimeEncode: aStream [
"Return a ReadWriteStream of characters. The data of aStream is encoded as 65 innocuous characters. (See class comment). 3 bytes in aStream goes to 4 bytes in output."
| me |
@ -189,14 +189,14 @@ MimeConverter subclass: Base64MimeConverter [
ifTrue:
[mimeStream
skip: -2;
nextPut: $=;
nextPut: $=.
nextPut: $_;
nextPut: $_.
^mimeStream].
phase2
ifTrue:
[mimeStream
skip: -1;
nextPut: $=.
nextPut: $_.
^mimeStream]
]
@ -220,6 +220,6 @@ MimeConverter subclass: Base64MimeConverter [
Eval [
Base64MimeConverter initialize
Base64LikeConverter initialize
]

View File

@ -20,7 +20,7 @@ PackageLoader fileInPackage: 'Sockets'.
Object subclass: SIPBase64 [
SIPBase64 class >> encode: aString [
^ (Base64MimeConverter mimeEncode: aString readStream) contents
^ (Base64LikeConverter mimeEncode: aString readStream) contents
]
]