[squeak-dev] The Trunk: MorphicExtras-mt.274.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Mar 5 15:23:14 UTC 2020


Marcel Taeumel uploaded a new version of MorphicExtras to project The Trunk:
http://source.squeak.org/trunk/MorphicExtras-mt.274.mcz

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

Name: MorphicExtras-mt.274
Author: mt
Time: 5 March 2020, 4:23:09.451454 pm
UUID: effd6ab6-57af-ba4c-810f-3d050dcf4521
Ancestors: MorphicExtras-mt.273

Make FancyMailComposition use ToolBuilder. Not sure whether we need this tool at all. :-) Maybe Merge with MailComposition.

=============== Diff against MorphicExtras-mt.273 ===============

Item was changed:
  Model subclass: #FancyMailComposition
+ 	instanceVariableNames: 'messageText theLinkToInclude to subject'
- 	instanceVariableNames: 'messageText textEditor morphicWindow mvcWindow theLinkToInclude to subject textFields'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'MorphicExtras-EToy-Download'!

Item was changed:
  ----- Method: FancyMailComposition>>addAttachment (in category 'actions') -----
  addAttachment
  
+ 	self changed: #acceptChanges.
- 	textEditor
- 		ifNotNil: [self hasUnacceptedEdits ifTrue: [textEditor accept]].
  
  	(FileChooserDialog openOn: FileDirectory default pattern: nil label: 'Choose attachment') ifNotNil: 
  		[:fileName |
  		FileStream readOnlyFileNamed: fileName do:
  			[:file | 
  			file binary.
  			self messageText:
  				((MailMessage from: self messageText asString)
  					addAttachmentFrom: file withName: (FileDirectory localNameFor: fileName);  
  				text)]]!

Item was removed:
- ----- Method: FancyMailComposition>>borderAndButtonColor (in category 'morphic gui') -----
- borderAndButtonColor
- 
- 	^Color r: 0.729 g: 0.365 b: 0.729!

Item was added:
+ ----- Method: FancyMailComposition>>buildButtonsWith: (in category 'toolbuilder') -----
+ buildButtonsWith: builder
+ 
+ 	| panel |
+ 	panel := builder pluggablePanelSpec new.
+ 	panel
+ 		layout: #horizontal;
+ 		children: OrderedCollection new.
+ 	
+ 	panel children addLast: (builder pluggableButtonSpec new
+ 		model: self;
+ 		label: 'send later';
+ 		help: 'add this to the queue of messages to be sent';
+ 		action: #submit;
+ 		color: Color white;
+ 		yourself).
+ 		
+ 	panel children addLast: (builder pluggableButtonSpec new
+ 		model: self;
+ 		label: 'send now';
+ 		help: 'send this message immediately';
+ 		action: #sendNow;
+ 		color: Color white;
+ 		yourself).
+ 
+ 	panel children addLast: (builder pluggableButtonSpec new
+ 		model: self;
+ 		label: 'add attachment';
+ 		help: 'send a file with the message';
+ 		action: #addAttachment;
+ 		color: Color white;
+ 		yourself).
+ 
+ 	^ panel!

Item was added:
+ ----- Method: FancyMailComposition>>buildMessageTextWith: (in category 'toolbuilder') -----
+ buildMessageTextWith: builder
+ 
+ 	^ builder pluggableTextSpec new
+ 		model: self;
+ 		getText: #messageText;
+ 		setText: #messageText:;
+ 		menu: #menuGet:shifted:;
+ 		yourself!

Item was added:
+ ----- Method: FancyMailComposition>>buildTextFieldsWith: (in category 'toolbuilder') -----
+ buildTextFieldsWith: builder
+ 
+ 	| panel |
+ 	panel := builder pluggablePanelSpec new.
+ 	panel
+ 		layout: #vertical;
+ 		children: OrderedCollection new.
+ 	
+ 	panel children addLast: (builder pluggableInputFieldSpec new
+ 		model: self;
+ 		help: 'To';
+ 		getText: #to;
+ 		setText: #to:;
+ 		yourself).
+ 
+ 	panel children addLast: (builder pluggableInputFieldSpec new
+ 		model: self;
+ 		help: 'Subject';
+ 		getText: #subject;
+ 		setText: #subject:;
+ 		yourself).
+ 
+ 	^ panel!

Item was added:
+ ----- Method: FancyMailComposition>>buildWith: (in category 'toolbuilder') -----
+ buildWith: builder
+ 
+ 	^ builder build: (self buildWindowWith: builder specs: {
+ 		(0 @ 0 corner: 1 @ 0.1) -> [self buildButtonsWith: builder].
+ 		(0 @ 0.1 corner: 1 @ 0.3) -> [self buildTextFieldsWith: builder].
+ 		(0 @ 0.3 corner: 1 @ 1) -> [self buildMessageTextWith: builder]. })!

Item was removed:
- ----- Method: FancyMailComposition>>buttonWithAction:label:help: (in category 'morphic gui') -----
- buttonWithAction: aSymbol label: labelString help: helpString
- 
- 	^self newColumn
- 		wrapCentering: #center; cellPositioning: #topCenter;
- 		addMorph: (
- 			SimpleButtonMorph new 
- 				color: self borderAndButtonColor;
- 				target: self; 
- 				actionSelector: aSymbol;
- 				label: labelString;
- 				setBalloonText: helpString
- 		)
- 			!

Item was changed:
  ----- Method: FancyMailComposition>>celeste:to:subject:initialText:theLinkToInclude: (in category 'initialization') -----
  celeste: aCeleste to: argTo subject: argSubject initialText: aText theLinkToInclude: linkText 
   "self new celeste: Celeste current to: 'danielv at netvision.net.il' subject: 'Mysubj' initialText: 'atext' theLinkToInclude: 'linkText'"
  
  	to := argTo.
  	subject := argSubject.
  	messageText := aText.
+ 	theLinkToInclude := linkText.!
- 	theLinkToInclude := linkText.
- 	textFields := #().
- !

Item was changed:
  ----- Method: FancyMailComposition>>completeTheMessage (in category 'actions') -----
  completeTheMessage
  
  	| newText strm |
+ 	self changed: #acceptChanges.
- 	textFields do: [ :each | each hasUnacceptedEdits ifTrue: [ each accept ] ].
  
  	newText := String new: 200.
  	strm := WriteStream on: newText.
  	strm 
  		nextPutAll: 'Content-Type: text/html'; cr;
  		nextPutAll: 'From: ', MailSender userName; cr;
  		nextPutAll: 'To: ',to; cr;
  		nextPutAll: 'Subject: ',subject; cr;
  
  		cr;
  		nextPutAll: '<HTML><BODY><BR>';
  		nextPutAll: messageText asStringToHtml;
  		nextPutAll: '<BR><BR>',theLinkToInclude,'<BR></BODY></HTML>'.
+ 	^strm contents!
- 	^strm contents
- 
- 
- 
- 
- !

Item was added:
+ ----- Method: FancyMailComposition>>defaultWindowColor (in category 'user interface') -----
+ defaultWindowColor
+ 
+ 	^ Color veryLightGray!

Item was changed:
+ ----- Method: FancyMailComposition>>forgetIt (in category 'user interface') -----
- ----- Method: FancyMailComposition>>forgetIt (in category 'morphic gui') -----
  forgetIt
  
+ 	self changed: #close.!
- 	morphicWindow ifNotNil: [ morphicWindow delete ].
- 	mvcWindow ifNotNil: [ mvcWindow controller close ].
- !

Item was removed:
- ----- Method: FancyMailComposition>>morphicOpen (in category 'user interface') -----
- morphicOpen
- 	"open an interface for sending a mail message with the given initial 
- 	text "
- 	| textMorph buttonsList sendButton attachmentButton |
- 	morphicWindow := SystemWindow labelled: 'Mister Postman'.
- 	morphicWindow model: self.
- 	textEditor := textMorph := PluggableTextMorph
- 						on: self
- 						text: #messageText
- 						accept: #messageText:
- 						readSelection: nil
- 						menu: #menuGet:shifted:.
- 	morphicWindow addMorph: textMorph frame: (0 @ 0.1 corner: 1 @ 1).
- 	buttonsList := AlignmentMorph newRow.
- 	sendButton := PluggableButtonMorph
- 				on: self
- 				getState: nil
- 				action: #submit.
- 	sendButton
- 		hResizing: #spaceFill;
- 		vResizing: #spaceFill;
- 		label: 'send message';
- 		setBalloonText: 'Accept any unaccepted edits and add this to the queue of messages to be sent';
- 		onColor: Color white offColor: Color white.
- 	buttonsList addMorphBack: sendButton.
- 	
- 	attachmentButton := PluggableButtonMorph
- 				on: self
- 				getState: nil
- 				action: #addAttachment.
- 	attachmentButton
- 		hResizing: #spaceFill;
- 		vResizing: #spaceFill;
- 		label: 'add attachment';
- 		setBalloonText: 'Send a file with the message';
- 		onColor: Color white offColor: Color white.
- 	buttonsList addMorphBack: attachmentButton.
- 	
- 	morphicWindow addMorph: buttonsList frame: (0 @ 0 extent: 1 @ 0.1).
- 	morphicWindow openInWorld!

Item was removed:
- ----- Method: FancyMailComposition>>newColumn (in category 'morphic gui') -----
- newColumn
- 
- 	^AlignmentMorph newColumn color: self staticBackgroundColor!

Item was removed:
- ----- Method: FancyMailComposition>>newRow (in category 'morphic gui') -----
- newRow
- 
- 	^AlignmentMorph newRow color: self staticBackgroundColor!

Item was changed:
  ----- Method: FancyMailComposition>>open (in category 'user interface') -----
  open
+ 	
+ 	self flag: #refactor. "FancyMailComposition should probably be removed in favour of MailComposition."
+ 	^ ToolBuilder open: self!
- 	"FancyMailComposition should probably be removed in favour of MailComposition, but at least ought to be made a ToolBuilder thing"	"open an interface"
- 	self deprecated: 'ought to be removed of ToolBuilderised'.
- 	^ Project uiManager openFancyMailComposition: self!

Item was removed:
- ----- Method: FancyMailComposition>>openInMorphic (in category 'morphic gui') -----
- openInMorphic
- 	"open an interface for sending a mail message with the given initial 
- 	text "
- 	| buttonsList container toField subjectField |
- 	buttonsList := self newRow.
- 	buttonsList wrapCentering: #center; cellPositioning: #leftCenter.
- 	buttonsList
- 		addMorphBack: (
- 			(self 
- 				buttonWithAction: #submit
- 				label: 'send later'
- 				help: 'add this to the queue of messages to be sent')
- 		);
- 		addMorphBack: (
- 			(self 
- 				buttonWithAction: #sendNow
- 				label: 'send now'
- 				help: 'send this message immediately')
- 		);
- 		addMorphBack: (
- 			(self 
- 				buttonWithAction: #forgetIt
- 				label: 'forget it'
- 				help: 'forget about sending this message')
- 		).
- 	morphicWindow := container := AlignmentMorphBob1 new
- 		borderWidth: 8;
- 		borderColor: self borderAndButtonColor;
- 		color: Color white.
- 
- 	container 
- 		addMorphBack: (buttonsList vResizing: #shrinkWrap; minHeight: 25; yourself);
- 		addMorphBack: ((self simpleString: 'To:') vResizing: #shrinkWrap; minHeight: 18; yourself);
- 		addMorphBack: ((toField := PluggableTextMorph
- 			on: self
- 			text: #to
- 			accept: #to:) hResizing: #spaceFill; vResizing: #rigid; height: 50; yourself
- 		);
- 		addMorphBack: ((self simpleString: 'Subject:') vResizing: #shrinkWrap; minHeight: 18; yourself);
- 		addMorphBack: ((subjectField := PluggableTextMorph
- 			on: self
- 			text: #subject
- 			accept: #subject:) hResizing: #spaceFill; vResizing: #rigid; height: 50; yourself
- 		);
- 		addMorphBack: ((self simpleString: 'Message:') vResizing: #shrinkWrap; minHeight: 18; yourself);
- 		addMorphBack: ((textEditor := PluggableTextMorph
- 			on: self
- 			text: #messageText
- 			accept: #messageText:) hResizing: #spaceFill; vResizing: #spaceFill; yourself
- 		).
- 	textFields := {toField. subjectField. textEditor}.
- 	container 
- 		extent: 300 at 400;
- 		openInWorld.!

Item was removed:
- ----- Method: FancyMailComposition>>perform:orSendTo: (in category 'private') -----
- perform: selector orSendTo: otherTarget
- 
- 	(self respondsTo: selector)
- 		ifTrue: [^self perform: selector]
- 		ifFalse: [^otherTarget perform: selector]
- 
- 	!

Item was removed:
- ----- Method: FancyMailComposition>>simpleString: (in category 'morphic gui') -----
- simpleString: aString
- 
- 	^self newRow
- 		layoutInset: 2;
- 		addMorphBack: (StringMorph contents: aString) lock!

Item was removed:
- ----- Method: FancyMailComposition>>staticBackgroundColor (in category 'morphic gui') -----
- staticBackgroundColor
- 
- 	^Color veryLightGray!

Item was added:
+ ----- Method: FancyMailComposition>>windowTitle (in category 'user interface') -----
+ windowTitle
+ 
+ 	^ 'Mister Postman'!



More information about the Squeak-dev mailing list