Word advance/back in ParagraphEditor

Mark Guzdial guzdial at cc.gatech.edu
Wed Sep 16 19:20:22 UTC 1998


With fun new things in Squeak 2.2Beta, I've started to move more of my
day-to-day computing into Squeak.  I use word-forward and word-backward
keys in Eudora and BBedit alot (option-right and option-left), and I've
wanted that in Squeak.

The below code replaces cmd-Shift-A with wordAdvance (instead of
argAdvance, but actually results in the same thing on code segments), and
cmd-shift-Q (which no longer does command-completion) with wordBack.
You'll need to reinitialize the ParagraphEditor to get the new keys to be
recognized.

Mark

'From Squeak 2.2beta of Sept 16, 1998 on 16 September 1998 at 2:42:06 pm'!

!ParagraphEditor class methodsFor: 'keyboard shortcut tables' stamp: 'mjg
9/16/1998 14:41'!
initializeShiftCmdKeyShortcuts
	"Initialize the shift-command-key (or control-key) shortcut table."
	"NOTE: if you don't know what your keyboard generates, use Sensor
kbdTest"

	| cmdMap cmds |
	"shift-command and control shortcuts"
	cmdMap _ Array new: 256.  "use temp in case of a crash"
	cmdMap atAllPut: #noop:.
	cmdMap at: ( 1 + 1) put: #cursorHome:.			"home key"
	cmdMap at: ( 4 + 1) put: #cursorEnd:.			"end key"
	cmdMap at: ( 8 + 1) put: #forwardDelete:.
	"ctrl-H or delete key"
	cmdMap at: (13 + 1) put: #crWithIndent:.
	"ctrl-Return"
	cmdMap at: (27 + 1) put: #selectCurrentTypeIn:.	"escape key"
	cmdMap at: (28 + 1) put: #cursorLeft:.			"left arrow
key"
	cmdMap at: (29 + 1) put: #cursorRight:.			"right
arrow key"
	cmdMap at: (30 + 1) put: #cursorUp:.				"up
arrow key"
	cmdMap at: (31 + 1) put: #cursorDown:.			"down arrow
key"
	cmdMap at: (45 + 1) put: #changeEmphasis:.		"cmd-sh-minus"
	cmdMap at: (61 + 1) put: #changeEmphasis:.		"cmd-sh-plus"
	cmdMap at: (127 + 1) put: #forwardDelete:.		"del key"

	"Note: Command key overrides shift key, so, for example,
cmd-shift-9 produces $9 not $("
	'9[,''' do: [ :char | cmdMap at: (char asciiValue + 1) put:
#shiftEnclose: ].	"({< and double-quote"
	"Note: Must use cmd-9 or ctrl-9 to get '()' since cmd-shift-9 is a
Mac FKey command."
	cmdMap at: (27 + 1) put: #shiftEnclose:.	"ctrl-["

	cmds _ #(
		$a	wordAdvance:
		$b	browseItHere:
		$c	compareToClipboard:
		$d	duplicate:
		$e	methodStringsContainingIt:
		$f	displayIfFalse:
		$j	doAgainMany:
		$k	changeStyle:
		$n	referencesToIt:
		$p	prettyPrint:
		$q	wordBack:
		$r	indent:
		$l	outdent:
		$s	search:
		$t	displayIfTrue:
		$u	changeLfToCr:
		$v	pasteInitials:
		$w	methodNamesContainingIt:
		$x	makeLowercase:
		$y	makeUppercase:
		$z	makeCapitalized:
	).
	1 to: cmds size by: 2 do: [ :i |
		cmdMap at: ((cmds at: i) asciiValue + 1)
	put: (cmds at: i + 1).
		cmdMap at: (((cmds at: i) asciiValue - 96) + 1)	put: (cmds
at: i + 1).
	].
	ShiftCmdActions _ cmdMap.! !


'From Squeak 2.2beta of Sept 16, 1998 on 16 September 1998 at 2:42:16 pm'!

!ParagraphEditor methodsFor: 'typing/selecting keys' stamp: 'mjg 9/16/1998
14:19'!
wordAdvance: characterStream
	"Invoked by Command-shift-A.
	 Search forward from the end of the selection for a space.
	  Place the caret after the space.  If none are found, place the
		caret at the end of the text.  Does not affect the
undoability of the
	 	previous command."

	| start |
	sensor keyboard.		"flush character"
	self closeTypeIn: characterStream.
	start _ paragraph text findString: ' ' startingAt: stopBlock
stringIndex.
	start = 0 ifTrue: [start _ paragraph text size + 1].
	self selectAt: start + 1.
	^true! !

'From Squeak 2.2beta of Sept 16, 1998 on 16 September 1998 at 2:42:11 pm'!

!ParagraphEditor methodsFor: 'typing/selecting keys' stamp: 'mjg 9/16/1998
14:41'!
wordBack: characterStream
	"Move the cursor to the word before the caret."

	| startIndex |
	sensor keyboard.
	characterStream isEmpty
		ifTrue:
			[startBlock = stopBlock
				ifTrue: "a caret, delete at least one
character"
					[startIndex _ 1 max: startBlock
stringIndex - 1.
					[startIndex > 1 and:
						[(paragraph text at:
startIndex - 1) asCharacter tokenish]]
						whileTrue:
							[startIndex _
startIndex - 1]]
				ifFalse: "a non-caret, just delete it"
					[startIndex _ startBlock stringIndex].
			self selectAt: startIndex]
		ifFalse:
			[self selectAt: 0].
	^true! !

--------------------------
Mark Guzdial : Georgia Tech : College of Computing : Atlanta, GA 30332-0280
(404) 894-5618 : Fax (404) 894-0673 : guzdial at cc.gatech.edu
http://www.cc.gatech.edu/gvu/people/Faculty/Mark.Guzdial.html





More information about the Squeak-dev mailing list