[comp.lang.smalltalk] Umlaut characters

gollman@tuvie (Georg Gollman) (07/04/89)

I was a bit disturbed to find that ST-80, V2.3 on a Macintosh, does not
support umlaut-characters. In fact, the virtual machine is rather
uncooperative by claiming the charactercodes 128 to 143 for internal use.
My solution was, to add 16 to all codes greater 127 in the KCHR resource
(in truth I just changed the umlauts), losing the top 16 codes. Once past
the virtual machine the codes are readjusted in InputState>>keyAt:put:

To faciliate the editing of fonts I wrote a few tiny methods for StrikeFont
protocol experimental.

CharacterScanner>>characterNotInFont had a (to my eyes) superfluous
conditional (both branches being identical) - so I hacked it out.

WARNING: The stuff works for me, but be careful !!!
Remember that the keyboard mapping must be changed for
InputState>>keyAt:put: to work. 
GOOD LUCK, HAVE FUN and keep the comments coming !

--------------------------------------------------------

!CharacterScanner methodsFor: 'scanning'!

characterNotInFont
	"All fonts have an illegal character to be used when a character is    
	not within the font's legal range.  When characters out of ranged   
	are encountered in scanning text, then this special character   
	indicates the appropriate behavior.  The character is usually treated 
	  as a unary message understood by a subclass of 
	CharacterScanner. "

	| illegalAsciiString saveIndex stopCondition |
	saveIndex _ lastIndex.
	illegalAsciiString _ String with: (font maxAscii + 1) asCharacter.
	stopCondition _ self
				scanCharactersFrom: 1
				to: 1
				in: illegalAsciiString
				rightX: rightMargin
				stopConditions: stopConditions
				displaying: self doesDisplaying.
	lastIndex _ saveIndex + 1.
	stopCondition ~= (stopConditions at: EndOfRun)
		ifTrue: [^self perform: stopCondition]
		ifFalse: 
			[lastIndex = runStopIndex ifTrue: [^self perform: (stopConditions at: EndOfRun)].
			^false]! !

!InputState methodsFor: 'private'!

keyAt: keyNumber put: value 
	| index mask |
	index _ keyNumber bitAnd: 255.
	"Get rid of meta bits"
	(index < BitMin or: [index > OtherMeta3])
		ifTrue: 
			["Not a potential special character"
			"GG - 3 July 1989: Hacking in german keymap"
			index > OtherMeta3 ifTrue: [index _ index - 16].
			value = 1 ifTrue: ["only look at down strokes"
				index = InterruptKey
					ifTrue: [(lshiftState ~= 0 or: [(keyNumber bitAnd: 256)
								~= 0])
							ifTrue: [self forkEmergencyEvaluatorAt: Processor userInterruptPriority]
							ifFalse: [[ScheduledControllers interruptName: 'User Interrupt'] fork]]
					ifFalse: [index = EmergencyInterruptKey
							ifTrue: [self forkEmergencyEvaluatorAt: Processor userInterruptPriority]
							ifFalse: [^keyboardQueue nextPut: (KeyboardEvent code: index meta: (metaState bitOr: (keyNumber bitShift: -8)))]]]]
		ifFalse: 
			[self setStateFor: index with: value.
			metaState _ (((((ctrlState bitOr: (lshiftState bitOr: rshiftState))
						bitOr: lockState)
						bitOr: metaKeyState)
						bitOr: otherMetaKey1State)
						bitOr: otherMetaKey2State)
						bitOr: otherMetaKey3State]! !

!StrikeFont methodsFor: 'experimental'!

edit: aCharacter 
	"GG - 30 June 1989; Edit the form of aCharacter"

	self edit: aCharacter giving: aCharacter!

edit: inCharacter giving: outCharacter 
	"GG - 30 June 1989; Edit the form of inCharacter and store it as outCharacter"

	| form |
	form _ self characterForm: inCharacter asCharacter.
	BitEditor
		openScreenViewOnForm: form
		at: Sensor cursorPoint + (form width * 2 @ (form height * 4 + 50))
		magnifiedAt: Sensor cursorPoint
		scale: 5.
	self characterFormAt: outCharacter asCharacter put: form.
	self stopConditions at: outCharacter asInteger + 1 put: nil!

maxAscii: anInteger 
	"GG - 30 June 1989; Set the new maxAscii value. 
	Adjust the xTable and the stopConditions as necessary"

	| oldSize newSize |
	oldSize _ xTable size.
	newSize _ anInteger + 3.
	anInteger > maxAscii
		ifTrue: 
			[xTable _ (Array new: newSize)
						replaceFrom: 1
						to: oldSize
						with: xTable.
			xTable atAll: (Interval from: oldSize + 1 to: newSize)
				put: (xTable at: oldSize)]
		ifFalse: [xTable _ xTable copyFrom: 1 to: newSize].
	maxAscii _ anInteger.
	"the missing character must not be missing ..."
	stopConditions at: maxAscii + 2 put: nil! !