[squeak-dev] The Trunk: Collections-ar.334.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Mar 10 06:24:38 UTC 2010


Andreas Raab uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-ar.334.mcz

==================== Summary ====================

Name: Collections-ar.334
Author: ar
Time: 9 March 2010, 10:24:00.841 pm
UUID: 689affd2-3259-b84c-993f-7e2053244cf5
Ancestors: Collections-ar.333

Give Base64MimeConverter the ability to not break lines longer than 70 characters. Useful (for example) when using long base64 encodings in urls.

=============== Diff against Collections-ar.333 ===============

Item was changed:
  ----- Method: Base64MimeConverter class>>mimeEncode: (in category 'as yet unclassified') -----
  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."
+ 	^self mimeEncode: aStream multiLine: true atStart: true!
- 
- 	| me |
- 	me := self new dataStream: aStream.
- 	me mimeStream: (ReadWriteStream on: (String new: aStream size + 20 * 4 // 3)).
- 	me mimeEncode.
- 	me mimeStream position: 0.
- 	^ me mimeStream!

Item was added:
+ ----- Method: Base64MimeConverter class>>mimeEncode:multiLine: (in category 'as yet unclassified') -----
+ mimeEncode: aStream multiLine: aBool
+ 	"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."
+ 
+ 	^self mimeEncode: aStream multiLine: aBool atStart: true!

Item was changed:
  ----- Method: Base64MimeConverter>>mimeEncode (in category 'conversion') -----
  mimeEncode
  	"Convert from data to 6 bit characters."
  
  	| phase1 phase2 raw nib lineLength |
  	phase1 := phase2 := false.
  	lineLength := 0.
  	[dataStream atEnd] whileFalse: [
+ 		(multiLine and:[lineLength >= 70]) ifTrue: [ mimeStream cr.  lineLength := 0. ].
- 		lineLength >= 70 ifTrue: [ mimeStream cr.  lineLength := 0. ].
  		data := raw := dataStream next asInteger.
  		nib := (data bitAnd: 16rFC) bitShift: -2.
  		mimeStream nextPut: (ToCharTable at: nib+1).
  		(raw := dataStream next) ifNil: [raw := 0. phase1 := true].
  		data := ((data bitAnd: 3) bitShift: 8) + raw asInteger.
  		nib := (data bitAnd: 16r3F0) bitShift: -4.
  		mimeStream nextPut: (ToCharTable at: nib+1).
  		(raw := dataStream next) ifNil: [raw := 0. phase2 := true].
  		data := ((data bitAnd: 16rF) bitShift: 8) + (raw asInteger).
  		nib := (data bitAnd: 16rFC0) bitShift: -6.
  		mimeStream nextPut: (ToCharTable at: nib+1).
  		nib := (data bitAnd: 16r3F).
  		mimeStream nextPut: (ToCharTable at: nib+1).
  
  		lineLength := lineLength + 4.].
  	phase1 ifTrue: [mimeStream skip: -2; nextPut: $=; nextPut: $=.
  			^ mimeStream].
  	phase2 ifTrue: [mimeStream skip: -1; nextPut: $=.
  			^ mimeStream].
  
  !

Item was changed:
  MimeConverter subclass: #Base64MimeConverter
+ 	instanceVariableNames: 'data multiLine'
- 	instanceVariableNames: 'data'
  	classVariableNames: 'FromCharTable ToCharTable'
  	poolDictionaries: ''
  	category: 'Collections-Streams'!
  
  !Base64MimeConverter commentStamp: '<historical>' prior: 0!
  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.!

Item was added:
+ ----- Method: Base64MimeConverter class>>mimeEncode:multiLine:atStart: (in category 'as yet unclassified') -----
+ mimeEncode: aStream multiLine: aBool atStart: resetInput
+ 	"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 |
+ 	resetInput ifTrue:[aStream position: 0].
+ 	me := self new dataStream: aStream.
+ 	me multiLine: aBool.
+ 	me mimeStream: (ReadWriteStream on: (String new: aStream size + 20 * 4 // 3)).
+ 	me mimeEncode.
+ 	me mimeStream position: 0.
+ 	^ me mimeStream!

Item was added:
+ ----- Method: Base64MimeConverter>>multiLine (in category 'accessing') -----
+ multiLine
+ 	"Determines whether we allow multi-line encodings (the default) or force everything into a single line (for use with URLs etc. where the continuation marker and the line break cause problems)"
+ 	^multiLine!

Item was added:
+ ----- Method: Base64MimeConverter>>multiLine: (in category 'accessing') -----
+ multiLine: aBool
+ 	"Determines whether we allow multi-line encodings (the default) or force everything into a single line (for use with URLs etc. where the continuation marker and the line break cause problems)"
+ 	multiLine := aBool!

Item was added:
+ ----- Method: Base64MimeConverter class>>mimeEncodeContinue: (in category 'as yet unclassified') -----
+ mimeEncodeContinue: 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."
+ 	^self mimeEncode: aStream multiLine: true atStart: false!




More information about the Squeak-dev mailing list