[squeak-dev] The Trunk: Morphic-cmm.1457.mcz

Tobias Pape Das.Linux at gmx.de
Sun Jul 1 23:21:21 UTC 2018


Do I parse that correctly that you just killed font size handling via shortcuts and introduced a new one?

While this could all be justified, wouldn't it be friendlier to first talk about that?
Eg, via inbox or so?

Best regards
	-Tobias

> On 02.07.2018, at 01:11, commits at source.squeak.org wrote:
> 
> Chris Muller uploaded a new version of Morphic to project The Trunk:
> http://source.squeak.org/trunk/Morphic-cmm.1457.mcz
> 
> ==================== Summary ====================
> 
> Name: Morphic-cmm.1457
> Author: cmm
> Time: 1 July 2018, 6:11:16.205766 pm
> UUID: 2ca064ea-7c51-4c44-a60a-f71968f10eae
> Ancestors: Morphic-kfr.1456
> 
> - Fix underline and strikeout in TextMorphs.
> - Added Command+Shift+_ (underscore) to condense the selected expression into one line.
> - Add font-size selection options to Themes & Colors menu.
> 
> =============== Diff against Morphic-kfr.1456 ===============
> 
> Item was changed:
>  ----- Method: PasteUpMorph>>findWindow: (in category 'world menu') -----
>  findWindow: evt
>  	"Present a menu names of windows and naked morphs, and activate the one that gets chosen.  Collapsed windows appear below line, expand if chosen; naked morphs appear below second line; if any of them has been given an explicit name, that is what's shown, else the class-name of the morph shows; if a naked morph is chosen, bring it to front and have it don a halo."
>  	| menu expanded collapsed nakedMorphs |
>  	menu := MenuMorph new.
>  	expanded := SystemWindow windowsIn: self satisfying: [:w | w isCollapsed not].
>  	collapsed := SystemWindow windowsIn: self satisfying: [:w | w isCollapsed].
>  	nakedMorphs := self submorphsSatisfying:
>  		[:m | (m isSystemWindow not and: [(m isStickySketchMorph) not]) and:
>  			[(m isFlapTab) not]].
>  	(expanded isEmpty & (collapsed isEmpty & nakedMorphs isEmpty)) ifTrue: [^ Beeper beep].
> + 	(expanded asSortedCollection: [:w1 :w2 | w1 label caseInsensitiveLessOrEqual: w2 label]) do:
> + 		[:w | menu add: (w label contractTo: 80) target: w action: #beKeyWindow.
> - 	(expanded sort: [:w1 :w2 | w1 label caseInsensitiveLessOrEqual: w2 label]) do:
> - 		[:w | menu add: w label target: w action: #beKeyWindow.
>  			w model canDiscardEdits ifFalse: [menu lastItem color: Color red]].
>  	(expanded isEmpty | (collapsed isEmpty & nakedMorphs isEmpty)) ifFalse: [menu addLine].
> + 	(collapsed asSortedCollection: [:w1 :w2 | w1 label caseInsensitiveLessOrEqual: w2 label]) do: 
> + 		[:w | menu add: (w label contractTo: 80) target: w action: #collapseOrExpand.
> - 	(collapsed sort: [:w1 :w2 | w1 label caseInsensitiveLessOrEqual: w2 label]) do: 
> - 		[:w | menu add: w label target: w action: #collapseOrExpand.
>  		w model canDiscardEdits ifFalse: [menu lastItem color: Color red]].
>  	nakedMorphs isEmpty ifFalse: [menu addLine].
> + 	(nakedMorphs asSortedCollection: [:w1 :w2 | w1 nameForFindWindowFeature caseInsensitiveLessOrEqual: w2 nameForFindWindowFeature]) do:
> + 		[:w | menu add: (w nameForFindWindowFeature contractTo: 80) target: w action: #comeToFrontAndAddHalo].
> - 	(nakedMorphs sort: [:w1 :w2 | w1 nameForFindWindowFeature caseInsensitiveLessOrEqual: w2 nameForFindWindowFeature]) do:
> - 		[:w | menu add: w nameForFindWindowFeature target: w action: #comeToFrontAndAddHalo].
>  	menu addTitle: 'find window' translated.
>  	
>  	menu popUpEvent: evt in: self.!
> 
> Item was changed:
>  ----- Method: PasteUpMorph>>tryInvokeKeyboardShortcut: (in category 'events-processing') -----
>  tryInvokeKeyboardShortcut: aKeyboardEvent
> 
>  	aKeyboardEvent commandKeyPressed ifFalse: [^ self].
>  	
>  	aKeyboardEvent keyCharacter caseOf: {
>  		[$R] -> [Utilities browseRecentSubmissions].
>  		[$L] -> [self findAFileList: aKeyboardEvent].
>  		[$O] -> [self findAMonticelloBrowser].
>  		[$P] -> [self findAPreferencesPanel: aKeyboardEvent].
>  		"[$Z] -> [ChangeList browseRecentLog]."
>  		[$]] -> [Smalltalk snapshot: true andQuit: false].
> - 		[$+] -> [Preferences increaseFontSize].
> - 		[$-] -> [Preferences decreaseFontSize].
> - 		[$=] -> [Preferences restoreDefaultFonts].
>  	} otherwise: [^ self "no hit"].
>  	
>  	aKeyboardEvent ignore "hit!!".!
> 
> Item was changed:
>  ----- Method: SmalltalkEditor class>>initializeShiftCmdKeyShortcuts (in category 'keyboard shortcut tables') -----
>  initializeShiftCmdKeyShortcuts 
>  	"Initialize the shift-command-key (or control-key) shortcut table."
>  	"NOTE: if you don't know what your keyboard generates, use Sensor kbdTest"
> - 	"wod 11/3/1998: Fix setting of cmdMap for shifted keys to actually use the 
> - 	capitalized versions of the letters.
> - 	TPR 2/18/99: add the plain ascii values back in for those VMs that don't return the shifted values."
> - 
> - 	"SmalltalkEditor initialize"
> - 
>  	| cmds |
>  	super initializeShiftCmdKeyShortcuts.
> - 	
>  	cmds := #(
>  		$a	argAdvance:
>  		$b	browseItHere:
>  		$d	debugIt:
>  		$e	methodStringsContainingIt:
>  		$f	displayIfFalse:
>  		$g	fileItIn:
>  		$i	exploreIt:
>  		$n	referencesToIt:
>  		$s	invokePrettyPrint:
>  		$t	displayIfTrue:
>  		$v	pasteInitials:
>  		$w	methodNamesContainingIt:
>  	).
>  	1 to: cmds size by: 2 do: [ :i |
>  		shiftCmdActions at: ((cmds at: i) asciiValue + 1) put: (cmds at: i + 1).			"plain keys"
>  		shiftCmdActions at: ((cmds at: i) asciiValue - 32 + 1) put: (cmds at: i + 1).		"shifted keys"
>  		shiftCmdActions at: ((cmds at: i) asciiValue - 96 + 1) put: (cmds at: i + 1).		"ctrl keys"
> + 	].
> + 	"shift+cmd _ (underscore)"
> + 	shiftCmdActions at: $_ asciiValue+1 put: #flattenSelection:!
> - 	].!
> 
> Item was added:
> + ----- Method: SmalltalkEditor>>flattenSelection: (in category 'editing keys') -----
> + flattenSelection: dummy
> + 	"Replace all lines and consecutive whitespace characters of the current selection with one line separated by single spaces."
> + 	self replaceSelectionWith: self selection string condensedIntoOneLine.
> + 	^ true!
> 
> Item was changed:
>  ----- Method: TheWorldMainDockingBar>>themesAndWindowColorsOn: (in category 'submenu - extras') -----
>  themesAndWindowColorsOn: menu
> - 
>  	| themes |
> - 	themes := UserInterfaceTheme allThemes asArray sorted: [:t1 :t2 |
> - 		t1 name <= t2 name].
> - 	
>  	menu addItem:[:item|
>  		item
>  			contents: (Model useColorfulWindows ifTrue: ['<yes>'] ifFalse: ['<no>']), 'Colorful Windows' translated;
>  			target: self;
>  			selector: #toggleColorfulWindows].
>  	menu addItem:[:item|
>  		item
>  			contents: (SystemWindow gradientWindow not ifTrue: ['<yes>'] ifFalse: ['<no>']), 'Flat Widget Look' translated;
>  			target: self;
>  			selector: #toggleGradients].
>  	menu addLine.
>  	menu addItem:[:item |
>  		item
>  			contents: (((Preferences valueOfFlag: #menuAppearance3d ifAbsent: [false]) and: [Morph useSoftDropShadow]) ifTrue: ['<yes>'] ifFalse: ['<no>']), 'Soft Shadows' translated;
>  			target: self;
>  			selector: #toggleSoftShadows].
>  	menu addItem:[:item |
>  		item
>  			contents: (((Preferences valueOfFlag: #menuAppearance3d ifAbsent: [false]) and: [Morph useSoftDropShadow not]) ifTrue: ['<yes>'] ifFalse: ['<no>']), 'Hard Shadows' translated;
>  			target: self;
>  			selector: #toggleHardShadows].
>  	menu addLine.
>  	menu addItem:[:item |
>  		item
>  			contents: (SystemWindow roundedWindowCorners ifTrue: ['<yes>'] ifFalse: ['<no>']), 'Rounded Window/Dialog/Menu Look' translated;
>  			target: self;
>  			selector: #toggleRoundedWindowLook].
>  	menu addItem:[:item |
>  		item
>  			contents: (PluggableButtonMorph roundedButtonCorners ifTrue: ['<yes>'] ifFalse: ['<no>']), 'Rounded Button/Scrollbar Look' translated;
>  			target: self;
>  			selector: #toggleRoundedButtonLook].
> + 	themes := UserInterfaceTheme allThemes asArray sort: #name ascending.	
> - 
> - 	
> - 	menu addLine.
> - 	
>  	themes ifEmpty: [ 
>  		menu addItem: [ :item | 
>  			item
>  				contents: '(No UI themes found.)' translated;
>  				isEnabled: false ] ].
>  	themes do: [ :each |
>  		menu addItem: [ :item |
>  			item 
>  				contents: (UserInterfaceTheme current == each ifTrue: ['<yes>'] ifFalse: ['<no>']), each name;
>  				target: each;
>  				selector: #apply ] ].
>  	menu
> + 		addLine ;
> + 		add: 'Increase Font Size' translated target: Preferences selector: #increaseFontSize ;
> + 		add: 'Decrease Font Size' translated target: Preferences selector: #decreaseFontSize ;
> + 		addLine.
> + 	menu
>  		addLine;
>  		add: 'Restore UI Theme Background' translated target: self selector: #restoreThemeBackground;
>  		add: 'Edit Current UI Theme...' translated target: self selector: #editCurrentTheme.!
> 
> Item was changed:
> + (PackageInfo named: 'Morphic') postscript: 'SmalltalkEditor initializeShiftCmdKeyShortcuts'!
> - (PackageInfo named: 'Morphic') postscript: 'Project allMorphicProjects do: [:p |
> - 	p world allMorphsDo: [:m |
> - 		(m isKindOf: BorderedMorph) ifTrue: [
> - 			m borderColor: (m instVarNamed: #borderColor).
> - 			m borderWidth: (m instVarNamed: #borderWidth)]]].'!
> 
> 



More information about the Squeak-dev mailing list