More TextAttribute

Gerardo Richarte core.lists.squeak at core-sdi.com
Fri May 12 00:42:25 UTC 2000


Hi!
    Here we go once again a year latter! (-:
    Here is a changeSet that implements a new TextAttribute (those
accessible with
Cmd-6).
    TextGrabIt gives text the ability to evaluate Smalltalk expressions
and attach the
resulting Morph(*) to World's first hand(**).

    (*) it actually attaches the result of sending #asMorph to the
result, this integrates it
    nicely with some non-morphic objects (all objects if you have
MorphicWrappers)

    (**) I actually started using 'World activeHand', but somewhere in
time activeHand
    behavior changed to return nil almost every time, so I changed to
'World hands first'

    This changeSet also adds another option in Cmd-6 menu: print it, but
it's not ready
yet. The changes needed to implement a TextPrintIt are somehow 'big',
'cos it needs
to know the Controller where to insert Text (or something like that, I'm
not sure).
However I'll do it soon.

    Grabbing Bye!
    Richie++

PS: I'm sending two changes: MoreTextAttributes.2.cs and
TextGrabItComment.2.cs, I needed to do this becouse GrabIt comment has
'Grab Its' in it, and you need to have
everything filed in so this works. My first atempt was to only have one
changeset
manually arranged so it works... but it didn't work
-------------- next part --------------
'From Squeak2.7 of 5 January 2000 [latest update: #1782] on 9 May 2000 at 2:41:12 pm'!
TextDoIt subclass: #TextGrabIt
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Collections-Text'!

!ParagraphEditor methodsFor: 'editing keys' stamp: 'r++ 5/9/2000 09:47'!
changeEmphasis: characterStream 
	"Change the emphasis of the current selection or prepare to accept characters with the change in emphasis. Emphasis change amounts to a font change.  Keeps typeahead."
	| keyCode attribute oldAttributes index thisSel colors |		 "control 0..9 -> 0..9"
	keyCode _ ('0123456789-=' indexOf: sensor keyboard ifAbsent: [1]) - 1.
	oldAttributes _ paragraph text attributesAt: startBlock stringIndex forStyle: paragraph textStyle.
	thisSel _ self selection.

	"Decipher keyCodes for Command 0-9..."
	(keyCode between: 1 and: 5) ifTrue:
		[attribute _ TextFontChange fontNumber: keyCode].
	keyCode = 6 ifTrue:
		[colors _ #(black magenta red yellow green blue cyan white).
		index _ (PopUpMenu labelArray: colors , #('Do it' 'Print it' 'Grab it' 'Link to comment of class' 'Link to definition of class' 'Link to hierarchy of class' 'Link to method' 'URL' 'Copy hidden info')
							lines: (Array with: colors size)) startUp.
		index = 0 ifTrue: [^ true].
		index <= colors size
		ifTrue:
			[attribute _ TextColor color: (Color perform: (colors at: index))]
		ifFalse:
			[index _ index - colors size.
			index = 1 ifTrue: [attribute _ TextDoIt new.
				thisSel _ attribute analyze: self selection asString].
"			index = 2 ifTrue: [attribute _ TextDoIt new.
				thisSel _ attribute analyze: self selection asString].
"			index = 3 ifTrue: [attribute _ TextGrabIt new.
				thisSel _ attribute analyze: self selection asString].
			index = 4 ifTrue: [attribute _ TextLink new. 
				thisSel _ attribute analyze: self selection asString with: 'Comment'].
			index = 5 ifTrue: [attribute _ TextLink new. 
				thisSel _ attribute analyze: self selection asString with: 'Definition'].
			index = 6 ifTrue: [attribute _ TextLink new. 
				thisSel _ attribute analyze: self selection asString with: 'Hierarchy'].
			index = 7 ifTrue: [attribute _ TextLink new. 
				thisSel _ attribute analyze: self selection asString].
			index = 8 ifTrue: [attribute _ TextURL new. 
				thisSel _ attribute analyze: self selection asString].
			index = 9 ifTrue: ["Copy hidden info"
				self copyHiddenInfo.  ^ true].	"no other action"
		thisSel ifNil: [^ true]].	"Could not figure out what to link to"
		].
	(keyCode between: 7 and: 11) ifTrue:
		[sensor leftShiftDown
		ifTrue:
			[keyCode = 10 ifTrue: [attribute _ TextKern kern: -1].
			keyCode = 11 ifTrue: [attribute _ TextKern kern: 1]]
		ifFalse:
			[attribute _ TextEmphasis perform:
					(#(bold italic narrow underlined struckOut) at: keyCode - 6).
			oldAttributes do:
				[:att | (att dominates: attribute) ifTrue: [attribute turnOff]]]].
	(keyCode = 0) ifTrue:
		[attribute _ TextEmphasis normal].

	beginTypeInBlock ~~ nil
		ifTrue:  "only change emphasisHere while typing"
			[self insertTypeAhead: characterStream.
			emphasisHere _ Text addAttribute: attribute toArray: oldAttributes.
			^ true].
	self replaceSelectionWith: (thisSel asText addAttribute: attribute).
	^ true! !


!RunArray class methodsFor: 'instance creation' stamp: 'r++ 5/9/2000 10:07'!
scanFrom: strm
	"Read the style section of a fileOut or sources file.  nextChunk has already been done.  We need to return a RunArray of TextAttributes of various kinds."
	| rr vv aa this |
	(strm peekFor: $( ) ifFalse: [^ nil].
	rr _ OrderedCollection new.
	[strm skipSeparators.
	 strm peekFor: $)] whileFalse: 
		[rr add: (Number readFrom: strm)].
	vv _ OrderedCollection new.	"Value array"
	aa _ OrderedCollection new.	"Attributes list"
	[(this _ strm next) == nil] whileFalse: [
		this == $, ifTrue: [vv add: aa asArray.  aa _ OrderedCollection new].
		this == $f ifTrue: [aa add: 
			(TextFontChange new fontNumber: (Number readFrom: strm))].
		this == $b ifTrue: [aa add: (TextEmphasis bold)].
		this == $i ifTrue: [aa add: (TextEmphasis italic)].
		this == $u ifTrue: [aa add: (TextEmphasis underlined)].
		this == $= ifTrue: [aa add: (TextEmphasis struckOut)].
		this == $n ifTrue: [aa add: (TextEmphasis normal)].
		this == $- ifTrue: [aa add: (TextKern kern: -1)].
		this == $+ ifTrue: [aa add: (TextKern kern: 1)].
		this == $c ifTrue: [aa add: (TextColor scanFrom: strm)]. "color"
		this == $L ifTrue: [aa add: (TextLink scanFrom: strm)].	"L not look like 1"
		this == $R ifTrue: [aa add: (TextURL scanFrom: strm)].
				"R capitalized so it can follow a number"
		this == $q ifTrue: [aa add: (TextSqkPageLink scanFrom: strm)].
		this == $d ifTrue: [aa add: (TextDoIt scanFrom: strm)].
		this == $g ifTrue: [aa add: (TextGrabIt scanFrom: strm)].
		"space, cr do nothing"
		].
	aa size > 0 ifTrue: [vv add: aa asArray].
	^ self runs: rr asArray values: vv asArray
"
RunArray scanFrom: (ReadStream on: '(14 50 312)f1,f1b,f1LInteger +;i')
"! !

!TextGrabIt methodsFor: 'as yet unclassified' stamp: 'r++ 5/9/2000 10:13'!
actOnClickFor: anObject
	"Note: evalString gets evaluated IN THE CONTEXT OF anObject
	 -- meaning that self and all instVars are accessible"
	| answer |
	answer _ Compiler evaluate: evalString for: anObject logged: false.
	World ifNotNil: [World hands first attachMorph: answer asMorph].
	^ true ! !

!TextGrabIt methodsFor: 'as yet unclassified' stamp: 'r++ 5/9/2000 09:47'!
writeScanOn: strm

	strm nextPut: $g; nextPutAll: evalString; nextPutAll: ';;'! !


-------------- next part --------------
'From Squeak2.7 of 5 January 2000 [latest update: #1782] on 9 May 2000 at 2:49:51 pm'!

!TextGrabIt commentStamp: 'r++ 5/9/2000 14:49' prior: 0!
This is a TextAttribute that allows you to place an active text, that when clicked will create a Morph, resulting from evaluating an expresion you specify, and attach it to the World's active hand. (It's only useful in a Morphic enviroment)

Some working examples:

	BouncingAtomsMorph new
	Want to play Tetris?

Some examples with MorphicWrappers (couldn't resist!!):

	2+5
	TextGrabIt class
	A class teller

To see what's being done in each of this examples, select the text (try not to click on it) and from Cmd-6 select 'copy hidden info', then paste it somewhere to see it (for example try it on the last example, even if you don't have MorphicWrappers installed.

To create a new TextGrabIt select the text you want to activate, press Cmd-6 and choose 'Grab it'.
For example do it on this text:

	EllipseMorph new

And you can also specify a Smalltalk statement different than the visible text, for example select and make Grab it on:

	<EllipseMorph new color: Color blue; yourself>Click me to create a blue ellipse

!
]style[(267 22 2 20 59 3 2 10 8 14 616)f1,f1gBouncingAtomsMorph new;;,f1,f1gTetris new;;,f1,f1g2+5;;,f1,f1gTextGrabIt;;,f1,f1g(RequestBoxMorph request: 'drop anything in me,
I''ll tell you it''s class!!!!!!!!') class;;,f1!



More information about the Squeak-dev mailing list