The Inbox: Morphic-ct.1588.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
2 messages Options
Reply | Threaded
Open this post in threaded view
|

The Inbox: Morphic-ct.1588.mcz

commits-2
A new version of Morphic was added to project The Inbox:
http://source.squeak.org/inbox/Morphic-ct.1588.mcz

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

Name: Morphic-ct.1588
Author: ct
Time: 15 November 2019, 2:18:46.719005 pm
UUID: cd229fb4-796e-a349-9c09-811159cf9e6e
Ancestors: Morphic-mt.1587

TextEditor: Add support for different keyboard layouts, fix the 9-enclosing bug and clean up #enclose:

You now can do [Editor defaultKeyboardLayout: #qwertz] to adapt the editing behavior of Squeak to the qwertz layout. Squeakers from all the world, feel free to add further keyboard layouts to #specialShiftKeyMaps!

We also had an interesting dicussion concerning the 9-enclosing bug (see http://forum.world.st/When-did-it-become-a-good-idea-for-selected-text-to-be-enclosed-by-instead-of-replaced-by-9-td4936276.html) and wondered whether there would be really anyone willing to press 9 only, without any modifier key, to enclose the selection with brackets. He or she might press 9 and shift together in future (on a qwertz layout), it would be just incon{sist,veni}ent that 8 and 9 had such different behaviors.

Depends on Collections-ct.860.

=============== Diff against Morphic-mt.1587 ===============

Item was changed:
  Object subclass: #Editor
  instanceVariableNames: 'morph selectionShowing'
+ classVariableNames: 'BlinkingCursor DefaultKeyboardLayout DestructiveBackWord DumbbellCursor EnclosingCharacterMap KeystrokeActions SelectionsMayShrink SpecialShiftKeyMaps'
- classVariableNames: 'BlinkingCursor DestructiveBackWord DumbbellCursor KeystrokeActions SelectionsMayShrink'
  poolDictionaries: ''
  category: 'Morphic-Text Support'!
 
  !Editor commentStamp: 'hjh 9/28/2017 11:37' prior: 0!
  New text editors.
  TextEditor provides most of the functionality that used to be in TextMorphEditor.
  SmalltalkEditor is has Smalltalk code specific features.
  !

Item was added:
+ ----- Method: Editor class>>defaultKeyboardLayout (in category 'keyboard shortcut tables') -----
+ defaultKeyboardLayout
+
+ ^ DefaultKeyboardLayout ifNil: [#qwerty]!

Item was added:
+ ----- Method: Editor class>>defaultKeyboardLayout: (in category 'keyboard shortcut tables') -----
+ defaultKeyboardLayout: aSymbol
+
+ DefaultKeyboardLayout := aSymbol!

Item was added:
+ ----- Method: Editor class>>enclosingCharacterMap (in category 'keyboard shortcut tables') -----
+ enclosingCharacterMap
+
+ ^ EnclosingCharacterMap ifNil: [EnclosingCharacterMap :=
+ Dictionary fromKeys: '([<{|"''' values: ')]>}|"''']!

Item was changed:
  ----- Method: Editor class>>initialize (in category 'class initialization') -----
  initialize
  "
  Editor initialize
  "
  self initializeKeystrokeActions.
+ EnclosingCharacterMap := nil.
+ SpecialShiftKeyMaps := nil.
  self allSubclassesDo: [ :c | c initialize ]!

Item was added:
+ ----- Method: Editor class>>specialShiftKeyMaps (in category 'keyboard shortcut tables') -----
+ specialShiftKeyMaps
+
+ SpecialShiftKeyMaps ifNotNil: [^ SpecialShiftKeyMaps].
+ SpecialShiftKeyMaps := Dictionary new
+ at: #qwerty put: (Dictionary fromKeys: '[]\'',.90' values: '{}|"<>()');
+ at: #qwertz put: (Dictionary fromKeys: '89' values: '()');
+ yourself.
+ ^ SpecialShiftKeyMaps!

Item was added:
+ ----- Method: Editor>>enclosingCharacterFor:ifNone: (in category 'as yet unclassified') -----
+ enclosingCharacterFor: openingCharacter ifNone: aBlock
+
+ ^ self enclosingCharacterMap
+ at: openingCharacter
+ ifAbsent: aBlock!

Item was added:
+ ----- Method: Editor>>enclosingCharacterMap (in category 'as yet unclassified') -----
+ enclosingCharacterMap
+
+ ^ self class enclosingCharacterMap!

Item was added:
+ ----- Method: Editor>>keyboardLayout (in category 'accessing') -----
+ keyboardLayout
+
+ ^ self class defaultKeyboardLayout!

Item was added:
+ ----- Method: Editor>>mapSpecialKeyToShift: (in category 'private') -----
+ mapSpecialKeyToShift: aCharacter
+ "Maps special characters such as $[ on a qwerty keyboard to their uppercase equivalent, that would be ${ in this example. Probably required by some VM implementations."
+
+ ^ self specialShiftKeys
+ at: aCharacter
+ ifAbsent: [aCharacter]!

Item was added:
+ ----- Method: Editor>>specialShiftKeys (in category 'accessing') -----
+ specialShiftKeys
+
+ ^ self class specialShiftKeyMaps at: self keyboardLayout!

Item was changed:
  ----- Method: TextEditor>>enclose: (in category 'editing keys') -----
  enclose: aKeyboardEvent
  "Insert or remove bracket characters around the current selection."
 
+ | character left right startIndex stopIndex oldSelection text |
- | character left right startIndex stopIndex oldSelection which t |
- character := aKeyboardEvent shiftPressed
- ifTrue: ['{}|"<>' at: ('[]\'',.' indexOf: aKeyboardEvent keyCharacter) ifAbsent: [aKeyboardEvent keyCharacter]]
- ifFalse: [aKeyboardEvent keyCharacter].
  self closeTypeIn.
+
+ character := aKeyboardEvent keyCharacter.
+ (aKeyboardEvent shiftPressed
+ or: ["Allow Control key in lieu of Alt+Shift for certain special keys."
+ Preferences cmdKeysInText and: [aKeyboardEvent controlKeyPressed]])
+ ifTrue: [character := self mapSpecialKeyToShift: aKeyboardEvent keyCharacter].
  startIndex := self startIndex.
  stopIndex := self stopIndex.
  oldSelection := self selection.
+ left := character.
+ right := self enclosingCharacterFor: left ifNone: [^ false].
+
+ text := self text.
+ ((startIndex > 1 and: [stopIndex <= text size])
+ and: [ (text at: startIndex - 1) = left and: [(text at: stopIndex) = right]])
- which := '([<{|"''9' indexOf: character ifAbsent: [ ^ false ].
- "Allow Control key in lieu of Alt+Shift for (, {, and double-quote."
- left := ((Preferences cmdKeysInText and: [ aKeyboardEvent controlKeyPressed ])
- ifTrue: [ '({<{|""(' ]
- ifFalse: ['([<{|"''(']) at: which.
- right := ((Preferences cmdKeysInText and: [ aKeyboardEvent controlKeyPressed ])
- ifTrue: [ ')}>}|"")' ]
- ifFalse: [')]>}|"'')']) at: which.
- t := self text.
- ((startIndex > 1 and: [stopIndex <= t size])
- and: [ (t at: startIndex-1) = left and: [(t at: stopIndex) = right]])
  ifTrue:
  ["already enclosed; strip off brackets"
+ self selectFrom: startIndex - 1 to: stopIndex.
- self selectFrom: startIndex-1 to: stopIndex.
  self replaceSelectionWith: oldSelection]
  ifFalse:
  ["not enclosed; enclose by matching brackets"
+ self replaceSelectionWith: (Text
+ string: (String with: left), oldSelection string, (String with: right)
+ attributes: emphasisHere).
+ self selectFrom: startIndex + 1 to: stopIndex].
+ ^ true!
- self replaceSelectionWith:
- (Text string: (String with: left), oldSelection string, (String with: right) attributes: emphasisHere).
- self selectFrom: startIndex+1 to: stopIndex].
- ^true!


Reply | Threaded
Open this post in threaded view
|

Mac Users please test this :-) | Re: The Inbox: Morphic-ct.1588.mcz

Christoph Thiede
Hi all,

while revising this proposal for the Nine Key Bug, which I'd really like to
fix in the Trunk soon, I realized that a good part of the complexity of this
commit, #mapSpecialKeyToShift: and the keyboardLayout logic, is added
suspiciously and only "probably necessary for certain VM implementations". I
turned it off on my machine and could not identify any need to do implement
shift key mappings manually on the image-side. Are there any edge cases I
could be missing? Tested for both QWERTZ and QWERTY on:

- Windows 10,
- WSL Ubuntu with VcXsrv, and
- Squeak.js.

But I can't test it on Apple system. Could some Mac User maybe please merge
this version, comment out the following paragraph, and find out if the
editor enclosing functionality is still working well?

(aKeyboardEvent shiftPressed
                        or: ["Allow Control key in lieu of Alt+Shift for certain special keys."
                                Preferences cmdKeysInText and: [aKeyboardEvent controlKeyPressed]])
                ifTrue: [character := self mapSpecialKeyToShift: character].

Thanks in advance! :-) If I don't get any feedback within a week, I'll
assume this code branch is no longer required and remove it in my next
revision of this version.

Best,
Christoph



--
Sent from: http://forum.world.st/Squeak-Dev-f45488.html

Carpe Squeak!