'From Squeak5.1 of 6 December 2017 [latest update: #16551] on 24 March 2018 at 11:28:36 am'! Editor subclass: #TextEditor instanceVariableNames: 'model paragraph markBlock pointBlock beginTypeInIndex emphasisHere lastParenLocation otherInterval oldInterval typeAhead history ' classVariableNames: 'AutoEnclose AutoIndent ChangeText EncloseSelection FindText ' poolDictionaries: '' category: 'Morphic-Text Support'! TextEditor subclass: #SmalltalkEditor instanceVariableNames: 'styler ' classVariableNames: 'EncloseSelection AutoIndent AutoEnclose ' poolDictionaries: '' category: 'Morphic-Text Support'! !PreferenceWizardMorph methodsFor: 'buttons' stamp: 'tcj 3/24/2018 10:47'! stateAutoEnclose ^ SmalltalkEditor autoEnclose! ! !PreferenceWizardMorph methodsFor: 'buttons' stamp: 'tcj 3/24/2018 10:47'! stateAutoIndent ^ SmalltalkEditor autoIndent! ! !PreferenceWizardMorph methodsFor: 'buttons' stamp: 'tcj 3/24/2018 10:47'! stateEncloseSelection ^ SmalltalkEditor encloseSelection! ! !PreferenceWizardMorph methodsFor: 'buttons' stamp: 'tcj 3/24/2018 10:50'! toggleAutoEnclose SmalltalkEditor autoEnclose: SmalltalkEditor autoEnclose not. self changed: #stateAutoEnclose.! ! !PreferenceWizardMorph methodsFor: 'buttons' stamp: 'tcj 3/24/2018 10:49'! toggleAutoIndent SmalltalkEditor autoIndent: SmalltalkEditor autoIndent not. self changed: #stateAutoIndent.! ! !PreferenceWizardMorph methodsFor: 'buttons' stamp: 'tcj 3/24/2018 10:49'! toggleEncloseSelection SmalltalkEditor encloseSelection: SmalltalkEditor encloseSelection not. self changed: #stateEncloseSelection.! ! !ReleaseBuilder class methodsFor: 'scripts' stamp: 'tcj 3/24/2018 10:49'! setPreferences "Preferences class defaultValueTableForCurrentRelease" " Preferences outOfTheBox." "<-- uncomment after #defaultValueTableForCurrentRelease is fixed up." "General User interaction" Preferences enable: #generalizedYellowButtonMenu ; enable: #swapMouseButtons; disable: #mouseOverForKeyboardFocus. Morph indicateKeyboardFocus: true. Project uiManager openToolsAttachedToMouseCursor: false. SearchBar useScratchPad: false. HandMorph sendMouseWheelToKeyboardFocus: false. HandMorph synthesizeMouseWheelEvents: true. "Smalltalk editing." SmalltalkEditor autoEnclose: true ; autoIndent: true ; encloseSelection: false. "Text input." TextEditor destructiveBackWord: false ; blinkingCursor: true ; dumbbellCursor: false. PluggableTextMorph simpleFrameAdornments: false. "Windows" SystemWindow reuseWindows: false. SystemWindow windowsRaiseOnClick: true. SystemWindow windowTitleActiveOnFirstClick: true. Model windowActiveOnFirstClick: false. "Not good for little screen real estate." Model useColorfulWindows: false. Preferences disable: #showSplitterHandles; disable: #fastDragWindowForMorphic. CornerGripMorph drawCornerResizeHandles: false; passiveColor: (Color gray: 0.85); activeColor: (Color r: 1 g: 0.599 b: 0.0). ProportionalSplitterMorph smartHorizontalSplitters: false ; smartVerticalSplitters: false. "Scroll bars." Preferences enable: #scrollBarsNarrow; enable: #scrollBarsOnRight; enable: #alwaysHideHScrollbar; disable: #alwaysShowHScrollbar; disable: #alwaysShowVScrollbar. ScrollBar scrollBarsWithoutArrowButtons: true; scrollBarsWithoutMenuButton: true. ScrollPane useRetractableScrollBars: false. "Rounded corners." Morph preferredCornerRadius: 8. SystemWindow roundedWindowCorners: false. DialogWindow roundedDialogCorners: false. MenuMorph roundedMenuCorners: false. PluggableButtonMorph roundedButtonCorners: false. ScrollBar roundedScrollBarLook: false. "Gradients." SystemWindow gradientWindow: false. DialogWindow gradientDialog: false. MenuMorph gradientMenu: false. PluggableButtonMorph gradientButton: false. ScrollBar gradientScrollBar: false. "Shadows" Preferences enable: #menuAppearance3d. Morph useSoftDropShadow: true. "Lists and Trees" PluggableListMorph filterableLists: true; clearFilterAutomatically: false; highlightHoveredRow: true; menuRequestUpdatesSelection: true. PluggableTreeMorph filterByLabelsOnly: false; maximumSearchDepth: 1. "Standard Tools" TheWorldMainDockingBar showWorldMainDockingBar: true; showSecondsInClock: true; twentyFourHourClock: true. SearchBar useSmartSearch: true. Workspace shouldStyle: false. Browser listClassesHierarchically: true; showClassIcons: true; showMessageIcons: true; sortMessageCategoriesAlphabetically: true. Preferences enable: #annotationPanes; enable: #optionalButtons; disable: #diffsWithPrettyPrint; enable: #traceMessages; enable: #alternativeBrowseIt; enable: #menuWithIcons; enable: #visualExplorer. SystemNavigation thoroughSenders: true. Preferences disable: #debugLogTimestamp. "Halo" Preferences enable: #showBoundsInHalo ; disable: #alternateHandlesLook; disable: #showDirectionHandles. "System" NetNameResolver enableIPv6: false. Scanner allowUnderscoreAsAssignment: true; prefAllowUnderscoreSelectors: true. Deprecation showDeprecationWarnings: false. "that's all, folks"! ! !TextEditor methodsFor: 'typing support' stamp: 'tcj 3/24/2018 10:37'! dispatchOnKeyboardEvent: aKeyboardEvent "Carry out the action associated with this character, if any. Type-ahead is passed so some routines can flush or use it." | honorCommandKeys typedChar | typedChar := aKeyboardEvent keyCharacter. "Handle one-line input fields." (typedChar == Character cr and: [morph acceptOnCR]) ifTrue: [^ true]. "Clear highlight for last opened parenthesis." self clearParens. "Handle line breaks and auto indent." typedChar == Character cr ifTrue: [ aKeyboardEvent controlKeyPressed ifTrue: [^ self normalCharacter: aKeyboardEvent]. aKeyboardEvent shiftPressed ifTrue: [^ self lf: aKeyboardEvent]. aKeyboardEvent commandKeyPressed ifTrue: [^ self crlf: aKeyboardEvent]. ^ self crWithIndent: aKeyboardEvent]. "Handle indent/outdent with selected text block." typedChar == Character tab ifTrue: [ aKeyboardEvent shiftPressed ifTrue: [self outdent: aKeyboardEvent. ^ true] ifFalse: [self hasMultipleLinesSelected ifTrue: [self indent: aKeyboardEvent. ^ true]]]. honorCommandKeys := Preferences cmdKeysInText. (honorCommandKeys and: [typedChar == Character enter]) ifTrue: [^ self dispatchOnEnterWith: aKeyboardEvent]. "Special keys overwrite crtl+key combinations - at least on Windows. To resolve this conflict, assume that keys other than cursor keys aren't used together with Crtl." ((self class specialShiftCmdKeys includes: aKeyboardEvent keyValue) and: [aKeyboardEvent keyValue < 27]) ifTrue: [^ aKeyboardEvent controlKeyPressed ifTrue: [self perform: (self class shiftCmdActions at: aKeyboardEvent keyValue + 1) with: aKeyboardEvent] ifFalse: [self perform: (self class cmdActions at: aKeyboardEvent keyValue + 1) with: aKeyboardEvent]]. "backspace, and escape keys (ascii 8 and 27) are command keys" ((honorCommandKeys and: [aKeyboardEvent commandKeyPressed]) or: [self class specialShiftCmdKeys includes: aKeyboardEvent keyValue]) ifTrue: [ ^ aKeyboardEvent shiftPressed ifTrue: [self perform: (self class shiftCmdActions at: aKeyboardEvent keyValue + 1) with: aKeyboardEvent] ifFalse: [self perform: (self class cmdActions at: aKeyboardEvent keyValue + 1) with: aKeyboardEvent]]. "the control key can be used to invoke shift-cmd shortcuts" (honorCommandKeys and: [ aKeyboardEvent controlKeyPressed ]) ifTrue: [^ self perform: (self class shiftCmdActions at: aKeyboardEvent keyValue + 1) with: aKeyboardEvent]. self normalCharacter: aKeyboardEvent. ^ false! ! !SmalltalkEditor methodsFor: 'typing/selecting keys' stamp: 'nice 8/3/2011 19:28'! crWithIndent: aKeyboardEvent "Replace the current text selection with CR followed by as many tabs as on the current line (+/- bracket count) -- initiated by Shift-Return." self addString: (String streamContents: [:characterStream | characterStream crtab: self tabCount]). "Now inject CR with tabCount tabs" ^ false! ! !SmalltalkEditor methodsFor: 'typing/selecting keys' stamp: 'nice 2/8/2010 10:57'! tabCount ^ self class autoIndent ifTrue: [ | tabCount s i char | s := paragraph string. i := self stopIndex. tabCount := 0. [(i := i-1) > 0 and: [(char := s at: i) ~= Character cr and: [char ~= Character lf]]] whileTrue: "Count tabs and brackets (but not a leading bracket)" [(char = Character tab and: [i < s size and: [(s at: i+1) ~= $[ ]]) ifTrue: [tabCount := tabCount + 1]. char = $[ ifTrue: [tabCount := tabCount + 1]. char = $] ifTrue: [tabCount := tabCount - 1]]. tabCount ] ifFalse: [ 0 ]! ! !SmalltalkEditor methodsFor: 'typing support' stamp: 'tcj 3/24/2018 10:38'! dispatchOnKeyboardEvent: aKeyboardEvent | typedChar | typedChar := aKeyboardEvent keyCharacter. "Enclose selection with brackets etc." ((self class encloseSelection and: [self hasSelection]) and: [self enclose: aKeyboardEvent]) ifTrue: [^ true]. "Automatically enclose paired characters such as brackets." (self class autoEnclose and: [self autoEncloseFor: typedChar]) ifTrue: [^ true]. ^ super dispatchOnKeyboardEvent: aKeyboardEvent. ! ! !SmalltalkEditor class methodsFor: 'preferences' stamp: 'tpr 8/12/2016 16:39'! autoEnclose ^ AutoEnclose ifNil: [ false ]! ! !SmalltalkEditor class methodsFor: 'preferences' stamp: 'cmm 7/3/2010 16:17'! autoEnclose: aBoolean AutoEnclose := aBoolean! ! !SmalltalkEditor class methodsFor: 'preferences' stamp: 'mt 4/19/2016 09:08'! autoIndent ^ AutoIndent ifNil: [ true ]! ! !SmalltalkEditor class methodsFor: 'preferences' stamp: 'cmm 2/5/2010 11:16'! autoIndent: aBoolean AutoIndent := aBoolean! ! !SmalltalkEditor class methodsFor: 'preferences' stamp: 'tpr 8/12/2016 16:49'! encloseSelection ' categoryList: #('Morphic' 'editing') description: 'When true, selecting text and typing an opening parenthesis, bracket, square-bracket, single quote, or double quote will add corresponding character around the selection without requiring a cmd key.' type: #Boolean> ^ EncloseSelection ifNil: [ false ]! ! !SmalltalkEditor class methodsFor: 'preferences' stamp: 'mt 4/19/2016 09:12'! encloseSelection: boolean EncloseSelection := boolean.! ! !TextMorph class methodsFor: 'class initialization' stamp: 'tcj 3/24/2018 10:34'! initialize "TextMorph initialize" "Initialize the default text editor class to use" DefaultEditorClass := TextEditor. "Initialize constants shared by classes associated with text display." CaretForm := (ColorForm extent: 16@5 fromArray: #(2r001100e26 2r001100e26 2r011110e26 2r111111e26 2r110011e26) offset: -2@0) colors: (Array with: Color transparent with: Preferences textHighlightColor). self registerInFlapsRegistry. ! ! !TextMorphForEditView methodsFor: 'private' stamp: 'tcj 3/24/2018 10:54'! editorClass ^SmalltalkEditor! ! TextMorph initialize! TextEditor class removeSelector: #autoEnclose! TextEditor class removeSelector: #autoEnclose:! TextEditor class removeSelector: #autoIndent! TextEditor class removeSelector: #autoIndent:! TextEditor class removeSelector: #encloseSelection! TextEditor class removeSelector: #encloseSelection:! TextEditor subclass: #SmalltalkEditor instanceVariableNames: 'styler' classVariableNames: 'AutoEnclose AutoIndent EncloseSelection' poolDictionaries: '' category: 'Morphic-Text Support'! TextEditor removeSelector: #crWithIndent:! TextEditor removeSelector: #tabCount! Editor subclass: #TextEditor instanceVariableNames: 'model paragraph markBlock pointBlock beginTypeInIndex emphasisHere lastParenLocation otherInterval oldInterval typeAhead history' classVariableNames: 'ChangeText FindText' poolDictionaries: '' category: 'Morphic-Text Support'! "Postscript: Reinitialize TextMorph to use TextEditor rather than SmalltalkEditor." TextMorph initialize. !