page width

Steven Elkins sgelkins at nortelnetworks.com
Wed Nov 10 09:51:05 UTC 1999


Scott Wallace <Scott.Wallace at disney.com> wrote:
> The reason why a number of us stopped having our mail client wrap our outgoing text is that when we set up Eudora to wrap messages, it also insists on wrapping the text in outgoing textual *attachments* -- such as Squeak fileouts.

I noticed the 'true ifTrue: [ ^aString ]' at the beginning of
CelesteComposition>>breakLines:atWidth: and guessed this
might be the reason.  I've been using Celeste at work
and home for about a week and felt obliged to make the
following changes:

1. Celeste>>updateTOC gives walkbacks every now and then
when currentMessages is nil, so I added the usual idiom in
a couple of places to prevent them.

2. In CelesteComposition>>breakLines:atWidth:, removed the 
guard at the beginning.

3. In CelesteComposition>>submit, added a #confirm: to ask
the user whether to wrap the text.

4. In CelesteComposition>>openInMorphic, corrected the way
the button label is spelled.

I know this doesn't help people who use Eudora, but it does
emphasize (for the zillionth time) how nice it is to use an
environment like Squeak.

Steve

--------------------changes--------------------

'From Squeak2.6 of 11 October 1999 [latest update: #1559] on 10 November 1999 at 9:21:47 am'!

!Celeste methodsFor: 'table of contents pane' stamp: 'sge 11/9/1999 16:39'!
updateTOC
	"Update the table of contents after a moving, removing, or deleting a message. Select a message near the removed message in the table of contents if possible."

	| currentMsgIndex |
	((currentCategory isNil) |
	 (currentMsgID isNil) |
	 (currentMessages isNil or: [currentMessages size < 2]))
		ifTrue: [currentMsgIndex _ 1]
		ifFalse: [currentMsgIndex _ currentMessages indexOf: currentMsgID].
	currentMsgID _ nil.
	self setCategory: currentCategory.  "update currentMessages, currentTOC"
	(currentMessages isNil or: [currentMessages isEmpty]) ifFalse: [
		(currentMsgIndex <= currentMessages size)
			ifTrue: [currentMsgID _ currentMessages at: currentMsgIndex]
			ifFalse: [currentMsgID _ currentMessages last].
	].
	self changed: #tocEntryList.
	self changed: #messageText.! !


!CelesteComposition methodsFor: 'private' stamp: 'sge 11/9/1999 12:56'!
breakLines: aString atWidth: width 
	"break lines in the given string into shorter lines"
	| result start end |
	result _ WriteStream on: (String new: aString size * 50 // 49).
	aString asString
		linesDo: 
			[:line | 
			start _ 1.
			"output one shorter line each time through this loop"
			[start + width <= line size]
				whileTrue: 
					["find the end of the line"
					end _ start + width - 1.
					[end >= start and: [(line at: end + 1) isSeparator not]]
						whileTrue: [end _ end - 1].
					end < start ifTrue: ["a word spans the entire width!!"
						end _ start + width - 1].
					"copy the line to the output"
					result nextPutAll: (line copyFrom: start to: end).
					result cr.
					"get ready for next iteration"
					start _ end + 1.
					(line at: start) isSeparator ifTrue: [start _ start + 1]].
			"write out the final part of the line"
			result nextPutAll: (line copyFrom: start to: line size).
			result cr].
	^ result contents! !

!CelesteComposition methodsFor: 'access' stamp: 'sge 11/9/1999 13:02'!
submit
	"submit the message" 
	textEditor
		ifNotNil: [self hasUnacceptedEdits ifTrue: [textEditor accept]].
	celeste queueMessageWithText: ((self confirm: 'Wrap text?')
			ifTrue: [self breakLines: messageText atWidth: 72]
			ifFalse: [messageText]).
	morphicWindow ifNotNil: [morphicWindow delete].
	mvcWindow ifNotNil: [mvcWindow controller close]! !

!CelesteComposition methodsFor: 'interface' stamp: 'sge 11/5/1999 16:38'!
openInMorphic
	"open an interface for sending a mail message with the given initial text"
	| textMorph buttonsList sendButton |

	morphicWindow _ SystemWindow labelled: 'Mister Postman'.
	morphicWindow model: self.
	
	textEditor _ textMorph _ PluggableTextMorph 
		on: self 
		text: #messageText  
		accept: #messageText:.
	morphicWindow addMorph: textMorph  frame: (0 at 0.1 corner: 1 at 1).

	buttonsList _ AlignmentMorph newRow.

	sendButton _ PluggableButtonMorph on: self getState: nil	 action: #submit.
	sendButton label: 'send message'.
	sendButton onColor: Color white  offColor: Color white.
	buttonsList addMorphBack: sendButton.
	
	morphicWindow addMorph: buttonsList  frame: (0 at 0 extent: 1 at 0.1).

	morphicWindow openInMVC.! !





More information about the Squeak-dev mailing list