[squeak-dev] The Trunk: Morphic-topa.786.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Mar 24 12:12:08 UTC 2015


Tobias Pape uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-topa.786.mcz

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

Name: Morphic-topa.786
Author: topa
Time: 24 March 2015, 1:11:32.699 pm
UUID: 4f85b986-fcc9-4344-a042-9cb323a6484c
Ancestors: Morphic-cmm.785

Font Importer Tool:

- Clarify 'Install' (now 'Link' via context menu)
- Provide Help for 'Import' and 'Link'
- Be a StringHolder now (so that perform:orSendTo: works as intended oO)

=============== Diff against Morphic-cmm.785 ===============

Item was changed:
+ StringHolder subclass: #FontImporterTool
- Model subclass: #FontImporterTool
  	instanceVariableNames: 'title allFonts emphasis window currentSelection currentParent warningSeen'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Morphic-Support'!
  
  !FontImporterTool commentStamp: 'topa 3/9/2015 18:56' prior: 0!
  A tool to import platform (native) fonts into the image!

Item was changed:
  ----- Method: FontImporterTool>>buildButtonBarWith: (in category 'toolbuilder') -----
  buildButtonBarWith: builder
  	"Build the button bar"
  	| panelSpec buttonSpec |
  	panelSpec := builder pluggablePanelSpec new.
  	panelSpec children: OrderedCollection new.
  
  	buttonSpec := builder pluggableButtonSpec new
  			model: self;
  			label: ' Import ' translated; 
+ 			help: 'Include the font data in the image and provide a TextStyle for the font';
  			action: #import;
+ 			frame: (0 at 0 corner: 0.5 at 1);
- 			frame: (0 at 0 corner: (1/3)@1);
  			yourself.
  	panelSpec children addLast: buttonSpec.
  
- 	buttonSpec := builder pluggableButtonSpec new
- 			model: self;
- 			label: ' Install ' translated; 
- 			action: #install;
- 			frame: ((1/3)@0 corner: (2/3)@1);
- 			yourself.
- 	panelSpec children addLast: buttonSpec.
  
- 
  	buttonSpec := builder pluggableButtonSpec new
  			model: self;
  			label: ' Close ' translated; 
  			action: #close;
+ 			frame: (0.5 at 0 corner: 1 at 1);
- 			frame: ((2/3)@0 corner: 1 at 1);
  			yourself.
  	panelSpec children addLast: buttonSpec.
  
  
  	^panelSpec!

Item was changed:
  ----- Method: FontImporterTool>>buildFontListWith: (in category 'toolbuilder') -----
  buildFontListWith: builder
  	"Build the font choosers list of font names"
  	
  	^ builder pluggableTreeSpec new
  		model: self;
  		roots: #allFonts; 
  		label: #labelOf: ;
  		getChildren: #childrenOf: ;
  		getSelected: #currentSelection;
  		setSelected: #currentSelection:;
  		setSelectedParent: #currentParent:;
+ 		menu: #fontListMenu:;
  		autoDeselect: false;
  		yourself
  !

Item was changed:
  ----- Method: FontImporterTool>>buildPreviewPaneWith: (in category 'toolbuilder') -----
  buildPreviewPaneWith: builder
  	"Build the preview panel"
  	
  	^ builder pluggablePanelSpec new
  		children: {
  			builder pluggableTextSpec new
  				model: self;
  				getText: #filename;
  				frame: (LayoutFrame 
  					fractions: (0 at 0 corner: 1 at 0)
  					offsets: (0 at 0 corner: 0@ -25));
  				yourself.
  
+ 			(self buildCodePaneWith: builder)
- 			 builder pluggableTextSpec new
  				name: #preview;
- 				model: self;
- 				getText: #contents;
  				frame: (LayoutFrame 
  					fractions: (0 at 0 corner: 1 at 0.75)
  					offsets: (0@ 30 corner: 0 at 0));
  				yourself.
  				
  			builder pluggableTextSpec new
  				model: self;
  				getText: #copyright;
  				frame: (LayoutFrame 
  					fractions: (0 at 0.75 corner: 1 at 1));
  				yourself
  			
  		};
  		yourself!

Item was removed:
- ----- Method: FontImporterTool>>buildWindowWith: (in category 'toolbuilder') -----
- buildWindowWith: builder
- 
- 	^ builder pluggableWindowSpec new
- 		model: self;
- 		label: #windowTitle;
- 		children: OrderedCollection new;
- 		yourself
- !

Item was removed:
- ----- Method: FontImporterTool>>buildWindowWith:specs: (in category 'toolbuilder') -----
- buildWindowWith: builder specs: specs
- 	| windowSpec |
- 	windowSpec := self buildWindowWith: builder.
- 	specs do:[:assoc| | action widgetSpec rect |
- 		rect := assoc key.
- 		action := assoc value.
- 		widgetSpec := action value.
- 		widgetSpec ifNotNil:[
- 			widgetSpec frame: rect.
- 			windowSpec children add: widgetSpec]].
- 	^windowSpec!

Item was changed:
  ----- Method: FontImporterTool>>buildWith: (in category 'toolbuilder') -----
  buildWith: builder
  	"Create the ui for the browser"
  	"ToolBuilder open: self"
  	| windowSpec |
  	windowSpec := self buildWindowWith: builder specs: {
  		(self fontListFrame) -> [self buildFontListWith: builder].
  		(self previewFrame) -> [self buildPreviewPaneWith: builder].
  		(self buttonsFrame) -> [self buildButtonBarWith: builder].
  	}.
  	windowSpec extent: self initialExtent.
  	window := builder build: windowSpec.
  	"Yes, that's a hack. But it looks ugly with line breaks."
  	(builder widgetAt: #preview) textMorph wrapFlag: false.
  	^window!

Item was added:
+ ----- Method: FontImporterTool>>fontListMenu: (in category 'font list') -----
+ fontListMenu: aMenu
+ 
+ 	^ aMenu addTranslatedList: #(
+ 		('Import Font'	import	'Include the font data in the image and provide a TextStyle for the font')
+ 		('Link Font'		link  'Install the font as a link to its file and provide a TextStyle for the referenced font'))
+ 	yourself!

Item was removed:
- ----- Method: FontImporterTool>>install (in category 'actions') -----
- install
- 	| filenames fonts |
- 	fonts := self currentSelection.
- 	self warningSeen ifFalse: [
- 		(UIManager default confirm: (
- 'Note that installing a font instead of importing may make the
- image un-portable, since the installed font must be present on
- the system the next time the image is run.
- 
- This warning is only shown once per session.' ) trueChoice: 'Proceed' falseChoice: 'Cancel')
- 		ifFalse: [^ self].
- 		self warningSeen: true]..
- 	filenames := fonts allFilenames.
- 	filenames do: [:filename | | readFonts |
- 		readFonts := TTFileDescription readFontsFrom: filename.
- 		readFonts isCollection
- 					ifFalse: [TTCFont newTextStyleFromTT: readFonts]
- 					ifTrue: [self importFontFamily: readFonts]].
- 	self allFonts: nil. "force redraw"!

Item was added:
+ ----- Method: FontImporterTool>>link (in category 'actions') -----
+ link
+ 	| filenames fonts |
+ 	fonts := self currentSelection.
+ 	self warningSeen ifFalse: [
+ 		(UIManager default confirm: (
+ 'Note that linking a font instead of importing may make the
+ image un-portable, since the linked font must be present on
+ the system the next time the image is run.
+ 
+ This warning is only shown once per session.' ) trueChoice: 'Proceed' falseChoice: 'Cancel')
+ 		ifFalse: [^ self].
+ 		self warningSeen: true]..
+ 	filenames := fonts allFilenames.
+ 	filenames do: [:filename | | readFonts |
+ 		readFonts := TTFileDescription readFontsFrom: filename.
+ 		readFonts isCollection
+ 					ifFalse: [TTCFont newTextStyleFromTT: readFonts]
+ 					ifTrue: [self importFontFamily: readFonts]].
+ 	self allFonts: nil. "force redraw"!



More information about the Squeak-dev mailing list