> OBCodeBrowser  >> subscribe
>     "We want to be notified first about changes of the definition, so that
> we can replace it with a custom one."
>
>     | actions |
>     super subscribe.
>     actions := announcer subscriptions
>         at: OBDefinitionChanged
>         ifAbsent: [ ActionSequence new ].
>     announcer subscriptions
>         at: OBDefinitionChanged
>         put: (actions copyWithFirst: (MessageSend
>             receiver: self
>             selector: #definitionChanged:))
>
> to:
>
> OBCodeBrowser  >> subscribe
>     "We want to be notified first about changes of the definition, so that
> we can replace it with a custom one."
>
>     | actions |
>     super subscribe.
>     announcer on: OBDefinitionChanged send: #definitionChanged: to: self.

This change breaks the undo/redo mechanism of class definitions and
subsequently the undo/redo mechanism of all other code changes and
refactorings.

> And from:
>
> OBTextMorphWithShout >> editorClass
>     "Answer the class used to create the receiver's editor"
>
>     ^OBTextMorphEditorWithShout
>
> to:
>
> OBTextMorphWithShout >> editorClass
>     "Answer the class used to create the receiver's editor"
>
>     ^SmalltalkEditor

This breaks OB in various ways. Not every editor is a Smalltalk
editor, there are lots of editors that don't need Smalltalk semantics
(editing comments, editing organization, displaying lint results,
displaying diffs, ...).

Furthermore, OBTextMorphWithShould should be gone. It is not needed
any longer and was removed to make OB properly work in Pharo 1.2.

Lukas

-- 
Lukas Renggli
www.lukas-renggli.ch

Reply via email to