smalltalk
/
osmo-st-sip
Archived
1
0
Fork 0
This repository has been archived on 2022-02-17. You can view files and clone it, but cannot push or open issues or pull requests.
osmo-st-sip/callagent/Base64MimeConverter.st

215 lines
7.2 KiB
Smalltalk
Raw Permalink Blame History

This file contains invisible Unicode characters

This file contains invisible Unicode characters that are indistinguishable to humans but may be processed differently by a computer. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

Eval [
'From Pharo-1.1-11411 of 17 July 2010 [Latest update: #11411] on 19 February 2011 at 9:09:05 pm'
]
ReadWriteStream subclass: MIMERWStream [
| readLimit |
<category: 'OsmoSIP-Base64'>
nextPut: aInt [
| res |
res := super nextPut: aInt.
readLimit := self readLimit max: self position.
^ res
]
contents [
^ collection copyFrom: 1 to: self readLimit.
]
readLimit [
^ readLimit ifNil: [readLimit := 0].
]
]
Object subclass: MimeConverter [
| dataStream mimeStream |
<category: 'OsmoSIP-Base64'>
dataStream [
<category: 'accessing'>
^dataStream
]
dataStream: anObject [
<category: 'accessing'>
dataStream := anObject
]
mimeStream [
<category: 'accessing'>
^mimeStream
]
mimeStream: anObject [
<category: 'accessing'>
mimeStream := anObject
]
mimeDecode [
"Do conversion reading from mimeStream writing to dataStream"
<category: 'conversion'>
self subclassResponsibility
]
mimeEncode [
"Do conversion reading from dataStream writing to mimeStream"
<category: 'conversion'>
self subclassResponsibility
]
]
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.'>
<category: 'OsmoSIP-Base64'>
FromCharTable := nil.
ToCharTable := nil.
Base64LikeConverter class >> initialize [
FromCharTable := Array new: 256. "nils"
ToCharTable := Array new: 64.
($A asciiValue to: $Z asciiValue) doWithIndex:
[:val :ind |
FromCharTable at: val + 1 put: ind - 1.
ToCharTable at: ind put: val asCharacter].
($a asciiValue to: $z asciiValue) doWithIndex:
[:val :ind |
FromCharTable at: val + 1 put: ind + 25.
ToCharTable at: ind + 26 put: val asCharacter].
($0 asciiValue to: $9 asciiValue) doWithIndex:
[:val :ind |
FromCharTable at: val + 1 put: ind + 25 + 26.
ToCharTable at: ind + 26 + 26 put: val asCharacter].
FromCharTable at: $+ asciiValue + 1 put: 62.
ToCharTable at: 63 put: $+.
FromCharTable at: $/ asciiValue + 1 put: 63.
ToCharTable at: 64 put: $/
]
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 |
me := self new dataStream: aStream.
me
mimeStream: (MIMERWStream on: (String new: (aStream size + 20) * 4 // 3)).
me mimeEncode.
me mimeStream position: 0.
^me mimeStream
]
mimeDecode [
"Convert a stream in base 64 with only a-z,A-Z,0-9,+,/ to a full byte stream of characters. Reutrn a whole stream for the user to read."
<category: 'conversion'>
| nibA nibB nibC nibD |
[mimeStream atEnd] whileFalse:
[(nibA := self nextValue) ifNil: [^dataStream].
(nibB := self nextValue) ifNil: [^dataStream].
dataStream nextPut: ((nibA bitShift: 2) + (nibB bitShift: -4)) asCharacter.
nibB := nibB bitAnd: 15.
(nibC := self nextValue) ifNil: [^dataStream].
dataStream nextPut: ((nibB bitShift: 4) + (nibC bitShift: -2)) asCharacter.
nibC := nibC bitAnd: 3.
(nibD := self nextValue) ifNil: [^dataStream].
dataStream nextPut: ((nibC bitShift: 6) + nibD) asCharacter].
^dataStream
]
mimeDecodeToByteArray [
"Convert a stream in base 64 with only a-z,A-Z,0-9,+,/ to a full ByteArray of 0-255 values. Reutrn a whole stream for the user to read."
<category: 'conversion'>
| nibA nibB nibC nibD |
[mimeStream atEnd] whileFalse:
[(nibA := self nextValue) ifNil: [^dataStream].
(nibB := self nextValue) ifNil: [^dataStream].
dataStream nextPut: (nibA bitShift: 2) + (nibB bitShift: -4).
nibB := nibB bitAnd: 15.
(nibC := self nextValue) ifNil: [^dataStream].
dataStream nextPut: (nibB bitShift: 4) + (nibC bitShift: -2).
nibC := nibC bitAnd: 3.
(nibD := self nextValue) ifNil: [^dataStream].
dataStream nextPut: (nibC bitShift: 6) + nibD].
^dataStream
]
mimeEncode [
"Convert from data to 6 bit characters."
<category: 'conversion'>
| phase1 phase2 raw nib lineLength |
phase1 := phase2 := false.
lineLength := 0.
[dataStream atEnd] whileFalse:
[lineLength >= 70
ifTrue:
[mimeStream cr.
lineLength := 0].
data := raw := dataStream next asInteger.
nib := (data bitAnd: 252) bitShift: -2.
mimeStream nextPut: (ToCharTable at: nib + 1).
dataStream atEnd
ifTrue: [raw := 0. phase1 := true]
ifFalse: [raw := dataStream next].
data := ((data bitAnd: 3) bitShift: 8) + raw asInteger.
nib := (data bitAnd: 1008) bitShift: -4.
mimeStream nextPut: (ToCharTable at: nib + 1).
dataStream atEnd
ifTrue: [raw := 0. phase2 := true]
ifFalse: [raw := dataStream next].
data := ((data bitAnd: 15) bitShift: 8) + raw asInteger.
nib := (data bitAnd: 4032) bitShift: -6.
mimeStream nextPut: (ToCharTable at: nib + 1).
nib := data bitAnd: 63.
mimeStream nextPut: (ToCharTable at: nib + 1).
lineLength := lineLength + 4].
phase1
ifTrue:
[mimeStream
skip: -2;
nextPut: $_;
nextPut: $_.
^mimeStream].
phase2
ifTrue:
[mimeStream
skip: -1;
nextPut: $_.
^mimeStream]
]
nextValue [
"The next six bits of data char from the mimeStream, or nil. Skip all other chars"
<category: 'conversion'>
| raw num |
[raw := mimeStream next.
raw ifNil: [^nil]. "end of stream"
raw == $= ifTrue: [^nil].
num := FromCharTable at: raw asciiValue + 1.
num ifNotNil: [^num].
"else ignore space, return, tab, ..."
true]
whileTrue
]
]
Eval [
Base64LikeConverter initialize
]