[squeak-dev] The Trunk: Collections-pre.790.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Apr 30 13:41:19 UTC 2018


Patrick Rein uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-pre.790.mcz

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

Name: Collections-pre.790
Author: pre
Time: 30 April 2018, 3:40:58.440101 pm
UUID: 24dbc4a0-d944-a942-a1d5-d8ef264cac5d
Ancestors: Collections-pre.789

Updates the q encoding converter to be able to encode header values. Beyond this there seems to be an issue regarding the separation of concerns between String and this converter. Currently the decoding happens mostly in String while the encoding happens in the MimeConverter.

=============== Diff against Collections-pre.789 ===============

Item was added:
+ QuotedPrintableMimeConverter subclass: #QEncodingMimeConverter
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Collections-Streams'!
+ 
+ !QEncodingMimeConverter commentStamp: 'pre 4/30/2018 12:13' prior: 0!
+ I do q format MIME decoding as specified in RFC 2047 ""MIME Part Three: Message Header Extensions for Non-ASCII Text". See String>>decodeMimeHeader!

Item was added:
+ ----- Method: QEncodingMimeConverter>>encodeChar:to: (in category 'private-encoding') -----
+ encodeChar: aChar to: aStream
+ 
+ 	aChar = Character space
+ 		ifTrue: [^ aStream nextPut: $_].
+ 	^ super encodeChar: aChar to: aStream!

Item was added:
+ ----- Method: QEncodingMimeConverter>>encodeWord: (in category 'private-encoding') -----
+ encodeWord: aString
+ 
+ 	| characterEncodedString |
+ 	(aString noneSatisfy: [:c | self conversionNeededFor: c])
+ 		ifTrue: [^ aString].
+ 	
+ 	characterEncodedString := aString squeakToUtf8.
+ 		
+ 	^ String streamContents: [:stream |
+ 		stream nextPutAll: '=?UTF-8?Q?'.
+ 		characterEncodedString do: [:c | self encodeChar: c to: stream].
+ 		stream nextPutAll: '?=']!

Item was added:
+ ----- Method: QEncodingMimeConverter>>mimeDecode (in category 'conversion') -----
+ mimeDecode
+ 	"Do conversion reading from mimeStream writing to dataStream. See String>>decodeMimeHeader for the character set handling."
+ 
+ 	| c |
+ 	[mimeStream atEnd] whileFalse: [
+ 		c := mimeStream next.
+ 		c = $=
+ 			ifTrue: [c := Character value: mimeStream next digitValue * 16
+ 				+ mimeStream next digitValue]
+ 			ifFalse: [c = $_ ifTrue: [c := $ ]].
+ 		dataStream nextPut: c].
+ 	^ dataStream!

Item was added:
+ ----- Method: QEncodingMimeConverter>>mimeEncode (in category 'conversion') -----
+ mimeEncode
+ 	"Do conversion reading from dataStream writing to mimeStream. Break long lines and escape non-7bit chars."
+ 	
+ 	| currentWord encodedWord |
+ 	
+ 	[dataStream atEnd] whileFalse: [
+ 		self readUpToWordInto: mimeStream.
+ 		currentWord := self readWord.
+ 		encodedWord := self encodeWord: currentWord.
+ 		mimeStream nextPutAll: encodedWord].
+ 	
+ 	^ mimeStream!

Item was added:
+ ----- Method: QEncodingMimeConverter>>readUpToWordInto: (in category 'private-encoding') -----
+ readUpToWordInto: aStream
+ 
+ 	| currentCharacter |
+ 	[dataStream atEnd] whileFalse:
+ 		[currentCharacter := dataStream peek.
+ 		 currentCharacter isSeparator 
+ 			ifTrue: [aStream nextPut: currentCharacter.
+ 					dataStream next]
+ 			ifFalse: [^ true]]!

Item was added:
+ ----- Method: QEncodingMimeConverter>>readWord (in category 'private-encoding') -----
+ readWord
+ 
+ 	| strm |
+ 	strm := WriteStream on: (String new: 20).
+ 	[dataStream atEnd] whileFalse: [
+ 		dataStream peek isSeparator 
+ 			ifTrue: [^ strm contents] 
+ 			ifFalse: [strm nextPut: dataStream next]].
+ 	^ strm contents!

Item was added:
+ ----- Method: QEncodingMimeConverter>>reservedCharacters (in category 'private-encoding') -----
+ reservedCharacters
+ 
+ 	^ '?=_ ' !

Item was changed:
  ----- Method: QuotedPrintableMimeConverter>>encodeChar:to: (in category 'as yet unclassified') -----
  encodeChar: aChar to: aStream
  
+ 	(self conversionNeededFor: aChar)
+ 			ifFalse: [aStream nextPut: aChar]
+ 			ifTrue: [aStream nextPut: $=;
+ 						nextPut: (Character digitValue: aChar asciiValue // 16);
+ 						nextPut: (Character digitValue: aChar asciiValue \\ 16)].
+ 			
+ 	
- 	aStream nextPut: $=;
- 		nextPut: (Character digitValue: aChar asciiValue // 16);
- 		nextPut: (Character digitValue: aChar asciiValue \\ 16)
  !

Item was changed:
  ----- Method: QuotedPrintableMimeConverter>>mimeEncode (in category 'conversion') -----
  mimeEncode
  	"Do conversion reading from dataStream writing to mimeStream. Break long lines and escape non-7bit chars."
  
  	| currentCharacter line lineStream linePosition |
  	currentCharacter := nil.
  	[(line := dataStream nextLine) isNil] whileFalse: [
  		lineStream := ReadStream on: line.
  		linePosition := 0.
  		
  		[lineStream atEnd] whileFalse: [
+ 			currentCharacter := lineStream next.
+ 			self encodeChar: currentCharacter to: mimeStream.
- 			(self conversionNeededFor: (currentCharacter := lineStream next))
- 				ifFalse: [mimeStream nextPut: currentCharacter]
- 				ifTrue: [self encodeChar: currentCharacter to: mimeStream].
  			linePosition := linePosition + 1.
  			linePosition = 73 ifTrue: [mimeStream nextPut: $=; crlf. linePosition := 0]].
  		dataStream atEnd ifFalse: [mimeStream crlf]].
  	^ mimeStream!

Item was changed:
  ----- Method: String>>decodeMimeHeader (in category 'internet') -----
  decodeMimeHeader
  	"See RFC 2047, MIME Part Three: Message Header Extension for Non-ASCII  
  	Text and RFC 1342. Text containing non-ASCII characters is encoded by the sequence  
  	=?character-set?encoding?encoded-text?=  
  	Encoding is Q (quoted printable) or B (Base64), handled by  
+ 	Base64MimeConverter / QEncodingMimeConverter.
- 	Base64MimeConverter / RFC2047MimeConverter.
  
  	Thanks to Yokokawa-san, it works in m17n package.  Try the following:
  
  	'=?ISO-2022-JP?B?U1dJS0lQT1AvGyRCPUJDKyVpJXMlQRsoQi8=?= =?ISO-2022-JP?B?GyRCJVElRiUjJSobKEIoUGF0aW8p?=' decodeMimeHeader.
  "
  	| input output temp charset decoder encodedStream encoding pos |
  	input := ReadStream on: self.
  	output := WriteStream on: String new.
  	[output
  		nextPutAll: (input upTo: $=).
  	"ASCII Text"
  	input atEnd]
  		whileFalse: [(temp := input next) = $?
  				ifTrue: [charset := input upTo: $?.
  					encoding := (input upTo: $?) asUppercase.
  					temp := input upTo: $?.
  					input next.
  					"Skip final ="
  					(charset isNil or: [charset size = 0]) ifTrue: [charset := 'LATIN-1'].
  					encodedStream := WriteStream on: String new.
  					decoder := encoding = 'B'
  								ifTrue: [Base64MimeConverter new]
+ 								ifFalse: [QEncodingMimeConverter new].
- 								ifFalse: [RFC2047MimeConverter new].
  					decoder
  						mimeStream: (ReadStream on: temp);
  						 dataStream: encodedStream;
  						 mimeDecode.
  					
  					output nextPutAll: (MultiByteBinaryOrTextStream with: encodedStream contents encoding: charset) contents.
  					pos := input position.
  					input skipSeparators.
  					"Delete spaces if followed by ="
  					input peek = $=
  						ifFalse: [input position: pos]]
  				ifFalse: [output nextPut: $=;
  						 nextPut: temp]].
  	^ output contents!



More information about the Squeak-dev mailing list