pharo-project / pharo

Pharo is a dynamic reflective pure object-oriented language supporting live programming inspired by Smalltalk.
http://pharo.org
Other
1.21k stars 355 forks source link

ClyTextEditor (in fact RubTextEditor) is not using correctly KeyboardKey #8329

Closed Ducasse closed 3 years ago

Ducasse commented 3 years ago
String class >> with: aCharacter
    | newCollection |
    newCollection := aCharacter asInteger < 256
        ifTrue:[ ByteString new: 1]
        ifFalse:[ WideString new: 1].
    newCollection at: 1 put: aCharacter.
    ^newCollection

breaks because aCharacter is a KeyboardKey

It is invoked here

ClyTextEditor >> encloseWith: aMatchingPair
    "Insert or remove bracket characters around the current selection."

    | left right startIndex stopIndex oldSelection text newString |
    self closeTypeIn.
    startIndex := self startIndex.
    stopIndex := self stopIndex.
    oldSelection := self selection.

    left := aMatchingPair key.
    right := aMatchingPair value.
    text := self text.
    ((startIndex > 1 and: [stopIndex <= text size])
            and: [ (text at: startIndex-1) = left and: [(text at: stopIndex) = right]])
        ifTrue: [
            "already enclosed; strip off brackets"
            newString := (self shouldNestCharacter: left)
                         ifTrue: [ self unNesting: oldSelection with: left ] 
                         ifFalse: [ oldSelection ].
            self selectFrom: startIndex-1 to: stopIndex.
            self replaceSelectionWith: newString ]
        ifFalse: [
            " Checks if the characters inside the selection need to be escaped or not. "
            newString := (self shouldNestCharacter: left)
                         ifTrue: [ self nesting: oldSelection with: left ] 
                         ifFalse: [ "not enclosed; enclose by matching brackets"
                                      (String with: left), oldSelection string, (String with: right) ].
                                                                          ^^^^^^^^^^^^^^^^^^                                    ^^^^^^^^^^^^^^^^^^^^^^
            self replaceSelectionWith:
                (Text string: newString attributes: self emphasisHere).
            "we add the difference of the newString and the oldSelection, here, to ajust to eventual nesting. The 2 corrsponds to se left and right characters added which are not in oldSelection."
            self selectFrom: startIndex+1 to: stopIndex+(newString size - oldSelection size - 2)].
    ^true
Ducasse commented 3 years ago

Guille I could find how to get the character from the keyboardKey (may be this is not needed).

I also think that this expression will be always false :newString := (self shouldNestCharacter: left) because left is not a character

Ducasse commented 3 years ago

I saw that we have table to go from character to keyboardKey but not the inverse.

Ducasse commented 3 years ago

Maybe it can make sense to add

asCharacter 
  ^ Character value: value

I do not if this is not violating the original design.

Ducasse commented 3 years ago

To be able to work I did

encloseWith: aMatchingPair
    "Insert or remove bracket characters around the current selection."

    | left right startIndex stopIndex oldSelection text newString |
    self closeTypeIn.
    startIndex := self startIndex.
    stopIndex := self stopIndex.
    oldSelection := self selection.

    left := Character value: aMatchingPair key value.
    right := Character value: aMatchingPair value value.
    text := self text.
    ((startIndex > 1 and: [stopIndex <= text size])
            and: [ (text at: startIndex-1) = left and: [(text at: stopIndex) = right]])
        ifTrue: [
            "already enclosed; strip off brackets"
            newString := (self shouldNestCharacter: left)
                         ifTrue: [ self unNesting: oldSelection with: left ] 
                         ifFalse: [ oldSelection ].
            self selectFrom: startIndex-1 to: stopIndex.
            self replaceSelectionWith: newString ]
        ifFalse: [
            " Checks if the characters inside the selection need to be escaped or not. "
            newString := (self shouldNestCharacter: left)
                         ifTrue: [ self nesting: oldSelection with: left ] 
                         ifFalse: [ "not enclosed; enclose by matching brackets"
                                      (String with: left), oldSelection string, (String with: right) ].
            self replaceSelectionWith:
                (Text string: newString attributes: self emphasisHere).
            "we add the difference of the newString and the oldSelection, here, to ajust to eventual nesting. The 2 corrsponds to se left and right characters added which are not in oldSelection."
            self selectFrom: startIndex+1 to: stopIndex+(newString size - oldSelection size - 2)].
    ^true
Ducasse commented 3 years ago

In fact my solution does not work because the pair value is not a KeyboardKey but a KeyboardEvent???? so Character value: aMatchingPair value value. is breaking obviously :)

Ducasse commented 3 years ago
performCmdActionsWith: aKeyboardEvent shifted: aBoolean return: return
    | key actions action|
    key := aKeyboardEvent key.
    actions := self cmdActions.
    action := (actions at: key ifAbsent: [ ^ false ]).
    return value: (self perform: action with: aKeyboardEvent).

encloseWith: is called by performCmdActionsWith: aKeyboardEvent shifted: aBoolean return: return so now I do not get why I do not get a pair and not just an aKeyboardEvent.

Ducasse commented 3 years ago

So may be we need a table to be able to go from [ to ] and ( to )....

guillep commented 3 years ago

I think this is related to this change https://github.com/pharo-project/pharo/pull/8316

It seems enclose: and encloseWith: are not really interchangeable. encloseWith: expects an association, while enclose: receives a keyboard event.

Ducasse commented 3 years ago

I have the impression also that we need a way to go from the [ to ] or ( to )