[ENH] Celeste receives attachments

Bob Arning arning at charm.net
Thu Apr 27 00:29:49 UTC 2000


On Thu, 27 Apr 2000 02:19:08 +0300 Daniel Vainsencher <danielv at netvision.net.il> wrote:
>Guys, anybody feel like doing the encoding side of QuotedPrintable? (base64 is basically enough, but QuotedPrintable is, well, printable...)

I have included below what I use. You will need to change the class to one you have. If anything is missing, the whole magilla can be found in 

	http://www.charm.net/~arning/SqMailServer.24Apr1833.cs

Cheers,
Bob

===== code follows =====
'From Squeak2.8alpha of 13 January 2000 [latest update: #2040] on 26 April 2000 at 8:24:58 pm'!
"Change Set:		QPStuff
Date:			26 April 2000
Author:			Bob Arning

Hopefully all the bits needed to create a QP version of a message"!


!EekMailSMTPSocket methodsFor: 'as yet unclassified' stamp: 'RAA 4/26/2000 20:22'!
convertToQuotedPrintable: lines

	|  newLines |
	newLines _ OrderedCollection new.
	lines do: [ :aString | 
		self convertToQuotedPrintable: aString addTo: newLines.
	].
	^newLines! !

!EekMailSMTPSocket methodsFor: 'as yet unclassified' stamp: 'RAA 4/26/2000 20:22'!
convertToQuotedPrintable: aString addTo: lines

	| newLine newString breakPoint |
	aString isEmpty ifTrue: [^lines add: aString].
	newLine _ WriteStream on: ''.
	aString do: [ :char | 
		(self mustBeQuoted: char) ifTrue: [
			newLine 
				nextPut: $=;
				nextPutAll: char hex.
		] ifFalse: [
			newLine nextPut: char
		].
	].
	newString _ newLine contents.
	(#(9 32) includes: newString last asciiValue) ifTrue: [
		newString _ (newString copyFrom: 1 to: newString size - 1),
				'=',newString last hex
	].
	[newString size > 72] whileTrue: [
		breakPoint _ newString findBreakPointWithMaxLength: 72.
		breakPoint = 0 ifTrue: [breakPoint _ 72].
		(newString at: breakPoint) = $= ifTrue: [breakPoint _ breakPoint - 1].
		lines add: (newString copyFrom: 1 to: breakPoint),'='.
		newString _ newString copyFrom: breakPoint + 1 to: newString size.
	].
	newString = '.' ifTrue: [newString _ '. '].
	lines add: newString.
	^lines
! !

!EekMailSMTPSocket methodsFor: 'as yet unclassified' stamp: 'RAA 4/26/2000 20:23'!
mustBeQuoted: aCharacter

	| val |
	val _ aCharacter asciiValue.
	val = 9 ifTrue: [^false].
	val < 32 ifTrue: [^true].
	val = 61 ifTrue: [^true].
	^val > 126
! !

!EekMailSMTPSocket methodsFor: 'as yet unclassified' stamp: 'RAA 4/26/2000 20:22'!
prepareMessageText: aMessage

	| in lines requiresQuotedPrintable headers |
	headers _ OrderedCollection new.
	requiresQuotedPrintable _ false.
	in _ ReadStream on: aMessage messageTextForSend.
	lines _ OrderedCollection new.
	in linesDo: [ :thisLine |
		lines add: thisLine.
		requiresQuotedPrintable _ requiresQuotedPrintable or: [
			self requiresQuotedPrintable: thisLine
		]
	].
	headers 
		addAll: aMessage toHeaderLines;
		add: 'Subject: ',(aMessage subject copyWithout: Character cr);
		add: 'MIME-Version: 1.0';
		add: 'X-Mailer: eekMail 1.0'.
	requiresQuotedPrintable ifTrue: [
		lines _ self convertToQuotedPrintable: lines.
		headers add: 'Content-Transfer-Encoding: quoted-printable'
	].
	lines _ lines collect: [ :each | 
		(each size > 0 and: [each first = $.]) ifTrue: [
			'.',each
		] ifFalse: [
			each
		].
	].
	^headers, #(''), lines
! !

!EekMailSMTPSocket methodsFor: 'as yet unclassified' stamp: 'RAA 4/26/2000 20:21'!
requiresQuotedPrintable: aString

	aString isEmpty ifTrue: [^false].
	aString size > 500 ifTrue: [^true].
	(#(9 32) includes: aString last asciiValue) ifTrue: [^true].
	aString do: [ :ch | (self mustBeQuoted: ch) ifTrue: [^true]].
	^false! !


!String methodsFor: 'converting' stamp: 'RAA 4/26/2000 20:24'!
findBreakPointWithMaxLength: anInteger

	| prevSpace nextSpace |
	prevSpace _ 0.
	[
		nextSpace _ self 
			indexOf: $  
			startingAt: prevSpace + 1 
			ifAbsent: [self size].
		nextSpace <= anInteger
	] whileTrue: [prevSpace _ nextSpace].
	^prevSpace! !





More information about the Squeak-dev mailing list