[squeak-dev] The Inbox: Graphics-mt.528.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Jul 14 14:12:57 UTC 2022


A new version of Graphics was added to project The Inbox:
http://source.squeak.org/inbox/Graphics-mt.528.mcz

==================== Summary ====================

Name: Graphics-mt.528
Author: mt
Time: 8 July 2022, 1:44:04.359615 pm
UUID: 35713805-bd5f-c745-9b83-a8d102feb209
Ancestors: Graphics-kfr.527

Avoid deprecation warning when trying to parse binary content into a Form via #fromFileNamed: or #fromBinaryStream:.

=============== Diff against Graphics-kfr.527 ===============

Item was removed:
- SystemOrganization addCategory: #'Graphics-Display Objects'!
- SystemOrganization addCategory: #'Graphics-External-Ffenestri'!
- SystemOrganization addCategory: #'Graphics-Files'!
- SystemOrganization addCategory: #'Graphics-Fonts'!
- SystemOrganization addCategory: #'Graphics-Primitives'!
- SystemOrganization addCategory: #'Graphics-Text'!
- SystemOrganization addCategory: #'Graphics-Transformations'!

Item was removed:
- Object subclass: #AbstractFont
- 	instanceVariableNames: ''
- 	classVariableNames: 'ForceNonSubPixelCount'
- 	poolDictionaries: ''
- 	category: 'Graphics-Fonts'!
- 
- !AbstractFont commentStamp: '<historical>' prior: 0!
- AbstractFont defines the generic interface that all fonts need to implement.!

Item was removed:
- ----- Method: AbstractFont class>>emphasisStringFor: (in category 'utilities') -----
- emphasisStringFor: emphasisCode
- 	"Answer a translated string that represents the attributes given in emphasisCode."
- 
- 	| emphases |
- 	emphasisCode = 0 ifTrue: [ ^'Normal' translated ].
- 
- 	emphases := #('Bold' 'Italic' 'Underlined' 'Narrow' 'StruckOut').
- 
- 	^String streamContents: [ :s |
- 		1 to: emphases size do: [ :i |
- 			(emphasisCode bitAt: i) isZero ifFalse: [ s nextPutAll: (emphases at: i) translated; space ] ].
- 		s position isZero ifFalse: [ s skip: -1 ] ]!

Item was removed:
- ----- Method: AbstractFont class>>forceNonSubPixelCount (in category 'utilities') -----
- forceNonSubPixelCount
- 	"Answer the force non-subpixel count"
- 	^ForceNonSubPixelCount ifNil:[ForceNonSubPixelCount := 0]!

Item was removed:
- ----- Method: AbstractFont class>>forceNonSubPixelDuring: (in category 'utilities') -----
- forceNonSubPixelDuring: aBlock
- 	"Forces all font rendering to suppress subpixel anti-aliasing during the execution of aBlock"
- 	ForceNonSubPixelCount ifNil:[ForceNonSubPixelCount := 0].
- 	ForceNonSubPixelCount := ForceNonSubPixelCount + 1.
- 	aBlock ensure:[ForceNonSubPixelCount := ForceNonSubPixelCount - 1]!

Item was removed:
- ----- Method: AbstractFont>>approxWidthOfText: (in category 'measuring') -----
- approxWidthOfText: aText
- "Return the width of aText -- quickly, and a little bit dirty. Used by lists morphs containing Text objects to get a quick, fairly accurate measure of the width of a list item."
- 
-     | w |
-     
-     (aText isNil or: [aText size = 0 ])
-         ifTrue:[^0].
-        
-     w := self
-         widthOfString: aText asString.
- 
-      "If the text has no emphasis, just return the string size.  If it is empasized, 
-     just approximate the width by adding about 20% to the width"   
-     (((aText runLengthFor: 1) = aText size)
-         and: [(aText emphasisAt: 1) = 0 ])
-             ifTrue:[^w]
-             ifFalse:[ ^w * 6 // 5 ]. !

Item was removed:
- ----- Method: AbstractFont>>asNewTextStyle (in category 'converting') -----
- asNewTextStyle
- 	"Answer a new text style where the receiver is the default font. Try to lookup the an existing #textStyle so that TextFontChange can be used in views."
- 	
- 	| newTextStyle |
- 	newTextStyle := self textStyleOrNil
- 		ifNil: [TextStyle fontArray: {self}]
- 		ifNotNil: [:style | style copy].
- 	newTextStyle defaultFontIndex: (newTextStyle fontIndexOfPointSize: self pointSize).	
- 	^ newTextStyle!

Item was removed:
- ----- Method: AbstractFont>>asPointSize: (in category 'converting') -----
- asPointSize: differentPointSize
- 	"Convert the receiver into a different point size. Compared to #pointSize:, this operation does not modify the receiver but tries to lookup another font object or create one on-the-fly."
- 
- 	self pointSize = differentPointSize ifTrue: [^ self].
- 
- 	^ self class
- 		familyName: self familyName
- 		pointSize: differentPointSize
- 		emphasized: self emphasis!

Item was removed:
- ----- Method: AbstractFont>>asRegular (in category 'converting') -----
- asRegular
- 	"Try to lookup the receiver with normal emphasis. If the receiver itself looks bold face, this might be okay. Rely on what is registered on the font family's text style. Not that this is different from #emphasized: with 0, which does nothing."
- 	
- 	self emphasis = 0 ifTrue: [^ self].
- 	^ self textStyleOrNil
- 		ifNil: [self]
- 		ifNotNil: [:style | style fontOfPointSize: self pointSize]!

Item was removed:
- ----- Method: AbstractFont>>ascent (in category 'accessing') -----
- ascent
- 
- 	self subclassResponsibility.
- !

Item was removed:
- ----- Method: AbstractFont>>ascentOf: (in category 'accessing') -----
- ascentOf: aCharacter
- 
- 	^ self ascent.
- !

Item was removed:
- ----- Method: AbstractFont>>baseKern (in category 'accessing') -----
- baseKern
- 	^0!

Item was removed:
- ----- Method: AbstractFont>>basicAscentOf: (in category 'accessing') -----
- basicAscentOf: aCharacter
- 
- 	^ self ascent.
- !

Item was removed:
- ----- Method: AbstractFont>>basicDescentOf: (in category 'accessing') -----
- basicDescentOf: aCharacter
- 
- 	^ self descent.
- !

Item was removed:
- ----- Method: AbstractFont>>basicHasGlyphOf: (in category 'testing') -----
- basicHasGlyphOf: aCharacter
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: AbstractFont>>characterFormAt: (in category 'character shapes') -----
- characterFormAt: aCharacter
- 
- 	self subclassResponsibility.!

Item was removed:
- ----- Method: AbstractFont>>characterToGlyphMap (in category 'accessing') -----
- characterToGlyphMap
- 	"Return the character to glyph mapping table. If the table is not provided the character scanner will query the font directly for the width of each individual character."
- 	^nil!

Item was removed:
- ----- Method: AbstractFont>>depth (in category 'accessing') -----
- depth
- 	"Returns the glyphs' color depth."
- 	
- 	self subclassResponsibility.!

Item was removed:
- ----- Method: AbstractFont>>derivativeFonts (in category 'accessing') -----
- derivativeFonts
- 	^#()!

Item was removed:
- ----- Method: AbstractFont>>descent (in category 'accessing') -----
- descent
- 
- 	self subclassResponsibility.
- !

Item was removed:
- ----- Method: AbstractFont>>descentOf: (in category 'accessing') -----
- descentOf: aCharacter
- 
- 	^ self descent.
- !

Item was removed:
- ----- Method: AbstractFont>>displayStrikeoutOn:from:to: (in category 'displaying') -----
- displayStrikeoutOn: aDisplayContext from: baselineStartPoint to: baselineEndPoint
- 	"display the strikeout if appropriate for the receiver"!

Item was removed:
- ----- Method: AbstractFont>>displayString:on:from:to:at:kern: (in category 'displaying') -----
- displayString: aString on: aDisplayContext from: startIndex to: stopIndex at: aPoint kern: kernDelta
- 	"Draw the given string from startIndex to stopIndex 
- 	at aPoint on the (already prepared) display context."
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: AbstractFont>>displayString:on:from:to:at:kern:baselineY: (in category 'displaying') -----
- displayString: aString on: aDisplayContext from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY
- 	"Draw the given string from startIndex to stopIndex 
- 	at aPoint on the (already prepared) display context."
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: AbstractFont>>displayString:on:from:to:at:kern:from:baselineY: (in category 'displaying') -----
- displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta from: fromFont baselineY: baselineY
- 	"I am used as a fallback for fromFont. I should install myself on aBitBlt. The default implementation does not do that but directly uses my usual displaying method."
- 	
- 	self flag: #subclassResponsibility. "mt: Something like #installStrikeFont: or #installTTCFont:."
- 	^ self displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY!

Item was removed:
- ----- Method: AbstractFont>>displayUnderlineOn:from:to: (in category 'displaying') -----
- displayUnderlineOn: aDisplayContext from: baselineStartPoint to: baselineEndPoint
- 	"display the underline if appropriate for the receiver"!

Item was removed:
- ----- Method: AbstractFont>>emphasis (in category 'accessing') -----
- emphasis
- 
- 	^ 0!

Item was removed:
- ----- Method: AbstractFont>>emphasisString (in category 'accessing') -----
- emphasisString
- 	"Answer a translated string that represents the receiver's emphasis."
- 	
- 	^self emphasisStringFor: self emphasis!

Item was removed:
- ----- Method: AbstractFont>>emphasisStringFor: (in category 'accessing') -----
- emphasisStringFor: emphasisCode
- 	"Answer a translated string that represents the attributes given in emphasisCode."
- 	
- 	^self class emphasisStringFor: emphasisCode!

Item was removed:
- ----- Method: AbstractFont>>fallbackFont (in category 'accessing') -----
- fallbackFont
- 	"Answers the fallbackFont for the receiver. Try to use the #defaultFallback but for itself use a synthetic font that maps all characters to question marks."
- 
- 	^ TextStyle defaultFallback textStyleName = self textStyleName
- 		ifTrue: [
- 			FixedFaceFont new errorFont baseFont: self]
- 		ifFalse: [
- 			(TextStyle defaultFallbackFont
- 				emphasized: self emphasis)
- 				asPointSize: self pointSize]!

Item was removed:
- ----- Method: AbstractFont>>fallbackFont: (in category 'initialize-release') -----
- fallbackFont: aFont
- 	"Reset fallback font. Ignore. See #fallbackFont."!

Item was removed:
- ----- Method: AbstractFont>>fallbackTextStyle: (in category 'initialize-release') -----
- fallbackTextStyle: aTextStyle
- 
- "	| fonts f |
- 	fonts := aTextStyle fontArray.
- 	f := fonts first.
- 	f familyName = self familyName ifTrue: [^ self].
- 	1 to: fonts size do: [:i |
- 		self height > (fonts at: i) height ifTrue: [f := fonts at: i].
- 	]."
- 
- 	| fontsToUpdate |
- 	fontsToUpdate := self textStyleOrNil
- 		ifNil: [{self} "not-yet-installed"]
- 		ifNotNil: [:style | style fontArray "all point sizes"].
- 	
- 	fontsToUpdate do: [:font |  "All subfamilies / emphases"
- 		font privateFallbackTextStyle: aTextStyle.
- 		font derivativeFonts do: [:f | f privateFallbackTextStyle: aTextStyle ]].!

Item was removed:
- ----- Method: AbstractFont>>familyName (in category 'accessing') -----
- familyName
- 	"Answer the name to be used as a key in the TextConstants dictionary."
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: AbstractFont>>foregroundColor (in category 'displaying') -----
- foregroundColor
- 	
- 	^ Color black!

Item was removed:
- ----- Method: AbstractFont>>foregroundColor: (in category 'displaying') -----
- foregroundColor: fgColor
- 	"Install the given foreground color. This does nothing for other than TrueType fonts. In StrikeFonts, color installation is bound to BitBlt."!

Item was removed:
- ----- Method: AbstractFont>>formOf: (in category 'character shapes') -----
- formOf: aCharacter
- 
- 	self subclassResponsibility.!

Item was removed:
- ----- Method: AbstractFont>>hasDistinctGlyphsForAll: (in category 'testing') -----
- hasDistinctGlyphsForAll: asciiString
- 	"Answer true if the receiver has glyphs for all the characters
- 	in asciiString and no single glyph is shared by more than one character, false otherwise.
- 	The default behaviour is to answer true, but subclasses may reimplement"
- 	
- 	^true!

Item was removed:
- ----- Method: AbstractFont>>hasFixedWidth (in category 'testing') -----
- hasFixedWidth
- 	"Answer whether the receiver is a monospaced/fixed-width/non-proportional font. See TextStyle class >> #defaultFixed."
- 
- 	^ (self widthOf: $.) = (self widthOf: $w)!

Item was removed:
- ----- Method: AbstractFont>>hasGlyphOf: (in category 'testing') -----
- hasGlyphOf: aCharacter
- 
- 	^ self basicHasGlyphOf: aCharacter!

Item was removed:
- ----- Method: AbstractFont>>hasGlyphsForAll: (in category 'testing') -----
- hasGlyphsForAll: asciiString
- 	"Answer true if the receiver has glyphs for all the characters
- 	in asciiString, false otherwise.
- 	The default behaviour is to answer true, but subclasses may reimplement"
- 	
- 	^true!

Item was removed:
- ----- Method: AbstractFont>>height (in category 'accessing') -----
- height
- 	"Answer the height of the receiver, total of maximum extents of 
- 	characters above and below the baseline."
- 
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: AbstractFont>>installOn:foregroundColor:backgroundColor: (in category 'displaying') -----
- installOn: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor
- 	"Install the receiver on the given DisplayContext (either BitBlt or Canvas) for further drawing operations."
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: AbstractFont>>isFontSet (in category 'testing') -----
- isFontSet
- 
- 	^ false.
- !

Item was removed:
- ----- Method: AbstractFont>>isPairKerningCapable (in category 'testing') -----
- isPairKerningCapable
- "a hopefully temporary test method; better factoring of scan/measure/display should remove the need for it.
- Only FreeType fonts would currently add this to return true"
- 	^false!

Item was removed:
- ----- Method: AbstractFont>>isRegular (in category 'testing') -----
- isRegular
- 	^false!

Item was removed:
- ----- Method: AbstractFont>>isSubPixelPositioned (in category 'testing') -----
- isSubPixelPositioned
- 	"Answer true if the receiver is currently using subpixel positioned
- 	glyphs, false otherwise. This affects how padded space sizes are calculated
- 	when composing text. 
- 	Currently, only FreeTypeFonts are subPixelPositioned, and only when not
- 	Hinted"
- 	
- 	^false !

Item was removed:
- ----- Method: AbstractFont>>isSymbolFont (in category 'testing') -----
- isSymbolFont
- 	"Answer true if the receiver is a Symbol font, false otherwise.
- 	The default is to answer false, subclasses can reimplement"
- 	
- 	^false!

Item was removed:
- ----- Method: AbstractFont>>isSynthetic (in category 'testing') -----
- isSynthetic
- 	^ false!

Item was removed:
- ----- Method: AbstractFont>>isTTCFont (in category 'testing') -----
- isTTCFont
- 	^false!

Item was removed:
- ----- Method: AbstractFont>>kerningLeft:right: (in category 'kerning') -----
- kerningLeft: leftChar right: rightChar
- 	^0!

Item was removed:
- ----- Method: AbstractFont>>larger (in category 'converting') -----
- larger
- 	"Answer a font that is about 20% larger than the receiver but has the same font family and emphasis. Round to 0.5 points to not yield so many different font instances."
- 	
- 	^ self asPointSize: ((self pointSize asFloat * 1.2) roundTo: 0.5)!

Item was removed:
- ----- Method: AbstractFont>>lineGap (in category 'accessing') -----
- lineGap
- 
- 	^ 2 "pre-rendered legacy fonts"!

Item was removed:
- ----- Method: AbstractFont>>lineGapSlice (in category 'accessing') -----
- lineGapSlice
- 
- 	^ 1 "pre-rendered legacy fonts"!

Item was removed:
- ----- Method: AbstractFont>>lineGrid (in category 'accessing') -----
- lineGrid
- 	"Answer the relative space between lines"
- 
- 	^ self height + self lineGap!

Item was removed:
- ----- Method: AbstractFont>>linearWidthOf: (in category 'measuring') -----
- linearWidthOf: aCharacter
- 	"This is the scaled, unrounded advance width."
- 	^self widthOf: aCharacter!

Item was removed:
- ----- Method: AbstractFont>>maxAscii (in category 'accessing') -----
- maxAscii
- 
- 	self flag: #deprecated.
- 	^ self maxCodePoint!

Item was removed:
- ----- Method: AbstractFont>>maxCodePoint (in category 'accessing') -----
- maxCodePoint
- 	"Answer the largest code point that the receiver can translate into glyphs. Use the range from #minCodePoint to #maxCodePoint to configure a list of #fallbackFont's. Note that subclasses may insert 'holes' via #hasGlyphOf: test such as StrikeFont's internal xTable."
- 	
- 	^ 16r10FFFF "Unicode uses 21-bit but 16r110000 to 16r1FFFFF are not valid code points. See https://www.unicode.org/versions/stats/."!

Item was removed:
- ----- Method: AbstractFont>>minAscii (in category 'accessing') -----
- minAscii
- 
- 	self flag: #deprecated.
- 	^ self minCodePoint!

Item was removed:
- ----- Method: AbstractFont>>minCodePoint (in category 'accessing') -----
- minCodePoint
- 	"Answer the smallest code point that the receiver can translate into glyphs. Use the range from #minCodePoint to #maxCodePoint to configure a list of #fallbackFont's. Note that subclasses may insert 'holes' via #hasGlyphOf: test such as StrikeFont's internal xTable."
- 	
- 	^ 0!

Item was removed:
- ----- Method: AbstractFont>>pixelSize (in category 'accessing') -----
- pixelSize
- 	"Make sure that we don't return a Fraction"
- 	^ (TextStyle pointsToPixels: self pointSize) rounded!

Item was removed:
- ----- Method: AbstractFont>>pixelsPerInch (in category 'accessing') -----
- pixelsPerInch
- 	"Answers the PPI reference for the pre-rendered receiver."
- 	
- 	^ (self height * 72 / self pointSize asFloat) rounded!

Item was removed:
- ----- Method: AbstractFont>>pixelsPerInchChanged (in category 'notifications') -----
- pixelsPerInchChanged
- 	"The definition of TextStyle class>>pixelsPerInch has changed. Do whatever is necessary."!

Item was removed:
- ----- Method: AbstractFont>>pointSize (in category 'accessing') -----
- pointSize
- 	self subclassResponsibility.!

Item was removed:
- ----- Method: AbstractFont>>printShortDescriptionOn: (in category 'printing') -----
- printShortDescriptionOn: aStream
- 	aStream nextPutAll: self familyName!

Item was removed:
- ----- Method: AbstractFont>>privateFallbackTextStyle: (in category 'initialize-release') -----
- privateFallbackTextStyle: aTextStyleOrNil
- 
- 	self fallbackFont: nil. "Rely on lazy initialization of #fallbackFont."!

Item was removed:
- ----- Method: AbstractFont>>releaseCachedState (in category 'caching') -----
- releaseCachedState
- 	!

Item was removed:
- ----- Method: AbstractFont>>reset (in category 'initialize-release') -----
- reset
- 	"Clear all caches."!

Item was removed:
- ----- Method: AbstractFont>>sampleText (in category 'example') -----
- sampleText
- 
- 	| text |
- 	text := self isSymbolFont
- 		ifTrue: [self symbolSample asText]
- 		ifFalse: [Text textSample].
- 	text addAttribute: (TextFontReference toFont: self).
- 	^ text!

Item was removed:
- ----- Method: AbstractFont>>scanByteCharactersFrom:to:in:with:rightX: (in category 'character scanning') -----
- scanByteCharactersFrom: startIndex to: stopIndex in: aByteString with: aCharacterScanner rightX: rightX
- 	"scan a single byte character string"
- 	^aCharacterScanner scanByteCharactersFrom: startIndex to: stopIndex in: aByteString rightX: rightX!

Item was removed:
- ----- Method: AbstractFont>>scanMultibyteCharactersFrom:to:in:with:rightX: (in category 'character scanning') -----
- scanMultibyteCharactersFrom: startIndex to: stopIndex in: aWideString with: aCharacterScanner rightX: rightX
- 	"scan a multibyte character string"
- 	^aCharacterScanner scanMultibyteCharactersFrom: startIndex to: stopIndex in: aWideString rightX: rightX !

Item was removed:
- ----- Method: AbstractFont>>scanMultibyteJapaneseCharactersFrom:to:in:with:rightX: (in category 'character scanning') -----
- scanMultibyteJapaneseCharactersFrom: startIndex to: stopIndex in: aWideString with: aCharacterScanner rightX: rightX
- 	"scan a multibyte Japanese character string"
- 	^aCharacterScanner scanJapaneseCharactersFrom: startIndex to: stopIndex in: aWideString rightX: rightX 
- !

Item was removed:
- ----- Method: AbstractFont>>smaller (in category 'converting') -----
- smaller
- 	"Answer a font that is about 20% smaller than the receiver but has the same font family and emphasis. Round to 0.5 points to not yield so many different font instances."
- 
- 	^ self asPointSize: ((self pointSize asFloat * 0.8) roundTo: 0.5)!

Item was removed:
- ----- Method: AbstractFont>>subfamilyName (in category 'accessing') -----
- subfamilyName
- 
- 	^ self emphasisString!

Item was removed:
- ----- Method: AbstractFont>>symbolSample (in category 'example') -----
- symbolSample
- 	"Variation of Text class >> #symbolSample, which uses the receiver's available code points. This is important for fonts such as Wingdings."
- 	
- 	^ String streamContents: [:stream | | start lineLength character |
- 		lineLength := 0.
- 		(start := self minCodePoint max: 33) to: (self maxCodePoint min: start + 200) do: [:codePoint |
- 			(self hasGlyphOf: (character := Character value: codePoint))
- 				ifTrue: [stream nextPut: character.
- 					((lineLength := lineLength + 1) > 30) ifTrue: [
- 						lineLength := 0.
- 						stream cr]]]]!

Item was removed:
- ----- Method: AbstractFont>>textStyle (in category 'accessing') -----
- textStyle
- 	"Answer an instance of TextStyle that (most likely) includes the receiver. Note that if the receiver is used in more than one style, only answer the most prominent one."
- 
- 	^ self textStyleOrNil ifNil: [TextStyle fontArray: {self}]!

Item was removed:
- ----- Method: AbstractFont>>textStyleName (in category 'accessing') -----
- textStyleName
- 	"Answer the name to be used as a key in the TextConstants dictionary."
- 	^self familyName!

Item was removed:
- ----- Method: AbstractFont>>textStyleOrNil (in category 'accessing') -----
- textStyleOrNil
- 	"Like #textStyle but avoid creating a new style for orphaned fonts."
- 
- 	^ TextStyle named: self textStyleName!

Item was removed:
- ----- Method: AbstractFont>>widthAndKernedWidthOfLeft:right:into: (in category 'kerning') -----
- widthAndKernedWidthOfLeft: leftCharacter right: rightCharacterOrNil into: aTwoElementArray
- 	"Set the first element of aTwoElementArray to the width of leftCharacter and 
- 	the second element to the width of left character when kerned with
- 	rightCharacterOrNil. Answer aTwoElementArray"
- 	"Actually, nearly all users of this actually want just the widthOf the leftCharacter, so we will default to that for speed. See other implementations for more complex cases"
- 
- 	| w |
- 	w := self widthOf: leftCharacter.
- 	aTwoElementArray at: 1 put: w.
- 	aTwoElementArray at: 2 put: w
- 
- "	The old code, and what fonts which have pair-kerning would use - 
- 	w := self widthOf: leftCharacter.
- 	rightCharacterOrNil isNil
- 		ifTrue:[
- 			aTwoElementArray 
- 				at: 1 put: w; 
- 				at: 2 put: w]
- 		ifFalse:[
- 			k := self kerningLeft: leftCharacter right: rightCharacterOrNil.
- 			aTwoElementArray 
- 				at: 1 put: w; 
- 				at: 2 put: w+k].
- 	^aTwoElementArray
- "	!

Item was removed:
- ----- Method: AbstractFont>>widthOf: (in category 'measuring') -----
- widthOf: aCharacter
- 	"Return the width of the given character"
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: AbstractFont>>widthOfByteCharacter: (in category 'measuring') -----
- widthOfByteCharacter: aCharacter
- 	"Return the width of the given character whose codePoint is <= 16rFF."
- 
- 	^ self widthOf: aCharacter!

Item was removed:
- ----- Method: AbstractFont>>widthOfString: (in category 'measuring') -----
- widthOfString: aString
- 	aString ifNil:[^0].
- 	^self widthOfString: aString from: 1 to: aString size.
- "
- 	TextStyle default defaultFont widthOfString: 'zort' 21
- "!

Item was removed:
- ----- Method: AbstractFont>>widthOfString:from:to: (in category 'measuring') -----
- widthOfString: aString from: startIndex to: stopIndex
- 	"Measure the length of the given string between start and stop index."
- 
- 	| resultX |
- 	resultX := 0.
- 	startIndex to: stopIndex do: [:i | 
- 		resultX := resultX + (self widthOf: (aString at: i))].
- 	^ resultX
- 	
- "TODO: Use scanner to support kerning.
- CharacterScanner new
- 	measureString: asString inFont: self
- 	from: startIndex to: stopIndex
- "!

Item was removed:
- ----- Method: AbstractFont>>widthOfStringOrText: (in category 'measuring') -----
- widthOfStringOrText: aStringOrText
-     aStringOrText ifNil:[^0].
-     ^aStringOrText isText
-         ifTrue:[self approxWidthOfText: aStringOrText ]
-         ifFalse:[self widthOfString: aStringOrText ] !

Item was removed:
- ----- Method: AbstractFont>>xTable (in category 'accessing') -----
- xTable
- 	"Return the xTable for the font. The xTable defines the left x-value for each individual glyph in the receiver. If such a table is not provided, the character scanner will ask the font directly for the appropriate width of each individual character."
- 	^nil!

Item was removed:
- GIFReadWriter subclass: #AnimatedGIFReadWriter
- 	instanceVariableNames: 'forms delays comments'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!

Item was removed:
- ----- Method: AnimatedGIFReadWriter class>>basicNew (in category 'instance creation') -----
- basicNew
- 	"Notify that the class is being deprecated."
- 	self deprecated: 'This class is deprecated. Its functionality can be found in the regular GIFReadWriter class instead.'.
- 	^ super basicNew
- 	!

Item was removed:
- ----- Method: AnimatedGIFReadWriter class>>formsFromFileNamed: (in category 'image reading/writing') -----
- formsFromFileNamed: fileName 
- 	| stream |
- 	stream := FileStream readOnlyFileNamed: fileName.
- 	^ self formsFromStream: stream!

Item was removed:
- ----- Method: AnimatedGIFReadWriter class>>formsFromStream: (in category 'image reading/writing') -----
- formsFromStream: stream 
- 	| reader |
- 	reader := self new on: stream reset.
- 	Cursor read
- 		showWhile: [reader allImages.
- 			reader close].
- 	^reader!

Item was removed:
- ----- Method: AnimatedGIFReadWriter class>>typicalFileExtensions (in category 'image reading/writing') -----
- typicalFileExtensions
- 	"Answer a collection of file extensions (lowercase) which files that I can read might commonly have"
- 	^#()!

Item was removed:
- ----- Method: AnimatedGIFReadWriter class>>wantsToHandleGIFs (in category 'image reading/writing') -----
- wantsToHandleGIFs
- 	^ false!

Item was removed:
- ----- Method: AnimatedGIFReadWriter>>allImages (in category 'accessing') -----
- allImages
- 	| body colorTable |
- 	localColorTable := nil.
- 	forms := OrderedCollection new.
- 	delays := OrderedCollection new.
- 	comments := OrderedCollection new.
- 	self readHeader.
- 	[(body := self readBody) == nil]
- 		whileFalse: [colorTable := localColorTable
- 						ifNil: [colorPalette].
- 			transparentIndex
- 				ifNotNil: [transparentIndex + 1 > colorTable size
- 						ifTrue: [colorTable := colorTable forceTo: transparentIndex + 1 paddingWith: Color white].
- 					colorTable at: transparentIndex + 1 put: Color transparent].
- 			body colors: colorTable.
- 			forms add: body].
- 	^ forms!

Item was removed:
- ----- Method: AnimatedGIFReadWriter>>comment: (in category 'private') -----
- comment: aString
- 	comments add: aString!

Item was removed:
- ----- Method: AnimatedGIFReadWriter>>delays (in category 'accessing') -----
- delays
- 	^ delays!

Item was removed:
- ----- Method: AnimatedGIFReadWriter>>forms (in category 'accessing') -----
- forms
- 	^ forms!

Item was removed:
- ----- Method: AnimatedGIFReadWriter>>readBitData (in category 'private-decoding') -----
- readBitData
- 	| form |
- 	form := super readBitData.
- 	form offset: offset.
- 	^form!

Item was removed:
- Object subclass: #AnimatedImageFrame
- 	instanceVariableNames: 'form delay disposal offset interlace'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!
- 
- !AnimatedImageFrame commentStamp: '' prior: 0!
- I am a single frame in a sequence of frames that comprise an animated image. I am designed for use by classes like AnimatedImageMorph and am created during the reading of some image files such as GIFs (see GIFReadWriter).
- 
- I contain a Form describing my image, a delay time in milliseconds that describes how long I should be displayed in a sequence of animated frames, and a disposal symbol that implementors can use when compositing myself in a sequence of frames. 
- 
- See AnimatedImageMorph for examples of how I am used.!

Item was removed:
- ----- Method: AnimatedImageFrame>>defaultDelay (in category 'defaults') -----
- defaultDelay
- 	^ 66!

Item was removed:
- ----- Method: AnimatedImageFrame>>delay (in category 'accessing') -----
- delay
- 	^ delay!

Item was removed:
- ----- Method: AnimatedImageFrame>>delay: (in category 'accessing') -----
- delay: aNumber
- 	delay := aNumber!

Item was removed:
- ----- Method: AnimatedImageFrame>>disposal (in category 'accessing') -----
- disposal
- 	^ disposal!

Item was removed:
- ----- Method: AnimatedImageFrame>>disposal: (in category 'accessing') -----
- disposal: aSymbol
- 	"Disposal must be one of:
- 		#restoreBackground
- 		#leaveCurrent
- 		#restorePreviousState"
- 	"({ #restoreBackground.
- 		#leaveCurrent.
- 		#restorePreviousState } includes: aSymbol) ifTrue: [ 
- 			disposal := aSymbol ]."
- 	disposal := aSymbol!

Item was removed:
- ----- Method: AnimatedImageFrame>>form (in category 'accessing') -----
- form
- 	^ form!

Item was removed:
- ----- Method: AnimatedImageFrame>>form: (in category 'accessing') -----
- form: aForm
- 	form := aForm!

Item was removed:
- ----- Method: AnimatedImageFrame>>initialize (in category 'initialization') -----
- initialize
- 	super initialize.
- 	offset := 0 @ 0.
- 	delay := self defaultDelay.
- 	disposal := #otherDisposal.
- 	interlace := false!

Item was removed:
- ----- Method: AnimatedImageFrame>>interlace (in category 'accessing') -----
- interlace
- 	^ interlace!

Item was removed:
- ----- Method: AnimatedImageFrame>>interlace: (in category 'accessing') -----
- interlace: aBoolean
- 	interlace := aBoolean!

Item was removed:
- ----- Method: AnimatedImageFrame>>offset (in category 'accessing') -----
- offset
- 	^ offset!

Item was removed:
- ----- Method: AnimatedImageFrame>>offset: (in category 'accessing') -----
- offset: aPoint
- 	"This represents the frame form's offset in the
- 	parent image canvas"
- 	offset := aPoint!

Item was removed:
- Object subclass: #BDFFontReader
- 	instanceVariableNames: 'file properties'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Fonts'!
- 
- !BDFFontReader commentStamp: '<historical>' prior: 0!
- I am a conversion utility for reading X11 Bitmap Distribution Format fonts.  My code is derived from the multilingual Squeak changeset written by OHSHIMA Yoshiki (ohshima at is.titech.ac.jp), although all support for fonts with more than 256 glyphs has been ripped out.  See http://www.is.titech.ac.jp/~ohshima/squeak/squeak-multilingual-e.html .
- 
- My class methods contain tools for fetching BDF source files from a well-known archive site, batch conversion to Squeak's .sf2 format, and installation of these fonts as TextStyles.  Also, the legal notices for the standard 75dpi fonts I process this way are included as "x11FontLegalNotices'.!

Item was removed:
- ----- Method: BDFFontReader class>>convertFilesNamed:toFamilyNamed:inDirectoryNamed: (in category 'file creation') -----
- convertFilesNamed: fileName toFamilyNamed: familyName inDirectoryNamed: dirName
- 		"BDFFontReader convertFilesNamed: 'helvR' toFamilyNamed: 'Helvetica' inDirectoryNamed: '' "
- 
- 	"This utility converts X11 BDF font files to Squeak .sf2 StrikeFont files."
- 
- 	"For this utility to work as is, the BDF files must be named 'familyNN.bdf',
- 	and must reside in the directory named by dirName (use '' for the current directory).
- 	The output StrikeFont files will be named familyNN.sf2, and will be placed in the
- 	current directory."
- 
- 	| allFontNames dir |
- 	"Check for matching file names."
- 	dir := dirName isEmpty
- 		ifTrue: [FileDirectory default]
- 		ifFalse: [FileDirectory default directoryNamed: dirName].
- 	allFontNames := dir fileNamesMatching: fileName , '##.bdf'.
- 	allFontNames isEmpty ifTrue: [^ self error: 'No files found like ' , fileName , 'NN.bdf'].
- 	
- 	UIManager default informUserDuring: [:info |
- 		allFontNames do: [:fname | | f sizeChars | 
- 			info value: 'Converting ', familyName, ' BDF file ', fname, ' to SF2 format'.
- 			sizeChars := (fname copyFrom: fileName size + 1 to: fname size) copyUpTo: $. .
- 
- 			f := StrikeFont new readBDFFromFile: (dir fullNameFor: fname) name: familyName, sizeChars.
- 			f writeAsStrike2named: familyName, sizeChars, '.sf2'.
- 		].
- 	]!

Item was removed:
- ----- Method: BDFFontReader class>>convertX11FontsToStrike2 (in category 'resource download') -----
- convertX11FontsToStrike2  "BDFFontReader convertX11FontsToStrike2"
- 	"Given a set of standard X11 BDF font files (probably downloaded via BDFFontReader downloadFonts), produce .sf2 format fonts.  The source and destination directory is the current directory."
- 
- 	"Charter currently tickles a bug in the BDF parser.  Skip it for now."
- 	"self convertFilesNamed: 'charR' toFamilyNamed: 'Charter' inDirectoryNamed: ''."
- 
- 	self convertFilesNamed: 'courR' toFamilyNamed: 'Courier' inDirectoryNamed: ''.
- 	self convertFilesNamed: 'helvR' toFamilyNamed: 'Helvetica' inDirectoryNamed: ''.
- 
- 	self convertFilesNamed: 'lubR' toFamilyNamed: 'LucidaBright' inDirectoryNamed: ''.
- 	self convertFilesNamed: 'luRS' toFamilyNamed: 'Lucida' inDirectoryNamed: ''.
- 	self convertFilesNamed: 'lutRS' toFamilyNamed: 'LucidaTypewriter' inDirectoryNamed: ''.
- 
- 	self convertFilesNamed: 'ncenR' toFamilyNamed: 'NewCenturySchoolbook' inDirectoryNamed: ''.
- 	self convertFilesNamed: 'timR' toFamilyNamed: 'TimesRoman' inDirectoryNamed: ''.!

Item was removed:
- ----- Method: BDFFontReader class>>downloadFonts (in category 'resource download') -----
- downloadFonts  "BDFFontReader downloadFonts"
- 	"Download a standard set of BDF sources from x.org.  
- 	The combined size of these source files is around 1.2M; after conversion 
- 	to .sf2 format they may be deleted."
- 
- 	| heads tails filenames baseUrl basePath |
- 	heads := #( 'charR' 'courR' 'helvR' 'lubR' 'luRS' 'lutRS' 'ncenR' 'timR' ).
- 	tails := #( '08' '10' '12' '14' '18' '24').
- 
- 	filenames := OrderedCollection new.
- 	heads do: [:head |
- 		filenames addAll: (tails collect: [:tail | head , tail , '.bdf'])
- 	].
- 	baseUrl := 'http://cvsweb.xfree86.org/cvsweb/*checkout*/xc/fonts/bdf/75dpi/' asUrl.
- 	basePath := baseUrl path.
- 
- 	filenames do: [:filename |
- 		| document newPath newUrl |
- 		newUrl := baseUrl shallowCopy.
- 		newPath := OrderedCollection newFrom: basePath.
- 
- 		newPath addLast: filename.
- 		newUrl path: newPath.
- 
- 		UIManager default informUser: 'Fetching ' , filename during: 
- 			[document := newUrl retrieveContents].
- 
- 		MultiByteFileStream newFileNamed: filename do: [ :f |
- 			f 
- 				wantsLineEndConversion: true;
- 				nextPutAll: document content ]
- 	].
- !

Item was removed:
- ----- Method: BDFFontReader class>>gettingAndInstallingTheFonts (in category 'documentation') -----
- gettingAndInstallingTheFonts
- 
- 	"Download the 1.3M of BDF font source files from x.org:
- 
- 		BDFFontReader downloadFonts.
- 
- 	Convert them to .sf2 StrikeFont files:
- 
- 		BDFFontReader convertX11FontsToStrike2.
- 
- 	Install them into the system as TextStyles:
- 
- 		BDFFontReader installX11Fonts.
- 
- 	Read the legal notices in 'BDFFontReader x11FontLegalNotices' before
- 	redistributing images containing these fonts."!

Item was removed:
- ----- Method: BDFFontReader class>>installX11Fonts (in category 'resource download') -----
- installX11Fonts "BDFFontReader installX11Fonts"
- 	"Installs previously-converted .sf2 fonts into the TextConstants dictionary.  This makes them available as TextStyles everywhere in the image."
- 
- 	| families |
- 	families := #( 'Courier' 'Helvetica' 'LucidaBright' 'Lucida' 'LucidaTypewriter' 'NewCenturySchoolbook' 'TimesRoman' ).
- 
- 	families do: [:family | | fontArray textStyle |
- 		fontArray := StrikeFont readStrikeFont2Family: family.
- 		textStyle := TextStyle fontArray: fontArray.
- 		TextConstants at: family asSymbol put: textStyle.
- 	].
- !

Item was removed:
- ----- Method: BDFFontReader class>>openFileNamed: (in category 'file creation') -----
- openFileNamed: fileName
- 	^self new openFileNamed: fileName!

Item was removed:
- ----- Method: BDFFontReader>>errorFileFormat (in category 'reading') -----
- errorFileFormat
- 	self error: 'malformed bdf format'!

Item was removed:
- ----- Method: BDFFontReader>>errorUnsupported (in category 'reading') -----
- errorUnsupported
- 	self error: 'unsupported bdf'!

Item was removed:
- ----- Method: BDFFontReader>>getLine (in category 'reading') -----
- getLine
- 	^file nextLine!

Item was removed:
- ----- Method: BDFFontReader>>initialize (in category 'initialize') -----
- initialize
- 	properties := Dictionary new.!

Item was removed:
- ----- Method: BDFFontReader>>openFileNamed: (in category 'initialize') -----
- openFileNamed: fileName
- 	file := MultiByteFileStream readOnlyFileNamed: fileName.
- 	file wantsLineEndConversion: true!

Item was removed:
- ----- Method: BDFFontReader>>read (in category 'reading') -----
- read
- 	| xTable strikeWidth glyphs ascent descent minAscii maxAscii maxWidth chars charsNum height form encoding bbx array width blt lastAscii pointSize ret stream |
- 	form := encoding := bbx := nil.
- 	self readAttributes.
- 	height := Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2).
- 	ascent := Integer readFromString: (properties at: #'FONT_ASCENT') first.
- 	descent := Integer readFromString: (properties at: #'FONT_DESCENT') first.
- 	pointSize := (Integer readFromString: (properties at: #'POINT_SIZE') first) // 10.
- 	
- 	maxWidth := 0.
- 	minAscii := 9999.
- 	strikeWidth := 0.
- 	maxAscii := 0.
- 
- 	charsNum := Integer readFromString: (properties at: #CHARS) first.
- 	chars := Set new: charsNum.
- 
- 	1 to: charsNum do: [:i |
- 		array := self readOneCharacter.
- 		stream := ReadStream on: array.
- 		form := stream next.
- 		encoding := stream next.
- 		bbx := stream next.
- 		form ifNotNil: [
- 			width := bbx at: 1.
- 			maxWidth := maxWidth max: width.
- 			minAscii := minAscii min: encoding.
- 			maxAscii := maxAscii max: encoding.
- 			strikeWidth := strikeWidth + width.
- 			chars add: array.
- 		].
- 	].
- 
- 	chars := chars sorted: [:x :y | (x at: 2) <= (y at: 2)].
- 	charsNum := chars size. "undefined encodings make this different"
- 
- 	charsNum > 256 ifTrue: [
- 		"it should be 94x94 charset, and should be fixed width font"
- 		strikeWidth := 94*94*maxWidth.
- 		maxAscii := 94*94.
- 		minAscii := 0.
- 		xTable := XTableForFixedFont new.
- 		xTable maxAscii: 94*94.
- 		xTable width: maxWidth.
- 	] ifFalse: [
- 		xTable := (Array new: 258) atAllPut: 0.
- 	].
- 
- 	glyphs := Form extent: strikeWidth at height.
- 	blt := BitBlt toForm: glyphs.
- 	lastAscii := 0.
- 	
- 	charsNum > 256 ifTrue: [
- 		1 to: charsNum do: [:i |
- 			stream := ReadStream on: (chars at: i).
- 			form := stream next.
- 			encoding := stream next.
- 			bbx := stream next.
- 			encoding := ((encoding // 256) - 33) * 94 + ((encoding \\ 256) - 33).
- 			blt copy: ((encoding * maxWidth)@0 extent: maxWidth at height)
- 				from: 0 at 0 in: form.
- 		].
- 	] ifFalse: [
- 		1 to: charsNum do: [:i |
- 			stream := ReadStream on: (chars at: i).
- 			form := stream next.
- 			encoding := stream next.
- 			bbx := stream next.
- 			lastAscii+1 to: encoding-1 do: [:a | xTable at: a+2 put: (xTable at: a+1)].
- 			blt copy: (((xTable at: encoding+1)@(ascent - (bbx at: 2) - (bbx at: 4)))
- 					extent: (bbx at: 1)@(bbx at: 2))
- 				from: 0 at 0 in: form.
- 			xTable at: encoding+2 put: (xTable at: encoding+1)+(bbx at: 1).
- 			lastAscii := encoding.
- 		]
- 	].
- 
- 	ret := Array new: 8.
- 	ret at: 1 put: xTable.
- 	ret at: 2 put: glyphs.
- 	ret at: 3 put: minAscii.
- 	ret at: 4 put: maxAscii.
- 	ret at: 5 put: maxWidth.
- 	ret at: 6 put: ascent.
- 	ret at: 7 put: descent.
- 	ret at: 8 put: pointSize.
- 	^ret.
- " ^{xTable. glyphs. minAscii. maxAscii. maxWidth. ascent. descent. pointSize}"
- !

Item was removed:
- ----- Method: BDFFontReader>>readAttributes (in category 'reading') -----
- readAttributes
- 	| str a |
- 	"I don't handle double-quotes correctly, but it works"
- 	file reset.
- 	[file atEnd] whileFalse: [
- 		str := self getLine.
- 		(str beginsWith: 'STARTCHAR') ifTrue: [file skip: (0 - str size - 1). ^self].
- 		a := str substrings.
- 		properties at: a first asSymbol put: a allButFirst.
- 	].
- 	self error: 'file seems corrupted'.!

Item was removed:
- ----- Method: BDFFontReader>>readChars (in category 'reading') -----
- readChars
- 	| strikeWidth ascent descent minAscii maxAscii maxWidth chars charsNum height form encoding bbx array width pointSize stream |
- 	form := encoding := bbx := nil.
- 	self readAttributes.
- 	height := Integer readFromString: ((properties at: #FONTBOUNDINGBOX) at: 2).
- 	ascent := Integer readFromString: (properties at: #'FONT_ASCENT') first.
- 	descent := Integer readFromString: (properties at: #'FONT_DESCENT') first.
- 	pointSize := (Integer readFromString: (properties at: #'POINT_SIZE') first) // 10.
- 	
- 	maxWidth := 0.
- 	minAscii := 9999.
- 	strikeWidth := 0.
- 	maxAscii := 0.
- 
- 	charsNum := Integer readFromString: (properties at: #CHARS) first.
- 	chars := Set new: charsNum.
- 
- 	1 to: charsNum do: [:i |
- 		array := self readOneCharacter.
- 		stream := ReadStream on: array.
- 		form := stream next.
- 		encoding := stream next.
- 		bbx := stream next.
- 		form ifNotNil: [
- 			width := bbx at: 1.
- 			maxWidth := maxWidth max: width.
- 			minAscii := minAscii min: encoding.
- 			maxAscii := maxAscii max: encoding.
- 			strikeWidth := strikeWidth + width.
- 			chars add: array.
- 		].
- 	].
- 
- 	^chars sorted: [:x :y | (x at: 2) <= (y at: 2)]!

Item was removed:
- ----- Method: BDFFontReader>>readOneCharacter (in category 'reading') -----
- readOneCharacter
- 	| str a encoding bbx form bits hi low pos |
- 	((str := self getLine) beginsWith: 'ENDFONT') ifTrue: [^ {nil. nil. nil}].
- 	(str beginsWith: 'STARTCHAR') ifFalse: [self errorFileFormat].
- 	((str := self getLine) beginsWith: 'ENCODING') ifFalse: [self errorFileFormat].
- 	encoding := Integer readFromString: str substrings second.
- 	(self getLine beginsWith: 'SWIDTH') ifFalse: [self errorFileFormat].
- 	(self getLine beginsWith: 'DWIDTH') ifFalse: [self errorFileFormat].
- 	
- 	((str := self getLine) beginsWith: 'BBX') ifFalse: [self errorFileFormat].
- 	a := str substrings.
- 	bbx := (2 to: 5) collect: [:i | Integer readFromString: (a at: i)].
- 	((str := self getLine) beginsWith: 'ATTRIBUTES') ifTrue: [str := self getLine].
- 	(str beginsWith: 'BITMAP') ifFalse: [self errorFileFormat].
- 
- 	form := Form extent: (bbx at: 1)@(bbx at: 2).
- 	bits := form bits.
- 	pos := 0.
- 	1 to: (bbx at: 2) do: [:t |
- 		1 to: (((bbx at: 1) - 1) // 8 + 1) do: [:i |
- 			hi := (('0123456789ABCDEF' indexOf: (file next asUppercase)) - 1) bitShift: 4.
- 			low := ('0123456789ABCDEF' indexOf: (file next asUppercase)) - 1.
- 			
- 			bits byteAt: (pos+i) put: (hi+low).
- 		].
- 		file next ~= Character cr ifTrue: [self errorFileFormat].
- 		pos := pos + ((((bbx at: 1) // 32) + 1) * 4).
- 	].
- 
- 	(self getLine beginsWith: 'ENDCHAR') ifFalse: [self errorFileFormat].
- 
- 	encoding < 0 ifTrue: [^{nil. nil. nil}].
- 	^{form. encoding. bbx}.
- 	
- 	
- 	!

Item was removed:
- ImageReadWriter subclass: #BMPReadWriter
- 	instanceVariableNames: 'bfType bfSize bfOffBits biSize biWidth biHeight biPlanes biBitCount biCompression biSizeImage biXPelsPerMeter biYPelsPerMeter biClrUsed biClrImportant'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!

Item was removed:
- ----- Method: BMPReadWriter class>>displayAllFrom: (in category 'testing') -----
- displayAllFrom: fd
- 	"BMPReadWriter displayAllFrom: FileDirectory default"
- 	fd fileNames do:[:fName|
- 		(fName endsWith: '.bmp') ifTrue:[
- 			[(Form fromBinaryStream: (fd readOnlyFileNamed: fName)) display.
- 			Display forceDisplayUpdate] on: Error do:[:nix|].
- 		].
- 	].
- 	fd directoryNames do:[:fdName|
- 		self displayAllFrom: (fd directoryNamed: fdName)
- 	].!

Item was removed:
- ----- Method: BMPReadWriter class>>readAllFrom: (in category 'testing') -----
- readAllFrom: fd
- 	"MessageTally spyOn:[BMPReadWriter readAllFrom: FileDirectory default]"
- 	fd fileNames do:[:fName|
- 		(fName endsWith: '.bmp') ifTrue:[
- 			[Form fromBinaryStream: (fd readOnlyFileNamed: fName)] ifError: [].
- 		].
- 	].
- 	fd directoryNames do:[:fdName|
- 		self readAllFrom: (fd directoryNamed: fdName)
- 	].!

Item was removed:
- ----- Method: BMPReadWriter class>>typicalFileExtensions (in category 'image reading/writing') -----
- typicalFileExtensions
- 	"Answer a collection of file extensions (lowercase) which files that I can read might commonly have"
- 	^#('bmp')!

Item was removed:
- ----- Method: BMPReadWriter>>nextImage (in category 'reading') -----
- nextImage
- 	| colors |
- 	stream binary.
- 	self readHeader.
- 	biBitCount = 24 ifTrue:[^self read24BmpFile].
- 	"read the color map"
- 	colors := self readColorMap.
- 	^self readIndexedBmpFile: colors!

Item was removed:
- ----- Method: BMPReadWriter>>nextPutImage: (in category 'writing') -----
- nextPutImage: aForm
- 	| bhSize rowBytes rgb data colorValues depth image ppw scanLineLen pixline |
- 	depth := aForm depth.
- 	depth := #(1 4 8 32 ) detect: [ :each | each >= depth].
- 	image := aForm asFormOfDepth: depth.
- 	image unhibernate.
- 	bhSize := 14.  "# bytes in file header"
- 	biSize := 40.  "info header size in bytes"
- 	biWidth := image width.
- 	biHeight := image height.
- 	biClrUsed := depth = 32 ifTrue: [0] ifFalse:[1 << depth].  "No. color table entries"
- 	bfOffBits := biSize + bhSize + (4*biClrUsed).
- 	rowBytes := ((depth min: 24) * biWidth + 31 // 32) * 4.
- 	biSizeImage := biHeight * rowBytes.
- 
- 	"Write the file header"
- 	stream position: 0.
- 	stream nextLittleEndianNumber: 2 put: 19778.  "bfType = BM"
- 	stream nextLittleEndianNumber: 4 put: bfOffBits + biSizeImage.  "Entire file size in bytes"
- 	stream nextLittleEndianNumber: 4 put: 0.  "bfReserved"
- 	stream nextLittleEndianNumber: 4 put: bfOffBits.  "Offset of bitmap data from start of hdr (and file)"
- 
- 	"Write the bitmap info header"
- 	stream position: bhSize.
- 	stream nextLittleEndianNumber: 4 put: biSize.  "info header size in bytes"
- 	stream nextLittleEndianNumber: 4 put: image width.  "biWidth"
- 	stream nextLittleEndianNumber: 4 put: image height.  "biHeight"
- 	stream nextLittleEndianNumber: 2 put: 1.  "biPlanes"
- 	stream nextLittleEndianNumber: 2 put: (depth min: 24).  "biBitCount"
- 	stream nextLittleEndianNumber: 4 put: 0.  "biCompression"
- 	stream nextLittleEndianNumber: 4 put: biSizeImage.  "size of image section in bytes"
- 	stream nextLittleEndianNumber: 4 put: 2800.  "biXPelsPerMeter"
- 	stream nextLittleEndianNumber: 4 put: 2800.  "biYPelsPerMeter"
- 	stream nextLittleEndianNumber: 4 put: biClrUsed.
- 	stream nextLittleEndianNumber: 4 put: 0.  "biClrImportant"
- 	biClrUsed > 0 ifTrue: [
- 		"write color map; this works for ColorForms, too"
- 		colorValues := image colormapIfNeededForDepth: 32.
- 		1 to: biClrUsed do: [:i |
- 			rgb := colorValues at: i.
- 			0 to: 24 by: 8 do: [:j | stream nextPut: (rgb >> j bitAnd: 16rFF)]]].
- 
- 	depth < 32 ifTrue: [
- 		"depth = 1, 4 or 8."
- 		data := image bits asByteArray.
- 		ppw := 32 // depth.
- 		scanLineLen := biWidth + ppw - 1 // ppw * 4.  "# of bytes in line"
- 		1 to: biHeight do: [:i |
- 			stream next: scanLineLen putAll: data startingAt: (biHeight-i)*scanLineLen+1.
- 		].
- 	] ifFalse: [
- 		data := image bits.
- 		pixline := ByteArray new: (((biWidth * 3 + 3) // 4) * 4).
- 		1 to: biHeight do:[:i |
- 			self store24BitBmpLine: pixline from: data startingAt: (biHeight-i)*biWidth+1 width: biWidth.
- 			stream nextPutAll: pixline.
- 		].
- 	].
- 	stream position = (bfOffBits + biSizeImage) ifFalse: [self error: 'Write failure' translated].
- 	stream close.!

Item was removed:
- ----- Method: BMPReadWriter>>read24BmpFile (in category 'reading') -----
- read24BmpFile
- 	"Read 24-bit pixel data from the given a BMP stream."
- 	| form formBits pixelLine bitsIndex bitBlt |
- 	form := Form extent: biWidth at biHeight depth: 32.
- 	pixelLine := ByteArray new: (((24 * biWidth) + 31) // 32) * 4.
- 	bitsIndex := form height - 1 * biWidth + 1.
- 	formBits := form bits.
- 	1 to: biHeight do: [:i |
- 		pixelLine := stream nextInto: pixelLine.
- 		self read24BmpLine: pixelLine into: formBits startingAt: bitsIndex width: biWidth.
- 		bitsIndex := bitsIndex - biWidth.
- 	].
- 	bitBlt := BitBlt toForm: form.
- 	bitBlt combinationRule: 7 "bitOr:with:".
- 	bitBlt halftoneForm: (Bitmap with: 16rFF000000).
- 	bitBlt copyBits.
- 	^ form
- !

Item was removed:
- ----- Method: BMPReadWriter>>read24BmpLine:into:startingAt:width: (in category 'reading') -----
- read24BmpLine: pixelLine into: formBits startingAt: formBitsIndex width: width
- 	"Swizzles the bytes in a 24bpp scanline and fills in the given 32bpp form bits.
- 	Ensures that color black is represented as 16rFF000001 so that Form paint
- 	works properly."
- 
- 	| pixIndex rgb bitsIndex |
- 	<primitive: 'primitiveRead24BmpLine' module:'BMPReadWriterPlugin'>
- 	pixIndex := 0. "pre-increment"
- 	bitsIndex := formBitsIndex-1. "pre-increment"
- 	1 to: width do: [:j |
- 		rgb := 
- 			(pixelLine at: (pixIndex := pixIndex+1)) +
- 			((pixelLine at: (pixIndex := pixIndex+1)) bitShift: 8) +
- 			((pixelLine at: (pixIndex := pixIndex+1)) bitShift: 16).
- 		rgb = 0 ifTrue:[rgb := 16rFF000001] ifFalse:[rgb := rgb + 16rFF000000].
- 		formBits at: (bitsIndex := bitsIndex+1) put: rgb.
- 	].
- !

Item was removed:
- ----- Method: BMPReadWriter>>readColorMap (in category 'reading') -----
- readColorMap
- 	"Read colorCount BMP color map entries from the given binary stream. Answer an array of Colors."
- 	| colorCount colors maxLevel b g r ccStream |
- 	colorCount := (bfOffBits - 54) // 4.
- 	"Note: some programs (e.g. Photoshop 4.0) apparently do not set colorCount; assume that any data between the end of the header and the start of the pixel data is the color map"
- 	biBitCount >= 16 ifTrue:[^nil].
- 	colorCount = 0 ifTrue: [ "this BMP file does not have a color map"
- 		"default monochrome color map"
- 		biBitCount = 1 ifTrue: [^ Array with: Color white with: Color black].
- 		"default gray-scale color map"
- 		maxLevel := (2 raisedTo: biBitCount) - 1.
- 		^ (0 to: maxLevel) collect: [:level | Color gray: (level asFloat / maxLevel)]].
- 	ccStream := ReadStream on: (stream next: colorCount*4).
- 	colors := Array new: colorCount.
- 	1 to: colorCount do: [:i |
- 		b := ccStream next.
- 		g := ccStream next.
- 		r := ccStream next.
- 		ccStream next. "skip reserved"
- 		colors at: i put: (Color r: r g: g b: b range: 255)].
- 	^ colors
- !

Item was removed:
- ----- Method: BMPReadWriter>>readHeader (in category 'reading') -----
- readHeader
- 	| reserved |
- 	bfType := stream nextLittleEndianNumber: 2.
- 	bfSize := stream nextLittleEndianNumber: 4.
- 	reserved := stream nextLittleEndianNumber: 4.
- 	bfOffBits := stream nextLittleEndianNumber: 4.
- 	biSize := stream nextLittleEndianNumber: 4.
- 	biWidth := stream nextLittleEndianNumber: 4.
- 	biHeight := stream nextLittleEndianNumber: 4.
- 	biPlanes := stream nextLittleEndianNumber: 2.
- 	biBitCount := stream nextLittleEndianNumber: 2.
- 	biCompression := stream nextLittleEndianNumber: 4.
- 	biSizeImage := stream nextLittleEndianNumber: 4.
- 	biXPelsPerMeter := stream nextLittleEndianNumber: 4.
- 	biYPelsPerMeter := stream nextLittleEndianNumber: 4.
- 	biClrUsed := stream nextLittleEndianNumber: 4.
- 	biClrImportant := stream nextLittleEndianNumber: 4.
- !

Item was removed:
- ----- Method: BMPReadWriter>>readIndexedBmpFile: (in category 'reading') -----
- readIndexedBmpFile: colors
- 	"Read uncompressed pixel data of depth d from the given BMP stream, where d is 1, 4, 8, or 16"
- 	| form bytesPerRow pixelData pixelLine startIndex map bitBlt mask |
- 	colors 
- 		ifNil:[form := Form extent: biWidth at biHeight depth: biBitCount]
- 		ifNotNil:[form := ColorForm extent: biWidth at biHeight depth: biBitCount.
- 				form colors: colors].
- 	bytesPerRow := (((biBitCount* biWidth) + 31) // 32) * 4.
- 	pixelData := ByteArray new: bytesPerRow * biHeight.
- 	biHeight to: 1 by: -1 do: [:y |
- 		pixelLine := stream next: bytesPerRow.
- 		startIndex := ((y - 1) * bytesPerRow) + 1.
- 		pixelData 
- 			replaceFrom: startIndex 
- 			to: startIndex + bytesPerRow - 1 
- 			with: pixelLine 
- 			startingAt: 1].
- 	form bits copyFromByteArray: pixelData.
- 	biBitCount = 16 ifTrue:[
- 		map := ColorMap shifts: #(8 -8 0 0) masks: #(16rFF 16rFF00 0 0).
- 		mask := 16r80008000.
- 	].
- 	biBitCount = 32 ifTrue:[
- 		map := ColorMap shifts: #(24 8 -8 -24) masks: #(16rFF 16rFF00 16rFF0000 16rFF000000).
- 		mask := 16rFF000000.
- 	].
- 	map ifNotNil:[
- 		bitBlt := BitBlt toForm: form.
- 		bitBlt sourceForm: form.
- 		bitBlt colorMap: map.
- 		bitBlt combinationRule: Form over.
- 		bitBlt copyBits.
- 	].
- 	mask ifNotNil:[
- 		bitBlt := BitBlt toForm: form.
- 		bitBlt combinationRule: 7 "bitOr:with:".
- 		bitBlt halftoneForm: (Bitmap with: mask).
- 		bitBlt copyBits.
- 	].
- 	^ form
- !

Item was removed:
- ----- Method: BMPReadWriter>>store24BitBmpLine:from:startingAt:width: (in category 'writing') -----
- store24BitBmpLine: pixelLine from: formBits startingAt: formBitsIndex width: width
- 	"Stores a single scanline containing 32bpp RGBA values in a 24bpp scanline.
- 	Swizzles the bytes as needed."
- 
- 	| pixIndex rgb bitsIndex |
- 	<primitive: 'primitiveWrite24BmpLine' module:'BMPReadWriterPlugin'>
- 	pixIndex := 0. "pre-increment"
- 	bitsIndex := formBitsIndex-1. "pre-increment"
- 	1 to: width do: [:j |
- 		rgb := (formBits at: (bitsIndex := bitsIndex+1)) bitAnd: 16rFFFFFF.
- 		pixelLine at: (pixIndex := pixIndex+1) put: (rgb bitAnd: 255).
- 		pixelLine at: (pixIndex := pixIndex+1) put: ((rgb bitShift: -8) bitAnd: 255).
- 		pixelLine at: (pixIndex := pixIndex+1) put: ((rgb bitShift: -16) bitAnd: 255).
- 	].
- !

Item was removed:
- ----- Method: BMPReadWriter>>understandsImageFormat (in category 'testing') -----
- understandsImageFormat
- 	stream size < 54 ifTrue:[^false]. "min size = BITMAPFILEHEADER+BITMAPINFOHEADER"
- 	self readHeader.
- 	bfType = 19778 "BM" ifFalse:[^false].
- 	biSize = 40 ifFalse:[^false].
- 	biPlanes = 1 ifFalse:[^false].
- 	bfSize <= stream size ifFalse:[^false].
- 	biCompression = 0 ifFalse:[^false].
- 	^true!

Item was removed:
- Object subclass: #BitBlt
- 	instanceVariableNames: 'destForm sourceForm halftoneForm combinationRule destX destY width height sourceX sourceY clipX clipY clipWidth clipHeight colorMap'
- 	classVariableNames: 'CachedFontColorMaps ColorConvertingMaps SubPixelRenderColorFonts SubPixelRenderFonts'
- 	poolDictionaries: ''
- 	category: 'Graphics-Primitives'!
- 
- !BitBlt commentStamp: 'nice 12/27/2020 16:53' prior: 0!
- WARNING: BitBlt's shape cannot be modified since WarpBlt relies on the exact layout. Important primitives will break if you fail to heed this warning.
- 
- I represent a block transfer (BLT) of pixels from one Form ( the sourceForm) into a rectangle (destX, destY, width, height) of the destinationForm, as modified by a combination rule, a possible halftoneForm and a possible color map.
- 
- The source of pixels may be a similar rectangle (at sourceX, sourceY) in the sourceForm, or the halftoneForm, or both.  If both are specified, their pixel values are combined by a logical AND function prior to any further combination rule processing. The halftoneForm may be an actual Form or a simple WordArray of 32 bit values usually intended to represent Color values. In either case the 'top' of the form is effectively aligned with the top of the destinationForm and for each scanline the destination y modulo the size of the halftoneForm gives the index of the word to use. This makes it easy to make horizontal stripes, for example.
- 
- In any case, the pixels from the source (AND'd with the halftone, remember) are combined with those of the destination by as specified by the combinationRules below- 
- 	name	rule		result 
- 
- 					0	always 0
- 	and				1	src AND dst
- 					2	src AND not(dst)
- 	over			3	src only
- 	erase			4	not(src) AND& dst
- 					5 	dst only
- 	reverse		6	src XOR dst
- 	under			7	src OR dst
- 					8	not(src) AND not(dst)
- 					9	not(src) XOR dst
- 					10	not(dst)
- 					11	src OR not(dst)
- 					12	not(src)
- 					13	not(src) OR dst
- 					14	not(src) OR not(dst)
- 					15	always 1
- (You can find an interesting explanation of how this comes to be in http://dev-docs.atariforge.org/files/BLiTTER_1-25-1990.pdf - which interestingly fails to mention any connection to Smalltalk and PARC.)
-  Forms may be of different depths, see the comment in class Form.
- 
- In addition to the original 16 combination rules invented for monochrome Forms, this BitBlt supports
- 					16	fails (to simulate paint bits)
- 					17	fails (to simulate erase bits)
- 					18	sourceWord + destinationWord
- 					19	sourceWord - destinationWord
- 					20	rgbAdd: sourceWord with: destinationWord.  Sum of color components
- 					21	rgbSub: sourceWord with: destinationWord.  Difference of color components
- 					22	OLDrgbDiff: sourceWord with: destinationWord.  Sum of abs of differences in components
- 					23	OLDtallyIntoMap: destinationWord.  Tallies pixValues into a colorMap
- 							these old versions don't do bitwise dest clipping.  Use 32 and 33 now.
- 	blend			24	alphaBlend: sourceWord with: destinationWord.  32-bit source and dest only. Blend sourceWord 
- 							with destinationWord, assuming both are 32-bit pixels. The source is assumed to have 255*alpha
- 							in the high 8 bits of each pixel, while the high 8 bits of the destinationWord will be ignored.
- 							The blend produced is alpha*source + (1-alpha)*dest, with the computation being performed
- 							independently on each color component.  The high byte of the result will be 0.
- 	paint			25	pixPaint: sourceWord with: destinationWord.  Wherever the sourceForm is non-zero, it replaces
- 							the destination.  Can be used with a 1-bit source color mapped to (0, FFFFFFFF), and a fillColor 
- 							to fill the dest with that color wherever the source is 1.
- 	erase1BitShape	26	pixMask: sourceWord with: destinationWord.  Like pixPaint, but fills with 0.
- 					27	rgbMax: sourceWord with: destinationWord.  Max of each color component.
- 					28	rgbMin: sourceWord with: destinationWord.  Min of each color component.
- 					29	rgbMin: sourceWord bitInvert32 with: destinationWord.  Min with (max-source)
- 	blendAlpha		30	alphaBlendConst: sourceWord with: destinationWord.  alpha is an arg. works in 16 bits. Blend
- 							sourceWord with destinationWord using a constant alpha. Alpha is encoded as 0 meaning
- 							0.0, and 255 meaning 1.0. The blend produced is alpha*source + (1.0-alpha)*dest, with
- 							the computation being performed independently on each color component. 
- 	paintAlpha		31	alphaPaintConst: sourceWord with: destinationWord.  alpha is an arg. works in 16 bits.
- 					32	rgbDiff: sourceWord with: destinationWord.  Sum of abs of differences in components
- 					33	tallyIntoMap: destinationWord.  Tallies pixValues into a colorMap - Those tallied are exactly 
- 							those in the destination rectangle.  Note that the source should be specified == destination,
- 							in order for the proper color map checks  be performed at setup.
- 	blendAlphaScaled	34	alphaBlendScaled: srcWord with: dstWord. Alpha blend of scaled srcWord and destWord. In contrast
- 							to alphaBlend:with: the color produced is srcColor + (1-srcAlpha) * dstColor
- 					35	& 36 not used
- 	rgbMul			37	rgbMul: srcWord with: dstWord. 
- 					38	pixSwap: srcWord with: dstWord.
- 					39	pixClear: srcWord with: dstWord. Clear all pixels in destinationWord for which the pixels of 
- 							sourceWord have the same values. Used to clear areas of some constant color to zero.
- 					40	fixAlpha: srcWord with: dstWord. For any non-zero pixel value in destinationWord with zero alpha 
- 							channel take the alpha from sourceWord and fill it in. Intended for fixing alpha channels left at 
- 							zero during 16->32 bpp conversions.
- 					41	rgbComponentAlpha: srcWord with: dstWord.
- 					42	alphaScale: srcWord with: dstWord. Pre-scale the destWord (i.e. multiply rgb components by alpha channel)
- 					43	alphaUncale: srcWord with: dstWord. Un-scale the destWord (i.e. divide rgb components by alpha channel)
- 					44	alphaBlendUnscaled: srcWord with: dstWord. Alpha blend of unscaled srcWord and destWord.
- 							In contrast to alphaBlendScaled:with: the color produced is (srcAlpha*srcColor + (1-srcAlpha) * dstColor)/resultAlpha
- 							where resultAlpha is srcAlpha + destAlpha*(1-srcAlpha)
- 							This is equivalent to operations 42 + 34 + 43 (aphaScale, alphaBlendScaled, alphaUnscale)
- 
- Any transfer specified is further clipped by the specified clipping rectangle (clipX, clipY, clipWidth, clipHeight), and also by the bounds of the source and destination forms.
- 	To make a small Form repeat and fill a big form, use an InfiniteForm as the source.
- 
- Pixels copied from a source to a destination whose pixels have a different depth are converted based on the optional colorMap.  If colorMap is nil, then conversion to more bits is done by filling the new high-order bits with zero, and conversion to fewer bits is done by truncating the lost high-order bits.  
- 
- The colorMap, if specified, must be a either word array (ie Bitmap) with 2^n elements, where n is the pixel depth of the source, or a fully specified ColorMap which may contain a lookup table (ie Bitmap) and/or four separate masks and shifts which are applied to the pixels. For every source pixel, BitBlt will first perform masking and shifting and then index the lookup table, and select the corresponding pixelValue and mask it to the destination pixel size before storing.
- 	When blitting from a 32 or 16 bit deep Form to one 8 bits or less, the default is truncation.  This will produce very strange colors, since truncation of the high bits does not produce the nearest encoded color.  Supply a 512 long colorMap, and red, green, and blue will be shifted down to 3 bits each, and mapped.  The message copybits...stdColors will use the best map to the standard colors for destinations of depths 8, 4, 2 and 1.  Two other sized of colorMaps are allowed, 4096 (4 bits per color) and 32786 (five bits per color).
- 	Normal blits between 16 and 32 bit forms truncates or pads the colors automatically to provide the best preservation of colors.
- 	Colors can be remapped at the same depth.  Sometimes a Form is in terms of colors that are not the standard colors for this depth, for example in a GIF file.  Convert the Form to a MaskedForm and send colorMap: the list of colors that the picture is in terms of. (Note also that a Form can be copied to itself, and transformed in the process, if a non-nil colorMap is supplied.)!

Item was removed:
- ----- Method: BitBlt class>>alphaBlendDemo (in category 'examples') -----
- alphaBlendDemo
- 	"To run this demo, use...
- 		Display restoreAfter: [BitBlt alphaBlendDemo]	
- 	Displays 10 alphas, then lets you paint.  Option-Click to stop painting."
- 
- 	"This code exhibits alpha blending in any display depth by performing
- 	the blend in an off-screen buffer with 32-bit pixels, and then copying
- 	the result back onto the screen with an appropriate color map. - tk 3/10/97"
- 	
- 	"This version uses a sliding buffer for painting that keeps pixels in 32 bits
- 	as long as they are in the buffer, so as not to lose info by converting down
- 	to display resolution and back up to 32 bits at each operation. - di 3/15/97"
- 
- 	| brush buff dispToBuff buffToDisplay mapDto32 map32toD prevP p brushToBuff theta buffRect buffSize buffToBuff brushRect delta newBuffRect updateRect |  
- 
- 	"compute color maps if needed"
- 	Display depth <= 8 ifTrue: [
- 		mapDto32 := Color cachedColormapFrom: Display depth to: 32.
- 		map32toD := Color cachedColormapFrom: 32 to: Display depth].
- 
- 	"display 10 different alphas, across top of screen"
- 	buff := Form extent: 500 at 50 depth: 32.
- 	dispToBuff := BitBlt toForm: buff.
- 	dispToBuff colorMap: mapDto32.
- 	dispToBuff copyFrom: (50 at 10 extent: 500 at 50) in: Display to: 0 at 0.
- 	1 to: 10 do: [:i | dispToBuff fill: (50*(i-1)@0 extent: 50 at 50)
- 						fillColor: (Color red alpha: i/10)
- 						rule: Form blend].
- 	buffToDisplay := BitBlt toForm: Display.
- 	buffToDisplay colorMap: map32toD.
- 	buffToDisplay copyFrom: buff boundingBox in: buff to: 50 at 10.
- 
- 	"Create a brush with radially varying alpha"
- 	brush := Form extent: 30 at 30 depth: 32.
- 	1 to: 5 do: 
- 		[:i | brush fillShape: (Form dotOfSize: brush width*(6-i)//5)
- 				fillColor: (Color red alpha: 0.02 * i - 0.01)
- 				at: brush extent // 2].
- 
- 	"Now paint with the brush using alpha blending."
- 	buffSize := 100.
- 	buff := Form extent: brush extent + buffSize depth: 32.  "Travelling 32-bit buffer"
- 	dispToBuff := BitBlt toForm: buff.  "This is from Display to buff"
- 	dispToBuff colorMap: mapDto32.
- 	brushToBuff := BitBlt toForm: buff.  "This is from brush to buff"
- 	brushToBuff sourceForm: brush; sourceOrigin: 0 at 0.
- 	brushToBuff combinationRule: Form blend.
- 	buffToBuff := BitBlt toForm: buff.  "This is for slewing the buffer"
- 
- 	[Sensor yellowButtonPressed] whileFalse:
- 		[prevP := nil.
- 		buffRect := Sensor cursorPoint - (buffSize // 2) extent: buff extent.
- 		dispToBuff copyFrom: buffRect in: Display to: 0 at 0.
- 		[Sensor redButtonPressed] whileTrue:
- 			["Here is the painting loop"
- 			p := Sensor cursorPoint - (brush extent // 2).
- 			(prevP == nil or: [prevP ~= p]) ifTrue:
- 				[prevP == nil ifTrue: [prevP := p].
- 				(p dist: prevP) > buffSize ifTrue:
- 					["Stroke too long to fit in buffer -- clip to buffer,
- 						and next time through will do more of it"
- 					theta := (p-prevP) theta.
- 					p := ((theta cos at theta sin) * buffSize asFloat + prevP) truncated].
- 				brushRect := p extent: brush extent.
- 				(buffRect containsRect: brushRect) ifFalse:
- 					["Brush is out of buffer region.  Scroll the buffer,
- 						and fill vacated regions from the display"
- 					delta := brushRect amountToTranslateWithin: buffRect.
- 					buffToBuff copyFrom: buff boundingBox in: buff to: delta.
- 					newBuffRect := buffRect translateBy: delta negated.
- 					(newBuffRect areasOutside: buffRect) do:
- 						[:r | dispToBuff copyFrom: r in: Display to: r origin - newBuffRect origin].
- 					buffRect := newBuffRect].
- 
- 				"Interpolate from prevP to p..."
- 				brushToBuff drawFrom: prevP - buffRect origin
- 									to: p - buffRect origin
- 									withFirstPoint: false.
- 
- 				"Update (only) the altered pixels of the destination"
- 				updateRect := (p min: prevP) corner: (p max: prevP) + brush extent.
- 				buffToDisplay copy: updateRect from: updateRect origin - buffRect origin in: buff.
- 				prevP := p]]]!

Item was removed:
- ----- Method: BitBlt class>>antiAliasDemo (in category 'examples') -----
- antiAliasDemo 
- 	"To run this demo, use...
- 		Display restoreAfter: [BitBlt antiAliasDemo]
- 	Goes immediately into on-screen paint mode.  Option-Click to stop painting."
- 
- 	"This code exhibits alpha blending in any display depth by performing
- 	the blend in an off-screen buffer with 32-bit pixels, and then copying
- 	the result back onto the screen with an appropriate color map. - tk 3/10/97"
- 	
- 	"This version uses a sliding buffer for painting that keeps pixels in 32 bits
- 	as long as they are in the buffer, so as not to lose info by converting down
- 	to display resolution and back up to 32 bits at each operation. - di 3/15/97"
- 	
- 	"This version also uses WarpBlt to paint into twice as large a buffer,
- 	and then use smoothing when reducing back down to the display.
- 	In fact this same routine will now work for 3x3 soothing as well.
- 	Remove the statements 'buff displayAt: 0 at 0' to hide the buffer. - di 3/19/97"
- 
- 	| brush buff dispToBuff buffToDisplay mapDto32 map32toD prevP p brushToBuff theta buffRect buffSize buffToBuff brushRect delta newBuffRect updateRect scale p0 |  
- 	"compute color maps if needed"
- 	Display depth <= 8 ifTrue: [
- 		mapDto32 := Color cachedColormapFrom: Display depth to: 32.
- 		map32toD := Color cachedColormapFrom: 32 to: Display depth].
- 
- 	"Create a brush with radially varying alpha"
- 	brush := Form extent: 3 at 3 depth: 32.
- 	brush fill: brush boundingBox fillColor: (Color red alpha: 0.05).
- 	brush fill: (1 at 1 extent: 1 at 1) fillColor: (Color red alpha: 0.2).
- 
- 	scale := 2.  "Actual drawing happens at this magnification"
- 	"Scale brush up for painting in magnified buffer"
- 	brush := brush magnify: brush boundingBox by: scale.
- 
- 	"Now paint with the brush using alpha blending."
- 	buffSize := 100.
- 	buff := Form extent: (brush extent + buffSize) * scale depth: 32.  "Travelling 32-bit buffer"
- 	dispToBuff := (WarpBlt toForm: buff)  "From Display to buff - magnify by 2"
- 		sourceForm: Display;
- 		colorMap: mapDto32;
- 		combinationRule: Form over.
- 	brushToBuff := (BitBlt toForm: buff)  "From brush to buff"
- 		sourceForm: brush;
- 		sourceOrigin: 0 at 0;
- 		combinationRule: Form blend.
- 	buffToDisplay := (WarpBlt toForm: Display)  "From buff to Display - shrink by 2"
- 		sourceForm: buff;
- 		colorMap: map32toD;
- 		cellSize: scale;  "...and use smoothing"
- 		combinationRule: Form over.
- 	buffToBuff := BitBlt toForm: buff.  "This is for slewing the buffer"
- 
- 	[Sensor yellowButtonPressed] whileFalse:
- 		[prevP := nil.
- 		buffRect := Sensor cursorPoint - (buff extent // scale // 2) extent: buff extent // scale.
- 		p0 := (buff extent // 2) - (buffRect extent // 2).
- 		dispToBuff copyQuad: buffRect innerCorners toRect: buff boundingBox.
- buff displayAt: 0 at 0.  "** remove to hide sliding buffer **"
- 		[Sensor redButtonPressed] whileTrue:
- 			["Here is the painting loop"
- 			p := Sensor cursorPoint - buffRect origin + p0.  "p, prevP are rel to buff origin"
- 			(prevP == nil or: [prevP ~= p]) ifTrue:
- 				[prevP == nil ifTrue: [prevP := p].
- 				(p dist: prevP) > (buffSize-1) ifTrue:
- 					["Stroke too long to fit in buffer -- clip to buffer,
- 						and next time through will do more of it"
- 					theta := (p-prevP) theta.
- 					p := ((theta cos at theta sin) * (buffSize-2) asFloat + prevP) truncated].
- 				brushRect := p extent: brush extent.
- 				((buff boundingBox insetBy: scale) containsRect: brushRect) ifFalse:
- 					["Brush is out of buffer region.  Scroll the buffer,
- 						and fill vacated regions from the display"
- 					delta := (brushRect amountToTranslateWithin: (buff boundingBox insetBy: scale)) // scale.
- 					buffToBuff copyFrom: buff boundingBox in: buff to: delta*scale.
- 					newBuffRect := buffRect translateBy: delta negated.
- 					p := p translateBy: delta*scale.
- 					prevP := prevP translateBy: delta*scale.
- 					(newBuffRect areasOutside: buffRect) do:
- 						[:r | dispToBuff copyQuad: r innerCorners toRect: (r origin - newBuffRect origin*scale extent: r extent*scale)].
- 					buffRect := newBuffRect].
- 
- 				"Interpolate from prevP to p..."
- 				brushToBuff drawFrom: prevP to: p withFirstPoint: false.
- buff displayAt: 0 at 0.  "** remove to hide sliding buffer **"
- 
- 				"Update (only) the altered pixels of the destination"
- 				updateRect := (p min: prevP) corner: (p max: prevP) + brush extent.
- 				updateRect := updateRect origin // scale * scale
- 						corner: updateRect corner + scale // scale * scale.
- 				buffToDisplay copyQuad: updateRect innerCorners
- 							toRect: (updateRect origin // scale + buffRect origin
- 										extent: updateRect extent // scale).
- 				prevP := p]]]!

Item was removed:
- ----- Method: BitBlt class>>benchDiffsFrom:to: (in category 'benchmarks') -----
- benchDiffsFrom: before to: afterwards
- 	"Given two outputs of BitBlt>>benchmark show the relative improvements."
- 	| old new log oldLine newLine oldVal newVal improvement |
- 	log := WriteStream on: String new.
- 	old := ReadStream on: before.
- 	new := ReadStream on: afterwards.
- 	[old atEnd or:[new atEnd]] whileFalse:[
- 		oldLine := old nextLine.
- 		newLine := new nextLine.
- 		(oldLine includes: Character tab) ifTrue:[
- 			oldLine := ReadStream on: oldLine.
- 			newLine := ReadStream on: newLine.
- 			Transcript cr; show: (oldLine upTo: Character tab); tab.
- 			log cr; nextPutAll: (newLine upTo: Character tab); tab.
- 
- 			[oldLine skipSeparators. newLine skipSeparators.
- 			oldLine atEnd] whileFalse:[
- 				oldVal := Integer readFrom: oldLine.
- 				newVal := Integer readFrom: newLine.
- 				improvement := oldVal asFloat / newVal asFloat roundTo: 0.01.
- 				Transcript show: improvement printString; tab; tab.
- 				log print: improvement; tab; tab].
- 		] ifFalse:[
- 			Transcript cr; show: oldLine.
- 			log cr; nextPutAll: oldLine.
- 		].
- 	].
- 	^log contents!

Item was removed:
- ----- Method: BitBlt class>>benchmark (in category 'benchmarks') -----
- benchmark		"BitBlt benchmark"
- 	"Run a benchmark on different combinations rules, source/destination depths and BitBlt modes. Note: This benchmark doesn't give you any 'absolute' value - it is intended only for benchmarking improvements in the bitblt code and nothing else.
- 	Attention: *this*may*take*a*while*"
- 	| destRect log |
- 	log := WriteStream on: String new.
- 	destRect := 0 at 0 extent: 600 at 600.
- 	"Form paint/Form over - the most common rules"
- 	#( 25 3 ) do:[:rule|
- 		Transcript cr; show:'---- Combination rule: ', rule printString,' ----'.
- 		log cr; nextPutAll:'---- Combination rule: ', rule printString,' ----'.
- 		#(1 2 4 8 16 32) do:[:destDepth| | dest |
- 			dest := nil.
- 			dest := Form extent: destRect extent depth: destDepth.
- 			Transcript cr.
- 			log cr.
- 			#(1 2 4 8 16 32) do:[:sourceDepth| | t source bb |
- 				Transcript cr; show: sourceDepth printString, ' => ', destDepth printString.
- 				log cr; nextPutAll: sourceDepth printString, ' => ', destDepth printString.
- 				source := nil. bb := nil.
- 				source := Form extent: destRect extent depth: sourceDepth.
- 				(source getCanvas) fillOval: dest boundingBox color: Color yellow borderWidth: 30 borderColor: Color black.
- 				bb := WarpBlt toForm: dest.
- 				bb sourceForm: source.
- 				bb sourceRect: source boundingBox.
- 				bb destRect: dest boundingBox.
- 				bb colorMap: (source colormapIfNeededFor: dest).
- 				bb combinationRule: rule.
- 
- 				"Measure speed of copyBits"
- 				t := Time millisecondsToRun:[bb copyBits].
- 				Transcript tab; show: t printString.
- 				log tab; nextPutAll: t printString.
- 
- 				bb sourceForm: source destRect: source boundingBox.
- 
- 				"Measure speed of 1x1 warpBits"
- 				bb cellSize: 1.
- 				t := Time millisecondsToRun:[bb warpBits].
- 				Transcript tab; show: t printString.
- 				log tab; nextPutAll: t printString.
- 
- 				"Measure speed of 2x2 warpBits"
- 				bb cellSize: 2.
- 				t := Time millisecondsToRun:[bb warpBits].
- 				Transcript tab; show: t printString.
- 				log tab; nextPutAll: t printString.
- 
- 				"Measure speed of 3x3 warpBits"
- 				bb cellSize: 3.
- 				t := Time millisecondsToRun:[bb warpBits].
- 				Transcript tab; show: t printString.
- 				log tab; nextPutAll: t printString.
- 			].
- 		].
- 	].
- 	^log contents!

Item was removed:
- ----- Method: BitBlt class>>benchmark2 (in category 'benchmarks') -----
- benchmark2		"BitBlt benchmark"
- 	"Run a benchmark on different combinations rules, source/destination depths and BitBlt modes. Note: This benchmark doesn't give you any 'absolute' value - it is intended only for benchmarking improvements in the bitblt code and nothing else.
- 	Attention: *this*may*take*a*while*"
- 	| destRect log |
- 	log := WriteStream on: String new.
- 	destRect := 0 at 0 extent: 600 at 600.
- 	"Form paint/Form over - the most common rules"
- 	#( 25 3 ) do:[:rule|
- 		Transcript cr; show:'---- Combination rule: ', rule printString,' ----'.
- 		log cr; nextPutAll:'---- Combination rule: ', rule printString,' ----'.
- 		#(1 2 4 8 16 32) do:[:destDepth| | dest |
- 			dest := nil.
- 			dest := Form extent: destRect extent depth: destDepth.
- 			Transcript cr.
- 			log cr.
- 			#(1 2 4 8 16 32) do:[:sourceDepth| | t bb source |
- 				Transcript cr; show: sourceDepth printString, ' => ', destDepth printString.
- 				log cr; nextPutAll: sourceDepth printString, ' => ', destDepth printString.
- 				source := nil. bb := nil.
- 				source := Form extent: destRect extent depth: sourceDepth.
- 				(source getCanvas) fillOval: dest boundingBox color: Color yellow borderWidth: 30 borderColor: Color black.
- 				bb := WarpBlt toForm: dest.
- 				bb sourceForm: source.
- 				bb sourceRect: source boundingBox.
- 				bb destRect: dest boundingBox.
- 				bb colorMap: (source colormapIfNeededFor: dest).
- 				bb combinationRule: rule.
- 
- 				"Measure speed of copyBits"
- 				t := Time millisecondsToRun:[1 to: 10 do:[:i| bb copyBits]].
- 				Transcript tab; show: t printString.
- 				log tab; nextPutAll: t printString.
- 
- 				bb sourceForm: source destRect: source boundingBox.
- 
- 				"Measure speed of 1x1 warpBits"
- 				bb cellSize: 1.
- 				t := Time millisecondsToRun:[1 to: 4 do:[:i| bb warpBits]].
- 				Transcript tab; show: t printString.
- 				log tab; nextPutAll: t printString.
- 
- 				"Measure speed of 2x2 warpBits"
- 				bb cellSize: 2.
- 				t := Time millisecondsToRun:[bb warpBits].
- 				Transcript tab; show: t printString.
- 				log tab; nextPutAll: t printString.
- 
- 				"Measure speed of 3x3 warpBits"
- 				bb cellSize: 3.
- 				t := Time millisecondsToRun:[bb warpBits].
- 				Transcript tab; show: t printString.
- 				log tab; nextPutAll: t printString.
- 			].
- 		].
- 	].
- 	^log contents!

Item was removed:
- ----- Method: BitBlt class>>benchmark3 (in category 'benchmarks') -----
- benchmark3		"BitBlt benchmark"
- 	"Run a benchmark on different combinations rules, source/destination depths and BitBlt modes. Note: This benchmark doesn't give you any 'absolute' value - it is intended only for benchmarking improvements in the bitblt code and nothing else.
- 	Attention: *this*may*take*a*while*"
- 	| destRect log |
- 	log := WriteStream on: String new.
- 	destRect := 0 at 0 extent: 600 at 600.
- 	"Form paint/Form over - the most common rules"
- 	#( 25 3 ) do:[:rule|
- 		Transcript cr; show:'---- Combination rule: ', rule printString,' ----'.
- 		log cr; nextPutAll:'---- Combination rule: ', rule printString,' ----'.
- 		#(1 2 4 8 16 32) do:[:destDepth| | dest |
- 			dest := nil.
- 			dest := Form extent: destRect extent depth: destDepth.
- 			Transcript cr.
- 			log cr.
- 			#(1 2 4 8 16 32) do:[:sourceDepth| | t source bb |
- 				Transcript cr; show: sourceDepth printString, ' => ', destDepth printString.
- 				log cr; nextPutAll: sourceDepth printString, ' => ', destDepth printString.
- 				source := nil. bb := nil.
- 				source := Form extent: destRect extent depth: sourceDepth.
- 				(source getCanvas) fillOval: dest boundingBox color: Color yellow borderWidth: 30 borderColor: Color black.
- 				bb := WarpBlt toForm: dest.
- 				bb sourceForm: source.
- 				bb sourceRect: source boundingBox.
- 				bb destRect: dest boundingBox.
- 				bb colorMap: (source colormapIfNeededFor: dest).
- 				bb combinationRule: rule.
- 
- 				"Measure speed of copyBits"
- 				t := Time millisecondsToRun:[1 to: 10 do:[:i| bb copyBits]].
- 				Transcript tab; show: t printString.
- 				log tab; nextPutAll: t printString.
- 
- 				bb sourceForm: source destRect: source boundingBox.
- 
- 				"Measure speed of 1x1 warpBits"
- 				bb cellSize: 1.
- 				t := Time millisecondsToRun:[1 to: 4 do:[:i| bb warpBits]].
- 				Transcript tab; show: t printString.
- 				log tab; nextPutAll: t printString.
- 
- 				"Measure speed of 2x2 warpBits"
- 				bb cellSize: 2.
- 				t := Time millisecondsToRun:[bb warpBits].
- 				Transcript tab; show: t printString.
- 				log tab; nextPutAll: t printString.
- 
- 				"Measure speed of 3x3 warpBits"
- 				bb cellSize: 3.
- 				t := Time millisecondsToRun:[bb warpBits].
- 				Transcript tab; show: t printString.
- 				log tab; nextPutAll: t printString.
- 			].
- 		].
- 	].
- 	^log contents!

Item was removed:
- ----- Method: BitBlt class>>bitPeekerFromForm: (in category 'instance creation') -----
- bitPeekerFromForm: sourceForm
- 	"Answer an instance to be used extract individual pixels from the given Form. The destination for a 1x1 copyBits will be the low order bits of (bits at: 1)."
- 	| pixPerWord |
- 	pixPerWord := 32 // sourceForm depth.
- 	sourceForm unhibernate.
- 	^ self destForm: (Form extent: pixPerWord at 1 depth: sourceForm depth)
- 	 	sourceForm: sourceForm
- 		halftoneForm: nil
- 		combinationRule: Form over
- 		destOrigin: (pixPerWord - 1)@0
- 		sourceOrigin: 0 at 0
- 		extent: 1 at 1
- 		clipRect: (0 at 0 extent: pixPerWord at 1)
- !

Item was removed:
- ----- Method: BitBlt class>>bitPokerToForm: (in category 'instance creation') -----
- bitPokerToForm: destForm
- 	"Answer an instance to be used for valueAt: aPoint put: pixValue.
- 	The source for a 1x1 copyBits will be the low order of (bits at: 1)"
- 	| pixPerWord |
- 	pixPerWord := 32//destForm depth.
- 	destForm unhibernate.
- 	^ self destForm: destForm
- 	 	sourceForm: (Form extent: pixPerWord at 1 depth: destForm depth)
- 		halftoneForm: nil combinationRule: Form over
- 		destOrigin: 0 at 0 sourceOrigin: (pixPerWord-1)@0
- 		extent: 1 at 1 clipRect: (0 at 0 extent: destForm extent)
- !

Item was removed:
- ----- Method: BitBlt class>>cleanUp (in category 'class initialization') -----
- cleanUp
- 	"Flush caches"
- 
- 	self recreateColorMaps.!

Item was removed:
- ----- Method: BitBlt class>>current (in category 'instance creation') -----
- current
- 	"Return the class currently to be used for BitBlt"
- 	^self!

Item was removed:
- ----- Method: BitBlt class>>destForm:sourceForm:fillColor:combinationRule:destOrigin:sourceOrigin:extent:clipRect: (in category 'instance creation') -----
- destForm: df sourceForm: sf fillColor: hf combinationRule: cr destOrigin: destOrigin sourceOrigin: sourceOrigin extent: extent clipRect: clipRect 
- 	"Answer an instance of me with values set according to the arguments."
- 
- 	^ self new
- 		setDestForm: df
- 		sourceForm: sf
- 		fillColor: hf
- 		combinationRule: cr
- 		destOrigin: destOrigin
- 		sourceOrigin: sourceOrigin
- 		extent: extent
- 		clipRect: clipRect!

Item was removed:
- ----- Method: BitBlt class>>destForm:sourceForm:halftoneForm:combinationRule:destOrigin:sourceOrigin:extent:clipRect: (in category 'instance creation') -----
- destForm: df sourceForm: sf halftoneForm: hf combinationRule: cr destOrigin: destOrigin sourceOrigin: sourceOrigin extent: extent clipRect: clipRect 
- 	"Answer an instance of me with values set according to the arguments."
- 
- 	^ self new
- 		setDestForm: df
- 		sourceForm: sf
- 		fillColor: hf
- 		combinationRule: cr
- 		destOrigin: destOrigin
- 		sourceOrigin: sourceOrigin
- 		extent: extent
- 		clipRect: clipRect!

Item was removed:
- ----- Method: BitBlt class>>exampleAt:rule:fillColor: (in category 'private') -----
- exampleAt: originPoint rule: rule fillColor: mask 
- 	"This builds a source and destination form and copies the source to the
- 	destination using the specifed rule and mask. It is called from the method
- 	named exampleOne. Only works with Display depth of 1"
- 
- 	^self exampleOn: Display at: originPoint rule: rule fillColor: mask
- 
- 	"BitBlt exampleAt: 100 at 100 rule: 0 fillColor: nil"!

Item was removed:
- ----- Method: BitBlt class>>exampleColorMap (in category 'examples') -----
- exampleColorMap	"BitBlt exampleColorMap"
- 	"This example shows what one can do with the fixed part of a color map. The color map, as setup below, rotates the bits of a pixel all the way around. Thus you'll get a (sometime strange looking ;-) animation of colors which will end up exactly the way it looked at the beginning. The example is given to make you understand that the masks and shifts can be used for a lot more than simply color converting pixels. In this example, for instance, we use only two of the four independent shifters."
- 	| cc bb |
- 	cc := ColorMap masks: {
- 		1 << (Display depth-1). "mask out high bit of color component"
- 		1 << (Display depth-1) - 1. "mask all other bits"
- 		0.
- 		0}
- 		shifts: {
- 			1 - Display depth. "shift right to bottom most position"
- 			1. "shift all other pixels one bit left"
- 			0.
- 			0}.
- 	bb := BitBlt toForm: Display.
- 	bb 
- 		sourceForm: Display;
- 		combinationRule: 3;
- 		colorMap: cc.
- 	1 to: Display depth do:[:i|
- 		bb copyBits.
- 		Display forceDisplayUpdate.
- 	].
- !

Item was removed:
- ----- Method: BitBlt class>>exampleOn:at:rule:fillColor: (in category 'private') -----
- exampleOn: destinationForm at: originPoint rule: rule fillColor: mask 
- 	"This builds a source and destination form and copies the source to the
- 	destination using the specifed rule and mask. It is called from the method
- 	named exampleOne. Only works with Display depth of 1"
- 
- 	| s d border aBitBlt | 
- 	border:=Form extent: 32 at 32.
- 	border fillBlack.
- 	border fill: (1 at 1 extent: 30 at 30) fillColor: Color white.
- 	s := Form extent: 32 at 32.
- 	s fillWhite.
- 	s fillBlack: (7 at 7 corner: 25 at 25).
- 	d := Form extent: 32 at 32.
- 	d fillWhite.
- 	d fillBlack: (0 at 0 corner: 32 at 16).
- 
- 	s displayOn: destinationForm at: originPoint.
- 	border displayOn: destinationForm at: originPoint rule: Form under.
- 	d displayOn: destinationForm at: originPoint + (s width @0).
- 	border displayOn: destinationForm at: originPoint + (s width @0) rule: Form under.
- 
- 	d displayOn: destinationForm at: originPoint + (s extent // (2 @ 1)). 
- 	aBitBlt := BitBlt
- 				destForm: destinationForm
- 				sourceForm: s
- 				fillColor: mask
- 				combinationRule: rule
- 				destOrigin: originPoint + (s extent // (2 @ 1))
- 				sourceOrigin: 0 @ 0
- 				extent: s extent
- 				clipRect: destinationForm computeBoundingBox.
- 	aBitBlt copyBits.
- 	border 
- 		displayOn: destinationForm at: originPoint + (s extent // (2 @ 1))
- 		rule: Form under.
- 
- 	"BitBlt exampleOn: Display at: 100 at 100 rule: 0 fillColor: nil"  !

Item was removed:
- ----- Method: BitBlt class>>exampleOne (in category 'examples') -----
- exampleOne
- 	"This tests BitBlt by displaying the result of all sixteen combination rules that BitBlt is capable of using. (Please see the comment in BitBlt for the meaning of the combination rules). This only works at Display depth of 1. (Rule 15 does not work?)"
- 	| pathClass path displayDepth destination |
- 
- 	(Display supportsDisplayDepth: 1)
- 		ifTrue:
- 			[displayDepth := Display depth.
- 			 Display newDepth: 1.
- 			 destination := Display]
- 		ifFalse:
- 			[destination := Form extent: 480 @ 400 depth: 1].
- 
- 	(Smalltalk hasClassNamed: #Path)
- 		ifTrue: [pathClass := Smalltalk at: #Path]
- 		ifFalse: [^self inform: 'MVC class Path not present in this image'].
- 	path := pathClass new.
- 	0 to: 3 do: [:i | 0 to: 3 do: [:j | path add: j * 100 @ (i * 75)]].
- 	destination fillWhite.
- 	path := path translateBy: 60 @ 40.
- 	1 to: 16 do:
- 		[:index |
- 		BitBlt
- 			exampleOn: destination
- 			at: (path at: index)
- 			rule: index - 1
- 			fillColor: nil].
- 
- 	destination ~~ Display ifTrue:
- 		[destination displayOn: Display at: 0 asPoint].
- 	[Sensor anyButtonPressed] whileFalse: [].
- 	displayDepth ifNotNil: [Display newDepth: displayDepth].
- 
- 	"BitBlt exampleOne"!

Item was removed:
- ----- Method: BitBlt class>>exampleTwo (in category 'examples') -----
- exampleTwo
- 	"This is to test painting with a gray tone. It also tests that the seaming with gray patterns is correct in the microcode. Lets you paint for a while and then automatically stops. This only works at Depth of 1."
- 	| f aBitBlt displayDepth |
- 	"create a small black Form source as a brush. "
- 	displayDepth := Display depth.
- 	Display newDepth: 1.
- 	f := Form extent: 20 @ 20.
- 	f fillBlack.
- 	"create a BitBlt which will OR gray into the display. "
- 	aBitBlt := BitBlt
- 		destForm: Display
- 		sourceForm: f
- 		fillColor: Color gray
- 		combinationRule: Form over
- 		destOrigin: Sensor cursorPoint
- 		sourceOrigin: 0 @ 0
- 		extent: f extent
- 		clipRect: Display computeBoundingBox.
- 	"paint the gray Form on the screen for a while. "
- 	[Sensor anyButtonPressed] whileFalse: 
- 		[aBitBlt destOrigin: Sensor cursorPoint.
- 		aBitBlt copyBits].
- 	Display newDepth: displayDepth.
- 	"BitBlt exampleTwo"!

Item was removed:
- ----- Method: BitBlt class>>initialize (in category 'class initialization') -----
- initialize
- 	self recreateColorMaps!

Item was removed:
- ----- Method: BitBlt class>>recreateColorMaps (in category 'private') -----
- recreateColorMaps
- 	CachedFontColorMaps := ColorConvertingMaps := nil!

Item was removed:
- ----- Method: BitBlt class>>subPixelRenderColorFonts (in category 'preferences') -----
- subPixelRenderColorFonts
- 
- 	<preference: 'Subpixel font rendering for color fonts'
- 	category: 'Graphics'
- 	description: 'If true, non-black opaque fonts are rendered using subpixel combination rules by BitBlt. Subpixel font rendering has to be enabled to take effect.'
- 	type: #Boolean>
- 	^SubPixelRenderColorFonts ifNil: [ true ]
- 
- 	!

Item was removed:
- ----- Method: BitBlt class>>subPixelRenderColorFonts: (in category 'preferences') -----
- subPixelRenderColorFonts: aBoolean
- 
- 	SubPixelRenderColorFonts := aBoolean
- 
- 	!

Item was removed:
- ----- Method: BitBlt class>>subPixelRenderFonts (in category 'preferences') -----
- subPixelRenderFonts
- 
- 	<preference: 'Subpixel font rendering'
- 	category: 'Graphics'
- 	description: 'If true, black fonts are rendered using subpixel combination rules by BitBlt.'
- 	type: #Boolean>
- 	^SubPixelRenderFonts ifNil: [ true ]
- 
- 	!

Item was removed:
- ----- Method: BitBlt class>>subPixelRenderFonts: (in category 'preferences') -----
- subPixelRenderFonts: aBoolean
- 
- 	SubPixelRenderFonts := aBoolean
- 
- 	!

Item was removed:
- ----- Method: BitBlt class>>toForm: (in category 'instance creation') -----
- toForm: aForm
- 	^ self new setDestForm: aForm!

Item was removed:
- ----- Method: BitBlt>>basicDisplayString:from:to:at:strikeFont:kern: (in category 'copying') -----
- basicDisplayString: aString from: startIndex to: stopIndex at: aPoint strikeFont: font kern: kernDelta
- 
- 	destY := aPoint y.
- 	destX := aPoint x.
- 
- 	"the following are not really needed, but theBitBlt primitive will fail if not set"
- 	sourceX ifNil: [sourceX := 100].
- 	width ifNil: [width := 100].
- 
- 	self primDisplayString: aString from: startIndex to: stopIndex
- 			map: font characterToGlyphMap xTable: font xTable
- 			kern: kernDelta.
- 	^ destX at destY.
- !

Item was removed:
- ----- Method: BitBlt>>cachedFontColormapFrom:to: (in category 'private') -----
- cachedFontColormapFrom: sourceDepth to: destDepth
- 
- 	| srcIndex map |
- 	CachedFontColorMaps class == Array 
- 		ifFalse: [CachedFontColorMaps := (1 to: 9) collect: [:i | Array new: 32]].
- 	srcIndex := sourceDepth.
- 	sourceDepth > 8 ifTrue: [srcIndex := 9].
- 	(map := (CachedFontColorMaps at: srcIndex) at: destDepth) ~~ nil ifTrue: [^ map].
- 
- 	map := (Color cachedColormapFrom: sourceDepth to: destDepth) copy.
- 	(CachedFontColorMaps at: srcIndex) at: destDepth put: map.
- 	^ map
- !

Item was removed:
- ----- Method: BitBlt>>clipBy: (in category 'accessing') -----
- clipBy: aRectangle
- 	| aPoint right bottom |
- 	right := clipX + clipWidth.
- 	bottom := clipY + clipHeight.
- 	aPoint := aRectangle origin.
- 	aPoint x > clipX ifTrue:[clipX := aPoint x].
- 	aPoint y > clipY ifTrue:[clipY := aPoint y].
- 	aPoint := aRectangle corner.
- 	aPoint x < right ifTrue:[right := aPoint x].
- 	aPoint y < bottom ifTrue:[bottom := aPoint y].
- 	clipWidth := right - clipX.
- 	clipHeight := bottom - clipY.
- 	clipWidth < 0 ifTrue:[clipWidth := 0].
- 	clipHeight < 0 ifTrue:[clipHeight := 0].!

Item was removed:
- ----- Method: BitBlt>>clipByX1:y1:x2:y2: (in category 'accessing') -----
- clipByX1: x1 y1: y1 x2: x2 y2: y2
- 	| right bottom |
- 	right := clipX + clipWidth.
- 	bottom := clipY + clipHeight.
- 	x1 > clipX ifTrue:[clipX := x1].
- 	y1 > clipY ifTrue:[clipY := y1].
- 	x2 < right ifTrue:[right := x2].
- 	y2 < bottom ifTrue:[bottom := y2].
- 	clipWidth := right - clipX.
- 	clipHeight := bottom - clipY.
- 	clipWidth < 0 ifTrue:[clipWidth := 0].
- 	clipHeight < 0 ifTrue:[clipHeight := 0].!

Item was removed:
- ----- Method: BitBlt>>clipHeight (in category 'accessing') -----
- clipHeight
- 	^clipHeight!

Item was removed:
- ----- Method: BitBlt>>clipHeight: (in category 'accessing') -----
- clipHeight: anInteger 
- 	"Set the receiver's clipping area height to be the argument, anInteger."
- 
- 	clipHeight := anInteger!

Item was removed:
- ----- Method: BitBlt>>clipRange (in category 'private') -----
- clipRange
- 	"clip and adjust source origin and extent appropriately"
- 	"first in x"
- 	| sx sy dx dy bbW bbH |
- 	"fill in the lazy state if needed"
- 	destX ifNil:[destX := 0].
- 	destY ifNil:[destY := 0].
- 	width ifNil:[width := destForm width].
- 	height ifNil:[height := destForm height].
- 	sourceX ifNil:[sourceX := 0].
- 	sourceY ifNil:[sourceY := 0].
- 	clipX ifNil:[clipX := 0].
- 	clipY ifNil:[clipY := 0].
- 	clipWidth ifNil:[clipWidth := destForm width].
- 	clipHeight ifNil:[clipHeight := destForm height].
- 
- 	destX >= clipX
- 		ifTrue: [sx := sourceX.
- 				dx := destX.
- 				bbW := width]
- 		ifFalse: [sx := sourceX + (clipX - destX).
- 				bbW := width - (clipX - destX).
- 				dx := clipX].
- 	(dx + bbW) > (clipX + clipWidth)
- 		ifTrue: [bbW := bbW - ((dx + bbW) - (clipX + clipWidth))].
- 	"then in y"
- 	destY >= clipY
- 		ifTrue: [sy := sourceY.
- 				dy := destY.
- 				bbH := height]
- 		ifFalse: [sy := sourceY + clipY - destY.
- 				bbH := height - (clipY - destY).
- 				dy := clipY].
- 	(dy + bbH) > (clipY + clipHeight)
- 		ifTrue: [bbH := bbH - ((dy + bbH) - (clipY + clipHeight))].
- 	sourceForm ifNotNil:[
- 		sx < 0
- 			ifTrue: [dx := dx - sx.
- 					bbW := bbW + sx.
- 					sx := 0].
- 		sx + bbW > sourceForm width
- 			ifTrue: [bbW := bbW - (sx + bbW - sourceForm width)].
- 		sy < 0
- 			ifTrue: [dy := dy - sy.
- 					bbH := bbH + sy.
- 					sy := 0].
- 		sy + bbH > sourceForm height
- 			ifTrue: [bbH := bbH - (sy + bbH - sourceForm height)].
- 	].
- 	(bbW <= 0 or:[bbH <= 0]) ifTrue:[
- 		sourceX := sourceY := destX := destY := clipX := clipY := width := height := clipWidth := clipHeight := 0.
- 		^true].
- 	(sx = sourceX 
- 		and:[sy = sourceY 
- 		and:[dx = destX 
- 		and:[dy = destY 
- 		and:[bbW = width 
- 		and:[bbH = height]]]]]) ifTrue:[^false].
- 	sourceX := sx.
- 	sourceY := sy.
- 	destX := dx.
- 	destY := dy.
- 	width := bbW.
- 	height := bbH.
- 	^true!

Item was removed:
- ----- Method: BitBlt>>clipRect (in category 'accessing') -----
- clipRect
- 	"Answer the receiver's clipping area rectangle."
- 
- 	^clipX @ clipY extent: clipWidth @ clipHeight!

Item was removed:
- ----- Method: BitBlt>>clipRect: (in category 'accessing') -----
- clipRect: aRectangle 
- 	"Set the receiver's clipping area rectangle to be the argument, aRectangle."
- 
- 	clipX := aRectangle left truncated.
- 	clipY := aRectangle top truncated.
- 	clipWidth := aRectangle right truncated - clipX.
- 	clipHeight := aRectangle bottom truncated - clipY.!

Item was removed:
- ----- Method: BitBlt>>clipWidth (in category 'accessing') -----
- clipWidth
- 	^clipWidth!

Item was removed:
- ----- Method: BitBlt>>clipWidth: (in category 'accessing') -----
- clipWidth: anInteger 
- 	"Set the receiver's clipping area width to be the argument, anInteger."
- 
- 	clipWidth := anInteger!

Item was removed:
- ----- Method: BitBlt>>clipX (in category 'accessing') -----
- clipX
- 	^clipX!

Item was removed:
- ----- Method: BitBlt>>clipX: (in category 'accessing') -----
- clipX: anInteger 
- 	"Set the receiver's clipping area top left x coordinate to be the argument, 
- 	anInteger."
- 
- 	clipX := anInteger!

Item was removed:
- ----- Method: BitBlt>>clipY (in category 'accessing') -----
- clipY
- 	^clipY!

Item was removed:
- ----- Method: BitBlt>>clipY: (in category 'accessing') -----
- clipY: anInteger 
- 	"Set the receiver's clipping area top left y coordinate to be the argument, 
- 	anInteger."
- 
- 	clipY := anInteger!

Item was removed:
- ----- Method: BitBlt>>color (in category 'accessing') -----
- color
- 	"Return the current fill color as a Color.  
- 	 Gives the wrong answer if the halftoneForm is a complex pattern of more than one word."
- 
- 	halftoneForm ifNil: [^ Color black].
- 	^ Color colorFromPixelValue: halftoneForm first depth: destForm depth!

Item was removed:
- ----- Method: BitBlt>>colorConvertingMap:from:to:keepSubPixelAA: (in category 'private') -----
- colorConvertingMap: targetColor from: sourceDepth to: destDepth keepSubPixelAA: keepSubPix
- 
- 	| srcIndex map mapsForSource mapsForSourceAndDest |
- 	ColorConvertingMaps class == Array 
- 		ifFalse: [ColorConvertingMaps := (1 to: 10) collect: [:i | Array new: 32]].
- 		
- 	srcIndex := sourceDepth.
- 	sourceDepth > 8 ifTrue: [ srcIndex := keepSubPix ifTrue: [9] ifFalse: [10] ].
- 	mapsForSource := ColorConvertingMaps at: srcIndex.
- 	mapsForSourceAndDest := (mapsForSource at: destDepth) ifNil: [ mapsForSource at: destDepth put: Dictionary new ].
- 	
- 	map := mapsForSourceAndDest at: targetColor ifAbsentPut: [
- 		Color computeColorConvertingMap: targetColor from: sourceDepth to: destDepth keepSubPixelAA: keepSubPix ].
- 
- 	^ map!

Item was removed:
- ----- Method: BitBlt>>colorMap (in category 'accessing') -----
- colorMap
- 	^ colorMap!

Item was removed:
- ----- Method: BitBlt>>colorMap: (in category 'accessing') -----
- colorMap: map
- 	"See last part of BitBlt comment. 6/18/96 tk"
- 	colorMap := map.!

Item was removed:
- ----- Method: BitBlt>>combinationRule (in category 'accessing') -----
- combinationRule
- 	"Answer the receiver's combinationRule"
- 	
- 	^combinationRule!

Item was removed:
- ----- Method: BitBlt>>combinationRule: (in category 'accessing') -----
- combinationRule: anInteger 
- 	"Set the receiver's combination rule to be the argument, anInteger, a 
- 	number in the range 0-15."
- 
- 	combinationRule := anInteger!

Item was removed:
- ----- Method: BitBlt>>copy:from:in: (in category 'copying') -----
- copy: destRectangle from: sourcePt in: srcForm
- 	| destOrigin |
- 	sourceForm := srcForm.
- 	halftoneForm := nil.
- 	combinationRule := 3.  "store"
- 	destOrigin := destRectangle origin.
- 	destX := destOrigin x.
- 	destY := destOrigin y.
- 	sourceX := sourcePt x.
- 	sourceY := sourcePt y.
- 	width := destRectangle width.
- 	height := destRectangle height.
- 	self copyBits!

Item was removed:
- ----- Method: BitBlt>>copy:from:in:fillColor:rule: (in category 'copying') -----
- copy: destRectangle from: sourcePt in: srcForm fillColor: hf rule: rule
- 	"Specify a Color to fill, not a Form. 6/18/96 tk"  
- 	| destOrigin |
- 	sourceForm := srcForm.
- 	self fillColor: hf.	"sets halftoneForm"
- 	combinationRule := rule.
- 	destOrigin := destRectangle origin.
- 	destX := destOrigin x.
- 	destY := destOrigin y.
- 	sourceX := sourcePt x.
- 	sourceY := sourcePt y.
- 	width := destRectangle width.
- 	height := destRectangle height.
- 	srcForm == nil ifFalse:
- 		[colorMap := srcForm colormapIfNeededFor: destForm].
- 	^ self copyBits!

Item was removed:
- ----- Method: BitBlt>>copy:from:in:halftoneForm:rule: (in category 'copying') -----
- copy: destRectangle from: sourcePt in: srcForm halftoneForm: hf rule: rule 
- 	| destOrigin |
- 	sourceForm := srcForm.
- 	self fillColor: hf.		"sets halftoneForm"
- 	combinationRule := rule.
- 	destOrigin := destRectangle origin.
- 	destX := destOrigin x.
- 	destY := destOrigin y.
- 	sourceX := sourcePt x.
- 	sourceY := sourcePt y.
- 	width := destRectangle width.
- 	height := destRectangle height.
- 	self copyBits!

Item was removed:
- ----- Method: BitBlt>>copyBits (in category 'copying') -----
- copyBits
- 	"Primitive. Perform the movement of bits from the source form to the 
- 	destination form. Fail if any variables are not of the right type (Integer, 
- 	Float, or Form) or if the combination rule is not implemented. 
- 
- 	NOTE THAT this method has the side effect of showing the copied bits on
- 	screen if the destination form happens to be Display. The mechanism is
- 	similar to calling #primShowRectLeft:right:top:bottom: manually.
- 
- 	In addition to the original 16 combination rules, this BitBlt supports
- 	16	fail (to simulate paint)
- 	17	fail (to simulate mask)
- 	18	sourceWord + destinationWord
- 	19	sourceWord - destinationWord
- 	20	rgbAdd: sourceWord with: destinationWord
- 	21	rgbSub: sourceWord with: destinationWord
- 	22	rgbDiff: sourceWord with: destinationWord
- 	23	tallyIntoMap: destinationWord
- 	24	alphaBlend: sourceWord with: destinationWord
- 	25	pixPaint: sourceWord with: destinationWord
- 	26	pixMask: sourceWord with: destinationWord
- 	27	rgbMax: sourceWord with: destinationWord
- 	28	rgbMin: sourceWord with: destinationWord
- 	29	rgbMin: sourceWord bitInvert32 with: destinationWord
- "
- 	<primitive: 'primitiveCopyBits' module: 'BitBltPlugin' error: ec>
- 
- 	(combinationRule >= 30 and: [combinationRule <= 31]) ifTrue:
- 		["No alpha specified -- re-run with alpha = 1.0"
- 		^ self copyBitsTranslucent: 255].
- 	"Check for object movement during a surface callback, compressed source, destination or halftone forms.
- 	 Simply retry."
- 	(ec == #'object moved'
- 	 or: [(sourceForm isForm and: [sourceForm unhibernate])
- 	 or: [(destForm isForm and: [destForm unhibernate])
- 	 or: [halftoneForm isForm and: [halftoneForm unhibernate]]]]) ifTrue:
- 		[^self copyBits].
- 
- 	"Check for unimplmented rules"
- 	combinationRule = Form oldPaint ifTrue: [^self paintBits].
- 	combinationRule = Form oldErase1bitShape ifTrue: [^self eraseBits].
- 
- 	"Check if BitBlt doesn't support full color maps"
- 	(colorMap notNil and: [colorMap isColormap]) ifTrue:
- 		[colorMap := colorMap colors.
- 		^self copyBits].
- 	"Check if clipping got way out of range"
- 	self clipRange.
- 	"Convert all numeric parameters to integers and try again."
- 	self roundVariables.
- 	^self copyBitsAgain!

Item was removed:
- ----- Method: BitBlt>>copyBitsAgain (in category 'private') -----
- copyBitsAgain
- 	"Primitive. See BitBlt|copyBits, also a Primitive. Essential. See Object
- 	documentation whatIsAPrimitive."
- 
- 	<primitive: 'primitiveCopyBits' module: 'BitBltPlugin' error: ec>
- 	self primitiveFailed!

Item was removed:
- ----- Method: BitBlt>>copyBitsFrom:to:at: (in category 'private') -----
- copyBitsFrom: x0 to: x1 at: y
- 	destX := x0.
- 	destY := y.
- 	sourceX := x0.
- 	width := (x1 - x0).
- 	self copyBits.!

Item was removed:
- ----- Method: BitBlt>>copyBitsTranslucent: (in category 'copying') -----
- copyBitsTranslucent: factor
- 	"This entry point to BitBlt supplies an extra argument to specify translucency
- 	for operations 30 and 31.  The argument must be an integer between 0 and 255."
- 
- 	<primitive: 'primitiveCopyBits' module: 'BitBltPlugin'>
- 
- 	"Check for compressed source, destination or halftone forms"
- 	((sourceForm isForm) and: [sourceForm unhibernate])
- 		ifTrue: [^ self copyBitsTranslucent: factor].
- 	((destForm isForm) and: [destForm unhibernate])
- 		ifTrue: [^ self copyBitsTranslucent: factor].
- 	((halftoneForm isForm) and: [halftoneForm unhibernate])
- 		ifTrue: [^ self copyBitsTranslucent: factor].
- 
- 	self primitiveFailed  "Later do nicer error recovery -- share copyBits recovery"!

Item was removed:
- ----- Method: BitBlt>>copyForm:to:rule: (in category 'copying') -----
- copyForm: srcForm to: destPt rule: rule
- 	^ self copyForm: srcForm to: destPt rule: rule
- 		colorMap: (srcForm colormapIfNeededFor: destForm)!

Item was removed:
- ----- Method: BitBlt>>copyForm:to:rule:color: (in category 'copying') -----
- copyForm: srcForm to: destPt rule: rule color: color
- 	sourceForm := srcForm.
- 	halftoneForm := color.
- 	combinationRule := rule.
- 	destX := destPt x + sourceForm offset x.
- 	destY := destPt y + sourceForm offset y.
- 	sourceX := 0.
- 	sourceY := 0.
- 	width := sourceForm width.
- 	height := sourceForm height.
- 	self copyBits!

Item was removed:
- ----- Method: BitBlt>>copyForm:to:rule:colorMap: (in category 'copying') -----
- copyForm: srcForm to: destPt rule: rule colorMap: map
- 	sourceForm := srcForm.
- 	halftoneForm := nil.
- 	combinationRule := rule.
- 	destX := destPt x + sourceForm offset x.
- 	destY := destPt y + sourceForm offset y.
- 	sourceX := 0.
- 	sourceY := 0.
- 	width := sourceForm width.
- 	height := sourceForm height.
- 	colorMap := map.
- 	self copyBits!

Item was removed:
- ----- Method: BitBlt>>copyForm:to:rule:fillColor: (in category 'copying') -----
- copyForm: srcForm to: destPt rule: rule fillColor: color
- 	sourceForm := srcForm.
- 	self fillColor: color.	"sets halftoneForm"
- 	combinationRule := rule.
- 	destX := destPt x + sourceForm offset x.
- 	destY := destPt y + sourceForm offset y.
- 	sourceX := 0.
- 	sourceY := 0.
- 	width := sourceForm width.
- 	height := sourceForm height.
- 	self copyBits!

Item was removed:
- ----- Method: BitBlt>>copyFrom:in:to: (in category 'copying') -----
- copyFrom: sourceRectangle in: srcForm to: destPt
- 	| sourceOrigin |
- 	sourceForm := srcForm.
- 	halftoneForm := nil.
- 	combinationRule := 3.  "store"
- 	destX := destPt x.
- 	destY := destPt y.
- 	sourceOrigin := sourceRectangle origin.
- 	sourceX := sourceOrigin x.
- 	sourceY := sourceOrigin y.
- 	width := sourceRectangle width.
- 	height := sourceRectangle height.
- 	colorMap := srcForm colormapIfNeededFor: destForm.
- 	self copyBits!

Item was removed:
- ----- Method: BitBlt>>destForm (in category 'accessing') -----
- destForm
- 	^ destForm!

Item was removed:
- ----- Method: BitBlt>>destOrigin: (in category 'accessing') -----
- destOrigin: aPoint 
- 	"Set the receiver's destination top left coordinates to be those of the 
- 	argument, aPoint."
- 
- 	destX := aPoint x.
- 	destY := aPoint y!

Item was removed:
- ----- Method: BitBlt>>destRect (in category 'accessing') -----
- destRect
- 	"The rectangle we are about to blit to or just blitted to.  "
- 
- 	^ destX @ destY extent: width @ height!

Item was removed:
- ----- Method: BitBlt>>destRect: (in category 'accessing') -----
- destRect: aRectangle 
- 	"Set the receiver's destination form top left coordinates to be the origin of 
- 	the argument, aRectangle, and set the width and height of the receiver's 
- 	destination form to be the width and height of aRectangle."
- 
- 	destX := aRectangle left.
- 	destY := aRectangle top.
- 	width := aRectangle width.
- 	height := aRectangle height!

Item was removed:
- ----- Method: BitBlt>>destX: (in category 'accessing') -----
- destX: anInteger 
- 	"Set the top left x coordinate of the receiver's destination form to be the 
- 	argument, anInteger."
- 
- 	destX := anInteger!

Item was removed:
- ----- Method: BitBlt>>destX:destY:width:height: (in category 'accessing') -----
- destX: x destY: y width: w height: h
- 	"Combined init message saves 3 sends from DisplayScanner"
- 	destX := x.
- 	destY := y.
- 	width := w.
- 	height := h.!

Item was removed:
- ----- Method: BitBlt>>destY: (in category 'accessing') -----
- destY: anInteger 
- 	"Set the top left y coordinate of the receiver's destination form to be the 
- 	argument, anInteger."
- 
- 	destY := anInteger!

Item was removed:
- ----- Method: BitBlt>>displayGlyph:at:left:right:font: (in category 'copying') -----
- displayGlyph: aForm at: aPoint left: leftX right: rightX font: aFont
- 	"Display a glyph in a multi-lingual font. Do 2 pass rendering if necessary.
- 	This happens when #installStrikeFont:foregroundColor:backgroundColor: sets rule 37 (rgbMul).
- 	the desired effect is to do two bitblt calls. The first one is with rule 37 and special colormap.
- 	The second one is rule 34, with a colormap for applying the requested foreground color.
- 	This two together do component alpha blending, i.e. alpha blend red, green and blue separatedly.
- 	This is needed for arbitrary color over abitrary background text with subpixel AA."
- 
- 	| prevRule secondPassMap |
- 	self sourceForm: aForm.
- 	destX := aPoint x.
- 	destY := aPoint y.
- 	sourceX := leftX.
- 	sourceY := 0.
- 	width := rightX - leftX.
- 	height := aFont height.
- 	combinationRule = 37 ifTrue:[
- 		"We need to do a second pass. The colormap set is for use in the second pass."
- 		secondPassMap := colorMap.
- 		colorMap := sourceForm depth = destForm depth
- 			ifFalse: [ self cachedFontColormapFrom: sourceForm depth to: destForm depth ].
- 		self copyBits.
- 		prevRule := combinationRule.
- 		combinationRule := 20. "rgbAdd"
- 		colorMap := secondPassMap.
- 		self copyBits.
- 		combinationRule := prevRule.
- 	] ifFalse:[self copyBits].!

Item was removed:
- ----- Method: BitBlt>>displayString:from:to:at:strikeFont:kern: (in category 'copying') -----
- displayString: aString from: startIndex to: stopIndex at: aPoint strikeFont: font kern: kernDelta
- 	"If required, do a second pass with new rule and colorMap.
- 	This happens when #installStrikeFont:foregroundColor:backgroundColor: sets rule 37 (rgbMul).
- 	the desired effect is to do two bitblt calls. The first one is with rule 37 and special colormap.
- 	The second one is rule 34, with a colormap for applying the requested foreground color.
- 	This two together do component alpha blending, i.e. alpha blend red, green and blue separatedly.
- 	This is needed for arbitrary color over abitrary background text with subpixel AA."
- 
- 	| answer prevRule secondPassMap |
- 	"If combinationRule is rgbMul, we might need the special two-pass technique for component alpha blending.
- 	If not, do it simply"
- 	combinationRule = 37 "rgbMul" ifFalse: [
- 		^self basicDisplayString: aString from: startIndex to: stopIndex at: aPoint strikeFont: font kern: kernDelta ].
- 	
- 	"We need to do a second pass. The colormap set is for use in the second pass."
- 	secondPassMap := colorMap.
- 	colorMap := sourceForm depth ~= destForm depth
- 		ifTrue: [ self cachedFontColormapFrom: sourceForm depth to: destForm depth ].
- 	answer := self basicDisplayString: aString from: startIndex to: stopIndex at: aPoint strikeFont: font kern: kernDelta.
- 	colorMap := secondPassMap.
- 	secondPassMap ifNotNil: [
- 		prevRule := combinationRule.
- 		combinationRule := 20. "rgbAdd"
- 		self basicDisplayString: aString from: startIndex to: stopIndex at: aPoint strikeFont: font kern: kernDelta.
- 		combinationRule := prevRule ].
- 	^answer!

Item was removed:
- ----- Method: BitBlt>>drawFrom:to: (in category 'line drawing') -----
- drawFrom: startPoint to: stopPoint 
- 	
- 	 ^ self drawFrom: startPoint to: stopPoint withFirstPoint: true!

Item was removed:
- ----- Method: BitBlt>>drawFrom:to:withFirstPoint: (in category 'line drawing') -----
- drawFrom: startPoint to: stopPoint withFirstPoint: drawFirstPoint
- 	"Draw a line whose end points are startPoint and stopPoint.
- 	The line is formed by repeatedly calling copyBits at every
- 	point along the line.  If drawFirstPoint is false, then omit
- 	the first point so as not to overstrike at line junctions."
- 	| offset point1 point2 forwards |
- 	"Always draw down, or at least left-to-right"
- 	forwards := (startPoint y = stopPoint y and: [startPoint x < stopPoint x])
- 				or: [startPoint y < stopPoint y].
- 	forwards
- 		ifTrue: [point1 := startPoint. point2 := stopPoint]
- 		ifFalse: [point1 := stopPoint. point2 := startPoint].
- 	sourceForm == nil ifTrue:
- 		[destX := point1 x.
- 		destY := point1 y]
- 		ifFalse:
- 		[width := sourceForm width.
- 		height := sourceForm height.
- 		offset := sourceForm offset.
- 		destX := (point1 x + offset x) rounded.
- 		destY := (point1 y + offset y) rounded].
- 
- 	"Note that if not forwards, then the first point is the last and vice versa.
- 	We agree to always paint stopPoint, and to optionally paint startPoint."
- 	(drawFirstPoint or: [forwards == false  "ie this is stopPoint"])
- 		ifTrue: [self copyBits].
- 	self drawLoopX: (point2 x - point1 x) rounded 
- 				  Y: (point2 y - point1 y) rounded.
- 	(drawFirstPoint or: [forwards  "ie this is stopPoint"])
- 		ifTrue: [self copyBits].
- !

Item was removed:
- ----- Method: BitBlt>>drawLoopX:Y: (in category 'line drawing') -----
- drawLoopX: xDelta Y: yDelta 
- 	"Primitive. Implements the Bresenham plotting algorithm (IBM Systems
- 	Journal, Vol. 4 No. 1, 1965). It chooses a principal direction, and
- 	maintains a potential, P. When P's sign changes, it is time to move in
- 	the minor direction as well. This particular version does not write the
- 	first and last points, so that these can be called for as needed in client code.
- 	Optional. See Object documentation whatIsAPrimitive."
- 	| dx dy px py P |
- 	<primitive: 'primitiveDrawLoop' module: 'BitBltPlugin'>
- 	dx := xDelta sign.
- 	dy := yDelta sign.
- 	px := yDelta abs.
- 	py := xDelta abs.
- 	"self copyBits."
- 	py > px
- 		ifTrue: 
- 			["more horizontal"
- 			P := py // 2.
- 			1 to: py do: 
- 				[:i |
- 				destX := destX + dx.
- 				(P := P - px) < 0 ifTrue: 
- 						[destY := destY + dy.
- 						P := P + py].
- 				i < py ifTrue: [self copyBits]]]
- 		ifFalse: 
- 			["more vertical"
- 			P := px // 2.
- 			1 to: px do:
- 				[:i |
- 				destY := destY + dy.
- 				(P := P - py) < 0 ifTrue: 
- 						[destX := destX + dx.
- 						P := P + px].
- 				i < px ifTrue: [self copyBits]]]!

Item was removed:
- ----- Method: BitBlt>>eraseBits (in category 'private') -----
- eraseBits
- 	"Perform the erase operation, which puts 0's in the destination
- 	wherever the source (which is assumed to be just 1 bit deep)
- 	has a 1.  This requires the colorMap to be set in order to AND
- 	all 1's into the destFrom pixels regardless of their size."
- 	| oldMask oldMap |
- 	oldMask := halftoneForm.
- 	halftoneForm := nil.
- 	oldMap := colorMap.
- 	self colorMap: (Bitmap with: 0 with: 16rFFFFFFFF).
- 	combinationRule := Form erase.
- 	self copyBits. 		"Erase the dest wherever the source is 1"
- 	halftoneForm := oldMask.	"already converted to a Bitmap"
- 	colorMap := oldMap!

Item was removed:
- ----- Method: BitBlt>>fill:fillColor:rule: (in category 'copying') -----
- fill: destRect fillColor: grayForm rule: rule
- 	"Fill with a Color, not a Form. 6/18/96 tk"
- 	sourceForm := nil.
- 	self fillColor: grayForm.		"sets halftoneForm"
- 	combinationRule := rule.
- 	destX := destRect left.
- 	destY := destRect top.
- 	sourceX := 0.
- 	sourceY := 0.
- 	width := destRect width.
- 	height := destRect height.
- 	self copyBits!

Item was removed:
- ----- Method: BitBlt>>fillColor (in category 'accessing') -----
- fillColor
- 	^ halftoneForm!

Item was removed:
- ----- Method: BitBlt>>fillColor: (in category 'accessing') -----
- fillColor: aColorOrPattern 
- 	"The destForm will be filled with this color or pattern of colors.  May be an old Color, a new type Color, a Bitmap (see BitBlt comment), a Pattern, or a Form.  6/18/96 tk"
- 
- 	aColorOrPattern == nil ifTrue: [halftoneForm := nil. ^ self].
- 	destForm == nil ifTrue: [self error: 'Must set destForm first'].
- 	halftoneForm := destForm bitPatternFor: aColorOrPattern !

Item was removed:
- ----- Method: BitBlt>>getPluginName (in category 'private') -----
- getPluginName
- 	"Private. Return the name of the plugin representing BitBlt.
- 	Used for dynamically switching between different BB representations only."
- 	^'BitBltPlugin'!

Item was removed:
- ----- Method: BitBlt>>halftoneForm (in category 'accessing') -----
- halftoneForm
- 	"Returns the receivers half tone form. See class commment."
- 	
- 	^halftoneForm!

Item was removed:
- ----- Method: BitBlt>>halftoneForm: (in category 'accessing') -----
- halftoneForm: aBitmap
- 	"Sets the receivers half tone form. See class commment."
- 	
- 	halftoneForm := aBitmap
- 	
-  !

Item was removed:
- ----- Method: BitBlt>>height: (in category 'accessing') -----
- height: anInteger 
- 	"Set the receiver's destination form height to be the argument, anInteger."
- 
- 	height := anInteger!

Item was removed:
- ----- Method: BitBlt>>installStrikeFont: (in category 'private') -----
- installStrikeFont: aStrikeFont
- 
- 	^ self installStrikeFont: aStrikeFont foregroundColor: Color black backgroundColor: Color transparent!

Item was removed:
- ----- Method: BitBlt>>installStrikeFont:foregroundColor:backgroundColor: (in category 'private') -----
- installStrikeFont: aStrikeFont foregroundColor: foregroundColor backgroundColor: backgroundColor
- 	| lastSourceDepth targetColor |
- 	sourceForm ifNotNil:[lastSourceDepth := sourceForm depth].
- 	sourceForm := aStrikeFont glyphs.
- 
- 	"Ignore any halftone pattern since we use a color map approach here"
- 	halftoneForm := nil.
- 	sourceY := 0.
- 	height := aStrikeFont height.
- 
- 	sourceForm depth = 1 ifTrue: [
- 		self combinationRule: Form paint.
- 		(colorMap notNil and:[lastSourceDepth = sourceForm depth]) ifFalse: [
- 			"Set up color map for a different source depth (color font)"
- 			"Uses caching for reasonable efficiency"
- 			colorMap := self cachedFontColormapFrom: sourceForm depth to: destForm depth.
- 			colorMap at: 1 put: (destForm pixelValueFor: backgroundColor)].
- 		colorMap at: 2 put: (destForm pixelValueFor: foregroundColor).
- 	]
- 	ifFalse: [
- 		(self class subPixelRenderFonts and: [ foregroundColor = Color black
- 			"Only use rgbMul with opaque colors as alpha values get lost for translucent colors."
- 			or: [ self class subPixelRenderColorFonts and: [foregroundColor isOpaque] ]]) ifTrue: [
- 			destForm depth > 8 ifTrue: [
- 				"rgbMul is equivalent to component alpha blend if text is black (only faster, hehe)"
- 				self combinationRule: Form rgbMul.
- 				colorMap := (destForm depth = 32 or: [ (foregroundColor = Color black) not ]) ifTrue: [
- 					"rgbMul / rgbAdd IS component alpha blend for any color of text (neat trick, eh!!)"
- 					"This colorMap is to be used on the second pass with rule 20 (rgbAdd)
- 					See #displayString:from:to:at:strikeFont:kern:"
- 					"Note: In 32bpp we always need the second pass, as the source could have transparent pixels, and we need to add to the alpha channel"
- 					self colorConvertingMap: foregroundColor from: sourceForm depth to: destForm depth keepSubPixelAA: true]]
- 			ifFalse: [
- 				self combinationRule: Form paint.
- 				targetColor := foregroundColor = Color black ifFalse: [ foregroundColor ].
- 				colorMap := self colorConvertingMap: targetColor from: sourceForm depth to: destForm depth keepSubPixelAA: true]
- 		]
- 		ifFalse: [
- 			"Do not use rule 34 for 16bpp display. TTCFont uses it, but it builds a glyphs cache for each color used!!"
- 			self combinationRule: (destForm depth = 32 ifTrue: [Form blendAlphaScaled] ifFalse: [Form paint]).
- 			colorMap := self colorConvertingMap: foregroundColor from: sourceForm depth to: destForm depth keepSubPixelAA: false
- 		]
- 	].!

Item was removed:
- ----- Method: BitBlt>>installTTCFont: (in category 'private') -----
- installTTCFont: aTTCFont
- 
- 	^ self installTTCFont: aTTCFont foregroundColor: Color black backgroundColor: Color transparent!

Item was removed:
- ----- Method: BitBlt>>installTTCFont:foregroundColor:backgroundColor: (in category 'private') -----
- installTTCFont: aTTCFont foregroundColor: foregroundColor backgroundColor: backgroundColor
- 	"Set up the parameters.  Since the glyphs in a TTCFont is 32bit depth form, it tries to use rule=34 to get better AA result if possible."
- 
- 	((aTTCFont depth = 32)) ifTrue: [
- 		destForm depth <= 8 ifTrue: [
- 			self colorMap: (self cachedFontColormapFrom: aTTCFont depth to: destForm depth).
- 			self combinationRule: Form paint.
- 		] ifFalse: [
- 			self colorMap: nil.
- 			self combinationRule: 34.
- 		].
- 		halftoneForm := nil.
- 		sourceY := 0.
- 		height := aTTCFont height.
- 	].
- !

Item was removed:
- ----- Method: BitBlt>>paintBits (in category 'private') -----
- paintBits
- 	"Perform the paint operation, which requires two calls to BitBlt."
- 	| color oldMap saveRule |
- 	sourceForm depth = 1 ifFalse: 
- 		[^ self halt: 'paint operation is only defined for 1-bit deep sourceForms'].
- 	saveRule := combinationRule.
- 	color := halftoneForm.  halftoneForm := nil.
- 	oldMap := colorMap.
- 	"Map 1's to ALL ones, not just one"
- 	self colorMap: (Bitmap with: 0 with: 16rFFFFFFFF).
- 	combinationRule := Form erase.
- 	self copyBits. 		"Erase the dest wherever the source is 1"
- 	halftoneForm := color.
- 	combinationRule := Form under.
- 	self copyBits.	"then OR, with whatever color, into the hole"
- 	colorMap := oldMap.
- 	combinationRule := saveRule
- 
- " | dot |
- dot := Form dotOfSize: 32.
- ((BitBlt destForm: Display
- 		sourceForm: dot
- 		fillColor: Color lightGray
- 		combinationRule: Form paint
- 		destOrigin: Sensor cursorPoint
- 		sourceOrigin: 0 at 0
- 		extent: dot extent
- 		clipRect: Display boundingBox)
- 		colorMap: (Bitmap with: 0 with: 16rFFFFFFFF)) copyBits"!

Item was removed:
- ----- Method: BitBlt>>pixelAt: (in category 'copying') -----
- pixelAt: aPoint
- 	"Assumes this BitBlt has been set up specially (see the init message,
- 	BitBlt bitPeekerFromForm:.  Returns the pixel at aPoint."
- 	sourceX := aPoint x.
- 	sourceY := aPoint y.
- 	destForm unhibernate. "before poking"
- 	destForm bits at: 1 put: 0.  "Just to be sure"
- 	self copyBits.
- 	^ destForm bits at: 1!

Item was removed:
- ----- Method: BitBlt>>pixelAt:put: (in category 'copying') -----
- pixelAt: aPoint put: pixelValue
- 	"Assumes this BitBlt has been set up specially (see the init message,
- 	BitBlt bitPokerToForm:.  Overwrites the pixel at aPoint."
- 	destX := aPoint x.
- 	destY := aPoint y.
- 	sourceForm unhibernate. "before poking"
- 	sourceForm bits at: 1 put: pixelValue.
- 	self copyBits
- "
- | bb |
- bb := (BitBlt bitPokerToForm: Display).
- [Sensor anyButtonPressed] whileFalse:
- 	[bb pixelAt: Sensor cursorPoint put: 55]
- "!

Item was removed:
- ----- Method: BitBlt>>primCompareColor:to:test: (in category 'private') -----
- primCompareColor: colorValueA to: colorValueB test: testID
- 	"Call the prim that compares pixel color values and can tell if two Forms that overlap in some manner when composited are touching colors as defined by the testID.
- "
- 	<primitive: 'primitiveCompareColors' module: 'BitBltPlugin'>
- 	"to signal failure without an error we'll return -1"
- 	^-1!

Item was removed:
- ----- Method: BitBlt>>primDisplayString:from:to:map:xTable:kern: (in category 'private') -----
- primDisplayString: aString from: startIndex to: stopIndex map: glyphMap xTable: xTable kern: kernDelta
- 	| ascii |
- 	<primitive:'primitiveDisplayString' module:'BitBltPlugin'>
- 
- 	((sourceForm isForm) and: [sourceForm unhibernate])
- 		ifTrue: [^ self primDisplayString: aString from: startIndex to: stopIndex map: glyphMap xTable: xTable kern: kernDelta].
- 	((destForm isForm) and: [destForm unhibernate])
- 		ifTrue: [^ self primDisplayString: aString from: startIndex to: stopIndex map: glyphMap xTable: xTable kern: kernDelta].
- 	((halftoneForm isForm) and: [halftoneForm unhibernate])
- 		ifTrue: [^ self primDisplayString: aString from: startIndex to: stopIndex map: glyphMap xTable: xTable kern: kernDelta].
- 
- 	startIndex to: stopIndex do:[:charIndex|
- 		ascii := (aString at: charIndex) asciiValue.
- 		glyphMap ifNotNil:[ascii := glyphMap at: ascii+1].
- 		sourceX := xTable at: ascii + 1.
- 		width := (xTable at: ascii + 2) - sourceX.
- 		self copyBits.
- 		destX := destX + width + kernDelta.
- 	].!

Item was removed:
- ----- Method: BitBlt>>roundVariables (in category 'private') -----
- roundVariables
- 
- 	| maxVal minVal |
- 	maxVal := SmallInteger maxVal.
- 	minVal := SmallInteger minVal.
- 	destX := destX asInteger min: maxVal max: minVal.
- 	destY := destY asInteger min: maxVal max: minVal.
- 	width := width asInteger min: maxVal max: minVal.
- 	height := height asInteger min: maxVal max: minVal.
- 	sourceX := sourceX asInteger min: maxVal max: minVal.
- 	sourceY := sourceY asInteger min: maxVal max: minVal.
- 	clipX := clipX asInteger min: maxVal max: minVal.
- 	clipY := clipY asInteger min: maxVal max: minVal.
- 	clipWidth := clipWidth asInteger min: maxVal max: minVal.
- 	clipHeight := clipHeight asInteger min: maxVal max: minVal.
- !

Item was removed:
- ----- Method: BitBlt>>setDestForm: (in category 'private') -----
- setDestForm: df
- 	| bb |
- 	bb := df boundingBox.
- 	destForm := df.
- 	clipX := bb left.
- 	clipY := bb top.
- 	clipWidth := bb width.
- 	clipHeight := bb height!

Item was removed:
- ----- Method: BitBlt>>setDestForm:sourceForm:fillColor:combinationRule:destOrigin:sourceOrigin:extent:clipRect: (in category 'private') -----
- setDestForm: df sourceForm: sf fillColor: hf combinationRule: cr destOrigin: destOrigin sourceOrigin: sourceOrigin extent: extent clipRect: clipRect
- 
- 	| aPoint |
- 	destForm := df.
- 	sourceForm := sf.
- 	self fillColor: hf.	"sets halftoneForm"
- 	combinationRule := cr.
- 	destX := destOrigin x.
- 	destY := destOrigin y.
- 	sourceX := sourceOrigin x.
- 	sourceY := sourceOrigin y.
- 	width := extent x.
- 	height := extent y.
- 	aPoint := clipRect origin.
- 	clipX := aPoint x.
- 	clipY := aPoint y.
- 	aPoint := clipRect corner.
- 	clipWidth := aPoint x - clipX.
- 	clipHeight := aPoint y - clipY.
- 	sourceForm == nil ifFalse:
- 		[colorMap := sourceForm colormapIfNeededFor: destForm]!

Item was removed:
- ----- Method: BitBlt>>sourceForm (in category 'accessing') -----
- sourceForm
- 
- 	^ sourceForm!

Item was removed:
- ----- Method: BitBlt>>sourceForm: (in category 'accessing') -----
- sourceForm: aForm 
- 	"Set the receiver's source form to be the argument, aForm."
- 
- 	sourceForm := aForm!

Item was removed:
- ----- Method: BitBlt>>sourceOrigin: (in category 'accessing') -----
- sourceOrigin: aPoint 
- 	"Set the receiver's source form coordinates to be those of the argument, 
- 	aPoint."
- 
- 	sourceX := aPoint x.
- 	sourceY := aPoint y!

Item was removed:
- ----- Method: BitBlt>>sourceRect: (in category 'accessing') -----
- sourceRect: aRectangle 
- 	"Set the receiver's source form top left x and y, width and height to be 
- 	the top left coordinate and extent of the argument, aRectangle."
- 
- 	sourceX := aRectangle left.
- 	sourceY := aRectangle top.
- 	width := aRectangle width.
- 	height := aRectangle height!

Item was removed:
- ----- Method: BitBlt>>sourceX: (in category 'accessing') -----
- sourceX: anInteger 
- 	"Set the receiver's source form top left x to be the argument, anInteger."
- 
- 	sourceX := anInteger!

Item was removed:
- ----- Method: BitBlt>>sourceY: (in category 'accessing') -----
- sourceY: anInteger 
- 	"Set the receiver's source form top left y to be the argument, anInteger."
- 
- 	sourceY := anInteger!

Item was removed:
- ----- Method: BitBlt>>tallyMap (in category 'accessing') -----
- tallyMap
- 	"Return the map used for tallying pixels"
- 	^colorMap!

Item was removed:
- ----- Method: BitBlt>>tallyMap: (in category 'accessing') -----
- tallyMap: aBitmap
- 	"Install the map used for tallying pixels"
- 	colorMap := aBitmap!

Item was removed:
- ----- Method: BitBlt>>width: (in category 'accessing') -----
- width: anInteger 
- 	"Set the receiver's destination form width to be the argument, anInteger."
- 
- 	width := anInteger!

Item was removed:
- DisplayScanner subclass: #BitBltDisplayScanner
- 	instanceVariableNames: 'bitBlt fillBlt'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Text'!
- 
- !BitBltDisplayScanner commentStamp: 'nice 10/12/2013 01:36' prior: 0!
- A BitBltDisplayScanner displays characters on Screen or other Form with help of a BitBlt.
- 
- Instance Variables
- 	bitBlt:		<BitBlt>
- 	fillBlt:		<BitBlt>
- 
- bitBlt
- 	- the object which knows how to copy bits from one Form (the font glyph data) to another (the destination Form)
- 
- fillBlt
- 	- another object for copying form bits, initialized for displaying the background.
- 
- !

Item was removed:
- ----- Method: BitBltDisplayScanner class>>defaultFont (in category 'queries') -----
- defaultFont
- 	^ TextStyle defaultFont!

Item was removed:
- ----- Method: BitBltDisplayScanner>>displayEmbeddedForm:at: (in category 'displaying') -----
- displayEmbeddedForm: aForm at: aPoint
- 
- 	aForm 
- 		displayOn: bitBlt destForm 
- 		at: aPoint
- 		clippingBox: bitBlt clipRect
- 		rule: Form blend
- 		fillColor: Color white !

Item was removed:
- ----- Method: BitBltDisplayScanner>>displayString:from:to:at: (in category 'displaying') -----
- displayString: string from: startIndex to: stopIndex at: aPoint
- 	
- 	font 
- 		displayString: string 
- 		on: bitBlt 
- 		from: startIndex 
- 		to: stopIndex 
- 		at: aPoint 
- 		kern: kern!

Item was removed:
- ----- Method: BitBltDisplayScanner>>fillTextBackground (in category 'displaying') -----
- fillTextBackground
- 	fillBlt == nil ifFalse:
- 		["Not right"
- 		fillBlt destX: line left destY: lineY
- 			width: line width left height: line lineHeight; copyBits].!

Item was removed:
- ----- Method: BitBltDisplayScanner>>plainTab (in category 'stop conditions') -----
- plainTab
- 	| nextDestX |
-  	nextDestX := super plainTab.
- 	fillBlt == nil ifFalse:
- 		[fillBlt destX: destX destY: destY width: nextDestX - destX height: font height; copyBits].
- 	^nextDestX!

Item was removed:
- ----- Method: BitBltDisplayScanner>>setDestForm: (in category 'private') -----
- setDestForm: df
- 	bitBlt setDestForm: df.!

Item was removed:
- ----- Method: BitBltDisplayScanner>>setFont (in category 'private') -----
- setFont 
- 	super setFont.  "Sets font and emphasis bits, and maybe foregroundColor"
- 	font installOn: bitBlt foregroundColor: foregroundColor backgroundColor: Color transparent!

Item was removed:
- ----- Method: BitBltDisplayScanner>>setPort: (in category 'private') -----
- setPort: aBitBlt
- 	"Install the BitBlt to use"
- 	bitBlt := aBitBlt.
- 	bitBlt sourceX: 0; width: 0.	"Init BitBlt so that the first call to a primitive will not fail"
- 	bitBlt sourceForm: nil. "Make sure font installation won't be confused"
- !

Item was removed:
- ----- Method: BitBltDisplayScanner>>text:textStyle:foreground:background:fillBlt:ignoreColorChanges: (in category 'private') -----
- text: t textStyle: ts foreground: foreColor background: backColor fillBlt: blt ignoreColorChanges: shadowMode
- 	text := t.
- 	textStyle := ts. 
- 	foregroundColor := defaultTextColor := foreColor.
- 	(backgroundColor := backColor) isTransparent ifFalse:
- 		[fillBlt := blt.
- 		fillBlt fillColor: backgroundColor].
- 	ignoreColorChanges := shadowMode!

Item was removed:
- ArrayedCollection variableWordSubclass: #Bitmap
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Primitives'!
- 
- !Bitmap commentStamp: '<historical>' prior: 0!
- My instances provide contiguous storage of bits, primarily to hold the graphical data of Forms. Forms and their subclasses provide the additional structural information as to how the bits should be interpreted in two dimensions.!

Item was removed:
- ----- Method: Bitmap class>>decodeIntFrom: (in category 'instance creation') -----
- decodeIntFrom: s
- 	"Decode an integer in stream s as follows...
- 		0-223	0-223
- 		224-254	(0-30)*256 + next byte (0-7935)
- 		255		next 4 bytes	"		
- 	| int |
- 	int := s next.
- 	int <= 223 ifTrue: [^ int].
- 	int <= 254 ifTrue: [^ (int-224)*256 + s next].
- 	int := s next.
- 	1 to: 3 do: [:j | int := (int bitShift: 8) + s next].
- 	^ int!

Item was removed:
- ----- Method: Bitmap class>>decompressFromByteArray: (in category 'instance creation') -----
- decompressFromByteArray: byteArray
- 	| s bitmap size |
- 	s := ReadStream on: byteArray.
- 	size := self decodeIntFrom: s.
- 	bitmap := self new: size.
- 	bitmap decompress: bitmap fromByteArray: byteArray at: s position+1.
- 	^ bitmap!

Item was removed:
- ----- Method: Bitmap class>>newFromStream: (in category 'instance creation') -----
- newFromStream: s
- 	| len |
- 	s next = 16r80 ifTrue:
- 		["New compressed format"
- 		len := self decodeIntFrom: s.
- 		^ Bitmap decompressFromByteArray: (s nextInto: (ByteArray new: len))].
- 	s skip: -1.
- 	len := s nextInt32.
- 	len <= 0
- 		ifTrue: ["Old compressed format"
- 				^ (self new: len negated) readCompressedFrom: s]
- 		ifFalse: ["Old raw data format"
- 				^ s nextWordsInto: (self new: len)]!

Item was removed:
- ----- Method: Bitmap class>>swapBytesIn:from:to: (in category 'utilities') -----
- swapBytesIn: aNonPointerThing from: start to: stop
- 	"Perform a bigEndian/littleEndian byte reversal of my words.
- 	We only intend this for non-pointer arrays.  Do nothing if I contain pointers."
- 	| hack blt |
- 	"The implementation is a hack, but fast for large ranges"
- 	hack := Form new hackBits: aNonPointerThing.
- 	blt := (BitBlt toForm: hack) sourceForm: hack.
- 	blt combinationRule: Form reverse.  "XOR"
- 	blt sourceY: start-1; destY: start-1; height: stop-start+1; width: 1.
- 	blt sourceX: 0; destX: 3; copyBits.  "Exchange bytes 0 and 3"
- 	blt sourceX: 3; destX: 0; copyBits.
- 	blt sourceX: 0; destX: 3; copyBits.
- 	blt sourceX: 1; destX: 2; copyBits.  "Exchange bytes 1 and 2"
- 	blt sourceX: 2; destX: 1; copyBits.
- 	blt sourceX: 1; destX: 2; copyBits.
- !

Item was removed:
- ----- Method: Bitmap>>asByteArray (in category 'converting') -----
- asByteArray
- 	"Faster way to make a byte array from me.
- 	copyFromByteArray: makes equal Bitmap."
- 	| f bytes hack |
- 	f := Form extent: 4 at self size depth: 8 bits: self.
- 	bytes := ByteArray new: self size * 4.
- 	hack := Form new hackBits: bytes.
- 	Smalltalk isLittleEndian ifTrue:[hack swapEndianness].
- 	hack copyBits: f boundingBox
- 		from: f
- 		at: (0 at 0)
- 		clippingBox: hack boundingBox
- 		rule: Form over
- 		fillColor: nil
- 		map: nil.
- 
- 	"f displayOn: hack."
- 	^ bytes.
- !

Item was removed:
- ----- Method: Bitmap>>atAllPut: (in category 'accessing') -----
- atAllPut: value
- 	"Fill the receiver, an indexable bytes or words object, with the given positive integer. The range of possible fill values is [0..255] for byte arrays and [0..(2^32 - 1)] for word arrays."
- 	<primitive: 145>
- 	super atAllPut: value.!

Item was removed:
- ----- Method: Bitmap>>bitPatternForDepth: (in category 'accessing') -----
- bitPatternForDepth: depth
- 	"The raw call on BitBlt needs a Bitmap to represent this color.  I already am Bitmap like.  I am already adjusted for a specific depth.  Interpret me as an array of (32/depth) Color pixelValues.  BitBlt aligns the first element of this array with the top scanline of the destinationForm, the second with the second, and so on, cycling through the color array as necessary. 6/18/96 tk"
- 
- 	^ self!

Item was removed:
- ----- Method: Bitmap>>byteAt: (in category 'accessing') -----
- byteAt: byteAddress
- 	"Extract a byte from a Bitmap.  Note that this is a byte address and it is one-order.  For repeated use, create an instance of BitBlt and use pixelAt:.  See Form pixelAt:  7/1/96 tk"
- 	| lowBits |
- 	lowBits := byteAddress - 1 bitAnd: 3.
- 	^((self at: byteAddress - 1 - lowBits // 4 + 1)
- 		bitShift: (lowBits - 3) * 8)
- 		bitAnd: 16rFF!

Item was removed:
- ----- Method: Bitmap>>byteAt:put: (in category 'accessing') -----
- byteAt: byteAddress put: byte
- 	"Insert a byte into a Bitmap.  Note that this is a byte address and it is one-order.  For repeated use, create an instance of BitBlt and use pixelAt:put:.  See Form pixelAt:put:  7/1/96 tk"
- 	| longWord shift lowBits longAddr |
- 	(byte < 0 or:[byte > 255]) ifTrue:[^self errorImproperStore].
- 	lowBits := byteAddress - 1 bitAnd: 3.
- 	longWord := self at: (longAddr := (byteAddress - 1 - lowBits) // 4 + 1).
- 	shift := (3 - lowBits) * 8.
- 	longWord := longWord - (longWord bitAnd: (16rFF bitShift: shift)) 
- 		+ (byte bitShift: shift).
- 	self at: longAddr put: longWord.
- 	^ byte!

Item was removed:
- ----- Method: Bitmap>>byteSize (in category 'accessing') -----
- byteSize
- 	^self size * 4!

Item was removed:
- ----- Method: Bitmap>>compress:toByteArray: (in category 'filing') -----
- compress: bm toByteArray: ba
- 	"Store a run-coded compression of the receiver into the byteArray ba,
- 	and return the last index stored into. ba is assumed to be large enough.
- 	The encoding is as follows...
- 		S {N D}*.
- 		S is the size of the original bitmap, followed by run-coded pairs.
- 		N is a run-length * 4 + data code.
- 		D, the data, depends on the data code...
- 			0	skip N words, D is absent
- 			1	N words with all 4 bytes = D (1 byte)
- 			2	N words all = D (4 bytes)
- 			3	N words follow in D (4N bytes)
- 		S and N are encoded as follows...
- 			0-223	0-223
- 			224-254	(0-30)*256 + next byte (0-7935)
- 			255		next 4 bytes"		
- 	| size k word j lowByte eqBytes i |
- 	<primitive: 'primitiveCompressToByteArray' module: 'MiscPrimitivePlugin'>
- 	<var: #bm declareC: 'int *bm'>
- 	<var: #ba declareC: 'unsigned char *ba'>
- 	size := bm size.
- 	i := self encodeInt: size in: ba at: 1.
- 	k := 1.
- 	[k <= size] whileTrue:
- 		[word := bm at: k.
- 		lowByte := word bitAnd: 16rFF.
- 		eqBytes := ((word >> 8) bitAnd: 16rFF) = lowByte
- 				and: [((word >> 16) bitAnd: 16rFF) = lowByte
- 				and: [((word >> 24) bitAnd: 16rFF) = lowByte]].
- 		j := k.
- 		[j < size and: [word = (bm at: j+1)]]  "scan for = words..."
- 			whileTrue: [j := j+1].
- 		j > k ifTrue:
- 			["We have two or more = words, ending at j"
- 			eqBytes
- 				ifTrue: ["Actually words of = bytes"
- 						i := self encodeInt: j-k+1*4+1 in: ba at: i.
- 						ba at: i put: lowByte.  i := i+1]
- 				ifFalse: [i := self encodeInt: j-k+1*4+2 in: ba at: i.
- 						i := self encodeBytesOf: word in: ba at: i].
- 			k := j+1]
- 			ifFalse:
- 			["Check for word of 4 = bytes"
- 			eqBytes ifTrue:
- 				["Note 1 word of 4 = bytes"
- 				i := self encodeInt: 1*4+1 in: ba at: i.
- 				ba at: i put: lowByte.  i := i+1.
- 				k := k + 1]
- 				ifFalse:
- 				["Finally, check for junk"
- 				[j < size and: [(bm at: j) ~= (bm at: j+1)]]  "scan for ~= words..."
- 					whileTrue: [j := j+1].
- 				j = size ifTrue: [j := j + 1].
- 				"We have one or more unmatching words, ending at j-1"
- 				i := self encodeInt: j-k*4+3 in: ba at: i.
- 				k to: j-1 do:
- 					[:m | i := self encodeBytesOf: (bm at: m) in: ba at: i].
- 				k := j]]].
- 	^ i - 1  "number of bytes actually stored"
- "
- Space check:
-  | n rawBytes myBytes b |
- n := rawBytes := myBytes := 0.
- Form allInstancesDo:
- 	[:f | f unhibernate.
- 	b := f bits.
- 	n := n + 1.
- 	rawBytes := rawBytes + (b size*4).
- 	myBytes := myBytes + (b compressToByteArray size).
- 	f hibernate].
- Array with: n with: rawBytes with: myBytes
- ColorForms: (116 230324 160318 )
- Forms: (113 1887808 1325055 )
- 
- Integerity check:
- Form allInstances do:
- 	[:f | f unhibernate.
- 	f bits = (Bitmap decompressFromByteArray: f bits compressToByteArray)
- 		ifFalse: [self halt].
- 	f hibernate]
- 
- Speed test:
- MessageTally spyOn: [Form allInstances do:
- 	[:f | Bitmap decompressFromByteArray: f bits compressToByteArray]]
- "!

Item was removed:
- ----- Method: Bitmap>>compressGZip (in category 'filing') -----
- compressGZip
- 	| ba hackwa hackba blt rowsAtATime sourceOrigin rowsRemaining bufferStream gZipStream |
- 
- "just hacking around to see if further compression would help Nebraska"
- 
- 	bufferStream := WriteStream on: (ByteArray new: 5000).
- 	gZipStream := GZipWriteStream on: bufferStream.
- 
- 	ba := nil.
- 	rowsAtATime := 20000.		"or 80000 bytes"
- 	hackwa := Form new hackBits: self.
- 	sourceOrigin := 0 at 0.
- 	[(rowsRemaining := hackwa height - sourceOrigin y) > 0] whileTrue: [
- 		rowsAtATime := rowsAtATime min: rowsRemaining.
- 		(ba isNil or: [ba size ~= (rowsAtATime * 4)]) ifTrue: [
- 			ba := ByteArray new: rowsAtATime * 4.
- 			hackba := Form new hackBits: ba.
- 			blt := (BitBlt toForm: hackba) sourceForm: hackwa.
- 		].
- 		blt 
- 			combinationRule: Form over;
- 			sourceOrigin: sourceOrigin;
- 			destX: 0 destY: 0 width: 4 height: rowsAtATime;
- 			copyBits.
- 		"bufferStream nextPutAll: ba."
- 		sourceOrigin := sourceOrigin x @ (sourceOrigin y + rowsAtATime).
- 	].
- 	gZipStream close.
- 	^bufferStream contents
- !

Item was removed:
- ----- Method: Bitmap>>compressToByteArray (in category 'filing') -----
- compressToByteArray
- 	"Return a run-coded compression of this bitmap into a byteArray"		
- 	| byteArray lastByte |
- 	"Without skip codes, it is unlikely that the compressed bitmap will be any larger than was the original.  The run-code cases are...
- 	N >= 1 words of equal bytes:  4N bytes -> 2 bytes (at worst 4 -> 2)
- 	N > 1 equal words:  4N bytes -> 5 bytes (at worst 8 -> 5)
- 	N > 1 unequal words:  4N bytes -> 4N + M, where M is the number of bytes required to encode the run length.
- 
- The worst that can happen is that the method begins with unequal words, and than has interspersed occurrences of a word with equal bytes.  Thus we require a run-length at the beginning, and after every interspersed word of equal bytes.  However, each of these saves 2 bytes, so it must be followed by a run of 1984 (7936//4) or more (for which M jumps from 2 to 5) to add any extra overhead.  Therefore the worst case is a series of runs of 1984 or more, with single interspersed words of equal bytes.  At each break we save 2 bytes, but add 5.  Thus the overhead would be no more than 5 (encoded size) + 2 (first run len) + (S//1984*3)."
- 	
- "NOTE: This code is copied in Form hibernate for reasons given there."
- 	byteArray := ByteArray new: (self size*4) + 7 + (self size//1984*3).
- 	lastByte := self compress: self toByteArray: byteArray.
- 	^ byteArray copyFrom: 1 to: lastByte!

Item was removed:
- ----- Method: Bitmap>>copyFromByteArray: (in category 'accessing') -----
- copyFromByteArray: byteArray 
- 	"This method should work with either byte orderings"
- 
- 	| myHack byteHack |
- 	myHack := Form new hackBits: self.
- 	byteHack := Form new hackBits: byteArray.
- 	Smalltalk  isLittleEndian ifTrue: [byteHack swapEndianness].
- 	byteHack displayOn: myHack!

Item was removed:
- ----- Method: Bitmap>>decompress:fromByteArray:at: (in category 'filing') -----
- decompress: bm fromByteArray: ba at: index
- 	"Decompress the body of a byteArray encoded by compressToByteArray (qv)...
- 	The format is simply a sequence of run-coded pairs, {N D}*.
- 		N is a run-length * 4 + data code.
- 		D, the data, depends on the data code...
- 			0	skip N words, D is absent
- 				(could be used to skip from one raster line to the next)
- 			1	N words with all 4 bytes = D (1 byte)
- 			2	N words all = D (4 bytes)
- 			3	N words follow in D (4N bytes)
- 		S and N are encoded as follows (see decodeIntFrom:)...
- 			0-223	0-223
- 			224-254	(0-30)*256 + next byte (0-7935)
- 			255		next 4 bytes"	
- 	"NOTE:  If fed with garbage, this routine could read past the end of ba, but it should fail before writing past the ned of bm."
- 	| i code n anInt data end k pastEnd |
- 	<primitive: 'primitiveDecompressFromByteArray' module: 'MiscPrimitivePlugin'>
- 	<var: #bm type: 'int *'>
- 	<var: #ba type: 'unsigned char *'>
- 	<var: #anInt type: 'unsigned int'> "Force the type, otherwise it is inferred as unsigned char because assigned from ba"
- 	<var: #data type: 'unsigned int'>
- 	i := index.  "byteArray read index"
- 	end := ba size.
- 	k := 1.  "bitmap write index"
- 	pastEnd := bm size + 1.
- 	[i <= end] whileTrue:
- 		["Decode next run start N"
- 		anInt := ba at: i.  i := i+1.
- 		anInt <= 223 ifFalse:
- 			[anInt <= 254
- 				ifTrue: [anInt := (anInt-224)*256 + (ba at: i).  i := i+1]
- 				ifFalse: [anInt := 0.
- 						1 to: 4 do: [:j | anInt := (anInt bitShift: 8) + (ba at: i).  i := i+1]]].
- 		n := anInt >> 2.
- 		(k + n) > pastEnd ifTrue: [^ self primitiveFail].
- 		code := anInt bitAnd: 3.
- 		code = 0 ifTrue: ["skip"].
- 		code = 1 ifTrue: ["n consecutive words of 4 bytes = the following byte"
- 						data := ba at: i.  i := i+1.
- 						data := data bitOr: (data bitShift: 8).
- 						data := data bitOr: (data bitShift: 16).
- 						1 to: n do: [:j | bm at: k put: data.  k := k+1]].
- 		code = 2 ifTrue: ["n consecutive words = 4 following bytes"
- 						data := 0.
- 						1 to: 4 do: [:j | data := (data bitShift: 8) bitOr: (ba at: i).  i := i+1].
- 						1 to: n do: [:j | bm at: k put: data.  k := k+1]].
- 		code = 3 ifTrue: ["n consecutive words from the data..."
- 						1 to: n do:
- 							[:m | data := 0.
- 							1 to: 4 do: [:j | data := (data bitShift: 8) bitOr: (ba at: i).  i := i+1].
- 							bm at: k put: data.  k := k+1]]]!

Item was removed:
- ----- Method: Bitmap>>defaultElement (in category 'accessing') -----
- defaultElement
- 	"Return the default element of the receiver"
- 	^0!

Item was removed:
- ----- Method: Bitmap>>encodeBytesOf:in:at: (in category 'filing') -----
- encodeBytesOf: anInt in: ba at: i
- 	"Copy the integer anInt into byteArray ba at index i, and return the next index"
- 
- 	<inline: true>
- 	<var: #ba declareC: 'unsigned char *ba'>
- 	0 to: 3 do:
- 		[:j | ba at: i+j put: (anInt >> (3-j*8) bitAnd: 16rFF)].
- 	^ i+4!

Item was removed:
- ----- Method: Bitmap>>encodeInt: (in category 'filing') -----
- encodeInt: int
- 	"Encode the integer int as per encodeInt:in:at:, and return it as a ByteArray"
- 	| byteArray next |
- 	byteArray := ByteArray new: 5.
- 	next := self encodeInt: int in: byteArray at: 1.
- 	^ byteArray copyFrom: 1 to: next - 1
- !

Item was removed:
- ----- Method: Bitmap>>encodeInt:in:at: (in category 'filing') -----
- encodeInt: anInt in: ba at: i
- 	"Encode the integer anInt in byteArray ba at index i, and return the next index.
- 	The encoding is as follows...
- 		0-223	0-223
- 		224-254	(0-30)*256 + next byte (0-7935)
- 		255		next 4 bytes"		
- 
- 	<inline: true>
- 	<var: #ba declareC: 'unsigned char *ba'>
- 	anInt <= 223 ifTrue: [ba at: i put: anInt. ^ i+1].
- 	anInt <= 7935 ifTrue: [ba at: i put: anInt//256+224. ba at: i+1 put: anInt\\256.  ^ i+2].
- 	ba at: i put: 255.
- 	^ self encodeBytesOf: anInt in: ba at: i+1!

Item was removed:
- ----- Method: Bitmap>>fromByteStream: (in category 'initialize-release') -----
- fromByteStream: aStream 
- 	"Initialize the array of bits by reading integers from the argument, 
- 	aStream."
- 	aStream nextWordsInto: self!

Item was removed:
- ----- Method: Bitmap>>integerAt: (in category 'accessing') -----
- integerAt: index
- 	"Return the integer at the given index"
- 	| word |
- 	<primitive: 165>
- 	word := self basicAt: index.
- 	word < 16r3FFFFFFF ifTrue:[^word]. "Avoid LargeInteger computations"
- 	^word >= 16r80000000	"Negative?!!"
- 		ifTrue:["word - 16r100000000"
- 				(word bitInvert32 + 1) negated]
- 		ifFalse:[word]!

Item was removed:
- ----- Method: Bitmap>>integerAt:put: (in category 'accessing') -----
- integerAt: index put: anInteger
- 	"Store the integer at the given index"
- 	| word |
- 	<primitive: 166>
- 	anInteger < 0
- 		ifTrue:["word := 16r100000000 + anInteger"
- 				word := (anInteger + 1) negated bitInvert32]
- 		ifFalse:[word := anInteger].
- 	self  basicAt: index put: word.
- 	^anInteger!

Item was removed:
- ----- Method: Bitmap>>isColormap (in category 'testing') -----
- isColormap
- 	"Bitmaps were used as color maps for BitBlt.
- 	This method allows to recognize real color maps."
- 	^false!

Item was removed:
- ----- Method: Bitmap>>pixelValueForDepth: (in category 'accessing') -----
- pixelValueForDepth: depth
- 	"Self is being used to represent a single color.  Answer bits that appear in ONE pixel of this color in a Bitmap of the given depth. The depth must be one of 1, 2, 4, 8, 16, or 32.  Returns an integer.  First pixel only.  "
- 
- 	^ (self at: 1) bitAnd: (1 bitShift: depth) - 1!

Item was removed:
- ----- Method: Bitmap>>primFill: (in category 'accessing') -----
- primFill: aPositiveInteger
- 	"Fill the receiver, an indexable bytes or words object, with the given positive integer. The range of possible fill values is [0..255] for byte arrays and [0..(2^32 - 1)] for word arrays."
- 
- 	<primitive: 145>
- 	self errorImproperStore.!

Item was removed:
- ----- Method: Bitmap>>printOn: (in category 'printing') -----
- printOn: aStream
- 	self printNameOn: aStream.
- 	aStream nextPutAll: ' of length '; print: self size!

Item was removed:
- ----- Method: Bitmap>>readCompressedFrom: (in category 'filing') -----
- readCompressedFrom: strm
- 	"Decompress an old-style run-coded stream into this bitmap:
- 		[0 means end of runs]
- 		[n = 1..127] [(n+3) copies of next byte]
- 		[n = 128..191] [(n-127) next bytes as is]
- 		[n = 192..255] [(n-190) copies of next 4 bytes]"
- 	| n byte out outBuff bytes |
- 	out := WriteStream on: (outBuff := ByteArray new: self size*4).
- 	[(n := strm next) > 0] whileTrue:
- 		[(n between: 1 and: 127) ifTrue:
- 			[byte := strm next.
- 			1 to: n+3 do: [:i | out nextPut: byte]].
- 		(n between: 128 and: 191) ifTrue:
- 			[1 to: n-127 do: [:i | out nextPut: strm next]].
- 		(n between: 192 and: 255) ifTrue:
- 			[bytes := (1 to: 4) collect: [:i | strm next].
- 			1 to: n-190 do: [:i | bytes do: [:b | out nextPut: b]]]].
- 	out position = outBuff size ifFalse: [self error: 'Decompression size error'].
- 	"Copy the final byteArray into self"
- 	self copyFromByteArray: outBuff.!

Item was removed:
- ----- Method: Bitmap>>replaceFrom:to:with:startingAt: (in category 'accessing') -----
- replaceFrom: start to: stop with: replacement startingAt: repStart 
- 	"Primitive. This destructively replaces elements from start to stop in the receiver starting at index, repStart, in the collection, replacement. Answer the receiver. Range checks are performed in the primitive only. Optional. See Object documentation whatIsAPrimitive."
- 	<primitive: 105>
- 	super replaceFrom: start to: stop with: replacement startingAt: repStart!

Item was removed:
- ----- Method: Bitmap>>restoreEndianness (in category 'filing') -----
- restoreEndianness
- 	"This word object was just read in from a stream.  Bitmaps are always compressed and serialized in a machine-independent way.  Do not correct the Endianness."
- 
- 	"^ self"
- !

Item was removed:
- ----- Method: Bitmap>>storeBits:to:on: (in category 'filing') -----
- storeBits: startBit to: stopBit on: aStream 
- 	"Store my bits as a hex string, breaking the lines every 100 bytes or 
- 	so to comply with the maximum line length limits of Postscript (255 
- 	bytes). "
- 	| lineWidth |
- 	lineWidth := 0.
- 	self
- 		do: [:word | 
- 			startBit
- 				to: stopBit
- 				by: -4
- 				do: [:shift | 
- 					aStream nextPut: (word >> shift bitAnd: 15) asHexDigit.
- 					lineWidth := lineWidth + 1].
- 			(lineWidth > 100)
- 				ifTrue: [aStream cr.
- 					lineWidth := 0]].
- 	lineWidth > 0 ifTrue: [ aStream cr ].!

Item was removed:
- ----- Method: Bitmap>>writeOn: (in category 'filing') -----
- writeOn: aStream 
- 	"Store the array of bits onto the argument, aStream. A leading byte of 16r80 identifies this as compressed by compressToByteArray (qv)."
- 
- 	| b |
- 	aStream nextPut: 16r80.
- 	b := self compressToByteArray.
- 	aStream
- 		nextPutAll: (self encodeInt: b size);
- 		nextPutAll: b.
- !

Item was removed:
- ----- Method: Bitmap>>writeUncompressedOn: (in category 'filing') -----
- writeUncompressedOn: aStream 
- 	"Store the array of bits onto the argument, aStream.
- 	(leading byte ~= 16r80) identifies this as raw bits (uncompressed)."
- 
- 	aStream nextInt32Put: self size.
- 	aStream nextPutAll: self
- !

Item was removed:
- ----- Method: ByteString>>scanCharactersFrom:to:with:rightX:font: (in category '*Graphics-Text') -----
- scanCharactersFrom: startIndex to: stopIndex with: aCharacterScanner rightX: rightX  font: aFont
- 	"NB: strongly consider getting almost all these parameters from the scanner"
- 	"Since I'm a byte char string, I know that we have to scan single-byte characters and don't have to handle encodings etc"
- 	startIndex > stopIndex
- 		ifTrue: [^aCharacterScanner handleEndOfRunAt: stopIndex].
- 	^aFont scanByteCharactersFrom: startIndex to: stopIndex in: self with: aCharacterScanner rightX: rightX!

Item was removed:
- ----- Method: ByteSymbol>>scanCharactersFrom:to:with:rightX:font: (in category '*Graphics-Text') -----
- scanCharactersFrom: startIndex to: stopIndex with: aCharacterScanner rightX: rightX  font: aFont
- 	"NB: strongly consider getting almost all these parameters from the scanner"
- 	"Since I'm a byte char string, I know that we have to scan single-byte characters and don't have to handle encodings etc"
- 	startIndex > stopIndex
- 		ifTrue: [^aCharacterScanner handleEndOfRunAt: stopIndex].
- 	^aFont scanByteCharactersFrom: startIndex to: stopIndex in: self with: aCharacterScanner rightX: rightX!

Item was removed:
- Rectangle subclass: #CharacterBlock
- 	instanceVariableNames: 'stringIndex text textLine'
- 	classVariableNames: ''
- 	poolDictionaries: 'TextConstants'
- 	category: 'Graphics-Text'!
- 
- !CharacterBlock commentStamp: 'mtf 5/15/2010 12:44' prior: 0!
- I describe the location of one character displayed on the screen. My instances are used to return the results of methods:
- 	Paragraph characterBlockAtPoint: aPoint and
- 	Paragraph characterBlockForIndex: stringIndex.
- Any recomposition or movement of a Paragraph can make the information I store stale.
- 
- text (Text): The text where my character is from
- stringIndex (Integer): The index of my character in the text, starting from 1
- textLine (TextLine): The displayed line my character is on
- origin (Point): The top-left corner of the area allocated for displaying my
- 		character's glyph, in pixels, counting right then down from the
- 		top-left corner of the text display area, and starting from 0 at 0
- corner (Point): The bottom-right corner of the area allocated for displaying my
- 		character's glyph, in pixels, counting right then down from the
- 		top-left corner of the text display area, and starting from 0 at 0
- !

Item was removed:
- ----- Method: CharacterBlock>>< (in category 'comparing') -----
- < aCharacterBlock 
- 	"Answer whether the string index of the receiver precedes that of 
- 	aCharacterBlock."
- 
- 	^stringIndex < aCharacterBlock stringIndex!

Item was removed:
- ----- Method: CharacterBlock>><= (in category 'comparing') -----
- <= aCharacterBlock 
- 	"Answer whether the string index of the receiver does not come after that 
- 	of aCharacterBlock."
- 
- 	^(self > aCharacterBlock) not!

Item was removed:
- ----- Method: CharacterBlock>>= (in category 'comparing') -----
- = aCharacterBlock
- 
- 	self species = aCharacterBlock species
- 		ifTrue: [^stringIndex = aCharacterBlock stringIndex]
- 		ifFalse: [^false]!

Item was removed:
- ----- Method: CharacterBlock>>> (in category 'comparing') -----
- > aCharacterBlock 
- 	"Answer whether the string index of the receiver comes after that of 
- 	aCharacterBlock."
- 
- 	^aCharacterBlock < self!

Item was removed:
- ----- Method: CharacterBlock>>>= (in category 'comparing') -----
- >= aCharacterBlock 
- 	"Answer whether the string index of the receiver does not precede that of 
- 	aCharacterBlock."
- 
- 	^(self < aCharacterBlock) not!

Item was removed:
- ----- Method: CharacterBlock>>max: (in category 'comparing') -----
- max: aCharacterBlock
- 	aCharacterBlock ifNil:[^self].
- 	^aCharacterBlock > self
- 		ifTrue:[ aCharacterBlock]
- 		ifFalse:[self].!

Item was removed:
- ----- Method: CharacterBlock>>min: (in category 'comparing') -----
- min: aCharacterBlock
- 	aCharacterBlock ifNil:[^self].
- 	^aCharacterBlock < self
- 		ifTrue:[ aCharacterBlock]
- 		ifFalse:[self].!

Item was removed:
- ----- Method: CharacterBlock>>moveBy: (in category 'private') -----
- moveBy: aPoint 
- 	"Change the corner positions of the receiver so that its area translates by 
- 	the amount defined by the argument, aPoint."
- 
- 	origin := origin + aPoint.
- 	corner := corner + aPoint!

Item was removed:
- ----- Method: CharacterBlock>>printOn: (in category 'printing') -----
- printOn: aStream
- 
- 	aStream nextPutAll: 'a CharacterBlock with index '.
- 	stringIndex printOn: aStream.
- 	(text ~~ nil and: [text size> 0 and: [stringIndex between: 1 and: text size]])
- 		ifTrue: [aStream nextPutAll: ' and character '.
- 				(text at: stringIndex) printOn: aStream].
- 	aStream nextPutAll: ' and rectangle '.
- 	super printOn: aStream.
- 	textLine ifNotNil: [aStream cr; nextPutAll: ' in '.
- 				textLine printOn: aStream].
- !

Item was removed:
- ----- Method: CharacterBlock>>stringIndex (in category 'accessing') -----
- stringIndex
- 	"Answer the position of the receiver in the string it indexes."
- 
- 	^stringIndex!

Item was removed:
- ----- Method: CharacterBlock>>stringIndex:text:topLeft:extent: (in category 'private') -----
- stringIndex: anInteger text: aText topLeft: topLeft extent: extent
- 
- 	stringIndex := anInteger.
- 	text := aText.
- 	super setOrigin: topLeft corner: topLeft + extent !

Item was removed:
- ----- Method: CharacterBlock>>textLine (in category 'accessing') -----
- textLine
- 	^ textLine!

Item was removed:
- ----- Method: CharacterBlock>>textLine: (in category 'accessing') -----
- textLine: aLine
- 	textLine := aLine!

Item was removed:
- CharacterScanner subclass: #CharacterBlockScanner
- 	instanceVariableNames: 'characterPoint characterIndex nextLeftMargin specialWidth lastCharacterWidth'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Text'!
- 
- !CharacterBlockScanner commentStamp: 'nice 10/6/2013 22:04' prior: 0!
- A CharacterScanner does scan text to compute the CharacterBlock for a character specified by its index in the text or its proximity to the cursor location. The CharacterBlock stores information both about character layout and character index in the text.
- 
- This class is essential for selecting text with the mouse or with arrow keys.
- 
- Instance Variables
- 	characterIndex:		<Integer | nil>
- 	characterPoint:		<Point>
- 	lastCharacterWidth:		<Number | nil>
- 	nextLeftMargin:		<Number>
- 	specialWidth:		<Number | nil>
- 
- characterIndex
- 	- the index of character for which the layout information is searched, or nil when the layout is searched by cursor location
- 
- characterPoint
- 	- the cursor location for which nearest character index and layout are searched.
- 
- lastCharacterWidth
- 	- a number indicating the width of last character being processed.
- 	Note that this variable is left to nil during the inner scan loop, and only set on stopConditions.
- 
- nextLeftMargin
- 	- a number specifying the distance between left of composition zone and left of first character for the next line.
- 
- specialWidth
- 	- a number holding the width of an embedded object if any, or nil if none.
- !

Item was removed:
- ----- Method: CharacterBlockScanner>>characterBlockAtPoint:index:in: (in category 'scanning') -----
- characterBlockAtPoint: aPoint index: index in: textLine
- 	"This method is the Morphic characterBlock finder.  It combines
- 	MVC's characterBlockAtPoint:, -ForIndex:, and buildCharacterBlockIn:"
- 	| runLength lineStop stopCondition |
- 	line := textLine.
- 	rightMargin := line rightMargin.
- 	lastIndex := line first.
- 	self setStopConditions.		"also sets font"
- 	characterIndex := index.  " == nil means scanning for point"
- 	characterPoint := aPoint.
- 	(characterPoint isNil or: [characterPoint y > line bottom])
- 		ifTrue: [characterPoint := line bottomRight].
- 	destX := leftMargin := line leftMarginForAlignment: alignment.
- 	destY := line top.
- 	(text isEmpty or: [(characterPoint y < destY or: [characterPoint x < destX])
- 				or: [characterIndex notNil and: [characterIndex < line first]]])
- 		ifTrue:	[^ (CharacterBlock new stringIndex: line first text: text
- 					topLeft: destX at destY extent: 0 @ textStyle lineGrid)
- 					textLine: line].
- 	runLength := text runLengthFor: line first.
- 	lineStop := characterIndex	"scanning for index"
- 		ifNil: [ line last ].			"scanning for point"
- 	runStopIndex := lastIndex + (runLength - 1) min: lineStop.
- 	lastCharacterWidth := 0.
- 	spaceCount := 0.
- 
- 	[
- 		stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
- 			in: text string rightX: characterPoint x.
- 		"see setStopConditions for stopping conditions for character block operations."
- 		self perform: stopCondition
- 	] whileFalse.
- 	characterIndex
- 		ifNil: ["Result for characterBlockAtPoint: "
- 				^ (CharacterBlock new
- 					stringIndex: lastIndex
- 					text: text topLeft: characterPoint + (font descentKern @ 0)
- 					extent: lastCharacterWidth @ line lineHeight - (font baseKern @ 0))
- 							textLine: line]
- 		ifNotNil: ["Result for characterBlockForIndex: "
- 				^ (CharacterBlock new
- 					stringIndex: characterIndex
- 					text: text topLeft: characterPoint + ((font descentKern) - kern @ 0)
- 					extent: lastCharacterWidth @ line lineHeight)
- 							textLine: line]!

Item was removed:
- ----- Method: CharacterBlockScanner>>cr (in category 'stop conditions') -----
- cr 
- 	"Answer a CharacterBlock that specifies the current location of the mouse 
- 	relative to a carriage return stop condition that has just been 
- 	encountered. The ParagraphEditor convention is to denote selections by 
- 	CharacterBlocks, sometimes including the carriage return (cursor is at 
- 	the end) and sometimes not (cursor is in the middle of the text)."
- 
- 	((characterIndex ~= nil
- 		and: [characterIndex > text size])
- 			or: [(line last = text size)
- 				and: [(destY + line lineHeight) < characterPoint y]])
- 		ifTrue:	["When off end of string, give data for next character"
- 				destY := destY +  line lineHeight.
- 				characterPoint := (nextLeftMargin ifNil: [leftMargin]) @ destY.
- 				(lastIndex < text size and: [(text at: lastIndex) = CR and: [(text at: lastIndex+1) = Character lf]])
- 					ifTrue: [lastIndex := lastIndex + 2]
- 					ifFalse: [lastIndex := lastIndex + 1].
- 				lastCharacterWidth := 0.
- 				^ true].
- 		characterPoint := destX @ destY.
- 		lastCharacterWidth := rightMargin - destX.
- 		^true!

Item was removed:
- ----- Method: CharacterBlockScanner>>crossedX (in category 'stop conditions') -----
- crossedX
- 	"Text display has wrapping. The scanner just found a character past the x 
- 	location of the cursor. We know that the cursor is pointing at a character 
- 	or before one."
- 
- 	self retrieveLastCharacterWidth.
- 	
- 	characterPoint x <= (destX + (lastCharacterWidth // 2))
- 		ifTrue:	[characterPoint := destX @ destY.
- 				^true].
- 	lastIndex >= line last 
- 		ifTrue:	[characterPoint := destX @ destY.
- 				^true].
- 
- 	"Pointing past middle of a character, return the next character."
- 	lastIndex := lastIndex + 1.
- 	characterPoint := destX + lastCharacterWidth + kern @ destY.
- 	^ true!

Item was removed:
- ----- Method: CharacterBlockScanner>>endOfRun (in category 'stop conditions') -----
- endOfRun
- 	"Before arriving at the cursor location, the selection has encountered an 
- 	end of run. Answer false if the selection continues, true otherwise. Set 
- 	up indexes for building the appropriate CharacterBlock."
- 
- 	| runLength lineStop |
- 	
- 	(((characterIndex ~~ nil and:
- 		[runStopIndex < characterIndex and: [runStopIndex < text size]])
- 			or:	[characterIndex == nil and: [lastIndex < line last]]) or: [
- 				((lastIndex < line last)
- 				and: [((text at: lastIndex) leadingChar ~= (text at: lastIndex+1) leadingChar)
- 					and: [lastIndex ~= characterIndex]])])
- 		ifTrue:	["We're really at the end of a real run."
- 				runLength := text runLengthFor: (lastIndex := lastIndex + 1).
- 				lineStop := characterIndex	"scanning for index"
- 						ifNil: [line last].		"scanning for point".
- 				(runStopIndex := lastIndex + (runLength - 1)) > lineStop
- 					ifTrue: [runStopIndex := lineStop].
- 				self setStopConditions.
- 				^false].
- 
- 	self retrieveLastCharacterWidth.
- 		
- 	(characterIndex == nil and: [lastIndex = line last])
- 		ifTrue: [characterPoint x > (destX + (lastCharacterWidth // 2))
- 			ifTrue:
- 				[ "Correct for clicking right half of last character in line
- 				means selecting AFTER the char"
- 				lastIndex := lastIndex + 1.
- 				lastCharacterWidth := 0.
- 				characterPoint := destX + lastCharacterWidth @ destY.
- 				^true]].
- 
- 	characterPoint := destX @ destY.
- 	characterIndex ~~ nil
- 		ifTrue:	["If scanning for an index and we've stopped on that index,
- 				then we back destX off by the width of the character stopped on
- 				(it will be pointing at the right side of the character) and return"
- 				runStopIndex = characterIndex
- 					ifTrue:	[characterPoint := destX - lastCharacterWidth @ destY.
- 							^true].
- 				"Otherwise the requested index was greater than the length of the
- 				string.  Return string size + 1 as index, indicate further that off the
- 				string by setting character to nil and the extent to 0."
- 				lastIndex :=  lastIndex + 1.
- 				lastCharacterWidth := 0.
- 				^true].
- 
- 	"Scanning for a point and either off the end of the line or off the end of the string."
- 	runStopIndex = text size
- 		ifTrue:	["off end of string"
- 				lastIndex :=  lastIndex + 1.
- 				lastCharacterWidth := 0.
- 				^true].
- 	"just off end of line without crossing x"
- 	lastIndex := lastIndex + 1.
- 	^true!

Item was removed:
- ----- Method: CharacterBlockScanner>>indentationLevel: (in category 'text attributes') -----
- indentationLevel: anInteger
- 	super indentationLevel: anInteger.
- 	nextLeftMargin := leftMargin.
- 	indentationLevel timesRepeat: [
- 		nextLeftMargin := textStyle nextTabXFrom: nextLeftMargin
- 					leftMargin: leftMargin
- 					rightMargin: rightMargin]!

Item was removed:
- ----- Method: CharacterBlockScanner>>paddedSpace (in category 'stop conditions') -----
- paddedSpace
- 	"When the line is justified, the spaces will not be the same as the font's 
- 	space character. A padding of extra space must be considered in trying 
- 	to find which character the cursor is pointing at. Answer whether the 
- 	scanning has crossed the cursor."
- 
- 	| pad |
- 	spaceCount := spaceCount + 1.
- 	pad := line justifiedPadFor: spaceCount font: font.
- 	lastCharacterWidth := spaceWidth + pad.
- 	(destX + lastCharacterWidth)  >= characterPoint x
- 		ifTrue:
- 			[^self crossedX].
- 	lastIndex := lastIndex + 1.
- 	destX := destX + lastCharacterWidth + kern.
- 	pendingKernX := 0.
- 	^ false
- !

Item was removed:
- ----- Method: CharacterBlockScanner>>placeEmbeddedObjectFrom: (in category 'private') -----
- placeEmbeddedObjectFrom: aTextAttribute
- 	
- 	| width anchoredMorphOrForm textAnchorProperties |
- 	anchoredMorphOrForm := aTextAttribute anchoredMorph.
- 	textAnchorProperties := self textAnchorPropertiesFor: anchoredMorphOrForm.
- 	
- 	textAnchorProperties anchorLayout == #document ifTrue: [^ true].
- 	width := textAnchorProperties consumesHorizontalSpace 
- 		ifTrue: [anchoredMorphOrForm width + textAnchorProperties horizontalPadding]
- 		ifFalse: [0].
- 	
- 	lastCharacterWidth := width.	
- 	
- 	(destX + width > characterPoint x) ifTrue: [^false].
- 	destX := destX + width + kern.
- 	^ true!

Item was removed:
- ----- Method: CharacterBlockScanner>>retrieveLastCharacterWidth (in category 'private') -----
- retrieveLastCharacterWidth
- 	| lastCharacter |
- 	lastIndex > text size ifTrue: [^lastCharacterWidth := 0].
- 	lastCharacter := text at: lastIndex.
- 	(lastCharacter charCode >= 256 or: [(stopConditions at: lastCharacter charCode + 1) isNil])
- 		ifTrue: [lastCharacterWidth := font widthOf: (text at: lastIndex)].
- 	"if last character was a stop condition, then the width is already set"
- 	^lastCharacterWidth!

Item was removed:
- ----- Method: CharacterBlockScanner>>setFont (in category 'stop conditions') -----
- setFont
- 	super setFont!

Item was removed:
- ----- Method: CharacterBlockScanner>>tab (in category 'stop conditions') -----
- tab
- 	| nextDestX |
- 	nextDestX := self plainTab.
- 	lastCharacterWidth := nextDestX - destX max: 0.
- 	nextDestX >= characterPoint x
- 		ifTrue: 
- 			[^ self crossedX].
- 	destX := nextDestX.
- 	lastIndex := lastIndex + 1.
- 	^false!

Item was removed:
- Object subclass: #CharacterScanner
- 	instanceVariableNames: 'destX lastIndex xTable map destY stopConditions text textStyle alignment leftMargin rightMargin font line runStopIndex spaceCount spaceWidth emphasisCode kern indentationLevel wantsColumnBreaks pendingKernX'
- 	classVariableNames: 'ColumnBreakStopConditions CompositionStopConditions DefaultStopConditions MeasuringStopConditions PaddedSpaceCondition'
- 	poolDictionaries: 'TextConstants'
- 	category: 'Graphics-Text'!
- 
- !CharacterScanner commentStamp: 'nice 10/22/2013 20:04' prior: 0!
- A CharacterScanner holds the state associated with scanning text. Subclasses scan characters for specified purposes, such as computing a CharacterBlock or placing characters into Forms.
- 
- Instance Variables
- 	alignment:		<Integer>
- 	destX:		<Number>
- 	destY:		<Number>
- 	emphasisCode:		<Object>
- 	font:		<AbstractFont>
- 	indentationLevel:		<Integer>
- 	kern:		<Number>
- 	lastIndex:		<Integer>
- 	leftMargin:		<Number>
- 	line:		<TextLine>
- 	map:		<Array>
- 	pendingKernX:		<Number>
- 	rightMargin:		<Number>
- 	runStopIndex:		<Integer>
- 	spaceCount:		<Integer>
- 	spaceWidth:		<Number>
- 	stopConditions:		<Array>
- 	text:		<Text>
- 	textStyle:		<TextStyle>
- 	wantsColumnBreaks:		<Boolean>
- 	xTable:		<Array>
- 
- alignment
- 	- an Integer encoding the alignment of text
- 
- destX
- 	- horizontal position for next character (distance from left of composition area)
- 
- destY
- 	- vertical position for next character (distance from top of composition area)
- 
- emphasisCode
- 	- an Integer encoding the current text emphasis to use (bold, italic, ...)
- 
- font
- 	- the current font used for measuring/composing/displaying characters
- 
- indentationLevel
- 	- an Integer specifying a number of leading tabs to be inserted at beginning of new lines
- 
- kern
- 	- a Number specifying additional horizontal spacing to place between characters (spacing is reduced when kern is negative)
- 
- lastIndex
- 	- the Integer index of next character to be processed in the text
- 
- leftMargin
- 	- a Number specifying the distance between left of composition zone and left of first character in the line.
- 
- line
- 	- an object holding information about the line currently being displayed (like first and last index in text).
- 	Note: this is either a TextLine in Morphic, or TextLineInterval for ST80 compatibility
- 
- map
- 	- an array mapping character code to glyph position.
- 	This is used by primitive 103 only, in case of ByteString.
- 
- pendingKernX
- 	- a Number to be added to horizontal spacing of next char if ever it is in the same font than previous one.
- 	The inner scan loop is interrupted by a change of text run.
- 	But some changes won't change the font, so the kerning must be remembered and applied later.
- 
- rightMargin
- 	- a Number specifying the distance between right of composition zone and right of last character in the line.
- 
- runStopIndex
- 	- the Integer index of last character in current text run.
- 
- spaceCount
- 	- the number of spaces encoutered so far in current line. This is useful for adjusting the spacing in cas of Justified alignment.
- 
- spaceWidth
- 	- the width of space character in current font.
- 
- stopConditions
- 	- an Array mapping a table of characters codes for which special actions are to be taken.
- 	These are typically control characters like carriage return or horizontal tab.
- 
- text
- 	- the text to be measured/composed/displayed
- 
- textStyle
- 	- an object holding a context for the text style (which set of font to use, which margins, etc...)
- 
- wantsColumnBreaks
- 	- a Boolean indicating whether some special handling for multiple columns is requested.
- 	THIS ONLY MAKES SENSE IN CompositionScanner AND SHOULD BE MOVED TO THE SUBCLASS
- 	
- xTable
- 	- an array mapping character code to glyph x coordinate in form.
- 	This is used by primitive 103 only, in case of ByteString.
- 	
- Implementation note: accelerated Character scanning with primitive 103 requires following order for 5 first instance variables, please don't alter:
- destX lastIndex xTable map destY
- !

Item was removed:
- ----- Method: CharacterScanner class>>initialize (in category 'class initialization') -----
- initialize
- "
- 	CharacterScanner initialize
- "
- 	| a |
- 	a := Array new: 258.
- 	a at: 1 + 1 put: #embeddedObject.
- 	a at: Tab asciiValue + 1 put: #tab.
- 	a at: CR asciiValue + 1 put: #cr.
- 	a at: Character lf asciiValue + 1 put: #cr.
- 	"Note: following two codes are used only by primitive 103 for accelerated Character scanning"
- 	a at: 257 put: #endOfRun.
- 	a at: 258 put: #crossedX.
- 	
- 	DefaultStopConditions := a copy.
- 
- 	CompositionStopConditions := a copy.
- 	CompositionStopConditions at: Space asciiValue + 1 put: #space.
- 	ColumnBreakStopConditions := CompositionStopConditions copy.
- 	ColumnBreakStopConditions at: Character characterForColumnBreak asciiValue + 1 put: #columnBreak.
- 
- 	PaddedSpaceCondition := a copy.
- 	PaddedSpaceCondition at: Space asciiValue + 1 put: #paddedSpace.
- 
- 	MeasuringStopConditions := (Array new: 258)
- 		at: 257 put: #endOfRun;
- 		at: 258 put: #crossedX;
- 		yourself!

Item was removed:
- ----- Method: CharacterScanner>>addEmphasis: (in category 'text attributes') -----
- addEmphasis: code
- 	"Set the bold-ital-under-strike emphasis."
- 	emphasisCode := emphasisCode bitOr: code!

Item was removed:
- ----- Method: CharacterScanner>>addKern: (in category 'text attributes') -----
- addKern: kernDelta
- 	"Set the current kern amount."
- 	kern := kern + kernDelta!

Item was removed:
- ----- Method: CharacterScanner>>advanceIfFirstCharOfLine (in category 'private') -----
- advanceIfFirstCharOfLine
- 	lastIndex = line first
- 		ifTrue:
- 			[destX := destX + pendingKernX + (font widthOf: (text at: line first)).
- 			lastIndex := lastIndex + 1.
- 			pendingKernX := 0].!

Item was removed:
- ----- Method: CharacterScanner>>basicScanByteCharactersFrom:to:in:rightX: (in category 'scanning') -----
- basicScanByteCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX 
- 	"This is a scanning method for single-byte characters in a ByteString
- 	a font that does not do character-pair kerning."
- 	
- 	| codePointPlusOne nextDestX char |
- 	lastIndex := startIndex.
- 	[lastIndex <= stopIndex]
- 		whileTrue: [
- 			"get the character value"
- 			char := sourceString at: lastIndex.
- 			codePointPlusOne := char asInteger + 1.
- 			"if there is an entry in 'stops' for this value, return it"
- 			(stopConditions at: codePointPlusOne)
- 				ifNotNil: [^ stopConditions at: codePointPlusOne].
- 			"bump nextDestX by the width of the current character"
- 			nextDestX := destX + (font widthOfByteCharacter: char).
- 			"if the next x is past the right edge, return crossedX"
- 			nextDestX > rightX
- 				ifTrue: [^#crossedX].
- 			"update destX and incorporate thr kernDelta"
- 			destX := nextDestX + kern.
- 			lastIndex := lastIndex + 1].
- 	^self handleEndOfRunAt: stopIndex
- 
- !

Item was removed:
- ----- Method: CharacterScanner>>columnBreak (in category 'stop conditions') -----
- columnBreak
- 
- 	pendingKernX := 0.
- 	^true!

Item was removed:
- ----- Method: CharacterScanner>>embeddedObject (in category 'stop conditions') -----
- embeddedObject
- 
- 	| previousAttributes newAttributes |
- 	pendingKernX := 0.
- 	"If a text anchor was already at the previous index, it was already dealt with"
- 	previousAttributes := lastIndex > 1 ifTrue: [text attributesAt: lastIndex - 1] ifFalse: [#()].
- 	newAttributes := (text attributesAt: lastIndex) copyWithoutAll: previousAttributes.
- 	(newAttributes reject: [:each | each anchoredMorph isNil])
- 		ifNotEmpty: [:attributes | (self placeEmbeddedObjectsFrom: attributes) ifTrue: [^ true]].
- 	self setFont.
-  
- 	"Note: if ever several objects are embedded on same character, only indent lastIndex once"
- 	lastIndex := lastIndex + 1.
- 	^ false!

Item was removed:
- ----- Method: CharacterScanner>>handleEndOfRunAt: (in category 'scanner methods') -----
- handleEndOfRunAt: stopIndex
- 	" make sure the lastIndex is set to stopIndex and then return the stopCondition for endOfRun; important for  a couple of outside users"
- 
- 	lastIndex := stopIndex.
- 	^#endOfRun!

Item was removed:
- ----- Method: CharacterScanner>>handleIndentation (in category 'private') -----
- handleIndentation
- 	self indentationLevel timesRepeat: [
- 		destX := self plainTab]!

Item was removed:
- ----- Method: CharacterScanner>>indentationLevel (in category 'private') -----
- indentationLevel
- 	"return the number of tabs that are currently being placed at the beginning of each line"
- 	^indentationLevel ifNil:[0]!

Item was removed:
- ----- Method: CharacterScanner>>indentationLevel: (in category 'text attributes') -----
- indentationLevel: anInteger
- 	"set the number of tabs to put at the beginning of each line"
- 	indentationLevel := anInteger!

Item was removed:
- ----- Method: CharacterScanner>>initialize (in category 'initialize') -----
- initialize
- 	destX := destY := leftMargin := 0.!

Item was removed:
- ----- Method: CharacterScanner>>leadingTab (in category 'private') -----
- leadingTab
- 	"return true if only tabs lie to the left"
- 	line first to: lastIndex do:
- 		[:i | (text at: i) == Tab ifFalse: [^ false]].
- 	^ true!

Item was removed:
- ----- Method: CharacterScanner>>measureString:inFont:from:to: (in category 'scanning') -----
- measureString: aString inFont: aFont from: startIndex to: stopIndex
- 	"Measure aString width in given font aFont.
- 	The string shall not include line breaking, tab or other control character."
- 	destX := destY := lastIndex := 0.
- 	pendingKernX := 0.
- 	font := aFont.
- 	kern := 0 - font baseKern.
- 	spaceWidth := font widthOf: Space.
- 	stopConditions := MeasuringStopConditions.
- 	self scanCharactersFrom: startIndex to: stopIndex in: aString rightX: 999999.
- 	^destX!

Item was removed:
- ----- Method: CharacterScanner>>placeEmbeddedObjectFrom: (in category 'private-text-anchor') -----
- placeEmbeddedObjectFrom: aTextAttribute
- 	"Place the anchoredMorph or return false if it cannot be placed"
- 	^ true!

Item was removed:
- ----- Method: CharacterScanner>>placeEmbeddedObjectsFrom: (in category 'private-text-anchor') -----
- placeEmbeddedObjectsFrom: textAttributes
- 	textAttributes do: [:attr |
- 		"Try to placeEmbeddedObject: - if it answers false, then there's no place left"
- 		(self placeEmbeddedObjectFrom: attr) ifFalse: [^ self crossedX]].
- 	^ false!

Item was removed:
- ----- Method: CharacterScanner>>plainTab (in category 'private') -----
- plainTab
- 	"This is the basic method of adjusting destX for a tab.
- 	Answer the next destX"
- 	pendingKernX := 0.
- 	^(alignment = Justified and: [self leadingTab not])
- 		ifTrue:		"embedded tabs in justified text are weird"
- 			[destX + (textStyle tabWidth - (line justifiedTabDeltaFor: spaceCount)) max: destX]
- 		ifFalse: 
- 			[textStyle nextTabXFrom: destX
- 				leftMargin: leftMargin
- 				rightMargin: rightMargin].!

Item was removed:
- ----- Method: CharacterScanner>>primScanCharactersFrom:to:in:rightX:stopConditions:kern: (in category 'scanning') -----
- primScanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta
- 	"Primitive. This is the inner loop of text display--but see #scanCharactersFrom:to:in:rightX: which would get the string, stopConditions and displaying from the instance. March through sourceString from startIndex to stopIndex. If any character is flagged with a non-nil entry in stops, then return the corresponding value. Determine width of each character from xTable, indexed by map. If destX would exceed rightX, then return stops at: 258. Advance destX by the width of the character. If stopIndex has been reached, then return stops at: 257. 
- 	
- 	Optional. See Object documentation whatIsAPrimitive.
- 	
- 	NOTE THAT this primitive does only work for our legacy StrikeFont because #setActualFont: needs #xTable and #characterToGlyphMap, which are both not available for TTCFont this way and thus we end up calling #widthOf: manually on the font."
- 	
- 	<primitive: 103>
- 	^self basicScanByteCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX 
- 	
- "Here are some sketchy benchmarks to illustrate the performance issue regarding the use of TrueType fonts:
- 
- 1) TTCFont only; with primitive fail
-  '1,160 per second. 865 microseconds per run. 0.44 % GC time.' 
- 
- 2) TTCFont only; without primitive fail
-  '5,730 per second. 175 microseconds per run. 6.12 % GC time.' 
- 
- 3) StrikeFont only; using primitive 103
-  '29,700 per second. 33.6 microseconds per run. 1.11978 % GC time.' 
- 
- 4) StrikeFont only; without primitive 103
-  '13,900 per second. 71.7 microseconds per run. 1.17976 % GC time.' 
- 
- "!

Item was removed:
- ----- Method: CharacterScanner>>scanByteCharactersFrom:to:in:rightX: (in category 'scanning') -----
- scanByteCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX 
- "this is a scanning method for
- single byte characters in a ByteString
- a font that does not do character-pair kerning"
- 	^self primScanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stopConditions kern: kern
- !

Item was removed:
- ----- Method: CharacterScanner>>scanCharactersFrom:to:in:rightX: (in category 'scanning') -----
- scanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX 
- 	^sourceString scanCharactersFrom: startIndex to: stopIndex with: self rightX: rightX font: font!

Item was removed:
- ----- Method: CharacterScanner>>scanCharactersFrom:to:in:rightX:stopConditions:kern: (in category 'scanning') -----
- scanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta 
- 	^sourceString scanCharactersFrom: startIndex to: stopIndex with: self rightX: rightX font: font!

Item was removed:
- ----- Method: CharacterScanner>>scanKernableByteCharactersFrom:to:in:rightX: (in category 'scanning') -----
- scanKernableByteCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX 
- "this is a scanning method for
- single byte characters in a ByteString
- a font that does do character-pair kerning via widthAndKernedWidthOfLeft:right:into:"
- 	| ascii nextDestX char floatDestX widthAndKernedWidth nextCharOrNil atEndOfRun |
- 	lastIndex := startIndex.
- 	floatDestX := destX.
- 	widthAndKernedWidth := Array new: 2.
- 	atEndOfRun := false.
- 	[lastIndex <= stopIndex]
- 		whileTrue: [
- 			"get the character value"
- 			char := sourceString at: lastIndex.
- 			ascii := char asciiValue + 1.
- 			"if there is an entry in 'stops' for this value, return it"
- 			(stopConditions at: ascii)
- 				ifNotNil: [^ stopConditions at: ascii].
- 			"get the next character..."
- 			nextCharOrNil := lastIndex + 1 <= stopIndex
- 						ifTrue: [sourceString at: lastIndex + 1]
- 						ifFalse: ["if we're at or past the stopIndex, see if there is anything in the full string"
- 							atEndOfRun := true.
- 							lastIndex + 1 <= sourceString size
- 								ifTrue: [sourceString at: lastIndex + 1]].
- 			"get the font's kerning info for the pair of current character and next character"
- 			"for almost all fonts in common use this is a waste of time since they don't support pair kerning and both values are #widthOf: char"
- 			font
- 				widthAndKernedWidthOfLeft: char
- 				right: nextCharOrNil
- 				into: widthAndKernedWidth.
- 			"bump nextDestX by the width of the current character"
- 			nextDestX := floatDestX
- 						+ (widthAndKernedWidth at: 1).
- 			"if the next x is past the right edge, return crossedX"
- 			nextDestX > rightX
- 				ifTrue: [^ #crossedX].
- 			"bump floatDestX by the *kerned* width of the current
- 			character, which is where the *next* char will go"
- 			floatDestX := floatDestX + kern
- 						+ (widthAndKernedWidth at: 2).
- 			"if we are at the end of this run we keep track of the
- 			character-kern-delta for possible later use and then rather
- 			insanely remove that character-kern-delta from floatDestX,
- 			making it equivalent to (old floatDestX) + kernDelta +
- 			width-of-character - no idea why"
- 			atEndOfRun
- 				ifTrue: [pendingKernX := (widthAndKernedWidth at: 2)
- 								- (widthAndKernedWidth at: 1).
- 					floatDestX := floatDestX - pendingKernX].
- 			"save the next x for next time around the loop"
- 			destX := floatDestX.
- 			lastIndex := lastIndex + 1].
- 	^self handleEndOfRunAt: stopIndex
- !

Item was removed:
- ----- Method: CharacterScanner>>setActualFont: (in category 'text attributes') -----
- setActualFont: aFont
- 	"Set the basal font to an isolated font reference."
- 
- 	xTable := aFont xTable.
- 	map := aFont characterToGlyphMap.
- 	font := aFont.!

Item was removed:
- ----- Method: CharacterScanner>>setAlignment: (in category 'text attributes') -----
- setAlignment: style
- 	alignment := style.
- 	!

Item was removed:
- ----- Method: CharacterScanner>>setFont (in category 'private') -----
- setFont
- 	| priorFont |
- 	"Set the font and other emphasis."
- 	priorFont := font.
- 	text ifNotNil:[
- 		emphasisCode := 0.
- 		kern := 0.
- 		indentationLevel := 0.
- 		alignment := textStyle alignment.
- 		font := nil.
- 		(text attributesAt: lastIndex forStyle: textStyle)
- 			do: [:att | att emphasizeScanner: self]].
- 	font ifNil: [self setFont: textStyle defaultFontIndex].
- 	self setActualFont: (font emphasized: emphasisCode).
- 	priorFont 
- 		ifNotNil: [
- 			font = priorFont 
- 				ifTrue:[
- 					"font is the same, perhaps the color has changed?
- 					We still want kerning between chars of the same
- 					font, but of different color. So add any pending kern to destX"
- 					destX := destX + (pendingKernX ifNil:[0])].
- 			destX := destX + priorFont descentKern].
- 	pendingKernX := 0. "clear any pending kern so there is no danger of it being added twice"
- 	destX := destX - font descentKern.
- 	"NOTE: next statement should be removed when clipping works"
- 	leftMargin ifNotNil: [destX := destX max: leftMargin].
- 	kern := kern - font baseKern.
- 
- 	"Install various parameters from the font."
- 	spaceWidth := font widthOf: Space.!

Item was removed:
- ----- Method: CharacterScanner>>setFont: (in category 'text attributes') -----
- setFont: fontNumber
- 	"Set the font by number from the textStyle."
- 
- 	self setActualFont: (textStyle fontAt: fontNumber)!

Item was removed:
- ----- Method: CharacterScanner>>setStopConditions (in category 'private') -----
- setStopConditions
- 	"Set the font and the stop conditions for the current run."
- 	
- 	self setFont.
- 	stopConditions := alignment = Justified
- 		ifTrue: [PaddedSpaceCondition]
- 		ifFalse: [DefaultStopConditions]!

Item was removed:
- ----- Method: CharacterScanner>>text:textStyle: (in category 'private') -----
- text: t textStyle: ts
- 	text := t.
- 	textStyle := ts!

Item was removed:
- ----- Method: CharacterScanner>>textAnchorPropertiesFor: (in category 'private-text-anchor') -----
- textAnchorPropertiesFor: aMorphOrForm
- 
- 	^ aMorphOrForm textAnchorProperties!

Item was removed:
- ----- Method: CharacterScanner>>textColor: (in category 'text attributes') -----
- textColor: ignored
- 	"Overridden in DisplayScanner"!

Item was removed:
- Object subclass: #Color
- 	instanceVariableNames: 'rgb cachedDepth cachedBitPattern'
- 	classVariableNames: 'Black Blue BlueShift Brown CachedColormaps ColorChart ColorNames ComponentMask ComponentMax Cyan DarkGray Gray GrayToIndexMap Green GreenShift HalfComponentMask HighLightBitmaps IndexedColors LightBlue LightBrown LightCyan LightGray LightGreen LightMagenta LightOrange LightRed LightYellow Magenta MaskingMap Orange PaleBlue PaleBuff PaleGreen PaleMagenta PaleOrange PalePeach PaleRed PaleTan PaleYellow PantonePurpleU PureBlue PureCyan PureGreen PureMagenta PureRed PureYellow RGBToNames RandomStream Red RedShift TranslucentPatterns Transparent VeryDarkGray VeryLightGray VeryPaleRed VeryVeryDarkGray VeryVeryLightGray White Yellow'
- 	poolDictionaries: ''
- 	category: 'Graphics-Primitives'!
- 
- !Color commentStamp: '<historical>' prior: 0!
- This class represents abstract color, regardless of the depth of bitmap it will be shown in.  At the very last moment a Color is converted to a pixelValue that depends on the depth of the actual Bitmap inside the Form it will be used with.  The supported depths (in bits) are 1, 2, 4, 8, 16, and 32.  The number of actual colors at these depths are: 2, 4, 16, 256, 32768, and 16 million.  (See comment in BitBlt.)  To change the depth of the Display and set how many colors you can see, execute: (Display newDepth: 8).  (See comment in DisplayMedium)
- 	Color is represented as the amount of light in red, green, and blue.  White is (1.0, 1.0, 1.0) and black is (0, 0, 0).  Pure red is (1.0, 0, 0).  These colors are "additive".  Think of Color's instance variables as:
- 	r	amount of red, a Float between 0.0 and 1.0.
- 	g	amount of green, a Float between 0.0 and 1.0.
- 	b	amount of blue, a Float between 0.0 and 1.0.
- (But, in fact, the three are encoded as values from 0 to 1023 and combined in a single integer, rgb.  The user does not need to know this.)
- 	Many colors are named.  You find a color by name by sending a message to class Color, for example (Color lightBlue).  Also, (Color red: 0.2 green: 0.6 blue: 1.0) or (Color r: 0.2 g: 0.6 b: 1.0) creates a color. (see below)
- 	A color is essentially immutable.  Once you set red, green, and blue, you cannot change them.  Instead, create a new Color and use it.
- 	Applications such as contour maps and bar graphs will want to display one of a set of shades based on a number.  Convert the range of this number to an integer from 1 to N.  Then call (Color green lightShades: N) to get an Array of colors from white to green.  Use the Array messages at:, atPin:, or atWrap: to pull out the correct color from the array.  atPin: gives the first (or last) color if the index is out of range.  atWrap: wraps around to the other end if the index is out of range.
- 	Here are some fun things to run in when your screen has color:
- 		Pen new mandala: 30 diameter: Display height-100.
- 		Pen new web  "Draw with the mouse, opt-click to end"
- 		Display fillWhite.  Pen new hilberts: 5.
- 		Form toothpaste: 30  "Draw with mouse, opt-click to end"
- You might also want to try the comment in
- 	Form>class>examples>tinyText...
- 
- 
- Messages:
- 	mixed: proportion with: aColor	Answer this color mixed with the given color additively. The proportion, a number between 0.0 and 1.0, determines what what fraction of the receiver to use in the mix.
- 
- 	+ 	add two colors
- 	- 	subtract two colors
- 	*	multiply the values of r, g, b by a number or an Array of factors.  ((Color named: #white) * 0.3) gives a darkish gray.  (aColor * #(0 0 0.9)) gives a color with slightly less blue.
- 	/	divide a color by a factor or an array of three factors.
- 
- 	errorForDepth: d     How close the nearest color at this depth is to this abstract color.  Sum of the squares of the RGB differences, square rooted and normalized to 1.0.  Multiply by 100 to get percent.
- 
- 	hue			Returns the hue of the color. On a wheel from 0 to 360 with pure red at 0 and again at 360.
- 	saturation	Returns the saturation of the color.  0.0 to 1.0
- 	brightness	Returns the brightness of the color.  0.0 to 1.0
- 
- 	name    Look to see if this Color has a name.
- 	display	Show a swatch of this color tracking the cursor.
- 
- 	lightShades: thisMany		An array of thisMany colors from white to the receiver. 
- 	darkShades: thisMany		An array of thisMany colors from black to the receiver.  Array is of length num.
- 	mix: color2 shades: thisMany		An array of thisMany colors from the receiver to color2.
- 	wheel: thisMany			An array of thisMany colors around the color wheel starting and ending at the receiver.
- 
- 	pixelValueForDepth: d    Returns the bits that appear be in a Bitmap of this depth for this color.  Represents the nearest available color at this depth.  Normal users do not need to know which pixelValue is used for which color. 
- 
- Messages to Class Color.
- 	red: r green: g blue: b		Return a color with the given r, g, and b components.
- 	r: g: b:		Same as above, for fast typing.
- 
-  	hue: h saturation: s brightness: b		Create a color with the given hue, saturation, and brightness.
- 
- 	pink
-  	blue
- 	red ...	Many colors have messages that return an instance of Color.
- 	canUnderstand: #brown	  Returns true if #brown is a defined color.
- 	names		An OrderedCollection of the names of the colors.
- 	named: #notAllThatGray put: aColor    Add a new color to the list and create an access message and a class variable for it.
- 	fromUser	Shows the palette of colors available at this display depth.  Click anywhere to return the color you clicked on.
- 
- 	hotColdShades: thisMany	An array of thisMany colors showing temperature from blue to red to white hot.
- 
-     stdColorsForDepth: d        An Array of colors available at this depth.  For 16 bit and 32 bits, returns a ColorGenerator.  It responds to at: with a Color for that index, simulating a very big Array. 
- 
-    colorFromPixelValue: value depth: d    Returns a Color whose bit pattern (inside a Bitmap) at this depth is the number specified.  Normal users do not need to use this.
- 
- (See also comments in these classes: Form, Bitmap, BitBlt, Pattern, MaskedForm.)!

Item was removed:
- ----- Method: Color class>>aluminum (in category 'named colors - crayons') -----
- aluminum
- 
- 	^ Color r: 153/255 g: 153/255 b: 153/255!

Item was removed:
- ----- Method: Color class>>aqua (in category 'named colors - crayons') -----
- aqua
- 
- 	^ Color r: 0.0 g: 128/255 b: 1.0!

Item was removed:
- ----- Method: Color class>>asparagus (in category 'named colors - crayons') -----
- asparagus
- 
- 	^ Color r: 128/255 g: 128/255 b: 0.0!

Item was removed:
- ----- Method: Color class>>banana (in category 'named colors - crayons') -----
- banana
- 
- 	^ Color r: 1.0 g: 1.0 b: 102/255!

Item was removed:
- ----- Method: Color class>>black (in category 'named colors') -----
- black
- 	^Black!

Item was removed:
- ----- Method: Color class>>blue (in category 'named colors') -----
- blue
- 	^Blue!

Item was removed:
- ----- Method: Color class>>blueberry (in category 'named colors - crayons') -----
- blueberry
- 
- 	^ Color r: 0.0 g: 0.0 b: 1.0!

Item was removed:
- ----- Method: Color class>>brown (in category 'named colors') -----
- brown
- 	^Brown!

Item was removed:
- ----- Method: Color class>>bubblegum (in category 'named colors - crayons') -----
- bubblegum
- 
- 	^ Color r: 1.0 g: 102/255 b: 1.0!

Item was removed:
- ----- Method: Color class>>cachedColormapFrom:to: (in category 'colormaps') -----
- cachedColormapFrom: sourceDepth to: destDepth
- 	"Return a cached colormap for mapping between the given depths. Always return a real colormap, not nil; this allows the client to get an identity colormap that can then be copied and modified to do color transformations."
- 	"Note: This method returns a shared, cached colormap to save time and space. Clients that need to modify a colormap returned by this method should make a copy and modify that!!"
- 	"Note: The colormap cache may be cleared by evaluating 'Color shutDown'."
- 
- 	| srcIndex map |
- 	CachedColormaps class == Array ifFalse: [CachedColormaps := (1 to: 9) collect: [:i | Array new: 32]].
- 	srcIndex := sourceDepth.
- 	sourceDepth > 8 ifTrue: [srcIndex := 9].
- 	(map := (CachedColormaps at: srcIndex) at: destDepth) ~~ nil ifTrue: [^ map].
- 
- 	map := self computeColormapFrom: sourceDepth to: destDepth.
- 	(CachedColormaps at: srcIndex) at: destDepth put: map.
- 	^ map
- !

Item was removed:
- ----- Method: Color class>>cantaloupe (in category 'named colors - crayons') -----
- cantaloupe
- 
- 	^ Color r: 1.0 g: 204/255 b: 102/255!

Item was removed:
- ----- Method: Color class>>carnation (in category 'named colors - crayons') -----
- carnation
- 
- 	^ Color r: 1.0 g: 111/255 b: 207/255!

Item was removed:
- ----- Method: Color class>>cayenne (in category 'named colors - crayons') -----
- cayenne
- 
- 	^ Color r: 128/255 g: 0.0 b: 0.0!

Item was removed:
- ----- Method: Color class>>cleanUp: (in category 'class initialization') -----
- cleanUp: aggressive
- 	self initializeNamesMap!

Item was removed:
- ----- Method: Color class>>clover (in category 'named colors - crayons') -----
- clover
- 
- 	^ Color r: 0.0 g: 128/255 b: 0.0!

Item was removed:
- ----- Method: Color class>>colorFrom: (in category 'instance creation') -----
- colorFrom: parm
- 	"Return an instantiated color from parm.  If parm is already a color, return it, else return the result of my performing it if it's a symbol or, if it is a list, it can either be an array of three numbers, which will be interpreted as RGB values, or a list of symbols, the first of which is sent to me and then the others of which are in turn sent to the prior result, thus allowing entries of the form #(blue darker).  Else just return the thing"
- 
- 	| aColor firstParm |
- 	(parm isKindOf: Color) ifTrue: [^ parm].
- 	(parm isSymbol) ifTrue: [^ self perform: parm].
- 	(parm isString) ifTrue: [^ self fromString: parm].
- 	((parm isKindOf: SequenceableCollection) and: [parm size > 0])
- 		ifTrue:
- 			[firstParm := parm first.
- 			(firstParm isKindOf: Number) ifTrue:
- 				[^ self fromRgbTriplet: parm].
- 			aColor := self colorFrom: firstParm.
- 			parm withIndexDo:
- 				[:sym :ind | ind > 1 ifTrue:
- 					[aColor := aColor perform: sym]].
- 			^ aColor].
- 	^ parm
- 
- "
- Color colorFrom: #(blue darker)
- Color colorFrom: Color blue darker
- Color colorFrom: #blue
- Color colorFrom: #(0.0 0.0 1.0)
- "!

Item was removed:
- ----- Method: Color class>>colorFromPixelValue:depth: (in category 'instance creation') -----
- colorFromPixelValue: p depth: d
- 	"Convert a pixel value for the given display depth into a color."
- 	"Details: For depths of 8 or less, the pixel value is simply looked up in a table. For greater depths, the color components are extracted and converted into a color."
- 
- 	| r g b alpha |
- 	d = 8 ifTrue: [^ IndexedColors at: (p bitAnd: 16rFF) + 1].
- 	d = 4 ifTrue: [^ IndexedColors at: (p bitAnd: 16r0F) + 1].
- 	d = 2 ifTrue: [^ IndexedColors at: (p bitAnd: 16r03) + 1].
- 	d = 1 ifTrue: [^ IndexedColors at: (p bitAnd: 16r01) + 1].
- 
- 	(d = 16) | (d = 15) ifTrue: [
- 		"five bits per component"
- 		r := (p bitShift: -10) bitAnd: 16r1F.
- 		g := (p bitShift: -5) bitAnd: 16r1F.
- 		b := p bitAnd: 16r1F.
- 		(r = 0 and: [g = 0]) ifTrue: [
- 			b = 0 ifTrue: [^Color transparent].
- 			b = 1 ifTrue: [^Color black]].
- 		^ Color r: r g: g b: b range: 31].
- 
- 	d = 32 ifTrue: [
- 		"eight bits per component; 8 bits of alpha"
- 		r := (p bitShift: -16) bitAnd: 16rFF.
- 		g := (p bitShift: -8) bitAnd: 16rFF.
- 		b := p bitAnd: 16rFF.
- 		alpha := p bitShift: -24.
- 		alpha = 0 ifTrue: [^Color transparent].
- 		(r = 0 and: [g = 0 and: [b = 0]])  ifTrue: [^Color transparent].
- 		alpha < 255
- 			ifTrue: [^ (Color r: r g: g b: b range: 255) alpha: (alpha asFloat / 255.0)]
- 			ifFalse: [^ (Color r: r g: g b: b range: 255)]].
- 
- 	d = 12 ifTrue: [
- 		"four bits per component"
- 		r := (p bitShift: -8) bitAnd: 16rF.
- 		g := (p bitShift: -4) bitAnd: 16rF.
- 		b := p bitAnd: 16rF.
- 		^ Color r: r g: g b: b range: 15].
- 
- 	d = 9 ifTrue: [
- 		"three bits per component"
- 		r := (p bitShift: -6) bitAnd: 16r7.
- 		g := (p bitShift: -3) bitAnd: 16r7.
- 		b := p bitAnd: 16r7.
- 		^ Color r: r g: g b: b range: 7].
- 
- 	self error: 'unknown pixel depth: ', d printString
- !

Item was removed:
- ----- Method: Color class>>colorMapIfNeededFrom:to: (in category 'colormaps') -----
- colorMapIfNeededFrom: sourceDepth to: destDepth
- 	"Return a colormap for mapping between the given depths, or nil if no colormap is needed."
- 	"Note: This method returns a shared, cached colormap to save time and space. Clients that need to modify a colormap returned by this method should make a copy and modify that!!"
- 
- 	sourceDepth = destDepth ifTrue: [^ nil].  "not needed if depths are the same"
- 
- 	(sourceDepth >= 16) & (destDepth >= 16) ifTrue: [
- 		"mapping is done in BitBlt by zero-filling or truncating each color component"
- 		^ nil].
- 
- 	^ Color cachedColormapFrom: sourceDepth to: destDepth
- !

Item was removed:
- ----- Method: Color class>>colorNames (in category 'other') -----
- colorNames
- 	"Return a collection of color names."
- 
- 	^ ColorNames asArray, self orderedCrayonColorNames!

Item was removed:
- ----- Method: Color class>>colorRampForDepth:extent: (in category 'examples') -----
- colorRampForDepth: depth extent: aPoint
- 	"Returns a form of the given size showing R, G, B, and gray ramps for the given depth. Useful for testing color conversions between different depths."
- 	"(Color colorRampForDepth: Display depth extent: 256 at 80) display"
- 	"(Color colorRampForDepth: 32 extent: 256 at 80) displayOn: Display at: 0 at 0 rule: Form paint"
- 
- 	| f dx dy r |
- 	f := Form extent: aPoint depth: depth.
- 	dx := aPoint x // 256.
- 	dy := aPoint y // 4.
- 	0 to: 255 do: [:i |
- 		r := (dx * i)@0 extent: dx at dy.
- 		f fill: r fillColor: (Color r: i g: 0 b: 0 range: 255).
- 		r := r translateBy: 0 at dy.
- 		f fill: r fillColor: (Color r: 0 g: i b: 0 range: 255).
- 		r := r translateBy: 0 at dy.
- 		f fill: r fillColor: (Color r: 0 g: 0 b: i range: 255).
- 		r := r translateBy: 0 at dy.
- 		f fill: r fillColor: (Color r: i g: i b: i range: 255)].
- 	^ f
- !

Item was removed:
- ----- Method: Color class>>colorTest:extent:colorMapper: (in category 'color from user') -----
- colorTest: depth extent: chartExtent colorMapper: colorMapper
- 	"Create a palette of colors sorted horizontally by hue and vertically by lightness. Useful for eyeballing the color gamut of the display, or for choosing a color interactively."
- 	"Note: It is slow to build this palette, so it should be cached for quick access."
- 	"(Color colorTest: 32 extent: 570 at 180 colorMapper: [:c | c]) display"
- 	"(Color colorTest: 32 extent: 570 at 180 colorMapper:
- 		[:c | Color
- 			r: (c red * 7) asInteger / 7
- 			g: (c green * 7) asInteger / 7
- 			b: (c blue * 3) asInteger / 3]) display"
- 	"(Color colorTest: 32 extent: 570 at 180 colorMapper:
- 		[:c | Color
- 			r: (c red * 5) asInteger / 5
- 			g: (c green * 5) asInteger / 5
- 			b: (c blue * 5) asInteger / 5]) display"
- 	"(Color colorTest: 32 extent: 570 at 180 colorMapper:
- 		[:c | Color
- 			r: (c red * 15) asInteger / 15
- 			g: (c green * 15) asInteger / 15
- 			b: (c blue * 15) asInteger / 15]) display"
- 	"(Color colorTest: 32 extent: 570 at 180 colorMapper:
- 		[:c | Color
- 			r: (c red * 31) asInteger / 31
- 			g: (c green * 31) asInteger / 31
- 			b: (c blue * 31) asInteger / 31]) display"
- 
- 	| startHue palette transHt vSteps transCaption grayWidth hSteps y c x |
- 	palette := Form extent: chartExtent depth: depth.
- 	transCaption := "(DisplayText text: 'no color' asText textStyle: (TextConstants at: #ComicPlain)) form storeString"
- 		(Form extent: 34 at 9 depth: 1
- 			fromArray: #(0 0 256 0 256 0 3808663859 2147483648 2491688266 2147483648 2491688266 0 2491688266 0 2466486578 0 0 0)
- 			offset: 0 at 0).
- 	transHt := transCaption height.
- 	palette fillWhite: (0 at 0 extent: palette width at transHt).
- 	palette fillBlack: (0 at transHt extent: palette width at 1).
- 	transCaption displayOn: palette at: palette boundingBox topCenter - ((transCaption width // 2)@0).
- 	grayWidth := 10.
- 	startHue := 338.0.
- 	vSteps := palette height - transHt // 2.
- 	hSteps := palette width - grayWidth.
- 	x := 0.
- 	startHue to: startHue + 360.0 by: 360.0/hSteps do: [:h | | basicHue |
- 		basicHue := Color h: h asFloat s: 1.0 v: 1.0.
- 		y := transHt+1.
- 		0 to: vSteps do: [:n |
-  			c := basicHue mixed: (n asFloat / vSteps asFloat) with: Color white.
- 			c := colorMapper value: c.
- 			palette fill: (x at y extent: 1 at 1) fillColor: c.
- 			y := y + 1].
- 		1 to: vSteps do: [:n |
-  			c := Color black mixed: (n asFloat / vSteps asFloat) with: basicHue.
- 			c := colorMapper value: c.
- 			palette fill: (x at y extent: 1 at 1) fillColor: c.
- 			y := y + 1].
- 		x := x + 1].
- 	y := transHt + 1.
- 	1 to: vSteps * 2 do: [:n |
-  		c := Color black mixed: (n asFloat / (vSteps*2) asFloat) with: Color white.
- 		c := colorMapper value: c.
- 		palette fill: (x at y extent: 10 at 1) fillColor: c.
- 		y := y + 1].
- 	^ palette
- !

Item was removed:
- ----- Method: Color class>>computeColorConvertingMap:from:to:keepSubPixelAA: (in category 'colormaps') -----
- computeColorConvertingMap: targetColor from: sourceDepth to: destDepth keepSubPixelAA: keepSubPix
- 
- 	sourceDepth < 16 ifTrue: [
- 		"source is 1-, 2-, 4-, or 8-bit indexed color.
- 		Assumed not to include subpixelAA"
- 		^ self computeIndexedColorConvertingMap: targetColor from: sourceDepth to: destDepth
- 	] ifFalse: [
- 		"source is 16-bit or 32-bit RGB.
- 		Might include subpixelAA"
- 		^ self computeRGBColorConvertingMap: targetColor to: destDepth keepSubPixelAA: keepSubPix
- 	]!

Item was removed:
- ----- Method: Color class>>computeColormapFrom:to: (in category 'colormaps') -----
- computeColormapFrom: sourceDepth to: destDepth
- 	"Compute a colorMap for translating between the given depths. A colormap is a Bitmap whose entries contain the pixel values for the destination depth. Typical clients use cachedColormapFrom:to: instead."
- 
- 	| map bitsPerColor |
- 	sourceDepth < 16 ifTrue: [
- 		"source is 1-, 2-, 4-, or 8-bit indexed color"
- 		map := (IndexedColors copyFrom: 1 to: (1 bitShift: sourceDepth))
- 					collect: [:c | c pixelValueForDepth: destDepth].
- 		map := map as: Bitmap.
- 	] ifFalse: [
- 		"source is 16-bit or 32-bit RGB"
- 		destDepth > 8
- 			ifTrue: [bitsPerColor := 5]  "retain maximum color resolution"
- 			ifFalse: [bitsPerColor := 4].
- 		map := self computeRGBColormapFor: destDepth bitsPerColor: bitsPerColor].
- 
- 	"Note: zero is transparent except when source depth is one-bit deep"
- 	sourceDepth > 1 ifTrue: [map at: 1 put: 0].
- 	^ map
- !

Item was removed:
- ----- Method: Color class>>computeIndexedColorConvertingMap:from:to: (in category 'colormaps') -----
- computeIndexedColorConvertingMap: targetColor from: sourceDepth to: destDepth
- 	| map |
- 	
- 	map := (IndexedColors copyFrom: 1 to: (1 bitShift: sourceDepth)) collect: [ :cc | | f c | 
- 		f := 1.0 - (cc red + cc green + cc blue / 3.0 ).
- 		c := targetColor notNil
- 			ifTrue: [
- 				destDepth = 32
- 					ifTrue: [ targetColor * f alpha: f]
- 					ifFalse: [ targetColor alphaMixed: f*1.5 with: Color white ]]
- 			ifFalse: [ cc ].
- 		destDepth = 32
- 			ifTrue: [ c pixelValueForDepth: destDepth]
- 			ifFalse: [
- 				f = 0.0
- 					ifTrue: [ 0 ]
- 					ifFalse: [ c pixelValueForDepth: destDepth ]]].
- 	map := map as: Bitmap.
- 	^map!

Item was removed:
- ----- Method: Color class>>computeRGBColorConvertingMap:to:keepSubPixelAA: (in category 'colormaps') -----
- computeRGBColorConvertingMap: targetColor to: destDepth keepSubPixelAA: keepSubPix
- 	"Builds a colormap intended to convert from subpixelAA black values to targetColor values.
- 	keepSubPix
- 		ifTrue: [ Answer colors that also include subpixelAA ]
- 		ifFalse: [ 
- 			Take fullpixel luminance level. Apply it to targetColor.
- 			I.e. answer colors with NO subpixelAA ]"
- 
- 	| mask map c bitsPerColor r g b f v |
- 
- 	destDepth > 8
- 		ifTrue: [bitsPerColor := 5]  "retain maximum color resolution"
- 		ifFalse: [bitsPerColor := 4].
- 	"Usually a bit less is enough, but make it configurable"
- 	bitsPerColor := bitsPerColor min: Preferences aaFontsColormapDepth.
- 	mask := (1 bitShift: bitsPerColor) - 1.
- 	map := Bitmap new: (1 bitShift: (3 * bitsPerColor)).
- 	0 to: map size - 1 do: [:i |
- 		r := (i bitShift: 0 - (2 * bitsPerColor)) bitAnd: mask.
- 		g := (i bitShift: 0 - bitsPerColor) bitAnd: mask.
- 		b := (i bitShift: 0) bitAnd: mask.
- 		f := 1.0 - (r + g + b / 3.0 / mask).
- 		c := targetColor notNil
- 			ifTrue: [
- 				(keepSubPix and: [destDepth > 8]) ifTrue: [
- 						Color
- 							r: 1.0 - (r/mask) * targetColor red
- 							g: 1.0 - (g/mask) * targetColor green
- 							b: 1.0 - (b/mask) * targetColor blue
- 							alpha: f	* targetColor alpha "alpha will be ignored below, in #pixelValueForDepth: if destDepth ~= 32" ]
- 				ifFalse: [
- 					destDepth = 32
- 						ifTrue: [ targetColor * f alpha: f * targetColor alpha ]
- 						ifFalse: [ targetColor alphaMixed: f*1.5 with: Color white ]]]
- 			ifFalse: [ Color r: r g: g b: b range: mask].	"This is currently used only to keep some SubPixelAA on destDepth = 8, using a single pass of rule 25"
- 		v := destDepth = 32
- 			ifTrue: [ c pixelValueForDepth: destDepth]
- 			ifFalse: [
- 				f < 0.1
- 					ifTrue: [ 0 ]
- 					ifFalse: [ c pixelValueForDepth: destDepth ]].
- 		map at: i + 1 put: v ].
- 	^ map!

Item was removed:
- ----- Method: Color class>>computeRGBColormapFor:bitsPerColor: (in category 'colormaps') -----
- computeRGBColormapFor: destDepth bitsPerColor: bitsPerColor
- 	"Compute a colorMap for translating from 16-bit or 32-bit RGB color to the given depth, using the given number of of bits per color component."
- 
- 	| mask map c |
- 	(#(3 4 5) includes: bitsPerColor)
- 		ifFalse: [self error: 'BitBlt only supports 3, 4, or 5 bits per color component'].
- 	mask := (1 bitShift: bitsPerColor) - 1.
- 	map := Bitmap new: (1 bitShift: (3 * bitsPerColor)).
- 	0 to: map size - 1 do: [:i |
- 		c := Color
- 			r: ((i bitShift: 0 - (2 * bitsPerColor)) bitAnd: mask)
- 			g: ((i bitShift: 0 - bitsPerColor) bitAnd: mask)
- 			b: ((i bitShift: 0) bitAnd: mask)
- 			range: mask.
- 		map at: i + 1 put: (c pixelValueForDepth: destDepth)].
- 
- 	map at: 1 put: (Color transparent pixelWordForDepth: destDepth).  "zero always transparent"
- 	^ map
- !

Item was removed:
- ----- Method: Color class>>cyan (in category 'named colors') -----
- cyan
- 	^Cyan!

Item was removed:
- ----- Method: Color class>>darkGray (in category 'named colors') -----
- darkGray
- 	^DarkGray!

Item was removed:
- ----- Method: Color class>>eggplant (in category 'named colors - crayons') -----
- eggplant
- 
- 	^ Color r: 64/255 g: 0.0 b: 128/255!

Item was removed:
- ----- Method: Color class>>fern (in category 'named colors - crayons') -----
- fern
- 
- 	^ Color r: 64/255 g: 128/255 b: 0.0!

Item was removed:
- ----- Method: Color class>>flora (in category 'named colors - crayons') -----
- flora
- 
- 	^ Color r: 102/255 g: 1.0 b: 102/255!

Item was removed:
- ----- Method: Color class>>fromArray: (in category 'instance creation') -----
- fromArray: colorDef
- 	colorDef size = 3
- 			ifTrue: [^self r: (colorDef at: 1) g: (colorDef at: 2) b: (colorDef at: 3)].
- 	colorDef size = 0
- 			ifTrue: [^Color transparent].
- 	colorDef size = 4
- 			ifTrue: [^(TranslucentColor r: (colorDef at: 1) g: (colorDef at: 2) b: (colorDef at: 3)) alpha: (colorDef at: 4)].
- 	self error: 'Undefined color definition'!

Item was removed:
- ----- Method: Color class>>fromColorref: (in category 'instance creation') -----
- fromColorref: aColorref 
- 	| red green blue |
- 	red := aColorref bitAnd: 16rFF.
- 	green := (aColorref bitAnd: 16rFF00)
- 				>> 8.
- 	blue := (aColorref bitAnd: 16rFF0000)
- 				>> 16.
- 	^ self r: red g: green b: blue range: 255.!

Item was removed:
- ----- Method: Color class>>fromHTMLString: (in category 'other') -----
- fromHTMLString: aColorHex
- 	"Do not call this method directly, call Color>>#fromString: instead as it is more generic"
- 
- 	| green red blue resultColor |
- 	red := (Integer readFrom: (aColorHex first: 2) base: 16).
- 	green := (Integer readFrom: (aColorHex copyFrom: 3 to: 4) base: 16).
- 	blue := (Integer readFrom: (aColorHex copyFrom: 5 to: 6) base: 16).
- 	resultColor := self r: red g: green b: blue range: 255.
- 	^ (aColorHex size = 8) 
- 		ifTrue: [resultColor alpha: ((Integer readFrom: (aColorHex last: 2) base: 16) / 255)]
- 		ifFalse: [resultColor]!

Item was removed:
- ----- Method: Color class>>fromRGBString: (in category 'other') -----
- fromRGBString: rgb
- 	"Do not call this method directly, call Color>>#fromString: instead as it is more generic"
- 	
- 	| green red blue |
- 	red := (Integer readFrom:(rgb at: 1)) min: 255 max: 0.
- 	green := (Integer readFrom:(rgb at: 2)) min: 255 max: 0.
- 	blue := (Integer readFrom:(rgb at: 3)) min: 255 max: 0.
- 	^self r: red g: green b: blue range: 255!

Item was removed:
- ----- Method: Color class>>fromRgbTriplet: (in category 'instance creation') -----
- fromRgbTriplet: list
- 	^ self r: list first g: list second b: list last!

Item was removed:
- ----- Method: Color class>>fromString: (in category 'instance creation') -----
- fromString: aString
- 	"for HTML color spec: #FFCCAA or white/black/red/other name, or an r,g,b triplet string"
- 	"Color fromString: '#FFCCAA'.
- 	 Color fromString: 'white'.
- 	 Color fromString: 'orange'
- 	 Color fromString: '126,42,33' "
- 	
- 	| aColorHex rgb|
- 	aString isEmptyOrNil ifTrue: [ ^self white ].
- 	aString first = $#
- 		ifTrue: [ aColorHex := aString allButFirst ]
- 		ifFalse: [ aColorHex := aString ].
- 	
- 	"is the string a 6 digit hex number?"
- 	((aColorHex size = 6 or: [aColorHex size = 8]) and: [ 
- 		aColorHex allSatisfy: [ :each | '0123456789ABCDEFabcdef' includes: each ] ])
- 			ifTrue: [^ self fromHTMLString: aColorHex ].
- 	
- 	"is the string in the form a,b,c ?"
- 	rgb := aColorHex findTokens: $, .
- 	rgb size = 3 ifTrue: [^ self fromRGBString: rgb].
- 	
- 	"try to match aColorHex with known named colors, case insensitive"
- 	^self perform: (ColorNames detect: [:colorSymbol | aColorHex sameAs: colorSymbol] ifNone: [ #white ])!

Item was removed:
- ----- Method: Color class>>fromUser (in category 'color from user') -----
- fromUser
- 	"Displays a color palette of colors, waits for a mouse click, and returns the selected color. Any pixel on the Display can be chosen, not just those in the color palette."
- 	"Note: Since the color chart is cached, you may need to do 'ColorChart := nil' after changing the oldColorPaletteForDepth:extent: method."
- 	"Color fromUser"
- 
- 	| d startPt save tr oldColor c here s |
- 	d := Display depth.
- 	((ColorChart == nil) or: [ColorChart depth ~= Display depth]) 
- 		ifTrue: [ColorChart := self oldColorPaletteForDepth: d extent: (2 * 144)@80].
- 	Sensor cursorPoint y < Display center y 
- 		ifTrue: [startPt := 0@(Display boundingBox bottom - ColorChart height)]
- 		ifFalse: [startPt := 0 at 0].
- 
- 	save := Form fromDisplay: (startPt extent: ColorChart extent).
- 	ColorChart displayAt: startPt.
- 	tr := ColorChart extent - (50 at 19) corner: ColorChart extent.
- 	tr := tr translateBy: startPt.
- 
- 	oldColor := nil.
- 	[Sensor anyButtonPressed] whileFalse: [
- 		c := Display colorAt: (here := Sensor cursorPoint).
- 		(tr containsPoint: here)
- 			ifFalse: [Display fill: (0 at 61+startPt extent: 20 at 19) fillColor: c]
- 			ifTrue: [
- 				c := Color transparent.
- 				Display fill: (0 at 61+startPt extent: 20 at 19) fillColor: Color white].
- 		c = oldColor ifFalse: [
- 			Display fillWhite: (20 at 61 + startPt extent: 135 at 19).
- 			c isTransparent
- 				ifTrue: [s := 'transparent']
- 				ifFalse: [s := c shortPrintString.
- 						s := s copyFrom: 7 to: s size - 1].
- 			s displayAt: 20 at 61 + startPt.
- 			oldColor := c]].
- 	save displayAt: startPt.
- 	Sensor waitNoButton.
- 	^ c
- !

Item was removed:
- ----- Method: Color class>>grape (in category 'named colors - crayons') -----
- grape
- 
- 	^ Color r: 128/255 g: 0.0 b: 1.0!

Item was removed:
- ----- Method: Color class>>gray (in category 'named colors') -----
- gray
- 	^Gray!

Item was removed:
- ----- Method: Color class>>gray: (in category 'instance creation') -----
- gray: brightness
- 	"Return a gray shade with the given brightness in the range [0.0..1.0]."
- 
- 	^ self basicNew setRed: brightness green: brightness blue: brightness
- !

Item was removed:
- ----- Method: Color class>>green (in category 'named colors') -----
- green
- 	^Green!

Item was removed:
- ----- Method: Color class>>h:s:v: (in category 'instance creation') -----
- h: hue s: saturation v: brightness
- 	"Create a color with the given hue, saturation, and brightness. Hue is given as the angle in degrees of the color on the color circle where red is zero degrees. Saturation and brightness are numbers in [0.0..1.0] where larger values are more saturated or brighter colors. For example, (Color h: 0 s: 1 v: 1) is pure red."
- 	"Note: By convention, brightness is abbreviated 'v' to to avoid confusion with blue."
- 
- 	^ self basicNew setHue: hue saturation: saturation brightness: brightness!

Item was removed:
- ----- Method: Color class>>h:s:v:alpha: (in category 'instance creation') -----
- h: h s: s v: v alpha: alpha
- 
- 	^ (self h: h s: s v: v) alpha: alpha!

Item was removed:
- ----- Method: Color class>>honeydew (in category 'named colors - crayons') -----
- honeydew
- 
- 	^ Color r: 204/255 g: 1.0 b: 102/255!

Item was removed:
- ----- Method: Color class>>hotColdShades: (in category 'examples') -----
- hotColdShades: thisMany
- 	"An array of thisMany colors showing temperature from blue to red to white hot.  (Later improve this by swinging in hue.)  "
- 	"Color showColors: (Color hotColdShades: 25)"
- 
- 	| n s1 s2 s3 s4 s5 |
- 	thisMany < 5 ifTrue: [^ self error: 'must be at least 5 shades'].
- 	n := thisMany // 5.
- 	s1 := self white mix: self yellow shades: (thisMany - (n*4)).
- 	s2 := self yellow mix: self red shades: n+1.
- 	s2 := s2 copyFrom: 2 to: n+1.
- 	s3 := self red mix: self green darker shades: n+1.
- 	s3 := s3 copyFrom: 2 to: n+1.
- 	s4 := self green darker mix: self blue shades: n+1.
- 	s4 := s4 copyFrom: 2 to: n+1.
- 	s5 := self blue mix: self black shades: n+1.
- 	s5 := s5 copyFrom: 2 to: n+1.
- 	^ s1, s2, s3, s4, s5
- !

Item was removed:
- ----- Method: Color class>>ice (in category 'named colors - crayons') -----
- ice
- 
- 	^ Color r: 102/255 g: 1.0 b: 1.0!

Item was removed:
- ----- Method: Color class>>indexedColors (in category 'other') -----
- indexedColors
- 
- 	^ IndexedColors!

Item was removed:
- ----- Method: Color class>>initialize (in category 'class initialization') -----
- initialize
- 	"Color initialize"
- 
- 	"Details: Externally, the red, green, and blue components of color
- 	are floats in the range [0.0..1.0]. Internally, they are represented
- 	as integers in the range [0..ComponentMask] packing into a
- 	small integer to save space and to allow fast hashing and
- 	equality testing.
- 
- 	For a general description of color representations for computer
- 	graphics, including the relationship between the RGB and HSV
- 	color models used here, see Chapter 17 of Foley and van Dam,
- 	Fundamentals of Interactive Computer Graphics, Addison-Wesley,
- 	1982."
- 
- 	ComponentMask := 1023.
- 	HalfComponentMask := 512.  "used to round up in integer calculations"
- 	ComponentMax := 1023.0.  "a Float used to normalize components"
- 	RedShift := 20.
- 	GreenShift := 10.
- 	BlueShift := 0.
- 
- 	PureRed		 := self r: 1 g: 0 b: 0.
- 	PureGreen	 := self r: 0 g: 1 b: 0.
- 	PureBlue	 := self r: 0 g: 0 b: 1.
- 	PureYellow	 := self r: 1 g: 1 b: 0.
- 	PureCyan	 := self r: 0 g: 1 b: 1.
- 	PureMagenta := self r: 1 g: 0 b: 1.
- 
- 	RandomStream := Random new.
- 
- 	self initializeIndexedColors.
- 	self initializeGrayToIndexMap.
- 	self initializeNames.
- 	self initializeHighLights.
- !

Item was removed:
- ----- Method: Color class>>initializeGrayToIndexMap (in category 'class initialization') -----
- initializeGrayToIndexMap
- 	"Build an array of gray values available in the 8-bit colormap. This array is indexed by a gray level between black (1) and white (256) and returns the pixel value for the corresponding gray level."
- 	"Note: This method must be called after initializeIndexedColors, since it uses IndexedColors."
- 	"Color initializeGrayToIndexMap"
- 
- 	| grayLevels grayIndices c distToClosest dist indexOfClosest |
- 	"record the level and index of each gray in the 8-bit color table"
- 	grayLevels := OrderedCollection new.
- 	grayIndices := OrderedCollection new.
- 	"Note: skip the first entry, which is reserved for transparent"
- 	2 to: IndexedColors size do: [:i |
- 		c := IndexedColors at: i.
- 		c saturation = 0.0 ifTrue: [  "c is a gray"
- 			grayLevels add: (c privateBlue) >> 2.  "top 8 bits; R, G, and B are the same"
- 			grayIndices add: i - 1]].  "pixel values are zero-based"
- 	grayLevels := grayLevels asArray.
- 	grayIndices := grayIndices asArray.
- 
- 	"for each gray level in [0..255], select the closest match"
- 	GrayToIndexMap := ByteArray new: 256.
- 	0 to: 255 do: [:level |
- 		distToClosest := 10000.  "greater than distance to any real gray"
- 		1 to: grayLevels size do: [:i |
- 			dist := (level - (grayLevels at: i)) abs.
- 			dist < distToClosest ifTrue: [
- 				distToClosest := dist.
- 				indexOfClosest := grayIndices at: i]].
- 		GrayToIndexMap at: (level + 1) put: indexOfClosest].
- !

Item was removed:
- ----- Method: Color class>>initializeHighLights (in category 'class initialization') -----
- initializeHighLights
- 	"Create a set of Bitmaps for quickly reversing areas of the screen without converting colors. "
- 	"Color initializeHighLights"
- 
- 	| t |
- 	t := Array new: 32.
- 	t at: 1 put: (Bitmap with: 16rFFFFFFFF).
- 	t at: 2 put: (Bitmap with: 16rFFFFFFFF).
- 	t at: 4 put: (Bitmap with: 16r55555555).
- 	t at: 8 put: (Bitmap with: 16r7070707).
- 	t at: 16 put: (Bitmap with: 16rFFFFFFFF).
- 	t at: 32 put: (Bitmap with: 16rFFFFFFFF).
- 	HighLightBitmaps := t.
- !

Item was removed:
- ----- Method: Color class>>initializeIndexedColors (in category 'class initialization') -----
- initializeIndexedColors
- 	"Build an array of colors corresponding to the fixed colormap used
- 	 for display depths of 1, 2, 4, or 8 bits."
- 	"Color initializeIndexedColors"
- 
- 	| a index grayVal |
- 	a := Array new: 256.
- 
- 	"1-bit colors (monochrome)"
- 	a at: 1 put: (Color r: 1.0 g: 1.0 b: 1.0).		"white or transparent"
- 	a at: 2 put: (Color r: 0.0 g: 0.0 b: 0.0).	"black"
- 
- 	"additional colors for 2-bit color"
- 	a at: 3 put: (Color r: 1.0 g: 1.0 b: 1.0).	"opaque white"
- 	a at: 4 put: (Color r: 0.5 g: 0.5 b: 0.5).	"1/2 gray"
- 
- 	"additional colors for 4-bit color"
- 	a at:  5 put: (Color r: 1.0 g: 0.0 b: 0.0).	"red"
- 	a at:  6 put: (Color r: 0.0 g: 1.0 b: 0.0).	"green"
- 	a at:  7 put: (Color r: 0.0 g: 0.0 b: 1.0).	"blue"
- 	a at:  8 put: (Color r: 0.0 g: 1.0 b: 1.0).	"cyan"
- 	a at:  9 put: (Color r: 1.0 g: 1.0 b: 0.0).	"yellow"
- 	a at: 10 put: (Color r: 1.0 g: 0.0 b: 1.0).	"magenta"
- 
- 	a at: 11 put: (Color r: 0.125 g: 0.125 b: 0.125).		"1/8 gray"
- 	a at: 12 put: (Color r: 0.25 g: 0.25 b: 0.25).		"2/8 gray"
- 	a at: 13 put: (Color r: 0.375 g: 0.375 b: 0.375).		"3/8 gray"
- 	a at: 14 put: (Color r: 0.625 g: 0.625 b: 0.625).		"5/8 gray"
- 	a at: 15 put: (Color r: 0.75 g: 0.75 b: 0.75).		"6/8 gray"
- 	a at: 16 put: (Color r: 0.875 g: 0.875 b: 0.875).		"7/8 gray"
- 
- 	"additional colors for 8-bit color"
- 	"24 more shades of gray (1/32 increments but not repeating 1/8 increments)"
- 	index := 17.
- 	1 to: 31 do: [:v |
- 		(v \\ 4) = 0 ifFalse: [
- 			grayVal := v / 32.0.
- 			a at: index put: (Color r: grayVal g: grayVal b: grayVal).
- 			index := index + 1]].
- 
- 	"The remainder of color table defines a color cube with six steps
- 	 for each primary color. Note that the corners of this cube repeat
- 	 previous colors, but this simplifies the mapping between RGB colors
- 	 and color map indices. This color cube spans indices 40 through 255
- 	 (indices 41-256 in this 1-based array)."
- 	0 to: 5 do: [:r |
- 		0 to: 5 do: [:g |
- 			0 to: 5 do: [:b |
- 				index := 41 + ((36 * r) + (6 * b) + g).
- 				index > 256 ifTrue: [
- 					self error: 'index out of range in color table compuation'].
- 				a at: index put: (Color r: r g: g b: b range: 5)]]].
- 
- 	IndexedColors := a.
- !

Item was removed:
- ----- Method: Color class>>initializeNames (in category 'class initialization') -----
- initializeNames
- 	"Name some colors."
- 	"Color initializeNames"
- 
- 	ColorNames := Set new.
- 	self named: #black put: (Color r: 0 g: 0 b: 0).
- 	self named: #veryVeryDarkGray put: (Color r: 0.125 g: 0.125 b: 0.125).
- 	self named: #veryDarkGray put: (Color r: 0.25 g: 0.25 b: 0.25).
- 	self named: #darkGray put: (Color r: 0.375 g: 0.375 b: 0.375).
- 	self named: #gray put: (Color r: 0.5 g: 0.5 b: 0.5).
- 	self named: #lightGray put: (Color r: 0.625 g: 0.625 b: 0.625).
- 	self named: #veryLightGray put: (Color r: 0.75 g: 0.75 b: 0.75).
- 	self named: #veryVeryLightGray put: (Color r: 0.875 g: 0.875 b: 0.875).
- 	self named: #white put: (Color r: 1.0 g: 1.0 b: 1.0).
- 	self named: #red put: (Color r: 1.0 g: 0 b: 0).
- 	self named: #yellow put: (Color r: 1.0 g: 1.0 b: 0).
- 	self named: #green put: (Color r: 0 g: 1.0 b: 0).
- 	self named: #cyan put: (Color r: 0 g: 1.0 b: 1.0).
- 	self named: #blue put: (Color r: 0 g: 0 b: 1.0).
- 	self named: #magenta put: (Color r: 1.0 g: 0 b: 1.0).
- 	self named: #brown put: (Color r: 0.6 g: 0.2 b: 0).
- 	self named: #orange put: (Color r: 1.0 g: 0.6 b: 0).
- 	self named: #lightRed put: (Color r: 1.0 g: 0.8 b: 0.8).
- 	self named: #lightYellow put: (Color r: 1.0 g: 1.0 b: 0.8).
- 	self named: #lightGreen put: (Color r: 0.8 g: 1.0 b: 0.6).
- 	self named: #lightCyan put: (Color r: 0.4 g: 1.0 b: 1.0).
- 	self named: #lightBlue put: (Color r: 0.8 g: 1.0 b: 1.0).
- 	self named: #lightMagenta put: (Color r: 1.0 g: 0.8 b: 1.0).
- 	self named: #lightBrown put: (Color r: 1.0 g: 0.6 b: 0.2).
- 	self named: #lightOrange put: (Color r: 1.0 g: 0.8 b: 0.4).
- 	self named: #transparent put: (TranslucentColor new alpha: 0.0).
- 	self named: #paleBuff put: (Color r: 254 g: 250 b: 235 range: 255).
- 	self named: #paleBlue put: (Color r: 222 g: 249 b: 254 range: 255).
- 	self named: #paleYellow put: (Color r: 255 g: 255 b: 217 range: 255).
- 	self named: #paleGreen put: (Color r: 223 g: 255 b: 213 range: 255).
- 	self named: #paleRed put: (Color r: 255 g: 230 b: 230 range: 255).
- 	self named: #veryPaleRed put: (Color r: 255 g: 242 b: 242 range: 255).
- 	self named: #paleTan put: (Color r: 235 g: 224 b: 199 range: 255).
- 	self named: #paleMagenta put: (Color r: 255 g: 230 b: 255 range: 255).
- 	self named: #paleOrange put: (Color r: 253 g: 237 b: 215 range: 255).
- 	self named: #palePeach put: (Color r: 255 g: 237 b: 213 range: 255).
- 	self named: #pantonePurpleU put: (Color r: 193 g: 81 b: 184 range: 255).
- 	self initializeNamesMap
- 
- !

Item was removed:
- ----- Method: Color class>>initializeNamesMap (in category 'class initialization') -----
- initializeNamesMap
- 	"enable mapping a color to its name"
- 	"Color initializeNamesMap"
- 
- 	RGBToNames := Dictionary new.
- 	self colorNames do: [:sym | (self perform: sym) addName: sym]!

Item was removed:
- ----- Method: Color class>>initializeTranslucentPatterns (in category 'class initialization') -----
- initializeTranslucentPatterns
- 	"Color initializeTranslucentPatterns"
- 	
- 	TranslucentPatterns := Array new: 8.
- 	#(1 2 4 8) do:[:d| | pattern patternList mask bits |
- 		patternList := Array new: 5.
- 		mask := (1 bitShift: d) - 1.
- 		bits := 2 * d.
- 		[bits >= 32] whileFalse: [
- 			mask := mask bitOr: (mask bitShift: bits).  "double the length of mask"
- 			bits := bits + bits].
- 		"0% pattern"
- 		pattern := Bitmap with: 0 with: 0.
- 		patternList at: 1 put: pattern.
- 		"25% pattern"
- 		pattern := Bitmap with: mask with: 0.
- 		patternList at: 2 put: pattern.
- 		"50% pattern"
- 		pattern := Bitmap with: mask with: mask bitInvert32.
- 		patternList at: 3 put: pattern.
- 		"75% pattern"
- 		pattern := Bitmap with: mask with: 16rFFFFFFFF.
- 		patternList at: 4 put: pattern.
- 		"100% pattern"
- 		pattern := Bitmap with: 16rFFFFFFFF with: 16rFFFFFFFF.
- 		patternList at: 5 put: pattern.
- 		TranslucentPatterns at: d put: patternList.
- 	].!

Item was removed:
- ----- Method: Color class>>iron (in category 'named colors - crayons') -----
- iron
- 
- 	^ Color r: 76/255 g: 76/255 b: 76/255!

Item was removed:
- ----- Method: Color class>>lavender (in category 'named colors - crayons') -----
- lavender
- 
- 	^ Color r: 204/255 g: 102/255 b: 1.0!

Item was removed:
- ----- Method: Color class>>lead (in category 'named colors - crayons') -----
- lead
- 
- 	^ Color r: 25/255 g: 25/255 b: 25/255!

Item was removed:
- ----- Method: Color class>>lemon (in category 'named colors - crayons') -----
- lemon
- 
- 	^ Color r: 1.0 g: 1.0 b: 0.0!

Item was removed:
- ----- Method: Color class>>licorice (in category 'named colors - crayons') -----
- licorice
- 
- 	^ Color r: 0.0 g: 0.0 b: 0.0!

Item was removed:
- ----- Method: Color class>>lightBlue (in category 'named colors') -----
- lightBlue
- 	^LightBlue!

Item was removed:
- ----- Method: Color class>>lightBrown (in category 'named colors') -----
- lightBrown
- 	^LightBrown!

Item was removed:
- ----- Method: Color class>>lightCyan (in category 'named colors') -----
- lightCyan
- 	^LightCyan!

Item was removed:
- ----- Method: Color class>>lightGray (in category 'named colors') -----
- lightGray
- 	^LightGray!

Item was removed:
- ----- Method: Color class>>lightGreen (in category 'named colors') -----
- lightGreen
- 	^LightGreen!

Item was removed:
- ----- Method: Color class>>lightMagenta (in category 'named colors') -----
- lightMagenta
- 	^LightMagenta!

Item was removed:
- ----- Method: Color class>>lightOrange (in category 'named colors') -----
- lightOrange
- 	^LightOrange!

Item was removed:
- ----- Method: Color class>>lightRed (in category 'named colors') -----
- lightRed
- 	^LightRed!

Item was removed:
- ----- Method: Color class>>lightYellow (in category 'named colors') -----
- lightYellow
- 	^LightYellow!

Item was removed:
- ----- Method: Color class>>lime (in category 'named colors - crayons') -----
- lime
- 
- 	^ Color r: 128/255 g: 1.0 b: 0.0!

Item was removed:
- ----- Method: Color class>>magenta (in category 'named colors') -----
- magenta
- 	^Magenta!

Item was removed:
- ----- Method: Color class>>magnesium (in category 'named colors - crayons') -----
- magnesium
- 
- 	^ Color r: 179/255 g: 179/255 b: 179/255!

Item was removed:
- ----- Method: Color class>>maraschino (in category 'named colors - crayons') -----
- maraschino
- 
- 	^ Color r: 1.0 g: 0.0 b: 0.0!

Item was removed:
- ----- Method: Color class>>maroon (in category 'named colors - crayons') -----
- maroon
- 
- 	^ Color r: 128/255 g: 0.0 b: 64/255!

Item was removed:
- ----- Method: Color class>>maskingMap: (in category 'other') -----
- maskingMap: depth
- 	"Return a color map that maps all colors except transparent to words of all ones. Used to create a mask for a Form whose transparent pixel value is zero. Cache the most recently used map."
- 
- 	| sizeNeeded |
- 	depth <= 8
- 		ifTrue: [sizeNeeded := 1 bitShift: depth]
- 		ifFalse: [sizeNeeded := 4096].
- 
- 	(MaskingMap == nil or: [MaskingMap size ~= sizeNeeded]) ifTrue:
- 		[MaskingMap := Bitmap new: sizeNeeded withAll: 16rFFFFFFFF.
- 		MaskingMap at: 1 put: 0.  "transparent"].
- 
- 	^ MaskingMap
- !

Item was removed:
- ----- Method: Color class>>mercury (in category 'named colors - crayons') -----
- mercury
- 
- 	^ Color r: 230.0 g: 230.0 b: 230.0!

Item was removed:
- ----- Method: Color class>>midnight (in category 'named colors - crayons') -----
- midnight
- 
- 	^ Color r: 0.0 g: 0.0 b: 128/255!

Item was removed:
- ----- Method: Color class>>mocha (in category 'named colors - crayons') -----
- mocha
- 
- 	^ Color r: 128/255 g: 64/255 b: 0.0!

Item was removed:
- ----- Method: Color class>>moss (in category 'named colors - crayons') -----
- moss
- 
- 	^ Color r: 0.0 g: 128/255 b: 64/255!

Item was removed:
- ----- Method: Color class>>named: (in category 'instance creation') -----
- named: colorName
- 
- 	| colorSym result |
- 	(colorSym := Symbol lookup: colorName) ifNil: [^ nil].
- 	result := (self class canUnderstand: colorSym)
- 		ifTrue: [self perform: colorSym]
- 		ifFalse: [self classPool at: colorSym ifAbsent: nil].
- 	^ result isColor ifTrue: [result]!

Item was removed:
- ----- Method: Color class>>named:put: (in category 'class initialization') -----
- named: newName put: aColor
- 	"Add a new color to the list and create an access message and a class variable for it.  The name should start with a lowercase letter.  (The class variable will start with an uppercase letter.)  (Color colorNames) returns a list of all color names.  "
- 	| str cap sym accessor csym |
- 	(aColor isKindOf: self) ifFalse: [^ self error: 'not a Color'].
- 	str := newName asString.
- 	sym := str asSymbol.
- 	cap := str capitalized.
- 	csym := cap asSymbol.
- 	(self class canUnderstand: sym) ifFalse: [
- 		"define access message"
- 		accessor := str, (String with: Character cr with: Character tab), 			'^', cap.
- 		self class compile: accessor
- 			classified: 'named colors'].
- 	(self classPool includesKey: csym) ifFalse: [
- 		self addClassVarName: cap].
- 	ColorNames add: sym.
- 	^ self classPool at: csym put: aColor!

Item was removed:
- ----- Method: Color class>>new (in category 'instance creation') -----
- new
- 
- 	^ self r: 0.0 g: 0.0 b: 0.0!

Item was removed:
- ----- Method: Color class>>nickel (in category 'named colors - crayons') -----
- nickel
- 
- 	^ Color r: 128/255 g: 128/255 b: 128/255!

Item was removed:
- ----- Method: Color class>>ocean (in category 'named colors - crayons') -----
- ocean
- 
- 	^ Color r: 0.0 g: 64/255 b: 128/255!

Item was removed:
- ----- Method: Color class>>oldColorPaletteForDepth:extent: (in category 'color from user') -----
- oldColorPaletteForDepth: depth extent: paletteExtent
- 	"Returns a form of the given size showing a color palette for the given depth."
- 	"(Color oldColorPaletteForDepth: Display depth extent: 720 at 100) display"
- 
- 	| c p f nSteps rect w h q |
- 	f := Form extent: paletteExtent depth: depth.
- 	f fill: f boundingBox fillColor: Color white.
- 	nSteps := depth > 8 ifTrue: [12] ifFalse: [6].
- 	w := paletteExtent x // (nSteps * nSteps).
- 	h := paletteExtent y - 20 // nSteps.
- 	0 to: nSteps-1 do: [:r |
- 		0 to: nSteps-1 do: [:g |
- 			0 to: nSteps-1 do: [:b |
- 				c := Color r: r g: g b: b range: nSteps - 1.
- 				rect := ((r * nSteps * w) + (b * w)) @ (g * h) extent: w@(h + 1).
- 				f fill: rect fillColor: c]]].
- 	q := Quadrangle origin: paletteExtent - (50 at 19) corner: paletteExtent.
- 	q displayOn: f.
- 	'Trans.' displayOn: f at: q origin + (9 at 1).
- 
- 	w := ((paletteExtent x - q width - 130) // 64) max: 1.
- 	p := paletteExtent x - q width - (64 * w) - 1 @ (paletteExtent y - 19).
- 	0 to: 63 do:
- 		[:v | c := Color r: v g: v b: v range: 63.
- 		f fill: ((v * w)@0 + p extent: (w + 1)@19) fillColor: c].
- 	^ f
- !

Item was removed:
- ----- Method: Color class>>orange (in category 'named colors') -----
- orange
- 	^Orange!

Item was removed:
- ----- Method: Color class>>orchid (in category 'named colors - crayons') -----
- orchid
- 
- 	^ Color r: 102/255 g: 102/255 b: 1.0!

Item was removed:
- ----- Method: Color class>>orderedCrayonColorNames (in category 'other') -----
- orderedCrayonColorNames
- 	
- 	^ #(cantaloupe honeydew spindrift sky lavender carnation licorice snow salmon banana flora ice orchid bubblegum lead mercury tangerine lime seaFoam aqua grape strawberry tungsten silver maraschino lemon spring turquoise blueberry magenta iron magnesium mocha fern moss ocean eggplant maroon steel aluminum cayenne asparagus clover teal midnight plum tin nickel)!

Item was removed:
- ----- Method: Color class>>orderedCrayonColors (in category 'other') -----
- orderedCrayonColors
- 	"self orderedCrayonColors explore."
- 	
- 	^ OrderedDictionary newFrom: (self orderedCrayonColorNames collect: [:ea | ea -> (self perform: ea)])!

Item was removed:
- ----- Method: Color class>>paleBlue (in category 'named colors') -----
- paleBlue
- 	^PaleBlue!

Item was removed:
- ----- Method: Color class>>paleBuff (in category 'named colors') -----
- paleBuff
- 	^PaleBuff!

Item was removed:
- ----- Method: Color class>>paleGreen (in category 'named colors') -----
- paleGreen
- 	^PaleGreen!

Item was removed:
- ----- Method: Color class>>paleMagenta (in category 'named colors') -----
- paleMagenta
- 	^PaleMagenta!

Item was removed:
- ----- Method: Color class>>paleOrange (in category 'named colors') -----
- paleOrange
- 	^PaleOrange!

Item was removed:
- ----- Method: Color class>>palePeach (in category 'named colors') -----
- palePeach
- 	^PalePeach!

Item was removed:
- ----- Method: Color class>>paleRed (in category 'named colors') -----
- paleRed
- 	^PaleRed!

Item was removed:
- ----- Method: Color class>>paleTan (in category 'named colors') -----
- paleTan
- 	^PaleTan!

Item was removed:
- ----- Method: Color class>>paleYellow (in category 'named colors') -----
- paleYellow
- 	^PaleYellow!

Item was removed:
- ----- Method: Color class>>pantonePurpleU (in category 'named colors') -----
- pantonePurpleU
- 	^PantonePurpleU!

Item was removed:
- ----- Method: Color class>>pixelScreenForDepth: (in category 'other') -----
- pixelScreenForDepth: depth
- 	"Return a 50% stipple containing alternating pixels of all-zeros and all-ones to be used as a mask at the given depth."
- 
- 	| mask bits |
- 	mask := (1 bitShift: depth) - 1.
- 	bits := 2 * depth.
- 	[bits >= 32] whileFalse: [
- 		mask := mask bitOr: (mask bitShift: bits).  "double the length of mask"
- 		bits := bits + bits].
- 	^ Bitmap with: mask with: mask bitInvert32
- !

Item was removed:
- ----- Method: Color class>>plum (in category 'named colors - crayons') -----
- plum
- 
- 	^ Color r: 128/255 g: 0.0 b: 128/255!

Item was removed:
- ----- Method: Color class>>quickHighLight: (in category 'other') -----
- quickHighLight: depth
- 	"Quickly return a Bitblt-ready raw colorValue for highlighting areas.  6/22/96 tk"
- 
- 	^ HighLightBitmaps at: depth!

Item was removed:
- ----- Method: Color class>>r:g:b: (in category 'instance creation') -----
- r: r g: g b: b
- 	"Return a color with the given r, g, and b components in the range [0.0..1.0]."
- 
- 	^ self basicNew setRed: r green: g blue: b
- !

Item was removed:
- ----- Method: Color class>>r:g:b:alpha: (in category 'instance creation') -----
- r: r g: g b: b alpha: alpha
- 
- 	^ (self r: r g: g b: b) alpha: alpha!

Item was removed:
- ----- Method: Color class>>r:g:b:range: (in category 'instance creation') -----
- r: r g: g b: b range: range
- 	"Return a color with the given r, g, and b components specified as integers in the range [0..r]. This avoids the floating point arithmetic in the red:green:blue: message and is thus a bit faster for certain applications (such as computing a sequence of colors for a palette)."
- 
- 	^ self basicNew setRed: r green: g blue: b range: range!

Item was removed:
- ----- Method: Color class>>random (in category 'instance creation') -----
- random
- 	"Return a random color that isn't too dark or under-saturated."
- 
- 	^ self basicNew
- 		setHue: (360.0 * RandomStream next)
- 		saturation: (0.3 + (RandomStream next * 0.7))
- 		brightness: (0.4 + (RandomStream next * 0.6))!

Item was removed:
- ----- Method: Color class>>red (in category 'named colors') -----
- red
- 	^Red!

Item was removed:
- ----- Method: Color class>>salmon (in category 'named colors - crayons') -----
- salmon
- 
- 	^ Color r: 1.0 g: 102/255 b: 102/255!

Item was removed:
- ----- Method: Color class>>seaFoam (in category 'named colors - crayons') -----
- seaFoam
- 
- 	^ Color r: 0.0 g: 1.0 b: 128/255!

Item was removed:
- ----- Method: Color class>>showColorCube (in category 'examples') -----
- showColorCube
- 	"Show a 12x12x12 color cube."
- 	"Color showColorCube"
- 
- 	0 to: 11 do: [:r |
- 		0 to: 11 do: [:g |
- 			0 to: 11 do: [:b |	
- 				Display fill: (((r*60) + (b*5)) @ (g*5) extent: 5 at 5)
- 					fillColor: (Color r: r g: g b: b range: 11)]]].
- !

Item was removed:
- ----- Method: Color class>>showColors: (in category 'examples') -----
- showColors: colorList
- 	"Display the given collection of colors across the top of the Display."
- 
- 	| w r |
- 	w := Display width // colorList size.
- 	r := 0 at 0 extent: w@((w min: 30) max: 10).
- 	colorList do: [:c |
- 		Display fill: r fillColor: c.
- 		r := r translateBy: w at 0].
- !

Item was removed:
- ----- Method: Color class>>showHSVPalettes (in category 'examples') -----
- showHSVPalettes
- 	"Shows a palette of hues, varying the saturation and brightness for each one. Best results are with depths 16 and 32."
- 	"Color showHSVPalettes"
- 
- 	| left top c |
- 	left := top := 0.
- 	0 to: 179 by: 15 do: [:h |
- 		0 to: 10 do: [:s |
- 			left := (h * 4) + (s * 4).
- 			0 to: 10 do: [:v |
- 				c := Color h: h s: s asFloat / 10.0 v: v asFloat / 10.0.
- 				top := (v * 4).
- 				Display fill: (left at top extent: 4 at 4) fillColor: c.
- 
- 				c := Color h: h + 180 s: s asFloat / 10.0 v: v asFloat / 10.0.
- 				top := (v * 4) + 50.
- 				Display fill: (left at top extent: 4 at 4) fillColor: c]]].
- !

Item was removed:
- ----- Method: Color class>>showHuesInteractively (in category 'examples') -----
- showHuesInteractively
- 	"Shows a palette of hues at a (saturation, brightness) point determined by the mouse position. Click the mouse button to exit and return the selected (saturation, brightness) point."
- 	"Color showHuesInteractively"
- 
- 	| p s v |
- 	[Sensor anyButtonPressed] whileFalse: [
- 		p := Sensor cursorPoint.
- 		s := p x asFloat / 300.0.
- 		v := p y asFloat / 300.0.
- 		self showColors: (self wheel: 12 saturation: s brightness: v)].
- 	^ (s min: 1.0) @ (v min: 1.0)!

Item was removed:
- ----- Method: Color class>>shutDown (in category 'other') -----
- shutDown
- 	"Color shutDown"
- 
- 	ColorChart := nil.		"Palette of colors for the user to pick from"
- 	CachedColormaps := nil.	"Maps to translate between color depths"
- 	MaskingMap := nil.		"Maps all colors except transparent to black for creating a mask"
- !

Item was removed:
- ----- Method: Color class>>silver (in category 'named colors - crayons') -----
- silver
- 
- 	^ Color r: 204/255 g: 204/255 b: 204/255!

Item was removed:
- ----- Method: Color class>>sky (in category 'named colors - crayons') -----
- sky
- 
- 	^ Color r: 102/255 g: 204/255 b: 1.0!

Item was removed:
- ----- Method: Color class>>snow (in category 'named colors - crayons') -----
- snow
- 
- 	^ Color r: 1.0 g: 1.0 b: 1.0!

Item was removed:
- ----- Method: Color class>>spindrift (in category 'named colors - crayons') -----
- spindrift
- 
- 	^ Color r: 102/255 g: 1.0 b: 204/255!

Item was removed:
- ----- Method: Color class>>spring (in category 'named colors - crayons') -----
- spring
- 
- 	^ Color r: 0.0 g: 1.0 b: 0.0!

Item was removed:
- ----- Method: Color class>>steel (in category 'named colors - crayons') -----
- steel
- 
- 	^ Color r: 102/255 g: 102/255 b: 102/255!

Item was removed:
- ----- Method: Color class>>strawberry (in category 'named colors - crayons') -----
- strawberry
- 
- 	^ Color r: 1.0 g: 0.0 b: 128/255!

Item was removed:
- ----- Method: Color class>>tan (in category 'named colors') -----
- tan
- 	^  Color r: 0.8 g: 0.8 b: 0.5!

Item was removed:
- ----- Method: Color class>>tangerine (in category 'named colors - crayons') -----
- tangerine
- 
- 	^ Color r: 1.0 g: 128/255 b: 0.0!

Item was removed:
- ----- Method: Color class>>teal (in category 'named colors - crayons') -----
- teal
- 
- 	^ Color r: 0.0 g: 128/255 b: 128/255!

Item was removed:
- ----- Method: Color class>>tin (in category 'named colors - crayons') -----
- tin
- 
- 	^ Color r: 127/255 g: 127/255 b: 127/255!

Item was removed:
- ----- Method: Color class>>translucentMaskFor:depth: (in category 'other') -----
- translucentMaskFor: alphaValue depth: d
- 	"Return a pattern representing a mask usable for stipple transparency"
- 	^(TranslucentPatterns at: d) at: ((alphaValue min: 1.0 max: 0.0) * 4) rounded + 1!

Item was removed:
- ----- Method: Color class>>transparent (in category 'named colors') -----
- transparent
- 	^Transparent!

Item was removed:
- ----- Method: Color class>>tungsten (in category 'named colors - crayons') -----
- tungsten
- 
- 	^ Color r: 51/255 g: 51/255 b: 51/255!

Item was removed:
- ----- Method: Color class>>turquoise (in category 'named colors - crayons') -----
- turquoise
- 
- 	^ Color r: 0.0 g: 1.0 b: 1.0!

Item was removed:
- ----- Method: Color class>>veryDarkGray (in category 'named colors') -----
- veryDarkGray
- 	^VeryDarkGray!

Item was removed:
- ----- Method: Color class>>veryLightGray (in category 'named colors') -----
- veryLightGray
- 	^VeryLightGray!

Item was removed:
- ----- Method: Color class>>veryPaleRed (in category 'named colors') -----
- veryPaleRed
- 	^VeryPaleRed!

Item was removed:
- ----- Method: Color class>>veryVeryDarkGray (in category 'named colors') -----
- veryVeryDarkGray
- 	^VeryVeryDarkGray!

Item was removed:
- ----- Method: Color class>>veryVeryLightGray (in category 'named colors') -----
- veryVeryLightGray
- 	^VeryVeryLightGray!

Item was removed:
- ----- Method: Color class>>wheel: (in category 'examples') -----
- wheel: thisMany
- 	"Return a collection of thisMany colors evenly spaced around the color wheel."
- 	"Color showColors: (Color wheel: 12)"
- 
- 	^ Color wheel: thisMany saturation: 0.9 brightness: 0.7
- !

Item was removed:
- ----- Method: Color class>>wheel:saturation:brightness: (in category 'examples') -----
- wheel: thisMany saturation: s brightness: v
- 	"Return a collection of thisMany colors evenly spaced around the color wheel, all of the given saturation and brightness."
- 	"Color showColors: (Color wheel: 12 saturation: 0.4 brightness: 1.0)"
- 	"Color showColors: (Color wheel: 12 saturation: 0.8 brightness: 0.5)"
- 
- 	^ (Color h: 0.0 s: s v: v) wheel: thisMany
- !

Item was removed:
- ----- Method: Color class>>white (in category 'named colors') -----
- white
- 	^White!

Item was removed:
- ----- Method: Color class>>yellow (in category 'named colors') -----
- yellow
- 	^Yellow!

Item was removed:
- ----- Method: Color>>* (in category 'transformations') -----
- * aNumberOrArray
- 	"Answer this color with its RGB multiplied by the given number, or
- 	 multiply this color's RGB values by the corresponding entries in the
- 	given array."
- 	"(Color brown * 2) display"
- 	"(Color brown * #(1 0 1)) display"
- 	| multipliers |
- 	multipliers := aNumberOrArray isCollection
- 		ifTrue: [aNumberOrArray]
- 		ifFalse:
- 			[Array
- 				with: aNumberOrArray
- 				with: aNumberOrArray
- 				with: aNumberOrArray].
- 
- 	^ Color basicNew
- 		setPrivateRed: (self privateRed * multipliers first) asInteger
- 		green: (self privateGreen * multipliers second) asInteger
- 		blue: (self privateBlue * multipliers third) asInteger.!

Item was removed:
- ----- Method: Color>>+ (in category 'transformations') -----
- + aColor
- 	"Answer this color mixed with the given color in an additive color space.  "
- 	"(Color blue + Color green) display"
- 
- 	^ Color basicNew
- 		setPrivateRed: self privateRed + aColor privateRed
- 		green: self privateGreen + aColor privateGreen
- 		blue: self privateBlue + aColor  privateBlue
- !

Item was removed:
- ----- Method: Color>>- (in category 'transformations') -----
- - aColor
- 	"Answer aColor is subtracted from the given color in an additive color space.  "
- 	"(Color white - Color red) display"
- 
- 	^ Color basicNew
- 		setPrivateRed: self privateRed - aColor privateRed
- 		green: self privateGreen - aColor privateGreen
- 		blue: self privateBlue - aColor  privateBlue
- !

Item was removed:
- ----- Method: Color>>/ (in category 'transformations') -----
- / aNumber
- 	"Answer this color with its RGB divided by the given number. "
- 	"(Color red / 2) display"
- 
- 	^ Color basicNew
- 		setPrivateRed: (self privateRed / aNumber) asInteger
- 		green: (self privateGreen / aNumber) asInteger
- 		blue: (self privateBlue / aNumber) asInteger
- !

Item was removed:
- ----- Method: Color>>= (in category 'comparing') -----
- = aColor
- 	"Return true if the receiver equals the given color. This method handles TranslucentColors, too."
- 
- 	aColor isColor ifFalse: [^ false].
- 	^ aColor privateRGB = rgb and:
- 		[aColor privateAlpha = self privateAlpha]
- !

Item was removed:
- ----- Method: Color>>addFillStyleMenuItems:hand:from: (in category 'Morphic menu') -----
- addFillStyleMenuItems: aMenu hand: aHand from: aMorph
- 	"Add the items for changing the current fill style of the receiver"
- 	aMenu add: 'change color...' translated target: self selector: #changeColorIn:event: argument: aMorph!

Item was removed:
- ----- Method: Color>>addName: (in category 'other') -----
- addName: aSymbol
- 	"private - associate a name to this color."
- 	
- 	| knownNames |
- 	[(self class respondsTo: aSymbol) and: [(self class perform: aSymbol) = self]] assert.
- 	knownNames := RGBToNames at: rgb ifAbsent: [#()].
- 	(knownNames includes: aSymbol)
- 		ifFalse: [ RGBToNames at: rgb put: (knownNames copyWith: aSymbol)]!

Item was removed:
- ----- Method: Color>>adjustBrightness: (in category 'transformations') -----
- adjustBrightness: brightness
- 	"Adjust the relative brightness of this color. (lowest value is 0.005 so that hue information is not lost)"
- 
- 	^ Color
- 		h: self hue
- 		s: self saturation
- 		v: (self brightness + brightness min: 1.0 max: 0.005)
- 		alpha: self alpha!

Item was removed:
- ----- Method: Color>>adjustSaturation:brightness: (in category 'transformations') -----
- adjustSaturation: saturation brightness: brightness
- 	"Adjust the relative saturation and brightness of this color. (lowest value is 0.005 so that hue information is not lost)"
- 
- 	^ Color
- 		h: self hue
- 		s: (self saturation + saturation min: 1.0 max: 0.005)
- 		v: (self brightness + brightness min: 1.0 max: 0.005)
- 		alpha: self alpha!

Item was removed:
- ----- Method: Color>>alpha (in category 'accessing') -----
- alpha
- 	"Return the opacity ('alpha') value of opaque so that normal colors can be compared to TransparentColors."
- 
- 	^ 1.0
- !

Item was removed:
- ----- Method: Color>>alpha: (in category 'transformations') -----
- alpha: alphaValue 
- 	"Answer a new Color with the given amount of opacity ('alpha')."
- 
- 	alphaValue = 1.0
- 		ifFalse: [^ TranslucentColor basicNew setRgb: rgb alpha: alphaValue]!

Item was removed:
- ----- Method: Color>>alphaMixed:with: (in category 'transformations') -----
- alphaMixed: proportion with: aColor 
- 	"Answer this color mixed with the given color. The proportion, a number 
- 	between 0.0 and 1.0, determines what what fraction of the receiver to  
- 	use in the mix. For example, 0.9 would yield a color close to the  
- 	receiver. This method uses RGB interpolation; HSV interpolation can lead 
- 	to surprises.  Mixes the alphas (for transparency) also."
- 
- 	| frac1 frac2 |
- 	frac1 := proportion asFloat min: 1.0 max: 0.0.
- 	frac2 := 1.0 - frac1.
- 	^ Color
- 		r: self red * frac1 + (aColor red * frac2)
- 		g: self green * frac1 + (aColor green * frac2)
- 		b: self blue * frac1 + (aColor blue * frac2)
- 		alpha: self alpha * frac1 + (aColor alpha * frac2)!

Item was removed:
- ----- Method: Color>>asColor (in category 'conversions') -----
- asColor
- 	"Convert the receiver into a color"
- 	^self!

Item was removed:
- ----- Method: Color>>asColorref (in category 'conversions') -----
- asColorref
- 	"Convert the receiver into a colorref"
- 	^ (self red * 255) rounded + ((self green * 255) rounded << 8) + ((self blue * 255) rounded << 16)!

Item was removed:
- ----- Method: Color>>asHTMLColor (in category 'conversions') -----
- asHTMLColor
- 	| s |
- 	s := '#000000' copy.
- 	s at: 2 put: (Character digitValue: ((rgb bitShift: -6 - RedShift) bitAnd: 15)).
- 	s at: 3 put: (Character digitValue: ((rgb bitShift: -2 - RedShift) bitAnd: 15)).
- 	s at: 4 put: (Character digitValue: ((rgb bitShift: -6 - GreenShift) bitAnd: 15)).
- 	s at: 5 put: (Character digitValue: ((rgb bitShift: -2 - GreenShift) bitAnd: 15)).
- 	s at: 6 put: (Character digitValue: ((rgb bitShift: -6 - BlueShift) bitAnd: 15)).
- 	s at: 7 put: (Character digitValue: ((rgb bitShift: -2 - BlueShift) bitAnd: 15)).
- 	^ s!

Item was removed:
- ----- Method: Color>>asNontranslucentColor (in category 'conversions') -----
- asNontranslucentColor
- 	^ self!

Item was removed:
- ----- Method: Color>>atLeastAsLuminentAs: (in category 'transformations') -----
- atLeastAsLuminentAs: aFloat
- 
- 	| revisedColor |
- 	revisedColor := self.
- 	[revisedColor luminance < aFloat] whileTrue: [revisedColor := revisedColor slightlyLighter].
- 	^revisedColor
- !

Item was removed:
- ----- Method: Color>>atMostAsLuminentAs: (in category 'transformations') -----
- atMostAsLuminentAs: aFloat
- 
- 	| revisedColor |
- 	revisedColor := self.
- 	[revisedColor luminance > aFloat] whileTrue: [revisedColor := revisedColor slightlyDarker].
- 	^revisedColor
- !

Item was removed:
- ----- Method: Color>>attemptToMutateError (in category 'private') -----
- attemptToMutateError
- 	"A color is immutable. Once a color's red, green, and blue have been initialized, you cannot change them. Instead, create a new Color and use it."
- 
- 	self error: 'Color objects are immutable once created'
- !

Item was removed:
- ----- Method: Color>>balancedPatternForDepth: (in category 'conversions') -----
- balancedPatternForDepth: depth
- 	"A generalization of bitPatternForDepth: as it exists.  Generates a 2x2 stipple of color.
- 	The topLeft and bottomRight pixel are closest approx to this color"
- 	| pv1 pv2 mask1 mask2 pv3 c |
- 	(depth == cachedDepth and:[cachedBitPattern size = 2]) ifTrue: [^ cachedBitPattern].
- 	(depth between: 4 and: 16) ifFalse: [^ self bitPatternForDepth: depth].
- 	cachedDepth := depth.
- 	pv1 := self pixelValueForDepth: depth.
- "
- 	Subtract error due to pv1 to get pv2.
- 	pv2 := (self - (err1 := (Color colorFromPixelValue: pv1 depth: depth) - self))
- 						pixelValueForDepth: depth.
- 	Subtract error due to 2 pv1's and pv2 to get pv3.
- 	pv3 := (self - err1 - err1 - ((Color colorFromPixelValue: pv2 depth: depth) - self))
- 						pixelValueForDepth: depth.
- "
- 	"Above two statements computed faster by the following..."
- 	pv2 := (c := self - ((Color colorFromPixelValue: pv1 depth: depth) - self))
- 						pixelValueForDepth: depth.
- 	pv3 := (c + (c - (Color colorFromPixelValue: pv2 depth: depth)))
- 						pixelValueForDepth: depth.
- 
- 	"Return to a 2-word bitmap that encodes a 2x2 stipple of the given pixelValues."
- 	mask1 := (#(- - -	
- 			16r01010101 - - -			"replicates every other 4 bits"
- 			16r00010001 - - - - - - -	"replicates every other 8 bits"
- 			16r00000001) at: depth).	"replicates every other 16 bits"
- 	mask2 := (#(- - -	
- 			16r10101010 - - -			"replicates the other 4 bits"
- 			16r01000100 - - - - - - -	"replicates the other 8 bits"
- 			16r00010000) at: depth).	"replicates the other 16 bits"
- 	^ cachedBitPattern := Bitmap with: (mask1*pv1) + (mask2*pv2) with: (mask1*pv3) + (mask2*pv1)!

Item was removed:
- ----- Method: Color>>bitPatternForDepth: (in category 'conversions') -----
- bitPatternForDepth: depth
- 	"Return a Bitmap, possibly containing a stipple pattern, that best represents this color at the given depth. BitBlt calls this method to convert colors into Bitmaps. The resulting Bitmap may be multiple words to represent a stipple pattern of several lines.  "
- 	"See also:	pixelValueAtDepth:	-- value for single pixel
- 				pixelWordAtDepth:	-- a 32-bit word filled with the pixel value"
- 	"Details: The pattern for the most recently requested depth is cached."
- 	"Note for depths > 2, there are stippled and non-stippled versions (generated with #balancedPatternForDepth: and #bitPatternForDepth:, respectively). The stippled versions don't work with the window bit caching of StandardSystemView, so we make sure that for these depths, only unstippled patterns are returned"
- 
- 	(depth == cachedDepth and: [depth <= 2 or: [cachedBitPattern size = 1]]) ifTrue: [^ cachedBitPattern].
- 	cachedDepth := depth.
- 
- 	depth > 2 ifTrue: [^ cachedBitPattern := Bitmap with: (self pixelWordForDepth: depth)].
- 	depth = 1 ifTrue: [^ cachedBitPattern := self halfTonePattern1].
- 	depth = 2 ifTrue: [^ cachedBitPattern := self halfTonePattern2].
- !

Item was removed:
- ----- Method: Color>>blacker (in category 'transformations') -----
- blacker
- 
- 	^ self alphaMixed: 0.8333 with: Color black
- !

Item was removed:
- ----- Method: Color>>blue (in category 'accessing') -----
- blue
- 	"Return the blue component of this color, a float in the range [0.0..1.0]."
- 
- 	^ self privateBlue asFloat / ComponentMax!

Item was removed:
- ----- Method: Color>>brightness (in category 'accessing') -----
- brightness
- 	"Return the brightness of this color, a float in the range [0.0..1.0]."
- 
- 	^ ((self privateRed max:
- 	    self privateGreen) max:
- 	    self privateBlue) asFloat / ComponentMax!

Item was removed:
- ----- Method: Color>>byteEncode: (in category 'printing') -----
- byteEncode: aStream
- 
- 	aStream
- 		print: '(';
- 		print: self species name;
- 		print: ' r: ';
- 		write: (self red roundTo: 0.001);
- 		print: ' g: ';
- 		write: (self green roundTo: 0.001);
- 		print: ' b: ';
- 		write: (self blue roundTo: 0.001) ;
- 		print: ')'.
- !

Item was removed:
- ----- Method: Color>>changeColorIn:event: (in category 'Morphic menu') -----
- changeColorIn: aMorph event: evt
- 	"Note: This is just a workaround to make sure we don't use the old color inst var"
- 	aMorph changeColorTarget: aMorph selector: #fillStyle: originalColor: self hand: evt hand!

Item was removed:
- ----- Method: Color>>closestPixelValue1 (in category 'conversions') -----
- closestPixelValue1
- 	"Return the nearest approximation to this color for a monochrome Form."
- 
- 	"fast special cases"
- 	rgb = 0 ifTrue: [^ 1].  "black"
- 	rgb = 16r3FFFFFFF ifTrue: [^ 0].  "white"
- 
- 	self luminance > 0.5
- 		ifTrue: [^ 0]  "white"
- 		ifFalse: [^ 1].  "black"
- !

Item was removed:
- ----- Method: Color>>closestPixelValue2 (in category 'conversions') -----
- closestPixelValue2
- 	"Return the nearest approximation to this color for a 2-bit deep Form."
- 
- 	| lum |
- 	"fast special cases"
- 	rgb = 0 ifTrue: [^ 1].  "black"
- 	rgb = 16r3FFFFFFF ifTrue: [^ 2].  "opaque white"
- 
- 	lum := self luminance.
- 	lum < 0.2 ifTrue: [^ 1].  "black"
- 	lum > 0.6 ifTrue: [^ 2].  "opaque white"
- 	^ 3  "50% gray"
- !

Item was removed:
- ----- Method: Color>>closestPixelValue4 (in category 'conversions') -----
- closestPixelValue4
- 	"Return the nearest approximation to this color for a 4-bit deep Form."
- 
- 	| bIndex |
- 	"fast special cases"
- 	rgb = 0 ifTrue: [^ 1].  "black"
- 	rgb = 16r3FFFFFFF ifTrue: [^ 2].  "opaque white"
- 
- 	rgb = PureRed privateRGB ifTrue: [^ 4].
- 	rgb = PureGreen privateRGB ifTrue: [^ 5].
- 	rgb = PureBlue privateRGB ifTrue: [^ 6].
- 	rgb = PureCyan privateRGB ifTrue: [^ 7].
- 	rgb = PureYellow privateRGB ifTrue: [^ 8].
- 	rgb = PureMagenta privateRGB ifTrue: [^ 9].
- 
- 	bIndex := (self luminance * 8.0) rounded.  "bIndex in [0..8]"
- 	^ #(
- 		1	"black"
- 		10	"1/8 gray"
- 		11	"2/8 gray"
- 		12	"3/8 gray"
- 		3	"4/8 gray"
- 		13	"5/8 gray"
- 		14	"6/8 gray"
- 		15	"7/8 gray"
- 		2	"opaque white"
- 	) at: bIndex + 1.
- !

Item was removed:
- ----- Method: Color>>closestPixelValue8 (in category 'conversions') -----
- closestPixelValue8
- 	"Return the nearest approximation to this color for an 8-bit deep Form."
- 
- 	"fast special cases"
- 	rgb = 0 ifTrue: [^ 1].  "black"
- 	rgb = 16r3FFFFFFF ifTrue: [^ 255].  "white"
- 
- 	self saturation < 0.2 ifTrue: [
- 		^ GrayToIndexMap at: (self privateGreen >> 2) + 1.  "nearest gray"
- 	] ifFalse: [
- 		"compute nearest entry in the color cube"
- 		^ 40 +
- 		  ((((self privateRed * 5) + HalfComponentMask) // ComponentMask) * 36) +
- 		  ((((self privateBlue * 5) + HalfComponentMask) // ComponentMask) * 6) +
- 		  (((self privateGreen * 5) + HalfComponentMask) // ComponentMask)].
- !

Item was removed:
- ----- Method: Color>>colorForInsets (in category 'other') -----
- colorForInsets
- 	^ self!

Item was removed:
- ----- Method: Color>>dansDarker (in category 'transformations') -----
- dansDarker
- 	"Return a darker shade of the same color.
- 	An attempt to do better than the current darker method.
- 	(now obsolete, since darker has been changed to do this. -dew)"
- 	^ Color h: self hue s: self saturation
- 		v: (self brightness - 0.16 max: 0.0)!

Item was removed:
- ----- Method: Color>>darkShades: (in category 'groups of shades') -----
- darkShades: thisMany
- 	"An array of thisMany colors from black to the receiver.  Array is of length num. Very useful for displaying color based on a variable in your program.  "
- 	"Color showColors: (Color red darkShades: 12)"
- 
- 	^ self class black mix: self shades: thisMany
- !

Item was removed:
- ----- Method: Color>>darker (in category 'transformations') -----
- darker
- 	"Answer a darker shade of this color."
- 
- 	^ self adjustBrightness: -0.08!

Item was removed:
- ----- Method: Color>>diff: (in category 'comparing') -----
- diff: theOther
- 	"Returns a number between 0.0 and 1.0"
- 
- 	^ ((self privateRed - theOther privateRed) abs
- 		+ (self privateGreen - theOther privateGreen) abs
- 		+ (self privateBlue - theOther privateBlue) abs)
- 		/ 3.0 / ComponentMax!

Item was removed:
- ----- Method: Color>>display (in category 'other') -----
- display
- 	"Show a swatch of this color tracking the cursor until the next mouseClick. "
- 	"Color red display"
- 	| f |
- 	f := Form extent: 40 at 20 depth: Display depth.
- 	f fillColor: self.
- 	Cursor blank showWhile:
- 		[f follow: [Sensor cursorPoint] while: [Sensor noButtonPressed]]!

Item was removed:
- ----- Method: Color>>dominantColor (in category 'conversions') -----
- dominantColor
- 	^ self!

Item was removed:
- ----- Method: Color>>duller (in category 'transformations') -----
- duller
- 	"Answer a darker, desaturated color.  If the original color isn't very saturated, desaturate it by less (otherwise will just end up with grey). If the original color is a grey, don't try to be smart."
- 	| sat adjust |
- 	(sat := self saturation) > 0.3
- 		ifTrue: [adjust := -0.1]
- 		ifFalse: [adjust := 0.1 - sat max: 0.0].
- 	^ sat isZero 
- 		ifTrue: [self adjustBrightness: -0.1]
- 		ifFalse: [self adjustSaturation: adjust brightness: -0.1]!

Item was removed:
- ----- Method: Color>>flushCache (in category 'private') -----
- flushCache
- 	"Flush my cached bit pattern."
- 
- 	cachedDepth := nil.
- 	cachedBitPattern := nil.
- !

Item was removed:
- ----- Method: Color>>green (in category 'accessing') -----
- green
- 	"Return the green component of this color, a float in the range [0.0..1.0]."
- 
- 	^ self privateGreen asFloat / ComponentMax!

Item was removed:
- ----- Method: Color>>halfTonePattern1 (in category 'conversions') -----
- halfTonePattern1
- 	"Return a halftone-pattern to approximate luminance levels on 1-bit deep Forms."
- 
- 	| lum |
- 	lum := self luminance.
- 	lum < 0.1 ifTrue: [^ Bitmap with: 16rFFFFFFFF]. "black"
- 	lum < 0.4 ifTrue: [^ Bitmap with: 16rBBBBBBBB with: 16rEEEEEEEE]. "dark gray"
- 	lum < 0.6 ifTrue: [^ Bitmap with: 16r55555555 with: 16rAAAAAAAA]. "medium gray"
- 	lum < 0.9 ifTrue: [^ Bitmap with: 16r44444444 with: 16r11111111]. "light gray"
- 	^ Bitmap with: 0  "1-bit white"
- !

Item was removed:
- ----- Method: Color>>halfTonePattern2 (in category 'conversions') -----
- halfTonePattern2
- 	"Return a halftone-pattern to approximate luminance levels on 2-bit deep Forms."
- 
- 	| lum |
- 	lum := self luminance.
- 	lum < 0.125 ifTrue: [^ Bitmap with: 16r55555555].  "black"
- 	lum < 0.25 ifTrue: [^ Bitmap with: 16r55555555 with: 16rDDDDDDDD].  "1/8 gray"
- 	lum < 0.375 ifTrue: [^ Bitmap with: 16rDDDDDDDD with: 16r77777777].  "2/8 gray"
- 	lum < 0.5 ifTrue: [^ Bitmap with: 16rFFFFFFFF with: 16r77777777].  "3/8 gray"
- 	lum < 0.625 ifTrue: [^ Bitmap with: 16rFFFFFFFF].  "4/8 gray"
- 	lum < 0.75 ifTrue: [^ Bitmap with: 16rFFFFFFFF with: 16rBBBBBBBB].  "5/8 gray"
- 	lum < 0.875 ifTrue: [^ Bitmap with: 16rEEEEEEEE with: 16rBBBBBBBB].  "6/8 gray"
- 	lum < 1.0 ifTrue: [^ Bitmap with: 16rAAAAAAAA with: 16rBBBBBBBB].  "7/8 gray"
- 	^ Bitmap with: 16rAAAAAAAA  "opaque white"
- 
- "handy expression for computing patterns for 2x2 tiles;
-  set p to a string of 4 letters (e.g., 'wggw' for a gray-and-
-  white checkerboard) and print the result of evaluating:
- | p d w1 w2 |
- p := 'wggw'.
- d := Dictionary new.
- d at: $b put: '01'.
- d at: $w put: '10'.
- d at: $g put: '11'.
- w1 := (d at: (p at: 1)), (d at: (p at: 2)).
- w1 := '2r', w1, w1, w1, w1, w1, w1, w1, w1, ' hex'.
- w2 := (d at: (p at: 3)), (d at: (p at: 4)).
- w2 := '2r', w2, w2, w2, w2, w2, w2, w2, w2, ' hex'.
- Array with: (Compiler evaluate: w1) with: (Compiler evaluate: w2) 
- "!

Item was removed:
- ----- Method: Color>>hash (in category 'comparing') -----
- hash
- 
- 	^ rgb!

Item was removed:
- ----- Method: Color>>hue (in category 'accessing') -----
- hue
- 	"Return the hue of this color, an angle in the range [0.0..360.0]."
- 
- 	| r g b max min span h |
- 	r := self privateRed.
- 	g := self privateGreen.
- 	b := self privateBlue. 
- 
- 	max := ((r max: g) max: b).
- 	min := ((r min: g) min: b).
- 	span := (max - min) asFloat.
- 	span = 0.0 ifTrue: [ ^ 0.0 ].
- 
- 	r = max ifTrue: [
- 		h := ((g - b) asFloat / span) * 60.0.
- 	] ifFalse: [
- 		g = max
- 			ifTrue: [ h := 120.0 + (((b - r) asFloat / span) * 60.0). ]
- 			ifFalse: [ h := 240.0 + (((r - g) asFloat / span) * 60.0). ].
- 	].
- 
- 	h < 0.0 ifTrue: [ h := 360.0 + h ].
- 	^ h!

Item was removed:
- ----- Method: Color>>indexInMap: (in category 'conversions') -----
- indexInMap: aColorMap
- 	"Return the index corresponding to this color in the given color map. RGB colors are truncated to 3-, 4-, or 5-bits per color component when indexing into such a colorMap.  "
- 
- 	aColorMap size = 2 ifTrue: [^ (self pixelValueForDepth: 1) + 1].
- 	aColorMap size = 4 ifTrue: [^ (self pixelValueForDepth: 2) + 1].
- 	aColorMap size = 16 ifTrue: [^ (self pixelValueForDepth: 4) + 1].
- 	aColorMap size = 256 ifTrue: [^ (self pixelValueForDepth: 8) + 1].
- 	aColorMap size = 512 ifTrue: [^ (self pixelValueForDepth: 9) + 1].
- 	aColorMap size = 4096 ifTrue: [^ (self pixelValueForDepth: 12) + 1].
- 	aColorMap size = 32768 ifTrue: [^ (self pixelValueForDepth: 16) + 1].
- 	self error: 'unknown pixel depth'.
- !

Item was removed:
- ----- Method: Color>>isBitmapFill (in category 'testing') -----
- isBitmapFill
- 	^false!

Item was removed:
- ----- Method: Color>>isBlack (in category 'testing') -----
- isBlack
- 	"Return true if the receiver represents black"
- 	^rgb = 0!

Item was removed:
- ----- Method: Color>>isColor (in category 'testing') -----
- isColor
- 
- 	^ true
- !

Item was removed:
- ----- Method: Color>>isGradientFill (in category 'testing') -----
- isGradientFill
- 	^false!

Item was removed:
- ----- Method: Color>>isGray (in category 'testing') -----
- isGray
- 	"Return true if the receiver represents a shade of gray"
- 	^(self privateRed = self privateGreen) and:[self privateRed = self privateBlue]!

Item was removed:
- ----- Method: Color>>isOpaque (in category 'testing') -----
- isOpaque
- 	^true!

Item was removed:
- ----- Method: Color>>isOrientedFill (in category 'testing') -----
- isOrientedFill
- 	"Return true if the receiver keeps an orientation (e.g., origin, direction, and normal)"
- 	^false!

Item was removed:
- ----- Method: Color>>isSolidFill (in category 'testing') -----
- isSolidFill
- 	^true!

Item was removed:
- ----- Method: Color>>isTranslucent (in category 'testing') -----
- isTranslucent
- 
- 	^ false
- !

Item was removed:
- ----- Method: Color>>isTranslucentColor (in category 'testing') -----
- isTranslucentColor
- 	"This means: self isTranslucent, but isTransparent not"
- 	^ false!

Item was removed:
- ----- Method: Color>>isTransparent (in category 'testing') -----
- isTransparent
- 
- 	^ false
- !

Item was removed:
- ----- Method: Color>>lightShades: (in category 'groups of shades') -----
- lightShades: thisMany
- 	"An array of thisMany colors from white to self. Very useful for displaying color based on a variable in your program.  "
- 	"Color showColors: (Color red lightShades: 12)"
- 
- 	^ self class white mix: self shades: thisMany
- !

Item was removed:
- ----- Method: Color>>lighter (in category 'transformations') -----
- lighter
- 	"Answer a lighter shade of this color."
- 
- 	^ self adjustSaturation: -0.03 brightness: 0.08!

Item was removed:
- ----- Method: Color>>luminance (in category 'accessing') -----
- luminance
- 	"Return the luminance of this color, a brightness value weighted by the human eye's color sensitivity."
- 
- 	^ ((299 * self privateRed) +
- 	   (587 * self privateGreen) +
- 	   (114 * self privateBlue)) / (1000 * ComponentMax)
- !

Item was removed:
- ----- Method: Color>>makeForegroundColor (in category 'conversions') -----
- makeForegroundColor
-         "Make a foreground color contrasting with me"
-         ^self luminance >= 0.5
-                 ifTrue: [Color black]
-                 ifFalse: [Color white]!

Item was removed:
- ----- Method: Color>>mix:shades: (in category 'groups of shades') -----
- mix: color2 shades: thisMany
- 	"Return an array of thisMany colors from self to color2. Very useful for displaying color based on a variable in your program.  "
- 	"Color showColors: (Color red mix: Color green shades: 12)"
- 
- 	| redInc greenInc blueInc out rr gg bb |
- 	thisMany = 1 ifTrue: [^ Array with: color2].
- 	redInc := color2 red - self red / (thisMany-1).
- 	greenInc := color2 green - self green / (thisMany-1).
- 	blueInc := color2 blue - self blue / (thisMany-1).
- 	rr := self red.  gg := self green.  bb := self blue.
- 	out := (1 to: thisMany) collect: [:num | | c |
- 		c := Color r: rr g: gg b: bb.
- 		rr := rr + redInc.
- 		gg := gg + greenInc.
- 		bb := bb + blueInc.
- 		c].
- 	out at: out size put: color2.	"hide roundoff errors"
- 	^ out
- !

Item was removed:
- ----- Method: Color>>mixed:with: (in category 'transformations') -----
- mixed: proportion with: aColor 
- 	"Mix with another color and do not preserve transpareny.  Only use this for extracting the RGB value and mixing it.  All other callers should use instead: 
- 	aColor alphaMixed: proportion with: anotherColor
- 	"
- 
- 	| frac1 frac2 |
- 	frac1 := proportion asFloat min: 1.0 max: 0.0.
- 	frac2 := 1.0 - frac1.
- 	^ Color
- 		r: self red * frac1 + (aColor red * frac2)
- 		g: self green * frac1 + (aColor green * frac2)
- 		b: self blue * frac1 + (aColor blue * frac2)!

Item was removed:
- ----- Method: Color>>muchDarker (in category 'transformations') -----
- muchDarker
- 
- 	^ self alphaMixed: 0.5 with: Color black
- !

Item was removed:
- ----- Method: Color>>muchLighter (in category 'transformations') -----
- muchLighter
- 
- 	^ self alphaMixed: 0.233 with: Color white
- !

Item was removed:
- ----- Method: Color>>name (in category 'other') -----
- name
- 	"Return this color's name, or nil if it has no name."
- 
- 	^ (RGBToNames at: rgb ifAbsent: [nil]) ifNotNil: [:names | names at: 1 ifAbsent: [nil]]!

Item was removed:
- ----- Method: Color>>names (in category 'other') -----
- names
- 	"Return a collection of all known names for this color.
- 	These are Symbol that can be used as message send to Color."
- 
- 	^ RGBToNames at: rgb ifAbsent: [Array new]!

Item was removed:
- ----- Method: Color>>negated (in category 'transformations') -----
- negated
- 	"Return an RGB inverted color"
- 	^Color
- 		r: 1.0 - self red
- 		g: 1.0 - self green
- 		b: 1.0 - self blue
- 		alpha: self alpha!

Item was removed:
- ----- Method: Color>>orColorUnlike: (in category 'transformations') -----
- orColorUnlike: theOther
- 	"If this color is a lot like theOther, then return its complement, otherwide, return self"
- 
- 	(self diff: theOther) < 0.3
- 		ifTrue: [^ theOther negated]
- 		ifFalse: [^ self]!

Item was removed:
- ----- Method: Color>>paler (in category 'transformations') -----
- paler
- 	"Answer a paler shade of this color."
- 
- 	^ self adjustSaturation: -0.09 brightness: 0.09
- !

Item was removed:
- ----- Method: Color>>pixelValue32 (in category 'conversions') -----
- pixelValue32
- 	"Note: pixelWord not pixelValue so we include translucency"
- 	^self pixelWordForDepth: 32!

Item was removed:
- ----- Method: Color>>pixelValueForDepth: (in category 'conversions') -----
- pixelValueForDepth: d
- 	"Answers an integer representing the bits that appear in a single pixel of this color in a Form of the given depth.
- 	 The depth must be one of 1, 2, 4, 8, 16, or 32. Contrast with pixelWordForDepth: and bitPatternForDepth:, which
- 	 answer either a 32-bit word packed with the given pixel value or a multiple-word Bitmap containing a pattern.
- 	 The inverse is the class message colorFromPixelValue:depth:"
- 	"Details:
- 		For depths of 8 or less, the result is a colorMap index.
- 		For depths of 16 and 32, it is a direct color value with 5 or 8 bits per color component."
- 	"Transparency:
- 		The pixel value zero is reserved for transparent.
- 		For depths greater than 8, black maps to the darkest possible blue."
- 
- 	| val |
- 	d > 8 ifTrue: "most common case"
- 		[d = 32 ifTrue: "eight bits per component; top 8 bits set to all ones (opaque alpha)"
- 			["this subexpression is a SmallInteger in both 32- and 64-bits."
- 			 val :=	((rgb bitShift: -6) bitAnd: 16rFF0000) bitOr:
- 					(((rgb bitShift: -4) bitAnd: 16rFF00) bitOr:
- 					((rgb bitShift: -2) bitAnd: 16rFF)).
- 			"16rFF000000 & 16rFF000001 are LargeIntegers in 32-bits, SmallIntegers in 64-bits."
- 			^val = 0 ifTrue: [16rFF000001] ifFalse: [16rFF000000 + val]].
- 			
- 		d = 16 ifTrue: "five bits per component; top bits ignored"
- 			[val := (((rgb bitShift: -15) bitAnd: 16r7C00) bitOr:
- 					 ((rgb bitShift: -10) bitAnd: 16r03E0)) bitOr:
- 					 ((rgb bitShift: -5) bitAnd: 16r001F).
- 			^val = 0 ifTrue: [1] ifFalse: [val]].
- 
- 		d = 12 ifTrue: "for indexing a color map with 4 bits per color component"
- 			[val := (((rgb bitShift: -18) bitAnd: 16r0F00) bitOr:
- 					 ((rgb bitShift: -12) bitAnd: 16r00F0)) bitOr:
- 					 ((rgb bitShift: -6) bitAnd: 16r000F).
- 			^val = 0 ifTrue: [1] ifFalse: [val]].
- 
- 		d = 9 ifTrue: "for indexing a color map with 3 bits per color component"
- 			[val := (((rgb bitShift: -21) bitAnd: 16r01C0) bitOr:
- 				 ((rgb bitShift: -14) bitAnd: 16r0038)) bitOr:
- 				 ((rgb bitShift: -7) bitAnd: 16r0007).
- 			^val = 0 ifTrue: [1] ifFalse: [val]]].
- 	d = 8 ifTrue: [^ self closestPixelValue8].
- 	d = 4 ifTrue: [^ self closestPixelValue4].
- 	d = 2 ifTrue: [^ self closestPixelValue2]..
- 	d = 1 ifTrue: [^ self closestPixelValue1].
- 
- 	self error: 'unknown pixel depth: ', d printString
- !

Item was removed:
- ----- Method: Color>>pixelWordFor:filledWith: (in category 'conversions') -----
- pixelWordFor: depth filledWith: pixelValue
- 	"Return to a 32-bit word that concatenates enough copies of the given pixel value to fill the word (i.e., 32/depth copies). Depth should be one of 1, 2, 4, 8, 16, or 32. The pixel value should be an integer in 0..2^depth-1."
- 	| halfword |
- 	depth = 32 ifTrue: [^ pixelValue].
- 	depth = 16
- 		ifTrue: [halfword := pixelValue]
- 		ifFalse: [halfword := pixelValue * 
- 					(#(16rFFFF				"replicates at every bit"
- 						16r5555 -			"replicates every 2 bits"
- 						16r1111 - - -			"replicates every 4 bits"
- 						16r0101) at: depth)	"replicates every 8 bits"].
- 	^ halfword bitOr: (halfword bitShift: 16)!

Item was removed:
- ----- Method: Color>>pixelWordForDepth: (in category 'conversions') -----
- pixelWordForDepth: depth
- 	"Return to a 32-bit word that concatenates enough copies of the receiver's pixel value to fill the word (i.e., 32/depth copies). Depth should be one of 1, 2, 4, 8, 16, or 32. The pixel value should be an integer in 0..2^depth-1."
- 
- 	| pixelValue |
- 	pixelValue := self pixelValueForDepth: depth.
- 	^ self pixelWordFor: depth filledWith: pixelValue
- !

Item was removed:
- ----- Method: Color>>printHtmlString (in category 'html') -----
- printHtmlString
- 	"answer a string whose characters are the html representation  
- 	of the receiver"
- 	^ ((self red * 255) rounded printStringBase: 16 length: 2 padded: true)
- 		, ((self green * 255) rounded printStringBase: 16 length: 2 padded: true)
- 		, ((self blue * 255) rounded printStringBase: 16 length: 2 padded: true)!

Item was removed:
- ----- Method: Color>>printOn: (in category 'printing') -----
- printOn: aStream
- 	| name |
- 	(name := self name) ifNotNil:
- 		[^ aStream
- 			nextPutAll: 'Color ';
- 			nextPutAll: name].
- 	self storeOn: aStream.
- !

Item was removed:
- ----- Method: Color>>privateAlpha (in category 'private') -----
- privateAlpha
- 	"Private!! Return the raw alpha value for opaque. Used only for equality testing."
- 
- 	^ 255!

Item was removed:
- ----- Method: Color>>privateBlue (in category 'private') -----
- privateBlue
- 	"Private!! Return the internal representation of my blue component."
- 
- 	^ rgb bitAnd: ComponentMask!

Item was removed:
- ----- Method: Color>>privateGreen (in category 'private') -----
- privateGreen
- 	"Private!! Return the internal representation of my green component.
- 	Replaced >> by bitShift: 0 -. SqR!! 2/25/1999 23:08"
- 
- 	^ (rgb bitShift: 0 - GreenShift) bitAnd: ComponentMask!

Item was removed:
- ----- Method: Color>>privateRGB (in category 'private') -----
- privateRGB
- 	"Private!! Return the internal representation of my RGB components."
- 
- 	^ rgb
- !

Item was removed:
- ----- Method: Color>>privateRed (in category 'private') -----
- privateRed
- 	"Private!! Return the internal representation of my red component."
- 
- 	^ (rgb bitShift: 0 - RedShift) bitAnd: ComponentMask!

Item was removed:
- ----- Method: Color>>raisedColor (in category 'other') -----
- raisedColor
- 	^ self!

Item was removed:
- ----- Method: Color>>red (in category 'accessing') -----
- red
- 	"Return the red component of this color, a float in the range [0.0..1.0]."
- 
- 	^ self privateRed asFloat / ComponentMax!

Item was removed:
- ----- Method: Color>>rgbTriplet (in category 'other') -----
- rgbTriplet
- 	"Color fromUser rgbTriplet"
- 
- 	^ Array
- 		with: (self red roundTo: 0.01)
- 		with: (self green roundTo: 0.01)
- 		with: (self blue roundTo: 0.01)
- !

Item was removed:
- ----- Method: Color>>saturation (in category 'accessing') -----
- saturation
- 	"Return the saturation of this color, a value between 0.0 and 1.0."
- 
- 	| r g b max min |
- 	r := self privateRed.
- 	g := self privateGreen.
- 	b := self privateBlue. 
- 
- 	max := min := r.
- 	g > max ifTrue: [max := g].
- 	b > max ifTrue: [max := b].
- 	g < min ifTrue: [min := g].
- 	b < min ifTrue: [min := b].
- 
- 	max = 0
- 		ifTrue: [ ^ 0.0 ]
- 		ifFalse: [ ^ (max - min) asFloat / max asFloat ].
- !

Item was removed:
- ----- Method: Color>>scaledPixelValue32 (in category 'conversions') -----
- scaledPixelValue32
- 	"Return the alpha scaled pixel value for depth 32"
- 	^self pixelWordForDepth: 32!

Item was removed:
- ----- Method: Color>>setHue:saturation:brightness: (in category 'private') -----
- setHue: hue saturation: saturation brightness: brightness
- 	"Initialize this color to the given hue, saturation, and brightness. See the comment in the instance creation method for details."
- 
- 	| s v hf i f p q t | 
- 	s := (saturation asFloat max: 0.0) min: 1.0.
- 	v := (brightness asFloat max: 0.0) min: 1.0.
- 
- 	"zero saturation yields gray with the given brightness"
- 	s = 0.0 ifTrue: [ ^ self setRed: v green: v blue: v ].
- 
- 	hf := hue asFloat.
- 	(hf < 0.0 or: [hf >= 360.0])
- 		ifTrue: [hf := hf \\ 360].
- 	hf := hf / 60.0.
- 	i := hf asInteger.  "integer part of hue"
- 	f := hf fractionPart.         "fractional part of hue"
- 	p := (1.0 - s) * v.
- 	q := (1.0 - (s * f)) * v.
- 	t := (1.0 - (s * (1.0 - f))) * v.
- 
- 	0 = i ifTrue: [ ^ self setRed: v green: t blue: p ].
- 	1 = i ifTrue: [ ^ self setRed: q green: v blue: p ].
- 	2 = i ifTrue: [ ^ self setRed: p green: v blue: t ].
- 	3 = i ifTrue: [ ^ self setRed: p green: q blue: v ].
- 	4 = i ifTrue: [ ^ self setRed: t green: p blue: v ].
- 	5 = i ifTrue: [ ^ self setRed: v green: p blue: q ].
- 
- 	self error: 'implementation error'.
- !

Item was removed:
- ----- Method: Color>>setPrivateRed:green:blue: (in category 'private') -----
- setPrivateRed: r green: g blue: b
- 	"Initialize this color's r, g, and b components to the given values in the range [0..ComponentMax].  Encoded in a single variable as 3 integers in [0..1023]."
- 
- 	rgb == nil ifFalse: [self attemptToMutateError].
- 	rgb := ((r min: ComponentMask max: 0) bitShift: RedShift) +
- 		((g min: ComponentMask max: 0) bitShift: GreenShift) +
- 		 (b min: ComponentMask max: 0).
- 	cachedDepth := nil.
- 	cachedBitPattern := nil.
- !

Item was removed:
- ----- Method: Color>>setRGB: (in category 'private') -----
- setRGB: rgb0
- 	rgb == nil ifFalse: [self attemptToMutateError].
- 	rgb := rgb0!

Item was removed:
- ----- Method: Color>>setRed:green:blue: (in category 'private') -----
- setRed: r green: g blue: b
- 	"Initialize this color's r, g, and b components to the given values in the range [0.0..1.0].  Encoded in a single variable as 3 integers in [0..1023]."
- 
- 	rgb == nil ifFalse: [self attemptToMutateError].
- 	rgb :=
- 		(((r * ComponentMax) rounded bitAnd: ComponentMask) bitShift: RedShift) +
- 		(((g * ComponentMax) rounded bitAnd: ComponentMask) bitShift: GreenShift) +
- 		 ((b * ComponentMax) rounded bitAnd: ComponentMask).
- 	cachedDepth := nil.
- 	cachedBitPattern := nil.
- !

Item was removed:
- ----- Method: Color>>setRed:green:blue:range: (in category 'private') -----
- setRed: r green: g blue: b range: range
- 	"Initialize this color's r, g, and b components to the given values in the range [0..r]."
- 
- 	^ self setRed: r / range green: g / range blue: b / range!

Item was removed:
- ----- Method: Color>>shortPrintString (in category 'printing') -----
- shortPrintString
- 	"Return a short (but less precise) print string for use where space is tight."
- 
- 	^String streamContents: [:s | s
- 		nextPutAll: '(';
- 		print: self class;
- 		nextPutAll: ' r: '; print: self red maxDecimalPlaces: 2;
- 		nextPutAll: ' g: '; print: self green maxDecimalPlaces: 2;
- 		nextPutAll: ' b: '; print: self blue maxDecimalPlaces: 2;
- 		nextPutAll: ')']!

Item was removed:
- ----- Method: Color>>slightlyDarker (in category 'transformations') -----
- slightlyDarker
- 
- 	^ self adjustBrightness: -0.03
- !

Item was removed:
- ----- Method: Color>>slightlyLighter (in category 'transformations') -----
- slightlyLighter
- 
- 	^ self adjustSaturation: -0.01 brightness: 0.03!

Item was removed:
- ----- Method: Color>>slightlyWhiter (in category 'transformations') -----
- slightlyWhiter
- 
- 	^ self alphaMixed: 0.85 with: Color white
- !

Item was removed:
- ----- Method: Color>>storeArrayOn: (in category 'printing') -----
- storeArrayOn: aStream
- 
- 	aStream nextPutAll: '#('.
- 	self storeArrayValuesOn: aStream.
- 	aStream nextPutAll: ') '
- !

Item was removed:
- ----- Method: Color>>storeArrayValuesOn: (in category 'printing') -----
- storeArrayValuesOn: aStream
- 
- 	aStream
- 		print: self red maxDecimalPlaces: 3;
- 		space;
- 		print: self green maxDecimalPlaces: 3;
- 		space;
- 		print: self blue maxDecimalPlaces: 3.
- !

Item was removed:
- ----- Method: Color>>storeOn: (in category 'printing') -----
- storeOn: aStream
- 
- 	aStream
- 		nextPutAll: '(' , self species name;
- 		nextPutAll: ' r: '; print: self red maxDecimalPlaces: 3;
- 		nextPutAll: ' g: '; print: self green maxDecimalPlaces: 3;
- 		nextPutAll: ' b: '; print: self blue maxDecimalPlaces: 3;
- 		nextPutAll: ')'.
- !

Item was removed:
- ----- Method: Color>>thriceDarker (in category 'transformations') -----
- thriceDarker
- 	"Answer a significantly darker shade of this color."
- 
- 	^ self adjustSaturation: 0.09 brightness: -0.22!

Item was removed:
- ----- Method: Color>>thriceLighter (in category 'transformations') -----
- thriceLighter
- 	"Answer a significantly lighter shade of this color."
- 
- 	^ self adjustSaturation: -0.09 brightness: 0.22!

Item was removed:
- ----- Method: Color>>twiceDarker (in category 'transformations') -----
- twiceDarker
- 	"Answer a significantly darker shade of this color."
- 
- 	^ self adjustSaturation: 0.075 brightness: -0.15!

Item was removed:
- ----- Method: Color>>twiceLighter (in category 'transformations') -----
- twiceLighter
- 	"Answer a significantly lighter shade of this color."
- 
- 	^ self adjustSaturation: -0.06 brightness: 0.15!

Item was removed:
- ----- Method: Color>>veryDeepCopyWith: (in category 'copying') -----
- veryDeepCopyWith: deepCopier
- 	"I am immutable in the Morphic world. Do not record me."
- 	^ self!

Item was removed:
- ----- Method: Color>>veryMuchDarker (in category 'transformations') -----
- veryMuchDarker
- 
- 	^ self alphaMixed: 0.25 with: Color black
- !

Item was removed:
- ----- Method: Color>>veryMuchLighter (in category 'transformations') -----
- veryMuchLighter
- 
- 	^ self alphaMixed: 0.1165 with: Color white
- !

Item was removed:
- ----- Method: Color>>wheel: (in category 'groups of shades') -----
- wheel: thisMany
- 	"An array of thisMany colors around the color wheel starting at self and ending all the way around the hue space just before self.  Array is of length thisMany.  Very useful for displaying color based on a variable in your program.  "
- 
- 	| sat bri step hue |
- 	sat := self saturation.
- 	bri := self brightness.
- 	hue := self hue.
- 	step := 360.0 / (thisMany max: 1).
- 	^ (1 to: thisMany) collect: [:num | | c |
- 		c := Color h: hue s: sat v: bri.  "hue is taken mod 360"
- 		hue := hue + step.
- 		c].
- "
- (Color wheel: 8) withIndexDo: [:c :i | Display fill: (i*10 at 20 extent: 10 at 20) fillColor: c]
- "!

Item was removed:
- ----- Method: Color>>whiter (in category 'transformations') -----
- whiter
- 
- 	^ self alphaMixed: 0.8333 with: Color white
- !

Item was removed:
- Form subclass: #ColorForm
- 	instanceVariableNames: 'colors cachedDepth cachedColormap'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Display Objects'!
- ColorForm class
- 	instanceVariableNames: 'grayScalePalette'!
- 
- !ColorForm commentStamp: '<historical>' prior: 0!
- ColorForm is a normal Form plus a color map of up to 2^depth Colors. Typically, one reserves one entry in the color map for transparent. This allows 1, 3, 15, or 255 non-transparent colors in ColorForms of depths 1, 2, 4, and 8 bits per pixel. ColorForms don't support depths greater than 8 bits because that would require excessively large color maps with little real benefit, since 16-bit and 32-bit depths already support thousands and millions of colors.
- 
- ColorForms have several uses:
-   1) Precise colors. You can have up to 256 true colors, instead being limited to the 8-bit color palette.
-   2) Easy transparency. Just store (Color transparent) at the desired position in the color map.
-   3) Cheap color remapping by changing the color map.
- 
- A color map is an Array of up to 2^depth Color objects. A Bitmap colorMap is automatically computed and cached for rapid display. Note that if you change the color map, you must resubmit it via the colors: method to flush this cache.
- 
- ColorForms can be a bit tricky. Note that:
-   a) When you BitBlt from one ColorForm to another, you must remember to copy the color map of the source ColorForm to the destination ColorForm.
-   b) A ColorForm's color map is an array of depth-independent Color objects. BitBlt requires a BitMap of actual pixel values, adjusted to the destination depth. These are different things!! ColorForms automatically maintain a cache of the BitBlt-style color map corresponding to the colors array for the last depth on which the ColorForm was displayed, so there should be little need for clients to work with BitBlt-style color maps.
-   c) The default map for 8 bit depth has black in the first entry, not transparent.  Say (cform colors at: 1 put: Color transparent).
- !
- ColorForm class
- 	instanceVariableNames: 'grayScalePalette'!

Item was removed:
- ----- Method: ColorForm class>>grayScalePalette (in category 'constants') -----
- grayScalePalette
- 	grayScalePalette ifNil: [
- 		grayScalePalette := (0 to: 255) collect: [:brightness | Color gray: brightness asFloat / 255.0].
- 		grayScalePalette at: 1 put: Color transparent].
- 	^ grayScalePalette!

Item was removed:
- ----- Method: ColorForm class>>mappingWhiteToTransparentFrom: (in category 'as yet unclassified') -----
- mappingWhiteToTransparentFrom: aFormOrCursor
- 	"Return a ColorForm copied from the given Form or Cursor with white mapped to transparent."
- 
- 	| f map |
- 	aFormOrCursor depth <= 8 ifFalse: [
- 		^ self error: 'argument depth must be 8-bits per pixel or less'].
- 	(aFormOrCursor isColorForm) ifTrue: [
- 		f := aFormOrCursor deepCopy.
- 		map := aFormOrCursor colors.
- 	] ifFalse: [
- 		f := ColorForm extent: aFormOrCursor extent depth: aFormOrCursor depth.
- 		f copyBits: aFormOrCursor boundingBox
- 			from: aFormOrCursor
- 			at: 0 at 0
- 			clippingBox: aFormOrCursor boundingBox
- 			rule: Form over
- 			fillColor: nil.
- 		map := Color indexedColors copyFrom: 1 to: (1 bitShift: aFormOrCursor depth)].
- 	map := map collect: [:c |
- 		c = Color white ifTrue: [Color transparent] ifFalse: [c]].
- 	f colors: map.
- 	^ f
- !

Item was removed:
- ----- Method: ColorForm class>>twoToneFromDisplay:using:backgroundColor: (in category 'as yet unclassified') -----
- twoToneFromDisplay: aRectangle using: oldForm backgroundColor: bgColor
- 	"Return a 1-bit deep ColorForm copied from the given rectangle of the display. All colors except the background color will be mapped to black."
- 
- 	| f |
- 	((oldForm ~~ nil) and: [oldForm extent = aRectangle extent]) ifTrue: [
- 		f := oldForm fromDisplay: aRectangle.
- 	] ifFalse: [
- 		f := ColorForm extent: aRectangle extent depth: 1.
- 		f twoToneFromDisplay: aRectangle backgroundColor: bgColor.
- 		f colors: (Array
- 			with: bgColor
- 			with: Color black)].
- 	^ f
- !

Item was removed:
- ----- Method: ColorForm>>asCursorForm (in category 'copying') -----
- asCursorForm
- 
- 	^ (self asFormOfDepth: 32) offset: offset; as: StaticForm!

Item was removed:
- ----- Method: ColorForm>>asFormWithSingleTransparentColors (in category 'postscript generation') -----
- asFormWithSingleTransparentColors
- 	| transparentIndexes |
- 	transparentIndexes := self transparentColorIndexes.
- 	transparentIndexes size <= 1 ifTrue:[^self]
- 		ifFalse:[^self mapTransparencies:transparentIndexes].!

Item was removed:
- ----- Method: ColorForm>>asGrayScale (in category 'color manipulation') -----
- asGrayScale
- 	"Return a grayscale ColorForm computed by mapping each color into its grayscale equivalent"
- 	^ self copy colors:
- 		(colors collect:
- 			[:c | c isTransparent ifTrue: [c]
- 						ifFalse: [Color gray: c luminance]])!

Item was removed:
- ----- Method: ColorForm>>blankCopyOf:scaledBy: (in category 'copying') -----
- blankCopyOf: aRectangle scaledBy: scale
- 	^Form extent: (aRectangle extent * scale) truncated depth: 32!

Item was removed:
- ----- Method: ColorForm>>clearColormapCache (in category 'private') -----
- clearColormapCache
- 
- 	cachedDepth := nil.
- 	cachedColormap := nil.
- !

Item was removed:
- ----- Method: ColorForm>>collectColors: (in category 'converting') -----
- collectColors: aBlock
- 
- 	^ (ColorForm extent: self extent depth: self depth bits: self bits)
- 		colors: (self colors collect: aBlock);
- 		yourself!

Item was removed:
- ----- Method: ColorForm>>colorAt: (in category 'pixel accessing') -----
- colorAt: aPoint
- 	"Return the color of the pixel at aPoint."
- 
- 	^ self colors at: (self pixelValueAt: aPoint) + 1
- !

Item was removed:
- ----- Method: ColorForm>>colorAt:put: (in category 'pixel accessing') -----
- colorAt: aPoint put: aColor
- 	"Store the given color into the pixel at aPoint. The given color must match one of the colors in the receiver's colormap."
- 
- 	| i |
- 	i := self colors indexOf: aColor
- 		ifAbsent: [^ self error: 'trying to use a color that is not in my colormap'].
- 	self pixelValueAt: aPoint put: i - 1.
- !

Item was removed:
- ----- Method: ColorForm>>colormapIfNeededFor: (in category 'color mapping') -----
- colormapIfNeededFor: destForm
- 	| newMap color pv |
- 	(self hasNonStandardPalette or:[destForm hasNonStandardPalette]) ifFalse:[
- 		^self colormapIfNeededForDepth: destForm depth.
- 	].
- 	colors == nil ifTrue: [
- 		"use the standard colormap"
- 		^ super colormapIfNeededFor: destForm].
- 
- 	(destForm depth = cachedDepth and:[cachedColormap isColormap]) 
- 		ifTrue: [^ cachedColormap].
- 	newMap := WordArray new: (1 bitShift: self depth).
- 	1 to: colors size do: [:i |
- 		color := colors at: i.
- 		pv := destForm pixelValueFor: color.
- 		(pv = 0 and:[color isTransparent not]) ifTrue:[pv := 1].
- 		newMap at: i put: pv].
- 
- 	cachedDepth := destForm depth.
- 	^cachedColormap := ColorMap shifts: nil masks: nil colors: newMap.!

Item was removed:
- ----- Method: ColorForm>>colormapIfNeededForDepth: (in category 'color manipulation') -----
- colormapIfNeededForDepth: destDepth
- 	"Return a colormap for displaying the receiver at the given depth, or nil if no colormap is needed."
- 
- 	| newMap |
- 	colors == nil ifTrue: [
- 		"use the standard colormap"
- 		^ Color colorMapIfNeededFrom: self depth to: destDepth].
- 
- 	(destDepth = cachedDepth and:[cachedColormap isColormap not]) 
- 		ifTrue: [^ cachedColormap].
- 	newMap := Bitmap new: colors size.
- 	1 to: colors size do: [:i |
- 		newMap
- 			at: i
- 			put: ((colors at: i) pixelValueForDepth: destDepth)].
- 
- 	cachedDepth := destDepth.
- 	^ cachedColormap := newMap.
- !

Item was removed:
- ----- Method: ColorForm>>colors (in category 'accessing') -----
- colors
- 	"Return my color palette."
- 
- 	self ensureColorArrayExists.
- 	^ colors
- !

Item was removed:
- ----- Method: ColorForm>>colors: (in category 'accessing') -----
- colors: colorList
- 	"Set my color palette to the given collection."
- 
- 	| colorArray colorCount newColors |
- 	colorList ifNil: [
- 		colors := cachedDepth := cachedColormap := nil.
- 		^ self].
- 
- 	colorArray := colorList asArray.
- 	colorCount := colorArray size.
- 	newColors := Array new: (1 bitShift: self depth).
- 	1 to: newColors size do: [:i |
- 		i <= colorCount
- 			ifTrue: [newColors at: i put: (colorArray at: i)]
- 			ifFalse: [newColors at: i put: Color transparent]].
- 
- 	colors := newColors.
- 	cachedDepth := nil.
- 	cachedColormap := nil.
- !

Item was removed:
- ----- Method: ColorForm>>colorsFromArray: (in category 'accessing') -----
- colorsFromArray: colorArray
- 	| colorList |
- 	colorList := colorArray collect: [:colorDef |
- 		Color fromArray: colorDef].
- 	self colors: colorList!

Item was removed:
- ----- Method: ColorForm>>colorsUsed (in category 'color manipulation') -----
- colorsUsed
- 	"Return a list of the colors actually used by this ColorForm."
- 
- 	| myColor list |
- 	myColor := self colors.
- 	list := OrderedCollection new.
- 	self tallyPixelValues withIndexDo: [:count :i |
- 		count > 0 ifTrue: [list add: (myColor at: i)]].
- 	^ list asArray
- !

Item was removed:
- ----- Method: ColorForm>>copy: (in category 'copying') -----
- copy: aRect
-  	"Return a new ColorForm containing the portion of the receiver delineated by aRect."
- 
- 	| newForm |
- 	newForm := self species extent: aRect extent depth: depth.
- 	((BitBlt
- 		destForm: newForm
- 		sourceForm: self
- 		fillColor: nil
- 		combinationRule: Form over
- 		destOrigin: 0 at 0
- 		sourceOrigin: aRect origin
- 		extent: aRect extent
- 		clipRect: newForm boundingBox)
- 		colorMap: nil) copyBits.
- 	colors ifNotNil: [newForm colors: colors copy].
- 	^ newForm
- !

Item was removed:
- ----- Method: ColorForm>>decodeArray (in category 'postscript generation') -----
- decodeArray
- 	^self depth = 1 ifTrue:['[1 0]'] ifFalse:['[0 255]'].!

Item was removed:
- ----- Method: ColorForm>>depth: (in category 'private') -----
- depth: bitsPerPixel
- 
- 	bitsPerPixel > 8 ifTrue: [self error: 'ColorForms only support depths up to 8 bits'].
- 	super depth: bitsPerPixel.
- !

Item was removed:
- ----- Method: ColorForm>>displayOn:at:clippingBox:rule:fillColor: (in category 'displaying') -----
- displayOn: aDisplayMedium at: aDisplayPoint clippingBox: clipRectangle rule: rule fillColor: aForm
- 
- 	aDisplayMedium copyBits: self boundingBox
- 		from: self
- 		at: aDisplayPoint + self offset
- 		clippingBox: clipRectangle
- 		rule: rule
- 		fillColor: aForm
- 		map: (self colormapIfNeededFor: aDisplayMedium).
- !

Item was removed:
- ----- Method: ColorForm>>displayOnPort:at: (in category 'displaying') -----
- displayOnPort: port at: location
- 
- 	port copyForm: self to: location rule: Form paint!

Item was removed:
- ----- Method: ColorForm>>dominantColor (in category 'analyzing') -----
- dominantColor
- 	"Overridden to consider color table"
- 	
- 	| tally max maxi |
- 	tally := self tallyPixelValues.
- 	max := maxi := 0.
- 	tally withIndexDo: [:n :i | n > max ifTrue: [max := n. maxi := i]].
- 	^ self colors at: maxi!

Item was removed:
- ----- Method: ColorForm>>ensureColorArrayExists (in category 'private') -----
- ensureColorArrayExists
- 	"Return my color palette."
- 
- 	colors ifNil: [
- 		self depth > 8 ifTrue: [^ self error: 'ColorForms only support depths up to 8 bits'].
- 		self colors: (Color indexedColors copyFrom: 1 to: (1 bitShift: self depth))].
- !

Item was removed:
- ----- Method: ColorForm>>ensureTransparentColor (in category 'color manipulation') -----
- ensureTransparentColor
- 	"Ensure that the receiver (a) includes Color transparent in its color map and (b) that the entry for Color transparent is the first entry in its color map."
- 
- 	| i |
- self error: 'not yet implemented'.
- 	(colors includes: Color transparent)
- 		ifTrue: [
- 			(colors indexOf: Color transparent) = 1 ifTrue: [^ self].
- 			"shift the entry for color transparent"]
- 		ifFalse: [
- 			i := self unusedColormapEntry.
- 			i = 0 ifTrue: [self error: 'no color map entry is available'].
- 			colors at: i put: Color transparent.
- 			"shift the entry for color transparent"].
- !

Item was removed:
- ----- Method: ColorForm>>flipBy:centerAt: (in category 'scaling, rotation') -----
- flipBy: direction centerAt: aPoint
- 	| oldColors newForm |
- 	oldColors := colors.
- 	self colors: nil.
- 	newForm := super flipBy: direction centerAt: aPoint.
- 	self colors: oldColors.
- 	newForm colors: oldColors.
- 	^newForm !

Item was removed:
- ----- Method: ColorForm>>getTransparencyUnificationLUT (in category 'postscript generation') -----
- getTransparencyUnificationLUT
- 	| lut transparentIndex |
- 	lut := Array new:colors size.
- 	transparentIndex := self indexOfColor:Color transparent.
- 	1 to: colors size do:
- 		[ :i | lut at:i put:(((colors at:i) = Color transparent) ifTrue:[transparentIndex] ifFalse:[i])].
-  !

Item was removed:
- ----- Method: ColorForm>>hibernate (in category 'fileIn/Out') -----
- hibernate
- 	"Make myself take up less space. See comment in Form>hibernate."
- 
- 	super hibernate.
- 	self clearColormapCache.
- 	colors ifNotNil:[colors := colors asColorArray].!

Item was removed:
- ----- Method: ColorForm>>indexOfColor: (in category 'color manipulation') -----
- indexOfColor: aColor
- 	"Return the index of aColor in my color array"
- 
- 	self ensureColorArrayExists.
- 	^ colors indexOf: aColor!

Item was removed:
- ----- Method: ColorForm>>isColorForm (in category 'testing') -----
- isColorForm
- 	^true!

Item was removed:
- ----- Method: ColorForm>>isGrayScale (in category 'testing') -----
- isGrayScale
- 	^ self colors = ColorForm grayScalePalette.!

Item was removed:
- ----- Method: ColorForm>>isTranslucent (in category 'testing') -----
- isTranslucent
- 	"Answer whether this form may be translucent"
- 	^true!

Item was removed:
- ----- Method: ColorForm>>isTransparentAt: (in category 'pixel accessing') -----
- isTransparentAt: aPoint 
- 	"Return true if the receiver is transparent at the given point."
- 
- 	^ (self colorAt: aPoint) isTransparent
- !

Item was removed:
- ----- Method: ColorForm>>mapColor:to: (in category 'color manipulation') -----
- mapColor: oldColor to: newColor
- 	"Replace all occurances of the given color with the given new color in my color map."
- 
- 	self ensureColorArrayExists.
- 	1 to: colors size do: [:i | 
- 		(colors at: i) = oldColor ifTrue: [colors at: i put: newColor]].
- 	self clearColormapCache.
- !

Item was removed:
- ----- Method: ColorForm>>mapTransparencies: (in category 'postscript generation') -----
- mapTransparencies:transparentIndexes
- 	^self deepCopy mapColors:transparentIndexes to:(transparentIndexes at:1).!

Item was removed:
- ----- Method: ColorForm>>maskingMap (in category 'displaying') -----
- maskingMap
- 	"Return a color map that maps all colors except transparent to words of all ones. Used to create a mask for a Form whose transparent pixel value is zero."
- 	| maskingMap |
- 	maskingMap := Bitmap new: (1 bitShift: depth) withAll: 16rFFFFFFFF.
- 	1 to: colors size do:[:i|
- 		(colors at: i) isTransparent ifTrue:[maskingMap at: i put: 0].
- 	].
- 	colors size+1 to: maskingMap size do:[:i| maskingMap at: i put: 0].
- 	^maskingMap!

Item was removed:
- ----- Method: ColorForm>>postCopy (in category 'copying') -----
- postCopy
- 	super postCopy.
- 	colors := colors copy.
- !

Item was removed:
- ----- Method: ColorForm>>readAttributesFrom: (in category 'fileIn/Out') -----
- readAttributesFrom: aBinaryStream
- 	super readAttributesFrom: aBinaryStream.
- 	colors := ColorArray new: (2 raisedTo: depth).
- 	1 to: colors size do: [:idx | 
- 		colors basicAt: idx put: (aBinaryStream nextLittleEndianNumber: 4).
- 	]. 
- 	!

Item was removed:
- ----- Method: ColorForm>>replaceColor:with: (in category 'color manipulation') -----
- replaceColor: oldColor with: newColor
- 	"Replace all occurances of the given color with the given new color in my color map."
- 
- 	self ensureColorArrayExists.
- 	1 to: colors size do: [:i | 
- 		(colors at: i) = oldColor ifTrue: [colors at: i put: newColor]].
- 	self clearColormapCache.
- !

Item was removed:
- ----- Method: ColorForm>>replaceColorAt:with: (in category 'color manipulation') -----
- replaceColorAt: aPoint with: newColor
- 	"Replace a color map entry with newColor.  The entry replaced is the one used by aPoint.  If there are are two entries in the colorMap for the oldColor, just replace ONE!!!!  There are often two whites or two blacks, and this is what you want, when replacing one."
- 
- 	| oldIndex |
- 	self ensureColorArrayExists.
- 	oldIndex := self pixelValueAt: aPoint.
- 	colors at: oldIndex+1 put: newColor.
- 	self clearColormapCache.
- !

Item was removed:
- ----- Method: ColorForm>>replaceColorAtIndex:with: (in category 'color manipulation') -----
- replaceColorAtIndex: index with: newColor
- 	"Replace a color map entry with newColor."
- 
- 	self ensureColorArrayExists.
- 	colors at: index put: newColor.
- 	cachedColormap == nil ifFalse:
- 		[cachedColormap at: index put: (newColor pixelValueForDepth: cachedDepth)]!

Item was removed:
- ----- Method: ColorForm>>scaledIntoFormOfSize:smoothing: (in category 'scaling, rotation') -----
- scaledIntoFormOfSize: aNumberOrPoint smoothing: factor
- 
- 	^ (self asFormOfDepth: 32) scaledIntoFormOfSize: aNumberOrPoint smoothing: factor!

Item was removed:
- ----- Method: ColorForm>>scaledToSize:smoothing: (in category 'scaling, rotation') -----
- scaledToSize: newExtent smoothing: factor
- 	"super method did not seem to work so well on ColorForms"
- 
- 	^(self asFormOfDepth: 32) scaledToSize: newExtent smoothing: factor!

Item was removed:
- ----- Method: ColorForm>>setColors:cachedColormap:depth: (in category 'private') -----
- setColors: colorArray cachedColormap: aBitmap depth: anInteger
- 	"Semi-private. Set the color array, cached colormap, and cached colormap depth to avoid having to recompute the colormap when switching color palettes in animations."
- 
- 	colors := colorArray.
- 	cachedDepth := anInteger.
- 	cachedColormap := aBitmap.
- !

Item was removed:
- ----- Method: ColorForm>>setColorspaceOn: (in category 'postscript generation') -----
- setColorspaceOn:aStream
- 	self depth = 1 ifTrue:[
- 		aStream print:'/DeviceRGB setcolorspace 0 setgray'; cr.
- 	]
- 	ifFalse:[
- 	aStream print:'[ /Indexed /DeviceRGB ';
- 	write:self colors size-1;
- 	print:' <'.
- 	(self colormapIfNeededForDepth: 32 ) storeBits:20 to:0 on:aStream.
- 	aStream print:'> ] setcolorspace'; cr.].
- !

Item was removed:
- ----- Method: ColorForm>>setExtent:depth: (in category 'private') -----
- setExtent: extent depth: bitsPerPixel
- 	"Create a virtual bit map with the given extent and bitsPerPixel."
- 
- 	bitsPerPixel > 8 ifTrue: [self error: 'ColorForms only support depths up to 8 bits'].
- 	super setExtent: extent depth: bitsPerPixel.
- !

Item was removed:
- ----- Method: ColorForm>>storeOn: (in category 'fileIn/Out') -----
- storeOn: aStream
- 	aStream nextPut: $(.
- 	super storeOn: aStream.
- 	aStream
- 		cr; tab;
- 		nextPutAll: 'colorsFromArray: #('.
- 	self colors do: [:color |
- 		color storeArrayOn: aStream].
- 	aStream nextPutAll: ' ))'.!

Item was removed:
- ----- Method: ColorForm>>transparentAllPixelsLike: (in category 'color manipulation') -----
- transparentAllPixelsLike: aPoint
- 	"Make all occurances of the given pixel value transparent.  Very useful when two entries in the colorMap have the same value.  This only changes ONE."
- 
- 	self replaceColorAt: aPoint with: Color transparent.
- !

Item was removed:
- ----- Method: ColorForm>>transparentColor: (in category 'color manipulation') -----
- transparentColor: aColor
- 	"Make all occurances of the given color transparent.  Note: for colors like black and white, which have two entries in the colorMap, this changes BOTH of them.  Not always what you want."
- 
- 	self replaceColor: aColor with: Color transparent.
- !

Item was removed:
- ----- Method: ColorForm>>transparentColorIndexes (in category 'postscript generation') -----
- transparentColorIndexes
- 	^(1 to: colors size) select: [ :index | (colors at:index) isTransparent ].
- !

Item was removed:
- ----- Method: ColorForm>>twoToneFromDisplay:backgroundColor: (in category 'color manipulation') -----
- twoToneFromDisplay: aRectangle backgroundColor: bgColor
- 	"Copy one-bit deep ColorForm from the Display using a color map that maps all colors except the background color to black. Used for caching the contents of inactive MVC windows."
- 
- 	| map |
- 	(width = aRectangle width and: [height = aRectangle height])
- 		ifFalse: [self setExtent: aRectangle extent depth: depth].
- 
- 	"make a color map mapping the background color
- 	 to zero and all other colors to one"
- 	map := Bitmap new: (1 bitShift: (Display depth min: 9)).
- 	1 to: map size do: [:i | map at: i put: 16rFFFFFFFF].
- 	map at: (bgColor indexInMap: map) put: 0.
- 
- 	(BitBlt toForm: self)
- 		destOrigin: 0 at 0;
- 		sourceForm: Display;
- 		sourceRect: aRectangle;
- 		combinationRule: Form over;
- 		colorMap: map;
- 		copyBits.
- !

Item was removed:
- ----- Method: ColorForm>>unhibernate (in category 'fileIn/Out') -----
- unhibernate
- 	colors ifNotNil:[colors := colors asArray].
- 	^super unhibernate.
- !

Item was removed:
- ----- Method: ColorForm>>unusedColormapEntry (in category 'private') -----
- unusedColormapEntry
- 	"Return the index of an unused color map entry, or zero if there isn't one."
- 
- 	| tallies |
- 	tallies := self tallyPixelValues.
- 	1 to: tallies size do: [:i |
- 		(tallies at: i) = 0 ifTrue: [^ i]].
- 	^ 0
- !

Item was removed:
- ----- Method: ColorForm>>writeAttributesOn: (in category 'fileIn/Out') -----
- writeAttributesOn: file
- 	| colorArray |
- 	super writeAttributesOn: file.
- 	colorArray := self colors asColorArray.
- 	1 to: (2 raisedTo: depth) do: [:idx |
- 		file nextLittleEndianNumber: 4 put: (colorArray basicAt: idx).
- 	] !

Item was removed:
- Object subclass: #ColorMap
- 	instanceVariableNames: 'shifts masks colors'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Primitives'!

Item was removed:
- ----- Method: ColorMap class>>colors: (in category 'instance creation') -----
- colors: colorArray
- 	^self new setShifts: nil masks: nil colors: colorArray!

Item was removed:
- ----- Method: ColorMap class>>mapBitsFrom:to: (in category 'instance creation') -----
- mapBitsFrom: srcBitMask to: dstBitMask
- 	"Return an array consisting of the shift and the mask for
- 	mapping component values out of srcBitMask and into dstBitMask.
- 	While this computation is somewhat complicated it eases the batch
- 	conversion of all the pixels in BitBlt."
- 	| srcBits dstBits srcLow srcHigh dstLow dstHigh bits mask shift |
- 	(srcBitMask = 0 or:[dstBitMask = 0]) ifTrue:[^#(0 0)]. "Zero mask and shift"
- 	"Compute low and high bit position for source and dest bit mask"
- 	srcLow := srcBitMask lowBit - 1.	srcHigh := srcBitMask highBit.
- 	dstLow := dstBitMask lowBit - 1.	dstHigh := dstBitMask highBit.
- 	"Compute the number of bits in source and dest bit mask"
- 	srcBits := srcHigh - srcLow.		dstBits := dstHigh - dstLow.
- 	"Compute the maximum number of bits we can transfer inbetween"
- 	bits := srcBits min: dstBits.
- 	"Compute the (unshifted) transfer mask"
- 	mask := (1 bitShift: bits) - 1.
- 	"Shift the transfer mask to the mask the highest n bits of srcBitMask"
- 	mask := mask bitShift: (srcHigh - bits).
- 	"Compute the delta shift so that the most significant bit of the
- 	source bit mask falls on the most significant bit of the dest bit mask.
- 	Note that delta is used for #bitShift: so
- 		shift > 0 : shift right
- 		shift < 0 : shift left
- 	e.g., if dstHigh > srcHigh we need to shift left and if dstHigh < srcHigh
- 	we need to shift right. This leads to:"
- 	shift := dstHigh - srcHigh.
- 	"And that's all we need"
- 	^Array with: shift with: mask!

Item was removed:
- ----- Method: ColorMap class>>mappingFrom:to: (in category 'instance creation') -----
- mappingFrom: srcBitMasks to: dstBitMasks
- 	"Return a color map mapping from the array of source bit masks
- 	to the array of dest bit masks."
- 	| shifts masks shiftAndMask |
- 	shifts := IntegerArray new: 4.
- 	masks := WordArray new: 4.
- 	1 to: 4 do:[:i|
- 		shiftAndMask := self mapBitsFrom: (srcBitMasks at: i) to: (dstBitMasks at: i).
- 		shifts at: i put: (shiftAndMask at: 1).
- 		masks at: i put: (shiftAndMask at: 2).
- 	].
- 	^self shifts: shifts masks: masks!

Item was removed:
- ----- Method: ColorMap class>>mappingFromARGB: (in category 'instance creation') -----
- mappingFromARGB: dstBitMasks
- 	"Return a ColorMap mapping from canonical ARGB space into dstBitMasks"
- 	^self mappingFrom: #(16rFF0000 16rFF00 16rFF 16rFF000000) to: dstBitMasks!

Item was removed:
- ----- Method: ColorMap class>>mappingToARGB: (in category 'instance creation') -----
- mappingToARGB: srcBitMasks
- 	"Return a ColorMap mapping from srcBitMasks into canonical ARGB space"
- 	^self mappingFrom: srcBitMasks to: #(16rFF0000 16rFF00 16rFF 16rFF000000)!

Item was removed:
- ----- Method: ColorMap class>>masks:shifts: (in category 'instance creation') -----
- masks: maskArray shifts: shiftArray
- 	^self shifts: shiftArray masks: maskArray colors: nil.!

Item was removed:
- ----- Method: ColorMap class>>shifts:masks: (in category 'instance creation') -----
- shifts: shiftArray masks: maskArray
- 	^self shifts: shiftArray masks: maskArray colors: nil.!

Item was removed:
- ----- Method: ColorMap class>>shifts:masks:colors: (in category 'instance creation') -----
- shifts: shiftArray masks: maskArray colors: colorArray
- 	^self new setShifts: shiftArray masks: maskArray colors: colorArray!

Item was removed:
- ----- Method: ColorMap>>= (in category 'comparing') -----
- = aColorMap
- 	"Return true if the receiver is equal to aColorMap"
- 	self species == aColorMap species ifFalse:[^false].
- 	self isIndexed == aColorMap isIndexed ifFalse:[^false].
- 	^self colors = aColorMap colors and:[
- 		self shifts = aColorMap shifts and:[
- 			self masks = aColorMap masks]]!

Item was removed:
- ----- Method: ColorMap>>alphaMask (in category 'accessing') -----
- alphaMask
- 	^masks at: 4!

Item was removed:
- ----- Method: ColorMap>>alphaMask: (in category 'accessing') -----
- alphaMask: value
- 	masks at: 4 put: value!

Item was removed:
- ----- Method: ColorMap>>alphaShift (in category 'accessing') -----
- alphaShift
- 	^shifts at: 4!

Item was removed:
- ----- Method: ColorMap>>alphaShift: (in category 'accessing') -----
- alphaShift: value
- 	shifts at: 4 put: value!

Item was removed:
- ----- Method: ColorMap>>at: (in category 'accessing') -----
- at: index
- 	^colors at: index!

Item was removed:
- ----- Method: ColorMap>>at:put: (in category 'accessing') -----
- at: index put: value
- 	^colors at: index put: value!

Item was removed:
- ----- Method: ColorMap>>blueMask (in category 'accessing') -----
- blueMask
- 	^masks at: 3!

Item was removed:
- ----- Method: ColorMap>>blueMask: (in category 'accessing') -----
- blueMask: value
- 	masks at: 3 put: value!

Item was removed:
- ----- Method: ColorMap>>blueShift (in category 'accessing') -----
- blueShift
- 	^shifts at: 3!

Item was removed:
- ----- Method: ColorMap>>blueShift: (in category 'accessing') -----
- blueShift: value
- 	shifts at: 3 put: value!

Item was removed:
- ----- Method: ColorMap>>colors (in category 'accessing') -----
- colors
- 	^colors!

Item was removed:
- ----- Method: ColorMap>>greenMask (in category 'accessing') -----
- greenMask
- 	^masks at: 2!

Item was removed:
- ----- Method: ColorMap>>greenMask: (in category 'accessing') -----
- greenMask: value
- 	masks at: 2 put: value!

Item was removed:
- ----- Method: ColorMap>>greenShift (in category 'accessing') -----
- greenShift
- 	^shifts at: 2!

Item was removed:
- ----- Method: ColorMap>>greenShift: (in category 'accessing') -----
- greenShift: value
- 	shifts at: 2 put: value.!

Item was removed:
- ----- Method: ColorMap>>hash (in category 'comparing') -----
- hash
- 	"Hash is re-implemented because #= is re-implemented"
- 	^colors hash bitXor: (shifts hash bitXor: masks hash)!

Item was removed:
- ----- Method: ColorMap>>inverseMap (in category 'accessing') -----
- inverseMap
- 	"Return the inverse map of the receiver"
- 	| newMasks newShifts |
- 	colors ifNotNil:[^self error:'Not yet implemented'].
- 	newMasks := WriteStream on: (Array new: 4).
- 	newShifts := WriteStream on: (Array new: 4).
- 	masks with: shifts do:[:mask :shift|
- 		newMasks nextPut: (mask bitShift: shift).
- 		newShifts nextPut: shift negated].
- 	^ColorMap
- 		shifts: newShifts contents
- 		masks: newMasks contents!

Item was removed:
- ----- Method: ColorMap>>isColormap (in category 'testing') -----
- isColormap
- 	^true!

Item was removed:
- ----- Method: ColorMap>>isFixed (in category 'testing') -----
- isFixed
- 	"Return true if the receiver does not use a lookup mechanism for pixel mapping"
- 	^self isIndexed not!

Item was removed:
- ----- Method: ColorMap>>isIndexed (in category 'testing') -----
- isIndexed
- 	"Return true if the receiver uses a lookup mechanism for pixel mapping"
- 	^colors notNil!

Item was removed:
- ----- Method: ColorMap>>mapPixel: (in category 'pixel mapping') -----
- mapPixel: pixelValue
- 	"Perform a forward pixel mapping operation"
- 	| pv |
- 	(shifts == nil and:[masks == nil]) ifFalse:[
- 		pv := (((pixelValue bitAnd: self redMask) bitShift: self redShift) bitOr:
- 			((pixelValue bitAnd: self greenMask) bitShift: self greenShift)) bitOr:
- 			(((pixelValue bitAnd: self blueMask) bitShift: self blueShift) bitOr:
- 			((pixelValue bitAnd: self alphaMask) bitShift: self alphaShift)).
- 	] ifTrue:[pv := pixelValue].
- 	colors ifNotNil:[pv := colors at: pv].
- 	"Need to check for translucency else Form>>paint goes gaga"
- 	pv = 0 ifTrue:[pixelValue = 0 ifFalse:[pv := 1]].
- 	^pv!

Item was removed:
- ----- Method: ColorMap>>mappingTo: (in category 'pixel mapping') -----
- mappingTo: aColorMap
- 	"Compute a new color map through the receiver and aColorMap.
- 	Both maps are assumed to be mappings into canonical ARGB space"
- 	| fixedMap |
- 	self = aColorMap ifTrue:[^nil]. "No mapping needed"
- 	aColorMap isIndexed ifTrue:[^nil]. "We can't compute mappings to an indexed map yet"
- 	fixedMap := self species mappingFrom: self rgbaBitMasks to: aColorMap rgbaBitMasks.
- 	self isIndexed ifFalse:[^fixedMap].
- 	"If the receiver is indexed then we need to map the colors as well"
- 	self flag: #untested.
- 	^ColorMap
- 		shifts: fixedMap shifts
- 		masks: fixedMap masks
- 		colors: (colors collect:[:pv| aColorMap pixelMap: pv]).
- !

Item was removed:
- ----- Method: ColorMap>>masks (in category 'accessing') -----
- masks
- 	^masks!

Item was removed:
- ----- Method: ColorMap>>pixelMap: (in category 'pixel mapping') -----
- pixelMap: pixelValue
- 	"Perform a reverse pixel mapping operation"
- 	| pv |
- 	colors == nil
- 		ifTrue:[pv := pixelValue]
- 		ifFalse:[pv := colors at: pixelValue].
- 	(shifts == nil and:[masks == nil]) 
- 		ifFalse:[pv := (((pv bitAnd: self redMask) bitShift: self redShift) bitOr: 
- 				((pv bitAnd: self greenMask) bitShift: self greenShift)) bitOr:
- 					(((pv bitAnd: self blueMask) bitShift: self blueShift) bitOr: 
- 						((pv bitAnd: self alphaMask) bitShift: self alphaShift))].
- 	"Need to check for translucency else Form>>paint goes gaga"
- 	pv = 0 ifTrue:[pixelValue = 0 ifFalse:[pv := 1]].
- 	^pv!

Item was removed:
- ----- Method: ColorMap>>redMask (in category 'accessing') -----
- redMask
- 	^masks at: 1!

Item was removed:
- ----- Method: ColorMap>>redMask: (in category 'accessing') -----
- redMask: value
- 	masks at: 1 put: value!

Item was removed:
- ----- Method: ColorMap>>redShift (in category 'accessing') -----
- redShift
- 	^shifts at: 1!

Item was removed:
- ----- Method: ColorMap>>redShift: (in category 'accessing') -----
- redShift: value
- 	shifts at: 1 put: value!

Item was removed:
- ----- Method: ColorMap>>rgbaBitMasks (in category 'accessing') -----
- rgbaBitMasks
- 	"Return the rgba bit masks for the receiver"
- 	^masks asArray with: shifts collect:[:m :s| m bitShift: s]!

Item was removed:
- ----- Method: ColorMap>>setShifts:masks:colors: (in category 'private') -----
- setShifts: shiftArray masks: maskArray colors: colorArray
- 	shiftArray ifNotNil:[shifts := shiftArray asIntegerArray].
- 	maskArray ifNotNil:[masks := maskArray asWordArray].
- 	colorArray ifNotNil:[colors := colorArray asWordArray].!

Item was removed:
- ----- Method: ColorMap>>shifts (in category 'accessing') -----
- shifts
- 	^shifts!

Item was removed:
- DisplayTransform subclass: #CompositeTransform
- 	instanceVariableNames: 'globalTransform localTransform'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Transformations'!
- 
- !CompositeTransform commentStamp: '<historical>' prior: 0!
- A composite transform provides the effect of several levels of coordinate transformations.!

Item was removed:
- ----- Method: CompositeTransform class>>globalTransform:localTransform: (in category 'instance creation') -----
- globalTransform: gt localTransform: lt
- 	^self new globalTransform: gt localTransform: lt!

Item was removed:
- ----- Method: CompositeTransform>>angle (in category 'accessing') -----
- angle
- 	^ localTransform angle + globalTransform angle!

Item was removed:
- ----- Method: CompositeTransform>>asCompositeTransform (in category 'converting') -----
- asCompositeTransform
- 	^self!

Item was removed:
- ----- Method: CompositeTransform>>asMatrixTransform2x3 (in category 'converting') -----
- asMatrixTransform2x3
- 	^globalTransform asMatrixTransform2x3
- 		composedWithLocal: localTransform asMatrixTransform2x3!

Item was removed:
- ----- Method: CompositeTransform>>asMorphicTransform (in category 'converting') -----
- asMorphicTransform
- 	"Squash a composite transform down to a simple one"
- 	^ MorphicTransform
- 		offset: (self localPointToGlobal: 0 at 0) negated
- 		angle: self angle
- 		scale: self scale!

Item was removed:
- ----- Method: CompositeTransform>>composedWith: (in category 'initialization') -----
- composedWith: aTransform
- 	"Return a new transform that has the effect of transforming points first by the receiver and then by the argument."
- 
- 	self isIdentity ifTrue: [^ aTransform].
- 	aTransform isIdentity ifTrue: [^ self].
- 	^ CompositeTransform new globalTransform: self
- 							localTransform: aTransform!

Item was removed:
- ----- Method: CompositeTransform>>globalPointToLocal: (in category 'transforming points') -----
- globalPointToLocal: aPoint
- 	"Transform aPoint from global coordinates into local coordinates"
- 	^localTransform globalPointToLocal:
- 		(globalTransform globalPointToLocal: aPoint)!

Item was removed:
- ----- Method: CompositeTransform>>globalTransform:localTransform: (in category 'initialization') -----
- globalTransform: gt localTransform: lt
- 	globalTransform := gt.
- 	localTransform := lt!

Item was removed:
- ----- Method: CompositeTransform>>inverseTransformation (in category 'accessing') -----
- inverseTransformation
- 	"Return the inverse transformation of the receiver"
- 	^self species new
- 		globalTransform: localTransform inverseTransformation
- 		localTransform: globalTransform inverseTransformation!

Item was removed:
- ----- Method: CompositeTransform>>invert: (in category 'transformations') -----
- invert: aPoint
- 	^ globalTransform invert: (localTransform invert: aPoint)!

Item was removed:
- ----- Method: CompositeTransform>>isCompositeTransform (in category 'testing') -----
- isCompositeTransform
- 	^true!

Item was removed:
- ----- Method: CompositeTransform>>isIdentity (in category 'testing') -----
- isIdentity
- 	^ globalTransform isIdentity and: [localTransform isIdentity]!

Item was removed:
- ----- Method: CompositeTransform>>isPureTranslation (in category 'testing') -----
- isPureTranslation
- 	^ globalTransform isPureTranslation and: [localTransform isPureTranslation]!

Item was removed:
- ----- Method: CompositeTransform>>localPointToGlobal: (in category 'transforming points') -----
- localPointToGlobal: aPoint
- 	"Transform aPoint from global coordinates into local coordinates"
- 	^globalTransform localPointToGlobal:
- 		(localTransform localPointToGlobal: aPoint)!

Item was removed:
- ----- Method: CompositeTransform>>scale (in category 'accessing') -----
- scale
- 	^ localTransform scale * globalTransform scale!

Item was removed:
- ----- Method: CompositeTransform>>transform: (in category 'transformations') -----
- transform: aPoint
- 	^ localTransform transform: (globalTransform transform: aPoint)!

Item was removed:
- CharacterScanner subclass: #CompositionScanner
- 	instanceVariableNames: 'spaceX spaceIndex lineHeight baseline lineGap lineGapSlice topMargin bottomMargin lineHeightAtSpace baselineAtSpace lastBreakIsNotASpace nextIndexAfterLineBreak'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Text'!
- 
- !CompositionScanner commentStamp: 'nice 10/6/2013 23:24' prior: 0!
- A CompositionScanner measures text and determines where line breaks.
- Given a rectangular zone on input, it is used to split text in horizontal lines, and produce information about those lines on output (at which index a line starts/stops, which vertical space does the line require, which horizontal space if left for adjusting inter-word spacing, etc...)
- 
- Instance Variables
- 	baseline:		<Number>
- 	baselineAtSpace:		<Number>
- 	lastBreakIsNotASpace:		<Boolean>
- 	lineHeight:		<Number>
- 	lineHeightAtSpace:		<Number>
- 	nextIndexAfterLineBreak:		<Integer>
- 	spaceIndex:		<Integer>
- 	spaceX:		<Number>
- 
- baseline
- 	- the distance between top of line and the base line (that is the bottom of latin characters abcdehiklmnorstuvwx in most fonts)
- 
- baselineAtSpace
- 	- memorize the baseline at last encountered space or other breakable character.
- 	This is necessary because the CompositionScanner wants to break line at a breakable character.
- 	If a word layout overflows the right margin, the scanner has to roll back and restore the line state to last encountered breakable character.
- 
- lastBreakIsNotASpace
- 	- indicates that the last breakable character was not a space.
- 	This is necessary because handling a line break at a space differs from non space.
- 	If line break occurs on space, the space won't be displayed in next line.
- 	If it's another breakable character, it has to be displayed on next line.
- 
- lineHeight
- 	- the total line height from top to bottom, including inter-line spacing.
- 
- lineHeightAtSpace
- 	- the line height at last encountered space or other breakable character.
- 	See baselineAtSpace for explanation.
- 
- nextIndexAfterLineBreak
- 	- the index of character after the last line break that was encountered.
- 
- spaceIndex
- 	- the index of last space or other breakable character that was encountered
- 
- spaceX
- 	- the distance from left of composition zone to left of last encountered space or other breakable character 
- 	See baselineAtSpace for explanation.
- 
- Note: if a line breaks on a space, a linefeed or a carriage return, then the space, linefeed or carriage return is integrated in the line.
- If there is a carriage return - linefeed pair, the pair is integrated to the line as if it were a single line break for compatibility with legacy software.!

Item was removed:
- ----- Method: CompositionScanner>>alignmentMorphOffsetFor:of: (in category 'private') -----
- alignmentMorphOffsetFor: textAnchorProperties of: aMorphOrForm
- 
- 	^ textAnchorProperties verticalAlignmentMorph caseOf: {
- 				[#top] -> [textAnchorProperties padding top].
- 				[#center] -> [(aMorphOrForm height / 2) floor].
- 				[#baseline] -> [textAnchorProperties morphBaselineGetter
- 					ifNil: [0]
- 					ifNotNil: [:s | aMorphOrForm perform: s]].
- 				[#bottom] -> [aMorphOrForm height + textAnchorProperties padding bottom]}!

Item was removed:
- ----- Method: CompositionScanner>>atEnd (in category 'testing') -----
- atEnd
- 
- 	^ lastIndex = text size!

Item was removed:
- ----- Method: CompositionScanner>>baselineAdjustmentFor: (in category 'private') -----
- baselineAdjustmentFor: textAnchorProperties
- 
- 	^ textAnchorProperties verticalAlignmentLine caseOf: {
- 				[#top] -> [font ascent].
- 				[#center] -> [(font ascent / 2) floor].
- 				[#baseline] -> [0].
- 				[#bottom] -> [font descent negated]}.
- 			
- 	!

Item was removed:
- ----- Method: CompositionScanner>>canComputeDefaultLineHeight (in category 'testing') -----
- canComputeDefaultLineHeight
- 	^ rightMargin notNil!

Item was removed:
- ----- Method: CompositionScanner>>columnBreak (in category 'stop conditions') -----
- columnBreak
- 
- 	"Answer true. Set up values for the text line interval currently being 
- 	composed."
- 
- 	pendingKernX := 0.
- 	line stop: lastIndex.
- 	spaceX := destX.
- 	lastBreakIsNotASpace := false.
- 	line paddingWidth: rightMargin - spaceX.
- 	^true!

Item was removed:
- ----- Method: CompositionScanner>>composeFrom:inRectangle:firstLine:leftSide:rightSide: (in category 'scanning') -----
- composeFrom: startIndex inRectangle: lineRectangle
- 	firstLine: firstLine leftSide: leftSide rightSide: rightSide
- 	"Answer an instance of TextLineInterval that represents the next line in the paragraph."
- 	| runLength stopCondition lineSpacing |
- 	"Set up margins"
- 	leftMargin := lineRectangle left.
- 	leftSide ifTrue: [leftMargin := leftMargin +
- 						(firstLine ifTrue: [textStyle firstIndent]
- 								ifFalse: [textStyle restIndent])].
- 	destX := spaceX := leftMargin.
- 	rightMargin := lineRectangle right.
- 	rightSide ifTrue: [rightMargin := rightMargin - textStyle rightIndent].
- 	lastIndex := startIndex.	"scanning sets last index"
- 	destY := lineRectangle top.
- 	lineHeight := baseline := 0. "Will be increased by setFont"
- 	lineGap := lineGapSlice := -9999. "Will be increased by setFont; allow negative to show all effects of a custom #extraGap value. See TTFontDescription."
- 	topMargin := bottomMargin := 0.
- 	line := (TextLine start: lastIndex stop: 0 internalSpaces: 0 paddingWidth: 0)
- 				rectangle: lineRectangle.
- 	self setStopConditions.	"also sets font"
- 	runLength := text runLengthFor: startIndex.
- 	runStopIndex := (lastIndex := startIndex) + (runLength - 1).
- 	nextIndexAfterLineBreak := spaceCount := 0.
- 	lastBreakIsNotASpace := false.
- 	self handleIndentation.
- 	leftMargin := destX.
- 	line leftMargin: leftMargin.
- 
- 	[stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
- 		in: text string rightX: rightMargin.
- 	"See setStopConditions for stopping conditions for composing."
- 	self perform: stopCondition] whileFalse.
- 
- 	lineHeight := lineHeight + lineGap.
- 	baseline := baseline + lineGapSlice.
- 	
- 	(lineSpacing := textStyle lineSpacing) = 0.0 ifFalse: [
- 		"Modify lineHeight to realize lineSpacing instead of bottomMargin to avoid
- 		rendering glitches for lineSpacing values < 0.0."
- 		lineHeight := lineHeight + (lineSpacing * lineHeight) truncated.
- 		"ALT: bottomMargin := bottomMargin + (lineSpacing * lineHeight) truncated"].
- 
- 	line lineHeight: lineHeight baseline: baseline.
- 	"TODO: Allow special characters or text attributes to accumulate extra top or bottom margin."
- 	line topMargin: topMargin bottomMargin: bottomMargin.
- 	^ line!

Item was removed:
- ----- Method: CompositionScanner>>computeDefaultLineHeight (in category 'scanning') -----
- computeDefaultLineHeight
- 	"Compute the default line height for a potentially empty text"
- 	rightMargin notNil
- 		ifTrue: [lastIndex := 1.
- 			self setFont.
- 			^ lineHeight + lineGap]
- 		ifFalse: [^textStyle lineGrid]!

Item was removed:
- ----- Method: CompositionScanner>>cr (in category 'stop conditions') -----
- cr
- 	"Answer true. Set up values for the text line interval currently being 
- 	composed."
- 
- 	pendingKernX := 0.
- 	(lastIndex < text size and: [(text at: lastIndex) = CR and: [(text at: lastIndex+1) = Character lf]]) ifTrue: [lastIndex := lastIndex + 1].
- 	line stop: lastIndex.
- 	nextIndexAfterLineBreak := lastIndex + 1.
- 	spaceX := destX.
- 	lastBreakIsNotASpace := false.
- 	line paddingWidth: rightMargin - spaceX.
- 	^true!

Item was removed:
- ----- Method: CompositionScanner>>crossedX (in category 'stop conditions') -----
- crossedX
- 	"There is a word that has fallen across the right edge of the composition 
- 	rectangle. This signals the need for wrapping which is done to the last 
- 	space that was encountered, as recorded by the space stop condition,
- 	or any other breakable character if the language permits so."
- 
- 	pendingKernX := 0.
- 	
- 	lastBreakIsNotASpace ifTrue:
- 		["In some languages line break is possible before a non space."
- 		^self wrapAtLastBreakable].
- 	 
- 	spaceCount >= 1 ifTrue:
- 		["The common case. there is a space on the line."
- 		^self wrapAtLastSpace].
- 	
- 	"Neither internal nor trailing spaces -- almost never happens."
- 	self advanceIfFirstCharOfLine.
- 	^self wrapHere!

Item was removed:
- ----- Method: CompositionScanner>>doesTheLineBreakAfterLastChar (in category 'testing') -----
- doesTheLineBreakAfterLastChar
- 
- 	^nextIndexAfterLineBreak > text size!

Item was removed:
- ----- Method: CompositionScanner>>endOfRun (in category 'stop conditions') -----
- endOfRun
- 	"Answer true if scanning has reached the end of the paragraph. 
- 	Otherwise step conditions (mostly install potential new font) and answer 
- 	false."
- 
- 	| runLength |
- 	lastIndex = text size
- 	ifTrue:	[line stop: lastIndex.
- 			spaceX := destX.
- 			line paddingWidth: rightMargin - destX.
- 			^true]
- 	ifFalse:	[runLength := (text runLengthFor: (lastIndex := lastIndex + 1)).
- 			runStopIndex := lastIndex + (runLength - 1).
- 			self setStopConditions.
- 			^false]
- !

Item was removed:
- ----- Method: CompositionScanner>>initialize (in category 'initialize') -----
- initialize
- 	wantsColumnBreaks := false.
- 	super initialize!

Item was removed:
- ----- Method: CompositionScanner>>lineHeightForMorphOfHeight:aligned:to: (in category 'private') -----
- lineHeightForMorphOfHeight: aMorphHeight aligned: morphPosition to: linePosition 
- 	
- 	^ self
- 		lineHeightForMorphOfHeight: aMorphHeight
- 		aligned: morphPosition 
- 		to: linePosition
- 		paddedWith: 0
- 		andOptionalMorphBaseline: 0!

Item was removed:
- ----- Method: CompositionScanner>>lineHeightForMorphOfHeight:aligned:to:paddedWith:andOptionalMorphBaseline: (in category 'private') -----
- lineHeightForMorphOfHeight: aMorphHeight aligned: morphPosition to: linePosition paddedWith: verticalPadding andOptionalMorphBaseline: morphBaseline
- 	"The idea here is to first compute the total height and then subtract the overlapping area."
- 
- 	| adjustedLineHeight morphHeight total |
- 	morphHeight := aMorphHeight + verticalPadding.
- 	total := font height + morphHeight.
- 	adjustedLineHeight := 0.
- 	
- 	morphPosition = #top 		ifTrue: [
- 			linePosition = #top			ifTrue: [adjustedLineHeight := total - font height].
- 			linePosition = #center 		ifTrue: [adjustedLineHeight := total - (font descent + (font ascent / 2))].
- 			linePosition = #baseline 	ifTrue: [adjustedLineHeight := total - font descent].
- 			linePosition = #bottom 		ifTrue: [adjustedLineHeight := total].].
- 	morphPosition = #center 	ifTrue: [ | upperMorphHalf lowerMorphHalf |
- 			"The overlapping area of a morph aligned at the center position can be determined by splitting 
- 			the morph into a top half which is aligned at the bottom and a lower half aligned at the top."
- 			upperMorphHalf := self 
- 				lineHeightForMorphOfHeight: aMorphHeight // 2 
- 				aligned: #bottom to: linePosition. 
- 			lowerMorphHalf := self 
- 				lineHeightForMorphOfHeight: aMorphHeight // 2
- 				aligned: #top to: linePosition.
- 			adjustedLineHeight := upperMorphHalf + lowerMorphHalf - font height].
- 	morphPosition = #baseline ifTrue: [ | upperMorphHalf lowerMorphHalf |
- 			"We use the same trick as we used with the center position but with different proportions of the morph."
- 			upperMorphHalf := self 
- 				lineHeightForMorphOfHeight: morphBaseline 
- 				aligned: #bottom to: linePosition. 
- 			lowerMorphHalf := self 
- 				lineHeightForMorphOfHeight: aMorphHeight - morphBaseline 
- 				aligned: #top to: linePosition.
- 			adjustedLineHeight := upperMorphHalf + lowerMorphHalf - font height].
- 	morphPosition = #bottom 	ifTrue: [
- 			linePosition = #top			ifTrue: [adjustedLineHeight := total].
- 			linePosition = #center 		ifTrue: [adjustedLineHeight := total - (font ascent / 2)].
- 			linePosition = #baseline 	ifTrue: [adjustedLineHeight := total - font ascent].
- 			linePosition = #bottom 		ifTrue: [adjustedLineHeight := total - font height].].
- 
- 	^ adjustedLineHeight!

Item was removed:
- ----- Method: CompositionScanner>>placeEmbeddedObjectFrom: (in category 'private') -----
- placeEmbeddedObjectFrom: aTextAttribute
- 
- 	| width anchoredMorphOrForm textAnchorProperties |
- 	anchoredMorphOrForm := aTextAttribute anchoredMorph.
- 	textAnchorProperties := self textAnchorPropertiesFor: anchoredMorphOrForm.
- 	
- 	textAnchorProperties anchorLayout == #document ifTrue: [^ true].
- 	"If it is not anchored at the document, we assume that it is inline."
- 	width := anchoredMorphOrForm width + textAnchorProperties horizontalPadding.
- 	(textAnchorProperties consumesHorizontalSpace and: [destX + width > rightMargin and: [(leftMargin + width) <= rightMargin or: [lastIndex > line first]]])
- 		ifTrue: ["Won't fit, but would on next line"
- 				^ false].
- 	
- 	"The width had to be set beforehand to determine line wrapping. 
- 	We can now re-use and reset it as it might not be necessary anymore. --pre"
- 	width := textAnchorProperties consumesHorizontalSpace 
- 		ifTrue: [anchoredMorphOrForm width + textAnchorProperties horizontalPadding]
- 		ifFalse: [0].
- 	destX := destX + width + kern.
- 	
- 	baseline := baseline max: 
- 		(self alignmentMorphOffsetFor: textAnchorProperties of: anchoredMorphOrForm) 
- 			+ (self baselineAdjustmentFor: textAnchorProperties).
- 	lineHeight := lineHeight max: (self 
- 		lineHeightForMorphOfHeight: anchoredMorphOrForm height
- 		aligned: textAnchorProperties verticalAlignmentMorph 
- 		to: textAnchorProperties verticalAlignmentLine
- 		paddedWith: textAnchorProperties verticalPadding
- 		andOptionalMorphBaseline: (textAnchorProperties morphBaselineGetter 
- 			ifNotNil: [:getter | anchoredMorphOrForm perform: getter] ifNil: [0])).
- 	^ true!

Item was removed:
- ----- Method: CompositionScanner>>rightX (in category 'accessing') -----
- rightX
- 	"Meaningful only when a line has just been composed -- refers to the 
- 	line most recently composed. This is a subtrefuge to allow for easy 
- 	resizing of a composition rectangle to the width of the maximum line. 
- 	Useful only when there is only one line in the form or when each line 
- 	is terminated by a carriage return. Handy for sizing menus and lists."
- 
- 	^spaceX!

Item was removed:
- ----- Method: CompositionScanner>>setActualFont: (in category 'text attributes') -----
- setActualFont: aFont
- 	"Keep track of max height and ascent for auto lineheight"
- 	| descent |
- 	super setActualFont: aFont.
- 	lineHeight == nil
- 		ifTrue: [descent := font descent.
- 				baseline := font ascent.
- 				lineHeight := baseline + descent.
- 				lineGap := aFont lineGap.
- 				lineGapSlice := aFont lineGapSlice]
- 		ifFalse: [descent := lineHeight - baseline max: font descent.
- 				baseline := baseline max: font ascent.
- 				lineHeight := lineHeight max: baseline + descent.
- 				lineGap := lineGap max: aFont lineGap.
- 				lineGapSlice := lineGapSlice max: aFont lineGapSlice]!

Item was removed:
- ----- Method: CompositionScanner>>setStopConditions (in category 'private') -----
- setStopConditions
- 	"Set the font and the stop conditions for the current run."
- 	
- 	self setFont.
- 	stopConditions := wantsColumnBreaks == true
- 		ifTrue: [ColumnBreakStopConditions]
- 		ifFalse: [CompositionStopConditions]!

Item was removed:
- ----- Method: CompositionScanner>>space (in category 'stop conditions') -----
- space
- 	"Record left x and character index of the space character just encountered. 
- 	Used for wrap-around. Answer whether the character has crossed the 
- 	right edge of the composition rectangle of the paragraph."
- 
- 	spaceX := destX.
- 	spaceIndex := lastIndex.
- 	lineHeightAtSpace := lineHeight.
- 	baselineAtSpace := baseline.
- 	spaceCount := spaceCount + 1.
- 	lastBreakIsNotASpace := false.
- 	destX + spaceWidth > rightMargin ifTrue:[^self crossedX].
- 	destX := spaceX + spaceWidth + kern.
- 	lastIndex := lastIndex + 1.
- 	^false
- !

Item was removed:
- ----- Method: CompositionScanner>>tab (in category 'stop conditions') -----
- tab
- 	"Advance destination x according to tab settings in the paragraph's 
- 	textStyle. Answer whether the character has crossed the right edge of 
- 	the composition rectangle of the paragraph."
- 
- 	pendingKernX := 0.
- 	destX := textStyle
- 				nextTabXFrom: destX leftMargin: leftMargin rightMargin: rightMargin.
- 	destX > rightMargin ifTrue:	[^self crossedX].
- 	lastIndex := lastIndex + 1.
- 	^false
- !

Item was removed:
- ----- Method: CompositionScanner>>wantsColumnBreaks: (in category 'initialize') -----
- wantsColumnBreaks: aBoolean
- 
- 	wantsColumnBreaks := aBoolean!

Item was removed:
- ----- Method: CompositionScanner>>wrapAtLastBreakable (in category 'stop conditions') -----
- wrapAtLastBreakable
- 	"Wrap the line before last encountered breakable character."
- 	pendingKernX := 0.
- 	nextIndexAfterLineBreak := spaceIndex.
- 	line stop: spaceIndex - 1.
- 	lineHeight := lineHeightAtSpace.
- 	baseline := baselineAtSpace.
- 	line paddingWidth: rightMargin - spaceX.
- 	line internalSpaces: spaceCount.
- 	^true!

Item was removed:
- ----- Method: CompositionScanner>>wrapAtLastSpace (in category 'stop conditions') -----
- wrapAtLastSpace
- 	"Wrap the line before last encountered space"
- 	
- 	pendingKernX := 0.
- 	nextIndexAfterLineBreak := spaceIndex + 1.
- 	alignment = Justified ifTrue: [
- 		"gobble all subsequent spaces"
- 		[nextIndexAfterLineBreak <= text size and: [(text at: nextIndexAfterLineBreak) == Space]]
- 			whileTrue: [nextIndexAfterLineBreak := nextIndexAfterLineBreak + 1]].
- 	
- 	line stop: nextIndexAfterLineBreak - 1.
- 	lineHeight := lineHeightAtSpace.
- 	baseline := baselineAtSpace.
- 
- 	["remove the space at which we break..."
- 	spaceCount := spaceCount - 1.
- 	spaceIndex := spaceIndex - 1.
- 
- 	"...and every other spaces preceding the one at which we wrap.
- 		Double space after punctuation, most likely."
- 	spaceCount >= 1 and: [(text at: spaceIndex) = Space]]
- 		whileTrue:
- 			["Account for backing over a run which might
- 				change width of space."
- 			font := text fontAt: spaceIndex withStyle: textStyle.
- 			spaceX := spaceX - (font widthOf: Space)].
- 	line paddingWidth: rightMargin - spaceX.
- 	line internalSpaces: spaceCount.
- 	^true!

Item was removed:
- ----- Method: CompositionScanner>>wrapHere (in category 'stop conditions') -----
- wrapHere
- 	"Wrap the line before current character."
- 	pendingKernX := 0.
- 	nextIndexAfterLineBreak := lastIndex.
- 	lastIndex := lastIndex - 1.
- 	spaceX := destX.
- 	line paddingWidth: rightMargin - destX.
- 	line stop: (lastIndex max: line first).
- 	^true!

Item was removed:
- Form subclass: #Cursor
- 	instanceVariableNames: ''
- 	classVariableNames: 'BlankCursor BottomLeftCursor BottomRightCursor CornerCursor CrossHairCursor CurrentCursor DownCursor MarkerCursor MenuCursor MoveCursor NormalCursor OriginCursor ReadCursor ResizeLeftCursor ResizeTopCursor ResizeTopLeftCursor ResizeTopRightCursor RightArrowCursor SquareCursor TargetCursor TextCursor TopLeftCursor TopRightCursor UpCursor UseBiggerCursors WaitCursor WebLinkCursor WriteCursor XeqCursor'
- 	poolDictionaries: ''
- 	category: 'Graphics-Display Objects'!
- 
- !Cursor commentStamp: '<historical>' prior: 0!
- I am a Form that is a possible appearance for a mouse cursor.  My size is always 16x16, ever since the original implementation on the Alto.
- 
- There are many examples available in the "current cursor" category of class methods.  For example, "Cursor normal" and "Cursor wait".  For example:
- 
- 	Cursor wait show
- 
- !

Item was removed:
- ----- Method: Cursor class>>blank (in category 'constants') -----
- blank
- 	"Answer the instance of me that is all white."
- 
- 	^BlankCursor!

Item was removed:
- ----- Method: Cursor class>>bottomLeft (in category 'constants') -----
- bottomLeft
- 	"Cursor bottomLeft showWhile: [Sensor waitButton]"
- 	^BottomLeftCursor
- !

Item was removed:
- ----- Method: Cursor class>>bottomRight (in category 'constants') -----
- bottomRight
- 	"Cursor bottomRight showWhile: [Sensor waitButton]"
- 	^BottomRightCursor
- !

Item was removed:
- ----- Method: Cursor class>>corner (in category 'constants') -----
- corner
- 	"Answer the instance of me that is the shape of the bottom right corner 
- 	of a rectangle."
- 
- 	^CornerCursor!

Item was removed:
- ----- Method: Cursor class>>crossHair (in category 'constants') -----
- crossHair
- 	"Answer the instance of me that is the shape of a cross."
- 
- 	^CrossHairCursor!

Item was removed:
- ----- Method: Cursor class>>currentCursor (in category 'current cursor') -----
- currentCursor
- 	"Answer the instance of Cursor that is the one currently displayed."
- 
- 	^CurrentCursor!

Item was removed:
- ----- Method: Cursor class>>currentCursor: (in category 'current cursor') -----
- currentCursor: aCursor 
- 	"Make the instance of cursor, aCursor, be the current cursor. Display it. 
- 	Create an error if the argument is not a Cursor."
- 
- 	(aCursor isKindOf: self)
- 		ifTrue: [ | platformCursor |
- 			CurrentCursor := aCursor. "unscaled"
- 			self flag: #todo. "mt: The current OSVM platform code for macOS has an issue with *not* scaling up hardware cursors for Retina displays. So we avoid scaling it here and let the OS do it. Note that this is not good because we could never provide a high-resolution cursor from within Squeak since the OS would scale it up anyway."
- 			Smalltalk platformName = 'Mac OS'
- 				ifTrue: [platformCursor := aCursor]
- 				ifFalse: [platformCursor := aCursor scaleIconToDisplay].
- 			self useBiggerCursors
- 				ifTrue: [platformCursor := platformCursor enlargedBy: 2].
- 			platformCursor beCursor]
- 		ifFalse: [self error: 'The new cursor must be an instance of class Cursor']!

Item was removed:
- ----- Method: Cursor class>>down (in category 'constants') -----
- down
- 	"Answer the instance of me that is the shape of an arrow facing 
- 	downward."
- 
- 	^DownCursor!

Item was removed:
- ----- Method: Cursor class>>execute (in category 'constants') -----
- execute
- 	"Answer the instance of me that is the shape of an arrow slanted left 
- 	with a star next to it."
- 
- 	^XeqCursor!

Item was removed:
- ----- Method: Cursor class>>extent:fromArray:offset: (in category 'instance creation') -----
- extent: extentPoint fromArray: anArray offset: offsetPoint 
- 	"Answer a new instance of me with width and height specified by
- 	extentPoint, offset by offsetPoint, and bits from anArray.
- 	NOTE: This has been kluged to take an array of 16-bit constants,
- 	and shift them over so they are left-justified in a 32-bit bitmap"
- 
- 	extentPoint = (16 @ 16)
- 		ifTrue: 
- 			[^ super
- 				extent: extentPoint
- 				fromArray: (anArray collect: [:bits | bits bitShift: 16])
- 				offset: offsetPoint]
- 		ifFalse: [self error: 'cursors must be 16 at 16']!

Item was removed:
- ----- Method: Cursor class>>initBottomLeft (in category 'class initialization') -----
- initBottomLeft
- 
- 	BottomLeftCursor := 
- 		(Cursor extent: 16 @ 16
- 			fromArray: #(
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1111111111111111
- 		2r1111111111111111)
- 			offset: 0 @ -16).
- !

Item was removed:
- ----- Method: Cursor class>>initBottomRight (in category 'class initialization') -----
- initBottomRight
- 
- 	BottomRightCursor := 
- 		(Cursor extent: 16 @ 16
- 			fromArray: #(
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r1111111111111111
- 		2r1111111111111111)
- 			offset: -16 @ -16).
- !

Item was removed:
- ----- Method: Cursor class>>initCorner (in category 'class initialization') -----
- initCorner
- 
- 	CornerCursor := 
- 		(Cursor 
- 			extent: 16 @ 16
- 			fromArray: #(
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r1111111111111111
- 		2r1111111111111111)
- 			offset: -16 @ -16).
- !

Item was removed:
- ----- Method: Cursor class>>initCrossHair (in category 'class initialization') -----
- initCrossHair
- 
- 	CrossHairCursor :=   
- 		(Cursor
- 			extent: 16 @ 16
- 			fromArray: #(
- 		2r0000000000000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0111111111111100
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000000000000
- 		2r0)
- 			offset: -7 @ -7).
- 	
- 	!

Item was removed:
- ----- Method: Cursor class>>initDown (in category 'class initialization') -----
- initDown
- 
- 	DownCursor  :=
- 		     (Cursor
- 	extent: 16 @ 16
- 	fromArray: #(
- 		2r11000000000000
- 		2r11000000000000
- 		2r11000000000000
- 		2r11000000000000
- 		2r11000000000000
- 		2r11000000000000
- 		2r11000000000000
- 		2r1111110000000000
- 		2r111100000000000
- 		2r11000000000000
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0)
- 	offset: 0 @ 0).
- !

Item was removed:
- ----- Method: Cursor class>>initMarker (in category 'class initialization') -----
- initMarker
- 
- 	MarkerCursor := 
- 		Cursor
- 			extent: 16 @ 16
- 			fromArray: #(
- 		2r0111000000000000
- 		2r1111100000000000
- 		2r1111100000000000
- 		2r0111000000000000
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0)
- 			offset: 0 @ 0.
- !

Item was removed:
- ----- Method: Cursor class>>initMenu (in category 'class initialization') -----
- initMenu 
- 
- 	MenuCursor  :=
- 		        (Cursor
- 	extent: 16 @ 16
- 	fromArray: #(
- 		2r1111111111100000
- 		2r1000000000100000
- 		2r1010011000100000
- 		2r1000000000100000
- 		2r1101001101100000
- 		2r1111111111100000
- 		2r1000000000100000
- 		2r1011001010100000
- 		2r1000000000100000
- 		2r1010110010100000
- 		2r1000000000100000
- 		2r1010010100100000
- 		2r1000000000100000
- 		2r1111111111100000
- 		0)
- 	offset: 0 @ 0).
- !

Item was removed:
- ----- Method: Cursor class>>initMove (in category 'class initialization') -----
- initMove
- 
- 	MoveCursor := 
- 		Cursor 
- 			extent: 16 @ 16
- 			fromArray: #(
- 		2r1111111111111100
- 		2r1111111111111100
- 		2r1100001100001100
- 		2r1100001100001100
- 		2r1100001100001100
- 		2r1100001100001100
- 		2r1111111111111100
- 		2r1111111111111100
- 		2r1100001100001100
- 		2r1100001100001100
- 		2r1100001100001100
- 		2r1100001100001100
- 		2r1111111111111100
- 		2r1111111111111100
-           0)
- 			offset: 0 @ 0.
- !

Item was removed:
- ----- Method: Cursor class>>initNormal (in category 'class initialization') -----
- initNormal
- 
- 	NormalCursor :=   
- 		(Cursor
- 			extent: 16 @ 16
- 			fromArray: #(
- 		2r1000000000000000
- 		2r1100000000000000
- 		2r1110000000000000
- 		2r1111000000000000
- 		2r1111100000000000
- 		2r1111110000000000
- 		2r1111111000000000
- 		2r1111100000000000
- 		2r1111100000000000
- 		2r1001100000000000
- 		2r0000110000000000
- 		2r0000110000000000
- 		2r0000011000000000
- 		2r0000011000000000
- 		2r0000001100000000
- 		2r0000001100000000)
- 	offset: 0 @ 0).
- 
- 	
- 	!

Item was removed:
- ----- Method: Cursor class>>initNormalWithMask (in category 'class initialization') -----
- initNormalWithMask    "Cursor initNormalWithMask.  Cursor normal show"
- 	"Next two lines work simply for any cursor..."
- 	self initNormal.
- 	NormalCursor := CursorWithMask derivedFrom: NormalCursor.
- 
- 	"But for a good looking cursor, you have to tweak things..."
- 	NormalCursor := (CursorWithMask extent: 16 @ 16 depth: 1
- 			fromArray: #( 0 1073741824 1610612736 1879048192
- 				2013265920 2080374784 2113929216 2130706432
- 				2080374784 2080374784 1275068416 100663296
- 				100663296 50331648 50331648 0)
- 			offset: -1 @ -1)
- 		setMaskForm: (Form extent: 16 @ 16 depth: 1
- 			fromArray: #( 3221225472 3758096384 4026531840 4160749568
- 				4227858432 4261412864 4278190080 4286578688
- 				4278190080 4261412864 4261412864 3472883712
- 				251658240 125829120 125829120 50331648)
- 			offset: 0 @ 0).!

Item was removed:
- ----- Method: Cursor class>>initOrigin (in category 'class initialization') -----
- initOrigin
- 
- 	OriginCursor :=   
- 		(Cursor
- 			extent: 16 @ 16
- 			fromArray: #(
- 		2r1111111111111111
- 		2r1111111111111111
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000)
- 			offset: 0 @ 0).
- !

Item was removed:
- ----- Method: Cursor class>>initRead (in category 'class initialization') -----
- initRead
- 
- 	ReadCursor :=  
- 		(Cursor
- 			extent: 16 @ 16
- 			fromArray: #(
- 		2r0000000000000000
- 		2r0000000000000000
- 		2r0001000000001000
- 		2r0010100000010100
- 		2r0100000000100000
- 		2r1111101111100000
- 		2r1000010000100000
- 		2r1000010000100000
- 		2r1011010110100000
- 		2r0111101111000000
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0)
- 	offset: 0 @ 0).
- !

Item was removed:
- ----- Method: Cursor class>>initResizeLeft (in category 'class initialization') -----
- initResizeLeft
- 
-        ResizeLeftCursor :=
-                (Cursor extent: 16 @ 16 fromArray: #(
-                2r0000000000000000
-                2r0000000000000000
-                2r0000000000000000
-                2r0000000000000000
-                2r0000100000010000
-                2r0001100000011000
-                2r0011100000011100
-                2r0111111111111110
-                2r0011100000011100
-                2r0001100000011000
-                2r0000100000010000
-                2r0000000000000000
-                2r0000000000000000
-                2r0000000000000000
-                2r0000000000000000
-                2r0000000000000000 )
-        offset: -7 @ -7 ) withMask!

Item was removed:
- ----- Method: Cursor class>>initResizeTop (in category 'class initialization') -----
- initResizeTop
-     "Cursor initResizeTop"
-        ResizeTopCursor :=
-                (Cursor extent: 16 @ 16 fromArray: #(
-                2r000000100000000
-                2r000001110000000
-                2r000011111000000
-                2r000111111100000
-                2r000000100000000
-                2r000000100000000
-                2r000000100000000
-                2r000000100000000
-                2r000000100000000
-                2r000000100000000
-                2r000111111100000
-                2r000011111000000
-                2r000001110000000
-                2r000000100000000
-                2r000000000000000)
-        offset: -7 @ -7) withMask!

Item was removed:
- ----- Method: Cursor class>>initResizeTopLeft (in category 'class initialization') -----
- initResizeTopLeft
- 
-        ResizeTopLeftCursor :=
-                (Cursor extent: 16 @ 16 fromArray: #(
-                2r0000000000000000
-                2r0111110000000000
-                2r0111100000000000
-                2r0111000000000000
-                2r0110100000000000
-                2r0100010000000000
-                2r0000001000000000
-                2r0000000100000000
-                2r0000000010000000
-                2r0000000001000100
-                2r0000000000101100
-                2r0000000000011100
-                2r0000000000111100
-                2r0000000001111100
-                2r0000000000000000
-                2r0000000000000000)
-        offset: -7 @ -7) withMask!

Item was removed:
- ----- Method: Cursor class>>initResizeTopRight (in category 'class initialization') -----
- initResizeTopRight
- 
-        ResizeTopRightCursor :=
-                (Cursor extent: 16 @ 16 fromArray: #(
-                2r0000000000000000
-                2r0000000001111100
-                2r0000000000111100
-                2r0000000000011100
-                2r0000000000101100
-                2r0000000001000100
-                2r0000000010000000
-                2r0000000100000000
-                2r0000001000000000
-                2r0100010000000000
-                2r0110100000000000
-                2r0111000000000000
-                2r0111100000000000
-                2r0111110000000000
-                2r0000000000000000
-                2r0000000000000000)
-        offset: -7 @ -7) withMask!

Item was removed:
- ----- Method: Cursor class>>initRightArrow (in category 'class initialization') -----
- initRightArrow 
- 
- 	RightArrowCursor  :=
- 		      (Cursor
- 	extent: 16 @ 16
- 	fromArray: #(
- 		2r100000000000
- 		2r111000000000
- 		2r1111111110000000
- 		2r111000000000
- 		2r100000000000
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0)
- 	offset: 0 @ 0).
- 	
- 	"Cursor initRightArrow"!

Item was removed:
- ----- Method: Cursor class>>initSquare (in category 'class initialization') -----
- initSquare
- 
- 	SquareCursor := 
- 		(Cursor
- 			extent: 16 @ 16
- 			fromArray: #(
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0000001111000000
- 		2r0000001111000000
- 		2r0000001111000000
- 		2r0000001111000000
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0)
- 	offset: -8 @ -8).
- 
- 	!

Item was removed:
- ----- Method: Cursor class>>initTarget (in category 'class initialization') -----
- initTarget
- 	^TargetCursor := Cursor
- 				extent: 16 @ 16
- 				fromArray:  #(1984 6448 8456 16644 17284 33026 35106 65278 35106 33026 17284 16644 8456 6448 1984 0)
- 				offset: -7 @ -7!

Item was removed:
- ----- Method: Cursor class>>initText (in category 'class initialization') -----
- initText
- 
- 	TextCursor :=   
- 		(Cursor
- 			extent: 16 @ 16
- 			fromArray: #(
- 		2r0000000000000000
- 		2r0000111011100000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000000100000000
- 		2r0000111011100000
- 		2r0000000000000000
- 		2r0)
- 			offset: -7 @ -7).
- 	
- 	!

Item was removed:
- ----- Method: Cursor class>>initTopLeft (in category 'class initialization') -----
- initTopLeft
- 	TopLeftCursor := 
- 		(Cursor extent: 16 @ 16
- 			fromArray: #(
- 		2r1111111111111111
- 		2r1111111111111111
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000
- 		2r1100000000000000)
- 			offset: 0 @ 0).
- !

Item was removed:
- ----- Method: Cursor class>>initTopRight (in category 'class initialization') -----
- initTopRight
- 	TopRightCursor := 
- 		(Cursor extent: 16 @ 16
- 			fromArray: #(
- 		2r1111111111111111
- 		2r1111111111111111
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011
- 		2r0000000000000011)
- 			offset: -16 @ 0).
- !

Item was removed:
- ----- Method: Cursor class>>initUp (in category 'class initialization') -----
- initUp
- 
- 	UpCursor := 
- 		    (Cursor
- 	extent: 16 @ 16
- 	fromArray: #(
- 		2r11000000000000
- 		2r111100000000000
- 		2r1111110000000000
- 		2r11000000000000
- 		2r11000000000000
- 		2r11000000000000
- 		2r11000000000000
- 		2r11000000000000
- 		2r11000000000000
- 		2r11000000000000
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0
- 		2r0)
- 	offset: 0 @ 0).
- !

Item was removed:
- ----- Method: Cursor class>>initWait (in category 'class initialization') -----
- initWait
- 
- 	WaitCursor := 
- 		  (Cursor
- 			extent: 16 @ 16
- 			fromArray: #(
- 		2r1111111111111100
- 		2r1000000000000100
- 		2r0100000000001000
- 		2r0010000000010000
- 		2r0001110011100000
- 		2r0000111111000000
- 		2r0000011110000000
- 		2r0000011110000000
- 		2r0000100101000000
- 		2r0001000100100000
- 		2r0010000110010000
- 		2r0100001111001000
- 		2r1000111111110100
- 		2r1111111111111100
- 		0)
- 			offset: 0 @ 0).
- !

Item was removed:
- ----- Method: Cursor class>>initWrite (in category 'class initialization') -----
- initWrite
- 
- 	WriteCursor := (Cursor
- 	extent: 16 @ 16
- 	fromArray: #(
- 		2r0000000000011000
- 		2r0000000000111100
- 		2r0000000001001000
- 		2r0000000010010000
- 		2r0000000100100000
- 		2r0000001001000100
- 		2r0000010010000100
- 		2r0000100100001100
- 		2r0001001000010000
- 		2r0010010000010000
- 		2r0111100000001000
- 		2r0101000011111000
- 		2r1110000110000000
- 		2r0111111100000000
- 		2r0
- 		2r0)
- 	offset: 0 @ 0).
- !

Item was removed:
- ----- Method: Cursor class>>initXeq (in category 'class initialization') -----
- initXeq
- 
- 	XeqCursor := 
- 		(Cursor
- 			extent: 16 @ 16
- 			fromArray: #(
- 		2r1000000000010000
- 		2r1100000000010000
- 		2r1110000000111000
- 		2r1111000111111111
- 		2r1111100011000110
- 		2r1111110001000100
- 		2r1111111001111100
- 		2r1111000001101100
- 		2r1101100011000110
- 		2r1001100010000010
- 		2r0000110000000000
- 		2r0000110000000000
- 		2r0000011000000000
- 		2r0000011000000000
- 		2r0000001100000000
- 		2r0000001100000000)
- 	offset: 0 @ 0).
- !

Item was removed:
- ----- Method: Cursor class>>initialize (in category 'class initialization') -----
- initialize
- 	"Create all the standard cursors..."
- 		self initOrigin.
- 		self initRightArrow.
- 		self initMenu.
- 		self initCorner.
- 		self initRead.
- 		self initWrite.
- 		self initWait.
- 		BlankCursor := Cursor new.
- 		self initXeq.
- 		self initSquare.
- 		self initNormalWithMask.
- 		self initCrossHair.
- 		self initMarker.
- 		self initUp.
- 		self initDown.
- 		self initMove.
- 		self initBottomLeft.
- 		self initBottomRight.
- 		self initResizeLeft.
- 		self initResizeTop.
- 		self initResizeTopLeft.
- 		self initResizeTopRight.
- 		self initText.
- 		self initTopLeft.
- 		self initTopRight.
- 		self makeCursorsWithMask.
- 
- 		"Cursor initialize"
- !

Item was removed:
- ----- Method: Cursor class>>makeCursorsWithMask (in category 'class initialization') -----
- makeCursorsWithMask
- 	"Cursor initialize;makeCursorsWithMask"
- 
- 	self classPool associationsDo: [:var |
- 		((var value isKindOf: Cursor) and:[var value hasMask not])
- 			ifTrue: [var value: var value withMask]]!

Item was removed:
- ----- Method: Cursor class>>marker (in category 'constants') -----
- marker
- 	"Answer the instance of me that is the shape of a small ball."
- 
- 	^MarkerCursor!

Item was removed:
- ----- Method: Cursor class>>menu (in category 'constants') -----
- menu 
- 	"Answer the instance of me that is the shape of a menu."
- 
- 	^MenuCursor!

Item was removed:
- ----- Method: Cursor class>>move (in category 'constants') -----
- move
- 	"Answer the instance of me that is the shape of a cross inside a square."
- 
- 	^MoveCursor!

Item was removed:
- ----- Method: Cursor class>>new (in category 'instance creation') -----
- new
- 
- 	^ self extent: 16 @ 16
- 		fromArray: (Array new: 16 withAll: 0)
- 		offset: 0 @ 0
- 
- 	"Cursor new bitEdit show"!

Item was removed:
- ----- Method: Cursor class>>normal (in category 'constants') -----
- normal
- 	"Answer the instance of me that is the shape of an arrow slanted left."
- 
- 	^NormalCursor!

Item was removed:
- ----- Method: Cursor class>>origin (in category 'constants') -----
- origin
- 	"Answer the instance of me that is the shape of the top left corner of a 
- 	rectangle."
- 
- 	^OriginCursor!

Item was removed:
- ----- Method: Cursor class>>read (in category 'constants') -----
- read
- 	"Answer the instance of me that is the shape of eyeglasses."
- 
- 	^ReadCursor!

Item was removed:
- ----- Method: Cursor class>>resizeBottom (in category 'constants') -----
- resizeBottom
- 	"Cursor resizeBottom showWhile: [Sensor waitButton]"
- 	^self resizeTop!

Item was removed:
- ----- Method: Cursor class>>resizeBottomLeft (in category 'constants') -----
- resizeBottomLeft
- 	"Cursor resizeBottomLeft showWhile: [Sensor waitButton]"
- 	^self resizeTopRight!

Item was removed:
- ----- Method: Cursor class>>resizeBottomRight (in category 'constants') -----
- resizeBottomRight
- 	"Cursor resizeBottomRight showWhile: [Sensor waitButton]"
- 	^self resizeTopLeft!

Item was removed:
- ----- Method: Cursor class>>resizeForEdge: (in category 'instance creation') -----
- resizeForEdge: aSymbol
- 	"Cursor resizeForEdge: #top"
- 	"Cursor resizeForEdge: #bottomLeft"
- 	^self perform: ('resize', aSymbol first asString asUppercase, (aSymbol copyFrom: 2 to: aSymbol size)) asSymbol.!

Item was removed:
- ----- Method: Cursor class>>resizeLeft (in category 'constants') -----
- resizeLeft
- 	"Cursor resizeLeft showWhile: [Sensor waitButton]"
- 	^ResizeLeftCursor!

Item was removed:
- ----- Method: Cursor class>>resizeRight (in category 'constants') -----
- resizeRight
- 	"Cursor resizeRight showWhile: [Sensor waitButton]"
- 	^self resizeLeft!

Item was removed:
- ----- Method: Cursor class>>resizeTop (in category 'constants') -----
- resizeTop
- 	"Cursor resizeTop showWhile: [Sensor waitButton]"
- 	^ResizeTopCursor!

Item was removed:
- ----- Method: Cursor class>>resizeTopLeft (in category 'constants') -----
- resizeTopLeft
- 	"Cursor resizeTopLeft showWhile: [Sensor waitButton]"
- 	^ ResizeTopLeftCursor!

Item was removed:
- ----- Method: Cursor class>>resizeTopRight (in category 'constants') -----
- resizeTopRight
- 	"Cursor resizeTopRight showWhile: [Sensor waitButton]"
- 	^ResizeTopRightCursor!

Item was removed:
- ----- Method: Cursor class>>rightArrow (in category 'constants') -----
- rightArrow 
- 	"Answer the instance of me that is the shape of an arrow pointing to the right."
- 
- 	^RightArrowCursor!

Item was removed:
- ----- Method: Cursor class>>square (in category 'constants') -----
- square
- 	"Answer the instance of me that is the shape of a square."
- 
- 	^SquareCursor!

Item was removed:
- ----- Method: Cursor class>>startUp (in category 'class initialization') -----
- startUp
- 	self currentCursor: self currentCursor!

Item was removed:
- ----- Method: Cursor class>>target (in category 'constants') -----
- target
- 	"Answer the instance of me that is the shape of a gunsight."
- 	"Cursor target show"
- 	^TargetCursor ifNil:[self initTarget]!

Item was removed:
- ----- Method: Cursor class>>text (in category 'constants') -----
- text
- 	^ TextCursor!

Item was removed:
- ----- Method: Cursor class>>topLeft (in category 'constants') -----
- topLeft
- 	"Cursor topLeft showWhile: [Sensor waitButton]"
- 	^ TopLeftCursor!

Item was removed:
- ----- Method: Cursor class>>topRight (in category 'constants') -----
- topRight
- 	"Cursor topRight showWhile: [Sensor waitButton]"
- 	^ TopRightCursor!

Item was removed:
- ----- Method: Cursor class>>up (in category 'constants') -----
- up
- 	"Answer the instance of me that is the shape of an arrow facing upward."
- 
- 	^UpCursor!

Item was removed:
- ----- Method: Cursor class>>useBiggerCursors (in category 'preferences') -----
- useBiggerCursors
- 
- 	<preference: 'Use bigger mouse cursors'
- 		categoryList: #(mouse Accessibility)
- 		description: 'If true, mouse cursors are scaled up'
- 		type: #Boolean>
- 	^ UseBiggerCursors ifNil: [false]!

Item was removed:
- ----- Method: Cursor class>>useBiggerCursors: (in category 'preferences') -----
- useBiggerCursors: aBool
- 
- 	UseBiggerCursors := aBool.
- 	Cursor currentCursor: Cursor currentCursor.!

Item was removed:
- ----- Method: Cursor class>>wait (in category 'constants') -----
- wait
- 	"Answer the instance of me that is the shape of an Hourglass (was in the 
- 	shape of three small balls)."
- 
- 	^WaitCursor!

Item was removed:
- ----- Method: Cursor class>>webLink (in category 'constants') -----
- webLink
- 	"Return a cursor that can be used for emphasizing web links"
- 	"Cursor webLink showWhile: [Sensor waitButton]"
- 	^WebLinkCursor ifNil:[
- 		WebLinkCursor :=  (CursorWithMask extent: 16 at 16
- 			fromArray: #(3072 4608 4608 4608 4608 5046 4681 29257 37449 37449 32769 32769 49155 16386 24582 16380 )
- 			offset: -5 at 0) setMaskForm:
- 		(Form extent: 16 at 16 
- 			fromArray: (#(3072 7680 7680 7680 7680 8118 8191 32767 65535 65535 65535 65535 65535 32766 32766 16380 )  collect: [:bits | bits bitShift: 16])
- 			offset: 0 at 0)].!

Item was removed:
- ----- Method: Cursor class>>write (in category 'constants') -----
- write
- 	"Answer the instance of me that is the shape of a pen writing."
- 
- 	^WriteCursor!

Item was removed:
- ----- Method: Cursor>>asBigCursor (in category 'converting') -----
- asBigCursor
- 	"Big cursors are 32 bits deep (ARGB premultiplied)"
- 	depth = 32
- 		ifFalse: [^self enlargedBy: 2].
- 	^self!

Item was removed:
- ----- Method: Cursor>>asCursorForm (in category 'converting') -----
- asCursorForm
- 	| form |
- 	form := StaticForm extent: self extent depth: 8.
- 	form fillShape: self fillColor: Color black at: offset negated.
- 	^ form offset: offset!

Item was removed:
- ----- Method: Cursor>>beCursor (in category 'primitives') -----
- beCursor
- 	"Primitive. Tell the interpreter to use the receiver as the current cursor 
- 	image. Fail if the receiver does not match the size expected by the 
- 	hardware. Essential. See Object documentation whatIsAPrimitive."
- 
- 	<primitive: 101>
- 	self primitiveFailed!

Item was removed:
- ----- Method: Cursor>>beCursorWithMask: (in category 'primitives') -----
- beCursorWithMask: maskForm
- 	"Primitive. Tell the interpreter to use the receiver as the current cursor image with the given mask Form. Both the receiver and the mask should have extent 16 at 16 and a depth of one. The mask and cursor bits are combined as follow:
- 			mask	cursor	effect
- 			 0		  0		transparent (underlying pixel shows through)
- 			 1		  1		opaque black
- 			 1		  0		opaque white
- 			 0		  1		invert the underlying pixel"
- "Essential. See Object documentation whatIsAPrimitive."
- 
- 	<primitive: 101>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: Cursor>>changed: (in category 'updating') -----
- changed: aParameter
- 	"overriden to reinstall the cursor if it is the active cursor, in case the appearance has changed.  (Is this used anywhere?  Do cursors really change in place these days?)"
- 	self == CurrentCursor ifTrue: [self beCursor].
- 	super changed: aParameter!

Item was removed:
- ----- Method: Cursor>>enlargedBy: (in category 'converting') -----
- enlargedBy: scale
- 	"Big cursors are 32 bits deep (ARGB premultiplied)"
- 	| big |
- 	scale = 1 ifTrue: [^self].
- 	big := CursorWithAlpha extent: self extent * scale depth: 32.
- 	(self asCursorForm magnifyBy: scale) displayOn: big.
- 	big offset: (self offset - 0.5 * scale min: 0 at 0 max: big extent negated) asIntegerPoint.
- 	big fallback: self.
- 	^big!

Item was removed:
- ----- Method: Cursor>>hasMask (in category 'testing') -----
- hasMask
- 	^false!

Item was removed:
- ----- Method: Cursor>>printOn: (in category 'printing') -----
- printOn: aStream
- 
- 	self storeOn: aStream base: 2!

Item was removed:
- ----- Method: Cursor>>scaleIconToDisplay (in category 'converting') -----
- scaleIconToDisplay
- 	"Overwritten to use the custom #enlargedBy: method to scale up the receiver."
- 	
- 	^ self enlargedBy: (RealEstateAgent scaleFactor max: 1)!

Item was removed:
- ----- Method: Cursor>>show (in category 'displaying') -----
- show
- 	"Make the hardware's mouse cursor look like the receiver"
- 
- 	Cursor currentCursor: self!

Item was removed:
- ----- Method: Cursor>>showGridded: (in category 'displaying') -----
- showGridded: gridPoint 
- 	"Make the current cursor shape be the receiver, forcing the location of the cursor to the point nearest gridPoint."
- 	
- 	Sensor cursorPoint: (Sensor cursorPoint grid: gridPoint).
- 	Cursor currentCursor: self!

Item was removed:
- ----- Method: Cursor>>showWhile: (in category 'displaying') -----
- showWhile: aBlock 
- 	"While evaluating the argument, aBlock, make the receiver be the cursor shape."
- 	"ar 2/2/2006: Only allow this if active process is ui process"
- 	| oldcursor |
- 	Processor activeProcess == Project uiProcess ifFalse:[^aBlock value].
- 	oldcursor := Cursor currentCursor.
- 	self show.
- 	^aBlock ensure: [oldcursor show]
- !

Item was removed:
- ----- Method: Cursor>>withMask (in category 'converting') -----
- withMask
- 	^CursorWithMask derivedFrom: self!

Item was removed:
- Cursor subclass: #CursorWithAlpha
- 	instanceVariableNames: 'fallback'
- 	classVariableNames: 'Constants'
- 	poolDictionaries: ''
- 	category: 'Graphics-Display Objects'!
- 
- !CursorWithAlpha commentStamp: '<historical>' prior: 0!
- A 32-bit ARGB Cursor of arbitrary extent (some platforms may limit the size). Compositing assumes alpha is pre-multiplied.!

Item was removed:
- ----- Method: CursorWithAlpha class>>biggerNormal (in category 'constants') -----
- biggerNormal
- 	"self biggerNormal showWhile:[Sensor waitButton]"
- 	"(Base64MimeConverter mimeEncode: ((FileStream readOnlyFileNamed: 'EtoysCursor.png') binary)) upToEnd"
- 
- 	^self constants at: #biggerNormal ifAbsentPut: [
- 		| form cursor |
- 		form := (PNGReadWriter on: (Base64MimeConverter mimeDecodeToBytes:
- 			'iVBORw0KGgoAAAANSUhEUgAAABsAAAArCAYAAACJrvP4AAAACXBIWXMAAAsTAAALEwEAmpwY
- 			AAAEF0lEQVRYCb2XS0hcVxjHj2/G8ZWMQQbSGO2iRhERwRALBmJNoOOqwUXtYtxOTQJxI8SN
- 			CyXJqggVEghusrAuBB8IddUWF64CvnCj+AJrsYKio6JJOPn/j+dc5s6MztyZMR/857v3PL7f
- 			/c4595w7QmiTUvrN9ZV7wGhfB3jOunpgOoYtPQQm19fXn6DsulY2PJUSi4ARvLm5+SuiE5hS
- 			mAsBXSYzv99vLuXExMRL1H2jlRKoDYbAMhS4uLj4PJUwN4K5TTqEhQPHxsZeayCzTCrDqLC0
- 			tLQryTAqjNmFA1OR4YWwaMBk5/BSWDRgMhnGhEUDJpphXDACqdDXIpEMHcHCF43TDB3Bks0w
- 			IVj4kMabYcKwcGA8c+gIlp2drRaKGc5wYKwMHcFycnIiYOHACzLkhi9SAgsHRsnQOSzaMBJk
- 			FPoejo6OvkJ5iZY67R1lZoJe5kOBKysrzxzBCgoKrCcnpKysTO7v75sjMKafmZl5gX6uNPww
- 			M4EeQXrsEAJDJc7Ozngr8vPzRVVVldjZ2RGrq6uqrLi4WPT394u2tjZxeHj4P8C7qiLkJzMz
- 			8zNvc3NzT+jR/yl9xDBmZWWpTAoLC2V9fb3c29uTXV1dtuwaGxtVRgcHBzuI0QY91vLBUw+0
- 			voOnXPyyijBEUWWVlZViampKFBUVCcyDKC8vt9pitYnp6WlmfqO7u/uOVRHjIiKzjIwM2dDQ
- 			oDIKnZCWlhZbdoFAQFUvLCz8Bcb3WrfgqWItFR/XKrEIWG1trQWam5v7Z3Bw8C2jjoyMyNLS
- 			UgvIYeYQ05A5h5HA+GE1NTVWgPn5+b/RubWiosJ/enoaZNDq6moLhjrZ19fHYjk7O/sO9/eg
- 			G1oZ8JTNbJmZJ9Wgn9GyleJQMWhPT48NhnllsTw+Pv4X7WLCuI1YX8TsuLy8/CfKmrXuwt9t
- 			b2//iXX4LJder9cCut1uOT4+zio5PDz8G9pWaqm4uLaZDaZBXLY2GO4bdnd3PzAowDZYc3Mz
- 			i+X29vY82l0K4ypR/2JOTk7e49qsIuMLUEbdXFpaes6gk5OT0uPxWECeBGtra6ySvb29v6Bt
- 			ve7DfjZTsKOjo99RyvkzEOMtGOpuBoPBbQblQsK9Ejfnzs5OFsuNjY0JlF8IQ11clodWeVgo
- 			bxh0YGDABmOmNGxzh2j3EPJqRV2VqLvUFKyjo+NHBuWqxb4nS0pKVFZmGFG+gihJw8wTerHx
- 			/kEgXng6y7a2thYxnAHAHkHfavEcoxyZBcOh+AOHixS+7HwnfT4f/6nynSQoaZh5MjWcTU1N
- 			94aGhtrr6up8qLgPcVFQd7SuwVPmIdN5njk1wmi31a8QHu3VuYVrLhDaf+dOHGgvE4Gp3RsB
- 			cnUQMx+f9P1H7c9PXyHUIcoy01HXX637AibwgHAnFRPGAAAAAElFTkSuQmCC' 
- 				readStream) readStream) nextImage.
- 	cursor := CursorWithAlpha extent: form extent depth: 32.
- 	form displayOn: cursor.
- 	cursor offset: -2 @ -1.
- 	cursor preMultiplyAlpha.
- 	cursor]!

Item was removed:
- ----- Method: CursorWithAlpha class>>constants (in category 'constants') -----
- constants
- 	^Constants ifNil: [Constants := Dictionary new]!

Item was removed:
- ----- Method: CursorWithAlpha class>>fromDisplay: (in category 'instance creation') -----
- fromDisplay: aRectangle 
- 	"Answer an ARGB cursor with bitmap initialized from the area of the 
- 	display screen defined by aRectangle."
- 
- 	^ (self extent: aRectangle extent depth: 32)
- 		offset: aRectangle extent // -2;
- 		fromDisplay: aRectangle;
- 		fixAlpha!

Item was removed:
- ----- Method: CursorWithAlpha class>>resetConstants (in category 'constants') -----
- resetConstants
- 	Constants := nil.
- !

Item was removed:
- ----- Method: CursorWithAlpha>>asCursorForm (in category 'converting') -----
- asCursorForm
- 
- 	^ self as: StaticForm!

Item was removed:
- ----- Method: CursorWithAlpha>>beCursor (in category 'primitives') -----
- beCursor
- 	<primitive: 101>
- 	self fallback beCursor!

Item was removed:
- ----- Method: CursorWithAlpha>>fallback (in category 'accessing') -----
- fallback
- 	^fallback ifNil: [NormalCursor]!

Item was removed:
- ----- Method: CursorWithAlpha>>fallback: (in category 'accessing') -----
- fallback: aCursor
- 	fallback := aCursor!

Item was removed:
- Cursor subclass: #CursorWithMask
- 	instanceVariableNames: 'maskForm'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Display Objects'!
- 
- !CursorWithMask commentStamp: '<historical>' prior: 0!
- A Cursor which additionally has a 16x16 transparency bitmap called a "mask".  See the comment of beCursorWithMask: for details on how the mask is treated.!

Item was removed:
- ----- Method: CursorWithMask class>>derivedFrom: (in category 'as yet unclassified') -----
- derivedFrom: aForm      "Cursor initNormalWithMask.  Cursor normal show"
- 	"aForm is presumably a cursor"
- 	| cursor mask ext |
- 	ext := aForm extent.
- 	cursor := self extent: ext.
- 	cursor copy: (1 at 1 extent: ext) from: 0 at 0 in: aForm rule: Form over.
- 	mask := Form extent: ext.
- 	(1 at 1) eightNeighbors do:
- 		[:p | mask copy: (p extent: ext) from: 0 at 0 in: aForm rule: Form under].
- 	cursor setMaskForm: mask.
- 	cursor offset: ((aForm offset - (1 at 1)) max: ext negated).
- 	^ cursor!

Item was removed:
- ----- Method: CursorWithMask>>asCursorForm (in category 'converting') -----
- asCursorForm
- 	| form |
- 	form := StaticForm extent: self extent depth: 8.
- 	form fillShape: maskForm fillColor: Color white.
- 	form fillShape: self fillColor: Color black at: offset negated.
- 	^ form offset: offset!

Item was removed:
- ----- Method: CursorWithMask>>beCursor (in category 'primitives') -----
- beCursor
- 	maskForm unhibernate.
- 	^ self beCursorWithMask: maskForm!

Item was removed:
- ----- Method: CursorWithMask>>hasMask (in category 'mask') -----
- hasMask
- 	^true!

Item was removed:
- ----- Method: CursorWithMask>>maskForm (in category 'mask') -----
- maskForm
- 	^ maskForm!

Item was removed:
- ----- Method: CursorWithMask>>postCopy (in category 'copying') -----
- postCopy
- 	super postCopy.
- 	maskForm := maskForm copy!

Item was removed:
- ----- Method: CursorWithMask>>setMaskForm: (in category 'mask') -----
- setMaskForm: aForm
- 	maskForm := aForm!

Item was removed:
- ----- Method: CursorWithMask>>storeOn:base: (in category 'mask') -----
- storeOn: aStream base: anInteger
- 
- 	aStream nextPut: $(.
- 	super storeOn: aStream base: anInteger.
- 	aStream nextPutAll: ' setMaskForm: '.
- 	maskForm storeOn: aStream base: anInteger.
- 	aStream nextPut: $)!

Item was removed:
- ----- Method: CursorWithMask>>withMask (in category 'mask') -----
- withMask
- 	^self!

Item was removed:
- DisplayScreen subclass: #DisplayHostWindow
- 	instanceVariableNames: 'windowProxy title windowType eventQueue'
- 	classVariableNames: ''
- 	poolDictionaries: 'EventSensorConstants'
- 	category: 'Graphics-External-Ffenestri'!
- 
- !DisplayHostWindow commentStamp: '<historical>' prior: 0!
- A subclass of DisplayScreen that uses a (platform appropriate) HostWindowProxy
- to do its displaying in a separate host OS window. This is just one example of a
- client for HostWindowProxy.
- See #test #test2 and HostWindowTests for example usage.!

Item was removed:
- ----- Method: DisplayHostWindow class>>examplePaint (in category 'examples') -----
- examplePaint
- 	"DisplayHostWindow examplePaint inspect"
- 	"Should
- 		a) open a window
- 		b) fork a process to allow painting with mouse
- 		c) survive saving and re-opening the image
- 		d) close and terminate the process when clicking close box or pressing ESC or garbage collect
- 	This relies on the Morphic main loop repeatedly fetching events from Sensor.
- 	"
- 	| win evt pen |
- 	win := DisplayHostWindow extent: 400 at 400 depth: 32.
- 	win offset: 50 at 50; open; windowTitle: 'Paint Test'.
- 	pen := nil.
- 	[
- 		[win isOpen] whileTrue: [
- 			evt := win nextEvent.
- 			"check for ESC event"
- 			((evt at: 1) = EventTypeKeyboard and: [(evt at: 4) = EventKeyChar and: [(evt at: 3) = 27]])
- 				ifTrue: [win close].
- 			"process for mouse events"
- 			(evt at: 1) = EventTypeMouse ifTrue: [
- 				(evt at: 5) > 0	"button pressed"
- 					ifTrue: [
- 						pen ifNil: [
- 							pen := Pen newOnForm: win.
- 							pen roundNib: 5; color: Color random.
- 							pen place: (evt at: 3)@(evt at: 4)].
- 						pen goto: (evt at: 3)@(evt at: 4)]
- 					ifFalse: [pen := nil]].
- 			win forceToScreen.
- 		].
- 	] forkNamed: thisContext asString.
- 	^win!

Item was removed:
- ----- Method: DisplayHostWindow>>actualScreenSize (in category 'snapshots') -----
- actualScreenSize
- "return the host window size as if it were 'the' screen"
- 	^self windowSize!

Item was removed:
- ----- Method: DisplayHostWindow>>close (in category 'initialize-release') -----
- close
- 	"close this window"
- 	windowProxy ifNil: [ ^ self error: 'cannot close never opened window' ].
- 	"We don't use 'self windowProxy close' here because if we've never setup the window why do it now only to close it immediately?"
- 	windowProxy close.
- 	windowProxy := nil!

Item was removed:
- ----- Method: DisplayHostWindow>>eventQueue (in category 'accessing') -----
- eventQueue
- 	^eventQueue ifNil: [eventQueue := SharedQueue new]
- !

Item was removed:
- ----- Method: DisplayHostWindow>>forceToScreen (in category 'basic api') -----
- forceToScreen
- 	"update the area defined by my bounds"
- 	self forceToScreen: self boundingBox!

Item was removed:
- ----- Method: DisplayHostWindow>>forceToScreen: (in category 'basic api') -----
- forceToScreen: damageRectangle 
- 	"update the area defined by damageRectangle"
- 	windowProxy ifNotNil:[ windowProxy forceToScreen: damageRectangle]!

Item was removed:
- ----- Method: DisplayHostWindow>>handleActivated (in category 'private-events') -----
- handleActivated
- 	"window made active - some platforms only - do not rely upon this"!

Item was removed:
- ----- Method: DisplayHostWindow>>handleClose (in category 'private-events') -----
- handleClose
- 	"window close icon pressed"
- 
- 	self close.
- !

Item was removed:
- ----- Method: DisplayHostWindow>>handleIconise (in category 'private-events') -----
- handleIconise
- 	"window iconised or hidden etc"!

Item was removed:
- ----- Method: DisplayHostWindow>>handleMetricChange: (in category 'private-events') -----
- handleMetricChange: aRectangle
- 	"size or position of window changed"
- 
- 	offset := aRectangle origin.
- 
- 	(width = aRectangle width and: [height = aRectangle height])
- 		ifFalse: [self setExtent: aRectangle extent depth: depth].
- !

Item was removed:
- ----- Method: DisplayHostWindow>>handlePaint: (in category 'private-events') -----
- handlePaint: aRectangle
- 	"window area needs updating. Some platforms do not need to send this, do not rely on it in image"
- 
- 	self forceToScreen: aRectangle.
- !

Item was removed:
- ----- Method: DisplayHostWindow>>isOpen (in category 'accessing') -----
- isOpen
- 	^windowProxy notNil!

Item was removed:
- ----- Method: DisplayHostWindow>>nextEvent (in category 'accessing') -----
- nextEvent
- 	^self eventQueue next!

Item was removed:
- ----- Method: DisplayHostWindow>>nextEventOrNil (in category 'accessing') -----
- nextEventOrNil
- 	^self eventQueue nextOrNil!

Item was removed:
- ----- Method: DisplayHostWindow>>open (in category 'initialize-release') -----
- open
- 	"open the host window"
- 	windowProxy ifNil: [ windowProxy := HostWindowProxy on: self ].
- 	windowType ifNil: [ windowType := #defaultWindowType ].
- 	windowProxy perform: windowType.
- 	windowProxy open.
- 	title ifNotNil: [ windowProxy windowTitle: title ].
- !

Item was removed:
- ----- Method: DisplayHostWindow>>processEvent: (in category 'private-events') -----
- processEvent: evt
- 	"evt is a raw event buffer from VM. Check for window events (close etc.). Queue events if queue exists"
- 	(evt at: 1) = EventTypeWindow
- 		ifTrue: [self processWindowEvent: evt].
- 	self queueEvent: evt.
- !

Item was removed:
- ----- Method: DisplayHostWindow>>processWindowEvent: (in category 'private-events') -----
- processWindowEvent: evt
- 	(evt at: 3) caseOf: {
- 		[WindowEventMetricChange] -> [self handleMetricChange: ((evt at: 4)@(evt at: 5) corner: (evt at: 6)@(evt at: 7)) ].
- 		[WindowEventClose] ->	 [self handleClose].
- 		[WindowEventIconise] -> [self handleIconise]. 
- 		[WindowEventActivated] -> [self handleActivated]. 
- 		[WindowEventPaint] -> [self handlePaint: ((evt at: 4)@(evt at: 5) corner: (evt at: 6)@(evt at: 7))].
- 	} otherwise: ["unknown"]
- !

Item was removed:
- ----- Method: DisplayHostWindow>>queueEvent: (in category 'private-events') -----
- queueEvent: evt
- 	"Queue the given event in the event queue (if any).
- 	Note that the event buffer must be copied since it
- 	will be reused later on."
- 	eventQueue ifNil: [^self].	"queue gets created by client"
- 	eventQueue nextPut: evt shallowCopy.
- !

Item was removed:
- ----- Method: DisplayHostWindow>>resetProxy (in category 'snapshots') -----
- resetProxy
- 	"private - for use when resuming a snapshot file only. If the windowProxy had previously been created, nil it and reopen cleanly. IF you try to use this in a 'live' system it will NOT close the windows since startup conditions assume that proxies are invalid so we don't attempt to close them - since that could cause other problems"
- 	windowProxy ifNotNil: 
- 		[ windowProxy := nil.
- 		self open ]!

Item was removed:
- ----- Method: DisplayHostWindow>>test (in category 'testing') -----
- test
- 	"((DisplayHostWindow extent: 400 at 400 depth: 16 ) translateBy: 210 at 450) test"
- 	"Should
- 		a) open a window with the upper left portion of the current Display
- 		b) find the window size
- 		f) close the window"
- 	| size |
- 	self open.
- 	Display displayOn: self.
- 	self forceToScreen: self boundingBox.
- 	size := self windowSize.
- 	self close.
- 	^ size!

Item was removed:
- ----- Method: DisplayHostWindow>>test2 (in category 'testing') -----
- test2
- 	"((DisplayHostWindow extent: 400 @ 400 depth: 16 ) translateBy: 210 @ 450) test2"
- 	"Should
- 		a) open a window with the upper left portion of the current Display
- 		b) update the middle area with part of Display
- 		c) move the window from 210 @ 450 to 300 @ 300
- 		d) change the window title
- 		e) change the window size from 400 @ 400 to 600 @ 400
- 		f) wait 4 seconds so you can see the result
- 		g) close the window via the garbage collecttor finalizing it"
- 	self open.
- 	Display displayOn: self.
- 	self forceToScreen.
- 	Display displayOn: self at: -100 @ -200.
- 	self forceToScreen: (100 @ 100 extent: 200 @ 200).
- 	self windowPosition: 300 @ 300.
- 	self windowTitle: 'YooHoo!! New title'.
- 	self windowSize: 600 @ 400.
- 	(Delay forSeconds: 4) wait.!

Item was removed:
- ----- Method: DisplayHostWindow>>windowPosition (in category 'basic api') -----
- windowPosition
- 	"return the current position of the window"
- 		
- 	^windowProxy ifNotNil:[ windowProxy windowPosition]!

Item was removed:
- ----- Method: DisplayHostWindow>>windowPosition: (in category 'basic api') -----
- windowPosition: aPoint
- 	"set the position of the window and then return the new position"
- 	^windowProxy ifNotNil:[ windowProxy windowPosition: aPoint]!

Item was removed:
- ----- Method: DisplayHostWindow>>windowSize (in category 'basic api') -----
- windowSize
- 	"return the current size of the window - not neccessarily the same as my bitmap"
- 
- 	^windowProxy ifNotNil:[ windowProxy windowSize]!

Item was removed:
- ----- Method: DisplayHostWindow>>windowSize: (in category 'basic api') -----
- windowSize: aPoint
- 	"Set the size of the window and then return the current size of the window -
- not neccessarily the same "
- 		
- 	^windowProxy ifNotNil:[ windowProxy windowSize: aPoint]!

Item was removed:
- ----- Method: DisplayHostWindow>>windowTitle: (in category 'basic api') -----
- windowTitle: titleString 
- 	"set the label in the window titlebar to titleString"
- 	title := titleString.
- 	windowProxy ifNotNil: [ windowProxy windowTitle: title ]!

Item was removed:
- DisplayObject subclass: #DisplayMedium
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Display Objects'!
- 
- !DisplayMedium commentStamp: '<historical>' prior: 0!
- I am a display object which can both paint myself on a medium (displayOn: messages), and can act as a medium myself. My chief subclass is Form.!

Item was removed:
- ----- Method: DisplayMedium>>border:width: (in category 'bordering') -----
- border: aRectangle width: borderWidth 
- 	"Paint a border whose rectangular area is defined by aRectangle. The 
- 	width of the border of each side is borderWidth. Uses black for 
- 	drawing the border."
- 
- 	self border: aRectangle width: borderWidth fillColor: Color black.
- !

Item was removed:
- ----- Method: DisplayMedium>>border:width:fillColor: (in category 'bordering') -----
- border: aRectangle width: borderWidth fillColor: aHalfTone 
- 	"Paint a border whose rectangular area is defined by aRectangle. The 
- 	width of the border of each side is borderWidth. Uses aHalfTone for 
- 	drawing the border."
- 
- 	self border: aRectangle
- 		widthRectangle: 
- 			(Rectangle
- 				left: borderWidth
- 				right: borderWidth
- 				top: borderWidth
- 				bottom: borderWidth)
- 		rule: Form over
- 		fillColor: aHalfTone!

Item was removed:
- ----- Method: DisplayMedium>>border:width:rule:fillColor: (in category 'bordering') -----
- border: aRectangle width: borderWidth rule: combinationRule fillColor: aHalfTone 
- 	"Paint a border whose rectangular area is defined by aRectangle. The 
- 	width of the border of each side is borderWidth. Uses aHalfTone for 
- 	drawing the border."
- 
- 	self border: aRectangle
- 		widthRectangle: 
- 			(Rectangle
- 				left: borderWidth
- 				right: borderWidth
- 				top: borderWidth
- 				bottom: borderWidth)
- 		rule: combinationRule
- 		fillColor: aHalfTone!

Item was removed:
- ----- Method: DisplayMedium>>border:widthRectangle:rule:fillColor: (in category 'bordering') -----
- border: aRectangle widthRectangle: insets rule: combinationRule fillColor: aHalfTone
- 	"Paint a border whose rectangular area is defined by aRectangle. The 
- 	width of each edge of the border is determined by the four coordinates 
- 	of insets. Uses aHalfTone and combinationRule for drawing the border."
- 
- 	(aRectangle areasOutside: (aRectangle insetBy: insets)) do:
- 		[:edgeStrip | self fill: edgeStrip rule: combinationRule fillColor: aHalfTone]!

Item was removed:
- ----- Method: DisplayMedium>>copyBits:from:at:clippingBox:rule:fillColor: (in category 'displaying') -----
- copyBits: sourceRect from: sourceForm at: destOrigin clippingBox: clipRect rule: rule fillColor: aForm 
- 	"Make up a BitBlt table and copy the bits."
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: DisplayMedium>>deferUpdatesIn:while: (in category 'displaying') -----
- deferUpdatesIn: aRectangle while: aBlock
- 	"DisplayScreen overrides with something more involved..."
- 	^aBlock value!

Item was removed:
- ----- Method: DisplayMedium>>drawLine:from:to:clippingBox:rule:fillColor: (in category 'displaying') -----
- drawLine: sourceForm from: beginPoint to: endPoint clippingBox: clipRect rule: anInteger fillColor: aForm 
- 	"Draw line by copying the argument, sourceForm, starting at location 
- 	beginPoint and ending at endPoint, clipped by the rectangle, clipRect. 
- 	The rule and mask for copying are the arguments anInteger and aForm."
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: DisplayMedium>>fill:fillColor: (in category 'coloring') -----
- fill: aRectangle fillColor: aForm 
- 	"Replace a rectangular area of the receiver with the pattern described by 
- 	aForm according to the rule over."
- 
- 	self fill: aRectangle rule: Form over fillColor: aForm!

Item was removed:
- ----- Method: DisplayMedium>>fill:rule:fillColor: (in category 'coloring') -----
- fill: aRectangle rule: anInteger fillColor: aForm 
- 	"Replace a rectangular area of the receiver with the pattern described by 
- 	aForm according to the rule anInteger."
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: DisplayMedium>>fillBlack (in category 'coloring') -----
- fillBlack
- 	"Set all bits in the receiver to black (ones)."
- 
- 	self fill: self boundingBox fillColor: Color black!

Item was removed:
- ----- Method: DisplayMedium>>fillBlack: (in category 'coloring') -----
- fillBlack: aRectangle 
- 	"Set all bits in the receiver's area defined by aRectangle to black (ones)."
- 
- 	self fill: aRectangle rule: Form over fillColor: Color black!

Item was removed:
- ----- Method: DisplayMedium>>fillColor: (in category 'coloring') -----
- fillColor: aColor
- 	"Set all pixels in the receiver to the color.  Must be a correct color for this depth of medium.  TK 1 Jun 96"
- 
- 	self fill: self boundingBox fillColor: aColor!

Item was removed:
- ----- Method: DisplayMedium>>fillGray (in category 'coloring') -----
- fillGray
- 	"Set all bits in the receiver to gray."
- 
- 	self fill: self boundingBox fillColor: Color gray!

Item was removed:
- ----- Method: DisplayMedium>>fillGray: (in category 'coloring') -----
- fillGray: aRectangle
- 	"Set all bits in the receiver's area defined by aRectangle to the gray mask."
- 
- 	self fill: aRectangle rule: Form over fillColor: Color gray!

Item was removed:
- ----- Method: DisplayMedium>>fillShape:fillColor: (in category 'coloring') -----
- fillShape: aShapeForm fillColor: aColor
- 	"Fill a region corresponding to 1 bits in aShapeForm with aColor"
- 
- 	^ self fillShape: aShapeForm fillColor: aColor at: 0 at 0!

Item was removed:
- ----- Method: DisplayMedium>>fillShape:fillColor:at: (in category 'coloring') -----
- fillShape: aShapeForm fillColor: aColor at: location
- 	"Fill a region corresponding to 1 bits in aShapeForm with aColor"
- 
- 	((BitBlt destForm: self sourceForm: aShapeForm fillColor: aColor
- 		combinationRule: Form paint
- 		destOrigin: location + aShapeForm offset sourceOrigin: 0 at 0
- 		extent: self extent clipRect: self boundingBox)
- 		colorMap: (Bitmap with: 0 with: 16rFFFFFFFF))
- 		copyBits!

Item was removed:
- ----- Method: DisplayMedium>>fillWhite (in category 'coloring') -----
- fillWhite
- 	"Set all bits in the form to white."
- 
- 	self fill: self boundingBox fillColor: Color white.
- !

Item was removed:
- ----- Method: DisplayMedium>>fillWhite: (in category 'coloring') -----
- fillWhite: aRectangle
- 	"Set all bits in the receiver's area defined by aRectangle to white."
- 
- 	self fill: aRectangle rule: Form over fillColor: Color white.
- !

Item was removed:
- ----- Method: DisplayMedium>>fillWithColor: (in category 'coloring') -----
- fillWithColor: aColor
- 	"Fill the receiver's bounding box with the given color."
- 
- 	self fill: self boundingBox fillColor: aColor.
- !

Item was removed:
- ----- Method: DisplayMedium>>reverse (in category 'coloring') -----
- reverse
- 	"Change all the bits in the receiver that are white to black, and the ones 
- 	that are black to white."
- 
- 	self fill: self boundingBox rule: Form reverse fillColor: (Color quickHighLight: self depth)!

Item was removed:
- ----- Method: DisplayMedium>>reverse: (in category 'coloring') -----
- reverse: aRectangle
- 	"Change all the bits in the receiver's area that intersects with aRectangle 
- 	that are white to black, and the ones that are black to white."
- 
- 	self fill: aRectangle rule: Form reverse fillColor: (Color quickHighLight: self depth)!

Item was removed:
- ----- Method: DisplayMedium>>reverse:fillColor: (in category 'coloring') -----
- reverse: aRectangle fillColor: aMask	
- 	"Change all the bits in the receiver's area that intersects with aRectangle 
- 	according to the mask. Black does not necessarily turn to white, rather it 
- 	changes with respect to the rule and the bit in a corresponding mask 
- 	location. Bound to give a surprise."
- 
- 	self fill: aRectangle rule: Form reverse fillColor: aMask!

Item was removed:
- Object subclass: #DisplayObject
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Display Objects'!
- 
- !DisplayObject commentStamp: '<historical>' prior: 0!
- The abstract protocol for most display primitives that are used by Views for presenting information on the screen.!

Item was removed:
- ----- Method: DisplayObject class>>collectionFromFileNamed: (in category 'fileIn/Out') -----
- collectionFromFileNamed: fileName 
- 	"Answer a collection of Forms read from the external file 
- 	named fileName. The file format is: fileCode, {depth, extent, offset, bits}."
- 
- 	| formList f fileCode |
- 	formList := OrderedCollection new.
- 	f := (FileStream readOnlyFileNamed: fileName) binary.
- 	fileCode := f next.
- 	fileCode = 1
- 		ifTrue: [
- 			[f atEnd] whileFalse: [formList add: (self new readFromOldFormat: f)]]
- 		ifFalse: [
- 			fileCode = 2 ifFalse: [self error: 'unknown Form file format'. ^ formList].
- 			[f atEnd] whileFalse: [formList add: (self new readFrom: f)]].
- 	f close.
- 	^ formList
- !

Item was removed:
- ----- Method: DisplayObject class>>writeCollection:onFileNamed: (in category 'fileIn/Out') -----
- writeCollection: coll onFileNamed: fileName 
- 	"Saves a collection of Forms on the file fileName in the format:
- 		fileCode, {depth, extent, offset, bits}."
- 	| file |
- 	file := FileStream newFileNamed: fileName.
- 	file binary.
- 	file nextPut: 2.  "file code = 2"
- 	coll do: [:f | f writeOn: file].
- 	file close
- "
-  | f c | c := OrderedCollection new.
- [(f := Form fromUser) boundingBox area>25] whileTrue: [c add: f].
- Form writeCollection: c onFileNamed: 'test.forms'.
- c := Form collectionFromFileNamed: 'test.forms'.
- 1 to: c size do: [:i | (c at: i) displayAt: 0@(i*100)].
- "!

Item was removed:
- ----- Method: DisplayObject>>align:with: (in category 'transforming') -----
- align: alignmentPoint with: relativePoint 
- 	"Translate the receiver's offset such that alignmentPoint aligns with 
- 	relativePoint."
- 
- 	self offset: (self offset translateBy: relativePoint - alignmentPoint)!

Item was removed:
- ----- Method: DisplayObject>>boundingBox (in category 'display box access') -----
- boundingBox
- 	"Answer the rectangular area that represents the boundaries of the 
- 	receiver's space of information."
- 
- 	^self computeBoundingBox!

Item was removed:
- ----- Method: DisplayObject>>center (in category 'display box access') -----
- center
- 
- 	^ self boundingBox center!

Item was removed:
- ----- Method: DisplayObject>>computeBoundingBox (in category 'display box access') -----
- computeBoundingBox
- 	"Answer the rectangular area that represents the boundaries of the 
- 	receiver's area for displaying information. This is the primitive for 
- 	computing the area if it is not already known."
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: DisplayObject>>display (in category 'displaying-Display') -----
- display 
- 	"Display the receiver on the Display at location 0,0."
- 
- 	self displayOn: Display!

Item was removed:
- ----- Method: DisplayObject>>displayAt: (in category 'displaying-generic') -----
- displayAt: aDisplayPoint 
- 	"Display the receiver located at aDisplayPoint with default settings for 
- 	the displayMedium, rule and halftone."
- 
- 	self displayOn: Display
- 		at: aDisplayPoint
- 		clippingBox: Display boundingBox
- 		rule: Form over
- 		fillColor: nil!

Item was removed:
- ----- Method: DisplayObject>>displayOn: (in category 'displaying-generic') -----
- displayOn: aDisplayMedium
- 	"Simple default display in order to see the receiver in the upper left 
- 	corner of screen."
- 
- 	self displayOn: aDisplayMedium at: 0 @ 0!

Item was removed:
- ----- Method: DisplayObject>>displayOn:at: (in category 'displaying-generic') -----
- displayOn: aDisplayMedium at: aDisplayPoint 
- 	"Display the receiver located at aDisplayPoint with default settings for 
- 	rule and halftone."
- 
- 	self displayOn: aDisplayMedium
- 		at: aDisplayPoint
- 		clippingBox: aDisplayMedium boundingBox
- 		rule: Form over
- 		fillColor: nil!

Item was removed:
- ----- Method: DisplayObject>>displayOn:at:clippingBox: (in category 'displaying-generic') -----
- displayOn: aDisplayMedium at: aDisplayPoint clippingBox: clipRectangle 
- 	"Display the receiver located at aDisplayPoint with default settings for 
- 	rule and halftone. Information to be displayed must be confined to the 
- 	area that intersects with clipRectangle."
- 
- 	self displayOn: aDisplayMedium
- 		at: aDisplayPoint
- 		clippingBox: clipRectangle
- 		rule: Form over
- 		fillColor: nil!

Item was removed:
- ----- Method: DisplayObject>>displayOn:at:clippingBox:rule:fillColor: (in category 'displaying-generic') -----
- displayOn: aDisplayMedium at: aDisplayPoint clippingBox: clipRectangle rule: ruleInteger fillColor: aForm
- 	"This is the basic display primitive for graphic display objects. Display 
- 	the receiver located at aDisplayPoint with rule, ruleInteger, and mask, 
- 	aForm. Information to be displayed must be confined to the area that 
- 	intersects with clipRectangle."
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: DisplayObject>>displayOn:at:rule: (in category 'displaying-generic') -----
- displayOn: aDisplayMedium at: aDisplayPoint rule: ruleInteger
- 	"Display the receiver located at aPoint with default setting for the 
- 	halftone and clippingBox."
- 
- 	self displayOn: aDisplayMedium
- 		at: aDisplayPoint
- 		clippingBox: aDisplayMedium boundingBox
- 		rule: ruleInteger
- 		fillColor: nil!

Item was removed:
- ----- Method: DisplayObject>>displayOn:transformation:clippingBox: (in category 'displaying-generic') -----
- displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle 
- 	"Display primitive for the receiver where a DisplayTransformation is 
- 	provided as an argument. Alignment is defaulted to the receiver's 
- 	rectangle. Information to be displayed must be confined to the area that 
- 	intersects with clipRectangle."
- 
- 	self displayOn: aDisplayMedium
- 		transformation: displayTransformation
- 		clippingBox: clipRectangle
- 		align: self relativeRectangle center
- 		with: self relativeRectangle center
- 		rule: Form over
- 		fillColor: nil!

Item was removed:
- ----- Method: DisplayObject>>displayOn:transformation:clippingBox:align:with: (in category 'displaying-generic') -----
- displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle align: alignmentPoint with: relativePoint 
- 	"Display primitive where a DisplayTransformation is provided as an 
- 	argument, rule is over and mask is Form black. Information to be 
- 	displayed must be confined to the area that intersects with clipRectangle."
- 
- 	self displayOn: aDisplayMedium
- 		transformation: displayTransformation
- 		clippingBox: clipRectangle
- 		align: alignmentPoint
- 		with: relativePoint
- 		rule: Form over
- 		fillColor: nil!

Item was removed:
- ----- Method: DisplayObject>>displayOn:transformation:clippingBox:align:with:rule:fillColor: (in category 'displaying-generic') -----
- displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle align: alignmentPoint with: relativePoint rule: ruleInteger fillColor: aForm 
- 	"Display the receiver where a DisplayTransformation is provided as an 
- 	argument, rule is ruleInteger and mask is aForm. Translate by 
- 	relativePoint-alignmentPoint. Information to be displayed must be 
- 	confined to the area that intersects with clipRectangle."
- 
- 	| absolutePoint |
- 	absolutePoint := displayTransformation applyTo: relativePoint.
- 	self displayOn: aDisplayMedium
- 		at: (absolutePoint - alignmentPoint) 
- 		clippingBox: clipRectangle 
- 		rule: ruleInteger 
- 		fillColor: aForm !

Item was removed:
- ----- Method: DisplayObject>>displayOn:transformation:clippingBox:fixedPoint: (in category 'displaying-generic') -----
- displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle fixedPoint: aPoint 
- 	"Display the receiver where a DisplayTransformation is provided as an 
- 	argument, rule is over and mask is Form black. No translation. 
- 	Information to be displayed must be confined to the area that intersects 
- 	with clipRectangle."
- 
- 	self displayOn: aDisplayMedium
- 		transformation: displayTransformation
- 		clippingBox: clipRectangle
- 		align: aPoint
- 		with: aPoint
- 		rule: Form over
- 		fillColor: nil!

Item was removed:
- ----- Method: DisplayObject>>displayOn:transformation:clippingBox:rule:fillColor: (in category 'displaying-generic') -----
- displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle rule: ruleInteger fillColor: aForm 
- 	"Display the receiver where a DisplayTransformation is provided as an 
- 	argument, rule is ruleInteger and mask is aForm. No translation. 
- 	Information to be displayed must be confined to the area that intersects 
- 	with clipRectangle."
- 
- 	self displayOn: aDisplayMedium
- 		transformation: displayTransformation
- 		clippingBox: clipRectangle
- 		align: self relativeRectangle origin
- 		with: self relativeRectangle origin
- 		rule: ruleInteger
- 		fillColor: aForm!

Item was removed:
- ----- Method: DisplayObject>>displayOnPort: (in category 'displaying-generic') -----
- displayOnPort: aPort 
- 	self displayOnPort: aPort at: 0 at 0!

Item was removed:
- ----- Method: DisplayObject>>displayOnPort:at:rule: (in category 'displaying-generic') -----
- displayOnPort: port at: location rule: rule
- 
- 	port copyForm: self to: location rule: rule.
- !

Item was removed:
- ----- Method: DisplayObject>>extent (in category 'accessing') -----
- extent
- 	"Answer the point that represents the width and height of the receiver's 
- 	bounding box."
- 
- 	^self boundingBox extent!

Item was removed:
- ----- Method: DisplayObject>>follow:while: (in category 'displaying-Display') -----
- follow: locationBlock while: durationBlock
-    "Move an image around on the Display. Restore the background
-    continuously without causing flashing. The argument, locationBlock,
-    supplies each new location, and the argument, durationBlock, supplies
-    true to continue, and then false to stop.
-    8/20/96 sw: call follow:while:bitsBehind: to do the real work.  Note that th
- method
-    now returns the final bits behind as method value."
-  
-    | bitsBehind loc |
-    bitsBehind := Form fromDisplay: ((loc := locationBlock value) extent: self extent).
-    ^ self follow: locationBlock while: durationBlock bitsBehind: bitsBehind startingLoc: loc!

Item was removed:
- ----- Method: DisplayObject>>follow:while:bitsBehind:startingLoc: (in category 'displaying-Display') -----
- follow: locationBlock while: durationBlock bitsBehind: initialBitsBehind startingLoc: loc
-    "Move an image around on the Display. Restore the background continuously without causing flashing. The argument, locationBlock, supplies each new location, and the argument, durationBlock, supplies true to continue or false to stop. This variant takes the bitsBehind as an input argument, and returns the final saved saved bits as method value."
- 
-    | location rect1 save1 save1Blt buffer bufferBlt newLoc rect2 bothRects |
-    location := loc.
-    rect1 := location extent: self extent.
-    save1 := initialBitsBehind.
-    save1Blt := BitBlt toForm: save1.
-    buffer := Form extent: self extent*2 depth: Display depth.  "Holds overlapping region"
-    bufferBlt := BitBlt toForm: buffer.
-    Display deferUpdates: true.
-    self displayOn: Display at: location rule: Form paint.
-    Display deferUpdates: false; forceToScreen: (location extent: self extent).
-    [durationBlock value] whileTrue: [
- 		newLoc := locationBlock value.
- 		newLoc ~= location ifTrue: [
- 			rect2 := newLoc extent: self extent.
- 			bothRects := rect1 merge: rect2.
- 			(rect1 intersects: rect2)
- 				ifTrue: [  "when overlap, buffer background for both rectangles"
- 					bufferBlt copyFrom: bothRects in: Display to: 0 at 0.
- 					bufferBlt copyFrom: save1 boundingBox in: save1 to: rect1 origin - bothRects origin.
- 					"now buffer is clean background; get new bits for save1"
- 					save1Blt copy: (0 at 0 extent: self extent) from: rect2 origin - bothRects origin in: buffer.
- 					self displayOnPort: bufferBlt at: rect2 origin - bothRects origin rule: Form paint.
- 					Display deferUpdates: true.
- 					Display copy: bothRects from: 0 at 0 in: buffer rule: Form over.
- 					Display deferUpdates: false; forceToScreen: bothRects]
- 				ifFalse: [  "when no overlap, do the simple thing (both rects might be too big)"
- 					Display deferUpdates: true.
- 					Display copy: (location extent: save1 extent) from: 0 at 0 in: save1 rule: Form over.
- 					save1Blt copyFrom: rect2 in: Display to: 0 at 0.
- 					self displayOn: Display at: newLoc rule: Form paint.
- 					Display deferUpdates: false; 
- 						forceToScreen: (location extent: save1 extent); 
- 						forceToScreen: (newLoc extent: self extent)].
- 			location := newLoc.
- 			rect1 := rect2]].
- 
- 	^ save1 displayOn: Display at: location
- !

Item was removed:
- ----- Method: DisplayObject>>followCursor (in category 'displaying-generic') -----
- followCursor
- 	"Just show the Form following the mouse. 6/21/96 tk"
- 	Cursor blank showWhile:
- 		[self follow: [Sensor cursorPoint] while: [Sensor noButtonPressed]]
- !

Item was removed:
- ----- Method: DisplayObject>>height (in category 'accessing') -----
- height
- 	"Answer the number that represents the height of the receiver's 
- 	bounding box."
- 
- 	^self boundingBox height!

Item was removed:
- ----- Method: DisplayObject>>initialExtent (in category 'display box access') -----
- initialExtent
- 	"Included here for when a FormView is being opened
- 	as a window.  (4 at 4) covers border widths."
- 
- 	^ self extent + (4 at 4) !

Item was removed:
- ----- Method: DisplayObject>>isTransparent (in category 'testing') -----
- isTransparent
- 	^ false!

Item was removed:
- ----- Method: DisplayObject>>offset (in category 'accessing') -----
- offset
- 	"Answer the amount by which the receiver should be offset when it is 
- 	displayed or its position is tested."
- 
- 	self subclassResponsibility!

Item was removed:
- ----- Method: DisplayObject>>offset: (in category 'accessing') -----
- offset: aPoint 
- 	"Set the amount by which the receiver's position is offset."
- 
- 	^self!

Item was removed:
- ----- Method: DisplayObject>>relativeRectangle (in category 'accessing') -----
- relativeRectangle
- 	"Answer a Rectangle whose top left corner is the receiver's offset position 
- 	and whose width and height are the same as the receiver."
- 
- 	^Rectangle origin: self offset extent: self extent!

Item was removed:
- ----- Method: DisplayObject>>rounded (in category 'truncation and round off') -----
- rounded
- 	"Convert the offset of the receiver to integer coordinates."
- 
- 	self offset: self offset rounded!

Item was removed:
- ----- Method: DisplayObject>>scaleBy: (in category 'transforming') -----
- scaleBy: aPoint 
- 	"Scale the receiver's offset by aPoint."
- 
- 	self offset: (self offset scaleBy: aPoint)!

Item was removed:
- ----- Method: DisplayObject>>slideFrom:to:nSteps: (in category 'displaying-Display') -----
- slideFrom: startPoint to: stopPoint nSteps: nSteps 
- 	"does not display at the first point, but does at the last"
- 	| i p delta |
- 	i := 0.
- 	p := startPoint.
- 	delta := stopPoint - startPoint // nSteps.
- 	^ self
- 		follow: [(p := p + delta) truncated]
- 		while: [(i := i + 1) < nSteps]!

Item was removed:
- ----- Method: DisplayObject>>slideFrom:to:nSteps:delay: (in category 'displaying-Display') -----
- slideFrom: startPoint to: stopPoint nSteps: nSteps delay: milliSecs
- 	"Slide this object across the display over the given number of steps, pausing for the given number of milliseconds after each step."
- 	"Note: Does not display at the first point, but does at the last."
- 
- 	| i p delta |
- 	i := 0.
- 	p := startPoint.
- 	delta := (stopPoint - startPoint) / nSteps asFloat.
- 	^ self
- 		follow: [(p := p + delta) truncated]
- 		while: [
- 			(Delay forMilliseconds: milliSecs) wait.
- 			(i := i + 1) < nSteps]
- !

Item was removed:
- ----- Method: DisplayObject>>slideFrom:to:nSteps:delay:andStay: (in category 'displaying-Display') -----
- slideFrom: startPoint to: stopPoint nSteps: nSteps delay: milliSecs andStay: stayAtEnd
- 	"Does not display at the first point, but does at the last.
- 	Moreover, if stayAtEnd is true, it leaves the dragged image at the stopPoint"
- 	| i |
- 	i := 0.
- 	^ self follow: [startPoint + ((stopPoint-startPoint) * i // nSteps)]
- 		while: [ | done |
- 				milliSecs ifNotNil: [(Delay forMilliseconds: milliSecs) wait].
- 				((done := (i := i+1) > nSteps) and: [stayAtEnd])
- 					ifTrue: [^ self "Return without clearing the image"].
- 				done not]!

Item was removed:
- ----- Method: DisplayObject>>slideWithFirstFrom:to:nSteps:delay: (in category 'displaying-Display') -----
- slideWithFirstFrom: startPoint to: stopPoint nSteps: nSteps delay: milliSecs 
- 	"Slide this object across the display over the given number of steps, 
- 	pausing for the given number of milliseconds after each step."
- 	"Note: Does display at the first point and at the last."
- 	| i p delta |
- 	i := 0.
- 	delta := stopPoint - startPoint / nSteps asFloat.
- 	p := startPoint - delta.
- 	^ self follow: [(p := p + delta) truncated]
- 		while: 
- 			[(Delay forMilliseconds: milliSecs) wait.
- 			(i := i + 1) <= nSteps]!

Item was removed:
- ----- Method: DisplayObject>>translateBy: (in category 'transforming') -----
- translateBy: aPoint 
- 	"Translate the receiver's offset."
- 
- 	self offset: (self offset translateBy: aPoint)!

Item was removed:
- ----- Method: DisplayObject>>width (in category 'accessing') -----
- width
- 	"Answer the number that represents the width of the receiver's bounding 
- 	box."
- 
- 	^self boundingBox width!

Item was removed:
- ----- Method: DisplayObject>>writeOnFileNamed: (in category 'fileIn/Out') -----
- writeOnFileNamed: fileName 
- 	"Saves the receiver on the file fileName in the format:
- 		fileCode, depth, extent, offset, bits."
- 	| file |
- 	file := FileStream newFileNamed: fileName.
- 	file binary.
- 	file nextPut: 2.  "file code = 2"
- 	self writeOn: file.
- 	file close
- "
-  | f |
- [(f := Form fromUser) boundingBox area>25] whileTrue:
- 	[f writeOnFileNamed: 'test.form'.
- 	(Form newFromFileNamed: 'test.form') display].
- "!

Item was removed:
- ----- Method: DisplayObject>>writeUncompressedOnFileNamed: (in category 'fileIn/Out') -----
- writeUncompressedOnFileNamed: fileName 
- 	"Saves the receiver on the file fileName in the format:
- 		fileCode, depth, extent, offset, bits."
- 	| file |
- 	file := FileStream newFileNamed: fileName.
- 	file binary.
- 	file nextPut: 2.  "file code = 2"
- 	self writeUncompressedOn: file.
- 	file close
- "
-  | f |
- [(f := Form fromUser) boundingBox area>25] whileTrue:
- 	[f writeUncompressedOnFileNamed: 'test.form'.
- 	(Form fromBinaryStream: (FileStream oldFileNamed: 'test.form')) display].
- "!

Item was removed:
- CharacterScanner subclass: #DisplayScanner
- 	instanceVariableNames: 'lineY foregroundColor backgroundColor defaultTextColor paragraphColor morphicOffset ignoreColorChanges lastDisplayableIndex stopConditionsMustBeReset'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Text'!
- 
- !DisplayScanner commentStamp: 'pre 10/8/2019 16:16' prior: 0!
- A DisplayScanner is an abstract class for displaying characters.
- It is splitting text into elementary chunks of displayable String/Font pairs (see scanning protocol).
- Subclasses responsibility is to handle the effective rendering of these chunks on various backends.
- 
- Instance Variables
- 	backgroundColor:		<Color>
- 	defaultTextColor:		<Color>
- 	foregroundColor:		<Color>
- 	ignoreColorChanges:		<Boolean>
- 	lastDisplayableIndex:		<Integer>
- 	lineY:		<Number>
- 	morphicOffset:		<Point>
- 	stopConditionsMustBeReset:		<Boolean>
- 
- backgroundColor
- 	- the background color for displaying next chunk of text.
- 	Note that this can be set to Color transparent, in which case no background is displayed.
- 
- defaultTextColor
- 	- the default foreground color for displaying text in absence of other text attributes specification 
- 
- foregroundColor
- 	- the foreground color for displaying next chunk of text
- 
- ignoreColorChanges
- 	- indicates that any change of color specified in text attributes shall be ignored.
- 	This is used for displaying text in a shadow mode, when dragging text for example.
- 
- lastDisplayableIndex
- 	- the index of last character to be displayed.
- 	A different index than lastIndex is required in order to avoid display of control characters.
- 	This variable must be updated by the stop condition at each inner scan loop.
- 
- lineY
- 	- the distance between destination form top and current line top
- 
- morphicOffset
- 	- an offset for displaying the lines passed from morphic to the scanner (via NewParagraph>>#displayOn:using:at:)
- 
- stopConditionsMustBeReset
- 	- indicates that it's necessary to call setStopConditions in next scan loop.
- 
- Notes:
- In order to correctly set the lastDisplayableIndex, the display scanner performs the stopCondition BEFORE displaying the string being scanned.
- This explains why the stopCondition must not reset the font immediately, but differ this reset AFTER the display, thanks to stopConditionsMustBeReset.
- !

Item was removed:
- ----- Method: DisplayScanner class>>defaultFont (in category 'queries') -----
- defaultFont
- 	^ TextStyle defaultFont!

Item was removed:
- ----- Method: DisplayScanner class>>new (in category 'instance creation') -----
- new
- 	"Use default concrete class"
- 	^(self == DisplayScanner
- 		ifTrue: [BitBltDisplayScanner]
- 		ifFalse: [self]) basicNew initialize!

Item was removed:
- ----- Method: DisplayScanner>>cr (in category 'stop conditions') -----
- cr
- 	"When a carriage return is encountered, simply increment the pointer 
- 	into the paragraph."
- 
- 	pendingKernX := 0.
- 	lastDisplayableIndex := lastIndex - 1.
- 	(lastIndex < text size and: [(text at: lastIndex) = CR and: [(text at: lastIndex+1) = Character lf]])
- 		ifTrue: [lastIndex := lastIndex + 2]
- 		ifFalse: [lastIndex := lastIndex + 1].
- 	^false!

Item was removed:
- ----- Method: DisplayScanner>>crossedX (in category 'stop conditions') -----
- crossedX
- 	"This condition will sometimes be reached 'legally' during display, when, 
- 	for instance the space that caused the line to wrap actually extends over 
- 	the right boundary. This character is allowed to display, even though it 
- 	is technically outside or straddling the clipping rectangle since it is in 
- 	the normal case not visible and is in any case appropriately clipped by 
- 	the scanner."
- 
- 	self advanceIfFirstCharOfLine.
- 	lastDisplayableIndex := lastIndex - 1.
- 	^ true !

Item was removed:
- ----- Method: DisplayScanner>>defaultTextColor (in category 'private') -----
- defaultTextColor
- 	defaultTextColor ifNil:[defaultTextColor := Color black].
- 	^defaultTextColor!

Item was removed:
- ----- Method: DisplayScanner>>defaultTextColor: (in category 'private') -----
- defaultTextColor: color
- 	defaultTextColor := color.!

Item was removed:
- ----- Method: DisplayScanner>>displayEmbeddedForm:at: (in category 'displaying') -----
- displayEmbeddedForm: aForm at: aPoint
- 	self subclassResponsibility!

Item was removed:
- ----- Method: DisplayScanner>>displayLine:offset:leftInRun: (in category 'scanning') -----
- displayLine: textLine offset: offset leftInRun: leftInRun
- 	"The call on the primitive (scanCharactersFrom:to:in:rightX:) will be interrupted according to an array of stop conditions passed to the scanner at which time the code to handle the stop condition is run and the call on the primitive continued until a stop condition returns true (which means the line has terminated).  leftInRun is the # of characters left to scan in the current run; when 0, it is time to call setStopConditions."
- 	| stopCondition nowLeftInRun startIndex string lastPos lineHeight stop |
- 	line := textLine.
- 	morphicOffset := offset.
- 	lineY := line top + offset y.
- 	lineHeight := line lineHeight.
- 	rightMargin := line rightMargin + offset x.
- 	lastIndex := line first.
- 	leftInRun <= 0 ifTrue: [self setStopConditions].
- 	leftMargin := (line leftMarginForAlignment: alignment) + offset x.
- 	destX := leftMargin.
- 	self fillTextBackground.
- 	lastDisplayableIndex := lastIndex := line first.
- 	leftInRun <= 0
- 		ifTrue: [nowLeftInRun := text runLengthFor: lastIndex]
- 		ifFalse: [nowLeftInRun := leftInRun].
- 	destY := lineY + line baseline - font ascent.
- 	runStopIndex := lastIndex + (nowLeftInRun - 1) min: line last.
- 	spaceCount := 0.
- 	string := text string.
- 	[
- 		"reset the stopping conditions of this displaying loop, and also the font."
- 		stopConditionsMustBeReset
- 			ifTrue:[self setStopConditions].
- 		
- 		"remember where this portion of the line starts"
- 		startIndex := lastIndex.
- 		lastPos := destX at destY.
- 		
- 		"find the end of this portion of the line"
- 		stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
- 						in: string rightX: rightMargin.
- 		"handle the stop condition - this will also set lastDisplayableIndex"
- 		stop := self perform: stopCondition.
- 		
- 		"display that portion of the line"
- 		lastDisplayableIndex >= startIndex ifTrue:[
- 			self displayString: string
- 				from: startIndex 
- 				to: lastDisplayableIndex 
- 				at: lastPos].
- 		
- 		"if the stop condition were true, stop the loop"
- 		stop
- 	] whileFalse.
- 	^ runStopIndex - lastIndex   "Number of characters remaining in the current run"!

Item was removed:
- ----- Method: DisplayScanner>>displayString:from:to:at: (in category 'displaying') -----
- displayString: string from: startIndex  to: stopIndex at: aPoint
- 	self subclassResponsibility!

Item was removed:
- ----- Method: DisplayScanner>>embeddedObject (in category 'stop conditions') -----
- embeddedObject
- 
- 	"We have to set the last displayed index to a value smaller than last index
- 	in order to prevent the text anchor placeholder character to be printed. For
- 	details see end of DisplayScanner>>#displayLine:offset:leftInRun:"
- 	lastDisplayableIndex := lastIndex - 1.
- 	^ super embeddedObject!

Item was removed:
- ----- Method: DisplayScanner>>embeddedObject:shouldBePlacedInDocumentGiven: (in category 'private') -----
- embeddedObject: anchoredMorphOrForm shouldBePlacedInDocumentGiven: textAnchorProperties
- 	
- 	^ textAnchorProperties hasPositionInDocument 
- 		and: [textAnchorProperties anchorLayout == #document] 
- 		and: [anchoredMorphOrForm isMorph]!

Item was removed:
- ----- Method: DisplayScanner>>endOfRun (in category 'stop conditions') -----
- endOfRun
- 	"The end of a run in the display case either means that there is actually 
- 	a change in the style (run code) to be associated with the string or the 
- 	end of this line has been reached."
- 	| runLength |
- 	lastDisplayableIndex := lastIndex.
- 	lastIndex = line last ifTrue: [^true].
- 	runLength := text runLengthFor: (lastIndex := lastIndex + 1).
- 	runStopIndex := lastIndex + (runLength - 1) min: line last.
- 	"differ reset of stopConditions and font AFTER the dispaly of last scanned string"
- 	stopConditionsMustBeReset := true.
- 	^ false!

Item was removed:
- ----- Method: DisplayScanner>>fillTextBackground (in category 'displaying') -----
- fillTextBackground
- 	self subclassResponsibility!

Item was removed:
- ----- Method: DisplayScanner>>initialize (in category 'displaying') -----
- initialize
- 	super initialize.
- 	ignoreColorChanges := false.!

Item was removed:
- ----- Method: DisplayScanner>>paddedSpace (in category 'stop conditions') -----
- paddedSpace
- 	"Each space is a stop condition when the alignment is right justified. 
- 	Padding must be added to the base width of the space according to 
- 	which space in the line this space is and according to the amount of 
- 	space that remained at the end of the line when it was composed."
- 
- 	lastDisplayableIndex := lastIndex - 1.
- 	spaceCount := spaceCount + 1.
- 	destX := destX + spaceWidth + kern + (line justifiedPadFor: spaceCount font: font).
- 	lastIndex := lastIndex + 1.
- 	pendingKernX := 0.
- 	^ false!

Item was removed:
- ----- Method: DisplayScanner>>placeEmbeddedObject:inlineGiven: (in category 'private') -----
- placeEmbeddedObject: anchoredMorphOrForm inlineGiven: textAnchorProperties
- 	
- 	| alignedPositionY position |
- 	alignedPositionY := self verticallyAlignEmbeddedObject: anchoredMorphOrForm given: textAnchorProperties.
- 	position := (destX + textAnchorProperties padding left) @ alignedPositionY.
- 	anchoredMorphOrForm isMorph
- 		ifTrue: [
- 			"We have to remove the offset passed to us from morphic as this embedded morph
- 			will only be rendered later on. We now only set the position. --pre"
- 			self flag: #fishy. "Setting the position of the morph during drawing can be problematic --pre"
- 			anchoredMorphOrForm setPositionFromLayout: position - morphicOffset]
- 		ifFalse: ["we assume this to be a form"
- 			self displayEmbeddedForm: anchoredMorphOrForm at: position].!

Item was removed:
- ----- Method: DisplayScanner>>placeEmbeddedObjectFrom: (in category 'private') -----
- placeEmbeddedObjectFrom: aTextAttribute
- 	
- 	| width anchoredMorphOrForm textAnchorProperties |
- 	anchoredMorphOrForm := aTextAttribute anchoredMorph.
- 	textAnchorProperties := self textAnchorPropertiesFor: anchoredMorphOrForm.
- 	
- 	(self embeddedObject: anchoredMorphOrForm shouldBePlacedInDocumentGiven: textAnchorProperties) 
- 			ifTrue: [^ self placeEmbeddedObjectInDocument: anchoredMorphOrForm].
- 	self placeEmbeddedObject: anchoredMorphOrForm inlineGiven: textAnchorProperties.
- 	
- 	width := textAnchorProperties consumesHorizontalSpace 
- 				ifTrue: [anchoredMorphOrForm width + textAnchorProperties horizontalPadding]
- 				ifFalse: [0].
- 	destX := destX + width + kern.
- 	
- 	^ true!

Item was removed:
- ----- Method: DisplayScanner>>placeEmbeddedObjectInDocument: (in category 'private') -----
- placeEmbeddedObjectInDocument: anchoredMorphOrForm
- 	
- 	anchoredMorphOrForm position: 
- 			anchoredMorphOrForm textAnchorProperties positionInDocument +
- 			(anchoredMorphOrForm owner textBounds origin x @ (lineY - morphicOffset y)).
- 	^ true!

Item was removed:
- ----- Method: DisplayScanner>>setFont (in category 'private') -----
- setFont 
- 	foregroundColor := self defaultTextColor.
- 	super setFont.  "Sets font and emphasis bits, and maybe foregroundColor"
- 	text ifNotNil:[destY := lineY + line baseline - font ascent]!

Item was removed:
- ----- Method: DisplayScanner>>setStopConditions (in category 'private') -----
- setStopConditions
- 	super setStopConditions.
- 	stopConditionsMustBeReset := false!

Item was removed:
- ----- Method: DisplayScanner>>tab (in category 'stop conditions') -----
- tab
- 	lastDisplayableIndex := lastIndex - 1.
- 	destX := self plainTab.
- 	lastIndex := lastIndex + 1.
- 	^ false!

Item was removed:
- ----- Method: DisplayScanner>>text:textStyle:foreground:background:fillBlt:ignoreColorChanges: (in category 'private') -----
- text: t textStyle: ts foreground: foreColor background: backColor fillBlt: blt ignoreColorChanges: shadowMode
- 	text := t.
- 	textStyle := ts. 
- 	foregroundColor := defaultTextColor := foreColor.
- 	backgroundColor := backColor.
- 	ignoreColorChanges := shadowMode!

Item was removed:
- ----- Method: DisplayScanner>>textColor: (in category 'text attributes') -----
- textColor: textColor
- 	ignoreColorChanges ifTrue: [^ self].
- 	foregroundColor := textColor!

Item was removed:
- ----- Method: DisplayScanner>>verticallyAlignEmbeddedObject:given: (in category 'private') -----
- verticallyAlignEmbeddedObject: aMorphOrForm given: textAnchorProperties
- 
- 	| alignedPositionY positionInLine morphPosition padding morphBaselineGetter |
- 	alignedPositionY := lineY + line baseline.
- 	positionInLine := textAnchorProperties verticalAlignmentLine.
- 	positionInLine = #top 		ifTrue: 	[alignedPositionY := alignedPositionY - font ascent].
- 	positionInLine = #center 	ifTrue: 	[alignedPositionY := (alignedPositionY - (font ascent / 2)) floor].
- 	positionInLine = #bottom	ifTrue: 	[alignedPositionY := alignedPositionY + font descent].
- 	"#baseline does not require adjustments"
- 	
- 	padding := textAnchorProperties padding.
- 	morphBaselineGetter := textAnchorProperties morphBaselineGetter.
- 	morphPosition := textAnchorProperties verticalAlignmentMorph.
- 	morphPosition = #top		ifTrue: [alignedPositionY := alignedPositionY + padding top].
- 	morphPosition = #center 	ifTrue: [alignedPositionY := (alignedPositionY - (aMorphOrForm height / 2)) floor].
- 	morphPosition = #baseline	ifTrue: [
- 			alignedPositionY := alignedPositionY - (morphBaselineGetter ifNotNil: [:getter | 
- 				aMorphOrForm perform: getter] ifNil: [0])].
- 	morphPosition = #bottom 	ifTrue: [alignedPositionY := (alignedPositionY - aMorphOrForm height) - padding bottom].
- 	"We only apply padding to the position the morph is aligned to."	
- 	
- 	^ alignedPositionY!

Item was removed:
- Form subclass: #DisplayScreen
- 	instanceVariableNames: 'clippingBox extraRegions'
- 	classVariableNames: 'DeferringUpdates DisplayChangeSignature DisplayIsFullScreen PlatformScaleFactor RelativeScaleFactorEnabled'
- 	poolDictionaries: ''
- 	category: 'Graphics-Display Objects'!
- 
- !DisplayScreen commentStamp: '<historical>' prior: 0!
- There is only one instance of me, Display. It is a global and is used to handle general user requests to deal with the whole display screen. 
- 	Although I offer no protocol, my name provides a way to distinguish this special instance from all other Forms. This is useful, for example, in dealing with saving and restoring the system.
- 	To change the depth of your Display...
- 		Display newDepth: 16.
- 		Display newDepth: 8.
- 		Display newDepth: 1.
- Valid display depths are 1, 2, 4, 8, 16 and 32.  It is suggested that you run with your monitors setting the same, for better speed and color fidelity.  Note that this can add up to 4Mb for the Display form.  Finally, note that newDepth: ends by executing a 'ControlManager restore' which currently terminates the active process, so nothing that follows in the doit will get executed.
- 
- Depths 1, 2, 4 and 8 bits go through a color map to put color on the screen, but 16 and 32-bit color use the pixel values directly for RGB color (5 and 8 bits per, respectivlely).  The color choice an be observed by executing Color fromUser in whatever depth you are using.
- !

Item was removed:
- ----- Method: DisplayScreen class>>actualScreenDepth (in category 'snapshots') -----
- actualScreenDepth
- 	<primitive: 'primitiveScreenDepth'>
- 	^ Display depth!

Item was removed:
- ----- Method: DisplayScreen class>>actualScreenScaleFactor (in category 'snapshots') -----
- actualScreenScaleFactor
- 	<primitive: #primitiveScreenScaleFactor>
- 
- 	^ Float nan "Unknown scale factor"!

Item was removed:
- ----- Method: DisplayScreen class>>actualScreenSize (in category 'snapshots') -----
- actualScreenSize
- 	<primitive: 106>
- 	^ 640 at 480!

Item was removed:
- ----- Method: DisplayScreen class>>boundingBox (in category 'display box access') -----
- boundingBox
- 	"Answer the bounding box for the form representing the current display 
- 	screen."
- 
- 	^Display boundingBox!

Item was removed:
- ----- Method: DisplayScreen class>>checkForNewScreenScaleFactor (in category 'display box access') -----
- checkForNewScreenScaleFactor
- 	"Check whether the platform's scale factor has changed and if so take appropriate actions"
- 
- 	Display platformScaleFactor: DisplayScreen actualScreenScaleFactor.!

Item was removed:
- ----- Method: DisplayScreen class>>checkForNewScreenSize (in category 'display box access') -----
- checkForNewScreenSize
- 	"Check whether the screen size has changed and if so take appropriate actions"
- 
- 	Display isVirtualScreen ifTrue: [^Display checkForNewScreenSize].
- 
- 	Display extent = DisplayScreen actualScreenSize
- 		ifFalse: [Display restore].!

Item was removed:
- ----- Method: DisplayScreen class>>depth:width:height:fullscreen: (in category 'display box access') -----
- depth: depthInteger width: widthInteger height: heightInteger fullscreen: aBoolean
- 	"Force Squeak's window (if there's one) into a new size and depth."
- 	"DisplayScreen depth: 8 width: 1024 height: 768 fullscreen: false"
- 
- 	"August 2019: This method will be deprecated in the future!! Use the HostWindowPlugin instead if possible.
- 	
- 	This method is still the only way to change the size of the display, when the image is started with the -vm-display-none flag, because
- (1) you still have a Display, hurray!!, and (2) HostWindowPlugin will refuse to notice that, because you don't have any windows."
- 
- 	<primitive: 92>
- 	self primitiveFailed!

Item was removed:
- ----- Method: DisplayScreen class>>displayIsFullScreen (in category 'screen modes') -----
- displayIsFullScreen
- 
- 	^ DisplayIsFullScreen ifNil: [DisplayIsFullScreen := false]!

Item was removed:
- ----- Method: DisplayScreen class>>fullScreenOff (in category 'screen modes') -----
- fullScreenOff
- 
- 	Display fullScreenMode: (DisplayIsFullScreen := false).
- 	self checkForNewScreenSize.
- !

Item was removed:
- ----- Method: DisplayScreen class>>fullScreenOn (in category 'screen modes') -----
- fullScreenOn
- 
- 	Display fullScreenMode: (DisplayIsFullScreen := true).
- 	self checkForNewScreenSize.!

Item was removed:
- ----- Method: DisplayScreen class>>hostWindowExtent: (in category 'host window access') -----
- hostWindowExtent: aPoint
- 	
- 	[self
- 		primitiveWindow: self hostWindowIndex
- 		width: aPoint x
- 		height: aPoint y]
- 			on: Error "primitive failed such as in headless mode"
- 			do: [:ex | "ignore" ].
- 			
- 	Smalltalk windowSystemName = 'X11'
- 		ifTrue: [100 milliSeconds wait].
- 		
- 	^ self actualScreenSize!

Item was removed:
- ----- Method: DisplayScreen class>>hostWindowIndex (in category 'host window access') -----
- hostWindowIndex
- 	"By convention, the reference to the primary Squeak display window is 1.
- 	The host window plugin may use different conventions for references to
- 	windows. In general, the handles for references to host windows should be
- 	considered as meaningful only to the VM plugin, with host window index 1
- 	being a special case of a well known handle value."
- 
- 	^ 1!

Item was removed:
- ----- Method: DisplayScreen class>>hostWindowTitle: (in category 'host window access') -----
- hostWindowTitle: aString
- 
- 	[self
- 		primitiveWindow: self hostWindowIndex
- 		title: aString squeakToUtf8]
- 			on: Error "primitive failed such as in headless mode"
- 			do: [:ex | "ignore"].!

Item was removed:
- ----- Method: DisplayScreen class>>isDeferringUpdates (in category 'testing') -----
- isDeferringUpdates
- 
- 	^ DeferringUpdates == true!

Item was removed:
- ----- Method: DisplayScreen class>>primitiveWindow:title: (in category 'primitives - host window access') -----
- primitiveWindow: id title: titleString
- 
- 	<primitive: 'primitiveHostWindowTitle' module: 'HostWindowPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: DisplayScreen class>>primitiveWindow:width:height: (in category 'primitives - host window access') -----
- primitiveWindow: id width: width height: height
- 
- 	<primitive: 'primitiveHostWindowSizeSet' module: 'HostWindowPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: DisplayScreen class>>relativeScaleFactor (in category 'preferences') -----
- relativeScaleFactor
- 	<preference: 'Scale Factor'
- 		categoryList: #(Morphic Tools visuals Accessibility)
- 		description: 'Set the size of fonts and tools according to the pixels-per-inch of your display. Can be used to zoom in even further.'
- 		type: #String>
- 
- 	^ Display relativeUiScaleFactor!

Item was removed:
- ----- Method: DisplayScreen class>>relativeScaleFactor: (in category 'preferences') -----
- relativeScaleFactor: aFloatString
- 
- 	Display relativeUiScaleFactor: (aFloatString ifNotNil: [:s | s asNumber] ifNil: [1.0]).!

Item was removed:
- ----- Method: DisplayScreen class>>relativeScaleFactorEnabled (in category 'preferences') -----
- relativeScaleFactorEnabled
- 	<preference: 'Show Relative Scale Factor'
- 		categoryList: #(Morphic Tools visuals)
- 		description: 'When true, 100% means as-the-platform/monitor-demands, which is typical for macOS. When false, 100% means pixel-perfect, which is typical for Windows. Only works if #platformScaleFactorKnown.'
- 		type: #Boolean>
- 
- 	"Note that we set the default to 'false' because pixels are very prominent in the Morphic programming model. So it makes sense to communcate this kind of pixel scaling openly and thus not hide the #platformScaleFactor from the user."
- 	^ RelativeScaleFactorEnabled ifNil: [false].!

Item was removed:
- ----- Method: DisplayScreen class>>relativeScaleFactorEnabled: (in category 'preferences') -----
- relativeScaleFactorEnabled: aBoolean
- 
- 	RelativeScaleFactorEnabled := Display platformScaleFactorKnown and: [aBoolean ifNil: [false]].!

Item was removed:
- ----- Method: DisplayScreen class>>setNewScreenSize: (in category 'display box access') -----
- setNewScreenSize: aPoint
- 	"Ensure that the Display is set to the given extent."
- 	
- 	self hostWindowExtent: aPoint.
- 	self checkForNewScreenSize.
- 	
- 	"In the Windows version of the host window plugin, the extent currently includes window decorations. Therefore, we need two attempts to ensure that the Display extent is aPoint. Note that this is a bug in the plugin."
- 	(Display extent x < aPoint x or: [Display extent y < aPoint y]) ifTrue: [
- 		self hostWindowExtent: 2*aPoint - Display extent.
- 		self checkForNewScreenSize].!

Item was removed:
- ----- Method: DisplayScreen class>>toggleFullScreen (in category 'screen modes') -----
- toggleFullScreen
- 	"Toggle between full screen and windowed mode."
- 	
- 	self displayIsFullScreen
- 		ifTrue: [self fullScreenOff]
- 		ifFalse: [self fullScreenOn].!

Item was removed:
- ----- Method: DisplayScreen>>addExtraRegion:for: (in category 'displaying') -----
- addExtraRegion: aRectangle for: regionDrawer
- 	"Register the given rectangle as a region which is drawn by the specified region drawer. The region will be excluded from any updates when #forceDamageToScreen: is called. Note that the rectangle is only valid for a single update cycle; once #forceDamageToScreen: has been called, the region drawer and its region are being removed from the list"
- 	extraRegions ifNil:[extraRegions := #()].
- 	extraRegions := extraRegions copyWith: (Array with: regionDrawer with: aRectangle).
- !

Item was removed:
- ----- Method: DisplayScreen>>beDisplay (in category 'private') -----
- beDisplay
- 	"Primitive. Tell the interpreter to use the receiver as the current display 
- 	image. Fail if the form is too wide to fit on the physical display. 
- 	Essential. See Object documentation whatIsAPrimitive."
- 
- 	<primitive: 102>
- 	self primitiveFailed!

Item was removed:
- ----- Method: DisplayScreen>>boundingBox (in category 'other') -----
- boundingBox
- 	clippingBox == nil
- 		ifTrue: [clippingBox := super boundingBox].
- 	^ clippingBox!

Item was removed:
- ----- Method: DisplayScreen>>clippingTo:do: (in category 'other') -----
- clippingTo: aRect do: aBlock
- 	"Display clippingTo: Rectangle fromUser do:
- 	[ScheduledControllers restore: Display fullBoundingBox]"
- 	| saveClip |
- 	saveClip := clippingBox.
- 	clippingBox := aRect.
- 	aBlock value.
- 	clippingBox := saveClip!

Item was removed:
- ----- Method: DisplayScreen>>copyBits:from:at:clippingBox:rule:fillColor: (in category 'displaying') -----
- copyBits: rect from: sf at: destOrigin clippingBox: clipRect rule: cr fillColor: hf 
- 	(BitBlt
- 		destForm: self
- 		sourceForm: sf
- 		fillColor: hf
- 		combinationRule: cr
- 		destOrigin: destOrigin
- 		sourceOrigin: rect origin
- 		extent: rect extent
- 		clipRect: (clipRect intersect: clippingBox)) copyBits!

Item was removed:
- ----- Method: DisplayScreen>>copyBits:from:at:clippingBox:rule:fillColor:map: (in category 'displaying') -----
- copyBits: rect from: sf at: destOrigin clippingBox: clipRect rule: cr fillColor: hf map: map
- 	((BitBlt
- 		destForm: self
- 		sourceForm: sf
- 		fillColor: hf
- 		combinationRule: cr
- 		destOrigin: destOrigin
- 		sourceOrigin: rect origin
- 		extent: rect extent
- 		clipRect: (clipRect intersect: clippingBox)) colorMap: map) copyBits!

Item was removed:
- ----- Method: DisplayScreen>>copyFrom: (in category 'private') -----
- copyFrom: aForm
- 	"Take on all state of aForm, with complete sharing"
- 
- 	super copyFrom: aForm.
- 	clippingBox := super boundingBox!

Item was removed:
- ----- Method: DisplayScreen>>currentScaleError (in category 'scale factor') -----
- currentScaleError
- 	"Documentation and debugging only. The scale error originates in rounding errors while rendering the standard TTCFont font into pixels or using a pre-rendered StrikeFont in the first place.
- 	
- 	Display currentScaleError
- 	"
- 	
- 	^ RealEstateAgent scaleFactor - self uiScaleFactor
- 	
- "
- | errors current |
- errors := OrderedDictionary new.
- current := Display uiScaleFactor.
- 1.0 to: 3.0 by: 0.25 do: [:s |
- 	Display uiScaleFactor: s.
- 	errors at: s put: Display currentScaleError].
- Display uiScaleFactor: current.
- errors explore.
- "!

Item was removed:
- ----- Method: DisplayScreen>>defaultBitBltClass (in category 'blitter defaults') -----
- defaultBitBltClass
- 	"Return the BitBlt version to use when I am active"
- 	^BitBlt!

Item was removed:
- ----- Method: DisplayScreen>>defaultWarpBltClass (in category 'blitter defaults') -----
- defaultWarpBltClass
- 	"Return the WarpBlt version to use when I am active"
- 	^WarpBlt!

Item was removed:
- ----- Method: DisplayScreen>>deferUpdates: (in category 'other') -----
- deferUpdates: aBoolean
- 	"Set the deferUpdates flag in the virtual machine. When this flag is true, BitBlt operations on the Display are not automatically propagated to the screen. If this underlying platform does not support deferred updates, this primitive will fail. Answer whether updates were deferred before if the primitive succeeds, nil if it fails.
- 	
- 	Note that when disabling deferred upates again after modifying the receiver, it is advisable to call #forceDisplayUpdate so that the deferred updates can actually be displayed on the screen."
- 
- 	| wasDeferred |
- 	wasDeferred := DeferringUpdates == true.
- 	DeferringUpdates := aBoolean.
- 	^(self primitiveDeferUpdates: aBoolean) ifNotNil: [wasDeferred]!

Item was removed:
- ----- Method: DisplayScreen>>deferUpdatesIn:while: (in category 'other') -----
- deferUpdatesIn: aRectangle while: aBlock
- 	| result |
- 	((self deferUpdates: true) ifNil: [true]) ifTrue: [
- 		"Outer call did set this already. Ignore here."
- 		^ aBlock value].
- 	result := aBlock value.
- 	self deferUpdates: false.
- 	self forceToScreen: aRectangle.
- 	^result!

Item was removed:
- ----- Method: DisplayScreen>>displayChangeSignature (in category 'other') -----
- displayChangeSignature
- 
- 	^DisplayChangeSignature!

Item was removed:
- ----- Method: DisplayScreen>>findAnyDisplayDepth (in category 'private') -----
- findAnyDisplayDepth
- 	"Return any display depth that is supported on this system."
- 	^self findAnyDisplayDepthIfNone:[
- 		"Ugh .... now this is a biggie - a system that does not support
- 		any of the Squeak display depths at all."
- 		Smalltalk
- 			logSqueakError:'Fatal error: This system has no support for any display depth at all.'
- 			inContext: thisContext .
- 		Smalltalk quitPrimitive. "There is no way to continue from here"
- 	].!

Item was removed:
- ----- Method: DisplayScreen>>findAnyDisplayDepthIfNone: (in category 'private') -----
- findAnyDisplayDepthIfNone: aBlock
- 	"Return any display depth that is supported on this system.
- 	If there is none, evaluate aBlock."
- 	#(1 2 4 8 16 32 -1 -2 -4 -8 -16 -32) do:[:bpp|
- 		(self supportsDisplayDepth: bpp) ifTrue:[^bpp].
- 	].
- 	^aBlock value!

Item was removed:
- ----- Method: DisplayScreen>>flash: (in category 'displaying') -----
- flash: aRectangle 
- 	"Flash the area of the screen defined by the given rectangle."
- 
- 	self reverse: aRectangle.
- 	self forceDisplayUpdate.
- 	(Delay forMilliseconds: 50) wait.
- 	self reverse: aRectangle.
- 	self forceDisplayUpdate.
- !

Item was removed:
- ----- Method: DisplayScreen>>flash:andWait: (in category 'displaying') -----
- flash: aRectangle andWait: msecs
- 	"Flash the area of the screen defined by the given rectangle."
- 
- 	self reverse: aRectangle.
- 	self forceDisplayUpdate.
- 	(Delay forMilliseconds: msecs) wait.
- 	self reverse: aRectangle.
- 	self forceDisplayUpdate.
- 	(Delay forMilliseconds: msecs) wait.
- !

Item was removed:
- ----- Method: DisplayScreen>>flashAll:andWait: (in category 'displaying') -----
- flashAll: rectangleList andWait: msecs
- 	"Flash the areas of the screen defined by the given rectangles."
- 
- 	rectangleList do: [:aRectangle | self reverse: aRectangle].
- 	self forceDisplayUpdate.
- 	(Delay forMilliseconds: msecs) wait.
- 	rectangleList do: [:aRectangle | self reverse: aRectangle].
- 	self forceDisplayUpdate.
- 	(Delay forMilliseconds: msecs) wait.
- !

Item was removed:
- ----- Method: DisplayScreen>>forceDamageToScreen: (in category 'displaying') -----
- forceDamageToScreen: allDamage
- 	"Force all the damage rects to the screen."
- 	| regions rectList |
- 	rectList := allDamage.
- 	"Note: Reset extra regions at the beginning to prevent repeated errors"
- 	regions := extraRegions.
- 	extraRegions := nil.
- 	regions ifNotNil:[
- 		"exclude extra regions"
- 		regions do:[:drawerAndRect| | excluded remaining |
- 			excluded := drawerAndRect at: 2.
- 			remaining := WriteStream on: #().
- 			rectList do:[:r|
- 				remaining nextPutAll:(r areasOutside: excluded)].
- 			rectList := remaining contents].
- 	].
- 	rectList do:[:r| self forceToScreen: r].
- 	regions ifNotNil:[
- 		"Have the drawers paint what is needed"
- 		regions do:[:drawerAndRect| (drawerAndRect at: 1) forceToScreen].
- 	].!

Item was removed:
- ----- Method: DisplayScreen>>forceDisplayUpdate (in category 'other') -----
- forceDisplayUpdate
- 	"On platforms that buffer screen updates, force the screen to be updated immediately. On other platforms, or if the primitive is not implemented, do nothing."
- 
- 	<primitive: 231>
- 	"do nothing if primitive fails"!

Item was removed:
- ----- Method: DisplayScreen>>forceToScreen (in category 'other') -----
- forceToScreen
- 	"Force the entire display area to the screen"
- 	^self forceToScreen: self boundingBox!

Item was removed:
- ----- Method: DisplayScreen>>forceToScreen: (in category 'other') -----
- forceToScreen: aRectangle
- 	"Force the given rectangular section of the Display to be copied to the screen. The primitive call does nothing if the primitive is not implemented. Typically used when the deferUpdates flag in the virtual machine is on; see deferUpdates:."
- 
- 	self primShowRectLeft: aRectangle left
- 		right: aRectangle right
- 		top: aRectangle top
- 		bottom: aRectangle bottom.
- !

Item was removed:
- ----- Method: DisplayScreen>>fullBoundingBox (in category 'other') -----
- fullBoundingBox
- 	^ super boundingBox!

Item was removed:
- ----- Method: DisplayScreen>>fullScreenMode: (in category 'other') -----
- fullScreenMode: aBoolean
- 	"On platforms that support it, set full-screen mode to the value of the argument. (Note: you'll need to restore the Display after calling this primitive."
- 	"Display fullScreenMode: true. Display newDepth: Display depth"
- 
- 	<primitive: 233>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: DisplayScreen>>height (in category 'other') -----
- height
- 	^ self boundingBox height!

Item was removed:
- ----- Method: DisplayScreen>>isDisplayScreen (in category 'testing') -----
- isDisplayScreen
- 	^true!

Item was removed:
- ----- Method: DisplayScreen>>newDepth: (in category 'other') -----
- newDepth: pixelSize
- "
- 	Display newDepth: 8.
- 	Display newDepth: 1.
- "
- 	| area need |
- 	
- 	(self supportsDisplayDepth: pixelSize)
- 		ifFalse:[^self inform:'Display depth ', pixelSize printString, ' is not supported on this system'].
- 
- 	pixelSize = self nativeDepth ifTrue: [^ self  "no change"].
- 	pixelSize abs < self depth ifFalse:
- 		["Make sure there is enough space"
- 		area := self boundingBox area. "pixels"
- 
- 		need := (area * (pixelSize abs - self depth) // 8)  "new bytes needed"
- 				+ Smalltalk lowSpaceThreshold.
- 		(Smalltalk garbageCollectMost <= need
- 			and: [Smalltalk garbageCollect <= need])
- 			ifTrue: [self error: 'Insufficient free space']].
- 
- 	Display setExtent: Display extent depth: pixelSize.
- 	Display beDisplay.
- 
- 	Project current ifNotNil: [:p |
- 		p
- 			displayDepthChanged;
- 			displaySizeChanged].!

Item was removed:
- ----- Method: DisplayScreen>>objectForDataStream: (in category 'disk I/O') -----
- objectForDataStream: refStrm
- 	| dp |
- 	"I am about to be written on an object file.  Write a reference to the Display in the other system instead.  "
- 
- 	"A path to me"
- 	dp := DiskProxy global: #Display selector: #yourself args: #().
- 	refStrm replace: self with: dp.
- 	^ dp
- !

Item was removed:
- ----- Method: DisplayScreen>>platformScaleFactor (in category 'scale factor') -----
- platformScaleFactor
- 	"Answers the platform's (and thus monitor's) current scale factor as last reported via VM primitive. See #checkForNewScreenScaleFactor. For robustness, always report a sensible value. However, you should check via #platformScaleFactorKnown whether this value is reliable."
- 
- 	^ PlatformScaleFactor ifNil: [1.0 "Primitive not ready."]!

Item was removed:
- ----- Method: DisplayScreen>>platformScaleFactor: (in category 'scale factor') -----
- platformScaleFactor: aFloatOrNil
- 	"Report a new scale factor from the platform to the image. This can happen if you move Squeak's window between monitors with different pixels-per-inch. On some platforms, you can also set a scale factor independent of monitor PPI. Note that the user might have scaled the image regardless of the previous platform scale factor."
- 
- 	| old new |
- 	(aFloatOrNil isNil or: [aFloatOrNil isNaN]) ifTrue: [
- 		"Ignore. Primitive not ready (anymore)."
- 		PlatformScaleFactor := nil.
- 		^ self].
- 	PlatformScaleFactor ifNil: [
- 		"First time. Ignore. Assume that the user scaled manually until now."
- 		"self assert: [aFloatOrNil notNil]."
- 		"self assert: [aFloatOrNil isNaN not]."
- 		PlatformScaleFactor := aFloatOrNil.
- 		^ self].
- 	
- 	(old := self platformScaleFactor) = (new := aFloatOrNil) ifTrue: [^ self].
- 	PlatformScaleFactor := new.
- 	self uiScaleFactor: self uiScaleFactor * (new/old).!

Item was removed:
- ----- Method: DisplayScreen>>platformScaleFactorKnown (in category 'scale factor') -----
- platformScaleFactorKnown
- 	"Tools can help users understand whether Squeak will adjust the scale factor automatically or whether they have to scale manually. See class-side's #actualScreenScaleFactor and also #relativeUiScaleFactor."
- 
- 	^ PlatformScaleFactor notNil!

Item was removed:
- ----- Method: DisplayScreen>>primRetryShowRectLeft:right:top:bottom: (in category 'private') -----
- primRetryShowRectLeft: l right: r top: t bottom: b
- 	"Copy the given rectangular section of the Display to to the screen. This primitive is not implemented on all platforms. Do nothing if it fails. "
- 
- 	<primitive: 127>
- 	"do nothing if primitive fails"
- !

Item was removed:
- ----- Method: DisplayScreen>>primShowRectLeft:right:top:bottom: (in category 'private') -----
- primShowRectLeft: l right: r top: t bottom: b
- 	"Copy the given rectangular section of the Display to to the screen. This primitive is not implemented on all platforms. If this fails, retry integer coordinates."
- 
- 	<primitive: 127>
- 	"if this fails, coerce coordinates to integers and try again"
- 	self primRetryShowRectLeft: l truncated
- 		right: r rounded
- 		top: t truncated
- 		bottom: b rounded.
- !

Item was removed:
- ----- Method: DisplayScreen>>primSupportsDisplayDepth: (in category 'other') -----
- primSupportsDisplayDepth: pixelDepth
- 	"Return true if this pixel depth is supported on the current host platform.
- 	Primitive. Optional."
- 	<primitive: 91>
- 	^#(1 2 4 8 16 32) includes: pixelDepth!

Item was removed:
- ----- Method: DisplayScreen>>primitiveDeferUpdates: (in category 'other') -----
- primitiveDeferUpdates: aBoolean
- 	"Set the deferUpdates flag in the virtual machine. When this flag is true, BitBlt operations on the Display are not automatically propagated to the screen. If this underlying platform does not support deferred updates, this primitive will fail. Answer the receiver if the primitive succeeds, nil if it fails."
- 
- 	<primitive: 126>
- 	^ nil  "answer nil if primitive fails"
- !

Item was removed:
- ----- Method: DisplayScreen>>relativeUiScaleFactor (in category 'scale factor') -----
- relativeUiScaleFactor
- 	"Answers the scale factor as perceived by the user. Note that this concept might be platform-dependent. On Windows, for example, 100% means pixel-perfect while on macOS 100% means as-the-monitor-demands. So, Retina displays are effectively scaled even if the user sees 100% in a Choose-Your-Scale dialog."
- 	
- 	^ self class relativeScaleFactorEnabled
- 		ifTrue: [ "macOS" self uiScaleFactor / self platformScaleFactor ]
- 		ifFalse: [ "Windows" self uiScaleFactor ]!

Item was removed:
- ----- Method: DisplayScreen>>relativeUiScaleFactor: (in category 'scale factor') -----
- relativeUiScaleFactor: aFloat
- 	
- 	^ self class relativeScaleFactorEnabled
- 		ifTrue: [ "macOS" self uiScaleFactor: aFloat * self platformScaleFactor ]
- 		ifFalse: [ "Windows" self uiScaleFactor: aFloat ]!

Item was removed:
- ----- Method: DisplayScreen>>release (in category 'initialize-release') -----
- release
- 	"I am no longer Display. Release any resources if necessary"!

Item was removed:
- ----- Method: DisplayScreen>>restore (in category 'other') -----
- restore
- 
- 	| priorBits |
- 	priorBits := bits. "Must avoid to be GC'ed!!"
- 		self setExtent: self class actualScreenSize depth: self nativeDepth.
- 		self beDisplay.
- 	priorBits := nil. "Documentation only."
- 	
- 	Project current ifNotNil: [:p| p displaySizeChanged].!

Item was removed:
- ----- Method: DisplayScreen>>restoreAfter: (in category 'other') -----
- restoreAfter: aBlock
- 	"Evaluate the block, wait for a mouse click, and then restore the screen."
- 
- 	aBlock ensure: [
- 		Sensor waitButton.
- 		self restore].!

Item was removed:
- ----- Method: DisplayScreen>>setExtent:depth: (in category 'private') -----
- setExtent: aPoint depth: bitsPerPixel  "DisplayScreen startUp"
- 	"This method is critical.  If the setExtent fails, there will be no
- 	proper display on which to show the error condition..."
- 	"ar 5/1/1999: ... and that is exactly why we check for the available display depths first."
- 
- 	"RAA 27 Nov 99 - if depth and extent are the same and acceptable, why go through this.
- 	also - record when we change so worlds can tell if it is time to repaint"
- 
- 	(depth == bitsPerPixel and: [aPoint = self extent and: 
- 					[self supportsDisplayDepth: bitsPerPixel]]) ifFalse: [
- 		bits := nil.  "Free up old bitmap in case space is low"
- 		DisplayChangeSignature := (DisplayChangeSignature ifNil: [0]) + 1.
- 		(self supportsDisplayDepth: bitsPerPixel)
- 			ifTrue:[super setExtent: aPoint depth: bitsPerPixel]
- 			ifFalse:[(self supportsDisplayDepth: bitsPerPixel negated)
- 				ifTrue:[super setExtent: aPoint depth: bitsPerPixel negated]
- 				ifFalse:["Search for a suitable depth"
- 					super setExtent: aPoint depth: self findAnyDisplayDepth]].
- 	].
- 	clippingBox := super boundingBox!

Item was removed:
- ----- Method: DisplayScreen>>shrink (in category 'initialize-release') -----
- shrink 
- 	"Reduce the memory footprint of this display object before being stored into the .image file."
- 	
- 	self setExtent: 240 at 120 depth: self depth.!

Item was removed:
- ----- Method: DisplayScreen>>supportedDisplayDepths (in category 'other') -----
- supportedDisplayDepths
- 	"Return all pixel depths supported on the current host platform."
- 	^#(1 2 4 8 16 32 -1 -2 -4 -8 -16 -32) select: [:d | self supportsDisplayDepth: d]!

Item was removed:
- ----- Method: DisplayScreen>>supportsDisplayDepth: (in category 'other') -----
- supportsDisplayDepth: pixelDepth
- 	"Return true if this pixel depth is supported on the current host platform."
- 	Smalltalk platformName = 'Mac OS' ifTrue: [^pixelDepth abs = 32]. "Work around VM bug"
- 	^self primSupportsDisplayDepth: pixelDepth!

Item was removed:
- ----- Method: DisplayScreen>>uiScaleFactor (in category 'scale factor') -----
- uiScaleFactor
- 	"Answers the current scale factor used to configure all widgets, tools, or windows to be prepared for the current rendering system, i.e., BitBlt. Note that 1.0 is usually the design space for pixel-based metrics such as #borderWidth or #layoutInset (if not based on font metrics)."
- 	
- 	^ UserInterfaceTheme current isTTCBased
- 		ifTrue: [TextStyle pixelsPerInch / 96.0 "Hide rounding errors in TTCFont >> #height."]
- 		ifFalse: [RealEstateAgent scaleFactor roundTo: 0.25 "Force 25% steps. See, e.g., #doScale150."].!

Item was removed:
- ----- Method: DisplayScreen>>uiScaleFactor: (in category 'scale factor') -----
- uiScaleFactor: aFloat
- 	"Sets the effective scale factor for the user interface, i.e., all widgets, tools, and windows. Note that the user can override the #platformScaleFactor, which is just a hint recommended by the platform."
- 
- 	| oldPixelFactor newPixelFactor newScaleFactor |
- 	newScaleFactor := aFloat max: 0.75.
- 	
- 	(UserInterfaceTheme current canFakeScaleFactor: newScaleFactor) ifTrue: [
- 		self flag: #isTTCBased.
- 		^ UserInterfaceTheme current applyScaled: newScaleFactor].
- 	
- 	newScaleFactor = 0.75 ifTrue: [(Project uiManager
- 		confirm: ('You are currently using <b>TrueType fonts</b>. Your requested scale factor of <b>{1}%</b> looks better using pre-rendered <b>pixel fonts</b>.<br><br>Do you want to switch to pixel fonts now?' translated format: {(newScaleFactor * 100) rounded}) asTextFromHtml
- 		title: 'Blurry Fonts Detected' translated) == true
- 			ifTrue: [UserInterfaceTheme cleanUpAndReset. ^ self uiScaleFactor: newScaleFactor]].
- 	
- 	"Do nothing if the factor is unchanged. For comparison, use actual pixel-based scale factor to account for rounding errors, instead of #uiScaleFactor."
- 	oldPixelFactor := RealEstateAgent scaleFactor. 
- 	newScaleFactor = oldPixelFactor ifTrue: [^ self].
- 		
- 	"Update system's PPI to then compute the new pixel-based scale factor."
- 	TextStyle pixelsPerInch: 96.0 * newScaleFactor.
- 	newPixelFactor := RealEstateAgent resetScaleFactor; scaleFactor.
- 	
- 	"Let the current project (kind) decide how to update the system."
- 	Project current ifNotNil: [:p | p displayScaleChangedFrom: oldPixelFactor to: newPixelFactor].!

Item was removed:
- ----- Method: DisplayScreen>>usableArea (in category 'other') -----
- usableArea
- 	"Answer the usable area of the receiver.  5/22/96 sw."
- 
- 	^ self boundingBox deepCopy!

Item was removed:
- ----- Method: DisplayScreen>>width (in category 'other') -----
- width
- 	^ self boundingBox width!

Item was removed:
- DisplayObject subclass: #DisplayText
- 	instanceVariableNames: 'text textStyle offset form foreColor backColor'
- 	classVariableNames: ''
- 	poolDictionaries: 'TextConstants'
- 	category: 'Graphics-Display Objects'!
- 
- !DisplayText commentStamp: '<historical>' prior: 0!
- I represent Text whose emphasis changes are mapped to a set of fonts. My instances have an offset used in determining screen placement for displaying. They get used two different ways in the system. In the user interface, they mainly hold onto some text which is viewed by some form of ParagraphEditor. However, as a DisplayObject, they may need to display efficiently, so my instances have a cache for the bits.!

Item was removed:
- ----- Method: DisplayText class>>example (in category 'examples') -----
- example
- 	"Continually prints two lines of text wherever you point with the cursor.  Terminate by pressing any button on the
- 	mouse."
- 	| tx |
- 	tx := 'this is a line of characters and
- this is the second line.' asDisplayText.
- 	tx foregroundColor: Color black backgroundColor: Color transparent.
- 	tx := tx alignedTo: #center.
- 	[Sensor anyButtonPressed]
- 		whileFalse:
- 			[tx displayOn: Display at: Sensor cursorPoint]
- 
- 	"DisplayText example."!

Item was removed:
- ----- Method: DisplayText class>>text: (in category 'instance creation') -----
- text: aText 
- 	"Answer an instance of me such that the text displayed is aText 
- 	according to the system's default text style."
- 
- 	^self new
- 		setText: aText
- 		textStyle: DefaultTextStyle copy
- 		offset: 0 @ 0!

Item was removed:
- ----- Method: DisplayText class>>text:textStyle: (in category 'instance creation') -----
- text: aText textStyle: aTextStyle 
- 	"Answer an instance of me such that the text displayed is aText 
- 	according to the style specified by aTextStyle."
- 
- 	^self new
- 		setText: aText
- 		textStyle: aTextStyle
- 		offset: 0 @ 0!

Item was removed:
- ----- Method: DisplayText class>>text:textStyle:offset: (in category 'instance creation') -----
- text: aText textStyle: aTextStyle offset: aPoint 
- 	"Answer an instance of me such that the text displayed is aText 
- 	according to the style specified by aTextStyle. The display of the 
- 	information should be offset by the amount given as the argument, 
- 	aPoint."
- 
- 	^self new
- 		setText: aText
- 		textStyle: aTextStyle
- 		offset: aPoint!

Item was removed:
- ----- Method: DisplayText>>alignedTo: (in category 'accessing') -----
- alignedTo: alignPointSelector
- 	"Return a copy with offset according to alignPointSelector which is one of...
- 	#(topLeft, topCenter, topRight, leftCenter, center, etc)"
- 	| boundingBox |
- 	boundingBox := 0 at 0 corner: self form extent.
- 	^ self shallowCopy offset: (0 at 0) - (boundingBox perform: alignPointSelector)!

Item was removed:
- ----- Method: DisplayText>>asString (in category 'converting') -----
- asString
- 	"See String >> #asDisplayText."
- 	
- 	^ self string!

Item was removed:
- ----- Method: DisplayText>>asText (in category 'converting') -----
- asText
- 	"See Text >> #asDisplayText."
- 
- 	^ self text!

Item was removed:
- ----- Method: DisplayText>>backgroundColor (in category 'color') -----
- backgroundColor
- 	backColor == nil ifTrue: [^ Color transparent].
- 	^ backColor!

Item was removed:
- ----- Method: DisplayText>>boundingBox (in category 'display box access') -----
- boundingBox 
- 	"Refer to the comment in DisplayObject|boundingBox."
- 
- 	^self form boundingBox!

Item was removed:
- ----- Method: DisplayText>>composeForm (in category 'private') -----
- composeForm
- 
- 	form := Project current composeDisplayTextIntoForm: self.!

Item was removed:
- ----- Method: DisplayText>>computeBoundingBox (in category 'display box access') -----
- computeBoundingBox 
- 	"Compute minimum enclosing rectangle around characters."
- 
- 	| character font width carriageReturn lineWidth lineHeight |
- 	carriageReturn := Character cr.
- 	width := lineWidth := 0.
- 	font := textStyle defaultFont.
- 	lineHeight := textStyle lineGrid.
- 	1 to: text size do: 
- 		[:i | 
- 		character := text at: i.
- 		character = carriageReturn
- 		  ifTrue: 
- 			[lineWidth := lineWidth max: width.
- 			lineHeight := lineHeight + textStyle lineGrid.
- 			width := 0]
- 		  ifFalse: [width := width + (font widthOf: character)]].
- 	lineWidth := lineWidth max: width.
- 	^offset extent: lineWidth @ lineHeight!

Item was removed:
- ----- Method: DisplayText>>displayOn:at:clippingBox:rule:fillColor: (in category 'displaying') -----
- displayOn: aDisplayMedium at: aDisplayPoint clippingBox: clipRectangle rule: ruleInteger fillColor: aForm
- 	"For TT font, rule 34 is used if possible."
- 	"Refer to the comment in 
- 	DisplayObject|displayOn:at:clippingBox:rule:mask:."
- 
- 	| form1 rule |
- 	form1 := self form.
- 	rule := (ruleInteger = Form over and: [backColor isTransparent])
- 				ifTrue: [form1 depth = 32 ifTrue: [rule := 34] ifFalse: [Form paint]]
- 				ifFalse: [ruleInteger].
- 	form1 depth = 32 ifTrue: [rule := 34].
- 	form1
- 		displayOn: aDisplayMedium
- 		at: aDisplayPoint + offset
- 		clippingBox: clipRectangle
- 		rule: rule
- 		fillColor: aForm!

Item was removed:
- ----- Method: DisplayText>>displayOn:transformation:clippingBox:align:with:rule:fillColor: (in category 'displaying') -----
- displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle align: alignmentPoint with: relativePoint rule: ruleInteger fillColor: aForm 
- 	"Refer to the comment in 
- 	DisplayObject|displayOn:transformation:clippingBox:align:with:rule:mask:."
- 
- 	| absolutePoint |
- 	absolutePoint := displayTransformation applyTo: relativePoint.
- 	absolutePoint := absolutePoint x asInteger @ absolutePoint y asInteger.
- 	self displayOn: aDisplayMedium
- 		at: absolutePoint - alignmentPoint
- 		clippingBox: clipRectangle
- 		rule: ruleInteger
- 		fillColor: aForm!

Item was removed:
- ----- Method: DisplayText>>displayOnPort:at: (in category 'displaying') -----
- displayOnPort: aPort at: location
- 	self form displayOnPort: aPort at: location + offset!

Item was removed:
- ----- Method: DisplayText>>fontsUsed (in category 'accessing') -----
- fontsUsed
- 	"Return a list of all fonts used currently in this text.  8/19/96 tk"
- 
- 	^ text runs values asSet collect: [:each | textStyle fontAt: each]!

Item was removed:
- ----- Method: DisplayText>>foregroundColor (in category 'color') -----
- foregroundColor
- 	foreColor == nil ifTrue: [^ Color black].
- 	^ foreColor!

Item was removed:
- ----- Method: DisplayText>>foregroundColor:backgroundColor: (in category 'color') -----
- foregroundColor: cf backgroundColor: cb
- 	foreColor := cf.
- 	backColor := cb!

Item was removed:
- ----- Method: DisplayText>>form (in category 'accessing') -----
- form 
- 	"Answer the form into which the receiver's display bits are cached."
- 
- 	form == nil ifTrue: [self composeForm].
- 	^form!

Item was removed:
- ----- Method: DisplayText>>lineGrid (in category 'accessing') -----
- lineGrid
- 	"Answer the relative space between lines of the receiver's text."
- 
- 	^textStyle lineGrid!

Item was removed:
- ----- Method: DisplayText>>numberOfLines (in category 'accessing') -----
- numberOfLines 
- 	"Answer the number of lines of text in the receiver."
- 
- 	^self height // text lineGrid!

Item was removed:
- ----- Method: DisplayText>>offset (in category 'accessing') -----
- offset 
- 	"Refer to the comment in DisplayObject|offset."
- 
- 	^offset!

Item was removed:
- ----- Method: DisplayText>>offset: (in category 'accessing') -----
- offset: aPoint 
- 	"Refer to the comment in DisplayObject|offset:."
- 
- 	offset := aPoint!

Item was removed:
- ----- Method: DisplayText>>setText:textStyle:offset: (in category 'private') -----
- setText: aText textStyle: aTextStyle offset: aPoint
- 
- 	text := aText.
- 	textStyle := aTextStyle.
- 	offset := aPoint.
- 	form := nil!

Item was removed:
- ----- Method: DisplayText>>string (in category 'accessing') -----
- string
- 	"Answer the string of the characters displayed by the receiver."
- 
- 	^text string!

Item was removed:
- ----- Method: DisplayText>>text (in category 'accessing') -----
- text 
- 	"Answer the text displayed by the receiver."
- 
- 	^text!

Item was removed:
- ----- Method: DisplayText>>text: (in category 'accessing') -----
- text: aText 
- 	"Set the receiver to display the argument, aText."
- 	
- 	text := aText.
- 	form := nil.
- 	self changed.
- 	!

Item was removed:
- ----- Method: DisplayText>>textStyle (in category 'accessing') -----
- textStyle 
- 	"Answer the style by which the receiver displays its text."
- 
- 	^textStyle!

Item was removed:
- ----- Method: DisplayText>>textStyle: (in category 'accessing') -----
- textStyle: aTextStyle 
- 	"Set the style by which the receiver should display its text."
- 
- 	textStyle := aTextStyle.
- 	form := nil.
- 	self changed.
- 	!

Item was removed:
- Object subclass: #DisplayTransform
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Transformations'!
- 
- !DisplayTransform commentStamp: '<historical>' prior: 0!
- This class represents a base for generic transformations of 2D points between different coordinate systems (including scaling and rotation). The transformations map objects between one coordinate system and another where it is assumed that a nested hierarchy of transformations can be defined.
- 
- It is assumed that transformations deal with Integer points. All transformations should return Integer coordinates (even though float points may be passed in as argument).
- 
- Compositions of transformations MUST work in the following order. A 'global' transformation (the argument in #composedWithGlobal:) is defined as a transformation that takes place between the receiver (the 'local') transformation and any 'global' point computations, whereas a 'local' transformation (e.g., the argument in #composedWithLocal:) takes place between the receiver ('global') and any 'local' points. For the transformation methods this means that combining a global and a local transformation will result in the following order:
- 
- 		globalPointToLocal: globalPoint
- 			"globalPoint -> globalTransform -> localTransform -> locaPoint"
- 			^localTransform globalPointToLocal:
- 				(globalTransform globalPointToLocal: globalPoint)
- 
- 		localPointToGlobal: localPoint
- 			"localPoint -> localTransform -> globalTransform -> globalPoint"
- 			^globalTransform localPointToGlobal:
- 				(localTransform localPointToGlobal: localPoint)
- 
- !

Item was removed:
- ----- Method: DisplayTransform class>>identity (in category 'instance creation') -----
- identity
- 	^self new setIdentity!

Item was removed:
- ----- Method: DisplayTransform>>asCompositeTransform (in category 'converting') -----
- asCompositeTransform
- 	"Represent the receiver as a composite transformation"
- 	^CompositeTransform new
- 		globalTransform: self
- 		localTransform: self species identity!

Item was removed:
- ----- Method: DisplayTransform>>asMatrixTransform2x3 (in category 'converting') -----
- asMatrixTransform2x3
- 	"Represent the receiver as a 2x3 matrix transformation"
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: DisplayTransform>>composedWithGlobal: (in category 'composing') -----
- composedWithGlobal: aTransformation
- 	"Return the composition of the receiver and the global transformation passed in.
- 	A 'global' transformation is defined as a transformation that takes place
- 	between the receiver (the 'local') transformation and any 'global' point
- 	computations, e.g., for the methods
- 
- 		globalPointToLocal: globalPoint
- 			globalPoint -> globalTransform -> localTransform -> locaPoint
- 
- 		localPointToGlobal: localPoint
- 			localPoint -> localTransform -> globalTransform -> globalPoint
- 
- 		"
- 	^aTransformation composedWithLocal: self!

Item was removed:
- ----- Method: DisplayTransform>>composedWithLocal: (in category 'composing') -----
- composedWithLocal: aTransformation
- 	"Return the composition of the receiver and the local transformation passed in.
- 	A 'local' transformation is defined as a transformation that takes place
- 	between the receiver (the 'global') transformation and any 'local' point
- 	computations, e.g., for the methods
- 
- 		globalPointToLocal: globalPoint
- 			globalPoint -> globalTransform -> localTransform -> locaPoint
- 
- 		localPointToGlobal: localPoint
- 			localPoint -> localTransform -> globalTransform -> globalPoint
- 
- 		"
- 	self isIdentity ifTrue:[^ aTransformation].
- 	aTransformation isIdentity ifTrue:[^ self].
- 	^ CompositeTransform new globalTransform: self
- 							localTransform: aTransformation!

Item was removed:
- ----- Method: DisplayTransform>>globalBoundsToLocal: (in category 'transforming rects') -----
- globalBoundsToLocal: aRectangle
- 	"Transform aRectangle from global coordinates into local coordinates"
- 	^Rectangle encompassing: (self globalPointsToLocal: aRectangle corners)!

Item was removed:
- ----- Method: DisplayTransform>>globalPointToLocal: (in category 'transforming points') -----
- globalPointToLocal: aPoint
- 	"Transform aPoint from global coordinates into local coordinates"
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: DisplayTransform>>globalPointsToLocal: (in category 'transforming points') -----
- globalPointsToLocal: inArray
- 	"Transform all the points of inArray from global into local coordinates"
- 	^inArray collect:[:pt| self globalPointToLocal: pt]!

Item was removed:
- ----- Method: DisplayTransform>>inverseTransformation (in category 'accessing') -----
- inverseTransformation
- 	"Return the inverse transformation of the receiver"
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: DisplayTransform>>invertBoundsRect: (in category 'transforming points') -----
- invertBoundsRect: aRectangle
- 	"Return a rectangle whose coordinates have been transformed
- 	from local back to global coordinates."
- 
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: DisplayTransform>>invertPoint: (in category 'transforming points') -----
- invertPoint: aPoint
- 	^self globalPointToLocal: aPoint!

Item was removed:
- ----- Method: DisplayTransform>>invertRect: (in category 'transforming rects') -----
- invertRect: aRectangle
- 	^self globalBoundsToLocal: aRectangle!

Item was removed:
- ----- Method: DisplayTransform>>isCompositeTransform (in category 'testing') -----
- isCompositeTransform
- 	"Return true if the receiver is a composite transformation.
- 	Composite transformations may have impact on the accuracy."
- 	^false!

Item was removed:
- ----- Method: DisplayTransform>>isIdentity (in category 'testing') -----
- isIdentity
- 	"Return true if the receiver is the identity transform; that is, if applying to a point returns the point itself."
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: DisplayTransform>>isMatrixTransform2x3 (in category 'testing') -----
- isMatrixTransform2x3
- 	"Return true if the receiver is 2x3 matrix transformation"
- 	^false!

Item was removed:
- ----- Method: DisplayTransform>>isMorphicTransform (in category 'testing') -----
- isMorphicTransform
- 	"Return true if the receiver is a MorphicTransform, that is specifies the transformation values explicitly."
- 	^false!

Item was removed:
- ----- Method: DisplayTransform>>isPureTranslation (in category 'testing') -----
- isPureTranslation
- 	"Return true if the receiver specifies no rotation or scaling."
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: DisplayTransform>>localBoundsToGlobal: (in category 'transforming rects') -----
- localBoundsToGlobal: aRectangle
- 	"Transform aRectangle from local coordinates into global coordinates"
- 	^Rectangle encompassing: (self localPointsToGlobal: aRectangle corners)!

Item was removed:
- ----- Method: DisplayTransform>>localPointToGlobal: (in category 'transforming points') -----
- localPointToGlobal: aPoint
- 	"Transform aPoint from local coordinates into global coordinates"
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: DisplayTransform>>localPointsToGlobal: (in category 'transforming points') -----
- localPointsToGlobal: inArray
- 	"Transform all the points of inArray from local into global coordinates"
- 	^inArray collect:[:pt| self localPointToGlobal: pt]!

Item was removed:
- ----- Method: DisplayTransform>>setIdentity (in category 'initialize') -----
- setIdentity
- 	"Initialize the receiver to the identity transformation (e.g., not affecting points)"
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: DisplayTransform>>sourceQuadFor: (in category 'transforming rects') -----
- sourceQuadFor: aRectangle
- 	^ aRectangle innerCorners collect: 
- 		[:p | self globalPointToLocal: p]!

Item was removed:
- ----- Method: DisplayTransform>>transformPoint: (in category 'transforming points') -----
- transformPoint: aPoint
- 	"Point transform double dispatch"
- 	^self localPointToGlobal: aPoint!

Item was removed:
- ----- Method: DisplayTransform>>transformRect: (in category 'transforming rects') -----
- transformRect: aRectangle
- 	^self localBoundsToGlobal: aRectangle!

Item was removed:
- ----- Method: DisplayTransform>>transformedBy: (in category 'converting') -----
- transformedBy: aTransform
- 	^self composedWithGlobal: aTransform!

Item was removed:
- ----- Method: EventSensor>>testJoystick: (in category '*Graphics-KernelExtensions') -----
- testJoystick: index
- 	"Sensor testJoystick: 3"
- 
- 	| f pt buttons status |
- 	f := Form extent: 110 at 50.
- 	[Sensor anyButtonPressed] whileFalse: [
- 		pt := Sensor joystickXY: index.
- 		buttons := Sensor joystickButtons: index.
- 		status :=
- 'xy: ', pt printString, '
- buttons: ', buttons printStringHex.
- 		f fillWhite.
- 		status displayOn: f at: 10 at 10.
- 		f displayOn: Display at: 10 at 10.
- 	].
- !

Item was removed:
- AbstractFont subclass: #FixedFaceFont
- 	instanceVariableNames: 'baseFont substitutionCharacter displaySelector'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Fonts'!
- 
- !FixedFaceFont commentStamp: 'tak 12/22/2004 01:45' prior: 0!
- I am a font for special purpose like password or fallback.
- I can show same form whenever someone requests any character.
- 
- Variable displaySelector is future use to show a form dynamically.
- (Although it would be unnecessary...)!

Item was removed:
- ----- Method: FixedFaceFont>>ascent (in category 'accessing') -----
- ascent
- 	^baseFont ascent!

Item was removed:
- ----- Method: FixedFaceFont>>ascentOf: (in category 'accessing') -----
- ascentOf: aCharacter
- 	^ self ascent!

Item was removed:
- ----- Method: FixedFaceFont>>baseFont (in category 'accessing') -----
- baseFont
- 	^baseFont!

Item was removed:
- ----- Method: FixedFaceFont>>baseFont: (in category 'accessing') -----
- baseFont: aFont
- 	baseFont := aFont.
- 	self fixSubstitutionCharacter.!

Item was removed:
- ----- Method: FixedFaceFont>>baseKern (in category 'accessing') -----
- baseKern
- 	^baseFont baseKern!

Item was removed:
- ----- Method: FixedFaceFont>>basicHasGlyphOf: (in category 'private') -----
- basicHasGlyphOf: aCharacter
- 
- 	" We present the same for any character, so, yes"
- 	^ true!

Item was removed:
- ----- Method: FixedFaceFont>>characterFormAt: (in category 'character shapes') -----
- characterFormAt: character 
- 	^ baseFont characterFormAt: substitutionCharacter!

Item was removed:
- ----- Method: FixedFaceFont>>depth (in category 'accessing') -----
- depth
- 
- 	^ self baseFont depth!

Item was removed:
- ----- Method: FixedFaceFont>>descent (in category 'accessing') -----
- descent
- 	^baseFont descent!

Item was removed:
- ----- Method: FixedFaceFont>>descentKern (in category 'accessing') -----
- descentKern
- 	^baseFont descentKern!

Item was removed:
- ----- Method: FixedFaceFont>>descentOf: (in category 'accessing') -----
- descentOf: aCharacter
- 	^ self descent!

Item was removed:
- ----- Method: FixedFaceFont>>displayErrorOn:length:at:kern: (in category 'displaying') -----
- displayErrorOn: aCanvas length: length at: aPoint kern: kernDelta 
- 	| maskedString |
- 	maskedString := String new: length.
- 	maskedString atAllPut: substitutionCharacter.
- 	^ baseFont
- 		displayString: maskedString
- 		on: aCanvas
- 		from: 1
- 		to: length
- 		at: aPoint
- 		kern: kernDelta!

Item was removed:
- ----- Method: FixedFaceFont>>displayErrorOn:length:at:kern:baselineY: (in category 'displaying') -----
- displayErrorOn: aCanvas length: length at: aPoint kern: kernDelta baselineY: baselineY
- 	| maskedString |
- 	maskedString := String new: length.
- 	maskedString atAllPut: substitutionCharacter.
- 	^ baseFont
- 		displayString: maskedString
- 		on: aCanvas
- 		from: 1
- 		to: length
- 		at: aPoint
- 		kern: kernDelta
- 		baselineY: baselineY!

Item was removed:
- ----- Method: FixedFaceFont>>displayPasswordOn:length:at:kern: (in category 'displaying') -----
- displayPasswordOn: aCanvas length: length at: aPoint kern: kernDelta 
- 	| maskedString |
- 	maskedString := String new: length.
- 	maskedString atAllPut: substitutionCharacter.
- 	^ baseFont
- 		displayString: maskedString
- 		on: aCanvas
- 		from: 1
- 		to: length
- 		at: aPoint
- 		kern: kernDelta!

Item was removed:
- ----- Method: FixedFaceFont>>displayPasswordOn:length:at:kern:baselineY: (in category 'displaying') -----
- displayPasswordOn: aCanvas length: length at: aPoint kern: kernDelta baselineY: baselineY
- 	| maskedString |
- 	maskedString := String new: length.
- 	maskedString atAllPut: substitutionCharacter.
- 	^ baseFont
- 		displayString: maskedString
- 		on: aCanvas
- 		from: 1
- 		to: length
- 		at: aPoint
- 		kern: kernDelta
- 		baselineY: baselineY!

Item was removed:
- ----- Method: FixedFaceFont>>displayString:on:from:to:at:kern: (in category 'displaying') -----
- displayString: aString on: aDisplayContext from: startIndex to: stopIndex at: aPoint kern: kernDelta 
- 	| size |
- 	size := stopIndex - startIndex + 1.
- 	^ self perform: displaySelector withArguments: (Array with: aDisplayContext with: size with: aPoint with: kernDelta with: aPoint y + self ascent).!

Item was removed:
- ----- Method: FixedFaceFont>>displayString:on:from:to:at:kern:baselineY: (in category 'displaying') -----
- displayString: aString on: aDisplayContext from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY
- 	| size |
- 	size := stopIndex - startIndex + 1.
- 	^ self perform: displaySelector withArguments: (Array with: aDisplayContext with: size with: aPoint with: kernDelta with: baselineY).!

Item was removed:
- ----- Method: FixedFaceFont>>displayString:on:from:to:at:kern:from: (in category 'displaying') -----
- displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta from: fromFont 
- 	| destPoint |
- 	destPoint := self
- 				displayString: aString
- 				on: aBitBlt
- 				from: startIndex
- 				to: stopIndex
- 				at: aPoint
- 				kern: kernDelta.
- 	^ Array with: stopIndex + 1 with: destPoint!

Item was removed:
- ----- Method: FixedFaceFont>>displayString:on:from:to:at:kern:from:baselineY: (in category 'displaying') -----
- displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta from: fromFont baselineY: baselineY
- 	| destPoint |
- 	destPoint := self
- 				displayString: aString
- 				on: aBitBlt
- 				from: startIndex
- 				to: stopIndex
- 				at: aPoint
- 				kern: kernDelta
- 				baselineY: baselineY.
- 	^destPoint!

Item was removed:
- ----- Method: FixedFaceFont>>emphasized: (in category 'accessing') -----
- emphasized: emph
- 	^self class new baseFont: (baseFont emphasized: emph)!

Item was removed:
- ----- Method: FixedFaceFont>>errorCharacter (in category 'accessing') -----
- errorCharacter
- 	^$?!

Item was removed:
- ----- Method: FixedFaceFont>>errorFont (in category 'initialize-release') -----
- errorFont
- 	displaySelector := #displayErrorOn:length:at:kern:baselineY:.
- 	substitutionCharacter := self errorCharacter.
- 	self fixSubstitutionCharacter.!

Item was removed:
- ----- Method: FixedFaceFont>>familyName (in category 'accessing') -----
- familyName
- 	^baseFont familyName, '-pw'!

Item was removed:
- ----- Method: FixedFaceFont>>fixSubstitutionCharacter (in category 'private') -----
- fixSubstitutionCharacter
- 	
- 	substitutionCharacter ifNil: [^ self].
- 	baseFont ifNil: [^ self].
- 	(baseFont hasGlyphOf: substitutionCharacter) ifTrue: [^ self].
- 
- 	((baseFont minCodePoint max: 33) to: baseFont maxCodePoint)
- 		detect: [:codePoint | baseFont hasGlyphOf: (Character value: codePoint)]
- 		ifFound: [:codePoint | substitutionCharacter := Character value: codePoint]
- 		ifNone: [
- 			baseFont := TextStyle defaultFont.
- 			substitutionCharacter := $?].	
- 	self
- 		assert: [baseFont hasGlyphOf: substitutionCharacter]
- 		description: 'Could not find a possible substitution character and font!!'.!

Item was removed:
- ----- Method: FixedFaceFont>>fontPointSize: (in category 'accessing') -----
- fontPointSize: aNumber 
- 	self baseFont: (StrikeFont familyName: baseFont familyName pointSize: aNumber) copy!

Item was removed:
- ----- Method: FixedFaceFont>>fontSize: (in category 'accessing') -----
- fontSize: aNumber 
- 	self baseFont: (StrikeFont familyName: baseFont familyName size: aNumber) copy!

Item was removed:
- ----- Method: FixedFaceFont>>foregroundColor (in category 'displaying') -----
- foregroundColor
- 
- 	^ baseFont foregroundColor!

Item was removed:
- ----- Method: FixedFaceFont>>foregroundColor: (in category 'displaying') -----
- foregroundColor: fgColor
- 
- 	baseFont foregroundColor: fgColor.!

Item was removed:
- ----- Method: FixedFaceFont>>formOf: (in category 'private') -----
- formOf: aCharacter
- 	"No need to check #hasGlyphOf:."
- 
- 	^ self characterFormAt: aCharacter!

Item was removed:
- ----- Method: FixedFaceFont>>glyphInfoOf:into: (in category 'private') -----
- glyphInfoOf: aCharacter into: glyphInfoArray
- "since we replace every character with substitutionCharacter, get my baseFont's glyphInfo for that"
- 	^ baseFont glyphInfoOf: substitutionCharacter into: glyphInfoArray.
- !

Item was removed:
- ----- Method: FixedFaceFont>>height (in category 'accessing') -----
- height
- 	^baseFont height!

Item was removed:
- ----- Method: FixedFaceFont>>initialize (in category 'initialize-release') -----
- initialize
- 
- 	baseFont := TextStyle defaultFont.
- 	self passwordFont.!

Item was removed:
- ----- Method: FixedFaceFont>>installOn:foregroundColor:backgroundColor: (in category 'displaying') -----
- installOn: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor
- 	^baseFont installOn: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor!

Item was removed:
- ----- Method: FixedFaceFont>>isTTCFont (in category 'testing') -----
- isTTCFont
- 
- 	^ baseFont isTTCFont!

Item was removed:
- ----- Method: FixedFaceFont>>lineGrid (in category 'accessing') -----
- lineGrid
- 	^baseFont lineGrid!

Item was removed:
- ----- Method: FixedFaceFont>>maxCodePoint (in category 'accessing') -----
- maxCodePoint
- 	"Overwritten for robustness. The receiver MUST BE a reliable source of glyphs if all else fails. Font rendering must never stop."
- 	
- 	^ SmallInteger maxVal!

Item was removed:
- ----- Method: FixedFaceFont>>minSubstitutionCharacter (in category 'private') -----
- minSubstitutionCharacter
- 
- 	^ Character value: (baseFont ifNil: [0] ifNotNil: [baseFont minCodePoint])!

Item was removed:
- ----- Method: FixedFaceFont>>passwordCharacter (in category 'accessing') -----
- passwordCharacter
- 	^$*!

Item was removed:
- ----- Method: FixedFaceFont>>passwordFont (in category 'initialize-release') -----
- passwordFont
- 	displaySelector := #displayPasswordOn:length:at:kern:baselineY:.
- 	substitutionCharacter := self passwordCharacter.
- 	self fixSubstitutionCharacter.!

Item was removed:
- ----- Method: FixedFaceFont>>pointSize (in category 'accessing') -----
- pointSize
- 	^baseFont pointSize!

Item was removed:
- ----- Method: FixedFaceFont>>releaseCachedState (in category 'caching') -----
- releaseCachedState
- 	baseFont releaseCachedState.!

Item was removed:
- ----- Method: FixedFaceFont>>widthOf: (in category 'measuring') -----
- widthOf: aCharacter
- 	^ (baseFont hasGlyphOf: substitutionCharacter)
- 		ifTrue: [baseFont widthOf: substitutionCharacter]
- 		ifFalse: [1]!

Item was removed:
- Object subclass: #FontSet
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Fonts'!
- 
- !FontSet commentStamp: '<historical>' prior: 0!
- FontSet provides a mechanism for storing a set of fonts as a class that can be conveniently filedOut, filedIn, and installed as a TextStyle.
- 
- The most common use is...
- 	Find a font you like.
- 	Use BitFont to convert a bunch of sizes to data files named, eg, LovelyNN.BF
- 	Use FontSet convertFontsNamed: 'Lovely' to produce a FontSet named Lovely.
- 	FileOut that FontSet for later use.
- 	Use Lovely installAsTextStyle to make all sizes available in a TextStyle
- 		named #Lovely in the TextConstants dictionary.
- 	Use ctrl-k in any text pane to select the new Lovely style for that paragraph.
- 	Then use cmd-1 through 5 or cmd-k to set the point-size for any selection.
- !

Item was removed:
- ----- Method: FontSet class>>acceptsLoggingOfCompilation (in category 'compiling') -----
- acceptsLoggingOfCompilation
- 	"Dont log sources for my subclasses, so as not to waste time
- 	and space storing printString versions of the string literals."
- 
- 	^super acceptsLoggingOfCompilation
- 		and:
- 			[self == FontSet]!

Item was removed:
- ----- Method: FontSet class>>compileFont: (in category 'compiling') -----
- compileFont: strikeFont 
- 	| tempName literalString header sizeStr familyName |
- 	tempName := 'FontTemp.sf2'.
- 	strikeFont writeAsStrike2named: tempName.
- 	literalString := (Base64MimeConverter mimeEncode: (FileStream readOnlyFileNamed: tempName) binary) contents fullPrintString.
- 	sizeStr := strikeFont pointSize asString.
- 	familyName := strikeFont name first: (strikeFont name findLast: [:x | x isDigit not]).
- 
- 	header := 'size' , sizeStr , '
- 	^ self fontNamed: ''' , familyName , sizeStr , ''' fromMimeLiteral:
- ' .
- 	self class
- 		compile: header , literalString
- 		classified: 'fonts'
- 		notifying: nil.
- 	FileDirectory default deleteFileNamed: tempName
- !

Item was removed:
- ----- Method: FontSet class>>convertFontsNamed: (in category 'as yet unclassified') -----
- convertFontsNamed: familyName  "FontSet convertFontsNamed: 'Palatino' "
- 	^ self convertFontsNamed: familyName inDirectoryNamed: ''!

Item was removed:
- ----- Method: FontSet class>>convertFontsNamed:inDirectoryNamed: (in category 'converting') -----
- convertFontsNamed: familyName inDirectoryNamed: dirName
- 		"FontSet convertFontsNamed: 'Tekton' inDirectoryNamed: 'Tekton Fonts' "
- 	"This utility is for use after you have used BitFont to produce data files 
- 	for the fonts you wish to use.  It will read the BitFont files and build
- 	a fontset class from them.  If one already exists, the sizes that can be
- 	found will be overwritten."
- 	"For this utility to work as is, the BitFont data files must be named 'familyNN.BF',
- 	and must reside in the directory named by dirName (use '' for the current directory)."
- 
- 	| allFontNames fontSet dir |
- 	"Check first for matching file names and usable FontSet class name."
- 	dir := dirName isEmpty
- 		ifTrue: [FileDirectory default]
- 		ifFalse: [FileDirectory default directoryNamed: dirName].
- 	allFontNames := dir fileNamesMatching: familyName , '##.BF'.
- 	allFontNames isEmpty ifTrue: [^ self error: 'No files found like ' , familyName , 'NN.BF'].
- 	fontSet := self fontSetClass: familyName.
- 	allFontNames do:
- 		[:each |
- 		Transcript cr; show: each.
- 		fontSet compileFont: (StrikeFont new readFromBitFont: (dir fullNameFor: each))]!

Item was removed:
- ----- Method: FontSet class>>convertTextStyleNamed: (in category 'converting') -----
- convertTextStyleNamed: aString
- 	| style fontSet |
- 	(style := TextStyle named: aString) ifNil: [^ self error: 'unknown text style ' , aString].
- 	fontSet := self fontSetClass: aString.
- 	style fontArray do: [:each | fontSet compileFont: each]!

Item was removed:
- ----- Method: FontSet class>>fileOut (in category 'filein/out') -----
- fileOut
- 	"FileOut and then change the properties of the file so that it won't be
- 	treated as text by, eg, email attachment facilities"
- 
- 	super fileOut.
- 	(FileStream oldFileNamed: self name , '.st') setFileTypeToObject; close!

Item was removed:
- ----- Method: FontSet class>>fontCategory (in category 'private') -----
- fontCategory
- 	^ #'Graphics-Fonts'!

Item was removed:
- ----- Method: FontSet class>>fontName (in category 'private') -----
- fontName
- 
- 	self flag: #bob.		"temporary hack until I figure out what's happening here"
- 	(self name beginsWith: superclass name) ifFalse: [^self name].
- 	^ (self name copyFrom: superclass name size + 1 to: self name size) asSymbol!

Item was removed:
- ----- Method: FontSet class>>fontNamed:fromLiteral: (in category 'installing') -----
- fontNamed: fontName fromLiteral: aString
- 	"NOTE -- THIS IS AN OBSOLETE METHOD THAT MAY CAUSE ERRORS.
- 
- The old form of fileOut for FontSets produced binary literal strings which may not be accurately read in systems with support for international character sets.  If possible, file the FontSet out again from a system that produces the newer MIME encoding (current def of compileFont:), and uses the corresponding altered version of this method.  If this is not easy, then
- 	file the fontSet into an older system (3.7 or earlier),
- 	assume it is called FontSetZork...
- 	execute FontSetZork installAsTextStyle.
- 	copy the compileFont: method from this system into that older one.
- 	remove the class FontSetZork.
- 	Execute:  FontSet convertTextStyleNamed: 'Zork', and see that it creates a new FontSetZork.
- 	FileOut the new class FontSetZork.
- 	The resulting file should be able to be read into this system.
- "
- 
- 	^ StrikeFont new 
- 		name: fontName;
- 		readFromStrike2Stream: (ReadStream on: aString asByteArray)!

Item was removed:
- ----- Method: FontSet class>>fontNamed:fromMimeLiteral: (in category 'installing') -----
- fontNamed: fontName fromMimeLiteral: aString
- 	"This method allows a font set to be captured as sourcecode in a subclass.
- 	The string literals will presumably be created by printing, eg,
- 		(FileStream readOnlyFileNamed: 'Palatino24.sf2') contentsOfEntireFile,
- 		and following the logic in compileFont: to encode and add a heading.
- 
- 	See the method installAsTextStyle to see how this can be used."
- 
- 	^ StrikeFont new 
- 		name: fontName;
- 		readFromStrike2Stream: (Base64MimeConverter mimeDecodeToBytes: aString readStream)!

Item was removed:
- ----- Method: FontSet class>>fontSetClass: (in category 'private') -----
- fontSetClass: aString
- 	| className fontSet |
- 	className := (self name , (aString select: [:c | c isAlphaNumeric]) capitalized) asSymbol.
- 	fontSet := Smalltalk
- 		at: className
- 		ifAbsentPut: [self
- 			subclass: className
- 			instanceVariableNames: ''
- 			classVariableNames: ''
- 			poolDictionaries: ''
- 			category: self fontCategory].
- 	(fontSet inheritsFrom: self) ifFalse: [^ self error: 'The name ' , className , ' is already in use'].
- 	^ fontSet!

Item was removed:
- ----- Method: FontSet class>>installAsDefault (in category 'installing') -----
- installAsDefault  "FontSetNewYork installAsDefault"
- 	(UIManager default confirm: 'Do you want to install
- ''' , self fontName , ''' as default font?')
- 		ifFalse: [^ self].
- 	self installAsTextStyle.
- 	"TextConstants at: #OldDefaultTextStyle put: TextStyle default."
- 	TextConstants at: #DefaultTextStyle put: (TextStyle named: self fontName).
- 	#(ListParagraph PopUpMenu StandardSystemView) do:[:className|
- 		Smalltalk at: className ifPresent:[:aClass| aClass initialize].
- 	].!

Item was removed:
- ----- Method: FontSet class>>installAsTextStyle (in category 'installing') -----
- installAsTextStyle  "FontSetNewYork installAsTextStyle"
- 	| selectors |
- 	(TextConstants includesKey: self fontName) ifTrue:
- 		[(self confirm: 
- self fontName , ' is already defined in TextConstants.
- Do you want to replace that definition?')
- 			ifFalse: [^ self]].
- 	selectors := (self class selectors select: [:s | s beginsWith: 'size']) sort
- 		 replace: [:each | self perform: each].
- 	TextConstants
- 		at: self fontName
- 		put: (TextStyle fontArray: selectors)!

Item was removed:
- ----- Method: FontSet class>>size:fromLiteral: (in category 'installing') -----
- size: pointSize fromLiteral: aString 
- 	"This method allows a font set to be captured as sourcecode in a subclass.
- 	The string literals will presumably be created by printing, eg,
- 		(FileStream readOnlyFileNamed: 'Palatino24.sf2') contentsOfEntireFile,
- 		and then pasting into a browser after a heading like, eg,
- size24
- 	^ self size: 24 fromLiteral:
- 	'--unreadable binary data--'
- 
- 	See the method installAsTextStyle to see how this can be used."
- 
- 	"This method is old and for backward compatibility only.
- 	please use fontNamed:fromLiteral: instead."
- 
- 	self flag: #bob.	"used in Alan's projects"
- 	^(StrikeFont new)
- 		name: self fontName , (pointSize < 10 
- 							ifTrue: ['0' , pointSize printString]
- 							ifFalse: [pointSize printString]);
- 		readFromStrike2Stream: ((RWBinaryOrTextStream with: aString)
- 					reset;
- 					binary);
- 		yourself!

Item was removed:
- DisplayMedium subclass: #Form
- 	instanceVariableNames: 'bits width height depth offset'
- 	classVariableNames: 'CompressOnSnapshot'
- 	poolDictionaries: ''
- 	category: 'Graphics-Display Objects'!
- 
- !Form commentStamp: 'cbc 5/5/2017 10:07' prior: 0!
- A rectangular array of pixels, used for holding images.  All pictures, including character images are Forms.  The depth of a Form is how many bits are used to specify the color at each pixel.  The actual bits are held in a Bitmap, whose internal structure is different at each depth.  Class Color allows you to deal with colors without knowing how they are actually encoded inside a Bitmap.
- 	  The supported depths (in bits) are 1, 2, 4, 8, 16, and 32.  The number of actual colors at these depths are: 2, 4, 16, 256, 32768, and 16 million.
- 	Forms are indexed starting at 0 instead of 1; thus, the top-left pixel of a Form has coordinates 0 at 0.
- 	Forms are combined using BitBlt.  See the comment in class BitBlt.  Forms that repeat many times to fill a large destination are InfiniteForms.
- 
- 	colorAt: x at y		Returns the abstract Color at this location
- 	displayAt: x at y		shows this form on the screen
- 	displayOn: aMedium at: x at y	shows this form in a Window, a Form, or other DisplayMedium
- 	fillColor: aColor		Set all the pixels to the color.
- 	edit		launch an editor to change the bits of this form.
- 	pixelValueAt: x at y	The encoded color.  The encoding depends on the depth.
- 
- Note: If you want to hook up other external forms/displayScreens, please look at the (successful) Graphics-External package in http://www.squeaksource.com/Balloon3D.!

Item was removed:
- ----- Method: Form class>>allTypicalFileExtensions (in category 'file list services') -----
- allTypicalFileExtensions
- 
- 	^ImageReadWriter allTypicalFileExtensions add: 'form'; yourself!

Item was removed:
- ----- Method: Form class>>alphaScale (in category 'mode constants') -----
- alphaScale
- 	"Answer the integer denoting BitBlt's pre-multiply rgb components by alpha (alphaScale) rule."
- 
- 	^ 42!

Item was removed:
- ----- Method: Form class>>alphaUnscale (in category 'mode constants') -----
- alphaUnscale
- 	"Answer the integer denoting BitBlt's post-multiply rgb components by alpha (alphaUnscale) rule."
- 
- 	^ 43!

Item was removed:
- ----- Method: Form class>>and (in category 'mode constants') -----
- and
- 	"Answer the integer denoting the logical 'and' combination rule."
- 
- 	^1!

Item was removed:
- ----- Method: Form class>>blend (in category 'mode constants') -----
- blend
- 	"Answer the integer denoting BitBlt's alpha blend combination rule."
- 	^24!

Item was removed:
- ----- Method: Form class>>blendAlpha (in category 'mode constants') -----
- blendAlpha
- 	"Answer the integer denoting BitBlt's blend-with-constant-alpha rule."
- 
- 	^ 30!

Item was removed:
- ----- Method: Form class>>blendAlphaScaled (in category 'mode constants') -----
- blendAlphaScaled
- 	"Answer the integer denoting BitBlt's blend-with-alpha-scaled rule."
- 
- 	^ 34!

Item was removed:
- ----- Method: Form class>>blendAlphaUnscaled (in category 'mode constants') -----
- blendAlphaUnscaled
- 	"Answer the integer denoting BitBlt's blend-with-alpha-unscaled rule."
- 
- 	^ 44!

Item was removed:
- ----- Method: Form class>>compareMatchColor (in category 'mode constants') -----
- compareMatchColor
- 	"The primCompare test id values are
- 	compareMatchColors -> 0
- 	compareNotColorANotColorB -> 1
- 	compareNotColorAMatchColorB -> 2"
- 	^0!

Item was removed:
- ----- Method: Form class>>compareNotColorAMatchColorB (in category 'mode constants') -----
- compareNotColorAMatchColorB
- 	"The primCompare test id values are
- 	compareMatchColors -> 0
- 	compareNotColorANotColorB -> 1
- 	compareNotColorAMatchColorB -> 2"
- 	^2!

Item was removed:
- ----- Method: Form class>>compareNotColorANotColorB (in category 'mode constants') -----
- compareNotColorANotColorB
- 	"The primCompare test id values are
- 	compareMatchColors -> 0
- 	compareNotColorANotColorB -> 1
- 	compareNotColorAMatchColorB -> 2"
- 	^1!

Item was removed:
- ----- Method: Form class>>compareTallyFlag (in category 'mode constants') -----
- compareTallyFlag
- 	"The primCompare test id values are ORR'd with 8 to indicate tallying rather than simply reporting the first hit"
- 	^8!

Item was removed:
- ----- Method: Form class>>compressOnSnapshot (in category 'preferences') -----
- compressOnSnapshot
- 	<preference: 'Always compress graphics data on snapshot'
- 		categoryList: #(performance Graphics)
- 		description: 'When enabled, graphics data such as all instances of Form are compressed during image snapshots -- even when the image will not quit after the snapshot. This includes cache clean-up such as the TrueType glyph cache. Disable to avoid render lags after snapshots at the cost of a bigger footprint of your .image file. Note that snapshot-and-quit always compresses graphics data.'
- 		type: #Boolean>
- 
- 	^ CompressOnSnapshot ifNil: [true]!

Item was removed:
- ----- Method: Form class>>compressOnSnapshot: (in category 'preferences') -----
- compressOnSnapshot: aBoolean
- 
- 	CompressOnSnapshot := aBoolean.!

Item was removed:
- ----- Method: Form class>>dotOfSize: (in category 'instance creation') -----
- dotOfSize: diameter
- 	"Create a form which contains a round black dot."
- 	| radius form bb rect centerX centerY centerYBias centerXBias radiusSquared xOverY maxy dx |
- 	radius := diameter//2.
- 	form := self extent: diameter at diameter offset: (0 at 0) - (radius at radius).	
- 	bb := (BitBlt toForm: form)
- 		sourceX: 0; sourceY: 0;
- 		combinationRule: Form over;
- 		fillColor: Color black.
- 	rect := form boundingBox.
- 	centerX := rect center x.
- 	centerY := rect center y.
- 	centerYBias := rect height odd ifTrue: [0] ifFalse: [1].
- 	centerXBias := rect width odd ifTrue: [0] ifFalse: [1].
- 	radiusSquared := (rect height asFloat / 2.0) squared - 0.01.
- 	xOverY := rect width asFloat / rect height asFloat.
- 	maxy := rect height - 1 // 2.
- 
- 	"First do the inner fill, and collect x values"
- 	0 to: maxy do:
- 		[:dy |
- 		dx := ((radiusSquared - (dy * dy) asFloat) sqrt * xOverY) truncated.
- 		bb	destX: centerX - centerXBias - dx
- 			destY: centerY - centerYBias - dy
- 			width: dx + dx + centerXBias + 1
- 			height: 1;
- 			copyBits.
- 		bb	destY: centerY + dy;
- 			copyBits].
- 	^ form
- "
- Time millisecondsToRun:
- 	[1 to: 20 do: [:i | (Form dotOfSize: i) displayAt: (i*20)@(i*20)]]
- "!

Item was removed:
- ----- Method: Form class>>dotOfSize:color: (in category 'examples') -----
- dotOfSize: diameter color: color
- 
- 	| form |
- 	form := self extent: diameter asPoint depth: Display depth.
- 	form getCanvas fillOval: form boundingBox color: color.
- 	^form!

Item was removed:
- ----- Method: Form class>>erase (in category 'mode constants') -----
- erase
- 	"Answer the integer denoting mode erase."
- 
- 	^4!

Item was removed:
- ----- Method: Form class>>erase1bitShape (in category 'mode constants') -----
- erase1bitShape
- 	"Answer the integer denoting mode erase."
- 
- 	^ 26!

Item was removed:
- ----- Method: Form class>>exampleBorder (in category 'examples') -----
- exampleBorder    "Form exampleBorder"
- 	"This example demonstrates the border finding algorithm. Start
- 	by having the user sketch on the screen (end with option-click) and then select a rectangular
- 	area of the screen which includes all of the area to be filled. Finally,
- 	(with crosshair cursor), the user points at the interior of the region to be
- 	outlined, and the region begins with that place as its seed."
- 	| f r interiorPoint |
- 	Form exampleSketch.		"sketch a little area with an enclosed region"
- 	r := Rectangle fromUser.
- 	f := Form fromDisplay: r.
- 	interiorPoint := Cursor crossHair showWhile:
- 		[Sensor waitButton - r origin].
- 	Cursor execute showWhile:
- 		[f shapeBorder: Color blue width: 2 interiorPoint: interiorPoint
- 			sharpCorners: false internal: false].
- 	f displayOn: Display at: r origin	!

Item was removed:
- ----- Method: Form class>>exampleEdits (in category 'examples') -----
- exampleEdits
- 	"In Form category editing are messages edit and bitEdit that make it possible to 
- 	create editors on instances of Form. 
- 	 
- 	This is the general form editor:
- 	| f | 
- 	f := Form fromUser. 
- 	f edit. 
- 	 
- 	This is the general bit editor:
- 	| f | 
- 	f := Form fromUser. 
- 	f bitEdit."!

Item was removed:
- ----- Method: Form class>>exampleMagnify (in category 'examples') -----
- exampleMagnify
- 
- 	| f m |
- 	f := Form fromUser.
- 	m := f magnify: f boundingBox by: 5 @ 5.
- 	m displayOn: Display at: Sensor waitButton
- 
- 	"Form exampleMagnify."!

Item was removed:
- ----- Method: Form class>>exampleShrink (in category 'examples') -----
- exampleShrink
- 
- 	| f s |
- 	f := Form fromUser.
- 	s := f shrink: f boundingBox by: 2 @ 5.
- 	s displayOn: Display at: Sensor waitButton	
- 
- 	"Form exampleShrink."!

Item was removed:
- ----- Method: Form class>>exampleSketch (in category 'examples') -----
- exampleSketch
- 	"This is a simple drawing algorithm to get a sketch on the display screen.
- 	Draws whenever mouse button down.  Ends with option-click."
- 	| aPen color |
- 	aPen := Pen new.
- 	color := 0.
- 	[Sensor yellowButtonPressed]
- 		whileFalse:
- 		[aPen place: Sensor cursorPoint; color: (color := color + 1).
- 		[Sensor redButtonPressed]
- 			whileTrue: [aPen goto: Sensor cursorPoint]].
- 	Sensor waitNoButton.
- 
- 	"Form exampleSketch"!

Item was removed:
- ----- Method: Form class>>exampleSpaceFill (in category 'examples') -----
- exampleSpaceFill    "Form exampleSpaceFill"
- 	"This example demonstrates the area filling algorithm. Starts by having
- 	the user sketch on the screen (ended by option-click) and then select a rectangular
- 	area of the screen which includes all of the area to be filled. Finally,
- 	(with crosshair cursor), the user points at the interior of some region to be
- 	filled, and the filling begins with that place as its seed."
- 	| f r interiorPoint |
- 	Form exampleSketch.		"sketch a little area with an enclosed region"
- 	r := Rectangle fromUser.
- 	f := Form fromDisplay: r.
- 	interiorPoint := Cursor crossHair showWhile:
- 		[Sensor waitButton - r origin].
- 	Cursor execute showWhile:
- 		[f shapeFill: Color gray interiorPoint: interiorPoint].
- 	f displayOn: Display at: r origin	!

Item was removed:
- ----- Method: Form class>>extent: (in category 'instance creation') -----
- extent: extentPoint
- 	"Answer an instance of me with a blank bitmap of depth 1."
- 
- 	^ self extent: extentPoint depth: 1
- !

Item was removed:
- ----- Method: Form class>>extent:depth: (in category 'instance creation') -----
- extent: extentPoint depth: bitsPerPixel
- 	"Answer an instance of me with blank bitmap of the given dimensions and depth."
- 
- 	^ self basicNew setExtent: extentPoint depth: bitsPerPixel
- !

Item was removed:
- ----- Method: Form class>>extent:depth:bits: (in category 'instance creation') -----
- extent: extentPoint depth: bitsPerPixel bits: aBitmap
- 	"Answer an instance of me with blank bitmap of the given dimensions and depth."
- 
- 	^ self basicNew setExtent: extentPoint depth: bitsPerPixel bits: aBitmap!

Item was removed:
- ----- Method: Form class>>extent:depth:fromArray:offset: (in category 'instance creation') -----
- extent: extentPoint depth: bitsPerPixel fromArray: anArray offset: offsetPoint 
- 	"Answer an instance of me with a pixmap of the given depth initialized from anArray."
- 
- 	^ (self extent: extentPoint depth: bitsPerPixel)
- 		offset: offsetPoint;
- 		initFromArray: anArray
- !

Item was removed:
- ----- Method: Form class>>extent:fromArray:offset: (in category 'instance creation') -----
- extent: extentPoint fromArray: anArray offset: offsetPoint 
- 	"Answer an instance of me of depth 1 with bitmap initialized from anArray."
- 
- 	^ (self extent: extentPoint depth: 1)
- 		offset: offsetPoint;
- 		initFromArray: anArray
- !

Item was removed:
- ----- Method: Form class>>extent:fromStipple: (in category 'instance creation') -----
- extent: extentPoint fromStipple: fourNibbles
- 	"Answer an instance of me with bitmap initialized from
- 	a repeating 4x4 bit stipple encoded in a 16-bit constant."
- 	
- 	^ (self extent: extentPoint depth: 1)
- 		initFromArray: ((1 to: 4) collect:
- 				[:i | | nibble |
- 				nibble := (fourNibbles bitShift: -4*(4-i)) bitAnd: 16rF.
- 				16r11111111 * nibble])  "fill 32 bits with each 4-bit nibble"
- !

Item was removed:
- ----- Method: Form class>>extent:offset: (in category 'instance creation') -----
- extent: extentPoint offset: offsetPoint 
- 	"Answer an instance of me with a blank bitmap of depth 1."
- 
- 	^ (self extent: extentPoint depth: 1) offset: offsetPoint
- !

Item was removed:
- ----- Method: Form class>>fileReaderServicesForDirectory: (in category 'file list services') -----
- fileReaderServicesForDirectory: aFileDirectory
- 	^{
- 		self serviceImageImportDirectory.
- 		self serviceImageImportDirectoryWithSubdirectories.
- 	}!

Item was removed:
- ----- Method: Form class>>fileReaderServicesForFile:suffix: (in category 'file list services') -----
- fileReaderServicesForFile: fullName suffix: suffix
- 
- 	^(self  allTypicalFileExtensions 
- 		includes: suffix)
- 		ifTrue: [ self services ]
- 		ifFalse: [#()]
- !

Item was removed:
- ----- Method: Form class>>fromBMPFile: (in category 'BMP file reading') -----
- fromBMPFile: aBinaryStream
- 	"Obsolete"
- 	^self fromBinaryStream: aBinaryStream.!

Item was removed:
- ----- Method: Form class>>fromBMPFileNamed: (in category 'BMP file reading') -----
- fromBMPFileNamed: fileName
- 	"Obsolete"
- 	^self fromFileNamed: fileName
- !

Item was removed:
- ----- Method: Form class>>fromBinaryStream: (in category 'instance creation') -----
- fromBinaryStream: aBinaryStream
- 	"Read a Form or ColorForm from given file, using the first byte of the file to guess its format. Currently handles: GIF, uncompressed BMP, and both old and new DisplayObject writeOn: formats, JPEG, and PCX. Return nil if the file could not be read or was of an unrecognized format."
- 
- 	| firstByte |
- 	aBinaryStream binary.
- 	firstByte := aBinaryStream next.
- 	firstByte = 1 ifTrue: [
- 		"old Squeakform format"
- 		^ self new readFromOldFormat: aBinaryStream].
- 	firstByte = 2 ifTrue: [
- 		"new Squeak form format"
- 		^ self new readFrom: aBinaryStream].
- 
- 	"Try for JPG, GIF, or PCX..."
- 	"Note: The following call closes the stream."
- 	^ ImageReadWriter formFromStream: aBinaryStream
- !

Item was removed:
- ----- Method: Form class>>fromDisplay: (in category 'instance creation') -----
- fromDisplay: aRectangle 
- 	"Answer an instance of me with bitmap initialized from the area of the 
- 	display screen defined by aRectangle."
- 
- 	^ (self extent: aRectangle extent depth: Display depth)
- 		fromDisplay: aRectangle!

Item was removed:
- ----- Method: Form class>>fromDisplay:using: (in category 'instance creation') -----
- fromDisplay: aRectangle using: oldForm
- 	"Like fromDisplay: only if oldForm is the right size, copy into it and answer it instead."
- 
- 	((oldForm ~~ nil) and: [oldForm extent = aRectangle extent])
- 		ifTrue:
- 			[oldForm fromDisplay: aRectangle.
- 			 ^ oldForm]
- 		ifFalse:
- 			[^ self fromDisplay: aRectangle]!

Item was removed:
- ----- Method: Form class>>fromFileNamed: (in category 'instance creation') -----
- fromFileNamed: fileName
- 	"Read a Form or ColorForm from the given file."
- 
- 	| file form |
- 	file := (FileStream readOnlyFileNamed: fileName) binary.
- 	form := self fromBinaryStream: file.
- 	Smalltalk isMorphic ifTrue:[
- 		Project current resourceManager
- 			addResource: form
- 			url: (FileDirectory urlForFileNamed: file name) asString].
- 	file close.
- 	^ form
- !

Item was removed:
- ----- Method: Form class>>fromUser (in category 'instance creation') -----
- fromUser
- 	"Answer an instance of me with bitmap initialized from the area of the 
- 	display screen designated by the user. The grid for selecting an area is 
- 	1 at 1."
- 
- 	^self fromUser: 1 @ 1!

Item was removed:
- ----- Method: Form class>>fromUser: (in category 'instance creation') -----
- fromUser: gridPoint
- 	"Answer an instance of me with bitmap initialized from the area of the 
- 	display screen designated by the user. The grid for selecting an area is 
- 	aPoint. Ensures that the returned form has positive extent."
- 	| rect |
- 	rect := Rectangle fromUser: gridPoint.
- 	^ self fromDisplay: (rect origin extent: (rect extent max: gridPoint))!

Item was removed:
- ----- Method: Form class>>fromUserWithExtent: (in category 'instance creation') -----
- fromUserWithExtent: anExtent
- 	"Answer an instance of me with bitmap initialized from the area of the 
- 	display screen whose origin is designated by the user and whose size is anExtent"
- 
- 	^ self fromDisplay: (Rectangle originFromUser: anExtent)
- 
- "(Form fromUserWithExtent: 50 at 50) displayAt: 10 at 10"!

Item was removed:
- ----- Method: Form class>>importImage: (in category 'fileIn/Out') -----
- importImage: fullName
- 	"Import the given image file and store the resulting Form in the default Imports.
- 	The image is named with the short filename up to the first period, possibly with additions from the directory path to make it unique."
- 
- 	Imports default importImageFromFileNamed: fullName.
- !

Item was removed:
- ----- Method: Form class>>importImageAndShowImports: (in category 'file list services') -----
- importImageAndShowImports: fullName
- 
- 	self importImage: fullName.
- 	Imports default explore.!

Item was removed:
- ----- Method: Form class>>importImageDirectory: (in category 'fileIn/Out') -----
- importImageDirectory: dir
- 	"Import the given image file and store the resulting Form in the default Imports.
- 	The image is named with the short filename up to the first period, possibly with additions from the directory path to make it unique."
- 
- 	Imports default importImageDirectory: dir
- !

Item was removed:
- ----- Method: Form class>>importImageDirectoryWithSubdirectories: (in category 'fileIn/Out') -----
- importImageDirectoryWithSubdirectories: dir
- 	"Import the given image file and store the resulting Form in the default Imports.
- 	The image is named with the short filename up to the first period, possibly with additions from the directory path to make it unique."
- 
- 	Imports default importImageDirectoryWithSubdirectories: dir
- !

Item was removed:
- ----- Method: Form class>>initialize (in category 'initialize-release') -----
- initialize
- 
- 	FileServices registerFileReader: self!

Item was removed:
- ----- Method: Form class>>makeStar (in category 'examples') -----
- makeStar  "See the similar example in OpaqueForm"
- 	| sampleForm pen |
- 	sampleForm := Form extent: 50 at 50.  "Make a form"
- 	pen := Pen newOnForm: sampleForm.
- 	pen place: 24 at 50; turn: 18.		"Draw a 5-pointed star on it."
- 	1 to: 5 do: [:i | pen go: 19; turn: 72; go: 19; turn: -144].
- 	^ sampleForm
- "
- Form makeStar follow: [Sensor cursorPoint]
- 				while: [Sensor noButtonPressed]
- "!

Item was removed:
- ----- Method: Form class>>oldErase1bitShape (in category 'mode constants') -----
- oldErase1bitShape
- 	"Answer the integer denoting mode erase."
- 
- 	^ 17!

Item was removed:
- ----- Method: Form class>>oldPaint (in category 'mode constants') -----
- oldPaint
- 	"Answer the integer denoting the 'paint' combination rule."
- 
- 	^16!

Item was removed:
- ----- Method: Form class>>openAsBackground: (in category 'file list services') -----
- openAsBackground: fullName
- 	"Set an image as a background image.  Support Squeak's common file format 
- 	(GIF, JPG, PNG, 'Form stoteOn: (run coded)' and BMP)"
- 
- 	(self fromFileNamed: fullName) setAsBackground!

Item was removed:
- ----- Method: Form class>>openImageInWindow: (in category 'file list services') -----
- openImageInWindow: fullName
- 	"Handle five file formats: GIF, JPG, PNG, Form storeOn: (run coded), and BMP.
- 	Fail if file format is not recognized."
- 
- 	| image myStream |
- 
- 	myStream := (FileStream readOnlyFileNamed: fullName) binary.
- 	[image := self fromBinaryStream: myStream.
- 	Project current openImage: image name: fullName saveResource: true]
- 		ensure: [myStream close]!

Item was removed:
- ----- Method: Form class>>over (in category 'mode constants') -----
- over
- 	"Answer the integer denoting mode over."
- 
- 	^3!

Item was removed:
- ----- Method: Form class>>paint (in category 'mode constants') -----
- paint
- 	"Answer the integer denoting the 'paint' combination rule."
- 
- 	^25!

Item was removed:
- ----- Method: Form class>>paintAlpha (in category 'mode constants') -----
- paintAlpha
- 	"Answer the integer denoting BitBlt's paint-with-constant-alpha rule."
- 
- 	^ 31!

Item was removed:
- ----- Method: Form class>>reverse (in category 'mode constants') -----
- reverse
- 	"Answer the integer denoting mode reverse."
- 
- 	^6!

Item was removed:
- ----- Method: Form class>>rgbMul (in category 'mode constants') -----
- rgbMul
- 	"Answer the integer denoting 'Multiply each color component, 
- 	 their values regarded as fractions of 1' rule."
- 
- 	^ 37!

Item was removed:
- ----- Method: Form class>>serviceImageAsBackground (in category 'file list services') -----
- serviceImageAsBackground
- 	"Answer a service for setting the desktop background from a given graphical file's contents"
- 
- 	^ SimpleServiceEntry 
- 		provider: self 
- 		label: 'use graphic as background' translatedNoop
- 		selector: #openAsBackground:
- 		description: 'use the graphic as the background for the desktop' translatedNoop
- 		buttonLabel: 'background' translatedNoop!

Item was removed:
- ----- Method: Form class>>serviceImageImportAndShowImports (in category 'file list services') -----
- serviceImageImportAndShowImports
- 	"Answer a service for reading a graphic into ImageImports"
- 
- 	^	SimpleServiceEntry
- 			provider: self 
- 			label: 'read graphic into and show ImageImports'
- 			selector: #importImageAndShowImports:
- 			description: 'Load a graphic, placing it in the ImageImports repository and browse that repository.'
- 			buttonLabel: 'import'!

Item was removed:
- ----- Method: Form class>>serviceImageImportDirectory (in category 'file list services') -----
- serviceImageImportDirectory
- 	"Answer a service for reading a graphic into ImageImports"
- 
- 	^(SimpleServiceEntry
- 			provider: self 
- 			label: 'import all images from this directory' translatedNoop
- 			selector: #importImageDirectory:
- 			description: 'Load all graphics found in this directory, adding them to the ImageImports repository.' translatedNoop
- 			buttonLabel: 'import dir' translatedNoop)
- 			argumentGetter: [ :fileList | fileList directory ];
- 			yourself
- !

Item was removed:
- ----- Method: Form class>>serviceImageImportDirectoryWithSubdirectories (in category 'file list services') -----
- serviceImageImportDirectoryWithSubdirectories
- 	"Answer a service for reading all graphics from a directory and its subdirectories into ImageImports"
- 
- 	^(SimpleServiceEntry
- 			provider: self 
- 			label: 'import all images from here and subdirectories' translatedNoop
- 			selector: #importImageDirectoryWithSubdirectories:
- 			description: 'Load all graphics found in this directory and its subdirectories, adding them to the ImageImports repository.' translatedNoop
- 			buttonLabel: 'import subdirs' translatedNoop)
- 			argumentGetter: [ :fileList | fileList directory ];
- 			yourself
- !

Item was removed:
- ----- Method: Form class>>serviceImageImports (in category 'file list services') -----
- serviceImageImports
- 	"Answer a service for reading a graphic into ImageImports"
- 
- 	^	SimpleServiceEntry
- 			provider: self 
- 			label: 'read graphic into ImageImports'
- 			selector: #importImage:
- 			description: 'Load a graphic, placing it in the ImageImports repository.'
- 			buttonLabel: 'import'!

Item was removed:
- ----- Method: Form class>>serviceOpenImageInWindow (in category 'file list services') -----
- serviceOpenImageInWindow
- 	"Answer a service for opening a graphic in a window"
- 
- 	^ SimpleServiceEntry 
- 		provider: self 
- 		label: 'open graphic in a window' translatedNoop
- 		selector: #openImageInWindow:
- 		description: 'open a graphic file in a window' translatedNoop
- 		buttonLabel: 'open' translatedNoop!

Item was removed:
- ----- Method: Form class>>services (in category 'file list services') -----
- services
- 
- 	^ Array 
- 		with: self serviceImageImports
- 		with: self serviceImageImportAndShowImports
- 		with: self serviceOpenImageInWindow
- 		with: self serviceImageAsBackground !

Item was removed:
- ----- Method: Form class>>shutDown: (in category 'shut down') -----
- shutDown: quitting
- 	"When quitting, compress all instances in the system.  Will decompress on demand after start-up. Note that #compressOnShapshot can avoid hibernating forms during no-quit snapshotting to keep the system as responsive as possible directly after."
- 
- 	"Form shutDown: true"
- 	(quitting or: [self compressOnSnapshot]) ifTrue: [
- 		Form allInstancesDo: [:f | f hibernate].
- 		ColorForm allInstancesDo: [:f | f hibernate]].!

Item was removed:
- ----- Method: Form class>>toothpaste: (in category 'examples') -----
- toothpaste: diam		"Display restoreAfter: [Form toothpaste: 30]"
- 	"Draws wormlike lines by laying down images of spheres.
- 	See Ken Knowlton, Computer Graphics, vol. 15 no. 4 p352.
- 	Draw with mouse button down; terminate by option-click."
- 	| facade ball filter point queue port color q colors colr colr2 |
- 	colors := Display depth = 1
- 		ifTrue: [Array with: Color black]
- 		ifFalse: [Color red wheel: 12].
- 	facade := Form extent: diam at diam offset: (diam // -2) asPoint.
- 	(Form dotOfSize: diam) displayOn: facade
- 			at: (diam // 2) asPoint clippingBox: facade boundingBox
- 			rule: Form under fillColor: Color white.
- 	#(1 2 3) do:
- 		[:x |  "simulate facade by circles of gray"
- 		(Form dotOfSize: x * diam // 5) displayOn: facade
- 			at: (diam * 2 // 5) asPoint clippingBox: facade boundingBox
- 			rule: Form under
- 			fillColor: (Color perform: 
- 					(#(black gray lightGray) at: x)).
- 		"facade displayAt: 50*x at 50"].
- 	ball := Form dotOfSize: diam.
- 	color := 8.
- 	[port := BitBlt toForm: Display.
- 	"Expand 1-bit forms to any pixel depth"
- 	port colorMap: (Bitmap with: 0 with: 16rFFFFFFFF).
- 	queue := OrderedCollection new: 32.
- 	16 timesRepeat: [queue addLast: -20 @ -20].
- 	Sensor waitButton.
- 	Sensor yellowButtonPressed ifTrue: [^ self].
- 	filter := Sensor cursorPoint.
- 	colr := colors atWrap: (color := color + 5).  "choose increment relatively prime to colors size"
- 	colr2 := colr alphaMixed: 0.3 with: Color white.
- 	[Sensor redButtonPressed or: [queue size > 0]] whileTrue:
- 		[filter := filter * 4 + Sensor cursorPoint  //  5.
- 		point := Sensor redButtonPressed
- 			ifTrue: [filter] ifFalse: [-20 @ -20].
- 		port copyForm: ball to: point rule: Form paint fillColor: colr.
- 		(q := queue removeFirst) == nil ifTrue: [^ self].	"exit"
- 		Display depth = 1
- 			ifTrue: [port copyForm: facade to: q rule: Form erase]
- 			ifFalse: [port copyForm: facade to: q rule: Form paint fillColor: colr2].
- 		Sensor redButtonPressed ifTrue: [queue addLast: point]]] repeat.
- !

Item was removed:
- ----- Method: Form class>>under (in category 'mode constants') -----
- under
- 	"Answer the integer denoting mode under."
- 
- 	^7!

Item was removed:
- ----- Method: Form class>>unload (in category 'class initialization') -----
- unload
- 
- 	FileServices unregisterFileReader: self !

Item was removed:
- ----- Method: Form class>>xorHack: (in category 'examples') -----
- xorHack: size  "Display restoreAfter: [Form xorHack: 256]"
- 	"Draw a smiley face or stick figure, and end with option-click.
- 	Thereafter image gets 'processed' as long as you have button down.
- 	If you stop at just the right time, you'll see you figure upside down,
- 	and at the end of a full cycle, you'll see it perfectly restored.
- 	Dude -- this works in color too!!"
- 	| rect form i bb |
- 	rect := 5 @ 5 extent: size @ size.
- 	Display fillWhite: rect; border: (rect expandBy: 2) width: 2.
- 	Display border: (rect topRight - (0 @ 2) extent: rect extent * 2 + 4) width: 2.
- 	Form exampleSketch.
- 	form := Form fromDisplay: rect.
- 	bb := form boundingBox.
- 	i := 0.
- 	[Sensor yellowButtonPressed] whileFalse:
- 		[[Sensor redButtonPressed] whileTrue:
- 			[i := i + 1.
- 			(Array with: 0 @ 1 with: 0 @ -1 with: 1 @ 0 with: -1 @ 0) do:
- 				[:d | form copyBits: bb from: form at: d
- 					clippingBox: bb rule: Form reverse fillColor: nil].
- 			form displayAt: rect topLeft.
- 			i+2\\size < 4 ifTrue: [(Delay forMilliseconds: 300) wait]].
- 		(form magnify: form boundingBox by: 2 @ 2) displayAt: rect topRight + (2 @ 0).
- 		Sensor waitButton].!

Item was removed:
- ----- Method: Form>>adjustBrightness: (in category 'converting') -----
- adjustBrightness: brightness
- 
- 	^ self collectColors: [:color | color adjustSaturation: 0 brightness: brightness]!

Item was removed:
- ----- Method: Form>>adjustSaturation: (in category 'converting') -----
- adjustSaturation: saturation
- 
- 	^ self collectColors: [:color | color adjustSaturation: saturation brightness: 0]!

Item was removed:
- ----- Method: Form>>allocateForm: (in category 'initialize-release') -----
- allocateForm: extentPoint
- 	"Allocate a new form which is similar to the receiver and can be used for accelerated blts"
- 	^Form extent: extentPoint depth: self nativeDepth!

Item was removed:
- ----- Method: Form>>anyShapeFill (in category 'filling') -----
- anyShapeFill
- 	"Fill the interior of the outermost outlined region in the receiver, a 1-bit deep form.  Typically the resulting form is used with fillShape:fillColor: to paint a solid color.  See also convexShapeFill:"
- 
- 	| shape |
- 	"Draw a seed line around the edge and fill inward from the outside."
- 	shape := self findShapeAroundSeedBlock: [:f | f borderWidth: 1].
- 	"Reverse so that this becomes solid in the middle"
- 	shape := shape reverse.
- 	"Finally erase any bits from the original so the fill is only elsewhere"
- 	shape copy: shape boundingBox from: self to: 0 at 0 rule: Form erase.
- 	^ shape!

Item was removed:
- ----- Method: Form>>approxGaussianBlur (in category 'processing') -----
- approxGaussianBlur
- 
- 	^ self processUsingKernel: (Matrix rows: 3 columns: 3 contents: #(
- 		 1 2 1
- 		 2 4 2
- 		 1 2 1
- 	) *  0.0625)!

Item was removed:
- ----- Method: Form>>as8BitColorForm (in category 'converting') -----
- as8BitColorForm
- 	"Simple conversion of zero pixels to transparent.  Force it to 8 bits."
- 
- 	| f map |
- 	f := ColorForm extent: self extent depth: 8.
- 	self displayOn: f at: self offset negated.
- 	map := Color indexedColors copy.
- 	map at: 1 put: Color transparent.
- 	f colors: map.
- 	f offset: self offset.
- 	^ f
- !

Item was removed:
- ----- Method: Form>>asCursorForm (in category 'converting') -----
- asCursorForm
- 
- 	^ self as: StaticForm!

Item was removed:
- ----- Method: Form>>asFormOfDepth: (in category 'converting') -----
- asFormOfDepth: d
- 	"Create a copy of me with depth 'd'. Includes a correction for some bitmaps that when imported have poorly set up transparency"
- 	| newForm |
- 	d = self depth ifTrue:[^self].
- 	newForm := Form extent: self extent depth: d.
- 	(BitBlt toForm: newForm)
- 		colorMap: (self colormapIfNeededFor: newForm);
- 		copy: (self boundingBox)
- 		from: 0 at 0 in: self
- 		fillColor: nil rule: Form over.
- 	"Special case: For a 16 -> 32 bit conversion fill the alpha channel because it gets lost in translation."
- 	d = 32 ifTrue:[newForm fixAlpha].
- 	^newForm!

Item was removed:
- ----- Method: Form>>asGrayScale (in category 'converting') -----
- asGrayScale
- 	"Assume the receiver is a grayscale image. Return a grayscale ColorForm computed by extracting the brightness levels of one color component. This technique allows a 32-bit Form to be converted to an 8-bit ColorForm to save space while retaining a full 255 levels of gray. (The usual colormapping technique quantizes to 8, 16, or 32 levels, which loses information.)"
- 	| f32 srcForm result map bb |
- 	self depth = 32 ifFalse: [
- 		f32 := Form extent: width at height depth: 32.
- 		self displayOn: f32.
- 		^ f32 asGrayScale].
- 	self unhibernate.
- 	srcForm := Form extent: (width * 4)@height depth: 8.
- 	srcForm bits: bits.
- 	result := ColorForm extent: width at height depth: 8.
- 	map := Bitmap new: 256.
- 	2 to: 256 do: [:i | map at: i put: i - 1].
- 	map at: 1 put: 1.  "map zero pixel values to near-black"
- 	bb := (BitBlt toForm: result)
- 		sourceForm: srcForm;
- 		combinationRule: Form over;
- 		colorMap: map.
- 	0 to: width - 1 do: [:dstX |
- 		bb  sourceRect: (((dstX * 4) + 2)@0 extent: 1 at height);
- 			destOrigin: dstX at 0;
- 			copyBits].
- 
- 	"final BitBlt to zero-out pixels that were truely transparent in the original"
- 	map := Bitmap new: 512.
- 	map at: 1 put: 16rFF.
- 	(BitBlt toForm: result)
- 		sourceForm: self;
- 		sourceRect: self boundingBox;
- 		destOrigin: 0 at 0;
- 		combinationRule: Form erase;
- 		colorMap: map;
- 		copyBits.
- 	
- 	
- 	result colors: ColorForm grayScalePalette.
- 	^ result
- !

Item was removed:
- ----- Method: Form>>asSourceForm (in category 'converting') -----
- asSourceForm
- 	^self!

Item was removed:
- ----- Method: Form>>asTextAnchor (in category 'converting') -----
- asTextAnchor
- 	"Convert the receiver to be embedded in text."
- 
- 	self flag: #refactor. "mt: Text anchors should work outside of Morphic, too. Any instance of Form could be embedded in Text."
- 	^ (Smalltalk classNamed: 'TextAnchor')
- 		ifNil: [TextColor black "Fall back"]
- 		ifNotNil: [:cls | cls new anchoredMorph: self]!

Item was removed:
- ----- Method: Form>>balancedPatternFor: (in category 'color mapping') -----
- balancedPatternFor: aColor
- 	"Return the pixel word for representing the given color on the receiver"
- 	^aColor balancedPatternForDepth: self depth!

Item was removed:
- ----- Method: Form>>bitEdit (in category 'editing') -----
- bitEdit
- 	"Create and schedule a view located in an area designated by the user 
- 	that contains a view of the receiver magnified by 8 at 8 that can be 
- 	modified using the Bit Editor. It also contains a view of the original 
- 	form."
- 
- 	Project current bitEdit: self
- !

Item was removed:
- ----- Method: Form>>bitEditAt:scale: (in category 'editing') -----
- bitEditAt: magnifiedFormLocation scale: scaleFactor 
- 	"Create and schedule a view whose top left corner is magnifiedLocation 
- 	and that contains a view of the receiver magnified by scaleFactor that 
- 	can be modified using the Bit Editor. It also contains a view of the 
- 	original form."
- 
- 	Project current bitEdit: self at: magnifiedFormLocation scale: scaleFactor 
- !

Item was removed:
- ----- Method: Form>>bitPatternFor: (in category 'color mapping') -----
- bitPatternFor: aColor
- 	"Return the pixel word for representing the given color on the receiver"
- 	^aColor bitPatternForDepth: self depth!

Item was removed:
- ----- Method: Form>>bitPatternForDepth: (in category 'filling') -----
- bitPatternForDepth: suspectedDepth
- 	"Only called when a Form is being used as a fillColor.  Use a Pattern or InfiniteForm instead for this purpose.
- 	Interpret me as an array of (32/depth) Color pixelValues.  BitBlt aligns the first element of this array with the top scanline of the destinationForm, the second with the second, and so on, cycling through the color array as necessary. 6/18/96 tk"
- 
- 	^ self!

Item was removed:
- ----- Method: Form>>bits (in category 'accessing') -----
- bits
- 	"Answer the receiver's Bitmap containing its bits."
- 
- 	^ bits!

Item was removed:
- ----- Method: Form>>bits: (in category 'accessing') -----
- bits: aBitmap 
- 	"Reset the Bitmap containing the receiver's bits."
- 
- 	bits := aBitmap!

Item was removed:
- ----- Method: Form>>bitsPerComponent (in category 'postscript generation') -----
- bitsPerComponent
- 	^self depth <= 8 ifTrue:[self depth] ifFalse:[8].
- !

Item was removed:
- ----- Method: Form>>bitsSize (in category 'accessing') -----
- bitsSize
- 	| pixelsPerWord |
- 	depth ifNil: [depth := 1].
- 	pixelsPerWord := 32 // self depth.
- 	^width + pixelsPerWord - 1 // pixelsPerWord * height!

Item was removed:
- ----- Method: Form>>blankCopyOf:scaledBy: (in category 'copying') -----
- blankCopyOf: aRectangle scaledBy: scale 
- 	^ self species
- 		extent: (aRectangle extent * scale) truncated
- 		depth: depth!

Item was removed:
- ----- Method: Form>>border:width:rule:fillColor: (in category 'bordering') -----
- border: rect width: borderWidth rule: rule fillColor: fillColor
-         "Paint a border whose rectangular area is defined by rect. The
- width of the border of each side is borderWidth. Uses fillColor for drawing
- the border."
-         | blt |
-         blt := (BitBlt toForm: self) combinationRule: rule; fillColor: fillColor.
-         blt sourceOrigin: 0 at 0.
-         blt destOrigin: rect origin.
-         blt width: rect width; height: borderWidth; copyBits.
-         blt destY: rect corner y - borderWidth; copyBits.
-         blt destY: rect origin y + borderWidth.
-         blt height: rect height - borderWidth - borderWidth; width:
- borderWidth; copyBits.
-         blt destX: rect corner x - borderWidth; copyBits!

Item was removed:
- ----- Method: Form>>borderFormOfWidth:sharpCorners: (in category 'bordering') -----
- borderFormOfWidth: borderWidth sharpCorners: sharpen
- 	"Smear this form around and then subtract the original to produce
- 	an outline.  If sharpen is true, then cause right angles to be outlined
- 	by right angles (takes an additional diagonal smears ANDed with both
- 	horizontal and vertical smears)."
- 	| smearForm bigForm smearPort all cornerForm cornerPort nbrs |
- 	self depth > 1 ifTrue: [self halt]. "Only meaningful for B/W forms."
- 	bigForm := self deepCopy.
- 	all := bigForm boundingBox.
- 	smearForm := Form extent: self extent.
- 	smearPort := BitBlt toForm: smearForm.
- 	sharpen ifTrue:
- 		[cornerForm := Form extent: self extent.
- 		cornerPort := BitBlt toForm: cornerForm].
- 	nbrs := (0 at 0) fourNeighbors.
- 	1 to: borderWidth do:
- 		[:i |  "Iterate to get several layers of 'skin'"
- 		nbrs do:
- 			[:d |  "Smear the self in 4 directions to grow each layer of skin"
- 			smearPort copyForm: bigForm to: d rule: Form under].
- 		sharpen ifTrue:
- 			["Special treatment to smear sharp corners"
- 			nbrs with: ((2 to: 5) collect: [:i2 | nbrs atWrap: i2]) do:
- 				[:d1 :d2 |
- 				"Copy corner points diagonally"
- 				cornerPort copyForm: bigForm to: d1+d2 rule: Form over.
- 				"But only preserve if there were dots on either side"
- 				cornerPort copyForm: bigForm to: d1+d1+d2 rule: Form and.
- 				cornerPort copyForm: bigForm to: d1+d2+d2 rule: Form and.
- 				smearPort copyForm: cornerForm to: 0 at 0 rule: Form under].
- 			].
- 		bigForm copy: all from: 0 at 0 in: smearForm rule: Form over.
- 		].
- 	"Now erase the original shape to obtain the outline"
- 	bigForm copy: all from: 0 at 0 in: self rule: Form erase.
- 	^ bigForm!

Item was removed:
- ----- Method: Form>>borderWidth: (in category 'bordering') -----
- borderWidth: anInteger 
- 	"Set the width of the border for the receiver to be anInteger and paint it 
- 	using black as the border color."
- 
- 	self border: self boundingBox width: anInteger fillColor: Color black!

Item was removed:
- ----- Method: Form>>borderWidth:color: (in category 'bordering') -----
- borderWidth: anInteger color: aMask
- 	"Set the width of the border for the receiver to be anInteger and paint it 
- 	using aMask as the border color."
- 
- 	self border: self boundingBox width: anInteger fillColor: aMask!

Item was removed:
- ----- Method: Form>>borderWidth:fillColor: (in category 'bordering') -----
- borderWidth: anInteger fillColor: aMask
- 	"Set the width of the border for the receiver to be anInteger and paint it 
- 	using aMask as the border color."
- 
- 	self border: self boundingBox width: anInteger fillColor: aMask!

Item was removed:
- ----- Method: Form>>boundingBox (in category 'display box access') -----
- boundingBox
- 	^ Rectangle origin: 0 @ 0
- 			corner: width @ height!

Item was removed:
- ----- Method: Form>>bytesPerRow (in category 'postscript generation') -----
- bytesPerRow
- 	^ self numComponents * self paddedWidth * self bitsPerComponent / 8.!

Item was removed:
- ----- Method: Form>>center (in category 'display box access') -----
- center
- 	"Note that offset is ignored here.  Are we really going to embrace offset?  "
- 	^ (width @ height) // 2!

Item was removed:
- ----- Method: Form>>cgForPixelValue:orNot: (in category 'analyzing') -----
- cgForPixelValue: pv orNot: not
- 	"Return the center of gravity for all pixels of value pv.
- 	Note:  If orNot is true, then produce the center of gravity for all pixels
- 	that are DIFFERENT from the supplied (background) value"
- 	| xAndY |
- 	xAndY := (Array with: (self xTallyPixelValue: pv orNot: not)
- 					with: (self yTallyPixelValue: pv orNot: not)) collect:
- 		[:profile | | pixCount weighted |	"For both x and y profiles..."
- 		pixCount := 0.  weighted := 0.
- 		profile withIndexDo:
- 			[:t :i | pixCount := pixCount + t.
- 			weighted := weighted + (t*i)].
- 		pixCount = 0  "Produce average of nPixels weighted by coordinate"
- 			ifTrue: [0.0]
- 			ifFalse: [weighted asFloat / pixCount asFloat - 1.0]].
- 
- 	^ xAndY first @ xAndY last
- "
- | f cg |
- [Sensor anyButtonPressed] whileFalse:
- 	[f := Form fromDisplay: (Sensor cursorPoint extent: 50 at 50).
- 	cg := f cgForPixelValue: (Color black pixelValueForDepth: f depth) orNot: false.
- 	f displayAt: 0 at 0.
- 	Display fill: (cg extent: 2 at 2) fillColor: Color red].
- 	ScheduledControllers restore
- "!

Item was removed:
- ----- Method: Form>>clippedToSize: (in category 'scaling, rotation') -----
- clippedToSize: aPoint
-  	"Return a copy of this form that is clipped to the given size around the center."
- 	
- 	| newForm |
- 	newForm := self class extent: aPoint depth: depth.
- 	^ newForm copyBits: ((0 at 0 corner: aPoint) translateBy: (self extent - aPoint) // 2) from: self at: 0 at 0
- 		clippingBox: newForm boundingBox rule: Form over fillColor: nil!

Item was removed:
- ----- Method: Form>>collectColors: (in category 'converting') -----
- collectColors: aBlock
- 	"Create a new copy of the receiver with all the colors transformed by aBlock"
- 	^self collectPixels:[:pv|
- 		(aBlock value: (Color colorFromPixelValue: pv depth: self depth)) 
- 			pixelValueForDepth: self depth.
- 	].!

Item was removed:
- ----- Method: Form>>collectPixels: (in category 'converting') -----
- collectPixels: aBlock
- 	"Create a new copy of the receiver with all the pixels transformed by aBlock"
- 	self depth = 32 ifFalse:[
- 		"Perform the operation in 32bpp"
- 		^((self asFormOfDepth: 32) collectPixels: aBlock) asFormOfDepth: self depth].
- 	self unhibernate. "ensure unhibernated before touching bits"
- 	^Form 
- 		extent: self extent 
- 		depth: self depth
- 		bits: (self bits collect: aBlock)!

Item was removed:
- ----- Method: Form>>colorAt: (in category 'pixel access') -----
- colorAt: aPoint
- 	"Return the color in the pixel at the given point.  "
- 
- 	^ Color 
- 		colorFromPixelValue: (self pixelValueAt: aPoint)
- 		depth: self depth
- !

Item was removed:
- ----- Method: Form>>colorAt:put: (in category 'pixel access') -----
- colorAt: aPoint put: aColor
- 	"Store a Color into the pixel at coordinate aPoint.  "
- 
- 	self pixelValueAt: aPoint put: (self pixelValueFor: aColor).
- 
- "[Sensor anyButtonPressed] whileFalse:
- 	[Display colorAt: Sensor cursorPoint put: Color red]"
- !

Item was removed:
- ----- Method: Form>>colorReduced (in category 'converting') -----
- colorReduced
- 	"Return a color-reduced ColorForm version of the receiver, if possible, or the receiver itself if not."
- 
- 	| tally tallyDepth colorCount newForm cm oldPixelValues newFormColors nextColorIndex c |
- 	tally := self tallyPixelValues asArray.
- 	tallyDepth := (tally size log: 2) asInteger.
- 	colorCount := 0.
- 	tally do: [:n | n > 0 ifTrue: [colorCount := colorCount + 1]].
- 	(tally at: 1) = 0 ifTrue: [colorCount := colorCount + 1].  "include transparent"
- 	colorCount > 256 ifTrue: [^ self].  "cannot reduce"
- 	newForm := self formForColorCount: colorCount.
- 
- 	"build an array of just the colors used, and a color map to translate
- 	 old pixel values to their indices into this color array"
- 	cm := Bitmap new: tally size.
- 	oldPixelValues := self colormapIfNeededForDepth: 32.
- 	newFormColors := Array new: colorCount.
- 	newFormColors at: 1 put: Color transparent.
- 	nextColorIndex := 2.
- 	2 to: cm size do: [:i |
- 		(tally at: i) > 0 ifTrue: [
- 			oldPixelValues = nil
- 				ifTrue: [c := Color colorFromPixelValue: i - 1 depth: tallyDepth]
- 				ifFalse: [c := Color colorFromPixelValue: (oldPixelValues at: i) depth: 32].
- 			newFormColors at: nextColorIndex put: c.
- 			cm at: i put: nextColorIndex - 1.  "pixel values are zero-based indices"
- 			nextColorIndex := nextColorIndex + 1]].
- 
- 	"copy pixels into new ColorForm, mapping to new pixel values"
- 	newForm copyBits: self boundingBox
- 		from: self
- 		at: 0 at 0
- 		clippingBox: self boundingBox
- 		rule: Form over
- 		fillColor: nil
- 		map: cm.
- 	newForm colors: newFormColors.
- 	newForm offset: offset.
- 	^ newForm
- !

Item was removed:
- ----- Method: Form>>colormapFromARGB (in category 'color mapping') -----
- colormapFromARGB
- 	"Return a ColorMap mapping from canonical ARGB space into the receiver.
- 	Note: This version is optimized for Squeak forms."
- 	| map nBits |
- 	self depth <= 8 ifTrue:[
- 		map := Color colorMapIfNeededFrom: 32 to: self depth.
- 		map size = 512 ifTrue:[nBits := 3].
- 		map size = 4096 ifTrue:[nBits := 4].
- 		map size = 32768 ifTrue:[nBits := 5].
- 		^ColorMap
- 			shifts: (Array 
- 						with: 3 * nBits - 24
- 						with: 2 * nBits - 16
- 						with: 1 * nBits - 8
- 						with: 0)
- 			masks: (Array
- 						with: (1 << nBits) - 1 << (24 - nBits)
- 						with: (1 << nBits) - 1 << (16 - nBits)
- 						with: (1 << nBits) - 1 << (8 - nBits)
- 						with: 0)
- 			colors: map].
- 	self depth = 16 ifTrue:[
- 		^ColorMap
- 			shifts: #(-9 -6 -3 0)
- 			masks: #(16rF80000 16rF800 16rF8 0)].
- 	self depth = 32 ifTrue:[
- 		^ColorMap
- 			shifts: #(0 0 0 0)
- 			masks: #(16rFF0000 16rFF00 16rFF 16rFF000000)].
- 	self error:'Bad depth'!

Item was removed:
- ----- Method: Form>>colormapIfNeededFor: (in category 'color mapping') -----
- colormapIfNeededFor: destForm
- 	"Return a ColorMap mapping from the receiver to destForm."
- 	(self hasNonStandardPalette or:[destForm hasNonStandardPalette]) 
- 		ifTrue:[^self colormapFromARGB mappingTo: destForm colormapFromARGB]
- 		ifFalse:[^self colormapIfNeededForDepth: destForm depth]!

Item was removed:
- ----- Method: Form>>colormapIfNeededForDepth: (in category 'color mapping') -----
- colormapIfNeededForDepth: destDepth
- 	"Return a colormap for displaying the receiver at the given depth, or nil if no colormap is needed."
- 
- 	self depth = destDepth ifTrue: [^ nil].  "not needed if depths are the same"
- 	^ Color colorMapIfNeededFrom: self depth to: destDepth
- !

Item was removed:
- ----- Method: Form>>colormapToARGB (in category 'color mapping') -----
- colormapToARGB
- 	"Return a ColorMap mapping from the receiver into canonical ARGB space."
- 	self depth <= 8 ifTrue:[
- 		^ColorMap
- 			shifts: #(0 0 0 0)
- 			masks: #(16rFF0000 16rFF00 16rFF 16rFF000000)
- 			colors: (Color colorMapIfNeededFrom: self depth to: 32)].
- 	self depth = 16 ifTrue:[
- 		^ColorMap 
- 			shifts: #( 9 6 3 0) 
- 			masks: #(16r7C00 16r3E0 16r1F 0)].
- 	self depth = 32 ifTrue:[
- 		^ColorMap
- 			shifts: #(0 0 0 0) 
- 			masks: #(16rFF0000 16rFF00 16rFF 16rFF000000)].
- 	self error:'Bad depth'!

Item was removed:
- ----- Method: Form>>colorsUsed (in category 'analyzing') -----
- colorsUsed
- 	"Return a list of the Colors this form uses."
- 
- 	| tallies tallyDepth usedColors |
- 	tallies := self tallyPixelValues.
- 	tallyDepth := (tallies size log: 2) asInteger.
- 	usedColors := OrderedCollection new.
- 	tallies withIndexDo: [:count :i |
- 		count > 0 ifTrue: [
- 			usedColors add: (Color colorFromPixelValue: i - 1 depth: tallyDepth)]].
- 	^ usedColors asArray
- !

Item was removed:
- ----- Method: Form>>comeFullyUpOnReload: (in category 'fileIn/Out') -----
- comeFullyUpOnReload: smartRefStream
- 	bits isForm ifFalse:[^self].
- 	"make sure the resource gets loaded afterwards"
- 	ResourceCollector current ifNil:[^self].
- 	ResourceCollector current noteResource: bits replacing: self.
- !

Item was removed:
- ----- Method: Form>>computeBoundingBox (in category 'display box access') -----
- computeBoundingBox
- 	^ Rectangle origin: 0 @ 0
- 			corner: width @ height!

Item was removed:
- ----- Method: Form>>contentsOfArea: (in category 'copying') -----
- contentsOfArea: aRect
-  	"Return a new form which derives from the portion of the original form delineated by aRect."
- 	^self contentsOfArea: aRect 
- 		into: (self species extent: aRect extent depth: depth).!

Item was removed:
- ----- Method: Form>>contentsOfArea:into: (in category 'copying') -----
- contentsOfArea: aRect into: newForm
-  	"Return a new form which derives from the portion of the original form delineated by aRect."
- 	^ newForm copyBits: aRect from: self at: 0 at 0
- 		clippingBox: newForm boundingBox rule: Form over fillColor: nil!

Item was removed:
- ----- Method: Form>>convexShapeFill: (in category 'filling') -----
- convexShapeFill: aMask 
- 	"Fill the interior of the outtermost outlined region in the receiver.  The outlined region must not be concave by more than 90 degrees.  Typically aMask is Color black, to produce a solid fill. then the resulting form is used with fillShape: to paint a solid color.  See also anyShapeFill"
- 	| destForm tempForm |
- 	destForm := Form extent: self extent.  destForm fillBlack.
- 	tempForm := Form extent: self extent.
- 	(0 at 0) fourNeighbors do:
- 		[:dir |  "Smear self in all 4 directions, and AND the result"
- 		self displayOn: tempForm at: (0 at 0) - self offset.
- 		tempForm smear: dir distance: (dir dotProduct: tempForm extent) abs.
- 		tempForm displayOn: destForm at: 0 at 0
- 			clippingBox: destForm boundingBox
- 			rule: Form and fillColor: nil].
- 	destForm displayOn: self at: 0 at 0
- 		clippingBox: self boundingBox
- 		rule: Form over fillColor: aMask!

Item was removed:
- ----- Method: Form>>copy: (in category 'copying') -----
- copy: aRect
-  	"Return a new form which derives from the portion of the original form delineated by aRect."
- 	| newForm |
- 	newForm := self species extent: aRect extent depth: depth.
- 	^ newForm copyBits: aRect from: self at: 0 at 0
- 		clippingBox: newForm boundingBox rule: Form over fillColor: nil!

Item was removed:
- ----- Method: Form>>copy:from:in:rule: (in category 'copying') -----
- copy: destRectangle from: sourcePt in: sourceForm rule: rule 
- 	"Make up a BitBlt table and copy the bits."
- 	(BitBlt toForm: self)
- 		copy: destRectangle
- 		from: sourcePt in: sourceForm
- 		fillColor: nil rule: rule!

Item was removed:
- ----- Method: Form>>copy:from:to:rule: (in category 'copying') -----
- copy: sourceRectangle from: sourceForm to: destPt rule: rule
- 	^ self copy: (destPt extent: sourceRectangle extent)
- 		from: sourceRectangle topLeft in: sourceForm rule: rule!

Item was removed:
- ----- Method: Form>>copyBits:at:translucent: (in category 'copying') -----
- copyBits: sourceForm at: destOrigin translucent: factor
- 	"Make up a BitBlt table and copy the bits with the given colorMap."
- 	(BitBlt 
- 		destForm: self
- 		sourceForm: sourceForm
- 		halftoneForm: nil
- 		combinationRule: 30
- 		destOrigin: destOrigin
- 		sourceOrigin: 0 at 0
- 		extent: sourceForm extent
- 		clipRect: self boundingBox)
- 		copyBitsTranslucent: ((0 max: (factor*255.0) asInteger) min: 255)
- "
-  | f f2 f3 | f := Form fromUser. f2 := Form fromDisplay: (0 at 0 extent: f extent). f3 := f2 deepCopy.
- 0.0 to: 1.0 by: 1.0/32 do:
- 	[:t | f3 := f2 deepCopy. f3 copyBits: f at: 0 at 0 translucent: t.
- 	f3 displayAt: 0 at 0. (Delay forMilliseconds: 100) wait].
- "!

Item was removed:
- ----- Method: Form>>copyBits:from:at:clippingBox:rule:fillColor: (in category 'copying') -----
- copyBits: sourceRect from: sourceForm at: destOrigin clippingBox: clipRect rule: rule fillColor: aForm 
- 	"Make up a BitBlt table and copy the bits."
- 
- 	(BitBlt 
- 		destForm: self
- 		sourceForm: sourceForm
- 		fillColor: aForm
- 		combinationRule: rule
- 		destOrigin: destOrigin
- 		sourceOrigin: sourceRect origin
- 		extent: sourceRect extent
- 		clipRect: clipRect) copyBits!

Item was removed:
- ----- Method: Form>>copyBits:from:at:clippingBox:rule:fillColor:map: (in category 'copying') -----
- copyBits: sourceRect from: sourceForm at: destOrigin clippingBox: clipRect rule: rule fillColor: aForm map: map
- 	"Make up a BitBlt table and copy the bits.  Use a colorMap."
- 
- 	((BitBlt 
- 		destForm: self
- 		sourceForm: sourceForm
- 		fillColor: aForm
- 		combinationRule: rule
- 		destOrigin: destOrigin
- 		sourceOrigin: sourceRect origin
- 		extent: sourceRect extent
- 		clipRect: clipRect) colorMap: map) copyBits!

Item was removed:
- ----- Method: Form>>copyBits:from:at:colorMap: (in category 'copying') -----
- copyBits: sourceRect from: sourceForm at: destOrigin colorMap: map 
- 	"Make up a BitBlt table and copy the bits with the given colorMap."
- 	((BitBlt 
- 		destForm: self
- 		sourceForm: sourceForm
- 		halftoneForm: nil
- 		combinationRule: Form over
- 		destOrigin: destOrigin
- 		sourceOrigin: sourceRect origin
- 		extent: sourceRect extent
- 		clipRect: self boundingBox) colorMap: map) copyBits!

Item was removed:
- ----- Method: Form>>copyWithColorsReducedTo: (in category 'converting') -----
- copyWithColorsReducedTo: nColors
- 	"Note: this has not been engineered.
- 	There are better solutions in the literature."
- 	| palette colorMap |
- 	self depth > 16 ifTrue:[^(self asFormOfDepth: 16) copyWithColorsReducedTo: nColors]. "First reduce to 16 bit depth"
- 	palette := self reducedPaletteOfSize: nColors.
- 	colorMap := (1 to: (1 bitShift: depth)) collect:
- 		[:i | | pc closest |
- 		pc := Color colorFromPixelValue: i-1 depth: depth.
- 		closest := palette detectMin: [:c | c diff: pc].
- 		closest pixelValueForDepth: depth].
- 	^ self deepCopy copyBits: self boundingBox from: self at: 0 at 0 colorMap: (colorMap as: Bitmap)
- 		!

Item was removed:
- ----- Method: Form>>darker (in category 'converting') -----
- darker
- 	"Answer a darker variant of this form."
- 	^self collectColors:[:color| color darker darker]!

Item was removed:
- ----- Method: Form>>decodeArray (in category 'postscript generation') -----
- decodeArray
- 	^self depth <= 8 ifTrue:['[1 0]'] ifFalse:['[0 1 0 1 0 1 ]'].
- !

Item was removed:
- ----- Method: Form>>deepCopy (in category 'copying') -----
- deepCopy
- 	^self copy!

Item was removed:
- ----- Method: Form>>defaultCanvasClass (in category 'accessing') -----
- defaultCanvasClass
- 	"Return the default canvas used for drawing onto the receiver"
- 	^Display defaultCanvasClass!

Item was removed:
- ----- Method: Form>>depth (in category 'accessing') -----
- depth
- 	^ depth < 0 ifTrue:[0-depth] ifFalse:[depth]!

Item was removed:
- ----- Method: Form>>depth: (in category 'accessing') -----
- depth: bitsPerPixel
- 	(bitsPerPixel > 32 or:
- 		[(bitsPerPixel bitAnd: bitsPerPixel-1) ~= 0])
- 		ifTrue: [self halt: 'bitsPerPixel must be 1, 2, 4, 8, 16 or 32'].
- 	depth := bitsPerPixel!

Item was removed:
- ----- Method: Form>>dimmed (in category 'converting') -----
- dimmed
- 	"Answer a dimmed variant of this form."
- 	^self collectColors:[:color| (color alpha: (color alpha min: 0.2)) ]!

Item was removed:
- ----- Method: Form>>displayInterpolatedIn:on: (in category 'displaying') -----
- displayInterpolatedIn: aRectangle on: aForm
- 	"Display the receiver on aForm, using interpolation if necessary.
- 		Form fromUser displayInterpolatedOn: Display.
- 	Note: When scaling we attempt to use bilinear interpolation based
- 	on the 3D engine. If the engine is not there then we use WarpBlt.
- 	"
- 	| engine adjustedR |
- 	self extent = aRectangle extent ifTrue:[^self displayOn: aForm at: aRectangle origin].
- 	engine := Smalltalk at: #B3DRenderEngine 
- 		ifPresent: [:engineClass | (engineClass defaultForPlatformOn: aForm)].
- 	engine ifNil:[
- 		"We've got no bilinear interpolation. Use WarpBlt instead"
- 		(WarpBlt toForm: aForm)
- 			sourceForm: self destRect: aRectangle;
- 			combinationRule: 3;
- 			cellSize: 2;
- 			warpBits.
- 		^self
- 	].
- 
- 	"Otherwise use the 3D engine for our purposes"
- 
- 	"there seems to be a slight bug in B3D which the following adjusts for"
- 	adjustedR := (aRectangle withRight: aRectangle right + 1) translateBy: 0 at 1.
- 	engine viewport: adjustedR.
- 	engine material: ((Smalltalk at: #B3DMaterial) new emission: Color white).
- 	engine texture: self.
- 	engine render: ((Smalltalk at: #B3DIndexedQuadMesh) new plainTextureRect).
- 	engine finish.!

Item was removed:
- ----- Method: Form>>displayInterpolatedOn: (in category 'displaying') -----
- displayInterpolatedOn: aForm
- 	"Display the receiver on aForm, using interpolation if necessary.
- 		Form fromUser displayInterpolatedOn: Display.
- 	Note: When scaling we attempt to use bilinear interpolation based
- 	on the 3D engine. If the engine is not there then we use WarpBlt.
- 	"
- 	| engine |
- 	self extent = aForm extent ifTrue:[^self displayOn: aForm].
- 	engine := Smalltalk at: #B3DRenderEngine 
- 		ifPresent:[:engineClass| (engineClass defaultForPlatformOn: aForm)].
- 	engine ifNil:[
- 		"We've got no bilinear interpolation. Use WarpBlt instead"
- 		(WarpBlt toForm: aForm)
- 			sourceForm: self destRect: aForm boundingBox;
- 			combinationRule: 3;
- 			cellSize: 2;
- 			warpBits.
- 		^self
- 	].
- 	"Otherwise use the 3D engine for our purposes"
- 	engine viewport: aForm boundingBox.
- 	engine material: ((Smalltalk at: #B3DMaterial) new emission: Color white).
- 	engine texture: self.
- 	engine render: ((Smalltalk at: #B3DIndexedQuadMesh) new plainTextureRect).
- 	engine finish.!

Item was removed:
- ----- Method: Form>>displayOn:at:clippingBox:rule:fillColor: (in category 'displaying') -----
- displayOn: aDisplayMedium at: aDisplayPoint clippingBox: clipRectangle rule: rule fillColor: aForm
- 
- 	aDisplayMedium copyBits: self boundingBox
- 		from: self
- 		at: aDisplayPoint + self offset
- 		clippingBox: clipRectangle
- 		rule: rule
- 		fillColor: aForm
- 		map: (self colormapIfNeededFor: aDisplayMedium).
- !

Item was removed:
- ----- Method: Form>>displayOn:transformation:clippingBox:align:with:rule:fillColor: (in category 'displaying') -----
- displayOn: aDisplayMedium transformation: displayTransformation clippingBox: clipRectangle align: alignmentPoint with: relativePoint rule: ruleInteger fillColor: aForm 
- 	"Graphically, it means nothing to scale a Form by floating point values.  
- 	Because scales and other display parameters are kept in floating point to 
- 	minimize round off errors, we are forced in this routine to round off to the 
- 	nearest integer."
- 
- 	| absolutePoint scale magnifiedForm |
- 	absolutePoint := displayTransformation applyTo: relativePoint.
- 	absolutePoint := absolutePoint x asInteger @ absolutePoint y asInteger.
- 	displayTransformation noScale
- 		ifTrue: [magnifiedForm := self]
- 		ifFalse: 
- 			[scale := displayTransformation scale.
- 			scale := scale x @ scale y.
- 			(1 at 1 = scale)
- 					ifTrue: [scale := nil. magnifiedForm := self]
- 					ifFalse: [magnifiedForm := self magnify: self boundingBox by: scale]].
- 	magnifiedForm
- 		displayOn: aDisplayMedium
- 		at: absolutePoint - alignmentPoint
- 		clippingBox: clipRectangle
- 		rule: ruleInteger
- 		fillColor: aForm!

Item was removed:
- ----- Method: Form>>displayOnPort:at: (in category 'displaying') -----
- displayOnPort: port at: location
- 	port copyForm: self to: location rule: Form over!

Item was removed:
- ----- Method: Form>>displayResourceFormOn: (in category 'displaying') -----
- displayResourceFormOn: aForm
- 	"a special display method for blowing up resource thumbnails"
- 	| engine tx cmap blitter |
- 	self extent = aForm extent ifTrue:[^self displayOn: aForm].
- 	engine := Smalltalk at: #B3DRenderEngine ifPresent:
- 		[:engineClass | engineClass defaultForPlatformOn: aForm].
- 	engine ifNil:[
- 		"We've got no bilinear interpolation. Use WarpBlt instead"
- 		(WarpBlt toForm: aForm)
- 			sourceForm: self destRect: aForm boundingBox;
- 			combinationRule: 3;
- 			cellSize: 2;
- 			warpBits.
- 		^self
- 	].
- 	tx := self asTexture.
- 	(blitter := BitBlt toForm: tx)
- 		sourceForm: self; destRect: aForm boundingBox;
- 		sourceOrigin: 0 at 0;
- 		combinationRule: Form paint.
- 	"map transparency to current World background color"
- 	(Project current world color respondsTo: #pixelWordForDepth:) ifTrue: [
- 		cmap := Bitmap new: (self depth <= 8 ifTrue: [1 << self depth] ifFalse: [4096]).
- 		cmap at: 1 put: (tx pixelWordFor: Project current world color).
- 		blitter colorMap: cmap.
- 	].
- 	blitter copyBits.
- 	engine viewport: aForm boundingBox.
- 	engine material: ((Smalltalk at: #B3DMaterial) new emission: Color white).
- 	engine texture: tx.
- 	engine render: ((Smalltalk at: #B3DIndexedQuadMesh) new plainTextureRect).
- 	engine finish.
- 	"the above, using bilinear interpolation doesn't leave transparent pixel values intact"
- 	(WarpBlt toForm: aForm)
- 		sourceForm: self destRect: aForm boundingBox;
- 		combinationRule: Form and;
- 		colorMap: (Color maskingMap: self depth);
- 		warpBits.!

Item was removed:
- ----- Method: Form>>displayScaledOn: (in category 'displaying') -----
- displayScaledOn: aForm
- 	"Display the receiver on aForm, scaling if necessary.
- 		Form fromUser displayScaledOn: Display.
- 	"
- 	self extent = aForm extent ifTrue:[^self displayOn: aForm].
- 	(WarpBlt toForm: aForm)
- 		sourceForm: self destRect: aForm boundingBox;
- 		combinationRule: Form paint;
- 		cellSize: 2;
- 		warpBits.!

Item was removed:
- ----- Method: Form>>dominantColor (in category 'analyzing') -----
- dominantColor
- 	| tally max maxi |
- 	self depth > 16 ifTrue:
- 		[^(self asFormOfDepth: 16) dominantColor].
- 	tally := self tallyPixelValues.
- 	max := maxi := 0.
- 	tally withIndexDo: [:n :i | n > max ifTrue: [max := n. maxi := i]].
- 	^ Color colorFromPixelValue: maxi - 1 depth: self depth!

Item was removed:
- ----- Method: Form>>drawLine:from:to:clippingBox:rule:fillColor: (in category 'displaying') -----
- drawLine: sourceForm from: beginPoint to: endPoint clippingBox: clipRect rule: anInteger fillColor: aForm 
- 	"Refer to the comment in 
- 	DisplayMedium|drawLine:from:to:clippingBox:rule:mask:." 
- 	
- 	| dotSetter |
- 	"set up an instance of BitBlt for display"
- 	dotSetter := BitBlt
- 		destForm: self
- 		sourceForm: sourceForm
- 		fillColor: aForm
- 		combinationRule: anInteger
- 		destOrigin: beginPoint
- 		sourceOrigin: 0 @ 0
- 		extent: sourceForm extent
- 		clipRect: clipRect.
- 	dotSetter drawFrom: beginPoint to: endPoint!

Item was removed:
- ----- Method: Form>>dyed: (in category 'converting') -----
- dyed: aColor
- 	"Dye this form with the given color. For now, the alpha channel should be sufficient to preserve the meaning of the form."
- 	
- 	^ self collectColors: [:ea | aColor alpha: ea alpha]!

Item was removed:
- ----- Method: Form>>edgeDetect (in category 'processing') -----
- edgeDetect
- 
- 	^ self processUsingKernel: (Matrix rows: 3 columns: 3 contents: #(
- 		-1 -1 -1
- 		-1  8 -1
- 		-1 -1 -1
- 	))!

Item was removed:
- ----- Method: Form>>edit (in category 'editing') -----
- edit
- 	"Open a form editor on this form. "
-  
- 	Project current formEdit: self!

Item was removed:
- ----- Method: Form>>emboss (in category 'processing') -----
- emboss
- 
- 	^ self processUsingKernel: (Matrix rows: 3 columns: 3 contents: #(
- 		-2 -1  0
- 		-1  1  1
- 		 0  1  2
- 	))!

Item was removed:
- ----- Method: Form>>eraseShape: (in category 'filling') -----
- eraseShape: bwForm
- 	"use bwForm as a mask to clear all pixels where bwForm has 1's"
- 	((BitBlt destForm: self sourceForm: bwForm 
- 		fillColor: nil
- 		combinationRule: Form erase1bitShape	"Cut a hole in the picture with my mask"
- 		destOrigin: bwForm offset 
- 		sourceOrigin: 0 at 0
- 		extent: self extent clipRect: self boundingBox)
- 		colorMap: (Bitmap with: 0 with: 16rFFFFFFFF))
- 		copyBits.
- !

Item was removed:
- ----- Method: Form>>extent (in category 'accessing') -----
- extent
- 	^ width @ height!

Item was removed:
- ----- Method: Form>>fadeImage:at:indexAndMaskDo: (in category 'transitions') -----
- fadeImage: otherImage at: topLeft
- 	indexAndMaskDo: indexAndMaskBlock
- 	
- 	"This fade uses halftones as a blending hack.
- 	Zeros in the halftone produce the original image (self), and 
- 	ones in the halftone produce the 'otherImage'.
- 	IndexAndMaskBlock gets evaluated prior to each cycle,
- 	and the resulting boolean determines whether to continue cycling."
- 	| index imageRect maskForm resultForm pix returnPix|
- 	imageRect := otherImage boundingBox.
- 	resultForm := self copy: (topLeft extent: imageRect extent).
- 	maskForm := Form extent: 32 at 32.
- 	index := 0.
- 
- 	[indexAndMaskBlock value: (index := index+1) value: maskForm]
- 	whileTrue:
- 		[maskForm reverse.
- 		resultForm copyBits: imageRect from: resultForm at: 0 at 0
- 			clippingBox: imageRect rule: Form over fillColor: maskForm.
- 		maskForm reverse.
- 		resultForm copyBits: imageRect from: otherImage at: 0 at 0
- 			clippingBox: imageRect rule: Form under fillColor: maskForm.
- 		self copyBits: imageRect from: resultForm at: topLeft
- 				clippingBox: self boundingBox rule: Form over fillColor: nil.
- 		Display forceDisplayUpdate]!

Item was removed:
- ----- Method: Form>>fadeImageCoarse:at: (in category 'transitions') -----
- fadeImageCoarse: otherImage at: topLeft
- 	"Display fadeImageCoarse: (Form fromDisplay: (40 at 40 extent: 300 at 300)) reverse at: 40 at 40"
- 	| d pix|
- 	d := self depth.
- 	^ self fadeImage: otherImage at: topLeft indexAndMaskDo:
- 		[:i :mask | | j |
- 		i=1 ifTrue: [pix := (1 bitShift: d) - 1.
- 					1 to: 8//d-1 do: [:q | pix := pix bitOr: (pix bitShift: d*4)]]			.
- 		i <= 16 ifTrue:[
- 		j := i-1//4+1.
- 		(0 to: 28 by: 4) do: [:k |
- 			mask bits at: j+k
- 				put: (pix bitOr: (mask bits at: j+k))].
- 		true]
- 		ifFalse: [false]]!

Item was removed:
- ----- Method: Form>>fadeImageFine:at: (in category 'transitions') -----
- fadeImageFine: otherImage at: topLeft
- 	"Display fadeImageFine: (Form fromDisplay: (40 at 40 extent: 300 at 300)) reverse at: 40 at 40"
- 	| d pix|
- 	d := self depth.
- 	^ self fadeImage: otherImage at: topLeft indexAndMaskDo:
- 		[:i :mask | | j ii  |
- 		i=1 ifTrue: [pix := (1 bitShift: d) - 1.
- 					1 to: 8//d-1 do:
- 						[:q | pix := pix bitOr: (pix bitShift: d*4)]].
- 		i <= 16 ifTrue:
- 		[ii := #(0 10 2 8 7 13 5 15 1 11 3 9 6 12 4 14) at: i.
- 		j := ii//4+1.
- 		(0 to: 28 by: 4) do:
- 			[:k | mask bits at: j+k put:
- 				((mask bits at: j+k) bitOr: (pix))].
- 		true]
- 		ifFalse: [false]]!

Item was removed:
- ----- Method: Form>>fadeImageHor:at: (in category 'transitions') -----
- fadeImageHor: otherImage at: topLeft
- 	"Display fadeImageHor: (Form fromDisplay: (10 at 10 extent: 300 at 300)) reverse at: 10 at 10"
- 	^ self fadeImage: otherImage at: topLeft indexAndMaskDo:
- 		[:i :mask |
- 		mask fill: (0@(mask height//2-i) extent: mask width@(i*2)) fillColor: Color black.
- 		(i*2) <= mask width]!

Item was removed:
- ----- Method: Form>>fadeImageHorFine:at: (in category 'transitions') -----
- fadeImageHorFine: otherImage at: topLeft
- 	"Display fadeImageHorFine: (Form fromDisplay: (10 at 10 extent: 300 at 300)) reverse at: 10 at 10"
- 	^ self fadeImage: otherImage at: topLeft indexAndMaskDo:
- 		[:i :mask |
- 		mask fill: (0@(i-1) extent: mask width at 1) fillColor: Color black.
- 		mask fill: (0@(i-1+16) extent: mask width at 1) fillColor: Color black.
- 		(i*2) <= mask width]!

Item was removed:
- ----- Method: Form>>fadeImageSquares:at: (in category 'transitions') -----
- fadeImageSquares: otherImage at: topLeft 
- 	"Display fadeImageSquares: (Form fromDisplay: (40 at 40 extent: 300 at 300)) reverse at: 40 at 40"
- 	^ self fadeImage: otherImage at: topLeft indexAndMaskDo:
- 		[:i :mask |
- 		mask fill: ((16-i) asPoint extent: (i*2) asPoint) fillColor: Color black.
- 		i <= 16]!

Item was removed:
- ----- Method: Form>>fadeImageVert:at: (in category 'transitions') -----
- fadeImageVert: otherImage at: topLeft
- 	"Display fadeImageVert: (Form fromDisplay: (10 at 10 extent: 300 at 300)) reverse at: 10 at 10"
- 	| d |
- 	d := self depth.
- 	^ self fadeImage: otherImage at: topLeft indexAndMaskDo:
- 		[:i :mask |
- 		mask fill: ((mask width//2//d-i*d)@0 extent: i*2*d at mask height) fillColor: Color black.
- 		i <= (mask width//d)]!

Item was removed:
- ----- Method: Form>>fill:rule:fillColor: (in category 'filling') -----
- fill: aRectangle rule: anInteger fillColor: aForm 
- 	"Replace a rectangular area of the receiver with the pattern described by aForm 
- 	according to the rule anInteger."
- 	(BitBlt toForm: self)
- 		copy: aRectangle
- 		from: 0 at 0 in: nil
- 		fillColor: aForm rule: anInteger!

Item was removed:
- ----- Method: Form>>fillAlpha: (in category 'other') -----
- fillAlpha: alphaValue
- 	"Fill a 32bit form with a constant alpha value"
- 	| bb |
- 	self depth = 32 ifFalse:[^self error: 'Only valid for 32 bit forms'].
- 	bb := BitBlt toForm: self.
- 	bb combinationRule: 7. "bitOr:with:".
- 	bb fillColor: (Bitmap with: alphaValue << 24).
- 	bb copyBits.
- !

Item was removed:
- ----- Method: Form>>fillFromXColorBlock: (in category 'filling') -----
- fillFromXColorBlock: colorBlock
- 	"Horizontal Gradient Fill.
- 	Supply relative x in [0.0 ... 1.0] to colorBlock,
- 	and paint each pixel with the color that comes back"
- 	| xRel |
- 	0 to: width-1 do:
- 		[:x |  xRel := x asFloat / (width-1) asFloat.
- 		self fill: (x at 0 extent: 1 at height) 
- 			fillColor: (colorBlock value: xRel)]
- "
- ((Form extent: 100 at 100 depth: Display depth)
- 	fillFromXColorBlock: [:x | Color r: x g: 0.0 b: 0.5]) display
- "!

Item was removed:
- ----- Method: Form>>fillFromXYColorBlock: (in category 'filling') -----
- fillFromXYColorBlock: colorBlock
- 	"General Gradient Fill.
- 	Supply relative x and y in [0.0 ... 1.0] to colorBlock,
- 	and paint each pixel with the color that comes back"
- 	| poker yRel xRel |
- 	poker := BitBlt bitPokerToForm: self.
- 	0 to: height-1 do:
- 		[:y | yRel := y asFloat / (height-1) asFloat.
- 		0 to: width-1 do:
- 			[:x |  xRel := x asFloat / (width-1) asFloat.
- 			poker pixelAt: x at y
- 				put: ((colorBlock value: xRel value: yRel) pixelWordForDepth: self depth)]]
- "
-  | d |
- ((Form extent: 100 at 20 depth: Display depth)
- 	fillFromXYColorBlock:
- 	[:x :y | d := 1.0 - (x - 0.5) abs - (y - 0.5) abs.
- 	Color r: d g: 0 b: 1.0-d]) display
- "!

Item was removed:
- ----- Method: Form>>fillFromYColorBlock: (in category 'filling') -----
- fillFromYColorBlock: colorBlock
- 	"Vertical Gradient Fill.
- 	Supply relative y in [0.0 ... 1.0] to colorBlock,
- 	and paint each pixel with the color that comes back"
- 	| yRel |
- 	0 to: height-1 do:
- 		[:y |  yRel := y asFloat / (height-1) asFloat.
- 		self fill: (0 at y extent: width at 1) 
- 			fillColor: (colorBlock value: yRel)]
- "
- ((Form extent: 100 at 100 depth: Display depth)
- 	fillFromYColorBlock: [:y | Color r: y g: 0.0 b: 0.5]) display
- "!

Item was removed:
- ----- Method: Form>>findShapeAroundSeedBlock: (in category 'filling') -----
- findShapeAroundSeedBlock: seedBlock
- 	"Build a shape that is black in any region marked by seedBlock. 
- 	SeedBlock will be supplied a form, in which to blacken various
- 	pixels as 'seeds'.  Then the seeds are smeared until 
- 	there is no change in the smear when it fills the region, ie,
- 	when smearing hits a black border and thus goes no further."
- 	| smearForm previousSmear all count smearPort |
- 	self depth > 1 ifTrue: [self halt]. "Only meaningful for B/W forms."
- 	all := self boundingBox.
- 	smearForm := Form extent: self extent.
- 	smearPort := BitBlt toForm: smearForm.
- 	seedBlock value: smearForm.		"Blacken seeds to be smeared"
- 	smearPort copyForm: self to: 0 @ 0 rule: Form erase.  "Clear any in black"
- 	previousSmear := smearForm deepCopy.
- 	count := 1.
- 	[count = 10 and:   "check for no change every 10 smears"
- 		[count := 1.
- 		previousSmear copy: all from: 0 @ 0 in: smearForm rule: Form reverse.
- 		previousSmear isAllWhite]]
- 		whileFalse: 
- 			[smearPort copyForm: smearForm to: 1 @ 0 rule: Form under.
- 			smearPort copyForm: smearForm to: -1 @ 0 rule: Form under.
- 			"After horiz smear, trim around the region border"
- 			smearPort copyForm: self to: 0 @ 0 rule: Form erase.
- 			smearPort copyForm: smearForm to: 0 @ 1 rule: Form under.
- 			smearPort copyForm: smearForm to: 0 @ -1 rule: Form under.
- 			"After vert smear, trim around the region border"
- 			smearPort copyForm: self to: 0 @ 0 rule: Form erase.
- 			count := count + 1.
- 			count = 9 ifTrue: "Save penultimate smear for comparison"
- 				[previousSmear copy: all from: 0 @ 0 in: smearForm rule: Form over]].
- 	"Now paint the filled region in me with aHalftone"
- 	^ smearForm!

Item was removed:
- ----- Method: Form>>finish (in category 'initialize-release') -----
- finish
- 	"If there are any pending operations on the receiver complete them. Do not return before all modifications have taken effect."!

Item was removed:
- ----- Method: Form>>fixAlpha (in category 'other') -----
- fixAlpha
- 	"Fix the alpha channel if the receiver is 32bit"
- 	| bb |
- 	self depth = 32 ifFalse:[^self].
- 	bb := BitBlt toForm: self.
- 	bb combinationRule: 40 "fixAlpha:with:".
- 	bb copyBits.!

Item was removed:
- ----- Method: Form>>flipBy:centerAt: (in category 'scaling, rotation') -----
- flipBy: direction centerAt: aPoint
- 	"Return a copy of the receiver flipped either #vertical or #horizontal."
- 	| newForm quad |
- 	newForm := self class extent: self extent depth: depth.
- 	quad := self boundingBox innerCorners.
- 	quad := (direction = #vertical ifTrue: [#(2 1 4 3)] ifFalse: [#(4 3 2 1)])
- 		collect: [:i | quad at: i].
- 	(WarpBlt toForm: newForm)
- 		sourceForm: self;
- 		colorMap: (self colormapIfNeededFor: newForm);
- 		combinationRule: 3;
- 		copyQuad: quad toRect: newForm boundingBox.
- 	newForm offset: (self offset flipBy: direction centerAt: aPoint).
- 	^ newForm
- "
- [Sensor anyButtonPressed] whileFalse:
- 	[((Form fromDisplay: (Sensor cursorPoint extent: 130 at 66))
- 			flipBy: #vertical centerAt: 0 at 0) display]
- "
- "Consistency test...
-  | f f2 p | [Sensor anyButtonPressed] whileFalse:
- 	[f := Form fromDisplay: ((p := Sensor cursorPoint) extent: 31 at 41).
- 	Display fillBlack: (p extent: 31 at 41).
- 	f2 := f flipBy: #vertical centerAt: 0 at 0.
- 	(f2 flipBy: #vertical centerAt: 0 at 0) displayAt: p]
- "
- !

Item was removed:
- ----- Method: Form>>flipVertically (in category 'converting') -----
- flipVertically
- 	"Flip the image along the y axis"
- 	| rowLen row topIndex botIndex |
- 	self unhibernate.
- 	rowLen := bits size // height.
- 	row := Bitmap new: rowLen.
- 	topIndex := 1.
- 	botIndex := bits size - rowLen + 1.
- 	1 to: height // 2 do: [:i |
- 		self assert:[topIndex+rowLen <= botIndex].
- 		row replaceFrom: 1 to: rowLen with: bits startingAt: topIndex.
- 		bits replaceFrom: topIndex to: topIndex+rowLen-1 with: bits startingAt: botIndex.
- 		bits replaceFrom: botIndex to: botIndex+rowLen-1 with: row startingAt: 1.
- 		topIndex := topIndex + rowLen.
- 		botIndex := botIndex - rowLen.
- 	].
- !

Item was removed:
- ----- Method: Form>>floodFill2:at: (in category 'filling') -----
- floodFill2: aColor at: interiorPoint
- 	"Fill the shape (4-connected) at interiorPoint.  The algorithm is based on Paul Heckbert's 'A Seed Fill Algorithm', Graphic Gems I, Academic Press, 1990.
- 	NOTE: This is a less optimized variant for flood filling which is precisely along the lines of Heckbert's algorithm. For almost all cases #floodFill:at: will be faster (see the comment there) but this method is left in both as reference and as a fallback if such a strange case is encountered in reality."
- 	| poker stack old new x y top x1 x2 dy left goRight |
- 	poker := BitBlt bitPokerToForm: self.
- 	stack := OrderedCollection new: 50.
- 	"read old pixel value"
- 	old := self pixelValueAt: interiorPoint.
- 	"compute new value"
- 	new := self pixelValueFor: aColor.
- 	old = new ifTrue:[^self]. "no point, is there?!!"
- 
- 	x := interiorPoint x.
- 	y := interiorPoint y.
- 	(y >= 0 and:[y < height]) ifTrue:[
- 		stack addLast: {y. x. x. 1}. "y, left, right, dy"
- 		stack addLast: {y+1. x. x. -1}].
- 	[stack isEmpty] whileFalse:[
- 		top := stack removeLast.
- 		y := top at: 1. x1 := top at: 2. x2 := top at: 3. dy := top at: 4.
- 		y := y + dy.
- 		"Segment of scanline (y-dy) for x1 <= x <= x2 was previously filled.
- 		Now explore adjacent pixels in scanline y."
- 		x := x1.
- 		[x >= 0 and:[(self pixelValueAt: x at y) = old]] whileTrue:[
- 			poker pixelAt: x at y put: new.
- 			x := x - 1].
- 		goRight := x < x1.
- 		left := x+1.
- 		(left < x1 and:[y-dy >= 0 and:[y-dy < height]]) 
- 			ifTrue:[stack addLast: {y. left. x1-1. 0-dy}].
- 		goRight ifTrue:[x := x1 + 1].
- 		[
- 			goRight ifTrue:[
- 				[x < width and:[(self pixelValueAt: x at y) = old]] whileTrue:[
- 					poker pixelAt: x at y put: new.
- 					x := x + 1].
- 				(y+dy >= 0 and:[y+dy < height]) 
- 					ifTrue:[stack addLast: {y. left. x-1. dy}].
- 				(x > (x2+1) and:[y-dy >= 0 and:[y-dy >= 0]]) 
- 					ifTrue:[stack addLast: {y. x2+1. x-1. 0-dy}]].
- 			[(x := x + 1) <= x2 and:[(self pixelValueAt: x at y) ~= old]] whileTrue.
- 			left := x.
- 			goRight := true.
- 		x <= x2] whileTrue.
- 	].
- !

Item was removed:
- ----- Method: Form>>floodFill:at: (in category 'filling') -----
- floodFill: aColor at: interiorPoint
- 	Preferences areaFillsAreVeryTolerant ifTrue:
- 		[^ self floodFill: aColor at: interiorPoint tolerance: 0.2].
- 	Preferences areaFillsAreTolerant ifTrue:
- 		[^ self floodFill: aColor at: interiorPoint tolerance: 0.1].
- 	^ self floodFill: aColor at: interiorPoint tolerance: 0
- !

Item was removed:
- ----- Method: Form>>floodFill:at:tolerance: (in category 'filling') -----
- floodFill: aColor at: interiorPoint tolerance: tolerance
- 	"Fill the shape (4-connected) at interiorPoint.  The algorithm is based on Paul Heckbert's 'A Seed Fill Algorithm', Graphic Gems I, Academic Press, 1990.
- 	NOTE (ar): This variant has been heavily optimized to prevent the overhead of repeated calls to BitBlt. Usually this is a really big winner but the runtime now depends a bit on the complexity of the shape to be filled. For extremely complex shapes (say, a Hilbert curve) with very few pixels to fill it can be slower than #floodFill2:at: since it needs to repeatedly read the source bits. However, in all practical cases I found this variant to be 15-20 times faster than anything else.
- 	Further note (di):  I have added a feature that allows this routine to fill areas of approximately constant color (such as  photos, scans, and jpegs).  It does this by computing a color map for the peeker that maps all colors close to 'old' into colors identical to old.  This mild colorblindness achieves the desired effect with no further change or degradation of the algorithm.  tolerance should be 0 (exact match), or a value corresponding to those returned by Color>>diff:, with 0.1 being a reasonable starting choice."
- 
- 	| peeker poker stack old new x y top x1 x2 dy left goRight span spanBits w box debug |
- 	debug := false. "set it to true to see the filling process"
- 	box := interiorPoint extent: 1 at 1.
- 	span := Form extent: width at 1 depth: 32.
- 	spanBits := span bits.
- 
- 	peeker := BitBlt toForm: span.
- 	peeker 
- 		sourceForm: self; 
- 		combinationRule: 3; 
- 		width: width; 
- 		height: 1.
- 
- 	"read old pixel value"
- 	peeker sourceOrigin: interiorPoint; destOrigin: interiorPoint x @ 0; width: 1; copyBits.
- 	old := spanBits at: interiorPoint x + 1.
- 
- 	"compute new value (take care since the algorithm will fail if old = new)"
- 	new := self privateFloodFillValue: aColor.
- 	old = new ifTrue: [^ box].
- 	tolerance > 0 ifTrue:
- 		["Set up color map for approximate fills"
- 		peeker colorMap: (self floodFillMapFrom: self to: span mappingColorsWithin: tolerance to: old)].
- 
- 	poker := BitBlt toForm: self.
- 	poker 
- 		fillColor: aColor;
- 		combinationRule: 3;
- 		width: width;
- 		height: 1.
- 
- 	stack := OrderedCollection new: 50.
- 	x := interiorPoint x.
- 	y := interiorPoint y.
- 	(y >= 0 and:[y < height]) ifTrue:[
- 		stack addLast: {y. x. x. 1}. "y, left, right, dy"
- 		stack addLast: {y+1. x. x. -1}].
- 
- 	[stack isEmpty] whileFalse:[
- 		debug ifTrue:[self displayOn: Display].
- 		top := stack removeLast.
- 		y := top at: 1. x1 := top at: 2. x2 := top at: 3. dy := top at: 4.
- 		y := y + dy.
- 		debug ifTrue:[
- 			Display 
- 				drawLine: (Form extent: 1 at 1 depth: 8) fillWhite
- 				from: (x1-1)@y to: (x2+1)@y 
- 				clippingBox: Display boundingBox
- 				rule: Form over fillColor: nil].
- 		"Segment of scanline (y-dy) for x1 <= x <= x2 was previously filled.
- 		Now explore adjacent pixels in scanline y."
- 		peeker sourceOrigin: 0 at y; destOrigin: 0 at 0; width: width; copyBits.
- 			"Note: above is necessary since we don't know where we'll end up filling"
- 		x := x1.
- 		w := 0.
- 		[x >= 0 and:[(spanBits at: x+1) = old]] whileTrue:[
- 			w := w + 1.
- 			x := x - 1].
- 		w > 0 ifTrue:[
- 			"overwrite pixels"
- 			poker destOrigin: x+1 at y; width: w; copyBits.
- 			box := box quickMerge: ((x+1 at y) extent: w at 1)].
- 		goRight := x < x1.
- 		left := x+1.
- 		(left < x1 and:[y-dy >= 0 and:[y-dy < height]]) 
- 			ifTrue:[stack addLast: {y. left. x1-1. 0-dy}].
- 		goRight ifTrue:[x := x1 + 1].
- 		[
- 			goRight ifTrue:[
- 				w := 0.
- 				[x < width and:[(spanBits at: x+1) = old]] whileTrue:[
- 					w := w + 1.
- 					x := x + 1].
- 				w > 0 ifTrue:[
- 					"overwrite pixels"
- 					poker destOrigin: (x-w)@y; width: w; copyBits.
- 					box := box quickMerge: ((x-w at y) extent: w at 1)].
- 				(y+dy >= 0 and:[y+dy < height]) 
- 					ifTrue:[stack addLast: {y. left. x-1. dy}].
- 				(x > (x2+1) and:[y-dy >= 0 and:[y-dy >= 0]]) 
- 					ifTrue:[stack addLast: {y. x2+1. x-1. 0-dy}]].
- 			[(x := x + 1) <= x2 and:[(spanBits at: x+1) ~= old]] whileTrue.
- 			left := x.
- 			goRight := true.
- 		x <= x2] whileTrue.
- 	].
- 	^box!

Item was removed:
- ----- Method: Form>>floodFillMapFrom:to:mappingColorsWithin:to: (in category 'filling') -----
- floodFillMapFrom: sourceForm to: scanlineForm mappingColorsWithin: dist to: centerPixVal
- 	"This is a helper routine for floodFill.  It's written for clarity (scanning the entire
- 	map using colors) rather than speed (which would require hacking rgb components
- 	in the nieghborhood of centerPixVal.  Note that some day a better proximity metric
- 	would be (h s v) where tolerance could be reduced in hue."
- 
- 	| colorMap centerColor |
- 	scanlineForm depth = 32 ifFalse: [self error: 'depth 32 assumed'].
- 	"First get a modifiable identity map"
- 	colorMap := 	(Color cachedColormapFrom: sourceForm depth to: scanlineForm depth) copy.
- 	centerColor := Color colorFromPixelValue: (centerPixVal bitOr: 16rFFe6) depth: scanlineForm depth.
- 	"Now replace all entries that are close to the centerColor"
- 	1 to: colorMap size do:
- 		[:i | ((Color colorFromPixelValue: ((colorMap at: i) bitOr: 16rFFe6) depth: scanlineForm depth)
- 				diff: centerColor) <= dist ifTrue: [colorMap at: i put: centerPixVal]].
- 	^ colorMap!

Item was removed:
- ----- Method: Form>>flush (in category 'initialize-release') -----
- flush
- 	"If there are any pending operations on the receiver start doing them. In time, they will show up on the receiver but not necessarily immediately after this method returns."!

Item was removed:
- ----- Method: Form>>form (in category 'accessing') -----
- form
- 	"Answer the receiver's form.  For vanilla Forms, this degenerates to self.  Makes several methods that operate on both Forms and MaskedForms much more straightforward.   6/1/96 sw"
- 
- 	^ self!

Item was removed:
- ----- Method: Form>>formForColorCount: (in category 'other') -----
- formForColorCount: colorCount
- 	"Return a ColorForm of sufficient depth to represent the given number of colors. The maximum number of colors is 256."
- 
- 	colorCount > 256 ifTrue: [^ self error: 'too many colors'].
- 
- 	colorCount > 16 ifTrue: [^ ColorForm extent: self extent depth: 8].
- 	colorCount > 4 ifTrue: [^ ColorForm extent: self extent depth: 4].
- 	colorCount > 2 ifTrue: [^ ColorForm extent: self extent depth: 2].
- 	^ ColorForm extent: self extent depth: 1
- !

Item was removed:
- ----- Method: Form>>fromDisplay: (in category 'initialize-release') -----
- fromDisplay: aRectangle 
- 	"Create a virtual bit map from a user specified rectangular area on the 
- 	display screen. Reallocates bitmap only if aRectangle ~= the receiver's 
- 	extent."
- 
- 	(width = aRectangle width and: [height = aRectangle height])
- 		ifFalse: [self setExtent: aRectangle extent depth: depth].
- 	self
- 		copyBits: (aRectangle origin extent: self extent)
- 		from: Display
- 		at: 0 @ 0
- 		clippingBox: self boundingBox
- 		rule: Form over
- 		fillColor: nil!

Item was removed:
- ----- Method: Form>>getCanvas (in category 'accessing') -----
- getCanvas
- 	"Return a Canvas that can be used to draw onto the receiver"
- 	^self defaultCanvasClass on: self!

Item was removed:
- ----- Method: Form>>hackBits: (in category 'private') -----
- hackBits: bitThing
- 	"This method provides an initialization so that BitBlt may be used, eg, to 
- 	copy ByteArrays and other non-pointer objects efficiently.
- 	The resulting form looks 4 wide, 8 deep, and bitThing-size-in-words high."
- 	width := 4.
- 	depth := 8.
- 	bitThing class isBits ifFalse: [self error: 'bitThing must be a non-pointer object'].
- 	height := bitThing basicSize * bitThing bytesPerBasicElement // width.
- 	bits := bitThing!

Item was removed:
- ----- Method: Form>>hasBeenModified (in category 'accessing') -----
- hasBeenModified
- 	"Return true if something *might* have been drawn into the receiver"
- 	^(bits == nil or:[bits class == ByteArray]) not
- 	"Read the above as: If the receiver has forgotten its contents (bits == nil) 
- 	or is still hibernated it can't be modified."!

Item was removed:
- ----- Method: Form>>hasBeenModified: (in category 'accessing') -----
- hasBeenModified: aBool
- 	"Change the receiver to reflect the modification state"
- 	aBool ifTrue:[^self unhibernate].
- 	self shouldPreserveContents
- 		ifTrue:[self hibernate]
- 		ifFalse:[bits := nil]!

Item was removed:
- ----- Method: Form>>hasNonStandardPalette (in category 'testing') -----
- hasNonStandardPalette
- 	"Return true if the receiver has a non-standard palette.
- 	Non-standard means that RGBA components may be located
- 	at positions differing from the standard Squeak RGBA layout
- 	at the receiver's depth."
- 	^false!

Item was removed:
- ----- Method: Form>>height (in category 'display box access') -----
- height
- 	^ height!

Item was removed:
- ----- Method: Form>>hibernate (in category 'fileIn/Out') -----
- hibernate
- 	"Replace my bitmap with a compactly encoded representation (a ByteArray).  It is vital that BitBlt and any other access to the bitmap (such as writing to a file) not be used when in this state.  Since BitBlt will fail if the bitmap size is wrong (not = bitsSize), we do not allow replacement by a byteArray of the same (or larger) size."
- 
- 	"NOTE: This method copies code from Bitmap compressToByteArray so that it can
- 	nil out the old bits during the copy, thus avoiding 2x need for extra storage."
- 	| compactBits lastByte |
- 	(bits isMemberOf: Bitmap) ifFalse: [^ self  "already hibernated or weird state"].
- 	compactBits := ByteArray new: (bits size*4) + 7 + (bits size//1984*3).
- 	lastByte := bits compress: bits toByteArray: compactBits.
- 	lastByte < (bits size*4) ifTrue:
- 		[bits := nil.  "Let GC reclaim the old bits before the copy if necessary"
- 		bits := compactBits copyFrom: 1 to: lastByte]!

Item was removed:
- ----- Method: Form>>initFromArray: (in category 'private') -----
- initFromArray: array
- 	"Fill the bitmap from array.  If the array is shorter,
- 	then cycle around in its contents until the bitmap is filled."
- 	| ax aSize array32 i j word16 |
- 	ax := 0.
- 	aSize := array size.
- 	aSize > bits size ifTrue:
- 		["backward compatibility with old 16-bit bitmaps and their forms"
- 		array32 := Array new: height * (width + 31 // 32).
- 		i := j := 0.
- 		1 to: height do:
- 			[:y | 1 to: width+15//16 do:
- 				[:x16 | word16 := array at: (i := i + 1).
- 				x16 odd ifTrue: [array32 at: (j := j+1) put: (word16 bitShift: 16)]
- 						ifFalse: [array32 at: j put: ((array32 at: j) bitOr: word16)]]].
- 		^ self initFromArray: array32].
- 	1 to: bits size do:
- 		[:index |
- 		(ax := ax + 1) > aSize ifTrue: [ax := 1].
- 		bits at: index put: (array at: ax)]!

Item was removed:
- ----- Method: Form>>innerPixelRectFor:orNot: (in category 'analyzing') -----
- innerPixelRectFor: pv orNot: not
- 	"Return a rectangle describing the smallest part of me that includes 
- 	all pixels of value pv.
- 	Note:  If orNot is true, then produce a copy that includes all pixels
- 	that are DIFFERENT from the supplied (background) value"
- 
- 	| xTally yTally |
- 	xTally := self xTallyPixelValue: pv orNot: not.
- 	yTally := self yTallyPixelValue: pv orNot: not.
- 	^ ((xTally findFirst: [:t | t>0]) - 1) @ ((yTally findFirst: [:t | t>0]) - 1)
- 		corner:
- 			(xTally findLast: [:t | t>0])@(yTally findLast: [:t | t>0])!

Item was removed:
- ----- Method: Form>>isAllWhite (in category 'testing') -----
- isAllWhite
- 	"Answer whether all bits in the receiver are white"
- 	| word |
- 	self unhibernate.
- 	word := Color white pixelWordForDepth: self depth.
- 	1 to: bits size do: [:i | (bits at: i) = word ifFalse: [^ false]].
- 	^ true!

Item was removed:
- ----- Method: Form>>isBigEndian (in category 'testing') -----
- isBigEndian
- 	"Return true if the receiver contains big endian pixels, meaning the left-most pixel is stored in the most significant bits of a word."
- 	^depth > 0!

Item was removed:
- ----- Method: Form>>isDisplayScreen (in category 'testing') -----
- isDisplayScreen
- 	^false!

Item was removed:
- ----- Method: Form>>isForm (in category 'testing') -----
- isForm
- 	^true!

Item was removed:
- ----- Method: Form>>isGrayScale (in category 'testing') -----
- isGrayScale
- 	^ false!

Item was removed:
- ----- Method: Form>>isLittleEndian (in category 'testing') -----
- isLittleEndian
- 	"Return true if the receiver contains little endian pixels, meaning the left-most pixel is stored in the least significant bits of a word."
- 	^depth < 0!

Item was removed:
- ----- Method: Form>>isStatic (in category 'testing') -----
- isStatic
- 
- 	^false!

Item was removed:
- ----- Method: Form>>isTranslucent (in category 'testing') -----
- isTranslucent
- 	"Answer whether this form may be translucent"
- 	^self depth = 32!

Item was removed:
- ----- Method: Form>>isTransparentAt: (in category 'pixel access') -----
- isTransparentAt: aPoint 
- 	"Return true if the receiver is transparent at the given point."
- 
- 	self depth = 1 ifTrue: [^ false].  "no transparency at depth 1"
- 	^ (self pixelValueAt: aPoint) = (self pixelValueFor: Color transparent)
- !

Item was removed:
- ----- Method: Form>>isVirtualScreen (in category 'testing') -----
- isVirtualScreen
- 	"Am I a virtual display screen?"
- 	^false!

Item was removed:
- ----- Method: Form>>lighter (in category 'converting') -----
- lighter
- 	"Answer a lighter variant of this form"
- 	^self collectColors:[:color| color lighter lighter].!

Item was removed:
- ----- Method: Form>>magnify:by: (in category 'scaling, rotation') -----
- magnify: aRectangle by: scale 
- 	"Answer a Form created as a scaling of the receiver.
- 	Scale may be a Float, and may be greater or less than 1.0."
- 	^ self magnify: aRectangle by: scale smoothing: 1
- 
- "Dynamic test...
- [Sensor anyButtonPressed] whileFalse:
- 	[(Display magnify: (Sensor cursorPoint extent: 31 at 41) by: 5 at 3) display]
- "
- "Scaling test...
- | f cp | f := Form fromDisplay: (Rectangle originFromUser: 100 at 100).
- Display restoreAfter: [Sensor waitNoButton.
- [Sensor anyButtonPressed] whileFalse:
- 	[cp := Sensor cursorPoint.
- 	(f magnify: f boundingBox by: (cp x asFloat at cp y asFloat)/f extent) display]]
- "
- "Consistency test...
-  | f f2 p | [Sensor anyButtonPressed] whileFalse:
- 	[f := Form fromDisplay: ((p := Sensor cursorPoint) extent: 31 at 41).
- 	Display fillBlack: (p extent: 31 at 41).
- 	f2 := f magnify: f boundingBox by: 5 at 3.
- 	(f2 shrink: f2 boundingBox by: 5 at 3) displayAt: p]
- "
- !

Item was removed:
- ----- Method: Form>>magnify:by:smoothing: (in category 'scaling, rotation') -----
- magnify: aRectangle by: scale smoothing: cellSize
-         "Answer a Form created as a scaling of the receiver.
-         Scale may be a Float or even a Point, and may be greater or less than 1.0."
-         | newForm |
-         newForm := self blankCopyOf: aRectangle scaledBy: scale.
-         (WarpBlt toForm: newForm)
-                 sourceForm: self;
-                 colorMap: (self colormapIfNeededFor: newForm);
-                 cellSize: cellSize;  "installs a new colormap if cellSize > 1"
-                 combinationRule: 3;
-                 copyQuad: aRectangle innerCorners toRect: newForm boundingBox.
-         ^ newForm
- 
- "Dynamic test...
- [Sensor anyButtonPressed] whileFalse:
-         [(Display magnify: (Sensor cursorPoint extent: 131 at 81) by: 0.5 smoothing: 2) display]
- "
- "Scaling test...
- | f cp | f := Form fromDisplay: (Rectangle originFromUser: 100 at 100).
- Display restoreAfter: [Sensor waitNoButton.
- [Sensor anyButtonPressed] whileFalse:
-         [cp := Sensor cursorPoint.
-         (f magnify: f boundingBox by: (cp x asFloat at cp y asFloat)/f extent smoothing: 2) display]]
- "!

Item was removed:
- ----- Method: Form>>magnifyBy: (in category 'scaling, rotation') -----
- magnifyBy: scale 
- 	"Answer a Form created as a scaling of the receiver.
- 	Scale may be a Float or even a Point, and may be greater or less than 1.0."
- 	| effectiveScale |
- 	effectiveScale := scale isPoint ifTrue: [scale r] ifFalse: [scale].
- 	^ self magnify: self boundingBox by: scale
- 			smoothing: (effectiveScale < 1 ifTrue: [2] ifFalse: [1])!

Item was removed:
- ----- Method: Form>>makeBWForm: (in category 'color mapping') -----
- makeBWForm: foregroundColor
- 	"Map this form into a B/W form with 1's in the foreground regions."
- 	| bwForm map |
- 	bwForm := Form extent: self extent.
- 	map := self newColorMap.  "All non-foreground go to 0's"
- 	map at: (foregroundColor indexInMap: map) put: 1.
- 	bwForm copyBits: self boundingBox from: self at: 0 at 0 colorMap: map.
- 	^ bwForm!

Item was removed:
- ----- Method: Form>>mapColor:to: (in category 'color mapping') -----
- mapColor: oldColor to: newColor
- 	"Make all pixels of the given color in this Form to the given new color."
- 	"Warnings: This method modifies the receiver. It may lose some color accuracy on 32-bit Forms, since the transformation uses a color map with only 15-bit resolution."
- 
- 	| map |
- 	map := (Color cachedColormapFrom: self depth to: self depth) copy.
- 	map at: (oldColor indexInMap: map) put: (newColor pixelWordForDepth: self depth).
- 	(BitBlt toForm: self)
- 		sourceForm: self;
- 		sourceOrigin: 0 at 0;
- 		combinationRule: Form over;
- 		destX: 0 destY: 0 width: width height: height;
- 		colorMap: map;
- 		copyBits.
- !

Item was removed:
- ----- Method: Form>>mapColors:to: (in category 'color mapping') -----
- mapColors: oldColorBitsCollection to: newColorBits
- 	"Make all pixels of the given color in this Form to the given new color."
- 	"Warnings: This method modifies the receiver. It may lose some color accuracy on 32-bit Forms, since the transformation uses a color map with only 15-bit resolution."
- 
- 	| map |
- 	self depth < 16
- 		ifTrue: [map := (Color cachedColormapFrom: self depth to: self depth) copy]
- 		ifFalse: [
- 			"use maximum resolution color map"
- 			"source is 16-bit or 32-bit RGB; use colormap with 5 bits per color component"
- 			map := Color computeRGBColormapFor: self depth bitsPerColor: 5].
- 	oldColorBitsCollection do:[ :oldColor | map at: oldColor put: newColorBits].
- 
- 	(BitBlt toForm: self)
- 		sourceForm: self;
- 		sourceOrigin: 0 at 0;
- 		combinationRule: Form over;
- 		destX: 0 destY: 0 width: width height: height;
- 		colorMap: map;
- 		copyBits.
- !

Item was removed:
- ----- Method: Form>>maskingMap (in category 'color mapping') -----
- maskingMap
- 	"Return a color map that maps all colors except transparent to words of all ones. Used to create a mask for a Form whose transparent pixel value is zero."
- 	^Color maskingMap: self depth!

Item was removed:
- ----- Method: Form>>nativeDepth (in category 'accessing') -----
- nativeDepth
- 	"Return the 'native' depth of the receiver, e.g., including the endianess"
- 	^depth!

Item was removed:
- ----- Method: Form>>newColorMap (in category 'color mapping') -----
- newColorMap 
- 	"Return an uninitialized color map array appropriate to this Form's depth."
- 
- 	^ Bitmap new: (1 bitShift: (self depth min: 15))
- !

Item was removed:
- ----- Method: Form>>numComponents (in category 'postscript generation') -----
- numComponents
- 	^self depth <= 8 ifTrue:[1] ifFalse:[3].
- !

Item was removed:
- ----- Method: Form>>objectForDataStream: (in category 'fileIn/Out') -----
- objectForDataStream: refStream
- 	| prj repl |
- 	prj := refStream project.
- 	prj ifNil:[^super objectForDataStream: refStream].
- 	ResourceCollector current ifNil:[^super objectForDataStream: refStream].
- 	repl := ResourceCollector current objectForDataStream: refStream fromForm: self.
- 	^repl!

Item was removed:
- ----- Method: Form>>offset (in category 'accessing') -----
- offset
- 	^offset ifNil:[0 at 0]!

Item was removed:
- ----- Method: Form>>offset: (in category 'accessing') -----
- offset: aPoint
- 
- 	offset := aPoint!

Item was removed:
- ----- Method: Form>>orderedDither32To16 (in category 'converting') -----
- orderedDither32To16
- 	"Do an ordered dithering for converting from 32 to 16 bit depth."
- 	| ditherMatrix ii out inBits outBits index pv dmv r di dmi dmo g b pvOut outIndex |
- 	self depth = 32 ifFalse:[^self error:'Must be 32bit for this'].
- 	ditherMatrix := #(	0	8	2	10
- 						12	4	14	6
- 						3	11	1	9
- 						15	7	13	5).
- 	ii := (0 to: 31) collect:[:i| i].
- 	out := Form extent: self extent depth: 16.
- 	inBits := self bits.
- 	outBits := out bits.
- 	index := outIndex := 0.
- 	pvOut := 0.
- 	0 to: self height-1 do:[:y|
- 		0 to: self width-1 do:[:x|
- 			pv := inBits at: (index := index + 1).
- 			dmv := ditherMatrix at: (y bitAnd: 3) * 4 + (x bitAnd: 3) + 1.
- 			r := pv bitAnd: 255.	di := r * 496 bitShift: -8.
- 			dmi := di bitAnd: 15.	dmo := di bitShift: -4.
- 			r := dmv < dmi ifTrue:[ii at: 2+dmo] ifFalse:[ii at: 1+dmo].
- 			g := (pv bitShift: -8) bitAnd: 255.	di := g * 496 bitShift: -8.
- 			dmi := di bitAnd: 15.	dmo := di bitShift: -4.
- 			g := dmv < dmi ifTrue:[ii at: 2+dmo] ifFalse:[ii at: 1+dmo].
- 			b := (pv bitShift: -16) bitAnd: 255.	di := b * 496 bitShift: -8.
- 			dmi := di bitAnd: 15.	dmo := di bitShift: -4.
- 			b := dmv < dmi ifTrue:[ii at: 2+dmo] ifFalse:[ii at: 1+dmo].
- 			pvOut := (pvOut bitShift: 16) + 
- 						(b bitShift: 10) + (g bitShift: 5) + r.
- 			(x bitAnd: 1) = 1 ifTrue:[
- 				outBits at: (outIndex := outIndex+1) put: pvOut.
- 				pvOut := 0].
- 		].
- 		(self width bitAnd: 1) = 1 ifTrue:[
- 			outBits at: (outIndex := outIndex+1) put: (pvOut bitShift: -16).
- 			pvOut := 0].
- 	].
- 	^out!

Item was removed:
- ----- Method: Form>>paddedWidth (in category 'postscript generation') -----
- paddedWidth
- 	^ (self width + (self rowPadding-1)// self rowPadding) * self rowPadding.!

Item was removed:
- ----- Method: Form>>pageImage:at:corner: (in category 'transitions') -----
- pageImage: otherImage at: topLeft corner: corner
- 	"Produce a page-turning illusion that gradually reveals otherImage
- 	located at topLeft in this form.  Corner specifies which corner, as
- 		1=topLeft, 2=topRight, 3=bottomRight, 4=bottomLeft."
- 	| bb maskForm resultForm delta maskLoc maskRect stepSize cornerSel smallRect |
- 	stepSize := 10.
- 	bb := otherImage boundingBox.
- 	resultForm := self copy: (topLeft extent: bb extent).
- 	maskForm := Form extent: ((otherImage width min: otherImage height) + stepSize) asPoint.
- 
- 	"maskLoc := starting loc rel to topLeft"
- 	otherImage width > otherImage height
- 		ifTrue: ["wide image; motion is horizontal."
- 				(corner between: 2 and: 3) not ifTrue:
- 					["motion is to the right"
- 					delta := 1 @ 0.
- 					maskLoc := bb topLeft - (corner = 1
- 						ifTrue: [maskForm width @ 0]
- 						ifFalse: [maskForm width @ stepSize])]
- 					ifFalse:
- 					["motion is to the left"
- 					delta := -1 @ 0.
- 					maskLoc := bb topRight - (corner = 2
- 						ifTrue: [0 @ 0]
- 						ifFalse: [0 @ stepSize])]]
- 		ifFalse: ["tall image; motion is vertical."
- 				corner <= 2 ifTrue:
- 					["motion is downward"
- 					delta := 0 @ 1.
- 					maskLoc := bb topLeft - (corner = 1
- 						ifTrue: [0 @ maskForm height]
- 						ifFalse: [stepSize @ maskForm height])]
- 					ifFalse:
- 					["motion is upward"
- 					delta := 0 @ -1.
- 					maskLoc := bb bottomLeft - (corner = 3
- 						ifTrue: [stepSize @ 0]
- 						ifFalse: [0 @ 0])]].
- 
- 	"Build a solid triangle in the mask form"
- 	(Pen newOnForm: maskForm) in: [:p |
- 		corner even  "Draw 45-degree line"
- 			ifTrue: [p place: 0 @ 0; turn: 135; go: maskForm width * 3 // 2]
- 			ifFalse: [p place: 0 @ (maskForm height - 1); turn: 45; go: maskForm width * 3 // 2]].
- 	maskForm smear: delta negated distance: maskForm width.
- 	"Copy the mask to full resolution for speed.  Make it be the reversed
- 	so that it can be used for ORing in the page-corner color"
- 	maskForm := (Form extent: maskForm extent depth: otherImage depth)
- 		copyBits: maskForm boundingBox from: maskForm at: 0 @ 0
- 		colorMap: (Bitmap with: 16rFFFFFFFF with: 0).
- 
- 	"Now move the triangle maskForm across the resultForm selecting the
- 	triangular part of otherImage to display, and across the resultForm,
- 	selecting the part of the original image to erase."
- 	cornerSel := #(topLeft topRight bottomRight bottomLeft) at: corner.
- 	1 to: (otherImage width + otherImage height // stepSize) + 1 do:
- 		[:i |		"Determine the affected square"
- 		maskRect := (maskLoc extent: maskForm extent) intersect: bb.
- 		((maskLoc x * delta x) + (maskLoc y * delta y)) < 0 ifTrue:
- 			[smallRect := 0 @ 0 extent: (maskRect width min: maskRect height) asPoint.
- 			maskRect := smallRect align: (smallRect perform: cornerSel)
- 								with: (maskRect perform: cornerSel)].
- 
- 		"AND otherForm with triangle mask, and OR into result"
- 		resultForm copyBits: bb from: otherImage at: 0 @ 0
- 				clippingBox: maskRect rule: Form over fillColor: nil.
- 		resultForm copyBits: maskForm boundingBox from: maskForm at: maskLoc
- 				clippingBox: maskRect rule: Form erase fillColor: nil.
- 		resultForm copyBits: maskForm boundingBox from: maskForm at: maskLoc
- 				clippingBox: maskRect rule: Form under fillColor: Color lightBrown.
- 
- 		"Now update Display in a single BLT."
- 		self copyBits: maskRect from: resultForm at: topLeft + maskRect topLeft
- 				clippingBox: self boundingBox rule: Form over fillColor: nil.
- 		Display forceDisplayUpdate.
- 		maskLoc := maskLoc + (delta * stepSize)]
- "
- 1 to: 4 do: [:corner | Display pageImage:
- 				(Form fromDisplay: (10 at 10 extent: 200 at 300)) reverse
- 			at: 10 at 10 corner: corner]
- "
- !

Item was removed:
- ----- Method: Form>>pageWarp:at:forward: (in category 'transitions') -----
- pageWarp: otherImage at: topLeft forward: forward
- 	"Produce a page-turning illusion that gradually reveals otherImage
- 	located at topLeft in this form.
- 	forward == true means turn pages toward you, else away. [ignored for now]"
- 	| pageRect oldPage nSteps buffer p leafRect sourceQuad warp oldBottom d |
- 	pageRect := otherImage boundingBox.
- 	oldPage := self copy: (pageRect translateBy: topLeft).
- 	(forward ifTrue: [oldPage] ifFalse: [otherImage])
- 		border: pageRect
- 		widthRectangle: (Rectangle
- 				left: 0
- 				right: 2
- 				top: 1
- 				bottom: 1)
- 		rule: Form over
- 		fillColor: Color black.
- 	oldBottom := self copy: ((pageRect bottomLeft + topLeft) extent: (pageRect width@(pageRect height//4))).
- 	nSteps := 8.
- 	buffer := Form extent: otherImage extent + (0@(pageRect height//4)) depth: self depth.
- 	d := pageRect topLeft + (0@(pageRect height//4)) - pageRect topRight.
- 	1 to: nSteps-1 do:
- 		[:i | forward
- 			ifTrue: [buffer copy: pageRect from: otherImage to: 0 at 0 rule: Form over.
- 					p := pageRect topRight + (d * i // nSteps)]
- 			ifFalse: [buffer copy: pageRect from: oldPage to: 0 at 0 rule: Form over.
- 					p := pageRect topRight + (d * (nSteps-i) // nSteps)].
- 		buffer copy: oldBottom boundingBox from: oldBottom to: pageRect bottomLeft rule: Form over.
- 		leafRect := pageRect topLeft corner: p x @ (pageRect bottom + p y).
- 		sourceQuad := Array with: pageRect topLeft
- 			with: pageRect bottomLeft + (0 at p y)
- 			with: pageRect bottomRight
- 			with: pageRect topRight - (0 at p y).
- 		warp := (WarpBlt toForm: buffer)
- 				clipRect: leafRect;
- 				sourceForm: (forward ifTrue: [oldPage] ifFalse: [otherImage]);
- 				combinationRule: Form paint.
- 		warp copyQuad: sourceQuad toRect: leafRect.
- 		self copy: buffer boundingBox from: buffer to: topLeft rule: Form over.
- 		Display forceDisplayUpdate].
- 
- 	buffer copy: pageRect from: otherImage to: 0 at 0 rule: Form over.
- 	buffer copy: oldBottom boundingBox from: oldBottom to: pageRect bottomLeft rule: Form over.
- 	self copy: buffer boundingBox from: buffer to: topLeft rule: Form over.
- 	Display forceDisplayUpdate.
- "
- 1 to: 4 do: [:corner | Display pageWarp:
- 				(Form fromDisplay: (10 at 10 extent: 200 at 300)) reverse
- 			at: 10 at 10 forward: false]
- "
- !

Item was removed:
- ----- Method: Form>>paintBits:at:translucent: (in category 'displaying') -----
- paintBits: sourceForm at: destOrigin translucent: factor
- 	"Make up a BitBlt table and copy the bits with the given colorMap."
- 	(BitBlt destForm: self
- 		sourceForm: sourceForm
- 		halftoneForm: nil
- 		combinationRule: 31
- 		destOrigin: destOrigin
- 		sourceOrigin: 0 at 0
- 		extent: sourceForm extent
- 		clipRect: self boundingBox)
- 		copyBitsTranslucent: ((0 max: (factor*255.0) asInteger) min: 255)
- "
-  | f f2 f3 | f := Form fromUser. f replaceColor: f peripheralColor withColor: Color transparent.
- f2 := Form fromDisplay: (0 at 0 extent: f extent). f3 := f2 deepCopy.
- 0.0 to: 1.0 by: 1.0/32 do:
- 	[:t | f3 := f2 deepCopy. f3 paintBits: f at: 0 at 0 translucent: t.
- 	f3 displayAt: 0 at 0. (Delay forMilliseconds: 100) wait].
- "!

Item was removed:
- ----- Method: Form>>pixelCompare:with:at: (in category 'analyzing') -----
- pixelCompare: aRect with: otherForm at: otherLoc
- 	"Compare the selected bits of this form (those within aRect) against
- 	those in a similar rectangle of otherFrom.  Return the sum of the
- 	absolute value of the differences of the color values of every pixel.
- 	Obviously, this is most useful for rgb (16- or 32-bit) pixels but,
- 	in the case of 8-bits or less, this will return the sum of the differing
- 	bits of the corresponding pixel values (somewhat less useful)"
- 	| pixPerWord temp |
- 	pixPerWord := 32//self depth.
- 	(aRect left\\pixPerWord = 0 and: [aRect right\\pixPerWord = 0]) ifTrue:
- 		["If word-aligned, use on-the-fly difference"
- 		^ (BitBlt toForm: self) copy: aRect from: otherLoc in: otherForm
- 				fillColor: nil rule: 32].
- 	"Otherwise, combine in a word-sized form and then compute difference"
- 	temp := self copy: aRect.
- 	temp copy: aRect from: otherLoc in: otherForm rule: 21.
- 	^ (BitBlt toForm: temp) copy: aRect from: otherLoc in: nil
- 				fillColor: (Bitmap with: 0) rule: 32
- "  Dumb example prints zero only when you move over the original rectangle...
-  | f diff | f := Form fromUser.
- [Sensor anyButtonPressed] whileFalse:
- 	[diff := f pixelCompare: f boundingBox
- 		with: Display at: Sensor cursorPoint.
- 	diff printString , '        ' displayAt: 0 at 0]
- "!

Item was removed:
- ----- Method: Form>>pixelValueAt: (in category 'pixel access') -----
- pixelValueAt: aPoint 
- 	"Return the raw pixel value at the given point. This pixel value depends on the receiver's depth. Typical clients use colorAt: to get a Color.  "
- 
- 	^ self primPixelValueAtX: aPoint x y: aPoint y!

Item was removed:
- ----- Method: Form>>pixelValueAt:put: (in category 'pixel access') -----
- pixelValueAt: aPoint put: pixelValue
- 	"Store the given raw pixel value at the given point. Typical clients use colorAt:put: to store a color. "
- 
- 	(BitBlt bitPokerToForm: self) pixelAt: aPoint put: pixelValue.
- !

Item was removed:
- ----- Method: Form>>pixelValueFor: (in category 'color mapping') -----
- pixelValueFor: aColor
- 	"Return the pixel word for representing the given color on the receiver"
- 	^aColor pixelValueForDepth: self depth!

Item was removed:
- ----- Method: Form>>pixelWordFor: (in category 'color mapping') -----
- pixelWordFor: aColor
- 	"Return the pixel word for representing the given color on the receiver"
- 	^aColor pixelWordForDepth: self depth!

Item was removed:
- ----- Method: Form>>postCopy (in category 'copying') -----
- postCopy
- 	super postCopy.
- 	bits := bits copy
- !

Item was removed:
- ----- Method: Form>>preMultiplyAlpha (in category 'other') -----
- preMultiplyAlpha
- 	"Pre-multiply each pixel by its alpha, for proper alpha compositing (BitBlt rule 34).
- 	E.g., half-transparent green 16r7F00FF00 becomes 16r7F007F00"
- 
- 	depth = 32 ifFalse: [^self].
- 	1 to: bits size do: [:i |
- 		| v a r g b |
- 		v := bits at: i.
- 		a := v bitShift: -24.
- 		r := ((v bitShift: -16) bitAnd: 255) * a // 255.
- 		g := ((v bitShift: -8) bitAnd: 255) * a // 255.
- 		b := (v bitAnd: 255) * a // 255.
- 		bits at: i put: (a bitShift: 24) + (r bitShift: 16) + (g bitShift: 8) + b].!

Item was removed:
- ----- Method: Form>>primCountBits (in category 'analyzing') -----
- primCountBits
- 	"Count the non-zero pixels of this form."
- 	self depth > 8 ifTrue:
- 		[^(self asFormOfDepth: 8) primCountBits].
- 	^ (BitBlt toForm: self)
- 		fillColor: (Bitmap with: 0);
- 		destRect: (0 at 0 extent: width at height);
- 		combinationRule: 32;
- 		copyBits!

Item was removed:
- ----- Method: Form>>primPixelValueAtX:y: (in category 'pixel access') -----
- primPixelValueAtX: x y: y 
- 	"Return the raw pixel value at the given point. This pixel value depends on the receiver's depth. Typical clients use colorAt: to get a Color. Make sure the colorMap is nil for ColorForms "
- 
- 	<primitive: 'primitivePixelValueAt' module:'BitBltPlugin'>
- 	^(BitBlt bitPeekerFromForm: self) colorMap: nil;  pixelAt: x at y!

Item was removed:
- ----- Method: Form>>primPrintHScale:vScale:landscape: (in category 'other') -----
- primPrintHScale: hScale vScale: vScale landscape: aBoolean
- 	"On platforms that support it, this primitive prints the receiver, assumed to be a Form, to the default printer."
- 	"(Form extent: 10 at 10) primPrintHScale: 1.0 vScale: 1.0 landscape: true"
- 
- 	<primitive: 232>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: Form>>printOn: (in category 'fileIn/Out') -----
- printOn: aStream
-     aStream
-         nextPutAll: self class name;
-         nextPut: $(; print: width;
-         nextPut: $x; print: height;
-         nextPut: $x; print: depth;
-         nextPut: $).
- !

Item was removed:
- ----- Method: Form>>printPostscript:operator: (in category 'postscript generation') -----
- printPostscript: aStream operator: operator 
- 	aStream preserveStateDuring: 
- 			[:inner | 
- 			inner rectclip: (0 @ 0 extent: width @ height).
- 			self setColorspaceOn: inner.
- 			inner
- 				print: '[ ';
- 				cr;
- 				print: '/ImageType 1';
- 				cr;
- 				print: '/ImageMatrix [1 0 0 1 0 0]';
- 				cr;
- 				print: '/MultipleDataSources false';
- 				cr;
- 				print: '/DataSource level1 { { currentfile ';
- 				write: self bytesPerRow;
- 				print: ' string readhexstring pop }} bind { currentfile /ASCIIHexDecode filter } ifelse';
- 				cr;
- 				print: '/Width ';
- 				write: self paddedWidth;
- 				cr;
- 				print: '/Height ';
- 				write: self height;
- 				cr;
- 				print: '/Decode ';
- 				print: self decodeArray;
- 				cr;
- 				print: '/BitsPerComponent ';
- 				write: self bitsPerComponent;
- 				cr;
- 				print: 'makeDict ';
- 				print: operator;
- 				cr.
- 			self storePostscriptHexOn: inner.
- 			inner
- 				print: $>;
- 				cr.
- 			inner cr].
- 	aStream cr!

Item was removed:
- ----- Method: Form>>privateFloodFillValue: (in category 'private') -----
- privateFloodFillValue: aColor
- 	"Private. Compute the pixel value in the receiver's depth but take into account implicit color conversions by BitBlt."
- 	| f1 f2 bb |
- 	f1 := Form extent: 1 at 1 depth: depth.
- 	f2 := Form extent: 1 at 1 depth: 32.
- 	bb := BitBlt toForm: f1.
- 	bb fillColor: aColor; 
- 		destRect: (0 at 0 corner: 1 at 1); 
- 		combinationRule: 3; 
- 		copyBits.
- 	bb := BitBlt toForm: f2.
- 	bb sourceForm: f1; 
- 		sourceOrigin: 0 at 0;
- 		destRect: (0 at 0 corner: 1 at 1);
- 		combinationRule: 3;
- 		copyBits.
- 	^f2 pixelValueAt: 0 at 0.!

Item was removed:
- ----- Method: Form>>processUsingKernel: (in category 'processing') -----
- processUsingKernel: filter
- 
- 	^ self processUsingKernel: filter factor: 1.0 bias: 0.0!

Item was removed:
- ----- Method: Form>>processUsingKernel:factor:bias: (in category 'processing') -----
- processUsingKernel: filter factor: factor bias: bias
- 	| image result |
- 
- 	image := self.
- 	result := Form extent: image extent depth: image depth.
- 
- 	0 to: image height - 1 do: [:y |
- 		0 to: image width - 1 do: [:x |
- 			| r g b |
- 			r := g := b := 0.0.
- 
- 			0 to: filter rowCount - 1 do: [:filterY |
- 				0 to: filter columnCount - 1 do: [:filterX |
- 					| imageX imageY |
- 					imageX := (x - (filter columnCount // 2) + filterX + image width) \\
- 								image width.
- 					imageY := (y - (filter rowCount // 2) + filterY + image height) \\
- 								image height.
- 					r := r + ((image colorAt: imageX at imageY) red *
- 								(filter at: filterY + 1 at: filterX + 1)).
- 					g := g + ((image colorAt: imageX at imageY) green *
- 								(filter at: filterY + 1 at: filterX + 1)).
- 					b := b + ((image colorAt: imageX at imageY) blue *
- 								(filter at: filterY + 1 at: filterX + 1))]].
- 
- 			result colorAt: x at y put: (Color
- 				r: ((factor * r + bias) min: 1.0 max: 0.0)
- 				g: ((factor * g + bias) min: 1.0 max: 0.0)
- 				b: ((factor * b + bias) min: 1.0 max: 0.0))]].
- 	^ result
- !

Item was removed:
- ----- Method: Form>>readAttributesFrom: (in category 'fileIn/Out') -----
- readAttributesFrom: aBinaryStream
- 	| offsetX offsetY |
- 	depth := aBinaryStream next.
- 	(self depth isPowerOfTwo and: [self depth between: 1 and: 32])
- 		ifFalse: [self error: 'invalid depth; bad Form file?'].
- 	width := aBinaryStream nextWord.
- 	height := aBinaryStream nextWord.
- 	offsetX  := aBinaryStream nextWord.
- 	offsetY := aBinaryStream nextWord.
- 	offsetX > 32767 ifTrue: [offsetX := offsetX - 65536].
- 	offsetY > 32767 ifTrue: [offsetY := offsetY - 65536].
- 	offset := Point x: offsetX y: offsetY.
- 	
- !

Item was removed:
- ----- Method: Form>>readBitsFrom: (in category 'fileIn/Out') -----
- readBitsFrom: aBinaryStream
- 	
- 	bits := Bitmap newFromStream: aBinaryStream.
- 	bits size = self bitsSize ifFalse: [self error: 'wrong bitmap size; bad Form file?'].
- 	^ self
- !

Item was removed:
- ----- Method: Form>>readFrom: (in category 'fileIn/Out') -----
- readFrom: aBinaryStream
- 	"Reads the receiver from the given binary stream with the format:
- 		depth, extent, offset, bits."
- 	self readAttributesFrom: aBinaryStream.
- 	self readBitsFrom: aBinaryStream!

Item was removed:
- ----- Method: Form>>readFromOldFormat: (in category 'fileIn/Out') -----
- readFromOldFormat: aBinaryStream
- 	"Read a Form in the original ST-80 format."
- 
- 	| w h offsetX offsetY newForm theBits pos |
- 	self error: 'this method must be updated to read into 32-bit word bitmaps'.
- 	w := aBinaryStream nextWord.
- 	h := aBinaryStream nextWord.
- 	offsetX  := aBinaryStream nextWord.
- 	offsetY := aBinaryStream nextWord.
- 	offsetX > 32767 ifTrue: [offsetX := offsetX - 65536].
- 	offsetY > 32767 ifTrue: [offsetY := offsetY - 65536].
- 	newForm := Form extent: w @ h offset: offsetX @ offsetY.
- 	theBits := newForm bits.
- 	pos := 0.
- 	1 to: w + 15 // 16 do: [:j |
- 		1 to: h do: [:i |
- 			theBits at: (pos := pos+1) put: aBinaryStream nextWord]].
- 	newForm bits: theBits.
- 	^ newForm
- !

Item was removed:
- ----- Method: Form>>readNativeResourceFrom: (in category 'resources') -----
- readNativeResourceFrom: byteStream
- 	| img aStream |
- 	aStream := byteStream.
- 	img := [ImageReadWriter formFromStream: aStream] on: Error do:[:ex| nil].
- 	img ifNil:[^nil].
- 	(img isColorForm and:[self isColorForm]) ifTrue:[
- 		| cc |
- 		cc := img colors.
- 		img colors: nil.
- 		img displayOn: self.
- 		img colors: cc.
- 	] ifFalse:[
- 		img displayOn: self.
- 	].
- 	img := nil.!

Item was removed:
- ----- Method: Form>>readResourceFrom: (in category 'resources') -----
- readResourceFrom: aStream 
- 	"Store a resource representation of the receiver on aStream.
- 	Must be specific to the receiver so that no code is filed out."
- 
- 	| bitsSize msb |
- 	(aStream next: 4) asString = self resourceTag 
- 		ifFalse: 
- 			[aStream position: aStream position - 4.
- 			^self readNativeResourceFrom: aStream].
- 	width := aStream nextNumber: 4.
- 	height := aStream nextNumber: 4.
- 	depth := aStream nextNumber: 4.
- 	bitsSize := aStream nextNumber: 4.
- 	bitsSize = 0 
- 		ifFalse: 
- 			[bits := aStream next: bitsSize.
- 			^self].
- 	msb := (aStream nextNumber: 4) = 1.
- 	bitsSize := aStream nextNumber: 4.
- 	bits := Bitmap new: self bitsSize.
- 	(Form 
- 		extent: width @ height
- 		depth: depth
- 		bits: (aStream next: bitsSize * 4)) displayOn: self.
- 	msb = Smalltalk isBigEndian 
- 		ifFalse: 
- 			[Bitmap 
- 				swapBytesIn: bits
- 				from: 1
- 				to: bits size]!

Item was removed:
- ----- Method: Form>>rectangleEnclosingPixelsNotOfColor: (in category 'analyzing') -----
- rectangleEnclosingPixelsNotOfColor: aColor
- 	"Answer the smallest rectangle enclosing all the pixels of me that are different from the given color. Useful for extracting a foreground graphic from its background."
- 
- 	| cm slice copyBlt countBlt top bottom newH left right |
- 	"map the specified color to 1 and all others to 0"
- 	cm := Bitmap new: (1 bitShift: (self depth min: 15)).
- 	cm primFill: 1.
- 	cm at: (aColor indexInMap: cm) put: 0.
- 
- 	"build a 1-pixel high horizontal slice and BitBlts for counting pixels of interest"
- 	slice := Form extent: width at 1 depth: 1.
- 	copyBlt := (BitBlt toForm: slice)
- 		sourceForm: self;
- 		combinationRule: Form over;
- 		destX: 0 destY: 0 width: width height: 1;
- 		colorMap: cm.
- 	countBlt := (BitBlt toForm: slice)
- 		fillColor: (Bitmap with: 0);
- 		destRect: (0 at 0 extent: slice extent);
- 		combinationRule: 32.
- 
- 	"scan in from top and bottom"
- 	top := (0 to: height)
- 		detect: [:y |
- 			copyBlt sourceOrigin: 0 at y; copyBits.
- 			countBlt copyBits > 0]
- 		ifNone: [^ 0 at 0 extent: 0 at 0].
- 	bottom := (height - 1 to: top by: -1)
- 		detect: [:y |
- 			copyBlt sourceOrigin: 0 at y; copyBits.
- 			countBlt copyBits > 0].
- 
- 	"build a 1-pixel wide vertical slice and BitBlts for counting pixels of interest"
- 	newH := bottom - top + 1.
- 	slice := Form extent: 1 at newH depth: 1.
- 	copyBlt := (BitBlt toForm: slice)
- 		sourceForm: self;
- 		combinationRule: Form over;
- 		destX: 0 destY: 0 width: 1 height: newH;
- 		colorMap: cm.
- 	countBlt := (BitBlt toForm: slice)
- 		fillColor: (Bitmap with: 0);
- 		destRect: (0 at 0 extent: slice extent);
- 		combinationRule: 32.
- 
- 	"scan in from left and right"
- 	left := (0 to: width)
- 		detect: [:x |
- 			copyBlt sourceOrigin: x at top; copyBits.
- 			countBlt copyBits > 0].
- 	right := (width - 1 to: left by: -1)
- 		detect: [:x |
- 			copyBlt sourceOrigin: x at top; copyBits.
- 			countBlt copyBits > 0].
- 
- 	^ left at top corner: (right + 1)@(bottom + 1)
- !

Item was removed:
- ----- Method: Form>>reducedPaletteOfSize: (in category 'color mapping') -----
- reducedPaletteOfSize: nColors
- 	"Return an array of colors of size nColors, such that those colors
- 	represent well the pixel values actually found in this form."
- 	| threshold tallies colorTallies dist delta palette cts top cluster |
- 	tallies := self tallyPixelValues.  "An array of tallies for each pixel value"
- 	threshold := width * height // 500.
- 
- 	"Make an array of (color -> tally) for all tallies over threshold"
- 	colorTallies := Array streamContents:
- 		[:s | tallies withIndexDo:
- 			[:v :i | v >= threshold ifTrue:
- 				[s nextPut: (Color colorFromPixelValue: i-1 depth: depth) -> v]]].
- 
- 	"Extract a set of clusters by picking the top tally, and then removing all others
- 	whose color is within dist of it.  Iterate the process, adjusting dist until we get nColors."
- 	dist := 0.2.  delta := dist / 2.
- 		[cts := colorTallies copy.
- 		palette := Array streamContents: [:s |
- 			[cts isEmpty] whileFalse:
- 				[top := cts detectMax: [:a | a value].
- 				cluster := cts select: [:a | (a key diff: top key) < dist].
- 				s nextPut: top key -> (cluster detectSum: [:a | a value]).
- 				cts := cts copyWithoutAll: cluster]].
- 		palette size = nColors or: [delta < 0.001]]
- 		whileFalse:
- 			[palette size > nColors
- 				ifTrue: [dist := dist + delta]
- 				ifFalse: [dist := dist - delta].
- 			delta := delta / 2].
- 	^ palette collect: [:a | a key]
- !

Item was removed:
- ----- Method: Form>>relativeTextAnchorPosition (in category 'other') -----
- relativeTextAnchorPosition
- 
- 	^nil		"so forms can be in TextAnchors"!

Item was removed:
- ----- Method: Form>>replaceByResource: (in category 'fileIn/Out') -----
- replaceByResource: aForm
- 	"Replace the receiver by some resource that just got loaded"
- 	(self extent = aForm extent and:[self depth = aForm depth]) ifTrue:[
- 		bits := aForm bits.
- 	].!

Item was removed:
- ----- Method: Form>>replaceColor:withColor: (in category 'image manipulation') -----
- replaceColor: oldColor withColor: newColor
- 	"Replace one color with another everywhere is this form"
- 
- 	| cm newInd target ff |
- 	self depth = 32
- 		ifTrue: [cm := (Color  cachedColormapFrom: 16 to: 32) copy]
- 		ifFalse: [cm := Bitmap new: (1 bitShift: (self depth min: 15)).
- 				1 to: cm size do: [:i | cm at: i put: i - 1]].
- 	newInd := newColor pixelValueForDepth: self depth.
- 	cm at: (oldColor pixelValueForDepth: (self depth min: 16))+1 put: newInd.
- 	target := newColor isTransparent 
- 		ifTrue: [ff := Form extent: self extent depth: depth.
- 			ff fillWithColor: newColor.  ff]
- 		ifFalse: [self].
- 	(BitBlt toForm: target)
- 		sourceForm: self;
- 		sourceOrigin: 0 at 0;
- 		combinationRule: Form paint;
- 		destX: 0 destY: 0 width: width height: height;
- 		colorMap: cm;
- 		copyBits.
- 	newColor = Color transparent 
- 		ifTrue: [target displayOn: self].!

Item was removed:
- ----- Method: Form>>resourceTag (in category 'resources') -----
- resourceTag
- 	^'FORM'!

Item was removed:
- ----- Method: Form>>rgbaBitMasks (in category 'color mapping') -----
- rgbaBitMasks
- 	"Return the masks for specifying the R,G,B, and A components in the receiver"
- 	self depth <= 8
- 		ifTrue:[^#(16rFF0000 16rFF00 16rFF 16rFF000000)].
- 	self depth = 16
- 		ifTrue:[^#(16r7C00 16r3E0 16r1F 16r0)].
- 	self depth = 32
- 		ifTrue:[^#(16rFF0000 16rFF00 16rFF 16rFF000000)].
- 	self error:'Bad depth for form'!

Item was removed:
- ----- Method: Form>>rotateBy: (in category 'scaling, rotation') -----
- rotateBy: deg
- 	"Rotate the receiver by the indicated number of degrees."
- 	"rot is the destination form, bit enough for any angle."
- 
- 	^ self rotateBy: deg smoothing: 1
- "
-  | a f |  f := Form fromDisplay: (0 at 0 extent: 200 at 200).  a := 0.
- [Sensor anyButtonPressed] whileFalse:
- 	[((Form fromDisplay: (Sensor cursorPoint extent: 130 at 66))
- 		rotateBy: (a := a+5)) display].
- f display
- "!

Item was removed:
- ----- Method: Form>>rotateBy:centerAt: (in category 'scaling, rotation') -----
- rotateBy: direction centerAt: aPoint
- 	"Return a rotated copy of the receiver. 
- 	direction = #none, #right, #left, or #pi"
- 	| newForm quad rot scale |
- 	direction == #none ifTrue: [^ self].
- 	scale :=  (direction = #pi ifTrue: [width at height] ifFalse: [height at width]) / self extent .
- 	newForm := self blankCopyOf: self boundingBox scaledBy: scale.
- 	quad := self boundingBox innerCorners.
- 	rot := #(right pi left) indexOf: direction.
- 	(WarpBlt toForm: newForm)
- 		sourceForm: self;
- 		colorMap: (self colormapIfNeededFor: newForm);
- 		combinationRule: 3;
- 		copyQuad: ((1+rot to: 4+rot) collect: [:i | quad atWrap: i])
- 			 toRect: newForm boundingBox.
- 	newForm offset: (self offset rotateBy: direction centerAt: aPoint).
- 	^ newForm
- "
- [Sensor anyButtonPressed] whileFalse:
- 	[((Form fromDisplay: (Sensor cursorPoint extent: 130 at 66))
- 		rotateBy: #left centerAt: 0 at 0) display]
- "
- "Consistency test...
-  | f f2 p | [Sensor anyButtonPressed] whileFalse:
- 	[f := Form fromDisplay: ((p := Sensor cursorPoint) extent: 31 at 41).
- 	Display fillBlack: (p extent: 31 at 41).
- 	f2 := f rotateBy: #left centerAt: 0 at 0.
- 	(f2 rotateBy: #right centerAt: 0 at 0) displayAt: p]
- "
- !

Item was removed:
- ----- Method: Form>>rotateBy:magnify:smoothing: (in category 'scaling, rotation') -----
- rotateBy: deg magnify: scale smoothing: cellSize
- 	"Rotate the receiver by the indicated number of degrees and magnify. scale can be a Point to make for interesting 3D effects "
- 	"rot is the destination form, big enough for any angle."
- 
- 	| side rot warp r1 pts bigSide |
- 	side := 1 + self extent r asInteger.
- 	bigSide := (side asPoint * scale) rounded.
- 	rot := self blankCopyOf: self boundingBox scaledBy: ( bigSide / self extent ).
- 	warp := (WarpBlt toForm: rot)
- 		sourceForm: self;
- 		colorMap: (self colormapIfNeededFor: rot);
- 		cellSize: cellSize;  "installs a new colormap if cellSize > 1"
- 		combinationRule: Form paint.
- 	r1 := (0 at 0 extent: side at side) align: (side at side)//2 with: self boundingBox center.
- 
- 	"Rotate the corners of the source rectangle." 
- 	pts := r1 innerCorners collect:
- 		[:pt | | p |
- 		p := pt - r1 center.
- 		(r1 center x asFloat + (p x asFloat*deg degreeCos) + (p y asFloat*deg degreeSin)) @
- 		(r1 center y asFloat - (p x asFloat*deg degreeSin) + (p y asFloat*deg degreeCos))].
- 	warp copyQuad: pts toRect: rot boundingBox.
- 	^ rot
- "
-  | a f |  f := Form fromDisplay: (0 at 0 extent: 200 at 200).  a := 0.
- [Sensor anyButtonPressed] whileFalse:
- 	[((Form fromDisplay: (Sensor cursorPoint extent: 130 at 66))
- 		rotateBy: (a := a+5) magnify: 0.75 at 2 smoothing: 2) display].
- f display
- "!

Item was removed:
- ----- Method: Form>>rotateBy:smoothing: (in category 'scaling, rotation') -----
- rotateBy: deg smoothing: cellSize
- 	"Rotate the receiver by the indicated number of degrees."
- 	^self rotateBy: deg magnify: 1 smoothing: cellSize
- "
-  | a f |  f := Form fromDisplay: (0 at 0 extent: 200 at 200).  a := 0.
- [Sensor anyButtonPressed] whileFalse:
- 	[((Form fromDisplay: (Sensor cursorPoint extent: 130 at 66))
- 		rotateBy: (a := a+5) smoothing: 2) display].
- f display
- "!

Item was removed:
- ----- Method: Form>>rowPadding (in category 'postscript generation') -----
- rowPadding
- 	^ 32 // self depth!

Item was removed:
- ----- Method: Form>>scaledToSize: (in category 'scaling, rotation') -----
- scaledToSize: numberOrPoint
- 
- 	^ self scaledToSize: numberOrPoint smoothing: 2!

Item was removed:
- ----- Method: Form>>scaledToSize:smoothing: (in category 'scaling, rotation') -----
- scaledToSize: numberOrPoint smoothing: factor
- 
- 	| scale newExtent |
- 	newExtent := numberOrPoint asPoint.
- 	
- 	newExtent = self extent ifTrue: [^ self copy].
- 	
- 	(self height isZero or: [self width isZero])
- 		ifTrue: [^ self species extent: newExtent depth: self depth].
- 		
- 	scale := newExtent x / self width min: newExtent y / self height.
- 	^ self magnify: self boundingBox by: scale smoothing: factor!

Item was removed:
- ----- Method: Form>>setAsBackground (in category 'other') -----
- setAsBackground
- 	"Set this form as a background image."
- 
- 	Project current setAsBackground: self
- !

Item was removed:
- ----- Method: Form>>setColorspaceOn: (in category 'postscript generation') -----
- setColorspaceOn:aStream
- 	self numComponents = 1 ifTrue:[aStream print:'/DeviceGray setcolorspace 0 setgray'; cr.]
- 		ifFalse:[aStream print:'/DeviceRGB setcolorspace'; cr.].!

Item was removed:
- ----- Method: Form>>setExtent:depth: (in category 'private') -----
- setExtent: extent depth: bitsPerPixel
- 	"Create a virtual bit map with the given extent and bitsPerPixel."
- 
- 	width := extent x asInteger.
- 	width < 0 ifTrue: [width := 0].
- 	height := extent y asInteger.
- 	height < 0 ifTrue: [height := 0].
- 	depth := bitsPerPixel.
- 	bits := Bitmap new: self bitsSize!

Item was removed:
- ----- Method: Form>>setExtent:depth:bits: (in category 'private') -----
- setExtent: extent depth: bitsPerPixel bits: bitmap
- 	"Create a virtual bit map with the given extent and bitsPerPixel."
- 	| bitsClass |
- 	(width := extent x asInteger) < 0 ifTrue: [width := 0].
- 	(height := extent y asInteger) < 0 ifTrue: [height := 0].
- 	depth := bitsPerPixel.
- 	(bits isNil
- 	 or: [(bitsClass := bits class) isBits
- 		and: [self bitsSize * 4 "bytes per pixel" = (bitmap size * bitsClass elementSize)]]) ifFalse:
- 		[^self error: 'Bad dimensions and/or bitmap kind'].
- 	bits := bitmap!

Item was removed:
- ----- Method: Form>>setResourceBits: (in category 'private') -----
- setResourceBits: aForm
- 	"Private. Really. Used for setting the 'resource bits' when externalizing some form"
- 	bits := aForm.!

Item was removed:
- ----- Method: Form>>shapeBorder:width: (in category 'bordering') -----
- shapeBorder: aColor width: borderWidth
- 	"A simplified version for shapes surrounded by transparency (as SketchMorphs).
- 	Note also this returns a new form that may be larger, and does not affect the original."
- 	| shapeForm borderForm newForm |
- 	newForm := Form extent: self extent + (borderWidth*2) depth: self depth.
- 	newForm fillColor: Color transparent.
- 	self displayOn: newForm at: (0 at 0) + borderWidth.
- 	"First identify the shape in question as a B/W form"
- 	shapeForm := (newForm makeBWForm: Color transparent) reverse.
- 	"Now find the border of that shape"
- 	borderForm := shapeForm borderFormOfWidth: borderWidth sharpCorners: false.
- 	"Finally use that shape as a mask to paint the border with color"
- 	^ newForm fillShape: borderForm fillColor: aColor!

Item was removed:
- ----- Method: Form>>shapeBorder:width:interiorPoint:sharpCorners:internal: (in category 'bordering') -----
- shapeBorder: aColor width: borderWidth interiorPoint: interiorPoint
- 	sharpCorners: sharpen internal: internal
- 	"Identify the shape (region of identical color) at interiorPoint,
- 	and then add an outline of width=borderWidth and color=aColor.
- 	If sharpen is true, then cause right angles to be outlined by
- 	right angles.  If internal is true, then produce a border that lies
- 	within the identified shape.  Thus one can put an internal border
- 	around the whole background, thus effecting a normal border
- 	around every other foreground image."
- 	| shapeForm borderForm interiorColor |
- 	"First identify the shape in question as a B/W form"
- 	interiorColor := self colorAt: interiorPoint.
- 	shapeForm := (self makeBWForm: interiorColor) reverse
- 				findShapeAroundSeedBlock:
- 					[:form | form pixelValueAt: interiorPoint put: 1].
- 	"Reverse the image to grow the outline inward"
- 	internal ifTrue: [shapeForm reverse].
- 	"Now find the border fo that shape"
- 	borderForm := shapeForm borderFormOfWidth: borderWidth sharpCorners: sharpen.
- 	"Finally use that shape as a mask to paint the border with color"
- 	self fillShape: borderForm fillColor: aColor!

Item was removed:
- ----- Method: Form>>shapeFill:interiorPoint: (in category 'filling') -----
- shapeFill: aColor interiorPoint: interiorPoint
- 	"Identify the shape (region of identical color) at interiorPoint,
- 	and then fill that shape with the new color, aColor
- 	: modified di's original method such that it returns the bwForm, for potential use by the caller"
- 
- 	| bwForm interiorPixVal map ppd color ind |
- 	self depth = 1 ifTrue:
- 		[^ self shapeFill: aColor
- 			seedBlock: [:form | form pixelValueAt: interiorPoint put: 1]].
- 
- 	"First map this form into a B/W form with 0's in the interior region."
- 		"bwForm := self makeBWForm: interiorColor."	"won't work for two whites"
- 	interiorPixVal := self pixelValueAt: interiorPoint.
- 	bwForm := Form extent: self extent.
- 	map := Bitmap new: (1 bitShift: (self depth min: 12)).  "Not calling newColorMap.  All 
- 			non-foreground go to 0.  Length is 2 to 4096."
- 	ppd := self depth.	"256 long color map in depth 8 is not one of the following cases"
- 	3 to: 5 do: [:bitsPerColor | 
- 		(2 raisedTo: bitsPerColor*3) = map size 
- 			ifTrue: [ppd := bitsPerColor*3]].	"ready for longer maps than 512"
- 
- 	ppd <= 8
- 		ifTrue: [map at: interiorPixVal+1 put: 1]
- 		ifFalse: [interiorPixVal = 0 
- 			ifFalse: [color := Color colorFromPixelValue: interiorPixVal depth: self depth.
- 				ind := color pixelValueForDepth: ppd.
- 				map at: ind+1 put: 1]
- 			ifTrue: [map at: 1 put: 1]].
- 	bwForm copyBits: self boundingBox from: self at: 0 at 0 colorMap: map.
- 	bwForm reverse.  "Make interior region be 0's"
- 
- 	"Now fill the interior region and return that shape"
- 	bwForm := bwForm findShapeAroundSeedBlock:
- 					[:form | form pixelValueAt: interiorPoint put: 1].
- 
- 	"Finally use that shape as a mask to flood the region with color"
- 	self eraseShape: bwForm.
- 	self fillShape: bwForm fillColor: aColor.
- 	^ bwForm!

Item was removed:
- ----- Method: Form>>shapeFill:seedBlock: (in category 'filling') -----
- shapeFill: aColor seedBlock: seedBlock
- 	self depth > 1 ifTrue: [self error: 'This call only meaningful for B/W forms'].
- 	(self findShapeAroundSeedBlock: seedBlock)
- 		displayOn: self at: 0 at 0 clippingBox: self boundingBox
- 		rule: Form under fillColor: aColor !

Item was removed:
- ----- Method: Form>>sharpen (in category 'processing') -----
- sharpen
- 
- 	^ self processUsingKernel: (Matrix rows: 3 columns: 3 contents: #(
- 		 0 -1  0
- 		-1  5 -1
- 		 0 -1  0
- 	))!

Item was removed:
- ----- Method: Form>>shouldPreserveContents (in category 'testing') -----
- shouldPreserveContents
- 	"Return true if the receiver should preserve it's contents when flagged to be clean. Most forms can not be trivially restored by some drawing operation but some may."
- 	^true!

Item was removed:
- ----- Method: Form>>shrink:by: (in category 'scaling, rotation') -----
- shrink: aRectangle by: scale 
- 	| scalePt |
- 	scalePt := scale asPoint.
- 	^ self magnify: aRectangle by: (1.0 / scalePt x asFloat) @ (1.0 / scalePt y asFloat)!

Item was removed:
- ----- Method: Form>>shutDown (in category 'initialize-release') -----
- shutDown
- 	"The system is going down. Try to preserve some space"
- 	self hibernate!

Item was removed:
- ----- Method: Form>>size (in category 'accessing') -----
- size
- 	"Should no longer be used -- use bitsSize instead.  length of variable part of instance."
- 	^ super size!

Item was removed:
- ----- Method: Form>>slideImage:at:delta: (in category 'transitions') -----
- slideImage: otherImage at: topLeft delta: delta
- 	"Display slideImage: (Form fromDisplay: (40 at 40 extent: 300 at 300)) reverse
- 		at: 40 at 40 delta: 3 at -4"
- 	| bb nSteps clipRect |
- 	bb := otherImage boundingBox.
- 	clipRect := topLeft extent: otherImage extent.
- 	nSteps := 1.
- 	delta x = 0 ifFalse: [nSteps := nSteps max: (bb width//delta x abs) + 1].
- 	delta y = 0 ifFalse: [nSteps := nSteps max: (bb height//delta y abs) + 1].
- 	1 to: nSteps do:
- 			[:i | self copyBits: bb from: otherImage
- 				at: delta*(i-nSteps) + topLeft
- 				clippingBox: clipRect rule: Form paint fillColor: nil.
- 			Display forceDisplayUpdate]!

Item was removed:
- ----- Method: Form>>smear:distance: (in category 'image manipulation') -----
- smear: dir distance: dist
- 	"Smear any black pixels in this form in the direction dir in Log N steps"
- 	| skew bb |
- 	bb := BitBlt destForm: self sourceForm: self fillColor: nil
- 		combinationRule: Form under destOrigin: 0 at 0 sourceOrigin: 0 at 0
- 		extent: self extent clipRect: self boundingBox.
- 	skew := 1.
- 	[skew < dist] whileTrue:
- 		[bb destOrigin: dir*skew; copyBits.
- 		skew := skew+skew]!

Item was removed:
- ----- Method: Form>>store15To24HexBitsOn: (in category 'postscript generation') -----
- store15To24HexBitsOn:aStream
- 
- 	| buf lineWidth |
- 
- 	"write data for 16-bit form, optimized for encoders writing directly to files to do one single file write rather than 12. I'm not sure I understand the significance of the shifting pattern, but I think I faithfully translated it from the original"
- 
- 	lineWidth := 0.
- 	buf := String new: 12.
- 	self unhibernate.
- 	bits do: [:word | | i | 
- 		i := 0.
- 		"upper pixel"
- 		buf at: (i := i + 1) put: ((word bitShift: -27) bitAnd: 15) asHexDigit.
- 		buf at: (i := i + 1) put: ((word bitShift: -32) bitAnd: 8) asHexDigit.
- 
- 		buf at: (i := i + 1) put: ((word bitShift: -22) bitAnd: 15) asHexDigit.
- 		buf at: (i := i + 1) put: ((word bitShift: -27) bitAnd: 8) asHexDigit.
- 
- 		buf at: (i := i + 1) put: ((word bitShift: -17) bitAnd: 15) asHexDigit.
- 		buf at: (i := i + 1) put: ((word bitShift: -22) bitAnd: 8) asHexDigit.
- 
- 		"lower pixel"
- 
- 		buf at: (i := i + 1) put: ((word bitShift: -11) bitAnd: 15) asHexDigit.
- 		buf at: (i := i + 1) put: ((word bitShift: -16) bitAnd: 8) asHexDigit.
- 
- 		buf at: (i := i + 1) put: ((word bitShift: -6) bitAnd: 15) asHexDigit.
- 		buf at: (i := i + 1) put: ((word bitShift: -11) bitAnd: 8) asHexDigit.
- 
- 		buf at: (i := i + 1) put: ((word bitShift: -1) bitAnd: 15) asHexDigit.
- 		buf at: (i := i + 1) put: ((word bitShift: -6) bitAnd: 8) asHexDigit.
- 		aStream nextPutAll: buf.
- 		lineWidth := lineWidth + 12.
- 		lineWidth > 100 ifTrue: [ aStream cr. lineWidth := 0 ].
- 		"#( 31 26 21 15 10 5 )  do:[:startBit | ]"
- 	].!

Item was removed:
- ----- Method: Form>>store32To24HexBitsOn: (in category 'postscript generation') -----
- store32To24HexBitsOn:aStream
- 	^self storeBits:20 to:0 on:aStream.!

Item was removed:
- ----- Method: Form>>storeBits:to:on: (in category 'postscript generation') -----
- storeBits:startBit to:stopBit on:aStream
- 	self unhibernate.
- 	bits storeBits:startBit to:stopBit on:aStream.!

Item was removed:
- ----- Method: Form>>storeBitsOn:base: (in category 'fileIn/Out') -----
- storeBitsOn:aStream base:anInteger
- 	self unhibernate.
- 	bits do: [:word | 
- 		anInteger = 10
- 			ifTrue: [aStream space]
- 			ifFalse: [aStream crtab: 2].
- 		word storeOn: aStream base: anInteger].
- !

Item was removed:
- ----- Method: Form>>storeHexBitsOn: (in category 'postscript generation') -----
- storeHexBitsOn:aStream
- 	^self storeBits:28 to:0 on:aStream.!

Item was removed:
- ----- Method: Form>>storeOn: (in category 'fileIn/Out') -----
- storeOn: aStream
- 
- 	self storeOn: aStream base: 10!

Item was removed:
- ----- Method: Form>>storeOn:base: (in category 'fileIn/Out') -----
- storeOn: aStream base: anInteger 
- 	"Store the receiver out as an expression that can be evaluated to recreate a Form with the same contents as the original."
- 
- 	self unhibernate.
- 	aStream nextPut: $(.
- 	aStream nextPutAll: self species name.
- 	aStream crtab: 1.
- 	aStream nextPutAll: 'extent: '.
- 	self extent printOn: aStream.
- 	aStream crtab: 1.
- 	aStream nextPutAll: 'depth: '.
- 	self depth printOn: aStream.
- 	aStream crtab: 1.
- 	aStream nextPutAll: 'fromArray: #('.
- 	self storeBitsOn:aStream base:anInteger.
- 	aStream nextPut: $).
- 	aStream crtab: 1.
- 	aStream nextPutAll: 'offset: '.
- 	self offset printOn: aStream.
- 	aStream nextPut: $).
- !

Item was removed:
- ----- Method: Form>>storePostscriptHexOn: (in category 'postscript generation') -----
- storePostscriptHexOn: inner 
- 	self depth <= 8 ifTrue: [self storeHexBitsOn: inner].
- 	self depth = 16 ifTrue: [self store15To24HexBitsOn: inner].
- 	self depth = 32 ifTrue: [self store32To24HexBitsOn: inner]!

Item was removed:
- ----- Method: Form>>storeResourceOn: (in category 'resources') -----
- storeResourceOn: aStream
- 	"Store a resource representation of the receiver on aStream.
- 	Must be specific to the receiver so that no code is filed out."
- 	self hibernate.
- 	aStream nextPutAll: self resourceTag asByteArray. "tag"
- 	aStream nextNumber: 4 put: width.
- 	aStream nextNumber: 4 put: height.
- 	aStream nextNumber: 4 put: depth.
- 	(bits isMemberOf: ByteArray) ifFalse:[
- 		"must store bitmap"
- 		aStream nextNumber: 4 put: 0. "tag"
- 		aStream nextNumber: 4 put: (Smalltalk isBigEndian ifTrue:[1] ifFalse:[0]).
- 	].
- 	aStream nextNumber: 4 put: bits size.
- 	aStream nextPutAll: bits.
- !

Item was removed:
- ----- Method: Form>>swapEndianness (in category 'initialize-release') -----
- swapEndianness
- 	"Swap from big to little endian pixels and vice versa"
- 	depth := 0 - depth.!

Item was removed:
- ----- Method: Form>>tallyPixelValues (in category 'analyzing') -----
- tallyPixelValues
- 	"Answer a Bitmap whose elements contain the number of pixels in this Form with the pixel value corresponding to their index. Note that the pixels of multiple Forms can be tallied together using tallyPixelValuesInRect:into:."
- 
- 	^ self tallyPixelValuesInRect: self boundingBox
- 		into: (Bitmap new: (1 bitShift: (self depth min: 15)))
- "
- Move a little rectangle around the screen and print its tallies...
-  | r tallies nonZero |
- Cursor blank showWhile: [
- [Sensor anyButtonPressed] whileFalse:
- 	[r := Sensor cursorPoint extent: 10 at 10.
- 	Display border: (r expandBy: 2) width: 2 rule: Form reverse fillColor: nil.
- 	tallies := (Display copy: r) tallyPixelValues.
- 	nonZero := (1 to: tallies size) select: [:i | (tallies at: i) > 0]
- 			thenCollect: [:i | (tallies at: i) -> (i-1)].
- 	nonZero printString , '          ' displayAt: 0 at 0.
- 	Display border: (r expandBy: 2) width: 2 rule: Form reverse fillColor: nil]]
- "
- !

Item was removed:
- ----- Method: Form>>tallyPixelValuesInRect:into: (in category 'analyzing') -----
- tallyPixelValuesInRect: destRect into: valueTable
- 	"Tally the selected pixels of this Form into valueTable, a Bitmap of depth 2^depth similar to a color map. Answer valueTable."
- 
- 	(BitBlt toForm: self)
- 		sourceForm: self;  "src must be given for color map ops"
- 		sourceOrigin: 0 at 0;
- 		tallyMap: valueTable;
- 		combinationRule: 33;
- 		destRect: destRect;
- 		copyBits.
- 	^ valueTable
- 
- "
- Move a little rectangle around the screen and print its tallies...
-  | r tallies nonZero |
- Cursor blank showWhile: [
- [Sensor anyButtonPressed] whileFalse:
- 	[r := Sensor cursorPoint extent: 10 at 10.
- 	Display border: (r expandBy: 2) width: 2 rule: Form reverse fillColor: nil.
- 	tallies := (Display copy: r) tallyPixelValues.
- 	nonZero := (1 to: tallies size) select: [:i | (tallies at: i) > 0]
- 			thenCollect: [:i | (tallies at: i) -> (i-1)].
- 	nonZero printString , '          ' displayAt: 0 at 0.
- 	Display border: (r expandBy: 2) width: 2 rule: Form reverse fillColor: nil]]
- "!

Item was removed:
- ----- Method: Form>>trimBordersOfColor: (in category 'image manipulation') -----
- trimBordersOfColor: aColor
- 	"Answer a copy of this Form with each edge trimmed in to the first pixel that is not of the given color. (That is, border strips of the given color are removed)."
- 
- 	| r |
- 	r := self rectangleEnclosingPixelsNotOfColor: aColor.
- 	^ self copy: r
- !

Item was removed:
- ----- Method: Form>>unhibernate (in category 'fileIn/Out') -----
- unhibernate
- 	"If my bitmap has been compressed into a ByteArray,
- 	then expand it now, and return true."
- 	| resBits |
- 	bits isForm ifTrue:[
- 		resBits := bits.
- 		bits := Bitmap new: self bitsSize.
- 		resBits displayResourceFormOn: self.
- 		^true].
- 	bits == nil ifTrue:[bits := Bitmap new: self bitsSize. ^true].
- 	(bits isMemberOf: ByteArray)
- 		ifTrue: [bits := Bitmap decompressFromByteArray: bits. ^ true].
- 	^ false!

Item was removed:
- ----- Method: Form>>veryDeepCopyWith: (in category 'copying') -----
- veryDeepCopyWith: deepCopier
- 	"Return self.  I am immutable in the Morphic world.  Do not record me."
- 	^ self!

Item was removed:
- ----- Method: Form>>width (in category 'display box access') -----
- width
- 	^ width!

Item was removed:
- ----- Method: Form>>wipeImage:at:clippingBox:rectForIndex: (in category 'transitions') -----
- wipeImage: otherImage at: topLeft clippingBox: clipBox rectForIndex: rectForIndexBlock
- 
- 	| i clipRect t rectOrList waitTime |
- 	i := 0.
- 	clipRect := topLeft extent: otherImage extent.
- 	clipBox ifNotNil: [clipRect := clipRect intersect: clipBox].
- 	[rectOrList := rectForIndexBlock value: (i := i + 1).
- 	 rectOrList == nil]
- 		whileFalse: [
- 			t := Time millisecondClockValue.
- 			rectOrList asOrderedCollection do: [:r |
- 				self copyBits: r from: otherImage at: topLeft + r topLeft
- 					clippingBox: clipRect rule: Form over fillColor: nil].
- 			Display forceDisplayUpdate.
- 			waitTime := 3 - (Time millisecondClockValue - t).
- 			waitTime > 0 ifTrue:
- 				["(Delay forMilliseconds: waitTime) wait"]].
- !

Item was removed:
- ----- Method: Form>>wipeImage:at:delta: (in category 'transitions') -----
- wipeImage: otherImage at: topLeft delta: delta
- 	"Display wipeImage: (Form fromDisplay: (40 at 40 extent: 300 at 300)) reverse
- 		at: 40 at 40 delta: 0 at -2"
- 
- 	self wipeImage: otherImage at: topLeft delta: delta clippingBox: nil.
- !

Item was removed:
- ----- Method: Form>>wipeImage:at:delta:clippingBox: (in category 'transitions') -----
- wipeImage: otherImage at: topLeft delta: delta clippingBox: clipBox
- 
- 	| wipeRect bb nSteps |
- 	bb := otherImage boundingBox.
- 	wipeRect := delta x = 0
- 		ifTrue:
- 		[delta y = 0 ifTrue: [nSteps := 1. bb "allow 0 at 0"] ifFalse: [
- 		nSteps := bb height//delta y abs + 1.  "Vertical movement"
- 		delta y > 0
- 			ifTrue: [bb topLeft extent: bb width at delta y]
- 			ifFalse: [bb bottomLeft+delta extent: bb width at delta y negated]]]
- 		ifFalse:
- 		[nSteps := bb width//delta x abs + 1.  "Horizontal movement"
- 		delta x > 0
- 			ifTrue: [bb topLeft extent: delta x at bb height]
- 			ifFalse: [bb topRight+delta extent: delta x negated at bb height]].
- 	^ self wipeImage: otherImage at: topLeft clippingBox: clipBox rectForIndex:
- 		[:i | i <= nSteps
- 			ifTrue: [wipeRect translateBy: (delta* (i-1))]
- 			ifFalse: [nil]]!

Item was removed:
- ----- Method: Form>>writeAttributesOn: (in category 'fileIn/Out') -----
- writeAttributesOn: file
- 	self unhibernate.
- 	file nextPut: depth.
- 	file nextWordPut: width.
- 	file nextWordPut: height.
- 	file nextWordPut: ((self offset x) >=0
- 					ifTrue: [self offset x]
- 					ifFalse: [self offset x + 65536]).
- 	file nextWordPut: ((self offset y) >=0
- 					ifTrue: [self offset y]
- 					ifFalse: [self offset y + 65536]).
- 	!

Item was removed:
- ----- Method: Form>>writeBMPfileNamed: (in category 'fileIn/Out') -----
- writeBMPfileNamed: fName  "Display writeBMPfileNamed: 'display.bmp'"
- 	BMPReadWriter putForm: self onFileNamed: fName!

Item was removed:
- ----- Method: Form>>writeBitsOn: (in category 'fileIn/Out') -----
- writeBitsOn: file
- 	bits writeOn: file!

Item was removed:
- ----- Method: Form>>writeJPEGfileNamed: (in category 'fileIn/Out') -----
- writeJPEGfileNamed: fileName 
- 	"Write a JPEG file to the given filename using default settings"
- 
- 	self writeJPEGfileNamed: fileName progressive: false
- 
- "
- Display writeJPEGfileNamed: 'display.jpeg'
- Form fromUser writeJPEGfileNamed: 'yourPatch.jpeg'
- "!

Item was removed:
- ----- Method: Form>>writeJPEGfileNamed:progressive: (in category 'fileIn/Out') -----
- writeJPEGfileNamed: fileName  progressive: aBoolean
- 	"Write a JPEG file to the given filename using default settings.  Make it progressive or not, depending on the boolean argument"
- 
- 	JPEGReadWriter2 putForm: self quality: -1 "default" progressiveJPEG: aBoolean onFileNamed: fileName
- 
- "
- Display writeJPEGfileNamed: 'display.jpeg' progressive: false.
- Form fromUser writeJPEGfileNamed: 'yourPatch.jpeg' progressive: true
- "!

Item was removed:
- ----- Method: Form>>writeOn: (in category 'fileIn/Out') -----
- writeOn: file
- 	"Write the receiver on the file in the format
- 		depth, extent, offset, bits."
- 	self writeAttributesOn: file.
- 	self writeBitsOn: file!

Item was removed:
- ----- Method: Form>>writeOnMovie: (in category 'fileIn/Out') -----
- writeOnMovie: file
- 	"Write just my bits on the file."
- 	self unhibernate.
- 	bits writeUncompressedOn: file!

Item was removed:
- ----- Method: Form>>writePNGfileNamed: (in category 'fileIn/Out') -----
- writePNGfileNamed: fName  "Display writePNGfileNamed: 'display.png'"
- 	PNGReadWriter putForm: self onFileNamed: fName!

Item was removed:
- ----- Method: Form>>writeUncompressedOn: (in category 'fileIn/Out') -----
- writeUncompressedOn: file
- 	"Write the receiver on the file in the format depth, extent, offset, bits.  Warning:  Caller must put header info on file!!  Use writeUncompressedOnFileNamed: instead."
- 	self unhibernate.
- 	file binary.
- 	file nextPut: depth.
- 	file nextWordPut: width.
- 	file nextWordPut: height.
- 	file nextWordPut: ((self offset x) >=0
- 					ifTrue: [self offset x]
- 					ifFalse: [self offset x + 65536]).
- 	file nextWordPut: ((self offset y) >=0
- 					ifTrue: [self offset y]
- 					ifFalse: [self offset y + 65536]).
- 	bits writeUncompressedOn: file!

Item was removed:
- ----- Method: Form>>xTallyPixelValue:orNot: (in category 'analyzing') -----
- xTallyPixelValue: pv orNot: not
- 	"Return an array of the number of pixels with value pv by x-value.
- 	Note that if not is true, then this will tally those different from pv."
- 	| cm slice countBlt copyBlt |
- 	cm := self newColorMap.		"Map all colors but pv to zero"
- 	not ifTrue: [cm atAllPut: 1].		"... or all but pv to one"
- 	cm at: pv+1 put: 1 - (cm at: pv+1).
- 	slice := Form extent: 1 at height.
- 	copyBlt := (BitBlt destForm: slice sourceForm: self
- 				halftoneForm: nil combinationRule: Form over
- 				destOrigin: 0 at 0 sourceOrigin: 0 at 0 extent: 1 @ slice height
- 				clipRect: slice boundingBox) colorMap: cm.
- 	countBlt := (BitBlt toForm: slice)
- 				fillColor: (Bitmap with: 0);
- 				destRect: (0 at 0 extent: slice extent);
- 				combinationRule: 32.
- 	^ (0 to: width-1) collect:
- 		[:x |
- 		copyBlt sourceOrigin: x at 0; copyBits.
- 		countBlt copyBits]!

Item was removed:
- ----- Method: Form>>yTallyPixelValue:orNot: (in category 'analyzing') -----
- yTallyPixelValue: pv orNot: not
- 	"Return an array of the number of pixels with value pv by y-value.
- 	Note that if not is true, then this will tally those different from pv."
- 	| cm slice copyBlt countBlt |
- 	cm := self newColorMap.		"Map all colors but pv to zero"
- 	not ifTrue: [cm atAllPut: 1].		"... or all but pv to one"
- 	cm at: pv+1 put: 1 - (cm at: pv+1).
- 	slice := Form extent: width at 1.
- 	copyBlt := (BitBlt destForm: slice sourceForm: self
- 				halftoneForm: nil combinationRule: Form over
- 				destOrigin: 0 at 0 sourceOrigin: 0 at 0 extent: slice width @ 1
- 				clipRect: slice boundingBox) colorMap: cm.
- 	countBlt := (BitBlt toForm: slice)
- 				fillColor: (Bitmap with: 0);
- 				destRect: (0 at 0 extent: slice extent);
- 				combinationRule: 32.
- 	^ (0 to: height-1) collect:
- 		[:y |
- 		copyBlt sourceOrigin: 0 at y; copyBits.
- 		countBlt copyBits]!

Item was removed:
- ----- Method: Form>>zoomIn:orOutTo:at:vanishingPoint: (in category 'transitions') -----
- zoomIn: goingIn orOutTo: otherImage at: topLeft vanishingPoint: vp 
- 	"Display zoomInTo: (Form fromDisplay: (40 at 40 extent: 300 at 300)) reverse at: 40 at 40.
- 	Display zoomOutTo: (Form fromDisplay: (40 at 40 extent: 300 at 300)) reverse at: 40 at 40."
- 	| nSteps minTime startTime |
- 	nSteps := 16.
- 	minTime := 500.  "milliseconds"
- 	startTime := Time millisecondClockValue.
- 	^ self wipeImage: otherImage at: topLeft clippingBox: nil rectForIndex:
- 		[:i | | lead bigR j lilR | "i runs from 1 to nsteps"
- 		i > nSteps
- 			ifTrue: [nil "indicates all done"]
- 			ifFalse:
- 			["If we are going too fast, delay for a bit"
- 			lead := startTime + (i-1*minTime//nSteps) - Time millisecondClockValue.
- 			lead > 10 ifTrue: [(Delay forMilliseconds: lead) wait].
- 
- 			"Return an array with the difference rectangles for this step."
- 			j := goingIn ifTrue: [i] ifFalse: [nSteps+1-i].
- 			bigR := vp - (vp*(j)//nSteps) corner:
- 				vp + (otherImage extent-vp*(j)//nSteps).
- 			lilR := vp - (vp*(j-1)//nSteps) corner:
- 				vp + (otherImage extent-vp*(j-1)//nSteps).
- 			bigR areasOutside: lilR]]!

Item was removed:
- ----- Method: Form>>zoomInTo:at: (in category 'transitions') -----
- zoomInTo: otherImage at: topLeft
- 	"Display zoomInTo: (Form fromDisplay: (40 at 40 extent: 300 at 300)) reverse at: 40 at 40"
- 	^ self zoomIn: true orOutTo: otherImage at: topLeft
- 		vanishingPoint: otherImage extent//2+topLeft!

Item was removed:
- ----- Method: Form>>zoomOutTo:at: (in category 'transitions') -----
- zoomOutTo: otherImage at: topLeft
- 	"Display zoomOutTo: (Form fromDisplay: (40 at 40 extent: 300 at 300)) reverse at: 40 at 40"
- 	^ self zoomIn: false orOutTo: otherImage at: topLeft
- 		vanishingPoint: otherImage extent//2+topLeft!

Item was removed:
- StrikeFont subclass: #FormSetFont
- 	instanceVariableNames: 'tintable combinationRule'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Fonts'!
- 
- !FormSetFont commentStamp: 'ct 2/14/2020 16:49' prior: 0!
- FormSetFonts are designed to capture individual images as character forms for imbedding in normal text.  While most often used to insert an isolated glyph in some text, the code is actually designed to support an entire user-defined font.  The TextAttribute subclass TextFontReference is specifically designed for such in-line insertion of exceptional fonts in normal text.!

Item was removed:
- ----- Method: FormSetFont class>>copy:toClipBoardAs:ascent: (in category 'examples') -----
- copy: charForm toClipBoardAs: char ascent: ascent
- 	Clipboard clipboardText:
- 		(Text string: char asString
- 			attribute: (TextFontReference toFont: 
- 				(FormSetFont new
- 					fromFormArray: (Array with: charForm)
- 					asciiStart: char asciiValue
- 					ascent: ascent)))
- "
- 	The S in the Squeak welcome window was installed by doing the following
- 	in a workspace (where the value of, eg, charForm will persist through BitEdit...
- 	f := TextStyle default fontAt: 4.
- 	oldS := f characterFormAt: $S.
- 	charForm := Form extent: oldS extent depth: 8.
- 	oldS displayOn: charForm.
- 	charForm bitEdit.
- 	...Play around with the BitEditor, then accept and close...
- 	FormSetFont copy: charForm toClipBoardAs: $S ascent: f ascent.
- 	...Then do a paste into the Welcome window
- "!

Item was removed:
- ----- Method: FormSetFont class>>example (in category 'examples') -----
- example    "FormSetFont example"
- 	"Lets the user select a (small) area of the screen to represent the
- 	character A, then copies 'A' to the clipboard with that as the letter form.
- 	Thereafter, a paste operation will imbed that character in any text."
- 	| charForm |
- 	charForm := Form fromUser.
- 	self copy: charForm toClipBoardAs: $A ascent: charForm height!

Item was removed:
- ----- Method: FormSetFont>>combinationRule (in category 'accessing') -----
- combinationRule
- 
- 	^ combinationRule!

Item was removed:
- ----- Method: FormSetFont>>combinationRule: (in category 'accessing') -----
- combinationRule: anObject
- 
- 	combinationRule := anObject!

Item was removed:
- ----- Method: FormSetFont>>displayString:on:from:to:at:kern: (in category 'displaying') -----
- displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta
- 	"Draw the given string from startIndex to stopIndex "
- 
- 	combinationRule ifNotNil: [:r | aBitBlt combinationRule: r].
- 	tintable == false ifTrue: [aBitBlt colorMap: nil].
- 	
- 	^ super displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta!

Item was removed:
- ----- Method: FormSetFont>>fromFormArray:asciiStart:ascent: (in category 'initialize-release') -----
- fromFormArray: formArray asciiStart: asciiStart ascent: ascentVal
- 	| height width x badChar |
- 	type := 2.
- 	name := 'aFormFont'.
- 	minAscii := asciiStart.
- 	maxAscii := minAscii + formArray size - 1.
- 	ascent := ascentVal.
- 	subscript := superscript := emphasis := 0.
- 	height := width := 0.
- 	maxWidth := 0.
- 	formArray do:
- 		[:f | width := width + f width.
- 		maxWidth := maxWidth max: f width.
- 		height := height max: f height + f offset y].
- 	badChar := (Form extent: 7 at height) borderWidth: 1.
- 	width := width + badChar width.
- 	descent := height - ascent.
- 	pointSize := height.
- 	glyphs := Form extent: width @ height depth: formArray first depth.
- 	xTable := Array new: maxAscii + 3 withAll: 0.
- 	x := 0.
- 	formArray withIndexDo:
- 		[:f :i | f displayOn: glyphs at: x at 0.
- 		xTable at: minAscii + i+1 put: (x := x + f width)].
- 	badChar displayOn: glyphs at: x at 0.
- 	xTable at: maxAscii + 3 put: x + badChar width.
- 	characterToGlyphMap := nil.!

Item was removed:
- ----- Method: FormSetFont>>initialize (in category 'initialize-release') -----
- initialize
- 
- 	super initialize.
- 	self preserveColors.!

Item was removed:
- ----- Method: FormSetFont>>makeTintable (in category 'tinting') -----
- makeTintable
- 	"Default."
- 	
- 	self tintable: true.
- 	self combinationRule: Form over.!

Item was removed:
- ----- Method: FormSetFont>>preserveColors (in category 'tinting') -----
- preserveColors
- 
- 	self tintable: false.
- 	self combinationRule: Form paint.!

Item was removed:
- ----- Method: FormSetFont>>preserveColorsWithAlpha (in category 'tinting') -----
- preserveColorsWithAlpha
- 	"Useful for rendering Emojis."
- 	
- 	self tintable: false.
- 	self combinationRule: Form blend.!

Item was removed:
- ----- Method: FormSetFont>>reset (in category 'emphasis') -----
- reset  "Ignored by FormSetFonts"!

Item was removed:
- ----- Method: FormSetFont>>tintable (in category 'accessing') -----
- tintable
- 
- 	^ tintable!

Item was removed:
- ----- Method: FormSetFont>>tintable: (in category 'accessing') -----
- tintable: anObject
- 
- 	tintable := anObject!

Item was removed:
- Form subclass: #FormStub
- 	instanceVariableNames: 'locator'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Display Objects'!

Item was removed:
- ----- Method: FormStub>>locator (in category 'accessing') -----
- locator
- 	^locator!

Item was removed:
- ----- Method: FormStub>>locator: (in category 'accessing') -----
- locator: aString
- 	locator := aString!

Item was removed:
- ----- Method: FormStub>>objectForDataStream: (in category 'fileIn/Out') -----
- objectForDataStream: refStream
- 	"Force me into outPointers so that I get notified about startup"
- 	refStream replace: self with: self.
- 	^self!

Item was removed:
- ImageReadWriter subclass: #GIFReadWriter
- 	instanceVariableNames: 'width height bitsPerPixel colorPalette rowByteSize xpos ypos pass interlace transparentIndex localColorTable loopCount offset frames canvasWidth canvasHeight backgroundColorIndex comment'
- 	classVariableNames: 'Extension ImageSeparator Terminator'
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!
- 
- !GIFReadWriter commentStamp: 'ct 6/10/2022 13:02' prior: 0!
- I am GIFReadWriter.
- I am a concrete ImageReadWriter.
- 
- Updated implementation of a GIF file (byte-level) decoder.
- 
- I implement a Stream-like behavior over a GIF image file, and can both read and write GIF files.
- 
- Previously, two classes distinguished between "still" and "animated" GIFs. However, the standard specifies that any GIF can have "frames" and be animated. This reimplementation treats this as normal.
- 
- See these links for more detailed information:
-  
-  https://www.w3.org/Graphics/GIF/spec-gif89a.txt
-  https://en.wikipedia.org/wiki/GIF
-  http://www.matthewflickinger.com/lab/whatsinagif/bits_and_bytes.asp
- 
- For writing GIF files, I take a collection of AnimatedImageFrame objects and write the appropriate headers, Graphics Control Extensions, and everything else needed for writing an animated GIF.
- 
- For reading GIF files, I take a binary filestream and set my own `frames` variable to be a collection of AnimatedImageFrames, which themselves contain decoded Forms and instructions for disposal, delay, etc.
- 
- NOTE: I make use of the LzwGifDecoder and LzwGifEncoder classes in order to encode/decode individual bitmap data for each image frame of the GIF.
- 
- See `GIFReadWriter exampleAnim` for more information.  !

Item was removed:
- ----- Method: GIFReadWriter class>>exampleAnim (in category 'examples') -----
- exampleAnim
- 	"This example writes out an animated gif of
- 	 a red circle"
- 
- 	| writer extent center frameDelay |
- 	writer := GIFReadWriter on: (FileStream fileNamed: 'anim.gif').
- 	writer loopCount: 20.		"Repeat 20 times"
- 	frameDelay := 10.		"Wait 10/100 seconds"
- 	extent := 42 at 42.
- 	center := extent / 2.
- 	Cursor write showWhile: [
- 		[2 to: center x - 1 by: 2 do: [:r |
- 			"Make a fancy anim without using Canvas - inefficient as hell"
- 			| frame |
- 			frame := AnimatedImageFrame new
- 				delay: frameDelay;
- 				form: (ColorForm extent: extent depth: 8).
- 			0.0 to: 359.0 do: [:theta | frame form colorAt: (center + (Point r: r degrees: theta)) rounded put: Color red].
- 			writer nextPutFrame: frame ]
- 		]	ensure: [writer close]].!

Item was removed:
- ----- Method: GIFReadWriter class>>formsFromFileNamed: (in category 'image reading/writing') -----
- formsFromFileNamed: aFile
- 	^ (self on: aFile asDirectoryEntry readStream binary)
- 			readHeader;
- 			readBody;
- 			yourself!

Item was removed:
- ----- Method: GIFReadWriter class>>formsFromStream: (in category 'image reading/writing') -----
- formsFromStream: aBinaryStream
- 	^ (self on: aBinaryStream)
- 		readHeader;
- 		readBody;
- 		yourself!

Item was removed:
- ----- Method: GIFReadWriter class>>grabScreenAndSaveOnDisk (in category 'examples') -----
- grabScreenAndSaveOnDisk
- 	"GIFReadWriter grabScreenAndSaveOnDisk"
- 
- 	| form fileName |
- 	form := Form fromUser.
- 	form bits size = 0 ifTrue: [^Beeper beep].
- 	fileName := FileDirectory default nextNameFor: 'Squeak' extension: 'gif'.
- 	Project uiManager
- 		informUser: ('Writing {1}' translated format: {fileName})
- 		during: [GIFReadWriter putForm: form onFileNamed: fileName].!

Item was removed:
- ----- Method: GIFReadWriter class>>initialize (in category 'initialization') -----
- initialize
- 	"GIFReadWriter initialize"
- 	ImageSeparator := $, asInteger.
- 	Extension := $!! asInteger.
- 	Terminator := $; asInteger!

Item was removed:
- ----- Method: GIFReadWriter class>>typicalFileExtensions (in category 'image reading/writing') -----
- typicalFileExtensions
- 	"Answer a collection of file extensions (lowercase) which files that I can 
- 	read might commonly have"
- 
- 	^ self allSubclasses
- 		detect: [ :cls | cls wantsToHandleGIFs ]
- 		ifFound: [ #() ]
- 		ifNone: [ 
- 			"if none of my subclasses wants , then i''ll have to do"
- 			#('gif') ]!

Item was removed:
- ----- Method: GIFReadWriter class>>wantsToHandleGIFs (in category 'image reading/writing') -----
- wantsToHandleGIFs
- 	^ true!

Item was removed:
- ----- Method: GIFReadWriter>>backgroundColor (in category 'accessing') -----
- backgroundColor
- 	backgroundColorIndex ifNotNil: [ 
- 		colorPalette ifNotNil: [ 
- 			^ colorPalette at: backgroundColorIndex + 1]].
- 	^ Color transparent.!

Item was removed:
- ----- Method: GIFReadWriter>>canvasHeight (in category 'accessing') -----
- canvasHeight
- 	^ canvasHeight!

Item was removed:
- ----- Method: GIFReadWriter>>canvasHeight: (in category 'accessing') -----
- canvasHeight: aNumber
- 	canvasHeight := aNumber!

Item was removed:
- ----- Method: GIFReadWriter>>canvasWidth (in category 'accessing') -----
- canvasWidth
- 	^ canvasWidth!

Item was removed:
- ----- Method: GIFReadWriter>>canvasWidth: (in category 'accessing') -----
- canvasWidth: aNumber
- 	canvasWidth := aNumber!

Item was removed:
- ----- Method: GIFReadWriter>>close (in category 'stream access') -----
- close
- 	"A read close"
- 	^super close!

Item was removed:
- ----- Method: GIFReadWriter>>delays (in category 'accessing') -----
- delays
- 	"Respond with an ordered collection of Frame delay values"
- 	^ frames collect: [ :frame | frame delay ]!

Item was removed:
- ----- Method: GIFReadWriter>>form (in category 'accessing') -----
- form
- 	"By default, answer with the first Form available in the
- 	ImageFrames collection. If there are not any frames, answer nil"
- 	frames ifNil: [ ^ nil ].
- 	frames ifEmpty: [ ^ nil ].
- 	^ frames first form.!

Item was removed:
- ----- Method: GIFReadWriter>>forms (in category 'accessing') -----
- forms
- 	frames ifNil: [ ^ nil ].
- 	^ frames collect: [ :f | f form ].!

Item was removed:
- ----- Method: GIFReadWriter>>frames (in category 'accessing') -----
- frames
- 	^ frames!

Item was removed:
- ----- Method: GIFReadWriter>>frames: (in category 'accessing') -----
- frames: aCollectionOfImageFrames
- 	"Set the receiver's underlying collection of
- 	ImageFrame objects. Used when attempting to write
- 	out GIF images"
- 	frames := aCollectionOfImageFrames!

Item was removed:
- ----- Method: GIFReadWriter>>isAnimated (in category 'testing') -----
- isAnimated
- 	frames ifNil: [ ^ false ].
- 	^ frames size > 1!

Item was removed:
- ----- Method: GIFReadWriter>>loopCount: (in category 'accessing') -----
- loopCount: aNumber
- 	"Set looping. This must be done before any image is written!!"
- 	loopCount := aNumber!

Item was removed:
- ----- Method: GIFReadWriter>>nextImage (in category 'accessing') -----
- nextImage
- 	"This method ensures older compatibility with ImageReadWriter.
- 	We respond with the Form corresponding to the *first image* on
- 	the receiver's read byte stream"
- 	self
- 		readHeader;
- 		readBody.
- 	^ self form.!

Item was removed:
- ----- Method: GIFReadWriter>>nextPutFrame: (in category 'accessing') -----
- nextPutFrame: anAnimatedImageFrame
- 	"Given the current settings, write the bytes onto the
- 	output stream for the given ImageFrame and its form"
- 	| aForm reduced tempForm tempFrame |
- 	
- 	aForm := anAnimatedImageFrame form copy.
- 	aForm unhibernate.
- 	aForm depth > 8 ifTrue:[
- 		reduced := aForm colorReduced.  "minimize depth"
- 		reduced depth > 8 ifTrue: [
- 			"Not enough color space; do it the hard way."
- 			reduced := reduced asFormOfDepth: 8].
- 	] ifFalse:[reduced := aForm].
- 	reduced depth < 8 ifTrue: [
- 		"writeBitData: expects depth of 8"
- 		tempForm := reduced class extent: reduced extent depth: 8.
- 		(reduced isColorForm) ifTrue:[
- 			tempForm
- 				copyBits: reduced boundingBox
- 				from: reduced at: 0 at 0
- 				clippingBox: reduced boundingBox
- 				rule: Form over
- 				fillColor: nil
- 				map: nil.
- 			tempForm colors: reduced colors.
- 		] ifFalse: [reduced displayOn: tempForm].
- 		reduced := tempForm.
- 	].
- 	(reduced isColorForm) ifTrue:[
- 		(reduced colorsUsed includes: Color transparent) ifTrue: [
- 			transparentIndex := (reduced colors indexOf: Color transparent) - 1.
- 		]
- 	] ifFalse: [transparentIndex := nil].
- 	width := reduced width.
- 	height := reduced height.
- 	bitsPerPixel := reduced depth.
- 	colorPalette := reduced colormapIfNeededForDepth: 32.
- 	interlace := false.
- 	tempFrame := AnimatedImageFrame new 
- 		form: reduced;
- 		offset: anAnimatedImageFrame offset;
- 		delay: anAnimatedImageFrame delay;
- 		disposal: anAnimatedImageFrame disposal.
- 	self writeHeader.
- 	self writeFrameHeader: tempFrame.
- 	self writeBitData: reduced bits.!

Item was removed:
- ----- Method: GIFReadWriter>>nextPutImage: (in category 'accessing') -----
- nextPutImage: aForm
- 	"Given the current settings, write the bytes onto the
- 	output stream for the given ImageFrame and its form"
- 	| reduced tempForm tempFrame |
- 	
- 	aForm unhibernate.
- 	aForm depth > 8 ifTrue:[
- 		reduced := aForm colorReduced.  "minimize depth"
- 		reduced depth > 8 ifTrue: [
- 			"Not enough color space; do it the hard way."
- 			reduced := reduced asFormOfDepth: 8].
- 	] ifFalse:[reduced := aForm].
- 	reduced depth < 8 ifTrue: [
- 		"writeBitData: expects depth of 8"
- 		tempForm := reduced class extent: reduced extent depth: 8.
- 		(reduced isColorForm) ifTrue:[
- 			tempForm
- 				copyBits: reduced boundingBox
- 				from: reduced at: 0 at 0
- 				clippingBox: reduced boundingBox
- 				rule: Form over
- 				fillColor: nil
- 				map: nil.
- 			tempForm colors: reduced colors.
- 		] ifFalse: [reduced displayOn: tempForm].
- 		reduced := tempForm.
- 	].
- 	(reduced isColorForm) ifTrue:[
- 		(reduced colorsUsed includes: Color transparent) ifTrue: [
- 			transparentIndex := (reduced colors indexOf: Color transparent) - 1.
- 		]
- 	] ifFalse: [transparentIndex := nil].
- 	width := reduced width.
- 	height := reduced height.
- 	bitsPerPixel := reduced depth.
- 	colorPalette := reduced colormapIfNeededForDepth: 32.
- 	interlace := false.
- 	tempFrame := AnimatedImageFrame new 
- 		form: reduced;
- 		offset: reduced offset.
- 	self writeHeader.
- 	self writeFrameHeader: tempFrame.
- 	self writeBitData: reduced bits.!

Item was removed:
- ----- Method: GIFReadWriter>>processColorsFor: (in category 'private - decoding') -----
- processColorsFor: anImageFrame
- 	"Colors can only be mapped after the GCE has been evaluated
- 	for a given image frame. We perform this action using either
- 	the local or global color table for this frame's form"
- 	| colorTable |
- 	colorTable := localColorTable ifNil: [ colorPalette ].
- 	
- 	"Use a copy so we don't mess up the global color table as we parse"
- 	colorTable := colorTable copyFrom: 1 to: colorTable size.
- 	
- 	transparentIndex 
- 		ifNotNil: [ 
- 			transparentIndex + 1 > colorTable size
- 				ifTrue: [ 
- 					colorTable := colorTable
- 										forceTo: transparentIndex + 1
- 										paddingWith: Color white ].
- 				colorTable
- 					at: transparentIndex + 1
- 					put: Color transparent ].
- 	anImageFrame form colors: colorTable.!

Item was removed:
- ----- Method: GIFReadWriter>>readApplicationExtension (in category 'private - decoding') -----
- readApplicationExtension
- 	"Uses the underlying stream to read a so-called
- 	Application Extension to the GIF Image. These extensions
- 	are at the whole file -- not individual frame like a GCE --
- 	level. It appears the only kind widely used is the NETSCAPE
- 	extension for determining the number of times an animated
- 	GIF should loop."
- 	| bytesFollow appName appAuthCode caughtInfo numSubBlocks loopVal1 loopVal2 |
- 	"How many bytes before data begins?
- 	Usually 11"
- 	bytesFollow := self next.
- 	appName := (String streamContents: [ :s |
- 		1 to: 8 do: [ :num |
- 			s
- 				nextPut: self next asCharacter ] ]).
- 	appAuthCode := (String streamContents: [ :s |
- 		1 to: 3 do: [ :num |
- 			s
- 				nextPut: self next asCharacter ] ]).
- 	caughtInfo := (appName size + appAuthCode size).
- 	caughtInfo = bytesFollow ifFalse: [ 
- 		(bytesFollow = caughtInfo) timesRepeat: [ 
- 			self next ] ].
- 	numSubBlocks := self next.
- 	appName = 'NETSCAPE' 
- 		ifTrue: [ 
- 			self next. "Data sub-block index (always 1)"
- 			"If it's the NETSCAPE extension, the next
- 			byte will set the loopCount. This is stored in
- 			a 2-byte lo-hi unsigned format"
- 			loopVal1 := self next.
- 			loopVal2 := self next.
- 			loopCount := (loopVal2 * 256) + loopVal1.
- 			self next = 0 ifFalse: [ ^ self error: 'Corrupt NETSCAPE Application Block' ].
- 			^ self ].
- 
- 	"For now we ignore Application Extensions
- 	that are not the NETSCAPE kind"
- 	[ numSubBlocks = 0 ] whileFalse: [ 
- 		self next: numSubBlocks.
- 		numSubBlocks := self next ].
- 	!

Item was removed:
- ----- Method: GIFReadWriter>>readBitDataOnFrame: (in category 'private - decoding') -----
- readBitDataOnFrame: aFrame
- 	"using modified Lempel-Ziv Welch algorithm."
- 	| initCodeSize  packedBits hasLocalColor localColorSize maxOutCodes decoder c  bytes |
- 	maxOutCodes := 4096.
- 	offset := self readWord @ self readWord.	"Image Left at Image Top"
- 	width := self readWord.
- 	height := self readWord.
- 	"---
- 	Local Color Table Flag        1 Bit
- 	Interlace Flag                1 Bit
- 	Sort Flag                     1 Bit
- 	Reserved                      2 Bits
- 	Size of Local Color Table     3 Bits
- 	----"
- 	packedBits := self next.
- 	interlace := (packedBits bitAnd: 64) ~= 0.
- 	aFrame interlace: interlace.
- 	hasLocalColor := (packedBits bitAnd: 128) ~= 0.
- 	localColorSize := 1 bitShift: (packedBits bitAnd: 7) + 1.
- 	hasLocalColor 
- 		ifTrue: [ 
- 			localColorTable := self readColorTable: localColorSize ]
- 		ifFalse: [ localColorTable := nil ].
- 	pass := 0.
- 	xpos := 0.
- 	ypos := 0.
- 	rowByteSize := (width + 3) // 4 * 4.
- 	bytes := (ByteArray new: rowByteSize * height).
- 
- 	initCodeSize := self next.
- 
- 	c := ColorForm 
- 		extent: width at height
- 		depth: 8. 
- 
- 	decoder := LzwGifDecoder new.
- 	decoder 
- 		codeStream: stream;
- 		minimumCodeSize: initCodeSize;
- 		maxCode: maxOutCodes;
- 		onDecodedBit: [ :bit |
- 			bytes
- 				at: (ypos * rowByteSize + xpos + 1)
- 				put: bit.
- 			self updatePixelPosition ].
- 	decoder decode.
- 	c bits copyFromByteArray: bytes.
- 	^ c!

Item was removed:
- ----- Method: GIFReadWriter>>readBody (in category 'private - decoding') -----
- readBody
- 	"Read the GIF blocks. Modified to return a frame."
- 	| block frame |
- 	frame := nil.
- 	frames := OrderedCollection new.
- 	[ stream atEnd ] whileFalse: [ 
- 		block := self next.
- 		
- 		"If we have reached the terminator byte, return."
- 		block = Terminator ifTrue: [ ^ frame ].
- 		block = ImageSeparator 
- 			ifTrue: [ 
- 				frame ifNil: [ frame := AnimatedImageFrame new ].
- 				frame form: (self readBitDataOnFrame: frame). "Adjusting message for testing"
- 				frame offset: offset. "Set from instance var, which is set in readBitData"
- 				frame form offset: offset. "Set the offset on the underlying Form as well"
- 				
- 				frames add: frame.
- 				self processColorsFor: frame.
- 				frame := nil. ]
- 			ifFalse: 
- 				[ "If it's not actual image data, perhaps
- 					it's an Extension of some kind (there can be several)"
- 					block = Extension 
- 						ifTrue: [ 
- 							frame ifNil: [ frame := AnimatedImageFrame new ].
- 							self readExtensionBlock: block withFrame: frame ]
- 						ifFalse: [ ^ self error: 'Unknown Bytes!!' ] ] 
- 		].
- 	^ frames.!

Item was removed:
- ----- Method: GIFReadWriter>>readColorTable: (in category 'private - decoding') -----
- readColorTable: numberOfEntries 
- 	| array r g b |
- 	array := Array new: numberOfEntries.
- 	1 
- 		to: array size
- 		do: 
- 			[ :i | 
- 			r := self next.
- 			g := self next.
- 			b := self next.
- 			array 
- 				at: i
- 				put: (Color 
- 						r: r
- 						g: g
- 						b: b
- 						range: 255) ].
- 	^ array!

Item was removed:
- ----- Method: GIFReadWriter>>readCommentExtension (in category 'private - decoding') -----
- readCommentExtension
- 	| blockTerminator |
- 	blockTerminator := self next.
- 	blockTerminator > 0
- 		ifTrue: [ comment := self next: blockTerminator.
- 			blockTerminator := self next ].
- 	blockTerminator = 0
- 		ifFalse: [ ^ self error: 'Invalid Block Terminator' ]!

Item was removed:
- ----- Method: GIFReadWriter>>readDisposal: (in category 'private - decoding') -----
- readDisposal: aPackedByte
- 	"Read the three-bit disposal flag from
- 	the packed byte in the Graphic Control Extension block.
- 	Disposal is three-bits with the following codes:
- 	 |0 0 0 [0 0 0] 0 0|
- 	1 => leave current frame and draw on top of it (#leaveCurrent)
- 	2 => Restore to background color (#restoreBackground)
- 	3 => Restore to state before current frame was drawn (#restorePrevState)"
- 	| least middle both |
- 	(both := (aPackedByte bitAnd: 12) = 12).
- 	both ifTrue: [ ^ #restorePrevState ].
- 	
- 	least := (aPackedByte bitAnd: 4) = 4.
- 	least ifTrue: [ ^ #leaveCurrent ].
- 	
- 	middle := (aPackedByte bitAnd: 8) = 8.
- 	middle ifTrue: [ ^ #restoreBackground ].
- 	
- 	^ #otherDisposal
- 	!

Item was removed:
- ----- Method: GIFReadWriter>>readExtensionBlock:withFrame: (in category 'private - decoding') -----
- readExtensionBlock: aGifBlock withFrame: anImageFrame
- 	"Determine which type of extension block we are
- 	looking at. The most common is the Graphic Control Extension (GCE)
- 	which tells us information about the image frame, including delays
- 	offsets in the canvas, and how to dispose of the frame in animation"
- 	| extensionType packedByte delayByte1 delayByte2 |
- 	extensionType := self next.
- 	
- 	"255 is an Application Extension.
- 	 This seems to always be the NETSCAPE
- 	 extension, which has looping information.
- 	This extension does not affect individual frames,
- 	but rather sets the loopCount for the whole image"
- 	extensionType = 255 ifTrue: [ 
- 		^ self readApplicationExtension ].
- 	
- 	
- 	"249 Corresponds to the GCE"
- 	extensionType = 249 ifTrue: [ 
- 		self next = 4 ifFalse: [ ^ self "The GIF is likely corrupt in this case" ].
- 		"====
- 		Reserved                      3 Bits (Ignore)
- 		Disposal Method               3 Bits 
- 		User Input Flag               1 Bit  (Ignore)
- 		Transparent Color Flag        1 Bit  (Need to Implement)
- 		==="
- 		packedByte := self next.
- 		delayByte1 := self next.
- 		delayByte2 := self next.
- 		transparentIndex := self next.
- 		(packedByte bitAnd: 1) = 0 "Changed to see if other endian is the real end..."
- 			ifTrue: [ transparentIndex := nil ].
- 		anImageFrame 
- 			disposal: (self readDisposal: packedByte);
- 			"Delay time is stored as 2 bytes unsigned"
- 			delay: (delayByte2 * 256 + delayByte1) * 10.
- 		self next = 0 ifFalse: [ ^ self error: 'Corrupt GCE Block!!' ].
- 		^ self ].
- 
- 	extensionType = 254 ifTrue: [ 
- 		^ self readCommentExtension ].
- 
- 	"If you get to this point, we don't know the Extension Type"
- 	^ self error: 'Unknown GIF Extension: ',(extensionType asString).!

Item was removed:
- ----- Method: GIFReadWriter>>readHeader (in category 'private - decoding') -----
- readHeader
- 	| is89 byte hasColorMap |
- 	(self hasMagicNumber: 'GIF87a' asByteArray) 
- 		ifTrue: [ is89 := false ]
- 		ifFalse: 
- 			[ (self hasMagicNumber: 'GIF89a' asByteArray) 
- 				ifTrue: [ is89 := true ]
- 				ifFalse: [ ^ self error: 'This does not appear to be a GIF file' translated ] ].
- 	"Width and Height for whole canvas, not
- 	just an invididual frame/form"
- 	canvasWidth := self readWord.
- 	canvasHeight := self readWord.
- 	byte := self next.
- 	hasColorMap := (byte bitAnd: 128) ~= 0.
- 	bitsPerPixel := (byte bitAnd: 7) + 1.
- 	backgroundColorIndex := self next.
- 	self next ~= 0 ifTrue: 
- 		[ is89 ifFalse: [ ^ self error: 'corrupt GIF file (screen descriptor)' ] ].
- 	hasColorMap 
- 		ifTrue: [ colorPalette := self readColorTable: (1 bitShift: bitsPerPixel) ]
- 		ifFalse: 
- 			[ colorPalette := nil	"Palette monochromeDefault" ]!

Item was removed:
- ----- Method: GIFReadWriter>>readPixelFrom: (in category 'private-encoding') -----
- readPixelFrom: bits
- 	"Since bits is a Bitmap with 32 bit values, watch out for the
- padding at the end of each row.  But, GIF format already wants padding to
- 32 bit boundary!!  OK as is.  tk 9/14/97"
- 
- 	| pixel |
- 	ypos >= height ifTrue: [^nil].
- 	pixel := bits byteAt: (ypos * rowByteSize + xpos + 1).
- 	self updatePixelPosition.
- 	^pixel!

Item was removed:
- ----- Method: GIFReadWriter>>readWord (in category 'private - decoding') -----
- readWord
- 	^self next + (self next bitShift: 8)!

Item was removed:
- ----- Method: GIFReadWriter>>setStream: (in category 'accessing') -----
- setStream: aStream 
- 	"Feed it in from an existing source"
- 	stream := aStream!

Item was removed:
- ----- Method: GIFReadWriter>>understandsImageFormat (in category 'accessing') -----
- understandsImageFormat
- 	^('abc' collect: [:x | stream next asCharacter]) = 'GIF'!

Item was removed:
- ----- Method: GIFReadWriter>>updatePixelPosition (in category 'private') -----
- updatePixelPosition
- 	(xpos := xpos + 1) >= width ifFalse: [ ^ self ].
- 	xpos := 0.
- 	interlace ifFalse: 
- 		[ ypos := ypos + 1.
- 		^ self ].
- 	pass = 0 ifTrue: 
- 		[ (ypos := ypos + 8) >= height ifTrue: 
- 			[ pass := pass + 1.
- 			ypos := 4 ].
- 		^ self ].
- 	pass = 1 ifTrue: 
- 		[ (ypos := ypos + 8) >= height ifTrue: 
- 			[ pass := pass + 1.
- 			ypos := 2 ].
- 		^ self ].
- 	pass = 2 ifTrue: 
- 		[ (ypos := ypos + 4) >= height ifTrue: 
- 			[ pass := pass + 1.
- 			ypos := 1 ].
- 		^ self ].
- 	pass = 3 ifTrue: 
- 		[ ypos := ypos + 2.
- 		^ self ].
- 	^ self caseError!

Item was removed:
- ----- Method: GIFReadWriter>>writeBitData: (in category 'private - encoding') -----
- writeBitData: bits 
- 	"using modified Lempel-Ziv Welch algorithm."
- 	| encoder initCodeSize |
- 	encoder := LzwGifEncoder new
- 		rowByteSize: (width * 8 + 31) // 32 * 4;
- 		extent: width at height;
- 		codeStream: stream.
- 	initCodeSize := bitsPerPixel <= 1 
- 		ifTrue: [ 2 ]
- 		ifFalse: [ bitsPerPixel ].
- 	encoder minimumCodeSize: initCodeSize.
- 	encoder encode: bits.!

Item was removed:
- ----- Method: GIFReadWriter>>writeDisposal:toPackedByte: (in category 'writing') -----
- writeDisposal: aSymbol toPackedByte: aByte
- 	"Using the GIF Graphics Control Extension
- 	packed byte format, respond with a modified version
- 	of the passed byte that includes the correct 3-bit
- 	disposal code corresponding to the passed in symbol"
- 	
- 	aSymbol = #restoreBackground
- 		ifTrue: [ 
- 			"This is a value of 2 in the 3-bit structure,
- 			so 010, then shifted two to the left (equal to 8)"
- 			^ aByte + (2 bitShift: 2) ].
- 	
- 	aSymbol = #leaveCurrent
- 		ifTrue: [ 
- 			"This is a value of 1 in the 3-bit structure,
- 			so 001, then shifted two to the left (equal to 4)"
- 			^ aByte + (1 bitShift: 2) ].
- 	
- 	aSymbol = #restorePrevState
- 		ifTrue: [ 
- 			"This is a value of 3 in the 3-bit structure,
- 			so 011, then shifted two to the left (equal to 12)"
- 			^ aByte + (3 bitShift: 2) ].
- 	^ aByte
- 		!

Item was removed:
- ----- Method: GIFReadWriter>>writeFrameHeader: (in category 'accessing') -----
- writeFrameHeader: anImageFrame
- 	"Write any Extensions and/or headers that apply
- 	to individual frames/subimages"
- 	| interlaceByte |
- 	anImageFrame delay notNil | transparentIndex notNil ifTrue: [ 
- 		self writeGCEForFrame: anImageFrame ].
- 	
- 	"Next is the image descriptor"
- 	self 
- 		nextPut: ImageSeparator;
- 		writeWord: (anImageFrame offset x);
- 		writeWord: (anImageFrame offset y);
- 		writeWord: (anImageFrame form extent x);
- 		writeWord: (anImageFrame form extent y).
- 	
- 	interlaceByte := interlace
- 		ifTrue: [ 64 ]
- 		ifFalse: [ 0 ].
- 	self nextPut: interlaceByte
- 	!

Item was removed:
- ----- Method: GIFReadWriter>>writeGCEForFrame: (in category 'private - encoding') -----
- writeGCEForFrame: anAnimatedImageFrame
- 	"Writes a Graphics Control Extension onto
- 	the output stream for the given image frame"
- 	| nextDelay packedByte |
- 	nextDelay := anAnimatedImageFrame delay.
- 	anAnimatedImageFrame delay ifNil: [ nextDelay := 0 ].
- 	"Set the bits of the packed byte"
- 	"====
- 		Reserved                      3 Bits (Ignore)
- 		Disposal Method               3 Bits 
- 		User Input Flag               1 Bit  (Ignore)
- 		Transparent Color Flag        1 Bit 
- 		==="
- 	packedByte := 0.
- 	transparentIndex
- 		ifNotNil: [ packedByte := 1 ].
- 	packedByte := self 
- 		writeDisposal: (anAnimatedImageFrame disposal)
- 		toPackedByte: packedByte.
- 	
- 	self 
- 		nextPut: Extension;
- 		nextPutAll: #(249 4) asByteArray;
- 		nextPut: packedByte;
- 		"nextPut: (transparentIndex
- 				ifNil: [ 0 ]
- 				ifNotNil: [ 9 ]);"
- 		writeWord: nextDelay // 10;
- 		nextPut: (transparentIndex ifNil: [ 0 ]);
- 		nextPut: 0.!

Item was removed:
- ----- Method: GIFReadWriter>>writeHeader (in category 'private - encoding') -----
- writeHeader
- 	| byte |
- 	"Write the overall image file header onto the
- 	output stream. This includes the global information
- 	about the file, such as canvasWidth etc. Only do so
- 	if the stream is in the initial position."
- 	stream position = 0 ifFalse: [ ^ self ].
- 
- 	self nextPutAll: 'GIF89a' asByteArray.
- 	self writeWord: width.	"Screen Width"
- 	self writeWord: height.	"Screen Height"
- 	byte := 128.	"has color map"
- 	byte := byte bitOr: (bitsPerPixel - 1 bitShift: 5).	"color resolution"
- 	byte := byte bitOr: bitsPerPixel - 1.	"bits per pixel"
- 	self nextPut: byte.
- 	self nextPut: 0.	"background color."
- 	self nextPut: 0.	"reserved / unused 'pixel aspect ratio"
- 	colorPalette do: 
- 		[ :pixelValue | 
- 		self
- 			nextPut: ((pixelValue bitShift: -16) bitAnd: 255);
- 			nextPut: ((pixelValue bitShift: -8) bitAnd: 255);
- 			nextPut: (pixelValue bitAnd: 255) ].
- 	loopCount notNil ifTrue: 
- 		[ self writeNetscapeExtension ].!

Item was removed:
- ----- Method: GIFReadWriter>>writeNetscapeExtension (in category 'private - encoding') -----
- writeNetscapeExtension
- 	"Writes a GIF Application Extension corresponding
- 	to the NETSCAPE2.0 version, with specifies the loopCount."
- 	self
- 		nextPut: Extension;
- 		nextPut: 255; "Indicates Application Extension"
- 		nextPut: 11; "Indicates how many bytes follow, almost always 11"
- 		nextPutAll: ('NETSCAPE2.0' asByteArray);
- 		nextPut: 3;
- 		nextPut: 1;
- 		writeWord: (loopCount ifNil: [ 0 ]);
- 		nextPut: 0.!

Item was removed:
- ----- Method: GIFReadWriter>>writeWord: (in category 'private - encoding') -----
- writeWord: aWord
- 	self nextPut: (aWord bitAnd: 255).
- 	self nextPut: ((aWord bitShift: -8) bitAnd: 255).
- 	^aWord!

Item was removed:
- StrikeFont subclass: #HostFont
- 	instanceVariableNames: 'fullWidth kernPairs ranges'
- 	classVariableNames: 'IsoToSqueakMap'
- 	poolDictionaries: 'TextConstants'
- 	category: 'Graphics-Fonts'!

Item was removed:
- ----- Method: HostFont class>>defaultRanges (in category 'accessing') -----
- defaultRanges
- 
- 	^ Array with: (Array with: 0 with: 16r2AFF).
- !

Item was removed:
- ----- Method: HostFont class>>fontName:size:emphasis: (in category 'instance creation') -----
- fontName: fontName size: ptSize emphasis: emphasisCode
- 	"
- 		^HostFont fontName: (HostFont fontNameFromUser) size: 12 emphasis: 0.
- 	"
- 	^self new fontName: fontName size: ptSize emphasis: emphasisCode!

Item was removed:
- ----- Method: HostFont class>>fontName:size:emphasis:rangesArray: (in category 'instance creation') -----
- fontName: fontName size: ptSize emphasis: emphasisCode rangesArray: ranges
- 	"
- 		^HostFont fontName: (HostFont fontNameFromUser) size: 12 emphasis: 0.
- 	"
- 	^self new fontName: fontName size: ptSize emphasis: emphasisCode rangesArray: ranges!

Item was removed:
- ----- Method: HostFont class>>fontNameFromUser (in category 'accessing') -----
- fontNameFromUser
- 	"HostFont fontNameFromUser"
- 	| fontNames index labels |
- 	fontNames := self listFontNames sort.
- 	labels := WriteStream on: (String new: 100).
- 	fontNames do:[:fn| labels nextPutAll: fn] separatedBy:[labels cr].
- 	index := (UIManager default chooseFrom: (labels contents substrings) title: 'Choose your font').
- 	index = 0 ifTrue:[^nil].
- 	^fontNames at: index!

Item was removed:
- ----- Method: HostFont class>>initWin32 (in category 'system defaults') -----
- initWin32
- 	"HostFont initWin32"
- 	#(
- 			"Basic fonts"
- 			('Arial'				"menu/text serifless"
- 				(10 11 12 13 14 16 18 20 22 24 26 28 30 36 48 60 72 90))
- 			('Times New Roman'	"menu/text serifs"
- 				(10 11 12 13 14 16 18 20 22 24 26 28 30 36 48 60 72 90))
- 			('Courier New'			"menu/text fixed"
- 				(10 11 12 13 14 16 18 20 22 24 26 28 30 36 48 60 72 90))
- 			('Wingdings'			"deco"
- 				(10 11 12 13 14 16 18 20 22 24 26 28 30 36 48 60 72 90))
- 			('Symbol'				"deco"
- 				(10 11 12 13 14 16 18 20 22 24 26 28 30 36 48 60 72 90))
- 
- 			"Nice fonts"
- 			('Verdana'			"menu/text serifless"
- 				(10 11 12 13 14 16 18 20 22 24 26 28 30 36 48 60 72 90))
- 
- 			('Tahoma'			"menu/text serifless"
- 				(10 11 12 13 14 16 18 20 22 24 26 28 30 36 48 60 72 90))
- 
- 			('Garamond'			"menu/text serifs"
- 				(10 11 12 13 14 16 18 20 22 24 26 28 30 36 48 60 72 90))
- 			('Georgia'			"menu/text serifs"
- 				(10 11 12 13 14 16 18 20 22 24 26 28 30 36 48 60 72 90))
- 
- 			('Comic Sans MS'	"eToy"
- 				(10 11 12 13 14 16 18 20 22 24 26 28 30 36 48 60 72 90))
- 
- 			"Optional fonts"
- 			('Impact'			"flaps"
- 				(10 11 12 13 14 16 18 20 22 24 26 28 30 36 48 60 72 90))
- 
- 			('Webdings'			"deco"
- 				(10 11 12 13 14 16 18 20 22 24 26 28 30 36 48 60 72 90))
- 
- 			('System'		"12pt only"
- 				(12))
- 			('Fixedsys'		"12pt only"
- 				(12))
- 		) do:[:spec| HostFont textStyleFrom: spec first sizes: spec last].
- 
- 	TextConstants removeKey: #Atlanta ifAbsent: [].
- 	TextConstants removeKey: #ComicPlain ifAbsent: [].
- 	TextConstants removeKey: #ComicBold ifAbsent: [].
- 	TextConstants removeKey: #Courier ifAbsent: [].
- 	TextConstants removeKey: #Palatino ifAbsent: [].
- 
- 	TextConstants at: #DefaultFixedTextStyle put: (TextConstants at: #'Courier New').
- 	TextConstants at: #Helvetica put:  (TextConstants at: #'Arial').
- 
- !

Item was removed:
- ----- Method: HostFont class>>listFontName: (in category 'accessing') -----
- listFontName: index
- 	<primitive:'primitiveListFont' module:'FontPlugin'>
- 	^nil!

Item was removed:
- ----- Method: HostFont class>>listFontNames (in category 'accessing') -----
- listFontNames
- 	"HostFont listFontNames"
- 	"List all the OS font names"
- 	| font fontNames index |
- 	fontNames := WriteStream on: Array new.
- 	index := 0.
- 	[font := self listFontName: index.
- 	font == nil] whileFalse:[
- 		fontNames nextPut: font.
- 		index := index + 1].
- 	^fontNames contents!

Item was removed:
- ----- Method: HostFont class>>rangesForJapanese (in category 'accessing') -----
- rangesForJapanese
- 
- 	| basics etc |
- 	basics := {
- 		Array with: 0 with: 255
- 	}.
- 	etc := {
- 		Array with: 16r370 with: 16r3FF. "greek"
- 		Array with: 16r400 with: 16r52F. "cyrillic"
- 		Array with: 16r1D00 with: 16r1D7F. "phonetic"
- 		Array with: 16r1E00 with: 16r1EFF. "latin extended additional"
- 		Array with: 16r2000 with: 16r206F. "general punctuation"
- 		Array with: 16r20A0 with: 16r20CF. "currency symbols"
- 		Array with: 16r2100 with: 16r214F. "letterlike"
- 		Array with: 16r2150 with: 16r218F. "number form"
- 		Array with: 16r2190 with: 16r21FF. "arrows"
- 		Array with: 16r2200 with: 16r22FF. "math operators"
- 		Array with: 16r2300 with: 16r23FF. "misc tech"
- 		Array with: 16r2460 with: 16r24FF. "enclosed alnum"
- 		Array with: 16r2500 with: 16r257F. "box drawing"
- 		Array with: 16r2580 with: 16r259F. "box elem"
- 		Array with: 16r25A0 with: 16r25FF. "geometric shapes"
- 		Array with: 16r2600 with: 16r26FF. "misc symbols"
- 		Array with: 16r2700 with: 16r27BF. "dingbats"
- 		Array with: 16r27C0 with: 16r27EF. "misc math A"
- 		Array with: 16r27F0 with: 16r27FF. "supplimental arrow A"
- 		Array with: 16r2900 with: 16r297F. "supplimental arrow B"
- 		Array with: 16r2980 with: 16r29FF. "misc math B"
- 		Array with: 16r2A00 with: 16r2AFF. "supplimental math op"
- 		Array with: 16r2900 with: 16r297F. "supplimental arrow B"
- 		Array with: 16r2E80 with: 16r2EFF. "cjk radicals suppliment"
- 		Array with: 16r2F00 with: 16r2FDF. "kangxi radicals"
- 		Array with: 16r3000 with: 16r303F. "cjk symbols"
- 		Array with: 16r3040 with: 16r309F. "hiragana"
- 		Array with: 16r30A0 with: 16r30FF. "katakana"
- 		Array with: 16r3190 with: 16r319F. "kanbun"
- 		Array with: 16r31F0 with: 16r31FF. "katakana extension"
- 		Array with: 16r3200 with: 16r32FF. "enclosed CJK"
- 		Array with: 16r3300 with: 16r33FF. "CJK compatibility"
- 		Array with: 16r3400 with: 16r4DBF. "CJK unified extension A"
- 		Array with: 16r4E00 with: 16r9FAF. "CJK ideograph"
- 		Array with: 16rF900 with: 16rFAFF. "CJK compatiblity ideograph"
- 		Array with: 16rFE30 with: 16rFE4F. "CJK compatiblity forms"
- 		Array with: 16rFF00 with: 16rFFEF. "half and full"
- 	}.
- 
- 	^ basics, etc.
- !

Item was removed:
- ----- Method: HostFont class>>textStyleFrom: (in category 'accessing') -----
- textStyleFrom: fontName
- 	"HostFont textStyleFromUser"
- 	| styleName fonts |
- 	styleName := fontName asSymbol.
- 	"(TextConstants includesKey: styleName)
- 		ifTrue:[(self confirm: 
- styleName , ' is already defined in TextConstants.
- Do you want to replace that definition?')
- 			ifFalse: [^ self]]."
- 	fonts := #(10 11 12 13 14 16 18 20 22 24 26 28 30 36 48 60 72 90).
- 	('Rendering ', styleName) displayProgressFrom: 1 to: fonts size during:[:bar|
- 			fonts := fonts
- 				collect:[:ptSize| bar value: (fonts indexOf: ptSize).
- 							   self fontName: styleName 
- 									size: ptSize
- 									emphasis: 0]
- 				thenSelect:[:font| font notNil]]. "reject those that failed"
- 	fonts size = 0 ifTrue:[^self error:'Could not create font style', styleName].
- 	TextConstants
- 		at: styleName
- 		put: (TextStyle fontArray: fonts).!

Item was removed:
- ----- Method: HostFont class>>textStyleFrom:sizes: (in category 'accessing') -----
- textStyleFrom: fontName sizes: ptSizes
- 	| styleName fonts |
- 	styleName := fontName asSymbol.
- 	(TextConstants includesKey: styleName)
- 		ifTrue:[(self confirm: 
- styleName , ' is already defined in TextConstants.
- Do you want to replace that definition?')
- 			ifFalse: [^ self]].
- 	('Rendering ', styleName) displayProgressFrom: 1 to: ptSizes size during:[:bar|
- 			fonts := ptSizes
- 				collect:[:ptSize| bar value: (ptSizes indexOf: ptSize).
- 							   self fontName: styleName 
- 									size: ptSize
- 									emphasis: 0]
- 				thenSelect:[:font| font notNil]]. "reject those that failed"
- 	fonts size = 0 ifTrue:[^self error:'Could not create font style', styleName].
- 	TextConstants
- 		at: styleName
- 		put: (TextStyle fontArray: fonts).!

Item was removed:
- ----- Method: HostFont class>>textStyleFrom:sizes:ranges: (in category 'accessing') -----
- textStyleFrom: fontName sizes: ptSizes ranges: ranges
- 	| styleName fonts |
- 	styleName := fontName asSymbol.
- 	(TextConstants includesKey: styleName)
- 		ifTrue:[(self confirm: 
- styleName , ' is already defined in TextConstants.
- Do you want to replace that definition?')
- 			ifFalse: [^ self]].
- 	('Rendering ', styleName) displayProgressFrom: 1 to: ptSizes size during:[:bar|
- 			fonts := ptSizes
- 				collect:[:ptSize| bar value: (ptSizes indexOf: ptSize).
- 							   self fontName: styleName 
- 									size: ptSize
- 									emphasis: 0 rangesArray: ranges
- 				]
- 				thenSelect:[:font| font notNil]]. "reject those that failed"
- 	fonts size = 0 ifTrue:[^self error:'Could not create font style', styleName].
- 	TextConstants
- 		at: styleName
- 		put: (TextStyle fontArray: fonts).!

Item was removed:
- ----- Method: HostFont class>>textStyleFromUser (in category 'accessing') -----
- textStyleFromUser
- 	"HostFont textStyleFromUser"
- 	| styleName fonts |
- 	styleName := self fontNameFromUser ifNil:[^self].
- 	styleName := styleName asSymbol.
- 	(TextConstants includesKey: styleName)
- 		ifTrue:[(self confirm: 
- styleName , ' is already defined in TextConstants.
- Do you want to replace that definition?')
- 			ifFalse: [^ self]].
- 	fonts := #(10 12 14 16 18 20 22 24 26 28 30 36 48 60 72 90).
- 	('Rendering ', styleName) displayProgressFrom: 1 to: fonts size during:[:bar|
- 			fonts := fonts
- 				collect:[:ptSize| bar value: (fonts indexOf: ptSize).
- 							   self fontName: styleName 
- 									size: ptSize
- 									emphasis: 0]
- 				thenSelect:[:font| font notNil]]. "reject those that failed"
- 	fonts size = 0 ifTrue:[^self error:'Could not create font style', styleName].
- 	TextConstants
- 		at: styleName
- 		put: (TextStyle fontArray: fonts).!

Item was removed:
- ----- Method: HostFont>>baseKern (in category 'accessing') -----
- baseKern
- 	^0!

Item was removed:
- ----- Method: HostFont>>createCharacterToGlyphMap (in category 'accessing') -----
- createCharacterToGlyphMap
- 
- 	^ IdentityGlyphMap new.
- !

Item was removed:
- ----- Method: HostFont>>descentKern (in category 'accessing') -----
- descentKern
- 	^0!

Item was removed:
- ----- Method: HostFont>>displayString:on:from:to:at:kern: (in category 'accessing') -----
- displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta 
- 
- 	^ self displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: aPoint y + self ascent.
- !

Item was removed:
- ----- Method: HostFont>>displayString:on:from:to:at:kern:baselineY: (in category 'accessing') -----
- displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY
- 
-  	^ super displayMultiString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY.
- !

Item was removed:
- ----- Method: HostFont>>emphasized: (in category 'emphasis') -----
- emphasized: code
- 	| derivative addedEmphasis base safeCode |
- 	code = 0 ifTrue: [^ self].
- 	derivativeFonts == nil ifTrue:[derivativeFonts := Array new: 32].
- 	derivative := derivativeFonts at: (safeCode := code min: derivativeFonts size).
- 	derivative == nil ifFalse: [^ derivative].  "Already have this style"
- 
- 	"Dont have it -- derive from another with one with less emphasis"
- 	addedEmphasis := 1 bitShift: safeCode highBit - 1.
- 	base := self emphasized: safeCode - addedEmphasis.  "Order is Bold, Ital, Under, Narrow"
- 	addedEmphasis = 1 ifTrue:   "Compute synthetic bold version of the font"
- 		[derivative := (base copy name: base name) makeBoldGlyphs].
- 	addedEmphasis = 2 ifTrue:   "Compute synthetic italic version of the font"
- 		[ derivative := (base copy name: base name) makeItalicGlyphs].
- 	addedEmphasis = 4 ifTrue:   "Compute underlined version of the font"
- 		[derivative := (base copy name: base name) makeUnderlinedGlyphs].
- 	addedEmphasis = 8 ifTrue:   "Compute narrow version of the font"
- 		[derivative := (base copy name: base name) makeCondensedGlyphs].
- 	addedEmphasis = 16 ifTrue:   "Compute struck-out version of the font"
- 		[derivative := (base copy name: base name) makeStruckOutGlyphs].
- 	derivative emphasis: safeCode.
- 	derivativeFonts at: safeCode put: derivative.
- 	^ derivative!

Item was removed:
- ----- Method: HostFont>>fontName:size:emphasis: (in category 'private-creation') -----
- fontName: fontName size: ptSize emphasis: emphasisCode
- 
- 	^ self fontName: fontName size: ptSize emphasis: emphasisCode rangesArray: (Array with: (Array with: 0 with: 255)).
- !

Item was removed:
- ----- Method: HostFont>>fontName:size:emphasis:rangesArray: (in category 'private-creation') -----
- fontName: fontName size: ptSize emphasis: emphasisCode rangesArray: rangesArray
- 	"
- 		^HostFont fontName: ('MS UI Gothic') size: 12 emphasis: 0 rangesArray: EFontBDFFontReaderForRanges basicNew rangesForJapanese.
- 	"
- 	| fontHandle xStart w glyphForm fontHeight fw enc rangesStream currentRange |
- 	fontHandle := self primitiveCreateFont: fontName size: ptSize emphasis: emphasisCode.
- 	fontHandle ifNil:[^nil].
- 	ranges := rangesArray.
- 	ranges ifNil: [ranges := Array with: (Array with: 0 with: 255)].
- 	pointSize := ptSize.
- 	name := fontName.
- 	emphasis := emphasisCode.
- 	minAscii := 0.
- 	maxAscii := ranges last last.
- 	ascent := self primitiveFontAscent: fontHandle.
- 	descent := self primitiveFontDescent: fontHandle.
- 	kernPairs := Array new: (self primitiveFontNumKernPairs: fontHandle).
- 	1 to: kernPairs size do:[:i|
- 		kernPairs at: i put: (self primitiveFont: fontHandle getKernPair: i)].
- 	fontHeight := ascent + descent.
- 	xTable := Array new: maxAscii + 3.
- 	fullWidth := Array new: maxAscii + 1.
- 	xStart := maxWidth := 0.
- 	rangesStream := ReadStream on: (ranges collect: [:e | (e first to: e second)]).
- 	currentRange := rangesStream next.
- 	0 to: maxAscii do:[:i|
- 		xTable at: i+1 put: xStart.
- 		i > currentRange last ifTrue: [
- 			[rangesStream atEnd not and: [currentRange := rangesStream next. currentRange last < i]] whileTrue.
- 			rangesStream atEnd ifTrue: [].
- 		].
- 		(currentRange includes: i) ifTrue: [
- 			xTable at: i+1 put: xStart.
- 			fw := self primitiveFont: fontHandle fullWidthOfChar: i.
- 			(#(	1 "anchored morph"
- 				9 "tab"
- 				10 "LF"
- 				13 "CR"
- 			) includes: i) ifTrue:[fw := {0. 0. 0}].
- 			fullWidth at: i+1 put: fw.
- 			w := fw at: 2.
- 			(fw at: 1) > 0 ifTrue:[w := w + (fw at: 1)].
- 			(fw at: 3) > 0 ifTrue:[w := w + (fw at: 3)].
- 			w > maxWidth ifTrue:[maxWidth := w].
- 			xStart := xStart + w].
- 		].
- 	xStart = 0 ifTrue:[^nil].
- 	strikeLength := xStart.
- 	xTable at: maxAscii+1 put: xStart.
- 	xTable at: maxAscii+2 put: xStart.
- 	xTable at: maxAscii+3 put: xStart.
- 	glyphs := Form extent: xTable last @ fontHeight depth: 1.
- 	glyphForm := Form extent: maxWidth @ fontHeight depth: 1.
- 	0 to: maxAscii do:[:i|
- 		glyphForm fillWhite.
- 		self primitiveFont: fontHandle glyphOfChar: i into: glyphForm.
- 		xStart := xTable at: i+1.
- 		glyphForm displayOn: glyphs at: xStart at 0.
- 		"glyphForm displayOn: Display at: xStart at 0."
- 	].
- 	enc := self primitiveFontEncoding: fontHandle.
- 	enc = 1 ifTrue:[characterToGlyphMap := self isoToSqueakMap].
- 	self primitiveDestroyFont: fontHandle.
- 	^self!

Item was removed:
- ----- Method: HostFont>>getFontData (in category 'accessing') -----
- getFontData
- 	| fontHandle bufSize buffer |
- 	fontHandle := self primitiveCreateFont: name size: pointSize emphasis: emphasis.
- 	fontHandle ifNil:[^nil].
- 	bufSize := self primitiveFontDataSize: fontHandle.
- 	buffer := ByteArray new: bufSize.
- 	self primitiveFont: fontHandle getData: buffer.
- 	^buffer!

Item was removed:
- ----- Method: HostFont>>isoToSqueakMap (in category 'private-creation') -----
- isoToSqueakMap
- 	^nil
- !

Item was removed:
- ----- Method: HostFont>>makeBoldGlyphs (in category 'emphasis') -----
- makeBoldGlyphs
- 	"First check if we can use some OS support for this"
- 	(self class listFontNames includes: name) ifFalse:[^super makeBoldGlyphs].
- 	"Now attempt a direct creation through the appropriate primitives"
- 	(self fontName: name size: pointSize emphasis: (emphasis bitOr: 1) rangesArray: ranges) 
- 		ifNil:[^super makeBoldGlyphs]. "nil means we failed"!

Item was removed:
- ----- Method: HostFont>>makeItalicGlyphs (in category 'emphasis') -----
- makeItalicGlyphs
- 	"First check if we can use some OS support for this"
- 	(self class listFontNames includes: name) ifFalse:[^super makeItalicGlyphs].
- 	"Now attempt a direct creation through the appropriate primitives"
- 	(self fontName: name size: pointSize emphasis: (emphasis bitOr: 2) rangesArray: ranges)
- 		ifNil:[^super makeItalicGlyphs]. "nil means we failed"!

Item was removed:
- ----- Method: HostFont>>makeStruckOutGlyphs (in category 'emphasis') -----
- makeStruckOutGlyphs
- 	"First check if we can use some OS support for this"
- 	(self class listFontNames includes: name) ifFalse:[^super makeStruckOutGlyphs].
- 	"Now attempt a direct creation through the appropriate primitives"
- 	(self fontName: name size: pointSize emphasis: (emphasis bitOr: 8) rangesArray: ranges)
- 		ifNil:[^super makeStruckOutGlyphs]. "nil means we failed"!

Item was removed:
- ----- Method: HostFont>>makeUnderlinedGlyphs (in category 'emphasis') -----
- makeUnderlinedGlyphs
- 	"First check if we can use some OS support for this"
- 	(self class listFontNames includes: name) ifFalse:[^super makeUnderlinedGlyphs].
- 	"Now attempt a direct creation through the appropriate primitives"
- 	(self fontName: name size: pointSize emphasis: (emphasis bitOr: 4) rangesArray: ranges)
- 		ifNil:[^super makeUnderlinedGlyphs]. "nil means we failed"!

Item was removed:
- ----- Method: HostFont>>primitiveCreateFont:size:emphasis: (in category 'primitives') -----
- primitiveCreateFont: fontName size: fontSize emphasis: fontFlags
- 	<primitive:'primitiveCreateFont' module:'FontPlugin'>
- 	^nil!

Item was removed:
- ----- Method: HostFont>>primitiveDestroyFont: (in category 'primitives') -----
- primitiveDestroyFont: fontHandle
- 	<primitive:'primitiveDestroyFont' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: HostFont>>primitiveFont:fullWidthOfChar: (in category 'primitives') -----
- primitiveFont: fontHandle fullWidthOfChar: aCharIndex 
- 	<primitive:'primitiveFontFullWidthOfChar' module:'FontPlugin'>
- 	^Array 
- 		with: 0
- 		with: (self primitiveFont: fontHandle widthOfChar: aCharIndex)
- 		with: 0!

Item was removed:
- ----- Method: HostFont>>primitiveFont:getData: (in category 'primitives') -----
- primitiveFont: fontHandle getData: buffer
- 	<primitive:'primitiveGetFontData' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: HostFont>>primitiveFont:getKernPair: (in category 'primitives') -----
- primitiveFont: fontHandle getKernPair: kernIndex
- 	<primitive:'primitiveFontGetKernPair' module:'FontPlugin'>
- 	^0!

Item was removed:
- ----- Method: HostFont>>primitiveFont:glyphOfChar:into: (in category 'primitives') -----
- primitiveFont: fontHandle glyphOfChar: aCharIndex into: glyphForm 
- 	<primitive:'primitiveFontGlyphOfChar' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: HostFont>>primitiveFont:widthOfChar: (in category 'primitives') -----
- primitiveFont: fontHandle widthOfChar: aCharIndex 
- 	<primitive:'primitiveFontWidthOfChar' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: HostFont>>primitiveFontAscent: (in category 'primitives') -----
- primitiveFontAscent: fontHandle
- 	<primitive:'primitiveFontAscent' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: HostFont>>primitiveFontDataSize: (in category 'primitives') -----
- primitiveFontDataSize: fontHandle
- 	<primitive:'primitiveFontDataSize' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: HostFont>>primitiveFontDescent: (in category 'primitives') -----
- primitiveFontDescent: fontHandle
- 	<primitive:'primitiveFontDescent' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: HostFont>>primitiveFontEmbeddingFlags: (in category 'primitives') -----
- primitiveFontEmbeddingFlags: fontHandle
- 	<primitive:'primitiveFontEmbeddingFlags' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: HostFont>>primitiveFontEncoding: (in category 'primitives') -----
- primitiveFontEncoding: fontHandle
- 	<primitive:'primitiveFontEncoding' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: HostFont>>primitiveFontNumKernPairs: (in category 'primitives') -----
- primitiveFontNumKernPairs: fontHandle
- 	<primitive:'primitiveFontNumKernPairs' module:'FontPlugin'>
- 	^0!

Item was removed:
- ----- Method: HostFont>>testEmbeddingFlags (in category 'accessing') -----
- testEmbeddingFlags
- 	"HostFont basicNew testEmbeddingFlags"
- 	| list |
- 	list := self class listFontNames.
- 	list do:[:fName| | fontHandle |
- 		fontHandle := self primitiveCreateFont: fName size: 12 emphasis: 0.
- 		fontHandle ifNotNil:[
- 			type := self primitiveFontEmbeddingFlags: fontHandle.
- 			Transcript cr; show: fName,': ', type printString.
- 			self primitiveDestroyFont: fontHandle.
- 		].
- 	].!

Item was removed:
- Object subclass: #HostWindowProxy
- 	instanceVariableNames: 'windowHandle sourceForm'
- 	classVariableNames: 'ActiveProxyClass Registry'
- 	poolDictionaries: ''
- 	category: 'Graphics-External-Ffenestri'!
- 
- !HostWindowProxy commentStamp: 'bf 1/4/2012 18:37' prior: 0!
- This is a proxy for a Host OS window and as such is considered a disposable item. When an image is restarted the client must recreate suitable instances from the information they hold. Platform specific subclasses are available to translate abstract requirements into possible platform concrete data.
- There is a registry of instances so that when users let go they can be guaranteed to close down properly. Because the instances point to the source Form in use this can on occasion result in a cycle that defeats the Weak mechanism - hence the implementation of #executor & #asExecutor.
- The only requirements placed on the sourceForm instvar are those of being like a DisplayScreen - can return a bits array, the width, depth etc PLUS implement processEvent: AND able to respond to #resetProxy to remove and rebuild the window proxy!

Item was removed:
- ----- Method: HostWindowProxy class>>activeWindowProxyClass (in category 'system startup') -----
- activeWindowProxyClass
- 	"Return the concrete HostWindowProxy subclass for the platform on which we are
- currently running."
- 
- 	HostWindowProxy allSubclasses do: [:class |
- 		class isActiveHostWindowProxyClass ifTrue: [^ class]].
- 
- 	"no responding subclass; use HostWindowProxy"
- 	^ HostWindowProxy
- !

Item was removed:
- ----- Method: HostWindowProxy class>>initialize (in category 'class initialization') -----
- initialize
- "Add me to the system startup list and make sure to do a file-in init for first time loading"
- "HostWindowProxy initialize"
- 	self setDefaultWindowProxyClass.
- 	Smalltalk addToStartUpList: self.!

Item was removed:
- ----- Method: HostWindowProxy class>>isActiveHostWindowProxyClass (in category 'system startup') -----
- isActiveHostWindowProxyClass
- "subclasses must override this"
- 	self subclassResponsibility!

Item was removed:
- ----- Method: HostWindowProxy class>>on: (in category 'initialize-release') -----
- on: aSourceForm
- "Build a new window proxy by finding the appropriate platform specific subclass
- and setting it up for this Form-like argument"
- 	^ActiveProxyClass new on: aSourceForm!

Item was removed:
- ----- Method: HostWindowProxy class>>processEvent: (in category 'events') -----
- processEvent: evt
- 	"evt is a raw event buffer from VM. Pass it on to the appropiate proxy."
- 	self registry keys do: [:proxy |
- 		(proxy wantsEvent: evt) ifTrue: [proxy processEvent: evt]].
- !

Item was removed:
- ----- Method: HostWindowProxy class>>register: (in category 'registry') -----
- register: anObject
- "boilerplate WeakRegistry usage"
- 	^self registry add: anObject!

Item was removed:
- ----- Method: HostWindowProxy class>>registry (in category 'registry') -----
- registry
- "boilerplate WeakRegistry usage"
- 	^Registry ifNil: [Registry := WeakRegistry new]!

Item was removed:
- ----- Method: HostWindowProxy class>>setDefaultWindowProxyClass (in category 'system startup') -----
- setDefaultWindowProxyClass
- 	"connect to the proper platform subclass of proxy"
- 	ActiveProxyClass := self activeWindowProxyClass!

Item was removed:
- ----- Method: HostWindowProxy class>>startUp: (in category 'system startup') -----
- startUp: resuming
- 	resuming ifFalse: [^self].
- 	"system startup - find the appropriate proxy class for this platform"
- 	self setDefaultWindowProxyClass.
- 	"any currently extant instances must tell their sourceForm to resetProxy in order to kill potentially wrong-platform versions and reset to correct-platform"
- 	self registry keys do: [:i | i resetProxy]!

Item was removed:
- ----- Method: HostWindowProxy class>>unregister: (in category 'registry') -----
- unregister: anObject
- "boilerplate WeakRegistry usage"
- 	^self registry remove: anObject ifAbsent:[]!

Item was removed:
- ----- Method: HostWindowProxy>>asExecutor (in category 'finalization') -----
- asExecutor
- 	sourceForm := nil!

Item was removed:
- ----- Method: HostWindowProxy>>attributes (in category 'window decorations') -----
- attributes
- "return the ByteArray representing the desired window attributes. This is utterly platform dependent and my default is an empty ByteArray to signify a default window"
- 	^ByteArray new!

Item was removed:
- ----- Method: HostWindowProxy>>bits (in category 'metrics') -----
- bits
- "return the bits - normally of the sourceForm"
- 	^sourceForm bits!

Item was removed:
- ----- Method: HostWindowProxy>>close (in category 'initialize-release') -----
- close
- 	"close this window"
- 	windowHandle ifNil: [^self].
- 	self unregister.
- 	self primitiveWindowClose: windowHandle.
- 	windowHandle := nil.
- !

Item was removed:
- ----- Method: HostWindowProxy>>defaultWindowType (in category 'window decorations') -----
- defaultWindowType
- "set up my attributes to be a default window - a titlebar, usual decorations etc"
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: HostWindowProxy>>depth (in category 'metrics') -----
- depth
- "return the depth - normally of the sourceForm"
- 	^sourceForm depth!

Item was removed:
- ----- Method: HostWindowProxy>>executor (in category 'finalization') -----
- executor
- 	^self shallowCopy asExecutor!

Item was removed:
- ----- Method: HostWindowProxy>>finalize (in category 'finalization') -----
- finalize
- 	"close this window"
- 	self close!

Item was removed:
- ----- Method: HostWindowProxy>>forceToScreen: (in category 'window manipulation') -----
- forceToScreen: damageRectangle 
- 	"update the area of the sourceForm defined by damageRectangle"
- 	self
- 		primitiveUpdateHostWindow: windowHandle
- 		bitmap: self bits
- 		width: self width
- 		height: self height
- 		depth: self depth
- 		left: damageRectangle left
- 		right: damageRectangle right
- 		top: damageRectangle top
- 		bottom: damageRectangle bottom!

Item was removed:
- ----- Method: HostWindowProxy>>height (in category 'metrics') -----
- height
- "return the height - normally of the sourceForm"
- 	^sourceForm height!

Item was removed:
- ----- Method: HostWindowProxy>>isOpen (in category 'accessing') -----
- isOpen
- "am I already opened?"
- 	^windowHandle notNil!

Item was removed:
- ----- Method: HostWindowProxy>>offset (in category 'metrics') -----
- offset
- "return the offset - normally of the sourceForm"
- 	^sourceForm offset!

Item was removed:
- ----- Method: HostWindowProxy>>on: (in category 'initialize-release') -----
- on: aSourceForm 
- 	"set my sourceForm; usually an actual Form but so long as methods like bits, height etc work, it can be anything"
- 	sourceForm := aSourceForm!

Item was removed:
- ----- Method: HostWindowProxy>>open (in category 'initialize-release') -----
- open
- 	"open a host window built around my position, size and bitmap"
- 	windowHandle
- 		ifNil: [sourceForm
- 				ifNotNil:[windowHandle := self
- 						primitiveCreateHostWindowWidth: self width
- 						height: self height
- 						originX: self offset x
- 						y: self offset y
- 						attributes: self attributes.
- 						windowHandle ifNotNil:[self register].
- 						^windowHandle]]!

Item was removed:
- ----- Method: HostWindowProxy>>primitiveCreateHostWindowWidth:height:originX:y:attributes: (in category 'system primitives') -----
- primitiveCreateHostWindowWidth: w height: h originX: x y: y attributes: list
- "create and open a host window. list is a ByteArray list of window attributes in some platform manner. See subclasses for information"
- 	<primitive: 'primitiveCreateHostWindow' module: 'HostWindowPlugin'>
- 	^self error: 'Unable to create Host Window'!

Item was removed:
- ----- Method: HostWindowProxy>>primitiveUpdateHostWindow:bitmap:width:height:depth:left:right:top:bottom: (in category 'system primitives') -----
- primitiveUpdateHostWindow: id bitmap: bitmap width: w height: h depth: d left: l
- right: r top: t bottom: b 
- 	"Force the pixels to the screen. The bitmap details and affected area are given
- explicitly to avoid dependence upon any object structure"
- 	<primitive: 'primitiveShowHostWindowRect' module:'HostWindowPlugin'>
- 	^self windowProxyError: 'update'!

Item was removed:
- ----- Method: HostWindowProxy>>primitiveWindowClose: (in category 'system primitives') -----
- primitiveWindowClose: id
- "Close the window"
- 	<primitive: 'primitiveCloseHostWindow' module: 'HostWindowPlugin'>
- 	^self windowProxyError: 'close'!

Item was removed:
- ----- Method: HostWindowProxy>>primitiveWindowPosition: (in category 'system primitives') -----
- primitiveWindowPosition: id
- "Find the topleft corner of the window"
- 	<primitive: 'primitiveHostWindowPosition' module: 'HostWindowPlugin'>
- 	^self windowProxyError: 'get position'!

Item was removed:
- ----- Method: HostWindowProxy>>primitiveWindowPosition:x:y: (in category 'system primitives') -----
- primitiveWindowPosition: id x: x y: y
- "Set the topleft corner of the window - return what is actually set"
- 	<primitive: 'primitiveHostWindowPositionSet' module: 'HostWindowPlugin'>
- 	^self windowProxyError: 'set position'!

Item was removed:
- ----- Method: HostWindowProxy>>primitiveWindowSize: (in category 'system primitives') -----
- primitiveWindowSize: id
- "Find the size of the window, just like primitiveScreenSize"
- 	<primitive: 'primitiveHostWindowSize' module: 'HostWindowPlugin'>
- 	^self windowProxyError: 'get size'!

Item was removed:
- ----- Method: HostWindowProxy>>primitiveWindowSize:x:y: (in category 'system primitives') -----
- primitiveWindowSize: id x: x y: y
- "Set the size of the window, just like primitiveScreenSize. Return the actually
- achieved size"
- 	<primitive: 'primitiveHostWindowSizeSet' module: 'HostWindowPlugin'>
- 	^self windowProxyError: 'set size'!

Item was removed:
- ----- Method: HostWindowProxy>>primitiveWindowTitle:string: (in category 'system primitives') -----
- primitiveWindowTitle: id string: titleString
- "Set the label of the title bar of the window"
- 	<primitive: 'primitiveHostWindowTitle' module: 'HostWindowPlugin'>
- 	^self error: 'Unable to set title of Host Window'!

Item was removed:
- ----- Method: HostWindowProxy>>printOn: (in category 'printing') -----
- printOn: aStream
- 	super printOn:aStream.
- 	aStream nextPutAll: ' (windowIndex '.
- 	windowHandle printOn: aStream.
- 	aStream nextPut: $)!

Item was removed:
- ----- Method: HostWindowProxy>>processEvent: (in category 'events') -----
- processEvent: evt
- 	"evt is a raw event buffer from VM. delegate to client window"
- 	sourceForm processEvent: evt!

Item was removed:
- ----- Method: HostWindowProxy>>recreate (in category 'window manipulation') -----
- recreate
- "something has changed that require deleting the host window before opening it
- with new attributes"
- 	self close; open!

Item was removed:
- ----- Method: HostWindowProxy>>register (in category 'finalization') -----
- register
- 	^self class register: self!

Item was removed:
- ----- Method: HostWindowProxy>>resetProxy (in category 'finalization') -----
- resetProxy
- "tell my sourceForm to kill me (gulp) and resurrect me in the correct clothing"
- 	sourceForm ifNotNil:[ sourceForm resetProxy]!

Item was removed:
- ----- Method: HostWindowProxy>>unregister (in category 'finalization') -----
- unregister
- 	^self class unregister: self!

Item was removed:
- ----- Method: HostWindowProxy>>wantsEvent: (in category 'events') -----
- wantsEvent: evt
- 	"evt is a raw event buffer from VM. check if its window field matches ours"
- 	^ windowHandle = (evt at: 8)!

Item was removed:
- ----- Method: HostWindowProxy>>width (in category 'metrics') -----
- width
- "return the width - normally of the sourceForm"
- 	^sourceForm width!

Item was removed:
- ----- Method: HostWindowProxy>>windowPosition (in category 'window manipulation') -----
- windowPosition
- 	"return the current position of the window"
- 		^self primitiveWindowPosition: windowHandle!

Item was removed:
- ----- Method: HostWindowProxy>>windowPosition: (in category 'window manipulation') -----
- windowPosition: aPoint
- 	"set the position of the window and then return the new position"
- 		^self primitiveWindowPosition: windowHandle x: aPoint x y: aPoint y!

Item was removed:
- ----- Method: HostWindowProxy>>windowProxyError: (in category 'accessing') -----
- windowProxyError: problemString
- 	"Could be useful to raise an exception but not yet"!

Item was removed:
- ----- Method: HostWindowProxy>>windowSize (in category 'window manipulation') -----
- windowSize
- 	"return the current size of the window "
- 		^self primitiveWindowSize: windowHandle!

Item was removed:
- ----- Method: HostWindowProxy>>windowSize: (in category 'window manipulation') -----
- windowSize: aPoint
- 	"Set the size of the window and then return the actually set size of the window - not neccessarily the same "
- 		^self primitiveWindowSize: windowHandle x: aPoint x y: aPoint y!

Item was removed:
- ----- Method: HostWindowProxy>>windowTitle: (in category 'window manipulation') -----
- windowTitle: titleString
- "set the label in the window titlebar to titleString"
- 	^self primitiveWindowTitle: windowHandle string: titleString squeakToUtf8!

Item was removed:
- Object subclass: #IdentityGlyphMap
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Fonts'!

Item was removed:
- ----- Method: IdentityGlyphMap>>at: (in category 'accessing') -----
- at: index
- 
- 	^ index - 1.
- !

Item was removed:
- DisplayTransform subclass: #IdentityTransform
- 	instanceVariableNames: ''
- 	classVariableNames: 'Default'
- 	poolDictionaries: ''
- 	category: 'Graphics-Transformations'!

Item was removed:
- ----- Method: IdentityTransform class>>initialize (in category 'class initialization') -----
- initialize
- 	"IdentityTransform initialize"
- 	Default := self basicNew.!

Item was removed:
- ----- Method: IdentityTransform class>>new (in category 'instance creation') -----
- new
- 	"There can be only one"
- 	^Default!

Item was removed:
- ----- Method: IdentityTransform>>angle (in category 'accessing') -----
- angle
- 	^ 0.0!

Item was removed:
- ----- Method: IdentityTransform>>asMatrixTransform2x3 (in category 'converting') -----
- asMatrixTransform2x3
- 	"Represent the receiver as a 2x3 matrix transformation"
- 	^MatrixTransform2x3 identity!

Item was removed:
- ----- Method: IdentityTransform>>composedWith: (in category 'composing') -----
- composedWith: aTransform
- 	^aTransform!

Item was removed:
- ----- Method: IdentityTransform>>composedWithGlobal: (in category 'composing') -----
- composedWithGlobal: aTransformation
- 	^aTransformation!

Item was removed:
- ----- Method: IdentityTransform>>composedWithLocal: (in category 'composing') -----
- composedWithLocal: aTransformation
- 	^aTransformation!

Item was removed:
- ----- Method: IdentityTransform>>globalBoundsToLocal: (in category 'transforming rects') -----
- globalBoundsToLocal: aRectangle
- 	"Transform aRectangle from global coordinates into local coordinates"
- 	^aRectangle!

Item was removed:
- ----- Method: IdentityTransform>>globalPointToLocal: (in category 'transforming points') -----
- globalPointToLocal: aPoint
- 	"Transform aPoint from global coordinates into local coordinates"
- 	^aPoint!

Item was removed:
- ----- Method: IdentityTransform>>globalPointsToLocal: (in category 'transforming points') -----
- globalPointsToLocal: inArray
- 	"Transform all the points of inArray from global into local coordinates"
- 	^inArray!

Item was removed:
- ----- Method: IdentityTransform>>inverseTransformation (in category 'accessing') -----
- inverseTransformation
- 	"Return the inverse transformation of the receiver"
- 	^self!

Item was removed:
- ----- Method: IdentityTransform>>invertBoundsRect: (in category 'transforming points') -----
- invertBoundsRect: aRectangle
- 	"Return a rectangle whose coordinates have been transformed
- 	from local back to global coordinates. Since I am the identity matrix
- 	no transformation is made."
- 
- 	^aRectangle
- !

Item was removed:
- ----- Method: IdentityTransform>>isIdentity (in category 'testing') -----
- isIdentity
- 	"Return true if the receiver is the identity transform; that is, if applying to a point returns the point itself."
- 	^true!

Item was removed:
- ----- Method: IdentityTransform>>isPureTranslation (in category 'testing') -----
- isPureTranslation
- 	"Return true if the receiver specifies no rotation or scaling."
- 	^true!

Item was removed:
- ----- Method: IdentityTransform>>localBoundsToGlobal: (in category 'transforming rects') -----
- localBoundsToGlobal: aRectangle
- 	"Transform aRectangle from local coordinates into global coordinates"
- 	^aRectangle!

Item was removed:
- ----- Method: IdentityTransform>>localPointToGlobal: (in category 'transforming points') -----
- localPointToGlobal: aPoint
- 	"Transform aPoint from local coordinates into global coordinates"
- 	^aPoint!

Item was removed:
- ----- Method: IdentityTransform>>localPointsToGlobal: (in category 'transforming points') -----
- localPointsToGlobal: inArray
- 	"Transform all the points of inArray from local into global coordinates"
- 	^inArray!

Item was removed:
- ----- Method: IdentityTransform>>setIdentity (in category 'initialize') -----
- setIdentity
- 	"I *am* the identity transform"
- 	^self!

Item was removed:
- ----- Method: IdentityTransform>>sourceQuadFor: (in category 'transforming rects') -----
- sourceQuadFor: aRectangle
- 	^ aRectangle innerCorners!

Item was removed:
- Object subclass: #ImageReadWriter
- 	instanceVariableNames: 'stream'
- 	classVariableNames: 'ImageNotStoredSignal MagicNumberErrorSignal'
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!
- 
- !ImageReadWriter commentStamp: '<historical>' prior: 0!
- Copyright (c) Kazuki Yasumatsu, 1995. All rights reserved.
- 
- I am an abstract class to provide for encoding and/or decoding an image on a stream.
- 
- Instance Variables:
- 	stream		<ReadStream | WriteStream>	stream for image storages
- 
- Class Variables:
- 	ImageNotStoredSignal		<Signal>	image not stored error signal
- 	MagicNumberErrorSignal		<Signal>	magic number error signal
- 
- Subclasses must implement the following messages:
- 	accessing
- 		nextImage
- 		nextPutImage:
- 	testing
- 		canUnderstand         (added tao 10/26/97)!

Item was removed:
- ----- Method: ImageReadWriter class>>allTypicalFileExtensions (in category 'image reading/writing') -----
- allTypicalFileExtensions
- 	"Answer a collection of file extensions (lowercase) which files that my subclasses can read might commonly have"
- 	"ImageReadWriter allTypicalFileExtensions"
- 	| extensions |
- 	extensions := Set new.
- 	self allSubclassesDo: [ :cls | extensions addAll: cls typicalFileExtensions ].
- 	^extensions!

Item was removed:
- ----- Method: ImageReadWriter class>>formFromFileNamed: (in category 'image reading/writing') -----
- formFromFileNamed: fileName
- 	"Answer a ColorForm stored on the file with the given name."
- 	| stream |
- 	stream := FileStream readOnlyFileNamed: fileName.
- 	^self formFromStream: stream!

Item was removed:
- ----- Method: ImageReadWriter class>>formFromStream: (in category 'image reading/writing') -----
- formFromStream: aBinaryStream
- 	"Answer a ColorForm stored on the given stream.  closes the stream"
- 	| reader readerClass form  |
- 
- 	readerClass := self withAllSubclasses
- 		detect: [:subclass |
- 			aBinaryStream reset.
- 			subclass understandsImageFormat: aBinaryStream]
- 		ifNone: [
- 			aBinaryStream close.
- 			^self error: 'image format not recognized' translated].
- 	aBinaryStream reset.
- 	reader := readerClass new on: aBinaryStream.
- 	Cursor read showWhile: [
- 		form := reader nextImage.
- 		reader close].
- 	^ form
- !

Item was removed:
- ----- Method: ImageReadWriter class>>on: (in category 'instance creation') -----
- on: aStream
- 	"Answer an instance of the receiver for encoding and/or decoding images on the given."
- 
- 	^ self new on: aStream
- !

Item was removed:
- ----- Method: ImageReadWriter class>>putForm:onFileNamed: (in category 'image reading/writing') -----
- putForm: aForm onFileNamed: fileName
- 	"Store the given form on a file of the given name."
- 
- 	| writer theFile |
- 	theFile := FileStream newFileNamed: fileName.
- 	writer := self on: theFile binary.
- 	Cursor write showWhile: [writer nextPutImage: aForm].
- 	writer close.
- 	theFile directory setMacFileNamed: theFile localName type: '    ' creator: '    '.!

Item was removed:
- ----- Method: ImageReadWriter class>>putForm:onStream: (in category 'image reading/writing') -----
- putForm: aForm onStream: aWriteStream
- 	"Store the given form on a file of the given name."
- 
- 	| writer |
- 	writer := self on: aWriteStream.
- 	Cursor write showWhile: [writer nextPutImage: aForm].
- 	writer close.
- !

Item was removed:
- ----- Method: ImageReadWriter class>>typicalFileExtensions (in category 'image reading/writing') -----
- typicalFileExtensions
- 	"Answer a collection of file extensions (lowercase) which files that I can read might commonly have"
- 	^#()!

Item was removed:
- ----- Method: ImageReadWriter class>>understandsImageFormat: (in category 'image reading/writing') -----
- understandsImageFormat: aStream 
- 	^[(self new on: aStream) understandsImageFormat] on: Error do:[:ex| ex return: false]!

Item was removed:
- ----- Method: ImageReadWriter>>atEnd (in category 'stream access') -----
- atEnd
- 
- 	^stream atEnd!

Item was removed:
- ----- Method: ImageReadWriter>>changePadOfBits:width:height:depth:from:to: (in category 'private') -----
- changePadOfBits: bits width: width height: height depth: depth from: oldPad
- to: newPad
- 	"Change padding size of bits."
- 
- 	| srcRowByteSize dstRowByteSize newBits srcRowBase rowEndOffset |
- 	(#(8 16 32) includes: oldPad)
- 		ifFalse: [^self error: ('Invalid pad: {1}' translated format: {oldPad})].
- 	(#(8 16 32) includes: newPad)
- 		ifFalse: [^self error: ('Invalid pad: {1}' translated format: {newPad})].
- 	srcRowByteSize := width * depth + oldPad - 1 // oldPad * (oldPad / 8).
- 	srcRowByteSize * height = bits size
- 		ifFalse: [^self error: 'Incorrect bitmap array size.' translated].
- 	dstRowByteSize := width * depth + newPad - 1 // newPad * (newPad / 8).
- 	newBits := ByteArray new: dstRowByteSize * height.
- 	srcRowBase := 1.
- 	rowEndOffset := dstRowByteSize - 1.
- 	1 to: newBits size by: dstRowByteSize do:
- 		[:dstRowBase |
- 		newBits replaceFrom: dstRowBase
- 			to: dstRowBase + rowEndOffset
- 			with: bits
- 			startingAt: srcRowBase.
- 		srcRowBase := srcRowBase + srcRowByteSize].
- 	^newBits!

Item was removed:
- ----- Method: ImageReadWriter>>close (in category 'stream access') -----
- close
- 	
- 	stream close!

Item was removed:
- ----- Method: ImageReadWriter>>contents (in category 'stream access') -----
- contents
- 
- 	^stream contents!

Item was removed:
- ----- Method: ImageReadWriter>>cr (in category 'stream access') -----
- cr
- 
- 	^stream nextPut: Character cr asInteger!

Item was removed:
- ----- Method: ImageReadWriter>>hasMagicNumber: (in category 'private') -----
- hasMagicNumber: aByteArray
- 	| position |
- 	position := stream position.
- 	((stream size - position) >= aByteArray size and:
- 	[(stream next: aByteArray size)  = aByteArray])
- 		ifTrue: [^true].
- 	stream position: position.
- 	^false!

Item was removed:
- ----- Method: ImageReadWriter>>lf (in category 'stream access') -----
- lf
- 	"PPM and PBM are used LF as CR."
- 
- 	^stream nextPut: Character lf asInteger!

Item was removed:
- ----- Method: ImageReadWriter>>next (in category 'stream access') -----
- next
- 
- 	^stream next!

Item was removed:
- ----- Method: ImageReadWriter>>next: (in category 'stream access') -----
- next: size
- 
- 	^stream next: size!

Item was removed:
- ----- Method: ImageReadWriter>>nextImage (in category 'accessing') -----
- nextImage
- 	"Dencoding an image on stream and answer the image."
- 
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: ImageReadWriter>>nextLong (in category 'stream access') -----
- nextLong
- 	"Read a 32-bit quantity from the input stream."
- 
- 	^(stream next bitShift: 24) + (stream next bitShift: 16) +
- 		(stream next bitShift: 8) + stream next!

Item was removed:
- ----- Method: ImageReadWriter>>nextLongPut: (in category 'stream access') -----
- nextLongPut: a32BitW
- 	"Write out a 32-bit integer as 32 bits."
- 
- 	stream nextPut: ((a32BitW bitShift: -24) bitAnd: 16rFF).
- 	stream nextPut: ((a32BitW bitShift: -16) bitAnd: 16rFF).
- 	stream nextPut: ((a32BitW bitShift: -8) bitAnd: 16rFF).
- 	stream nextPut: (a32BitW bitAnd: 16rFF).
- 	^a32BitW!

Item was removed:
- ----- Method: ImageReadWriter>>nextPut: (in category 'stream access') -----
- nextPut: aByte
- 
- 	^stream nextPut: aByte!

Item was removed:
- ----- Method: ImageReadWriter>>nextPutAll: (in category 'stream access') -----
- nextPutAll: aByteArray
- 
- 	^stream nextPutAll: aByteArray!

Item was removed:
- ----- Method: ImageReadWriter>>nextPutImage: (in category 'accessing') -----
- nextPutImage: anImage
- 	"Encoding anImage on stream."
- 
- 	^self subclassResponsibility!

Item was removed:
- ----- Method: ImageReadWriter>>nextWord (in category 'stream access') -----
- nextWord
- 	"Read a 16-bit quantity from the input stream."
- 
- 	^(stream next bitShift: 8) + stream next!

Item was removed:
- ----- Method: ImageReadWriter>>nextWordPut: (in category 'stream access') -----
- nextWordPut: a16BitW
- 	"Write out a 16-bit integer as 16 bits."
- 
- 	stream nextPut: ((a16BitW bitShift: -8) bitAnd: 16rFF).
- 	stream nextPut: (a16BitW bitAnd: 16rFF).
- 	^a16BitW!

Item was removed:
- ----- Method: ImageReadWriter>>on: (in category 'private') -----
- on: aStream
- 	stream := aStream.
- 	stream binary.!

Item was removed:
- ----- Method: ImageReadWriter>>peekFor: (in category 'stream access') -----
- peekFor: aValue
- 
- 	^stream peekFor: aValue!

Item was removed:
- ----- Method: ImageReadWriter>>position (in category 'stream access') -----
- position
- 
- 	^stream position!

Item was removed:
- ----- Method: ImageReadWriter>>position: (in category 'stream access') -----
- position: anInteger
- 
- 	^stream position: anInteger!

Item was removed:
- ----- Method: ImageReadWriter>>size (in category 'stream access') -----
- size
- 
- 	^stream size!

Item was removed:
- ----- Method: ImageReadWriter>>skip: (in category 'stream access') -----
- skip: anInteger
- 
- 	^stream skip: anInteger!

Item was removed:
- ----- Method: ImageReadWriter>>space (in category 'stream access') -----
- space
- 
- 	^stream nextPut: Character space asInteger!

Item was removed:
- ----- Method: ImageReadWriter>>tab (in category 'stream access') -----
- tab
- 
- 	^stream nextPut: Character tab asInteger!

Item was removed:
- ----- Method: ImageReadWriter>>understandsImageFormat (in category 'testing') -----
- understandsImageFormat
- 	"Test to see if the image stream format is understood by this decoder.
- 	This should be implemented in each subclass of ImageReadWriter so that
- 	a proper decoder can be selected without ImageReadWriter having to know
- 	about all possible image file types."
- 
- 	^ false!

Item was removed:
- ----- Method: ImageReadWriter>>unpackBits:depthTo8From:with:height:pad: (in category 'private') -----
- unpackBits: bits depthTo8From: depth with: width height: height pad: pad
- 	"Unpack bits of depth 1, 2, or 4 image to it of depth 8 image."
- 
- 	| bitMask pixelInByte bitsWidth upBitsWidth stopWidth
- 	 trailingSize upBits bitIndex upBitIndex val |
- 	(#(1 2 4) includes: depth)
- 		ifFalse: [^self error: 'depth must be 1, 2, or 4' translated].
- 	(#(8 16 32) includes: pad)
- 		ifFalse: [^self error: 'pad must be 8, 16, or 32' translated].
- 	bitMask := (1 bitShift: depth) - 1.
- 	pixelInByte := 8 / depth.
- 	bitsWidth := width * depth + pad - 1 // pad * (pad / 8).
- 	upBitsWidth := width * 8 + pad - 1 // pad * (pad / 8).
- 	stopWidth := width * depth + 7 // 8.
- 	trailingSize := width - (stopWidth - 1 * pixelInByte).
- 	upBits := ByteArray new: upBitsWidth * height.
- 	1 to: height do: [:i |
- 		bitIndex := i - 1 * bitsWidth.
- 		upBitIndex := i - 1 * upBitsWidth.
- 		1 to: stopWidth - 1 do: [:j |
- 			val := bits at: (bitIndex := bitIndex + 1).
- 			upBitIndex := upBitIndex + pixelInByte.
- 			1 to: pixelInByte do: [:k |
- 				upBits at: (upBitIndex - k + 1) put: (val bitAnd: bitMask).
- 				val := val bitShift: depth negated]].
- 		val := (bits at: (bitIndex := bitIndex + 1))
- 				bitShift: depth negated * (pixelInByte - trailingSize).
- 		upBitIndex := upBitIndex + trailingSize.
- 		1 to: trailingSize do: [:k |
- 			upBits at: (upBitIndex - k + 1) put: (val bitAnd: bitMask).
- 			val := val bitShift: depth negated]].
- 	^ upBits
- !

Item was removed:
- DisplayObject subclass: #InfiniteForm
- 	instanceVariableNames: 'patternForm'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Display Objects'!
- 
- !InfiniteForm commentStamp: '<historical>' prior: 0!
- I represent a Form obtained by replicating a pattern form indefinitely in all directions.!

Item was removed:
- ----- Method: InfiniteForm class>>with: (in category 'instance creation') -----
- with: aForm 
- 	"Answer an instance of me whose pattern form is the argument, aForm."
- 
- 	^self new form: aForm!

Item was removed:
- ----- Method: InfiniteForm>>addFillStyleMenuItems:hand:from: (in category 'Morphic menu') -----
- addFillStyleMenuItems: aMenu hand: aHand from: aMorph
- 	"Add the items for changing the current fill style of the receiver"
- 
- 	"prevents a walkback when control menu is built for morph with me as color"!

Item was removed:
- ----- Method: InfiniteForm>>asColor (in category 'converting') -----
- asColor
- 	^ patternForm dominantColor!

Item was removed:
- ----- Method: InfiniteForm>>asForm (in category 'converting') -----
- asForm
- 	^ patternForm!

Item was removed:
- ----- Method: InfiniteForm>>bitPatternForDepth: (in category 'fillstyle protocol') -----
- bitPatternForDepth: suspectedDepth
- 	^ patternForm!

Item was removed:
- ----- Method: InfiniteForm>>colorForInsets (in category 'displaying') -----
- colorForInsets
- 	^ Color transparent!

Item was removed:
- ----- Method: InfiniteForm>>computeBoundingBox (in category 'display box access') -----
- computeBoundingBox 
- 	"Refer to the comment in DisplayObject|computeBoundingBox."
- 
- 	^0 @ 0 corner: SmallInteger maxVal @ SmallInteger maxVal!

Item was removed:
- ----- Method: InfiniteForm>>direction (in category 'fillstyle protocol') -----
- direction
- 	^patternForm width @ 0!

Item was removed:
- ----- Method: InfiniteForm>>displayOn:at:clippingBox:rule:fillColor: (in category 'displaying') -----
- displayOn: aDisplayMedium at: aDisplayPoint clippingBox: clipRectangle rule: ruleInteger fillColor: aForm
- 	"This is the real display message, but it doesn't get used until the new
- 	display protocol is installed."
- 	| targetBox patternBox bb |
- 	(patternForm isForm) ifFalse:
- 		[^ aDisplayMedium fill: clipRectangle rule: ruleInteger fillColor: patternForm].
- 
- 	"Do it iteratively"
- 	targetBox := aDisplayMedium boundingBox intersect: clipRectangle.
- 	patternBox := patternForm boundingBox.
- 	bb := BitBlt destForm: aDisplayMedium sourceForm: patternForm fillColor: aForm
- 		combinationRule: ruleInteger destOrigin: 0 at 0 sourceOrigin: 0 at 0
- 		extent: patternBox extent clipRect: clipRectangle.
- 	bb colorMap:
- 		(patternForm colormapIfNeededFor: aDisplayMedium).
- 	(targetBox left truncateTo: patternBox width)
- 		to: targetBox right - 1 by: patternBox width do:
- 		[:x |
- 		(targetBox top truncateTo: patternBox height)
- 			to: targetBox bottom - 1 by: patternBox height do:
- 			[:y |
- 			bb destOrigin: x at y; copyBits]]!

Item was removed:
- ----- Method: InfiniteForm>>displayOnPort:at: (in category 'displaying') -----
- displayOnPort: aPort at: offset
- 
- 	| targetBox patternBox savedMap top left |
- 
- 	self flag: #bob.
- 
- 	"this *may* not get called at the moment. I have been trying to figure out the right way for this to work and am using #displayOnPort:offsetBy: as my current offering - Bob"
- 
- 	(patternForm isForm) ifFalse: [
- 		"patternForm is a Pattern or Color; just use it as a mask for BitBlt"
- 		^ aPort fill: aPort clipRect fillColor: patternForm rule: Form over].
- 
- 	"do it iteratively"
- 	targetBox := aPort clipRect.
- 	patternBox := patternForm boundingBox.
- 	savedMap := aPort colorMap.
- 	aPort sourceForm: patternForm;
- 		fillColor: nil;
- 		combinationRule: Form paint;
- 		sourceRect: (0 at 0 extent: patternBox extent);
- 		colorMap: (patternForm colormapIfNeededFor: aPort destForm).
- 	top := (targetBox top truncateTo: patternBox height) "- (offset y \\ patternBox height)".
- 	left :=  (targetBox left truncateTo: patternBox width) "- (offset x \\ patternBox width)".
- 	left to: (targetBox right - 1) by: patternBox width do:
- 		[:x | top to: (targetBox bottom - 1) by: patternBox height do:
- 			[:y | aPort destOrigin: x at y; copyBits]].
- 	aPort colorMap: savedMap.
- !

Item was removed:
- ----- Method: InfiniteForm>>displayOnPort:offsetBy: (in category 'displaying') -----
- displayOnPort: aPort offsetBy: offset
- 
- 	| targetBox patternBox savedMap top left |
- 
- 	"this version tries to get the form aligned where the user wants it and not just aligned with the cliprect"
- 
- 	(patternForm isForm) ifFalse: [
- 		"patternForm is a Pattern or Color; just use it as a mask for BitBlt"
- 		^ aPort fill: aPort clipRect fillColor: patternForm rule: Form over].
- 
- 	"do it iteratively"
- 	targetBox := aPort clipRect.
- 	patternBox := patternForm boundingBox.
- 	savedMap := aPort colorMap.
- 	aPort sourceForm: patternForm;
- 		fillColor: nil;
- 		combinationRule: Form paint;
- 		sourceRect: (0 at 0 extent: patternBox extent);
- 		colorMap: (patternForm colormapIfNeededFor: aPort destForm).
- 	top := (targetBox top truncateTo: patternBox height) + offset y.
- 	left :=  (targetBox left truncateTo: patternBox width) + offset x.
- 
- 	left to: (targetBox right - 1) by: patternBox width do:
- 		[:x | top to: (targetBox bottom - 1) by: patternBox height do:
- 			[:y | aPort destOrigin: x at y; copyBits]].
- 	aPort colorMap: savedMap.
- !

Item was removed:
- ----- Method: InfiniteForm>>dominantColor (in category 'accessing') -----
- dominantColor
- 	^ patternForm dominantColor!

Item was removed:
- ----- Method: InfiniteForm>>form (in category 'fillstyle protocol') -----
- form
- 	"Bitmap fills respond to #form"
- 	^patternForm!

Item was removed:
- ----- Method: InfiniteForm>>form: (in category 'private') -----
- form: aForm
- 
- 	patternForm := aForm!

Item was removed:
- ----- Method: InfiniteForm>>isBitmapFill (in category 'fillstyle protocol') -----
- isBitmapFill
- 	^true!

Item was removed:
- ----- Method: InfiniteForm>>isGradientFill (in category 'fillstyle protocol') -----
- isGradientFill
- 	^false!

Item was removed:
- ----- Method: InfiniteForm>>isOrientedFill (in category 'fillstyle protocol') -----
- isOrientedFill
- 	^true!

Item was removed:
- ----- Method: InfiniteForm>>isSolidFill (in category 'fillstyle protocol') -----
- isSolidFill
- 	^false!

Item was removed:
- ----- Method: InfiniteForm>>isTiled (in category 'fillstyle protocol') -----
- isTiled
- 	"Return true if the receiver should be drawn as a tiled pattern"
- 	^true!

Item was removed:
- ----- Method: InfiniteForm>>isTranslucent (in category 'fillstyle protocol') -----
- isTranslucent
- 	"Return true since the bitmap may be translucent and we don't really want to check"
- 	^true!

Item was removed:
- ----- Method: InfiniteForm>>normal (in category 'fillstyle protocol') -----
- normal
- 	^0 @ patternForm height!

Item was removed:
- ----- Method: InfiniteForm>>offset (in category 'accessing') -----
- offset 
- 	"Refer to the comment in DisplayObject|offset."
- 
- 	^0 @ 0!

Item was removed:
- ----- Method: InfiniteForm>>origin (in category 'fillstyle protocol') -----
- origin
- 	^0 at 0!

Item was removed:
- ----- Method: InfiniteForm>>origin: (in category 'fillstyle protocol') -----
- origin: aPoint
- 	"Ignored"
- !

Item was removed:
- ----- Method: InfiniteForm>>raisedColor (in category 'displaying') -----
- raisedColor
- 	^ Color transparent!

Item was removed:
- ----- Method: Integer>>asColorOfDepth: (in category '*Graphics-converting') -----
- asColorOfDepth: d
- 	"Return a color value representing the receiver as color of the given depth"
- 	^Color colorFromPixelValue: self depth: d!

Item was removed:
- Object subclass: #JPEGColorComponent
- 	instanceVariableNames: 'currentX currentY hSampleFactor vSampleFactor mcuBlocks widthInBlocks heightInBlocks dctSize mcuWidth mcuHeight priorDCValue id qTableIndex dcTableIndex acTableIndex'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!
- 
- !JPEGColorComponent commentStamp: '<historical>' prior: 0!
- I represent a single component of color in JPEG YCbCr color space.  I can accept a list of blocks in my component from the current MCU, then stream the samples from this block for use in color conversion.  I also store the running DC sample value for my component, used by the Huffman decoder.
- 
- The following layout is fixed for the JPEG primitives to work:
- 	currentX 		<SmallInteger>
- 	currentY 		<SmallInteger>
- 	hSampleFactor 	<SmallInteger>
- 	vSampleFactor 	<SmallInteger>
- 	mcuBlocks 		<Array of: <IntegerArray of: DCTSize2 * Integer>>
- 	widthInBlocks 	<SmallInteger>
- 	heightInBlocks 	<SmallInteger>
- 	dctSize 			<SmallInteger>
- 	mcuWidth 		<SmallInteger>
- 	mcuHeight 		<SmallInteger>
- 	priorDCValue 	<SmallInteger>
- !

Item was removed:
- ----- Method: JPEGColorComponent>>acTableIndex (in category 'accessing') -----
- acTableIndex
- 
- 	^acTableIndex!

Item was removed:
- ----- Method: JPEGColorComponent>>acTableIndex: (in category 'accessing') -----
- acTableIndex: anInteger
- 
- 	acTableIndex := anInteger!

Item was removed:
- ----- Method: JPEGColorComponent>>dcTableIndex (in category 'accessing') -----
- dcTableIndex
- 
- 	^dcTableIndex!

Item was removed:
- ----- Method: JPEGColorComponent>>dcTableIndex: (in category 'accessing') -----
- dcTableIndex: anInteger
- 
- 	dcTableIndex := anInteger!

Item was removed:
- ----- Method: JPEGColorComponent>>heightInBlocks (in category 'accessing') -----
- heightInBlocks
- 
- 	^heightInBlocks!

Item was removed:
- ----- Method: JPEGColorComponent>>heightInBlocks: (in category 'accessing') -----
- heightInBlocks: anInteger
- 
- 	heightInBlocks := anInteger!

Item was removed:
- ----- Method: JPEGColorComponent>>id (in category 'accessing') -----
- id
- 
- 	^id!

Item was removed:
- ----- Method: JPEGColorComponent>>id: (in category 'accessing') -----
- id: anObject
- 
- 	id := anObject!

Item was removed:
- ----- Method: JPEGColorComponent>>initializeSampleStreamBlocks: (in category 'sample streaming') -----
- initializeSampleStreamBlocks: aCollection
- 
- 	mcuBlocks := aCollection.
- 	self resetSampleStream!

Item was removed:
- ----- Method: JPEGColorComponent>>mcuWidth:mcuHeight:dctSize: (in category 'accessing') -----
- mcuWidth: mw mcuHeight: mh dctSize: ds
- 
- 	mcuWidth := mw.
- 	mcuHeight := mh.
- 	dctSize := ds.
- 	hSampleFactor := mcuWidth // widthInBlocks.
- 	vSampleFactor := mcuHeight // heightInBlocks!

Item was removed:
- ----- Method: JPEGColorComponent>>nextSample (in category 'sample streaming') -----
- nextSample
- 
- 	| dx dy blockIndex sampleIndex sample |
- 	dx := currentX // hSampleFactor.
- 	dy := currentY // vSampleFactor.
- 	blockIndex := dy // dctSize * widthInBlocks + (dx // dctSize) + 1.
- 	sampleIndex := dy \\ dctSize * dctSize + (dx \\ dctSize) + 1.
- 	sample := (mcuBlocks at: blockIndex) at: sampleIndex.
- 	currentX := currentX + 1.
- 	currentX < (mcuWidth * dctSize)
- 		ifFalse:
- 			[currentX := 0.
- 			currentY := currentY + 1].
- 	^ sample!

Item was removed:
- ----- Method: JPEGColorComponent>>priorDCValue: (in category 'accessing') -----
- priorDCValue: aNumber
- 
- 	priorDCValue := aNumber!

Item was removed:
- ----- Method: JPEGColorComponent>>qTableIndex (in category 'accessing') -----
- qTableIndex
- 	^qTableIndex!

Item was removed:
- ----- Method: JPEGColorComponent>>qTableIndex: (in category 'accessing') -----
- qTableIndex: anInteger
- 
- 	qTableIndex := anInteger!

Item was removed:
- ----- Method: JPEGColorComponent>>resetSampleStream (in category 'sample streaming') -----
- resetSampleStream
- 
- 	currentX := 0.
- 	currentY := 0!

Item was removed:
- ----- Method: JPEGColorComponent>>totalMcuBlocks (in category 'accessing') -----
- totalMcuBlocks
- 
- 	^ heightInBlocks * widthInBlocks!

Item was removed:
- ----- Method: JPEGColorComponent>>updateDCValue: (in category 'accessing') -----
- updateDCValue: aNumber
- 
- 	priorDCValue := priorDCValue + aNumber.
- 	^priorDCValue!

Item was removed:
- ----- Method: JPEGColorComponent>>widthInBlocks (in category 'accessing') -----
- widthInBlocks
- 
- 	^widthInBlocks!

Item was removed:
- ----- Method: JPEGColorComponent>>widthInBlocks: (in category 'accessing') -----
- widthInBlocks: anInteger
- 
- 	widthInBlocks := anInteger!

Item was removed:
- Object subclass: #JPEGHuffmanTable
- 	instanceVariableNames: 'bits values mincode maxcode valptr lookaheadBits lookaheadSymbol'
- 	classVariableNames: 'BitBufferSize Lookahead'
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!
- 
- !JPEGHuffmanTable commentStamp: '<historical>' prior: 0!
- I represent the table of values used to decode Huffman entropy-encoded bitstreams.  From the JFIF file header entropy values, I build a derived table of codes and values for faster decoding.!

Item was removed:
- ----- Method: JPEGHuffmanTable class>>initialize (in category 'initialization') -----
- initialize
- 
- 	Lookahead := 8.
- 	BitBufferSize := 16!

Item was removed:
- ----- Method: JPEGHuffmanTable class>>lookahead (in category 'constants') -----
- lookahead
- 
- 	^ Lookahead!

Item was removed:
- ----- Method: JPEGHuffmanTable>>bits: (in category 'accessing') -----
- bits: anObject
- 
- 	bits := anObject!

Item was removed:
- ----- Method: JPEGHuffmanTable>>lookaheadBits (in category 'accessing') -----
- lookaheadBits
- 	^lookaheadBits!

Item was removed:
- ----- Method: JPEGHuffmanTable>>lookaheadSymbol (in category 'accessing') -----
- lookaheadSymbol
- 	^lookaheadSymbol!

Item was removed:
- ----- Method: JPEGHuffmanTable>>makeDerivedTables (in category 'computation') -----
- makeDerivedTables
- 
- 	| huffSize huffCode code si index lookbits |
- 	mincode := Array new: 16.
- 	maxcode := Array new: 17.
- 	valptr := Array new: 17.
- 	huffSize := OrderedCollection new.
- 	1 to: 16 do: [:l | 1 to: (bits at: l) do: [:i | huffSize add: l]].
- 	huffSize add: 0.
- 	code := 0.
- 	huffCode := Array new: huffSize size.
- 	si := huffSize at: 1.
- 	index := 1.
- 	[(huffSize at: index) ~= 0] whileTrue:
- 		[[(huffSize at: index) = si] whileTrue:
- 			[huffCode at: index put: code.
- 			index := index + 1.
- 			code := code + 1].
- 		code := code << 1.
- 		si := si + 1].
- 
- 	index := 1.
- 	1 to: 16 do:
- 		[:l |
- 		(bits at: l) ~= 0
- 			ifTrue:
- 				[valptr at: l put: index.
- 				mincode at: l put: (huffCode at: index).
- 				index := index + (bits at: l).
- 				maxcode at: l put: (huffCode at: index-1)]
- 			ifFalse:
- 				[maxcode at: l put: -1]].
- 	maxcode at: 17 put: 16rFFFFF.
- 
- 	lookaheadBits := (Array new: 1 << Lookahead) atAllPut: 0.
- 	lookaheadSymbol := Array new: 1 << Lookahead.
- 	index := 1.
- 	1 to: Lookahead do:
- 		[:l |
- 		1 to: (bits at: l) do:
- 			[:i |
- 			lookbits := (huffCode at: index) << (Lookahead - l) + 1.
- 			(1 << (Lookahead - l) to: 1 by: -1) do:
- 				[:ctr |
- 				lookaheadBits at: lookbits put: l.
- 				lookaheadSymbol at: lookbits put: (values at: index).
- 				lookbits := lookbits + 1].
- 			index := index + 1]]!

Item was removed:
- ----- Method: JPEGHuffmanTable>>maxcode (in category 'accessing') -----
- maxcode
- 	^maxcode!

Item was removed:
- ----- Method: JPEGHuffmanTable>>valueForCode:length: (in category 'computation') -----
- valueForCode: code length: length
- 
- 	^ values at: ((valptr at: length) + code - (mincode at: length))!

Item was removed:
- ----- Method: JPEGHuffmanTable>>values: (in category 'accessing') -----
- values: anObject
- 
- 	values := anObject!

Item was removed:
- ReadStream subclass: #JPEGReadStream
- 	instanceVariableNames: 'bitBuffer bitsInBuffer'
- 	classVariableNames: 'MaxBits'
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!
- 
- !JPEGReadStream commentStamp: '<historical>' prior: 0!
- Encapsulates huffman encoded access to JPEG data.
- 
- The following layout is fixed for the JPEG primitives to work:
- 
- 	collection	<ByteArray | String>
- 	position		<SmallInteger>
- 	readLimit	<SmallInteger>
- 	bitBuffer	<SmallInteger>
- 	bitsInBuffer	<SmallInteger>!

Item was removed:
- ----- Method: JPEGReadStream class>>initialize (in category 'class initialization') -----
- initialize
- 	"JPEGReadStream initialize"
- 	MaxBits := 16.!

Item was removed:
- ----- Method: JPEGReadStream>>buildLookupTable:counts: (in category 'huffman trees') -----
- buildLookupTable: values counts: counts
- 	| min max |
- 	min := max := nil.
- 	1 to: counts size do:[:i|
- 		(counts at: i) = 0 ifFalse:[
- 			min ifNil:[min := i-1].
- 			max := i]].
- 	^self
- 		createHuffmanTables: values 
- 		counts: {0},counts 
- 		from: min+1 
- 		to: max.!

Item was removed:
- ----- Method: JPEGReadStream>>createHuffmanTables:counts:from:to: (in category 'huffman trees') -----
- createHuffmanTables: values counts: counts from: minBits to: maxBits
- 	"Create the actual tables"
- 	| table tableStart tableSize tableEnd 
- 	valueIndex tableStack numValues deltaBits maxEntries
- 	lastTable lastTableStart tableIndex lastTableIndex |
- 
- 	table := WordArray new: ((4 bitShift: minBits) max: 16).
- 
- 	"Create the first entry - this is a dummy.
- 	It gives us information about how many bits to fetch initially."
- 	table at: 1 put: (minBits bitShift: 24) + 2. "First actual table starts at index 2"
- 
- 	"Create the first table from scratch."
- 	tableStart := 2. "See above"
- 	tableSize := 1 bitShift: minBits.
- 	tableEnd := tableStart + tableSize.
- 	"Store the terminal symbols"
- 	valueIndex := (counts at: minBits+1).
- 	tableIndex := 0.
- 	1 to: valueIndex do:[:i|
- 		table at: tableStart + tableIndex put: (values at: i).
- 		tableIndex := tableIndex + 1].
- 	"Fill up remaining entries with invalid entries"
- 	tableStack := OrderedCollection new: 10. "Should be more than enough"
- 	tableStack addLast: 
- 		(Array 
- 			with: minBits	"Number of bits (e.g., depth) for this table"
- 			with: tableStart	"Start of table"
- 			with: tableIndex "Next index in table"
- 			with: minBits	"Number of delta bits encoded in table"
- 			with: tableSize - valueIndex "Entries remaining in table").
- 	"Go to next value index"
- 	valueIndex := valueIndex + 1.
- 	"Walk over remaining bit lengths and create new subtables"
- 	minBits+1 to: maxBits do:[:bits|
- 		numValues := counts at: bits+1.
- 		[numValues > 0] whileTrue:["Create a new subtable"
- 			lastTable := tableStack last.
- 			lastTableStart := lastTable at: 2.
- 			lastTableIndex := lastTable at: 3.
- 			deltaBits := bits - (lastTable at: 1).
- 			"Make up a table of deltaBits size"
- 			tableSize := 1 bitShift: deltaBits.
- 			tableStart := tableEnd.
- 			tableEnd := tableEnd + tableSize.
- 			[tableEnd > table size ]
- 				whileTrue:[table := self growHuffmanTable: table].
- 			"Connect to last table"
- 			self assert:[(table at: lastTableStart + lastTableIndex) = 0]."Entry must be unused"
- 			table at: lastTableStart + lastTableIndex put: (deltaBits bitShift: 24) + tableStart.
- 			lastTable at: 3 put: lastTableIndex+1.
- 			lastTable at: 5 put: (lastTable at: 5) - 1.
- 			self assert:[(lastTable at: 5) >= 0]. "Don't exceed tableSize"
- 			"Store terminal values"
- 			maxEntries := numValues min: tableSize.
- 			tableIndex := 0.
- 			1 to: maxEntries do:[:i|
- 				table at: tableStart + tableIndex put: (values at: valueIndex).
- 				valueIndex := valueIndex + 1.
- 				numValues := numValues - 1.
- 				tableIndex := tableIndex+1].
- 			"Check if we have filled up the current table completely"
- 			maxEntries = tableSize ifTrue:[
- 				"Table has been filled. Back up to the last table with space left."
- 				[tableStack isEmpty not and:[(tableStack last at: 5) = 0]]
- 						whileTrue:[tableStack removeLast].
- 			] ifFalse:[
- 				"Table not yet filled. Put it back on the stack."
- 				tableStack addLast:
- 					(Array
- 						with: bits		"Nr. of bits in this table"
- 						with: tableStart	"Start of table"
- 						with: tableIndex "Index in table"
- 						with: deltaBits	"delta bits of table"
- 						with: tableSize - maxEntries "Unused entries in table").
- 			].
- 		].
- 	].
- 	 ^table copyFrom: 1 to: tableEnd-1!

Item was removed:
- ----- Method: JPEGReadStream>>decodeValueFrom: (in category 'huffman trees') -----
- decodeValueFrom: table
- 	"Decode the next value in the receiver using the given huffman table."
- 	| bits bitsNeeded tableIndex value |
- 	bitsNeeded := (table at: 1) bitShift: -24.	"Initial bits needed"
- 	tableIndex := 2.							"First real table"
- 	[bits := self getBits: bitsNeeded.			"Get bits"
- 	value := table at: (tableIndex + bits).		"Lookup entry in table"
- 	(value bitAnd: 16r3F000000) = 0] 			"Check if it is a non-leaf node"
- 		whileFalse:["Fetch sub table"
- 			tableIndex := value bitAnd: 16rFFFF.	"Table offset in low 16 bit"
- 			bitsNeeded := (value bitShift: -24) bitAnd: 255. "Additional bits in high 8 bit"
- 			bitsNeeded > MaxBits ifTrue:[^self error: 'Invalid huffman table entry' translated]].
- 	^value!

Item was removed:
- ----- Method: JPEGReadStream>>fillBuffer (in category 'accessing') -----
- fillBuffer
- 
- 	| byte |
- 	[bitsInBuffer <= 16]
- 		whileTrue:[
- 			byte := self next.
- 			(byte = 16rFF and: [(self peekFor: 16r00) not])
- 					ifTrue:
- 						[self position: self position - 1.
- 						^0].
- 			bitBuffer := (bitBuffer bitShift: 8) bitOr: byte.
- 			bitsInBuffer := bitsInBuffer + 8].
- 	^ bitsInBuffer!

Item was removed:
- ----- Method: JPEGReadStream>>getBits: (in category 'accessing') -----
- getBits: requestedBits
- 	| value |
- 	requestedBits > bitsInBuffer ifTrue:[
- 		self fillBuffer.
- 		requestedBits > bitsInBuffer ifTrue:[
- 			self error: 'not enough bits available to decode' translated]].
- 	value := bitBuffer bitShift: (requestedBits - bitsInBuffer).
- 	bitBuffer := bitBuffer bitAnd: (1 bitShift: (bitsInBuffer - requestedBits)) -1.
- 	bitsInBuffer := bitsInBuffer - requestedBits.
- 	^ value!

Item was removed:
- ----- Method: JPEGReadStream>>growHuffmanTable: (in category 'huffman trees') -----
- growHuffmanTable: table
- 	| newTable |
- 	newTable := table species new: table size * 2.
- 	newTable replaceFrom: 1 to: table size with: table startingAt: 1.
- 	^newTable!

Item was removed:
- ----- Method: JPEGReadStream>>nextByte (in category 'accessing') -----
- nextByte
- 	^self next asInteger!

Item was removed:
- ----- Method: JPEGReadStream>>nextBytes: (in category 'accessing') -----
- nextBytes: n
- 	^(self next: n) asByteArray!

Item was removed:
- ----- Method: JPEGReadStream>>reset (in category 'accessing') -----
- reset
- 	super reset.
- 	self resetBitBuffer!

Item was removed:
- ----- Method: JPEGReadStream>>resetBitBuffer (in category 'accessing') -----
- resetBitBuffer
- 	bitBuffer := 0.
- 	bitsInBuffer := 0.
- !

Item was removed:
- ImageReadWriter subclass: #JPEGReadWriter
- 	instanceVariableNames: 'width height components currentComponents qTable hACTable hDCTable restartInterval restartsToGo mcuWidth mcuHeight mcusPerRow mcuRowsInScan mcuMembership mcuSampleBuffer mcuImageBuffer majorVersion minorVersion dataPrecision densityUnit xDensity yDensity ss se ah al sosSeen residuals ditherMask'
- 	classVariableNames: 'ConstBits DCTK1 DCTK2 DCTK3 DCTK4 DCTSize DCTSize2 DitherMasks FIXn0n298631336 FIXn0n34414 FIXn0n390180644 FIXn0n541196100 FIXn0n71414 FIXn0n765366865 FIXn0n899976223 FIXn1n175875602 FIXn1n40200 FIXn1n501321110 FIXn1n77200 FIXn1n847759065 FIXn1n961570560 FIXn2n053119869 FIXn2n562915447 FIXn3n072711026 FloatSampleOffset HuffmanTableSize JFIFMarkerParser JPEGNaturalOrder MaxSample Pass1Bits Pass1Div Pass2Div QTableScaleFactor QuantizationTableSize SampleOffset'
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!
- 
- !JPEGReadWriter commentStamp: '<historical>' prior: 0!
- I am a subclass of ImageReadWriter that understands JFIF file streams, and can decode JPEG images.
- This code is based upon the Independent Joint Photographic Experts Group (IJPEG) software, originally written in C by Tom Lane, Philip Gladstone, Luis Ortiz, Jim Boucher, Lee Crocker, Julian Minguillon, George Phillips, Davide Rossi, Ge' Weijers, and other members of the Independent JPEG Group.
- 
- !

Item was removed:
- ----- Method: JPEGReadWriter class>>initialize (in category 'initialization') -----
- initialize
- 	"JPEGReadWriter initialize"
- 	"general constants"
- 	DCTSize := 8.
- 	MaxSample := (2 raisedToInteger: DCTSize) - 1.
- 	SampleOffset := MaxSample // 2.
- 	FloatSampleOffset := SampleOffset asFloat.
- 	DCTSize2 := DCTSize squared.
- 	QuantizationTableSize := 4.
- 	HuffmanTableSize := 4.
- 
- 	"floating-point Inverse Discrete Cosine Transform (IDCT) constants"
- 	ConstBits := 13.
- 	Pass1Bits := 2.
- 	DCTK1 := 2 sqrt.
- 	DCTK2 := 1.847759065.
- 	DCTK3 := 1.082392200.
- 	DCTK4 := -2.613125930.
- 	Pass1Div := 1 bitShift: ConstBits - Pass1Bits.
- 	Pass2Div := 1 bitShift: ConstBits + Pass1Bits + 3.
- 
- 	"fixed-point Inverse Discrete Cosine Transform (IDCT) constants"
- 	FIXn0n298631336 := 2446.
- 	FIXn0n390180644 := 3196.
- 	FIXn0n541196100 := 4433.
- 	FIXn0n765366865 := 6270.
- 	FIXn0n899976223 := 7373.
- 	FIXn1n175875602 := 9633.
- 	FIXn1n501321110 := 12299.
- 	FIXn1n847759065 := 15137.
- 	FIXn1n961570560 := 16069.
- 	FIXn2n053119869 := 16819.
- 	FIXn2n562915447 := 20995.
- 	FIXn3n072711026 := 25172.
- 
- 	"fixed-point color conversion constants"
- 	FIXn0n34414 := 22554.
- 	FIXn0n71414 := 46802.
- 	FIXn1n40200 := 91881.
- 	FIXn1n77200 :=  116130.
- 
- 	"reordering table from JPEG zig-zag order"
- 	JPEGNaturalOrder := #(
- 		1 2 9 17 10 3 4 11
- 		18 25 33 26 19 12 5 6
- 		13 20 27 34 41 49 42 35
- 		28 21 14 7 8 15 22 29
- 		36 43 50 57 58 51 44 37
- 		30 23 16 24 31 38 45 52
- 		59 60 53 46 39 32 40 47
- 		54 61 62 55 48 56 63 64).
- 
- 	"scale factors for the values in the Quantization Tables"
- 	QTableScaleFactor := (0 to: DCTSize-1) collect:
- 		[:k | k = 0
- 			ifTrue: [1.0]
- 			ifFalse: [(k * Float pi / 16) cos * 2 sqrt]].
- 
- 	"dithering masks"
- 	(DitherMasks := Dictionary new)
- 		add: 0 -> 0;
- 		add: 1 -> 127;
- 		add: 2 -> 63;
- 		add: 4 -> 63;
- 		add: 8 -> 31;
- 		add: 16 -> 7;
- 		add: 32 -> 0.
- 
- 	"dictionary of marker parsers"
- 	(JFIFMarkerParser := Dictionary new)
- 		add: (16r01 -> #parseNOP);
- 		add: (16rC0 -> #parseStartOfFile);
- 		add: (16rC4 -> #parseHuffmanTable);
- 		addAll: ((16rD0 to: 16rD7) collect: [:m | Association key: m value: #parseNOP]);
- 		add: (16rD8 -> #parseStartOfInput);
- 		add: (16rD9 -> #parseEndOfInput);
- 		add: (16rDA -> #parseStartOfScan);
- 		add: (16rDB -> #parseQuantizationTable);
- 		add: (16rDD -> #parseDecoderRestartInterval);
- 		add: (16rE0 -> #parseAPPn);
- 		add: (16rE1 -> #parseAPPn)!

Item was removed:
- ----- Method: JPEGReadWriter class>>typicalFileExtensions (in category 'image reading/writing') -----
- typicalFileExtensions
- 	"Answer a collection of file extensions (lowercase) which files that I can read might commonly have"
- 	^#('jpg' 'jpeg')!

Item was removed:
- ----- Method: JPEGReadWriter class>>understandsImageFormat: (in category 'image reading/writing') -----
- understandsImageFormat: aStream
- 	(JPEGReadWriter2 understandsImageFormat: aStream) ifTrue:[^false].
- 	aStream reset; binary.
- 	aStream next = 16rFF ifFalse: [^ false].
- 	aStream next = 16rD8 ifFalse: [^ false].
- 	^true!

Item was removed:
- ----- Method: JPEGReadWriter>>colorConvertFloatYCbCrMCU (in category 'colorspace conversion') -----
- colorConvertFloatYCbCrMCU
- 
- 	| ySampleStream crSampleStream cbSampleStream y cb cr red green blue bits |
- 	ySampleStream := currentComponents at: 1.
- 	cbSampleStream := currentComponents at: 2.
- 	crSampleStream := currentComponents at: 3.
- 	ySampleStream resetSampleStream.
- 	cbSampleStream resetSampleStream.
- 	crSampleStream resetSampleStream.
- 	bits := mcuImageBuffer bits.
- 	1 to: bits size do:
- 		[:i |
- 		y := ySampleStream nextSample.
- 		cb := cbSampleStream nextSample - FloatSampleOffset.
- 		cr := crSampleStream nextSample - FloatSampleOffset.
- 		red := self sampleFloatRangeLimit: (y + (1.40200 * cr)).
- 		green := self sampleFloatRangeLimit: (y - (0.34414 * cb) - (0.71414 * cr)).
- 		blue := self sampleFloatRangeLimit: (y + (1.77200 * cb)).
- 		bits at: i put: 16rFF000000 + (red << 16) + (green << 8) + blue].
- 	!

Item was removed:
- ----- Method: JPEGReadWriter>>colorConvertGrayscaleMCU (in category 'colorspace conversion') -----
- colorConvertGrayscaleMCU
- 
- 	| ySampleStream y bits |
- 	ySampleStream := currentComponents at: 1.
- 	ySampleStream resetSampleStream.
- 	bits := mcuImageBuffer bits.
- 	1 to: bits size do:
- 		[:i |
- 		y := (ySampleStream nextSample) + (residuals at: 2).
- 		y > MaxSample ifTrue: [y := MaxSample].
- 		residuals at: 2 put: (y bitAnd: ditherMask).
- 		y := y bitAnd: MaxSample - ditherMask.
- 		y < 1 ifTrue: [y := 1].
- 		bits at: i put: 16rFF000000 + (y<<16) + (y<<8) + y].
- 	!

Item was removed:
- ----- Method: JPEGReadWriter>>colorConvertIntYCbCrMCU (in category 'colorspace conversion') -----
- colorConvertIntYCbCrMCU
- 
- 	| ySampleStream crSampleStream cbSampleStream y cb cr red green blue bits |
- 	ySampleStream := currentComponents at: 1.
- 	cbSampleStream := currentComponents at: 2.
- 	crSampleStream := currentComponents at: 3.
- 	ySampleStream resetSampleStream.
- 	cbSampleStream resetSampleStream.
- 	crSampleStream resetSampleStream.
- 	bits := mcuImageBuffer bits.
- 	1 to: bits size do:
- 		[:i |
- 		y := ySampleStream nextSample.
- 		cb := cbSampleStream nextSample - SampleOffset.
- 		cr := crSampleStream nextSample - SampleOffset.
- 		red := y + ((FIXn1n40200 * cr) // 65536) + (residuals at: 1).
- 		red > MaxSample
- 			ifTrue: [red := MaxSample]
- 			ifFalse: [red < 0 ifTrue: [red := 0]].
- 		residuals at: 1 put: (red bitAnd: ditherMask).
- 		red := red bitAnd: MaxSample - ditherMask.
- 		red < 1 ifTrue: [red := 1].
- 		green := y - ((FIXn0n34414 * cb) // 65536) -
- 			((FIXn0n71414 * cr) // 65536) + (residuals at: 2).
- 		green > MaxSample
- 			ifTrue: [green := MaxSample]
- 			ifFalse: [green < 0 ifTrue: [green := 0]].
- 		residuals at: 2 put: (green bitAnd: ditherMask).
- 		green := green bitAnd: MaxSample - ditherMask.
- 		green < 1 ifTrue: [green := 1].
- 		blue := y + ((FIXn1n77200 * cb) // 65536) + (residuals at: 3).
- 		blue > MaxSample
- 			ifTrue: [blue := MaxSample]
- 			ifFalse: [blue < 0 ifTrue: [blue := 0]].
- 		residuals at: 3 put: (blue bitAnd: ditherMask).
- 		blue := blue bitAnd: MaxSample - ditherMask.
- 		blue < 1 ifTrue: [blue := 1].
- 		bits at: i put: 16rFF000000 + (red bitShift: 16) + (green bitShift: 8) + blue].
- 	!

Item was removed:
- ----- Method: JPEGReadWriter>>colorConvertMCU (in category 'colorspace conversion') -----
- colorConvertMCU
- 
- 	^ currentComponents size = 3
- 		ifTrue:
- 			[self useFloatingPoint
- 				ifTrue: [self colorConvertFloatYCbCrMCU]
- 				ifFalse: [self primColorConvertYCbCrMCU: currentComponents
- 								bits: mcuImageBuffer bits
- 								residuals: residuals
- 								ditherMask: ditherMask.]]
- 		ifFalse: [self primColorConvertGrayscaleMCU]!

Item was removed:
- ----- Method: JPEGReadWriter>>dctFloatRangeLimit: (in category 'dct') -----
- dctFloatRangeLimit: value
- 
- 	^ (value / 8.0) + FloatSampleOffset.!

Item was removed:
- ----- Method: JPEGReadWriter>>decodeBlockInto:component:dcTable:acTable: (in category 'huffman encoding') -----
- decodeBlockInto: anArray component: aColorComponent dcTable: huffmanDC acTable: huffmanAC
- 
- 	| byte i zeroCount |
- 	byte := stream decodeValueFrom: huffmanDC.
- 	byte ~= 0 ifTrue: [byte := self scaleAndSignExtend: ( self getBits: byte) inFieldWidth: byte].
- 	byte := aColorComponent updateDCValue: byte.
- 	anArray atAllPut: 0.
- 	anArray at: 1 put: byte.
- 	i := 2.
- 	[i <= DCTSize2] whileTrue:
- 		[byte := stream decodeValueFrom: huffmanAC.
- 		zeroCount := byte >> 4.
- 		byte := byte bitAnd: 16r0F.
- 		byte ~= 0
- 			ifTrue:
- 				[i := i + zeroCount.
- 				byte := self scaleAndSignExtend: ( self getBits: byte) inFieldWidth: byte.
- 				anArray at:	 (JPEGNaturalOrder at: i) put: byte]
- 			ifFalse:
- 				[zeroCount = 15 ifTrue: [i := i + zeroCount] ifFalse: [^ self]].
- 		i := i + 1]
- 		!

Item was removed:
- ----- Method: JPEGReadWriter>>decodeMCU (in category 'huffman encoding') -----
- decodeMCU
- 
- 	| comp ci |
- 	(restartInterval ~= 0 and: [restartsToGo = 0]) ifTrue: [self processRestart].
- 	1 to: mcuMembership size do:[:i|
- 		ci := mcuMembership at: i.
- 		comp := currentComponents at: ci.
- 		self
- 			primDecodeBlockInto: (mcuSampleBuffer at: i)
- 			component: comp
- 			dcTable: (hDCTable at: comp dcTableIndex)
- 			acTable: (hACTable at: comp acTableIndex)
- 			stream: stream.
- 	].
- 	restartsToGo := restartsToGo - 1.!

Item was removed:
- ----- Method: JPEGReadWriter>>getBits: (in category 'huffman encoding') -----
- getBits: requestedBits
- 	^stream getBits: requestedBits!

Item was removed:
- ----- Method: JPEGReadWriter>>hACTable (in category 'accessing') -----
- hACTable
- 
- 	hACTable ifNil: [hACTable := Array new: HuffmanTableSize].
- 	^ hACTable!

Item was removed:
- ----- Method: JPEGReadWriter>>hDCTable (in category 'accessing') -----
- hDCTable
- 
- 	hDCTable ifNil: [hDCTable := Array new: HuffmanTableSize].
- 	^ hDCTable!

Item was removed:
- ----- Method: JPEGReadWriter>>idctBlockFloat:component: (in category 'dct') -----
- idctBlockFloat: anArray component: aColorComponent
- 
- 	| t0 t1 t2 t3 t4 t5 t6 t7 t10 t11 t12 t13 z5 z10 z11 z12 z13 qt ws |
- 	qt := self qTable at: (aColorComponent qTableIndex).
- 	ws := Array new: DCTSize2.
- 
- 	"Pass 1: process columns from input, store into work array"
- 	1 to: DCTSize do: [:i |
- 		t0 := (anArray at: i) * (qt at: i).
- 		t1 := (anArray at: (DCTSize*2 + i)) * (qt at: (DCTSize*2 + i)).
- 		t2 := (anArray at: (DCTSize*4 + i)) * (qt at: (DCTSize*4 + i)).
- 		t3 := (anArray at: (DCTSize*6 + i)) * (qt at: (DCTSize*6 + i)).
- 		t10 := t0 + t2.
- 		t11 := t0 - t2.
- 		t13 := t1 + t3.
- 		t12 := (t1 - t3) * DCTK1 - t13.
- 		t0 := t10 + t13.
- 		t3 := t10 - t13.
- 		t1 := t11 + t12.
- 		t2 := t11 - t12.
- 		t4 := (anArray at: (DCTSize + i)) * (qt at: (DCTSize + i)).
- 		t5 := (anArray at: (DCTSize*3 + i)) * (qt at: (DCTSize*3 + i)).
- 		t6 := (anArray at: (DCTSize*5 + i)) * (qt at: (DCTSize*5 + i)).
- 		t7 := (anArray at: (DCTSize*7 + i)) * (qt at: (DCTSize*7 + i)).
- 		z13 := t6 + t5.
- 		z10 := t6 - t5.
- 		z11 := t4 + t7.
- 		z12 := t4 - t7.
- 		t7 := z11 + z13.
- 		t11 := (z11 - z13) * DCTK1.
- 		z5 := (z10 + z12) * DCTK2.
- 		t10 := DCTK3 * z12 - z5.
- 		t12 := DCTK4 * z10 + z5.
- 		t6 := t12 - t7.
- 		t5 := t11 - t6.
- 		t4 := t10 + t5.
- 		ws at: i put: t0 + t7.
- 		ws at: (DCTSize*7 + i) put: t0 - t7.
- 		ws at: (DCTSize + i) put: t1 + t6.
- 		ws at: (DCTSize*6 + i) put: t1 - t6.
- 		ws at: (DCTSize*2 + i) put: t2 + t5.
- 		ws at: (DCTSize*5 + i) put: t2 - t5.
- 		ws at: (DCTSize*4 + i) put: t3 + t4.
- 		ws at: (DCTSize*3 + i) put: t3 - t4].
- 
- 		"Pass 2: process rows from the workspace"
- 	0 to: DCTSize2-DCTSize by: DCTSize do: [:i |
- 		t10 := (ws at: (i+1)) + (ws at: (i+5)).
- 		t11 := (ws at: (i+1)) - (ws at: (i+5)).
- 		t13 := (ws at: (i+3)) + (ws at: (i+7)).
- 		t12 := ((ws at: (i+3)) - (ws at: (i+7))) * DCTK1 - t13.
- 		t0 := t10 + t13.
- 		t3 := t10 - t13.
- 		t1 := t11 + t12.
- 		t2 := t11 - t12.
- 		z13 := (ws at: (i+6)) + (ws at: (i+4)).
- 		z10 := (ws at: (i+6)) - (ws at: (i+4)).
- 		z11 := (ws at: (i+2)) + (ws at: (i+8)).
- 		z12 := (ws at: (i+2)) - (ws at: (i+8)).
- 		t7 := z11 + z13.
- 		t11 := (z11 - z13) * DCTK1.
- 		z5 := (z10 + z12) * DCTK2.
- 		t10 := DCTK3 * z12 - z5.
- 		t12 := DCTK4 * z10 + z5.
- 		t6 := t12 - t7.
- 		t5 := t11 - t6.
- 		t4 := t10 + t5.
- 
- 		"final output stage: scale down by a factor of 8 and range-limit"
- 		anArray at: (i+1) put: (self dctFloatRangeLimit: (t0 + t7)).
- 		anArray at: (i+8) put: (self dctFloatRangeLimit: (t0 - t7)).
- 		anArray at: (i+2) put: (self dctFloatRangeLimit: (t1 + t6)).
- 		anArray at: (i+7) put: (self dctFloatRangeLimit: (t1 - t6)).
- 		anArray at: (i+3) put: (self dctFloatRangeLimit: (t2 + t5)).
- 		anArray at: (i+6) put: (self dctFloatRangeLimit: (t2 - t5)).
- 		anArray at: (i+5) put: (self dctFloatRangeLimit: (t3 + t4)).
- 		anArray at: (i+4) put: (self dctFloatRangeLimit: (t3 - t4))]
- 
- 
- !

Item was removed:
- ----- Method: JPEGReadWriter>>idctBlockInt:component: (in category 'dct') -----
- idctBlockInt: anArray component: aColorComponent
- 	^self idctBlockInt: anArray qt: (self qTable at: aColorComponent qTableIndex)!

Item was removed:
- ----- Method: JPEGReadWriter>>idctBlockInt:qt: (in category 'dct') -----
- idctBlockInt: anArray qt: qt
- 
- 	|  ws anACTerm dcval z1 z2 z3 z4 z5 t0 t1 t2 t3 t10 t11 t12 t13 shift |
- 	ws := Array new: DCTSize2.
- 
- 	"Pass 1: process columns from anArray, store into work array"
- 	shift := 1 bitShift: ConstBits - Pass1Bits.
- 	1 to: DCTSize do:
- 		[:i |
- 		anACTerm := nil.
- 		1 to: DCTSize-1 do:[:row|
- 			anACTerm ifNil:[
- 				(anArray at: row * DCTSize + i) = 0 ifFalse:[anACTerm := row]]].
- 		anACTerm == nil
- 			ifTrue:
- 				[dcval := (anArray at: i) * (qt at: 1) bitShift: Pass1Bits.
- 				0 to: DCTSize-1 do: [:j | ws at: (j * DCTSize + i) put: dcval]]
- 			ifFalse:
- 				[z2 := (anArray at: (DCTSize * 2 + i)) * (qt at: (DCTSize * 2 + i)).
- 				z3 := (anArray at: (DCTSize * 6 + i)) * (qt at: (DCTSize * 6 + i)).
- 				z1 := (z2 + z3) * FIXn0n541196100.
- 				t2 := z1 + (z3 * FIXn1n847759065 negated).
- 				t3 := z1 + (z2 * FIXn0n765366865).
- 				z2 := (anArray at: i) * (qt at: i).
- 				z3 := (anArray at: (DCTSize * 4 + i)) * (qt at: (DCTSize * 4 + i)).
- 				t0 := (z2 + z3) bitShift: ConstBits.
- 				t1 := (z2 - z3) bitShift: ConstBits.
- 				t10 := t0 + t3.
- 				t13 := t0 - t3.
- 				t11 := t1 + t2.
- 				t12 := t1 - t2.
- 				t0 := (anArray at: (DCTSize * 7 + i)) * (qt at: (DCTSize * 7 + i)).
- 				t1 := (anArray at: (DCTSize * 5 + i)) * (qt at: (DCTSize * 5 + i)).
- 				t2 := (anArray at: (DCTSize * 3 + i)) * (qt at: (DCTSize * 3 + i)).
- 				t3 := (anArray at: (DCTSize + i)) * (qt at: (DCTSize + i)).
- 				z1 := t0 + t3.
- 				z2 := t1 + t2.
- 				z3 := t0 + t2.
- 				z4 := t1 + t3.
- 				z5 := (z3 + z4) * FIXn1n175875602.
- 				t0 := t0 * FIXn0n298631336.
- 				t1 := t1 * FIXn2n053119869.
- 				t2 := t2 * FIXn3n072711026.
- 				t3 := t3 * FIXn1n501321110.
- 				z1 := z1 * FIXn0n899976223 negated.
- 				z2 := z2 * FIXn2n562915447 negated.
- 				z3 := z3 * FIXn1n961570560 negated.
- 				z4 := z4 * FIXn0n390180644 negated.
- 				z3 := z3 + z5.
- 				z4 := z4 + z5.
- 				t0 := t0 + z1 + z3.
- 				t1 := t1 +z2 +z4.
- 				t2 := t2 + z2 + z3.
- 				t3 := t3 + z1 + z4.
- 				ws at: i put: (t10 + t3) >> (ConstBits - Pass1Bits).
- 				ws at: (DCTSize * 7 + i) put: (t10 - t3) // shift.
- 				ws at: (DCTSize * 1 + i) put: (t11 + t2) // shift.
- 				ws at: (DCTSize * 6 + i) put: (t11 - t2) // shift.
- 				ws at: (DCTSize * 2 + i) put: (t12 + t1) // shift.
- 				ws at: (DCTSize * 5 + i) put: (t12 - t1) // shift.
- 				ws at: (DCTSize * 3 + i) put: (t13 + t0) // shift.
- 				ws at: (DCTSize * 4 + i) put: (t13 - t0) // shift]].
- 
- 	"Pass 2: process rows from work array, store back into anArray"
- 	shift := 1 bitShift: ConstBits + Pass1Bits + 3.
- 	0 to: DCTSize2-DCTSize by: DCTSize do:
- 		[:i |
- 		z2 := ws at: i + 3.
- 		z3 := ws at: i + 7.
- 		z1 := (z2 + z3) * FIXn0n541196100.
- 		t2 := z1 + (z3 * FIXn1n847759065 negated).
- 		t3 := z1 + (z2 * FIXn0n765366865).
- 		t0 := (ws at: (i + 1)) + (ws at: (i + 5)) bitShift: ConstBits.
- 		t1 := (ws at: (i + 1)) - (ws at: (i + 5)) bitShift: ConstBits.
- 		t10 := t0 + t3.
- 		t13 := t0 - t3.
- 		t11 := t1 + t2.
- 		t12 := t1 -t2.
- 		t0 := ws at: (i + 8).
- 		t1 := ws at: (i + 6).
- 		t2 := ws at: (i + 4).
- 		t3 := ws at: (i + 2).
- 		z1 := t0 + t3.
- 		z2 := t1 + t2.
- 		z3 := t0 + t2.
- 		z4 := t1 + t3.
- 		z5 := (z3 + z4) * FIXn1n175875602.
- 		t0 := t0 * FIXn0n298631336.
- 		t1 := t1 * FIXn2n053119869.
- 		t2 := t2 * FIXn3n072711026.
- 		t3 := t3 * FIXn1n501321110.
- 		z1 := z1 * FIXn0n899976223 negated.
- 		z2 := z2 * FIXn2n562915447 negated.
- 		z3 := z3 * FIXn1n961570560 negated.
- 		z4 := z4 * FIXn0n390180644 negated.
- 		z3 := z3 + z5.
- 		z4 := z4 + z5.
- 		t0 := t0 + z1 + z3.
- 		t1 := t1 + z2 + z4.
- 		t2 := t2 + z2 + z3.
- 		t3 := t3 + z1 + z4.
- 		anArray at: (i + 1) put: (self sampleRangeLimit: (t10 + t3) // shift + SampleOffset).
- 		anArray at: (i + 8) put: (self sampleRangeLimit: (t10 - t3) // shift + SampleOffset).
- 		anArray at: (i + 2) put: (self sampleRangeLimit: (t11 + t2) // shift + SampleOffset).
- 		anArray at: (i + 7) put: (self sampleRangeLimit: (t11 - t2) // shift + SampleOffset).
- 		anArray at: (i + 3) put: (self sampleRangeLimit: (t12 + t1) // shift + SampleOffset).
- 		anArray at: (i + 6) put: (self sampleRangeLimit: (t12 - t1) // shift + SampleOffset).
- 		anArray at: (i + 4) put: (self sampleRangeLimit: (t13 + t0) // shift + SampleOffset).
- 		anArray at: (i + 5) put: (self sampleRangeLimit: (t13 - t0) // shift + SampleOffset)].
- 
- 
- !

Item was removed:
- ----- Method: JPEGReadWriter>>idctMCU (in category 'dct') -----
- idctMCU
- 
- 	| comp fp ci |
- 	fp := self useFloatingPoint.
- 	1 to: mcuMembership size do:[:i|
- 		ci := mcuMembership at: i.
- 		comp := currentComponents at: ci.
- 		fp ifTrue:[
- 			self idctBlockFloat: (mcuSampleBuffer at: i) component: comp.
- 		] ifFalse:[
- 			self primIdctInt: (mcuSampleBuffer at: i)
- 				qt: (qTable at: comp qTableIndex)]].!

Item was removed:
- ----- Method: JPEGReadWriter>>initialSOSSetup (in category 'marker parsing') -----
- initialSOSSetup
- 
- 	mcuWidth := (components detectMax: [:c | c widthInBlocks]) widthInBlocks.
- 	mcuHeight := (components detectMax: [:c | c heightInBlocks]) heightInBlocks.
- 	components do:[:c |
- 		c mcuWidth: mcuWidth mcuHeight: mcuHeight dctSize: DCTSize].
- 	stream resetBitBuffer.!

Item was removed:
- ----- Method: JPEGReadWriter>>nextImage (in category 'public access') -----
- nextImage
- 
- 	^ self nextImageDitheredToDepth: Display depth
- !

Item was removed:
- ----- Method: JPEGReadWriter>>nextImageDitheredToDepth: (in category 'public access') -----
- nextImageDitheredToDepth: depth
- 
- 	| form xStep yStep x y bb |
- 	ditherMask := DitherMasks
- 		at: depth
- 		ifAbsent: [self error: 'can only dither to display depths' translated].
- 	residuals := WordArray new: 3.
- 	sosSeen := false.
- 	self parseFirstMarker.
- 	[sosSeen] whileFalse: [self parseNextMarker].
- 	form := Form extent: (width @ height) depth: depth.
- 	bb := BitBlt toForm: form.
- 	bb sourceForm: mcuImageBuffer.
- 	bb colorMap: (mcuImageBuffer colormapIfNeededFor: form).
- 	bb sourceRect: mcuImageBuffer boundingBox.
- 	bb combinationRule: Form over.
- 	xStep := mcuWidth * DCTSize.
- 	yStep := mcuHeight * DCTSize.
- 	y := 0.
- 	1 to: mcuRowsInScan do:
- 		[:row |
- 		x := 0.
- 		1 to: mcusPerRow do:
- 			[:col |
- 			self decodeMCU.
- 			self idctMCU.
- 			self colorConvertMCU.
- 			bb destX: x; destY: y; copyBits.
- 			x := x + xStep].
- 		y := y + yStep].
- 	^ form!

Item was removed:
- ----- Method: JPEGReadWriter>>okToIgnoreMarker: (in category 'marker parsing') -----
- okToIgnoreMarker: aMarker
- 
- 	^ (((16rE0 to: 16rEF) includes: aMarker) "unhandled APPn markers"
- 		or: [aMarker = 16rDC or: [aMarker = 16rFE]]) "DNL or COM markers"
- 		or: [aMarker = 16r99] "Whatever that is"!

Item was removed:
- ----- Method: JPEGReadWriter>>on: (in category 'private') -----
- on: aStream
- 	super on: aStream.
- 	stream := JPEGReadStream on: stream upToEnd.!

Item was removed:
- ----- Method: JPEGReadWriter>>parseAPPn (in category 'marker parsing') -----
- parseAPPn
- 
- 	| length buffer thumbnailLength markerStart |
- 	markerStart := self position.
- 	length := self nextWord.
- 	buffer := self next: 4.
- 	(buffer asString = 'JFIF') ifFalse: [
- 		"Skip APPs that we're not interested in"
- 		stream next: length-6.
- 		^self].
- 	self next.
- 	majorVersion := self next.
- 	minorVersion := self next.
- 	densityUnit := self next.
- 	xDensity := self nextWord.
- 	yDensity := self nextWord.
- 	thumbnailLength := self next * self next * 3.
- 	length := length - (self position - markerStart).
- 	length = thumbnailLength ifFalse: [self error: 'APP0 thumbnail length is incorrect.' translated].
- 	self next: length!

Item was removed:
- ----- Method: JPEGReadWriter>>parseDecoderRestartInterval (in category 'marker parsing') -----
- parseDecoderRestartInterval
- 
- 	| length |
- 	length := self nextWord.
- 	length = 4 ifFalse: [self error: 'DRI length is incorrect.' translated].
- 	restartInterval := self nextWord.!

Item was removed:
- ----- Method: JPEGReadWriter>>parseFirstMarker (in category 'marker parsing') -----
- parseFirstMarker
- 
- 	| marker |
- 	self next = 16rFF ifFalse: [self error: 'JFIF marker expected' translated].
- 	marker := self next.
- 	marker = 16rD9
- 		ifTrue: [^self "halt: 'EOI encountered.'"].
- 	marker = 16rD8 ifFalse: [self error: 'SOI marker expected' translated].
- 	self parseStartOfInput.
- !

Item was removed:
- ----- Method: JPEGReadWriter>>parseHuffmanTable (in category 'marker parsing') -----
- parseHuffmanTable
- 
- 	| length markerStart index bits count huffVal isACTable hTable |
- 	markerStart := self position.
- 	length := self nextWord.
- 	[self position - markerStart >= length] whileFalse:
- 		[index := self next.
- 		isACTable := (index bitAnd: 16r10) ~= 0.
- 		index := (index bitAnd: 16r0F) + 1.
- 		index > HuffmanTableSize
- 			ifTrue: [self error: ('image has more than {1} quantization tables' translated format: {HuffmanTableSize})].
- 		bits := self next: 16.
- 		count := bits sum.
- 		(count > 256 or: [(count > (length - (self position - markerStart)))])
- 			ifTrue: [self error: 'Huffman Table count is incorrect' translated].
- 		huffVal := self next: count.
- 		hTable := stream buildLookupTable: huffVal counts: bits.
- 		isACTable
- 			ifTrue:
- 				[self hACTable at: index put: hTable]
- 			ifFalse:
- 				[self hDCTable at: index put: hTable]].!

Item was removed:
- ----- Method: JPEGReadWriter>>parseNOP (in category 'marker parsing') -----
- parseNOP
- 
- 	"don't need to do anything, here"!

Item was removed:
- ----- Method: JPEGReadWriter>>parseNextMarker (in category 'marker parsing') -----
- parseNextMarker
- 	"Parse the next marker of the stream"
- 
- 	| byte discardedBytes |
- 	discardedBytes := 0.
- 	[(byte := self next) = 16rFF] whileFalse: [discardedBytes := discardedBytes + 1].	
- 	[[(byte := self next) = 16rFF] whileTrue. byte = 16r00] whileTrue:
- 		[discardedBytes := discardedBytes + 2].
- 	discardedBytes > 0 ifTrue: [self "notifyWithLabel: 'warning: extraneous data discarded'"].
- 	self perform:
- 		(JFIFMarkerParser
- 			at: byte
- 			ifAbsent:
- 				[(self okToIgnoreMarker: byte)
- 					ifTrue: [#skipMarker]
- 					ifFalse: [self error: ('marker {1} cannot be handled' translated format: {byte printStringHex})]])!

Item was removed:
- ----- Method: JPEGReadWriter>>parseQuantizationTable (in category 'marker parsing') -----
- parseQuantizationTable
- 
- 	| length markerStart n prec value table |
- 	markerStart := self position.
- 	length := self nextWord.
- 	[self position - markerStart >= length] whileFalse:
- 		[value := self next.
- 		n := (value bitAnd: 16r0F) + 1.
- 		prec := (value >> 4) > 0.
- 		n > QuantizationTableSize
- 			 ifTrue: [self error: ('image has more than {1} quantization tables' translated format: {QuantizationTableSize})].
- 		table := IntegerArray new: DCTSize2.
- 		1 to: DCTSize2 do:
- 			[:i |
- 			value := (prec
- 				ifTrue: [self nextWord]
- 				ifFalse: [self next]).
- 			table at: (JPEGNaturalOrder at: i) put: value].
- 		self useFloatingPoint ifTrue: [self scaleQuantizationTable: table].
- 		self qTable at: n put: table]!

Item was removed:
- ----- Method: JPEGReadWriter>>parseStartOfFile (in category 'marker parsing') -----
- parseStartOfFile
- 
- 	| length markerStart value n |
- 	markerStart := self position.
- 	length := self nextWord.
- 	dataPrecision := self next.
- 	dataPrecision = 8
- 		ifFalse: [self error: ('cannot handle {1}-bit components' translated format: {dataPrecision})].
- 	height := self nextWord.
- 	width := self nextWord.
- 	n := self next.
- 	(height = 0) | (width = 0) | (n = 0) ifTrue: [self error: 'empty image' translated].
- 	(length - (self position - markerStart)) ~= (n * 3)
- 		ifTrue: [self error: 'component length is incorrect' translated].
- 	components := Array new: n.
- 	1 to: components size do:
- 		[:i |
- 		components
- 			at: i
- 			put:
- 				(JPEGColorComponent new
- 					id: self next;
- 					"heightInBlocks: (((value := self next) >> 4) bitAnd: 16r0F);
- 					widthInBlocks: (value bitAnd: 16r0F);"
- 					widthInBlocks: (((value := self next) >> 4) bitAnd: 16r0F);
- 					heightInBlocks: (value bitAnd: 16r0F);
- 
- 					qTableIndex: self next + 1)]!

Item was removed:
- ----- Method: JPEGReadWriter>>parseStartOfInput (in category 'marker parsing') -----
- parseStartOfInput
- 
- 	restartInterval := 0.
- 	densityUnit := 0.
- 	xDensity := 1.
- 	yDensity := 1
- !

Item was removed:
- ----- Method: JPEGReadWriter>>parseStartOfScan (in category 'marker parsing') -----
- parseStartOfScan
- 
- 	| length n id value dcNum acNum comp |
- 	length := self nextWord.
- 	n := self next.
- 	(length ~= (n*2 + 6)) | (n < 1) ifTrue: [self error: 'SOS length is incorrect' translated].
- 	currentComponents := Array new: n.
- 	1 to: n do: [:i |
- 		id := self next.
- 		value := self next.
- 		dcNum := (value >> 4) bitAnd: 16r0F.
- 		acNum := value bitAnd: 16r0F.
- 		comp := components detect: [:c | c id = id].
- 		comp
- 			dcTableIndex: dcNum+1;
- 			acTableIndex: acNum+1.
- 		currentComponents at: i put: comp].
- 	ss := self next.
- 	se := self next.
- 	value := self next.
- 	ah := (value >> 4) bitAnd: 16r0F.
- 	al := value bitAnd: 16r0F.
- 	self initialSOSSetup.
- 	self perScanSetup.
- 	sosSeen := true!

Item was removed:
- ----- Method: JPEGReadWriter>>perScanSetup (in category 'marker parsing') -----
- perScanSetup
- 
- 	mcusPerRow := (width / (mcuWidth * DCTSize)) ceiling.
- 	mcuRowsInScan := (height / (mcuHeight * DCTSize)) ceiling.
- 	(currentComponents size = 3 or: [currentComponents size = 1])
- 		ifFalse: [self error: 'JPEG color space not recognized' translated].
- 	mcuMembership := OrderedCollection new.
- 	currentComponents withIndexDo:
- 		[:c :i |
- 		c priorDCValue: 0.
- 		mcuMembership addAll: ((1 to: c totalMcuBlocks) collect: [:b | i])].
- 	mcuMembership := mcuMembership asArray.
- 	mcuSampleBuffer := (1 to: mcuMembership size) collect: [:i | IntegerArray new: DCTSize2].
- 	currentComponents withIndexDo:
- 		[:c :i |
- 			c initializeSampleStreamBlocks:
- 				((1 to: mcuMembership size)
- 					select: [:j | i = (mcuMembership at: j)]
- 					thenCollect: [:j | mcuSampleBuffer at: j])].
- 	mcuImageBuffer := Form
- 		extent: (mcuWidth @ mcuHeight) * DCTSize
- 		depth: 32.
- 	restartsToGo := restartInterval.!

Item was removed:
- ----- Method: JPEGReadWriter>>primColorConvertGrayscaleMCU (in category 'colorspace conversion') -----
- primColorConvertGrayscaleMCU
- 	self primColorConvertGrayscaleMCU: (currentComponents at: 1)
- 			bits: mcuImageBuffer bits
- 			residuals: residuals
- 			ditherMask: ditherMask.!

Item was removed:
- ----- Method: JPEGReadWriter>>primColorConvertGrayscaleMCU:bits:residuals:ditherMask: (in category 'colorspace conversion') -----
- primColorConvertGrayscaleMCU: componentArray bits: bits residuals: residualArray ditherMask: mask
- 	<primitive: 'primitiveColorConvertGrayscaleMCU' module: 'JPEGReaderPlugin'>
- 	"JPEGReaderPlugin doPrimitive: #primitiveColorConvertGrayscaleMCU."
- 	^self colorConvertGrayscaleMCU!

Item was removed:
- ----- Method: JPEGReadWriter>>primColorConvertIntYCbCrMCU (in category 'colorspace conversion') -----
- primColorConvertIntYCbCrMCU
- 	self primColorConvertYCbCrMCU: currentComponents
- 			bits: mcuImageBuffer bits
- 			residuals: residuals
- 			ditherMask: ditherMask.!

Item was removed:
- ----- Method: JPEGReadWriter>>primColorConvertYCbCrMCU:bits:residuals:ditherMask: (in category 'colorspace conversion') -----
- primColorConvertYCbCrMCU: componentArray bits: bits residuals: residualArray ditherMask: mask
- 	<primitive: 'primitiveColorConvertMCU' module: 'JPEGReaderPlugin'>
- 	^self colorConvertIntYCbCrMCU!

Item was removed:
- ----- Method: JPEGReadWriter>>primDecodeBlockInto:component:dcTable:acTable:stream: (in category 'huffman encoding') -----
- primDecodeBlockInto: sampleBuffer component: comp dcTable: dcTable acTable: acTable stream: jpegStream
- 	<primitive: 'primitiveDecodeMCU' module: 'JPEGReaderPlugin'>
- 	^self decodeBlockInto: sampleBuffer component: comp dcTable: dcTable acTable: acTable!

Item was removed:
- ----- Method: JPEGReadWriter>>primIdctBlockInt:component: (in category 'dct') -----
- primIdctBlockInt: anArray component: aColorComponent
- 	^self primIdctInt: anArray qt: (self qTable at: aColorComponent qTableIndex)!

Item was removed:
- ----- Method: JPEGReadWriter>>primIdctInt:qt: (in category 'dct') -----
- primIdctInt: anArray qt: qt
- 	<primitive: 'primitiveIdctInt' module: 'JPEGReaderPlugin'>
- 	^self idctBlockInt: anArray qt: qt!

Item was removed:
- ----- Method: JPEGReadWriter>>processRestart (in category 'huffman encoding') -----
- processRestart
- 	stream resetBitBuffer.
- 	self parseNextMarker.
- 	currentComponents do: [:c | c priorDCValue: 0].
- 	restartsToGo := restartInterval.!

Item was removed:
- ----- Method: JPEGReadWriter>>qTable (in category 'accessing') -----
- qTable
- 
- 	qTable ifNil: [qTable := Array new: QuantizationTableSize].
- 	^ qTable!

Item was removed:
- ----- Method: JPEGReadWriter>>sampleFloatRangeLimit: (in category 'colorspace conversion') -----
- sampleFloatRangeLimit: aNumber
- 
- 	^ (aNumber rounded max: 0) min: MaxSample!

Item was removed:
- ----- Method: JPEGReadWriter>>sampleRangeLimit: (in category 'colorspace conversion') -----
- sampleRangeLimit: aNumber
- 
- 	aNumber < 0 ifTrue: [^ 0].
- 	aNumber > MaxSample ifTrue: [^ MaxSample].
- 	^ aNumber!

Item was removed:
- ----- Method: JPEGReadWriter>>scaleAndSignExtend:inFieldWidth: (in category 'huffman encoding') -----
- scaleAndSignExtend: aNumber inFieldWidth: w
- 
- 	aNumber < (1 bitShift: (w - 1))
- 		ifTrue: [^aNumber - (1 bitShift: w) + 1]
- 		ifFalse: [^aNumber]!

Item was removed:
- ----- Method: JPEGReadWriter>>scaleQuantizationTable: (in category 'dct') -----
- scaleQuantizationTable: table
- 
- 	| index |
- 
- 	index := 1.
- 	1 to: DCTSize do:
- 		[:row |
- 		1 to: DCTSize do:
- 			[:col |
- 			table at: index
- 				put: ((table at: index) * (QTableScaleFactor at: row) *
- 					(QTableScaleFactor at: col)) rounded.
- 			index := index + 1]].
- 	^ table
- !

Item was removed:
- ----- Method: JPEGReadWriter>>setStream: (in category 'public access') -----
- setStream: aStream
- 	"Feed it in from an existing source"
- 	stream := JPEGReadStream on: aStream upToEnd.!

Item was removed:
- ----- Method: JPEGReadWriter>>skipMarker (in category 'marker parsing') -----
- skipMarker
- 
- 	| length markerStart |
- 	markerStart := self position.
- 	length := self nextWord.
- 	self next: length - (self position - markerStart)
- !

Item was removed:
- ----- Method: JPEGReadWriter>>understandsImageFormat (in category 'testing') -----
- understandsImageFormat
- 	"Answer true if the image stream format is understood by this decoder."
- 	self next = 16rFF ifFalse: [^ false].
- 	self next = 16rD8 ifFalse: [^ false].
- 	^ true
- !

Item was removed:
- ----- Method: JPEGReadWriter>>useFloatingPoint (in category 'preferences') -----
- useFloatingPoint
- 
- 	^ false!

Item was removed:
- ImageReadWriter subclass: #JPEGReadWriter2
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!
- 
- !JPEGReadWriter2 commentStamp: '<historical>' prior: 0!
- I provide fast JPEG compression and decompression. I require the VM pluginJPEGReadWriter2Plugin, which is typically stored in same directory as the Squeak virtual machine.
- 
- JPEGReadWriter2Plugin is based on LIBJPEG library. This sentence applies to the plugin:
-    "This software is based in part on the work of the Independent JPEG Group".
- 
- The LIBJPEG license allows it to be used free for any purpose so long as its origin and copyright are acknowledged. You can read more about LIBJPEG and get the complete source code at www.ijg.org.
- !

Item was removed:
- ----- Method: JPEGReadWriter2 class>>primJPEGPluginIsPresent (in category 'image reading/writing') -----
- primJPEGPluginIsPresent
- 	<primitive: 'primJPEGPluginIsPresent' module: 'JPEGReadWriter2Plugin'>
- 	^false!

Item was removed:
- ----- Method: JPEGReadWriter2 class>>putForm:quality:progressiveJPEG:onFileNamed: (in category 'image reading/writing') -----
- putForm: aForm quality: quality progressiveJPEG: progressiveFlag onFileNamed: fileName
- 	"Store the given Form as a JPEG file of the given name, overwriting any existing file of that name. Quality goes from 0 (low) to 100 (high), where -1 means default. If progressiveFlag is true, encode as a progressive JPEG."
- 
- 	| writer theFile |
- 	FileDirectory deleteFilePath: fileName.
- 	theFile := FileStream newFileNamed: fileName.
- 	writer := self on: theFile binary.
- 	Cursor write showWhile: [
- 		writer nextPutImage: aForm quality: quality progressiveJPEG: progressiveFlag].
- 	writer close.
- 	theFile directory setMacFileNamed: theFile localName type: '    ' creator: '    '.!

Item was removed:
- ----- Method: JPEGReadWriter2 class>>typicalFileExtensions (in category 'image reading/writing') -----
- typicalFileExtensions
- 	"Answer a collection of file extensions (lowercase) which files that I can read might commonly have"
- 	^#('jpg' 'jpeg')!

Item was removed:
- ----- Method: JPEGReadWriter2>>compress:quality: (in category 'public access') -----
- compress: aForm quality: quality
- 	"Encode the given Form and answer the compressed ByteArray. Quality goes from 0 (low) to 100 (high), where -1 means default.
- 	We can only compress:
- 		* 32-bit deep Forms 
- 		* -32-bit deep Forms
- 		* 16-bit deep Forms
- 		* -16-bit deep Forms
- 		* GrayScale ColorForms (see #isGrayScale)"
- 	| sourceForm jpegCompressStruct jpegErrorMgr2Struct buffer byteCount |
- 	
- 	aForm unhibernate.
- 	
- 	sourceForm := self supports8BitGrayscaleJPEGs 
- 		ifTrue: [ 
- 			(aForm depth = 32) | (aForm depth = 16) | (aForm isGrayScale)
- 				ifTrue: [aForm]
- 				ifFalse: [aForm asFormOfDepth: 32 ]]
- 		ifFalse: [
- 			(aForm nativeDepth > 0) & ((aForm depth = 32) | ((aForm depth = 16) & (aForm width even)))
- 				ifTrue: [aForm]
- 				ifFalse: [aForm asFormOfDepth: 32 ]].
- 	
- 	jpegCompressStruct := ByteArray new: self primJPEGCompressStructSize.
- 	jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
- 	buffer := ByteArray new: sourceForm width * sourceForm height + 1024.
- 	byteCount := self primJPEGWriteImage: jpegCompressStruct 
- 		onByteArray: buffer
- 		form: sourceForm
- 		quality: quality
- 		progressiveJPEG: false
- 		errorMgr: jpegErrorMgr2Struct.
- 	byteCount = 0 ifTrue: [self error: 'buffer too small for compressed data' translated].
- 	^ buffer copyFrom: 1 to: byteCount
- !

Item was removed:
- ----- Method: JPEGReadWriter2>>imageExtent: (in category 'public access') -----
- imageExtent: aByteArray 
- 	"Answer the extent of the compressed image encoded in the given ByteArray."
- 
- 	| jpegDecompressStruct jpegErrorMgr2Struct w h |
- 	jpegDecompressStruct := ByteArray new: self primJPEGDecompressStructSize.
- 	jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
- 	self
- 		primJPEGReadHeader: jpegDecompressStruct 
- 		fromByteArray: aByteArray
- 		errorMgr: jpegErrorMgr2Struct.
- 	w := self primImageWidth: jpegDecompressStruct.
- 	h := self primImageHeight: jpegDecompressStruct.
- 	^ w @ h
- !

Item was removed:
- ----- Method: JPEGReadWriter2>>isPluginPresent (in category 'testing') -----
- isPluginPresent
- 	^self primJPEGPluginIsPresent!

Item was removed:
- ----- Method: JPEGReadWriter2>>nextImage (in category 'public access') -----
- nextImage
- 	"Decode and answer a Form from my stream."
- 
- 	^ self nextImageSuggestedDepth: Display depth
- !

Item was removed:
- ----- Method: JPEGReadWriter2>>nextImageSuggestedDepth: (in category 'public access') -----
- nextImageSuggestedDepth: suggestedDepth
- 	"Decode and answer a Form of the given depth from my stream. Close the stream if it is a file stream.
- 	We can read RGB JPEGs into:
- 		* 32-bit Forms
- 		* -32-bit Forms
- 		* 16-bit Forms (with or without dithering!!)
- 		* -16-bit Forms (with or without dithering!!)
- 	We can read grayscale JPEGs into:
- 		* 32-bit Forms
- 		* -32-bit Forms
- 		* 16-bit Forms (with or without dithering!!)
- 		* -16-bit Forms (with or without dithering!!)
- 		* 8-bit grayScale ColorForms (see #isGrayScale)
- 		* -8-bit grayScale ColorForms (see #isGrayScale)"
- 
- 	| bytes width height components form jpegDecompressStruct jpegErrorMgr2Struct |
- 	bytes := stream upToEnd.
- 	stream close.
- 	jpegDecompressStruct := ByteArray new: self primJPEGDecompressStructSize.
- 	jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
- 	self 
- 		primJPEGReadHeader: jpegDecompressStruct 
- 		fromByteArray: bytes
- 		errorMgr: jpegErrorMgr2Struct.
- 	width := self primImageWidth: jpegDecompressStruct.
- 	height := self primImageHeight: jpegDecompressStruct.
- 	components := self primImageNumComponents: jpegDecompressStruct.
- 	form :=
- 		self supports8BitGrayscaleJPEGs
- 			ifTrue: [
- 				components = 3
- 					ifTrue: [ Form extent: width at height depth: suggestedDepth ]
- 					ifFalse: [ (Form extent: width at height depth: suggestedDepth) asGrayScale ]]
- 			ifFalse: [
- 				Form
- 					extent: width at height
- 					depth: 
- 						(suggestedDepth = 32 
- 							ifTrue: [ 32 ]
- 							ifFalse: [
- 								((suggestedDepth = 16) & (width even))
- 									ifTrue: [ 16 ]
- 									ifFalse: [ 32 ]])].
- 					
- 	self
- 		primJPEGReadImage: jpegDecompressStruct
- 		fromByteArray: bytes
- 		onForm: form
- 		doDithering: true
- 		errorMgr: jpegErrorMgr2Struct.
- 	^ form!

Item was removed:
- ----- Method: JPEGReadWriter2>>nextPutImage: (in category 'public access') -----
- nextPutImage: aForm
- 	"Encode the given Form on my stream with default quality."
- 
- 	^ self nextPutImage: aForm quality: -1 progressiveJPEG: false
- !

Item was removed:
- ----- Method: JPEGReadWriter2>>nextPutImage:quality:progressiveJPEG: (in category 'public access') -----
- nextPutImage: aForm quality: quality progressiveJPEG: progressiveFlag
- 	"Encode the given Form on my stream with the given settings. Quality goes from 0 (low) to 100 (high), where -1 means default. If progressiveFlag is true, encode as a progressive JPEG.
- 	We can compress:
- 		* 32-bit deep Forms 
- 		* -32-bit deep Forms
- 		* 16-bit deep
- 		* -16-bit deep
- 		* GrayScale ColorForms (see #isGrayScale)"
- 
- 	| sourceForm jpegCompressStruct jpegErrorMgr2Struct buffer byteCount |
- 	
- 	aForm unhibernate.
- 	
- 	sourceForm := self supports8BitGrayscaleJPEGs 
- 		ifTrue: [ 
- 			(aForm depth = 32) | (aForm depth = 16) | (aForm isGrayScale)
- 				ifTrue: [aForm]
- 				ifFalse: [aForm asFormOfDepth: 32 ]]
- 		ifFalse: [
- 			(aForm nativeDepth > 0) & ((aForm depth = 32) | ((aForm depth = 16) & (aForm width even)))
- 				ifTrue: [aForm]
- 				ifFalse: [aForm asFormOfDepth: 32 ]].
- 	
- 	jpegCompressStruct := ByteArray new: self primJPEGCompressStructSize.
- 	jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
- 	buffer := ByteArray new: sourceForm width * sourceForm height + 1024.
- 	"Try to write the image. Retry with a larger buffer if needed."
- 	[
- 		byteCount := self primJPEGWriteImage: jpegCompressStruct 
- 			onByteArray: buffer
- 			form: sourceForm
- 			quality: quality
- 			progressiveJPEG: progressiveFlag
- 			errorMgr: jpegErrorMgr2Struct.
- 		byteCount = 0 and: [ buffer size < (sourceForm width * sourceForm height * 3 + 1024) ] ]
- 			whileTrue: [ buffer := ByteArray new: buffer size * 2 ].
- 	byteCount = 0 ifTrue: [ self error: 'buffer too small for compressed data' translated ].
- 	stream next: byteCount putAll: buffer startingAt: 1.
- 	self close.
- !

Item was removed:
- ----- Method: JPEGReadWriter2>>primImageHeight: (in category 'primitives') -----
- primImageHeight: aJPEGCompressStruct
- 
- 	<primitive: 'primImageHeight' module: 'JPEGReadWriter2Plugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: JPEGReadWriter2>>primImageNumComponents: (in category 'primitives') -----
- primImageNumComponents: aJPEGDecompressStruct
- 
- 	<primitive: 'primImageNumComponents' module: 'JPEGReadWriter2Plugin'>
- 	^ 3!

Item was removed:
- ----- Method: JPEGReadWriter2>>primImageWidth: (in category 'primitives') -----
- primImageWidth: aJPEGCompressStruct
- 
- 	<primitive: 'primImageWidth' module: 'JPEGReadWriter2Plugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: JPEGReadWriter2>>primJPEGCompressStructSize (in category 'primitives') -----
- primJPEGCompressStructSize
- 
- 	<primitive: 'primJPEGCompressStructSize' module: 'JPEGReadWriter2Plugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: JPEGReadWriter2>>primJPEGDecompressStructSize (in category 'primitives') -----
- primJPEGDecompressStructSize
- 
- 	<primitive: 'primJPEGDecompressStructSize' module: 'JPEGReadWriter2Plugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: JPEGReadWriter2>>primJPEGErrorMgr2StructSize (in category 'primitives') -----
- primJPEGErrorMgr2StructSize
- 
- 	<primitive: 'primJPEGErrorMgr2StructSize' module: 'JPEGReadWriter2Plugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: JPEGReadWriter2>>primJPEGPluginIsPresent (in category 'primitives') -----
- primJPEGPluginIsPresent
- 	<primitive: 'primJPEGPluginIsPresent' module: 'JPEGReadWriter2Plugin'>
- 	^false!

Item was removed:
- ----- Method: JPEGReadWriter2>>primJPEGReadHeader:fromByteArray:errorMgr: (in category 'primitives') -----
- primJPEGReadHeader: aJPEGDecompressStruct fromByteArray: source errorMgr: aJPEGErrorMgr2Struct
- 
- 	<primitive: 'primJPEGReadHeaderfromByteArrayerrorMgr' module: 'JPEGReadWriter2Plugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: JPEGReadWriter2>>primJPEGReadImage:fromByteArray:onForm:doDithering:errorMgr: (in category 'primitives') -----
- primJPEGReadImage: aJPEGDecompressStruct fromByteArray: source onForm: form doDithering: ditherFlag errorMgr: aJPEGErrorMgr2Struct
- 
- 	<primitive: 'primJPEGReadImagefromByteArrayonFormdoDitheringerrorMgr' module: 'JPEGReadWriter2Plugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: JPEGReadWriter2>>primJPEGWriteImage:onByteArray:form:quality:progressiveJPEG:errorMgr: (in category 'primitives') -----
- primJPEGWriteImage: aJPEGCompressStruct onByteArray: destination form: form quality: quality progressiveJPEG: progressiveFlag errorMgr: aJPEGErrorMgr2Struct
- 
- 	<primitive: 'primJPEGWriteImageonByteArrayformqualityprogressiveJPEGerrorMgr' module: 'JPEGReadWriter2Plugin'>
- 	self primitiveFailed
- !

Item was removed:
- ----- Method: JPEGReadWriter2>>primSupports8BitGrayscaleJPEGs (in category 'primitives') -----
- primSupports8BitGrayscaleJPEGs
- 	<primitive: 'primSupports8BitGrayscaleJPEGs' module: 'JPEGReadWriter2Plugin'>
- 	^ false!

Item was removed:
- ----- Method: JPEGReadWriter2>>supports8BitGrayscaleJPEGs (in category 'testing') -----
- supports8BitGrayscaleJPEGs
- 	^ self primSupports8BitGrayscaleJPEGs!

Item was removed:
- ----- Method: JPEGReadWriter2>>uncompress:into: (in category 'public access') -----
- uncompress: aByteArray into: aForm
- 	^ self uncompress: aByteArray into: aForm doDithering: true
- !

Item was removed:
- ----- Method: JPEGReadWriter2>>uncompress:into:doDithering: (in category 'public access') -----
- uncompress: aByteArray into: aForm doDithering: ditherFlag
- 	"Uncompress an image from the given ByteArray into the given Form. 
- 	Fails if the given Form has the wrong dimensions or depth.
- 	We can read RGB JPEGs into:
- 		* 32-bit Forms
- 		* -32-bit Forms
- 		* 16-bit Forms (with or without dithering!!)
- 		* -16-bit Forms (with or without dithering!!)
- 	We can read grayscale JPEGs into:
- 		* 32-bit Forms
- 		* -32-bit Forms
- 		* 16-bit Forms (with or without dithering!!)
- 		* -16-bit Forms (with or without dithering!!)
- 		* 8-bit grayScale ColorForms (see #isGrayScale)
- 		* -8-bit grayScale ColorForms (see #isGrayScale)"
- 
- 	| jpegDecompressStruct jpegErrorMgr2Struct width height components |
- 	
- 	aForm unhibernate.
- 	
- 	jpegDecompressStruct := ByteArray new: self primJPEGDecompressStructSize.
- 	jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
- 	self 
- 		primJPEGReadHeader: jpegDecompressStruct 
- 		fromByteArray: aByteArray
- 		errorMgr: jpegErrorMgr2Struct.
- 	width := self primImageWidth: jpegDecompressStruct.
- 	height := self primImageHeight: jpegDecompressStruct.
- 	components := self primImageNumComponents: jpegDecompressStruct.
- 	
- 	((aForm width = width) & (aForm height = height)) ifFalse: [
- 		^ self error: 'form dimensions do not match' translated ].
- 	self supports8BitGrayscaleJPEGs
- 		ifTrue: [
- 			components = 3
- 				ifTrue: [
- 					aForm depth = 8
- 						ifTrue: [ ^ self error: 'Cannot uncompress multi-channel JPEGs into 8-bit deep forms' translated ]].
- 			components = 1
- 				ifTrue: [
- 					aForm depth = 8
- 						ifTrue: [
- 							aForm isGrayScale 
- 								ifFalse: [ ^ self error: 'Cannot uncompress single-channel JPEGs into 8-bit deep forms that are not grayscale' translated ]]]]
- 						
- 		ifFalse: [
- 			aForm nativeDepth < 0
- 				ifTrue: [ ^ self error: 'Current plugin version doesn''t support uncompressing JPEGs into little-endian forms' translated ]
- 				ifFalse: [
- 					aForm depth = 16
- 						ifTrue: [
- 							width odd
- 								ifTrue: [ ^ self error: 'Current plugin version doesn''t support uncompressing JPEGs with an odd width into 16-bit deep forms' translated ]].
- 					aForm depth = 8
- 						ifTrue: [ ^ self error: 'Current plugin version doesn''t support uncompressing JPEGs into 8-bit deep forms' translated ]]].
- 
- 	self primJPEGReadImage: jpegDecompressStruct
- 		fromByteArray: aByteArray
- 		onForm: aForm
- 		doDithering: ditherFlag
- 		errorMgr: jpegErrorMgr2Struct.!

Item was removed:
- ----- Method: JPEGReadWriter2>>understandsImageFormat (in category 'testing') -----
- understandsImageFormat
- 	"Answer true if the image stream format is understood by this decoder."
- 	self isPluginPresent ifFalse:[^false]. "cannot read it otherwise"
- 	self next = 16rFF ifFalse: [^ false].
- 	self next = 16rD8 ifFalse: [^ false].
- 	^ true
- !

Item was removed:
- Object subclass: #LayoutFrame
- 	instanceVariableNames: 'leftFraction leftOffset topFraction topOffset rightFraction rightOffset bottomFraction bottomOffset'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Primitives'!
- 
- !LayoutFrame commentStamp: '<historical>' prior: 0!
- I define a frame for positioning some morph in a proportional layout.
- 
- Instance variables:
- 	leftFraction 
- 	topFraction 
- 	rightFraction 
- 	bottomFraction 	<Float>		The fractional distance (between 0 and 1) to place the morph in its owner's bounds
- 	leftOffset 
- 	topOffset 
- 	rightOffset 
- 	bottomOffset 	<Integer>	Fixed pixel offset to apply after fractional positioning (e.g., "10 pixel right of the center of the owner")!

Item was removed:
- ----- Method: LayoutFrame class>>classVersion (in category 'accessing') -----
- classVersion
- 	^ 2 "fractions and offsets are never 'nil' anymore"
- !

Item was removed:
- ----- Method: LayoutFrame class>>fractions: (in category 'instance creation') -----
- fractions: fractionsOrNil
- 	^self fractions: fractionsOrNil offsets: nil!

Item was removed:
- ----- Method: LayoutFrame class>>fractions:offsets: (in category 'instance creation') -----
- fractions: fractionsOrNil offsets: offsetsOrNil
- 
- 	| fractions offsets |
- 
- 	fractions := fractionsOrNil ifNil: [0 at 0 extent: 0 at 0].
- 	offsets := offsetsOrNil ifNil: [0 at 0 extent: 0 at 0].
- 	^self new
- 		topFraction: fractions top offset: offsets top;
- 		leftFraction: fractions left offset: offsets left;
- 		bottomFraction: fractions bottom offset: offsets bottom;
- 		rightFraction: fractions right offset: offsets right
- !

Item was removed:
- ----- Method: LayoutFrame class>>fullFrame (in category 'instance creation') -----
- fullFrame
- 
- 	^ self fractions: (0 @ 0 corner: 1 @ 1)!

Item was removed:
- ----- Method: LayoutFrame class>>offsets: (in category 'instance creation') -----
- offsets: offsetsOrNil
- 	^self fractions: nil offsets: offsetsOrNil!

Item was removed:
- ----- Method: LayoutFrame class>>withClassVersion: (in category 'objects from disk') -----
- withClassVersion: aVersion
- 
- 	aVersion <= self classVersion ifTrue: [^ self].
- 	^ super withClassVersion: aVersion!

Item was removed:
- ----- Method: LayoutFrame>>bottomFraction (in category 'accessing') -----
- bottomFraction
- 	^bottomFraction!

Item was removed:
- ----- Method: LayoutFrame>>bottomFraction: (in category 'accessing') -----
- bottomFraction: aNumber
- 	bottomFraction := aNumber!

Item was removed:
- ----- Method: LayoutFrame>>bottomFraction:offset: (in category 'accessing') -----
- bottomFraction: aNumber offset: anInteger
- 
- 	bottomFraction := aNumber.
- 	bottomOffset := anInteger!

Item was removed:
- ----- Method: LayoutFrame>>bottomOffset (in category 'accessing') -----
- bottomOffset
- 	^bottomOffset!

Item was removed:
- ----- Method: LayoutFrame>>bottomOffset: (in category 'accessing') -----
- bottomOffset: anInteger
- 	bottomOffset := anInteger!

Item was removed:
- ----- Method: LayoutFrame>>convertToCurrentVersion:refStream: (in category 'objects from disk') -----
- convertToCurrentVersion: varDict refStream: smartRefStrm
- 	| className oldClassVersion |
- 
- 	"JW 2/1/2001"
- 	"Since class version isn't passed in varDict, look it up through smartRefSrm."
- 	className := varDict at: #ClassName.
- 	oldClassVersion := (smartRefStrm structures at: className) first.
- 	(oldClassVersion = 0) ifTrue: [ self negateBottomRightOffsets; fixup ].
- 	(oldClassVersion = 1) ifTrue: [ self fixup ].
- 	^super convertToCurrentVersion: varDict refStream: smartRefStrm.
- !

Item was removed:
- ----- Method: LayoutFrame>>fixup (in category 'objects from disk') -----
- fixup
- 	"Set-up default value for un-initialized layout frames"
- 	
- 	"LayoutFrame allInstancesDo: [:e | e fixup]."
- 	
- 	leftFraction ifNil: [leftFraction := 0].
- 	leftOffset ifNil: [leftOffset := 0].
- 	topFraction ifNil: [topFraction := 0].
- 	topOffset ifNil: [topOffset := 0].
- 	rightFraction ifNil: [rightFraction := 0].
- 	rightOffset ifNil: [rightOffset := 0].
- 	bottomFraction ifNil: [bottomFraction := 0].
- 	bottomOffset ifNil: [bottomOffset := 0].!

Item was removed:
- ----- Method: LayoutFrame>>hasFixedHeight (in category 'testing') -----
- hasFixedHeight
- 
- 	^ self topFraction = self bottomFraction!

Item was removed:
- ----- Method: LayoutFrame>>hasFixedWidth (in category 'testing') -----
- hasFixedWidth
- 
- 	^ self leftFraction = self rightFraction!

Item was removed:
- ----- Method: LayoutFrame>>initialize (in category 'initialize-release') -----
- initialize
- 	"By default, let the frame be empty.
- 	This way, we can later define a proportional layout via fractions,
- 	or a fixed layout via offsets, or whatever mixture of both."
- 	
- 	leftFraction := leftOffset := topFraction := topOffset := rightFraction := rightOffset := bottomFraction := bottomOffset := 0!

Item was removed:
- ----- Method: LayoutFrame>>layout:in: (in category 'layout') -----
- layout: oldBounds in: newBounds
- 	"Return the proportional rectangle insetting the given bounds"
- 	| left right top bottom | 
- 	left := newBounds left + (newBounds width * leftFraction).
- 	left := left + leftOffset.
- 	right := newBounds right - (newBounds width * (1.0 - rightFraction)).
- 	right := right + rightOffset.
- 	top := newBounds top + (newBounds height * topFraction).
- 	top := top + topOffset.
- 	bottom := newBounds bottom - (newBounds height * (1.0 - bottomFraction)).
- 	bottom := bottom + bottomOffset.
- 	^(left rounded @ top rounded) corner: (right rounded @ bottom rounded)!

Item was removed:
- ----- Method: LayoutFrame>>leftFraction (in category 'accessing') -----
- leftFraction
- 	^leftFraction!

Item was removed:
- ----- Method: LayoutFrame>>leftFraction: (in category 'accessing') -----
- leftFraction: aNumber
- 	leftFraction := aNumber!

Item was removed:
- ----- Method: LayoutFrame>>leftFraction:offset: (in category 'accessing') -----
- leftFraction: aNumber offset: anInteger
- 
- 	leftFraction := aNumber.
- 	leftOffset := anInteger!

Item was removed:
- ----- Method: LayoutFrame>>leftOffset (in category 'accessing') -----
- leftOffset
- 	^leftOffset!

Item was removed:
- ----- Method: LayoutFrame>>leftOffset: (in category 'accessing') -----
- leftOffset: anInteger
- 	leftOffset := anInteger!

Item was removed:
- ----- Method: LayoutFrame>>minExtentFrom: (in category 'layout') -----
- minExtentFrom: minExtent
- 	"Return the minimal extent the given bounds can be represented in"
- 	^ (self minWidthFrom: minExtent x) @ (self minHeightFrom: minExtent y)!

Item was removed:
- ----- Method: LayoutFrame>>minHeightFrom: (in category 'layout') -----
- minHeightFrom: minHeight
- 	"Return the minimal height the given bounds can be represented in
- 	we have:
- 		top = (height * topFraction + topOffset)
- 		bottom = (height * bottomFraction + bottomOffset)
- 	we want to fullfill those constraints if possible:
- 		0 <= top <= height
- 		0 <= bottom <= heigth
- 		bottom - top >= minHeight"
- 	| height |
- 	height := bottomFraction = topFraction
- 		ifTrue: [0]
- 		ifFalse: [minHeight + topOffset - bottomOffset / (bottomFraction - topFraction) max: 0].
- 	topFraction < 1 ifTrue: [height := height max: topOffset / (1 - topFraction)].
- 	bottomFraction < 1 ifTrue: [height := height max: bottomOffset / (1 - bottomFraction)].
- 	topFraction > 0 ifTrue: [height := height max: topOffset negated / topFraction].
- 	bottomFraction > 0 ifTrue: [height := height max: bottomOffset negated / bottomFraction].
- 	^ height truncated!

Item was removed:
- ----- Method: LayoutFrame>>minWidthFrom: (in category 'layout') -----
- minWidthFrom: minWidth
- 	"Return the minimal width the given bounds can be represented in
- 	we have:
- 		left = (width * leftFraction + leftOffset)
- 		right = (width * rightFraction + rightOffset)
- 	we want to fullfill those constraints if possible:
- 		0 <= left <= width
- 		0 <= right <= heigth
- 		right - left >= minwidth"
- 	| width |
- 	width := rightFraction = leftFraction
- 		ifTrue: [0]
- 		ifFalse: [minWidth + leftOffset - rightOffset / (rightFraction - leftFraction) max: 0].
- 	leftFraction < 1 ifTrue: [width := width max: leftOffset / (1 - leftFraction)].
- 	rightFraction < 1 ifTrue: [width := width max: rightOffset / (1 - rightFraction)].
- 	leftFraction > 0 ifTrue: [width := width max: leftOffset negated / leftFraction].
- 	rightFraction > 0 ifTrue: [width := width max: rightOffset negated / rightFraction].
- 	^ width truncated!

Item was removed:
- ----- Method: LayoutFrame>>negateBottomRightOffsets (in category 'objects from disk') -----
- negateBottomRightOffsets
- 
- 	bottomOffset ifNotNil: [ bottomOffset := bottomOffset negated ].
- 	rightOffset ifNotNil: [ rightOffset := rightOffset negated ].
- 
- !

Item was removed:
- ----- Method: LayoutFrame>>printOn: (in category 'printing') -----
- printOn: aStream
- 
- 	super printOn: aStream.
- 	
- 	aStream nextPutAll: '( '.
- 	
- 	{ {'l'. self leftFraction. self leftOffset}. {'t'. self topFraction. self topOffset}. {'r'. self rightFraction. self rightOffset}. {'b'. self bottomFraction. self bottomOffset} } do: [:spec |
- 		aStream nextPutAll: spec first; space.
- 		
- 		spec second printOn: aStream maxDecimalPlaces: 2.
- 		
- 		aStream nextPutAll: (spec third >= 0 ifTrue: ['+'] ifFalse: ['-']).
- 		spec third abs printOn: aStream maxDecimalPlaces: 0]
- 			separatedBy: [aStream space].
- 			
- 	aStream nextPutAll: ' )'.!

Item was removed:
- ----- Method: LayoutFrame>>rightFraction (in category 'accessing') -----
- rightFraction
- 	^rightFraction!

Item was removed:
- ----- Method: LayoutFrame>>rightFraction: (in category 'accessing') -----
- rightFraction: aNumber
- 	rightFraction := aNumber!

Item was removed:
- ----- Method: LayoutFrame>>rightFraction:offset: (in category 'accessing') -----
- rightFraction: aNumber offset: anInteger
- 
- 	rightFraction := aNumber.
- 	rightOffset := anInteger!

Item was removed:
- ----- Method: LayoutFrame>>rightOffset (in category 'accessing') -----
- rightOffset
- 	^rightOffset!

Item was removed:
- ----- Method: LayoutFrame>>rightOffset: (in category 'accessing') -----
- rightOffset: anInteger
- 	rightOffset := anInteger!

Item was removed:
- ----- Method: LayoutFrame>>topFraction (in category 'accessing') -----
- topFraction
- 	^topFraction!

Item was removed:
- ----- Method: LayoutFrame>>topFraction: (in category 'accessing') -----
- topFraction: aNumber
- 	topFraction := aNumber!

Item was removed:
- ----- Method: LayoutFrame>>topFraction:offset: (in category 'accessing') -----
- topFraction: aNumber offset: anInteger
- 
- 	topFraction := aNumber.
- 	topOffset := anInteger!

Item was removed:
- ----- Method: LayoutFrame>>topOffset (in category 'accessing') -----
- topOffset
- 	^topOffset!

Item was removed:
- ----- Method: LayoutFrame>>topOffset: (in category 'accessing') -----
- topOffset: anInteger
- 	topOffset := anInteger!

Item was removed:
- Object subclass: #LzwGifDecoder
- 	instanceVariableNames: 'suffixTable prefixTable eoiCode clearCode bitMask codeSize minimumCodeSize maxCode nextAvailableCode numLeftoverBits codeStream codeStreamBuffer outBlock'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!
- 
- !LzwGifDecoder commentStamp: '' prior: 0!
- I implement the modified Lempel-Ziv-Welch (LZW) algorithm for lossless GIF decompression. My primary purpose is to decode streams of bytes that have been encoded with this modified version of LZW as used in the GIF standard.
- 
- My instances require, at minimum, a maximum code size (via #maxCode:), a minimum code size (via #minimumCodeSize:), and of course a stream of bytes to decode (via #codeStream:). Once these are set, implementors can simply send the #decode message, which will respond with a decoded ByteArray.
- 
- Optionally, implementors can make use of the #onDecodedBit: message, which takes a Block with a single argument corresponding to a decoded bit. This Block is called each time a complete byte/bit-level value for the bitmap has been decoded.
- 
- For an example of use, see GIFReadWriter >> #readBitDataOnFrame:.
- 
- I am separated out from GIFReadWriter for clarity and better debugging.
- 
- 
- 
- See:
- https://en.wikipedia.org/wiki/Lempel%E2%80%93Ziv%E2%80%93Welch
- https://www.w3.org/Graphics/GIF/spec-gif89a.txt
- 
- !

Item was removed:
- ----- Method: LzwGifDecoder>>bufferData (in category 'as yet unclassified') -----
- bufferData
- 	"The GIF Format stores the data for each image in sub-blocks of up to 255 bytes.
- 	Decoding LZW for such small chunks adds a LOT of overhead.
- 	So instead, we buffer *all* of the data into one ByteArray and provide stream access
- 	to it.
- 	Data sub-blocks are structured such that the first byte gives the size of the data chunk
- 	that follows. A size of 0 indicates that there is no more data to deal with"
- 	| chunkSize buff |
- 	buff := WriteStream on: ByteArray new.
- 	chunkSize := codeStream next.
- 	[ chunkSize > 0 ] whileTrue: [
- 		buff nextPutAll: (codeStream next: chunkSize).
- 		chunkSize := codeStream next ].
- 	"chunkSize > 0 ifTrue: [ buff nextPutAll: (codeStream next: chunkSize)]."
- 	codeStreamBuffer := buff contents readStream!

Item was removed:
- ----- Method: LzwGifDecoder>>checkCodeSize (in category 'private') -----
- checkCodeSize
- 	"Ensure that the next available code to enter
- 	into the table is not equal to the bitMask.
- 	If it is, we increment the code size and update the
- 	mask value."
- 	nextAvailableCode := nextAvailableCode + 1.
- 	(nextAvailableCode bitAnd: bitMask) = 0
- 		ifTrue: [ 
- 			"GIF89a specifies a 'deferred' clearCode
- 			implementation, which means we keep going
- 			with the current table even if its full but
- 			a clear hasn't been found. We use the max
- 			code size at that point."
- 			nextAvailableCode >= maxCode ifTrue: [ ^ self ].
- 			codeSize := codeSize + 1.
- 			bitMask := bitMask + nextAvailableCode ].!

Item was removed:
- ----- Method: LzwGifDecoder>>codeStream: (in category 'private') -----
- codeStream: aReadableStream 
- 	"Set the stream of encoded bytes we will decode
- 	to be the internal codeStream. We read off the first
- 	byte immediately, which tells us how many subsequent bytes
- 	to use in our buffer for decoding"
- 	| chunkSize buff |
- 	codeStream := aReadableStream.
- 	"chunkSize := codeStream next.
- 	codeStreamBuffer := ReadStream on: (codeStream next: chunkSize)."
- 	self bufferData
- 	!

Item was removed:
- ----- Method: LzwGifDecoder>>decode (in category 'api') -----
- decode
- 	| currentCode prevCode outStream |
- 	self initializeTables.
- 	outStream := WriteStream with: (ByteArray new).
- 	numLeftoverBits := 0.
- 	currentCode := self nextCode.
- 	currentCode = clearCode ifFalse: [ ^ self error: 'First code on the stream should always be the clear code!!' ].
- 	
- 	"The first real code simply gets output
- 	onto the stream, then we enter the loop"
- 	currentCode := self nextCode.
- 	self writeBit: currentCode on: outStream.
- 	prevCode := currentCode.
- 	currentCode := self nextCode.
- 	[ currentCode = eoiCode ] whileFalse: [ 
- 		currentCode = clearCode
- 			ifTrue: [ 
- 				self initializeTables.
- 				currentCode := self nextCode.
- 				self
- 					writeBit: (suffixTable at: (currentCode + 1))
- 					on: outStream.
- 				prevCode := nil ]
- 			ifFalse: [ self handleCode: currentCode withPreviousCode: prevCode on: outStream ].
- 		prevCode := currentCode.
- 		currentCode := self nextCode ].
- 	^ outStream contents.
- 
- 	
- 	!

Item was removed:
- ----- Method: LzwGifDecoder>>handleCode:withPreviousCode:on: (in category 'private') -----
- handleCode: anInteger withPreviousCode: prevInteger on: aWriteStream
- 	"Check for the code in the tables
- 	and perform the appropriate LZW action"
- 	| first searchIndex searchStack |
- 	"The code already exists in the table"
- 	anInteger < nextAvailableCode
- 		ifTrue: [ 
- 			anInteger < clearCode
- 				"If it's less than the clearCode
- 				then it is one of the original entries
- 				and we can simply use the suffix"
- 				ifTrue: [ 
- 					first := (suffixTable at: (anInteger + 1)).
- 					self writeBit: first on: aWriteStream ]
- 				"Otherwise we need to loop backwards along
- 				the prefix index values and take the suffix each
- 				time"
- 				ifFalse: [ 
- 					searchStack := OrderedCollection new.
- 					searchIndex := anInteger + 1.
- 					[ searchIndex > clearCode ] whileTrue: [ 
- 						searchStack add: (suffixTable at: searchIndex).
- 						searchIndex := (prefixTable at: searchIndex) + 1 ].
- 					searchStack add: (suffixTable at: searchIndex).
- 					first := searchStack last.
- 					searchStack reverseDo: [ :int |
- 						self writeBit: int on: aWriteStream ] ]. 
- 			]
- 		ifFalse: [ 
- 			"Here, the incoming code is not yet in the code tables"
- 			prevInteger < clearCode
- 				ifTrue: [ 
- 					first := (suffixTable at: (prevInteger + 1)).
- 					self
- 						writeBit: first on: aWriteStream;
- 						writeBit: first on: aWriteStream.
- 					 ]
- 				ifFalse: [ 
- 					searchStack := OrderedCollection new.
- 					searchIndex := prevInteger + 1.
- 					[ searchIndex > clearCode ] whileTrue: [ 
- 						searchStack add: (suffixTable at: searchIndex).
- 						searchIndex := (prefixTable at: searchIndex) + 1 ].
- 					searchStack add: (suffixTable at: searchIndex).
- 					first := searchStack last.
- 					searchStack reverseDo: [ :int |
- 						self writeBit: int on: aWriteStream ].
- 					self writeBit: first on: aWriteStream ]. 
- 			].
- 		"We add prevCode and the new
- 		suffix to a new entry in the code table, but
- 		only if we aren't at the max. NOTE: due to
- 		GIF 89a spec's 'deferred clear', if you get to
- 		the maxCode and haven't seen a clear, you stop
- 		writing to the tables but continue querying."
- 		nextAvailableCode >= maxCode
- 			ifFalse: [ 
- 				suffixTable at: (nextAvailableCode + 1) put: first.
- 				prefixTable at: (nextAvailableCode + 1) put: prevInteger ].
- 		self checkCodeSize.!

Item was removed:
- ----- Method: LzwGifDecoder>>initializeTables (in category 'initialization') -----
- initializeTables
- 	"The two arrays are our lookup tables.
- 	We do this instead of Dictionaries because
- 	the method is much, much faster"
- 	prefixTable := Array new: (maxCode).
- 	suffixTable := Array new: (maxCode).
- 	
- 	"The initial code size and mask settings
- 	also get reinitialized each time"
- 	codeSize := minimumCodeSize + 1.
- 	clearCode := (1 bitShift: minimumCodeSize).
- 	eoiCode := clearCode + 1.
- 	nextAvailableCode := clearCode + 2.
- 	bitMask := (1 bitShift: codeSize) - 1.
- 	
- 	"Fill the tables with the initial values"
- 	1 to: clearCode do: [ :n |
- 		prefixTable at: n put: (n - 1).
- 		suffixTable at: n put: (n - 1) ].!

Item was removed:
- ----- Method: LzwGifDecoder>>maxCode: (in category 'accessing') -----
- maxCode: anInteger 
- 	maxCode := anInteger!

Item was removed:
- ----- Method: LzwGifDecoder>>minimumCodeSize: (in category 'accessing') -----
- minimumCodeSize: anInteger 
- 	minimumCodeSize := anInteger!

Item was removed:
- ----- Method: LzwGifDecoder>>nextByte (in category 'private - packing') -----
- nextByte
- 	^ codeStreamBuffer next!

Item was removed:
- ----- Method: LzwGifDecoder>>nextCode (in category 'private') -----
- nextCode
- 	| integer numBitsRead newRemainder shiftAmount byte |
- 	"Retrieve the next code of codeSize bits.
- 	Store the remaining bits etc for later computation"
- 	integer := 0.
- 	numLeftoverBits = 0
- 		ifTrue: [ 
- 			numBitsRead := 8.
- 			shiftAmount := 0 ]
- 		ifFalse: [ 
- 			numBitsRead := numLeftoverBits.
- 			shiftAmount := numLeftoverBits - 8 ].
- 		[ numBitsRead < codeSize ] whileTrue: [ 
- 			byte := self nextByte.
- 			byte == nil ifTrue: [ ^ eoiCode ].
- 			integer := integer + (byte bitShift: shiftAmount).
- 			shiftAmount := shiftAmount + 8.
- 			numBitsRead := numBitsRead + 8 ].
- 		(newRemainder := numBitsRead - codeSize) = 0
- 			ifTrue: [ byte := self nextByte ]
- 			ifFalse: [ byte := self peekByte ].
- 		byte == nil ifTrue: [ ^ eoiCode ].
- 		numLeftoverBits := newRemainder.
- 		^ integer + (byte bitShift: shiftAmount) bitAnd: bitMask.!

Item was removed:
- ----- Method: LzwGifDecoder>>onDecodedBit: (in category 'accessing') -----
- onDecodedBit: aBlock
- 	"This block will be executed once each time a new
- 	value is decoded from the stream, with the value
- 	as the sole argument passed to the block"
- 	outBlock := aBlock!

Item was removed:
- ----- Method: LzwGifDecoder>>peekByte (in category 'private - packing') -----
- peekByte
- 	^ codeStreamBuffer peek!

Item was removed:
- ----- Method: LzwGifDecoder>>writeBit:on: (in category 'writing') -----
- writeBit: anInteger on: aWriteStream
- 	"Write the incoming decoded value onto a
- 	writestream. If I have an outBlock set, 
- 	send this value also"
- 	aWriteStream nextPut: anInteger.
- 	outBlock ifNil: [ ^ self ].
- 	outBlock value: anInteger.!

Item was removed:
- Object subclass: #LzwGifEncoder
- 	instanceVariableNames: 'suffixTable prefixTable eoiCode clearCode codeSize minimumCodeSize maxCode nextAvailableCode numLeftoverBits bitBuffer codeStream codeStreamBuffer rowByteSize xPos yPos dimensions'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!
- 
- !LzwGifEncoder commentStamp: '' prior: 0!
- I implement the modified Lempel-Ziv-Welch (LZW) algorithm for lossless GIF bitmap compression. My primary purpose is to encode/compress streams of bitmap bytes as specified by the GIF standard.
- 
- My instances require at minimum:
- - A size of bytes in a row of bitmap bits for the image (#rowByteSize:)
- - The extent of the image being encoded (#extent:)
- - An array of bits in a bitmap (as bytes) for encoding (sent with #encode:)
- - A stream of Bytes on which to output the encoded bytes (#codeStream:)
- - A minimum code size as specified from GIF header information (#minimimCodeSize:)
- 
- Once all of these are set, implementors simply send the #encode: message along with a
- collection of bitmap values as bytes that need to be encoded. Instead of responding with a collection of encoded bytes, #encode: will write to the output stream specified by #codeStream: directly.
- 
- For an example of use, see GIFReadWriter >> #writeBitData:
- 
- NOTE: LZW compression for GIFs is complex and the #encode: method is largely taken verbatim from Kazuki Yasumatsu's 1995 Squeak implementation (as opposed to the Decoder, which was heavily refactored for readability and comprehension). Any contributions to fleshing this out in a comprehensible way are much appreciated!!
- 
- See:
- https://en.wikipedia.org/wiki/Lempel%E2%80%93Ziv%E2%80%93Welch
- https://www.w3.org/Graphics/GIF/spec-gif89a.txt!

Item was removed:
- ----- Method: LzwGifEncoder>>checkCodeSize (in category 'private') -----
- checkCodeSize
- 	"Determine whether or not we need to increment
- 	the codeSize"
- 	(nextAvailableCode > maxCode and: [ codeSize < 12 ])
- 		ifTrue: [ 
- 			codeSize := codeSize + 1.
- 			maxCode := (1 bitShift: codeSize) - 1 ].!

Item was removed:
- ----- Method: LzwGifEncoder>>checkSettings (in category 'private') -----
- checkSettings
- 	"Ensure that the appropriate variables
- 	that are needed for proper encoding
- 	have been set"
- 	codeStream ifNil: [ ^ self error: 'You must set a codeStream (byte stream) to write onto!!' ].
- 	dimensions ifNil: [ ^ self error: 'You must provide the extent of the image we will encode!!' ].
- 	rowByteSize ifNil: [ ^ self error: 'You must provide a rowByteSize for the supplied image bits!!' ].!

Item was removed:
- ----- Method: LzwGifEncoder>>codeStream: (in category 'accessing') -----
- codeStream: aByteStream
- 	codeStream := aByteStream.!

Item was removed:
- ----- Method: LzwGifEncoder>>dimensions: (in category 'accessing') -----
- dimensions: anExtentPoint
- 	"Set the extent (as point) of the
- 	image that will be encoded"
- 	dimensions := anExtentPoint!

Item was removed:
- ----- Method: LzwGifEncoder>>encode: (in category 'converting') -----
- encode: bits
- 	| maxBits maxMaxCode tSize tShift fCode ent pixel index nomatch disp |
- 	self checkSettings.
- 	xPos := yPos := 0.
- 	codeStream nextPut: minimumCodeSize.
- 	bitBuffer := 0.
- 	numLeftoverBits := 0.
- 	codeStreamBuffer := WriteStream on: (ByteArray new: 256).
- 	self initializeParameters.
- 	
- 	"These temp vars are taken from the
- 	original GIFReadWriter implementation"
- 	maxBits := 12.
- 	maxMaxCode := 1 bitShift: maxBits.
- 	tSize := 5003.
- 	prefixTable := Array new: tSize.
- 	suffixTable := Array new: tSize.
- 	tShift := 0.
- 	fCode := tSize.
- 	[ fCode < 65536 ] whileTrue: [ 
- 		tShift := tShift + 1.
- 		fCode := fCode * 2 ].
- 	tShift := 8 - tShift.
- 	1 to: tSize do: [ :i |
- 		suffixTable at: i put: -1 ].
- 	
- 	"We immediately write the clearCode
- 	to the output stream"
- 	self writeCodeAndCheckCodeSize: clearCode.
- 	
- 	"This loop is also taken from the original
- 	GIFReadWriter implementation"
- 	ent := self readPixelFrom: bits.
- 	[ (pixel := self readPixelFrom: bits) == nil ] whileFalse: 
- 		[ fCode := (pixel bitShift: maxBits) + ent.
- 		index := ((pixel bitShift: tShift) bitXor: ent) + 1.
- 		(suffixTable at: index) = fCode 
- 			ifTrue: [ ent := prefixTable at: index ]
- 			ifFalse: 
- 				[ nomatch := true.
- 				(suffixTable at: index) >= 0 ifTrue: 
- 					[ disp := tSize - index + 1.
- 					index = 1 ifTrue: [ disp := 1 ].
- 					"probe"
- 					
- 					[ (index := index - disp) < 1 ifTrue: [ index := index + tSize ].
- 					(suffixTable at: index) = fCode ifTrue: 
- 						[ ent := prefixTable at: index.
- 						nomatch := false
- 						"continue whileFalse:" ].
- 					nomatch and: [ (suffixTable at: index) > 0 ] ] whileTrue: 
- 						[ "probe"
- 						 ] ].
- 				"nomatch"
- 				nomatch ifTrue: 
- 					[ self writeCodeAndCheckCodeSize: ent.
- 					ent := pixel.
- 					nextAvailableCode < maxMaxCode 
- 						ifTrue: 
- 							[ prefixTable 
- 								at: index
- 								put: nextAvailableCode.
- 							suffixTable 
- 								at: index
- 								put: fCode.
- 							nextAvailableCode := nextAvailableCode + 1 ]
- 						ifFalse: 
- 							[ self writeCodeAndCheckCodeSize: clearCode.
- 							1 
- 								to: tSize
- 								do: 
- 									[ :i | 
- 									suffixTable 
- 										at: i
- 										put: -1 ].
- 							self initializeParameters ] ] ] ].
- 	prefixTable := suffixTable := nil.
- 	self writeCodeAndCheckCodeSize: ent.
- 	self writeCodeAndCheckCodeSize: eoiCode.
- 	self flushBits.
- 	codeStream nextPut: 0.
- 				!

Item was removed:
- ----- Method: LzwGifEncoder>>extent: (in category 'accessing') -----
- extent: anExtentPoint
- 	"Set the extent (as point) of the
- 	image that will be encoded"
- 	dimensions := anExtentPoint!

Item was removed:
- ----- Method: LzwGifEncoder>>flushBits (in category 'private - bits access') -----
- flushBits
- 	numLeftoverBits = 0 ifFalse: 
- 		[ self nextBytePut: bitBuffer.
- 		numLeftoverBits := 0 ].
- 	self flushBuffer!

Item was removed:
- ----- Method: LzwGifEncoder>>flushBuffer (in category 'private') -----
- flushBuffer
- 	"Write out the current codeStreamBuffer size,
- 	followed by its actual contents, to the true
- 	output codeStream"
- 	codeStreamBuffer isEmpty ifTrue: [ ^ self ].
- 	codeStream
- 		nextPut: codeStreamBuffer size;
- 		nextPutAll: codeStreamBuffer contents.
- 	codeStreamBuffer := (ByteArray new: 256) writeStream.!

Item was removed:
- ----- Method: LzwGifEncoder>>initializeParameters (in category 'initialization') -----
- initializeParameters
- 	"The initial code size and mask settings
- 	also get reinitialized each time"
- 	codeSize := minimumCodeSize + 1.
- 	clearCode := (1 bitShift: minimumCodeSize).
- 	eoiCode := clearCode + 1.
- 	nextAvailableCode := clearCode + 2.
- 	maxCode := (1 bitShift: codeSize) - 1.!

Item was removed:
- ----- Method: LzwGifEncoder>>minimumCodeSize: (in category 'accessing') -----
- minimumCodeSize: anInteger
- 	minimumCodeSize := anInteger!

Item was removed:
- ----- Method: LzwGifEncoder>>nextBytePut: (in category 'private - packing') -----
- nextBytePut: anInteger
- 	"Write a complete byte to the output byteStream.
- 	Be sure to reset one we reach the limit, which is
- 	255 for GIF files. Then write the length of the next
- 	byte chunks to the stream also"
- 	codeStreamBuffer nextPut: anInteger.
- 	codeStreamBuffer size >= 254
- 		ifTrue: [ self flushBuffer ].!

Item was removed:
- ----- Method: LzwGifEncoder>>nextCodePut: (in category 'private - bits access') -----
- nextCodePut: anInteger
- 	"Attempt to put the bits on the
- 	output stream. If we have remaining bits,
- 	then we need to use bitwise operations to
- 	fill the next byte properly before putting
- 	it on the output stream"
- 	| numBitsWritten shiftCount newInteger |
- 	shiftCount := 0.
- 	numLeftoverBits = 0
- 		ifTrue: [ 
- 			numBitsWritten := 8.
- 			newInteger := anInteger ]
- 		ifFalse: [ 
- 			numBitsWritten := numLeftoverBits.
- 			newInteger := bitBuffer + (anInteger bitShift: 8 - numLeftoverBits) ].
- 	[ numBitsWritten < codeSize ] whileTrue: [ 
- 		self nextBytePut: ((newInteger bitShift: shiftCount) bitAnd: 255).
- 		shiftCount := shiftCount - 8.
- 		numBitsWritten := numBitsWritten + 8 ].
- 	(numLeftoverBits := numBitsWritten - codeSize) = 0
- 		ifTrue: [ self nextBytePut: (newInteger bitShift: shiftCount) ]
- 		ifFalse: [ bitBuffer := newInteger bitShift: shiftCount ].
- 	^ anInteger
- 	!

Item was removed:
- ----- Method: LzwGifEncoder>>readPixelFrom: (in category 'private - encoding') -----
- readPixelFrom: bits
- 	"Using the current x and y positions and
- 	the specified byte size for a row, determine
- 	the value for the next pixel in the provided bits"
- 	| pixel |
- 	yPos >= (dimensions y) ifTrue: [ ^ nil ].
- 	pixel := bits byteAt: yPos * rowByteSize + xPos + 1.
- 	self updatePixelPosition.
- 	^ pixel
- 	!

Item was removed:
- ----- Method: LzwGifEncoder>>rowByteSize: (in category 'accessing') -----
- rowByteSize: anInteger
- 	rowByteSize := anInteger!

Item was removed:
- ----- Method: LzwGifEncoder>>updatePixelPosition (in category 'private') -----
- updatePixelPosition
- 	"Increment the xPos. If we are at the width
- 	position, set xPos to 0 and increment the yPos"
- 	xPos := xPos + 1.
- 	xPos >= (dimensions x) ifFalse: [ ^ self ].
- 	xPos := 0.
- 	yPos := yPos + 1.!

Item was removed:
- ----- Method: LzwGifEncoder>>writeCodeAndCheckCodeSize: (in category 'writing') -----
- writeCodeAndCheckCodeSize: aCode
- 	self nextCodePut: aCode.
- 	self checkCodeSize.!

Item was removed:
- HostWindowProxy subclass: #MacOS9WindowProxy
- 	instanceVariableNames: 'windowClass windowAttributes'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-External-Ffenestri'!

Item was removed:
- ----- Method: MacOS9WindowProxy class>>altDBoxProc (in category 'constants') -----
- altDBoxProc
- 	^3
- !

Item was removed:
- ----- Method: MacOS9WindowProxy class>>closeBoxAttribute (in category 'constants') -----
- closeBoxAttribute
- 	^1!

Item was removed:
- ----- Method: MacOS9WindowProxy class>>dBoxProc (in category 'constants') -----
- dBoxProc
- 	^1!

Item was removed:
- ----- Method: MacOS9WindowProxy class>>documentProc (in category 'constants') -----
- documentProc
- 	^0!

Item was removed:
- ----- Method: MacOS9WindowProxy class>>documentWindowClass (in category 'constants') -----
- documentWindowClass
- 	^self zoomDocProc!

Item was removed:
- ----- Method: MacOS9WindowProxy class>>floatGrowProc (in category 'constants') -----
- floatGrowProc
- 	^1987
- !

Item was removed:
- ----- Method: MacOS9WindowProxy class>>floatProc (in category 'constants') -----
- floatProc
- 	^1985
- !

Item was removed:
- ----- Method: MacOS9WindowProxy class>>floatSideGrowProc (in category 'constants') -----
- floatSideGrowProc
- 	^1995
- !

Item was removed:
- ----- Method: MacOS9WindowProxy class>>floatSideProc (in category 'constants') -----
- floatSideProc
- 	^1993
- !

Item was removed:
- ----- Method: MacOS9WindowProxy class>>floatSideZoomGrowProc (in category 'constants') -----
- floatSideZoomGrowProc
- 	^1999!

Item was removed:
- ----- Method: MacOS9WindowProxy class>>floatSideZoomProc (in category 'constants') -----
- floatSideZoomProc
- 	^1997!

Item was removed:
- ----- Method: MacOS9WindowProxy class>>floatZoomGrowProc (in category 'constants') -----
- floatZoomGrowProc
- 	^1991
- !

Item was removed:
- ----- Method: MacOS9WindowProxy class>>floatZoomProc (in category 'constants') -----
- floatZoomProc
- 	^1989
- !

Item was removed:
- ----- Method: MacOS9WindowProxy class>>isActiveHostWindowProxyClass (in category 'system startup') -----
- isActiveHostWindowProxyClass
- "Am I active?"
- 	^Smalltalk platformName  = 'Mac OS' and: [Smalltalk osVersion asInteger < 1000]!

Item was removed:
- ----- Method: MacOS9WindowProxy class>>movableDBoxProc (in category 'constants') -----
- movableDBoxProc
- 	^5
- !

Item was removed:
- ----- Method: MacOS9WindowProxy class>>noAttributes (in category 'constants') -----
- noAttributes
- 	^0!

Item was removed:
- ----- Method: MacOS9WindowProxy class>>noGrowDocProc (in category 'constants') -----
- noGrowDocProc
- 	^4
- !

Item was removed:
- ----- Method: MacOS9WindowProxy class>>plainDBox (in category 'constants') -----
- plainDBox
- 	^2!

Item was removed:
- ----- Method: MacOS9WindowProxy class>>rDocProc (in category 'constants') -----
- rDocProc
- 	^16
- !

Item was removed:
- ----- Method: MacOS9WindowProxy class>>standardDocumentAttributes (in category 'constants') -----
- standardDocumentAttributes 
- 	^self closeBoxAttribute!

Item was removed:
- ----- Method: MacOS9WindowProxy class>>zoomDocProc (in category 'constants') -----
- zoomDocProc
- 	^8!

Item was removed:
- ----- Method: MacOS9WindowProxy class>>zoomNoGrow (in category 'constants') -----
- zoomNoGrow
- 	^12
- !

Item was removed:
- ----- Method: MacOS9WindowProxy>>attributes (in category 'accessing') -----
- attributes
- 	| val |
- 	val := ByteArray new: 8.
- 	val 
- 		unsignedLongAt: 1
- 		put: windowClass
- 		bigEndian: Smalltalk isBigEndian.
- 	val 
- 		unsignedLongAt: 5
- 		put: windowAttributes
- 		bigEndian: Smalltalk isBigEndian.
- 	^ val!

Item was removed:
- ----- Method: MacOS9WindowProxy>>defaultWindowType (in category 'metrics') -----
- defaultWindowType
- 	self windowClass: self class documentWindowClass.
- 	self windowAttributes: self class standardDocumentAttributes.!

Item was removed:
- ----- Method: MacOS9WindowProxy>>windowAttributes (in category 'accessing') -----
- windowAttributes
- 	^windowAttributes
- !

Item was removed:
- ----- Method: MacOS9WindowProxy>>windowAttributes: (in category 'accessing') -----
- windowAttributes: aNumber
- 	windowAttributes := aNumber!

Item was removed:
- ----- Method: MacOS9WindowProxy>>windowClass (in category 'accessing') -----
- windowClass
- 	^windowClass
- !

Item was removed:
- ----- Method: MacOS9WindowProxy>>windowClass: (in category 'accessing') -----
- windowClass: aNumber
- 	windowClass := aNumber!

Item was removed:
- HostWindowProxy subclass: #MacOSXWindowProxy
- 	instanceVariableNames: 'windowClass windowAttributes'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-External-Ffenestri'!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>activatesAttribute (in category 'constants') -----
- activatesAttribute 
- 	^2 raisedTo: 17!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>alertWindowClass (in category 'constants') -----
- alertWindowClass
- 	^1!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>altPlainWindowClass (in category 'constants') -----
- altPlainWindowClass
- 	^16!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>asyncDragAttribute (in category 'constants') -----
- asyncDragAttribute 
- 	^2 raisedTo: 23!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>closeBoxAttribute (in category 'constants') -----
- closeBoxAttribute
- 	^2 raisedTo: 0!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>collapseBoxAttribute (in category 'constants') -----
- collapseBoxAttribute
- 	^2 raisedTo: 3!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>compositingAttribute (in category 'constants') -----
- compositingAttribute 
- 	^2 raisedTo: 19!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>documentWindowClass (in category 'constants') -----
- documentWindowClass
- 	^6!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>doesNotCycleAttribute (in category 'constants') -----
- doesNotCycleAttribute
- 	^2 raisedTo: 15!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>drawerWindowClass (in category 'constants') -----
- drawerWindowClass
- 	^20!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>floatingWindowClass (in category 'constants') -----
- floatingWindowClass
- 	^5!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>fullZoomAttribute (in category 'constants') -----
- fullZoomAttribute
- 	^self verticalZoomAttribute bitOr: self horizontalZoomAttribute!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>helpWindowClass (in category 'constants') -----
- helpWindowClass
- 	^10!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>hideOnFullScreenAttribute (in category 'constants') -----
- hideOnFullScreenAttribute 
- 	^2 raisedTo: 26!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>hideOnSuspendAttribute (in category 'constants') -----
- hideOnSuspendAttribute 
- 	^2 raisedTo: 24!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>horizontalZoomAttribute (in category 'constants') -----
- horizontalZoomAttribute
- 	^2 raisedTo: 1!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>ignoreClicksAttribute (in category 'constants') -----
- ignoreClicksAttribute 
- 	^2 raisedTo: 29!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>inWindowMenuAttribute (in category 'constants') -----
- inWindowMenuAttribute 
- 	^2 raisedTo: 27!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>isActiveHostWindowProxyClass (in category 'system startup') -----
- isActiveHostWindowProxyClass
- "Am I active?"
- 	^Smalltalk platformName  = 'Mac OS' and: [Smalltalk osVersion asInteger >= 1000]!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>liveResizeAttribute (in category 'constants') -----
- liveResizeAttribute 
- 	^2 raisedTo: 28!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>metalAttribute (in category 'constants') -----
- metalAttribute
- 	^2 raisedTo: 8!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>modalWindowClass (in category 'constants') -----
- modalWindowClass
- 	^3!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>movableAlertWindowClass (in category 'constants') -----
- movableAlertWindowClass
- 	^2!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>movableModalWindowClass (in category 'constants') -----
- movableModalWindowClass
- 	^4!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>noAttributes (in category 'constants') -----
- noAttributes
- 	^0!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>noConstrainAttribute (in category 'constants') -----
- noConstrainAttribute 
- 	^2 raisedTo: 31!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>noShadowAttribute (in category 'constants') -----
- noShadowAttribute 
- 	^2 raisedTo: 21!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>noUpdatesAttribute (in category 'constants') -----
- noUpdatesAttribute 
- 	^2 raisedTo: 16!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>opaqueForEventsAttribute (in category 'constants') -----
- opaqueForEventsAttribute 
- 	^2 raisedTo: 18!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>overlayWindowClass (in category 'constants') -----
- overlayWindowClass
- 	^14!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>plainWindowClass (in category 'constants') -----
- plainWindowClass
- 	^13!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>resizableAttribute (in category 'constants') -----
- resizableAttribute
- 	^2 raisedTo: 4!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>sheetAlertWindowClass (in category 'constants') -----
- sheetAlertWindowClass
- 	^15!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>sheetWindowClass (in category 'constants') -----
- sheetWindowClass
- 	^11!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>sideTitlebarAttribute (in category 'constants') -----
- sideTitlebarAttribute
- 	^2 raisedTo: 5!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>simpleWindowClass (in category 'constants') -----
- simpleWindowClass
- 	^18!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>standardDocumentAttributes (in category 'constants') -----
- standardDocumentAttributes 
- 	^self noConstrainAttribute + self standardHandlerAttribute + self closeBoxAttribute + self fullZoomAttribute + self collapseBoxAttribute + self resizableAttribute
- 
- 
- "16r8200001E printStringBase: 2 '2r 10000010 00000000 00000000 00011110'"!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>standardFloatingAttributes (in category 'constants') -----
- standardFloatingAttributes
- 	^self closeBoxAttribute + self collapseBoxAttribute
- !

Item was removed:
- ----- Method: MacOSXWindowProxy class>>standardHandlerAttribute (in category 'constants') -----
- standardHandlerAttribute 
- 	^2 raisedTo: 25!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>toolbarButtonAttribute (in category 'constants') -----
- toolbarButtonAttribute
- 	^2 raisedTo: 6!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>toolbarWindowClass (in category 'constants') -----
- toolbarWindowClass
- 	^12!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>utilityWindowClass (in category 'constants') -----
- utilityWindowClass
- 	^8!

Item was removed:
- ----- Method: MacOSXWindowProxy class>>verticalZoomAttribute (in category 'constants') -----
- verticalZoomAttribute
- 	^2 raisedTo: 2!

Item was removed:
- ----- Method: MacOSXWindowProxy>>attributes (in category 'accessing') -----
- attributes
- 	| val |
- 	val := ByteArray new: 8.
- 	val 
- 		unsignedLongAt: 1
- 		put: windowClass
- 		bigEndian: Smalltalk isBigEndian.
- 	val 
- 		unsignedLongAt: 5
- 		put: windowAttributes
- 		bigEndian: Smalltalk isBigEndian.
- 	^ val!

Item was removed:
- ----- Method: MacOSXWindowProxy>>defaultWindowType (in category 'metrics') -----
- defaultWindowType
- 	self windowClass: self class documentWindowClass.
- 	self windowAttributes: self class standardDocumentAttributes.!

Item was removed:
- ----- Method: MacOSXWindowProxy>>windowAttributes (in category 'accessing') -----
- windowAttributes
- 	^windowAttributes
- !

Item was removed:
- ----- Method: MacOSXWindowProxy>>windowAttributes: (in category 'accessing') -----
- windowAttributes: aNumber
- 	windowAttributes := aNumber!

Item was removed:
- ----- Method: MacOSXWindowProxy>>windowClass (in category 'accessing') -----
- windowClass
- 	^windowClass
- !

Item was removed:
- ----- Method: MacOSXWindowProxy>>windowClass: (in category 'accessing') -----
- windowClass: aNumber
- 	windowClass := aNumber!

Item was removed:
- DisplayTransform variableWordSubclass: #MatrixTransform2x3
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Transformations'!
- 
- !MatrixTransform2x3 commentStamp: '<historical>' prior: 0!
- This class represents a transformation for points, that is a combination of scale, offset, and rotation. It is implemented as a 2x3 matrix containing the transformation from the local coordinate system in the global coordinate system. Thus, transforming points from local to global coordinates is fast and cheap whereas transformations from global to local coordinate systems are relatively expensive.
- 
- Implementation Note: It is assumed that the transformation deals with Integer points. All transformations will return Integer coordinates (even though float points may be passed in here).!

Item was removed:
- ----- Method: MatrixTransform2x3 class>>identity (in category 'instance creation') -----
- identity
- 	^self new setScale: 1.0!

Item was removed:
- ----- Method: MatrixTransform2x3 class>>new (in category 'instance creation') -----
- new
- 	^self new: 6!

Item was removed:
- ----- Method: MatrixTransform2x3 class>>newFromStream: (in category 'instance creation') -----
- newFromStream: s
- 	"Only meant for my subclasses that are raw bits and word-like.  For quick unpack form the disk."
- 	self isPointers | self isWords not ifTrue: [^ super newFromStream: s].
- 		"super may cause an error, but will not be called."
- 	^ s nextWordsInto: (self new: 6)!

Item was removed:
- ----- Method: MatrixTransform2x3 class>>transformFromLocal:toGlobal: (in category 'instance creation') -----
- transformFromLocal: localBounds toGlobal: globalBounds
- 	^((self withOffset: (globalBounds center)) composedWithLocal:
- 		(self withScale: (globalBounds extent / localBounds extent) asFloatPoint))
- 			composedWithLocal: (self withOffset: localBounds center negated)
- "
- 	^(self identity)
- 		setScale: (globalBounds extent / localBounds extent) asFloatPoint;
- 		setOffset: localBounds center negated asFloatPoint;
- 		composedWithGlobal:(self withOffset: globalBounds center asFloatPoint)
- "!

Item was removed:
- ----- Method: MatrixTransform2x3 class>>withAngle: (in category 'instance creation') -----
- withAngle: angle
- 	^self new setAngle: angle!

Item was removed:
- ----- Method: MatrixTransform2x3 class>>withOffset: (in category 'instance creation') -----
- withOffset: aPoint
- 	^self identity setOffset: aPoint!

Item was removed:
- ----- Method: MatrixTransform2x3 class>>withRotation: (in category 'instance creation') -----
- withRotation: angle
- 	^self new setAngle: angle!

Item was removed:
- ----- Method: MatrixTransform2x3 class>>withScale: (in category 'instance creation') -----
- withScale: aPoint
- 	^self new setScale: aPoint!

Item was removed:
- ----- Method: MatrixTransform2x3>>= (in category 'comparing') -----
- = aMatrixTransform2x3 
- 	| length |
- 	<primitive: 'primitiveEqual' module: 'FloatArrayPlugin'>
- 	self class = aMatrixTransform2x3 class ifFalse: [^ false].
- 	length := self size.
- 	length = aMatrixTransform2x3 size ifFalse: [^ false].
- 	1 to: self size do: [:i | (self at: i)
- 			= (aMatrixTransform2x3 at: i) ifFalse: [^ false]].
- 	^ true!

Item was removed:
- ----- Method: MatrixTransform2x3>>a11 (in category 'element access') -----
- a11
- 	^self at: 1!

Item was removed:
- ----- Method: MatrixTransform2x3>>a11: (in category 'element access') -----
- a11: value
- 	 self at: 1 put: value!

Item was removed:
- ----- Method: MatrixTransform2x3>>a12 (in category 'element access') -----
- a12
- 	^self at: 2!

Item was removed:
- ----- Method: MatrixTransform2x3>>a12: (in category 'element access') -----
- a12: value
- 	 self at: 2 put: value!

Item was removed:
- ----- Method: MatrixTransform2x3>>a13 (in category 'element access') -----
- a13
- 	^self at: 3!

Item was removed:
- ----- Method: MatrixTransform2x3>>a13: (in category 'element access') -----
- a13: value
- 	 self at: 3 put: value!

Item was removed:
- ----- Method: MatrixTransform2x3>>a21 (in category 'element access') -----
- a21
- 	 ^self at: 4!

Item was removed:
- ----- Method: MatrixTransform2x3>>a21: (in category 'element access') -----
- a21: value
- 	 self at: 4 put: value!

Item was removed:
- ----- Method: MatrixTransform2x3>>a22 (in category 'element access') -----
- a22
- 	 ^self at: 5!

Item was removed:
- ----- Method: MatrixTransform2x3>>a22: (in category 'element access') -----
- a22: value
- 	 self at: 5 put: value!

Item was removed:
- ----- Method: MatrixTransform2x3>>a23 (in category 'element access') -----
- a23
- 	 ^self at: 6!

Item was removed:
- ----- Method: MatrixTransform2x3>>a23: (in category 'element access') -----
- a23: value
- 	 self at: 6 put: value!

Item was removed:
- ----- Method: MatrixTransform2x3>>asMatrixTransform2x3 (in category 'converting') -----
- asMatrixTransform2x3
- 	^self!

Item was removed:
- ----- Method: MatrixTransform2x3>>at: (in category 'accessing') -----
- at: index
- 	<primitive: 'primitiveAt' module: 'FloatArrayPlugin'>
- 	^Float fromIEEE32Bit: (self basicAt: index)!

Item was removed:
- ----- Method: MatrixTransform2x3>>at:put: (in category 'accessing') -----
- at: index put: value
- 	<primitive: 'primitiveAtPut' module: 'FloatArrayPlugin'>
- 	value isFloat 
- 		ifTrue:[self basicAt: index put: value asIEEE32BitWord]
- 		ifFalse:[self at: index put: value asFloat].
- 	^value!

Item was removed:
- ----- Method: MatrixTransform2x3>>byteSize (in category 'objects from disk') -----
- byteSize
- 	^self basicSize * self bytesPerBasicElement!

Item was removed:
- ----- Method: MatrixTransform2x3>>bytesPerBasicElement (in category 'objects from disk') -----
- bytesPerBasicElement
- 	"Answer the number of bytes that each of my basic elements requires.
- 	In other words:
- 		self basicSize * self bytesPerBasicElement
- 	should equal the space required on disk by my variable sized representation."
- 	^4!

Item was removed:
- ----- Method: MatrixTransform2x3>>bytesPerElement (in category 'objects from disk') -----
- bytesPerElement
- 
- 	^ 4.
- !

Item was removed:
- ----- Method: MatrixTransform2x3>>composedWithLocal: (in category 'composing') -----
- composedWithLocal: aTransformation
- 	"Return the composition of the receiver and the local transformation passed in"
- 	aTransformation isMatrixTransform2x3 ifFalse:[^super composedWithLocal: aTransformation].
- 	^self composedWithLocal: aTransformation asMatrixTransform2x3 into: self class new!

Item was removed:
- ----- Method: MatrixTransform2x3>>composedWithLocal:into: (in category 'composing') -----
- composedWithLocal: aTransformation into: result
- 	"Return the composition of the receiver and the local transformation passed in.
- 	Store the composed matrix into result."
- 	| a11 a12 a13 a21 a22 a23 b11 b12 b13 b21 b22 b23 matrix |
- 	<primitive: 'primitiveComposeMatrix' module: 'Matrix2x3Plugin'>
- 	matrix := aTransformation asMatrixTransform2x3.
- 	a11 := self a11.		b11 := matrix a11.
- 	a12 := self a12.		b12 := matrix a12.
- 	a13 := self a13.		b13 := matrix a13.
- 	a21 := self a21.		b21 := matrix a21.
- 	a22 := self a22.		b22 := matrix a22.
- 	a23 := self a23.		b23 := matrix a23.
- 	result a11: (a11 * b11) + (a12 * b21).
- 	result a12: (a11 * b12) + (a12 * b22).
- 	result a13: a13 + (a11 * b13) + (a12 * b23).
- 	result a21: (a21 * b11) + (a22 * b21).
- 	result a22: (a21 * b12) + (a22 * b22).
- 	result a23: a23 + (a21 * b13) + (a22 * b23).
- 	^result!

Item was removed:
- ----- Method: MatrixTransform2x3>>explorerContents (in category 'explorer') -----
- explorerContents
- 	^(Float32Array newFrom: self) explorerContents!

Item was removed:
- ----- Method: MatrixTransform2x3>>globalBounds:toLocal: (in category 'transforming rects') -----
- globalBounds: srcRect toLocal: dstRect
- 	"Transform aRectangle from global coordinates into local coordinates"
- 	<primitive: 'primitiveInvertRectInto' module: 'Matrix2x3Plugin'>
- 	^super globalBoundsToLocal: srcRect!

Item was removed:
- ----- Method: MatrixTransform2x3>>globalBoundsToLocal: (in category 'transforming rects') -----
- globalBoundsToLocal: aRectangle
- 	"Transform aRectangle from global coordinates into local coordinates"
- 	^self globalBounds: aRectangle toLocal: Rectangle new!

Item was removed:
- ----- Method: MatrixTransform2x3>>globalPointToLocal: (in category 'transforming points') -----
- globalPointToLocal: aPoint
- 	"Transform aPoint from global coordinates into local coordinates"
- 	<primitive: 'primitiveInvertPoint' module: 'Matrix2x3Plugin'>
- 	^(self invertPoint: aPoint) rounded!

Item was removed:
- ----- Method: MatrixTransform2x3>>hash (in category 'comparing') -----
- hash
- 	| result |
- 	<primitive: 'primitiveHashArray' module: 'FloatArrayPlugin'>
- 	result := 0.
- 	1 to: self size do:[:i| result := result + (self basicAt: i) ].
- 	^result bitAnd: 16r1FFFFFFF!

Item was removed:
- ----- Method: MatrixTransform2x3>>inverseTransformation (in category 'accessing') -----
- inverseTransformation
- 	"Return the inverse transformation of the receiver.
- 	The inverse transformation is computed by first calculating
- 	the inverse offset and then computing transformations
- 	for the two identity vectors (1 at 0) and (0 at 1)"
- 	| r1 r2 r3 m |
- 	r3 := self invertPoint: 0 at 0.
- 	r1 := (self invertPoint: 1 at 0) - r3.
- 	r2 := (self invertPoint: 0 at 1) - r3.
- 	m := self species new.
- 	m
- 		a11: r1 x; a12: r2 x; a13: r3 x;
- 		a21: r1 y; a22: r2 y; a23: r3 y.
- 	^m!

Item was removed:
- ----- Method: MatrixTransform2x3>>invertPoint: (in category 'transforming points') -----
- invertPoint: aPoint
- 	"Transform aPoint from global coordinates into local coordinates"
- 	| x y det a11 a12 a21 a22 detX detY |
- 	x := aPoint x asFloat - (self a13).
- 	y := aPoint y asFloat - (self a23).
- 	a11 := self a11.	a12 := self a12.
- 	a21 := self a21.	a22 := self a22.
- 	det := (a11 * a22) - (a12 * a21).
- 	det = 0.0 ifTrue:[^0 at 0]. "So we have at least a valid result"
- 	det := 1.0 / det.
- 	detX := (x * a22) - (a12 * y).
- 	detY := (a11 * y) - (x * a21).
- 	^(detX * det) @ (detY * det)!

Item was removed:
- ----- Method: MatrixTransform2x3>>isIdentity (in category 'testing') -----
- isIdentity
- 	"Return true if the receiver is the identity transform; that is, if applying to a point returns the point itself."
- 	<primitive: 'primitiveIsIdentity' module: 'Matrix2x3Plugin'>
- 	^self isPureTranslation and:[self a13 = 0.0 and:[self a23 = 0.0]]!

Item was removed:
- ----- Method: MatrixTransform2x3>>isMatrixTransform2x3 (in category 'testing') -----
- isMatrixTransform2x3
- 	"Return true if the receiver is 2x3 matrix transformation"
- 	^true!

Item was removed:
- ----- Method: MatrixTransform2x3>>isPureTranslation (in category 'testing') -----
- isPureTranslation
- 	"Return true if the receiver specifies no rotation or scaling."
- 	<primitive: 'primitiveIsPureTranslation' module: 'Matrix2x3Plugin'>
- 	^self a11 = 1.0 and:[self a12 = 0.0 and:[self a22 = 1.0 and:[self a21 = 0.0]]]!

Item was removed:
- ----- Method: MatrixTransform2x3>>localBounds:toGlobal: (in category 'transforming rects') -----
- localBounds: srcRect toGlobal: dstRect
- 	"Transform aRectangle from local coordinates into global coordinates"
- 	<primitive: 'primitiveTransformRectInto' module: 'Matrix2x3Plugin'>
- 	^super localBoundsToGlobal: srcRect!

Item was removed:
- ----- Method: MatrixTransform2x3>>localBoundsToGlobal: (in category 'transforming rects') -----
- localBoundsToGlobal: aRectangle
- 	"Transform aRectangle from local coordinates into global coordinates"
- 	^self localBounds: aRectangle toGlobal: Rectangle new!

Item was removed:
- ----- Method: MatrixTransform2x3>>localPointToGlobal: (in category 'transforming points') -----
- localPointToGlobal: aPoint
- 	"Transform aPoint from local coordinates into global coordinates"
- 	<primitive: 'primitiveTransformPoint' module: 'Matrix2x3Plugin'>
- 	^(self transformPoint: aPoint) rounded!

Item was removed:
- ----- Method: MatrixTransform2x3>>offset (in category 'accessing') -----
- offset
- 	"The translation applied to all transformed points."
- 	"Note: While other transform types also implement this method their actual behavior can differ. Only use it if you know what kind of transform you have on hand. Otherwise, use #localPointToGlobal: instead."
- 	^self a13 @ self a23!

Item was removed:
- ----- Method: MatrixTransform2x3>>offset: (in category 'accessing') -----
- offset: aPoint
- 	self a13: aPoint x asFloat.
- 	self a23: aPoint y asFloat.!

Item was removed:
- ----- Method: MatrixTransform2x3>>printOn: (in category 'printing') -----
- printOn: aStream
- 	aStream 
- 		nextPutAll: self class name;
- 		nextPut: $(;
- 		cr; print: self a11; tab; print: self a12; tab; print: self a13;
- 		cr; print: self a21; tab; print: self a22; tab; print: self a23;
- 		cr; nextPut:$).!

Item was removed:
- ----- Method: MatrixTransform2x3>>restoreEndianness (in category 'objects from disk') -----
- restoreEndianness
- 	"This word object was just read in from a stream.  It was stored in Big Endian (Mac) format.  Swap each pair of bytes (16-bit word), if the current machine is Little Endian.
- 	Why is this the right thing to do?  We are using memory as a byteStream.  High and low bytes are reversed in each 16-bit word, but the stream of words ascends through memory.  Different from a Bitmap."
- 
- 	| w b1 b2 b3 b4 |
- 	Smalltalk  isLittleEndian ifTrue: [
- 		1 to: self basicSize do: [:i |
- 			w := self basicAt: i.
- 			b1 := w digitAt: 1.
- 			b2 := w digitAt: 2.
- 			b3 := w digitAt: 3.
- 			b4 := w digitAt: 4.
- 			w := (b1 << 24) + (b2 << 16) + (b3 << 8) + b4.
- 			self basicAt: i put: w.
- 		]
- 	].
- 
- !

Item was removed:
- ----- Method: MatrixTransform2x3>>setAngle: (in category 'private') -----
- setAngle: angle
- 	"Set the raw rotation angle in the receiver"
- 	| rad s c |
- 	rad := angle degreesToRadians.
- 	s := rad sin.
- 	c := rad cos.
- 	self a11: c.
- 	self a12: s negated.
- 	self a21: s.
- 	self a22: c.!

Item was removed:
- ----- Method: MatrixTransform2x3>>setIdentiy (in category 'initialize') -----
- setIdentiy
- 	"Initialize the receiver to the identity transformation (e.g., not affecting points)"
- 	self
- 		a11: 1.0; a12: 0.0; a13: 0.0;
- 		a21: 0.0; a22: 1.0; a23: 0.0.!

Item was removed:
- ----- Method: MatrixTransform2x3>>setOffset: (in category 'private') -----
- setOffset: aPoint
- 	"Set the raw offset in the receiver"
- 	| pt |
- 	pt := aPoint asPoint.
- 	self a13: pt x asFloat.
- 	self a23: pt y asFloat.!

Item was removed:
- ----- Method: MatrixTransform2x3>>setScale: (in category 'private') -----
- setScale: aPoint
- 	"Set the raw scale in the receiver"
- 	| pt |
- 	pt := aPoint asPoint.
- 	self a11: pt x asFloat.
- 	self a22: pt y asFloat.!

Item was removed:
- ----- Method: MatrixTransform2x3>>transformDirection: (in category 'transforming points') -----
- transformDirection: aPoint
- 	"Transform aPoint from local coordinates into global coordinates"
- 	| x y |
- 	x := (aPoint x * self a11) + (aPoint y * self a12).
- 	y := (aPoint x * self a21) + (aPoint y * self a22).
- 	^x @ y!

Item was removed:
- ----- Method: MatrixTransform2x3>>transformPoint: (in category 'transforming points') -----
- transformPoint: aPoint
- 	"Transform aPoint from local coordinates into global coordinates"
- 	| x y |
- 	x := (aPoint x * self a11) + (aPoint y * self a12) + self a13.
- 	y := (aPoint x * self a21) + (aPoint y * self a22) + self a23.
- 	^x @ y!

Item was removed:
- ----- Method: MatrixTransform2x3>>writeOn: (in category 'objects from disk') -----
- writeOn: aStream
- 	aStream nextWordsPutAll: self.!

Item was removed:
- Notification subclass: #MissingFont
- 	instanceVariableNames: 'familyName pixelSize'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Fonts'!
- 
- !MissingFont commentStamp: '<historical>' prior: 0!
- signaled by font loading code when reading a DiskProxy that calls for a missing font.!

Item was removed:
- ----- Method: MissingFont class>>forFamilyName:pixelSize: (in category 'instance creation') -----
- forFamilyName: aName pixelSize: aSize
- 	^(self new)
- 		familyName: aName;
- 		pixelSize: aSize;
- 		yourself.!

Item was removed:
- ----- Method: MissingFont>>defaultAction (in category 'handling') -----
- defaultAction
- 	familyName ifNil: [ familyName := 'NoName' ].
- 	pixelSize ifNil: [ pixelSize := 12 ].
- 
- 	^((familyName beginsWith: 'Comic')
- 		ifTrue: [ TextStyle named: (Preferences standardEToysFont familyName) ]
- 		ifFalse: [ TextStyle default ]) fontOfSize: pixelSize.!

Item was removed:
- ----- Method: MissingFont>>familyName (in category 'accessing') -----
- familyName
- 	"Answer the value of familyName"
- 
- 	^ familyName!

Item was removed:
- ----- Method: MissingFont>>familyName: (in category 'accessing') -----
- familyName: anObject
- 	"Set the value of familyName"
- 
- 	familyName := anObject!

Item was removed:
- ----- Method: MissingFont>>pixelSize (in category 'accessing') -----
- pixelSize
- 	"Answer the value of pixelSize"
- 
- 	^ pixelSize!

Item was removed:
- ----- Method: MissingFont>>pixelSize: (in category 'accessing') -----
- pixelSize: anObject
- 	"Set the value of pixelSize"
- 
- 	pixelSize := anObject!

Item was removed:
- ----- Method: MissingFont>>printOn: (in category 'printing') -----
- printOn: aStream
- 	super printOn: aStream.
- 	aStream nextPut: $(;
- 		nextPutAll: familyName;
- 		nextPut: $-;
- 		print: pixelSize;
- 		nextPut: $).!

Item was removed:
- DisplayTransform subclass: #MorphicTransform
- 	instanceVariableNames: 'offset angle scale'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Transformations'!
- 
- !MorphicTransform commentStamp: '<historical>' prior: 0!
- This class implements simple translation, scaling and rotation for points, as well as inverse transformations.  These transformations are used in TransformMorphs (clipping scrollers) and TransformationMorphs (general flex-morph wrappers) to map, eg, global mouse coords into local coords, and to invert, eg, local damage rectangles into global damage rectangles.!

Item was removed:
- ----- Method: MorphicTransform class>>identity (in category 'instance creation') -----
- identity
- 
- 	^ self offset: 0 at 0 angle: 0.0 scale: 1.0!

Item was removed:
- ----- Method: MorphicTransform class>>new (in category 'instance creation') -----
- new
- 
- 	^ self offset: 0 at 0
- !

Item was removed:
- ----- Method: MorphicTransform class>>offset: (in category 'instance creation') -----
- offset: aPoint
- 
- 	^ self offset: aPoint angle: 0.0 scale: 1.0!

Item was removed:
- ----- Method: MorphicTransform class>>offset:angle:scale: (in category 'instance creation') -----
- offset: aPoint angle: radians scale: factor
- 
- 	^ self basicNew setOffset: aPoint angle: radians scale: factor!

Item was removed:
- ----- Method: MorphicTransform>>angle (in category 'accessing') -----
- angle
- 	^ angle!

Item was removed:
- ----- Method: MorphicTransform>>asMatrixTransform2x3 (in category 'converting') -----
- asMatrixTransform2x3
- 	^((MatrixTransform2x3 withRotation: angle radiansToDegrees negated) composedWithLocal:
- 		(MatrixTransform2x3 withScale: scale))
- 			offset: offset negated!

Item was removed:
- ----- Method: MorphicTransform>>asMorphicTransform (in category 'converting') -----
- asMorphicTransform
- 
- 	^ self!

Item was removed:
- ----- Method: MorphicTransform>>composedWith: (in category 'transformations') -----
- composedWith: aTransform
- 	"Return a new transform that has the effect of transforming points first by the receiver and then by the argument."
- 
- 	self isIdentity ifTrue: [^ aTransform].
- 	aTransform isIdentity ifTrue: [^ self].
- 	^ CompositeTransform new globalTransform: self
- 							localTransform: aTransform!

Item was removed:
- ----- Method: MorphicTransform>>composedWithLocal: (in category 'composing') -----
- composedWithLocal: aTransform
- 	aTransform isIdentity ifTrue:[^self].
- 	self isIdentity ifTrue:[^aTransform].
- 	aTransform isMorphicTransform ifFalse:[^super composedWithLocal: aTransform].
- 	self isPureTranslation ifTrue:[
- 		^aTransform withOffset: aTransform offset + self offset].
- 	aTransform isPureTranslation ifTrue:[
- 		^self withOffset: (self localPointToGlobal: aTransform offset negated) negated].
- 	^super composedWithLocal: aTransform.!

Item was removed:
- ----- Method: MorphicTransform>>globalPointToLocal: (in category 'transforming points') -----
- globalPointToLocal: aPoint
- 	"Transform aPoint from global coordinates into local coordinates"
- 	^self transform: aPoint!

Item was removed:
- ----- Method: MorphicTransform>>inverseTransformation (in category 'accessing') -----
- inverseTransformation
- 	"Return the inverse transformation of the receiver"
- 	^MorphicTransform
- 		offset: (self transform: 0 at 0) - (self transform: offset)
- 		angle: angle negated
- 		scale: scale reciprocal!

Item was removed:
- ----- Method: MorphicTransform>>invert: (in category 'transformations') -----
- invert: aPoint
- 	"Transform the given point from local to global coordinates."
- 	| p3 p2 |
- 	self isPureTranslation ifTrue: [^ aPoint - offset].
- 	p3 :=  aPoint * scale.
- 	p2 := ((p3 x * angle cos) + (p3 y * angle sin))
- 		@ ((p3 y * angle cos) - (p3 x * angle sin)).
- 	^ (p2 - offset)
- !

Item was removed:
- ----- Method: MorphicTransform>>invertBoundsRect: (in category 'transformations') -----
- invertBoundsRect: aRectangle
- 	"Return a rectangle whose coordinates have been transformed
- 	from local back to global coordinates.  NOTE: if the transformation
- 	is not just a translation, then it will compute the bounding box
- 	in global coordinates."
- 	| outerRect |
- 	self isPureTranslation
- 	ifTrue:
- 		[^ (self invert: aRectangle topLeft)
- 			corner: (self invert: aRectangle bottomRight)]
- 	ifFalse:
- 		[outerRect := Rectangle encompassing:
- 			(aRectangle innerCorners collect: [:p | self invert: p]).
- 		"Following asymmetry due to likely subsequent truncation"
- 		^ outerRect topLeft - (1 at 1) corner: outerRect bottomRight + (2 at 2)]!

Item was removed:
- ----- Method: MorphicTransform>>invertRect: (in category 'transformations') -----
- invertRect: aRectangle
- 
- 	self error: 'method name changed to emphasize enclosing bounds'.
- 	^ self invertBoundsRect: aRectangle!

Item was removed:
- ----- Method: MorphicTransform>>isIdentity (in category 'testing') -----
- isIdentity
- 	"Return true if the receiver is the identity transform; that is, if applying to a point returns the point itself."
- 
- 	^ self isPureTranslation and: [offset = (0 at 0)]
- !

Item was removed:
- ----- Method: MorphicTransform>>isMorphicTransform (in category 'testing') -----
- isMorphicTransform
- 	^true!

Item was removed:
- ----- Method: MorphicTransform>>isPureTranslation (in category 'testing') -----
- isPureTranslation
- 	"Return true if the receiver specifies no rotation or scaling."
- 
- 	^ angle = 0.0 and: [scale = 1.0]
- !

Item was removed:
- ----- Method: MorphicTransform>>localPointToGlobal: (in category 'transforming points') -----
- localPointToGlobal: aPoint
- 	"Transform aPoint from global coordinates into local coordinates"
- 	^self invert: aPoint!

Item was removed:
- ----- Method: MorphicTransform>>offset (in category 'accessing') -----
- offset
- 	"The translation applied to the transformed coordinate system's origin."
- 	"Note: While other transform types also implement this method their actual behavior can differ. Only use it if you know what kind of transform you have on hand. Otherwise, use #localPointToGlobal: instead."
- 	^ offset
- !

Item was removed:
- ----- Method: MorphicTransform>>printOn: (in category 'printing') -----
- printOn: aStream
- 	super printOn: aStream.
- 	aStream nextPut:$(;
- 		nextPutAll:'angle = '; print: angle;
- 		nextPutAll:'; scale = '; print: scale;
- 		nextPutAll:'; offset = '; print: offset;
- 		nextPut:$).!

Item was removed:
- ----- Method: MorphicTransform>>scale (in category 'accessing') -----
- scale
- 	^ scale!

Item was removed:
- ----- Method: MorphicTransform>>setAngle: (in category 'private') -----
- setAngle: aFloat
- 
- 	angle := aFloat.
- !

Item was removed:
- ----- Method: MorphicTransform>>setIdentiy (in category 'initialize') -----
- setIdentiy
- 	scale := 1.0.
- 	offset := 0 at 0.
- 	angle := 0.0.!

Item was removed:
- ----- Method: MorphicTransform>>setOffset: (in category 'private') -----
- setOffset: aPoint
- 
- 	offset := aPoint.
- !

Item was removed:
- ----- Method: MorphicTransform>>setOffset:angle:scale: (in category 'private') -----
- setOffset: aPoint angle: a scale: s
- 
- 	offset := aPoint.
- 	angle := a.
- 	scale := s!

Item was removed:
- ----- Method: MorphicTransform>>setScale: (in category 'private') -----
- setScale: aFloat
- 
- 	scale := aFloat.
- !

Item was removed:
- ----- Method: MorphicTransform>>transform: (in category 'transformations') -----
- transform: aPoint
- 	"Transform the given point from global to local coordinates."
- 	| p2 p3 |
- 	self isPureTranslation ifTrue: [^ aPoint + offset].
- 	p2 := aPoint + offset.
- 	p3 := (((p2 x * angle cos) - (p2 y * angle sin))
- 		@ ((p2 y * angle cos) + (p2 x * angle sin)))
- 			/ scale.
- 	^ p3!

Item was removed:
- ----- Method: MorphicTransform>>transformBoundsRect: (in category 'transformations') -----
- transformBoundsRect: aRectangle
- 	"Return a rectangle whose coordinates have been transformed
- 	from global to local coordinates.  NOTE: if the transformation
- 	is not just a translation, then it will compute the bounding box
- 	in global coordinates."
- 	| outerRect |
- 	self isPureTranslation
- 	ifTrue:
- 		[^ (self transform: aRectangle topLeft)
- 			corner: (self transform: aRectangle bottomRight)]
- 	ifFalse:
- 		[outerRect := Rectangle encompassing:
- 			(aRectangle innerCorners collect: [:p | self transform: p]).
- 		"Following asymmetry due to likely subsequent truncation"
- 		^ outerRect topLeft - (1 at 1) corner: outerRect bottomRight + (2 at 2)]!

Item was removed:
- ----- Method: MorphicTransform>>transformPoint: (in category 'transformations') -----
- transformPoint: aPoint
- 	"Point transform double dispatch"
- 	^self transform: aPoint!

Item was removed:
- ----- Method: MorphicTransform>>withAngle: (in category 'accessing') -----
- withAngle: a
- 	"Return a copy of me with a different Angle"
- 	^ self copy setAngle: a!

Item was removed:
- ----- Method: MorphicTransform>>withOffset: (in category 'accessing') -----
- withOffset: a
- 	"Return a copy of me with a different Offset"
- 	^ self copy setOffset: a!

Item was removed:
- ----- Method: MorphicTransform>>withScale: (in category 'accessing') -----
- withScale: a
- 	"Return a copy of me with a different Scale"
- 	^ self copy setScale: a!

Item was removed:
- ----- Method: Number>>@ (in category '*Graphics-converting') -----
- @ y 
- 	"Primitive. Answer a Point whose x value is the receiver and whose y 
- 	value is the argument. Optional. No Lookup. See Object documentation 
- 	whatIsAPrimitive."
- 
- 	<primitive: 18>
- 	^Point x: self y: y!

Item was removed:
- ----- Method: Number>>em (in category '*Graphics-scale factor') -----
- em
- 	"Documentation only. Please use #pt or #px instead. Convert the receiver from multiples of width-of-capital-letter-M to pixels using the system's default font. Works also with pre-rendered fonts."
- 	
- 	^ (self * (TextStyle defaultFont widthOf: $M)) rounded!

Item was removed:
- ----- Method: Number>>ex (in category '*Graphics-scale factor') -----
- ex
- 	"Documentation only. Please use #pt or #px instead. Convert the receiver from multiples of x-height-of-font to pixels using the system's default TrueType font."
- 
- 	| font description |
- 	font := TextStyle defaultTTFont.
- 	description :=  font ttcDescription.
- 	^ (self asFloat
- 		* (description xHeight asFloat / description unitsPerEm)
- 		* (font widthOf: $M)) rounded!

Item was removed:
- ----- Method: Number>>pt (in category '*Graphics-scale factor') -----
- pt
- 	"Convert the receiver from points to pixels. Note that this will not work correctly for 'faked' scale factors where larger (pre-rendered) fonts are used instead of adjusting the system's current ppi value."
- 
- 	^ (TextStyle pointsToPixels: self) rounded
- 
- "
- (TextStyle pixelsPerInch = 96.0 ifTrue: [
- 	| extra |
- 	extra := TextStyle defaultFont pointSize / TTCFont referencePointSize.
- 	^ (TextStyle pointsToPixels: self * extra) rounded]
- "!

Item was removed:
- ----- Method: Number>>px (in category '*Graphics-scale factor') -----
- px
- 	"Convert the receiver representing raw pixels at 100% (96ppi) to the current scale factor. Note that you currently have to do this manually for all graphics-related properties and layout-specific measures such as #borderWidth: and #layoutInset:. Only for model windows (see #initialExtent) that are no dialogs, that scaling will happen automatically in ToolBuilder."
- 
- 	self flag: #discuss. "mt: For self > 4, I would recommend #rounded instead of #truncated. For smaller values, however, rounding makes no sense because we have no sub-pixel access and things would look too big too soon."
- 	^ (self * RealEstateAgent scaleFactor) truncated!

Item was removed:
- ----- Method: Object>>fullScreenSize (in category '*Graphics-KernelExtensions') -----
- fullScreenSize
- 	"Answer the size to which a window displaying the receiver should be set"
- 	| adj |
- 	adj := (3 * Preferences scrollBarWidth) @ 0.
- 	^ Rectangle origin: adj extent: (DisplayScreen actualScreenSize - adj)!

Item was removed:
- ImageReadWriter subclass: #PCXReadWriter
- 	instanceVariableNames: 'version encoding colorPlanes isGrayScale width height bitsPerPixel colorPalette rowByteSize'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!

Item was removed:
- ----- Method: PCXReadWriter class>>typicalFileExtensions (in category 'image reading/writing') -----
- typicalFileExtensions
- 	"Answer a collection of file extensions (lowercase) which files that I can read might commonly have"
- 	^#('pcx')!

Item was removed:
- ----- Method: PCXReadWriter>>nextImage (in category 'accessing') -----
- nextImage
- 	"Read in the next PCX image from the stream."
- 
- 	| bytes form |
- 	self readHeader.
- 	bytes := self readBody.
- 	colorPalette := self readPalette.
- 	self close.
- 	form := ColorForm extent: width at height depth: bitsPerPixel.
- 	(Form new hackBits: bytes) displayOn: (Form new hackBits: form bits).
- 	form colors: colorPalette.
- 	^ form
- !

Item was removed:
- ----- Method: PCXReadWriter>>nextWord (in category 'private-decoding') -----
- nextWord
- 	^self next + (self next bitShift: 8)!

Item was removed:
- ----- Method: PCXReadWriter>>readBody (in category 'private-decoding') -----
- readBody
- 
- 	| array scanLine rowBytes position byte count pad |
- 	pad := #(0 3 2 1) at: (width \\ 4 + 1).
- 	array := ByteArray new: ((width + pad) * height * bitsPerPixel) // 8.
- 	scanLine := ByteArray new: rowByteSize.
- 	position := 1.
- 	1 to: height do:
- 		[:line |
- 		rowBytes := 0.
- 		[rowBytes < rowByteSize] whileTrue:
- 			[byte := self next.
- 			byte < 16rC0
- 				ifTrue:
- 					[rowBytes := rowBytes + 1.
- 					scanLine at: rowBytes put: byte]
- 				ifFalse:
- 					[count := byte - 16rC0.
- 					byte := self next.
- 					1 to: count do: [:i | scanLine at: rowBytes + i put: byte].
- 					rowBytes := rowBytes + count]].
- 		array
- 			replaceFrom: position
- 			to: position + width - 1
- 			with: scanLine
- 			startingAt: 1.
- 		position := position + width + pad].
- 	^ array
- !

Item was removed:
- ----- Method: PCXReadWriter>>readHeader (in category 'private-decoding') -----
- readHeader
- 
- 	| xMin xMax yMin yMax |
- 	self next.	"skip over manufacturer field"
- 	version := self next.
- 	encoding := self next.
- 	bitsPerPixel := self next.
- 	xMin := self nextWord.
- 	yMin := self nextWord.
- 	xMax := self nextWord.
- 	yMax := self nextWord.
- 	width := xMax - xMin + 1.
- 	height := yMax - yMin + 1.
- 	self next: 4. "skip over device resolution"
- 	self next: 49. "skip over EGA color palette"
- 	colorPlanes := self next.
- 	rowByteSize := self nextWord.
- 	isGrayScale := (self next: 2) = 2.
- 	self next: 58. "skip over filler"
- 
- 
- 
- !

Item was removed:
- ----- Method: PCXReadWriter>>readPalette (in category 'private-decoding') -----
- readPalette
- 
- 	| r g b array |
- 	self next = 12 ifFalse: [self error: 'no Color Palette!!' translated].
- 	array := Array new: (1 bitShift: bitsPerPixel).
- 	1 to: array size do:
- 		[:i |
- 		r := self next.  g := self next.  b := self next.
- 		array at: i put: (Color r: r g: g b: b range: 255)].
- 	^ array.
- !

Item was removed:
- ImageReadWriter subclass: #PNGReadWriter
- 	instanceVariableNames: 'chunk form width height depth backColor bitsPerChannel colorType interlaceMethod bitsPerPixel bytesPerScanline thisScanline prevScanline rowSize idatChunkStream unknownChunks palette transparentPixelValue filtersSeen swizzleMap cachedDecoderMap bigEndian'
- 	classVariableNames: 'BPP BlockHeight BlockWidth Debugging StandardColors StandardSwizzleMaps'
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!
- 
- !PNGReadWriter commentStamp: '<historical>' prior: 0!
- I am a subclass of ImageReadWriter that decodes Portable Network Graphics
- (PNG) images.
- 
- Submitted by Duane Maxwell!

Item was removed:
- ----- Method: PNGReadWriter class>>computeSwizzleMapForDepth: (in category 'class initialization') -----
- computeSwizzleMapForDepth: depth
- 	"Answer a map that maps pixels in a word to their opposite location. Used for 'middle-endian' forms where the byte-order is different from the bit order (good joke, eh?)."
- 	| map swizzled |
- 	map := Bitmap new: 256.
- 	depth = 4 ifTrue:[
- 		0 to: 255 do:[:pix|
- 			swizzled := 0.
- 			swizzled := swizzled bitOr: (((pix bitShift: 0) bitAnd: 15) bitShift: 4).
- 			swizzled := swizzled bitOr: (((pix bitShift: -4) bitAnd: 15) bitShift: 0).
- 			map at: pix+1 put: swizzled.
- 		].
- 		^ColorMap colors: map
- 	].
- 
- 	depth = 2 ifTrue:[
- 		0 to: 255 do:[:pix|
- 			swizzled := 0.
- 			swizzled := swizzled bitOr: (((pix bitShift: 0) bitAnd: 3) bitShift: 6).
- 			swizzled := swizzled bitOr: (((pix bitShift: -2) bitAnd: 3) bitShift: 4).
- 			swizzled := swizzled bitOr: (((pix bitShift: -4) bitAnd: 3) bitShift: 2).
- 			swizzled := swizzled bitOr: (((pix bitShift: -6) bitAnd: 3) bitShift: 0).
- 			map at: pix+1 put: swizzled.
- 		].
- 		^ColorMap colors: map
- 	].
- 
- 	depth = 1 ifTrue:[
- 		0 to: 255 do:[:pix|
- 			swizzled := 0.
- 			swizzled := swizzled bitOr: (((pix bitShift: 0) bitAnd: 1) bitShift: 7).
- 			swizzled := swizzled bitOr: (((pix bitShift: -1) bitAnd: 1) bitShift: 6).
- 			swizzled := swizzled bitOr: (((pix bitShift: -2) bitAnd: 1) bitShift: 5).
- 			swizzled := swizzled bitOr: (((pix bitShift: -3) bitAnd: 1) bitShift: 4).
- 			swizzled := swizzled bitOr: (((pix bitShift: -4) bitAnd: 1) bitShift: 3).
- 			swizzled := swizzled bitOr: (((pix bitShift: -5) bitAnd: 1) bitShift: 2).
- 			swizzled := swizzled bitOr: (((pix bitShift: -6) bitAnd: 1) bitShift: 1).
- 			swizzled := swizzled bitOr: (((pix bitShift: -7) bitAnd: 1) bitShift: 0).
- 			map at: pix+1 put: swizzled.
- 		].
- 		^ColorMap colors: map
- 	].
- 	self error: 'Unrecognized depth'!

Item was removed:
- ----- Method: PNGReadWriter class>>debugging: (in category 'support') -----
- debugging: aBoolean
- 
- 	Debugging := aBoolean!

Item was removed:
- ----- Method: PNGReadWriter class>>initialize (in category 'class initialization') -----
- initialize
- 	"
- 	PNGReadWriter initialize
- 	"
- 
- 	BPP := {	#(1 2 4 8 16).
- 			#(0 0 0 0 0).
- 			#(0 0 0 24 48).
- 			#(1 2 4 8 0).
- 			#(0 0 0 16 32).
- 			#(0 0 0 0 0).
- 			#(0 0 0 32 64).
- 			#(0 0 0 0 0) }.
- 
- 	BlockHeight := #(8 8 4 4 2 2 1).
- 	BlockWidth := #(8 4 4 2 2 1 1).
- 
- 	StandardColors := Color indexedColors collect:[:aColor|
- 		Color 
- 			r: (aColor red * 255) truncated / 255
- 			g: (aColor green * 255) truncated / 255
- 			b: (aColor blue * 255) truncated / 255.
- 	].
- 
- 	StandardSwizzleMaps := Array new: 4.
- 	#(1 2 4) do:[:i| StandardSwizzleMaps at: i put: (self computeSwizzleMapForDepth: i)].!

Item was removed:
- ----- Method: PNGReadWriter class>>typicalFileExtensions (in category 'image reading/writing') -----
- typicalFileExtensions
- 	"Answer a collection of file extensions (lowercase) which files that I can read might commonly have"
- 	^#('png')!

Item was removed:
- ----- Method: PNGReadWriter>>copyPixels: (in category 'pixel copies') -----
- copyPixels: y
- 	"Handle non-interlaced pixels of supported colorTypes"
- 
- 	| s |
- 	s := #(copyPixelsGray: nil copyPixelsRGB: copyPixelsIndexed:
- 		  copyPixelsGrayAlpha: nil copyPixelsRGBA:) at: colorType+1.
- 	self perform: s asSymbol with: y
- !

Item was removed:
- ----- Method: PNGReadWriter>>copyPixels:at:by: (in category 'pixel copies') -----
- copyPixels: y at: startX by: incX
- 	"Handle interlaced pixels of supported colorTypes"
- 
- 	| s |
- 	s := #(copyPixelsGray:at:by: nil copyPixelsRGB:at:by: copyPixelsIndexed:at:by:
- 		  copyPixelsGrayAlpha:at:by: nil copyPixelsRGBA:at:by:) at: colorType+1.
- 	self perform: s asSymbol with: y with: startX with: incX
- !

Item was removed:
- ----- Method: PNGReadWriter>>copyPixelsGray: (in category 'pixel copies') -----
- copyPixelsGray: y 
- 	"Handle non-interlaced grayscale color mode (colorType = 0)"
- 
- 	| base bits bytesLeft word |
- 	bitsPerChannel = 16 ifTrue: [
- 		"Warning: This is extremely slow. Besides we are downsampling to 8 bits!!"
- 		| blitter |
- 		blitter := BitBlt bitPokerToForm: form.
- 		0 to: width - 1 do: [ :x |
- 			| high low value |
- 			high := thisScanline at: x * 2 + 1.
- 			low := thisScanline at: x * 2 + 2.
- 			value := (high * 256 + low = transparentPixelValue)
- 				ifTrue: [0 "transparent"]
- 				ifFalse: [high max: 1].
- 			blitter pixelAt: x @ y put: value ].
- 			^self ].
- 
- 	"Just copy the bits"
- 
- 	"This Smalltalk version might be easier to understand than the others below."
- 	base := y * (form width * bitsPerChannel + 31 // 32) + 1.
- 	bits := form bits.
- 	0 to: thisScanline size // 4 - 1 do: [ :i |
- 		| ii |
- 		ii := i * 4.
- 		"This somewhat weird mixture of (#* and #+) with (#bitShift: and #bitOr:) 
- 		is to make use of faster arithmetic bytecodes, but not of slow largeintegers."
- 		word :=
- 			(((thisScanline at: ii + 1) * 256 + 
- 			(thisScanline at: ii + 2) * 256 + 
- 			(thisScanline at: ii + 3)) bitShift: 8) bitOr: 
- 			(thisScanline at: ii + 4).
- 		bits at: base + i put: word ].	
- 	(bytesLeft := thisScanline size bitAnd: 3) = 0 ifFalse: [
- 		word := 0.
- 		thisScanline size - bytesLeft + 1 to: thisScanline size do: [ :ii |
- 			word := word * 256 + (thisScanline at: ii) ].
- 		word := word bitShift: 8 * (4 - bytesLeft).
- 		bits at: base + (thisScanline size // 4) put: word ].
- 
- 	"This interesting technique (By Andreas Raab) is faster for very large images, but might be slower for small ones"
- 	"^self copyPixelsGrayWeirdBitBltHack: y ".
- 	"It uses the following method:
- 	PNGReadWriter >> copyPixelsGrayWeirdBitBltHack: y 
- 	""Handle non-interlaced black and white color mode (colorType = 0)
- 	By Andreas Raab""
- 	
- 	| source dest cmap |
- 	source := Form extent: 1 @ (thisScanline size // 4) depth: 32 bits: thisScanline.
- 	dest := Form extent: 1 @ (form bits size) depth: 32 bits: form bits.
- 	cmap := Smalltalk isLittleEndian
- 		ifTrue:[ColorMap 
- 					shifts: #(-24 -8 8 24) 
- 					masks: #(16rFF000000 16r00FF0000 16r0000FF00 16r000000FF)].
- 	(BitBlt toForm: dest)
- 		sourceForm: source;
- 		destX: 0 destY: (y * form width*bitsPerChannel//32) width: 1 height: (form width+31*bitsPerChannel//32);
- 		colorMap: cmap;
- 		combinationRule: 3;
- 		copyBits."
- 		
- 	"This interesting technique  (By Yoshiki Ohshima) is faster for very large images, but might be slower for small ones"
- 	"form bits copyFromByteArray2: thisScanline to: y * (form width* bitsPerChannel // 32)".
- 	"It uses the following method:
- 	BitMap >> copyFromByteArray2: byteArray to: i
- 	""This method should work with either byte orderings""
- 
- 	| myHack byteHack |
- 	myHack := Form new hackBits: self.
- 	byteHack := Form new hackBits: byteArray.
- 	Smalltalk  isLittleEndian ifTrue: [byteHack swapEndianness].
- 	byteHack displayOn: myHack at:  0 at i"!

Item was removed:
- ----- Method: PNGReadWriter>>copyPixelsGray:at:by: (in category 'pixel copies') -----
- copyPixelsGray: y at: startX by: incX
- 	"Handle interlaced grayscale color mode (colorType = 0)"
- 
- 	| offset bits blitter pixPerByte shifts b pixel mask pixelNumber |
- 	bitsPerChannel = 16
- 		ifTrue: [
- 			"Warning: This is extremely slow. Besides we are downsampling to 8 bits!!"
- 			blitter := BitBlt bitPokerToForm: form.
- 			startX to: width-1 by: incX do: [ :x |
- 				| high low value |
- 				high := thisScanline at: x//incX<<1 + 1.
- 				low := thisScanline at: x//incX<<1 + 2.
- 				value := (high * 256 + low = transparentPixelValue)
- 					ifTrue: [0 "transparent"]
- 					ifFalse: [high max: 1].
- 				blitter pixelAt: x @ y put: value ].
- 				^self ].
- 	offset := y*rowSize+1.
- 	bits := form bits.
- 	bitsPerChannel = 8 ifTrue: [
- 		startX to: width-1 by: incX do: [ :x | | w |
- 			w := offset + (x>>2).
- 			b := 3- (x \\ 4) * 8.
- 			pixel := (thisScanline at: x // incX + 1)<<b.
- 			mask := (255<<b) bitInvert32.
- 			bits at: w put: (((bits at: w) bitAnd: mask) bitOr: pixel)
- 		].
- 		^ self
- 	].
- 	bitsPerChannel = 1 ifTrue: [
- 		pixPerByte := 8.
- 		mask := 1.
- 		shifts := #(7 6 5 4 3 2 1 0).
- 	].
- 	bitsPerChannel = 2 ifTrue: [
- 		pixPerByte := 4.
- 		mask := 3.
- 		shifts := #(6 4 2 0).
- 	].
- 	bitsPerChannel = 4 ifTrue: [
- 		pixPerByte := 2.
- 		mask := 15.
- 		shifts := #(4 0).
- 	].
- 
- 	blitter := BitBlt bitPokerToForm: form.
- 	pixelNumber := 0.
- 	startX to: width-1 by: incX do: [ :x | | rawByte |
- 		rawByte := thisScanline at: (pixelNumber // pixPerByte) + 1.
- 		pixel := (rawByte >> (shifts at: (pixelNumber \\ pixPerByte) + 1)) bitAnd: mask.
- 		blitter pixelAt: (x at y) put: pixel.
- 		pixelNumber := pixelNumber + 1.
- 	].
- !

Item was removed:
- ----- Method: PNGReadWriter>>copyPixelsGrayAlpha: (in category 'pixel copies') -----
- copyPixelsGrayAlpha: y
- 	"Handle non-interlaced grayscale with alpha color mode (colorType = 4)"
- 
- 	| i pixel gray b |
- 	b := BitBlt bitPokerToForm: form.
- 	bitsPerChannel = 8
- 		ifTrue: [
- 			0 to: width-1 do: [ :x |
- 				i := (x << 1) + 1.
- 				gray := thisScanline at: i.
- 				pixel := ((thisScanline at: i+1)<<24) + (gray<<16) + (gray<<8) + gray.
- 				b pixelAt: x at y put: pixel.
- 				]
- 			]
- 		ifFalse: [
- 			0 to: width-1 do: [ :x |
- 				i := (x << 2) + 1.
- 				gray := thisScanline at: i.
- 				pixel := ((thisScanline at: i+2)<<24) + (gray<<16) + (gray<<8) + gray.
- 				b pixelAt: x at y put: pixel.
- 				]
- 			]
- !

Item was removed:
- ----- Method: PNGReadWriter>>copyPixelsGrayAlpha:at:by: (in category 'pixel copies') -----
- copyPixelsGrayAlpha: y at: startX by: incX
- 	"Handle interlaced grayscale with alpha color mode (colorType = 4)"
- 
- 	| i pixel gray b |
- 	b := BitBlt bitPokerToForm: form.
- 	bitsPerChannel = 8
- 		ifTrue: [
- 			startX to: width-1 by: incX do: [ :x |
- 				i := (x // incX << 1) + 1.
- 				gray := thisScanline at: i.
- 				pixel := ((thisScanline at: i+1)<<24) + (gray<<16) + (gray<<8) + gray.
- 				b pixelAt: x at y put: pixel.
- 				]
- 			]
- 		ifFalse: [
- 			startX to: width-1 by: incX do: [ :x |
- 				i := (x // incX << 2) + 1.
- 				gray := thisScanline at: i.
- 				pixel := ((thisScanline at: i+2)<<24) + (gray<<16) + (gray<<8) + gray.
- 				b pixelAt: x at y put: pixel.
- 				]
- 			]
- !

Item was removed:
- ----- Method: PNGReadWriter>>copyPixelsIndexed: (in category 'pixel copies') -----
- copyPixelsIndexed: y
- 	"Handle non-interlaced indexed color mode (colorType = 3)"
- 	| hack hackBlt swizzleHack swizzleBlt scanline hackDepth |
- 	scanline := ByteArray new: bytesPerScanline + 3 // 4 * 4.
- 	scanline replaceFrom: 1 to: thisScanline size with: thisScanline startingAt: 1.
- 	hackDepth := bigEndian ifTrue:[form depth] ifFalse:[form depth negated].
- 	hack := Form extent: width at 1 depth: hackDepth bits: scanline.
- 	hackBlt := BitBlt toForm: form.
- 	hackBlt sourceForm: hack.
- 	hackBlt combinationRule: Form over.
- 	hackBlt destOrigin: 0 at y.
- 	hackBlt width: width; height: 1.
- 
- 	(form depth < 8 and:[bigEndian not]) ifTrue:[
- 		swizzleHack := Form new hackBits: scanline.
- 		swizzleBlt := BitBlt toForm: swizzleHack.
- 		swizzleBlt sourceForm: swizzleHack.
- 		swizzleBlt combinationRule: Form over.
- 		swizzleBlt colorMap: (StandardSwizzleMaps at: form depth).
- 		swizzleBlt copyBits.
- 	].
- 
- 	hackBlt copyBits.!

Item was removed:
- ----- Method: PNGReadWriter>>copyPixelsIndexed:at:by: (in category 'pixel copies') -----
- copyPixelsIndexed: y at: startX by: incX
- 	"Handle interlaced indexed color mode (colorType = 3)"
- 
- 	| offset bits pixPerByte shifts blitter pixel mask pixelNumber |
- 	offset := y*rowSize+1.
- 	bits := form bits.
- 	bitsPerChannel = 8
- 		ifTrue: [
- 			startX to: width-1 by: incX do: [ :x | | b w |
- 				w := offset + (x>>2).
- 				b := 3 - (x \\ 4) * 8.
- 				pixel := (thisScanline at: x // incX + 1)<<b.
- 				mask := (255<<b) bitInvert32.
- 				bits at: w put: (((bits at: w) bitAnd: mask) bitOr: pixel)].
- 			^ self ].
- 	bitsPerChannel = 1 ifTrue: [
- 		pixPerByte := 8.
- 		mask := 1.
- 		shifts := #(7 6 5 4 3 2 1 0).
- 	].
- 	bitsPerChannel = 2 ifTrue: [
- 		pixPerByte := 4.
- 		mask := 3.
- 		shifts := #(6 4 2 0).
- 	].
- 	bitsPerChannel = 4 ifTrue: [
- 		pixPerByte := 2.
- 		mask := 15.
- 		shifts := #(4 0).
- 	].
- 
- 	blitter := BitBlt bitPokerToForm: form.
- 	pixelNumber := 0.
- 	startX to: width-1 by: incX do: [ :x | | rawByte |
- 		rawByte := thisScanline at: (pixelNumber // pixPerByte) + 1.
- 		pixel := (rawByte >> (shifts at: (pixelNumber \\ pixPerByte) + 1)) bitAnd: mask.
- 		blitter pixelAt: (x at y) put: pixel.
- 		pixelNumber := pixelNumber + 1.
- 	].
- !

Item was removed:
- ----- Method: PNGReadWriter>>copyPixelsRGB: (in category 'pixel copies') -----
- copyPixelsRGB: y
- 	"Handle non-interlaced RGB color mode (colorType = 2)"
- 
- 	| i pixel tempForm tempBits |
- 	(transparentPixelValue isNil and: [ bitsPerChannel = 8 ]) ifTrue: [ "Do the same trick as in #copyPixelsRGBA:"
- 		| targetIndex |
- 		tempBits := ByteArray new: thisScanline size * 4 // 3 withAll: 16rFF.
- 		tempForm := Form extent: width at 1 depth: 32 bits: tempBits.
- 		targetIndex := 1.
- 		1 to: thisScanline size by: 3 do: [ :index |
- 			tempBits
- 				at: targetIndex put: (thisScanline at: index);
- 				at: targetIndex + 1 put: (thisScanline at: index + 1);
- 				at: targetIndex + 2 put: (thisScanline at: index + 2).
- 			targetIndex := targetIndex + 4 ].
- 		cachedDecoderMap 
- 			ifNil:[cachedDecoderMap := self rgbaDecoderMapForDepth: depth].
- 		(BitBlt toForm: form)
- 			sourceForm: tempForm;
- 			destOrigin: 0 at y;
- 			combinationRule: Form over;
- 			colorMap: cachedDecoderMap;
- 			copyBits.
- 		^self ].
- 	tempForm := Form extent: width at 1 depth: 32.
- 	tempBits := tempForm bits.
- 	pixel := LargePositiveInteger new: 4.
- 	pixel at: 4 put: 16rFF.
- 	bitsPerChannel = 8
- 		ifTrue:
- 			[i := 1.
- 			1 to: width do:
- 				[ :x |
- 				pixel
- 					at: 3 put: (thisScanline at: i);
- 					at: 2 put: (thisScanline at: i+1);
- 					at: 1 put: (thisScanline at: i+2).
- 				tempBits at: x put: pixel normalize.
- 				i := i + 3].
- 			transparentPixelValue
- 				ifNotNil:
- 					[1 to: width do: [ :x |
- 						(tempBits at: x) = transparentPixelValue
- 							ifTrue: [tempBits at: x put: 0]]]]
- 		ifFalse:
- 			[i := 1.
- 			1 to: width do:
- 				[ :x |
- 				(transparentPixelValue == nil or: [(1 to: 6) anySatisfy: [:k | (transparentPixelValue digitAt: k) ~= (thisScanline at: i + 6 - k)]])
- 					ifTrue:
- 						[pixel
- 							at: 3 put: (thisScanline at: i);
- 							at: 2 put: (thisScanline at: i+2);
- 							at: 1 put: (thisScanline at: i+4).
- 						tempBits at: x put: pixel normalize]
- 					ifFalse:
- 						[tempBits at: x put: 0].
- 				i := i + 6]].
- 	
- 	tempForm displayOn: form at: 0 at y rule: Form over.
- !

Item was removed:
- ----- Method: PNGReadWriter>>copyPixelsRGB:at:by: (in category 'pixel copies') -----
- copyPixelsRGB: y at: startX by: incX
- 	"Handle interlaced RGB color mode (colorType = 2)"
- 
- 	| i pixel tempForm tempBits xx loopsToDo |
- 
- 	tempForm := Form extent: width at 1 depth: 32.
- 	tempBits := tempForm bits.
- 	pixel := LargePositiveInteger new: 4.
- 	pixel at: 4 put: 16rFF.
- 	loopsToDo := width - startX + incX - 1 // incX.
- 	bitsPerChannel = 8
- 		ifTrue:
- 			[i := (startX // incX * 3) + 1.
- 			xx := startX+1.
- 			1 to: loopsToDo do:
- 				[ :j |
- 				pixel
- 					at: 3 put: (thisScanline at: i);
- 					at: 2 put: (thisScanline at: i+1);
- 					at: 1 put: (thisScanline at: i+2).
- 				tempBits at: xx put: pixel normalize.
- 				i := i + 3.
- 				xx := xx + incX].
- 			transparentPixelValue
- 				ifNotNil: [startX to: width-1 by: incX do: [ :x |
- 					(tempBits at: x+1) = transparentPixelValue
- 						ifTrue: [	tempBits at: x+1 put: 0]]]]
- 		ifFalse:
- 			[i := (startX // incX * 6) + 1.
- 			xx := startX+1.
- 			1 to: loopsToDo do:
- 				[ :j |
- 				(transparentPixelValue == nil or: [(1 to: 6) anySatisfy: [:k | (transparentPixelValue digitAt: k) ~= (thisScanline at: i + 6 - k)]])
- 					ifTrue:
- 						[pixel
- 							at: 3 put: (thisScanline at: i);
- 							at: 2 put: (thisScanline at: i+2);
- 							at: 1 put: (thisScanline at: i+4).
- 						tempBits at: xx put: pixel normalize.]
- 					ifFalse:
- 						[tempBits at: xx put: 0].
- 				i := i + 6.
- 				xx := xx + incX]].
- 	tempForm displayOn: form at: 0 at y rule: Form over.
- 
- !

Item was removed:
- ----- Method: PNGReadWriter>>copyPixelsRGBA: (in category 'pixel copies') -----
- copyPixelsRGBA: y
- 	"Handle non-interlaced RGBA color modes (colorType = 6)"
- 
- 	| i pixel tempForm tempBits ff |
- 	bitsPerChannel = 8 ifTrue: [
- 		ff := Form extent: width at 1 depth: 32 bits: thisScanline.
- 		cachedDecoderMap 
- 			ifNil:[cachedDecoderMap := self rgbaDecoderMapForDepth: depth].
- 		(BitBlt toForm: form)
- 			sourceForm: ff;
- 			destOrigin: 0 at y;
- 			combinationRule: Form over;
- 			colorMap: cachedDecoderMap;
- 			copyBits.
- 		^self.
- 	].
- 	tempForm := Form extent: width at 1 depth: 32.
- 	tempBits := tempForm bits.
- 	pixel := LargePositiveInteger new: 4.
- 	i := -7.
- 	0 to: width-1 do: [ :x |
- 			i := i + 8.
- 			pixel at: 4 put: (thisScanline at: i+6);
- 				at: 3 put: (thisScanline at: i);
- 				at: 2 put: (thisScanline at: i+2);
- 				at: 1 put: (thisScanline at: i+4).
- 			tempBits at: x+1 put: pixel normalize.
- 	].
- 	tempForm displayOn: form at: 0 at y rule: Form over.
- !

Item was removed:
- ----- Method: PNGReadWriter>>copyPixelsRGBA:at:by: (in category 'pixel copies') -----
- copyPixelsRGBA: y at: startX by: incX
- 	"Handle interlaced RGBA color modes (colorType = 6)"
- 
- 	| i pixel tempForm tempBits |
- 
- 	tempForm := Form extent: width at 1 depth: 32.
- 	tempBits := tempForm bits.
- 	pixel := LargePositiveInteger new: 4.
- 	bitsPerChannel = 8 ifTrue: [
- 		i := (startX // incX << 2) + 1.
- 		startX to: width-1 by: incX do: [ :x |
- 			pixel at: 4 put: (thisScanline at: i+3);
- 				at: 3 put: (thisScanline at: i);
- 				at: 2 put: (thisScanline at: i+1);
- 				at: 1 put: (thisScanline at: i+2).
- 			tempBits at: x+1 put: pixel normalize.
- 			i := i + 4.
- 		]
- 	] ifFalse: [
- 		i := (startX // incX << 3) +1.
- 		startX to: width-1 by: incX do: [ :x |
- 			pixel at: 4 put: (thisScanline at: i+6);
- 				at: 3 put: (thisScanline at: i);
- 				at: 2 put: (thisScanline at: i+2);
- 				at: 1 put: (thisScanline at: i+4).
- 			tempBits at: x+1 put: pixel normalize.
- 			i := i + 8.
- 		].
- 	].
- 	tempForm displayOn: form at: 0 at y rule: Form paintAlpha.
- 
- !

Item was removed:
- ----- Method: PNGReadWriter>>debugging (in category 'accessing') -----
- debugging
- 
- 	^Debugging == true!

Item was removed:
- ----- Method: PNGReadWriter>>doPass: (in category 'miscellaneous') -----
- doPass: pass
- 	"Certain interlace passes are skipped with certain small image
- dimensions"
- 
- 	pass = 1 ifTrue: [ ^ true ].
- 	((width = 1) and: [height = 1]) ifTrue: [ ^ false ].
- 	pass = 2 ifTrue: [ ^ width >= 5 ].
- 	pass = 3 ifTrue: [ ^ height >= 5 ].
- 	pass = 4 ifTrue: [ ^ (width >=3 ) or: [height >= 5] ].
- 	pass = 5 ifTrue: [ ^ height >=3 ].
- 	pass = 6 ifTrue: [ ^ width >=2 ].
- 	pass = 7 ifTrue: [ ^ height >=2 ].
- 
- !

Item was removed:
- ----- Method: PNGReadWriter>>filterAverage: (in category 'filtering') -----
- filterAverage: count
- 	"Use the average of the pixel to the left and the pixel above as a predictor"
- 
- 	| delta |
- 	delta := bitsPerPixel // 8 max: 1.
- 	1 to: delta do: [:i |
- 		thisScanline at: i put: ((thisScanline at: i) + ((prevScanline at: i) // 2) bitAnd: 255)].
- 	delta + 1 to: count do: [:i |
- 		thisScanline at: i put:
- 			((thisScanline at: i)
- 			+ ((prevScanline at: i)
- 			+ (thisScanline at: i - delta) // 2) bitAnd: 255)]!

Item was removed:
- ----- Method: PNGReadWriter>>filterHorizontal: (in category 'filtering') -----
- filterHorizontal: count
- 	"Use the pixel to the left as a predictor"
- 
- 	| delta |
- 	delta := bitsPerPixel // 8 max: 1.
- 	delta+1 to: count do: [ :i |
- 		thisScanline at: i put: (((thisScanline at: i) +
- (thisScanline at: i-delta)) bitAnd: 255) ]
- 
- 
- !

Item was removed:
- ----- Method: PNGReadWriter>>filterNone: (in category 'filtering') -----
- filterNone: count
- !

Item was removed:
- ----- Method: PNGReadWriter>>filterPaeth: (in category 'filtering') -----
- filterPaeth: count
- 	"Select one of (the pixel to the left, the pixel above and the pixel to above left) to
- 	predict the value of this pixel"
- 
- 	| delta |
- 	delta := bitsPerPixel // 8 max: 1.
- 	1 to: delta do: [ :i |
- 		thisScanline at: i put:
- 			(((thisScanline at: i) + (prevScanline at: i)) bitAnd: 255)].
- 	delta+1 to: count do: [ :i |
- 		thisScanline
- 			at: i
- 			put: (((thisScanline at: i) + (self
- 				paethPredictLeft: (thisScanline at: i-delta)
- 				above: (prevScanline at: i)
- 				aboveLeft: (prevScanline at: i-delta)))
- 					bitAnd: 255)]
- 
- !

Item was removed:
- ----- Method: PNGReadWriter>>filterScanline:count: (in category 'filtering') -----
- filterScanline: filterType count: count
- 
- 	self
- 		perform: (
- 			#(filterNone: filterHorizontal: filterVertical: filterAverage: filterPaeth:)
- 				at: filterType+1)
- 		with: count.
- 
- !

Item was removed:
- ----- Method: PNGReadWriter>>filterVertical: (in category 'filtering') -----
- filterVertical: count
- 	"Use the pixel above as a predictor"
- 
- 	1 to: count do: [ :i |
- 		thisScanline at: i put: (((thisScanline at: i) +
- (prevScanline at: i)) bitAnd: 255) ]
- 
- !

Item was removed:
- ----- Method: PNGReadWriter>>grayColorsFor: (in category 'miscellaneous') -----
- grayColorsFor: d
- 	"return a color table for a gray image"
- 
- 	palette := Array new: 1<<d.
- 	d = 1 ifTrue: [
- 		palette at: 1 put: Color black.
- 		palette at: 2 put: Color white.
- 		^  palette
- 		].
- 	d = 2 ifTrue: [
- 		palette at: 1 put: Color black.
- 		palette at: 2 put: (Color gray: 85.0 / 255.0).
- 		palette at: 3 put: (Color gray: 170.0 / 255.0).
- 		palette at: 4 put: Color white.
- 		^ palette
- 		].
- 	d = 4 ifTrue: [
- 		0 to: 15 do: [ :g |
- 			palette at: g+1 put: (Color gray: (g/15) asFloat) ].
- 		^ palette
- 		].
- 	d = 8 ifTrue: [
- 		0 to: 255 do: [ :g |
- 			palette at: g+1 put: (Color gray: (g/255) asFloat) ].
- 		^ palette
- 		].
- !

Item was removed:
- ----- Method: PNGReadWriter>>nextImage (in category 'accessing') -----
- nextImage
- 	bigEndian := Smalltalk isBigEndian.
- 	filtersSeen := Bag new.
- 	idatChunkStream := nil.
- 	transparentPixelValue := nil.
- 	unknownChunks := Set new.
- 	stream reset.
- 	stream binary.
- 	stream skip: 8.
- 	[stream atEnd] whileFalse: [self processNextChunk].
- 	"Set up our form"
- 	palette ifNotNil: 
- 			["Dump the palette if it's the same as our standard palette"
- 
- 			palette = (StandardColors copyFrom: 1 to: palette size) 
- 				ifTrue: [palette := nil]].
- 	(depth <= 8 and: [palette notNil]) 
- 		ifTrue: 
- 			[form := ColorForm extent: width @ height depth: depth.
- 			form colors: palette]
- 		ifFalse: [form := Form extent: width @ height depth: depth].
- 	backColor ifNotNil: [form fillColor: backColor].
- 	idatChunkStream 
- 		ifNil: [ self error: 'image data is missing' translated ]
- 		ifNotNil: [ self processIDATChunk ].
- 	unknownChunks isEmpty 
- 		ifFalse: 
- 			["Transcript show: ' ',unknownChunks asSortedCollection asArray printString."
- 
- 			].
- 	self debugging 
- 		ifTrue: 
- 			[Transcript
- 				cr;
- 				show: 'form = ' , form printString.
- 			Transcript
- 				cr;
- 				show: 'colorType = ' , colorType printString.
- 			Transcript
- 				cr;
- 				show: 'interlaceMethod = ' , interlaceMethod printString.
- 			Transcript
- 				cr;
- 				show: 'filters = ' , filtersSeen sortedCounts asArray printString].
- 	^form!

Item was removed:
- ----- Method: PNGReadWriter>>nextPutImage: (in category 'writing') -----
- nextPutImage: aForm
- 	"Write out the given form. We're keeping it simple here, no interlacing, no filters."
- 	^self nextPutImage: aForm interlace: 0 filter: 0. "no filtering"!

Item was removed:
- ----- Method: PNGReadWriter>>nextPutImage:interlace:filter: (in category 'writing') -----
- nextPutImage: aForm interlace: aMethod filter: aFilterType 
- 	"Note: For now we keep it simple - interlace and filtering are simply ignored"
- 
- 	| crcStream |
- 	bigEndian := Smalltalk isBigEndian.
- 	form := aForm.
- 	width := aForm width.
- 	height := aForm height.
- 	aForm depth <= 8 
- 		ifTrue: 
- 			[bitsPerChannel := aForm depth.
- 			colorType := 3.
- 			bytesPerScanline := (width * aForm depth + 7) // 8]
- 		ifFalse: 
- 			[bitsPerChannel := 8.
- 			colorType := 6.
- 			bytesPerScanline := width * 4].
- 	self writeFileSignature.
- 	crcStream := WriteStream on: (ByteArray new: 1000).
- 	crcStream resetToStart.
- 	self writeIHDRChunkOn: crcStream.
- 	self writeChunk: crcStream.
- 	form depth <= 8 
- 		ifTrue: 
- 			[crcStream resetToStart.
- 			self writePLTEChunkOn: crcStream.
- 			self writeChunk: crcStream.
- 			form isColorForm 
- 				ifTrue: 
- 					[crcStream resetToStart.
- 					self writeTRNSChunkOn: crcStream.
- 					self writeChunk: crcStream]].
- 	form depth = 16 
- 		ifTrue: 
- 			[crcStream resetToStart.
- 			self writeSBITChunkOn: crcStream.
- 			self writeChunk: crcStream].
- 	crcStream resetToStart.
- 	self writeIDATChunkOn: crcStream.
- 	self writeChunk: crcStream.
- 	crcStream resetToStart.
- 	self writeIENDChunkOn: crcStream.
- 	self writeChunk: crcStream!

Item was removed:
- ----- Method: PNGReadWriter>>paethPredictLeft:above:aboveLeft: (in category 'filtering') -----
- paethPredictLeft: a above: b aboveLeft: c
- 	"Predicts the value of a pixel based on nearby pixels, based on
- Paeth (GG II, 1991)"
- 
- 	| pa pb pc |
- 	pa := b > c ifTrue: [b - c] ifFalse: [c - b].
- 	pb := a > c ifTrue: [a - c] ifFalse: [c - a].
- 	pc := a + b - c - c.
- 	pc < 0 ifTrue: [
- 		pc := pc * -1].
- 	((pa <= pb) and: [pa <= pc]) ifTrue: [^ a].
- 	(pb <= pc) ifTrue: [^ b].
- 	^ c
- !

Item was removed:
- ----- Method: PNGReadWriter>>processBackgroundChunk (in category 'chunks') -----
- processBackgroundChunk
- 
- 	| val red green blue max |
- 
- 	"Transcript show: '  BACKGROUND: ',chunk printString."
- 	colorType = 3 ifTrue: [
- 		backColor := palette at: chunk first + 1.
- 		^self
- 	].
- 	max := (2 raisedTo: bitsPerChannel) - 1.
- 	(colorType = 0 or: [colorType = 4]) ifTrue: [
- 		val := chunk unsignedShortAt: 1 bigEndian: true.
- 		backColor := Color gray: val / max.
- 		^self
- 	].
- 	(colorType = 2 or: [colorType = 6]) ifTrue: [
- 		red := chunk unsignedShortAt: 1 bigEndian: true.
- 		green := chunk unsignedShortAt: 3 bigEndian: true.
- 		blue := chunk unsignedShortAt: 5 bigEndian: true.
- 		backColor := Color r: red/max g: green/max b: blue/max.
- 		^self
- 	].
- "self halt."
- 
- "====
- The bKGD chunk specifies a default background color to present the image against. Note that viewers are not bound to honor this chunk; a viewer can choose to use a different background. 
- 
- For color type 3 (indexed color), the bKGD chunk contains: 
- 
- 
-    Palette index:  1 byte
- 
- The value is the palette index of the color to be used as background. 
- 
- For color types 0 and 4 (grayscale, with or without alpha), bKGD contains: 
- 
- 
-    Gray:  2 bytes, range 0 .. (2^bitdepth)-1
- 
- (For consistency, 2 bytes are used regardless of the image bit depth.) The value is the gray level to be used as background. 
- 
- For color types 2 and 6 (truecolor, with or without alpha), bKGD contains: 
- 
- 
-    Red:   2 bytes, range 0 .. (2^bitdepth)-1
-    Green: 2 bytes, range 0 .. (2^bitdepth)-1
-    Blue:  2 bytes, range 0 .. (2^bitdepth)-1
- 
- (For consistency, 2 bytes per sample are used regardless of the image bit depth.) This is the RGB color to be used as background. 
- 
- When present, the bKGD chunk must precede the first IDAT chunk, and must follow the PLTE chunk, if any. 
- ==="
- !

Item was removed:
- ----- Method: PNGReadWriter>>processIDATChunk (in category 'chunks') -----
- processIDATChunk
- 
- 	interlaceMethod = 0
- 		ifTrue: [ self processNonInterlaced ]
- 		ifFalse: [ self processInterlaced ]
- !

Item was removed:
- ----- Method: PNGReadWriter>>processIHDRChunk (in category 'chunks') -----
- processIHDRChunk
- 	width := chunk longAt: 1 bigEndian: true.
- 	height := chunk longAt: 5 bigEndian: true.
- 	bitsPerChannel := chunk at: 9.
- 	colorType := chunk at: 10.
- 	"compression := chunk at: 11." "TODO - validate compression"
- 	"filterMethod := chunk at: 12." "TODO - validate filterMethod"
- 	interlaceMethod := chunk at: 13. "TODO - validate interlace method"
- 	(#(2 4 6) includes: colorType)
- 		ifTrue: [depth := 32].
- 	(#(0 3) includes: colorType) ifTrue: [
- 		depth := bitsPerChannel min: 8.
- 		colorType = 0 ifTrue: [ "grayscale"
- 			palette := self grayColorsFor: depth.
- 		].
- 	].
- 	bitsPerPixel := (BPP at: colorType+1) at: bitsPerChannel highBit.
- 	bytesPerScanline := width * bitsPerPixel + 7 // 8.
- 	rowSize := width * depth + 31 >> 5.
- !

Item was removed:
- ----- Method: PNGReadWriter>>processInterlaced (in category 'chunks') -----
- processInterlaced
- 	| z startingCol colIncrement rowIncrement startingRow |
- 	startingCol := #(0 4 0 2 0 1 0 ).
- 	colIncrement := #(8 8 4 4 2 2 1 ).
- 	rowIncrement := #(8 8 8 4 4 2 2 ).
- 	startingRow := #(0 0 4 0 2 0 1 ).
- 	z := ZLibReadStream 
- 		on: idatChunkStream originalContents
- 		from: 1
- 		to: idatChunkStream position.
- 	1 to: 7 do: [:pass |
- 		| cx sc bytesPerPass |
- 		(self doPass: pass)
- 			ifTrue:
- 				[cx := colIncrement at: pass.
- 				sc := startingCol at: pass.
- 				bytesPerPass := width - sc + cx - 1 // cx * bitsPerPixel + 7 // 8.
- 				prevScanline := ByteArray new: bytesPerPass.
- 				thisScanline := ByteArray new: bytesPerScanline.
- 				(startingRow at: pass)
- 					to: height - 1
- 					by: (rowIncrement at: pass)
- 					do: [:y |
- 						| filter temp |
- 						filter := z next.
- 						filtersSeen add: filter.
- 						(filter isNil or: [(filter between: 0 and: 4) not])
- 							ifTrue: [^ self].
- 						thisScanline := z next: bytesPerPass into: thisScanline startingAt: 1.
- 						self filterScanline: filter count: bytesPerPass.
- 						self copyPixels: y at: sc by: cx.
- 						temp := prevScanline.
- 						prevScanline := thisScanline.
- 						thisScanline := temp.
- 					]
- 				]
- 	].
- 	z atEnd ifFalse:[self error: 'Unexpected data' translated].!

Item was removed:
- ----- Method: PNGReadWriter>>processNextChunk (in category 'chunks') -----
- processNextChunk
- 
- 	| length chunkType crc chunkCrc |
- 
- 	length := self nextLong.
- 
- 	chunkType := (self next: 4) asString.
- 	(chunk isNil or: [ chunk size ~= length ])
- 		ifTrue: [ chunk := self next: length ]
- 		ifFalse: [ stream next: length into: chunk startingAt: 1 ].
- 	chunkCrc := self nextLong bitXor: 16rFFFFFFFF.
- 	crc := self updateCrc: 16rFFFFFFFF from: 1 to: 4 in: chunkType.
- 	crc := self updateCrc: crc from: 1 to: length in: chunk.
- 	crc = chunkCrc ifFalse:[
- 		self error: ('PNGReadWriter crc error in chunk {1}' translated format: {chunkType}).
- 	].
- 
- 	chunkType = 'IEND' ifTrue: [stream setToEnd. ^self	"*should* be the last chunk"].
- 	chunkType = 'sBIT' ifTrue: [^self processSBITChunk "could indicate unusual sample depth in original"].
- 	chunkType = 'gAMA' ifTrue: [^self 	"indicates gamma correction value"].
- 	chunkType = 'bKGD' ifTrue: [^self processBackgroundChunk].
- 	chunkType = 'pHYs' ifTrue: [^self processPhysicalPixelChunk].
- 	chunkType = 'tRNS' ifTrue: [^self processTransparencyChunk].
- 
- 	chunkType = 'IHDR' ifTrue: [^self processIHDRChunk].
- 	chunkType = 'PLTE' ifTrue: [^self processPLTEChunk].
- 	chunkType = 'IDAT' ifTrue: [
- 		"---since the compressed data can span multiple
- 		chunks, stitch them all together first. later,
- 		if memory is an issue, we need to figure out how
- 		to do this on the fly---"
- 		idatChunkStream
- 			ifNil: [ idatChunkStream := WriteStream with: chunk copy ]
- 			ifNotNil: [ idatChunkStream nextPutAll: chunk ].
- 		^self
- 	].
- 	unknownChunks add: chunkType.
- !

Item was removed:
- ----- Method: PNGReadWriter>>processNonInterlaced (in category 'chunks') -----
- processNonInterlaced
- 	| z filter temp copyMethod debug |
- 	debug := self debugging.
- 	copyMethod := #(copyPixelsGray: nil copyPixelsRGB: copyPixelsIndexed:
- 		  copyPixelsGrayAlpha: nil copyPixelsRGBA:) at: colorType+1.
- 	debug ifTrue: [ Transcript cr; nextPutAll: 'NI chunk size='; print: idatChunkStream position ].
- 	z := ZLibReadStream 
- 		on: idatChunkStream originalContents
- 		from: 1
- 		to: idatChunkStream position.
- 	prevScanline := ByteArray new: bytesPerScanline.
- 	thisScanline := ByteArray new: bytesPerScanline.
- 	0 to: height-1 do: [ :y |
- 		filter := z next.
- 		debug ifTrue:[filtersSeen add: filter].
- 		thisScanline := z next: bytesPerScanline into: thisScanline startingAt: 1.
- 		(debug and: [ thisScanline size < bytesPerScanline ]) ifTrue: [ Transcript nextPutAll: ('wanted {1} but only got {2}' format: { bytesPerScanline. thisScanline size }); cr ].
- 		filter = 0 ifFalse:[self filterScanline: filter count: bytesPerScanline].
- 		self perform: copyMethod with: y.
- 		temp := prevScanline.
- 		prevScanline := thisScanline.
- 		thisScanline := temp.
- 		].
- 	z atEnd ifFalse:[self error:'Unexpected data'].
- 	debug ifTrue: [Transcript  nextPutAll: ' compressed size='; print: z position  ].
- !

Item was removed:
- ----- Method: PNGReadWriter>>processPLTEChunk (in category 'chunks') -----
- processPLTEChunk
- 
- 	| colorCount i |
- 
- 	colorCount := chunk size // 3.
- 	self flag: #todo. "validate colorCount against depth"
- 	palette := Array new: colorCount.
- 	0 to: colorCount-1 do: [ :index |
- 		i := index * 3 + 1.
- 		palette at: index+1 put:
- 			(Color r: (chunk at: i)/255.0 g: (chunk at: i+1)/255.0 b: (chunk at: i+2)/255.0)
- 		].!

Item was removed:
- ----- Method: PNGReadWriter>>processPhysicalPixelChunk (in category 'chunks') -----
- processPhysicalPixelChunk
- 
- 	"Transcript show: '  PHYSICAL: ',chunk printString."
- !

Item was removed:
- ----- Method: PNGReadWriter>>processSBITChunk (in category 'chunks') -----
- processSBITChunk
- 	| rBits gBits bBits aBits |
- 	colorType = 6 ifFalse:[^self].
- 	rBits := chunk at: 1.
- 	gBits := chunk at: 2.
- 	bBits := chunk at: 3.
- 	aBits := chunk at: 4.
- 	(rBits = 5 and:[gBits = 5 and:[bBits = 5 and:[aBits = 1]]]) ifTrue:[
- 		depth := 16.
- 	].!

Item was removed:
- ----- Method: PNGReadWriter>>processTransparencyChunk (in category 'chunks') -----
- processTransparencyChunk
- 
- 	"Transcript show: '  TRANSPARENCY ',chunk printString."
- 	colorType = 0
- 		ifTrue:
- 			[transparentPixelValue := chunk unsignedShortAt: 1 bigEndian: true.
- 			bitsPerChannel <= 8
- 				ifTrue: [palette at: transparentPixelValue + 1 put: Color transparent]
- 				ifFalse: [palette at: 1 put: Color transparent].
- 			^self].
- 	colorType = 2
- 		ifTrue:
- 			[| red green blue |
- 			red :=  chunk unsignedShortAt: 1 bigEndian: true.
- 			green :=  chunk unsignedShortAt: 3 bigEndian: true.
- 			blue :=  chunk unsignedShortAt: 5 bigEndian: true.
- 			transparentPixelValue := bitsPerChannel <= 8
- 				ifTrue: [16rFF00 + red << 8 + green << 8 + blue]
- 				ifFalse: [red << 16 + green << 16 + blue].
- 			^self].
- 	colorType = 3
- 		ifTrue:
- 			[chunk withIndexDo: [ :alpha :index |
- 				palette at: index put: ((palette at: index) alpha: alpha/255)].
- 			^self].
- !

Item was removed:
- ----- Method: PNGReadWriter>>rgbaDecoderMapForDepth: (in category 'pixel copies') -----
- rgbaDecoderMapForDepth: decoderDepth
- 	bigEndian ifTrue:[
- 		depth = 16 ifTrue:[
- 			"Big endian, 32 -> 16 color mapping."
- 			^ColorMap
- 				shifts: #(-17 -14 -11 0)
- 				masks: #(16rF8000000 16rF80000 16rF800 16r00)
- 		] ifFalse:[
- 			"Big endian, 32 -> 32 color mapping"
- 			^ColorMap 
- 				shifts: #(-8 -8 -8 24) 
- 				masks: #(16rFF000000 16rFF0000 16rFF00 16rFF).
- 		].
- 	].
- 	depth = 16 ifTrue:[
- 		"Little endian, 32 -> 16 color mapping."
- 		^ColorMap
- 			shifts: #(7 -6 -19 0)
- 			masks: #(16rF8 16rF800 16rF80000 0)
- 	] ifFalse:[
- 		"Little endian, 32 -> 32 color mapping"
- 		^ColorMap 
- 			shifts: #(-16 0 16 0) 
- 			masks: #(16rFF0000 16rFF00 16rFF 16rFF000000).
- 	].!

Item was removed:
- ----- Method: PNGReadWriter>>understandsImageFormat (in category 'accessing') -----
- understandsImageFormat
- 	#(137 80 78 71 13 10 26 10) do: [ :byte |
- 		stream next = byte ifFalse: [^ false]].
- 	^ true
- !

Item was removed:
- ----- Method: PNGReadWriter>>updateCrc:from:to:in: (in category 'writing') -----
- updateCrc: oldCrc from: start to: stop in: aCollection
- 	^ZipWriteStream updateCrc: oldCrc from: start to: stop in: aCollection!

Item was removed:
- ----- Method: PNGReadWriter>>writeChunk: (in category 'writing') -----
- writeChunk: crcStream
- 	| bytes length crc debug |
- 	debug := self debugging.
- 	bytes := crcStream originalContents.
- 	length := crcStream position.
- 	crc := self updateCrc: 16rFFFFFFFF from: 1 to: length in: bytes.
- 	crc := crc bitXor: 16rFFFFFFFF.
- 	debug ifTrue: [ Transcript cr;
- 		print: stream position; space;
- 		nextPutAll: (bytes copyFrom: 1 to: 4) asString;
- 		nextPutAll: ' len='; print: length;
- 		nextPutAll: ' crc=0x'; nextPutAll: crc printStringHex  ].
- 	stream nextNumber: 4 put: length-4. "exclude chunk name"
- 	stream next: length putAll: bytes startingAt: 1.
- 	stream nextNumber: 4 put: crc.
- 	debug ifTrue: [ Transcript nextPutAll: ' afterPos='; print: stream position ].
- 	crcStream resetToStart.!

Item was removed:
- ----- Method: PNGReadWriter>>writeFileSignature (in category 'writing') -----
- writeFileSignature
- 	stream nextPutAll: #[ 16r89 16r50 16r4E  16r47 16r0D 16r0A 16r1A 16r0A ]!

Item was removed:
- ----- Method: PNGReadWriter>>writeIDATChunkOn: (in category 'writing') -----
- writeIDATChunkOn: aStream
- 	"Write the IDAT chunk"
- 	| z |
- 	aStream nextPutAll: 'IDAT' asByteArray.
- 	z := ZLibWriteStream on: aStream.
- 	form depth <= 8 
- 		ifTrue:[self writeType3DataOn: z]
- 		ifFalse:[ self writeType6DataOn: z].
- 	self debugging ifTrue: [
- 		Transcript cr;
- 			nextPutAll: 'compressed size=';
- 			print: aStream position;
- 			nextPutAll: ' uncompressed size=';
- 			print: z position  ]
- !

Item was removed:
- ----- Method: PNGReadWriter>>writeIENDChunkOn: (in category 'writing') -----
- writeIENDChunkOn: aStream
- 	"Write the IEND chunk"
- 	aStream nextPutAll: 'IEND' asByteArray.!

Item was removed:
- ----- Method: PNGReadWriter>>writeIHDRChunkOn: (in category 'writing') -----
- writeIHDRChunkOn: aStream
- 	"Write the IHDR chunk"
- 	aStream nextPutAll: 'IHDR' asByteArray.
- 	aStream nextInt32Put: width.
- 	aStream nextInt32Put: height.
- 	aStream nextNumber: 1 put: bitsPerChannel.
- 	aStream nextNumber: 1 put: colorType.
- 	aStream nextNumber: 1 put: 0. "compression"
- 	aStream nextNumber: 1 put: 0. "filter method"
- 	aStream nextNumber: 1 put: 0. "interlace method"
- !

Item was removed:
- ----- Method: PNGReadWriter>>writePLTEChunkOn: (in category 'writing') -----
- writePLTEChunkOn: aStream
- 	"Write the PLTE chunk"
- 	| colors |
- 	aStream nextPutAll: 'PLTE' asByteArray.
- 	(form isColorForm) 
- 		ifTrue:[colors := form colors]
- 		ifFalse:[colors := Color indexedColors copyFrom: 1 to: (1 bitShift: form depth)].
- 	colors do:[:aColor|
- 		| r g b |
- 		r := (aColor red * 255) truncated.
- 		g := (aColor green * 255) truncated.
- 		b := (aColor blue * 255) truncated.
- 		aStream nextPut: r; nextPut: g; nextPut: b.
- 	].!

Item was removed:
- ----- Method: PNGReadWriter>>writeSBITChunkOn: (in category 'writing') -----
- writeSBITChunkOn: aStream
- 	"Write the IDAT chunk"
- 	aStream nextPutAll: 'sBIT' asByteArray.
- 	form depth = 16 ifFalse: [self notYetImplemented].
- 	aStream nextPut: 5.
- 	aStream nextPut: 5.
- 	aStream nextPut: 5.
- 	aStream nextPut: 1.!

Item was removed:
- ----- Method: PNGReadWriter>>writeTRNSChunkOn: (in category 'writing') -----
- writeTRNSChunkOn: aStream
- 	"Write out tRNS chunk"
- 	aStream nextPutAll: 'tRNS' asByteArray.
- 	form colors do:[:aColor|
- 		aStream nextPut: (aColor alpha * 255) truncated.
- 	].!

Item was removed:
- ----- Method: PNGReadWriter>>writeType3DataOn: (in category 'writing') -----
- writeType3DataOn: zStream
- 	"Write color indexed data."
- 	| scanline hack hackBlt swizzleBlt swizzleHack hackDepth |
- 	scanline := ByteArray new: bytesPerScanline + 3 // 4 * 4.
- 	hackDepth := bigEndian ifTrue:[form depth] ifFalse:[form depth negated].
- 	hack := Form extent: width at 1 depth: hackDepth bits: scanline.
- 	hackBlt := BitBlt toForm: hack.
- 	hackBlt sourceForm: form.
- 	hackBlt combinationRule: Form over.
- 	hackBlt destOrigin: 0 at 0.
- 	hackBlt width: width; height: 1.
- 	(form depth < 8 and:[bigEndian not]) ifTrue:[
- 		swizzleHack := Form new hackBits: scanline.
- 		swizzleBlt := BitBlt toForm: swizzleHack.
- 		swizzleBlt sourceForm: swizzleHack.
- 		swizzleBlt combinationRule: Form over.
- 		swizzleBlt colorMap: (StandardSwizzleMaps at: form depth).
- 	].
- 	0 to: height-1 do:[:i|
- 		hackBlt sourceOrigin: 0 at i; copyBits.
- 		swizzleBlt ifNotNil:[swizzleBlt copyBits].
- 		zStream nextPut: 0. "filterType"
- 		zStream next: bytesPerScanline putAll: scanline startingAt: 1.
- 	].
- 	zStream close.!

Item was removed:
- ----- Method: PNGReadWriter>>writeType6DataOn: (in category 'writing') -----
- writeType6DataOn: zStream
- 	"Write RGBA data."
- 	| scanline hack hackBlt cm miscBlt |
- 	scanline := ByteArray new: bytesPerScanline.
- 	hack := Form extent: width at 1 depth: 32 bits: scanline.
- 	form depth = 16 ifTrue:[
- 		"Expand 16 -> 32"
- 		miscBlt := BitBlt toForm: hack.
- 		miscBlt sourceForm: form.
- 		miscBlt combinationRule: Form over.
- 		miscBlt destOrigin: 0 at 0.
- 		miscBlt width: width; height: 1.
- 	].
- 	hackBlt := BitBlt toForm: hack.
- 	hackBlt sourceForm: (miscBlt ifNil:[form] ifNotNil:[hack]).
- 	hackBlt combinationRule: Form over.
- 	hackBlt destOrigin: 0 at 0.
- 	hackBlt width: width; height: 1.
- 	bigEndian ifTrue:[
- 		cm := ColorMap 
- 			shifts: #(8 8 8 -24) 
- 			masks: #(16rFF0000 16rFF00 16rFF 16rFF000000).
- 	] ifFalse:[
- 		cm := ColorMap 
- 			shifts: #(-16 0 16 0) 
- 			masks: #(16rFF0000 16rFF00 16rFF 16rFF000000).
- 	].
- 	hackBlt colorMap: cm.
- 	0 to: height-1 do:[:i|
- 		miscBlt ifNil:[
- 			hackBlt sourceOrigin: 0 at i; copyBits.
- 		] ifNotNil:[
- 			miscBlt sourceOrigin: 0 at i; copyBits.
- 			hack fixAlpha.
- 			hackBlt copyBits.
- 		].
- 		zStream nextPut: 0. "filterType"
- 		zStream nextPutAll: scanline.
- 	].
- 	zStream close.!

Item was removed:
- ImageReadWriter subclass: #PNMReadWriter
- 	instanceVariableNames: 'first type origin cols rows depth maxValue tupleType pragma'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!
- 
- !PNMReadWriter commentStamp: 'nice 3/24/2010 07:37' prior: 0!
- I am a subclass of ImageReadWriter that decodes portable anymap file formats
- (pbm, pgm, ppm and  pam) images.
- 
- I accept the #origin pragma for SE files as described in:
- Algoritms For Image Processing And Computer Vision. J. R. Parker
- 
- Don't work with 2 bytes samples (16 bit grays, > 32 bits color, etc...), 
- pam files preliminary support.
- 
- f := ImageReadWriter formFromFileNamed: 'Tools:Squeak3.4:Carmen.ppm'.
- f morphEdit
- 
- Submitted by Javier Diaz Reinoso, Oct/2003!

Item was removed:
- ----- Method: PNMReadWriter class>>testToSEFile: (in category 'testing') -----
- testToSEFile: filename
- 	"write SE file with origin
- 		PNMReadWriter testToSEFile: 'Tools:Squeak3.4:outSE.pbm'.
- 	"
- 	| prw f |
- 	prw := self new.
- 	prw stream: ((FileStream newFileNamed: filename) binary).
- 	prw pragma: '#origin 10 10', String lf.
- 	f := Form fromUser.
- 	prw nextPutImage: f!

Item was removed:
- ----- Method: PNMReadWriter class>>typicalFileExtensions (in category 'image reading/writing') -----
- typicalFileExtensions
- 	"Answer a collection of file extensions (lowercase) which files that I can read might commonly have"
- 	^#('pbm' 'pgm' 'pnm' 'ppm' 'pam')!

Item was removed:
- ----- Method: PNMReadWriter>>cleanLine (in category 'reading') -----
- cleanLine
- 	"upTo LF or CR, tab as space"
- 
- 	^stream nextLine ifNotNil: [:line | line replaceAll: Character tab with: Character space]!

Item was removed:
- ----- Method: PNMReadWriter>>getTokenPbm: (in category 'reading') -----
- getTokenPbm: aCollection
- 	"get a number, return rest of collection"
- 	| line tokens token |
- 	tokens := aCollection.
- 	tokens size = 0 ifTrue:[
- 		[
- 			line := self pbmGetLine.
- 			line ifNil:[^{nil . nil}].
- 			tokens := line findTokens: ' '.
- 			tokens size = 0
- 		] whileTrue:[].
- 	].
- 	"Transcript cr; show: tokens asString."
- 	token := tokens removeFirst.
- 	^{token asInteger . tokens}
- !

Item was removed:
- ----- Method: PNMReadWriter>>nextImage (in category 'reading') -----
- nextImage
- 	"read one image"
- 	| data p |
- 	first ifNil:[
- 		first := false.
- 		data := stream contentsOfEntireFile.
- 		stream := (RWBinaryOrTextStream with: data) reset.
- 	]
- 	ifNotNil:[
- 		type < 4 ifTrue:[
- 			self error: 'Plain PBM, PGM or PPM have only one image' translated
- 		].
- 	].
- 	stream ascii.
- 	p := stream next.
- 	type := (stream next) asInteger - 48.
- 	(p = $P and:[type > 0 and:[type < 8]]) ifFalse:[
- 		self error: 'Not a PNM file' translated
- 	].
- 	type = 7 ifTrue:[
- 		self readHeaderPAM
- 	]
- 	ifFalse: [
- 		self readHeader
- 	].
- 	type caseOf: {
- 		[1] 	->	[^self readPlainBW].
- 		[2] 	->	[^self readPlainGray].
- 		[3] 	->	[^self readPlainRGB].
- 		[4] 	->	[^self readBWreverse: false].
- 		[5] 	->	[^self readGray].
- 		[6] 	->	[^self readRGB].
- 		[7] 	->	[	"PAM"
- 					(tupleType asUppercase) caseOf: {
- 						['BLACKANDWHITE'] 		-> [^self readBWreverse: true].
- 						['GRAYSCALE'] 			-> [^self readGray].
- 						['RGB'] 					-> [^self readRGB].
- 						['RGB_ALPHA'] 			-> [^self notYetImplemented].
- 						['GRAYSCALE_ALPHA'] 	-> [^self notYetImplemented].
- 					} otherwise: [^self readData].
- 				]
- 	}!

Item was removed:
- ----- Method: PNMReadWriter>>nextPutBW:reverse: (in category 'writing') -----
- nextPutBW: aForm reverse: flagXor
- 	| myType val nBytes bytesRow |
- 	cols := aForm width.
- 	rows := aForm height.
- 	depth := aForm depth.
- 	"stream position: 0."
- 	aForm depth = 1 ifTrue:[myType := $4] ifFalse:[myType := $5].
- 	self writeHeader: myType.
- 	stream binary.
- 	nBytes := (cols/8) ceiling.
- 	bytesRow := (cols/32) ceiling * 4.
- 	0 to: rows-1 do: [:y | | i |
- 		i := 1 + (bytesRow*y).
- 		0 to: nBytes-1 do: [:x |
- 			val := aForm bits byteAt: i.
- 			flagXor ifTrue:[val := val bitXor: 16rFF].
- 			stream nextPut: val.
- 			i := i+1.
- 		]
- 	].
- !

Item was removed:
- ----- Method: PNMReadWriter>>nextPutGray: (in category 'writing') -----
- nextPutGray: aForm
- 	| myType val |
- 	cols := aForm width.
- 	rows := aForm height.
- 	depth := aForm depth.
- 	"stream position: 0."
- 	aForm depth = 1 ifTrue:[myType := $4] ifFalse:[myType := $5].
- 	self writeHeader: myType.
- 	0 to: rows-1 do: [:y |
- 		0 to: cols-1 do: [:x |
- 			val := aForm pixelValueAt: x at y.
- 			stream nextPut: val.
- 		]
- 	].
- !

Item was removed:
- ----- Method: PNMReadWriter>>nextPutImage: (in category 'writing') -----
- nextPutImage: aForm
- 	aForm unhibernate.
- 	aForm depth	 caseOf: {
- 		[1] 		-> [self nextPutBW: aForm reverse: false].
- 		[16] 	-> [self nextPutRGB: aForm].
- 		[32] 	-> [self nextPutRGB: aForm].
- 	} otherwise: [
- 		(aForm respondsTo: #colors) ifTrue:[
- 			aForm colors ifNil: [
- 				self nextPutGray: aForm
- 			]
- 			ifNotNil: [
- 				self nextPutRGB: aForm
- 			]
- 		]
- 		ifFalse:[
- 			self nextPutGray: aForm
- 		]
- 	]!

Item was removed:
- ----- Method: PNMReadWriter>>nextPutRGB: (in category 'writing') -----
- nextPutRGB: aForm
- 	| myType f shift mask |
- 	cols := aForm width.
- 	rows := aForm height.
- 	depth := aForm depth.
- 	f := aForm.
- 	depth < 16 ifTrue:[
- 		f := aForm asFormOfDepth: 32.
- 		depth := 32.
- 	].
- 	myType := $6.
- 	"stream position: 0."
- 	self writeHeader: myType.
- 	depth = 32 ifTrue:[shift := 8. mask := 16rFF] ifFalse:[shift := 5. mask := 16r1F].
- 	0 to: rows-1 do: [:y |
- 		0 to: cols-1 do: [:x | | p r g b |
- 			p := f pixelValueAt: x at y.
- 			b := p bitAnd: mask. p := p >> shift.
- 			g := p bitAnd: mask. p := p >> shift.
- 			r := p bitAnd: mask.
- 			stream nextPut: r.
- 			stream nextPut: g.
- 			stream nextPut: b.
- 		]
- 	].
- !

Item was removed:
- ----- Method: PNMReadWriter>>origin (in category 'accessing') -----
- origin
- 	^origin!

Item was removed:
- ----- Method: PNMReadWriter>>pbmGetLine (in category 'reading') -----
- pbmGetLine
- 	"Get the next non-comment line from the PBM stream
- 	Look for 'pragmas' - commands hidden in the comments"
- 	
-  	| line |
- 	[
- 		line := self cleanLine.
- 		line ifNil: [^nil].
- 		(line size > 0 and:[(line at: 1) = $#]) ifTrue:[
- 			self pbmParam: line.
- 		].
- 		(line size = 0) or:[(line at: 1) = $#]
- 	]
-  	whileTrue: [].
- 	^line!

Item was removed:
- ----- Method: PNMReadWriter>>pbmParam: (in category 'reading') -----
- pbmParam: line
- 	"Look for a parameter hidden in a comment"
- 	| key tokens |
- 	tokens := line findTokens: ' '.
- 	key := (tokens at: 1) asLowercase.
- 	(key = '#origin' and:[tokens size = 3]) ifTrue:[	"ORIGIN key word"
- 		"This is for SE files as described in:
- 		Algoritms For Image Processing And Computer Vision. J. R. Parker"
- 		origin := ((tokens at: 2) asInteger) @ ((tokens at: 3) asInteger)
- 	].
- !

Item was removed:
- ----- Method: PNMReadWriter>>pragma: (in category 'accessing') -----
- pragma: s
- 	pragma := s!

Item was removed:
- ----- Method: PNMReadWriter>>r:g:b:for: (in category 'reading') -----
- r: r g: g b: b for: aDepth
- 	"integer value according depth"
- 	| val |
- 	aDepth = 16 ifTrue: [
- 		val := (1 << 15) + (r << 10) + (g << 5) + b.
- 	]
- 	ifFalse:[
- 		val := (16rFF << 24) + (r << 16) + (g << 8) + b.
- 	].
- 	^val
- !

Item was removed:
- ----- Method: PNMReadWriter>>readBWreverse: (in category 'reading') -----
- readBWreverse: flagXor
- 	"B&W for PAM"
- 	| val form bytesRow nBytes |
- 	stream binary.
- 	form := Form extent: cols at rows depth: 1.
- 	nBytes := (cols/8) ceiling.
- 	bytesRow := (cols/32) ceiling * 4.
- 	0 to: rows-1 do: [:y | | i |
- 		i := 1 + (bytesRow*y).
- 		0 to: nBytes-1 do: [:x |
- 			val := stream next.
- 			flagXor ifTrue:[val := val bitXor: 16rFF].
- 			form bits byteAt: i put: val.
- 			i := i+1.
- 		]
- 	].
- 	^form
- !

Item was removed:
- ----- Method: PNMReadWriter>>readData (in category 'reading') -----
- readData
- 	"generic data"
- 	| data nBits nBytes val sample |
- 	stream binary.
- 	data := OrderedCollection new.
- 	nBits := maxValue floorLog:2.
- 	nBytes := (nBits+1) >> 3.
- 	(nBits+1 rem: 8) > 0 ifTrue:[nBytes := nBytes+1].
- 
- 	0 to: rows-1 do: [:y |
- 		0 to: cols-1 do: [:x |
- 			val := 0.
- 			1 to: nBytes do: [:n |
- 				sample := stream next.
- 				val := val << 8 + sample.
- 			].
- 			data add: val.
- 		]
- 	].
- 	^data
- 
- !

Item was removed:
- ----- Method: PNMReadWriter>>readGray (in category 'reading') -----
- readGray
- 	"gray form, return ColorForm with gray ramp"
- 	| form poker |
- 	maxValue > 255 ifTrue:[self error: ('Gray value > {1} bits not supported in Squeak' translated format: {8})].
- 	stream binary.
- 	form := ColorForm extent: cols at rows depth: depth.
- 	form colors: nil.
- 	poker := BitBlt bitPokerToForm: form.
- 	0 to: rows-1 do: [:y |
- 		0 to: cols-1 do: [:x |
- 			|val|
- 			val := stream next.
- 			poker pixelAt: x at y put: val.
- 		]
- 	].
- 	"a better way is using a gamma corrected palette"
- 	form colors: ((0 to: 255) collect:[:c|
- 		c > maxValue
- 			ifTrue:[Color white]
- 			ifFalse:[Color gray: (c/maxValue) asFloat]]).
- 	form colors at: 1 put: (Color black).
- 	^form
- !

Item was removed:
- ----- Method: PNMReadWriter>>readHeader (in category 'reading') -----
- readHeader
- 	"read header for pbm, pgm or ppm"
- 	| tokens aux d c  |
- 	tokens := OrderedCollection new.
- 	aux := self getTokenPbm: tokens.
- 	cols := aux at: 1. tokens := aux at: 2.
- 	aux := self getTokenPbm: tokens.
- 	rows := aux at: 1. tokens := aux at: 2.
- 
- 	(type = 1 or:[type = 4]) ifTrue:[
- 		maxValue := 1
- 	]
- 	ifFalse: [
- 		aux := self getTokenPbm: tokens.
- 		maxValue := aux at: 1. tokens := aux at: 2.
- 	].
- 	d := {1 . 2 . 4 . 	8 . 		16 . 32}.
- 	c := {2 . 4 . 16 . 256 . 32768 . 16777216}. 
- 	(type = 3 or:[type = 6]) ifTrue: [
- 		maxValue >= 65536 ifTrue:[
- 			self error: ('Pixmap > {1} bits not supported in PPM' translated format: {48})
- 		].
- 		maxValue >= 256 ifTrue:[
- 			self error: ('Pixmap > {1} bits are not supported in Squeak' translated format: {32})
- 		].
- 		maxValue < 32 ifTrue:[depth := 16] ifFalse:[depth := 32].
- 	]
- 	ifFalse: [
- 		depth := nil.
- 		1 to: c size do:[:i| ((c at: i) > maxValue and:[depth = nil]) ifTrue:[depth:=d at: i]].
- 	].
- 	Transcript cr; show: 'PBM file class ', type asString, ' size ', cols asString, ' x ', 
- 		rows asString, ' maxValue =', maxValue asString, ' depth=', depth asString.
- !

Item was removed:
- ----- Method: PNMReadWriter>>readHeaderPAM (in category 'reading') -----
- readHeaderPAM
- 	"read pam header, not tested"
- 	| loop |
- 	tupleType := ''.
- 	loop := true.
- 	loop whileTrue:[ | key val tokens line |
- 		line := self pbmGetLine.
- 		tokens := line findTokens: ' '.
- 		tokens size = 2 ifTrue:[
- 			key := tokens at: 1 asUppercase.
- 			val := tokens at: 2.
- 			key caseOf: {
- 				['WIDTH'] 		-> [cols := val asInteger].
- 				['HEIGHT'] 		-> [rows := val asInteger].
- 				['DEPTH'] 		-> [depth := val asInteger].
- 				['MAXVAL']		-> [maxValue := val asInteger].
- 				['TUPLETYPE']	-> [tupleType := tupleType, ' ', val].
- 				['ENDHDR']		-> [loop := false].
- 			}
- 		]
- 	].
- 	Transcript cr; show: 'PAM file class ', type asString, ' size ', cols asString, ' x ', 
- 		rows asString, ' maxValue =', maxValue asString, ' depth=', depth asString.
- !

Item was removed:
- ----- Method: PNMReadWriter>>readPlainBW (in category 'reading') -----
- readPlainBW
- 	"plain BW"
- 	| val form poker |
- 	form := Form extent: cols at rows depth: depth.
- 	poker := BitBlt bitPokerToForm: form.
- 	0 to: rows-1 do: [:y |
- 		0 to: cols-1 do: [:x |
- 			[val := stream next. (val = $0 or:[val = $1])] whileFalse:[
- 				val ifNil: [self error: 'End of file reading PBM' translated].
- 			].
- 			poker pixelAt: x at y put: (val asInteger).
- 		]
- 	].
- 	^form
- !

Item was removed:
- ----- Method: PNMReadWriter>>readPlainGray (in category 'reading') -----
- readPlainGray
- 	"plain gray"
- 	| val form poker aux tokens |
- 	form := Form extent: cols at rows depth: depth.
- 	poker := BitBlt bitPokerToForm: form.
- 	tokens := OrderedCollection new.
- 	0 to: rows-1 do: [:y |
- 		0 to: cols-1 do: [:x |
- 			aux := self getTokenPbm: tokens.
- 			val := aux at: 1. tokens := aux at: 2.
- 			poker pixelAt: x at y put: val.
- 		]
- 	].
- 	^form
- !

Item was removed:
- ----- Method: PNMReadWriter>>readPlainRGB (in category 'reading') -----
- readPlainRGB
- 	"RGB form, use 32 bits"
- 	| val form poker tokens aux |
- 	maxValue > 255 ifTrue:[self error: ('RGB value > {1} bits not supported in Squeak' translated format: {32})].
- 	form := Form extent: cols at rows depth: 32.
- 	poker := BitBlt bitPokerToForm: form.
- 	tokens := OrderedCollection new.
- 	0 to: rows-1 do: [:y |
- 		0 to: cols-1 do: [:x | | r g b|
- 			aux := self getTokenPbm: tokens. r := aux at: 1. tokens := aux at: 2.
- 			aux := self getTokenPbm: tokens. g := aux at: 1. tokens := aux at: 2.
- 			aux := self getTokenPbm: tokens. b := aux at: 1. tokens := aux at: 2.
- 			val := self r: r g: g b: b for: depth.
- 			poker pixelAt: x at y put: val.
- 		]
- 	].
- 	^form
- !

Item was removed:
- ----- Method: PNMReadWriter>>readRGB (in category 'reading') -----
- readRGB
- 	"RGB form, use 16/32 bits"
- 	| val form poker sample shift |
- 	maxValue > 255 ifTrue:[self error: ('RGB value > {1} bits not supported in Squeak' translated format: {32})].
- 	stream binary.
- 	form := Form extent: cols at rows depth: depth.
- 	poker := BitBlt bitPokerToForm: form.
- 	depth = 32 ifTrue:[shift := 8] ifFalse:[shift := 5].
- 	0 to: rows-1 do: [:y |
- 		0 to: cols-1 do: [:x |
- 			val := 16rFF.	"no transparency"
- 			1 to: 3 do: [:i |
- 				sample := stream next.
- 				val := val << shift + sample.
- 			].
- 			poker pixelAt: x at y put: val.
- 		]
- 	].
- 	^form
- !

Item was removed:
- ----- Method: PNMReadWriter>>stream: (in category 'accessing') -----
- stream: s
- 	stream := s!

Item was removed:
- ----- Method: PNMReadWriter>>tupleType (in category 'accessing') -----
- tupleType
- 	^tupleType!

Item was removed:
- ----- Method: PNMReadWriter>>understandsImageFormat (in category 'testing') -----
- understandsImageFormat
- 	"P1 to P7"
- 	| p  |
- 	p := stream next asCharacter.
- 	type := stream next - 48.
- 	^(p = $P and:[type > 0 and:[type < 8]])
- 	!

Item was removed:
- ----- Method: PNMReadWriter>>writeHeader: (in category 'writing') -----
- writeHeader: myType
- 	"this is ascii"
- 	stream nextPut: ($P asciiValue).
- 	stream nextPut: (myType asciiValue).
- 	stream nextPut: 10.		"nl"
- 	pragma ifNotNil:[
- 		stream nextPutAll: (pragma asByteArray).
- 	].
- 	stream nextPutAll: (cols printString) asByteArray.
- 	stream nextPut: 32.		" "
- 	stream nextPutAll: (rows printString) asByteArray.
- 	stream nextPut: 10.		"nl"
- 	depth > 1 ifTrue: [| d c maxV |
- 		d := {1 . 2 . 4  . 8   . 16 . 32}.
- 		c := {1 . 3 . 15 . 255 . 31 . 255}. 
- 		maxV := nil.
- 		1 to: d size do:[:i| ((d at: i) = depth and:[maxV = nil]) ifTrue:[maxV := c at: i]].
- 		stream nextPutAll: (maxV printString) asByteArray.
- 		stream nextPut: 10.		"nl"
- 	]
- 	!

Item was removed:
- BitBlt subclass: #Pen
- 	instanceVariableNames: 'location direction penDown'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Primitives'!
- 
- !Pen commentStamp: '<historical>' prior: 0!
- My instances can scribble on the screen or some other Form, drawing and printing at any angle. Since I am a BitBlt, the drawing can be done with an arbitary source Form.
- !

Item was removed:
- ----- Method: Pen class>>example (in category 'examples') -----
- example
- 	"Draw a spiral with a pen that is 2 pixels wide."
- 	"Display restoreAfter: [Pen example]"
- 
- 	| bic |
- 	bic := self new.
- 	bic defaultNib: 2.
- 	bic color: Color blue.
- 	bic combinationRule: Form over.
- 	1 to: 100 do: [:i | bic go: i*4. bic turn: 89].
- !

Item was removed:
- ----- Method: Pen class>>feltTip:cellSize: (in category 'tablet drawing examples') -----
- feltTip: width cellSize: cellSize
- 	"Warning: This example potentially uses a large amount of memory--it creates a Form with cellSize squared bits for every Display pixel."
- 	"In this example, all drawing is done into a large, monochrome Form and then scaled down onto the Display using smoothing. The larger the cell size, the more possible shades of gray can be generated, and the smoother the resulting line appears. A cell size of 8 yields 64 possible grays, while a cell size of 16 gives 256 levels, which is about the maximum number of grays that the human visual system can distinguish. The width parameter determines the maximum line thickness. Requires the optional tablet support primitives which may not be supported on all platforms. Works best in full screen mode. Shift-mouse to exit." 
- 	"Pen feltTip: 2.7 cellSize: 8"
- 
- 	| tabletScale bitForm pen warp |
- 	tabletScale := self tabletScaleFactor.
- 	bitForm := Form extent: Display extent * cellSize depth: 1.
- 	pen := Pen newOnForm: bitForm.
- 	pen color: Color black.
- 	warp := (WarpBlt toForm: Display)
- 		sourceForm: bitForm;
- 		colorMap: (bitForm colormapIfNeededFor: Display);
- 		cellSize: cellSize;
- 		combinationRule: Form over.
- 	Display fillColor: Color white.
- 	Display restoreAfter: [ | p r nibSize srcR startP dstR |
- 		[Sensor shiftPressed and: [Sensor anyButtonPressed]] whileFalse: [
- 			p := (Sensor tabletPoint * cellSize * tabletScale) rounded.
- 			nibSize := (Sensor tabletPressure * (cellSize * width)) rounded.
- 		     nibSize > 0
- 				ifTrue: [
- 					pen squareNib: nibSize.
- 					startP := pen location.
- 					pen goto: p.
- 					r := startP rect: pen location.
- 					dstR := (r origin // cellSize) corner: ((r corner + nibSize + (cellSize - 1)) // cellSize).
- 					srcR := (dstR origin * cellSize) corner: (dstR corner * cellSize).
- 					warp copyQuad: srcR innerCorners toRect: dstR]
- 				ifFalse: [
- 					pen place: p]]].
- !

Item was removed:
- ----- Method: Pen class>>inkBrush (in category 'tablet drawing examples') -----
- inkBrush
- 	"Similar to simplePressurePen, but this example uses the average of the recent pen pressure values. The effect is that of a Japanese ink brush that comes up gradually off the paper as the brush is lifted, causing end (and beginning) of each stroke to taper. Requires the optional tablet support primitives which may not be supported on all platforms. Works best in full screen mode. Shift-mouse to exit." 
- 	"Pen inkBrush"
- 
- 	| tabletScale historyMSecs pressureHistory pen |
- 	tabletScale := self tabletScaleFactor.
- 	historyMSecs := 120.
- 	pressureHistory := OrderedCollection new.
- 	pen := Pen newOnForm: Display.
- 	pen color: Color black.
- 	Display fillColor: Color white.
- 	Display restoreAfter: [ | sum p averagePressure now currentPressure |
- 		[Sensor shiftPressed and: [Sensor anyButtonPressed]] whileFalse: [
- 			"compute the average pressure over last historyMSecs milliseconds"
- 			now := Time millisecondClockValue.
- 			currentPressure := (20.0 * Sensor tabletPressure) rounded.
- 			pressureHistory addLast: (Array with: now with: currentPressure).
- 			[pressureHistory size > 0 and:
- 			 [(pressureHistory first first + historyMSecs) < now]]
- 				whileTrue: [pressureHistory removeFirst].  "prune old entries"
- 			sum := pressureHistory inject: 0 into: [:t :e | t + e last].
- 			averagePressure := sum // pressureHistory size.
- 
- 			p := (Sensor tabletPoint * tabletScale) rounded.
- 		     averagePressure > 0
- 				ifTrue: [
- 					pen roundNib: averagePressure.
- 					pen goto: p]
- 				ifFalse: [
- 					pen place: p]]].
- !

Item was removed:
- ----- Method: Pen class>>new (in category 'instance creation') -----
- new
- 	^ self newOnForm: Display!

Item was removed:
- ----- Method: Pen class>>newOnForm: (in category 'instance creation') -----
- newOnForm: aForm
- 	| pen |
- 	pen := super new.
- 	pen setDestForm: aForm.
- 	pen sourceOrigin: 0 at 0.
- 	pen home.
- 	pen defaultNib: 1.
- 	pen north.
- 	pen down.
- 	^ pen!

Item was removed:
- ----- Method: Pen class>>simplePressurePen (in category 'tablet drawing examples') -----
- simplePressurePen
- 	"An example of using a pressure sensitive pen to control the thickness of the pen. This requires the optional tablet support primitives which may not be supported on all platforms. Works best in full screen mode. Shift-mouse to exit." 
- 	"Pen simplePressurePen"
- 
- 	| tabletScale pen |
- 	tabletScale := self tabletScaleFactor.
- 	pen := Pen newOnForm: Display.
- 	pen color: Color black.
- 	Display fillColor: Color white.
- 	Display restoreAfter: [ | p pressure |
- 		[Sensor shiftPressed and: [Sensor anyButtonPressed]] whileFalse: [
- 			p := (Sensor tabletPoint * tabletScale) rounded.
- 			pressure := (15.0 * Sensor tabletPressure) rounded.
- 		     pressure > 0
- 				ifTrue: [
- 					pen roundNib: pressure.
- 					pen goto: p]
- 				ifFalse: [
- 					pen place: p]]].
- !

Item was removed:
- ----- Method: Pen class>>tabletScaleFactor (in category 'tablet drawing examples') -----
- tabletScaleFactor
- 	"Answer a Point that scales tablet coordinates to Display coordinates, where the full extent of the tablet maps to the extent of the entire Display."
- 
- 	| tabletExtent |
- 	tabletExtent := Sensor tabletExtent.
- 	^ (Display width asFloat / tabletExtent x) @ (Display height asFloat / tabletExtent y)
- !

Item was removed:
- ----- Method: Pen class>>testMouseTracking (in category 'tablet drawing examples') -----
- testMouseTracking
- 	"A very simple example of drawing using the mouse. Compare the tracking speed of this example with that of testTabletTracking. Mouse down to draw a stroke, shift-mouse to exit." 
- 	"Pen testMouseTracking"
- 
- 	| pen |
- 	pen := Pen newOnForm: Display.
- 	pen roundNib: 8.
- 	pen color: Color black.
- 	Display fillColor: Color white.
- 	Display restoreAfter: [ | p |
- 		[Sensor shiftPressed and: [Sensor anyButtonPressed]] whileFalse: [
- 			p := Sensor cursorPoint.
- 		     Sensor anyButtonPressed
- 				ifTrue: [pen goto: p]
- 				ifFalse: [
- 					pen color: Color random.
- 					pen place: p]]].
- !

Item was removed:
- ----- Method: Pen class>>testTabletTracking (in category 'tablet drawing examples') -----
- testTabletTracking
- 	"A very simple example of drawing using the pen of a digitizing tablet such as a Wacom ArtZ tablet. This requires the optional tablet support primitives which may not be supported on all platforms. Compare the tracking speed of this example with that of testMouseTracking. On a Macintosh, the tablet primitives provide roughly 120 samples/second versus only 60 mouse samples/second, and the difference is noticable. Works best in full screen mode. Mouse down to draw a stroke, shift-mouse to exit." 
- 	"Pen testTabletTracking"
- 
- 	| tabletScale pen |
- 	tabletScale := self tabletScaleFactor.
- 	pen := Pen newOnForm: Display.
- 	pen roundNib: 8.
- 	pen color: Color black.
- 	Display fillColor: Color white.
- 	Display restoreAfter: [ | p |
- 		[Sensor shiftPressed and: [Sensor anyButtonPressed]] whileFalse: [
- 			p := (Sensor tabletPoint * tabletScale) rounded.
- 		     Sensor tabletPressure > 0
- 				ifTrue: [pen goto: p]
- 				ifFalse: [
- 					pen color: Color random.
- 					pen place: p]]].
- !

Item was removed:
- ----- Method: Pen>>color: (in category 'operations') -----
- color: aColorOrInteger
- 	"Set the pen to the given color or to a color chosen from a fixed set of colors."
- 
- 	| count c |
- 	aColorOrInteger isInteger
- 		ifTrue: [
- 			destForm depth = 1 ifTrue: [^ self fillColor: Color black].
- 			count := 19.  "number of colors in color wheel"
- 			c := (Color red wheel: count) at: ((aColorOrInteger * 7) \\ count) + 1]
- 		ifFalse: [c := aColorOrInteger].  "assume aColorOrInteger is a Color"
- 	self fillColor: c.
- !

Item was removed:
- ----- Method: Pen>>defaultNib: (in category 'initialize-release') -----
- defaultNib: widthInteger 
- 	"Nib is the tip of a pen. This sets up the pen, with a nib of width widthInteger. You can also set the shape of the pen nib using:
- 		roundNib: widthInteger, or
- 		squareNib: widthInteger, or
- 		sourceForm: aForm"
- "Example:
- 	| bic |
- 	bic := Pen new sourceForm: Cursor normal.
- 	bic combinationRule: Form paint; turn: 90.
- 	10 timesRepeat: [bic down; go: 3; up; go: 10]."
- 
- 	self color: Color black.
- 	self squareNib: widthInteger.
- !

Item was removed:
- ----- Method: Pen>>direction (in category 'accessing') -----
- direction
- 	"Answer the receiver's current direction. 0 is towards the top of the
- 	screen."
- 
- 	^direction!

Item was removed:
- ----- Method: Pen>>down (in category 'operations') -----
- down
- 	"Set the state of the receiver's pen to down (drawing)."
- 
- 	penDown := true!

Item was removed:
- ----- Method: Pen>>dragon: (in category 'geometric designs') -----
- dragon: n  "Display restoreAfter: [Display fillWhite. Pen new dragon: 10]."
- 	"Display restoreAfter: [Display fillWhite. 1 to: 4 do:
- 				[:i | Pen new color: i; turn: 90*i; dragon: 10]]"
- 	"Draw a dragon curve of order n in the center of the screen."
- 	n = 0
- 		ifTrue: [self go: 5]
- 		ifFalse: [n > 0
- 				ifTrue: [self dragon: n - 1; turn: 90; dragon: 1 - n]
- 				ifFalse: [self dragon: -1 - n; turn: -90; dragon: 1 + n]]
- !

Item was removed:
- ----- Method: Pen>>filberts:side: (in category 'geometric designs') -----
- filberts: n side: s   "Display restoreAfter: [Pen new filberts: 4 side: 5]"
- 	"Two Hilbert curve fragments form a Hilbert tile. Draw four interlocking 
- 	tiles of order n and sides length s."
- 	| n2 |
- 	Display fillWhite.
- 	n2 := 1 bitShift: n - 1.
- 	self up; go: 0 - n2 * s; down.
- 	1 to: 4 do: 
- 		[:i | 
- 		self fill: [:p |
- 				p hilbert: n side: s.
- 				p go: s.
- 				p hilbert: n side: s.
- 				p go: s.
- 				p up.
- 				p go: n2 - 1 * s.
- 				p turn: -90.
- 				p go: n2 * s.
- 				p turn: 180.
- 				p down]
- 			color: (Color perform: (#(yellow red green blue) at: i))]!

Item was removed:
- ----- Method: Pen>>fill:color: (in category 'operations') -----
- fill: drawBlock color: color
- 	| region tileForm tilePen shape saveColor recorder |
- 	drawBlock value: (recorder := self as: PenPointRecorder).
- 	region := Rectangle encompassing: recorder points.
- 	tileForm := Form extent: region extent+6.
- 	tilePen := Pen newOnForm: tileForm.
- 	tilePen location: location-(region origin-3)
- 		direction: direction
- 		penDown: penDown.
- 	drawBlock value: tilePen.  "Draw the shape in B/W"
- 	saveColor := halftoneForm.
- 	drawBlock value: self.
- 	halftoneForm := saveColor.
- 	shape := (tileForm findShapeAroundSeedBlock: [:f | f borderWidth: 1]) reverse.
- 	shape copy: shape boundingBox from: tileForm to: 0 at 0 rule: Form erase.
- 	destForm fillShape: shape fillColor: color at: region origin-3!

Item was removed:
- ----- Method: Pen>>go: (in category 'operations') -----
- go: distance 
- 	"Move the pen in its current direction a number of bits equal to the 
- 	argument, distance. If the pen is down, a line will be drawn using the 
- 	receiver's form source as the shape of the drawing brush."
- 
- 	self goto: (direction degreeCos @ direction degreeSin) * distance + location!

Item was removed:
- ----- Method: Pen>>goto: (in category 'operations') -----
- goto: aPoint 
- 	"Move the receiver to position aPoint. If the pen is down, a line will be 
- 	drawn from the current position to the new one using the receiver's 
- 	form source as the shape of the drawing brush. The receiver's set 
- 	direction does not change."
- 	| old |
- 	old := location.
- 	location := aPoint.
- 	penDown ifTrue: [self drawFrom: old rounded
- 								to: location rounded]
- 
- 	"NOTE:  This should be changed so it does NOT draw the first point, so as
- 	not to overstrike at line junctions.  At the same time, place should draw
- 	a single dot if the pen is down, as should down (put-pen-down) if it
- 	was not down before."!

Item was removed:
- ----- Method: Pen>>hilbert:side: (in category 'geometric designs') -----
- hilbert: n side: s 
- 	"Draw an nth level Hilbert curve with side length s in the center of the 
- 	screen. Write directly into the display's bitmap only. A Hilbert curve is 
- 	a space-filling curve."
- 
- 	| a m |
- 	n = 0 ifTrue: [^self turn: 180].
- 	n > 0
- 		ifTrue: 
- 			[a := 90.
- 			m := n - 1]
- 		ifFalse: 
- 			[a := -90.
- 			m := n + 1].
- 	self turn: a.
- 	self hilbert: 0 - m side: s.
- 	self turn: a; go: s.
- 	self hilbert: m side: s.
- 	self turn: 0 - a; go: s; turn: 0 - a.
- 	self hilbert: m side: s.
- 	self go: s; turn: a.
- 	self hilbert: 0 - m side: s.
- 	self turn: a
- 	" 
- 	(Pen new) hilbert: 3 side: 8. 
- 	(Pen new sourceForm: Cursor wait) combinationRule: Form under; 
- 	hilbert: 3 side: 25.
- 	"!

Item was removed:
- ----- Method: Pen>>hilberts: (in category 'geometric designs') -----
- hilberts: n   "Display restoreAfter: [Display fillWhite.  Pen new hilberts: 5]"
- 	"Draws n levels of nested Hilbert curves"
- 	| s |
- 	self up; turn: 90; go: 128; down.
- 	1 to: n do: 
- 		[:i | 
- 		s := 256 bitShift: 0 - i.
- 		self defaultNib: n - i * 2 + 1.
- 		self color: i+1.
- 		self up; go: 0 - s / 2; turn: -90; go: s / 2; turn: 90; down.
- 		self hilbert: i side: s.
- 		self go: s.
- 		self hilbert: i side: s.
- 		self go: s]!

Item was removed:
- ----- Method: Pen>>home (in category 'operations') -----
- home
- 	"Place the receiver at the center of its frame."
- 	location := destForm boundingBox center!

Item was removed:
- ----- Method: Pen>>location (in category 'accessing') -----
- location
- 	"Answer where the receiver is currently located."
- 
- 	^location!

Item was removed:
- ----- Method: Pen>>location:direction:penDown: (in category 'private') -----
- location: aPoint direction: aFloat penDown: aBoolean
- 	location := aPoint.
- 	direction := aFloat.
- 	penDown := aBoolean!

Item was removed:
- ----- Method: Pen>>mandala: (in category 'geometric designs') -----
- mandala: npoints
- 	"Display restoreAfter: [Pen new mandala: 30]"
- 	"On a circle of diameter d, place npoints number of points. Draw all 	possible connecting lines between the circumferential points."
- 	| l points d |
- 	Display fillWhite.
- 	d := Display height-50.
- 	l := 3.14 * d / npoints.
- 	self home; up; turn: -90; go: d // 2; turn: 90; go: 0 - l / 2; down.
- 	points := Array new: npoints.
- 	1 to: npoints do: 
- 		[:i | 
- 		points at: i put: location rounded.
- 		self go: l; turn: 360.0 / npoints].
- 	npoints // 2
- 		to: 1
- 		by: -1
- 		do: 
- 			[:i | 
- 			self color: i.
- 			1 to: npoints do: 
- 				[:j | 
- 				self place: (points at: j).
- 				self goto: (points at: j + i - 1 \\ npoints + 1)]]
- !

Item was removed:
- ----- Method: Pen>>north (in category 'operations') -----
- north
- 	"Set the receiver's direction to facing toward the top of the display screen."
- 
- 	direction := 270!

Item was removed:
- ----- Method: Pen>>place: (in category 'operations') -----
- place: aPoint 
- 	"Set the receiver at position aPoint. No lines are drawn."
- 
- 	location := aPoint!

Item was removed:
- ----- Method: Pen>>print:withFont: (in category 'operations') -----
- print: str withFont: font
- 	"Print the given string in the given font at the current heading"
- 	| lineStart scale wasDown |
- 	scale := sourceForm width.
- 	wasDown := penDown.
- 	lineStart := location.
- 	str do:
- 		[:char |
- 		char = Character cr ifTrue:
- 			[self place: lineStart; up; turn: 90; go: font height*scale; turn: -90; down]
- 		ifFalse:
- 			[ | charStart pix rowStart form backgroundCode |
- 			form := font characterFormAt: char.
- 			backgroundCode := 1<< (form depth // 3 * 3) - 1.
- 			charStart := location.
- wasDown ifTrue: [
- 			self up; turn: -90; go: font descent*scale; turn: 90; down.
- 			0 to: form height-1 do:
- 				[:y |
- 				rowStart := location.
- 				pix := RunArray newFrom:
- 					((0 to: form width-1) collect: [:x | form pixelValueAt: x at y]).
- 				pix runs with: pix values do:
- 					[:run :value |
- 					value = backgroundCode
- 						ifTrue: [self up; go: run*scale; down]
- 						ifFalse: [self go: run*scale]].
- 				self place: rowStart; up; turn: 90; go: scale; turn: -90; down].
- ].
- 			self place: charStart; up; go: form width*scale; down].
- 			].
- 	wasDown ifFalse: [self up]
- "
- Display restoreAfter:
- [Pen new squareNib: 2; color: Color red; turn: 45;
- 	print: 'The owl and the pussycat went to sea
- in a beautiful pea green boat.' withFont: TextStyle defaultFont]
- "!

Item was removed:
- ----- Method: Pen>>roundNib: (in category 'initialize-release') -----
- roundNib: diameter
- 	"Makes this pen draw with a round dot of the given diameter."
- 
- 	self sourceForm: (Form dotOfSize: diameter).
- 	combinationRule := Form paint.
- !

Item was removed:
- ----- Method: Pen>>sourceForm: (in category 'private') -----
- sourceForm: aForm
- 	(aForm depth = 1 and: [destForm depth > 1])
- 		ifTrue: ["Map 1-bit source to all ones for color mask"
- 				colorMap := Bitmap with: 0 with: 16rFFFFFFFF]
- 		ifFalse: [colorMap := nil].
- 	^ super sourceForm: aForm!

Item was removed:
- ----- Method: Pen>>spiral:angle: (in category 'geometric designs') -----
- spiral: n angle: a 
- 	"Draw a double squiral (see Papert, MindStorms), where each design is made
- 	by moving the receiver a distance of n after turning the amount + or -a."
- 
- 	1 to: n do: 
- 		[:i | 
- 		self color: i * 2.
- 		self go: i; turn: a]
- "
- 	Display restoreAfter: [
- 		Display fillWhite. Pen new spiral: 200 angle: 89; home; spiral: 200 angle: -89].
- "!

Item was removed:
- ----- Method: Pen>>squareNib: (in category 'initialize-release') -----
- squareNib: widthInteger 
- 	"Makes this pen draw with a square nib of the given width."
- 
- 	self sourceForm: (Form extent: widthInteger @widthInteger) fillBlack.
- 	self combinationRule: Form over.  "a bit faster than paint mode"
- !

Item was removed:
- ----- Method: Pen>>turn: (in category 'operations') -----
- turn: degrees 
- 	"Change the direction that the receiver faces by an amount equal to the 
- 	argument, degrees."
- 
- 	direction := direction + degrees!

Item was removed:
- ----- Method: Pen>>up (in category 'operations') -----
- up
- 	"Set the state of the receiver's pen to up (no drawing)."
- 
- 	penDown := false!

Item was removed:
- ----- Method: Pen>>web (in category 'geometric designs') -----
- web   "Display restoreAfter: [Pen new web]"
- 	"Draw pretty web-like patterns from the mouse movement on the screen.
- 	Press the mouse button to draw, option-click to exit.
- 	By Dan Ingalls and Mark Lentczner. "
- 	| history newPoint ancientPoint lastPoint filter color |
- 	"self erase."
- 	color := 1.
- 	[ history := OrderedCollection new.
- 	Sensor waitButton.
- 	Sensor yellowButtonPressed ifTrue: [^ self].
- 	filter := lastPoint := Sensor cursorPoint.
- 	20 timesRepeat: [ history addLast: lastPoint ].
- 	self color: (color := color + 1).
- 	[ Sensor redButtonPressed ] whileTrue: 
- 		[ newPoint := Sensor cursorPoint.
- 		(newPoint = lastPoint) ifFalse:
- 			[ ancientPoint := history removeFirst.
- 			filter := filter * 4 + newPoint // 5.
- 			self place: filter.
- 			self goto: ancientPoint.
- 			lastPoint := newPoint.
- 			history addLast: filter ] ] ] repeat!

Item was removed:
- Pen subclass: #PenPointRecorder
- 	instanceVariableNames: 'points'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Primitives'!
- 
- !PenPointRecorder commentStamp: 'nice 3/24/2010 07:38' prior: 0!
- This class is a special kind of Pen that instead of actually drawing lines records the destination points for those lines. These points can later be accessed through my accessing method #points.
- 
- This can be useful when determining the boundaries of a drawing session.
- 
- Example:
- 
- | pen |
- pen := PenPointRecorder new.
- pen up; goto: 100 at 100; down; goto: 120 at 120.
- Transcript cr;
- 	show: 'Bounding box for drawing: ';
- 	show: (Rectangle encompassing: pen points)
- 
- Implementation note: Shouldn't we override #drawFrom:to:withFirstPoint: instead, and what about #drawLoopX:Y:? Aren't we missing those calls?!

Item was removed:
- ----- Method: PenPointRecorder>>drawFrom:to: (in category 'line drawing') -----
- drawFrom: p1 to: p2
- 	"Overridden to skip drawing but track bounds of the region traversed."
- 
- 	points ifNil: [points := OrderedCollection with: p1].
- 	points addLast: p2!

Item was removed:
- ----- Method: PenPointRecorder>>points (in category 'accessing') -----
- points
- 	^ points!

Item was removed:
- Object subclass: #Point
- 	instanceVariableNames: 'x y'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Primitives'!
- 
- !Point commentStamp: '<historical>' prior: 0!
- I represent an x-y pair of numbers usually designating a location on the screen.!

Item was removed:
- ----- Method: Point class>>fromUser (in category 'instance creation') -----
- fromUser
- 	Sensor waitNoButton.
- 	Cursor crossHair show.
- 	Sensor waitButton.
- 	Cursor normal show.
- 	^ Sensor cursorPoint
- 
- "Point fromUser"!

Item was removed:
- ----- Method: Point class>>fromUserWithCursor: (in category 'instance creation') -----
- fromUserWithCursor: aCursor
- 	Sensor waitNoButton.
- 	aCursor showWhile:[Sensor waitButton].
- 	^ Sensor cursorPoint
- 
- "Point fromUserWithCursor: Cursor target"!

Item was removed:
- ----- Method: Point class>>r:degrees: (in category 'instance creation') -----
- r: rho degrees: degrees
- 	"Answer an instance of me with polar coordinates rho and theta."
- 
- 	^self basicNew setR: rho degrees: degrees!

Item was removed:
- ----- Method: Point class>>u:v: (in category 'instance creation') -----
- u: xInteger v: yInteger 
- 	"Answer an instance of me with coordinates xInteger and yInteger."
- 
- 	^self new setX: xInteger setY: yInteger!

Item was removed:
- ----- Method: Point class>>x:y: (in category 'instance creation') -----
- x: xInteger y: yInteger 
- 	"Answer an instance of me with coordinates xInteger and yInteger."
- 
- 	^self basicNew setX: xInteger setY: yInteger!

Item was removed:
- ----- Method: Point>>* (in category 'arithmetic') -----
- * arg 
- 	"Answer a Point that is the product of the receiver and arg."
- 
- 	arg isPoint ifTrue: [^ (x * arg x) @ (y * arg y)].
- 	^ arg adaptToPoint: self andSend: #*!

Item was removed:
- ----- Method: Point>>+ (in category 'arithmetic') -----
- + arg 
- 	"Answer a Point that is the sum of the receiver and arg."
- 
- 	arg isPoint ifTrue: [^ (x + arg x) @ (y + arg y)].
- 	^ arg adaptToPoint: self andSend: #+!

Item was removed:
- ----- Method: Point>>- (in category 'arithmetic') -----
- - arg 
- 	"Answer a Point that is the difference of the receiver and arg."
- 
- 	arg isPoint ifTrue: [^ (x - arg x) @ (y - arg y)].
- 	^ arg adaptToPoint: self andSend: #-!

Item was removed:
- ----- Method: Point>>/ (in category 'arithmetic') -----
- / arg 
- 	"Answer a Point that is the quotient of the receiver and arg."
- 
- 	arg isPoint ifTrue: [^ (x / arg x) @ (y / arg y)].
- 	^ arg adaptToPoint: self andSend: #/!

Item was removed:
- ----- Method: Point>>// (in category 'arithmetic') -----
- // arg 
- 	"Answer a Point that is the quotient of the receiver and arg."
- 
- 	arg isPoint ifTrue: [^ (x // arg x) @ (y // arg y)].
- 	^ arg adaptToPoint: self andSend: #//!

Item was removed:
- ----- Method: Point>>< (in category 'comparing') -----
- < aPoint 
- 	"Answer whether the receiver is above and to the left of aPoint."
- 
- 	^x < aPoint x and: [y < aPoint y]!

Item was removed:
- ----- Method: Point>><= (in category 'comparing') -----
- <= aPoint 
- 	"Answer whether the receiver is neither below nor to the right of aPoint."
- 
- 	^x <= aPoint x and: [y <= aPoint y]!

Item was removed:
- ----- Method: Point>>= (in category 'comparing') -----
- = aPoint
- 
- 	self species = aPoint species
- 		ifTrue: [^x = aPoint 
- 	"Refer to the comment in Object|=." x and: [y = aPoint y]]
- 		ifFalse: [^false]!

Item was removed:
- ----- Method: Point>>> (in category 'comparing') -----
- > aPoint 
- 	"Answer whether the receiver is below and to the right of aPoint."
- 
- 	^x > aPoint x and: [y > aPoint y]!

Item was removed:
- ----- Method: Point>>>= (in category 'comparing') -----
- >= aPoint 
- 	"Answer whether the receiver is neither above nor to the left of aPoint."
- 
- 	^x >= aPoint x and: [y >= aPoint y]!

Item was removed:
- ----- Method: Point>>\\ (in category 'arithmetic') -----
- \\ arg 
- 	"Answer a Point that is the mod of the receiver and arg."
- 
- 	arg isPoint ifTrue: [^ (x \\ arg x) @ (y \\ arg y)].
- 	^ arg adaptToPoint: self andSend: #\\!

Item was removed:
- ----- Method: Point>>abs (in category 'arithmetic') -----
- abs
- 	"Answer a Point whose x and y are the absolute values of the receiver's x 
- 	and y."
- 
- 	^ x abs @ y abs!

Item was removed:
- ----- Method: Point>>adaptToCollection:andSend: (in category 'converting') -----
- adaptToCollection: rcvr andSend: selector
- 	"If I am involved in arithmetic with a Collection, return a Collection of
- 	the results of each element combined with me in that expression."
- 
- 	^ rcvr collect: [:element | element perform: selector with: self]!

Item was removed:
- ----- Method: Point>>adaptToNumber:andSend: (in category 'converting') -----
- adaptToNumber: rcvr andSend: selector
- 	"If I am involved in arithmetic with an Integer, convert it to a Point."
- 	^ rcvr at rcvr perform: selector with: self!

Item was removed:
- ----- Method: Point>>adaptToString:andSend: (in category 'converting') -----
- adaptToString: rcvr andSend: selector
- 	"If I am involved in arithmetic with a String, convert it to a Number."
- 	^ rcvr asNumber perform: selector with: self!

Item was removed:
- ----- Method: Point>>adhereTo: (in category 'transforming') -----
- adhereTo: aRectangle
- 	"If the receiver lies outside aRectangle, return the nearest point on the boundary of the rectangle, otherwise return self."
- 
- 	(aRectangle containsPoint: self) ifTrue: [^ self].
- 	^ ((x max: aRectangle left) min: aRectangle right)
- 		@ ((y max: aRectangle top) min: aRectangle bottom)!

Item was removed:
- ----- Method: Point>>area (in category 'point functions') -----
- area
- 	^ x * y!

Item was removed:
- ----- Method: Point>>asFloatPoint (in category 'converting') -----
- asFloatPoint
- 	^ x asFloat @ y asFloat!

Item was removed:
- ----- Method: Point>>asIntegerPoint (in category 'converting') -----
- asIntegerPoint
- 	^ x asInteger @ y asInteger!

Item was removed:
- ----- Method: Point>>asNonFractionalPoint (in category 'converting') -----
- asNonFractionalPoint
- (x isFraction or: [y isFraction])
- 	ifTrue:[^ x asFloat @ y asFloat]!

Item was removed:
- ----- Method: Point>>asPoint (in category 'converting') -----
- asPoint
- 	"Answer the receiver itself."
- 
- 	^self!

Item was removed:
- ----- Method: Point>>bearingToPoint: (in category 'point functions') -----
- bearingToPoint: anotherPoint
-     "Return the bearing, in degrees, from the receiver to anotherPoint.
-      Adapted from Playground, where the ultimate provenance of the algorithm was a wild earlier method of Jay Fenton's which I never checked carefully, but the thing has always seemed to work"
- 
-     | deltaX deltaY  |
-     deltaX := anotherPoint x -  x.
-     deltaY := anotherPoint y - y.
- 
-     deltaX abs < 0.001
-         ifTrue:
-             [^ deltaY > 0 ifTrue: [180] ifFalse: [0]].
- 
-     ^ ((deltaX >= 0 ifTrue: [90] ifFalse: [270])
-             - ((deltaY / deltaX) arcTan negated radiansToDegrees)) rounded
- !

Item was removed:
- ----- Method: Point>>bitShiftPoint: (in category 'private') -----
- bitShiftPoint: bits
- 	x := x bitShift: bits.
- 	y := y bitShift: bits.!

Item was removed:
- ----- Method: Point>>ceiling (in category 'truncation and round off') -----
- ceiling
- 	"Answer a Point that is the receiver's x and y ceiling. Answer the receiver if its coordinates are already integral."
- 
- 	(x isInteger and: [y isInteger]) ifTrue: [^ self].
- 	^ x ceiling @ y ceiling
- !

Item was removed:
- ----- Method: Point>>center: (in category 'converting to rectangle') -----
- center: aPoint 
- 	"Answer a Rectangle whose extent is the receiver and whose center is 
- 	aPoint. This is one of the infix ways of expressing the creation of a 
- 	rectangle."
- 
- 	^Rectangle center: aPoint extent: self!

Item was removed:
- ----- Method: Point>>closeTo: (in category 'comparing') -----
- closeTo: aPoint
- 	^(x closeTo: aPoint x) and: [y closeTo: aPoint y]!

Item was removed:
- ----- Method: Point>>corner: (in category 'converting to rectangle') -----
- corner: aPoint 
- 	"Answer a Rectangle whose origin is the receiver and whose corner is 
- 	aPoint. This is one of the infix ways of expressing the creation of a 
- 	rectangle."
- 
- 	^Rectangle origin: self corner: aPoint!

Item was removed:
- ----- Method: Point>>crossProduct: (in category 'point functions') -----
- crossProduct: aPoint 
- 	"Answer a number that is the cross product of the receiver and the 
- 	argument, aPoint."
- 
- 	^ (x * aPoint y) - (y * aPoint x)!

Item was removed:
- ----- Method: Point>>deepCopy (in category 'copying') -----
- deepCopy
- 	"Implemented here for better performance."
- 
- 	^x deepCopy @ y deepCopy!

Item was removed:
- ----- Method: Point>>degrees (in category 'polar coordinates') -----
- degrees
- 	"Answer the angle the receiver makes with origin in degrees. right is 0; down is 90."
- 	| tan theta |
- 	x = 0
- 		ifTrue: [y >= 0
- 				ifTrue: [^ 90.0]
- 				ifFalse: [^ 270.0]]
- 		ifFalse: 
- 			[tan := y asFloat / x asFloat.
- 			theta := tan arcTan.
- 			x >= 0
- 				ifTrue: [y >= 0
- 						ifTrue: [^ theta radiansToDegrees]
- 						ifFalse: [^ 360.0 + theta radiansToDegrees]]
- 				ifFalse: [^ 180.0 + theta radiansToDegrees]]!

Item was removed:
- ----- Method: Point>>dist: (in category 'point functions') -----
- dist: aPoint 
- 	"Answer the distance between aPoint and the receiver."
- 
- 	| dx dy |
- 
- 	dx := aPoint x - x.
- 	dy := aPoint y - y.
- 
- 	^ ((dx * dx) + (dy * dy)) sqrt!

Item was removed:
- ----- Method: Point>>dotProduct: (in category 'point functions') -----
- dotProduct: aPoint 
- 	"Answer a number that is the dot product of the receiver and the 
- 	argument, aPoint. That is, the two points are multipled and the 
- 	coordinates of the result summed."
- 
- 	^ (x * aPoint x) + (y * aPoint y)!

Item was removed:
- ----- Method: Point>>eightNeighbors (in category 'point functions') -----
- eightNeighbors
- 	^ (Array with: self + (1 @ 0)
- 		with: self + (1 @ 1)
- 		with: self + (0 @ 1)
- 		with: self + (-1 @ 1)) ,
- 	(Array with: self + (-1 @ 0)
- 		with: self + (-1 @ -1)
- 		with: self + (0 @ -1)
- 		with: self + (1 @ -1))
- !

Item was removed:
- ----- Method: Point>>exactCenter: (in category 'converting to rectangle') -----
- exactCenter: aPoint 
- 	"Answer a Rectangle whose extent is the receiver and whose center is exactly aPoint. This is one of the infix ways of expressing the creation of a rectangle."
- 
- 	^ Rectangle exactCenter: aPoint extent: self!

Item was removed:
- ----- Method: Point>>extent: (in category 'converting to rectangle') -----
- extent: aPoint 
- 	"Answer a Rectangle whose origin is the receiver and whose extent is 
- 	aPoint. This is one of the infix ways of expressing the creation of a 
- 	rectangle."
- 
- 	^Rectangle origin: self extent: aPoint!

Item was removed:
- ----- Method: Point>>flipBy:centerAt: (in category 'point functions') -----
- flipBy: direction centerAt: c
- 	"Answer a Point which is flipped according to the direction about the point c.
- 	Direction must be #vertical or #horizontal."
- 	direction == #vertical ifTrue: [^ x @ (c y * 2 - y)].
- 	direction == #horizontal ifTrue: [^ (c x * 2 - x) @ y].
- 	self error: 'unrecognizable direction'!

Item was removed:
- ----- Method: Point>>floor (in category 'truncation and round off') -----
- floor
- 	"Answer a Point that is the receiver's x and y floor. Answer the receiver if its coordinates are already integral."
- 
- 	(x isInteger and: [y isInteger]) ifTrue: [^ self].
- 	^ x floor @ y floor
- !

Item was removed:
- ----- Method: Point>>fourDirections (in category 'point functions') -----
- fourDirections
- 	"Return vertices for a square centered at 0 asPoint with the receiver as first corner.
- 	Returns the four rotation of the reciever in counter clockwise order with the reciever 	appearing last. "
- 	^ Array with: self leftRotated
- 			with: self negated
- 			with: self rightRotated
- 			with: self 
- 		
- !

Item was removed:
- ----- Method: Point>>fourNeighbors (in category 'point functions') -----
- fourNeighbors
- 	^ Array with: self + (1 @ 0)
- 		with: self + (0 @ 1)
- 		with: self + (-1 @ 0)
- 		with: self + (0 @ -1)
- !

Item was removed:
- ----- Method: Point>>grid: (in category 'point functions') -----
- grid: aPoint 
- 	"Answer a Point to the nearest rounded grid modules specified by aPoint."
- 
- 	| newX newY |
- 	newX := x + (aPoint x // 2) truncateTo: aPoint x.
- 	newY := y + (aPoint y // 2) truncateTo: aPoint y.
- 	^newX @ newY!

Item was removed:
- ----- Method: Point>>guarded (in category 'extent functions') -----
- guarded
- 	"Return a positive nonzero extent."
- 	^ self max: 1 at 1!

Item was removed:
- ----- Method: Point>>hash (in category 'comparing') -----
- hash
- 	"Hash is reimplemented because = is implemented."
- 
- 	^(x hash hashMultiply + y hash) hashMultiply!

Item was removed:
- ----- Method: Point>>insideTriangle:with:with: (in category 'point functions') -----
- insideTriangle: p1 with: p2 with: p3
- 	"Return true if the receiver is within the triangle defined by the three coordinates.
- 	Note: This method computes the barycentric coordinates for the receiver and tests those coordinates."
- 	| p0 b0 b1 b2 b3 |
- 	p0 := self.
- 	b0 := ((p2 x - p1 x) * (p3 y - p1 y)) - ((p3 x - p1 x) * (p2 y - p1 y)).
- 	b0 isZero ifTrue:[^false]. "degenerate"
- 	b0 := 1.0 / b0.
- 	b1 := (((p2 x - p0 x) * (p3 y - p0 y)) - ((p3 x - p0 x) * (p2 y - p0 y))) * b0.
- 	b2 := (((p3 x - p0 x) * (p1 y - p0 y)) - ((p1 x - p0 x) * (p3 y - p0 y))) * b0.
- 	b3 := (((p1 x - p0 x) * (p2 y - p0 y)) - ((p2 x - p0 x) * (p1 y - p0 y))) * b0.
- 	b1 < 0.0 ifTrue:[^false].
- 	b2 < 0.0 ifTrue:[^false].
- 	b3 < 0.0 ifTrue:[^false].
- 	^true
- 
- !

Item was removed:
- ----- Method: Point>>interpolateTo:at: (in category 'interpolating') -----
- interpolateTo: end at: amountDone
- 	"Interpolate between the instance and end after the specified amount has been done (0 - 1)."
- 
- 	^ self + ((end - self) * amountDone).!

Item was removed:
- ----- Method: Point>>isInsideCircle:with:with: (in category 'geometry') -----
- isInsideCircle: a with: b with: c 
- 	"Returns TRUE if self is inside the circle defined by the     
- 	points a, b, c. See Guibas and Stolfi (1985) p.107"
- 	^ (a dotProduct: a)
- 		* (b triangleArea: c with: self) - ((b dotProduct: b)
- 			* (a triangleArea: c with: self)) + ((c dotProduct: c)
- 			* (a triangleArea: b with: self)) - ((self dotProduct: self)
- 			* (a triangleArea: b with: c)) > 0.0!

Item was removed:
- ----- Method: Point>>isIntegerPoint (in category 'testing') -----
- isIntegerPoint
- ^ x isInteger and: [ y isInteger ] !

Item was removed:
- ----- Method: Point>>isPoint (in category 'testing') -----
- isPoint
- 	^ true!

Item was removed:
- ----- Method: Point>>isZero (in category 'testing') -----
- isZero
- 	^x isZero and:[y isZero]!

Item was removed:
- ----- Method: Point>>leftRotated (in category 'point functions') -----
- leftRotated
- "Return the reciever rotated 90 degrees.
- i.e. self rotateBy: #left centerAt: 0 asPoint .
- Compare to transposed and normal. "
- 	^y  @x negated!

Item was removed:
- ----- Method: Point>>max: (in category 'comparing') -----
- max: aPoint 
- 	"Answer the lower right corner of the rectangle uniquely defined by the 
- 	receiver and the argument, aPoint."
- 
- 	^ (x max: aPoint x) @ (y max: aPoint y)!

Item was removed:
- ----- Method: Point>>min: (in category 'comparing') -----
- min: aPoint 
- 	"Answer the upper left corner of the rectangle uniquely defined by the 
- 	receiver and the argument, aPoint."
- 
- 	^ (x min: aPoint x) @ (y min: aPoint y)!

Item was removed:
- ----- Method: Point>>min:max: (in category 'comparing') -----
- min: aMin max: aMax 
- 
- 	^ (self min: aMin) max: aMax!

Item was removed:
- ----- Method: Point>>nearestPointAlongLineFrom:to: (in category 'point functions') -----
- nearestPointAlongLineFrom: p1 to: p2
- 	"Note this will give points beyond the endpoints.
- 	Streamlined by Gerardo Richarte 11/3/97"
- 	| x21 y21 t x1 y1 |
- 	p1 x = p2 x ifTrue: [^ p1 x @ y].
- 	p1 y = p2 y ifTrue: [^ x @ p1 y].
- 	x1 := p1 x asFloat.
- 	y1 := p1 y asFloat.
- 	x21 := p2 x asFloat - x1.
- 	y21 := p2 y asFloat - y1.
- 	t := ((y asFloat - y1 / x21) + (x asFloat - x1 / y21))
- 			/ ((x21 / y21) + (y21 / x21)).
- 	^ (x1 + (t * x21)) @ (y1 + (t * y21))
- "
- 	| old new |
- 	Pen new place: 200 at 100; goto: (old := 500 at 300).
- 	Display reverse: (old extent: 10 at 10).
- 	[Sensor anyButtonPressed] whileFalse:
- 		[(new := (Sensor cursorPoint nearestPointAlongLineFrom: 200 at 100 to: 500 at 300) )
- 			= old ifFalse:
- 				[Display reverse: (old extent: 10 at 10).
- 				Display reverse: ((old := new) extent: 10 at 10)]]
- "
- !

Item was removed:
- ----- Method: Point>>nearestPointOnLineFrom:to: (in category 'point functions') -----
- nearestPointOnLineFrom: p1 to: p2
- 	"This will not give points beyond the endpoints"
- 	^ (self nearestPointAlongLineFrom: p1 to: p2)
- 		adhereTo: (p1 rect: p2)!

Item was removed:
- ----- Method: Point>>negated (in category 'transforming') -----
- negated
- 	"Answer a point whose x and y coordinates are the negatives of those of the receiver.  6/6/96 sw"
- 	"Optimized for speed -- ar 8/26/2001"
- 	^ (0 - x) @ (0 - y)!

Item was removed:
- ----- Method: Point>>normal (in category 'point functions') -----
- normal
- 	"Answer a Point representing the unit vector rotated 90 deg clockwise.
- 	For the zero point return a normal of  -1 at 0   ."
- 
- 	| n d |
- 	
- 	n := y negated @ x.
- 	(d := (n x * n x + (n y * n y))) = 0 ifTrue: [ ^  -1 @0  ] .
- 	^n / d sqrt!

Item was removed:
- ----- Method: Point>>normalized (in category 'point functions') -----
- normalized
- 	"Optimized for speed -- ar 8/26/2001"
- 	| r |
- 	r := ((x*x) + (y * y)) sqrt.
- 	^(x / r) @ (y / r)!

Item was removed:
- ----- Method: Point>>octantOf: (in category 'point functions') -----
- octantOf: otherPoint 
- 	"Return 1..8 indicating relative direction to otherPoint.  
- 	1=ESE, 2=SSE, ... etc. clockwise to 8=ENE"
- 	"[Sensor anyButtonPressed] whileFalse: [(Display boundingBox center 
- 	octantOf: Sensor cursorPoint) printString displayAt: 0 at 0]"
- 	| quad moreHoriz |
- 	(x = otherPoint x and: [y > otherPoint y])
- 		ifTrue: [^ 6].
- 	"special case"
- 	(y = otherPoint y and: [x < otherPoint x])
- 		ifTrue: [^ 8].
- 	quad := self quadrantOf: otherPoint.
- 	moreHoriz := (x - otherPoint x) abs >= (y - otherPoint y) abs.
- 	(quad even eqv: moreHoriz)
- 		ifTrue: [^ quad * 2]
- 		ifFalse: [^ quad * 2 - 1]!

Item was removed:
- ----- Method: Point>>onLineFrom:to: (in category 'point functions') -----
- onLineFrom: p1 to: p2
- 	^ self onLineFrom: p1 to: p2 within: 2!

Item was removed:
- ----- Method: Point>>onLineFrom:to:within: (in category 'point functions') -----
- onLineFrom: p1 to: p2 within: epsilon
- 	"Answer true if the receiver lies on the given line segment between p1 and p2 within a small epsilon."
- 
- 	"is this point within the box spanning p1 and p2 expanded by epsilon? (optimized)"
- 	p1 x < p2 x
- 		ifTrue: [
- 			((x < (p1 x - epsilon)) or: [x > (p2 x + epsilon)]) ifTrue: [^ false]]
- 		ifFalse: [
- 			((x < (p2 x - epsilon)) or: [x > (p1 x + epsilon)]) ifTrue: [^ false]].
- 	p1 y < p2 y
- 		ifTrue: [
- 			((y < (p1 y - epsilon)) or: [y > (p2 y + epsilon)]) ifTrue: [^ false]]
- 		ifFalse: [
- 			((y < (p2 y - epsilon)) or: [y > (p1 y + epsilon)]) ifTrue: [^ false]].
- 
- 	"it's in the box; is it on the line?"
- 	^ (self dist: (self nearestPointAlongLineFrom: p1 to: p2)) <= epsilon!

Item was removed:
- ----- Method: Point>>origin: (in category 'converting to rectangle') -----
- origin: aPoint 
- 	"Answer a Rectangle whose extent is the receiver and whose origin is 
- 	aPoint. This is one of the infix ways of expressing the creation of a 
- 	rectangle."
- 
- 	^Rectangle origin: aPoint extent: self!

Item was removed:
- ----- Method: Point>>printOn: (in category 'printing') -----
- printOn: aStream 
- 	"The receiver prints on aStream in terms of infix notation."
- 
- 	x printOn: aStream.
- 	aStream nextPut: $@.
- 	(y isNumber and: [y negative]) ifTrue:
- 		"Avoid ambiguous @- construct"
- 		[aStream space].
- 	y printOn: aStream!

Item was removed:
- ----- Method: Point>>quadrantOf: (in category 'point functions') -----
- quadrantOf: otherPoint
- 	"Return 1..4 indicating relative direction to otherPoint.
- 	1 is downRight, 2=downLeft, 3=upLeft, 4=upRight"
- 	^ x <= otherPoint x
- 		ifTrue: [y < otherPoint y ifTrue: [1] ifFalse: [4]]
- 		ifFalse: [y <= otherPoint y ifTrue: [2] ifFalse: [3]]
- "
- [Sensor anyButtonPressed] whileFalse:
- 	[(Display boundingBox center quadrantOf: Sensor cursorPoint) printString displayAt: 0 at 0]
- "!

Item was removed:
- ----- Method: Point>>r (in category 'polar coordinates') -----
- r
- 	"Answer the receiver's radius in polar coordinate system."
- 
- 	^(self dotProduct: self) sqrt!

Item was removed:
- ----- Method: Point>>reciprocal (in category 'arithmetic') -----
- reciprocal
-     " Answer a Point with coordinates that are the reciprocals of mine. "
-     " Method was missing from release. "
-     " 20040301 20:50:35 TRee(Squeak3.6-5429-tree07.38) "
- 
-     ^ x reciprocal @ y reciprocal.
- !

Item was removed:
- ----- Method: Point>>rect: (in category 'converting to rectangle') -----
- rect: aPoint 
- 	"Answer a Rectangle that encompasses the receiver and aPoint.
- 	This is the most general infix way to create a rectangle."
- 
- 	^ Rectangle 
- 		origin: (self min: aPoint)
- 		corner: (self max: aPoint)!

Item was removed:
- ----- Method: Point>>rightRotated (in category 'point functions') -----
- rightRotated
- "Return the reciever rotated 90 degrees.
- i.e. self rotateBy: #right centerAt: 0 asPoint .
- Compare to transposed and normal. "
- 	^y negated @x!

Item was removed:
- ----- Method: Point>>rotateBy:about: (in category 'transforming') -----
- rotateBy: angle about: center
- 	"Even though Point.theta is measured CW, this rotates with the more conventional CCW interpretateion of angle."
- 
- 	| p r theta |
- 	p := self - center.
- 	r := p r.
- 	theta := angle asFloat - p theta.
- 	^ (center x asFloat + (r * theta cos)) @
- 	  (center y asFloat - (r * theta sin))!

Item was removed:
- ----- Method: Point>>rotateBy:centerAt: (in category 'point functions') -----
- rotateBy: direction centerAt: c
- 	"Answer a Point which is rotated according to direction, about the point c.
- 	Direction must be one of #right (CW), #left (CCW) or #pi (180 degrees)."
- 	| offset |
- 	offset := self - c.
- 	direction == #right ifTrue: [^ (offset y negated @ offset x) + c].
- 	direction == #left ifTrue: [^ (offset y @ offset x negated) + c].
- 	direction == #pi ifTrue: [^ c - offset].
- 	self error: 'unrecognizable direction'!

Item was removed:
- ----- Method: Point>>roundDownTo: (in category 'truncation and round off') -----
- roundDownTo: grid
- 	"Answer a Point that is the receiver's x and y rounded to grid x and 
- 	grid y by lower value (toward negative infinity)."
- 	
- 	| gridPoint |
- 	gridPoint := grid asPoint.
- 	^(x roundDownTo: gridPoint x) @ (y roundDownTo: gridPoint y)!

Item was removed:
- ----- Method: Point>>roundTo: (in category 'truncation and round off') -----
- roundTo: grid
- 	"Answer a Point that is the receiver's x and y rounded to grid x and 
- 	grid y."
- 	
- 	| gridPoint |
- 	gridPoint := grid asPoint.
- 	^(x roundTo: gridPoint x) @ (y roundTo: gridPoint y)!

Item was removed:
- ----- Method: Point>>roundUpTo: (in category 'truncation and round off') -----
- roundUpTo: grid
- 	"Answer a Point that is the receiver's x and y rounded to grid x and 
- 	grid y by upper value (toward infinity)."
- 	
- 	| gridPoint |
- 	gridPoint := grid asPoint.
- 	^(x roundUpTo: gridPoint x) @ (y roundUpTo: gridPoint y)!

Item was removed:
- ----- Method: Point>>rounded (in category 'truncation and round off') -----
- rounded
- 	"Answer a Point that is the receiver's x and y rounded. Answer the receiver if its coordinates are already integral."
- 
- 	(x isInteger and: [y isInteger]) ifTrue: [^ self].
- 	^ x rounded @ y rounded
- !

Item was removed:
- ----- Method: Point>>scaleBy: (in category 'transforming') -----
- scaleBy: factor 
- 	"Answer a Point scaled by factor (an instance of Point)."
- 
- 	^(factor x * x) @ (factor y * y)!

Item was removed:
- ----- Method: Point>>scaleFrom:to: (in category 'transforming') -----
- scaleFrom: rect1 to: rect2
- 	"Produce a point stretched according to the stretch from rect1 to rect2"
- 	^ rect2 topLeft + (((x-rect1 left) * rect2 width // rect1 width)
- 					@ ((y-rect1 top) * rect2 height // rect1 height))!

Item was removed:
- ----- Method: Point>>scaleTo: (in category 'extent functions') -----
- scaleTo: anExtent
- 	"Return a Point scalefactor for shrinking a thumbnail of the receiver's extent to fit within anExtent. self and anExtent are expected to have positive nonZero x and y."
- 
- 	|  factor  sX sY | 
- 	factor :=  3.0  reciprocal .
- 	sX := anExtent x / self  x asFloat  .
- 	sY :=  anExtent y / self  y asFloat  .
- 	sX = sY ifTrue: [ ^ sX @ sY ] . "Same aspect ratio"
- 	^ sX < sY ifTrue: [   sX @ (sX max: sY * factor) ] 
- 		ifFalse: [  (sY max: sX * factor ) @ sY  ] !

Item was removed:
- ----- Method: Point>>setR:degrees: (in category 'private') -----
- setR: rho degrees: degrees 
- 
- 	| radians |
- 	radians := degrees asFloat degreesToRadians.
- 	x := rho asFloat * radians cos.
- 	y := rho asFloat * radians sin.!

Item was removed:
- ----- Method: Point>>setX:setY: (in category 'private') -----
- setX: xValue setY: yValue
- 
- 	x := xValue.
- 	y := yValue!

Item was removed:
- ----- Method: Point>>sideOf: (in category 'geometry') -----
- sideOf: otherPoint 
- 	"Returns #left, #right or #center if the otherPoint lies to the left, right 
- 	or on the line given by the vector from 0 at 0 to self"
- 	| side |
- 	side := (self crossProduct: otherPoint) sign.
- 	^ {#right. #center. #left} at: side + 2
- !

Item was removed:
- ----- Method: Point>>sign (in category 'point functions') -----
- sign
- 
- 
- ^ (x sign @ y sign) .!

Item was removed:
- ----- Method: Point>>sortsBefore: (in category 'point functions') -----
- sortsBefore: otherPoint
- 	"Return true if the receiver sorts before the other point"
- 	^y = otherPoint y
- 		ifTrue:[x <= otherPoint x]
- 		ifFalse:[y <= otherPoint y]!

Item was removed:
- ----- Method: Point>>squaredDistanceTo: (in category 'point functions') -----
- squaredDistanceTo: aPoint
- 	"Answer the distance between aPoint and the receiver."
- 	| delta |
- 	delta := aPoint - self.
- 	^delta dotProduct: delta!

Item was removed:
- ----- Method: Point>>storeOn: (in category 'printing') -----
- storeOn: aStream 
- 	"x at y printed form is good for storing too"
- 	aStream nextPut: $(.
- 	self printOn: aStream.
- 	aStream nextPut: $).
- !

Item was removed:
- ----- Method: Point>>theta (in category 'polar coordinates') -----
- theta
- 	"Answer the angle the receiver makes with origin in radians. right is 0; 
- 	down is 90. 
- 	Corrected the constants from single precision to 64 Bit precision 
- 	and changed the sends in case of overflow to constants HK 2005-07-23"
- 
- 	| tan theta |
- 	x = 0
- 		ifTrue: [y >= 0
- 				ifTrue: [^ 1.5707963267948966 "90.0 degreesToRadians"]
- 				ifFalse: [^ 4.71238898038469 "270.0 degreesToRadians"]]
- 		ifFalse: 
- 			[tan := y asFloat / x asFloat.
- 			theta := tan arcTan.
- 			x >= 0
- 				ifTrue: [y >= 0
- 						ifTrue: [^theta]
- 						ifFalse: [^"360.0 degreesToRadians" 6.283185307179586 + theta]]
- 				ifFalse: [^"180.0 degreesToRadians" 3.141592653589793 + theta]]!

Item was removed:
- ----- Method: Point>>to:intersects:to: (in category 'geometry') -----
- to: end1 intersects: start2 to: end2 
- 	"Returns true if the linesegment from start1 (=self) to end1 intersects      
- 	    with the segment from start2 to end2, otherwise false."
- 	| start1 sideStart sideEnd |
- 	start1 := self.
- 	(((start1 = start2 or: [end1 = end2])
- 		or: [start1 = end2])
- 		or: [start2 = end1])
- 		ifTrue: [^ true].
- 	sideStart := start1 to: end1 sideOf: start2.
- 	sideEnd := start1 to: end1 sideOf: end2.
- 	sideStart = sideEnd ifTrue: [^ false].
- 	sideStart := start2 to: end2 sideOf: start1.
- 	sideEnd := start2 to: end2 sideOf: end1.
- 	sideStart = sideEnd ifTrue: [^ false].
- 	^ true!

Item was removed:
- ----- Method: Point>>to:sideOf: (in category 'geometry') -----
- to: end sideOf: otherPoint 
- 	"Returns #left, #right, #center if the otherPoint lies to the left, right or on the line given by the vector from self to end"
- 	^ end - self sideOf: otherPoint - self!

Item was removed:
- ----- Method: Point>>transformedBy: (in category 'transforming') -----
- transformedBy: aTransform
- 	"Point transform double dispatch"
- 	^aTransform transformPoint: self!

Item was removed:
- ----- Method: Point>>translateBy: (in category 'transforming') -----
- translateBy: delta 
- 	"Answer a Point translated by delta (an instance of Point)."
- 
- 	^(delta x + x) @ (delta y + y)!

Item was removed:
- ----- Method: Point>>transposed (in category 'point functions') -----
- transposed
- 	^y at x!

Item was removed:
- ----- Method: Point>>triangleArea:with: (in category 'geometry') -----
- triangleArea: b with: c
- 	"Returns twice the area of the oriented triangle (a, b, c), i.e., the   
- 	area is positive if the triangle is oriented counterclockwise"
- 	^ b x - self x * (c y - self y) - (b y - self y * (c x - self x))!

Item was removed:
- ----- Method: Point>>truncateTo: (in category 'truncation and round off') -----
- truncateTo: grid
- 	"Answer a Point that is the receiver's x and y truncated to grid x and 
- 	grid y."
- 	| gridPoint |
- 	gridPoint := grid asPoint.
- 	^(x truncateTo: gridPoint x) @ (y truncateTo: gridPoint y)!

Item was removed:
- ----- Method: Point>>truncated (in category 'truncation and round off') -----
- truncated
- 	"Answer a Point whose x and y coordinates are integers. Answer the receiver if its coordinates are already integral."
- 
- 	(x isInteger and: [y isInteger]) ifTrue: [^ self].
- 	^ x truncated @ y truncated
- !

Item was removed:
- ----- Method: Point>>u (in category 'accessing') -----
- u
- 	^x!

Item was removed:
- ----- Method: Point>>v (in category 'accessing') -----
- v
- 	^y!

Item was removed:
- ----- Method: Point>>veryDeepCopyWith: (in category 'copying') -----
- veryDeepCopyWith: deepCopier
- 	"Return self.  I am immutable in the Morphic world.  Do not record me."!

Item was removed:
- ----- Method: Point>>x (in category 'accessing') -----
- x
- 	"Answer the x coordinate."
- 
- 	^x!

Item was removed:
- ----- Method: Point>>y (in category 'accessing') -----
- y
- 	"Answer the y coordinate."
- 
- 	^y!

Item was removed:
- ----- Method: ProcessorScheduler class>>sweepHandIdleProcess (in category '*Graphics-KernelExtensions') -----
- sweepHandIdleProcess
- 	"A default background process which shows a sweeping circle of XOR-ed bits on the screen."
- 
- 	| sweepHand |
- 	sweepHand := Pen new.
- 	sweepHand defaultNib: 2.
- 	sweepHand combinationRule: 6.
- 	[
- 		2 timesRepeat: [
- 			sweepHand north.
- 			36 timesRepeat: [
- 				sweepHand place: Display boundingBox topRight + (-25 at 25).
- 				sweepHand go: 20.
- 				sweepHand turn: 10]].
- 		self relinquishProcessorForMicroseconds: 10000] repeat
- !

Item was removed:
- Rectangle subclass: #Quadrangle
- 	instanceVariableNames: 'borderWidth borderColor insideColor'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Primitives'!
- 
- !Quadrangle commentStamp: '<historical>' prior: 0!
- I represent a particular kind of Rectangle that has a border and inside color.!

Item was removed:
- ----- Method: Quadrangle class>>exampleInViewer (in category 'instance creation') -----
- exampleInViewer
- 	"Create a sample Quadrangle and open a Viewer on it"
- 
- 	(self region: (100 at 100 extent: 100 at 50) borderWidth: (1 + (6 atRandom)) borderColor: Color black insideColor: (Color perform: #(green red blue yellow) atRandom)) beViewed
- 
- "Quadrangle exampleInViewer"!

Item was removed:
- ----- Method: Quadrangle class>>origin:corner: (in category 'instance creation') -----
- origin: originPoint corner: cornerPoint 
- 	"Override Rectangles origin:corner: in order to get initialized.
- 
- 	Answer an instance of me whose corners (top left and bottom right) are 
- 	determined by the arguments."
- 
- 	^self new setOrigin: originPoint corner: cornerPoint!

Item was removed:
- ----- Method: Quadrangle class>>region:borderWidth:borderColor:insideColor: (in category 'instance creation') -----
- region: aRectangle borderWidth: anInteger borderColor: aMask1 insideColor: aMask2
- 	"Answer an instance of me with rectangle, border width and color, and 
- 	inside color determined by the arguments."
- 
- 	^super new
- 		setRegion: aRectangle
- 		borderWidth: anInteger
- 		borderColor: aMask1
- 		insideColor: aMask2!

Item was removed:
- ----- Method: Quadrangle>>align:with: (in category 'transforming') -----
- align: aPoint1 with: aPoint2 
- 	"Answer a new Quadrangle translated by aPoint2 - aPoint1.
- 	 5/24/96 sw: removed hard-coded class name so subclasses can gain same functionality."
- 
- 	^ self class
- 		region: (super translateBy: aPoint2 - aPoint1)
- 		borderWidth: borderWidth
- 		borderColor: borderColor
- 		insideColor: insideColor!

Item was removed:
- ----- Method: Quadrangle>>alignedTo: (in category 'transforming') -----
- alignedTo: alignPointSelector
- 	"Return a copy with offset according to alignPointSelector which is one of...
- 	#(topLeft, topCenter, topRight, leftCenter, center, etc)
- 	 5/24/96 sw: removed hard-coded class name so subclasses can gain same functionality."
- 
- 	^ self class
- 		region: (super translateBy: (0 at 0) - (self perform: alignPointSelector))
- 		borderWidth: borderWidth
- 		borderColor: borderColor
- 		insideColor: insideColor!

Item was removed:
- ----- Method: Quadrangle>>borderColor (in category 'bordering') -----
- borderColor
- 	"Answer the form that is the borderColor of the receiver."
- 
- 	^borderColor!

Item was removed:
- ----- Method: Quadrangle>>borderColor: (in category 'bordering') -----
- borderColor: aColor 
- 	"Set the borderColor of the receiver to aColor, a Form."
- 
- 	borderColor := aColor!

Item was removed:
- ----- Method: Quadrangle>>borderWidth (in category 'bordering') -----
- borderWidth
- 	"Answer the borderWidth of the receiver."
- 
- 	^borderWidth!

Item was removed:
- ----- Method: Quadrangle>>borderWidth: (in category 'bordering') -----
- borderWidth: anInteger 
- 	"Set the borderWidth of the receiver to anInteger."
- 
- 	borderWidth := anInteger!

Item was removed:
- ----- Method: Quadrangle>>borderWidthLeft:right:top:bottom: (in category 'bordering') -----
- borderWidthLeft: anInteger1 right: anInteger2 top: anInteger3 bottom: anInteger4
- 	"Set the border width of the receiver to a Rectangle that represents the 
- 	left, right, top, and bottom border widths."
- 
- 	borderWidth := anInteger1 @ anInteger3 corner: anInteger2 @ anInteger4!

Item was removed:
- ----- Method: Quadrangle>>display (in category 'displaying-Display') -----
- display 
- 	"Display the border and insideRegion of the receiver on the Display."
- 
- 	self displayOn: Display!

Item was removed:
- ----- Method: Quadrangle>>displayAlign:with:clippingBox: (in category 'displaying-Display') -----
- displayAlign: aPoint1 with: aPoint2 clippingBox: aRectangle 
- 	"Display the border and region of the receiver on the Display so that its 
- 	position at aPoint1 is aligned with position aPoint2. The displayed 
- 	information should be clipped so that only information with the area 
- 	determined by aRectangle is displayed." 
- 
- 	self displayOn: Display align: aPoint1 with: aPoint2 clippingBox: aRectangle!

Item was removed:
- ----- Method: Quadrangle>>displayOn: (in category 'displaying-generic') -----
- displayOn: aDisplayMedium
- 	"Display the border and insideRegion of the receiver."
- 
- 	borderWidth ~= 0 ifTrue: [
- 		aDisplayMedium
- 			border: self region
- 			widthRectangle: borderWidth
- 			rule: Form over
- 			fillColor: borderColor ].
- 	insideColor ifNotNil: [
- 		aDisplayMedium fill: self inside fillColor: insideColor ]!

Item was removed:
- ----- Method: Quadrangle>>displayOn:align:with:clippingBox: (in category 'displaying-generic') -----
- displayOn: aDisplayMedium align: aPoint1 with: aPoint2 clippingBox: aRectangle
- 	"Display the border and region of the receiver so that its position at 
- 	aPoint1 is aligned with position aPoint2. The displayed information 
- 	should be clipped so that only information with the area determined by 
- 	aRectangle is displayed."
- 
- 	| savedRegion |
- 	savedRegion := self region.
- 	self region: ((savedRegion align: aPoint1 with: aPoint2) intersect: aRectangle).
- 	self displayOn: aDisplayMedium.
- 	self region: savedRegion!

Item was removed:
- ----- Method: Quadrangle>>displayOn:transformation:clippingBox: (in category 'displaying-generic') -----
- displayOn: aDisplayMedium transformation: aWindowingTransformation clippingBox: aRectangle
- 	"Display the border and region of the receiver so that it is scaled and 
- 	translated with respect to aWindowingTransformation. The displayed 
- 	information should be clipped so that only information with the area 
- 	determined by aRectangle is displayed."
- 
- 	| screenRectangle |
- 	screenRectangle := 
- 		(aWindowingTransformation applyTo: self) intersect: aRectangle.
- 	(borderWidth ~= 0 and: [ insideColor notNil ])
- 		ifTrue: 
- 			[aDisplayMedium fill: screenRectangle fillColor: Color black "borderColor".
- 			aDisplayMedium
- 				fill: (screenRectangle insetBy: borderWidth)
- 				fillColor: insideColor]!

Item was removed:
- ----- Method: Quadrangle>>displayOnPort:at: (in category 'displaying-generic') -----
- displayOnPort: aPort at: p
- 	"Display the border and insideRegion of the receiver."
- 
- 	(insideColor == nil or: [borderWidth <= 0])
- 		ifFalse: [aPort fill: (self region translateBy: p) 
- 			fillColor: borderColor rule: Form over].
- 	insideColor == nil
- 		ifFalse: [aPort fill: (self inside translateBy: p) 
- 			fillColor: insideColor rule: Form over]!

Item was removed:
- ----- Method: Quadrangle>>displayTransformation:clippingBox: (in category 'displaying-Display') -----
- displayTransformation: aWindowingTransformation clippingBox: aRectangle 
- 	"Display the border and region of the receiver on the Display so that it 
- 	is scaled and translated with respect to aWindowingTransformation. The 
- 	displayed information should be clipped so that only information with 
- 	the area determined by aRectangle is displayed." 
- 
- 	self displayOn: Display transformation: aWindowingTransformation clippingBox: aRectangle!

Item was removed:
- ----- Method: Quadrangle>>initialize (in category 'initialize-release') -----
- initialize
- 	"Initialize the region to a null Rectangle, the borderWidth to 1, the 
- 	borderColor to black, and the insideColor to white."
- 
- 	origin := 0 @ 0.
- 	corner := 0 @ 0.
- 	borderWidth := 1.
- 	borderColor := Color black.
- 	insideColor := Color white.
- !

Item was removed:
- ----- Method: Quadrangle>>inside (in category 'bordering') -----
- inside
- 	"Answer a Rectangle that is the receiver inset by the borderWidth."
- 
- 	^self insetBy: borderWidth!

Item was removed:
- ----- Method: Quadrangle>>insideColor (in category 'bordering') -----
- insideColor
- 	"Answer the form that is the insideColor of the receiver."
- 
- 	^insideColor!

Item was removed:
- ----- Method: Quadrangle>>insideColor: (in category 'bordering') -----
- insideColor: aColor 
- 	"Set the insideColor of the receiver to aColor, a Form."
- 
- 	insideColor := aColor!

Item was removed:
- ----- Method: Quadrangle>>intersect: (in category 'rectangle functions') -----
- intersect: aRectangle 
- 	"Answer a new Quadrangle whose region is the intersection of the 
- 	receiver's area and aRectangle.
- 	 5/24/96 sw: removed hard-coded class name so subclasses can gain same functionality."
- 
- 	^ self class
- 	 	region: (super intersect: aRectangle)
- 		borderWidth: borderWidth
- 		borderColor: borderColor
- 		insideColor: insideColor!

Item was removed:
- ----- Method: Quadrangle>>region (in category 'bordering') -----
- region
- 	"Answer a Rectangle that defines the area of the receiver."
- 
- 	^origin corner: corner!

Item was removed:
- ----- Method: Quadrangle>>region: (in category 'bordering') -----
- region: aRectangle 
- 	"Set the rectangular area of the receiver to aRectangle."
- 
- 	origin := aRectangle origin.
- 	corner := aRectangle corner!

Item was removed:
- ----- Method: Quadrangle>>scaleBy: (in category 'transforming') -----
- scaleBy: aPoint 
- 	"Answer a new Quadrangle scaled by aPoint.
- 	 5/24/96 sw: removed hard-coded class name so subclasses can gain same functionality."
- 
- 	^ self class
- 		region: (super scaleBy: aPoint)
- 		borderWidth: borderWidth
- 		borderColor: borderColor
- 		insideColor: insideColor!

Item was removed:
- ----- Method: Quadrangle>>setHeight: (in category 'bordering') -----
- setHeight: aNumber 
- 	"Set the receiver's height"
- 
- 	self region: (origin extent: (self width @ aNumber))!

Item was removed:
- ----- Method: Quadrangle>>setLeft: (in category 'bordering') -----
- setLeft: aNumber 
- 	"Move the receiver so that its left edge is given by aNumber.  An example of a setter to go with #left"
- 
- 	self region: ((aNumber @ origin y) extent: self extent)!

Item was removed:
- ----- Method: Quadrangle>>setRegion:borderWidth:borderColor:insideColor: (in category 'private') -----
- setRegion: aRectangle borderWidth: anInteger borderColor: aMask1 insideColor: aMask2
- 
- 	origin := aRectangle origin.
- 	corner := aRectangle corner.
- 	borderWidth := anInteger.
- 	borderColor := aMask1.
- 	insideColor := aMask2!

Item was removed:
- ----- Method: Quadrangle>>setRight: (in category 'bordering') -----
- setRight: aNumber 
- 	"Move the receiver so that its right edge is given by aNumber.  An example of a setter to go with #right"
- 
- 	self region: ((origin x + (aNumber - self right) @ origin y) extent: self extent)!

Item was removed:
- ----- Method: Quadrangle>>setWidth: (in category 'bordering') -----
- setWidth: aNumber 
- 	"Set the receiver's width"
- 
- 	self region: (origin extent: (aNumber @ self height))!

Item was removed:
- ----- Method: Quadrangle>>translateBy: (in category 'transforming') -----
- translateBy: aPoint 
- 	"Answer a new Quadrangle translated by aPoint.
- 	 5/24/96 sw: removed hard-coded class name so subclasses can gain same functionality."
- 
- 	^ self class
- 		region: (super translateBy: aPoint)
- 		borderWidth: borderWidth
- 		borderColor: borderColor
- 		insideColor: insideColor!

Item was removed:
- Object subclass: #Rectangle
- 	instanceVariableNames: 'origin corner'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Primitives'!
- 
- !Rectangle commentStamp: 'nice 7/25/2010 14:56' prior: 0!
- I represent a rectangular area of the screen. Arithmetic functions take points as arguments and carry out scaling and translating operations to create new instances of me. Rectangle functions create new instances by determining intersections of rectangles with rectangles.
- 
- Note 1: only rectangles parallel to reference frame (Screen) can be represented by this class.
- 
- Note 2: the Rectangle is represented by two extremities of one diagonal. By convention, it must be the diagonal:
- 	from rectangle origin (the point having smallest coordinates in reference frame),
- 	to rectangle corner (the point having largest coordinates in reference frame).
- 
- Note 3: Screen coordinates conventions are:
- 	x is horizontal axis, zero at left border, oriented toward right;
- 	y is vertical axis, zero at top border, oriented toward bottom.
- This corresponds to the latin convention for writing text from left to right and top to bottom.
- 
- Note 4: the Rectangle extent is obtained by subtracting rectangle origin to rectangle corner coordinates.
- If this leads to a negative width (extent x coordinate) and/or a negative height (extent y coordinate), then the Rectangle is degenerated and considered empty.
- 
- Instance variables:
- 	origin	<Point> the coordinates of corner having smallest coordinates (top left in Screen coordinates)
- 	corner	<Point> the coordinates of corner having largest coordinates (bottom right in Screen coordinates)
- !

Item was removed:
- ----- Method: Rectangle class>>center:extent: (in category 'instance creation') -----
- center: centerPoint extent: extentPoint 
- 	"Answer an instance of me whose center is centerPoint and width 
- 	by height is extentPoint.  "
- 
- 	^self origin: centerPoint - (extentPoint//2) extent: extentPoint!

Item was removed:
- ----- Method: Rectangle class>>encompassing: (in category 'instance creation') -----
- encompassing: listOfPoints
- 	"A number of callers of encompass: should use this method."
- 	| topLeft bottomRight |
- 	topLeft := bottomRight := listOfPoints first.
- 	listOfPoints allButFirstDo:
- 		[:p |topLeft := topLeft min: p.
- 					bottomRight := bottomRight max: p].
- 	^self origin: topLeft corner: bottomRight
- 	!

Item was removed:
- ----- Method: Rectangle class>>exactCenter:extent: (in category 'instance creation') -----
- exactCenter: centerPoint extent: extentPoint 
- 	"Answer an instance of me whose center is centerPoint and width 
- 	by height is extentPoint. "
- 	^ self origin: centerPoint - (extentPoint / 2) extent: extentPoint
- !

Item was removed:
- ----- Method: Rectangle class>>fromUser (in category 'instance creation') -----
- fromUser
- 	"Answer an instance of me that is determined by having the user 
- 	designate the top left and bottom right corners. The gridding for user 
- 	selection is 1 at 1."
- 
- 	^self fromUser: 1 @ 1!

Item was removed:
- ----- Method: Rectangle class>>fromUser: (in category 'instance creation') -----
- fromUser: gridPoint
- 	"Answer a Rectangle that is determined by having the user 
- 	designate the top left and bottom right corners. 
- 	The cursor reamins linked with the sensor, but
- 	the outline is kept gridded."
- 	| originRect |
- 	originRect := Cursor origin showWhile: 
- 		[((Sensor cursorPoint grid: gridPoint) extent: 0 at 0) newRectFrom:
- 			[:f | (Sensor cursorPoint grid: gridPoint) extent: 0 at 0]].
- 	^ Cursor corner showWhile:
- 		[originRect newRectFrom:
- 			[:f | f origin corner: (Sensor cursorPoint grid: gridPoint)]]!

Item was removed:
- ----- Method: Rectangle class>>left:right:top:bottom: (in category 'instance creation') -----
- left: leftNumber right: rightNumber top: topNumber bottom: bottomNumber 
- 	"Answer an instance of me whose left, right, top, and bottom coordinates 
- 	are determined by the arguments."
- 
- 	^ self basicNew setOrigin: leftNumber @ topNumber corner: rightNumber @ bottomNumber!

Item was removed:
- ----- Method: Rectangle class>>locateMagnifiedView:scale: (in category 'instance creation') -----
- locateMagnifiedView: aForm scale: scaleFactor
- 	"Answer a rectangle at the location where the scaled view of the form,
- 	aForm, should be displayed."
- 
- 	^ self originFromUser: (aForm extent * scaleFactor + (0 at 50))
- !

Item was removed:
- ----- Method: Rectangle class>>merging: (in category 'instance creation') -----
- merging: listOfRects 
- 	"A number of callers of merge: should use this method."
- 	| bottomRight topLeft |
- 	topLeft := listOfRects first topLeft.
- 	bottomRight := listOfRects first bottomRight.
- 	listOfRects
- 		allButFirstDo: [:r | topLeft := topLeft min: r topLeft.
- 			bottomRight := bottomRight max: r bottomRight].
- 	^self origin: topLeft corner: bottomRight.
- 	!

Item was removed:
- ----- Method: Rectangle class>>origin:corner: (in category 'instance creation') -----
- origin: originPoint corner: cornerPoint 
- 	"Answer an instance of me whose corners (top left and bottom right) are 
- 	determined by the arguments."
- 
- 	^self basicNew setOrigin: originPoint corner: cornerPoint!

Item was removed:
- ----- Method: Rectangle class>>origin:extent: (in category 'instance creation') -----
- origin: originPoint extent: extentPoint 
- 	"Answer an instance of me whose top left corner is originPoint and width 
- 	by height is extentPoint."
- 
- 	^self basicNew setOrigin: originPoint corner: originPoint + extentPoint!

Item was removed:
- ----- Method: Rectangle class>>originFromUser: (in category 'instance creation') -----
- originFromUser: extentPoint 
- 	"Answer an instance of me that is determined by having the user 
- 	designate the top left corner. The width and height are determined by 
- 	extentPoint. The gridding for user selection is 1 at 1."
- 
- 	^self originFromUser: extentPoint grid: 1 @ 1!

Item was removed:
- ----- Method: Rectangle class>>originFromUser:grid: (in category 'instance creation') -----
- originFromUser: extentPoint grid: gridPoint 
- 	"Answer an instance of me that is determined by having the user 
- 	designate the top left corner. The width and height are determined by 
- 	extentPoint. The gridding for user selection is scaleFactor. Assumes that 
- 	the sender has determined an extent that is a proper multiple of 
- 	scaleFactor."
- 
- 	^ Cursor origin showWhile: 
- 		[((Sensor cursorPoint grid: gridPoint) extent: extentPoint) newRectFrom:
- 			[:f | (Sensor cursorPoint grid: gridPoint) extent: extentPoint]].
- !

Item was removed:
- ----- Method: Rectangle>>= (in category 'comparing') -----
- = aRectangle 
- 	"Answer true if the receiver's species, origin and corner match aRectangle's."
- 
- 	self species = aRectangle species
- 		ifTrue: [^origin = aRectangle origin and: [corner = aRectangle corner]]
- 		ifFalse: [^false]!

Item was removed:
- ----- Method: Rectangle>>aboveCenter (in category 'accessing') -----
- aboveCenter
- 	"Answer the point slightly above the center of the receiver."
- 
- 	^self topLeft + self bottomRight // (2 at 3)!

Item was removed:
- ----- Method: Rectangle>>adjustTo:along: (in category 'rectangle functions') -----
- adjustTo: newRect along: side 
- 	"Return a copy adjusted to fit a neighbor that has changed size."
- 	side = #left ifTrue: [^ self withRight: newRect left].
- 	side = #right ifTrue: [^ self withLeft: newRect right].
- 	side = #top ifTrue: [^ self withBottom: newRect top].
- 	side = #bottom ifTrue: [^ self withTop: newRect bottom].!

Item was removed:
- ----- Method: Rectangle>>align:with: (in category 'transforming') -----
- align: aPoint1 with: aPoint2 
- 	"Answer a Rectangle that is a translated by aPoint2 - aPoint1."
- 
- 	^self translateBy: aPoint2 - aPoint1!

Item was removed:
- ----- Method: Rectangle>>allAreasOutsideList:do: (in category 'rectangle functions') -----
- allAreasOutsideList: aCollection do: aBlock
- 	"Enumerate aBlock with all areas of the receiver not overlapping 
- 	any rectangle in the given collection"
- 	^self allAreasOutsideList: aCollection startingAt: 1 do: aBlock!

Item was removed:
- ----- Method: Rectangle>>allAreasOutsideList:startingAt:do: (in category 'rectangle functions') -----
- allAreasOutsideList: aCollection startingAt: startIndex do: aBlock
- 	"Enumerate aBlock with all areas of the receiver not overlapping 
- 	any rectangle in the given collection"
- 	| yOrigin yCorner aRectangle index rr |
- 	index := startIndex.
- 
- 	"Find the next intersecting rectangle from aCollection"
- 	[index <= aCollection size ifFalse:[^aBlock value: self].
- 	aRectangle := aCollection at: index.
- 	origin <= aRectangle corner and: [aRectangle origin <= corner]] 
- 		whileFalse:[index := index + 1].
- 
- 	"aRectangle is intersecting; process it"
- 	aRectangle origin y > origin y 
- 		ifTrue: [rr := origin corner: corner x @ (yOrigin := aRectangle origin y).
- 				rr allAreasOutsideList: aCollection startingAt: index+1 do: aBlock]
- 		ifFalse: [yOrigin := origin y].
- 	aRectangle corner y < corner y
- 		ifTrue: [rr := origin x @ (yCorner := aRectangle corner y) corner: corner.
- 				rr allAreasOutsideList: aCollection startingAt: index+1 do: aBlock]
- 		ifFalse: [yCorner := corner y].
- 	aRectangle origin x > origin x 
- 		ifTrue: [rr := origin x @ yOrigin corner: aRectangle origin x @ yCorner.
- 				rr allAreasOutsideList: aCollection startingAt: index+1 do: aBlock].
- 	aRectangle corner x < corner x 
- 		ifTrue: [rr := aRectangle corner x @ yOrigin corner: corner x @ yCorner.
- 				rr allAreasOutsideList: aCollection startingAt: index+1 do: aBlock].!

Item was removed:
- ----- Method: Rectangle>>amountToTranslateWithin: (in category 'rectangle functions') -----
- amountToTranslateWithin: aRectangle
- 	"Answer a Point, delta, such that self + delta is forced within aRectangle."
- 	"Altered so as to prefer to keep self topLeft inside when all of self
- 	cannot be made to fit 7/27/96 di"
- 	| dx dy |
- 	dx := 0.  dy := 0.
- 	self right > aRectangle right ifTrue: [dx := aRectangle right - self right].
- 	self bottom > aRectangle bottom ifTrue: [dy := aRectangle bottom - self bottom].
- 	(self left + dx) < aRectangle left ifTrue: [dx := aRectangle left - self left].
- 	(self top + dy) < aRectangle top ifTrue: [dy := aRectangle top - self top].
- 	^ dx at dy!

Item was removed:
- ----- Method: Rectangle>>area (in category 'accessing') -----
- area
- 	"Answer the receiver's area, the product of width and height."
- 	| w |
- 	(w := self width) <= 0 ifTrue: [^ 0].
- 	^ w * self height max: 0!

Item was removed:
- ----- Method: Rectangle>>areasOutside: (in category 'rectangle functions') -----
- areasOutside: aRectangle
- 	"Answer an Array of Rectangles comprising the parts of the receiver not 
- 	intersecting aRectangle."
- 
- 	| areas yOrigin yCorner |
- 	"Make sure the intersection is non-empty"
-      (self intersects: aRectangle)
- 		ifFalse: [^Array with: self].
- 	areas := OrderedCollection new.
- 	aRectangle origin y > origin y
- 		ifTrue: [areas addLast: (origin corner: corner x @ (yOrigin := aRectangle origin y))]
- 		ifFalse: [yOrigin := origin y].
- 	aRectangle corner y < corner y
- 		ifTrue: [areas addLast: (origin x @ (yCorner := aRectangle corner y) corner: corner)]
- 		ifFalse: [yCorner := corner y].
- 	aRectangle origin x > origin x 
- 		ifTrue: [areas addLast: (origin x @ yOrigin corner: aRectangle origin x @ yCorner)].
- 	aRectangle corner x < corner x 
- 		ifTrue: [areas addLast: (aRectangle corner x @ yOrigin corner: corner x @ yCorner)].
- 	^areas!

Item was removed:
- ----- Method: Rectangle>>bordersOn:along: (in category 'rectangle functions') -----
- bordersOn: her along: herSide 
- 	(herSide = #right and: [self left = her right])
- 	| (herSide = #left and: [self right = her left])
- 		ifTrue:
- 		[^ (self top max: her top) < (self bottom min: her bottom)].
- 	(herSide = #bottom and: [self top = her bottom])
- 	| (herSide = #top and: [self bottom = her top])
- 		ifTrue:
- 		[^ (self left max: her left) < (self right min: her right)].
- 	^ false!

Item was removed:
- ----- Method: Rectangle>>bottom (in category 'accessing') -----
- bottom
- 	"Answer the position of the receiver's bottom horizontal line."
- 
- 	^corner y!

Item was removed:
- ----- Method: Rectangle>>bottom: (in category 'accessing') -----
- bottom: aNumber
- 	^origin corner: corner x @ aNumber!

Item was removed:
- ----- Method: Rectangle>>bottomCenter (in category 'accessing') -----
- bottomCenter
- 	"Answer the point at the center of the bottom horizontal line of the 
- 	receiver."
- 
- 	^self center x @ self bottom!

Item was removed:
- ----- Method: Rectangle>>bottomHalf (in category 'transforming') -----
- bottomHalf
- 	^self withTop: self center y!

Item was removed:
- ----- Method: Rectangle>>bottomLeft (in category 'accessing') -----
- bottomLeft
- 	"Answer the point at the left edge of the bottom horizontal line of the 
- 	receiver."
- 
- 	^origin x @ corner y!

Item was removed:
- ----- Method: Rectangle>>bottomLeftQuadrant (in category 'transforming') -----
- bottomLeftQuadrant
- 	^self leftCenter corner: self bottomCenter!

Item was removed:
- ----- Method: Rectangle>>bottomRight (in category 'accessing') -----
- bottomRight
- 	"Answer the point at the right edge of the bottom horizontal line of the 
- 	receiver."
- 
- 	^corner!

Item was removed:
- ----- Method: Rectangle>>bottomRightQuadrant (in category 'transforming') -----
- bottomRightQuadrant
- 	^self center corner: self bottomRight!

Item was removed:
- ----- Method: Rectangle>>boundingBox (in category 'accessing') -----
- boundingBox
- 	^ self!

Item was removed:
- ----- Method: Rectangle>>ceiling (in category 'truncation and round off') -----
- ceiling
- 	"Answer the integer rectange to the bottom right of receiver.
- 	Return reciever if it already and integerRectange."
- 
- 	self isIntegerRectangle ifTrue: [ ^ self ] .
- 
- 	^origin ceiling corner: corner ceiling!

Item was removed:
- ----- Method: Rectangle>>center (in category 'accessing') -----
- center
- 	"Answer the point at the center of the receiver."
- 
- 	^self topLeft + self bottomRight // 2!

Item was removed:
- ----- Method: Rectangle>>centeredBeneath: (in category 'transforming') -----
- centeredBeneath: aRectangle
- 	 "Move the reciever so that its top center point coincides with the bottom center point of aRectangle.  5/20/96 sw:"
- 
- 	^ self align: self topCenter with: aRectangle bottomCenter!

Item was removed:
- ----- Method: Rectangle>>compressTo: (in category 'truncation and round off') -----
- compressTo: grid
- 	"Answer a Rectangle whose origin and corner are rounded to grid x and grid y.
- 	Rounding is done by upper value on origin and lower value on corner so that
- 	rounded rectangle is inside self."
- 
- 	^Rectangle origin: (origin roundUpTo: grid)
- 				corner: (corner roundDownTo: grid)!

Item was removed:
- ----- Method: Rectangle>>compressed (in category 'truncation and round off') -----
- compressed
- 	"Answer a Rectangle whose origin and corner are rounded to integers.
- 	Rounding is done by upper value on origin and lower value on corner so that
- 	rounded rectangle is inside self."
- 
- 	^Rectangle origin: origin ceiling corner: corner floor!

Item was removed:
- ----- Method: Rectangle>>containsPoint: (in category 'testing') -----
- containsPoint: aPoint 
- 	"Answer whether aPoint is within the receiver."
- 
- 	^origin <= aPoint and: [aPoint < corner]!

Item was removed:
- ----- Method: Rectangle>>containsRect: (in category 'testing') -----
- containsRect: aRect
- 	"Answer whether aRect is within the receiver (OK to coincide)."
- 
- 	^ aRect origin >= origin and: [aRect corner <= corner]
- !

Item was removed:
- ----- Method: Rectangle>>corner (in category 'accessing') -----
- corner
- 	"Answer the point at the bottom right corner of the receiver."
- 
- 	^corner!

Item was removed:
- ----- Method: Rectangle>>corners (in category 'accessing') -----
- corners
- 	"Return an array of corner points in the order of a quadrilateral spec for WarpBlt."
- 
- 	^ Array
- 		with: self topLeft
- 		with: self bottomLeft
- 		with: self bottomRight
- 		with: self topRight
- !

Item was removed:
- ----- Method: Rectangle>>deltaToEnsureInOrCentered:extra: (in category 'FMP') -----
- deltaToEnsureInOrCentered: r extra: aNumber
- 
- 	| dX dY halfXDiff halfYDiff |
- 	dX := dY := 0.
- 	halfXDiff := (r width - self width * aNumber) truncated.
- 	halfYDiff := (r height - self height  * aNumber) truncated.
- 	self left < r left
- 		ifTrue: [dX := self left - r left - halfXDiff]
- 		ifFalse: [self right > r right ifTrue: [dX := self right - r right + halfXDiff]].
- 	self top < r top
- 		ifTrue: [dY := self top - r top - halfYDiff]
- 		ifFalse: [self bottom > r bottom ifTrue: [dY := self bottom - r bottom + halfYDiff]].
- 	^dX @ dY
- !

Item was removed:
- ----- Method: Rectangle>>encompass: (in category 'rectangle functions') -----
- encompass: aPoint 
- 	"Answer a Rectangle that contains both the receiver and aPoint.  5/30/96 sw"
- 
- 	^ Rectangle 
- 		origin: (origin min: aPoint)
- 		corner: (corner max:  aPoint)!

Item was removed:
- ----- Method: Rectangle>>expandBy: (in category 'rectangle functions') -----
- expandBy: delta 
- 	"Answer a Rectangle that is outset from the receiver by delta. delta is a 
- 	Rectangle, Point, or scalar."
- 
- 	(delta isRectangle)
- 		ifTrue: [^Rectangle 
- 					origin: origin - delta origin 
- 					corner: corner + delta corner]
- 		ifFalse: [^Rectangle 
- 					origin: origin - delta 
- 					corner: corner + delta]!

Item was removed:
- ----- Method: Rectangle>>expandTo: (in category 'truncation and round off') -----
- expandTo: grid
- 	"Answer a Rectangle whose origin and corner are rounded to grid x and grid y.
- 	Rounding is done by upper value on origin and lower value on corner so that
- 	self is inside rounded rectangle."
- 
- 	^Rectangle origin: (origin roundDownTo: grid)
- 				corner: (corner roundUpTo: grid)!

Item was removed:
- ----- Method: Rectangle>>expanded (in category 'truncation and round off') -----
- expanded
- 	"Answer a Rectangle whose origin and corner are rounded to integers.
- 	Rounding is done by upper value on origin and lower value on corner so that
- 	self is inside rounded rectangle."
- 
- 	^Rectangle origin: origin floor corner: corner ceiling!

Item was removed:
- ----- Method: Rectangle>>extendBy: (in category 'rectangle functions') -----
- extendBy: delta 
- 	"Answer a Rectangle with the same origin as the receiver, but whose corner is offset by delta. delta is a 
- 	Rectangle, Point, or scalar."
- 
- 	(delta isRectangle)
- 		ifTrue: [^Rectangle 
- 					origin: origin
- 					corner: corner + delta corner]
- 		ifFalse: [^Rectangle 
- 					origin: origin
- 					corner: corner + delta]!

Item was removed:
- ----- Method: Rectangle>>extent (in category 'accessing') -----
- extent
- 	"Answer a point with the receiver's 
- 	width @ the receiver's height."
- 
- 	^corner - origin!

Item was removed:
- ----- Method: Rectangle>>flipBy:centerAt: (in category 'transforming') -----
- flipBy: direction centerAt: aPoint 
- 	"Return a copy flipped #vertical or #horizontal, about aPoint."
- 	| futureOrigin futureCorner |
- 	direction == #horizontal
- 		ifTrue:
- 			[futureOrigin := self topRight.
- 			futureCorner := self bottomLeft]
- 		ifFalse: [direction == #vertical
- 			ifTrue:
- 				[futureOrigin := self bottomLeft.
- 				futureCorner := self topRight]
- 			ifFalse: [self error: 'unrecognizable direction']].
- 	^ (futureOrigin flipBy: direction centerAt: aPoint)
- 		corner: (futureCorner flipBy: direction centerAt: aPoint)!

Item was removed:
- ----- Method: Rectangle>>floor (in category 'truncation and round off') -----
- floor
- 	"Answer the integer rectange to the topleft of receiver.
- 	Return reciever if it already and integerRectange."
- 
- 	self isIntegerRectangle ifTrue: [ ^ self ] .
- 
- 	^origin floor corner: corner floor!

Item was removed:
- ----- Method: Rectangle>>forPoint:closestSideDistLen: (in category 'rectangle functions') -----
- forPoint: aPoint closestSideDistLen: sideDistLenBlock
- 	"Evaluate the block with my side (symbol) closest to aPoint,
- 		the approx distance of aPoint from that side, and
- 		the length of the side (or 0 if aPoint is beyond the side)"
- 	| side |
- 	side := self sideNearestTo: aPoint.
- 	side == #right ifTrue:
- 		[^ sideDistLenBlock value: side value: (self right - aPoint x) abs
- 			value: ((aPoint y between: self top and: self bottom)
- 						ifTrue: [self height] ifFalse: [0])].
- 	side == #left ifTrue:
- 		[^ sideDistLenBlock value: side value: (self left - aPoint x) abs
- 			value: ((aPoint y between: self top and: self bottom)
- 						ifTrue: [self height] ifFalse: [0])].
- 	side == #bottom ifTrue:
- 		[^ sideDistLenBlock value: side value: (self bottom - aPoint y) abs
- 			value: ((aPoint x between: self left and: self right)
- 						ifTrue: [self width] ifFalse: [0])].
- 	side == #top ifTrue:
- 		[^ sideDistLenBlock value: side value: (self top - aPoint y) abs
- 			value: ((aPoint x between: self left and: self right)
- 						ifTrue: [self width] ifFalse: [0])].!

Item was removed:
- ----- Method: Rectangle>>hasPositiveExtent (in category 'testing') -----
- hasPositiveExtent
- 	^ (corner x > origin x) and: [corner y > origin y]!

Item was removed:
- ----- Method: Rectangle>>hash (in category 'comparing') -----
- hash
- 	"Hash is reimplemented because = is implemented."
- 
- 	^origin hash bitXor: corner hash!

Item was removed:
- ----- Method: Rectangle>>height (in category 'accessing') -----
- height
- 	"Answer the height of the receiver."
- 
- 	^corner y - origin y!

Item was removed:
- ----- Method: Rectangle>>innerCorners (in category 'accessing') -----
- innerCorners
- 	"Return an array of inner corner points,
- 	ie, the most extreme pixels included,
- 	in the order of a quadrilateral spec for WarpBlt"
- 	| r1 |
- 	r1 := self topLeft corner: self bottomRight - (1 at 1).
- 	^ Array with: r1 topLeft with: r1 bottomLeft with: r1 bottomRight with: r1 topRight!

Item was removed:
- ----- Method: Rectangle>>insetBy: (in category 'rectangle functions') -----
- insetBy: delta 
- 	"Answer a Rectangle that is inset from the receiver by delta. delta is a 
- 	Rectangle, Point, or scalar."
- 
- 	
- 	(delta isRectangle)
- 		ifTrue: [^Rectangle 
- 					origin: origin + delta origin 
- 					corner: corner - delta corner]
- 		ifFalse: [^Rectangle 
- 					origin: origin + delta 
- 					corner: corner - delta]!

Item was removed:
- ----- Method: Rectangle>>insetOriginBy:cornerBy: (in category 'rectangle functions') -----
- insetOriginBy: originDeltaPoint cornerBy: cornerDeltaPoint 
- 	"Answer a Rectangle that is inset from the receiver by a given amount in 
- 	the origin and corner."
- 
- 	^Rectangle
- 		origin: origin + originDeltaPoint
- 		corner: corner - cornerDeltaPoint!

Item was removed:
- ----- Method: Rectangle>>intersect: (in category 'rectangle functions') -----
- intersect: aRectangle 
- 	"Answer a Rectangle that is the area in which the receiver overlaps with 
- 	aRectangle. Optimized for speed; old code read:
- 		^Rectangle 
- 			origin: (origin max: aRectangle origin)
- 			corner: (corner min: aRectangle corner)
- 	"
- 	| aPoint left right top bottom |
- 	aPoint := aRectangle origin.
- 	aPoint x > origin x ifTrue:[left := aPoint x] ifFalse:[left := origin x].
- 	aPoint y > origin y ifTrue:[top := aPoint y] ifFalse:[top := origin y].
- 	aPoint := aRectangle corner.
- 	aPoint x < corner x ifTrue:[right := aPoint x] ifFalse:[right := corner x].
- 	aPoint y < corner y ifTrue:[bottom := aPoint y] ifFalse:[bottom := corner y].
- 	^Rectangle
- 		origin: (left at top)
- 		corner: (right at bottom)
- !

Item was removed:
- ----- Method: Rectangle>>intersects: (in category 'testing') -----
- intersects: aRectangle 
- 	"Answer whether aRectangle intersects the receiver anywhere."
- 	"Optimized; old code answered:
- 		(origin max: aRectangle origin) < (corner min: aRectangle corner)"
- 
- 	| rOrigin rCorner |
- 	rOrigin := aRectangle origin.
- 	rCorner := aRectangle corner.
- 	rCorner x <= origin x	ifTrue: [^ false].
- 	rCorner y <= origin y	ifTrue: [^ false].
- 	rOrigin x >= corner x	ifTrue: [^ false].
- 	rOrigin y >= corner y	ifTrue: [^ false].
- "None of the two rectangle shall be empty"
- 	corner x < origin x	ifTrue: [^ false].
- 	corner y < origin y	ifTrue: [^ false].
- 	rCorner x < rOrigin x	ifTrue: [^ false].
- 	rCorner y < rOrigin y	ifTrue: [^ false].
- 	^ true
- !

Item was removed:
- ----- Method: Rectangle>>isIntegerRectangle (in category 'truncation and round off') -----
- isIntegerRectangle
- 	"Answer true if all component of receiver are integral."
- 
- 	^origin isIntegerPoint and: [ corner isIntegerPoint ]!

Item was removed:
- ----- Method: Rectangle>>isRectangle (in category 'testing') -----
- isRectangle
- 	^true!

Item was removed:
- ----- Method: Rectangle>>isTall (in category 'testing') -----
- isTall
- 	^ self height > self width!

Item was removed:
- ----- Method: Rectangle>>isWide (in category 'testing') -----
- isWide
- 	^ self width > self height!

Item was removed:
- ----- Method: Rectangle>>isZero (in category 'testing') -----
- isZero
- 	^origin isZero and:[corner isZero]!

Item was removed:
- ----- Method: Rectangle>>left (in category 'accessing') -----
- left
- 	"Answer the position of the receiver's left vertical line."
- 
- 	^origin x!

Item was removed:
- ----- Method: Rectangle>>left: (in category 'accessing') -----
- left: aNumber
- 	^aNumber @ origin y corner: corner!

Item was removed:
- ----- Method: Rectangle>>leftCenter (in category 'accessing') -----
- leftCenter
- 	"Answer the point at the center of the receiver's left vertical line."
- 
- 	^self left @ self center y!

Item was removed:
- ----- Method: Rectangle>>leftHalf (in category 'transforming') -----
- leftHalf
- 	^self withRight: self center x!

Item was removed:
- ----- Method: Rectangle>>merge: (in category 'rectangle functions') -----
- merge: aRectangle 
- 	"Answer a Rectangle that contains both the receiver and aRectangle."
- 
- 	^Rectangle 
- 		origin: (origin min: aRectangle origin)
- 		corner: (corner max: aRectangle corner)!

Item was removed:
- ----- Method: Rectangle>>newRectButtonPressedDo: (in category 'transforming') -----
- newRectButtonPressedDo: newRectBlock 
- 	"Track the outline of a new rectangle until mouse button 
- 	changes. newFrameBlock produces each new rectangle from the 
- 	previous. Only tracks while mouse is down."
- 	| rect newRect buttonNow delay |
- 	delay := Delay forMilliseconds: 10.
- 	buttonNow := Sensor anyButtonPressed.
- 	rect := self.
- 	Display
- 		border: rect
- 		width: 2
- 		rule: Form reverse
- 		fillColor: Color gray.
- 	[buttonNow]
- 		whileTrue: [delay wait.
- 			buttonNow := Sensor anyButtonPressed.
- 			newRect := newRectBlock value: rect.
- 			newRect = rect
- 				ifFalse: [Display
- 						border: rect
- 						width: 2
- 						rule: Form reverse
- 						fillColor: Color gray.
- 					Display
- 						border: newRect
- 						width: 2
- 						rule: Form reverse
- 						fillColor: Color gray.
- 					rect := newRect]].
- 	Display
- 		border: rect
- 		width: 2
- 		rule: Form reverse
- 		fillColor: Color gray.
- 	Project current pointerMoved. 
- 	Sensor processEvent: Sensor createMouseEvent.
- 	^ rect!

Item was removed:
- ----- Method: Rectangle>>newRectFrom: (in category 'transforming') -----
- newRectFrom: newRectBlock
- 	"Track the outline of a new rectangle until mouse button changes.
- 	newFrameBlock produces each new rectangle from the previous"
- 	| rect newRect buttonStart buttonNow delay |
- 	delay := Delay forMilliseconds: 10.
- 	buttonStart := buttonNow := Sensor anyButtonPressed.
- 	rect := self.
- 	Display border: rect width: 2 rule: Form reverse fillColor: Color gray.
- 	[buttonNow == buttonStart] whileTrue: 
- 		[delay wait.
- 		buttonNow := Sensor anyButtonPressed.
- 		newRect := newRectBlock value: rect.
- 		newRect = rect ifFalse:
- 			[Display border: rect width: 2 rule: Form reverse fillColor: Color gray.
- 			Display border: newRect width: 2 rule: Form reverse fillColor: Color gray.
- 			rect := newRect]].
- 	Display border: rect width: 2 rule: Form reverse fillColor: Color gray.
- 	Project current pointerMoved. 
- 	Sensor processEvent: Sensor createMouseEvent.
- 	^ rect!

Item was removed:
- ----- Method: Rectangle>>origin (in category 'accessing') -----
- origin
- 	"Answer the point at the top left corner of the receiver."
- 
- 	^origin!

Item was removed:
- ----- Method: Rectangle>>outsetBy: (in category 'rectangle functions') -----
- outsetBy: delta 
- 	"Answer a Rectangle that is outset from the receiver by delta. delta is a 
- 	Rectangle, Point, or scalar."
- 
- 	(delta isRectangle)
- 		ifTrue: [^Rectangle 
- 					origin: origin - delta origin 
- 					corner: corner + delta corner]
- 		ifFalse: [^Rectangle 
- 					origin: origin - delta 
- 					corner: corner + delta]!

Item was removed:
- ----- Method: Rectangle>>pointAtFraction: (in category 'rectangle functions') -----
- pointAtFraction: relativePoint
- 	"For values between 0.0 and 1.0, answers a point that lies within the receiver.
- 	This method is a more general form of #center (meaning 0.5 at 0.5), #topLeft
- 	(meaning 0.0 at 0.0), #bottomCenter (meaning 0.5 at 1.0), etc.
- 	NOTE THAT for proportions that equal 1.0, the resulting point will NOT lie
- 	within the receiver, i.e., #containsPoint: will answer false."
- 	
- 	| result |
- 	result := self origin + (self extent * relativePoint).
- 	^ self isIntegerRectangle
- 		ifTrue: [result floor]
- 		ifFalse: [result]!

Item was removed:
- ----- Method: Rectangle>>pointNearestTo: (in category 'rectangle functions') -----
- pointNearestTo: aPoint
- 	"Return the point on my border closest to aPoint"
- 	| side |
- 	(self containsPoint: aPoint)
- 		ifTrue:
- 			[side := self sideNearestTo: aPoint.
- 			side == #right ifTrue: [^ self right @ aPoint y].
- 			side == #left ifTrue: [^ self left @ aPoint y].
- 			side == #bottom ifTrue: [^ aPoint x @ self bottom].
- 			side == #top ifTrue: [^ aPoint x @ self top]]
- 		ifFalse:
- 			[^ aPoint adhereTo: self]!

Item was removed:
- ----- Method: Rectangle>>printOn: (in category 'printing') -----
- printOn: aStream 
- 	"Refer to the comment in Object|printOn:."
- 
- 	origin printOn: aStream.
- 	aStream nextPutAll: ' corner: '.
- 	corner printOn: aStream!

Item was removed:
- ----- Method: Rectangle>>quickMerge: (in category 'rectangle functions') -----
- quickMerge: aRectangle 
- 	"Answer the receiver if it encloses the given rectangle or the merge of the two rectangles if it doesn't. THis method is an optimization to reduce extra rectangle creations."
- 
- 	| useRcvr rOrigin rCorner minX maxX minY maxY |
- 	useRcvr := true.
- 	rOrigin := aRectangle topLeft.
- 	rCorner := aRectangle bottomRight.
- 	minX := rOrigin x < origin x ifTrue: [useRcvr := false. rOrigin x] ifFalse: [origin x].
- 	maxX := rCorner x > corner x ifTrue: [useRcvr := false. rCorner x] ifFalse: [corner x].
- 	minY := rOrigin y < origin y ifTrue: [useRcvr := false. rOrigin y] ifFalse: [origin y].
- 	maxY := rCorner y > corner y ifTrue: [useRcvr := false. rCorner y] ifFalse: [corner y].
- 
- 	useRcvr
- 		ifTrue: [^ self]
- 		ifFalse: [^ Rectangle origin: minX at minY corner: maxX at maxY].
- !

Item was removed:
- ----- Method: Rectangle>>randomPoint (in category 'random') -----
- randomPoint
- 
- 	^ self randomPoint: ThreadSafeRandom value!

Item was removed:
- ----- Method: Rectangle>>randomPoint: (in category 'random') -----
- randomPoint: aGenerator
- 	"Answers a random point that lies within the receiver."
- 
- 	^ self pointAtFraction: aGenerator next @ aGenerator next!

Item was removed:
- ----- Method: Rectangle>>rectanglesAt:height: (in category 'rectangle functions') -----
- rectanglesAt: y height: ht
- 	(y+ht) > self bottom ifTrue: [^ Array new].
- 	^ Array with: (origin x @ y corner: corner x @ (y+ht))!

Item was removed:
- ----- Method: Rectangle>>right (in category 'accessing') -----
- right
- 	"Answer the position of the receiver's right vertical line."
- 
- 	^corner x!

Item was removed:
- ----- Method: Rectangle>>right: (in category 'accessing') -----
- right: aNumber
- 	^origin corner: aNumber @ corner y!

Item was removed:
- ----- Method: Rectangle>>rightCenter (in category 'accessing') -----
- rightCenter
- 	"Answer the point at the center of the receiver's right vertical line."
- 
- 	^self right @ self center y!

Item was removed:
- ----- Method: Rectangle>>rightHalf (in category 'transforming') -----
- rightHalf
- 	^self withLeft: self center x!

Item was removed:
- ----- Method: Rectangle>>rotateBy:centerAt: (in category 'transforming') -----
- rotateBy: direction centerAt: aPoint
- 	"Return a copy rotated #right, #left, or #pi about aPoint"
- 	| futureOrigin futureCorner |
- 	direction == #pi
- 		ifTrue:
- 			[futureOrigin := self corner.
- 			futureCorner := self origin]
- 		ifFalse: [direction == #left
- 			ifTrue:
- 				[futureOrigin := self topRight.
- 				futureCorner := self bottomLeft]
- 			ifFalse: [direction == #right
- 				ifTrue:
- 					[futureOrigin := self bottomLeft.
- 					futureCorner := self topRight]
- 				ifFalse: [self error: 'unrecognizable direction']]].
- 	^ (futureOrigin rotateBy: direction centerAt: aPoint)
- 		corner: (futureCorner rotateBy: direction centerAt: aPoint)!

Item was removed:
- ----- Method: Rectangle>>roundTo: (in category 'truncation and round off') -----
- roundTo: grid
- 	"Answer a Rectangle whose origin and corner are rounded to grid x and grid y."
- 
- 	^Rectangle origin: (origin roundTo: grid)
- 				corner: (corner roundTo: grid)!

Item was removed:
- ----- Method: Rectangle>>rounded (in category 'truncation and round off') -----
- rounded
- 	"Answer a Rectangle whose origin and corner are rounded."
- 
- 	^Rectangle origin: origin rounded extent: self extent rounded!

Item was removed:
- ----- Method: Rectangle>>scaleBy: (in category 'transforming') -----
- scaleBy: scale 
- 	"Answer a Rectangle scaled by scale, a Point or a scalar."
- 
- 	^Rectangle origin: origin * scale corner: corner * scale!

Item was removed:
- ----- Method: Rectangle>>scaleFrom:to: (in category 'transforming') -----
- scaleFrom: rect1 to: rect2
- 	"Produce a rectangle stretched according to the stretch from rect1 to rect2"
- 	^ (origin scaleFrom: rect1 to: rect2)
- 		corner: (corner scaleFrom: rect1 to: rect2)!

Item was removed:
- ----- Method: Rectangle>>setOrigin:corner: (in category 'private') -----
- setOrigin: topLeft corner: bottomRight
- 	origin := topLeft.
- 	corner := bottomRight!

Item was removed:
- ----- Method: Rectangle>>sideNearestTo: (in category 'rectangle functions') -----
- sideNearestTo: aPoint
- 	| distToLeft distToRight distToTop distToBottom closest side |
- 	distToLeft := aPoint x - self left.
- 	distToRight := self right - aPoint x.
- 	distToTop := aPoint y - self top.
- 	distToBottom := self bottom - aPoint y.
- 	closest := distToLeft. side := #left.
- 	distToRight < closest ifTrue: [closest := distToRight. side := #right].
- 	distToTop < closest ifTrue: [closest := distToTop. side := #top].
- 	distToBottom < closest ifTrue: [closest := distToBottom. side := #bottom].
- 	^ side
- "
-  | r | r := Rectangle fromUser.
- Display border: r width: 1.
- [Sensor anyButtonPressed] whileFalse:
- 	[(r sideNearestTo: Sensor cursorPoint) , '      ' displayAt: 0 at 0]
- "!

Item was removed:
- ----- Method: Rectangle>>squishedWithin: (in category 'transforming') -----
- squishedWithin: aRectangle
- 	"Return an adjustment of the receiver that fits within aRectangle by reducing its size, not by changing its origin.  "
- 
- 	^ origin corner: (corner min: aRectangle bottomRight)
- 
- "(50 @ 50 corner: 160 @ 100) squishedWithin:  (20 @ 10 corner: 90 @ 85)"
- !

Item was removed:
- ----- Method: Rectangle>>storeOn: (in category 'printing') -----
- storeOn: aStream 
- 	"printed form is good for storing too"
- 	
- 	aStream nextPut: $(.
- 	self printOn: aStream.
- 	aStream nextPut: $).!

Item was removed:
- ----- Method: Rectangle>>swallow: (in category 'rectangle functions') -----
- swallow: aRectangle 
- 	"Modify the receiver so that it contains aRectangle."
- 
- 	origin := origin min: aRectangle origin.
- 	corner := corner max: aRectangle corner!

Item was removed:
- ----- Method: Rectangle>>top (in category 'accessing') -----
- top
- 	"Answer the position of the receiver's top horizontal line."
- 
- 	^origin y!

Item was removed:
- ----- Method: Rectangle>>top: (in category 'accessing') -----
- top: aNumber
- 	^origin x @ aNumber corner: corner!

Item was removed:
- ----- Method: Rectangle>>topCenter (in category 'accessing') -----
- topCenter
- 	"Answer the point at the center of the receiver's top horizontal line."
- 
- 	^self center x @ self top!

Item was removed:
- ----- Method: Rectangle>>topHalf (in category 'transforming') -----
- topHalf
- 	^self withBottom: self center y!

Item was removed:
- ----- Method: Rectangle>>topLeft (in category 'accessing') -----
- topLeft
- 	"Answer the point at the top left corner of the receiver's top horizontal line."
- 
- 	^origin
- !

Item was removed:
- ----- Method: Rectangle>>topLeftQuadrant (in category 'transforming') -----
- topLeftQuadrant
- 	^self topLeft corner: self center!

Item was removed:
- ----- Method: Rectangle>>topRight (in category 'accessing') -----
- topRight
- 	"Answer the point at the top right corner of the receiver's top horizontal 
- 	line."
- 
- 	^corner x @ origin y!

Item was removed:
- ----- Method: Rectangle>>topRightQuadrant (in category 'transforming') -----
- topRightQuadrant
- 	^self topCenter corner: self rightCenter!

Item was removed:
- ----- Method: Rectangle>>translateBy: (in category 'transforming') -----
- translateBy: factor 
- 	"Answer a Rectangle translated by factor, a Point or a scalar."
- 
- 	^Rectangle origin: origin + factor corner: corner + factor!

Item was removed:
- ----- Method: Rectangle>>translatedAndSquishedToBeWithin: (in category 'transforming') -----
- translatedAndSquishedToBeWithin: aRectangle
- 	"Return an adjustment of the receiver that fits within aRectangle by
- 		- translating it to be within aRectangle if necessary, then
- 		- reducing its size, if necessary"
- 
- 	^ (self translatedToBeWithin: aRectangle) squishedWithin: aRectangle!

Item was removed:
- ----- Method: Rectangle>>translatedToBeWithin: (in category 'rectangle functions') -----
- translatedToBeWithin: aRectangle
- 	"Answer a copy of the receiver that does not extend beyond aRectangle.  7/8/96 sw"
- 
- 	^ self translateBy: (self amountToTranslateWithin: aRectangle)!

Item was removed:
- ----- Method: Rectangle>>truncateTo: (in category 'truncation and round off') -----
- truncateTo: grid
- 	"Answer a Rectangle whose origin and corner are truncated to grid x and grid y."
- 
- 	^Rectangle origin: (origin truncateTo: grid)
- 				corner: (corner truncateTo: grid)!

Item was removed:
- ----- Method: Rectangle>>truncated (in category 'truncation and round off') -----
- truncated
- 	"Answer a Rectangle whose origin and corner have any fractional parts removed. Answer the receiver if its coordinates are already integral."
- 
- 	(origin x isInteger and:
- 	[origin y isInteger and:
- 	[corner x isInteger and:
- 	[corner y isInteger]]])
- 		ifTrue: [^ self].
- 
- 	^ Rectangle origin: origin truncated corner: corner truncated
- !

Item was removed:
- ----- Method: Rectangle>>width (in category 'accessing') -----
- width
- 	"Answer the width of the receiver."
- 
- 	^corner x - origin x!

Item was removed:
- ----- Method: Rectangle>>withBottom: (in category 'rectangle functions') -----
- withBottom: y 
- 	"Return a copy of me with a different bottom y"
- 	^ origin x @ origin y corner: corner x @ y!

Item was removed:
- ----- Method: Rectangle>>withHeight: (in category 'rectangle functions') -----
- withHeight: height 
- 	"Return a copy of me with a different height"
- 	^ origin corner: corner x @ (origin y + height)!

Item was removed:
- ----- Method: Rectangle>>withLeft: (in category 'rectangle functions') -----
- withLeft: x 
- 	"Return a copy of me with a different left x"
- 	^ x @ origin y corner: corner x @ corner y!

Item was removed:
- ----- Method: Rectangle>>withRight: (in category 'rectangle functions') -----
- withRight: x 
- 	"Return a copy of me with a different right x"
- 	^ origin x @ origin y corner: x @ corner y!

Item was removed:
- ----- Method: Rectangle>>withSide:setTo: (in category 'rectangle functions') -----
- withSide: side setTo: value  "return a copy with side set to value"
- 	^ self perform: (#(withLeft: withRight: withTop: withBottom: )
- 							at: (#(left right top bottom) indexOf: side))
- 		with: value!

Item was removed:
- ----- Method: Rectangle>>withSideOrCorner:setToPoint: (in category 'rectangle functions') -----
- withSideOrCorner: side setToPoint: newPoint
- 	"Return a copy with side set to newPoint"
- 
- 	^ self withSideOrCorner: side setToPoint: newPoint minExtent: 0 at 0!

Item was removed:
- ----- Method: Rectangle>>withSideOrCorner:setToPoint:minExtent: (in category 'rectangle functions') -----
- withSideOrCorner: side setToPoint: newPoint minExtent: minExtent
- 	"Return a copy with side set to newPoint"
- 	^self withSideOrCorner: side setToPoint: newPoint minExtent: minExtent
- 		limit: ((#(left top) includes: side) ifTrue: [SmallInteger minVal] ifFalse: [SmallInteger maxVal])!

Item was removed:
- ----- Method: Rectangle>>withSideOrCorner:setToPoint:minExtent:limit: (in category 'rectangle functions') -----
- withSideOrCorner: side setToPoint: newPoint minExtent: minExtent limit: limit
- 	"Return a copy with side set to newPoint"
- 	side = #top ifTrue: [^ self withTop: (newPoint y min: corner y - minExtent y max: limit + minExtent y)].
- 	side = #bottom ifTrue: [^ self withBottom: (newPoint y min: limit - minExtent y max: origin y + minExtent y)].
- 	side = #left ifTrue: [^ self withLeft: (newPoint x min: corner x - minExtent x max: limit + minExtent x)].
- 	side = #right ifTrue: [^ self withRight: (newPoint x min: limit - minExtent x max: origin x + minExtent x)].
- 	side = #topLeft ifTrue: [^ (newPoint min: corner - minExtent) corner: self bottomRight].
- 	side = #bottomRight ifTrue: [^ self topLeft corner: (newPoint max: origin + minExtent)].
- 	side = #bottomLeft ifTrue: [^ self topRight rect: ((newPoint x min: corner x - minExtent x) @ (newPoint y max: origin y + minExtent y))].
- 	side = #topRight ifTrue: [^ self bottomLeft rect: ((newPoint x max: origin x + minExtent x) @ (newPoint y min: corner y - minExtent y))].!

Item was removed:
- ----- Method: Rectangle>>withTop: (in category 'rectangle functions') -----
- withTop: y 
- 	"Return a copy of me with a different top y"
- 	^ origin x @ y corner: corner x @ corner y!

Item was removed:
- ----- Method: Rectangle>>withWidth: (in category 'rectangle functions') -----
- withWidth: width 
- 	"Return a copy of me with a different width"
- 	^ origin corner: (origin x + width) @ corner y!

Item was removed:
- CompositionScanner subclass: #SegmentScanner
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: 'TextConstants'
- 	category: 'Graphics-Text'!
- 
- !SegmentScanner commentStamp: 'nice 10/6/2013 22:39' prior: 0!
- A SegmentScanner is a CompositionScanner specialized for composing TextOnCurve.
- !

Item was removed:
- ----- Method: SegmentScanner>>setStopConditions (in category 'private') -----
- setStopConditions
- 	"Set the font and the stop conditions for the current run."
- 	
- 	self setFont.
- 	stopConditions := DefaultStopConditions!

Item was removed:
- ----- Method: SmartRefStream>>transparentColorrcc0 (in category '*Graphics-conversion') -----
- transparentColorrcc0
- 	^ TranslucentColor!

Item was removed:
- Form subclass: #StaticForm
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Display Objects'!
- 
- !StaticForm commentStamp: '<historical>' prior: 0!
- An optimization for Nebraska - a StaticForm does not change once created so it may be cached on the remote end.!

Item was removed:
- ----- Method: StaticForm>>isStatic (in category 'testing') -----
- isStatic
- 
- 	^true!

Item was removed:
- AbstractFont subclass: #StrikeFont
- 	instanceVariableNames: 'characterToGlyphMap xTable glyphs name type minAscii maxAscii maxWidth strikeLength ascent descent xOffset raster subscript superscript emphasis derivativeFonts pointSize fallbackFont charIndexCompatibilitySlot lineGap lineGapSlice'
- 	classVariableNames: 'DefaultStringScanner'
- 	poolDictionaries: 'TextConstants'
- 	category: 'Graphics-Fonts'!
- 
- !StrikeFont commentStamp: 'fbs 11/28/2013 08:50' prior: 0!
- I represent a compact encoding of a set of Forms corresponding to characters in the ASCII character set. All the forms are placed side by side in a large form whose height is the font height, and whose width is the sum of all the character widths. The xTable variable gives the left-x coordinates of the subforms corresponding to the glyphs. Characters are mapped to glyphs by using the characterToGyphMap.
- 
- Subclasses can have non-trivial mapping rules as well as different representations for glyphs sizes (e.g., not using an xTable). If so, these classes should return nil when queried for xTable and/or the characterToGlyphMap. This will cause the CharacterScanner primitive to fail and query the font for the width of a character (so that a more programatical approach can be implemented).
- 
- For display, fonts need to implement two messages:
- 	#installOn: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor
- This method installs the receiver (a font) on the given DisplayContext (which may be an instance of BitBlt or Canvas (or any of its subclasses). The font should take the appropriate action to initialize the display context so that further display operations can be optimized.
- 	#displayString: aString on: aDisplayContext from: startIndex to: stopIndex at: aPoint kern: kernDelta
- This method is called for each subsequent run of characters in aString which is to be displayed with the (previously installed) settings.
- !

Item was removed:
- ----- Method: StrikeFont class>>actualFamilyNames (in category 'accessing') -----
- actualFamilyNames
- 	"Answer a sorted list of actual family names, without the Default aliases"
- 
- 	^(self familyNames copyWithoutAll: TextStyle defaultFamilyNames) asOrderedCollection!

Item was removed:
- ----- Method: StrikeFont class>>cleanUp: (in category 'class initialization') -----
- cleanUp: aggressive
- 
- 	aggressive ifTrue: [self allInstancesDo: [:sf | sf reset]].!

Item was removed:
- ----- Method: StrikeFont class>>convertFontsNamed: (in category 'examples') -----
- convertFontsNamed: familyName  " StrikeFont convertFontsNamed: 'NewYork' "
- 	"This utility is for use after you have used BitFont to produce data files 
- 	for the fonts you wish to use.  It will read the BitFont files and then 
- 	write them out in strike2 (*.sf2) format which is much more compact,
- 	and which can be read in again very quickly."
- 	"For this utility to work as is, the BitFont data files must be named
- 	'familyNN.BF', and must reside in the same directory as the image."
- 	(FileDirectory default fileNamesMatching: familyName , '*.BF') do:
- 		[:fname |
- 		| f |
- 		Transcript cr; show: fname.
- 		f := StrikeFont new readFromBitFont: fname.
- 		f writeAsStrike2named: f name , '.sf2']!

Item was removed:
- ----- Method: StrikeFont class>>createDejaVu: (in category 'font creation') -----
- createDejaVu: pointSize
- 	"Warning: Uses the methods in 'dejaVu font data' category, that will be removed soon (or are already removed) to save space."
- 	
- 	| base bold oblique boldOblique point actualPointSize |
- 	point := pointSize asString.
- 	actualPointSize := self fixDejaVuPointSIze: pointSize.
- 	base := (StrikeFont new
- 		buildFromForm: (self perform: ('dejaVuSansBook', point, 'Form') asSymbol)
- 		data: (self perform: ('dejaVuSansBook', point, 'Data') asSymbol)
- 		name: 'Bitmap DejaVu Sans ', point)
- 			pointSize: actualPointSize.
- 	bold := (StrikeFont new
- 		buildFromForm:  (self perform: ('dejaVuSansBold', point, 'Form') asSymbol)
- 		data: (self perform: ('dejaVuSansBold', point, 'Data') asSymbol)
- 		name: 'Bitmap DejaVu Sans ', point, 'B')
- 			emphasis: 1;
- 			pointSize: actualPointSize.
- 	oblique := (StrikeFont new
- 		buildFromForm: (self perform: ('dejaVuSansOblique', point, 'Form') asSymbol)
- 		data: (self perform: ('dejaVuSansOblique', point, 'Data') asSymbol)
- 		name: 'Bitmap DejaVu Sans ', point, 'I')
- 			emphasis: 2;
- 			pointSize: actualPointSize.
- 	boldOblique := (StrikeFont new
- 		buildFromForm: (self perform: ('dejaVuSansBoldOblique', point, 'Form') asSymbol)
- 		data: (self perform: ('dejaVuSansBoldOblique', point, 'Data') asSymbol)
- 		name: 'Bitmap DejaVu Sans ', point, 'BI')
- 			emphasis: 3;
- 			pointSize: actualPointSize.
- 		
- 	base derivativeFont: bold at: 1.
- 	base derivativeFont: oblique at: 2.
- 	base derivativeFont: boldOblique at: 3.
- 	
- 	^base!

Item was removed:
- ----- Method: StrikeFont class>>createDejaVuDark: (in category 'font creation') -----
- createDejaVuDark: pointSize
- 	
- 	| base bold oblique boldOblique point actualPointSize |
- 	point := pointSize asString.
- 	actualPointSize := self fixDejaVuPointSIze: pointSize.
- 	base := (StrikeFont new
- 		buildFromForm: (self perform: ('dejaVuSansBookDark', point, 'Form') asSymbol)
- 		data: (self perform: ('dejaVuSansBookDark', point, 'Data') asSymbol)
- 		name: 'Darkmap DejaVu Sans', point)
- 			pointSize: actualPointSize.
- 	bold := (StrikeFont new
- 		buildFromForm:  (self perform: ('dejaVuSansBoldDark', point, 'Form') asSymbol)
- 		data: (self perform: ('dejaVuSansBoldDark', point, 'Data') asSymbol)
- 		name: 'Darkmap DejaVu Sans', point, 'B')
- 			emphasis: 1;
- 			pointSize: actualPointSize.
- 	oblique := (StrikeFont new
- 		buildFromForm: (self perform: ('dejaVuSansObliqueDark', point, 'Form') asSymbol)
- 		data: (self perform: ('dejaVuSansObliqueDark', point, 'Data') asSymbol)
- 		name: 'Darkmap DejaVu Sans', point, 'I')
- 			emphasis: 2;
- 			pointSize: actualPointSize.
- 	boldOblique := (StrikeFont new
- 		buildFromForm: (self perform: ('dejaVuSansBoldObliqueDark', point, 'Form') asSymbol)
- 		data: (self perform: ('dejaVuSansBoldObliqueDark', point, 'Data') asSymbol)
- 		name: 'Darkmap DejaVu Sans', point, 'BI')
- 			emphasis: 3;
- 			pointSize: actualPointSize.
- 		
- 	base derivativeFont: bold at: 1.
- 	base derivativeFont: oblique at: 2.
- 	base derivativeFont: boldOblique at: 3.
- 	
- 	^base!

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBold12Data (in category 'dejaVu font data') -----
- dejaVuSansBold12Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold 12. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 12 15 4 0 255 18 0 0 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 16 23 31 44 55 71 85 90 97 104 112 125 131 138 144 150 161 172 183 194 205 216 227 238 249 260 266 272 285 298 311 320 336 348 360 372 385 396 407 420 433 439 445 457 467 483 496 510 522 536 548 560 571 584 596 614 626 638 650 657 663 670 683 691 699 710 721 730 741 752 759 770 781 786 791 802 807 824 835 846 857 868 876 886 894 905 915 930 940 950 959 970 976 987 1000 1000 1013 1021 1034 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1053 1060 1071 1082 1092 1103 1109 1117 1125 1141 1150 1160 1173 1180 1196 1204 1212 1225 1232 1239 1247 1259 1269 1275 1283 1290 1299 1309 1326 1343 1360 1369 1381 1393 1405 1417 1429 1441 1458 1470 1481 1492 1503 1514 1520 1526 1532 1538 1551 1564 1578 1592 1606 1620 1634 1647 1661 1674 1687 1700 1713 1725 1737 1749 1760 1771 1782 
 1793 1804 1815 1832 1841 1852 1863 1874 1885 1890 1895 1901 1906 1917 1928 1939 1950 1961 1972 1983 1996 2007 2018 2029 2040 2051 2061 2072 2082
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBold12Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBold13Data (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBold14Data (in category 'dejaVu font data') -----
- dejaVuSansBold14Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold 14. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 14 18 4 0 255 21 0 0 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 18 27 37 53 66 85 102 108 117 126 136 152 159 167 174 181 194 207 220 233 246 259 272 285 298 311 319 327 343 359 375 386 405 420 434 448 464 477 490 506 522 529 535 550 562 581 597 613 627 643 658 672 685 700 715 736 751 765 779 788 795 804 820 830 840 853 867 878 892 905 913 927 941 948 955 968 975 995 1009 1022 1036 1050 1059 1070 1079 1093 1105 1123 1135 1147 1158 1172 1179 1193 1209 1209 1225 1235 1251 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1274 1283 1296 1309 1321 1334 1341 1351 1361 1380 1391 1403 1419 1427 1446 1456 1466 1482 1490 1498 1508 1522 1534 1541 1551 1559 1570 1582 1602 1622 1642 1653 1668 1683 1698 1713 1728 1743 1764 1778 1791 1804 1817 1830 1837 1844 1851 1858 1874 1890 1906 1922 1938 1954 1970 1986 2002 2017 2032 2047 2062 2076 2090 2
 104 2117 2130 2143 2156 2169 2182 2202 2213 2226 2239 2252 2265 2272 2279 2286 2293 2306 2320 2333 2346 2359 2372 2385 2401 2414 2428 2442 2456 2470 2482 2496 2508
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBold14Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBold17Data (in category 'dejaVu font data') -----
- dejaVuSansBold17Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold 17. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 17 21 5 0 255 25 0 0 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 22 32 44 63 79 102 122 129 140 151 163 182 191 201 210 218 234 250 266 282 298 314 330 346 362 378 387 396 415 434 453 466 489 507 525 542 561 577 593 612 631 640 648 666 681 704 723 743 760 780 798 815 831 850 868 893 911 928 945 956 964 975 994 1006 1018 1034 1050 1064 1080 1096 1106 1122 1138 1146 1154 1169 1177 1201 1217 1233 1249 1265 1276 1290 1301 1317 1332 1353 1368 1383 1396 1412 1420 1436 1455 1455 1474 1486 1505 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1532 1542 1558 1574 1589 1605 1613 1625 1637 1660 1673 1688 1707 1717 1740 1752 1764 1783 1793 1803 1815 1832 1847 1856 1868 1878 1891 1906 1930 1954 1978 1991 2009 2027 2045 2063 2081 2099 2124 2141 2157 2173 2189 2205 2214 2223 2232 2241 2260 2279 2299 2319 2339 2359 2379 2398 2418 2437 2456 2475 
 2494 2511 2528 2545 2561 2577 2593 2609 2625 2641 2665 2679 2695 2711 2727 2743 2751 2759 2768 2776 2792 2808 2824 2840 2856 2872 2888 2907 2923 2939 2955 2971 2987 3002 3018 3033
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBold17Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBold20Data (in category 'dejaVu font data') -----
- dejaVuSansBold20Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold 20. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 20 25 6 0 255 30 0 0 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 25 37 51 74 93 120 144 152 164 176 190 213 223 234 244 254 273 292 311 330 349 368 387 406 425 444 455 466 489 512 535 551 578 599 620 640 662 680 698 720 743 753 763 784 801 828 851 874 894 917 938 957 975 997 1018 1048 1069 1089 1109 1121 1131 1143 1166 1180 1194 1212 1231 1247 1266 1284 1296 1315 1334 1343 1352 1370 1379 1407 1426 1445 1464 1483 1496 1512 1525 1544 1562 1587 1604 1622 1638 1657 1667 1686 1709 1709 1732 1746 1769 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1801 1813 1832 1851 1868 1887 1897 1911 1925 1952 1967 1984 2007 2018 2045 2059 2073 2096 2108 2120 2134 2154 2171 2181 2195 2207 2222 2239 2267 2295 2323 2339 2360 2381 2402 2423 2444 2465 2494 2514 2532 2550 2568 2586 2596 2606 2616 2626 2649 2672 2695 2718 2741 2764 2787 2810 2833 2855 2
 877 2899 2921 2941 2961 2980 2998 3016 3034 3052 3070 3088 3116 3132 3150 3168 3186 3204 3213 3222 3232 3241 3260 3279 3298 3317 3336 3355 3374 3397 3416 3435 3454 3473 3492 3510 3529 3547
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBold20Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBold7Data (in category 'dejaVu font data') -----
- dejaVuSansBold7Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 7 8 2 0 255 10 0 0 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 10 15 20 28 35 45 53 56 61 66 71 79 83 87 91 95 102 109 116 123 130 137 144 151 158 165 169 173 181 189 197 203 212 219 226 233 241 248 255 263 271 275 279 286 292 301 309 317 324 332 339 346 353 361 368 378 385 392 399 404 408 413 421 426 431 438 445 451 458 465 469 476 483 487 491 497 501 511 518 525 532 539 544 550 555 562 568 577 583 589 595 602 606 613 621 621 629 634 642 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 654 659 666 673 679 686 690 695 700 709 715 721 729 733 742 747 752 760 764 768 773 780 786 790 795 799 805 811 821 831 841 847 854 861 868 875 882 889 899 906 913 920 927 934 938 942 946 950 958 966 974 982 990 998 1006 1014 1022 1030 1038 1046 1054 1061 1068 1075 1082 1089 1096 1103 1110 1117 1127 1133 1140 1147 1154 1161 1165 1169 1173 1177 1184 1191 1198 1205 1212 1219 1226 1234 1241 1248 1255 1262 1269
  1275 1282 1288
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBold7Form (in category 'dejaVu font data') -----
- dejaVuSansBold7Form
- 	<generated>
- 	" Form data for DejaVu Sans Bold 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^Form fromBinaryStream: (
- 'iVBORw0KGgoAAAANSUhEUgAABQgAAAAKCAIAAAB38iSVAAAfOklEQVR4Ae1dIbutqtP3E/Ed
- +AR8AbLZSqUZbTYSiWQyWUwUi8VisFgMBguBcN8FgyzWdp111n722eee/3vPPM891z0iwDDw
- mxlGV/bPN5Ld9+PX1mj2bTtMevmfob/0l/6S3TdP+/Fsb4A79hP7yarrSs7Hzxr9bLWHe8L+
- fCD7uy1emDY2YY9bRSf78x3+S/ZI1cbsK0jznMfN2L8yMss0b/s2T4v5EybsstS/Sscs67pf
- /hP2xD5Kgvn8KDu7tAQXw56wNp2ToumbgrA734wlq0RV0EKsNjLnKmeqFYw3JpFplWV5yTJU
- 7V/r8NrXmFbrI9PMihA+HY8cWnVtTdPCdi6LsmmqgrcmcFaRk7KDIqZhhKnxdtVyymSrSlqo
- aW542QxtWUho4EJp5aIuECln+6F/E0OoHq5D30qMeDM/MnfXJdWUhMjJpA00vChrjjPSbQ8P
- LA1nqlesaJZ3F4G1NoKHsZG7VBSDNB7JqAIzNX2ow0lJtOr2r3oYwtxwrnRTFmo2KX9tOab1
- 9i5oPpj0q1a1aLfn+5ED7nRyjqmra7WYR6Uex82YdVltutSnZT/WeU4rXlnmiFTDF7bIvq4f
- Rp92Tla1Xu/37KpFLcf9usfeOhZ6O7VSqCGpz46tqNWth3snRaNXV/E6L/6ZDcqZaAzYIxHl
- Po+3Ese67DZKob+IK5ZOexsKi2RoUbarMbemjw+y3aNsP03W22Pj/ly+qq67+UgYTobTRxku
- +7FFGQKBMGulzY+tI7Mt87q7f/ytzCxtkeeFpzxn7UVUo8izLB8OWOwyy4peC0TqewePIcds
- 3GdO8n6zySBblLHZ2Ps+C8oHO9ShcZaJKdWVPscZ0Kny0GI+QqmtQ1mGSg1bkquNCCi330xM
- M1B865UBc/GL1HNM6sG1OUgCfcKFDqMzfc0IxujWMzHet0gaeo9w0a8Ges+B5x7PmwcVGnLk
- yooRmIe8/Y08pdXuI1Qb5WYmiTJXEGPXA0RBAkYLhs6W6n4Jc6c4MBGtpuP3GFAtDf1AvJki
- 325TIyrGWFlJPW0f9t8MZbgATI0DdIQJrbv5XHMdI6FqTCsHB2YsQGYYE0J53Yb5iXyE0e0i
- l8dzZqhXMJrFmau6KOQwC2bMs4dKMpC5nzJYGlCe1q78pJifrfqhkjg03301m+RPJKcjXKNi
- 9M27Vs4e7mMT1wUp6vm4SAnTugUpvVGY5FIDClpQDyBaOu2KShj0C/QzGTVIA66Zq5QFg8BO
- 7k/Mo0xCSewL7D11Ctw1Bb49U+kNINN1suxdMZTrHXYbqH70F2c/MNQJmwZQeSsuSMba5VxP
- lefD/hA374a4hat+rPtbTVyPXmzk0ChU+x4dtesl1j9q1S7lOYw3WwSme4AH5lC6v/ojDLzU
- +/PH/0CyqywZrzvzJ/Rl62B7PwV7gDTDNSwPAKDX9K6+RaM5o2L4JTtuL+RsHjhdlYe1kD/v
- ia6oG3Hr9oGuJG7E/e3aDrIU/QpgXZxo5jYrMzgpcFdt0GrYkCnBGBPKwV6JQBYWYrd82V3t
- eU59E+zehBnP/ZoMxpVSBeydzQuxjwIeQmLYx/p+DZuAW7D4hfm+SU6Ro58rwyTzDLDA0a4Y
- gbaqfvmBLogMdtRk9yBifOfuMdZh96709e6VoiuIMQLATVDYTyULzOgF3ZiUtzYp+TZzKwNa
- PzjGs8PHBGLC3v4K4jFxhD9AOcaOiVMmIoEwvjApwWfJiWEUC7jrwl/bmbtrZcJ1BtcAZIBD
- hOaV0omhgjDhsx8WcxCZQja6UYrCKR9d+AWFG4iyp3z8kU+wqyXyXxK0G/YyXhYoo2o+YV36
- 8U4R1iPcA79I+X5LsXG8Kb/4yM99a/p4gPXTKProb3clzU6q4r5xjK511l2cGNdbxBMEOQYS
- hqciE5AxWgsJjKLG2R4cmNGboBThUn8F1yocXZKU1tLLJGluAT8cDI8U3wtOoWNgS/v5CbJa
- WveQmg5dYXi6WYzmtxJO5FzvvgsN1IuRk/YprgFlQEgfb/Q2c60mEhvoRbZmjLLlyRD6q2w/
- SbvKXZ2XaM8hqYOUO9/OxenufJhcdenA2nHnVI77C+tocA+p29hZ74plu66Ymo5j3/fDxcn6
- j+gw1sQh0BE3Ytp2VYaqI4khZlm1bd2t2HTffHF2EniYY41vTw36VgMere1uwyoa+7GhjJRK
- cgp2HrQYTcxJUqcNa3hocOURBNJKJyCPjmDiRBRBWTl8eo5gnVTDfmIwLhj8H8IBezCY0gjT
- oZ0S8xLckrDdmOH2V1FWBUGRCQ00hedAK9BVv7JhMz11+hCeSVgt6wIAxkUKUgLNPgbfbC6V
- 6xrEaO2ifJ+ZqL0KFe3741+GVrbzS3idpWjm/aK/zmBHvAQvPZ+sZ4Y+Y16VYDXxGKHculNR
- cL8nYI8IBaGB7u06FEO0cCJG/eHES7KEErGTq4iuTJjKs968KDDsodAHmFx4EJZfcn3cp4zo
- I5SnYtq02y8A6dNKPtgxiHcuRM3uOhBvUYcZ473FrQuFMMZJz6F8Smo218JQyaVwPlkYCwi0
- IImrmRL07WHUx10aHceugF+quy79BPeDF0p9Mx5nCWNt1n8OfzeX080bhvlfjqnwg+n3YEqi
- 27I1MMt0OGA3SImOJvQZl93hY9/TrbtY3IFw6fDDkhzyONvVC8DbWqkeTh78Zhg1Gxol9XS7
- 2nfz8exqf1gDh/vzkDTobVrjhwoRa7bDxPtw9dji6JNuzN2HU7Idt9DpsZOqW22Y3AoaSx+v
- ho9dPSxcxDqTu5ehmQMeSOnp4/HJFyW9RE3sHvbm8vEnOMazclujHIy9Ox44is4eLcdRvK/p
- fX0DHy24o1+lnWcoOVWJAIFZWSCAjLlrx9D/qVHTEXddPs4t9mtviYGAUntMF9C/WTdwjmrM
- TUL29m9cNE5uQikpa+6Wahtw2Q6CU3KrFfD9CwS7GcqrWoiqSJoASo0huvyz8YAgKfQn0Xt3
- 8r+VyJsHZm0Fv10ygKFjVteDqYRmGSa2ahW5BLwuK2lrigyVQ9zw62HpOPrhwak9ppZFg2p1
- 5m8+2zfuwmx3svAGrrnevdIVcL+PufcnkyTzsjAoh1AKxvo9iAfs+zozwtlzaHt6nRCudIrm
- pH4Lsr+ZD8e2lRzh0jRlBZexPCI5CU8WC4z9Ot5fxn8O60FomBTuOK6ejtStZeM6stN8BTJr
- X3KxXPx8XrXHg0/a17LftknJbrtz92Xd1nlajsdY6Lqul2zTpa8pLaePGHiHLbh8gf5g6Vas
- SiuBvnEu1sdiUrTrvrTyYUsz+3brWIqmZtXyPOccGgnBwV45W2/VTTtu1jjggn9DRB5j5J3Y
- tGKH5GYZxvXDOXbN62tvy1I+lNsGqfS+uz6nOHPr6bZMH1wAyOW5GARbU5VwHnOVrxuaapN7
- RyfluH9MaFGiSWVlXa8Ge/PFVZIzAThlgzwija3spuNn5pyNTwbHuDr3LXf9yjGGGAxpuzLE
- YOxc5Tk4MIR6awd0676VkKpiXI7BikVi3zpfg3N3B/MEfggEk2wa9YE4x+5NZb6mFgBY2w7a
- GpQBFUn43Dh0HM2ng/CT8/8ne2u9BnP/1kKJYQeH6T+24dHtsdsIB6GLSqOkxsRRBLcN5Pzg
- eESdzoXWepy3B7xBTC/relG2vsR3D/PQJNQ/F2frxyj8xjTeREu9ZCYL4U+IZyfXkY61VxXM
- XTw2mcdxijSO83pAiyBwXJTduNpkL5o9OHAUHeOVu26oeV2Wddu3SXLibpkYXw+Uy/nEG/AK
- FoaCzCdBwWsE0azjuHo3ifrBbrd1oyUGN2yxkb8cyc52ZUb7L4uZDsc0LvbuGGvrRuRlSwKO
- 0ngdwhbkvt0jDPEP7Xv53DEOVIzrkCc6kNzK4Ra0AgcdqFAGLO/galpfHpa3lTmCM8PnhZe0
- 8FJk4TDTLo2XrthhB168CFy2lR2q+yGSfRx1em0mEQMuEOiRkwFVp3KCAOeNeL+Alysm82HG
- i2YOZwtwdJ4GTazvyhpAvdb71eWza5MezMJd8GpA6zJczsaufQVtvbPyoXNphkgAfpKTcDjT
- mTMd4z5lXuJtmVpQsGfaezGU936hJC5/7p+icBvFqsBzzhlF0GJvz0B+IcfzYKpw+QWge162
- W18hr3CpHGCN4xxiH4iLmkLDtY53IewXG/InhyzGI5ppv5ekj0J43vm0xfLWP8iagfZnG4Iv
- UfOTXcjIHEElNTmTEQ5N/dawNCwME6K/s1m9gtXj4XUPyWmHMrmcKuLb8lst9SsCpARHVWCi
- pSdyNZiQV8cYIj5Q4CW9r28mBIwgqi9NbGiQHCbl5bFn2vlj7vIT9lizANP6EZHK6Qks38af
- 1pRVWZZePmq+bWrJKnRn1zYdO1QCd7rpKXx2HKOcFTCVuHSgUXT3NViwHMMuAWTHzhkWS9+9
- n63cMeQqhjWAWcUwYt21GBx2FWVxwo01h7F2rVDG+9VbOmckXRbO9nA9WOvCqxXYYwkBaBYO
- ieaYJjOckFh3LYUN5yXNNUbVeLdezD+TQ3cfpFh05w4uNj0s6QMZqs15GA6HP0/vkix4+5G0
- YNgv01u5y7NwFJwq/BVwv58JKpdYPoi3g7/L2tmYYz9cAO4FxF+g/OtMUM43r0cPq+V2U7Wm
- jJHlz0L2d/PPoAPRuxlFHsV+lm9u120RIxHpGL/h+jmsX2P0bLYx3t10onBPs+Z4isU/ZhYR
- YQgfLswMs6ePv8mkrCoLDNdlOC66ov8V6F8wy1AdYfrHJSH7JkmIiOmHcwGOT7ThA99qWdci
- 2Be8XWIBUjCKfgLxz5lpb3F+L6n4e4+HOziDWGGkpDBC4A6k/ogqwBKIzMkx8wdm4SRgG0aA
- mYjCxpJgCazgIvlV89Scg2JLYjCAY7z92DEGVACHEI4HDmvdvwHlvUPCZMNRhpnU2qulGXDE
- 3Favh/VFG2CCzZTLYdKtUs24mpA1ETG+XQCfpJfWDrnRBxyzxFwd2LACkAuKPTRiVmCnPXYf
- ul7r1ilQ3eq+08k8AR3r7By+cYLupaRLlOWta+FuZBwVjsbuc7cH2A0nYJylxjoQgBYsOVx1
- HqcziNjAKXQkzLsAqwnF3No0xraczUicBkbHJAurVLJE6W4Yu51e21UyGtYlq5p+3Iy9JxJH
- ShzpfRlbWeUEhzbvpx+rW0mguHCGjOpt7fDpOVLRNwVi3XZunbQbOwCw6/EmhGDGml7PbdJd
- OEYK4IQTRpLm1j5jgohAArarWME452I2SR8i4Z87xkC1s85eOcYI45jZQknoc1oD5Ty2AgM/
- 7XLbFggOaUNVlAsRvDG12KeFy7NwhmlReDHz1ia5KIAnVTOGfqfSvsr5SCWwQvhj3IYcTIe4
- AeVV7RK2GCO35kRFw5Gvp6U452C/eAsxGw1KQqp3oaaL6wu0cXfssz27a7Z1M+lrpLt5JxtK
- 1bVqGlnm3uAfEs0hsutKGvz/sLgwa7VWtXP5DQiZlF0n8OkYxzXY9zIeTUxthbyImk7Hp9pW
- 4HSRQqKVkjkC0aWjS+OVp5rl1C/derVpSbj2DcuQG8Gl9HpRzFDy0hD02Q2kVxSsQHOvR3Rt
- FMLZeZ52Pu54rBayGaB7lMuua0Stbt2b2xK2GelC3ibprYkpGJPMQQPXpgCjys4Ktg44ws2l
- bhgCCTjsSNKTNjDKveavrX+83+w2tV0nAsYUkwUwW5oyqvpzxxj6n4t+PUw8o+NFUdbNtGzr
- 7Y9m+qy+QSsQEgXaNETWWNf3XSCw0BKC1zQwO530NVoWtRSinWEhcQw8TPNyMvezu7wUZR7O
- LSfJECb4XPsEYTEeaRp5y7Cb17KA8NX1mLoiVEgWdAPUA5azzxLHlKJ7BuZcg27lGBQMktki
- wSZ5QeS9RGSwRhJIomLrEZq4klnHtmmnzaYR23SrD+sFVL2dFct5xRGk5ySUbNpjegZoJnlx
- jA9BYDl/pLWr/eiws6HNXFHkTT/E5BA3uqL0usubzd44LWSZld2sK5TR5jhGTvNmAuGld3FG
- K1UzQkjOpc8WkQUrc4/KTYnTZ9MkZ4RZ2HuvgPtbmUbSAFWzoO9DfDqVX2V+3sHL72oqbytb
- nHvUZyH7u/lwlhqjkIUYbILmYlx7jjLCqyKaSc9h/Vfxr7CeGkXg9aUpaYT7vtNqPp5j8b/H
- dGzZd2BpNYu9oP9ToP8qE3IS4fqK6ddrgEi/0wYveDTvQ/y3MJ0j1vd915RFwWvVgyMG4wUr
- keEkPnK1BL7KvFoC0ZxLLZlrsZ87xvtQoyx/GjGfGx4SXjEF6ZfNHJ6adc1BpdJjXmtuT6nc
- oYbrCmY5guQfwK2y08JxkoTPSEeiDc+t5EXUnQ23xhyFTBNwRCDWktJQosRfTWllIEFwTeH0
- MtkQY2AebqVnAbBymErbsss06aZCoO5nnbQUHCSXVxDiOo4D5oDAuTecVwOowGl5Equekohg
- XBKokMsyMOQtP0gpVhXBfvxxnTyj1IHHRT3MD2+Kd0qpJtDtsh3W5Kl97GR4sBriST6+9UWM
- Uc5YTFt/E2p5+/N2j8hxqDGV87lvorIuYz4wbJ2YN+s2ixwBBkDMvlDLM8dYQGQFoPa+42Om
- p9kdcW8mFAbTcxgHrcdlh/mNwdRR3cMHoQ+FGMZx6AV+78QYCCzX9Oj7amQ3DEHgXAcHYD9v
- 6RaQ7WwFBs5akLmBMdbjEU/A/ItPhWhHexbm3ZYWllMQKSJ5DipX9neVHftGlDgcI39wjPd0
- 6YXcVzvSmDcVo9EIhSTwJDsdHFookKZ77UOUFZLJttLFnNXkrCO+Pndd8kDDrbG8sZe7n6b4
- BZqYpAZ9TtTMrbuKgGS2rswSnzyeNXGffRNTqeF4M6F8PECGoBjPn4KBwFF81LGXjjEQ6vaL
- HO5VmQq7ibO3hhIsuTYEQyvdbVshKPlcCK86T5UFkcLbqmc4f/LDJ1DVJW889iGEV2hRYNgM
- YxJmRIeHl1O2jgFXLslrqCTPz8chMkvcc7A84/oNts6PHGMb9ihgglOHeF0VNPSEAeR9jo4q
- eccnddvwSRnKr+nb+ygwfIbgniXEGckTjd8UJxCtkOrUTjtil4ds1o7B2eOkGKDCiY8EPupx
- bAuEiSUFW7AvvWX2pP8Yl4I7PVFN047H2sQkspL6dzFzymJgNMt4FQIcZxAh0LZvLQuHCSki
- exGhZt0kJYzhW7fXBZr4CcUT4/LxxNjsLmHJ/bebY1umcZwgR+aRkuSaiZ47AHRZ5aRqm+gY
- qwKjQh7X5m8NOXIN3aRRF+E97KoN4DW4LRHVtROI0wGzL7NLCZv72i3hZQZdqGGaH+5m3XZs
- 8zLrGtzLW2PzNE7ztk3y8iyQaXiOT0h6Cri/jWnXBmUPVMgeENqJ5QXEJ1D+VebnHeOxhUhH
- 3s0HZLEBVn4Wsr+bH7QrpAThCE0x3wFeA1ax/I9g/dfwn8P6GdAvlaoJgiiJCRAg9Njw+Pbs
- Uyz+15iRnqP/U6D/KhMQ6n3HeOt9r9oNgPuzEP8dTHDEEMbEUXDEYlcpY3AyFApfLYGvMq+W
- wHNL5lrs547xrDhEHK9ktlk5vWeNZP5ERY8LbMBTxaXuhTszylHq4kJAVy7GJRcRtU4CMqWX
- pvDhhmZ0T2VnAnNKC0uWXAyEv7SDr6nUh6Sn6psDyFhwq+KSUE6m8XNf0JVekbuHb2fdqyoP
- 3yzqh90m52+INW2j2sH4cC+v1DDNQ3t3jM2kiNeT+K0sNbldlhdlp0fdlCgevsFsIaZnzVDi
- 2UJb8U8IwIBjvA73knbtmm6aZ61KSHm1Z520jmmWcA3VHrNuy4JErwaq5pTmkSjhwLezawgm
- SjTTuifxgYZiDCGSYLPm7bE4pIQ4fdy44YwXhVUDPpuOTqnWLSenHzidQCvbvmsYLe4mOKK1
- FAzEifhiIz8XzpOXqhnMPSG2TrQBJOAoL+U49QwnmBd9WjumeEl+7BjTWg8KtID2m42HulJJ
- KUSj12h1mbWlOO82O4nggt4NsqPH8YwaHKcQ39JtDZWz5eJ1A8XCMi1sU2tvgwmQs/HfzKOi
- 6YehLdArxzjmRHHZNUHtVRDj2qYTCqTdtEIr/1jf9L2rh6aQaRMWVD6a543OQZIZF8rLT46b
- vb49a2YB2v51xzh+pKGQw9SWWfIOVeiz7iGxU0xHPCztp7GVKmQZgB+vFT33eiiG8nqYJt2J
- gqkPIGemUE+jKpRdtvgk9vnaMc45A+tN7w8l06oAZQ1chDqvDcXodTWMbR73mSiEQUchxCEP
- Q0OvnQ+BtUE13TB6FwvmFxINUK46vew2OHiYpcfO0aKKH1xIOHmvFUpTNI8hTw4ft9RAhAwX
- 2NU9cdUPPq0JaGk59Or1iXHy6Q0boSxm6X7RMQZO4yH0ZX0xe+tyYtwo1S9+C1/aOgeV00Pf
- 9Q54R+k4kcSwm329ERj0vBnXddlN2NAwTJxZVAlPxe+6pQSWDWKcFTklxCkE7wEbd911vT/3
- 1tMWlqVyPa1kBZ+Lu4bXwYVOETkaTySv5m2ucJbOwiuyh3N6J80J4kq76/X4xMSEBSv6roa3
- Azy6g/BpGR3jN8luugNxgDQgTECaTjpc6wNEpt/NmgSG76Ug+PrURS330Sk/LjubPosyIq/P
- GkBQFL6z9RxwfxtT+y0gr2TbNvAtFsIdREupxs3eIV51uk8g/grlX2cCiL95bceQ5C3r/Nx3
- bvzPQ/a38mEP8QcJnRaeDV8bivkOZZuUfwXrv4T/HNZjGBe+A1olM0LKdlmXXoSzu6dY/C8w
- uxKkrfQ0DV3FyuG4Z4fpeQL0fwb0X2R+1jGOwF0PQwTu9yH+W5jp2y5UTNdwc6VUdFieWQJf
- ZF4tgeeWzLXYwzvGh65fv2N8panGqBqWjj2Aup1Lgu6fKmjneKPJQ/TiGCWUwPAhRLvUeczt
- ohSj67dJdIVT+3uSeTDxr/Ts41vRpbxmQKUqODqAkrHSpYv5zLSdj4hSCeHhgByShK4fykJE
- 6IfhgFMkJhO/UxpLyrPkNgh8cst2TowScGgj7ZKR2FQhhqiOQLgQi03PZ4ZXkQWzT70SP/v4
- lqgknLumdD0phTejWDPOQytk08iKEgaWaZHmBVjvoyIG+/5JKC+bPYhCURTZbDLg5EcOzjno
- QsJP5gKYAHUp2W3gUK8n4gUFfQApXV43gms4Go0nzCIOeZQMagJm0osBOMnExTSnI70FLwjF
- ri69wJdXaNIeRoLCUQ/ATUoLg/IAtMOHNyPlVZeCWRqEhnf470IiPC6peFD/8LakrmLGR1wX
- tX9G+ZHBj0MsDYuJmqko4p+XSO3x+PEtoKUA2/368a3Pk936h1ZpcmKM8Tn65vwOfPH4OvGu
- GE4f9kzT17EYvBgGFca5M71gGCGchE6TAkZSqCplxt2DDMk7xscgwJRPSybX0TG2SZ3XhpwY
- kj5jMWxJwkUqhOuQyaWfgJfxfrlYX391Ol3DDodvF7k5VxbFL/ekekWEOU+P4XMcMg8fTw7f
- Oa907HDEizSnI40BAb/SP3SMZ1lEw+5X0RWY0h9RSek1Fu9TQ6No6/H69g0kTi+dEH04Sdey
- 7heTqNDz96vN3Fa1EgWK0YcrrVpS5AlT0a8/GfC6Gn9SfLwe4rUJjCAxPGLia7rmaX/q8+yp
- nmCM0rjAUDrH+Ecf39qmabfv/TSY3xa2x9KLN4yWcOA8cuQC0/bDXZvYHrBVvng2Wp9F49vb
- zA8A97cx4d8l0b10bz8hPgZaAeKvUP5lZgTxd68DhIGrz+oWFOKzkP3NfMAaVuvtNAgZ2KuS
- ZAje+b/Uc4X1X8u/wnq0lK55AZTHT3TQfrVPsfjfYJJKVHF0MRlTC4Z+AvRfZYJXAkp1xfTr
- 9XPgfh/iv4V5ZsWXXAIGJS7MpfDVEvgq82IJPLdkrsWyXZd53S/LPC+LFkUSlP0yHT26fLbb
- HBEZIUQMIJ0yzOvPVKJqiC4ueLCf/KpWXKXPSeU4cchjtz4F6JeHD/Ne0WtDoQJj327Jvtu6
- f38PdbBLficdowSns6rKnKAkmPRpiiP8tWQ+X++5BwDSfzfZ410tAj3aIA+Zt/NPikbt+kIf
- fh8dQ/pzTTF5LBdj+nNNX9YF8+MFZp7sDDZ9GIT5/hI+FC8q2TSCx1SRn9I+9yy+W/FNFDeO
- S8JzyoaCEB8Br/7ze+BF6F+nY+2bmjx+nPP1p7BoPV4cYwNxHPjtgz+BhgpfJn3jGYJvm36V
- kneMzdLmGCOMc/gxmP8MhXylsg8h1mTVjjWr+56T4gpeZpv47Sl3JPIFK8H+6rs7fLkQU4rj
- Wf2fTnbv3VbC9v95VYpw+Zv5173w9JvNb+zPF4xl+xwWfj/Txs4E7H+E8H1qnf2nj+dA/3Xm
- 14H7/ZLfx3y+yuGXly0U/saJTC2BF5bMpVhmVl2VN/L/lLVezS/cGeB3ln8hmR2+s35e2s8+
- v83LBpd/yezrvB6/q7FVt0rUQjU9nBr8rxMjJOf1uP2xYzng9bP/Xzpr983TfjxRZ7jzUrsq
- 9HCe9ieswpbTM1uhelOd4JXUQujfp3zxq5jPCX6NHHyGf5/Oj6MU/Rvy3CbdNk0/bvEsFwXH
- 2M66a9p2eHMRfb++Lb1g/uuAKa3xrPKrZKdOteN/GR/hAxkZU59zcSfFMCnaPy6EYOdesjzP
- C1bJbv/TUTe+h0WY6P/szv6lv2QaTkleDn/wuvpLV0sgWjKvi/0fsRbUJI4FPMsAAAAASUVO
- RK5CYII='
- 	) base64Decoded asByteArray readStream
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBold9Data (in category 'dejaVu font data') -----
- dejaVuSansBold9Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold 9. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 9 11 3 0 255 13 0 0 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 11 16 22 32 40 52 62 66 71 76 82 92 97 102 107 111 119 127 135 143 151 159 167 175 183 191 196 201 211 221 231 238 250 259 268 277 287 295 303 313 323 327 332 341 349 361 371 381 390 400 409 418 426 436 445 458 467 476 485 490 494 499 509 515 521 529 538 545 554 562 567 576 585 589 593 601 605 618 627 635 644 653 659 666 672 681 689 700 708 716 723 732 736 745 755 755 765 771 781 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 795 800 808 816 824 832 836 842 848 860 867 875 885 890 902 908 914 924 929 934 940 949 957 962 968 973 980 988 1000 1012 1024 1031 1040 1049 1058 1067 1076 1085 1098 1107 1115 1123 1131 1139 1143 1147 1151 1155 1165 1175 1185 1195 1205 1215 1225 1235 1245 1255 1265 1275 1285 1294 1303 1312 1320 1328 1336 1344 1352 1360 1373 1380 1388 1396 1404 1412 1416 1420 1425 1429 1437 1446 1454 1462 1470 1478 1486
  1496 1504 1513 1522 1531 1540 1548 1557 1565
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBold9Form (in category 'dejaVu font data') -----
- dejaVuSansBold9Form
- 	<generated>
- 	" Form data for DejaVu Sans Bold 9. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^Form fromBinaryStream: (
- 'iVBORw0KGgoAAAANSUhEUgAABh0AAAAOCAIAAAC0BkouAAApmUlEQVR4AexcqZ6sPtPuK8o9
- 5ApyA9FoLDYuMi4uKgqFQmFQGEwMBoHBIBCYiHwboSbd1fRwzsxZf+f95nmXf5PKVgvJQyXz
- v/3v/2984Qtf+MIXvvCFL3zhC18ADGV+28Ht9p50qkWUMj2Hp/Je89sbSDV5JNkUud3B7IBE
- qzzKqjr+U3Qr7nBzOjXKx/BLNfSjOKak+/VFNisaRbKZ7kVhbo6yCKracJ9hJ2PNumRHC+hL
- HlVVtxxPiz5koh7zWwK30UayOgaSH5lvJ5EFRXcWr312SKrRv98+jMVRwfTLSbIN9paQWXeW
- 9ur2QHFqDOorNxoK6v96ByUzvmJBbjq1HXKk0nZWqTuMX6qLOc+tBDdP4X//XTh7OJzk3frn
- 1PjCF/5YXilMrp9Owe23HR6XBb+uGy5Ixdu6rqnqJWbXd10/b8Ev4/7LTSuW7l37P6SrXyO2
- D1d/U+9UDsVQ/pMI2xY7OhnwCjDuqyOCR/P5+3gz2x9dMMObS37/oDAQuOwfBry827Z93lEB
- x+FnfbSB6f7TENax7/qI7rycbtMAkr5z8+ff0amKFISr9iOTcHF8t3x6lDTPrnPj8n1S6foD
- w49NBnaB3r0xw3lw+9O4eNzkuv4X/hy2eei76JE1vPm0a+puWFDAxDD4z+TGabn6VcpBd+Gt
- u7WxuurnxVXaNMun5vUXtlf04gPc4xN5XZaPMzgfCU+KlxC291RpVfwML8rxt3k2+BCeXX0g
- fLotYAPm8Yk6AezgL+t8B1NjikIN/lXiWyOEqtZz+VJKoeshhOn4MT73VtbD7GqrdLU8jz+2
- lbH1MPbW2P55XXaa3m6sH+vbjXbbr2ZuYbayUJU71156WRTlc/5lrHUh7OTD2JhCmCmkyutg
- te2nuauMqXr/MEUhy/6IXaeKwnbz/lMUaldwdfX+o7amHeahLfdWH8r0Vdp209iVUmpkJYSl
- ExkvTP+udzdnOc/3Ht51dF6YcV1bXeSyPjdfWiGsc7XIMtPOL7EwWSmbYWqN0pX7EX6IPLNN
- blzDKaJUdcEBomEFchOSDJUQ2q1hHaKp3fnbc66tPYxf2Tq5DMGVCsL74/Dr5A5i9sxtQl3Q
- 242oZr5oN2u+V6Dl6FGGUFNCKNfLc1DWRpnabUtvTItqD1abfl5dZWw7ovoDv92Y1Dm5UdX/
- mlyzjcm6TF/1FmoR08oSKzs3nBBC83476aJrN41tqcsOdCG7FTKDVN7KPKZjd9PWBbsRUpQx
- DKKy0xzbtRPQNqAHPrZYhmEOj5e710q347q4quzmkxa5udLCv2nRzsgjhhJCmJqfPdIYZSq3
- rYM1zfbskW5eokean95fIEMKBrxAmKpoKaae34RF8xhHultO1Yfamqpfl95oi1+NBF+J2J9q
- l2uOfXbl0Ni7K2+NLrIcISvq8TT9zfAjva7doaOJCe9hrotdVb2dYy4bwv92it+iAzBWFR3V
- o+MOeU/9W7fCQJbHx1P82YJBvfPhiXdZPC/pUwxVUKWaw9pJqO38UTHu5F7vlW0MxN+RFXDR
- RuzIcxt6S6BFtwRwuykySggUa7el1VxRKAOwop39YeSS3hAIL92KPWIz1FWsb28YySxA0nSO
- OjuWKqf57QWqX+MiLrCIymqAXlqdP0oz/Xe/vfx4vEUJuW7982dKV1klpRBS28rN59dx7dS9
- 6RBSI2duGITm0o4bfhUVHpRmagoQhLgRzXJZuwUdtZ2QD/6yHDA0mpGnToXtwqM3nl4QX2YE
- nL2dpfjxLJpblXqW9/lz80QIoBwFBrALmcoyh7QgeQVWhLiC+URsg86fbKbqAfePQXnRjOv/
- XjWsXLhwU6Hq+6o5d5Y9iRmc3eEiJNRYfbQExecttdL9iikCOAtqFdV0NOrhkcoWn6Ex1cfO
- 0XIPkwcRTe/j3bgMSqgeLLRDSO7roWuAjGduNsVNJ7DkMedGcnAS6HGNrcxjOInECa4rdhSN
- 8kkkFYi6aowPeAE/NpleEpAcglURCPnuqgma2L+LpVRSCFF2y791LQLQbsmn4KlzYGdnanWN
- z8Y/osEyVgeC++sQ5lbpxp+/XsRpC7gC1GCyhTkKiGAidmphpTDNdHClLkMbhx223ZKwgvea
- gHlRereTcY0l5EZYLtsRyWAZTBDVL868wOgq5wRGz55H3zq8+3UbEP20Xqruu9QDTZ63S9AE
- xU+MAbSX5eV1QKE9hUQgCvp9xLX0QPpc3GrJkUmHb80/bRvdhsNSRAXK8eN1NL0lsGYO5zrX
- QDSJUEqAJn1QtDnzpjkV0/nai44xu4OKMZxF5JDEVs+iJU4YQNrt/MWV3S4AJOSauSX2QmgE
- QdwMlZNTOYGqBP6J6h91Y3EqBzsQWLLS74OAjSWE4m63MFqSfvvBPBNJlgvjloCZJCE3Jmoo
- GcwF1yLkzLWQlFxITZGRx9hcVe6pbcFBeujOztKco7Yg/RhONI8wqSU9vhMRMYN5ekzMPijN
- 34I8VAX9ljQndyl9Cx6zvbCye8PMDu/dDMpvGNwsSM2CxC7SO4gR2kPj3Lp3uTfTPXpHJBpA
- rqf7Yv1oCC6P/bB9IlLncfruVxEMwy9vkE11Ed1Y1P50oQyQlf58X6zC98WcyQ5u3KV8Ajy2
- cyPwFcjYoHq7G3iMWiYhjKTuL37JscG6sxbA7S9OWKmo/cs6A9O78IhYnj1CFWgn1p83eqch
- LNdv3UOk9eTPSQn07fByP1SPTp/uhwLGkwWuOfaVK2+K3ERZN3VE0zSSvTbeNAOD9vcFzrjJ
- 8lNeKVgG/S4iKlKG5JPOCkoe62WuIrviB3ezpSKHvXzaP/BLi29gUp7xg2yuSMZgVgeaghzs
- scbRDNtn/KF0HuW8iNM2eGcSjKlm+km/SxLnhvI7BN/dxVQJf6inr0RCH2Ix3eOVUFReTI+4
- z09dveYpqOyhrriXMEbJ297cp30WQ7ttTGyFMJ5SG6RZjgBNnZCPs6uLpP44bx9intPpTOsc
- FWkLPafqoASLucQrnS8RGRHtVQ4IzNih1f8EEimdj0H4irwcLvqk3XZZvqOV7/YnV+gtUUn8
- YsbXEEmf80oM55VcgK+mA6RwaP7xPcLAenF7WG/VjyJ20gKyG07zNB/ItmDgdfnCbjHYwlVD
- KporNzEzANuluBQthbd3QRRW/2TS9VijIvIqoAXnsFwjaRLhKRG5xGm0STjNtbg9CNCUo6xc
- DyMBvwFidMC4zSXRa4SkjHBWtW03rGQvTfvcOvZNKU8rTKuwLXN4S66xlgVLZzLX8G8O0tHp
- nwYixNdIfuHSNk33Y5OZGsU5z0S1HfVqme+PohygCbYSAGVF/1kEyFfC+eQ/gU3DjFlRNv0a
- kveTChDYlS5un09lfjL+IWbk+dvgF8HHPV3i8QMQ4gOUkvTZ7McRD7sNx2NdpDzF5N/eIEgB
- b9HjRPUpgI8ItianVPdb5Dd966Z1m13bDf7MUwtttNYqO1yg2vmRjFN5LqQseOIevxBp9BsV
- Ko6es/Po6zLP83L83xERPuqYl31fFbAMfpu/1Uq149zpDALGNXXbt8XTK79oTlhRrt+/Zl/d
- EkhuSkFha/guGmu04PcRvQODi6q2PO3LV2hLIKuojncc9pfP1HF11XQdnMuqbj3XucYFTfr7
- IolFwISvQNR2zdwuOdivL2f9xe+LOmfYuGb9BNf6W1LAOrT4MtE2NnBb6rotZOW+Tcx+m/Rb
- rOxBWZls2qaum8e9pCQiXJSloq/swg+C7u2619wth6QSwlxLQgu3haEUlInxsWr3tnLrEu/C
- tOOKe3FdN61bvC41LM8JAkmOfB108ouwmpySzL50OUUdRR2eMh4VI/Fwd+0toxnKrIWp79y0
- LKPrhxkftFBaDD62FIwWJp4iGE4y3cVxM8pVvNi8eH9ccZ7C1GT4/ealx+o3Vbyw5mqty+nl
- Dt61FoTLJy3mRtF4XWjXRlAqBv+41Vi1k1+HUutmWJ927UM75BEEv87TNK/+ex/A8W7904Wp
- G7VjeK0ZvzIIb+YXRRgV5RD8EH/UE5bFq3Vu9tvcp0viJz+CBT5G+MPYd8O8LmN/d+VNUdah
- yk4x8ZJXMiivBJ/02o2WpaNdP1mltIKcMJUKGBCT2o7+eeknlKaP5Nglr/bGMfCp2cKYvW54
- aD01I9yFXpGsp3f2uXXsOb8wlvmdEo0NXrKLHuc1NqCw3c8dRVaQWgZd4QzHjyV5bJN+HMZl
- atjzijNW2rYQKb4u6H2/Cds8pZhqUHnE0sDzO3klKtx8ROzmA8q87oLyfoNmmbdw/OVdhA9+
- LNAncTIaH4/vv5SySdQ/KwO6tBK9G+/LcUopXFA8P2L41TWlyBj+y/Dg30NAmSPCpKmGeX29
- pVyD3abqMDLQpjQ3Jvtp8d7DfddKMrTVpc/+c9IE7fH+eLXSuc6KPwBI3h3B47e5sXbwj1eO
- inrza18rmqrWc7j32S7+TdnDNVfleKC3nSP4ydXquPWK00MHgvlcXokpI1L/aXFM88d5JVwO
- KOc9OCwqeGFCzPhnrtMlPlfYaNGwOvFWQNsV263d49GV+f1L6boh61ZsuhDP55ET79lGOwCl
- 3Ia2huvixz3rNR16s2Zat3WHf1F/wyZtBMUmneviTjISWy3me6IEVNvgsAKOVkJ8I3LyJost
- 8CHJLEmiYQrUTwtR8OsB79f78kllG5KFwdrpRFrMjxfDoYxJaBVLsTTWkl98Wl/CT3XG7me2
- JBN2xDETi+IlTLjAeCcuU2v3VnA0Srkawxsj4rAr5EpmNFk4YmzN0QmwMgsnLuRuUM6zwqQe
- Do6UKy0yxigXtUeToXmRMZiMGv1lXknW472Jdn7fEyVnOwgTT0zdDwWLyIqC0zhurhvXxjkc
- Y5noW1QtlzKjeHSgNWZvG3FMu18CbpIJcbbetZpoIGjF/dwJUPg4Ps9kVBN9Q5G9bWGHMNWc
- xm6qOEaoZUZpLI9XHnJGYx2X7vVkdK8na8kZpcz028Eg4+/j22bRWfytu6UWnEYF1HzsR1ns
- n4pq1Nle+tgLjmo0U+1Uy70KT0B1ELvAB6oor5Qwp38TyofD9/PxD/kLDGYcnoMRCrGwK2xl
- 8bwJbqO5H/gTKuvpmdvQeg73rbk59IxHfVVVNQ3cNTbDHqguuz0jq8KzrdKxEClMjTjpGUCW
- mNBGprWJS6s4LLD4X01CGX097ZzcsEKlT//FKBpdGsGSkTNpJEujX2aZM9O2Nnu5z+4O9d1L
- Pqjht/sdgfFuuuqF5KdXklLK4W7RUBbxoaiOPUUjpjAMlt/IR/POYTApYtPZ+8FiLeTR9vKw
- DkDEt8lNT72OhuOcEUSFHfz364zYJ3ORJm/GcNUPXACPIcsKB5JrmvT3Rc+nuRGZqU2WXqVE
- qELU95q5XXGwX1/ebx/6DdECN0HCNtcaXkHY33+Ga/01aTpISyljPwjy+EbDbUMkV3d9WWz7
- TWL2G6VXrAw1xCCZxbkq7WZnC5I42INEJQCJ+nZ5fmyRkTRQlstyetTnPJbvxSz9LQWUs1j/
- hurj8qMB1I8Io4oDA3GgmTBNbbL0WJgWal0QOWBrlND4P14AW0PlBHTB5TbnLOpCaC7L+f3y
- VN8Pgu/IqtFPtWR38gbkhDLYOudGMcbi+hwlc6mUsaVKvhH1dGdZkTxKmfNoaHYmZvSgLYmY
- ncspR+VxtrEwIiu0eyqP1mCU7eW4nwyqE4rL8a0IfCkH00UgCVmeR5JnEH+bjgUc8bfvijjP
- 6ygKrco5Y4V1j1Ysu4vY/7V3hQqS6tr2fFH+gS/gB6LRWCwOicOhUCgUCoPCYDAYBAaDQMQg
- Ivo1gZXes6dSU6em+vXMub3vvefcTioEQkhWVtbeAQgEfrt0fBa//QD4fQpZzyJ+XM0WQ/qm
- yMErUXFpn/jxXb3SPjdxmHTL1uVxfOq6tUuM6vf7JakSvrQc0BlpJTqdQLLYgL2iMhCQk4rw
- hDQmz/saqiLPi37ZT9forJmswpbOsnqpBeiYayUDi/KO4RKA2qcMoKGYdmy9XnpLybaO6T45
- tx3C6WDUeICiyNPIg6sR1YzEZREwXon5zfWrHbupONY0F6PtsPNJ/XTCOLzWLNGk38rgg1fa
- WqqJUJlHnpH/adb23bGgI8udoOgWWzU3uD/ow3FaCuIllZYNx8r7hGlMGGg+R2aBsuqtJL6T
- UdkZeYl39h+Abz9JLizSrLQpRHDs0wYCMlT7fk9875JLmF9Cto29tY9rRvG7RVEYGwLelc4q
- 0srElEAUMttiMozeLY7OHz/OK8F8BCN8mFfyk6pEW7sumw3bVHxgnQyeGovtbF1qew6uf83Z
- MyibqJ7vF7TP1cxqG2tJ+gzZW/aCMM6Ketw0E6SwUeI+yLDS9Kha3v86snBjYFdFs26n2hZg
- YoXaKJq5qpnLaIF6YSKeb8VGpYEnKZqkI8+NEWbrkzBMMuokWMZRmNaPebVANenLIDCTCUaA
- WwALgx6IbGuiVcdIRpNop52q8IMFwfe/cH2ZhzfLr7A5bubsVH3m42eYxc6hybZS3VjKsp4V
- bVuup3NJ5PAzXrvl6LknIytCWg9zluMxWSkPHdUPpPTgRObzO+lVn2GExPiM3k65UbsxE5ZT
- 5kHxqloMg8Pb1ohraFIabL4fZ2AHokl/XHAmF4zqGV8EH+SNqZOJl25eiX6YUb3cCs+hNEk4
- IwA+1/+XvhunTh6P3Awd0frrJfUvEeIvt3NTAa2r5WioxR2oDxDQ04ZgQAe+OuceJpsyOICb
- kDlRbUNWDAuyzuHflBxDWhGeNGjdlEna6Lc1glTkHPdEkLd1+qNCdjNhF7x2nkxV8Wb2eLIk
- SZklSd7Md2pf3/bCPwiwLDLRc7YlPmt3WF9EP3iQbX0cBCZugxQXqxyFQZBUI9Usp+0xMq7z
- rHbV56FT77b3dMNvIOPGPuTkPQxD4YNX2rsiS9O06ldHfCQ9t6npsROa9AiMUNW5b5tUdabn
- t3OXGlA3WNRkKFGvmRXKnt1pPyRcanf9RkTVui3TOM6LejMPvu37WMXmEx71XPDrcAE4tGAO
- mPRHZVnKL+0BPCygwmfuRm4ODPb69Ed5JRuAwovzftrI+CyqRf8O1vqqXDPkXredlOU5gonw
- EgnasquJ+0HHvLTbvo5XcqMyizS8qCjzEJgoHRSyRJSEl8/1ut8DUTRdOtKDT0iHl7HwfJvB
- PFFEVGsHkHOgtZel03HYBd4YrlNjSbEFtp+fAGafnm5NT6V30GlUWkVLmfcActaN316e5cRv
- TsDvLvIAr4Qtd1O307rEMw2hqsCQI7vdb0gYFMrqgzlZ+1J6l7dzU2dmPC2aIj45zyhrFVzB
- iUXjNsdMDw9/b6hLiCoYcptIhs04pOJAJV0VB0n7tnahL4+PTkLAGARS+kxoA9l2GcfJYXFs
- OBFmm1UNlAFeEh+/7vNKqrLwvJqo16I1WQzWAdWL2/d+aLfcLSwQvvEVJJ2yZmgUCwMWOetj
- DXyqxqiFtYYIH4IzKpXaq5jsP5M/WdQnP4iLupuJ9k+v3REAiVkc5+1Mgy1OfZMnkUewHT2w
- 47QjLBkgYD7pzWx9yDgvEnkiqre1vm4Ye1wibN5Rh4SPktPBqhgBNBGuC+bkZfB1eUnHrwmx
- niOdVaQy8QvF9XO8Utxu7vtn6SKtaKgNGUfyZ/e6NAku8ikL7P0g9lOuKJLjvBK3atb3C95q
- BInRZitZh4fG+Bleie6IymLbWoHeQmWDcWEIYRG3TWraokwl9Z4j4BhfpcMFGvQQTPW5XYXj
- k+C8EpSSg3uE+Q3b57apq7KsKhstJJpJLdIsXDvSqgCL0aj0eVbDstteLQ45wG5iDRBAbCxo
- p7nNQ/uWty4lm8DaeQX6BpNmN4t/dB7SVkx1y/qeCLuVty15xn7HnrkI8k0viUdiirlrxx5D
- thg5gHfRgxNtPf2maes98pgiyKZtW5e1DExmmDVt1w/vNimj2PSIDFBrFluNNALhYfNpX+vQ
- jjwDHBWHNrXDbt/E5EgmMjVDcWNSawGovTaRdfl8M3ei11bicmcYwbWvk9C3qthHeCWjdKkW
- faaNpwcXOK6ybQ9ZkoifVx/z2mFlYCeyMPgw6cv4p0lB92UaxybmERFRSineX+Wqlt5oh/tU
- /OyHTmKFyG5Vc5NaKi1P4jRNQ6vxCZP0PaUcjuCs4OnOzLwb24uF8d0BzuLKYImkt3e/xh98
- 31pEUiAaiyeNuHXrQ/GD7jIqB/uA3NCAHDuhdgWx7WF++X4Z1P6AuSpFx6aIM+423C9OKGPG
- hk0+bmBO4bwSttAc99xD9oAAFnqoUv/UJ/ohIg1vZexbR0gb1Yt2jawfMu/87lQpwcne/I0I
- sQt5EcSkjUQ5jumt61gwlsZJAuGACyb9SVnWPy6c3hDYgbO3buTmwmCvT3+UV+I3D9/Jc7Hz
- O1jrq3Lho1XYruqTmDVXWVlMY3n11yFH2S/kldyoDAWlUR3qIcWW38h5JbP6mJQbRH1duvFa
- auv3nKrKYzshZ+M8Fdfv/M4B5Fxo7VXpdBx2gTc2PucYPpOiKtLQDn1PALPPTtdGcRZQI5xD
- ht/Nk/FqQte6g99enOXGb27I6izi5pWIjXngkKBDUiQ8QaZHY15uQ950ZXTSN/Rb5XqoqDEo
- ygui0L9gVhVcCH4Gnw2TgEOE7WOhMShWgEYLEi+QdswcwqX+/umea2OjnGT+v9cr6dlK+Cyr
- hWNwxqGvYymsi81F1MZ5biWaQWyi4muldutsaVl/8EHmFavOo+MpeB+6B9vG3rl2aaZlrA/o
- AsH2UtAAe661q3vmjrKf3Nn2pW1+NhwDBNNqHZoytLqrtGfu2XGzkOr84b1DHs0kWiNplyev
- pFqDobcPqkuExYdTWEKUxl41Lss8pNIKc0z/N1Y8qVfy8rY3R9xcp019pDcm9d2OdFLRZDSK
- eSx9gdvgpYa+ibwneCUwcY77Z+n5uDaRsGfr9kVwI2zTNqEpOWUAz1YsBty8kjjQ9vJ2vyAA
- 1lFrIMWt1YKah7rMY0jkwDU7eCWETMKHv1uQsUEQhGWhZ/dLKeRFb2o0vq+PuY2FfiQxzpmD
- D8hi6lpbezxWMec+aGS39fW8Eg/1BczB3a31mNtRHX1pZDIx8iJURjot6wMcRuNNua9AbmZQ
- NEbS47xSUC032pb4yh2N7NlOolKP9Ct37ZLKmlRrF9t3Wu/xx8R53tSCbuPBI8hM57Wr7d4c
- UntRlkjbCa1MT2ALk4T6Q+/Fpdikqctzyg4SM22RXq2GkIRS/nlirddfMDsNyiP+9OVwKqMk
- jYGcsTfzal6JhEAWN74IYkAj8MbFEiVsuxwxXy7xFDg1EaVZlmbtvJOXEs6G+BOIERkKsqmD
- NyKC4vInNy16gb+kGsdT9OTdVgy18T8irgyg96O8H9qiaE9eKWrX66yP6KDPwjBK4ig8ohPC
- vVckfZefC0JNT9qypnY1Nx76GMdOpvZD6GR4JRFE8orFuaH2R00fduwoIo7BkYLzztZ327bj
- X0ofx9su82Hb/qsYbT15ZQRM7tvhwuMzXsm3Ojtu0Bqbu1g3pc8mjaLQtGoURWlthUHBucQa
- ax+6gP0qu25qO0F80q1jEdDPjf/mVHtt07RqNeQnbaT368FNtOjgxnVg+1AYh5nryCE3TPoT
- suKFLIGYpbUBWl03GsXWHeTmxmavTX+UV6oz8GRZeeqVusS3DvW/g7W+KpcerMFBEe6ZyrF3
- WvYuMPvEXBcqo3olPy6rk3jH+ghZWdvnAQ2t6wJRX5a+dRlNcsXxvAnkXGjtVelP8EqSvsq9
- E0BZTwCzz04ngfnFGeafjsPyzJCR5HpzJ357eZYTv7khq6vII7ySHqr8juL3iC4mAEQR9Vn6
- sjS4al/GcTmqz713AJXFPvoQBWHnhGem83w+HMdPri4HRl4x6DjYH7LEpf7hcNa9Z8qCSGp7
- k8VRFOXtcq1U65P0aPpZsdy5DK0ICFso0QRQSKX7VsmS4vERIOawpJlM4COjVFmmedNM7FCM
- O9/jtNthU9dNK43lftaCsiaElmbjKdnw0WysT9RP4nCtTyi393lIXM/2Nj+aAgfKkj8RHqzM
- YqK39KKk6BcFgSgzwtzta1sdwT1ssgyTqhuVJkGtsncjR2b06SXXPDtSv55bJV5SVYlR728g
- zm5puH5cyuqakPfESz86Ba5637qqmn6Ir9QovQ1N5o6vdJnmsZys3aqIoxBaav+X8ZVk3ZVn
- CRwFyu7fRN06o3MhPR32t7lAcIqrbfn96LetiRnWsU0dV8MpLjheAnDSR71Jd/YuGC04koKs
- SeWgLbiEG9HcJGkJZ0kc8+Flbl4JPrw2Ru/W04BN9+M70L4UljNlmnAMEA127oVgZjEgsPgy
- PUn7cJ07nLN3dRriK93YW6tm/XJeKUDgMP2mbZS3HrwSgtObARxfSuphxMaB1js2k0HJLQmh
- SyA5jLppnqZpHNoiK0bFO7NbyMMf+QleCYeb4Pf8soqWZR+du3Y8WlDuRN0m88Hdeqyh1sRz
- VWRsV8s89V1bZRFxHxgC5m651J5VKeopEmcuI8FJp2WO7TJrK/yG7EBwvdLZ/cBJ8QtulFT6
- wYVtGcrr9urFyeyQ70gE+Qyvt30ZuknhWmoeh34YEQ7ztbwSxFYI3+A2nBqJedZ6GEWRb16l
- xrHvwGdsFtATnaPsKZNHCMssTyNpqaiDiyr743OAQHgsIy77Z0bGNJngaqZD1HlovHovmiH0
- hOcb84R3OeFutd1s8T30bUeYKshhOHZC7UFepfKgzC5XXyHQ7R83DOBQMT9vO92jUrnk68wj
- 0WO80uPmblI9XR8/EFJSj5q9KdPO61Kdh89I40u3av4be47KPtXyOghVPXidHXE/AQXvwaQ/
- JAucCzFXwEoHcnNjsxenP8gr2ZEzbpe3fW3ykJzY81tY66tyDUhvfMg8IcjooZqUdlaZfy57
- F5h9Yq4blXHYQM7XpmiZhi9Ie+UCUV+UDowhjtjYW59ZVf+Fv7o6Tav17TaQc6G1V6U/wSu5
- UNYTwOyz00n4liOE1hmS3Bo5Na9Y1k7aUm789vosF35zQ1ZXkUd4pS31iG7WHaEw6dQ55JWz
- 5mIfSojQH2BS/DgPLquqRJ7cE4n57UlfuA9qwfvDUyHILvHIexxEOkTOrlzT46OZvRXhCTpV
- Q7sEgxNp6t1ki/vkSBc4ws3GXZr61ljXNflZMsyqYVZXIx+wRVCXztNN5nKRQ9Y14s+VjUZJ
- lAW+VftLz87i+6nI9SV8gQF278ZXoqaXsUOUUDBHWs3TDVu2nbJOR3S4pl93ff98cduXvKTX
- W4NW4IclW1+Sru9MMxb2hC+Hl1l0tlZDIA6YZud5cHC/euisEGqOilylFNlp4bn7Tfiij/du
- K4jr2eGH3BNW0TA24zCMC3oIP82kU2QZTPaFJHkSvtpxnUPnLiiPOZ5Vavx7sdWs+pQ3HMZ3
- 2r1Zs7cx7yxWBOc+qoavyctJEziOrx6Oq1iQb6ln4e+tUxFgXNVPRgw6QVIuUubjy3mlGJ7L
- lhGjvBKXb4h0xfyNEds7++0+Fvx1opOQASeKo9D3bnd1V4Smze3Dsj3AK2WdcdUHteTmlWiE
- wT3zH6wdMBnRj891O229MwetRxvKw0Dr5JWM54uPQ7t4wDv7UfCph310egxpe1LZEWhfvdaC
- cOUkdiGPr0TRApUK9kiCoBkwC+Q4nTLcfnB4HZ9tvHbY1gXCL0fHDTjiUfL2B46CcwKPwlAF
- l3jz2J9JYmkj3QJogVW/fbd6m5sy4ViW23Uq6BG1tSzLIgs9J2XGbO3zQxSsDYcl0s3lQDsO
- 4PcdtRumvWy6vq2iR2unFVTSA0vjffy/sBie55X4CEW1SCp7mldyGDCMKEelp/zQGy761ols
- otmwvQRLe8V+c7Kya5visy2HeXvkOmS2lS1u4A5M+qOyvLjRdMeIAy0AKj7efv15cO7/zy0f
- DJh6Hmt9XS6iasi0fSM+QemgsP9tjZe9A8w+OdeByjDS4lTHuqrqbkQR6weXxvLwlPasoMMF
- or4q3W7RBVFIHYQN/jL3LVLsyeEg9uAEcg609rr0O7xS5uCVHCjrCWD22eksbimO5Id1dlOa
- lXLjt9dnOfCbG7I6izwUtzuX4G4dNuTS9AzdxR7WVJetQxUF0hMCbR3k7YRMXWFSPHm8ROJn
- QW7muL3LIxqbKQqlILwGsb2QlAnCn2n/CKTgj4amD4hukw86wG0HvCdqybmlUXHCbtGud5kN
- Cl8vB5djGTIXoXrcmIaMxleam/SA66TeBrtV20ADm/k2ehGqDoadXnYpIp/WHJe9xoLHWpi3
- +82+Afmo70S0+9RV9bA+ABybrGjcynXuGEIlJHE97WrpmqYbp6EtQ1/W8JP6WG7BwOWHmLlp
- qyfdshPVXurRbJnOmr9ZITwZxvYBcU32fpmPK4xXBBNeeOwhsFLoh6BOWG4PbU7Hq8NZOcZ+
- 6pno2EjP+o2FqEe3wWXRhVSfcSpnswFQAHerQdNPzLX4UWNG/S7J984bYWt9VKpxQpY1Tyaj
- 4t6yKGttLWPJ+zyP3WbPeeRcNmWR1jZhLYC4PGiQBUWCyr0zZn1n3COGl4yne4X96Lz08IyY
- av91vNKCVQoRW0nwSgxLBliT7C0dsdE3hhKJcCjEBvvWZOT3OE/t5w9kG6rAEyceEnaDkTps
- UsGzzBX6Kjg4ovi1RY7X+RH7n/6eXvZ8RyDvdBHg/t2149HCn89ScLeeo6G8n+7HGAslZg9N
- X7rco67K9OwLTBLobBgoGLAmYTuTQ+67QCB2+TuAzk4WdGlcExEVwaW6+rPMBs7CuHmllxOm
- j0OCp4yvSfalte/Kjng8lLnt7WosilaTkbAsoWfiox9vq0Px7QVZkQXi1+BnG+tIehZYYc56
- vb2+dmzgueMYPM8rgftkfRK80t3z4PQ6VPWgX9VEXULmRzj9IYX/BqCO0pePXMduxhTTm1XK
- 34FJf04WRDEOXklYppsDKs8gNwc2e2X6U//fgj4/jLMe+PN5rPWludtQxllHjx2M4QFqNJxp
- GvmOsg5g9um5DlRGIWsxOgYQL8nij06Q1LsTRH1Z+hFZ2Ptgk6quy69XgKSk3gHkBANyDrT2
- qnQKcigYY8tMm+VGWU8As89Ph+ltPOJeNaZFYREAIS/lxm+vz3LgNxdkdRQBr9Rsl4/TuTIH
- r/RaU5m4oXjalTntm9iRsCmaglO3lXZfnTH6+1RYwu8JswcBPtIQZOYjN7yuWPc9a1or9chz
- s5NxWHuiJxvT/+467ELmfpxPBekE9q6/xvSMCG1hcewpFHHgPw83HWETtsNT7LOfUF8vX+1P
- FI79H2RuX2p4EtKdHu/PapuBGINufbz/oqc+bgcrc7zaHYX+TKPSD5H2JFH0iaDO6i98eUr/
- YqzQP6WefVezQdHVB+zvnRWpKo6yqh2nqcMi4V991PNQB1aL9/9pOx/ECau1v2m0Hmsokziy
- OC+unn6MRw99g5/ftfW2zl0R8RiITgPfByfpQXGuhLh3YRfhDzfGK8FWE1do3l9eG86Do3jx
- DJL4YGXfZlnLbtnPUUuzQwZVaiKGDgdnm7q6oBpzhER4zdi7rpv+5N9YOuPYEAsl5o7/nul1
- NGdcGP7sv2oca319rtPmYVCO5YYDmH1i7ssMj6N27QJRX5+OVbZm94ybplc4YzH3uxOtvT79
- JSjrySKfn+6wsalHhXeGUm789vosN35zQ1Z3kX+sbN5a0n8Kr1RFMqnnT0UHbZlnWTFsehub
- LMuKZnzuQmtfhEFsCbn7Zlb+3wbH0SCsRvW1sL4rkh8iOmX1+j/2iqzfStYufz9WmrIj2qmM
- iuH7EzMjW24sK7uZcL770lVnVpYV/a84uFjKgJiU8R/+3DS0nA0Q8Lgx9++vNOrA+wCHCG+j
- v8FUZ9/S43ofvbSR7xEZDgt6CLmTEGHWPD61fF3/V9mtuAH7WHiyUJ8wPIZoK2xHqe0bk7z6
- k9zVtmtD5DqWoUPqEerzL7KVRBrG/f/nTPXk9K5v+7Zve0wLYiMA/vft21z4zT0/uor8s++K
- GebNv9i+7dv0GT/xf9L6tu360bV59G3fFiEmiY1M8qcTavNQV+VBmmVF3f1rcqg4QvwX3az+
- hI3zpirLsp5+pTNYh+b4XTf9RbRnnWfvVja/qZJcMynCYvhL+79WT+iVv+3rP8nxNyR9+2aC
- EE7rX7ldMY99P4zTvP5XO+2+jsMwjN8Svm/7tseHhWkYECnvv2/f5sBvbsjqKvJ/cVTxGQH8
- hIwAAAAASUVORK5CYII='
- 	) base64Decoded asByteArray readStream
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldDark12Data (in category 'dejaVu font data') -----
- dejaVuSansBoldDark12Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Dark 12. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 12 15 4 0 255 18 0 0 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 16 23 31 44 55 71 85 90 97 104 112 125 131 138 144 150 161 172 183 194 205 216 227 238 249 260 266 272 285 298 311 320 336 348 360 372 385 396 407 420 433 439 445 457 467 483 496 510 522 536 548 560 571 584 596 614 626 638 650 657 663 670 683 691 699 710 721 730 741 752 759 770 781 786 791 802 807 824 835 846 857 868 876 886 894 905 915 930 940 950 959 970 976 987 1000 1000 1013 1021 1034 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1047 1053 1060 1071 1082 1092 1103 1109 1117 1125 1141 1150 1160 1173 1180 1196 1204 1212 1225 1232 1239 1247 1259 1269 1275 1283 1290 1299 1309 1326 1343 1360 1369 1381 1393 1405 1417 1429 1441 1458 1470 1481 1492 1503 1514 1520 1526 1532 1538 1551 1564 1578 1592 1606 1620 1634 1647 1661 1674 1687 1700 1713 1725 1737 1749 1760 1771 1782 
 1793 1804 1815 1832 1841 1852 1863 1874 1885 1890 1895 1901 1906 1917 1928 1939 1950 1961 1972 1983 1996 2007 2018 2029 2040 2051 2061 2072 2082
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldDark12Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldDark14Data (in category 'dejaVu font data') -----
- dejaVuSansBoldDark14Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Dark 14. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 14 18 4 0 255 21 0 0 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 18 27 37 53 66 85 102 108 117 126 136 152 159 167 174 181 194 207 220 233 246 259 272 285 298 311 319 327 343 359 375 386 405 420 434 448 464 477 490 506 522 529 535 550 562 581 597 613 627 643 658 672 685 700 715 736 751 765 779 788 795 804 820 830 840 853 867 878 892 905 913 927 941 948 955 968 975 995 1009 1022 1036 1050 1059 1070 1079 1093 1105 1123 1135 1147 1158 1172 1179 1193 1209 1209 1225 1235 1251 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1267 1274 1283 1296 1309 1321 1334 1341 1351 1361 1380 1391 1403 1419 1427 1446 1456 1466 1482 1490 1498 1508 1522 1534 1541 1551 1559 1570 1582 1602 1622 1642 1653 1668 1683 1698 1713 1728 1743 1764 1778 1791 1804 1817 1830 1837 1844 1851 1858 1874 1890 1906 1922 1938 1954 1970 1986 2002 2017 2032 2047 2062 2076 2090 2
 104 2117 2130 2143 2156 2169 2182 2202 2213 2226 2239 2252 2265 2272 2279 2286 2293 2306 2320 2333 2346 2359 2372 2385 2401 2414 2428 2442 2456 2470 2482 2496 2508
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldDark14Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldDark17Data (in category 'dejaVu font data') -----
- dejaVuSansBoldDark17Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Dark 17. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 17 21 5 0 255 25 0 0 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 22 32 44 63 79 102 122 129 140 151 163 182 191 201 210 218 234 250 266 282 298 314 330 346 362 378 387 396 415 434 453 466 489 507 525 542 561 577 593 612 631 640 648 666 681 704 723 743 760 780 798 815 831 850 868 893 911 928 945 956 964 975 994 1006 1018 1034 1050 1064 1080 1096 1106 1122 1138 1146 1154 1169 1177 1201 1217 1233 1249 1265 1276 1290 1301 1317 1332 1353 1368 1383 1396 1412 1420 1436 1455 1455 1474 1486 1505 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1524 1532 1542 1558 1574 1589 1605 1613 1625 1637 1660 1673 1688 1707 1717 1740 1752 1764 1783 1793 1803 1815 1832 1847 1856 1868 1878 1891 1906 1930 1954 1978 1991 2009 2027 2045 2063 2081 2099 2124 2141 2157 2173 2189 2205 2214 2223 2232 2241 2260 2279 2299 2319 2339 2359 2379 2398 2418 2437 2456 2475 
 2494 2511 2528 2545 2561 2577 2593 2609 2625 2641 2665 2679 2695 2711 2727 2743 2751 2759 2768 2776 2792 2808 2824 2840 2856 2872 2888 2907 2923 2939 2955 2971 2987 3002 3018 3033
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldDark17Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldDark20Data (in category 'dejaVu font data') -----
- dejaVuSansBoldDark20Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Dark 20. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 20 25 6 0 255 30 0 0 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 25 37 51 74 93 120 144 152 164 176 190 213 223 234 244 254 273 292 311 330 349 368 387 406 425 444 455 466 489 512 535 551 578 599 620 640 662 680 698 720 743 753 763 784 801 828 851 874 894 917 938 957 975 997 1018 1048 1069 1089 1109 1121 1131 1143 1166 1180 1194 1212 1231 1247 1266 1284 1296 1315 1334 1343 1352 1370 1379 1407 1426 1445 1464 1483 1496 1512 1525 1544 1562 1587 1604 1622 1638 1657 1667 1686 1709 1709 1732 1746 1769 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1792 1801 1813 1832 1851 1868 1887 1897 1911 1925 1952 1967 1984 2007 2018 2045 2059 2073 2096 2108 2120 2134 2154 2171 2181 2195 2207 2222 2239 2267 2295 2323 2339 2360 2381 2402 2423 2444 2465 2494 2514 2532 2550 2568 2586 2596 2606 2616 2626 2649 2672 2695 2718 2741 2764 2787 2810 2833 2855 2
 877 2899 2921 2941 2961 2980 2998 3016 3034 3052 3070 3088 3116 3132 3150 3168 3186 3204 3213 3222 3232 3241 3260 3279 3298 3317 3336 3355 3374 3397 3416 3435 3454 3473 3492 3510 3529 3547
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldDark20Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldDark7Data (in category 'dejaVu font data') -----
- dejaVuSansBoldDark7Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Dark 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 7 8 2 0 255 10 0 0 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 10 15 20 28 35 45 53 56 61 66 71 79 83 87 91 95 102 109 116 123 130 137 144 151 158 165 169 173 181 189 197 203 212 219 226 233 241 248 255 263 271 275 279 286 292 301 309 317 324 332 339 346 353 361 368 378 385 392 399 404 408 413 421 426 431 438 445 451 458 465 469 476 483 487 491 497 501 511 518 525 532 539 544 550 555 562 568 577 583 589 595 602 606 613 621 621 629 634 642 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 650 654 659 666 673 679 686 690 695 700 709 715 721 729 733 742 747 752 760 764 768 773 780 786 790 795 799 805 811 821 831 841 847 854 861 868 875 882 889 899 906 913 920 927 934 938 942 946 950 958 966 974 982 990 998 1006 1014 1022 1030 1038 1046 1054 1061 1068 1075 1082 1089 1096 1103 1110 1117 1127 1133 1140 1147 1154 1161 1165 1169 1173 1177 1184 1191 1198 1205 1212 1219 1226 1234 1241 1248 1255 1262 1269
  1275 1282 1288
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldDark7Form (in category 'dejaVu font data') -----
- dejaVuSansBoldDark7Form
- 	<generated>
- 	" Form data for DejaVu Sans Bold Dark 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^Form fromBinaryStream: (
- 'iVBORw0KGgoAAAANSUhEUgAABQgAAAAKCAYAAAD4kLPCAAAABGdBTUEAALGPC/xhBQAAACBj
- SFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAAABmJLR0QA/wD/AP+g
- vaeTAAAAB3RJTUUH4AYPCTYAi37+LgAAMJRJREFUeNrtfX94VNWZ/9t625mNUzJpoL0mzTpk
- AScglAFFhpQlE4o6KLIMCmVgpQks3Uz8AQ5S7FCXGik8jWxdDZbFsMtqqJZO1h/7HaWpAxUZ
- UB7HVCpDpTBRNiaQphNM052MDvv5/nHuOffe+ZWEiNCt7/PkgTvvPeeen+/7Oe95z3sIl4iS
- yTii0ein9r1TkQgikVMAgEQihkgkgo6O+KWq/mf0GX1Gn9GfNSWTcUQiEfGXibisjUQiiEbP
- XvC3juxphMvlQvDNriGVbTjfbItGEYlEEE8mh9QWF1quTLyzmjLEuzuY3uqODzrPz+jSEO8r
- bZ+cCIcRiXSKZz6+YrHEpS7u/0lKJGIIBAKIRCIIBAKIJf582jlVtg5GBg2Hut4Mwu12o+Gp
- 1y911f/saM9GDwrMYxFsS9dNbzbWocBcgqbgad3vbS82oki+Gj6fD1fLpTp+e6sfdns5Kqbb
- YCktR7i9R/C6jgVxvdWK6pXVsNsX6MZ0PN6BMiJYJ1tBUhmifX2feF231bphHjkJ4Z6eNF7w
- US9k+RoE3ujM8PtkrKpyw2KZqkvb1RbEVNtULFnigs12u6hPT3sY04tkOKseBcDm8o2lMuzz
- 1gAA5o+3wH7zYsyZZIFt7v3YuNAB56I1uH2qDZ7NLwyqLvzbFd+wwTBiXMb+6zwaQInBAPe6
- 3Rnz6O2NYFyeAY6FG9N4fX1RVgfXIkyQZXg2t+j4yWQct9lscDgcMJIJ9c0n0vLYvNAB+7wq
- zLXZ4Ntx5IL6LB6PC/kR7+7Q6Zvu90OYNNIs2jmVEokYKkrMsM9bn8ZLJuOsH2YvxpzxFtjn
- PZj2zsaFDjjm1+C2qTZ4Hw2m8bcuccA8cgoivb1DqhPXnalr+J0PeOF2V+XM70gTw5Kp4/SV
- x+rhdrsROt6dVk+/34/IqVMIhUI6WRyPdyAQCCD8dhjBoL5+PT1hFBOBiCBPrrqgvstGrz/V
- ALfbjeCx7Hi4840AXC4XGvfox807exrhdrvh39+u+53ry3CY1YXXc7PHg+rqB3SyJpmM48GV
- 1XC716GvL4qa6mr4NuwCALwZDCIUOoxgMIjIKdYP8Q4VuyaTcXR0dOi+vd/vRzB4DG+FQoie
- VeXW/icbMvaJrp4HMteTp01tI96f4RMnEAwG0RFXx5Doz3B6fw6H3lHWL6ltrqXu4yG43W7U
- b39F9/uRJtZfgQP68arFN9r+0tJmjwdu9xrEEokB1wnHQyEEgyEEg0GE32blpAONdbBarbDZ
- bLDZbLBarahrPJAxg9qZVhAVoukgU2Ytmz0gknHP2moYRnxd19CnDzZBNlvg3+/HNXIRGp4/
- qsvrzafqIFExgsfaxG9tLzaikE+oa25FLJFA26uNMBKhetNeXfqjzzag0MjeJSKdUmDlKoS/
- lVXyRHM9JCIYxi0GwBRDIRHIZBNljkQiOB1uwkjzFHTEO3RA/pOm28eaIV/HBMZTPg9MSh3I
- KKPxxXdE51fNsqPAbIZEBOvMWpG+qy2IspFmUXdDXhEanmXArvNoABZNu5CxEL7HX9Z9//TB
- JhRKBCIJ1Q8+B4BNjOmjDCBJgsFgSPtm+36/7pu8f1o2e1jbGgwwm80wSgRDwVR0xONIJGL4
- zmw7JF4WMsJd+2ORp3e+Q/AMBRPSBPalogONdciXeJklOBZ+T8c/2RLAEpcLdrsdTuc8NDa+
- qONzpUoSwVzyTSFYtW1lMBhgLhgJ96otIt0r2+tRMsIg2tg8chJC73ejvdUPWVLS5eVBlmU4
- HEsQ6WTCV8c35EGSCIZR09ERj+fkAWxhUD7Woo4XyQjb9CW6vuXjoL3Vj0JKz5vy2TwSY0iR
- ETy95YYaAMD6eXb2DdPEtLw58d+JjAJQqL9J8Gx+QX2WZPhb29F5NMDKUThN1Ov5H/p08kG+
- +jphXErrB/NIuKvUfhhS2gIZnnU7ADDFox3TRATLpPmIJRK6uWUw5MFsNkNS5l9qO/J25s/F
- EoGkYgFgO08G2G9Gi669RToje/fU3gbkE0G+ZgG+WWIGkQTXvU8CYMCMiCBPWMTSSIVobGkD
- wOU8wVJeo/xfEvM7L0/9HpfNrK5jEO3rg81EsC/eJNpyz1qXKqcU+cvpyA4fTEQwl1TodEcm
- 6u2NYKKJQFLZoMAkL1vqNwdL8XgHJhrZOGx8tS3nu93vhzBGM14utFxtrzayPCx3iN/cY1ie
- DftPibZ03rXrE63r5Ug97WHcbLfD4bjzz8qwAwCtzfWqTlf6ki/eaYzmWegYFasMhYYyfzh1
- HmWyw1K+8qLVP5GI4Z7q6jRgnkjEsOh6qyoPRs3MWe7lU5lecizZCgBYMEFm43/Vo0gm41gz
- z4nqe7YDYNhRNqo62/toEKfDTSAiWK9l39TO41e216NUlmE2myHL1+hAuarHWF7Oqh9dlHba
- /2QDxlssShlKdWVob/UjX8hWE5rCpxGPd2BmESuXocgxqD6vKbeIelQ/8CxqbtA/A4psNRLI
- OHFA2drbG0HFeAvDiNLQxu59lYpeUfBAX18UlaWyKI+rZmvO9Hs3VbN381XczuW0PH3VkN/z
- +9yqnp66POt7uYgbrvLyDDqsx3mVVytjrPTGtAX2/PGs7y3j5+sWd4lE7IJ4vb0RjBG4P91A
- +OA8u9DlHIMYNPocGBiDmgsKIMsyw/mpGFPBpkajnldkMECWZciyjIICM8xyeUbeyAKzSNd5
- NICSPIPu3ZI8A8wl7LmrLYjSPAPMJRWIJRLoagvCYiTxLLBqXp4yv4rguuPeFCwuwVwwFsGu
- LnR1BRmmytdjyFF5DOel4sBUvpSFXzLSLLCiZewNOfh5mfkFZjbPJGMafyDi5eN9ab12MmSJ
- YJmzToM5pyGWSKDzZECHObWYlPPlVL4iw+PJpKb9UvhFmfmFit7jMlmLOdW1wX1pdUom47h9
- kma9QgTXSlVutB9i36XiuRkNJp1HWT0Npbfq5uPpg02qzi4s1/G0GJbjXE4Ms0lYuMQBIouO
- x+0MBQUGmMvcg+63wVBPexhlRr0NQ8fvCWOM0t7aMnW/HxJGy1QszfFn6XiLri4HGuvYOq5i
- tXh302K2lvP+6P/BPUm1C/h2/Ap3WAiUXwyJCI6anQCAI7t8Qs4bJdbPou3DTZo1k6TT04Oq
- J7FxrK3n6YNNqv5M6c//ekDbnxZdG5za35C1P4dDfX1RlBey74XeTzd2xuMdmJZPIGmMjt/V
- FmTjmZh+zjT25mcp69Y72RrPs3GPeD/XOsFtIZClHGOIYK9i60R6+l4X7PPWIxqNIhqNsp2Y
- VdszZrDqOpmBFUWZMAWbj+UrXSCpTNeBz69zgqgMzc31IDIh0MmMP4lEDN+0mHUTnBvLVk4x
- g6QyrFvjBpER/nffxVyZQPKstMnOykKQJ1SiYrxFt2hi5VIXdqsrmEDx7VItzFXXySCSxK7N
- GCKQUQIRscGqWaTF4x2YKBGca/QLswshLjRca5/WgEAjSrmRxjgRHfE4+vqimgWEfgei7dVG
- NmHHT1INGYqgPx1ugpEItqnTUcQVvcIDmIB1FKlKw7X2abWOJgW4KwqRT+J4vAM2hSeXXoc5
- 37AJAMKMsaT/Uybz6YNNigGhEK47XIpRh6U7/BOvUt9iVHzDxv4vz7mgNk0m42isq4PHs3VQ
- 73cdC6K6uhrBUFtG/jNrnCCSYLdz42YhAifZ+H1B1NcIh8OhGFoJjjvVb59ortcYToxo2HtK
- My4JJJlQIEAYm09tLRpji5SPEpkZdBr2n8LpsEZ5af80fW7K1gc5eH19USZ8FcFstVqVMjAl
- yMvLx57ISxFU2mduIGRjyITGV9tEekv5ajx5LxfKDIym5q2fu8o4LL0VAHBTiX686oB9+Wq0
- t/t15eIbAmx8GdV2VeqtTa/98z4azJ5WyTtzWjY+1LaWYCktVf6vGs4yfdO19um0dhRgRfnm
- /LFMXrruZXN1111OBt7H3q7IMYLbF0DrVo/oS9+uY3hGec9aeR+OP1Wn1MuCwBsK2CMTGvae
- Egs3Q+litB3h4zAfTQdPCzmr/8uHv7VdlNtcNh8d3Uyp3T1dBhltOoX8yr+z+aDt69MHm8Rm
- EBsHywact729EXg8nrSNhDZFd2l1BC+bfN3dSCRiiEbT53q8uyMtHQBEo1F0c4Wt0XcA2wnN
- 9i1DiUN4qfNypRq31HKtUrzo1XL1dkZQ6/Ggbsse8VtzfT08nlqE23vE2HOt3ZM5zwy71KyO
- ZzX/zyzzErEsbdSRuY30+aeny1T3XOkY/lCfuR4jY9mgjV+XCx1+lOk225wa4a3BDQ/mSct1
- bTCXz+2UPh2ILnT+2PLVNM5Vjw7iS0Onvr4oLCShbs9x3e8tGt1pm2qDIW8Con19CG2vR92W
- X4j3fuT1IvBGp0aPWrBlWx37v2RBqLtbNbAqBte9DypGoTHz8fgGn/CEi8ViiCfjiMViIv/j
- e+pY/1TMhcfjwXXXMBlX99SbABieuGeOAyMLFJyaAX8Ol4SekQrhcrlQMd2mK0MmYguCfIS6
- Q7BocAWgxajP6NJEIhGc6oywxaLlDvScCGPJHLaJZV9WD4BtElZXrxzUxsv6StXA61p+B0yD
- 2EDh1HkqglkywTCOjVUuz9zrfoxbSw0Der3FuzuwfrFdt9aoX2wHUaHO+2uw7yUSMWyu9TDD
- sonprEzvDdSPmbDepeCd2tug4Zl0vO5u1TCQZzCk6HOG14aMQQeBMYfN45hoAIyU9TnlzzzJ
- rRt7pGCEoWLIS80HgB8uccGz8QUxlhc5nfAf0jvFEBEMI0bBJNaSMkLd3elY/mB2bH8x+Lkw
- p+gbowlWqxVWq11gPrVfi+F/zs/GdIrceP3ZBjgccxDqTjfEPP9DHxyOJWmY4uizDXC7a9HS
- EoDHU6uThX1nowiFQggEAgi9le5dGA6HEQ6HM55I/HGtGxbLJASOpju/tKVgnmg0mjGPbDi1
- 840Ayu3lGfM+qrRBqqdv5xsBVFevROhwCB6PR+edDLCTluFwGNE2vRw+sqcRHs864Ynm83jE
- hpbX60XwWBd2bfChbsseRecmxb9is91oZGOysDxt0yMaPYvu4yE0NTWn1aXzjQAcDkfWejqd
- 89LqeTrQBI9nHQ4cCKTpNn6qqSUQyGgDECee2tJ1UW9vBIucTuEUktZXCl5OJuN40OvVlSse
- 70CtxwP//nfT0nW/H0J1dXVafxwPNMHj8aE73gGv15tmXIzFYojH9fiG00aPB/WPqZuOA62J
- kgpO4v0GKAZCV83T4iX2/GTGyqcaCJll3YRlVU6xEO5qYy7w3ABSoHidmUeWIXC0M0Vwm1Be
- bodjrheAsriUbAgoRsWqVczQ1xQ+nVYWDlTk6XezysXVAcfKxSzRfX1RxWhh0XUWB6vWSrZL
- 8fLjPo0VW9btficSMQa+1j2P4VLgIWZUDZzshH+dWyz04/EOxQvFJABXNBrFznXphpTezgj8
- fuYVeFQY2lQhyRclYudDYyB8+l6XTmHqDIRGAhXa0NjYKPIHNKBEKkZj0x6Ew+GMi7/by8w6
- Y1nbq42sr/On4ViXYglXyvmcAugNpVXo6goqhlIZgZOdYveP7zSnPnPqeTuMmjtc6njSeGf4
- /X4EAgHx5/f7EQy+KcrF+9pcUob6+t06gfX+4RCCoS709kZgkVQDUE9PGBYiGEpnIhgMIhQK
- 4UBLADOvkdk7igC7TwOi2Rhj7vnCKHbdKgbYJLW/V/Od/nybEGbP+f0In+jB6bCyG2IsQ6S3
- Ew3rPIpCleDbcUTHD711XKdocvHEoooKhYcvb7t4Mqkx4i1DPJnEOy1Kf5pU0JaveVYNySa9
- opcUxUD5aHyxTd8WOQyERDKamvUL4VQDIVGh+o5SDu41YSiayQyoYjEtwbfriKYf7kYyGRfe
- Is67duVOu0Oftrs7pBja2CLpyA5FhpjYrl0iERNHEpLxOOLJOKom671g4slkWjumPguPCMWA
- zg38ns0tYo5bKlaLXT0igmPFZmHc497XqePSdpuPyZNeZQFJpHiFqHM4GY8jHk+idbcKON1r
- douxlWqYYjuF+kWjMCQqxhE+j8g4BsFjbXi8xqUrz2CJ7waLOmk8sAVANRUK+WCZqh5h8s53
- 6MaQv7Ud8XgHbp2QahBlY5l7h4rfpUI0PMvmzESd8bcQ8XgH5otdbklsMmiNqoZRJcJL2TJ1
- CeLJpNi1t825R9Tx/jk25il7qF2MvepNe/FkjbLhYipLa18uL81yiTBYO+Y4xI6q1V6lf6/E
- Ini8LMlkHHfdbNfUKx++rc/r042U09o2V93TyzUG7Yf8eo93yYJgW1eaQZ1vqHE9kEjEhPes
- v7Vd8S5lnrNtrzay+hROw6YFdtFm2/iO6tYWxRBAcPv8ynyS4Nm8R7xvrbwPZSalPF1daGth
- eRqKZmrkj6RspuXrjMh8vrp9fvFbJgMhoBr7te8ORBc6f1q2qpt5hjyDDhcAwB6fBw5HzUCf
- F8Rkpb7ur2yvF5tmRAT7AtWb+IDSLvLkVUK2AMCsQja+nE4n7Hal/W9aj76zUUwr1I8DS/lK
- 3aKDtyfPmygf1TWbchqn5481wzCqBDIfY8YxqJwsg+S5OtlhLrGwDVhFDgMMRNfX1yPS24t/
- r6/PefQpF91aYoC5rAITChRjjbEYkyxmGEpuzZqGe/nYptoEJuHHtdrbwyiTCI4VWwXIF/00
- xwYiE+oaD6CnJ4wbStn8tGr6Rkscm9nm+NDVFdR5t3P9RURwr6pC/hAMhACwZooZhglM/gic
- fqQNtVPMIGLY8EhTI+rrA+jtjaCxsUmX/sgWN0iaKLzE8kn1Usn1nonSjacA8J3Zdoal8mcJ
- HJopv0Qipnhv6sd7Nqx3WfBuUnkc9xtKb8Iq5T374gfRodkAGiwGHQrGHDYvCyYa6Fk4X0hj
- EOntxPcXOYV+DpzsHDaGvNR81eBrQmPLEeGBx/tcTe8AAMyR9cbg4bbvcJ9zYc7Mm/BMt6ub
- 0t/Ekgq2qSKX3ii8TrPhwYF4soZnGFGKpsDxjDwyFg86z8HyLGOnoqzELJ6dy+rEvM2EU3Nh
- 0YF461xOjbG5GI173hkwHfeoT/UY5qe/upS1PbelCJymOBglk3GscbvhdrsFXnQs2ax7V766
- NA0P58KgA/F09TQW6nj36Np0cHlyOn28SfHC02/IpqWVJGETSLVfMD2ix8SWG5h35sxR6Tzb
- nPuRTMZxY6mcnq68BslkXJeO49ZwT4+wwRiKZuZcE/E0oe5uHdalVINgLgMhAweqAYtZIaOI
- xWIinmAiEcNWxYBhv3kBLBLBbClHY2MjIp29qmcAB3Mr14rzzr963Cd4fBFhrVyFH9fVwev1
- wv9cKxtUhxT3Zw5CF28SoMazuUVYiOPJpDBIGkpu0hmBuALhAHPaSLMCvIywlJhhnVmLvrNR
- 1NfXo66ujk0A+wLU19ejsbElY/u8GQzC7/ez8+1vZz52sXicAVTIFvp7NYA5Hu9QvLn0HivZ
- DCl84t6o7H7zycmVq3b3jAMeLpjMk+YroJHgfigAAGkei8xwOR9Aqou18qc5zgnod3b4zk0i
- EcM0oz4dP7qhHgMZA9c8p7KQ1Csvreea9rmnPYwKcSxWgtV6PXy+HyJyqlMndLhrPz8CoDUw
- 7vf7sdzlgsy9BMgkjisBiuuyUnbbnPsBKJ6F0kQ072YGU0Me97RcAkeRAfZlj2sUXz7q6+sF
- AMrufcYM6/zoTyZPklTlCqjGWO6Blp+SL3cjzsVTx18Vksk4lpXbYbPZ4HDMQfBYV1ZPO+2u
- rrZcWQ2EfEHx0P4BxzX/3ZCXp3M7594c6QZCgmX8eF05eFvyRXcyGcdNilHNda+a3lBQCqfT
- KeaK9yeHc6Z13rVLs7uZj1JloWUey44z6NzBiUCSCa4lD+jkTqZ+TgNTB/XPPT1hYahuCihA
- URqDSG+vqgBGTcDXiwyg/GIUmwjmsdNQls/GIT8Cpho0WXrtrqvWeKA9ZsPTWRTZYJt7f5qc
- 0Ro9ensjsBDBvuzxrO8lErG0TYZOTYzYwVJPexhutxterxeVkxlANpctTxn3JnhqazGuQDWq
- CtljLEZdXR2L73G0EwHet6YxqKmpVnQRG8taebV6tUfnzbBxOTPWGUZNgM+3QZfPypVqPjpg
- ThJcd7gUY0qKR6amPbWbcmLOFDGZbxj1dYTbe9LSqfLfCJfLJXSqY+5cRW/KOrCdqSyivqYx
- 8Hq9SpkZ4NHmX12zUte2at0tGevO55p91mx4PD7Vy3h8BXw+H9xuN8LtPahb5hRA1ePxwP9y
- q66eiURM563MF8eutXuw5TabWHBwbz5L+RLhrWetrIKjxCDaVRxLEsCZHbXkeTrv2oUttyt5
- rtiGky0B1NXVYarwxJeFh/nxwyE4J6XP8WwGQl5/68ylCL99QsyPzbUe2Gw2OJ2LEAi0YPdj
- 9fB4Ng97/vBy8I1BTjvX8M2cYtTX1+v+eCiLVFo/zw4yFguvFW3MJSIJbrcb1SsVL7VjQdUQ
- LBl1XhXc88k6eSbGjVI9ydbfbIchb4TGq8mEEYY8VD/4XNqR7bkWM4hMCoYjkDwrY5n7+qKY
- LMuYfbNdjOdEjHnhjzCMQ7SvTxzDNo8cyXSQYhzrOhbE15XNpJGyWcwVfagFDdZRdFsqLuzr
- i2KcYQSajocxfQQ/qluM5oNqGbJR63N++Hw+BFpOAtBvdmbS8aoHuATX8h/iJqsVDgfzILSU
- r874DVU3r0rzrNKeGNEaCIXuN07M6vG7bZVbaScjnMvq0HUsqBhIJUgkwX7zXQBUXWSbamNH
- N6+5EZHOXhzYVidOzDir6rB4ggGUPwuHDvkx3mKBbyvb1E59zz3JDMovw7xZdsiyDOu1lQi3
- 9+CFjR7YbFOZ3MufiG+WmTPmx+fc/PEWGPJKhD7NhfUuJ14iEVO84RnGWSeOnV8ABh0ixhw2
- 7wINUDrjjGkaksm4wKba0y0XiiEvNR9gYZ+0m2u2ihqBNXn66ge3Y0GpAWSyYFJJhjVDFsx5
- sfnaeZ6KObVrA224B+1pG/maaxTDfpk4dp0LD17uPCIjPKtrMUbZtPLtOJIVp+bCoheDJ06G
- pXjzpuLNbM8cgxERLBaLcBbRYt6hYtBPm9d3NoqGhgb4fD5MtdngcMzX2YJ4WsOoCZgiTsim
- GLUz4NaLwcuGW7VrolTcni3NkAyEu9e5IVGhAISZaONCB2RZZoPAmC8637lItYq37GyE/Vrt
- bpfq3ZdMxhFLJLD+JivIOAYLKq0gMqJEsZAG27oE6HFW3YWpo7Tu8upRUKHYDqYvujINYoAt
- hN3uVULItrf6USgRzGazALZGKT1uGqdl49SyZNqF5ADasWIbANXwxo+baRUYJ7Hrfp0+JkrX
- saAQJjxwL6dkMo5AIIB7lyheJsrEFt5Gk8pRqnh4muVJYreEBw5t455iykKSezoywME9MvU7
- x/el7GBpBYOhaDqeeaZJ8ZiTGShPxLD2DhdG5BmUuGZ6Y0Yu0i40zSVT0NQU0BlhetrD8Hq9
- 8Hq98Pl88Pl88Hq9qKt7SpdPX1sUG2vVGJDasdCy2QMjSbBVqN48y8YZYJ5Wi8er7CAaAwCY
- ZiTIM1dh+RQzLBXrNEpPgtPpFOPB+2hQKD7z2G8iGAyKsev2+cXOvG3uQxnry5SrTXjp8KNi
- OmVvLEZj407FW/KYPq2y8GPeoft144/vMq5z6Q21orwl09DU1IQH7lEW/EP1IOR/msWk1ptS
- S9oFs0M5WmwovQlVwgDwtOadKrHoJ005eFvaF7PFaSIRE+3l9vl1HkAsPs3VqF75IOLJpEjr
- uHNbWlrP5hbVuDhiFEbxOVR2uyh/IhHDkw0NWOR0isWQdp6oIFxdoKvHL9iRqPZ3ld1vTcwJ
- sSMsjv+zxZ3+mDgz4NVoFwCaIym712n7QxLHUzjNz3DcUfWcUOM0pc7DVNm6fJIZVKgey8v2
- 3nDpzcY6de5yGa05osTnDADcrfSra+3T2F7F5qXWiAmonjOOFUx2a48Yc+8z/R/Thby/+FjO
- lY+QXYo3qHa+DNZAyPuvPnAiY/tqv5FIxNj4ME5EPJnEtAwgI1NZeBs573oGyWRc2TxK9T5I
- b9tB1T1fPWLyji52HNu9D7zRifZ3FcOE8g1tvVL1JY+HaSKCoaBIyY/pLtXTQtK1HV+UcCPb
- 48vU3V9PQysATRw4U6FicJDF0cNfPc7i/5GkyjRtKA4O8jllMxAe1CySOI8ZnCQ4HA4UFaiY
- wr4gPQj8UIkfzU0Nl6I1JJnNZvFHUqFuw1JLzz5YjTxDkdDZ6okBC0rlIjSdVtP19kZQqWxm
- ksmiO8bV/q4fRiLUPXUA9cvswvNr/Ty7fqNIMiLPMELEm34rFBIbsWycGeFZvZrhIuPErPWf
- ZDbDMYfNZ6drEXy+H+LlXT5oT8GUjTTDXDASFosF9psZpmGhRwi26aoBGlANtvwvEolgTrHq
- ZZCKC+PxDkwwGODb9SxmyjIsFjNImohdO9QyDJa0HoRjMngQngiHEQqFEAqFEA6fwFuhkHK6
- oiXrsWmtl3xnZ0DMda5Hek9FUFkkw7V8ic5AWFFihqFoelYDYXtKWbragrih1IICM2tr13I1
- TMvKcguIJHxDCT/jXLMLfW1RFkA9HMaWWjeTgf++XXhwu33KZnfae4T65lcQDAaxRTGEe39y
- GH1no6ItntrsyZof7+NbrrXCbLaI+Z4L611OvCO7fBmNyLY5dyqGa2YIHRQGzYUxLwbvAg2E
- viq3CG9Uv/0VzYkdow7bXiiGvNR8MU9ETFGj7pITracvjwNYrkk/EOa82HxOmTCnuoE/jnmd
- Sdy4HVQxwPRl8C5UMZlvx69y4sHLnpfylwun5sKiF4OXuvkzVAPh9lVKPRY/nhFLXggG/bR5
- 3BbE46wWFJh1tiBeR8vYsWpokpQ6ZsKtF4OXDbfmwu3Z0nyehkC/e7eTrsjLI/qr7O/c4dlA
- 1i/1U5KKaUHFeOojE3lq76MVi2YTEdGZ37xEm5v+k8orZ5BE+VQyykBEf6Qzf+gnIqIrrjDS
- h68/TY/84rfkeeQJKjp3hsg0lXyrlxLRh9R2+k/0taKriIio9cgJumXJUpKUb5vHOmju38i6
- 8uRZR1M+EZ078Ra1/elP4vePf3+OkillLyycQbt3/ysZr7iCiIiKJy+k7o9BZ89GaaJE5Lzv
- WYp/DDp+oIGIiPr7O+kG8+foc1+aQp39/fTor9qoo6ODOjo6qHnTMurv76QpGv5vn/0pfUAm
- WuGZR0REk+12kojozDst9N3vbqDf9RERjSTbJDOdP99Pjdu20abnD7F2+90+evjhh6mt60/0
- +/f20aQJs+lkHxFJxVQ5KY/Wrv0n6vnoI3rtiYdpzpxvUU9PD33hiyn1+8poKjAXUH/XKTrd
- myAionNnTlDrsVP0weFmuuWWefTII4/Q1sZm6icikkx0VaGRpi9xUT4RUbKX9v1sH8X6iYgM
- ZB7xBSIi+v17++inr/2WiPLp4S13ie99+Kce9eOiLHGKnz9P//P7NjKMK6Nnfv6fVH1zJWPJ
- 0+iWiTJ98OtmMn/uczR6+j8QEdEHv26mkZrnkilL6ffdHbStro6KP99By5bdQn8lSTTllnWs
- X2Jn6OXmZgoEAtTc3EzNzc30zO7dtO/N34ryfu0LnyPT6FLauO3f6Po5CykQOEA9b+9Si2sq
- IJPZRPJXRonfbpg2hc6dOkF/PdVGRCepsrKS3uonOvPaDvqPt/qp9u6VtKPxp0REZMjLo9bW
- VhqRZyAiop3/ulNti/5eOnToEP0hnhA//d1iFxvTLz1Ec2/7e9qwYQONG/03tDv030REdJ6I
- qD9Kd1VV0bivjqbWD4lIspD3bqfKT/bToUMh2rdvH7300s+o56OPVJ7xy7TinntoxYoVtHBh
- BRERzVjqpkIiSnTspzLbbPrr2bfQV41ElDIzjF+dTEuXLqXa2rlkSJkz52lgstywnGrm2oj6
- P6DbZ0ygbS/8RvB6Tr1CtbW1tGLFCtrw/f8Qv5+Lf5l+sGkDjTTL9HD9FspP9Kfley5uosd3
- PExG/oNS7Ntum0tERId/9gNa4bmfls6ezdqLiql2TYVIL19XTT09PdTZ+R7tfPIHZLziCpF2
- /1Pfpdq7vqtLu9Q9RaQtGPctOtXeShaJ6NxxP9X+8y/pv0O76eqvjqPDb52giTNmkFmiQZF5
- 0hSSJSLqP05LF36HvrNsA31IRGQYQeYvsDl2z3dWkEREiUSCiIxUe5+HiIiuvHI02UabRV72
- 2W5aVDFDraP1errKaKT3Duwkz49+SkT55PV6yURJemJjNTX/+gPxbtGXeT7quHxowWx6rYM9
- j/7yOdFXzXtPqOPj83o1suTvXUR/+DUFfnNmcA1wgfTqgX3UR0S2OTV09612ZQwkqf+8ZlT2
- RWnD9zfQvveZLDIXmKikqICNj+e30rYntlFtbS3ti/yezp9nY2y//xH63vfW0rsfsiz6z58n
- SwnTOYZRX6empiZaW1NNNtsNNMNWSP/b10/niaj/I9ZOX5SUfH5WR+5FC+mtD9PLLn9tNH30
- UY+YaboyD0DWa61kpCTdf4uddv7yvazvyV8bzfpHGYfx8730cZb3UstiGcPq+/LTD9HmRx6h
- riQR0RVC5ou2fej7urbVtuFDD20Qbaj73tgJQsde8bGRltZ6qaGhgcaYiBK9Udr581foyq+M
- ppESEfWfprVrv0eHXj9N5/tY3mfeCdA//mMtHe/TlPdvV9DssWZK9HTQmX4iS/kCqrSMosLC
- GXTdWDMx4VBI3ge8JCk1tU6vpIIvfpH+O7SbNjYdFuV7Yr2bjv/xj1Q8eSHdcYOFqO8P9Id+
- IssNLM/Xt6+lirs3UR8ROW65mc5F9tLxM38ko/EqeuuPoM1LHEREdPzEuwP25ZnYOSIicq7a
- LvRPSflS6kn20759++iDWD/FYjGKx5N06D9/MOgxMlT6l9feolnFRGSaQp3d3dTT00M9PT2E
- j7tpaXlJxjS/ePEl+p9EL53rZaPKPMnGcMKH71H0TBe99MB6Wrt2OxER9ZzsoXxFvhj+Kp/G
- jy+jwL/uov7z52lzzQbqJ6Lv3/m3dH/TYaLkb2jtxueoemMDHXrtNbpxLEvnmF9Lv9z3Mq39
- 1mzq7++kFTeV0+yqjURE9NLrIbppsoWeePRROtlH5FzpzVhmo/Eq8iyy0/5fvkZ2u53efesI
- 7dz5GM379iZyrKih0VdeSXl5o6n6uz56uG4jk3e3M3nq2rKb7ppnp9bXW8nlctH+p7y07VdR
- +uIXC2jKlCnir6ysjMqnO2hK6deIiNJwodF4Fd29vJI2fftb9LvPy7RzZzOVSb+hb6/aRM5V
- a2n0lVcOut8+PtdDhw4dor17W+l/8wxE3Sdp3759dPjw74iIaOyUKTRjxgyaMWMGTZkylmwz
- ZtDChQtp7tw5Yg5mo573D9HD/7Sb/kRE1Hea9h16j4iIvlRaRqVXGSmukVlG41W0/3QP9X9w
- mK4yGjPmV5xSFqPxKrq9ppa+5/OR73vfpbkzxxIR0bP3zaXGUDd5alfRwYOt5K7dQi/983K6
- 0jKaKisrafz4q2j3zp+SPL2a3vvJevpNH5NxzU+so0On/5D2nnnSclrrmk3nDr1EG378UzKX
- zaeH/+F6uvIro2nhwoVUWXkt1X//CZJnZs7vo496aOGk8RR457cUzxtNlVMZJsyF9S4n3mP1
- OylJRNbrK8nn81GZzOZT5+kTdPjwYdq377+oee8JPQZdWE3fz4RBc2HMi8HT0FCea9a7FKya
- pNYD/0bXyOX0QZKICqfS3GnqGvFCMeSl5vf3d1LlXxup8Y33yL1qDdnkfrp/4Tiq/cHPiYho
- idKXRESVlV+nv6+4nkKa9ANhzovN55QJc3JK9Jyg5uZmkr4kk2vJWvJVf0Nl/vEcue57mJbO
- tBIR0VtH38uJBy9b3gKFRybyPvAjeqy+nsrtdnL93SwNTv0X2vlvOwVOzYVFLwZvuGS5muV9
- eO8O2rw5M5YcKgb9tHncFvTe0Z/Tx2fOUP74b+tsQddew7D2e7/7Hf3tN+dQsaSmzYVbLwYv
- G24VlAG3Z02TGoPQv8Y96BiE2ah2ihmGCcuwaZkdZJqm26nsagti3Ait158RruU/1O2IzipU
- LcovbPSo8eIs7Jaw7vdDmCKrlnfDiAIUKF5omQJvs1t29Dss3KXSs7UFA1G2S0rEkcIsxypS
- Le8rp5hBJn3cn60rtcd381G37RfqN42pFn0jsx4fTHfNz3ppiGRC9dr0S2d4vBEen4wfq9Gm
- 0wbi3PVAteYYjaSLkyCs5zfob0bs64tiZqk+ppetgh3zFbdm8b4tmSYCcKrWcXZEhx9ByuaB
- 1NcWxY+8XnGcaSDqOhZkV44rnnSZKJOHG49lY1+wBtvq6lBdXY0lLhdkWY1ZIZPek7X9XeVm
- WalYeNeQph2tk28RO2q7H/Rqbk9maXgMA11/S0ZYr60UcTLT+JrxoO4MZB6jxwNNKC3QB62W
- r56O0Pvdory8H7LGeTFpLtbRxNFU07M2XCNiNJgytAXrX/576lhSj0w8l/YOj7+ireNj91Tr
- jn1p44qk1iuVHrunOiXAtXrDb2paPvapsFzcpKetk/X6Rbr5nnp0hNPLj/v0fW+yoCmouRxD
- 4zWaGjvsac0FMIGTnTr54F7H4gWWK7G8nFVMPvJYa9qjeNo2Tv0t9c+1dk/GS0oA9Sgzvzgq
- 0yUlnwQdfb4hfdznp3gQGo3quL7mRnG7+kolfg0fj00HT6OvL4qKlAu0eMypRCKGO79h0/FE
- fCAeAkEZE4lEDFWz7cgzGGDOsJvI31WPfuWLXcH8lHHJ5LTeg7B6014890C1iO+Xmi71G1wH
- xXJ8L7UsyWQ8pb5GVD+wSy8HpPS2zdyGpqz1E8c6xLhnt7glk3Es1dx461yzS3gpZeofADj8
- E6/wgNYG6Bfzw2TDcY1HIb+0jMW5Yzffitu9lUs/1GMZKn5ID72g9xIWl8ncq+KqbB6EPiXU
- R+qR34tFuS5cY95og4+plwkPPr/Vp5uTXPZnDFOiHCV+rKYa1fc8JubOGrdbXDKizoHcMR0P
- bKuDy3WHOPatPcmQiXas86CAhyDJK9CFFxmI3laOd58Ih9HRfeEX6OxY5xG41ZBXkDXweS7K
- drx5ODeap45vfsJDexHgykkWOJctGvCSkpZAANGzQ7sJkh2X71VCBaUHpv+nW6zgly20h8Pw
- +/2wSMx7XrvWEO+9352Gp7U6bqD8hJevoitPRSKIJRI5sd7lxOP/8tA/q9OOGKseXLsf9KJA
- e4mJMQsGzYQxLwYvC9Yc6Dn1+LIhbwTssxYLrD1cDHmp+YlEDFWz7HCvYZ76fX1R3Gy3i/Xj
- NBPBUFSiXmKZIf+BMOfF5gOZMWfqukFLvF8t4ydpMHo+Gp49mhMPXr48E1wul76dNKfsvjPb
- rvH+HRiLXgyesGOkzK1MeDPT82Cw5FAx6KfN49TTHsZ8hwOe1Q2638U6MEPaXLj1YvC07arF
- rblwe7Y0tOsuJ6z2pQgGgwgGg1hZYct6i/EnSaf2N0DKco10R0eH/pabWEwcf9VSd0dHxt9T
- id/oZJjAQL8w7KUY64ZK7MIRvXDLRRWyOaMBk9fvk7opjx87GUzbpFIsR1l4OfklKIMl3k+p
- 6QZbThZTSkJ9c+sn0j7DoRc2KmDRJMPpdCrHTAd3NHqwxNrkwoKfD++bwxuDahyv4ow3iH3a
- NJx5kEzGcepURByvdSzZOOi0sQucJ8Mp76Ug9ZZyQurRuJU3WGCdWaszDAxn0ZqNEonYgO2V
- TX8IuRvXj/lcfTcYGRiPd2CuzQaXawkWKjeG8piRQ6G9TzagOEM4h0+T4lx2a/Rk6vGGTG3L
- 2pUbtU05yz/UcZ9anotFPW+HUbtUCaydcvNeLtLGVuJxb1MNWolETBjtmW47Mai8Lydarmy8
- pvYti0Mq5byRd7iUGoPwQGMdZLMZhrw8WK12EZfqMxo6idAiZeqlTqnYYM0sO9y1tbhGvjor
- 9jnaEoCFCOZptYP67mCpu6NjUIbZT+q9EwF+QZcRI5VLFxv2Dy1e7p8T9Z2NYkm5BUTFQzru
- /n+RBtJNl5qfjd4Oh8V8/XMs/2Ao07o5Fx68nHi8XXjZ+XOm22hf/HEdiAj27+hDZOXCoheD
- N1zKhCWHm+7T5mWjtlAQweAxtR8zpM2V5yfJy4Zbc+H2bGnoyJ5GOJ1O3V/jniO42BTv7kAw
- GPzEjGID0SlNEG9+iclwdn8BFoslGAx+KuX/S6YT4bC4gfhyoJ4TYTzg9YpAs9kupPlLo1JZ
- hvVaO/wvvzv8zC4TUm/EHtjT+C+Nksk4IpGI+MtEXNZGIhFEo2cHlW/qZUkklV3qqg6JeEB7
- 1SN38gXNCR4Xzlax8lPTk4Oh1FvscrVDRYmZ3cL8CW6gfFqkBgmXxS3vg6UXGxvh8/nQ0MBu
- weOee3yTMpmMY3t9PXw+H5qaAkPKeyD6tObPY/dUw26fLTzZtRS4AM+xoVAyGcePvF7Ubdkz
- /Mw+Ix2x+MsE+7z1w8pn/Tw7zAUlwqvpz5WSyTi2rvbAarXCarXC5Vp5Ucf2paZfPe7DSHMB
- 7LOrLiu98xl9Rn9plEjE4BxvgVw0AU3B48PP8DP6P0/ZcGsu3J4tzf8H3Df6S1n8FGoAAAAl
- dEVYdGRhdGU6Y3JlYXRlADIwMTYtMDYtMTVUMDk6NTQ6MDArMDI6MDA9i9ZSAAAAJXRFWHRk
- YXRlOm1vZGlmeQAyMDE2LTA2LTE1VDA5OjU0OjAwKzAyOjAwTNZu7gAAAABJRU5ErkJggg=='
- 	) base64Decoded asByteArray readStream
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldDark9Data (in category 'dejaVu font data') -----
- dejaVuSansBoldDark9Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Dark 9. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 9 11 3 0 255 13 0 0 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 11 16 22 32 40 52 62 66 71 76 82 92 97 102 107 111 119 127 135 143 151 159 167 175 183 191 196 201 211 221 231 238 250 259 268 277 287 295 303 313 323 327 332 341 349 361 371 381 390 400 409 418 426 436 445 458 467 476 485 490 494 499 509 515 521 529 538 545 554 562 567 576 585 589 593 601 605 618 627 635 644 653 659 666 672 681 689 700 708 716 723 732 736 745 755 755 765 771 781 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 791 795 800 808 816 824 832 836 842 848 860 867 875 885 890 902 908 914 924 929 934 940 949 957 962 968 973 980 988 1000 1012 1024 1031 1040 1049 1058 1067 1076 1085 1098 1107 1115 1123 1131 1139 1143 1147 1151 1155 1165 1175 1185 1195 1205 1215 1225 1235 1245 1255 1265 1275 1285 1294 1303 1312 1320 1328 1336 1344 1352 1360 1373 1380 1388 1396 1404 1412 1416 1420 1425 1429 1437 1446 1454 1462 1470 1478 1486
  1496 1504 1513 1522 1531 1540 1548 1557 1565
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldDark9Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldOblique12Data (in category 'dejaVu font data') -----
- dejaVuSansBoldOblique12Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Oblique 12. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 12 15 4 0 255 19 0 0 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 16 23 31 42 53 69 83 88 95 102 110 123 129 136 142 151 162 173 184 195 206 217 228 239 250 261 267 273 286 299 312 321 337 349 361 373 386 397 408 421 434 440 450 463 473 489 502 516 528 542 554 566 577 590 602 620 635 647 660 668 674 682 695 703 711 722 733 742 753 764 772 783 794 799 808 819 824 841 852 863 874 885 893 903 911 922 932 947 959 970 980 991 997 1008 1021 1021 1034 1042 1055 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1074 1081 1092 1103 1113 1125 1131 1140 1148 1164 1173 1183 1196 1203 1219 1227 1235 1248 1255 1262 1270 1282 1292 1298 1306 1313 1322 1332 1349 1366 1383 1392 1404 1416 1428 1440 1452 1464 1483 1495 1506 1517 1528 1539 1545 1552 1559 1566 1580 1593 1607 1621 1635 1649 1663 1676 1692 1705 1718 1731 1744 1756 1768 1780 1791 1802 1813
  1824 1835 1846 1863 1872 1883 1894 1905 1916 1921 1928 1934 1940 1951 1962 1973 1984 1995 2006 2017 2030 2042 2053 2064 2075 2086 2097 2108 2119
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldOblique12Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldOblique14Data (in category 'dejaVu font data') -----
- dejaVuSansBoldOblique14Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Oblique 14. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 14 18 4 0 255 22 0 0 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 18 27 37 51 64 83 100 106 115 124 134 150 157 165 172 183 196 209 222 235 248 261 274 287 300 313 321 329 345 361 377 388 407 422 436 450 466 479 492 508 524 531 543 559 571 590 606 622 636 652 667 681 694 709 724 745 762 776 791 800 807 817 833 843 853 866 880 891 905 918 927 941 955 962 973 986 993 1013 1027 1040 1054 1068 1078 1089 1098 1112 1124 1142 1156 1169 1180 1194 1201 1215 1231 1231 1247 1257 1273 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1296 1305 1318 1331 1343 1357 1364 1375 1385 1404 1415 1427 1443 1451 1470 1480 1490 1506 1514 1522 1532 1546 1558 1565 1575 1583 1594 1606 1626 1646 1666 1677 1692 1707 1722 1737 1752 1767 1789 1803 1816 1829 1842 1855 1862 1870 1878 1886 1902 1918 1934 1950 1966 1982 1998 2014 2033 2048 2063 2078 2093 2107 2121 
 2135 2148 2161 2174 2187 2200 2213 2233 2244 2257 2270 2283 2296 2303 2311 2318 2325 2338 2352 2365 2378 2391 2404 2417 2433 2447 2461 2475 2489 2503 2516 2530 2543
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldOblique14Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldOblique17Data (in category 'dejaVu font data') -----
- dejaVuSansBoldOblique17Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Oblique 17. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 17 21 5 0 255 27 0 0 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 22 32 44 60 76 99 119 126 137 148 160 179 188 198 207 220 236 252 268 284 300 316 332 348 364 380 389 398 417 436 455 468 491 509 527 544 563 579 595 614 633 642 657 676 691 714 733 753 770 790 808 825 841 860 878 903 923 940 958 969 977 989 1008 1020 1032 1048 1064 1078 1094 1110 1121 1137 1153 1161 1174 1190 1198 1222 1238 1254 1270 1286 1298 1312 1323 1339 1354 1375 1392 1408 1422 1438 1446 1462 1481 1481 1500 1512 1531 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1558 1568 1584 1600 1615 1632 1640 1653 1665 1688 1701 1716 1735 1745 1768 1780 1792 1811 1821 1831 1843 1860 1875 1884 1896 1906 1919 1934 1958 1982 2006 2019 2037 2055 2073 2091 2109 2127 2154 2171 2187 2203 2219 2235 2244 2254 2264 2274 2293 2312 2332 2352 2372 2392 2412 2431 2453 2472 2491 2510 
 2529 2546 2563 2580 2596 2612 2628 2644 2660 2676 2700 2714 2730 2746 2762 2778 2786 2796 2805 2814 2830 2846 2862 2878 2894 2910 2926 2945 2962 2978 2994 3010 3026 3042 3058 3074
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldOblique17Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldOblique20Data (in category 'dejaVu font data') -----
- dejaVuSansBoldOblique20Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Oblique 20. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 20 25 6 0 255 32 0 0 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 25 37 51 70 89 116 140 148 160 172 186 209 219 230 240 256 275 294 313 332 351 370 389 408 427 446 457 468 491 514 537 553 580 601 622 642 664 682 700 722 745 755 772 794 811 838 861 884 904 927 948 967 986 1008 1029 1059 1083 1103 1124 1137 1147 1161 1184 1198 1212 1230 1249 1265 1284 1302 1315 1334 1353 1362 1377 1395 1404 1432 1451 1470 1489 1508 1522 1538 1551 1570 1588 1613 1632 1651 1667 1686 1696 1715 1738 1738 1761 1775 1798 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1830 1842 1861 1880 1897 1917 1927 1942 1956 1983 1998 2016 2039 2050 2077 2091 2105 2128 2140 2152 2166 2186 2203 2213 2227 2239 2254 2272 2300 2328 2356 2372 2393 2414 2435 2456 2477 2498 2530 2550 2568 2586 2604 2622 2632 2644 2655 2666 2689 2712 2735 2758 2781 2804 2827 2850 2876 2898 
 2920 2942 2964 2984 3004 3023 3041 3059 3077 3095 3113 3131 3159 3175 3193 3211 3229 3247 3256 3268 3278 3288 3307 3326 3345 3364 3383 3402 3421 3444 3464 3483 3502 3521 3540 3559 3578 3597
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldOblique20Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldOblique7Data (in category 'dejaVu font data') -----
- dejaVuSansBoldOblique7Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Oblique 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 7 8 2 0 255 12 0 0 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 10 15 20 27 34 44 52 55 60 65 70 78 82 86 90 96 103 110 117 124 131 138 145 152 159 166 170 174 182 190 198 204 213 221 228 235 243 250 257 265 273 277 283 291 297 306 314 322 329 337 344 351 358 366 373 383 392 399 407 412 416 421 429 434 439 446 453 459 466 473 478 485 492 496 501 508 512 522 529 536 543 550 555 561 566 573 579 588 595 602 608 615 619 626 634 634 642 647 655 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 667 672 679 686 692 699 703 709 714 723 729 735 743 747 756 761 766 774 778 782 787 794 800 804 809 813 819 825 835 845 855 861 869 877 885 893 901 909 921 928 935 942 949 956 960 964 968 972 980 988 996 1004 1012 1020 1028 1036 1045 1053 1061 1069 1077 1084 1091 1098 1105 1112 1119 1126 1133 1140 1150 1156 1163 1170 1177 1184 1188 1192 1196 1200 1207 1214 1221 1228 1235 1242 1249 1257 1264 1271 1278 1285 1
 292 1299 1306 1313
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldOblique7Form (in category 'dejaVu font data') -----
- dejaVuSansBoldOblique7Form
- 	<generated>
- 	" Form data for DejaVu Sans Bold Oblique 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^Form fromBinaryStream: (
- 'iVBORw0KGgoAAAANSUhEUgAABSEAAAAKCAIAAADEugyPAAAgrUlEQVR4Ae1doYKtuLLli/IP
- +YL8ADoaG4tD4uJQqCgUCoPCYDAYBAaDQGAiEOftZEF2YDe3d0+ffmfeu6fmzh12EZKkSKpW
- VSV08OvnaNOr3n5vlcs8Lyvq1I9rc/mX/tJf+kubni296pxNL7j1JXUxNUrm9fpJo6tr8U1a
- rQr7z5Xa7i7vN/rKdD8/L/+X3qZtXdws0suEK5CdYov5/Zf03A/TMo/DtP4b3tlsafl9WGHp
- KynVf8+sr5MwUsMrv4pDntb6xNRlHIq8VAmPy/HMFzKXIWV5O/sPDEUiskf5KGtO/E6ygAsW
- UKjg79PSSsZzfWbOdUpZ0ntNTFXCIlkVaRgpV3ibqognhUqipNQHKw2ZGrS9LBnl1bjqsQhZ
- XFY5Z/Ev3SfcXEdR9slyGRQXUgrGRHEd6zYmlGa9fpH9IAhJIOEnTTFlaVHEIS/HzR9lahsg
- VHTrqZZC8CRXMRfN8vZs2I6a17O+072grJy2D7pKKV6uV7gTjOdVIVh0bloXcZQ3dRrFl0E3
- acjiYn3Tws6L97RuVJZXw4eFhyr3rTwKZ0W7nRVa143rOvXj8mxlGoZxnoYHT3syyIKAkoAo
- yP9M3wce0Dx+3UP9KFzO9+p3W7pMZu3smaqxydLMzosul1k9ajOFh/7xzNAPRyGjNrW90ttT
- l/Ztv+rlUdbhjLbI8rL/WLa1SjPXNxTOM9XoF9nqR52ebPUy9uM0j8OILnydxlpJNPRCc1dK
- qSZfhpWZH8tVhvP6YsIwXtR8A6Lw9DDMeAPmVqDHMuI8ssS5KMeXjumOB0EQZquZQ3kQRHWT
- ESa9xpcsZHk/VXGY1NNzsqY0iCv3MuqUB4YY1n8rWRAIb7qs5V4gIDy3laM53ulDcKV43I3r
- 2YqqfFxHxWgd7+WXbkP66JL+XThnruKAJNOhTzPB0Lcoa7adVwseMkoeomkPWUy1NIxzyaXN
- Dl4QQkcf1OdmRCTMjvGaksTSY+BHtVunErZXQaHWW8lNQWrI9EC2dvHUwpXjEtNIT00cUsg1
- KbGEfpyGIg5ANH6q9XWqiywRQsSJqtxbdS/XPkJEf8zfUrCAgGgYpf0K9lykEUXlhKbVeDxr
- y1EaclF2WNeOT83/AiLb9WMmhFykIT2kx6Jq1HsfAlqM2r4sMz+9SgJRjM4WxtQMdth+eXen
- x5jziFkxlOfaQOAENCo0DIygATFrzd3Cm52qBE1DR+YxJ7sEmKwGX1ygMMrQyBuFaZRWh2hb
- O1VATA2r7tXjWTvJUNZMS2+AprZBRY/rtJnXLnNMyzdzG9ojzDrzlJ0VXJrrOgnN3d0sBSyu
- drBil85jDky2iSjv7cxpI2IGYLBXxvH60Ckjz8G+nSzc+531v5aGeauyEgEoaZbjdRXMiF3d
- 2GyUKc1wquk/4bYmsaqxf9v9aJkZR3p3HxMJ9KVG51pg7Nefrnzul/eZ/0bSYxVHQkJf/Tuo
- z6PAUmxm0Zra+XS8tT7EvRCW657enH4OtpIgzNrfJNM+k5U+xXLa5Fjv/MOZMFcMustMGEmM
- aVYGZ+RJdhj6ba4jGoDyQduHHoKK5OP/RI0y61CJkFFKWRhXw3PQa5cTPMnS6XuDW4c65qFt
- QvhNLE2KFmjaPkop6JHoHqzDK8AzoYT6IlZAh6tm9FWkutt5UqZsV02BuLqmrx5U4BT70uYM
- ejpMbyD6qqwudygLKleN+vO7MC6GWDVtp7v3BFVvdS3s8pn/uMHiC3+qUkoN/zKEeecn4F/K
- kxd+n3G8t3p51ZCE7CYJdjxgZop+Ag8oM3SBAZQ65gLmUZBRQn1mGOJ5x0weT9k4wlbGLCAh
- 3Etj10hYzUC8YRDgGtrjgChRUo+rBwBIlHVYYq9Wnhhyhtvxgf7CCx9CoYxn9cf8/DP+Pek6
- ix0+EomZuWnnYaHSivoAAxeMNBbiwk+qCZDglY9r8E8wYOuxfD0odZ40a2fnOChsFgfLTSXF
- i//fKzPHvKDPVifUU2UgjWXp7CmojY2Se/wfL6dn+21KI5kwSOYfkr4BHgvwlerPmNkQt0IG
- TaXRvJ76XTIjqmw9KidG3dYPdWMGDzSyNkbIyYNBj1UpsIIe4nDBsjY9hBuV21nB5r4W8Jw1
- 2UyO08oQT8uncLaCByCadifZsliYXvf/UIaDsvZ5vvBn29vYwxVDAbN+EvhgXnkUGw+1OUUb
- jQRoOaz/Ef7pjJinjejsFAyWJhWqX9dlWdahiJP62q1tKogxtLWdw/JRZ1mlAUlXz7cnAWmW
- 8SEZ2W8W4cngILigesjNLO8HSc1MXVoz1GfQCzU/iCVlkQQ0XZ5M2qAl3YUWxDiPOzaTxUwd
- M1BqF59FQK5KSYLEKsSv0yQeTanDIbErm4YRHFgs7FEdswOuOIRrFCZPYtzae96mLGBCJpHP
- 9M0/BuX8BLjYCC7Ah9kDD+pRPbFC0zkPMF6Q1ftrRu16S7M4NHdSo6wXrIsoTbnhhajzLRzY
- ljnm4v1EzrNieAlqAICSKIa8dsdmqRnUQZwmEbNXSp/iOCBazWDNCYG7C6mjntVIGOKIrKzS
- 1hg2M599omjT50Nv3jG7w0OjIecsOKSHPjD7yrZKUKtNVlSCMg5BmN9U4jfuZm2/QzrEp4/a
- 3EPgWIoG43/JfWxxhVv4MWMK7U3Ph6JjIdtLVLOr6klMdm8XhtbTkC1hPAopJLOadXomEpug
- cvIcfiUoaoBeo2kDZzK07cKrpMYbmWNiWUaZdrYpgYUsLLuZx5S6yexqeAx/w1KDow5ReMSt
- ytkKI2pWjetmn6VYaKBtLQR5wrW15U5K6O0NzW2p6tFPiBstqU/JFvOiu2Vbr8tAr4+i2ykH
- uhoDSCCNg9ZzhbqTiMgs6+oaRYlro/36eFh7wWmVq27eXn921rZJb+V7TLTy7Mx2XOjX5f7C
- 1OuqHeu1Hkfba32gbVmW/Qry8sDKvywEgFnKmwmdXCWF2+aGONgom/zc3rw7/WboJOc1fZOW
- Jg7YKY9XCSxIIUISFaMeqvKYD32hrJ6DAuHd3Edwz8yMWlOC+IKbjSTvxq5ULabfprXezP/p
- 7RkNz5TKcxkz3+6vvQqp8WZgFr8TESfWJqQyy9LINXElAyXD8aGIoApOOGE9zXSjzLiNJ259
- lYuQuLhYV+RFO9+75/n+ZhOV0s/hx2Q8dlIvph1ufffed7ReaB1K4pbtUlOTZhjevltLEVq/
- 2ojC3b2ni13+3+T3B5+dfWzkZq6ElfgmPIDF/z7zAhLM5e21hgnziA+bb4jfsvI/zIfLkea7
- EtBF8nQVm8PshvxASglcuI/BwO/i38AAh44MibzFaoeHz/N2qOIDMYLWWibq4vduUx7H5aA9
- 1qxS2YxzV6pm1E/uMEzz2PfTZX/MNL1sSdOTDAmDZM6wQXuw4Nc9VAANpUyv2HurZZydDUFX
- ZEU7Tl1VtvOpE+M0+zVuo8p3jTg3haoHq3srm39eyrw4stUbNPbaGeNLKbkoIm2N9dhCzT+p
- VTK/erNrKdOiX31OnWfNtA6V8mOgep6WdRkgW1+4y6ug5iJNcjjtZ4L8tqlWnnymplDXwlur
- srJffE6jHlVueqgKV9i3YZvPm5QE/P8M/pkHDZlr+Njpocbs9UVYgDuIc+OalSarluCZXiUh
- oxaaW6VGw0c1kgagWCY8ypcdO7JunRIT/TELPL3sEYGPzUvsR/GaJrC+fhbR6VNgmnUoXPLY
- WzLa2E4gyy/SVEZQgjDM7PCCBot60t0H0MtYUnOn2JyFbfEK1pQ6d9oNBxkq1mq8L/MsKJQd
- ypUG9BBZNW0/6hO2I3kzTNOit9NLR3SQROUO+5jVlctmlDWMwdqaK5Y9biNiZNPgixkHiQc8
- 1spTSnadagWF6oDUOnRd76jrhmmFZCB2GiVV54OabZ6MiMpod1YxJcw4h3Ecp2Weuiojh7m6
- OE4QL8QOD7OKKfgrJgmJGrvK9dR1kz7mGylGrafGuFqYXQdf9bN2rswrE+4chlvtQnhUPG/P
- PtiUNsxS2GpXCWuW0xqB74S7jsK0hmRQ2xE/chwQrcbhGSVUA26BimlWIZreGwoosgdrFh4S
- 2ytPVjMrIvi6nxVOVzMriDNmDJhmxiwYlw1zF0vP+AMbtophpgGnIoiDMATEyKTGC4XS2JnZ
- 2OVHQKkfK+GlztBhb+wHNQkDCkDqSRseerS1GfdzMjC6TrYArOlFVwTxiA11VlCD3qY6Dd4A
- mn4UFhQX6LnOwduXQTzsS7tJQrB2L3HpFN4m4kVxNWHXScwCkMg7l1kCsbR1qS0IAQ+6Rimj
- eHTY9n2bAYmg7c4/UT5sl1kJ+1JkAybeGvIwtkL4KYl8FMO03553Weg392sdK5e9FNiwc5Qk
- 1JMGxn4dAjQhsSMIH5VV6ROBZt0KjbQTlQahRuSY/xI+51AI5DGsNjN3gddNUHmtmb1AdDiU
- HW6ZZKmeUkagK6CBedbv24IQsN+GyGE3vAUQVkdU4tfVx0aOxUVL7+n96YeotJUncdViSsTy
- 3jO/bD1zaBLv9JRpB06NBjyxwUCESZokiV2ej5W4LdC9IGiAy9i7FO8yroGcXqiKKeEiQvs0
- MbYlqp6mLRT8CCiD5q7ul8fqaJvxXbe7EsRUjEVHRSooEdVrMaiFKIn2wBwOs21TSoK4niyi
- 2o7gWk6PlFGTCTtPi5fqYEbFaMC9QHDQTV2Rqyig1WcRl62Xj7LTr8PpLWdtOIjjr3VpNiV2
- pXM/De8xwm47JlKMYd7drS8pY25HMj1e/cuzwH/h43nw7+zyH+Cv/gaQPWidCzubqhVWHPPy
- Hh68woDvMwEAPLN+c421RmFb9TpWfM+LrF+18j/Nf8a7F91lHErAAyq0nLZtUL6FugUDv4d/
- AwM8uYHUuB3JMJoV1rgRpvr1xnDfMfkzaFMOLyXJ3eNvlSQ8TcV+GWXT9jFUeEUFboPqC7NJ
- +LFBtXiWjF1JBSb2WUTtajfOMEL4bhdqI1je7fiBug2521jFcZoKgpDG8jTuJAQMIPcw4MyM
- nsw6Do+skWpdSfEcbPNk0isTDjI1Q23PMUfXFgGkdGjhMa6t29HCk/nrwqQGJm0Pg5kRx3wB
- G4AKwKtddkCFj+CfX7I9Sga+X+1fn5115w5pEzLYtIsxrGMTk4CIPI9pQEXVtLBkIKGaBZNp
- riFMQrA+y7aplCr7Wdu7u2sEELb2mcutLTMqmBJiBOx1bpFsV2FZSK3hpCKiPOvMHriqbhrr
- KMuyqaumv9q6dRo64y72SEu8pizc7ou5TqBQABc8Px/vAHE1n5YSSiGptosr5XLjuo/sBCxz
- 8UwxwfKBECaE2fDIz/2iWswGUBX5acwWZah1glWROS3pHO/1ktEyUGyfNVykRd3NenOIjTgC
- bMVQx67MU84o2vTCbHPGCTxMjZgFScexYm50WVsnLG6WZxKYxHX9lKeGv/EkPh6Jl/gyRbHB
- IYiw7HsXBwHfEVDXR8ypFMG+U2Mr7V52EctBv/QBJtNVQmKMFmlwTN1LE0jqglAbwJ/PoSE0
- JbwOAjdjL0yphb0yOhzIUjy3BmBtYrAobwplgJoG8H1WOAgjjtU4bceCeu4qx/yHLqZePZgP
- AJcYLBYmTKO5HvfFjgItA3SPiFHRJAhlkYbnfL62s/QM79zE8LeKgHol0P163vy1QPD4NTeF
- TmLtIHI6a/+05qLf8rFzKXOlstiCvHTx9pSKvMxjtotobbHQjOJRMm9nJJSMRqkR5iLKBr+Q
- 51d1KeghjaVFgSQ3i889qCrFD//TNcplnoRHfATqEQ4wHLnjpylvrkFEIi2PSvDW8KwJfWaw
- bSzOULPpJ+6em3OaR9W7W13NqOcqjcvY8TheK1rM8ho6yjibVaUyczxsm/EUSVRRVg9tsPd2
- MR4dgxzWTqKJpY4RpoTkw7xtJDOcrC5i605PmwvRgiSC7nCneaHRAZJMMEVVpZLdWOWdRXzz
- WGURjibd+ti6xabPYT7O/VR5HEWJLPpxnh4/gLq+Mv3Qiu97zI0ExKnqutoJDsWJtqnmBkq1
- zlCCTJ5XtfDgU+4yWRHAKF4WT7KEE8zwJuWEUgJZUEbNJtjN3ycPnycUccQc0r3QkrIwM2aO
- G0CvraDsq8TMJCwkLhygJ8ycUHDs1MDccARD/GK+l4SwdtM52zdoTyuauBL8rrIo+3lzMWKf
- SNL4p06ScqgSLtIkPGtykIseaqhlu8VM9zlqkmVOoQDhj2ExeoTwkx08ztesCud3TJirXI+d
- eiRKBLPukNkMWKJ8mBa5kZ18CKiIeWxg98tdKsexFuGDeFZPa5eFPDYwl0Zmmx09PQvSvWKE
- CIQ+b+zyH+S7mSy7BbbsIApNfw8PXmHAt5kAADDiMD3318x7fjmyHWmzfNXK/zQfkzJ+Okjw
- hXaAxNK6r2LTxTTCSrwHA7+P/woDnGyjEpgcYzl8BIDRsJruDfefYcI4VkXKIe1XqPAxKvgm
- 08cGc+WSgj7fv0YlFpeGjLgNJm/DgJ9gbktb13VVJFEUS1U7hw6FqUhtUQRoPkQL32W+QoU7
- +PdRyc98bOxVZumVezwgGPwCGkI2cYmj+QixQFz6+bmEOefmRUljIbgxzMRsr0VSpexqBweh
- vxxhOsLtfMHNoDGT1eZ8ABJQCpxmMIJxvM+UHg3Jl4MEk8mqRePZfZLdhg3knk8LY+zVgLAK
- Vthpp4ceh77KnoqpQVQTaOZxIfIJRh+Ri6mixyrFaVVqNLufR3W7j54WBTltLquhU/SZxNja
- PGYUQAkbaz87LGpcctkOHnLbpkopVez0uCzbyXtq6aqceVu2MJGIiVf1bjdR3C69pPZ4wyKM
- PMecwgvCLl8zyCyxqlWUm5l13A6nnqdWHBu2U4ohrx8kfHiBVx/BG+nXnR+m7WBy7/24Pguz
- pG7btmm6cXH4m0mbtZDQMPF09IHFqu37SnL44a4Sb+7hXcAnwV2Qd7z8qC0qJn9l2ThZlyNI
- kNdKEIzU3TpcAzQNCbigzIj1kg8alROKQ49RVg2fFqZcYI1G1fyUZVvnaXSeKsCIULVeMiHM
- jQd3iGLzNmJgY0tSzxeMIqqxz0NvOKBVubDn8SGGc/6ZlNOLg424LAjL5JQDX3OG3fLosMLm
- +W98LyeDNiHkebgDFgsTby4iwKY+v75lZOkTG5PPGM5rgHkQwUt38Xsx3TzYrq5RhZ0peBDe
- kZuQ/k+UB8X14qFYLDQUxiiW2GLURyFM/BY1vzSHyYnaiggvaIPBu0jjMgTUuTSpf4oJaW0Q
- 4dnsMpxUar+3ZsJoeehANEcjo0FhLBwEBxHsGRDlMeRyf3XKqfbN9I6EWAZZr10OE5Ybzisc
- XUPIEL742G5ReGFQBDdJLNMIfg/8qC/Tmp6POx2uBaEHBYS36wen0SiJMCDknWiUCha2z/4v
- eQTTI1V+7OnbOmp2WWtzGI8Y4SeMMogREo1yFFznEbHptU0syKitdSPGA38dAqVJZrduqqIo
- u3UqsAlODyVnRlvxMJQ2ONsZQbNcxUA2R0hip3mZS4E8xtl8GymRYprzkAlBAyKnEU18Qi6P
- nZzz2HqZxnEy/856nUdrOz4YmHWnYTWWBJMQfNN6WJQJduYbk0QJi5T+6HNswziiIT2UgnNG
- H8QgjQfBMMTSSs9Eje1ngJapEDYns8yKPzNg57usXfHtnTbGxv5tGfquH6cm46/PghoZEcLw
- uZA7u/zH+EA4oF0L07zprWkHerqHB68w4PtMrHQYcZie+2uACirUMK/Ir8CeftXK/zTfS736
- Ft8LULJ0/LXVMUXO8B4M/Cb+DQwAgMEpF+hcoy2Wxho11ZbJ7nHNHxvuP8R0hIOct1DhjAq+
- y/TBACwvz4cLSPCv0SthZe1Ch+/DgJ9gwqEjlDJDzqFDB+B7mvmBwh+jhW8yX6HCDfz7oOTn
- PvY2JCFld19n0XNjLCLJCpNqj/OqG5axTBNV1+ZVUYrI3wkiRIOeYmMz5i4l8LGRY02rrnpu
- Ul5e3T/kZkFT5T60cKH7veJI6TBpDPy6k9u2fVQ+RshXnBvislBJ6PYDb0tflQUiOnFWIKyC
- D1PBOpRF0U7axrFSc7/vVBw6oK8ixkJ4IpgjcjbOvBCyaLv2aKh+ns8URd9kxNuLOKMtrBAP
- fomiG6rUfZZAj7Wq2nHsUSf3tL9sl4tMYPaHpsR5aZwOA5qIw5A7ClkMPp6FaciKflqcoBsZ
- UfZ0L9uE8nLsMxoQkbgdC2GGIIKLmgHPHaFchCGKuoBFMJ5Js+9LFEVdF1nMbBxhKuNd6Fni
- 0qGbx1dFkec4Kwgm3sL1+0+GXTZtlblQH/oAUwQDHxUDKvHj60gboofPu3k3ABNQfM3F1Aaw
- q1SeZQbJIJxcmK0osVli2+iyi/ut+eEaGB6adtEZwtOqqVJOAEH8rl6Prl0KR8XqCve744Ed
- DZ0MKU/Lum2KJHCB2KeTLEbfnUBdiDW61eqlgFDn+YwcHx4FZOg2d7kv8WB9SU4uOwZf9wuM
- ZeyWWKHyTGbNpDGlfTcJW1gBx/H9wkMD/kPC4orLtkpDd7hj33HHkqYtOcJAy34kjEZZ1zdK
- 1ethtLgsa4UJKddnCKnsh67KkzhvMRGdqYPFRVZZpdztoVhb56COEWbLy4Ya/yfKU44lDX/s
- fPwHhR92d63Ivs9i4M/m5GtzGCOXVVtJEhwHdjr5Ko3L2FFne5wnd192VVXTVHlIcL7GndHg
- qu6W7RhClBWZcJV4RwpRlTfTwqzKAMKQxD42CICYnM9nbfwNFG22FzSqoBscyJMMwOLWx8bC
- 9E5rbZu7cnuQv+djg2O6zPLb+tzGE0gSASY3clXCgVrGVkYMCrZt6qY3InFIH5S1yzxNfZ3i
- ONMwTeO0ODnTXYUuZbordA6weCVsBCMiFhEPmc1ax/WET7dWVVXbhPyeWN6mjJt9lnXGPnSS
- hyJGltUz395eM54OM07cIMD3GW2r8Zr6JmYkVo25/sqH0LE8qcgrdf5a51QQmpSSYXq8R0AU
- uzS6SR/f3RHKTEiat9PFt1fDUmNfL0Ea43QXK2Id6wh+kf702UXBPOHTIfd2+Q/xXYKLyaKE
- HjA3cqVUrkqYPQcP4rJpSsCDexjwXSYULIwpQkL310POcQwnP/KZ+JDhV638D/OhXsxPWTWZ
- 9V/ybjnOTiJ11BQptEQ8bvdg4Dfxb2DAAQ559KA4zbt5gyFDvmqYxjzahf+h4f5TzIDFTd+3
- lYrjfLFmFAqkH1ql6jtU8E2mAwMAhBCLz79cj8XZuDP5JRjwE0zvpA/6AMJ4oQdSdhR+RQvf
- Z75ChTv491ryeh57beTZx3ZufXX/sVJpIsdT+Rh+vz2/KQ2iPMUCcIawwMEJQbFos9Y0t3TG
- noATcka8Hf/eMkN0ATQKN/5bun7zDGjjdSzegWS8NjGeA6GJO8sWF4vnlTmCT6448ZnwFuB0
- gMKkOAl327/ihoFWCfNLupRTLg4+iztwN4RCQ6Ao0Norb6uvqCftZA5eojofgVUzBqecP38i
- vfS1yj775lmW5kgFnwmQNOo3fzEk/TSUeV6USjAmK9zEFoZn1iIL93ydn5Ki+FQsQFj0vCFU
- fzkbQxmXBbJN4F9eB5iIL/i0NVhRkBQN8QkHydAZCM05Bq4Sc41MkfNU3d20Xd07hdfkjQi+
- BDgcyAyziu3W7rjlzoSjaf9oJSySrAz33FWQXxjE0kpfCy/psaeoltzrXVSP2staYwiOFuX1
- QeSNvny5ENuhzz42z2B1Qv8jfw10Y1xuZzGCtOUQbG1yPT8R9Ak2jJFyXD2vmCKPtG1r5Sb8
- PyWESxzh1XdubUOVNTNEEDNyOvs61345ljZ+MVBaT5bnu8rY0MsIzjcjuodGEUzRx/Z4w+SW
- ufqRDr+T2bCtDUyCXMBEefdsv229tGG18ddSUegE3D03B12THJ0nYdKvaJS/SuMydlgdt8ZB
- +C4gKJL1Zucc6scBEBwTBcGoHXoMXmLtzzSMayqFnwE7vtel0cm4mvzktn8Y2PuSAqIhoCkh
- +Pmxj40C2Pzyfbo3YaANx0/vCYs6OhTLWsZOfiFGCq3rCMBlrMxOfcy8JpfQANqfky9j71WS
- qjKPD413Q1OTh8QSDXGe6J70aA3KhNTxm4QmKDm09/SedBv6ulf8TYLO8XJGLo0/V4JEuQzx
- UdkXWt/9k2brPK2vXxr0vmS2TNPYKaNsu/nlLjASiMC83j3rgDVUNNq7s8t/iA9pHysXJgnk
- 9qq8AQ8AA34PEwrWN6b31/ClQZRF7iPeX7XyP8kH6VoK2WA6LbkQ+ISy0SbiqaZZJAd9DwZ+
- L/8GBuDArU8wVWFIDwiTLx8b7j/AJDyRCcc1IlkaGCCkJ6jwigq+zfSxgVtNPt+/vjPu78OA
- H2GCtkklcV6P583I18KvaOH7zFeocAv/XkrCx064rMdxGMaxySIEgL9NSxwE5XzdmOWDA/8X
- 7q8njrvyP/IuYDxri2iwqel9UqH7kM8tZSFNqumVr9G5f0SbfvvpDSVfWzfsd55fUfJa5brd
- ywRnBn6YFkRy4zSNuTvef09fF9K3ydX7tYpbyf04y8+T/07fLd7lEby7N6fq+33Aa/jj5PaO
- 1uszY8Os3cIdeGvflflZMPeqDOrCL715D98X8wkbW9K8LLKIBu8vmbHBIU8GFf9zdFmFat9C
- hg24V59wqpP/sEa2T5c0pP9baWxrKZjvct/SNvAjE7xc/Uz3pTpEJf48wXV0sSpQmxA4kN8n
- /zz2WKbUeM4szipI5r+HEMjo4AF7k76TXKgmj6LXnfPLNNSSBVH9I2roG3dxhIfgO4oC3fs/
- SmtX5wga/pn2f97K/zT/laZp9YHX+2Dge/zvwO3tdtb/AebmenYBmHq26SdW3qOC7zO/b9zf
- L/mDzFcaukE7Cf/ki/Shwi3guS8Z6KlJkweliSGJvZffpm3qh3X7vRpncR/Kx1/+/moN8zDM
- eOgv/QmZTF2j8ixX1f+n16BEyLjIq3+5Sddj3+Pc2v9LWpfZ0vI6wOPOJ1OOXtNZf57chiAa
- iqJ9Nw4m8Mk6hHv/FynnJAjT6TZeELm/7f8vIXwuGJnzT2kdu6osy7rfvAwzsT72NndlUdbt
- +2P74em39jKOs2r0ecvQjb/NHm99pUrkTv+LKSIB5bn+4oqmlOfN/C+0DyoRnEdxIvE59/+r
- pPuYMR7n/35T95f+0qBiyvjNvpu/9G+GCg7wfF7yfwBJYEZ/iLwzswAAAABJRU5ErkJggg=='
- 	) base64Decoded asByteArray readStream
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldOblique9Data (in category 'dejaVu font data') -----
- dejaVuSansBoldOblique9Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Oblique 9. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 9 11 3 0 255 15 0 0 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 11 16 22 31 39 51 61 65 70 75 81 91 96 101 106 113 121 129 137 145 153 161 169 177 185 193 198 203 213 223 233 240 252 262 271 280 290 298 306 316 326 330 337 347 355 367 377 387 396 406 415 424 432 442 451 464 475 484 494 500 504 510 520 526 532 540 549 556 565 573 579 588 597 601 607 615 619 632 641 649 658 667 673 680 686 695 703 714 723 731 738 747 751 760 770 770 780 786 796 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 810 815 823 831 839 848 852 859 865 877 884 892 902 907 919 925 931 941 946 951 957 966 974 979 985 990 997 1005 1017 1029 1041 1048 1058 1068 1078 1088 1098 1108 1123 1132 1140 1148 1156 1164 1168 1173 1178 1183 1193 1203 1213 1223 1233 1243 1253 1263 1275 1285 1295 1305 1315 1324 1333 1342 1350 1358 1366 1374 1382 1390 1403 1410 1418 1426 1434 1442 1446 1451 1456 1461 1469 1478 1486 1494 1502 1510 151
 8 1528 1537 1546 1555 1564 1573 1581 1590 1598
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldOblique9Form (in category 'dejaVu font data') -----
- dejaVuSansBoldOblique9Form
- 	<generated>
- 	" Form data for DejaVu Sans Bold Oblique 9. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^Form fromBinaryStream: (
- 'iVBORw0KGgoAAAANSUhEUgAABj4AAAAOCAIAAAAQbPL9AAAr9UlEQVR4Aexbq6LkqhLNF/EP
- fAE/EB0dG4tD4uJQUVFRUTFRGExMDCImJiICg0D0bSC7hqS7p/fZdx73sdc5M9NdxaMoXouC
- zm7f+MY3vvGNb3zjG9/4xje+8W/ArQPK7mDbiwSbrDOPUu3urDFdhbIDaLzmX2n2A0TMZ60V
- +C7GQpT3f6jcL5knkR8589befgvWgfny6fjoElmH2otmc2CvrjJA4is3Ed8OKoIrxtCOufWN
- IrWKOQeKQ5L+tqsi8cjNyFALZ74IdPscJEMZAItH5+iu8hquXnX4yEN9VXd1upnKHyXXF61b
- uyxBu7hzXunNIoyHFo7m9suham922S0v9Hsbqs7r0T6McAx2l527ju/ee4N13Ccq9O0Ko7vg
- cTIs9vbfCjuGjsGlWN2frvsb3/hzoatFSX3eqKzxuJ1F++4TXeClu7HvZsimJyllWFr2+6dJ
- b6Cy+27/wh5uo+GfTm6gnWcxyL+MtApjP1eUM+ap/Yc97vb3Afb84f4FV0Kv/EY4s0NN/wuA
- ub8b+7W+9hm/MhONdf/L26wzi/RQ/o/er67bNGj1Zr+yhnfUc7Fa3d7DTNJj2b/icLP43Gpe
- 36dctZIeX7cnOk3NIFjnHw50H9oreYVcfxzf2JfQQ3Lynel2OfRy3i6DR6ppNf9rkx2WMmN+
- ZduuvMOtXV33Sk99U7fyH26KQOH+IGCCK6X8uFiiaN+2fTf/1A/J/v5IK0xb+ePu7+xfZ90T
- nuw+k9Xj2iagap9LA7zPvE7zHvvU0arW9kWkQzDK2/UJ0deCsVauzsw1ZYM253xry8W0rmPD
- mRj2h9x67JperVo2opsfxqDiKEONHmmW8f23cb+5qynvzdXBi6AVb6RN2zr3d5lcrdH9yVdu
- G9umV8uietEMmzukyrdaxphXXVWi91vPplpK62l3m+oYa+55+0YM0zKPXdtPt3eAkrtpXWTL
- uJieEgO3j6IqaGef5t8ULXLqbbvCzl1Z0EFvemzYY4+vQ0VbrUdWVs34uNdvHWftOKm+aYbZ
- fYU2e9gj5z4Oyj7GXwSr+/nVIOaUNuPyqNF9TVmz2NsqG8q77Vqx7ptmnNd56Nr+sdLbHLJr
- +48as05xbdNpbbYrsQ83TubVolhhdE/QJTEyJUqEEC5bcx6ibc3bcTHrWIsRUrtVCd5Mi+5F
- 3cr1Ep6ru4ZkGZP7rwkRdNVP6CWsvVWrk/Y1GN1RggMe9y97b7IPHCPar2ltPMdHeHcbC18K
- 6XyXmLEVzTAvU1/XHbDMwDdUYIT7smxQyqo6zpt532VTJ4FIN/rgMeLj9qI7NQu1N7MBmW4p
- uiOvt9ulLVwMs9nkqV82JbhQyzI0dTPoX3Hf0HuDoPZn0B1F9zTlOfRv/RhDGa7Vfl1YOiE6
- pVVf1602jzUOOfKh38m+PzJsqqtFp9e5reth9hVlQ10VZYKi6h8rsVOeeTC52VncP4h57Ssf
- RzdnU0iGuNzt3KAMQ6/EEkiWVeMOljQlziIIP6LtuyT+ezG70/peoAxQiAkKLOAWIgrmJqYJ
- Pqhjcu1u1u+3tr4nbhav+m0BALd0yLcmmrR3LLkOod0epXNfFTlGh1iaI6sUlRdC+qrZ4Loj
- AS7qxZ3vNI5cqNUWJn+Kopk/+r4tCQI54fKeX5DsAcQ7cx1pjpKKy3G1cTVnBQZxJaS9/U0s
- A0+tFOq0rGs1CM4opYzX/QjD8UJo8iMzGxPhyS8I57ybXEqwaJHqq3oMI1CkQoRJyRptHsoE
- kPoncqgIJRpMikauSa5ytjBDY1aVasHkS3owlSsTdmIGV0hnbboYpQ0sYZIOlMClX9qc6rjL
- WhkGwzz0IIpkrCNC5Wov5YOyYO3mbu8yQqXgpXQR24e6Qid1Ndub31qe4Unz3VwcU0bNIn6s
- NIwGN5cxo5GxRBEGmpnSQo7FIZav2zKDlF6nKYYFAdaujA7bMch7CrbtkmcPgFp2yTJA2Yd7
- ZqJgBCbKotXQgIHlwaGlesNAoDcREOqXiBeqX6Q1tomuxPW7W9McWvRle6Y6VkZgwBx+qgbP
- MkXU5nF/BYD8vzkIsoiwOvaz+S8Kevcfs+W4ijfSUy4mIcVYgT5Xn92fvjAXkncWhdhuvxjr
- KHg7Xd4hjKJK9/bXuReKfAp8PADZanI45OaWhlExLIc317FKWEE8AtmwBGHWhMpoGuNlpWfk
- nucUbLwQxW0kGYD0v/QuHmpHT2u/7h00HSc5Hz9hykIhd97crIJBhso2GR44FvhukGpR5ei6
- Pr/FwvCZGe4TJQjM6rR5XSM8b6FLIm1L5EXj9tk0Tie0td4e07wBcCqEUUbYE0fJuxbhV9qp
- OWzMa/VKi9BzrRJ3LXqVt82hXY19OgBw9hyo0u4N9wMGgvAdKGV3IL7IoxCh499EfiiQ/wfS
- 55kXVHHXi58jl5ubYA86+nQSp6/rQE9MluS07mH3BvNoH5Pv/CVbQ4F0VZF0JdqofKElvoER
- pGRPtMDmCnrR5qAM8x20n8DW8xPlK1jNCi9otL2yXw8NBC/V1lPUzs+0qDmY91LhJ3kFaNGh
- feR1K/C6U0b37FFbMCFZkUwScQiuZ9uz+EjcBWoIOQGZBP55wPVlUkHeuiTg621ueDBdXl7M
- tWosvsDxvkIv7bH21qN79vaN1BCohf0rbpbMG2dUHmML9hghInyn3Xyzc5XQ4ufvFrcBJtBp
- 590/5NDpgD3uhtXinjSzDjrWaxBtCbFncnv7IlKH5Yx1LQ5U/5fQwXgmqvrlBSFhR7jGnsQc
- P31WCa9HWRNG4fWqYZd5yNNp85kjQxifuO1Y6CVvYcZRRtt+6D2GYWDkSU6rG2A2cQaKaWly
- CF1B1b74bnOz7xmibORGkhUkjQJ02sYVs6zbOgSwuD8WrBRBCAYaPxewsuXBrcN6qIwiECeK
- awQcySBjGExeyOsy7GiVt1mkfIcSwofll1Dq1leJ+tUdn2FJB8OOgQgotTuamX/sb6ALr1ht
- PB/FTQ/kV6KTcJ0x2X5hHJwXLJwTnwZRGeOJD6jAe6FqaEB3c7qEnYYg4GRfcda+6NV8iq8u
- Pzklu7Y4+42II9vcAVFBCJxXyEthaw+6ZDCb+olfUNxx3NLjRyVpwmpSgODSy8/LrIbXcl8R
- aM7KDXLBYgEzlA5rqr1FXNODqWTcjYTzP6aTSbW4T9x1aWDcuWE/DrnHU3OIMGGFwj8Mu0Fd
- ABi9rxyI6PguI1R6dfvjjIAwBEcP4mtoCferS6NOVbfskn34LXlzHjNalf/gQw6aUiuTmEFu
- sI+GM5JLjK+PHWulKNbPd4jIe5SBSTzl1yj21FQfB+9uHKXep7AOw3K++1uo6rLLjjx1LFxe
- vcYmC4TKdv55KnCUsl9hMBQBHXwN9xGureq+779sj+5YnucF7aB2URZ3CfdbuOtKBIMZkMpv
- /73YBwQj9r8FW48+On0YJz+0rSLnH7NsWjU0T9n5e3xpLiwDywD5L45edcWxEQCWrvxBo1Bc
- EKzWabVm/vgqj9B8oePnADauN+ODMoir04kFlU1b5wgdpzW7qlEue3i+Nq/wI6/D76Kuax6P
- rHxcU7JekoJyXhIEZ4lfA6g9w5T72ksCtQPstq7rtoW/TYw9la1S/jIPS3N7w/rc0op+WUZ8
- rNJG9oMc2xz5sQWXoyhDrJvfGssQdFQp/LETdYv7TCuHhoZcbE3KKXjb1YG5M/mTS/OOF3Ec
- mvNP5AiXn0oDxLrvpWyjH5S5pnmPK6f6unb/pSUnZFmYn96CXIG4uf2c+z1ncb9ejusLl3vz
- Feb+BZhvXvl1tvYXtbd9HtMraqMHuaQTmeHnvShirp8SvN+p/RmvA+qLiooxyuoWnr8BtyeV
- aMM6cFnQtrFGGenW2wVzU96LGxZ3js+igg/2ttYFqRIWN3fNuOyr6oXwtgPcNvvXzWabpDq/
- YrY9y4PBYv2VnEQW6HBmCqdbv/b2qdwNNMc519YpUZKyMUkpk3+8sy+TgkdqTnc5Im3gA+vI
- MS7aaT+8hCtlbvvIESpvbp+U0pv1m58KfdrB2TmGxaVNIiNtK43br0+f4EWYf8FjnzwuQ3mw
- BLDyHOe0M7e9KUlZS1AsY9fP2z4PQnTaXH4rMG1mm5W6HqXtvi7LuttPnK7n1Z4ETYlx2T7b
- q3SFspz19uHqDuOi13afGoLL6aR23v/Lti/exnNG11OCCJ3MZ48MZplGOW/boqSKNmccE5kk
- nTihcn/i64+dzCgeAtK6CQ/i9o+3UZzzeH2XUxbvm0rGj4dU53hHPZkY8lT3lodPYlr7CsGK
- +Xg4wWLx3/Ztd9AUhYGwws1DVsWhDe+JylbroU73AZV2s4msV97+PcD6guiQvoyoOu23B3zE
- nOLPW5ZV8yjJG/uDNnU6DrW1Q1EZmJ/ZtiPNcsjLj+sRkZ+2oh3uTAJjW9dl261z1jrPKWOF
- RT0eDnT7Ggq21txxTwcncN8Fdi5i+m67Jz00ZQfrcrdcbyrWgWNMSM60+3inSgjBpJmvk2oa
- WlqQNITv7DO42D88DhwmunndH/naPPTT5kKkAEGwxkxNNL+fV3OU5PQo8PV2wjb5NaIBL5ig
- aTLuhAf7XCBCz7qQ3NlFNtzTWRfHcAiQmU1LPw3g4RuUyUZ3tNj7/aU8qYi2x8nSbLrlbFzd
- xcLAeWk0sl0saOEd2YMETM1Ijj84dnP4F7QQWr3KY6OW1MgYrYeKAvCw39xUg2FG1YeGsPCe
- 3ylRwJ1JWq/and1U+TG232SE1tHB+f2MANGBkZwVrY0+XKeu8wte/AHhFoZK3JBM+JkEmAFP
- q7aRQrQOuAhXJvodw3UNhK4mCwdsX7KY4/0DrA8QY0pBk1157Q+/shYiYGTckl+xGGuWAUPe
- TsN4Tk840W9pcNnNAlbycJtHYt+PWvcshxP7p2EHXkJgHeFcDPoS0cuLPF7I1nDOtGvHK4KD
- GKGyHuOxqqFFTFnREqXXL0Y3rMQops/rUIWdW4LAx7ik3Y9CUCiEscIvQQdFAHtKWuLYFe10
- vP+tfKAKbsDs0vvveRUqXymC8Wla6otEiIA8bkC6rTAhGBf0aELeStWxY0mCko9kpOSsRGBD
- xD4LWmAUgPO6n09ZcF5VxdWNqccYTRq7iZJ4FPdM8cdNVjYMHI5xLuS6SYEz8J9PHR41VJhg
- UoXJsqsylqmNmRuCMfl4W2Q8TfFW2bn18tKn3/wWgD3rgnLKxjutJH5noJ3zO6PwhiHMx21u
- Kkh/h+RFcA77V3tfiyCp73X9X1H2kBWwgWg0NhaHxOFQKBQKhUFhMBgMAoNBIDCIiHmbhJO6
- nSro/tVUPz3zTl9VlUAIIR8n535kGwrBPWHF8zyZE3rE4Bu/Rwqlrk76+YfyzFighjnY/XUU
- 1KVh3H3Gc27rpbe3Vopx2u/2CLCmFhFA35J41BZGzdNS7b1Qqx6LoqiqJOBgpcHxQa8D+2un
- uSzD7qVVdwF1jUmpFyZpBDtvEWWxIMz4nOrOyD0Ommwm+59hXNSBlS+a9PrpURp6NyuMNCK8
- vCN4TT+t6x0Z8nZ1tcE87u6Zo1w/QOg+2dttvWxOtNCxd8M8Yyz2gRqVI9mUaihWBI4nwaUM
- AaLnwIw3mPYFL7azzTK0g1l8unZSd62UABKYkeIDZH76mj7Fi/vV2TWw4Ig06osndY2pvj/3
- vVLMp7mGYoCBXh4LjDIFPLaaq8+x3zm6e1k68JuL5S7/Qvm9I8VZqamrJOasuFt/B619V+7b
- V9CwELT11h+GRZipzZQI8xxsXakF7iXA+8rcc1yHG1195ET1kbId2sjnoK4I+uJaPAONSDrT
- yZ5P04XwNGBjngiyeiTpwhj6vaWntb1eQ4AdezH+/nq+y14ZnT5Al5MI2NntMCYvNKo5PCGq
- YT1HgIB5zruQdMbc9DyW++OMM0o9kuuPdOb5eJc50/pIDZUB+YrBzmOe5wlZHOO8ePdXjXUU
- RmkOvKQ/LrCZEL6M93fZxYVzXGM3wDk33aPpe51NS+8wqxrs9Xv60SRBWtFyAp2O6yHYNTv0
- PWb/LBKcHS5BMrARAwH8CqXnEF30DvzusyTNSqXnCT8qlQaFoRAGguIuT4QkS99lUJ8P1Ncm
- gUF9+y0nW4YDKKYtTGulJ/ZbduqKBsBrI5e6wuABWzxW4W75uTRpGCaV+bqwBXDlMINknu/t
- jaS0//GmNYpvEiamXD+OBHUGdIwb6c5taoo0Tctu3oF7JE0/xqaRkLWgrnjUmNFOfdwcEPMK
- 9eCqF05uDHMwLQUDqQkLCsdADLyDa0393ixiLrMsS2MB/NksZqbTs0YQSQ9bYrQDERZXo7UK
- pkZgQdoQzEN34LqDqkHaLWFg7mVJO4MfDAbcgreAUQmLZjt4tBzKRrX2TRkF4lYzOL4Rsx0i
- cABRSxdTw3su4ry6C9OzFCHh3UzzsnBUW5MG1Mi215QizPo0w4ihYskpQyTe/NUirPU8mqBU
- MZToA10rP7iKzaoB0UQoc/8nw1C+SZQv9lluuvsgtS7zPJtgTb/cu6QMpeAWkyGXWH66Kagq
- xOkPyAW16qaD6ioJ/2KMsW8VA8065r6tWCaI9gw7UdKLUL6Xrnqe8dAnr2+0DxVpu8zt4WHB
- ogXWl9jtyDgraAAodFRAH7ymwyy3sQfoA2iI71IEDOZpt9GX9ksbcWvuJ9JuKAIaiBT+ztSr
- 15mCCCcI6/Sz6KeRNR/AsLXffe1c6qpP/RvTvbRREERJOSN3avJQBjGolmvB7l0DB18DFJAF
- mA+pYDuxkhdHL9nb3HNSobpcGmF9HTxm58Y+Fe+vTfDhHuI/tz5gZrE/hNYE+BKdzeZmBbTX
- LG2mW3o9Y9d0IdKg7NM6WE8rCOqznTYjbTHnZVE3K0Pmm1zh+x43TT7dLdncalmYrDA0Dut9
- NeS2TehEd8zePNl+LRGz9g6Dj50GcYtgYXo8kslitXpmFi90qkxao3xzewikCrmZIrZz6or2
- 8/VRjBpFEkzUvOfGwtQ2/dCIvdpV1zSEqplizzGRvlZ6gQ2HmxsESkillqHEJrRZ1+MdtrGi
- /uQw/oLTkCMmJAoxV1dzg+uuDM2gEZWFdtfiflxWeRRX6tcsrRPZ2pgPk5cJWUw1xtJG/nEz
- tpk0c6Ca2ySKYkeiKK3Gi6fP2o+YyTSRfG+WZQovXdj04+AVoj9x6Ps6JoZgBtxIGfh+pHPn
- Lj9m+Xj3bBi7ftnU1CQXtp9NRDAP4FDULOaD4mvUZcjeGt4YszVZEsfxWWgSpbapTQ3voG40
- hJcWmfnKUsdq0ePDb5cl2/t92G/HzcYGMCh6Yx9k7hiNNdq8nl7DwmFTyzT0fT+taui6eVNL
- l3M9D6xz9aAc6mSEIXyFqb47d23vcgnZRhaOcLwtT3zHY6EMZGwA4zn2O0Fxr03Hyu5gueu/
- qYavIOXq1fhS4S1+B619V66emRNLAEl+YPvF2ciIXMe2l44DykcA70tzT3Edgb5h0/dlTKg6
- YADmCY7ZbNvUOfr6VLr3+fRPl/8mldwzhO8LgzNc4Ob3ZwjwBOa9LJ3CPPrbAjN8NffvNmDv
- rQVj5xk499XpxEKN61hmm8NROK5g2GpdAL/PZZWfv+sM9V1g3bNbPqKuwFLjAaey9anBanMT
- 0Qgv77GTn7eT8ecyvZ77UZpIwxJkaWiI4jBrFZYKSmZM2yip5RF1bcX4cVYjWU5SBFXfxWwf
- 9E0R+lH9a26CnS7dR5jF9EJY+0k35EQYRrucxwTZupQaOwQHQC8VNs8UAFGU43AfmeTOVnYb
- 0nftlw3Wnpb52YrABDumwSdgnvAFp8A3wb+T4zwWS3eaBlRLL92R0VClAWOYso49w1Zqrb9V
- oc9Gu+7tuIoqIT0/zMpmhCmjQc+RaV8qYZjW47uwh21ll2FDB7iVh+fwXIWGRjHLsCfjRHpm
- FKm1YWh2YzeBGWqwodzc6AAQno/EdoMsq9SCz/nQa2NT3DLhg32SjgeBCCDebaxenbuIeMlK
- ykQcSKSAtjNV1aLLFeXjF0nah+lhlgW3+og48rE82weJNJVGM59IbivmuweyEFvouEX5rqTd
- enVj8rBtvWpcKRdMJWkXSsrjg569PuLB8Zga5PO420ZSeUIcJ5Vh5v2ySnQDZSEBNLTfQpLt
- JGIlsV8gMmN5hu6RTiz47uiBqB6CejIw3S+RrauK/E2KIg1JS1rPYpFMSuvtsTmvJDtmMr0Q
- bFNXd7MZsxjCSypuOKAM7OjuhrYgQwyKdB7P6pdSmJ1QSCKIiszWx4sGpSyg7HYLRbrTxo4U
- n9sl1nnYmU5A7iKFx9N2CypUz1ubCIQduapDgcaqtEFlYOdVNciTZrxoMbs54TIbl3UahiHD
- EpSXTTeMQ69NYJaEH4vNrpHalEPLdqkgDQgH/EEtVWhpsqMdRDa2qWVh20LS1QRd3Y3TgY2T
- 1ylVBlRZrez+BGGn9pSxKeLQJ9jxmroSx81RetiXr33s35bFMMnruoyEdpx/Wk6eflOp+4F/
- E+GJ8N60SU21XgGzcbOfGMvxsvRtr7DyOvtMArtFM69jFVskMFZpGMWhfV/u79RQGLf7UOkF
- NENmZgvLbmgyB5NQgW4yLDQjFrX2HebQRhnTng7aps/YXmlKZekcIo7LfAGWdQXN6CIuPH39
- pdKbf1P+Vgye/hk5eSimx3ftng90JYI1nCNrYrWGKBzKy9nqdOJGBwePW3JA3mmd24h6vHXa
- W+SI+MM836rcNa+k2zIK+THVqJS0c1RVITumYhDH4Vu9Hl+zrIUgX4AqPotCPioHoposDsMQ
- tgPnmOrPy6X9fMCWLmpXDaEd8cyYPcV+ZyjutelY2R10d/3X0aDM2CuZFvgdtPZduRgCGbtN
- 5eV2r4lshirixuqxSQVx4rsEeF+Xe43rcKNIe2wnofkAbBBhJGCH2y2X6Ovb0n8tfXNkZHYu
- 8zRws9BleYgAz2Deq9IpzHMhn23htLv/a63hgjgv89gW+ASc++p0NZa+J3wqoDWoX05cNnmI
- j8N0KK4z4Pf6rHPUd75lOLvlY+oKmwQShcqRuRYGsmjhts/Kwkbjc4hJut3y9CocS8/oGgLv
- sIcEMzr0+FZuCc50wOOZAkq8OeJr+jIfqB+NKyfmV3S9D5sLEOPZTDJ/YdqFAhYKIjeQ0DpU
- lhJNqO5RLUPfd00uiGMgtlFpGuEmbuIjqnVFCBvJ7JySegg2qRdqgKqFOH7TmRTUm4i7aaxi
- ceNQ1JggKqM7/54L3f7JhPr9IU5sdS84MQqi1rmr8oCjjbCGKfI6BGTH668t4TC96WJjaLC2
- 0U79LMAr4F6KNKRLI6IDiLKfpkE3JFremnpUy2PqlqKiJvZsCsr0srrt2rbFQSE0XSc3rU5P
- BTVyXsvYhuOPZveurtWbFpCnyIXNvJuCqlKJgfOQS5vUTS/GuUDjhfVQRxyxFfAgFk8L4aFQ
- McdpjtoDxu1yX6vdE6mdP7wRb8egU3WDVi5jV+apFJxWBhs/93p0VxujvfNvkbxI8CzuBx5D
- xHqCP8g2bCW8M5mLrNUkBJt810fGrS2OwjjZUwG34bs7AQEB4rGivECK4GEcMehG8Mo07mng
- vhT6J4aYo/VyeccjZ7DKCVtUDSMI89loIbY+kR78FQHosCT1e+uWxdHZkIv5jsOznt5FVRHr
- EZYVm/DcJ6otXHZfh/fOv4PFIrjlQTOethjqRjS9lBABxeZANMRtIAa/tEzigJ9kAcPq9tBm
- FspO6obfJ3bitltfWwEWwRoLSwlOjQCO0bLQTXWnPiCP2thVtq9aoyZkFMMd1Tr1v5q6Iroi
- +qSTfe/SJAxD8pjWeFikwRFhB6e7CAs24ySJk3rayO4oGBFXxdflHDpA8nTO2a7rsi766lZP
- T2b9UPsO6+1Usg7/x/Za6evTtquzrDbUlaxnwzcFwc7TBTKEtZpp871OTea/H/VqXazA/RlD
- wEVc5un/CxdNXTFfiiOQ8IKnQz55AN/SIEzEnoIzrGdj1zzP887irss0vsnZGZVA58B1UIHI
- UVGPAV71tXczTGs9l1WBoFFmyNtz5yYLpJSmVYMgyluFgSpNOUURIAqnwgusS28WqKxf5xrA
- QLt7uNdAizP1w/prMQNc6RcfxmlTc+Y/LIdA992umOF0s1NM9c25+aPcxFEkO8LTSuO0tmk7
- 80mvsN8Junt5uug2F8td/y1CDveLdhiXI0QjRvrvoLXvyrXoiFMTGBe80eChS0hMfq4B3pfm
- nuM6Asi5LwPBaHRd9M+kHfDt9Dxzjr6+Kx2RH08Eve4BAjyHea9KJ4DNhXwEZS33f8W72s4h
- sNkTcO6r020vssc8UFqjtieAeASXsHC6AH6vzzpHfedY9+yWj6mr3Xo4TWL3ZFO6p81haMiF
- 4Pjhyazrmm454vDzKCIkCO4MDJ6bJ0M07HuJ2DMIzyPIEltlvIwVTG3oNwSswyX4SlbgTscB
- Ld6NddNaKzDbujRsSllPm7YS0oa87azojpFalZO5SeUBc966TehZb7BsP8Svx/UXTi/GqomT
- Fyh1RQUAvcjrBUA/85mdU6BdL3QPiWyvglObq+VAOyts0nD22bLC62LEAZHhZHxI5ZskwL1z
- Hu0JWTNZ7iBPcFTOoTDMTNAxTSfdCyJhbXNdpAGhPkUQFU1vAeXclcmbZLVF3N3b2/JUgbqa
- tqUMhd50JQIxj8z64QpGV+KRSJ9LFzD8pcfnHWc/qamvkrTeCELK+mWdesQJ1nVAmftvpUgs
- L/osKuRBmQGsG9xOS3V/15gTq9H7MlcnBVX1yr4xEx8lpumLbKuRjaSL7u13KnAQyRLz2/Kc
- wDfWcge0Yv77YPlTkzLSRCifV/tEo+hkI09vDEd1e9+dMykknSWaNEpr9BZ0daxD8LCDgSTl
- tVFnHHjkUr0QmDlQS0+4JOzfxTwR7JjrFOz5wsHZDghzQmhvJExsVA1KHd9HWQsyN7rtEnNM
- jDC8R+zqFwiJoTNFDHZ/YOdxpMAGytnvFebGA5iqRXugZP5tclNjRa0Xj99hPozDMPRtXSRJ
- Pm7YB+IzHfoxdImlzTi2KFRbUC8wzkc3KJ0o7A8dQiH2VODC3uUUvmABblYabP66Dt77oIF2
- Pj9vxqsWo29kZJqWZerKPJOeJVAciIaeD0Pdrc8ZcA+dkSByoOpibAxhNYzX1IJ9L51nrEqM
- NC9sEusEg8LGBMWq0+US9T8jj1ArlDDBPXCbumbAbWod+67teoQyfTF1peZakAB254J4/2BS
- usSzQUF51Gwbxjahd+mr43BSCGLcFEmcpImw3VaHNo+zekNoLZn39+GQA4TqcAVTh4jSWOIW
- Ly7TwJ5e0mcBY9zTwjkLDB+6DaafizAO+GWDbC2OiXQRl326nxax2Lm5I44EY7By+o+ieh+M
- 7dOihpzMz5PjYg+7v7BtU4RN+M/S55I2qZ+2JPAz9wVwSdXT0uvIM4TaolcQT0qu/2/31+S9
- XVfSgJtYqOQaflHONlboB77B49eY6g/NpY7kjDFKMS8HUAMQOcd+5+julenAbw6Wu/6LOvN6
- 3tapg+L5gMHPo7Xvy6XaO8/Hipi5mmy7bYbqHWTlJcD7utxrXAfoS4WnzUxhQ7VAHY6N7Rn6
- +q70hNuYuaq1Ru95M467M3JTZmm+r9v3CPAc5r0snYIi+tsFZs5fB5vVFo9NT8C5r04nIQjK
- QAhJg8BQKMtk08Egwy/UFfB7fdYZ6jvHuqe3XFNX9FybaxpoDLSLjNpaTvAuo66VDkUCn45E
- r/3STKhV5sGuKqB63BMLEasDp9QVUcjXT+BOg6KwKXUFpBirF7s5dO0mUme1xEbo3pmT6Sge
- Z5bzOM0Wrw9HwlpL08D0kgVFvQcrd5oL8wsikVGzFJGupKGcuJVYKrzA96hPbGwC3wVYALVG
- jvQQrwGI4Rjhrm9E3yDOK8gptY7DA5mWjRJbXMisaudNubjfjbZgrBO9blNmdFJhfmIwJIJV
- sqSsm7pu2iZF3OTJ1QDQ5Rx0suMyLCvsnF0xxvwg791gXi6pDzl5ECyK3btgdQgLWDdGu+qc
- FFRVjubkDpTdLCQXguY16TD02Oau7aYN0BCxFQQqSd1LUTEYjrpzAi91Lo1wSeX8Rq+anPdF
- fXAcUsRcXApVM/QtGCbunsSVcHLck91TkGABAZ+TDTyIE3esN8wXFu/cJ2yCG6wHSyPksZso
- Zubcd/oSnNgBZFfiWP0SQSTpwGdUYWvZeRK1GY0ccxIBgRuHCOzY6dfFYowvyIMw3BWSiHO0
- koCy4G+Dh4Q+6mMc91zOK4KJkHuWbr/aXC/txlJSV2Xc1dLCJ8dvaKmtjui6DmgT5tnG8hLd
- LOKkGa9bDG8EOc4ej6LAszpSp5/7OIDlcZlk4aNYnEZXZOUCRpvozJc2sR56kt9ezWGBEZJs
- l/eWQliqEPMIWp+rRRx9A4jl9XL1dFtXH+cZfUijoCfAfsQKWA/upGJFLvxjoQ53bVooaMRi
- i9FZtJxXeJ26NBQkhsCpTFrpxf0wzfM8S66oKAi0aG+VHcw+59xIahv7bpi3i6ebaSCvmrYu
- 5OXTTx5QCG6ZoNuvIHuGw4IDnQtv024FQNfmZnkA9f7vC44p4GG//hoywfx03Fz/Axt8pA6Z
- s0Y41yj4XnFQxXU/f6acbSgwK0uspdeY6vtyw/NcfESszsDDjvi5opDMzscM2O8c3b0yHQiH
- /r7+a5ksV3g4bL+eR2vfmvsLMVJEXOuPUnBEnQe4skK3u8n8IcD7ytxrXAetW1AP4zgM42Tn
- QcAGLnyPi0AKDuiuTtHXd6Un2GVKSaP/CxmGgfAseRFzm+MLIMAzmPfKdIAi+tsFZs5fsoMg
- 2CxdnoBzX59uBbvmaLkPoQDFGLESOAd+r886RX1nWPf8lmvqCoWida5O5mXaJ2vrE7BRu6TS
- 55zhLbhMShRiVkRofkBRa/EKDfjWofQZIXlCmO3AGpZCVaxGBGSDTrrGncKJ6QOnUDeUo9Ma
- LKLPcjR4am4CTvSgxZHrrot4NE2xFqduOvOSEn4S1N2J2KP6zLm+t58nJRXyZDYpGpDYZQO7
- PKQliTAzCCn26IwU1ibV6SEoFgPjJDRtU5Td/Am4WSVZhdhYZ66a1GgF4dX8bFHb0NR12/Vt
- KT2/6G/9lwOqkY2G7TNHLp17i3Yix64WaGecqtbMLkpgzBN+lFWzok+EkO0fPYoYQh6E27Am
- JHpk0LvQ/uAf3VyAfqQA0IC9xgXYDjkvAmp0Q7pDB299RmMrcGoXubbCPdBna7L3XStIukU9
- qJUruNGNOuS8L/SoIJWy0Of3sfbcLS4qDOmL6F0lZTqQfKLIZfqtHeoKBWJ6cXycacQfA4gZ
- naYhTYSl8dKsmjpKS2ZAWr2sKzn2gRvfsXmZK+Jl9hKJHf4EX6EImJPuJ7WCZ3TAKaRsDMMh
- SSLYH2X8iQOaxXhcjdg6Opz7Wka+OW6G3wqBxkm3udINTjkvYdklOneB3UOudrWQ3HZ1chct
- HMCUyRERKxBi46oOam7o64swN7WBqsNtxocthgeRN4I4s0jemqwllx5uNaGmG9+2smWHUYzC
- 6fIwPcMCiikCExFqQh7N9S1rE9PtPZTk7gRO3hnHhrrm1el2SR41sYdx8fViIcRTosaczhg4
- 5A7CDpLuAXNlkPfaZxm6hP6b5+1GF0eQFG5zwaQxiNI0Dqx/yrUsfSkFt6vR9QpOREHltK3X
- JM7rn+46vLvy3Ck9mJ8py2qBtY3H7B0x2pNTHLoOZfkqfhWjyYtnJGAsePWsHl7jWlMG5WfK
- wZnL/mhWsGFSH2OqPzE3gBp/dc9OoStUdwbJuGew3zm6e2E61lb6+8O/lMgxh8clBXZFz6O1
- 78tFrLcwacheogjj0ryUCdgVY11DYJXK5F4DvK/PPcV1J9AX0MWwPLZc5pfDeo6+vi29JWeD
- BEnZlMl74OZX43YgQI9RBHgO816WTkER/U2B2Xb/9wybPQHnvj7dilr6Is+L90cGY5Wy9IDE
- /v0c+L0+6xT1nWDds1tAXVWLMnEATCQXUFevEGj+2b1dybrMy+q6+i8uS2GOglcfnp1M9s/C
- KlKekpC50P9CYganWVcUav47snsELbusn75hW+hznQaf50/XaFtIQU4h63ZVSGjpsG8SWKuK
- pKiq8qAvBKiBFwi6JQy6v1DW4zM82ZGwSFDC97tFHV1rU08Mh8lGpP68KnvbrgfRVSWx1/oL
- hNHYrsR/FublEFm9tH9et9FG851e/X4aUZhunhxudRREedX1fVumgp1iwQuZhyYkZ1z+H8t6
- NyjkTSuuHjWjMg12O/hV/f4Q2Jb5/6jPj2MPD0bU/FroNpuJYtzuuZipjoHOoFb9gwV6Mtfo
- cq5D4+Pz6qe58e/oNvzyLEVXfgS0YLFsR3zRlU5o+kCYuB1SfS7M4++wbttUgjt4hah1npdN
- ffk10EwwX0qPYbn5V2Sd52EftLL+J17XRWvfn3shXTsoIEXA5icA3styXyrYUZ6jr29Ox6tv
- yq3zppSzSzWHucl6OYd5r09/DTZ7/pavTz+XIm82+4XW7QL4fWnWGeoLzrDu+S3/uz9+Lmpf
- TF3l0s+69Uvn165I4yQz3HwSJ2nRPt1to8CPi/7zm2mHx/mRyPe/HQcPVepzZhnmOG+Wf/Ir
- 3RzbcBTd3y0449z3hfNGP5IlSbpLkhHzTKWOrVV6ZCZ586l2E8InIvyw+MNfP2aue3A9qacG
- C2j37xZqaH0uG44xSre/cmqCA+/HgoOJGbybnYCVMPtijPmwFP5YvnUstBGnB7dZL0uOkOqv
- FzUEprmAX55QsP0IYlv1F/vMbZ98lzN8GN2CMf9lzT/XsWsA+M/IkAkauuFHfuRH/qMsEXX+
- +pfkR1zUd411r2/ZttWR/z+omB/5kR+p67rtx/+6C/qRH+HcI8K9IPvTN1RDW+TZTs6lWdUO
- TxAXaZwkad7+McOlzN+k/Kg6aqj3Cyv4T/0dYjRMad4My+9/+USwIOv+xrGAQ9/+shn6R6pi
- 98nofoN1Wsah67px3v5KW5x16ruuH4YZbhL/iGzL/uLd8LPn/pEf+a2pb5j/uVXvR1zUd411
- L2/5f+RRZPoB5HDSAAAAAElFTkSuQmCC'
- 	) base64Decoded asByteArray readStream
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldObliqueDark12Data (in category 'dejaVu font data') -----
- dejaVuSansBoldObliqueDark12Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Oblique Dark 12. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 12 15 4 0 255 19 0 0 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 16 23 31 42 53 69 83 88 95 102 110 123 129 136 142 151 162 173 184 195 206 217 228 239 250 261 267 273 286 299 312 321 337 349 361 373 386 397 408 421 434 440 450 463 473 489 502 516 528 542 554 566 577 590 602 620 635 647 660 668 674 682 695 703 711 722 733 742 753 764 772 783 794 799 808 819 824 841 852 863 874 885 893 903 911 922 932 947 959 970 980 991 997 1008 1021 1021 1034 1042 1055 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1068 1074 1081 1092 1103 1113 1125 1131 1140 1148 1164 1173 1183 1196 1203 1219 1227 1235 1248 1255 1262 1270 1282 1292 1298 1306 1313 1322 1332 1349 1366 1383 1392 1404 1416 1428 1440 1452 1464 1483 1495 1506 1517 1528 1539 1545 1552 1559 1566 1580 1593 1607 1621 1635 1649 1663 1676 1692 1705 1718 1731 1744 1756 1768 1780 1791 1802 1813
  1824 1835 1846 1863 1872 1883 1894 1905 1916 1921 1928 1934 1940 1951 1962 1973 1984 1995 2006 2017 2030 2042 2053 2064 2075 2086 2097 2108 2119
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldObliqueDark12Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldObliqueDark14Data (in category 'dejaVu font data') -----
- dejaVuSansBoldObliqueDark14Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Oblique Dark 14. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 14 18 4 0 255 22 0 0 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 18 27 37 51 64 83 100 106 115 124 134 150 157 165 172 183 196 209 222 235 248 261 274 287 300 313 321 329 345 361 377 388 407 422 436 450 466 479 492 508 524 531 543 559 571 590 606 622 636 652 667 681 694 709 724 745 762 776 791 800 807 817 833 843 853 866 880 891 905 918 927 941 955 962 973 986 993 1013 1027 1040 1054 1068 1078 1089 1098 1112 1124 1142 1156 1169 1180 1194 1201 1215 1231 1231 1247 1257 1273 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1289 1296 1305 1318 1331 1343 1357 1364 1375 1385 1404 1415 1427 1443 1451 1470 1480 1490 1506 1514 1522 1532 1546 1558 1565 1575 1583 1594 1606 1626 1646 1666 1677 1692 1707 1722 1737 1752 1767 1789 1803 1816 1829 1842 1855 1862 1870 1878 1886 1902 1918 1934 1950 1966 1982 1998 2014 2033 2048 2063 2078 2093 2107 2121 
 2135 2148 2161 2174 2187 2200 2213 2233 2244 2257 2270 2283 2296 2303 2311 2318 2325 2338 2352 2365 2378 2391 2404 2417 2433 2447 2461 2475 2489 2503 2516 2530 2543
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldObliqueDark14Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldObliqueDark17Data (in category 'dejaVu font data') -----
- dejaVuSansBoldObliqueDark17Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Oblique Dark 17. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 17 21 5 0 255 27 0 0 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 22 32 44 60 76 99 119 126 137 148 160 179 188 198 207 220 236 252 268 284 300 316 332 348 364 380 389 398 417 436 455 468 491 509 527 544 563 579 595 614 633 642 657 676 691 714 733 753 770 790 808 825 841 860 878 903 923 940 958 969 977 989 1008 1020 1032 1048 1064 1078 1094 1110 1121 1137 1153 1161 1174 1190 1198 1222 1238 1254 1270 1286 1298 1312 1323 1339 1354 1375 1392 1408 1422 1438 1446 1462 1481 1481 1500 1512 1531 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1550 1558 1568 1584 1600 1615 1632 1640 1653 1665 1688 1701 1716 1735 1745 1768 1780 1792 1811 1821 1831 1843 1860 1875 1884 1896 1906 1919 1934 1958 1982 2006 2019 2037 2055 2073 2091 2109 2127 2154 2171 2187 2203 2219 2235 2244 2254 2264 2274 2293 2312 2332 2352 2372 2392 2412 2431 2453 2472 2491 2510 
 2529 2546 2563 2580 2596 2612 2628 2644 2660 2676 2700 2714 2730 2746 2762 2778 2786 2796 2805 2814 2830 2846 2862 2878 2894 2910 2926 2945 2962 2978 2994 3010 3026 3042 3058 3074
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldObliqueDark17Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldObliqueDark20Data (in category 'dejaVu font data') -----
- dejaVuSansBoldObliqueDark20Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Oblique Dark 20. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 20 25 6 0 255 32 0 0 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 25 37 51 70 89 116 140 148 160 172 186 209 219 230 240 256 275 294 313 332 351 370 389 408 427 446 457 468 491 514 537 553 580 601 622 642 664 682 700 722 745 755 772 794 811 838 861 884 904 927 948 967 986 1008 1029 1059 1083 1103 1124 1137 1147 1161 1184 1198 1212 1230 1249 1265 1284 1302 1315 1334 1353 1362 1377 1395 1404 1432 1451 1470 1489 1508 1522 1538 1551 1570 1588 1613 1632 1651 1667 1686 1696 1715 1738 1738 1761 1775 1798 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1821 1830 1842 1861 1880 1897 1917 1927 1942 1956 1983 1998 2016 2039 2050 2077 2091 2105 2128 2140 2152 2166 2186 2203 2213 2227 2239 2254 2272 2300 2328 2356 2372 2393 2414 2435 2456 2477 2498 2530 2550 2568 2586 2604 2622 2632 2644 2655 2666 2689 2712 2735 2758 2781 2804 2827 2850 2876 2898 
 2920 2942 2964 2984 3004 3023 3041 3059 3077 3095 3113 3131 3159 3175 3193 3211 3229 3247 3256 3268 3278 3288 3307 3326 3345 3364 3383 3402 3421 3444 3464 3483 3502 3521 3540 3559 3578 3597
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldObliqueDark20Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldObliqueDark7Data (in category 'dejaVu font data') -----
- dejaVuSansBoldObliqueDark7Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Oblique Dark 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 7 8 2 0 255 12 0 0 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 10 15 20 27 34 44 52 55 60 65 70 78 82 86 90 96 103 110 117 124 131 138 145 152 159 166 170 174 182 190 198 204 213 221 228 235 243 250 257 265 273 277 283 291 297 306 314 322 329 337 344 351 358 366 373 383 392 399 407 412 416 421 429 434 439 446 453 459 466 473 478 485 492 496 501 508 512 522 529 536 543 550 555 561 566 573 579 588 595 602 608 615 619 626 634 634 642 647 655 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 663 667 672 679 686 692 699 703 709 714 723 729 735 743 747 756 761 766 774 778 782 787 794 800 804 809 813 819 825 835 845 855 861 869 877 885 893 901 909 921 928 935 942 949 956 960 964 968 972 980 988 996 1004 1012 1020 1028 1036 1045 1053 1061 1069 1077 1084 1091 1098 1105 1112 1119 1126 1133 1140 1150 1156 1163 1170 1177 1184 1188 1192 1196 1200 1207 1214 1221 1228 1235 1242 1249 1257 1264 1271 1278 1285 1
 292 1299 1306 1313
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldObliqueDark7Form (in category 'dejaVu font data') -----
- dejaVuSansBoldObliqueDark7Form
- 	<generated>
- 	" Form data for DejaVu Sans Bold Oblique Dark 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^Form fromBinaryStream: (
- 'iVBORw0KGgoAAAANSUhEUgAABSEAAAAKCAYAAABL2JvYAAAABGdBTUEAALGPC/xhBQAAACBj
- SFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAAABmJLR0QA/wD/AP+g
- vaeTAAAAB3RJTUUH4AYPCTYB/HnOuAAALyFJREFUeNrtfXtsVFea58n23bk1Vg2+lmF1Y6+X
- OxaPMjQ0FQih1mFDkaZJOQ+GCiFyhQW5QjtyOU2gi2bCVA9NU0uTSQ0zbMfZIGI2yBRqxBYi
- 0+qapFGqSRCVpFGqUeiO2bChPEHe8gR5bMmqVcWtav32j/O459562AYc6Jl8Usny/e4599zz
- +M7vfK9LcIdofGQEudzwV/a8/v5+ZLNf0GePj6C/vx+54cKdev2v6Wv6mr6mf/U0PkJlbX9/
- f0V5/8VA1rznFmTy0d1hBALdyBUmV0dhOFe1XZMh3u7JULFYmPT91dpWjme/NtXyX9PdQV9k
- s5Z1cDWTQX//kOWea2wOFYrFO93cf7U0dq0fyWQSH6TTSKU+utPNmRLx9S1j3umk5E9jCAQC
- d/q1/yipWCygfbEBd1ukIn/DAgOu+5/ByPi4hTc+PoJ1Cwx4Hnkaa5e44G0/UMJ/2uNBIBDA
- TK0OoUhfSf3RjT54Hn4abUvdCO48VsLvXKaD1DfCSRzoOXdtWvvixK4A9IaVJe8JAK93+aHV
- tSD5a6ssPNThgz57Gba2+2E0r7GUvXQiBpdrCTb6fXAv3SB4o4MZLNF1hA+lAAAf9UVRp+mI
- vfEO3j0Sga7PR6g7hAZ9PoYuJ7HE9U2EukNwu1dN+l1Sh8JwuTxY1qxDb/5OWUwy/HkaLZqG
- 4P63y9ZxYyCFJlWFb9PLJbzR0QzmanXwt7djgWEg2muVUWNj/bjf5cJDD3mg1jQh8f6ghV8s
- FvCoywXf43580+VC79mBmxqzgvReY/39yH6Rt/CHLidhaHWI9pWXoTcGUjA0rezcG7yUQLPe
- gFB3CM367JI2jo+P4Am3G6Fd27HC7Uby8lBJHVuWGtDnf2fSmJATl5/yfBofH8HOYBCh7oNV
- yx7sDpXgUF42GNxdsm+PXetHIpHAxx9nkEyet/A+SqWQSqWQTCaR/uCKhff2/iAIcUAhCsKv
- fXBT41eJJoOludxPf27FkYfCYQQCHegfGyt5T/ue+um5BAKBAOJJ67tdjPfC7/cDAAbfovf0
- 9H2IYrGAZDKJTCaDZDIp7i/kcmK8xsdHMDJijlthOId4PI7sQBbJZFL0f7FYwO5gEKGQVW7a
- 6VA4DL9/i+V9isUCIqEQgsGdJfKKj+fAQBapVNrCu/JBGslkEqlUCun0Fdwuei0cRiCwo6zs
- 5HTqpSgCgQAyg6Ml7xcMdiGbt65dOl5n8ZsKGIj3n/zcic4Wn6RSSKXSSKVSyHxMZRI53xuF
- y+WC2+2G2+2Gy+VCtPd82QoGLyVQTwhIrRu5QgFnD4RAiI5tO4NQZ3zLMmHz+SxW6DpCB45g
- wwIDvs5Dgjc+PoLAYg3EaLNMiGfud4EQAkKcQqh2LNNBSKNlohcKOawX9xKos1aIZ9M21SNx
- yRS6+5/2gBAC77Ov0olwKgpCCNxP7ANABc71TBwztfuQK+RKQP/tplc3e0GUOciM0skwOpjB
- imZdvI971VbRL5dP9mCuYWBGjQpCahG/cN2spzsAh0LKlju5OwiFmDxj8bqSCfriI7Rf1Lql
- ov/e3k/LqaoKVVVBSL14ZrFYwC6/D07xTIfYyDs9LhCiQK2pgaZpUAiB8cBWAMCHfT1omqGK
- tmj6fWIhXDzVi7kzNcZT4NsUnda+nwrtfdIr2kwchmUjH/04g23BIDweDzweD8LhaFkBcKCd
- 1aE0ik2yWCzgsWYdRFFYP9fAaF4qANbYUD+eWOGGgz9bccC/9aBUHy2naRoMYy6iL52yPU+B
- qtZAVWugEAWBXYkJecViAbvb/airkcaprgmxN9Jme4kDkSPvAgC+v5quP2vdBJ71+0Vbhj9P
- w3DQvksN3LDdF0OhkMPK2XTea3Pbyj7H0l+EQGv6tthovm1oIAqVR/I9fN4d6vBZ2jh8JY3V
- 33SZ60JxItD5UoUxUWE0tyJ9ZfgmytbAvaJdrKkrybg0x6l8Cx/6BVIvh6EQAk3TUMOeqdbQ
- NWftqz0AgEibG4QQ+F94HWf2BC08ANjzOF3PXE4brV20HjaPXZ5uAED7YgOEELHeCSHQ568H
- QAG5kxAQoiN5eQgHWRvca34AALh+IQ5doWsVALpXusSc0jSNyQwHIq/Q8dveaoj31ld8DwNn
- e+G0ybG2RlNO+Z43wejFIxE4CYHWtGpSIPKjXirXPZtik1rfx56n88No3X5T8uF6Jk77SmmZ
- 8F6xFth73krbXunwiP6sdE2UX7W9ct2rbu6970ZKvxGD2+1GoOOlO92Um6YfrHGL+eHtOopC
- IYcWQkDmPCXuGfosiVouR2qXT/lwNdU1BdCDZKNCYLRundb3H7qcRCDQWbKPXknF0SLJT9fq
- 71es4+rpGH2/uW0AgBM7AhTPzFqJYrGAHY/7ENx2WNx/+c0e6NK6DB08CwA41O4GIToW6QSk
- cZ24/53DMTTrOjRNg67PR+zwO5bn/8PekLlHOFsExruddO71HiwwDNaG5pI2HH/Bb+7hi7fQ
- fbaB7utqg3dS435jIIVGMc8WiT1FIQSkfrm47+Ruun+427ZNWOfeLX7UiT2CwPP4ngnLAFR2
- zmFjxPfyU5EQ26cI1LqFJQdhmQqFHFbOos+UzyF8Dw2/lprSfQJ7sL08duJS2fsmQwfavQwz
- G2WVKAfavXRvrZtblv/KVj80TYNWN7dsH7wu+C1l+by8OmNeWf73V/JzlgM9b5cqIYc/T6O5
- RoVaU2NiGLUGikKgz39M3DcZTKvV1UHX9bKYVdNk3gmTpzig6zp0XUeNWlORN0PivbzJB4Uo
- 8LYfoNhtvg6i1ApFWftiA0SpRez0VaokXmqAEPo/wOW0hMGbF6On7xwAGasqcK+ia+LEjkBF
- HEr7a4bAknY+URRo2syy/Joa2t9anY7gtlhVfmj7wUnzJ6Lx8RE8u8YrnT0d8Hg8cBAC/+5T
- 0rgReJ6m54F9Ena18Nl5Yf96T1m+r4OuQ45hK/LbTb4dsw59lhSY1XrGuFjyboPvJ9Ao7QeE
- 1FqUnwefpXVHjpWWBYDvr6XrRVb4F4sFbGjRSvYY3pfLnebzZEwHAAGDgOiLYBACl3S2AoBT
- O/3Qmu7DHKfZ77eLzk+ApU/y88fjL1qui/MuIXA9+iML76UNbhDSaNlT8/ks3E4C4nCLfel8
- bxQKIdCXbMT1VJzqnBjOHnivl9a9xAVCHKLu2CaPkCsOQiwGmS2LpbOXvsaiBOZ7ZejAWZQj
- rjsK7HjVcn3rA+a5JhBJWMb6oXoi7b9WzBQwCIjTQCMh0JZ337bxSh0Ks/PT4bL819l7etv3
- Wq5HnjAxp32swyt1EKLDcBKQxqcsvGKxgA2LNRDiQPTVX4rr1c4t4+MjcCsERDfoGHUdBQCQ
- 4y/44Xn8RWSzWWSzWex90gtfZ/kXuXgsQg/NczcAABKRAAipxZatfhClxQJurl+JQyEKes/G
- YRCCwL5zAICj3QFpgROhWDt7MEQX98FXsMhBF+PxnbTj7FYU+lwC4pyDTRt9II4WocWlPAd6
- 3xsAQBWntQywc3A7PJyGoRAQJ534cwgBcSggHGQZZocXCjksUgh8O47hdtDoaAaNhMBYs0sM
- 5loGELWZTULBxwXkj9aaylZZcTk+PkIXr1KPJd80gQJ/744lOoizEQ8udZfwACtQlfuGKw1U
- VYWiEItClytBiFKPYDAIJ1EQ7fuIClK28GTFZ2DXCRQKObiZUHfdvxLNdfRd/TtPIZ/PooXx
- 3CtWoF6h80FWIE+WisUCeqNRhEKT20xvfJJCMBhEKj1Qls8PgGpDMxqYApUrSK693SMAsOub
- 92MhU6SR+lbLAUoo7Vn/cxAzNtaPOQpX9NWJPvM9f4z2l9iUFBjNbDwWbgIAbJir2dYPG1u2
- UZbj802vGq9LUhZpM3XUszb4d56S2utE73sDKBYLWMdAeOjAP1jq9u80N8Orp2MUdDoWCdnA
- 7wvu3m8ejJrowUh+jqykkvuLEB2pGzeQ3GXKEbX5Mes9ioH+sTG6Blgbx8b6xVwjxIk6oRRX
- EDt91fYMCRQs67zpsoFIwlynhECdMQtN7DAdOngWp3b6y4wlbT8ABFqsfcr7PBBJiE1HW0w9
- UK5n4kw54RTKMa0lgLGxfirrCIG+pBODgwk2dxsBUFnYyMr1/jwu3pMDdrNeA/1jQ2hl65wr
- OHkfW3/1SH42hGKxAG+DSg9qb7yDQrGI65k4HDZZVBjOwdukWg461y9I4IMQ6Es2TWpdn4pG
- EQ6/Zrk2PjKCbDaLXM56+O5cRtse3HMSX2SzZT3LBrLZEm+iwnAO2WweV/ooWNJarF5A5Z6V
- ZHuWNrcN2WzW1rZSGSTatv8M8tmsRa5cjPciFAoh8danFa91MZAUiCRL6jZ5iRJeVuqHrO25
- 9n4px8vlchYrdLX6rf05ULFMsViw9NlwLldSD19Lf6yKVXMd1qP31HsoFIsUezioIkmmgY9S
- zLizqMR6XY1uZk2NjfXDXSsZCSTlzO2mo11eEOfyknn1WBOTt85GNNWpcD+xD+nDMURfMsHv
- y+Ewkr8ekmR1PRJvJaBzRdHpS3RPV6xKXbrOFIT29iAaDguPjPGREYxIP0AyXq9qQygUwrL5
- egk+/cXLYczU6pjR2CrnbgddPR1jyol6+P1+rFrhLouRZaIHt1qkh9MwbMokE9/+zFJmfJzK
- pRfXukBIPYrFAg50h9BUp1qMLntDIUR+fHLCdl9g+J4QAn3harQ4poapD+8OghAFPW9fw9Bn
- STqP9Vbssyl4KtEvX6Wymsu8a2/3wEEI3E9Ebuq+c6/34IG5BlM6XsbAe71l76tGlfDh3cIf
- upyU+M6ySsiOZXp5DENMuXUzmHYymPVWeXZsG79wfcL/x8dHBAayY57UwA0bFrw5HHon+QDw
- k3Y/Qnsprh8fH8FGn8/igLFJwnyGIZ0bWjaIe6ph1+nmV8Os1nMCVSR7HnleYAmuLHWt7sTe
- zV7LuY/P5U6fD+HoL0rWwuhgBm1eL6KvWp24xsb68ZTfj974zxENh9EbtyowqVdc2uLZJ9Zg
- fz8ymUzZ6JnRqxl8q06FvnBjCY9jXuGhxjBTOSqHcQHgpY4A/Ft+UnK9WCzgWa/XYszjtCcY
- ROTHR3AiFkM0alWMjo+PIJ1Ol0RxDH+eRigUEo5JJ38YQThMccY7P40hFDqAfD6LUCgEABgZ
- GUGxWBD78qndFPvVMAca+14wwN77Z/E4+ofGStq8KxBAaFepl3ihkMMWvx+Rg2+VXN8WDKL3
- 1Hs4FA6XGAGvZjLIZrNlx5N7CpYbi7Gxfmz0+RDadQSVKJvNIjdcwOWTPQiHj1p4x34YQXj3
- 0ZIy3GMx+vc/L7m+KxRC76nfIX04hsgPj5XwTQxkxWSjgxkEAoESz/SJzlQcV8ke1OT4C374
- u46LC/T/18t2AAf63BJN/3diU4cPhMwRgPiv/T7MrNPYwbuO/q2pQz6fxSLJyuD1euFyrUY2
- n2eHNCcS75/BHELgfnAFtay8cLykHfxAR+rX0M6SXoi2SRHgz+6xxScR1b5TEP/WKxFJeaYj
- 9ckNs9PGRyhI2/UmbgdRa0C98AwbeK9XeB6lbtzALqYM8u88Lgbt571RqszRH7J4jsbjceQK
- BQquHVZFI++T4WHugeNEPEMVOx/1RU2LJCEwHugSda5tUkGIgkDnDsTjP7MobhvZZhXadRCZ
- TIZOJtsk4xYttWGteZBysk0uecnckA+exfULzJPI6QYAYUEIH0pRC0ktVcjwvkowxZPsbTf6
- cQZdT/mFUpAfMAqFHBKJBJLJpPglEgnhVjzwXq8Yc62pBbHYCcu7FIsFZDIZAMAa3VTIiTlc
- uwiJRALpdBqZTAZ7uqgHqWzlsito+JiKMWfKsnUCFB03FeyKjt6f/w4AcOlMAokzl6T1oyBy
- 5F1cPNXLLHx0ncj88Msn2OZC50M1nrlpE/g6zNCPM4kE+ofGLO1NXxnG2BAHMrWIZ65LdTst
- VkMuL7iSxr7+CSEwlraLfhfPkYwK1jXCwPIbhyUgReBui9juIYgcO4nWWrONQuHnoB4HhUJO
- HK79O49Lz56DXKGAfcxCpC0OTKEsNcR4mTcFB0RODuLfpCD+N+k0sl/kUSwWUCgWhYzSl2xi
- a6YgrRt6aDQV9lQRLMbMuQgj4+NirrlWf1/iudGz1zz8Gau2Yz+zGMreRPskaxjvT5k2LaR1
- 67rO1rZXyIVioYBisYDOlaYXO/cMEYBPGk9+gJSV1eYhxUB6eBijoxkYbCxSnwzglS7a/1M5
- 4HGSLZaEEHif/CsqV8dHsJwrVzgodRhC9v/uVC/m1amWvgOA09GwmGczGID3bqaGjw/7eqjV
- kPE9j+yg64hZjU3lTwddH5I3D+9b7+aDlrZpdfww1YjUwA0RnkcUXRhr7NfM8rWIp5JYzTyE
- XZ4OiWcaFB5jypQa9j7qrHlYxj3zFQPpz4ct99XNtLYJAN55I2bxKPM8/BwKxaKlnOIo7We5
- P+U+MPctBU4mawqFHDZKERAU7JwR+4L4ORZhfHyEGTno+uf3+DoPYc96D7gnRD6fxdI6ep/p
- Qbwd185RQ5PRul0YX40HusyDu7MFmasZLJyhCnnM91XXSrq2aHQAtcrfGEgxhRg9+CjSPOAy
- 2EkIiL7Gsi7KKSGHPkvSumqXVw2/kelm19RZSXmk1qglzzwVCcHr7Zr0erRH0wAU0K6UIkFk
- D0/z0EjxEQCMjIwzrFALn88Hj4fJtLUvIv9FVuynsrK1klJ362KOU5vR8/q5qm1fN1eDOqsJ
- Ol/jjjlYvUQH0anXpcBItY3MoGqNyHmzpwfJ80PI/CyO3vh7k+4zmR5rUqG1rMJCLpscjVhs
- aFCbHqtYhstc91KKPbmBKJfLYXAwgxaFwPvsQYvCFQD6IiE4iOnt8tzD1NuJ1D5U9jkmZmtE
- engY+5lnfmDXCcsa9TzyOHTiQCx5FZOlc/sCIKQRmdFRU+G34RCS+2i9kSMXUSjkEI3SiJSX
- olFL+Ny1cz0gxIHEp4PmWjDaSp5T/r51JfddPRFDPZNLmdEMdWQoUx8ADJztRS0h0OZa66mE
- D+9evlWpcPEIOzcpjVjPoqq0lnXIMYUHP7hOFtNOBbPeOo9iVTvmnOj/sbF+5pXrRM+bH+Kd
- N2JCURvYlbhlHHqn+Raj9NmLLNKFylZAxuIORPs+wgfMGC7jmomw63TzgcqY1T4+/Bd+7QPJ
- IciBYDBIMbTiRPhlqnCshCUn4nEcwM8vsmLPWk6ZdJ2TLqfUo7XVY+7hDUuFsq8Sxq2EYzlP
- jmqUeRfjvWjRNdEm38ZdlnLNcrnHaTnTE1lH/MJ1DH+exrwZKtRZZnTmxoU63Us/HaQOMHM1
- yFGhl96Iwev1YiE3Vta6kc3nJeypYCbHrMrEmLUcT44yPdfXI5ypCFHgXbfNUq7R0nfWOmUv
- W5kHUMc9ByFQ55Uah985LLdHEWc4GecmPh3EuYiJcy28wVLeqiaNnhk+HcTbe6j+wl7Ojp0F
- xmXnRy4fvO0Hqp6p7OU6pXLErnSspoTkWk6uaKHW0ixGmNad03vxXhgKgdq0Aq1zNRBHI2Kx
- mGnBFBPxOZFD4vKbpneZIjx3HkMsFkM4HEby7GW6cH5uKl74geUMCynknkdc0z46mqEAVplj
- AST5fJYKMbaxLJ+pMYDmgNGkwbWyG/kvsojFYohGo9AJgcuzHrFYDL295d12P0qlkEgkkEgk
- RKy7nbiAl92UD3f6LAKcA2hZaconAfc+kimfz+IxLnAXri9V6HABwzwvhy6zA4zuxtMMOHBv
- mbGxfgqmpB+3bgkgIf9snn/mM2uFwhMA2nRrOX1Zh7ifesrpzLPS3NxkBSUXRrIHz+hgBqvm
- GmJRulz3IxL5CfqvUc08P+yoIkREFQdJTucSCWzx+6GLg77TYt0ZG+vHUqZQMpa2U3C7wQ2i
- tOCNN2KW/tWWb8HGhbpwMRZegIqB7m7r+L1tU0rQXz3Sw8PC64OnDpBJePUSXQjS7ZLS2uRL
- v8Y2W9lSXoy5nGtzN6BYLOBpFmLu8TyE1Cc3KrTXXD+ibsWwhJ9x70qupLG3gXvxceLPsR+o
- +HVtpi4pzxXmbUIVEaJsTQ3t68UPUDnB2ri2yerNKssz/87j0js64Pf7UatwYHliCmWJsPIT
- Zwsyg6OmrBGgwIlA599b3o+Hasj1i8M6O9CZfUxlmQBeyhz0CdlJ7xUKjdo5WNiggii1qFUI
- jAd8aGEKKNnTdOBir+hX+0HJMpfZ8+0hhi8+zkFOLXrevFwiD9RmczzLed6Id2PyZHx8hBo5
- JNky1N+P/v6p56TaFQggEAhg3RovOzDR+SCHG3oeeRormaLM9/wxU/YQBwIdO9AdCCAU6RNe
- MYTUIxKJsL1MQfhQCtcvmJ6o4XCYgQ3az2ZIiQLf4xvR0/Ompa5wOCz2xeCeM5a2uTyrBVAM
- RBLmniYpAEdHM8zblV67MZBCo8UzV0Ggm845UTebR2Z9BO4HVwmQpM9fIZ4bPpSy3Gdvkyz3
- w+EwA7DUs0IuZ+/n8v1J65TnnPvBVQgGt5n7BdERiUQQDAbR0/chLr/J61Hg829ENPoSbtww
- 3zObz6NziS76l+9lvueP4SgLrzIe6BLjbqzaik1sfRut7fA2M0UjC8HiRgP+C+w4KvpWJwSk
- /iFc5G1l62VsqB+xWAyrF+piTEJ76aH+g3Qa7auoIYCniBFrpYwSkq9vtWGpMKqNj4/gQHcI
- brcbPt9GJJNncYJ5EXD+za4p3g67kuLoDq5coPhO/pXzOABoeplZqgrXyk4AKJGPrvs9CAZ3
- 0/78JIXF4lBDoOuzxYGQzx3XkpWYN0sV67rjfhfUmhphYFRrZqBGrTM9IQkRhkquRDHmLhCK
- xUq5tfL5LJboOh5+xANC6pG8PITxkXFcz8QxQ51nyhSFGt4VYipaR69mxLw3GGYJ7j8jzWcb
- PmJY0I4p8/ks5qkzEL+SwYoZPFKlEacvmG2oRJfOJBCJRJA8+5mQzUqZZ6vzngZgTaPh2xTF
- xiUueFo9VJlm27fleVnLMNvI+LgwaEf7PmJpkpgs6gjAwfYqUylkyjM7nY6GxX7sWb8HhUKO
- GlYUBQpR4FqyHrlCQUQ4qQ3z6EHQYSD56yGcfzUqyhtLfVjRpIIoi5Ar5PDoN13wtoUBoPx9
- jkXo66MpkQzDQHDbYZzZE4RhLKAHUYcOo56waA9rfZxSL4cxQ1XhecQMXayGD/8Y+PK6DURO
- CDwkK1s4xpgcpp0aZr1lHsOqAjcyjDLR/1YFViOy+bxwnvC/cPyWceid5gPA4LmEJXWMe1WX
- OFfys4K+ZCP+arMXhDiwgnljc7k1EXadbr5l/towqxifhrUAzPO27/ljkr7AycrWInbCNJRU
- wpJ3PY8QeB7ZhEeZAde/83hFjFsVx04Dz45nxbgxhys73/6/WTeBNnMmiyR1lGDPqWDWr5qX
- /yKLnp4eRCIRLHW74fWus+iaTENII5bM53KWKuCr4dxp4VXBuNXOVNXKTUkJGWlzgzhbShKO
- yjRwthfNus7yRThQyzYqY8E6ADSZaYsELEmtqcgqFgsYGuqnob31i/CtJhVEqacAUaEhndyL
- I/pS1HrQsilAAIiFJruJWzYiSYk2PJxGINAphO3gpQTqFZqvjdbvgEMhcK0sH8ffIrUlsC9Z
- 9p6XnqB5htLDZu4VrqgJRM6JUG27Eo8DQnu97xyOiVwXdrfp8fERJJNJcbjhGwR3Y9cXrqDg
- nRDozSuFdYQrk6+e4CCECjeeO04z1kku/WY75TAFGWxwz0iXZyMORcPMkk7BebFYwLY2L+o0
- TcovQi31E5HpYUagNd2HeDxpsSqMDmYQDocRDocRiUQQiUQQDocRjVrdrvMDWeztNj2S5APf
- 8Rf8NHfMOtPKFGjR4N12FN33aSCNTyGfz6KREAQif4/lDqpcMcNQqeBoZTn41CbqHfoiC7F3
- eZ5B8nSczWNqxeMeft5n4yXvLLxS6h8Sc1Tnyov9Z0x+bQvi8TjzBP21taxzDnp6etDb24tE
- 4hwA81CtL6P5SLYISxpdU7y9+vzViMfj2Mgsezwtg9kucz3J84HnDZW9avjhVc5zxJ/jfsKa
- 142nAfB17hKWFveazVjZpIp+s9wj5+RgbRRhxkzhPjycFvIjdPCseLZaM4Pl2pqNYFdsSmU1
- 3WDeEQTudmsO3Nd7erBmhbtkjpuHMGs4lPAyqF2OQrFohrPVtwoPM37I417nPI2GHYR7Nu3H
- 9lVGSZ8AVMGwqkmSx/WleeZMT0UF0T5rMmWhgGSWTJm4zJA9KwuFHJY7aZg7pw9eC7P514nb
- SSd3B4Vyihu2uCeXADtsLR16gucsOi7Wg30eco9R3/NUgUr7hKaPsHuTEkURc9O01DeKPapS
- XfEL16W2tQLgHuK0LqG4k9aa/ZoFgBMC77NmiAbncVlkln0I+XyWKTMNZPN5tn4pWJSfYW8T
- X3v8OQ/pfK58ZAKoMv1cvg/o83i6EDm3jOkdyRQms5aif2zM9N5wLBJ9It6zeT2NZpD2K94m
- ramFeqwx7FBiMCAE6owZdB02mh6KV05FBbg31vy1uF4sFui7K7UwGMaRPzrQxz1fHY3CI4gr
- +DiwTHxqGjArKSEvHolI67VVeHg4iAKv14sGybtBzhl7s8TDmO3hs6biQaF559iPKPUlsoBT
- 6lAYNWqDkPvck0ZrWoxmXUf8ilkun89iRQPHKMsQCoVE+M/gpwk4CEG07zzNB6XQsW+p01ju
- OFMBr89eKWTab9JpYST+2Q4fA8wdDCcpiJ2+VLEPFmsavGtYiJ5/IyKRn+CtYxHwKKDzr0ah
- 12nQ6mbCMAwEuikO2nqfBkKcaFvnFWAeMBXD/Nff3481jaYnhB1TFgo5LFRVRI6dxEpdh2Fo
- IMoiHDtitmGyJHtCzinjCXk1k0E6nWaRHlfxm3Sa4YmzFT+IxBWN+rLvIZ/PsgO9icvfPRIB
- IbXYuMknwu4HLyXQUKNCn726olfvUH+/CFnMZK7i/Ks0j32dpkHT6kQ/A0AX2+e8XjZOO45h
- 7Botn8lkWNqPWiTOvWWGaTIPoNL7WEjutX7E43EqG+c8hfwXWRFl07HSVbE+TlsfdENVZ4g8
- 1xPhw7udD5i43tzrqPwK7TrAFOdnxL2TwrTVMOt08Jjc5HsXxygT/c+xsWasQir1kenUwfDb
- reLQO80Xc1acAay41GKAc7YgPfy5CG/nXk4TYdfp5nN5XQ6zvrjWjNiZK5xY6pF4fxADZ3sZ
- NlqJHZt8prLnzWtVseRdz5P2Qq6EnAjjlsOx08GzY1eO+1yrqcHGzrf/z9/D8zQ9q8mGr5vF
- rF81j+ua1Joa6LqOujrNomsSafCIQ3j28rLVcO508Kph3GpnqmrlJq2EvDGQQstMDfrs1VUT
- W49d60fXOppMOBikLp7ets1IJM7h4BY/fP5OPLOaJhV1ECIsVJwosNWR+iQFgxD4dhxGx0JV
- KCF5bhH/1t1YL4ULyJYdTlxRxT3vOB3cbE2aW40qhWMLbxMnDenO5XLiB5ghz/zZw8Np6MTq
- 6SC3xeV5FGvYZs/DVz87n0QkEhEafO+aJ4V2nH90g26IyxGJRBA/TcOHd/r9CAZ3IpFIYM0C
- w3LAXz2bJmp2Soc5beZ96B8bw46HPfA8tB7xeFxqC908RU4z49vYvzMoNgEOHA/z9ti8I/lB
- xbN+B36ylYUCsOSwH/b1IBzeg2QyKZ7H3f75wuO56ez9DdD8Cq9Go2ZORkLgbmPJiC8nscAw
- 4HK5xK9B14VC0eot5IB3zZOWL5MViwVsfdANrc6aMHxLiwbX+h+he7kGojRiXoN54ONu4Fz5
- woWGOBQxa2ibwRXB30FXu19Y3RKXBukHmwiBOqMJkUgET67xQtfph5d4wmXiaITP57N4rxWK
- RQs/HA4jFAqJHFecV07Rw5PJEuJEoGMHdncFLdaoNpFvhQIXDkB5KB+vW7aUm95ZZo5Pcd+q
- LhYSSUAcc0RCdP4crWkxQqEQgsEg0leGhfU2cuwiDrZ7oc9ejd98nrZ4dIl7Tn6CV542ATJv
- I1e+q7MWIhaLYeEsno9ybdl3lInnPSopy5L8i7L7LpoKCubB2/WAAU1fjGg0iuc3sn6WrJam
- wrDRYpwQigaFen3x8AhZzsneKrLHsDUHUz1SN25guxSiwb195AT7Ls+j+NYsnq/V6vFUydNV
- TkKtGcsRCoUQCATQe+qiZQ3bv/64dbFmCTl4dTNPKl6aeuNWiMseb/s2bFhK3597QouwJOcc
- RKNRFj5JQ7R4XiCtaTl6e3sRDoeRKxQE4HF51uPZdXyt0X3JNCysRyKRQMfjPnjZxxo4uJVl
- Iwdm+vwVWMtDjJl8EPkNW7eLfYPP83Je8fZrIg2C3sSMK6ZSyJ5SRZRdtQtX36H55tSmx3Dj
- Rop6G7A2mc8obZPIo+TZiF2dASbrqJyW8zfb+7l8fzKPNiknJqeD3SGEw7uxqzvEPJZo+hEz
- XUQ9wuEosl+Yfag1Lcf6hz2Wuq15scxnWNZNrRsbRYoB0wvSkiid0P1INsrKh3PZq9hMV0AQ
- 6NiBeDxuOTAtcpoAmVMlJSSXZTwfLwCR2oETzbtze76eXUkJWSjk8FAjAXEun/SXuqnXt5k2
- hhsgxP4T6BAfA0v9LI5ls3mUx3eY8YzmNeq2eaMSQhDcfRKZTAZ7Wag5qV3ElFcfWMZXu48m
- i8/ns9iwwi0Ulq5Hq+NBGrWiwOPxoNkwxL7ufZZ6+l8+m0QsFkNPTw9isZjwOhwdzMBdT6A2
- e7FxhV5VYbj3Sa/wmLNjSrMNBHrDEqRSKTGPK+VxrzimwzRdTW9vL5pnqPCu67Ioa26GRAoT
- oxWb+XqWDI2fHItArZmHx5bpJXN6KvTZ+SSi0ajo58SZSwB4Iv1GrF1JzxehiDW3FleShg+d
- xjr2MTSnQiyOEPJ9XC6c6+uh8s7ZIubmZOrL57NYxTGN8W3Lxx+r4cO7nW969TgReKbDlK/E
- Ab//KYRCIcuHGgNSyoNoNIr2Cpi2EmadDh7fKzl244aBif5/kckdddY8tEmeZvyjXbeKQ+80
- v1Dg+bkJAp074GZRbNxrn6YTo3uif8sLwruOEEPg+Imw63TzgcqYVZy9GmbD7XbD620TebQ5
- xtGbVyKVSqG1yRz7aljybucRp4He3l7sCYfh9bYhm8+bGNdoRTweFxi3Go6dDp4duwrcx9ab
- nW//n+85FuzJdAQ3i1m/ah4nHils/6iLqTinUXpOqWw1nDsdPKAyxq12pqpWriQnZGJHoKwS
- 0tSOVs49wym5LwCiLEJfXxSE1AqvH8vXhgmBpi+2JNfnACty5CKKRfNwT4iC4G4qYE7tDUku
- 8Qr0Bl3kJbGHc3BBpDavF9dMr4mWSVmOK32YhoPnSv1hz19IJ5JV0QDQkKM5kveFscAn2mUq
- h8wfV2Lyr/jJP648kBPJE0JgLPaVeK8Ofmp+sIcfINYv1EvK8baMjfVb8zY5DSTODYrFozNF
- mj0R+y9eDltCGNQZTeg5+aFlvPlY+vxmDgl+WOFWOPEhDptXK6f8QBYvh8MIbp3cl3FvfJKC
- 3+8X3oBlx91JQIhu8cyk4zgHyWSSga0wmnUdgc59oh+5t57s8eDmeWEuXC/xttFmGiK57ehg
- BitmW8eB52Sy5wjR6nQEnomI59r58pzgPK7UlalYLOC5hz2WcmpNnUjWu0jy0gJ4jg4TpJt1
- mykEPjgUtijj5Pt4biEx35hyxt4v/LBKr9dblMH0K8smeBL3fDZkSUXA21iSd4wocD9ofsHa
- /o4ylZYl0JesFyBbLivnp4lfuI5nPLbDskNHT9+Hom5h1bUp7/P5rMjlx9vreeQ5yz1migRF
- eJvyucuVKdyaxlMZyIYDnmBcm9uGQrFYdsz42lMIVbrKyobS8SJCfgM81EVBtPeXcndSzyDm
- CTM8nMM621q/XbRnvaekbXyOyh9iEnvMTirjB99PWPLX8Bx1197sKQnz4h/3KClDCPxdr1jG
- SVYc3vgkhSUNOlS1xlzPzPhkescnMXDRGtLOc7DIH5URnvK2dwvGzuMU/wAZA2Zm3QlrffvO
- sbxrBO62fbiapPs9l7fmc0vbNPTrJOZJ767WzRMea99f6arYz+X6k4MTWV5yWtlg7V/3g5tR
- KBZFHiF6naaq4HnYLGO10FR8bxQpTMyk7vK6CUQSIvRM9gAyP3SSFu/G000AspekNR+gPReu
- /LEuETYkXePtsSshzRAjY1q+vFyOqn2cj3rUDU+qHlM26kKWFwo5rFsgr0XTaLW8tlS2cID+
- 064ggtt+CoDurzsCASFXk5Hy6Wvs/fnXfh/8T23BqgXWfakaHdkVQh1P8VJTVzY5fzmiSfmp
- MjSdTk9aaVuxDSwVCd2nj0y5jkqh4Dwc+2bImotTYevA9C59ZZMHasMKLKo1v4xZjoZ/kxZp
- BqZCH2cyyBUKyA9kkR2wYnv7B2YymQxei4bp3hk9UfE+M0cek10M002mPnFAZnswz0s4ET68
- 2/l8nLnc++RIpDS0X/IcnwqmLYdZp4PH90o77pvof65kNDF4k+XL0reKQ+80f3x8BB0PeUSK
- kXw+i0c8HvEFXEII3G63Zbz12css31GYCLtONx+YCLPWWiIOOHGMI/IHEgKtqRXZfL4qlrxb
- eeqsefAsseIvzfg29UB/P4G50ntyjFsNx04Hz45n7bjPzrf/Xw173ixm/ap5spxc5/UitL3H
- cr2FRbuWK1sN504HD6iMcaudqaqVI8ee98HleQapVAqpVApbV7mnbFWdCuXzWRiEIHrqSglv
- OJcrAbTlvrbJQ0nk68ViqXem+bl0Mwxu/TxmqWKhETdLreyjKdz6MxEtn6nB11H5y5K5Mu9+
- KzQyMjLhl0rL0fgE5eyW+ckQH69y5YbZ9YlAOe3vOV/ZwasS5fNZFmZBQ9/mN1jzpN4ummy/
- 3E4yx37kluqREzHbPX/vNN1KvxaLBWxbw9MbTO5rzbzczawbub1TXcd3A8nhhD3nzNxzZw+E
- oOs0RNLyQbAKOcFuhWj/FareU6l/y40ZH8tqdU1mnHc87IGn9RFsDQZFwumbkSGv7eb50pyW
- jf1OULk9rFUKgRmuuJcP4xAzSE0kL6ayr3F59lVRX0+P+KCPrJiciG4MpEzvStnT36Y0kz9w
- VMkYdzeTUHzZjBwAsGmeeksKsMmQPSfkwS1+1Kgq1JoZ8K7ZPKVw5q+plLiCOXHuEgC+/kx5
- 0O1xwfP4c1jjdlcMe0+nUti4TAfR193Wtk1WFtzO+3gKFLVmBov6ur3v9MdEhUIOe7eHhMHr
- 3zpNhEPvNL8SZTIfA5j4nCg/o9I9082/WTLxuhXLVMOSdx/PbDvHTPbIiE9SKYrPnGtK6qiG
- Y6eDd6t0s/qTauW+al4lSiQS1GGjQtlqe9Ht5lXDuNWwfrVy91w81YsfvXGayPRkx4/Js0/d
- T6aD/vCHL8kvf/kr4n5gNbm33jEtz5Dpxj8NkH8pfElaWloIIYRcuXKFEKKSlpbmW6r3V7/6
- FbnXuJ+0NP/ZtL/D13T39ff/OnqUvP3++8Th+FPy5JMhsnr1gjvdpLuGvjPvz8lv/9+/I/71
- 3yUH//sPiOMb37jTTbpt9Pvfj5J33vmAFAq/J4/+xeP/qt7tdhOVtZT+fN68sn1l3jN5mfyn
- 99xDvpT+V+c9Tb789OSdft0p0Y83rCZ7T58jhBCizTRI9/f2kv+2Z8uU6/mP99xD/q/iJIHn
- ouREz/Y7/Vol5PkPDvLh75tJ5p/eJ/dpWsX7XvDeR3767hUSPpQkf/vC6jvd7JuixX96D/nt
- lwpxPxgg77/7P6ckGz44fZqkrlwhhDjJzt3fI45vfIN8+eUQWf5nDeTq/E3ky98dJ1ffPk36
- Llwi995rkMB3N5O6P/mT29b2r2JN/fPFfySBF/+W/LlrPTn6P75n4b17+jT5k+b7yX92/6fb
- +kyZ/vCHL8nf/eUPyfisB8gP//KpaXvOv1W699/fQ76c2Uqyn//qpufmjzesJodSV0ig82Xy
- 6t/81zv9SrdE//K/3ycdwZ3k/4yOknvvvZc88+xe8uwz/+VON+uO0D//9h/Jqu88S+6ZuYCc
- ePs0ua9Ru9NN+pq+pn/T9OO/WE0Onb9CAt/dR179m+/e6eZ8TX8EVA3jVsP61cr9f/JI6ISs
- e4FQAAAAJXRFWHRkYXRlOmNyZWF0ZQAyMDE2LTA2LTE1VDA5OjU0OjAxKzAyOjAwm/zd5gAA
- ACV0RVh0ZGF0ZTptb2RpZnkAMjAxNi0wNi0xNVQwOTo1NDowMSswMjowMOqhZVoAAAAASUVO
- RK5CYII='
- 	) base64Decoded asByteArray readStream
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldObliqueDark9Data (in category 'dejaVu font data') -----
- dejaVuSansBoldObliqueDark9Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Bold Oblique Dark 9. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 9 11 3 0 255 15 0 0 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 11 16 22 31 39 51 61 65 70 75 81 91 96 101 106 113 121 129 137 145 153 161 169 177 185 193 198 203 213 223 233 240 252 262 271 280 290 298 306 316 326 330 337 347 355 367 377 387 396 406 415 424 432 442 451 464 475 484 494 500 504 510 520 526 532 540 549 556 565 573 579 588 597 601 607 615 619 632 641 649 658 667 673 680 686 695 703 714 723 731 738 747 751 760 770 770 780 786 796 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 806 810 815 823 831 839 848 852 859 865 877 884 892 902 907 919 925 931 941 946 951 957 966 974 979 985 990 997 1005 1017 1029 1041 1048 1058 1068 1078 1088 1098 1108 1123 1132 1140 1148 1156 1164 1168 1173 1178 1183 1193 1203 1213 1223 1233 1243 1253 1263 1275 1285 1295 1305 1315 1324 1333 1342 1350 1358 1366 1374 1382 1390 1403 1410 1418 1426 1434 1442 1446 1451 1456 1461 1469 1478 1486 1494 1502 1510 151
 8 1528 1537 1546 1555 1564 1573 1581 1590 1598
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBoldObliqueDark9Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBook12Data (in category 'dejaVu font data') -----
- dejaVuSansBook12Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Book 12. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 12 15 4 0 255 16 0 0 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 15 21 28 41 51 66 78 82 88 94 102 115 120 126 131 136 146 156 166 176 186 196 206 216 226 236 241 246 259 272 285 293 309 320 331 342 354 364 373 385 397 402 407 417 426 440 452 465 475 488 499 509 519 531 542 558 569 579 590 596 601 607 620 628 636 646 656 665 675 685 691 701 711 715 719 728 732 748 758 768 778 788 795 803 809 819 828 841 850 859 867 877 882 892 905 905 918 926 939 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 957 963 973 983 993 1003 1008 1016 1024 1040 1048 1058 1071 1077 1093 1101 1109 1122 1128 1134 1142 1152 1162 1167 1175 1181 1189 1199 1215 1231 1247 1255 1266 1277 1288 1299 1310 1321 1337 1348 1358 1368 1378 1388 1393 1398 1403 1408 1420 1432 1445 1458 1471 1484 1497 1510 1523 1535 1547 1559 1571 1581 1591 1601 1611 1621 1631 1641 1651 1661 1677 1686 1696 1706 1716 
 1726 1730 1734 1739 1744 1754 1764 1774 1784 1794 1804 1814 1827 1837 1847 1857 1867 1877 1886 1896 1905
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBook12Form (in category 'dejaVu font data') -----
- dejaVuSansBook12Form
- 	<generated>
- 	" Form data for DejaVu Sans Book 12. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^Form fromBinaryStream: (
- 'iVBORw0KGgoAAAANSUhEUgAAB3EAAAATCAIAAAABG2BVAAA4dklEQVR4Aeybq4KrvBaAeSLe
- oU/QF0CjsVgcEodDoaqqUJiomJiYmIiYmIiImIgITlag3W0aZvZcz/n/w7cvQ2ddWJcAIdBs
- OTj4n+fg4ODg4ODg4ODg4EChNvPkjVj2cazKgJ7ohFBc82zlNEkXi9V82qR5UYDiwO2TgiVB
- oSCKFMEJNksEG8vsRn3ly0/jRJ0BLVJ7KqQPwZYXG0vMCBLg3OHYqoNce2ZYfwb/eKsnv5TB
- oP9TX43PGXAVTpM+2yiIWcBF3htHQSHvlo+A260b+bmArdNg38puTEgj5NrffFbunTEGVGzH
- o2XDTedchMSwSagZ2mchbONoqEOnl5/HsjIe/2lwF5pWTzu10ND2QNGTJZAcId19hBD9/vD7
- l+M4unRt248wxA4O/vVky8HBwcHBwcF3IxnBmCi7HBwcHBz8X2AlnPeZWg5+GH6tw6oy2pG7
- a5V52lmmhLwEYYXIFDZqEbWRj1l2vmDUV2GlsBxU3Ghaht1zw+vcb5XURhqmP8H6pjSi9Run
- 3iw/j6HrKi+1yaTHdV1QvxYzrCjXFzS1kG9HnlTYCKUcuRWhpgM10SrheWBrUQawzoZgHhZ/
- W0wuYaMvw2KiWzi4KIYlxX4r87wa5msX3Oc9VvvLoxBPdRXLW+g+xHQVbldFzaGrPcEj6Bbp
- dWo5N35vE57b8pznedHNSTXLL97bqZog/TzLi9Esv4LGRWg5tbsqlvZBZYCe7a8XNxd0qWGj
- p4nY6VCuI4SP5Z6Ol61PINTyfThNMSZUuHcrIbwi5tolz9hUfHNDxKXK7hQ/uIauOBRAmM8X
- SlCCCfv7CKGMykXFJRjDTwiGavczT8woAefvKhoBevxV0TICFVh+n18Zw0yaL9ZWud9eU3ZK
- CKnMnzyE/6whVSmkcSkLz23LJuO1U9ug11ScIggTjEg8MjSeJkRlwpHiaJ7mGRHKtY2F91A3
- LO+qsu6RC5fhtiybkSRayDD6xdmhM1DgPyHiGWGCppmlViaMVmtSiUoIhtE8zxN6ObydNZIz
- AuJpRkRou9trKTzyQcGsO7yR3rtVxLdhgsi51O6p/o+mL+ZWU4gKoELtuAXHwiz/6zjDKZ5D
- iZn8hnCtlmsvUgNGPLRDGZd2ICiG4s0zwlQ8DCfvGFjNedqBlptKsvWxNMhstHeG53XvCDOh
- XOxc2lS+2j4dF8YlrNIenFmzStpG1UtIrRZAFACU1z3bSyFeC6Y48Y0ncOBiod0bLRMPp9OU
- k2nyjhJObLBcvQhPuutWUYymCWpOGb/ryLiXcU+NkqGeiZoo624FVza5y+BkzVHb2Dyycvqu
- Ztc8ojTMbdTLqPjRWd2ZRFLw+dbccLav6roqywHBqHgJj7VlUKjSFwKrQs4fOZTnJv/oGxkQ
- Z1nUPbLLl9GkKYr2yv5S3XDUNZWnrLr3g6yKqr2mi+FE76u8SR0e6qLsuN1+n7CKTA7+569s
- 16GtqtI37H4Xwi51fqqwcre1nraEo6m9Iu6Wj/MdR19kz5iw/xPPmXCYwmDK5fvx7JyKnd67
- ogFGsm0azPhdR6KhKquRKE1GvzEgudddbTzauD25YgTPAJZm+W3eC89wfL1c7yCuH2QCI0wI
- fa/u+ynf5tLOSLr+BhFpXPJlz7yZP3CqVlKq0Gm5TXs+gvPmnFEuTTTS1jaJdLESWKOFd5Q6
- UjTD1wlJ+wV9ZwQjCK3Te72v/6HMJUEzgS6nUQyj0KO9ugkulFLRvDcacUpJud8SC82TKq2w
- rikP0ojutP9qqtNvzMiUcR+ayUupOCUwzQaXz7N0/5lTjBDlUoHsQaok8xJMoBySQ9UYl5Et
- EKJ69rwYiWfEb5EoRhDeFhRDaVagRtFs/OmOcrv70G7npljG0z+7M/emaJou4zBckEg4u6vh
- se8v17dvgQ3xnq6IMXwZxngdINopwpTi6c2zIkzpZ5S+L/g44O02DNaCiqmtB+xeLhzOwAh2
- j3P4SMcaKYOPpI5UWitoH2C9L/gY+1H79wvb7H0NJewoWpOJRkUCxeauqauqqpt2nKhLvYvd
- xI+O0l87GJhJPXlKPhOyc1uE7yn0QuIzPGgxT9K+LuteOoeHpqx6/mxOBm9x9mnj2vuouFt+
- CLK+Q37q9VtabqrzkOXVpV60Tz6GUdtsQTmF6rLs500hy6KMZBt834t8amF9uamqZiRWE9gY
- 0K0s3tO28ubCqUO6x8eEDdjnFZZyOPmc6GOkl/Jvrq2yDUGcBxoJBHQ6OQYWOXfBdYmE8H07
- deTJcO59yLN0Cg9VWU/Q6W/F0iL9/ZL0GB5D/HFlgJKFYkajtKpHtTjcN77uwr7xhYyCmvQt
- XowT4LXHbpGD37g9SMssu5zzU4Jzw9KXSLx9a+PpY28cO0MPxxcj2WTb41mNu/jh54b1goaY
- aJhX2R+q/7T3hQqS+s7W/UR5hzwBL4BGY7E4JA6HQqFQKAwKg8FgEBgMAoGJiNg7wJlMbVd3
- Lr09PTv7+8/5vnvvbzYhHZKQnJxUVXJsjI2vDe1ys6tBbsBBkazm9Dt0s6PkMYQXDNHCj2zR
- W+Ua/NPrKXOxj4yjz2LnQhFV44cKH7pw2mIn0mrI5eUKIqkns0qiVAIvqfV9rx8RNR8MSVwY
- ooX2d32VBS4waxtfbgM9Mjfp1YPCSyYytSEVEGn7fc1A1FCI6xZuOI/sqjwKfNfZ4Hp+nBbm
- 5IBhClBSNPMD5GsIEIuP1stJp5Pm1XDfY2lOlNWmW0ke1vV3U0W9fvy6e+Fw0mYihctm5e8F
- Dzv+J3nqZgljhDpJ/uzN1gvKifvZmXmG5kzalVDOGB8IFfIc/n1Vyt5lTlBP6mwhmM1YGX46
- IgdknQuDu6+yFxsENkLMg69LnP1ltwZxsTCr2/59F7/dG9AhhGCpw8uOfNRX052XD2YUhfV8
- ZSdymDwc/xE3C6vS9tDa8pcF0PVk3nP2PmUUagzNRyuv935rn5l+wKJ7CksKR8yzwi7qiQo8
- AQxOslDaMZd0QTlXSVBYK0lYYoFv0/YUTfpPQvWhI50g//dF8zkSF+YOjC8RnyfsBwHs9B7E
- 818fwXTMuDKqv8QurPWd4BZ/nlNPXAjkPpfakcqjDWfeBXG3HvO84wRmXuxhGwUIs37tz4ik
- bZOjxIZZEHSHPSZZUOKWnfFRGoeIAa/G+erhNQH6mmosJFkGa/agBfGFIhj0ryb8rSLNwmId
- nDZC1HMTOLcWLDs4ncA+y2wQKEEQ2ILasTZoOx7DQXHT14fzX63RQTla8lvBWLEgrJhvPxlt
- JpiRQUTLeeJ9PgOMfwE/H+70oHOxIGz+nMmDpb8uFSOQbu272KFjuDvod7veYvJrLHixMkwR
- K+DTufc3z2aHvTTXc4yodIbDf2UeO3tHF2OQMBA6AfClHGFMZDVpm86IaYcLHYAIKs2orJAY
- fky/OsitaNWaCLrnBeptR+EUTbPb/QfTK/llEQgesoZiLINjazOzlK2agEO2/YQ2RJ3qYzMX
- 8QAm9d64IihTzHbQPQ/xacCuMDIRh5DjaFhi0o4mFdLUSCYt70c7q6z35hY8istS46PhEZP4
- 78Ytb4eoW/vDYL9ZPp/hTCXG8KztYzi0jWEuuNtHKZ53Djo3arYjs7OFeFWdIGvBZe3i7fNM
- KNJoI74OmSAIVOvuUgES8We66t69WYOllnvvmoUzGxTlU1Uauc4R1Ei6rhcm5dGeh/eEG9fz
- WLmYKGmopmBkFcOEGuVNU2WRh1OUezXXg0/8QcwJhvM+gqtAXOQmrA+pI5P+Lf/WnUHJzCKq
- OIzr5yxguC8VzpQ2OHnb775ICFBFJnGAdhYJ2+TFWVGWmY+cZqROkRSOH6ZZXpZFBJpO5CFa
- EyPBAGt6DD0/iuNoRxgXRDYywbPcqKyrLI0c4RSjOozO4zCMgDiOUDw0fY2TRuGGVdtWWSRM
- KvoOxdZdmwY4CcP09+0AuuMGSVVXaeDw2q59QSiBkFLY1Gf0KZChp4Aucffe3j/iOPIcFBU1
- M5tunKSs26bOkpAKsi5UzXh7PvRJXbAxRh7S7+j6vNV3UsMoG/XVr8u4qLu2KbLEww6/QeH8
- BAjvhSWc/Umf4iVMsYP3rSbNn+W/wjaBQyDI4Cc5qeCIfkEedPx7JhHlVdPUCT4/s8LRLgu3
- Hgs909rT6UJor6VJEnomQ2XWJ1TWC4u6qasiCX3zQb1/iXGEX5eh+Z6jHJ/57R7By9ahvLV6
- 6dIHs0G/E2/BJnLYYThi/+WD2omjT06/yaG0X+jtKJGkHpggg6bdqqdmeymCOMFuBYuOaq9W
- KIHq2RY4Slgpn32AHWqMpcIuvrAKPDm38cFpx1yF+/gpVpymPlFJPeVRgMnhl+7yOAjTUfG2
- tTf7v4//pGi+HgTMbxdtma6pvgl2/jie//qw3fIFk3Veu/pjbWUu0lg/8rqpi9CVUTWdKC05
- Ngom61yH1Cipo+FNQWtFVLTD0BVJEOY9yhm7siy7Sal5+48rR9m1z8VRaNluFozz1FWpc0OO
- 1GPbdOO0LEtfhujc14JWz0m36r1hastE3lJLtVomgkVpol/IrBnGJpOs2nYy323ttvGM8t3v
- e51hIEmOUrBbNrqzHUz0BNsoM/8eV7GY4jZt5WH+pA7m8durzG0q9pZTZ1aMtmtyny/9dSSx
- jX8qv5oPy9YBC5M9vx2cFX/DDLABpDyEwex9/DA4eHEQxZFBGKb1eILJ21n6y1LtXN3+J9lR
- uuGx+wgcshNClk/i3t8/2wnw0uq2qZLAJWMMEoGdw39xHjt7N5nDclh3t4Bl1fwDiYpOab2M
- tSf2n1NXX2JqztU4+r2K7o3NNQLgjJCAoYQAeogcdwsL3hWB5/lxuVyR+6Yqq+29p7Yuy2bR
- 17Zl0hCPrHv1YX/iECWHCXGCH8mTlgmr5ddUcCtmNYE2/FJjVZbNsFzRqqCaVJ+YeCYwJDrk
- OBHXW0SB+a2U7T/acatlV4SeQ0T8AtbuptjQDYtRz23kb8bMg7ob2wcDgM+3qMxte81ignkT
- YvUAqoy2330rPN57+uoQdhnasqzGdW+QouoX/RprhMQyhrtE0mjmLIhTMO26JVloyCgtN44y
- ttt/MMlapfI48pkf2YcuW2GbG+K6/0evPzRlkVw71m29ItvHNWX8OxPXgmJ6j7JEdV6Vu/fM
- G0EBmxU2g5BNoVkwyoVYRVv5xM7YVnNQgV2toPL3RWDH0iQeOUmRx0fgxjU/YUZ9ngX2D9Da
- 9JU3xwxj/qQzfspVM6q5cZget3apHxO7YxQF4sugMvfdgJGgImYOTFN2qecJLwqxuuxYawml
- lfQOmSb6Q3fbj90WcKlgJNcFwLzxCahlLJMI1rJnseahn5TtouxkN4vL8XerIpn3K7sYxCv7
- 2fgF5qHDDbuI0wogw5qv3EmniBOEQNORTQsoGpkQXMJE0aeAqmOXdj3Nw2FNHQP+67CjESJq
- X6Apz8nvgvIpTRmHLnTWYpoyJgT4p3BeS+xN6IUYukDfQVXkXQYyhNPac4WwNu9Sj3BuSIT4
- k27prvpIdy7bcJ7hiKrPmLOY8YEQxagPJx2SYTbWVMIHjdZTISjRRIQ7HLYvTWSudsFxK0nd
- KumSz4EDhmmwEeaqZST5O7JsYDBg/6saQkFPIE5PNHAM5E6187ysrALokSMDZdf86ZWVu//7
- orGOc01Zb+m0WK5M8dLu0AB15IDjrx1/pClrtf08qaulTZDKK2PSloW/i6VkSyMwHPVUpNqo
- OPnQ0GL/OMZQkJ6yasqqYyPwUTz99cGgBsC8+vqrwySWCMYVb7TGVLpOPF8T9li4mQLbASug
- TqZ8ZSSKv3gwdM4YYAVUU5P5rrt5TWXV0BeSGXAsfUFc5LDDeTFQvSQv8jzPss2tvZvB2FE9
- K7Afk+lxypVJmG8/RubREfBlnLsqz2LnWkxUxAmcwSY4YmBPQ/b4hgJBbLEXBYEBnTA7r16f
- NGtJrnZ/eswPPX/9hPxLXeShJ/Eh2PNz2Fnxt88gkIEdNcHZd2BkDHiYyXO8KPVzNGVasm4z
- n1pIfC73/sbZQICZqemSUE/826V1e3tt/1Oieb6Xpmxh7zQzhW98bVXnknl+hdTDwheoZQuV
- 209340HVDQ1yQp6bhnHayeE0kh0SzfGGVd0lnYbqcahxC7FS1IOFcy6LYvycV9RC+4Fl6u9f
- 37J2Td32ExJ5/MZlWRCHUJ8jwKjqqo7QKvjZcZw00iYeFtV4LbhRmobu8ZGzhQkBWlfwaQ41
- D33Tovt5T2+jYFxulblsL7iuCwsdRnp6XfnP0i3Esj4b3NZs+lTrMKK4bif6670gS2hehnV+
- H7l6QQDJ80B8m+XxfSgH7JTjlR29ntWU19bhmjI6fRjHoQi3dD/vJhhmes04DsO4fswUIkhS
- X1zcOM9jX8hw1GaLC4WxT93jvzf6ghj/XKnHRDOcMhTaVnrmUbge3D0fFV5ianwyxTWTsq+m
- z6MOYQcByYbQ5akKLqSFubJmv9zAUsk+pVM/Ebm8tEq9W5qyw7kF8SxwGnWG4lPXCbwIcUAz
- fZ2pYxGFWSsw5D7dW6p56DrEjWB/cqihKXFWBuep0yAW4l6YNsNsz03OA0Q+KLq4Xtxk1Jxf
- Gh2NS3Vu1ZUOdDrbCKwDiKHUjILbUOh11XwIUWEav2UfZpZUnJHAEJXPkKv+VE3Z69Y5c68E
- 5VOasuNK2PASY1shxA07ZYFBM3FeCxsxRgrNvyctr48ZIfiXk4WwRsPGDGdvGEhO0j1ocHqe
- j8L/mp5/TCX2/gvJcDA/OKx4YeBgWkN+cjBO7Lxk2XehoK5q9DBGFPOvFedMfq8tphywceYr
- F14HWxSLOwuCqAg/X5GhD8TBhiuU/Dg2qwdX0sgnZnFBBaSfxmbxEVE5INUEk6GyTlgsJswx
- EvYSEp/0FyIIIR3GjBgehXGkFNLZQjQUh3Fg5CD39v5l5kkR5AOpZJBnoSkuLHpi3CGkf0zO
- egtIJ4NO8S6YN3VBCunnJAkmA8IJijJzfvPeUFXsXQCZdYtZKgIpHC/mlTHoC+oS7+TtTJ+V
- Xni7tWmTkkaAyQmpp4sM8W6Xjd8yHjtvrx6iJYXzBincqN5+WvxmvaKnyhUoPHKlQPwxmrr9
- WhFsjfvhk+HKN5jtZZN4QrjlqOvIFVL6SUMNQORW+X4vPPit8LE8Ct/DIjsGrus6UqKSyLoL
- u9KuKT9uKc/x9NdHNDshLvT/uvwqraZ6yJsRI+cqmIka68D5LRjRpJlkyX7nGOUyquZl6tq2
- 6yc4571Hb8QiLsJNR61CwwMtdn/CS877zk1luM+EQ5t6FwInG5Y2JpMwqAh8qyRZjwj0xxYZ
- YY+fBKrXTJtFFUHUzEuD6p0LEOHWk9Jz44H13SPz650zSrK6wWgIsMm11s8cPUs05bH/M015
- haZMRppfzfjwfZiyHptmVFav6Cf77g9KOiJWPZt/bcy7Bs1ypnzEar844JB2VvxPZaDn6H4x
- /dKdc+fM9QkmD7wo9XlNOXHAWgk0TJowUX8e9/622fBGMQv1CWtQfL+sNBJgjUS3+46aso29
- IzMD3lF9nMdPNZoIZ2Z2On02lZjNuuFVqm9/9pNSpRd38zo1lJ/LpB7P0H4LsT+XSouVp5/V
- VeyBo+oxcqXzTvg3izRp6CXh/6AHQ9M0dVngQBYq0B8y+aydz/B8pJaxJD2dn3/WnsqsKjnj
- 5YUI1/cdxLmyk4T/N9XfUntq1OCde9ayEXhX5G7vQy0PPqspwwbWK7TuaBTItQkvVtTrO90X
- yRYzTlziTnGTgXzQ7x7QTrdOsTDmhBzzoUE4IfMloVWF6ccUCrqSAX3qfQgxem3LVKK+8Apc
- 9Es15TFAlA/EnsY5LQ3OjRY+rylDseI2aHqDmvsqkAJRj4ExfD/wHFL3duwL1/M2W5Ywh8U7
- se4UXpYn/pbu+mHSTurum9Iqqe4oOG3GQ85PPcRj5QIZTIHA762xd9lZZZEgcAb5TjBxT33b
- NE17A9u/d+PyHrPfu1BIN8nr+5cLrAV+MDg481TCx1wfPoqR777BC9KiSMIw75apjohFA5He
- 3BwmJ/QsxIzAZjZ3EcWugBE3zmaIbHeeL86VYIbAzW7+aIAyaSpJQ8hy6Hr3wAvHw+2DmvIG
- wQXlU5pyUhUeovKZc7KoSDyuKadNHUDrnCivhdUtOw+g9/+a4YofRT4SH7NZThXC7fphEgiv
- W+Jn7ebtsOrzpqPnNWXEtceMiu0BQltQh1Z38zDChOYXfbNN7OKI4VMGgnujGysMbruEOqCn
- 0WKWsFNwk+dvShyERVBaGqT0qaRFZQLypo+jOTwXHNf3fQevgh5HBUA0g8CT1HcB0gbkSS/w
- PcdEyNImLJoM4EW7wY1bYg8FNhP47oUYcRehayRl13XcsDiWSChjAeLhMMcFlAbaDTdGenxr
- DuEcY0gF4WPtsW0UfjMr2uwYSJR5EUgX74zxaa8MiXCKZcuhI8fe2tYmJfVE2ZsWX773jnC9
- wPTO27sHwuR7g+P42WakAB98uoCihVMHkwwZMzhYxXF4PZOTJFAFY9FZLzDnOd6FNIJTzzpz
- yeglh9kyboim7HpbNnbsqkznntCU2yc05c/5+lSdhFk3H7HU0n7ushB3S1DfI18+HMaB3c+x
- YAYGBA0xSbgTuw0f0Qk4hLuHSdVqmTsP+6sqdo7Ptlsg3TJNmWybwuzE+f7xSFBOCLLh18O8
- rkvflFW34P4iiJUI+QcNd6kk69y5Sbe3Vtv0GkmEX3wGqJ5fGOfFalJqLPdJZbM7Lkn17NEz
- aNMapzG1LgdWtR5KVlSNasW/Gtu05bjPQ4SDpmZDU50G+1C8a8pi/czx389rysROGfQYUjv4
- P5yBEL42yPfJONqY0qhu2x0rSj6pPQdgz2/5lNZlHrvCFVtt1YnyOZ+3s+JvmSFDBrKOGxKC
- 1R9nrgh4yln2eSbPWfrLUp/XlBW3UoKMSAT0z+Le3zjbgQW7xW0WmhAZdkeQY/PLS0Me4ceR
- C8f5b6kp29k7jX2xzEOBXbYoJw3KsZlMTv67SqBP0ul/KRVwNiLqEKt8G+23E/vXpRJif5fw
- X2fDuXuJggCMhGeY/F9N5ZGLEUOcghbieL7nShpy004SXpdq2QhYdkb2B5/RlAGt1MG7lMJ/
- IQpL23eH0aUTtUMP97286buu7UYNy7UjulzuIvwrAN9qbMGOZaRo8iMe6MbetkuOu576mM3k
- ajgZFCZhGXCbMK0qvgEapZudfObuYR5V5rvOX6b+cS7CNCkHpg3PgWocEONwgMkYw/qYptzE
- rrlOB+BcliiYLVkJ6Kpw90YFN11YZDGbqyl+HTSXxWImEPFMQl3DmhJm5pIsn6YXkE7+NLfh
- ZZihULKzxfscZvr70cUKujvS69BWceAJ2gx+XHVXDH3JPCTWkzbqIew09WBWCUdSyWbb8yMP
- c33F0mKEPPQRRzCRVMjx5zVl/C72wMjDQAMi8yT26/Cz6T8wrJo9TvCQpsxDWJzXlNN+PuIQ
- 5eOvpQp2Rb7vsxuactKrecuADlJkxlgRyIntb5ENSYQ/9Rt9mvo8cg1/OlsIXlkm5X7om0FE
- NVsOEg8dWqEfxPWwfJ6mbCZwNDgnuyaksjbB9Mc9lBV2BVMgbhooDf4FKFlXEq2TnVXQyQFb
- IMub0jO8u9m0Vuttnze1soTzUDPcm8yugMbocEj8NXLpVnhMGh72GL1533maNVT73ZVMYTr2
- BaYUEgGJmPdO7xcVGGcgxGMhFFaEg8LiFEqURitpDq7blFycS9qQjiU85WbTWLnowXRmzU5s
- LbPld2ob4OfWzIPnjb0y1GLdxK5tEhfmTvbWtjcpraeLtzAnIm4+kd6ZVh5khrM9Qj8Q7okf
- 3l9EMel5S4KIPGS+iUs37ptU8xRpNyfJIhK7ED+EIzRDh9jM2aFwp5oUnYXoAmSfY/VA6sO+
- gb7bD2uHSdFH5r5BPKjP+vrsJqhzisXDb+ZHStRzmcZJ3ioyLx2cbe5T+NXNywchHtvjC/LS
- ZhqHoR+oM2F33ITjhFXX17Bz30og9rAcEPJawnYQL8hLqvL9MSeyXlGOKSUZ1JAaMw6+7niD
- Jt4wwo2TSLKrbLoMK2PT195v0avX3JMXIeRNiIuXdtbqoePQieV2Xwqi4ZPqWQELqbp8Qz0s
- JvcSn2B97+91ydt+2EnL3NVNPy7LXKc+zk0ZLJ85nZZ9m6asqiTwfNh7WF5sGo7R5TfDuKgP
- c3I/SgLn6KaGhmLYfr7FVd5JQyarcWy3mV/k7bB5M+vO+22JXKsk9BHj0pLfb6c+Df3Nx8Fx
- w6Q4vvB1bLbgmssydoWzS0NKD9bygakp4jjFfYx2VvwtMwTI4PNj8oN2irCiSxXnwGeZvJ2l
- vyD1SU3ZdV0BneUNbpA2lIIi2+dx72+czUBV0JHhPUkv52dvisvrcLVan35TTdnO3u12Nu3y
- EWEVxiLBeJ5O/0OpG1xzyLd2OMWcrLTfTuxfl0o6/T7hZ3+aAD4yyKdj85+RY5UnmPzfSr3C
- 1DVVVfeMSV4VsjaxCYw/20nCy1KtGwHrzsj64JOash2YMf1ihrC9xUGn0E3q/27Z4SblxwZ/
- 7srQ994QpvU8N87xDtrESyXf2FTieCBFotmOlj50MftbkBfHqq+XoZ9W0P2oPaxcdxFyTV1x
- ERvM1WrC4F6AOTVfSWkMxBebhN57UlM2zozX9z5vEdCDMDBHZE4xrPBPIRfC9Ok1j9lvaDko
- uRqg48Mk1mjKftqogyDGLgvqilgcbLFZTDRhHFBR1wbjcekEeVlEHpJJD5pjc/7nmtDQ0FnZ
- 05BJBMs49PdxxxJZTX2TxcGF3RaK8Y/rjIgrHPg9FDcXka91Q6xiu9Q9fJ1INAB/IHE5ETaL
- DBvh+GGwASdgmJf5un5SUyasrlnIHYl+8A7f82Dw9Z4q3CBEmp9U481fJ1d/w4yLFQ444s80
- ZRzpP2an3Cm9d5YbF6mHE2ATE4apEiBGfjHpIUUefDu350Zs9SXVlCkwd58t5C7Ld6dr1WNz
- d6c5vKz7BE0Z0LBUTnucRRGzXyI6e4NeEnlsHWH/LoJaLxUJpkw1hK0F7oZMIaGcafVoVBxy
- uG19UxJr6Msvi1N9lW+rm7vvpSSPakJ58xxLzPyKbhsIjLQUsFAkVzFw8qatdzRNcczO9cy+
- EZQGY1h6iR+xU6a37aNijlVTxr/zeHn8EXrZCAYSXUfgUYTaWiuztgnbyQ8+VlJ7a1ubFPUk
- Ny+RFfMi3Cgrmo7ohvB+SJazYtNWSZy4oPHxFiaM7IzTR3kMoGL+NR3n7knHTpSpRy1MF7GF
- w33I1AKOMkhRvL/dWOdRFDgCK/6ZOda8hfSCOM5GlKQPkY5A+lFaVhVW0qeNW8/HKKNXejhS
- Cga60WU7WRL5DhTcH7bXS+gdfXBqZiBXh6+ZC1tFMopQW71Z0q5Kze8mbDLv5/3fNDn+wcn9
- XMf7LnA8LIIST1gNujEyJTRlhJjjNJ68ju7KxNvFwjBJ4+BY6Ik/lhsWBW7Pi8vBlJH7jpAc
- jiQnVZwkm+rF5B4nQh5Y9R6G7oo0ijckSRK44tjvJkmy/VMUF902qcTySuPDh496uDE+kUc1
- ZazSbeRKrikTuydiosvARhcy66VLAm/rJ8eLC9qrqk580PYKEc6Mn6xDC3KTInapaW2XeSa+
- li1/vey8yInTLA4O15QOtBY4dhxzEzuW8g2GIpLSfzfLsLPib5jB668yTOS+U5wU/pbBCz7g
- e345qLNM3s7SX5D6pKbsGHYqncN9Z+Wa8udx72+cjW/bgYR62ZPSFGJUYo1Gad9aU+bsnW/E
- VqI+k+0nzuOXSGAg5s10ik7/O6nQlNsG/Lw+uImd9tuJ/etS/0RThjct0ZdwqorXfIbJ/7VU
- GLgIQO5OflJSPdBUHp+tIi5TKORvaMrWjYB9Z2R58HFNmXv8ceip9l3XI8pg4LsCW4u3lLCn
- BGcZmyqjXOMmAz5UyKRXU+FvJUblNDaBRMSlIffNqameKuddPplXesx+TlNmGuhYpeDNgCpD
- VzqAFALE0j3+liH3g0MwEL6doJjpnVF0Aw/gewtHfUpTRlybDSLrFtulc4E0dk/oCT/b4j20
- KED6ad0g7gd33mGyBWlt1TicIy6NucjLIr/CSMrcOjJUPmH2WFmwRbdjJVRWhknW9Njb8iOm
- urmDum6H20Hf+6ZMQjAA6O/U2YH8C75wGGni2CAkN4ajJekFlci2IYjjaNv9BCZsFrvwDRjL
- Y7CFEx6Hiv2Ypqw6rB/Ln9/gwY9GlqGpqqbOQ+O9fu/xPn009oUMIx+NkzQPaMpgqyMehmkt
- oUSsEHNpZNNgzWPrJTPMJxMLSg7TosjzLC/KeoDLxblCCMtPmn4c+ioLicfczbsJ2sR30Obq
- lKYMhmfjiMaQM1pw/kwfMbYGIqvL67hDMqrLiClZsB0GuCsJHZn8Sh+QbGofZ3tTeifqF2rK
- JP4dYk1wTZm8HSKwY6iDECSddSRzQoYHOfAIHd6c4ttVY85UTmnKId0q8UfMQLX8HGprrcyt
- FlOpiyrZW9vapKaekAKBFaGHDLyoWHglsRagYpZLh2TUUMdqYv4mi672Dn23PQ7vm9xnF5ev
- FdZL2uAklPnbR0q+XLKC4GBm4ac1aPlTou1Kwjp4vSIuQdLLqqZtqjRCwEhAeEW/fJmmXPjk
- hz3XYZASgVwtTJjcNp4qxp9xDdDYvMev6KbjThFCfzKP+FWAAICvT3Us9nAkRIHfdy0IWcjj
- R8NSecWSgXsCOKjDpl9Nw07+uMnwtNllRAt1fxHvMDxEtYjw9V4OHrEDuiTGPCfJpnpeMZpL
- VjqljgsPwnKk1XsWoBz4fOyA1m+5uOn0Zw6ocZt2nCtNWW8GC0FU3RGt7aRu7yB0E/05xO3d
- 3nRpY+j/K5LesV97jr00Wetdz8HMac9PdgjG0oK02ooke/k07A8V1u2s+PtmMOy0u/KGdqPt
- ACMKPTOHMJxn8v/WHX3qaq1nV4ysn8i9v3E2vnMH4po8RywEh6k5MqXtwko7yeG/Mo+dvSOz
- n233bfVdHXvyYraflDstXQR+tdljKTud/tdSb0E2VtpvJ/avS31cU2ZrH2PjTzD5v5a6RTwP
- HOkArrcDaqDRA1GImw6/1tqBSqZyFGInCa9KtW4E7Dsj24OPa8p67bvtFhFtOzZPxUVIYT4Z
- c6vHhovwOxbCKxGbJQI1xqGAxu8XVG4zFDAf1LbcUge0uXYv1pupYfcaDJq/+CZ3PERDoehZ
- odexqT/0yZlnn0rjzUfV7ZWqrvyoauXGy0b4dkjkOBv0kJqlKBa2ENgEFlO4YCTrB6setqZ0
- 4oDdGRN3HBaFapk326BVG0ez/BzX1ps1cRRIunMNk6obVv0nsS/0OrdVHnp0m+dGmwU0qeux
- G7wgejodeE7aGUIZ1Qvp32MMTyGJj+Hfr9B0b7esTbPD/Zkfq1js34n1ExQTnofAksp/ndSQ
- B2t+9o4+t8PA2BPiWj+gKS+GtcNwxqopQ9ah9/jhpZhVEbHnFX6p+TEAwalCwpqy/FbR/rJ3
- dCNIO9s15USSOpCtHVtcB/+oVBwIMiYBhFTeQOZnXR15b4m/VWhi2iyxZHepW+qMO0KP2qCd
- 7U9BIkG1v05Thv+4DPtVo+I3TIDDiR030jNzdcdOOaKWxXVED/nhuKT0+huUZsPbfAtByUx0
- P0NTlhJe+ThVtDzyvKbcxswlmdymYGtte5OyehKsy9S3dRb5wlBwWkmyOKJirNrE+yrohlKS
- T5sabIKnavjxsIhSm08VyYmSSTANJ0lD4sW2YX73y4vobtY8lgdwRzgj2i6V3HN3OJEG5mFY
- f9fnpt1JiN66/nJNGVhy9JJX21jtmduqMZC45SxRT25bPQ8ZVoiiacvErLwwD0+SNE0zHF0L
- d/srTZK0nEEzsijKTIPObeZcKJxqtr+XrrbvwWunLhDwN4qj0N2m4f6Np7i7wYFG3qUpi6J8
- R1HU/YwGGMrjd704S3zM3eh3C1ZjR8NJMq3etrj3iYR5MmIsOPXQ+qje00Dc3ucD2XFNmdwr
- Tn32+Tku1ZSfwaluSt+76frzJAwHlh96quS+gqsxe3ugo9l5frq8YgQ+Uf4C7QzuIGdY8b+Q
- AcsQA9zAGR5n8q9Pfc0dfVhnQe8/lXt/32z8Ah4nigPqjU0XbgBrNC/tBIf/2jx2Hs59N6mv
- Lb9IfISHtKhmO53+t1I3NrhotVKobdKz0H4bsX9l6h9pymDjWA2BOQIbf4rJ/63UK4xNVWyr
- 7Z1wr8JxjjvhJlqIfS/wqlT7RsC+M7I8+KimDLJSNeMJY6xa7GwPG1QeN1NPVdnsZEZvd/T1
- 0JS55VoocGCFouA9dOjLopo1Hrx4teEuc2nMWQu+RGMcSy5jwa/zqb0KsPR1nhf9XVath7rM
- c8QqHHKP2mhjKCAQOM612ASNbOyYd8nfl6Vy5L++TtNCM2MN8wt9BKrugWHo81DiYH2cFMIC
- mibGPUtkgA4+PTjF3XqQR+m4JGoFsOCTgxU2niUhldf5ox3XodjKIOx/Jk1tbXk1dnUa+pTL
- BfmAp0bz7gwdAmYcp1I0LnOYFLi+j2Ed2zzLyS2FiKGMe06nAteQVW1bZyhUej6J0bZgex/0
- qzLQa+eTcyFmUai7HJvSThHDTzem+3g1t6HjmXmcDiGt5uPmGeaPjzznb4Wmv47l09iqM025
- fUpTxmRHjexkWCpLME1WrJ4qz3EcOFLYNGVYRrBr0JpI0kgyMDWCIxsmQMukca4QxduczGkw
- k9FzV1RmTNB45dKqKQNN7BzdP5HZ2iGjjlkMmZ9mewMA9l+4phIQpk1IZllOxz6zFHQOtNSZ
- XKdGqaf9KRqHJx/U12jKYIGwhUfNY4eHKsYMYJoFWuGKVGq9olb1Ea5RxhO9qBDF4kHms7JO
- 88rGJNnBCh/ZlxahhJ/XlJ1MoW672ri+UFNG3Ay8ONKHIsCqpO2tfatJnYtdU9br/Fuc3Bix
- btH+IF7E8VmYg+05cbFJpiERAGKhBnNUQGSDgi8OC1PYIu5b2CB2KrsVhzmHLV1q83igcUjO
- 3dGHY6G/DV49fgAPcvW4pkxXOj8f9osxnH77WlfFNGW+DI11fOFgoZA1MYXmM3BEX00vtbk5
- 3a/OROLx9nHSjkOdJ5tbu+9HcVpW5U7wvE6dnNq6nUvKTuk28XC7ox16CB0ZleOJ6gVlXTct
- Phc99wXEd1TveaxjV9fd5878GCf4zBHuH4PNrim/BGssIEWpPtmni2xGEjMWIXNOGwtcRIp5
- 2y1GdTc/OuhwJBVZr/6sfFxS/z5DoZQTrPifyuB3CxLVXDs4UOd4jMkzvCj1eU2Z+yQtDQLK
- w37ic7n3d82GbybFHT3ucc349L40eAgUZo6+sLBbSrNz+K/Pc0ZTduNiO0+sqrrtF2V5ZI3e
- C7fT6e+aGl+lRtJcL6/oOg5+fof224n9a1P/QFOmbLxfiS0U+PZTTP7vpHKXL/phspNR7HkP
- xY8UYtsLvCrVvhGw74wsD74k9gUlDUE1Q+xAVeh+A3LDdr84QYzL+ogFK0Kbkxdz46pKpXlD
- cuTrBVH8HvUPkCGoOYukSazkIHfiptHP2Ks0Eb+tmI8/PJs6CHHNezqIEejNeEdiRAoaKhVX
- nVzdv+e6zsdFKElrUoV0vD2esimBhB/l3ivdb4Hb9mdxDehVrQofvRDGcYAMVKNXvbnmmJur
- oLQwSSLfoRtptJWQ3lZlJImg1OxiaHvLE6jjkj3EejsP3KsugzgjV/zZzF5E1LJRAdu3Pg9v
- biXTGt9n7hFhl20jhV+ij+AP4Oz9DJin1CbBk68jDj1XGnnRtLx0DhxJiKO/kN6BqwGBEF6L
- Eu5aMaghN1Vy/TCOI0TC2eDg8WfslFkJlIoJP8ezrPpCBpbv16YpA+roHeQh5AD/6G8D2ZM0
- XPIZgcNaCAwW+CubvRZM+9tImAt7N7dMj9wzy62o+DZmrk0VwvjdK9NcSg7QoIEkkiBXoARO
- OOjV1WR9IscMWJyoTwPeyFpneIvjlZ3rYRrkA+crNEww1PDXa8o0DKX0wjRFpAQq/rrma42S
- NPLpLEqjUjp+GEWR70p8yMYwSvpplniSFIsHPaR7YZLEIcZEtNwek7PZubge6kgriYueqXrI
- U/kdfYccCXJD7i+lj3DbJUVSuaZsqww1lhdeGIbvy0dwyFjK1tr2JmX1xJyPiW6LNuuR05Qx
- +Lg62vWTBrxor1ecxC7rL0LjiAEgNS4gtApxnMlh7VzH9MHRXOYza/ptXqly5u6BIIqCA74f
- FYNlT2jTlOE22H5nTRnEpN066QlNmR6V4bx5s4SAn2CE2Mw7HOe3u+kKHxcxabUMfT+Ms1ZT
- 6iKgPIvMdqrlYQx1WnLVM0Jz+HFWt13X1lkcEEON85jSIOoUwuCGJ+0zzlcvSst6u5UWnyqq
- 98dYc18KCTjOHtSVXR74vKaMGOsI2Qz4Wf/lmrIqQz/rloOYBTGx72amKtQkdu7KLMvfkIRb
- ShDnw6It+fVYvMuC2SYRteOflL+23juLw5g/x4r/iQyZi2N4PlSEpBDSzxVn8mGcprFPmLyN
- pb809Vk75du7D+Gl2Ih/Kvf+ttnIUbFHJZClTY/nOmWmLGFayfGCOGalneDwX5zHzt7tvpt4
- xI3y2JNuEKcp9IFtT2Gn0981dW1pqoNEwN0+7ST0PWH4OaX9QbSF/vdA+63E/oWplP1a2Tv9
- k56vCH9j45S1Psfk/17qdVxcKeNquh3b1oTLvyrEshd4ZaplI2DdGVke/JM7+jrKpO0kHiKp
- 7lyqABqoqcoT33UM15ZuUHQzk7CvXKrXIvyQD9J2NhaoKQxIASfIuqEJJFqCUd9CYH8LqCFD
- 5I2H9yp0v0eDj7BjOoBaIeFyFUm+JXKZBnVz8XAlKJHaKaC8o/vgGwSQ4avGktBabJiLdrbs
- xIJiNPqgvHrUjZpJ/fYIdFIgyFrSNAj4IENuO0MjJgN+XK3sriEkJbWiP5q6aEl7y3MoOHKc
- h8b5oA3kZUEr2Xco8249TiJ3k/CNPql5aJuWbpH8CzvkoJRdBObdKYTjpSXoOrD0CKdLMkV5
- q4wREIXYVpCGxI9meQDYlSMV6gaHnrv4+HUCN4jbcTWF88c7BDdczZ/oUxZW5WYJc4NInuZZ
- BhdJ7ECFdB++KZ4TvUAD5AFLGfsXCuFmzcRfzTo+lzIxhQAyG5j3Bl6Z+JNClp27IvCu29yL
- 8kmfjU2sxpoczWFGndSt6MAOZh+WSKRJl6aOgSA2lYRqCC8n2XABAqy6bHU2oQnJnEfgpT25
- 6IPAHOTK2Kh1X3BH31jFgrar735sL1Xv7xOrT6ZpL6mpoNjBkIcemkJ58QWZmx2zKAB9Sa6b
- AtGoFGnAhK76esoCo4eEaeyDi5hv1iedNVUS3QSXZ4wHoimj4/AU9acJ6CMIL0sOEvCgm1L7
- BdTWXhlgrWKPvnVU9L8zJ+G6krf27SZFI7B64lQ1vPpqzW+tfenhyA/jTY0VvSLO98nN4NSv
- xbw7s6+XQUXZCz2WxiXN5UhCHGB2oN6yV9aFqcO/Ii584DuyK5ss/PTXg/M09WQ5dm19rDEX
- AiLolYlLw2EWjqUfZu4ROIwro+X/r5qvqjhMymac5r6KiaO9BdS6OXIlYQgZghZ8A7yoeiuj
- Bmzh+CRNWZBo2Pw+Z7umzJfmOIbD0ivQRIJEb+eB8pxOW/KzKJ9YrB8un0ebPcmK/4kMoK8L
- HyoEbPLnTF6AydtZ+utSGaE9/yd2wWz3EcRVj7Hx6dz7m2cbm6pbbng8N8NKneiFH2dJICyl
- WTn81+exs3c+SPgjMkhiT9Di02ay0+lvnYrwHYC3hWpUtelTQELoAO0PaapwQPstxP6VqSo3
- 7Jeyd/rv/E96SSyAu3yfZfJ/M9UOavMhbhZi2Qu8NNWyEbDtjCwPQlMWCbqQONlBU/4irLEg
- vnvscm3iTAqs87Kuy6J42OJl2jBbZT861s1CpUtfEOfQp7HUXCa2APFGGdQyH2/0uQRSrcu8
- Fzwv6+PPrvM821pZLdMOpD+CdZl5DxoxFz+rz7f8d8RUR+/KeDEs6r1VpyaPJYKQvADk60Cn
- fzG0Wub5+Hn19BuuXXahIdG/E9CdB+ZFP9Fh2/NzGwgWf/bBNsdX8zjWea/CNC14/p8FfJDd
- OEmqfuEXEv5SY77d9+9BuHn9CJnnZUGkBNtkyHMgyMI0v2FZ1VXCbFsBsaQu67LYehTXL3ER
- 03vY8FCnxE7hrwENtizzhNdmCilbXViTghpZRVJMtEfPUYZi6Q787FcDQWnPO2ZRDwmvGhal
- 1H1NWSu1NKkP7ey/BbtDw1hFe8g89TdMsBHcgBnD/iX8QJkrNNROfo5jMBLJHlg3jUGmY59a
- fOyAuRKv/KzUvurrv5uf3JW/4LG5iPzdAfkHej4axyt/2sLOvf/JbPb9bVFOhN4vy0xLs3P4
- b5Dnyb4lzMpOp79/qt5Tl6uXUXuHzveuf12HIxZzquzE/sWpz2sRpGWeYPLfJtWOtS+CaA/f
- BBULhdj3Al+UyjcC9p2R7UHYKYswjuMIiOM4dMXXbgLXCLc8fyXgGwgDurlkx+lPFl46F5Ge
- JkBFXvRgWT94cct/AyxdQY/nBTu1+4EFgYmWAzO9/ziME+jFL3/miGf29iwOnQm/XsFCeQOC
- O/0vA1660kuyoixzWKA8zgryJJTwUvzWyqC9u/mlyf+6ItFUReSJC4L7PwD4JQCiWe+EKiLW
- LfjH/xSonyZPidEyX/ad0mCjy9RuF8XkeV6047do+Z9158SMobbwD2Wnf81llg/r3Wx1luZF
- Ss4z/qsgYbWE48NLGmr7/zZ0V2R5kXkCMQT+B/CDH/xAN3maFwm50OIHP3jJRsC+M7I8eFF9
- 7kjpcLjRFxoA6qnvZ/U3mpSEPlAwHPga/OAHa9+USRT63oYgjPOqPXN4/QNsNNx4UP9D079S
- Sj8xPH6gtil++1/32lGTHA+MRnEDW2SVfxwsYoyTd/Offape2n5bxUey6H4WwPM0av9xOTS6
- ALKa/sBQZGmrPInjOK2WO8rm3BVv6Umat8MTe5/v/PWpPhAX4WXrjebpq7L5MguBpc0918Pt
- Tz/4blgbQe4qfBorIp4jrM1/HGOdSOp2HSHix/8y6BgIih8DlB/84H/tw8flWD/4wYs2Avad
- keXBy0+z/uAHP/i3sMzwIf3r+MEPXO8GXD/9L6jwyzwOQ991Xf+He/mu64bpO3+qeuqtNeR6
- YddN/3gcGL1Ofdf1/TCrT1Q2M1e6eb/+fH0/+AGBGrqOf2lPni7/z5i/IJTQumLO/d/Dzxj4
- wQ9+AOifD/8Hr98I2HdGlgf/D9u6u9lN83T8AAAAAElFTkSuQmCC'
- 	) base64Decoded asByteArray readStream
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBook14Data (in category 'dejaVu font data') -----
- dejaVuSansBook14Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Book 14. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 14 18 4 0 255 19 0 0 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 17 25 34 50 62 80 95 100 107 114 124 140 146 153 159 165 177 189 201 213 225 237 249 261 273 285 291 297 313 329 345 355 374 387 400 413 428 440 451 466 480 486 492 504 515 531 545 560 571 586 599 611 623 637 650 669 682 694 707 714 720 727 743 753 763 775 787 797 809 821 828 840 852 857 862 873 878 897 909 921 933 945 953 963 970 982 993 1009 1020 1031 1041 1053 1059 1071 1087 1087 1103 1113 1129 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1151 1159 1171 1183 1195 1207 1213 1223 1233 1252 1261 1273 1289 1296 1315 1325 1335 1351 1359 1367 1377 1389 1401 1407 1417 1425 1434 1446 1464 1482 1500 1510 1523 1536 1549 1562 1575 1588 1607 1620 1632 1644 1656 1668 1674 1680 1686 1692 1707 1721 1736 1751 1766 1781 1796 1812 1827 1841 1855 1869 1883 1895 1906 1918 1930 1
 942 1954 1966 1978 1990 2009 2019 2031 2043 2055 2067 2072 2077 2083 2089 2101 2113 2125 2137 2149 2161 2173 2189 2201 2213 2225 2237 2249 2260 2272 2283
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBook14Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBook17Data (in category 'dejaVu font data') -----
- dejaVuSansBook17Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Book 17. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 17 21 5 0 255 23 0 0 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 21 30 41 60 75 97 115 121 130 139 151 170 177 185 192 200 215 230 245 260 275 290 305 320 335 350 358 366 385 404 423 435 458 474 490 506 524 539 552 570 587 594 600 615 628 648 665 683 697 715 731 746 760 777 793 816 832 846 862 871 879 888 907 919 931 945 960 973 988 1002 1010 1025 1040 1046 1052 1065 1071 1093 1108 1122 1137 1152 1161 1173 1182 1197 1211 1230 1244 1258 1270 1285 1293 1308 1327 1327 1346 1358 1377 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1403 1412 1427 1442 1457 1472 1480 1492 1504 1527 1538 1552 1571 1579 1602 1614 1626 1645 1654 1663 1675 1690 1705 1712 1724 1733 1744 1758 1780 1802 1824 1836 1852 1868 1884 1900 1916 1932 1954 1970 1985 2000 2015 2030 2037 2044 2051 2058 2076 2093 2111 2129 2147 2165 2183 2202 2220 2237 2254 2271 2288 23
 02 2316 2330 2344 2358 2372 2386 2400 2414 2437 2450 2464 2478 2492 2506 2512 2518 2526 2533 2547 2562 2576 2590 2604 2618 2632 2651 2665 2680 2695 2710 2725 2739 2754 2768
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBook17Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBook20Data (in category 'dejaVu font data') -----
- dejaVuSansBook20Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Book 20. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 20 25 6 0 255 27 0 0 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 25 36 48 71 88 114 135 142 153 164 178 201 210 220 229 238 255 272 289 306 323 340 357 374 391 408 417 426 449 472 495 509 536 554 573 592 613 630 646 667 687 695 702 720 735 758 778 799 815 836 855 872 889 909 927 954 972 989 1007 1018 1027 1038 1061 1075 1089 1106 1123 1138 1155 1172 1182 1199 1216 1224 1232 1248 1256 1282 1299 1316 1333 1350 1361 1375 1386 1403 1419 1441 1457 1473 1487 1504 1513 1530 1553 1553 1576 1590 1613 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1645 1656 1673 1690 1707 1724 1733 1747 1761 1788 1801 1818 1841 1851 1878 1892 1906 1929 1940 1951 1965 1982 1999 2008 2022 2033 2046 2063 2089 2115 2141 2155 2173 2191 2209 2227 2245 2263 2289 2308 2325 2342 2359 2376 2384 2392 2400 2408 2429 2449 2470 2491 2512 2533 2554 2577 2598 2618 2638 
 2658 2678 2695 2711 2728 2745 2762 2779 2796 2813 2830 2857 2872 2889 2906 2923 2940 2948 2956 2965 2973 2990 3007 3024 3041 3058 3075 3092 3115 3132 3149 3166 3183 3200 3216 3233 3249
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBook20Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBook7Data (in category 'dejaVu font data') -----
- dejaVuSansBook7Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Book 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 7 8 2 0 255 9 0 0 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 9 13 18 26 32 41 49 52 56 60 65 73 76 80 83 87 93 99 105 111 117 123 129 135 141 147 151 155 163 171 179 184 193 200 207 214 221 227 233 240 247 250 253 259 265 273 280 288 294 302 309 315 321 328 335 344 351 357 364 368 372 376 384 389 394 400 406 411 417 423 427 433 439 442 445 451 454 463 469 475 481 487 491 496 500 506 512 520 526 532 537 543 547 553 561 561 569 574 582 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 593 597 603 609 615 621 625 630 635 644 649 655 663 667 676 681 686 694 698 702 707 713 719 722 727 731 736 742 751 760 769 774 781 788 795 802 809 816 825 832 838 844 850 856 859 862 865 868 875 882 890 898 906 914 922 930 938 945 952 959 966 972 978 984 990 996 1002 1008 1014 1020 1029 1034 1040 1046 1052 1058 1061 1064 1067 1070 1076 1082 1088 1094 1100 1106 1112 1120 1126 1132 1138 1144 1150 1156 1162 1168
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBook7Form (in category 'dejaVu font data') -----
- dejaVuSansBook7Form
- 	<generated>
- 	" Form data for DejaVu Sans Book 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^Form fromBinaryStream: (
- 'iVBORw0KGgoAAAANSUhEUgAABJAAAAAKCAIAAABkADNIAAAdjUlEQVR4AexareKluA7vE/Ud
- +gR9gepqLBaHrKtDoVBVKAwKg8FgEBgMoqKmouJ/CaWcnGHmzMfe73uzuzOckKZJmuaXliVf
- /wAK3oe/nzK7W/jbW+vC1//p//R/+nej4PaDrH/w/cl3v6Nqa3S9+E/FxVr/q2Z9LBn2sM2F
- n06BVeEHXI+wzP/J21cyOHvHOCT2/xxBYgRIj3/9Tg0eKPz98tQvtW62/7q8D3svhdq+Ya5G
- ZLV9Yy2FLIxRmepRZZnq2jSqKJsxoECpoprmtlAd2gRrRkTbKZ73f8Xauc7zZsGcQcmye5nv
- xipTTV1kTaqtW69VO/VVaYBz+buGw0wjJPh4+VX2Kq+mqS3K7lMO1E2j86IevwlYm/Oy358D
- asn1aL/hbqbIdF3KfPLv3plDfZVJNb/zt1apdjRlgWf4TCFlvnceLWsrhNofPnH5WGtRNE2Z
- 6REzz/iYQnVoE7haimZ2n215ByDXVfVo008clapZX8barq6xYrfN8+bcvt5DvbM+vIHRpCXl
- nPLqDwrQ0tVm2p/Gj03VI7Pmtm6RWcE758NpyZmNddUtDleMsA1VMxzjLTLW29Qs3Kb7bZo3
- 77Z19/E3UoUIolcN221PGJoamxfsOi/7EaXNBYTWgPS/X7rA9+QsJt/XVY9sGM27Dc5CTB5N
- wmSO0Nkf9jYehvm0nMSvbSZldpKUebt6LFsLqkZ3Pk6S5n2vpRpxMilZLH7TssB7qStks7h7
- MzByEDMnZzUZyVrUnvWSnISSCeYicvJxT2aE16eehpBsTZ4fK1TlMOSv9UihzZkaLSxwFQ2h
- etiufSg5IURW02VUdASIN5MFzlyTi6jqFuQUSOrJJV/SMH2p2seaIa/dpMmL5OhApM4ukayG
- oo84rIb98w+nrVc0+ib09oKxudFlJrO81P28v8l3JSFisPcizhlN0RHlZMMNZqW4XjBZbeEQ
- bJIgEbkeYWciJhAfHVYIgpOPyoxMTJZFbRVl2l02jAIkETOlNOLYWhIim0NIEgETJYo2FO0a
- f/YlJySb/MUv++2aIuVq2MeCk0iZ7v0jDqIwe/hFydQDhVXfHsr6sE7EkB4UQ6NGN+m7FoM9
- XB+L0GZU1ndOWs2IGm0jaAQ3vzSU8IhzSyNZOXztHXAscNxUEZLN4UsSUk3uQiBBRD3jXKX0
- Slc3KrAkN4cjFWepJwDs5xQ2xwv29l4Qworuw6YdNScMXPguubEkpPwl4PEDIXRwP9r4FO3u
- T1MkVaR3+OGh3A+UEOD8S8mvXak7/68zYDU5JEPRnjY4RUgx2KvdYZA17efu/jdSJWEQp7BJ
- /wJBprYL/lmwq2R/dz2Hksl6RhB5Ikituws9N32VODkDwxaE9WvPSHFntVu6XAqZScDcVysz
- 5ZwLTnnR/jmqJf2FBBIC9N/sSmC0DV0Jv4X6dFqYq4wexMs1wMGAcU5pPvtXYWF6/JEVncrY
- QZQQ8alZXJqcvBBzjsFnuXE/EQayfUF47X/yCluOXn3KPkWhuP2caQdFEgRgJqXZg6kfkr4+
- gSBv1+cmSjUeqJrdB/SkQBEov89hhLKLJYbIoQw4LHGWmgvAl+OBwQN0XMcDGHs88Dp808xk
- atgiUteUUH3t8emBhhRhHOIDPfiCESD6Db9M/Lz6zP9EaF5WlBkh+ZHP34XOHzEJr/ylCzPr
- cDEnCUwMmj6CZmwtpoCt2cpoO2owFnNZhcifvPb2boobGBYoklUpHRL0OECvzjAET0MpiqYS
- rLR/VBoJIe3mMXNFpqaGgeDcHktCVavoVfztqAnh8JgqRkGvtKdULWNJzwuL+XhHqBQsS7g8
- pDBdh/KkanTf6Rn2Vy9axEHJQqdTtFUqDkNOy3HRlHW/GZTkL+v3gJlTxQlVtw37UMYcX5LU
- WBzvTcnQjGBqnmDi+73NWFJaGsVIfoaP2EHlzeyctdYtpni/DnGKknK0MXEZEaYteTHggkyp
- dn6gVPn7EuJu09V4WsmyzrqhoMXxc2IpsSKtjSC88V9+ndFJ0Y9JzFfsMMBdQadXuOfqGCU5
- 5ZmIp6CERtCV/tZ1/izOifwMCWdWfyainAPkaaWrUoAXaZHgWO2DH2HPKBcvN5bNh7C0OSHF
- jsx4wYYbOC1W5+1BLkQOIyRrZmiuli2kDxTWuUExQrWDlVNxFd1cx74QDq4km/21VbZf32/7
- PEzb50o29NMzaovRZrLBTYIQDWgRjSEsr+d16WtAlKLbXsHnZ3o2C1pE2q7W21VzQsvxVV9o
- uXiwrM5kZ6OzECK3TydUi8ldzMU6ux9kw61w2e19MWV7CtW3dRDCVctbm3JviYSYKaVPjg5f
- wci0sZNwonSQphp4fjr9Y6NLfFJsb7m6K7BGbeEIVAPVy6woDs4uLSMw9U8l3drz1OaujYQ4
- +BD8PnSQ3If3h66CEGjE4EYqIO9ivpX27EhiTqbLDj75oyByknVJLclhs4eGE9mAATBCttBf
- JpMg60BJ1Jat4cpVyFY7ZbDexp+Fhl3rC1MwNeHbKLAnFYcMusMqg45x+nTSMub9Zsr6GxtG
- da5IOHiPe6gkBG8dLBlaUI+1QBqw1qILOMixT1M459DDI1sQB1t9G/P5C54/KGAGGv6wEFHS
- AwrhLSr6/zIaSyYgnRJS3ggCFCoWE/sD/V6qtBmJVM9/wem9lUV3Pce0p+UWwr4BJrulH7dw
- CY7dbOOGEjMASJUgGR1NHRzmpwBr5n8wHSHc9F2ldNNoSojZQro/LjPBks4/JdBPytp0XT/P
- HX/pf95oiMMbRXnvvj7C6JYR2tvzaTKvPPeLaYbv+4guInXbCKY+r3pfsBg9aBWge3NwynUf
- hYEWCd3kz19hy/GrJ2E4kwnOHhj3kPxTZi2AmZsVRxv6CVNzQs2Fd9Z/RM/F2gSUHzjuZxzl
- Hg8WcWIzswBSzyX4wgb7m2j4j+UDLW0z7K9vF3C1juWPpy47FxHkvwudH5j258wnaIIcJ4TD
- 7Ymsxx1X6VkRVK5DX6kOb9Ww6KLaMJoaM+1rW5ubCZ37tsyre8OXmDFoK+Zc1JN7Akx6dE8w
- RXf3le5WPLZVJbZzH003bxNE/sV02AiQaYcVOn1jxkPIdMvh3TEsnCPCFSUqBSVUIRT1X8FO
- 41s5XPDXPCDX6go7t/Zm3OzUmsXfSAn7aFn2Ny+B/K/874ExVtvQTjbc7nTL+31t0ywe2wDC
- 55/48y78gWebTDPan/Q2cVh8hgOb6q8R5zN2CcEt3B9z0xYs76N9faWKjBEiihyysVDNFuKU
- WSlFPYzDCEk1FKwYw5GYXPV9QROWY2jU2O80Fx1cPNuIOdynO0mLOHswEael8WjYae1vwDZY
- y2of9w+r/KPrmjWj5fg45WlCSvv+9fyG2NVIIlXJU9zABdnP87K5S3hShOTztk4TakpTOc7a
- LdWRfD+H09MeOGerKS5xujuBJehAB3pGRq1jW8TbuHK4P1NjujLTj5QA5dosjwYj1ppmDRFF
- 8nYJfp9nOF7NvYauJY7YDCGy68oUmSuS4/l2VIzCOT8ejAH4cSq6CR+xJgH2WmDetwAPhZHm
- WqTpEmFt+MA2PQ5soD+v4ICYLwELv6cHFYIys3/ZLidcUsKTNi4okWZLdxCQA9i1pRaQ2LfZ
- AZj18aSnz5JTlOQgCZCjGMlwkuON6bDLCGBOCAmLgHtZHy9pSN6d8dfkvOZvBMsKee7lVdz9
- XJglIUKAle6eiEHfLMm3PVxf0guk44EN1jcdDtOiYHsiZNKyjwMEOSzafuF67/7QyuJnbfyJ
- j6s+nOpMzghJvVRYFcffZmHqJgnkzQxRrWSSn4+NUsaX6Y4QTyHUgL/5o4e4WPHWnJrVp/zB
- H95JXtVxZlZ24Qu/SprDpsXFUf2KvtsjB8EjbCGSocovhqHPzlWS1KNzoxLlmLYVDJxrQfMu
- rSys6d4XDDihkYRBofAVp3pykKUxepuhhLVbQGNtHHuGES7qYboEO5Pi5WCfV37pOMfLz18h
- fydVwmo449CJCc4zg9Km1c2HYx74nowMU1Ok0Db+coFRdOkwaQ6X/qosVUmvO1r4MCLroRaE
- 1/MDK0dGCEuf05/U5aKo4dpPZFLkZp00y9oAq6QhJY2ONf8yb5jDgYgdVL5fpC7nelwqwbNC
- UlaOQ9T/pK2gTNVQnTcMQ+QKDoqAoHnUsDd/a+9qFaTleTZH1HPgCHoCaDQWi0Pi6lAoFAqF
- QWEwGAwCg6lA1FRUzHen2cx0NnPvz+zP87zv90axoUBh0l5NcqVbgL0OjOTBjA1RDEQNXSrf
- dNjQbGZLk8l8ATcyHs+L3adxsxe9zIfjjQFZMKLKT5VxrFZS33o+2svKroK3jtFr5XD220pE
- /8MsMsS7N9AzBMqnNQgibxxg9C2ubBBSybr9M2j443pMakHyB9KhJcXNw/Z7ISJKUj2Gzi8p
- H4KmhUVUkhd5Gkd+NQUXxmqbATuQN8uR7pGmkzTVd+uL5o729ff7CPGwTaLqEo9F1mgOpgw6
- H2o6yl0W3d/amCaV9QromMWQeXZbI2TjvFW/5DOd7qoiFfToj8HlQ02d4dOFumpS8fqqNLiK
- BPOTRbDUCe4vPNC720TnFiRwPZz6EoUIsqUCNe9jMV/bcMyNQieNO2wV5gRunE9wva/c2TKO
- in5ScZR387ZufiDVYClRXE+7w3sutYB0vCyrHIJDx9LWzbjhPW2XC+J6wQhTzRQWipi5DL1t
- u1Q4r21tkas6k1mtcm8QZlvXbZsyuNO0begdvS9jIdJ2J4SeCXdvnIq54g7bUQlc2VyID+AF
- NecUR3J1tomjcrHY6SyWWQbWITy9Z0dfU6Y+n1/st8VHg2kQorajiWDSA8JCmGnZh5LS37bL
- U+JJh8fnUCP5SOZVM2MSD/k2cSyvEousWa4lSPPQFqmEi5IcCbXX1VLqm5mpFPnkzkFEIi9h
- 0ovrZamTrD/wQ0WAsjqLIqxAwknKEzH8SJ7O+4AWh4owBTyh7QovSESkG8LfIm1s+Ou4o6vr
- pmkXbW8XBpwQ7rDR2AAHDIU7bDirjkC3H+rkz9GQQAPU17tfXe0npnFev5qlJ2K3y7bvmgLx
- 4+2WWamqIsWpwb/ZgNOFkGk9bI6tg5mPOkliPkzgp02Xy5GS5+aTTmI81ixKl2OUotz3Dt4i
- pDqgf07iqZIR+HuB7H2O4dULc9i8Yy86zR02q48zTA59qJ7JmX3fj+MYlYySltx7OXm0RFdz
- 71IInVq456Ht3qYIxnr80zKm7HSJ0b3oZQ2ky1gOp3sBe2w/qejm3ic+FdrjkCTbCA/gx/LU
- Gok0cjpFlxvAxQi/PKSCxcM7Q29lffp5MvLBKf6C7I2ojbY+IvYSt3IW5szTx2518LuEfYPn
- 4hfAHJHDJWO+m9WbWanNn5byJc6ikkgkYJMdwCe+BSxqYZJPNwz7IZMHO4yJbopVPXbYKpnU
- k3EUp1zHWqmmn7SxVq8DYufnTMVemRcoGHEXebtu2/oim3H3+btxWLSlFbMclz4vB+1Bx+k5
- 93HIpmnmw16jSGqYB5UgLeoY6yzFcSnTrBh2G2bYzFKJtB7AD4zRNu5Fq7zu6yQJGctppXFB
- FmdVmRLl+4R1j8yrTKC/BGgiRHwVIbJm5fevUmUvtk7SqoYY/3ExdQb35+LObRzG/XTE7r6T
- RM1+gHigqvvDQei669uEJvlQuLG5Y4hfOWx2zROonuB0tcwz4dbTXfQEiJmnMq31S31BXKrc
- L0D1rXHerEsronT381GWt+b1qazvFSQ18nq/9Txuhub+KhTbK4Ud43D2w8rpjzK9KS2wjpr9
- ctnkjfyezgxiUDhQPqt532ErPMFdygSz2YuCzn8GDX9aj6KbTODaSU0Hqq6EmtaHf/SqMDPG
- ofPrSgaaFN3zh3UcJc0GF0rVVwJB7SHSfbdmf6RJgKO+wVgtPX3xFZhy6HxKEwDBPekpzFJq
- IAdm82GOWeEE+BG4/C4NORFLp1Q7LhulWHzLxrg9JX4jn+ie03A85dDP27ztsF3GMqkCuA1D
- mEXuM2tZLv0qf9ivjtxcQloz8EacdU5XQtTzlEex6pvYL5Qx3q8vZw1ugeqgFmFixSSVuV/Z
- U2/c1E+O3KYyTbLMw00MUcuiXRnlNMJV1Cuax6AphlqMVzZCS++yvHLY3F4KpIEFOuf00kR+
- lTOXfpgOjfSIv4Yh1nPANseQkxeqC2QbepkKTIPgePfO7WnPrRfYSae7MvXTpfh7ZQ6VQr1E
- 94fDuBAVhy6Udlj0Hat6HTFQktQLLbaLKGmpe3G1urNPo2wEFFdxXG96LHyh1J77GjKlIFch
- yptdjtpenF07zKPiD1rotxw218Cssnllqd3FIV0suKEjhU8cjfhqY1fHlJrzFzoLRje+lWGL
- kjxFWsVfHTbotpliXMvaRQZ3s57flVSVBGPGV8sPFlzAlX2u6rpuJ1/193ZL1Y99A6uT8Y6w
- t899FSGoc4dtLv3nJbcfHSQq+xzHKvjmtpZRWmS+JsGUcZwXMko7d6sdxWAbaoLE9WLu88lE
- 02cOG1py0mzMYXtGzNIISETkMLhjYgsLhZTvwi+RKfmM4q2CAmD4g8KqCILAPkwh88WEAfWw
- /Xxzq3CEkkmwA3R9kflsQ1R+dbkU+OUNPo7fGTsfVtzxF2RvRJaJjz3GLI5w/G2hqT902DA1
- 1G8YFsHJphCiqHKZqyqRRZUFtT0rvKN3UVAGODn1OaZ/QTQU8Aikx8D0mAiy0scO2+YD4Ek5
- WG8bSZw2XVflCdpdNR6Xzwp7xFon6En5quwszdIkKV85CVOVIq75sdM4N+flRPfbKgl4NI7T
- djo0DIkD9mjxpznGpsgz4eEmL8rRv77Rh3E0QMC72PtMFMEwDtyzou9ykbYnkJcMzJ+yOjE6
- IwQE1ZJyczgzyBp6I7cbkYnE2A0eMDGAOyuZHxdbZ+XQF55whff/oJwlkqVJ7Hnsx75tu4Hj
- fZnnTRt+GTc27O/cFFXXptgBt9dVw+mZzuht3/dtOy2UtWcyFpGQmdod+tSQjPTfoTLYeNv1
- sQBvEB6zFUkspLKvT50XZy9uBwdpd77ny3HqWr66CkXnNOVyOPtNJa71RVaqMosQQBHw3kDP
- ECif17zvsNmjj0WxEzVnyKBg5FNo+NN6FD1izjzb775SVpcSqzcdtefQ+WUlA80A2Ye2inza
- DSfw08JUAw7zyZHudzQ4hyUYwi+67R5MOXQ+qeEOG7cuDoXvw+X3adCJSNMMJUUnAhP1ZaeS
- uGgUtvw2h43hKYd+1uY9h22fR/A6uNhzHUqoTPLLwWXfsarI6XXVZqqKYelCvwL81Gy4uDmO
- yj/tlGc7OIxuah/wjkBuzFxacYYz1Dm9XSjsfKg1PH/O46QdL9nyReIbDjAiG4BPjwdydeQT
- lkIUo6PILRbtGO+kIcwcp/UQ32IgQS8DbJfUgMFKv3/Gtc0xVugiw3ORVXVOMmCjEYGNeJVx
- 7e18pjbOWn9qKIiK5rZpXE/am4KOUc5jaStMX4qy34M0FEldd9OBl1ZYvCuzZphPe+eWV8Qs
- 0n2e1JvboWZjmAe4tZCx36YCK+6GeRrHaexKz5Mk/wq65NY2pSQSkO6kmixCfNetBi8vtade
- T02GfBtUhojCHCryHOaD1hlg4h+uYcOxYRtfzLXawCGkR+JV9uL6IsnbHZfL4d3c1oZ7oiSQ
- yveURrtXMQJwSIlEedhyfE0iLV9ib+c2L/tJFBTKJNBb3L4DlcCubYoQQml0TGCv9zzSSNYr
- puB84e9xjex6BxiCSRnaDHsWJl1lPcMFII47bHZVSDD+qsOG36GYX1J/4jq/p4t5saV2xwyb
- 0sjdN25rEuS2nXON+SgcTdgHo7W9Z0BhsE3DyCqj8PdlDhs/qD0AY50EM7bg3elx/M5b+5Lf
- sxumvPgL8jei+4R1bA7KcvJrwOK2TCk0HOCF12Azbf4RoHIxn3ubUjUI7cuSFKm4Vd24vQsL
- 3PWsIB+7GV5f9AYlkvswzwt/BM7blRRZz1py5ghCTDqvkGEz1uLpCb1ZnOcx9XqTZPSzkrFm
- LCQk16xxrPTL74jwUvLKRY8lsB/KIvsjRVWm8bUY2FmHsSaq1iiATdtRjI/tB1A0y+P7J0XT
- wsBZ/IxafswT9k82fh+207nP7SVJhodGEqbfa3LYUD7YDXw80kTzoS8jUWBsM1wM/DloAWuz
- NJZqOtg64WwzQfFH2msk5lfZoYRZGK9/BGe/p4TBmKhpnqcBEv4DGBsaxGP05ED5BU1l3jjA
- JJJ4Qeq5LfyCzX0SDX9YDwiY+cy2npSEoX2GlKV0c2H7x9D5RSWblIg7Uyml6mE5bt/fm2Th
- 522OdL+kwZQOsdoQTL0CwJRD53Ma7rBx69oaBoXvw+W3acIqa3QiQs5R0mzu6LAlQ9UnNRxP
- OfTzNnc1bGZSjBLJasSDuU+q9ZxKGeSgkGWLkjezY5uItLgRnlQaK6+qlDYSzIsMuA/3wKIL
- cmNwd4QcM2JcGGR6xRjxfdsMutSQPUOf1YsdiIZbDvuVBkOSzDi9XiWmPYKClw0Rp5H4q9+1
- KfuN1hMJamTZY++CAUxFooIelbeUfkFJhsOyX+cs8JiJ3qZ+2t/eV67vp7tcHM9wUge63ei5
- q6pmHLuyUIufqvos3PrlLP1iCNM1JLIhNLXHmApSx8Xm0EkmkfkAdNl7JeZzKMEVyjEqcbu2
- mLUDgBe3PiO/K1BaLDUJNMjLze87DIaEbeibsrvRohZdfdygL4nCX80L73bYEndsYy3xazeb
- 3dosIhFZrYMinNDUJ0V9J4ZeyF0cz9BbpPwY7m9GC/cDWuY7tUGyKH+WmVUUCDYLNh1B2RIq
- MKBNR54UE24WGtcmNAzabyZksYMd2rW43000pLBjrCRw2OAs7r8ax7jCRsrrdacZXH/M1wOs
- IEXNAk0arOBCTXg5OGxxdd5l2Pidt1JGYQEAzhjhC96/UfgIYgeQfcyGNmPELrn99acAOQoP
- QTZkVaHh7e29PWQbhfyJdGAbeaP61MTZwpK5m0s2mb95U2NO7tyX5am9pvhWKHZSaTgSFzSm
- 4GsfU+fryz3/c2inq6Nb/qVaz+llOYwmNgsTrONPZJJlWSKTsKCfi9GnD8Dpz3hPeH+ZQOw8
- rcf9/QtCiBG08Vw1Xz4sod2G156Tqrrm4aYjettO9/5/DIE24WbYVKDba9pMSC9lSu5ccGqp
- JZLJu82+cRUkZGjq+xuc/Zryxo10wQqExhdHTw6UT2oI1N44uCPNxhmWTnwGDX9B7yYo5qcR
- 2lS4WMKK3DQRrD2Hzi8rGWgiss+Oc75Q0vnkSPeDGnvVyKKp85uNLQbAlCwsqRcOnU9q6IMQ
- SqLZKLIuxMStkuFS+UNw+U2akGi27MFcMwYF7tiSoeqzGoanHPp5m+icylSNO1Ae9qnOcJfI
- L8pYZMMZKly454wx986BNcbaoIw2FL6t/yfETOUbcdYmTbrjdUeMvXxOnL/IfbqNYyoury7D
- +7i/vGqMDIGfFOPXpil4a0NTZTgUnxPDX/95cR+/2T53MU5MPyXu469mrZlUgvP1l40MzQXN
- 47cl3NafprlUzcbuwbb+Twq+vX1byQaLw0/BrMQ+rOOZJ+BKzW32blcNBeS+V8KBjbnfE/pr
- 77t/29eEZySMYVr2Kb4u5pjC+iUuWNkCWD+sLnSNkJJdF7QNwD8qPBCp+zQfvnjPMvgHBqWM
- hRCZGszl/4Ug2sbl5C7WokXe7LlthqHM6pP9j8Y2xXTuc9Os+65TuAPzsMx1nmAk698tZoZM
- eGkv/34hNPxlPRekHgPm8vYcOp9XPrF6dBzUflfDFpZuhbRSYTh0PqF5HgrfbvMjGi7Hthn2
- /QhVv6TheMqhn7eJ7DFV5R+pShA1HfY7cH0/3f/+cfZ/o9hj7BpVqaYb9//AnyMT+D9b/kVi
- /gvs2tmn/3F2ClsSgQiB/xXt1wWX19CNbNzfMQ0gi9bzz46wtY6Txjw+t+CWU/+IIOkgqUb3
- 3oS9DF03ru71tlXn2LXDvL99+S+YCobh+82Gfd4P80UzWodu1v9/EcosKv1MRm7rSoml7/+4
- ON1XuZRJXmEi+V8tdutTmVT9evmf/E9+BoGKJMG9K/8nv4mnHPp5m/8Dj+s6nwzBqkIAAAAA
- SUVORK5CYII='
- 	) base64Decoded asByteArray readStream
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBook9Data (in category 'dejaVu font data') -----
- dejaVuSansBook9Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Book 9. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 9 11 3 0 255 12 0 0 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 11 16 22 32 40 51 60 63 68 73 79 89 93 97 101 105 113 121 129 137 145 153 161 169 177 185 189 193 203 213 223 229 241 249 257 265 274 282 289 298 307 311 315 323 330 340 349 358 365 374 382 390 397 406 414 426 434 441 449 454 458 463 473 479 485 492 500 507 515 522 526 534 542 545 548 555 558 570 578 585 593 601 606 612 617 625 632 642 649 656 662 670 674 682 692 692 702 708 718 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 732 737 745 753 761 769 773 779 785 797 803 810 820 824 836 842 848 858 863 868 874 882 890 894 900 905 911 918 930 942 954 960 968 976 984 992 1000 1008 1020 1028 1036 1044 1052 1060 1064 1068 1072 1076 1085 1094 1103 1112 1121 1130 1139 1149 1158 1167 1176 1185 1194 1201 1208 1216 1223 1230 1237 1244 1251 1258 1270 1277 1284 1291 1298 1305 1308 1311 1315 1319 1326 1334 1341 1348 1355 1362 1369 1379 138
 6 1394 1402 1410 1418 1425 1433 1440
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBook9Form (in category 'dejaVu font data') -----
- dejaVuSansBook9Form
- 	<generated>
- 	" Form data for DejaVu Sans Book 9. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^Form fromBinaryStream: (
- 'iVBORw0KGgoAAAANSUhEUgAABaAAAAAOCAIAAABW7CymAAAo50lEQVR4AexarZrkrBKuK+Ie
- uILcQHR0bGxcJC4uKioqKgoThcFgMIiYmAgEBoHos4TuhDSzM93fzrPP+c6Zd3+n+K2iqHqB
- wO1N/OAHP/jBD37wgx/84Ac/UGMJAC3XSYnpcwAopI2F1lff0UtzSmUHJ8hZYBgANFy1AFDN
- ceddBgHNvN2+CVp0fsaDSkrc3CAARFcXS0WXw456Wm7XOQPhvPUl+m6lapdtsWWEvU3VaY1U
- 008gCIYHEBFPerSZ72VxtxRupQgANyxRnmX37pr12pB73e8op/VaBADZRIlXlenvWocW+/mr
- 388fvTd/AMDj1KSTtMvoFWj57b8cRjY5BpQP4iVv/8EP4Pa3oBe52avIWWOMiyXW6CA44YzW
- xpwtU9hNcbHHMacFF9o9j2JjyffDGQ/7am1ntdZJdT9N4wu+Ya5u7+llra32MGkv+hvm803a
- GPs3RjJGx872/Zok/f/Xw5odrzuTV1G/Xj+4WRjgXwsj+S8wsejUHkpwD7n+I+vLEqBo+SsT
- WP/RVtWKp9O+wGnJOePi7dHNylmIxlZyvhiX1oyr/TF+4DYlGOOrvS8cm6h8WNYsvmjR9vY/
- CPtqzHk9iJ3MxK2Sy83YTXKxurfyyV9PoEZvd2gTUwtr3Vvp9jSFNakOrC0ASvl3crKHe4FW
- udT47q06qbJnna8h+qYZZRr+SVWz7VnY1oRrI6eWjCrevkJpp9VMZ7XZSK45pUqbhc9MRn1Z
- jgFme6MFQMO+kfAsc1eRySSn6r6uR6mv0m1o6kmZjfcVoVFHRtCJL0YrNrHzkC6G3UrBCFUT
- LNNWhGurvDUkizV9IXlxpfUiKOU61W7jTVH0wnx0IdUUVb/aNJMNZT2sWv4qZvpapBiTq+JT
- PzL7PJAY+kktYuxHZd4ONQdXd5taYl9zS1fXdLFpq5X1dUvToTY+1O1s/Uo181U9swo6C2PW
- eZqXq48vtK27+ZXdbFbFGeNCRZW3NgNcjR82X6YaIKPbMZyjTQ64Vi5qL6a2HZQxrD/XSivB
- 5Wr0Ek52AbLNIGvGrgAg+vankL0PYvzD9drmHKAc5OlpvEOAO6GjvbNwLo0z6kFpAPAgzYO4
- DRgg9FPt/QguNhtSiQ0KMnbvLtqATk5928/GrkNH9WG0GkPWLLcUYaDL1aoad5uvLt4IHWnZ
- alc2eHc6T82r80dm+Sc5ysoeAB2WSbC2OaDy6h6aFQjKXjwFI3mYaDXJghAANCj7Od01i29s
- zcr5fSMCbauijFBUU7JHjWgBMh7EVuQAnVyHHLJWXOP2gFCpbjfZFVkScFmFqllHlUcMO3D9
- 8Iq1hkuktgvN4YG8N/FVd5iPx9YAQDF6dZ3KAfBxHnBeJgmCRoSfvgucYMDtPjgrEQRk9ZES
- 7NzVOUZP03brXGVeGFAc+cDK0EkALrvTOQ/D+gFac9zc5xABs+i2n5LiKChD+jQcwxVZF1qs
- c4tOYe23SSIvyOxufxvpNHDV62usnce+qauqqkk3iiVJx8uAntxGdBcbFOTclUa2JY4sWoxS
- J/XrSayHCxZwBSL6IzkJNjWqLTM4gZtBuIsnB5g+A0z4MUTeiWefv8oXSoKbXeVXlVG9PPkS
- 5EdXAHhcXBT0CxH8UosmP70jr4ftAzOiyqfGT+vLPq5fRolZjg2CE/XurvAB8M2KDIBElhI+
- r/odcRo5fjTDLa0QILI9Ekfpuzl/LAAywjnJAPD02G8rrX1vTPs4RNfowQ0B5C2GFH5ow0JJ
- WDiAUrlzAfLTPU6I3k/HJy331RagzT6lT9meYegfvh0ZAp+T46VGEPD56A3Tidgbczb317yK
- 6Q9rGu4V9BHsvx9uPRnnfx8YyWBHK0y6Lry9l3qW8Bred9fznIB8dfrNicOqrqNPs9diwBAQ
- ol+KM2LEb+nb7B3Phz5/kGgey6r7MxGEyjrsQE7CW/QJs8x18WAxeT3HxMny7OilY7dvgx+0
- +XjQMNUDjY7XLvDsgC9MBMdaG06OMH/ajZEjPH4Co2iZIXhtaQJMyCxHQjSyyR7NCbWvtQpQ
- gw/wwr5eJ1E2qfMJnPJOiMvBPMmXMQNARZ8Q9gmD5/3uSb6OyMsH+yzf6xfDtb6dKhxmnG7q
- ufZFCTJuf0t4Xmc1sRxh9HF9BKm8BCh7GVJwhaC4e8VSAhS9CiYvPZ1RCXMAnFcjX64ELKPr
- 19QlC1TkU5YSikiRHTMummFzcRFOW6VFRe1bfYl0JkXd5N5O/EF1dEp1vixqI0+V3ddFPqIl
- PCdQTV89zQIH8PmFiNmXqQjhJfkwJO/4qTFvH63nJGR5TFskRGQiOFCI84OdvOdTFYLbn8Lt
- 3CZrk642Pywmh11O/w/ULqI3bAncxvcxlnD3QCsKX3foMtiBptX5HHJ8mnREm6zIsdfUnFTq
- QL1Fhst9w+nqWedA5pw7feSGUy96rtvJEvfpEyX2YM7/xJx2qlE4UCRwc4MBsvmyJcxQQMB4
- Uqn0O7UTblcKk9l9RXdjpYLbAEFQDxOdPCilTRYoUXrBgYMC4bTciaXP9t0YQfU5oNbdLEEh
- Qt2x8uGMACif9ljs177o140XABVdw6duT9/ysd06A5eSjXU9mI/mo3dHmVYXJaQ8bM4+Ayjb
- 1se9tqsAcBdHl64sxrep3nkRk7UifEUWZjh3ZfRdn+lyhPMMIN4/YdoZGSYuWFdi2BU/bmr7
- aRaCj20JofPkjBFfcLSZpyAT9es2jsF/To6bk1FIMXVNS5fgIPM4hhUeSX58jRYCH2T1rBYx
- tX6QcnL7JkG+l4YpRdvinOd7cC8+qdnfV+NNhqteKDk2eSDu0aneIy+qug63Rt4e8XLODT6C
- S2R/REb6C0NbId+mt/e861F1VCrF5z3O1+yoP1M6doFrPVKy4Rk8lsBjnGbpEvk4TnJzUf+T
- VEowSvzqNzr25GNlcTgnh64e/49qxnI5VrvmZHWxPCV/5xUvIyhYLnSVh+JisCfBzZg5Y3oz
- zFKKkRTHvVhkljFQ7XJcXqxPyuzYJlb1O48gs5CSz32dl7ttd1elAyl8q2EKHh5eq66pHQPy
- O8KPFDO/dUI7n95DAZr17Rjr6cdm3nyGOC4+9OyVyf2cu32XMH3eepSDUmwapwA6T+RklpZn
- UZKIHTWAkzDVO+RQ+pZ4dyj85aHR10fRPV2KYJz2n7youksYT+F8iKjn7fbl6AkhclpRGqSG
- 0/1TAstPfpYG8/9+OIEAiNfpvw8hGdUnB0q3zG3zHl5N7wTz991Vix6dNJh+p7Esw9CY62hk
- PylSoTjt2kmFek+P7tumb48Nnt29famOuGc4euxfpwYv7rnZ1NiH1OFWJdRm7aaE9IL4nF/3
- E+O/wELibubDtt7nZ8a6MlDV70EYNG8GIaWSch7qaNCg+QEbjpE5QMfXzSeCXHrZZxTIbstq
- /NuAD5Vm/7zOWK1GBNBJc2+Vo7IXX574i9MHJtpg1PAX1lcvYjgebJZhP7Jqt3GfQZh5qZWH
- YThkpbfqpMqmdVKkZOMvyjnJg41p5GEneaiaCgMUZOf3gY8w/XvCE7GXKWY1L8jp63JPUV77
- vxFteNmaZzr2d1UzwkK196nL3yzycHpR1y+EVPiQ89pQLXKo7+vL7O0TqvPdRR/znEDY2mme
- ZzofH1fuhwVUDSZEobhDL2kRqp72Ca2zrKaRwE1VVo2LW6cMH3eIjo/T6iwfup6qOBCpzTqz
- SrnYiCvU3rFwx78poFpRItRdw6LhLaAylm0zyYpe+9CXtVyf/Eat1hkllbb3in2ZVYNUQ4XL
- /tcU8W4T1mR5J6TwoVYr6fVapnC1tf9FdHyROQnn1rFtqTzFoSRH2dM2V54ZtttFUmU1dU7V
- ODtiu5pHvpmFDd1wxj9vW7U5p8P834Vfoe1opvsCF51MqADLAQ/SXoVzjkphHW/zvOWXCycp
- N+s2JZdr+mYk93fHL9Dde2O7CXFXHgjOWFRTkKz+6oIDeTqrOnw8/Tk5UzpPu/NVlHb7683w
- S7S5+8bAdUdywE3f11WwO0GQ7ZcgO8MWNzPDf9q7Xn1JdaxbT8Q78AS8ABqNxeKQOBwKhUKh
- MCgMBhODiMEgEBhERH+dLGr/dlUll69OV5/7Z3rPzL1nQiqEEJK11/4ThqTZsh5zOMa4dmx4
- yjDsJY9XDIhoUJsm+yBJwwYNNM0XiSsla9jB8EfWo5EDduP9QXlAiVVEyIIAmSzxY3DdoBFc
- mCU+NQU1mNfhViNMGpe7ylxF2CZpEOI7a4rebndysZF0LxrhbWjqbkJ9+vtZtkU0hVmw0+H6
- MzF7WBBn7ThbfI4UvdXMWJo3srzF1cgn+DpqVO2bzY9M9H6UBEC0jGCir7AMYFjQYwK7/QNo
- 2hWm/cRU5yK4YRPFUAcvn7S1XJj2i8fPalv1fHy5xVH6d4XzcBAceMvlMEHxiOHY8lyf/cpI
- 1KiT8YWEaIo8gcppJ5Qw7pYxmcoIu9rZZ4y+mnDT6/qKTft8JA67mh1fmXgcGfcmDS+MfuNG
- SK9b8Z1iScEr0JJ2K74C+sk25Ia3assImz2LZQ3rDViN+AW25ppFRb72LffYt8m7ir8rc5u8
- U8bQ7Rv/mmuilXuBhf6dK05HUJt49VGCXdOPC3kwN12y90blgocTzVkzZHSn8UwOvLuLV68f
- zb95usDzvCCDtfz+wyj0PdjizjmfpOelqMDjHHMTBomeJ2rOwrAWOx+oQ3ax7/lxzSa2SAM/
- TtPwtJI1cu5hZfQCelKR+n6cZQ/3wkRssvtzxi30E9NglOpFgA8LRsDyIGg8xYMEh2RDHWQ/
- b3RaHjxts9Q/0Z53gbGdwo4RREbxSzwvI0ZYQw0vbWZRxachV8k89IOkNn/Pie+X41bHvhfm
- +M3Saf/ASuymHfnUjq7pGwl+ip/UwsKNOj4ZvnFcy5emKzRqiBcEN+51BQfDur30gIGjme/F
- jCfc2iL2yEYiD6bIkT2A2Sdvfj2MXVO3/dAajqGaDyBCreUeP5YaK8DLQB343nPhjksg1bfo
- ujz0yClymY0KjWZEZUYgMteZdUtti4GT27K8iypx01rIKiRnz3oWdFOraKIh68SsHcGiWT2w
- db6drdvKACsez7Bg97FyfQI8nURYTaIMrgkOmrSgIZD1IO7wSuG+pzYpN0BhqWy/MqKamAyY
- F3XYM70+rKUdCH3LTrDx/eUFK79Dmnbdam2qf0QpbsDjRjWfLMcadfk3+YqWQjE9yoPX1deg
- y3deMlhOT/9hJUO3TwsR/yERWHiW7yQ4rDgHoJEEbjKkVR6T1u8oHIMDEt8AEir0nguHNApR
- GETZS6HHCvs0DM6fs8IkDHyP/xxhUxHtC0U7dGXqnbtPMiyHCwUB7YRnVaAdZ+EyVJHv4cfV
- sNxrVqF/3heFGucEYT0fh2zCAAyOTP2gxrKr//bvS+XWV0WWRnffuvkOV4K0wJbiBfEztvE0
- DDPYhgo9jc88nwqVaIvgBDZJd3fu04Wmo6xQiSZHTS9A4bNjCEARhHUD45/oQY9qvv6DwML6
- j/JmVq/liR8SS9tlYVSy+vKs3/0llHLAXaoMkaisCY5+5zbzK4LjjO/axior+wXXMSkA/s5/
- ecYxXsOiAV+XyMOcaXJtrFdlMXfG+Dk3kf7M6DLP6+Mx8kYpBXCcZg35wj3gG2C4VLu44H3w
- oAC+SZHX1psC/JQuoPq0bXxnmlUiFeuJm+CAWsUJHTl2bdvkBtEXtCiKCh5Es+aBOMFhiRHg
- CxO0gpfAKJmYVez+2EuO5U2jwOSGqDMiOBZ2L2zzSBwFfMz/Rr117irCe16claMEnu+iMIye
- JAxSQPNj6esi8slPr+gnBoBZNBOmE7wZw1JwX2LzDPNmaK+esdHtegypR35l3COjLlPylDN4
- GDSqe9oTs4atAvtrmLX9aaPowfWg3Ng6yGBS2Np/cSqBB1VN+r+b4MDWzpxWLgiOsK5TwPpN
- D0uQGkQ0EleSl6mPiUoowfQZ8R0MXqN9TnCopfV14XBZH8hynWpdPxtPohBKqvZpAovsHnz3
- Jq2WxkxqwWZ4fZgFMb5hKVAm8KetYzi/qSp8iBnp4Z3D/a4xhSBgPV5s2kHeW/smNEpOFivB
- ccx5HBetYJTzoEtIj/1/eHEHUd4N0zS0evp72YpZh/43w9DmHuOzQqgY3TB0dRKl4sB70Xax
- bhrhcwpwjBUpSMpxGsskAIc7NLo1P636fjg9XPy0n6YqoR/yu/d9k+n6xWS6mp/vfT/Hh0DS
- 6VjkZ/Px5JqkJW/6rozv8XHN0BlEZZZ0qsPvhZeFzvewRkJ3ReXXYXGMAOrDLN+2fWt88tpx
- Goc2i9Np145j6FLfd+OMxyGWfC+8k5os70wx2FiA2qVLztEw0x4+wGqucHWHPpx222K854z6
- VIV4v7DfJHgjcCPq+j4Pnjz/Dz3LrgmOc8Su5avTdZdyXfWUKMS2zpwM2ZsEEP/Ss48mD5n+
- 9KgkWeLdwixL6mknKMYXPUJCALnkJR8Wg9Kwoc8iINII2C7O60Wx+UlO1DyG1CZbn3pJOxok
- YJ5QIW9FF3tJB0Y1NB4TaiwjPAjGMzWTZBnuPrTHOo0vgmw+tpveovbnvQrvlo07zDyj+tHj
- pg6RXQ4cm+OtHbIuy7Kqyiw0n0xeVVVZFvWw4Gqhi+PpeMS7Dpdg1ydAUXuYohMjOPZ1AcVj
- F6VpCNguZKMxYr/sssuMQQtu4eG4rYUH5yDLr4DKaoMVjm1dd+WqU4l1lULM8ngB99l4KGFv
- Bys84To72PiW8vWxXL7APAUdO8o1vDDSDbNyAx4rqvls+VsEx1Tr59CBwWADYQ/Dp/ol6PKd
- l5A7JTJfQC8XsBsJ8o8YTEhru2nFb4YGP/w+gsOCc14c5KfaY70qJ1mH3GGWA5KGAAlHKZ8v
- pBuBFAijqh2EGCtjGYFf0jR2iY+IEjsKsqKdXyykfcSCfH6wv41GA6ImL/PIB1x5D9v8jkIm
- cwITDgl1I63H4SSvm8W9/n+o3AqBXHDXWvl9gsMlsrrdghk5L6KGjwzRDH6U1r047qZI6KdB
- 1oytVsDaaYR+HCTVogA1EOCHKCM+ChCaNPtThmpoL2OVt1rt9T3NELR5Nf7Y5zLP86LIkwD9
- KYoiz7Oqk5bcivbsihtZaPmwgOB4SodROggOJVsfYWxUZBxASDRjCvueJjDaM7+OVxz3yp3u
- 8zCNfR6fMQKM4PCrfhq7wmfOcpxV4Qm3x8K7MannnZz8b2E+znNfxiw6Zp/6Hk53/G+1dCA4
- dWezkjMUYE+LLMufJMvAej7wI3Vxj9r1snbmZgqdl+igHS78eW0x5pV6lAt05nyC80s2bOfI
- B6XhQ+obCml8mISGZDHfQrJeERwo4QQHF5hWXsrD6WDtUwoMzbtG427pEpq6JjhoibkmOIJp
- NbGvzVBpoNqOVQQoQJaWdcjuFokQl0yfs+3VLAPCQn+YPuh0JD+/qs8luKsnakKQJQQv/V2C
- gz407IJjfr5uMtPdsvWYQ7NuLE2E/xuRsw/7LuDdw0RBH+PfC6lAUEGtfVOygdZq6eonRG1y
- 6DQbVsbeueAczI4N5cqUb0PGJwlk6zO2n62Zd86ZM6f9pvM878twEm1qIiJ47VM0S8sgg6QU
- Qa3qEBQqn7FEcMB1GfRCs9lckyjKL/cJSCHGJ9/c9yJvLDwhAjGcw2IfAfKNErhg9pFk0B6l
- PGCHjN7subgDBRQPqEZY1aFLbL13TsKTuynEPlchaSxzkxBljRKoYaW+3UZudDTHfDMJz3sv
- oqtSCv6ydY9vSUk7TOs9EWlXJP59d24GsSyyzUOk0Pqq0K13Xtae9wmKsijy4i55llfysOUe
- XjfFVxJtiJ4CPz+e9DFLlq6jCu4Ry/sU3g0Jap2aum3K5KxtYt82s8VQiNmo8ZK+hahTok1f
- ZUh98BvcPI6oCi8dzuRcZnnUq6SfaFS29KGxN2VpCA9Ehe3MJgAYHITgplGz4CXSBqbopv9v
- htTTqMr3Pe90R/J1R6NK4EOjLlTimDSLhno+MgUycX4CuNDnkY3g2DKnayc2R2aWV2udhud4
- NAKosYwM45pnZv6Xi+K/8uppyjB6RKCb+77WCYq2CE98iThi9rDBsMyprR1K5ZhX5PdsBxvf
- Vn48l2PZh+ODKgNL8jUX4LGjmk+Vv09w8BaKaeda4tegy3deou8tuc+8rJMP9l1f43nZJPdF
- fsIPv5PgsOAc2pGPR5fb0zixNAaOl/3sBiTfWYiUk/3P0rZOEbK0mVTBcgBW360oyIp2frGQ
- xtmCfB7fQh2y83HWzqTKWt/CNr+j0GhqeV5wIe0Y3TA7I4xC8D9yrf8fKrdDIDuus1e+JDiu
- 88AtfRHFMWwiYQJ/YO9nCVyYzik4IICFzGVcZuO9MZnMndlgiMy4XbrUwyoM5OclzdRlLN0G
- 218nuhH8Wzy8PPIvqvqF0uH4nh9o0Z/0/U/vNf8WZb55dq1c2xtCNMmDY3rw4JjVBcFxgN24
- JeKwRjaNsYeZjTd3i+t+HPrCuAQ1/etxA2uG+tDugFQegxKp7TpiaXIQb0yxHvucs0kvO858
- 2B01LcebebHu4fF0eRmHV+nHeXuJnxqrDDsjTV8KkN7JhwJEz6R5tJY8fcxr2lKzzasF/GhU
- lGUBmBXVTOMikgiE1Bc9OGgb5mIrZ+0DZDdtnUd4Na4cHNcEhw8fPr+Vh/vWFAKDOA4t5bzP
- JaAA/WQ69Uk/rQtwH+R14vLIuKWFNvxVdYt871f1vbIfRywCSOrJ5NhXMSBNTySUm+B4TTL6
- aIWo5q2LH2Y4bIB1W5iQcgBBv25LvERusoM86XWHKJCVjUQtLTkTuTXJNQX7/nGCAzlH0dUw
- DAMPL4svg1iuMXRj7qP/XMY84OCgxHzDG+TyDLbQGv1wTWiy8bvTe3EQHOG97fn1K+PtkK8B
- H0D3vU6vPcjWGfZ4cA+LfQR4fUS9+egsYmH4g9AXZ9mVwcmav/feA/tMTIrJAR8UXRX9rNCU
- IdIeQSSAQwrqhbJuJ92+NA/ufmv3xI9PRXj/upVrWvJ8Y1AgkSkNmW66pmQpIb1y+HqQs+vW
- pGvpmcvE8+Npd0eh8iQvxxBghyJcgX0qKsZpHMVK5RToB9Y7aiTsZlEYwSHaQJQojPK7F62i
- FQO25/3HSqryq6x94qfdYHxmFjRgSIg+8eJuhUaN4CoQHOI4uYOyN2+APYV6FLOd+UAdHITg
- pre416463i3tJ+MjovXbATd9U4ite6GVfsq6rmYbV/u6yJnOdniD4EBra5PopO+M4Dj6Ii3a
- 2dWcufP6Uw6duqoOPAqR02NIACwox7GgAKhjO8+N2Xo9yPFMWaWxu2l5qaPOl760MfYdetgD
- Xrq2diBT7pFaawcb31ye3ctZBvooK8oiI0jgAiRW9PIN5Zd/A2Bz4oZ7cHwNunznpZejfD2e
- UhE/hDE87eTDD91Q5/OXbDgHgK0axAy3CPC8aGQ6zkQYesib3Q5Ivq0QWR7grh4iJoYL/Out
- KMiKdn6p8B2Co/D1tk4WJwTXv4VtfkfhMTfBqRKHxss+5Nox1valz/RMHmBUHpwQ6FPlVghk
- x3W2ytcEByUkWdbD6QNZZllsIEOawaEgy7O0QJQUicjDQqxd8nyggDlbO93Mtu0X4uS3sqGO
- QI7iFpjcHA7SisnNLBgdWG/e3t25bMsil2WRkrtTIokpdkciCLLBlYPjMBtJeTxFW1ykalOl
- fw6RKKNX6/4LzbQRwQEuMKxmK8GBq6CWubpeCEWHMMHjgAQAIPNo73SL2sTQsJTySdWN66EY
- /cGF81xqEUOZUXx1kFfdvO6PbtJpvyg2m7P97G220DlVxYhUZP0GBcYLI/N9nquh363ETDMP
- T3h9V9HLIfbHsmwP9XEjysnESUQXf889WhHKRDKXuuWvERwU4Lr12GiQ1MbWJXpkcoxPVgwd
- IzhYQi9Kz2Hps7hHjRJpwsRdf+TDCHdBTNdnGVM+vV9GZucDi+Q7+ExYs77PZzhDn0gjiqAV
- SDjszOHr5nWbmooAip/biwRgN0KJW52DMpOtv4HgKHyMHiZwwt8jLYMSiQZ2+Fx43fZEkaRs
- Vu/kiAEvmM2twMCDo98sHhxUhz2s04MjTNOA1kBrNf4h8Dbd90IY3fGQPnB2DYtrBKxq+b4t
- Q313jtjvmjYnOKaDd5ilx46KDEwip5bgu3GQHwel/BzvJAUO4KQ+m3nNaLt9isGPK8uJwlc5
- ODaObKDA8rX2YweVs1uzQkSO+K6M1e60X3iPknlwkIjwJdqflIogSeElipMC1C6HfhjHLvH0
- yxnGoR/EfgYGB5WgiOWcrP2ONORApV7Vd/BKMetOua4dsv/AUiFIBDSbrU48Qw2beRDkqzO1
- NnwcnkEIoHC7rFVwy4X6sfdaC88zDzd9V5QIkartV4TUHgCelwCoKfc5wfGGYAwnNoZIpw/d
- 3SwhaTu/Gp/gwmlceBqdzSZpD0udlXnbvaTdXVzt0BGScJ3Q4gIbf1e5kjX0PSPBzYZSXIDH
- hWo+W/4GwTHBgng85uDw+/WL0OU7LzHEeCvaLguM95DYeTUk9Xz+oRvqfPiSHefw8QRT1mwv
- LMlUIfLODki+q9CoMIRJ1BhY0hpaURChnU8WvkdwYAFBOdDFO9jmdxRynb6I4ycjx33CYg5M
- +IkLAn2q3A6B7LjOXvma4ICOirXDLWaznH+oKX+MBkS646DsenNGShIaaoVhnoqcINpY93rb
- RWzet2HWb0FaTbMUQ+XfXey2VyiDyGp+AOTlmWS7BYHBxwHHKLwCpqCAGsC4N6RwvwWtWMY6
- ucG/yMgqhq6twrsrbD+tZP41ThNdb6IiB7GdlqVYR5fpPMyFbocTNDTdsSShfnzWRwCYHi4G
- 7MJmlPNQ8RAVSqDFjefnXhjlo1xEXwU3omOOviyafprFmZ2gEiieIiImDkF/kwAxj20FY+B1
- klEQFlr8JK8nuTkSHVNuHgPysOetLVxsX88ZNVb8hoNRHKtB2aGHvm9rkLChUJiiiL3vZymn
- wcRLJv1D/erUTkIerh9kXd+1kG7cX44+YT4CaL+bpRTTUJwudr96iooC2MLG+dKlbphZ+0qK
- CedLj2C+HprC5CcSjfrs5e0ol7krzkilzR6wZq+PT4nXx0aOT16Xe1HV9mKep95AF6cHB81t
- L2tG7UVf4PCT4SrPvDSfE217qonYgUQsczg7riieHX04xyeuBnrp+LTZzsSXtWZRHyc4WjO5
- +3mRYw0ljkUtIWKrCenDR9aMIO2FXOaxKiqpTqLTi4p5XXswdsVIUYth1szLIsVYZWkn2QEx
- 1JqfdON4D1xzERw5zRMzl55zcKgzUCsRO1X7IsGBe81wTiv7dRXAlO2iHMPCR2DBCFgfpCuy
- shvlusHZNW4lCDIvKYfRHNWOhJpRIRbJ2yHu2zxiy9OzU9gaCEfShxEkFRaTMn0jQhmPwLUU
- TPO0neQsxDSxTOZ7eZ1klOr8ZuG35qLmPEqGVb1HcODg55tf1hrOVnXVnXkv5rZK4XmFaP9u
- lPckWbckL7IkTrIijym3H4Tr4U4mqI49cNl2oSOl6w4OiU2Zmn1b/jWpMORG1T+mELjcJvsy
- wy3OddO0Htb9OI5tbNw3dcku9UghRxQOrKJ17H2hnKzTsoxNhp18ZJ0fOcHxy7INmaeVnKPw
- vGLcLKxWWNOxaNyK+1IHvr0lUvxRENp1O6fFOKQ57AIbf1d5l3rMTHWYZ8kNJIAM2yPgkesq
- 7oDHhWo+W/7uKSpx0QzD0NZF6NEJo1+ELt93Cb0CuzGsQNtYuhup7jnUMfuGWc5dyX/ohjqf
- v+QiOHw9UeBRBgESaPphmJZ16c/UQnZA8m2Fp0t1O63LlNOB/M24rIsYuyzJxcFQ0Lyucqry
- Sio72vnFwieCY3ATHIArSdkvqygiD3DlLWzzOwqfDv6nBIsQWWHUC7nO9BMXBPpQuR0C2XGd
- o/JncnCcJycbwp7TDTzPLSRMSrHT9S03+/P9LhQnGY8bvBljdlB3jsSQHjt5CLgck4nM8jDj
- X8jrgYVEWARkXrbgQu/xV2od6Nn8pNm5CRfC9Cuk1uOCNuHOShLEJfl3WM67fjkePMpbbnSG
- TekONRSz3b0cBoFIYxIv6uTxkhDEL4eFlNiQqL6l9YhYcaG0izzxGEAxTFK986Z6s4UbNwrZ
- azVeLHJqqnq6PyxPT82da/j4I3twKzZyds4jnw9FM228PmLU22lh+rzlhHmU8zP/Le3j3ZT9
- fk6JwE5wPDZ1CHyDL7dYexxNZumSX/D2SWSTgEp4akpJ+DvQYfIjP6cdmXF+sD67z3WHJCut
- Hry+EjFUONlGvLoXNngdtl9hDF2H24Ot82zHnXSpj/nA+eDwvvxFYGF4EDhbHKkPLrdGeG/a
- zkmVCS6Rb9SHCA6cZAHxPCI4JvBcFClG+Hubauo1vdm5zay+VEOVUCHSpOPrq+VBrYW4FhqN
- k502zSP12PHAoTjYJ8xqHrI1oCtl1egqMBnaBzmL1c9xL1O/SdE1nk9xtA+LdQReGq8iPjcz
- 6NRjmfCle27Sl3YgG2YLcwhCf2iKysR4pq5sHm4sCglOB2Du+DGQgS1ZAy0dV3r7mqLnv1vo
- jb8pbuepOWeLBUYV6PZBMEk20Q3yQS/uMfGvBgqLoA6726YqIm3EJZtoQeUj630zrW8ci66O
- r/hO0E0hPm76htgdKr88K7DyQCxRvdceHGqd2o5o7StRh3IcLb92CQd+tPDiuWx1oPVBwvG4
- bge4jj7GvwYbf1c5P5sPz8gFUNkCSHwNeFyo5qPlwBvXf3NXAvILbui7/hJ0+eZL69jU4/qQ
- Y6bqMPylr4F+Ggf2Nm1Q5/OX7FjLDvDwpSc5IQTNmx12QPJthXpIs4BK415MVcxhfCKOVxQU
- T4cd7fxiIYYoH3cOaVCCAcTfGOM2C6mXRS9/vIttPl/IRR0v6SdjU/PlJxYI9MFyGwSy4zp7
- ZRAc3aYQCmq0Rx8Ex4cFebn6F+pk245HB4BtRQnzmiW3WeeJ67Q9r5mxtX3VQNCTO4lLYPN/
- DRzFc/yKHLt+UppVV6Lu9S2XNi30FNctWepj4NfN1Z3ZJFOWP75bOBeelt28rOsi+6YI4Lbz
- q69gWzGmv0fU2f77TuBqaxIfBopvlmMzs/u6y3zaTIZV8C6PKwfOf2e6oj8r+vMPEbiDmThg
- QWXGL7LQZ4LGoU9R9x8RdbgWCmXWBGUZMzar2bp62JrQdR2fwH4/TAAZE8EEXcs+uM7k/vz3
- xafG6TCy46GUZabCCx35GtyT0zEaPG3Bb1syZOoh2eqFgIXnCUQ5ywDGua/psO1/ulhsKnCB
- 9NLl93y/GCiusftxdTFSfwSf2LiqfQNWePjQkB6rGLU10uXBsQ0e/Gt+UUwPfnMdBIYE7bwd
- +9JkCSKY/sWiVnMaRPPjvygEXb7/0qVsUizHHfavq7PNb7j0NvogPcUOSL6zEEIqoquHENlr
- FXo4rGjnc4VvrVh4G29gm99e6JKh7VZ7FCuHQJ8v5xDIievclW/asM/ltyFRUWW/aT9Yx6ZA
- UutDVnk5bV9f7sfxIiYVn80fORbBsoR+v+xDlT1QtUULWP+fFO/u7v6vmXz7XJdF1c0//hdE
- LU1ZlEVe9ZIVHsbMuLZlUZRF2YyX765uHqWb/mHPuXG3B8pFcikUi/H9i4R3rc/vObwx/3ky
- m7BHihC8EPjXeLYTB1gGEJyu/75883RlSUa5HFOS1Mfnv985QtIybr8CiPsjv/KJYSgV/ul4
- y0ZKcfw7YI+oudMh8rb8OwXR3EYQc/1H/sh/V7D9we/jj1jl3wKB2KZzXfl2HPuj/FHh/8i/
- RKBF/g/M12noEcjzR/7DcvN8Jp4XVf84dWadh74z2ixFv11LUzeT/FtgxdbXzbRddFQOTTsu
- P/55sk5dXTe9+DIztORBUM/Hv3K6qmPFMbH/ZPkjau3qZv7yizq2WYh5+Rc5yiD16SRmuR3/
- fiuVnIWQf6i8P/Kfl2NbhBDSbQX9I/8eCES47rry/wG1FRmeM7jnagAAAABJRU5ErkJggg=='
- 	) base64Decoded asByteArray readStream
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBookDark12Data (in category 'dejaVu font data') -----
- dejaVuSansBookDark12Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Book Dark 12. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 12 15 4 0 255 16 0 0 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 15 21 28 41 51 66 78 82 88 94 102 115 120 126 131 136 146 156 166 176 186 196 206 216 226 236 241 246 259 272 285 293 309 320 331 342 354 364 373 385 397 402 407 417 426 440 452 465 475 488 499 509 519 531 542 558 569 579 590 596 601 607 620 628 636 646 656 665 675 685 691 701 711 715 719 728 732 748 758 768 778 788 795 803 809 819 828 841 850 859 867 877 882 892 905 905 918 926 939 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 952 957 963 973 983 993 1003 1008 1016 1024 1040 1048 1058 1071 1077 1093 1101 1109 1122 1128 1134 1142 1152 1162 1167 1175 1181 1189 1199 1215 1231 1247 1255 1266 1277 1288 1299 1310 1321 1337 1348 1358 1368 1378 1388 1393 1398 1403 1408 1420 1432 1445 1458 1471 1484 1497 1510 1523 1535 1547 1559 1571 1581 1591 1601 1611 1621 1631 1641 1651 1661 1677 1686 1696 1706 1716 
 1726 1730 1734 1739 1744 1754 1764 1774 1784 1794 1804 1814 1827 1837 1847 1857 1867 1877 1886 1896 1905
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBookDark12Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBookDark14Data (in category 'dejaVu font data') -----
- dejaVuSansBookDark14Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Book Dark 14. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 14 18 4 0 255 19 0 0 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 17 25 34 50 62 80 95 100 107 114 124 140 146 153 159 165 177 189 201 213 225 237 249 261 273 285 291 297 313 329 345 355 374 387 400 413 428 440 451 466 480 486 492 504 515 531 545 560 571 586 599 611 623 637 650 669 682 694 707 714 720 727 743 753 763 775 787 797 809 821 828 840 852 857 862 873 878 897 909 921 933 945 953 963 970 982 993 1009 1020 1031 1041 1053 1059 1071 1087 1087 1103 1113 1129 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1145 1151 1159 1171 1183 1195 1207 1213 1223 1233 1252 1261 1273 1289 1296 1315 1325 1335 1351 1359 1367 1377 1389 1401 1407 1417 1425 1434 1446 1464 1482 1500 1510 1523 1536 1549 1562 1575 1588 1607 1620 1632 1644 1656 1668 1674 1680 1686 1692 1707 1721 1736 1751 1766 1781 1796 1812 1827 1841 1855 1869 1883 1895 1906 1918 1930 1
 942 1954 1966 1978 1990 2009 2019 2031 2043 2055 2067 2072 2077 2083 2089 2101 2113 2125 2137 2149 2161 2173 2189 2201 2213 2225 2237 2249 2260 2272 2283
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBookDark14Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBookDark17Data (in category 'dejaVu font data') -----
- dejaVuSansBookDark17Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Book Dark 17. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 17 21 5 0 255 23 0 0 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 21 30 41 60 75 97 115 121 130 139 151 170 177 185 192 200 215 230 245 260 275 290 305 320 335 350 358 366 385 404 423 435 458 474 490 506 524 539 552 570 587 594 600 615 628 648 665 683 697 715 731 746 760 777 793 816 832 846 862 871 879 888 907 919 931 945 960 973 988 1002 1010 1025 1040 1046 1052 1065 1071 1093 1108 1122 1137 1152 1161 1173 1182 1197 1211 1230 1244 1258 1270 1285 1293 1308 1327 1327 1346 1358 1377 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1396 1403 1412 1427 1442 1457 1472 1480 1492 1504 1527 1538 1552 1571 1579 1602 1614 1626 1645 1654 1663 1675 1690 1705 1712 1724 1733 1744 1758 1780 1802 1824 1836 1852 1868 1884 1900 1916 1932 1954 1970 1985 2000 2015 2030 2037 2044 2051 2058 2076 2093 2111 2129 2147 2165 2183 2202 2220 2237 2254 2271 2288 23
 02 2316 2330 2344 2358 2372 2386 2400 2414 2437 2450 2464 2478 2492 2506 2512 2518 2526 2533 2547 2562 2576 2590 2604 2618 2632 2651 2665 2680 2695 2710 2725 2739 2754 2768
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBookDark17Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBookDark20Data (in category 'dejaVu font data') -----
- dejaVuSansBookDark20Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Book Dark 20. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 20 25 6 0 255 27 0 0 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 25 36 48 71 88 114 135 142 153 164 178 201 210 220 229 238 255 272 289 306 323 340 357 374 391 408 417 426 449 472 495 509 536 554 573 592 613 630 646 667 687 695 702 720 735 758 778 799 815 836 855 872 889 909 927 954 972 989 1007 1018 1027 1038 1061 1075 1089 1106 1123 1138 1155 1172 1182 1199 1216 1224 1232 1248 1256 1282 1299 1316 1333 1350 1361 1375 1386 1403 1419 1441 1457 1473 1487 1504 1513 1530 1553 1553 1576 1590 1613 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1636 1645 1656 1673 1690 1707 1724 1733 1747 1761 1788 1801 1818 1841 1851 1878 1892 1906 1929 1940 1951 1965 1982 1999 2008 2022 2033 2046 2063 2089 2115 2141 2155 2173 2191 2209 2227 2245 2263 2289 2308 2325 2342 2359 2376 2384 2392 2400 2408 2429 2449 2470 2491 2512 2533 2554 2577 2598 2618 2638 
 2658 2678 2695 2711 2728 2745 2762 2779 2796 2813 2830 2857 2872 2889 2906 2923 2940 2948 2956 2965 2973 2990 3007 3024 3041 3058 3075 3092 3115 3132 3149 3166 3183 3200 3216 3233 3249
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBookDark20Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBookDark7Data (in category 'dejaVu font data') -----
- dejaVuSansBookDark7Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Book Dark 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 7 8 2 0 255 9 0 0 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 9 13 18 26 32 41 49 52 56 60 65 73 76 80 83 87 93 99 105 111 117 123 129 135 141 147 151 155 163 171 179 184 193 200 207 214 221 227 233 240 247 250 253 259 265 273 280 288 294 302 309 315 321 328 335 344 351 357 364 368 372 376 384 389 394 400 406 411 417 423 427 433 439 442 445 451 454 463 469 475 481 487 491 496 500 506 512 520 526 532 537 543 547 553 561 561 569 574 582 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 590 593 597 603 609 615 621 625 630 635 644 649 655 663 667 676 681 686 694 698 702 707 713 719 722 727 731 736 742 751 760 769 774 781 788 795 802 809 816 825 832 838 844 850 856 859 862 865 868 875 882 890 898 906 914 922 930 938 945 952 959 966 972 978 984 990 996 1002 1008 1014 1020 1029 1034 1040 1046 1052 1058 1061 1064 1067 1070 1076 1082 1088 1094 1100 1106 1112 1120 1126 1132 1138 1144 1150 1156 1162 1168
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBookDark7Form (in category 'dejaVu font data') -----
- dejaVuSansBookDark7Form
- 	<generated>
- 	" Form data for DejaVu Sans Book Dark 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^Form fromBinaryStream: (
- 'iVBORw0KGgoAAAANSUhEUgAABJAAAAAKCAYAAADrYqQfAAAABGdBTUEAALGPC/xhBQAAACBj
- SFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAAABmJLR0QA/wD/AP+g
- vaeTAAAAB3RJTUUH4AYPCTYDEnevlAAAMbBJREFUeNrtfX18k+W5/1eIJECl6QrnPBSrgQGm
- vEkAkdBxoGUVW1RGYDIDyloYZ7ToZK1MF4YvBWVWjkxa5Wg7PVomhxMUnUFFw4saQI6lk41G
- kSaCNYGuJKzUkwSC398fT54nefJSCsJw+3l9Pvn06f1+X/fb977u675u8O9MPp+PgXD4kuYR
- DgfY1NREkuxwu+hyHf97V/M7+o6+o+/oolOgzcOmpiY2NTUn9Q/5fBH/pgvOw9/SQLPZTPvB
- 1nOGDfl8dLnc551HOBygy+Xq0log1sd73mWIzSPV94WW6Tu6MGqO67tNTU30tAVIRtdtl7vj
- chfzn4JcLhcDAbFP/yORz+eTf5eaWg/aaTab2dDiv9zV/lbSgS3V1OnGssHvT/Db96yFukFT
- 6OpQjtdWt50j9CN4xx0mGibcpfBr2WFlaWkpZ+TlsdC0VDHXth60My+vgKufrGRe3l30hUKy
- X1ubgwLSOX+hicKg2y96Pe+/2UjjrSsS3Itv0LOweK3C7dUHSmiYUMQCg4Hla+2ye02Zmab5
- D3BRYSEt63Yq+Oc40sad6yzU6UR+yfwZexdzjVO5erVY53NR60E7S0tLeetkI/OK7knwD4cD
- vGWQwMJF65PGD4V8nJQl0LxsQ1L/NbPyaPhBAUfr9bQ2tiT4P1ZaypKSEur1N9B2IHFNXjff
- RNP8Cs7Ky2P1luQY5VwUCATkb4/Ho/D7qLaSOt1YNrW3J8TbtqaUQtakpP1xmG4YTaZCGn6w
- OMEv1ziVjz5qYV7eXYr+GAh4OEWnY/njb3Sp3NL6FYtVAgEPF5eUsN7uTBrH729gSUkJHc42
- 2a2jw8Wy0lLaPlTy90ObjTbbh9zvcNB1PFpHt8tFn8+XgF3KjHqq+/Shus9YemJ4eqG0pqyU
- lkc3pqz7AyUlrH5xr8L9sdJSVj75tsKtzeOhx9MWKbc4xitKSli1/t1ou0Tm5b9sqmVJSQV9
- oRBdLjfb2jzyfr65qYkul8iHcCBab/+hBlqtr/LQxw10OES+h0K+hDxiSWqn2k37FHVaVlqa
- UKcjexy02bZxv8PBho+jY+S4y0VPm1ivb4ohJX7G806iUMjHe0pKWL1xryKOJUl5j7tcMr+T
- leuh0lJWPvm6mG4neD7g8dDlctPtcsmYDe/VVlKv19NgMNBgMFCv17Oy9r2Ewk7IUNNUsYkk
- 2dJoZT91NsvKzNTfsEgR1u9v4A36EbQftNOoH5Ewydw+Qs/ytdEB+VFtJTUAAQ0t694kST5y
- m4EQChTxDmysZiZAAESaQTEgWhqtzESmPOGtnm0g0saTJPc8U05AoKOtTWZmIODhVONUegKB
- iy5cCocDLNJpaap4ieFwgMWT9GKZoaJ5aQ1JcdIanSUQAPWTyuS478m8AIE0llduJklue6w0
- 4iamY1r4qCLPj14U45kt1hh+QI4jjIu20YuW0mgeET5aLeaY9EEgk/UfHGV7exNzs7Wyu6Fg
- MQPhcJy7hqUPvXhReXihtG6xiapIWdUZ1ytAz+FtNpoKC6nX62k0TmZ1zZaE+GuLCwmks3ab
- W3bzHrBRUEV5o84YSuuOT2X/lh1WDs1Qy/5aYTwbWvy0P14ulwUAdUNuZL2tgSQT/IA01n9w
- NCEvIF3u01setTAzxk+bLebz1qoSqntdL4+How31TI/Ei/WLHcOx7h0dLo7PBJGZS+8BGzOR
- zvoPjir4IpU3747HZLfbhwsEBFobW2T/wkVrY8oQHY9OWz11adGyG34QBYfxddYNK2STt/0C
- 4hXIm4C2Iw5e3y/aJsgcT08gwHSpDdVqmf/C6GJaLWbFInu0oZ6CMI6ujg5Oy1JTn3+/XO+O
- DhdHakBTxUuclKFm3gJxTNvXllOFNBk03T9NT22OmYc2V4nub4nur64oISDQdtjLTIAlK14l
- KS5g49NB3ZR7E8ajShUdk5sqTGK5B91EXyjE8RlaBYjduc7CNBUIVY4CSDVvqWY6QO2QGV1a
- 3IrHCYRmZAIYi6eXlxYSGHzeAMW9r5aAirW73CnDhMMBTstWJ8yTXS2DmAdYvaM5yXdi3u59
- tVQBnZbp20aO56tYWFis2Gx9W2nVTKPYd6+7hb5QiIGAhzkA8xbXkRTXRZ1GXOMqX/zovNM/
- 3z5OinhleB+1Ym67WNR60E6LZV2Cm1hHEGkjOx035hwt9fm/JBmLwURcsdRsZtXzDrkO18tr
- UCZtB7zs6HBRBw2rX6ymBjrFOH53fRWH6HTU6/Ui3quJgtSWRisHCQIz+qgpXHfLJRGmvru+
- iiMieet0QxT5BwIeGtKV+CQcDnD2KJ04z4+9o0t53DfFQLVaTXWfoXQcaeP9NxupzcigWp0t
- Y1JpLteOmd9pWoGAh3dMMFCr1VKjApFu6NJ8t+JWsb9LuMx7wCa3vVb3w07TiI9LknUL8oi0
- 8fJY70qYZPWOD9MZPbfYRFVk7Tkfv5d+YSJiMEC8n1qdldRvw1Jz0nihkI/jI1jAOGdVQjxp
- blGr1Yq1s2TVqyTPjdPUanVknRWxWGfuGqjYS62O5JXO2l1u2h8vZy91L9G9V9R925pSCsIk
- egIBbltTSm3fXHoCAe55ppzavrn0hUI88Ew5tRm5DITDidj92tHypnbbY6VUQUXzUlH40/Kp
- NQXOUiXgJaU/UvoP6SvhelVS/5wYf+PU4vPyPxcpy6ehYayBwAA6jrR1itHO5Yc0g1yOo854
- v/HyHNfyqZVZEb9YbBYK+WRsJmFk66fK/ulvaeBgTZS3seuJ5bZoPeL79GQBxIACBZ8W54pz
- HdLHy3Xq6HAxRxXljYRRAgEPBwMsLL6dmjhMM3+UjnkzCthXm3NOHNcV2rnOQgCsfPG9BL9H
- ktRRxLpIGM/mwaB6+DTmqKJr/4ZlZgJprN3mVszLOlV0zKvVw1m5tJDq7JkkybIxWgIqCn21
- NEyJClPNOdE9q4TPY/NINl9JeDdWMLnmrrxIOjq5XoGAhyNj2tn0wCY5/JxsNQuXVvJ6dS9W
- 2Q59Y36L/NOwesuBBL9FEwRClaMo7/olhZFyCbS7o4e/Zh2oHp7HHK02oVxV84wyZiA7x/Pz
- hqqpHprHHA1o/PfnSJJ46RcmGm+9ny6Xiy6Xiw/NykuQXgcCHuaowMKlL5AUB6gG6bx9XiGF
- 6+Ypwh56t4pq9fXcta+WavVweWC0uu1yZwBA9XAx3vwhWhruWM/6xXlUD5rHlhYrNTEDRKLf
- FOiItFz6Qj7abDbFgBPLI8YJhXw0aMDCpS9HG1wVbeh7c3VEWib7qPtQSFcKVwIBDw0ayIKy
- CyHvYRvTI2V5a5U4gCzP7owMsEzaDntl6erg9CgfSPKNynKWLFxFn8/Hhbk6Ajn0BAL0f9wg
- 1tnn44o5RgI6ueNIZY4FEu5dteyjHkTHfmekXY/L7hqAhqL7GAr5aLfbGQiHZa0Gl8tF8ygt
- oRKBrbhZFTvXa4+Vypuu1bMN4ib4gFeeOJKdUHWFDmyzsba2a/xu9zaxuro6JfBaPddMy6Nb
- +OluK9MBmh8R+fFaRACn1eXSZrOx+GYRbOTdtUbZ9pHFy1BkietbKlbWvk7nHgdHpoHqoWKb
- yZO6ajDtB1vZ3tzEfL2eVbZDEd7p6Njv5O43rRHgmE7r7hbZz+74SNYWCYTD0bxqNincm9+q
- pgqgdkgRPYEAj+x30KjIJ0exeEpjIdYvdgyL7iMZCAc4OTM6QcbGjSVZoBHpFy2NVqZFFrL6
- D47GCDx0bPD7Fem0tzeJPNLksKHFzzceLxcFAtMfjOPv23y9RhSEFi594bzi7XixmmkxG9EH
- p+lF/h5009vcxKqqKnoC4unQRw47dQCNc1ZE+vzxBB6K42coXR0dItiOGW+iQDqN1sYW3j1O
- IISimDxBY/E6hsMB5qaB+mliWWfoQGQWRDZ10TqI40hMW8xHoONIW4yWURN377BSAAhhMn2h
- EF9eWkhtzny5be4eJ1A7aqGivY466+Xyk+LcKwDUjc2lAFCYoBT6J6NQyMflFoviZEzS0JFO
- jUiKvFONpCfQlvTkwh05/YhPQ+xDyr7mdrnockcF+oGAh8PVvVj5ulMRXxoXXSlD7Amm9J2q
- nydzD7R55DSlsifwKsWpjahFkQigY9PsrF6xbSGFD8WdNF6oAO9y0PwcLXUFv4nyIbI2S7hC
- 4oNBEx3LXaUL7eMFQhSTlD722kWtr3NTJfUjlNoSq2cbCNVgNrS0sKGhgYFwmDueq2b95mgf
- 31xVRdt73shck06b18v3VpXIwDBe8ObeJQpErZ+20NvU1OmmzbmpkkAaLRYLTSYTzWYzVQAt
- L+yTebLk1kJm99UmANGLxRMALLz1dlZVVfGpp6qYFpN/MhIFvul0dRzncHUfVu+IajZ0htn8
- /gYKUMnC+xcetSjGd+tBO8vLHzjnJjdWoG8uNrOvdlSXN2Szh2jldqpfnEd19kwGAh5RuLej
- uctxW1vtzARY+aLzvMPE1jtVmGQUi4n00+5P6ReLl84n3vn6jY8IFo0zlQIkv7+BAwDmzSpi
- GlS0rNsor5++UKhLOM3ucCgw17ndPzoP95wYPK38dnV0KNwl7G7/6CA/3Gbj4LSIwGCb+xvh
- rMvtT5Jry8tZ+7pb/v+h0lJad7Qkxvf7ufYOQ6RvPUKSnWK0rvhJ47Wrfqmw2dEP6pkGUMjK
- ok6nY6lFPDyPXYcX5UCxJofDAS42mVi1oVHRb1vdosZd7N4pHA7wYYuF1jdFTb1YP5fLRYfd
- TpvtQ0U6ktZ5vOZuy27xMKD0IeW6JuO4yLwn4pFEXBOP3Uhy/T0lNC96MiG9eYWFCfXb+LCF
- VU9tYGV5OWtf/4vCL5kW/abKStbW72Ob00GL5WEGwmFaLOvY6rbTYlnDQETLKBAIR9pBxX4Z
- akKVo8A/bR4PO467WF9fn4Cn1iTRiAoEPCw2m2ndrRQKPmuxsH6znY9aLApt/ObI+Lbb7Yrw
- oZCPHo8nQWtOos5uX0nt8WJlpUJBYVNlZYLWVCjk4wPl5Qk3BGojccW/0bqEAwFxnx+HEcPh
- ACvLy1lvjwrUzoXnA4EwwzHp4KVfmGha/JLsIP7/XAKDY4GeeFKbxll35FGrmy1XarHJxCHZ
- WgLpvG6QQCCNeXkz2NDijxRM4CidjqXLLLLQwDxEy7x73uTeh0wURt/OmYPUCpApkQi8kp/Y
- ieURhRuikCSdtsNRzacHp+mpHjRTZtpkCTRmTlaAh1DIF6nny7xQ2lRhIjTj5c0eNKL0O9nm
- pGyMVhZGxNOOR8wEBicAlW1rShXA7sHpeiIzh4PTYtpnVy01yGR1TQ3t9uhJ7h8fMBEYQJvN
- RqvVmgCcpIXWMHt1tC4YwKb2drp31VIVKf+8oWqqhxeTFKX2kuRb6gPSyWj8/7F8rq2s5CDp
- RGjwj+W2kQZg7E9SZT/aUC9rjhgnz6TdfjAp76RJvvyZPTK4MM5ZQW9zE202Gz0eDx8pM4vg
- PCJ5PfiChUAmi4sLFXyX2q2+QRxk80dpqR40hyQjAsIoQJXqEAiHuekB5aLW0igKtQqXvCD6
- qXIS+B+fl0T3TtEl7QskE/JRCJAeSCFAesBEqAZw/BAtgQFyX0q1sRbHbjoz1L1o2XiQz80z
- EmmZVCEtJp80pqtA/fRVCiGw2F+VPFo2RSePZbnOTrHO4zWgdszCLseTToLGp4nxSHLhKK0s
- cImn6Fz2ckoeikBiOF0dHWx125kOsGTVWyRFKTwGiEIj2yNmInK6P6WvlvoRemp1s9nW5mB6
- zKbIe9jGTIB9+2oJTXQOk04zdGNzmYnkm6CZQ9UyYCRFoKIdYpb9xU2msm/Ell8CZuqhM+Wx
- kQ7QOK+K50OihlX0BEzSjozXlhJG3x5ZrDz8oS5Ge7HIwrYjDubEnIBKp0Ht7U2cEhPWeKu4
- eSiTtTdFoXeb06E45ZNOtuLLoBs7Xx5zkmZq7Hds3xFPvFW0PLtT0f+VWp+gcerNHCBpD+SI
- Gi7xYaR8/S0NHJkedTctFgXV8eElXiXyRSynIrwqhzvXWWI0VEUtQ0NMPPMyKzdVmKiLCBTF
- OUdM694pOqqzb1H0O1PFJtYsyKNWN0MUemaC2hwzQyEfx/ZR02yxRsah2E4HX7BQBQ0rX/xI
- kV5UK29TpM1U7NVLHSlT9KrEotECC5dEhUXxB1MSFQ8XWLik62vwhfbxfc9amKHNEIXzfTMo
- XHuTwv+9mkqazRaeiyR+SnULhwMsn5EXbbvMXHkuWjhKK6+dMl/GCYRKYGFhIQsLC6mKnGxK
- Whf6/GKOTweFSXdH80s40AO1Q34oa2+motlDdMwrKmA6QN0gHXVDCvmkxUxtdhED4TBtFjMB
- gea5Znm9l+pUW1tLX8jHqqqqC9Z4mzlIoHnZak4QBOpH6KnuNZTLlkbzT0Z+fwMHqXvRZDKx
- l3qQYlPV0eFiDqDoVxItvlFHdfY0WWu6YJh4sl+1OfnpcKqxI2l9AqB50VxmCaO7LEBaNFpg
- 4VJR21mcu+czHA5wuLoXq99q5r76WlY/t5ctb1oVQsT4uPNHaRWHjUnD5GipHaPU1Iytd/Xe
- ZpalSKejw8VR2gyFUCsVJvq2+Uk49dXd4qFEPH46J05LgsUuqrskNOrC91FnPTO0oxQH7wJA
- w22PfCOcdbn9JS0eYAAdbW1cv6hQcegdG7+tzRFVNoho4XSG0S6FXypsdrRB3FvohgyjThAx
- S/kze8S0NCO5epmIJ6TrmalwUyr3nesskcNZcY23rNkiuye7nXKu9CXtueTh0+X1BgDVWRPY
- 1N6eFLulwmidud90nRDVBJr1607DBwIeTsoSWLLqVXoP2Jitzaa1sYUfrCmlus8EBsJh8eZE
- RNOs3dvEWXl58q0MSYh9vpisM/fx8i0bFc1lT8ruY2NuNyjSyUxMRyJJUyzvnnqFuzJ/VQSL
- 7lOuRZ9a5Vslna1RuhvF65mtrXb2U/frNHwqPJgKz6fCe4gXGKUSIOUgClgkCWZb3EnqhzYb
- B2vAvDsWc6QGNM5cIm7YAwG+VSVq42igYUnFUzJY2LiihCqo2Evdh8ZcI6EaTOurVpaUlLD6
- OXHTFgr5mBe5yiBdR2neUk2zeWmCTYuXlxYmSCRFwYm46Dw0I4/GyVN5rXAtp0420njr/QwE
- PLTZbKyrq6UAEbDZbDaF8KWrNHOQWtY8WBizWEugL1bdeP6o5AIkv7+BOSoRzEskqq9CIXBx
- b6ulBmm0HT7A8RqwcNkWuaNkazOo14sbMPUgURVd1BYCkZbJdE1E86QtKmH+oLpU1q4gpXvn
- UZVYZIrXCsXTAVHD4/HiQiJG+2u6Xi/fGY7/v6PDxbsK8sSJUJVGY+7NrK/fHFUhbbRSp9VS
- EAT516eXmoaCqHqit6mJK8rLeV3kCqA6I1u+v0lGNw/6fBFIvbykkOrsOWy0VVEFFY1Go7hh
- GL+Qi3N1srBs/igtoTOzvb2JAsDSNdvE9CILBlSayGQcPfmNP/mIpfjFiZRUAOfIg1Qtq0EL
- 8sZWzEslqk/3m0BfKKToJ/4W8c50aWkprW82JqQVq26dSoAUnSTSFMKilAKkyOI4N19PYdxM
- ju+rpblskaxpJ/ob+GRk82HdEdUuScajP8YCpkidC03zOKsoTwYVXY1nGPsD3jBCL0+8JNm4
- oSp6Xa1PP5YsrpL7WLJNawKQ2FfLjBi13zlD1cSAH9PvbxBVmyPCJFGLRsXqjTUUkMnqjdXs
- ox7KZ5+1MPbaLEl57JU/s0fBW/GKG2ShVCytmmOUTx8lihcgiQJSFS0bo8LUWCAUCvnY0NCg
- SLfD7UppQykVBdo8dDgcbGho4O3jBCI9N0ZQKqoet0Q0/ywv7BMF25ocNhzys8PtYkPDIVFL
- KwIIn1tskucN8bRvMB3ONu581kJENgHt7U3M0WawytZIMgJII/Hrlprl+GIZ0llvPyprWMQK
- imp3uRO+xb5jIJAmX9lOFL6K1znta8XT1JJVb0W0AVWd5vvgND2RZqCro4MbV5SIgurD3tS8
- SsEXOfzrYr/+sS566NHm8TAQDvOFyMmnpCEX2z9i6yOWT+TrAUmz5bA3sjEbQNuHtsiYGUzb
- B/XUIE3eiC28UUeo0kWe3SYCNYkP1Tua2VBVQiCTdnerfDolqu2nyX33yH5RezN23KUUII0W
- qMudT0/M+NlSU02z2czS0mVsamrmgW02VlU9T5LfqI9Lh0axqugk5RN0dfYk2mw2xU+6/y9R
- OBzg+qoqWt8U+6nI0zRWrq6k0ThP1kZw2upFIWS6jqWlpazf3CDPI+kAzYuWcfaNOvnKxfp7
- SjhIp5Pnar1+BKuedyRoIG16wER1v7G8a0YeAU2CCQKJ2tubONk4lTNyddRNWRblVYeLRv0N
- bGpv5851FmZos3nDaL0spOzocImgP20Ah2epZaFMS6OVWWo1tVqt/OulVtNQcF/K/G/QG+kL
- +Zir0zGvQDzZb/B/zCmGCUntmshzmsPOqqoqOvYckft2egzQlTcMN4pgeWmuCP7zCu5gQ4uf
- z1osLC8vZ3rM2h5PqcZO44YqefMWK0DyHrBxiG5YUlswpHglRwCozrqetvcO0/16rYzLhMhm
- TTQ/oKFxsjGyAdygjJs9gY9XllOFTDra2uisraTBIGoiJ4YRWFxspk6no14/iY4jbTH11rC0
- rDRpOtI4KDabFXVJhYkun9+P2d7exMwYv1DIx9x0UJj0a7a22iObb1UEV8Ve+06O01JhsYvl
- fr4CpEF91ARUFARB1ohcOEas+zfBWZfbXxr/E7LU8n5CMulBUqEVn5su4qG6R8yUtbQ6wWiX
- wo9Mjs3kw6cWcY9k0IC6KcvEtNJGctpwtYyNyNS46e/l7nA4UrrfcaOOgIqVNW+LV/AiV8qS
- YbdUGO1iucdigWS3KOI1xtbNMxIQWL/5A9YsM8tr1fliskvtLskWrFYr55rNLC+vVMgWxHjj
- uf+II3J1VVQOSbUWXSz3VPgtFUZNFb4bukAaTX+MHqVDz+7dAQDdu2swcOBAZGb2x8CBOgDA
- +0+vxL0rV+JYEHDufhvuILB/52toatWiv0aDaRV1+GBzPa7JIH6/9h70VA3G7hMnMOfhOnzl
- a0Xz53vR/tF+lNz3I/xi5jwEGUTFz2aj7r3P8e5vl2DHF/3R1N4EQ3gfsq4ej8UPrcTmvR5o
- uneXy6OJlA9hZfkDAIArAQAPbtmO9+1vYGHZQrxhfx+7X38MJz9rxANlZVi1aiWOAfhk9yu4
- u6wMK596JYEXWx5cgCuuuAJXXKHFBscXCr+TJ/djj+ssFiyaCwDo1kOD0FenAADBoBe+MND/
- 6gw5/JVJeH3i6G7c0G8snH0nw/Wn52X3gvtrcCoQwIsPlQKH38SG/V/AUroQQaRj65Pr0RQE
- nG+sxdZ3mjFg9Cwc9fvgdDpxyFaFkGsnNn/sQc8+GkCVA89fW/BFaxN0+Bw1T++U81j3H3XA
- gH/DrNEDAAAv31uBY6rBsDs+xus1lVCd2IEnXvkMJf+xAdNHazB1+BCs3LxdZniPHhl4w+nE
- E/dNT/r/KZcT297ZgSAA4+QfofrpWsyda5LbrY8wDHPLyrBgwQL597PFS2C+abJcRiEnByt+
- uxIPW5ZDlwaE/F+gzvqm7P/ehjr8LT0XTns1AOCPb+/B9AWLsLu2DmFhOnbv3o27x2gBXIUR
- +oEI+E7ixIndePfASeDYdsyZU46TAOr+s05OMwwNqq078VWrD/fdZsCO59bCGwzi7NkAgABO
- njlzzjF09mwQhzwh9L/2Wnz9dRDAYDR+/ld4vV74fE0yz8W8PkCrzwfvp7uQ0aMHzgYDcj/q
- 3r0n0gD8/umnUWf7OCatz+H1erHfWg0NwgiePZuyLGKcdAzI7MDCaUXY/+XJc08CYWDRgxU4
- +dGr2NfWF3cuvAmKHIJBzF9RDYPmGCoqHgOgitQ7AKAd3mAwLsEzijKePOFFujAQtbWvY8PK
- WV2OlzPqegy6OgOACv2vyQQAjDZX4EQ4gD0OB+6eOQm/f+Y+lP9ue+q2CQYAlUr+/8t9++Hv
- iPrfu3QJ8OX7+PWvV+EEdKi4eyIAoN+wfAxJC6N65ToEM/T4yQwTBvRsxeo1dUDmdRij1Yrp
- /Wkzfvd6IwCguvLXivJfe8sC5KiAwrl3Ksr0zn+UwfLfe1Cy4mUsKNClLLtWOwY/GNQdG9b/
- V1L/Hj0yMGbMGIVbb91A5OQMOnebx9C26pWYnJuLWT/+Cd777BgQaof/zBngDADVQJgmZyHT
- MBEZAHZ/+Gc0f+aG+vsTMGaIFr11AzFmzBA0u91Av8Hor9Gg8F4zNJG0nYfcAA5jVt4I/GRF
- HbQZAjShbujWTYMrAfTs1QcA4PF45fgFi4qgip3oVVnIn9gPvb8/EBqEcbI99Zjs1k3MubGh
- EWbLf2P5gknJA6qykD+2H4ZMMqCPehAq7p6IrMkmDNNeheDXX6fMt9nthvra0RjYuzduvGUi
- gK/g/TKYmlcp+CKmPxBFBSMBAOWrqyF8tQvfU6sx+MZbsPtPPvTS9ARwJbRXXonOaNCMMoxP
- C2Llyqfx+JPVUA+9GUXfF5BtmotB6jas/OVK9Bw0DqOFDiyvWINg2jAUjfhXAEDllhqkhf+G
- jjQD7P+zQkxvWhluEsJYueJB3L/299COmYl8XT9012hQe+8srHr9z6ja8D4WFOhw4uhuFEzN
- x587gIFXZ52zr/XTavC5478wMf/n8J8+jc/fq8NCy0potVp8+M4mDBv2fYy6aQb2uDq+cR//
- +usgwgACwf9TuL/72mYAQMjfhOXLl6O8vBzl5eUoK3sAjZ6TirDdu2vw4aY6/MH+FwDAgY/3
- A6phmD1jIIDeyMnJgaZ7d2T+a3/0UQFQXYVhw4ahv/A9sQyaIM5iAMp/+wBWLJoFBMNyP03P
- yBBnUk13ZGRchZ49r4JG0x8bGxqwodIMAND2FRD660H0G3c7pmUR2/d8lrLfn/Yfh+Zf+sN7
- cA/crZ/D6XQiGPTi+Mkz0HTrhvTvaYFAKz47chyCcDUytD2wY1UFdn4exoTBZ3HQcyW2NrwE
- TffuEEZOxwdOJ/bv3x/5NWLprcPQ1HwUQCJW6tZNgzMnj8P9f224MiMT2X0BIA1XnO3AUW8Q
- mm6p4ahuYj4qKiowccI1AIDsMXNxkkRHhwuDARiL14Ek3HufAwAsfsoOh8OB5fcvRP9MDSbd
- UgSDwYBX7B+h5pcF5+wXsTTaXAF/mwf3FOUheOq07H5luhYjx+ghfE+TNJ524BhssNux9aX/
- QE62gFP/FwSuIA5/chi4Mgy//zTG3rkclkIBe3Y1YcJoLdb8ZiW8waAcd8tTFfjdb9Zg0uLf
- YcjXH+O2+9egqflLaLp1SxJmFdavqcZHuzbg5CfvY8MfP5Hrvb3BgT3/9XTSdAAgFDqGbX94
- BW6POA46w0SXz+99zJlTjq9i/I68UYcP/wb4m60wFVagAxpUb/kA7V4vfL7PMDc3u1OclgqL
- XSz386UXqpejl/oabN66Ayv//WYAgMdzEureajHABeKsy+0PAFddlYM7CydC3C8IKLPMiQa7
- EgD+irzrB8Jx1gDP4c3QBYIQF83OMdql8ANSYzMVgnjlN4/hZ7fPQmMQGDNuXKRtgBWbtiLn
- rAM9VVdj884vU+Kmv5f73Dt/mtJ91yEvgDDWPDgXOeOm48RVWqD1i6TYLRVGu1juKSkCazTd
- uyu+P9y3H+rhhZhrykXR7HwAX0Ux33lgskvtLskWli9fjianE9u3v4KyGNnC50ePQZvdBwvH
- TseoojwAbXAf/eo8ZowLo1T4LRVGTRW+SwIkAChcVIEFNxlT+o8pmosf6rXoUA3GvKLR6IAO
- G557EtNvFEFc8ztb8berhmDq6ImwPGIB0ALnQXFT3CMjA+t/asLBjKl46K7ROIGrUffci7hO
- /TWCga/R75qBANqwfbsau75owuATf8a2Px1DxYoVCeXQDR2G+MXi1Ek/kHaVDLK7d9dg+fLl
- suBCGFmEj91uHDrkxEgVYFpaj2a3G9u3rAIAfPWVGzU1NXAeO4UfPVwHkiBPYm5uNk4dc6Km
- pgbur77Cwd/X4ZhqCGZNE0GyaWYR8PlObP7Tl/jw6Rp8iTTkFwwDIAoUTgUDQPgreYI9tm8r
- Rlybi8N9J8Pjfgs9I5uUY04n9u//DBqNBt/T9oQksJn171UoLZ2BVu8xhAEEgx3wn/mbHB4A
- 3n5jDwA1+n9PA6PBAIRbsfuTEzixdzfaAAy8RgRkx5q34i1XCCWl98h8a/P7AdVVyBkzCKOv
- jwzGUyfRq99AvLT9Y5Bn8MCPJgK4GoZRWpw9G0RtTQ22vt8s1/GlmP+FkUXwktjxqhV9g824
- 8fqrccUVV6LozqpI+AC8Xi/8fr/id/JvYj85cXQ3ru+XAZWqJ37yq5Uomm+By90B9wdPy2W+
- ZkQ+TDf9m/y/cUwO9r/zNkbmTQSOfYgnnngCmw6cxMn9z6G87n+xZNnPsH31GnyJTFRVlmP6
- 9Om46/ZChA69ha1/PhbtWJpe6N6nJ86GAkBY5P+U4iXIxOfIzy+F//RpBINePLJ8ObbuOxZZ
- 987g5JkzaP3cjZ8XTsS+DqDs5wulNTElaTL+FRkZGcjI6AEAuOvfFwBfvoYFv/5PXCXk4NGn
- luNqQOw3ZwDgSmi1WmRkZECbrY0mlCqfMwBU1+DPHh/G93Zi7NUjFHUN+o/LvJfzCIcxcoIJ
- 04bpYLy1GCN7xchpI/kEv+6Jp1eX4/OGBnRAnOinFC9BOr7EwrkPInj2LE58shvLnnwF6qFj
- MbB3bwCi0Kxs/fOoq6vDggW3yrxNHm+kIl7Rkl9h45u7MW8osWTOXQiePYvtGzZgy5a9mDBx
- IpY9VAYBwLG2kyn5nXn1QCD8GV55Wxwzr/xxOwCVPD+MvLMMIzXH8Mwzr0Cfb0LOVVeJ81aP
- DEwep8Mnf/kEmuvGIFPTH6P+JQDXp8dg/OEt0HTvjtOn/ZgzZTZODJiBtjYH0jw7MPEnj8p5
- SxtYnAnJbl84NuDH5U9DmFCMuod/JLdFKrrrp7Pw+d534D99GpeK/ucPdQjrzHA3H0LpZIM8
- BnAlgLAH2xv+ipOfNeIUgDGjhuH7QwYi1PwRnKdO4bTfD7e7FVlZ/QH/EfhPn8YHL2yFBDV1
- 2QKgMWD34cPwer3Y7diK/LH9Esrw/YEDgWNOOE+dwsbHNyAcAc9i/+x6XUSea2D6sQl/WDUd
- ZQ//T2KgmDTPdgQB9ISmWzecPRtMGiaWsq7tj1DLQXiDQbh2OwH0Rv8BmpS8SsUXadxJ9K/j
- i9D0txBa3XZ0/2I/lj/3mhxQWu+6a3ri5Ge74Tx1Cg2vbZfT6tEjAxU/N+GTV1ej/tBZLF9+
- HwAR1E+6rif2OPYg55bFmHG9Fo17G6GfXCgKr88G8dPxJnSk65AZbMTE2x6Uy/PQIxYce78e
- 73ypwRNPWgAAv//VXPzsd6+gfO0WVJhHAwAyr5mIT31BzB6ihfPwFzgX/fWvQeQtqIP74/9B
- Ro8e0P3bAvzV70VNTQ0+OuSOrL9nsPnpJd+sU3dCT+xyYt5oAeo+47B//344nU44nU643R+j
- aKSgCBsMerH3fz9BILKO64YOA8LNsL7lBvAVvF4vAKDf2HyMylJDnTkMZWVlmDhGTOedZ7ei
- A19ibEYGRi1YA4SP4g9vfor5K1bCZrPBdJ2AvNvvx+bNm7Fg9jAEg178NHcslqz+IwCg4Jc1
- cNpq8doTi/G25wosKE4uIOndeyDm/1s2tthbMHGECrNuNmHu3BJMGjEd1950Jwb27o3R5go0
- e71wNTejqel95Ov64ZZHN+OhO27A3k/SMG/mSEzNmgxvMCgf3EV/OhRMLsJE/dUAkICVevce
- iJ/fdh0mDroZw4w347/+sB33FFyFMX1zcd1tP5Xn9a6S3+9HMKjBj0pKYLpxUOR/sQ2GjBmD
- iRMnIj8/H/01GugnTMTcuXORnz82ZXri2NkH56lTONbgFMdOZFrWZPZH3vUDFeEzr5mIzZs3
- Y8wAbdL0hJwc5OfnIz8/HwN1vTFyThk+bnbhVOAUmhq3YeI1mdi6fC5+8+YZFM+biL1/0cD2
- 4Xb012jkuJ5tNfgybTy2Pz0XM6+Zis+CGmR0O4ol99cmhNm8dh7O9DiJmcZ8aHIXo6YsV673
- n56uQGM4eTqnT/tx540T8aXqahhvFIWanWGib5PfqodXIZw+EjWPLMMNY3MAAIGzanTv2VMc
- m2fPdgGnJaFL4d6F72x9f6igQsbgATjzty/xix/lY+sxoOK+e74Rzrrc/gCwbPoYlNXtQWXt
- JswbB+T2vQ4btovrQX55OQQcw96DZ2D/89vo8fl+LImJ3xlGuxR+QHJsJpHT+TH+70oNqqo2
- YHPVjyNrdQAZ2Tfgf4+5oMMxrNn4Zkrc9G1w//mkYQDS8MQf/hderxefNOzHhv/8lYzd3F99
- hdOnReyWCqNdLPeUlGKcZGWlwFjnickutbskW/jLXxoBZyMG3vwI3DGyhe8PGYiTznfhG7EI
- v719ohwvFY67WO5AcvyWCqOmDB9vA8m61JzyCtu5DFvWLcijMO5uvrCkkELcPX/l3U7QePMS
- Wc0v3gj2pKzIdbU00Sp6KOTj3Bui9jDUGdmirSXN4ATjze3tTdTFXDORDNoa563juSiVQcbm
- HdUEkr/OIxmwrN3l5sJRWtkOi6ReOzPmHmhh8eMkoyrrkH/prG84qrhrD0B+BSn+XqLx5iWK
- MoTDAY5PA00P/FGhlivnO69SDjd/rE52F4bfIqtvinkPVqiRt+y2ckDsy1+RJ0jlq1aRsldt
- cCTtJ5LR4M76zet1taysrD1n25Bkm9PByspKxdOJ8SQas1PaBEoDaHn2TW58WDQcarFYmJeX
- R+uborGyAkFpTL2jwyW+bLD0hYRXMYA0li57Vg67d2O14nU0aHS0u1tlA+ryL20Aq9bbSDLR
- D+KLD8kMC0tUU2ZWvtyWpmO9zSnarFDF20ASr5/E+kXte72Q4C5eDx2QpK7iWJDCx9odSJVP
- 9OWs6AtyjuerFP1d6kfSWEhV5/h4sa8vxseT2rl0zTZaigyKOqizxiqMzo9MMsaLjXpFG8df
- A5Guk8Xe8Sejd66lFzvE12eir0hVzTFSuvcfDZ+meEUjvjzWZeaE/iHFiTeiTYp3ntNj7A/E
- G9G+GPRG/MuBGrEt4vuyZOg9/m65MG6R+ApRklcG4++VSzaA4u1y+Fsa5NcfNZqoEXfpimXU
- wLt4hVPsE9FvyVab5G5taeG2h8T2My/boAgfm6Z7Vy0zIoZzAwGPXKZU+bYetEeMnyrv/8fP
- yxKvEvmSWAYyYitHtokkiHm5o696mZdtYNsRR1Iek+J1R13ErkSsrQ6xXOJYEq+3xfdfgfbW
- Vlmlv/wZ0Xik/DJSjIq/ZJNJeg3JvCx6Zbt4uMC8xVEbAKmusM3Wac/biPaF0sV4OCPeJlEo
- 5FPOJ5F5a/GNuoQxXf/BUb6w3MKq9e8yHBbbeW15OWs3RY2OijahUl/9a/c20Wp9lTu2RNXM
- O6P195RQEAQaDAYKgpBgFDUVNTU1kaRs/PtCScpfp9NRELJYcs9T552GAoOoVNExNWr+BZcr
- 8TVaZXoblpppusPUqRFtu92ueGL7XORtaqLreAc73K6Eq5GS/b3KTaJtJLfLxR1vWjlaP0J+
- 4js+zKIJgnx1W3pK/lzp1CzIU6xRZOeY6NvkF3udTbQVomw/af7pMk6LrOUXyz0WG3XlO+Fq
- pkaQTTR8E5x1uf3D4QB/YTKx6vlGOXyFySTvHSRbe/1iX8qLS78zjHYp/JJhMwl3SjY7JYq+
- OBbFMPX2oylx0+VyV7wAnabjzVONyvFisdLf0qB4xViXuzglRrtY7rG8jsVhYp8fGTNOxO/W
- g3aF3Uhpj3u+mOxSu0sUDgf4qtVKx/4jCvfZMS/GxcZLheMuljuZHL+lwqipwuOFJYXUG+fS
- brfTbrdz4RRDwitsF5PuMhgSnpITjScrrb17IjYeYikQZ+E8HEj+8szq2QYibTxJycis0h7J
- +dLLSwqpzpp2znBTdLqkr4mIxqC/2Ss5IZ8vYlC6a8YrOwvf5vEk8Lsz8iQJL6XfGZAUjXlf
- +AttF4tei2wS9Tfks6qqigUTDEz1xOyFkuc8eXohJBkZ72ofiKVnHxaN8MXa4Pp7UtRA+vnz
- yOPxcP6NOnlRvlT5SfPLpXi6+mKRJGQWBt2kEALMHa2neZmVO5+1ME2FBIHfxSBpzJ+PX3wb
- SO2SjMdtnbxgQZIdx12sra1lQ0MDFxcZzquOb6yN2v35e5HH41FsCqUXLlwdxxPqKfEllR0y
- iXydtEFXeHwxadem2k5tysTTwjFaAuksWbxKNrQ+Mk4QcldB1A7aPwqlOmBzbqqkXn/7Baba
- eX6DY/JrdduZk6GlWq2m4Qd3/EO8yPdtpJeXFFKbY6Yv5KMvFGIo7hXFN1aUs7SsjGMNU5LO
- O97mJuZmKl+e+iaUDBdfijDSq7pVVVXMHaKTD0P+2SgQ8HDRND2BwRdsBP7bTufCPZfbPxWJ
- NuvEQ77O4neG0S6F3/lSsn1RKmz0bXFPVuZwOMD7bhNt3ca/cJYszYvlfr4Uj7EuNPyldk9F
- drudnkAgwo9E24rJ+uXFck+G3zrDqMnCY9+mWvn1D+lXuyn1k6rflPY7HOd1QnMhJD2JTIoT
- k/SM/Xf0/y/5DzXw3tJSmkwmlpbemyAJ/menLLWaxqnF/9DAyeVyndfk/M9I0pOtqQwER/2b
- upRepgpU9+pFrVZLlQrUTyrrUrzLQdJGWaUC1b2yWP3i3i7HzQRomLL4spb/rVUl1PbN7XSD
- 39JolV/Q+DaTpEWrG3tHl4F3x3EXH7VYxCd5IwKk2Mc5OjpcLC8vZ1XV8xdV+HWp+7h0ul5Z
- o9Ra7DjuosOx/6LmJeW3xmJhve3cT7F/R10nq8VM/Q2LLjh+5e2FFIRBCa/Oftup3dvEOblG
- CoJAY+6tdDgv7UHY5aL3aiqZJQg0zX/ochflO/qOvtXkPWDjMJ1Ofk3uO/rnolT4LRVGTRX+
- /wGGW1Zhe4C0/QAAACV0RVh0ZGF0ZTpjcmVhdGUAMjAxNi0wNi0xNVQwOTo1NDowMyswMjow
- MAxjzM8AAAAldEVYdGRhdGU6bW9kaWZ5ADIwMTYtMDYtMTVUMDk6NTQ6MDMrMDI6MDB9PnRz
- AAAAAElFTkSuQmCC'
- 	) base64Decoded asByteArray readStream
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBookDark9Data (in category 'dejaVu font data') -----
- dejaVuSansBookDark9Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Book Dark 9. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 9 11 3 0 255 12 0 0 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 11 16 22 32 40 51 60 63 68 73 79 89 93 97 101 105 113 121 129 137 145 153 161 169 177 185 189 193 203 213 223 229 241 249 257 265 274 282 289 298 307 311 315 323 330 340 349 358 365 374 382 390 397 406 414 426 434 441 449 454 458 463 473 479 485 492 500 507 515 522 526 534 542 545 548 555 558 570 578 585 593 601 606 612 617 625 632 642 649 656 662 670 674 682 692 692 702 708 718 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 728 732 737 745 753 761 769 773 779 785 797 803 810 820 824 836 842 848 858 863 868 874 882 890 894 900 905 911 918 930 942 954 960 968 976 984 992 1000 1008 1020 1028 1036 1044 1052 1060 1064 1068 1072 1076 1085 1094 1103 1112 1121 1130 1139 1149 1158 1167 1176 1185 1194 1201 1208 1216 1223 1230 1237 1244 1251 1258 1270 1277 1284 1291 1298 1305 1308 1311 1315 1319 1326 1334 1341 1348 1355 1362 1369 1379 138
 6 1394 1402 1410 1418 1425 1433 1440
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansBookDark9Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansOblique12Data (in category 'dejaVu font data') -----
- dejaVuSansOblique12Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Oblique 12. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 12 15 4 0 255 17 0 0 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 15 21 28 41 51 66 78 82 88 95 103 116 121 127 132 140 150 160 170 180 190 200 210 220 230 240 245 250 263 276 289 297 313 325 336 347 359 369 378 390 402 407 416 427 436 450 462 475 485 498 509 519 529 541 552 568 581 591 603 609 614 621 634 642 650 660 670 679 689 699 706 716 726 730 737 746 750 766 776 786 796 806 813 821 827 837 846 859 869 879 888 898 903 913 926 926 939 947 960 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 978 984 994 1004 1014 1024 1029 1037 1045 1061 1069 1079 1092 1098 1114 1122 1130 1143 1149 1155 1163 1173 1183 1188 1196 1202 1210 1220 1236 1252 1268 1276 1288 1300 1312 1324 1336 1348 1365 1376 1386 1396 1406 1416 1421 1427 1433 1439 1451 1463 1476 1489 1502 1515 1528 1541 1555 1567 1579 1591 1603 1613 1623 1633 1643 1653 1663 1673 1683 1693 1709 1718 1728 1738 174
 8 1758 1762 1768 1773 1778 1788 1798 1808 1818 1828 1838 1848 1861 1871 1881 1891 1901 1911 1921 1931 1941
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansOblique12Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansOblique14Data (in category 'dejaVu font data') -----
- dejaVuSansOblique14Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Oblique 14. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 14 18 4 0 255 21 0 0 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 17 25 34 50 62 80 95 100 107 114 124 140 146 153 159 169 181 193 205 217 229 241 253 265 277 289 295 301 317 333 349 359 378 391 404 417 432 444 455 470 484 490 500 513 524 540 554 569 580 595 608 620 632 646 659 678 693 705 719 726 732 740 756 766 776 788 800 810 822 834 842 854 866 871 880 891 896 915 927 939 951 963 971 981 988 1000 1011 1027 1039 1051 1061 1073 1079 1091 1107 1107 1123 1133 1149 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1171 1179 1191 1203 1215 1227 1233 1243 1253 1272 1281 1293 1309 1316 1335 1345 1355 1371 1379 1387 1397 1409 1421 1427 1437 1445 1454 1466 1484 1502 1520 1530 1543 1556 1569 1582 1595 1608 1629 1642 1654 1666 1678 1690 1696 1703 1710 1717 1732 1746 1761 1776 1791 1806 1821 1837 1854 1868 1882 1896 1910 1922 1934 1946 1958
  1970 1982 1994 2006 2018 2037 2047 2059 2071 2083 2095 2100 2107 2113 2119 2131 2143 2155 2167 2179 2191 2203 2219 2231 2243 2255 2267 2279 2291 2303 2315
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansOblique14Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansOblique17Data (in category 'dejaVu font data') -----
- dejaVuSansOblique17Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Oblique 17. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 17 21 5 0 255 24 0 0 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 21 30 41 60 75 97 115 121 130 138 150 169 176 184 191 203 218 233 248 263 278 293 308 323 338 353 361 369 388 407 426 438 461 477 493 509 527 542 555 573 590 597 610 626 639 659 676 694 708 726 742 757 772 789 805 828 846 860 877 886 894 904 923 935 947 961 976 989 1004 1018 1027 1042 1057 1063 1074 1087 1093 1115 1130 1144 1159 1174 1184 1196 1205 1220 1234 1253 1268 1283 1296 1311 1319 1334 1353 1353 1372 1384 1403 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1429 1438 1453 1468 1483 1498 1506 1518 1530 1553 1564 1578 1597 1605 1628 1640 1652 1671 1680 1689 1701 1716 1731 1738 1750 1759 1770 1784 1806 1828 1850 1862 1878 1894 1910 1926 1942 1958 1982 1998 2013 2028 2043 2058 2065 2073 2081 2089 2107 2124 2142 2160 2178 2196 2214 2233 2253 2270 2287 2304 2321 2
 335 2349 2363 2377 2391 2405 2419 2433 2447 2470 2483 2497 2511 2525 2539 2545 2553 2560 2568 2582 2597 2611 2625 2639 2653 2667 2686 2701 2716 2731 2746 2761 2776 2791 2806
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansOblique17Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansOblique20Data (in category 'dejaVu font data') -----
- dejaVuSansOblique20Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Oblique 20. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 20 25 6 0 255 28 0 0 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 25 36 48 71 88 114 135 142 153 163 177 200 209 219 228 242 259 276 293 310 327 344 361 378 395 412 421 430 453 476 499 513 540 558 577 596 617 634 650 671 691 699 714 733 748 771 791 812 828 849 868 885 902 922 940 967 987 1004 1024 1035 1044 1054 1077 1091 1105 1122 1139 1154 1171 1188 1199 1216 1233 1241 1254 1270 1278 1304 1321 1338 1355 1372 1384 1398 1409 1426 1442 1464 1482 1500 1515 1532 1541 1558 1581 1581 1604 1618 1641 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1673 1684 1701 1718 1735 1752 1761 1775 1789 1816 1829 1846 1869 1879 1906 1920 1934 1957 1968 1979 1993 2010 2027 2036 2050 2061 2074 2091 2117 2143 2169 2183 2201 2219 2237 2256 2274 2292 2320 2339 2356 2373 2390 2407 2415 2425 2435 2445 2466 2486 2507 2528 2549 2570 2591 2614 2638 2658 2678
  2698 2718 2735 2751 2768 2785 2802 2819 2836 2853 2870 2897 2912 2929 2946 2963 2980 2988 2998 3007 3016 3033 3050 3067 3084 3101 3118 3135 3158 3176 3193 3210 3227 3244 3262 3279 3297
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansOblique20Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansOblique7Data (in category 'dejaVu font data') -----
- dejaVuSansOblique7Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Oblique 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 7 8 2 0 255 10 0 0 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 9 13 18 26 32 41 49 52 56 60 65 73 76 80 83 89 95 101 107 113 119 125 131 137 143 149 153 157 165 173 181 186 195 202 209 216 223 229 235 242 249 252 257 264 270 278 285 293 299 307 314 320 326 333 340 349 357 363 370 374 378 382 390 395 400 406 412 417 423 429 433 439 445 448 452 458 461 470 476 482 488 494 498 503 507 513 519 527 533 539 544 550 554 560 568 568 576 581 589 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 600 604 610 616 622 628 632 637 642 651 656 662 670 674 683 688 693 701 705 709 714 720 726 729 734 738 743 749 758 767 776 781 788 795 802 809 816 823 833 840 846 852 858 864 867 871 875 879 886 893 901 909 917 925 933 941 949 956 963 970 977 983 989 995 1001 1007 1013 1019 1025 1031 1040 1045 1051 1057 1063 1069 1072 1076 1079 1082 1088 1094 1100 1106 1112 1118 1124 1132 1138 1144 1150 1156 1162 1168 1174 1
 180
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansOblique7Form (in category 'dejaVu font data') -----
- dejaVuSansOblique7Form
- 	<generated>
- 	" Form data for DejaVu Sans Oblique 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^Form fromBinaryStream: (
- 'iVBORw0KGgoAAAANSUhEUgAABJwAAAAKCAIAAAB+PNPGAAAfT0lEQVR4AexZq8Ksug7OE/Ud
- +gR9AXQ1thaHrMOhUKiqKgwKg8FgEBhMBaKmomLOhFKm/GvWnHXZt3PJ3nut2R9pSUOSL23h
- 8eeItfaPm8zvZse/3G7d458v/5f/y/8F09U8xX6BnUXY+p+aam2rdvPff273/UdndE/VDxOZ
- zXz3Fc5/Vd7dfdo7eFf7v1hjgg/tjgGQhIn1/5MZglH7z2A171D8H/gZ9qmu9OO/T9wssnL9
- Ugk2nWVycSm0lJlQus6FcsnYumpVXRZVZ5PiVhXVOOmiVC/QTQzyriup6H8z51rB9c3ctWRc
- v2z1uuBSq4KXiz+RvirVONZCBmQfq7wa0ahFZbxan0PtJLJC6yov++eiSoH2i0J9sMMMbdWq
- SohmNF8sbDhr4rtTBxaUtWjnTboiK5o2WJtqd5Vs2uf09XofMdZF3fd1WaUzfRYf/WCTgr/1
- Mq+nL5pTk/NqiEqnrzLRKJlX4x4x9Jso9ail7NZEdeBUoNYncXeudH3TTPu3vtraqlnsa2rd
- tLNNXLzNi3F2W6+hDtnM292+wkBQyijhrfv5lBiaejD+G9yoqk6stR0an1gVbUCNfWqaV1K4
- tauaAacYVduvD2+tdc7i4IQ+0kq6zuvuzIorvEx60zHsuq5HczNpTPzpzDJv1m6rcamRDo38
- Fbc043u3NMnXQRvSj+VSt9yd3K/ubSuCoLPIJRa5BNyqc87zQzgX+ktOGE1JuR1VhhPR9xWX
- Y/J4k7xY3FbxYr5VtLXIiph1riszACC8PSzfJQGZxPKqnwBKFnMG3wV8ihOOkkLWoi29ANb6
- Y1VPX9Sifk6Ia/898UtDaGXDbzPkBA5rm2DioiWjTygbbbocFCrCipzKaUBIVm23gsKvgasS
- EKUKkN8awU5ksg83ZvASWnRHTDc0vizkwzbUAcnK7s/uBeJ6TyMLvb58NmhZiJznZa23ux1z
- mwPkcwTNIOEUIurRv2JURJzWAxb6QWZw+VFPqJmAKHl7nxBYiEZv2iK7sEAbfcl4u5wm1RmV
- YwDzAKJsBaFq80dolYRjaCFdkej8viC5igZfxsTINB0DyKrxxGmxpu9C8UNTxBVxvdivDiGZ
- mm3UFB81+amJAYAhcX2RUbJD4SkBY0/f1uyVYkPwgxtZklM7zly4V+S7lhNWTeHb5kBCGmZA
- O3NZwmf32LQA1thIYE8QWfnyPSHXR7ETGk/zBgObSRMjpz/CqRz2GB99dkS7/xiEbQYEp30v
- YwlQjj8UzWhV+RWNlhyOJd95xVcD7CAA5Pl7LMK0FvXQpVFO5PF3y6ql1Mvf2AtrQTBi1dMG
- i8EXA2BRmCMYex/lh6MlEhMjhV5/e2Oih6S6ubU7I53Vb4kkB9bv4f2aAD/yuuoipdpZMUCh
- 5RACCIC1rQBanwpLJ3jGc45EHItAcBHLMgoUe9xfF5y/4ChZdpv/oh6CBdYHgstk/zmRckrI
- UYL81nGWUSBXb+L3gQEU3Xv/b0PDGaXIqlSt7tNHpAC0stEJWOOiEz4poxhJQHTb50ep5bdH
- 35e5FUDE7N6AXzYmqyoQ/JqGT7BY34DiDrqGE6yTd2P8qhBFR5yS1fNHPo3MwNsEoTeEBAGS
- nwgq3BGh18ACTGh/ljX8HUtcRfPz91TzyAVMqovEGUQKWJrP/HjHaf4FjywnujtOwzTf4CTF
- P0rKwjQTRYZF6S2ZfgIjxY7yDTjJ7AmmHGoDh4YOJFf3nVrHohf05qN7GbDG3fUkASr7q7NS
- 4oiRso/AGOfJoiErB6iUBBAxvGzNaNmUhEr7+GlZkJ6r+0BTMSCvHtV14ROJLirsSJmqJpDN
- HvVLAK7XsAcGgGba96k+zS4JKZUkEBasOPZOGWX1FN65XaGvVh9N4kDkfi/nNQNS6GiSPzvb
- XEdgio0MG+w5BDsL3RBg6LqflLlhQGr7TZmiZe/utEiK/lLArkJhVKxpE14QYJXx3+t2XEMh
- bxoG0NsH7IMU7Wztvu92UUXZmxsN4ATSHpFBIVO6ZMWQPO4IqawbCJEuLXBR9Ob9UgMU+8OW
- hA7+MRSElMkMOC20i33YdZy2BKSDPc/oIf4O+GixbwbGGWH5mXgxLinI8Wdj0jUsBFPYcKJ/
- HdIzyCNilk41FQfIY7QYPBTZndt6CufrzLIY6/0+ZhEJWQooZQisXtBcLQ7vKc59aCcAiHxO
- 67bneHdcSJrnQzM1AIA04xcOINC2rQxtkB0oQNlvjx3f3q7uRxdp5mHaPhY0M/STfYNvTaXM
- w/cYVc2LI4FUelyXseKxWARBC/HpVYbGkoDQ1rtZi0tzxn0AaWeDrZAWVPTofEz5xbl9bLGm
- y2E/Qb3YPfjGXxPu9kK8ypGjRuMe3j1nI3G2uHPwbQa53k7wihDbEwyn00gi58fRi9BYiYYn
- eEuevaJnVJ+VBUD024XXswvhJHoTdnfohwUPINTxre3NITuCtPoBTdPmyNT2PMEF2a/+4c3c
- d/N+XFLtXXH5ZA9hE6ubPZYcQKLNq3Dken16gIZ3beoquJvOgcig1wkgcnq4geDnMK+E3dB7
- B7gjtuN7rdu7kuBCVncsipEy7BLnDGhvH0k1J2rzsQ+GTNY59snTxwhelBpdet+X3JJh4k/o
- CvfNpZxPhlj/XCgnVwXz6a0dGgx5l45OprMVPU5e0lfE07T091TRW8wERL6Qy24XR797YZzz
- DsTh75eY6rycFJ8OBcna9e/b040EyOCiM8kRk1G2Nn6UT/Lj0eJ0DkGwiv6GdIKr7fX6lmGr
- 5B92XTa79OMWKWHs5v3sNjIcYCWBrE23r5GMxYCl1ryzymgApvqullXbVgRAXfNPrchzGgva
- LwrOD2Wjuq6f544l89/EDQDZ/vCSMMzZj9y61CysaJv7gr7MM4NS43duvDcNh2SVkixLXvFW
- WVFWXe3H/Ij5+0k5cqvofuBRanl89EFSdvuTQYYg7UxEYn/CpaRA1GIOSjT2M58m1Pk7SMjW
- MRLi+98xtYVGEp809j9Fb36AH/eU9f5sfNHtEL06qXB3lOpj3xUOoFDrHZn+JviWQ0dsqgge
- 51T9q/2QU6Ae0Ucr3drIdr/dHKuiGhJga2u9mVnr6SInsxmzYo954887c7i14yxPL9xSksVf
- /gPxbI2s19vpgy5klygYVavVLFqnJH63wYy6xznWXnXL2XtPu98GHW5PvQ8Mm0GWM8xU82LK
- p2zLvLnb7aVstm9MSgDTVu1q1g5NShy1rWl59q+GPQHd3RlpD+AWXMXVYiq0MjFqaNR0q1nt
- 4LzRKnJjXOZN/No2nb11O/bW7dyH4aZOxog5fpsvHQmEGoqNHVO6wHqBYrtaFkg0WSEYACtk
- u/rQwEFRcpq3Q4dnlHYoCNb9NSe8aQRkjb+ZMlGAdN3xXWSw+EtxoK+WyEoamAb7eBSu0kA9
- egX7k9d09XlcETeQo/3SduASgNbu69A1bvyi2DEyZZiKN3VOuPIxn1nVr6vxUZkC1OOyzMt+
- 94jikVow+Um/H8MJNgf22KTb41lA0I6urvQSj5aVbMZbqo66yAgclyPxnvYmzvnYdaGISqXZ
- n+5naDWHWgOsWo8kWs2+72ubk1ydcaxzoFJVDAq0+/RkMdhwtgeQo56fOQAOiYI2hMWi4jkP
- KYcvYDLhnnT7DeD+Nu3eXRjY7a/jlno5wWBXvEoq99iysKKgeBc4v31RPPEiHM8Z3QPDhuAR
- 7+IOnJYFo0hsWx6McZgIotvSji0JLYtYlwOp/p2mO/ZcPEQg2pxsodOY4Zc/9+51sOQmhku+
- hTSeq4HczwBjM3b8B+vSyj1sGZg41hzyhNNbdAwASkRV0HhIHGXBnCTx6N2rDMn7lrax0F2H
- c5LEA0U7pk74KE4JGm+ztTt7/SikCOf429iwU6k6ckSG/zkuEAwq9DWJtxM7OraGILw5iL88
- 9Skpe3O+goQR55F8X7DksDZDteNGET/ZPuYEGC7Nt1mIIlNSAErCJXsjOaCEC21TEiCUJpNH
- A+IasbW6hoMIVScuilCCRqaveP5uopdYNa1KXAf7WKLPk0ivc1oeR0UsXhRgd5hrvLqh2NNs
- WoTzzrXlx/2SxTZe47vw8L0acWy0eaozIo6xaBMNJ5CxzDYx1454uG/qxpLSf39T96PR4lfF
- KMO4zRjLVVIodNV+fIvpALLZhcjvOQRhkfOxP9P7xYwMSF7JspQliUSAByJZM7T8zK87jwwF
- fvFhc9/ZQGZFg31llvNMqHXC2w/0694TIFWLbXsV6WYbR4N/Dqv78Q0qq8alzlhecELLcYjz
- f5WtIFQ2kpIi8W96Rhb1eklIPh7s1R/x3O9v79hJ8MDWCVYOBwuglKrlrDSfU30sWTmFokGp
- 9HjXQXm7Iid3IzYK3eQTZXooryqPh/RvH1Wpz4LlAx73/Ku9q1WTlFfCXBH3kCvIDURHx2Jx
- SBwOhUKhUBhUDAaDQWAwiAgMImLOpKpTnZ30zumvZ3e+3xL79FaHkKSh3vp5kwmvCjEClDG6
- fYsyBKCtc8/VujYQb5A8gacgX9KYEBA/+bxJD7tgIQHE/wg+/nb92wW8kmzzaXd4p6j94Uyc
- 8C/++RBMv6yMMRTsaiqzPJMJDBuNZDUtzsyIQu9XCHwcQCGGQtBw1Aio3T17FbUphg8akVel
- TLE5snZDbI2RFKKyKtLU/HZH4Bg/umrMBf4WYyGRywaoJyaESCb0DfUqpST0hbVfQE/OEP0J
- Pf10ergo0OReQwzBEqYcXRWhMAn4SDBCEmqJZbcAZN8QZFEzXR80Au3XkPN7mw/QnKgVoRnh
- lbwd8gSgzRZAcBIGcvQ5chZ9HOr+uYinW7Ak77VLJHTTtgK+XDMDNFUQWhAAM87AaVGDHpuq
- mY+LCIq4DBsGWFV/0r0QZWGSQWnSeYdrm2dVrbiqqyxzXvi5Lsu6auVcMu3ipP18ukwHNRyK
- YLMhslOUiAplr1wkWxtsPfsHtJw8fTTtzdtcpLxZbwRxzlWmmA9EDTLruFLCe3IgxmEelXoN
- PSlYr4egTq6XA9R3XQPvmFsNDEXwczPjtUOdM2QelM207tbTZhx3moSlqplp7880tLnkQAzM
- +sWQN5S9azL3NmLddb9WV7fLIFpkzT4VELdjfCXW92FQvQLwJvHuqOo3H91R3Z9uUofKBbIJ
- 19omd3KhnM57h04hXPFqAsYMpFnmpm7app2Oy40EWoFgLTG6Rc3hQtengtZhmRrTE/1hwxE6
- p7LNRNmVPC37jsNbCt2W+967lTGawb2Mdmn5e3cn5Cn8+EXR9m2Zgvk+p7glo5ZgU93o6ulA
- 7MmQHsxVqwnFjzxJKl+UgOUtz3ueQq329hhDWD5zTJr6oG7aNU+Y3rXk9bbU7+1piRCDk5Bn
- j14m/Jb2Y0SXdCs1PKgch7klcm2vufRUjevYw5jZPLn3zGzLuu3b3Ca4pMeQOp6Sg2nMdGCE
- 1rkc7bVv+zlXjlBxgD2B+jZo0mE7365VYcCPtPDZ0DuojXPSMcGMtyj17uZ1q2AcBVxILi+s
- /54niSwy13jYvMlK3VNkRqx2YmJeNDNc5UaLX4Wd+wGj6wM+FlwFfEIDb4YJJgWDnM83o1MX
- sq72zcJDhfHJdRwn+BNsNJhvIqdwz9DBsuBtgAeDhWh8CCez5WB6ZrMqb21gbZlgziBcPrfV
- 7lDsDTImZmmJsG1dCZc5qIuDOiqkd4ulR2cZ66pqen2c13UsAyQ+n39aKMEXZtxOGE+atcu6
- LjdZTxvRE4fF+vRc2bdKVuuxGwsFpjqHnFfd692Tk5NqmIZKJLx2PtfWZ1KicyGlAr40VerA
- NrJ8HGr8seKAssrqvhaiWe95NFke8Lrx9ysLdQsvrelL4fhn2bu63GEkKk0ZSZqqZon7L2V1
- vV21kGWdwzt+1gr6j8SadRzGzdiAmUlChHOA86rbzreuqru+QtiKZFOeIDDmqWhWb9JZ3VUi
- 629zl7KPwtNzHTPm7gffbDlnKlNc5PN5o4uLss55IurJUmPVLFNDPoOuVNYuP34lZrM3mRRC
- 1uOOI08TOUZXEWO2aFz/D9DtG5WUBW4cuyInSAQEfIynMXS+piHQBEAE4/Dzz5knQSJaLW78
- +o/g42/XgxyN22PjQKzSO2iwfWGwqCiaw2gG7R+C6ReVMYbiGra7T/3kGiy26J2bJ9fHwPdN
- GnjK9PVmHfMz1x+wNUbS1zQBngbAajD/Sx+Qfpw2ejvNJIH+8wR6/jKNDzTmrqracV4XDDSw
- pVrMXoPvrK8HIPuaJoZXdEVCTyBu83lQd1ac4+tKQsYuz6BCp9y/TKgGXg/0rUsBdPuA+3sd
- WiS86co0zYahxFL4tVTOXljYkyPrvuRAbyWJNqggX+7yBOheW1+BLqSA8AiGIkXehqhGaXhi
- 8D8OJKbSJ4yhPk4u6YeKjd1xX0cfFmnfZe0UzqvhLkwdxlaCG/EDcLo7ytUCs060FubhMoWn
- h0Af+SAKJll3XHYbS2cQ4d614knKOQQqq/1sP7fCWL4e9tB5scfQhdIOMw3Q01H4D1sc14Yn
- ovOkcJ7r0wwKOTCmV7xezZilhfYsC1bWpQTLeEGp5/0TZHOvwTNv915FlU9QitYrjwLWAVs6
- +wHyFnRo/b7+2QV1GnyRpW9L9MLhwsrYd3k7nL0uDd0iTFi0KzKC0oQpxdBJoiIV/lJeIJWr
- hnNrsER8AFYZ1Mv+ffpufnUGmzegGsZbunp1j3hx3Gpf782aum71erxBDSRqWZrbAFgz6rbg
- FGihmGMb24zs780FP+81BGI4H0OGS40rzPJhLFkie3sn+fAy546waifBs0IkgVt5dbjBlKAI
- hGIAkrXLgoiOOEWC/HSXcNeGYml4eF4UoytnWmSWiQRfCrQSF0aPYOZ8+OrvTrmVS2PedCrB
- aAlIazDRbxeGPdMVt2c3F4TV9jZ3pjHKgq7usfGFSiftFposCejuerhudVS1eX93MPQVde4q
- V54quSuALoiE0TmwDcwxGOSEVpH6QQNdCAZZo3q36CYWxj8GaTaEY8McVrXsnUh8xWzPmahK
- ybK6lKqqZCJa8j84bCqj96iXiep0xe5PzqErSEPcboi7Yrvj7VFQR7nz9BYGn1ow2XRd6X5g
- 0DuG8/MS34K4Ve65ga3jSiopRPFhZ9TaKNksN9wRvT0HVUzUYYd7bfWoMdtlJ47Ysbf4+K19
- leUZWGae5Te35Dz205Knzrp16xSlEVEohMv7Lktla+xlHAFoy7izA2ZqeJoyzgVs4V5q5vhx
- bjq5ufN+vJzX2jvjHKGeKfn7aK9aFUOfA90D+39STJFQ4f02r23f1tXRTPZ1maY5OuyGWAPZ
- hr+IzyVZM2dMtW0usUxht6as1yuOLfd127Z1O63bWy5xa3t+s137kDsPo1EQTGLjY7/tXLjg
- tA8F9HgTffV2WTtDFcyNfF7NMQkYW3iVJ9xSUjtGt+9U2h5q7XlVKZbwUlt/tM1neBpA58sa
- Ak0ERDDpP/28AXV/x2EhCblZ/xA+/m49yjHmiGsbNWgVcs5YMQAoAwo/BtOvKSMMJU5y0Y0D
- bCZs1wupDSdskANCRwx836NJga8isAKgmvkjtkZI+pqG8DQAVkI0+gDQXK8BMj6Bnr9Og4GG
- lApF3gIN15JXXSXSvO0g1IxB9kVNDK+0IY48gajN50HduY3jYn9yst0yFElaTBBvzNuG2LVq
- fVxHrYpxxHujYEx5rI0Qzf529mla+gxTcdxp5Yy4FBTUpcEuFwqEfiIWsrPXD7k+vdqPULGM
- 03Yv0w37D/3nI2xeTHzEZe05C9z1BwLxVaLa+0g9o/Ic8hTN39y374IMq6xyseGxHxe2KRjE
- umB0wLfeh4KCh7liIQOk9PwBCEuyHUjIMKqjkY5VRb/RRXW+UYdkTrPPbXkr7RT9drPBdd2Q
- 1HWnd9BvpWBYPGyGKdw5NNVFOxODiOXTacbM8Sp06y4QIk3VfDp2TZLIYZq01kOb4YCNznFG
- 9twqji4jJjbEBMt2HXMH5G/cbIljLoUb7+GV9o0iOOiQ4nwquPFqt2Qc+XzBheVEBh0qck7J
- yjmubkGftYXnIRGNU/mRH2/+3nA5GJQ153I0b5vrdrzpwczNkKhhdEwIBJ9AV6iB5mFo/LS6
- tBphy1IfP7Y8Ms99mvVsUKXLxEdNF/FIQeaSJaq7fImVaJnX0qCTF9B8DPIk+p22UxO30w55
- Cq+ndfhYL3EqhHb5+0KiRTcjLMfRkGDlMZYGlsurAqV1d7kbnuwsACc6CmaqIN0ORraecVMA
- IAEDlosdS+5GBRo/o8ucFidFawi4NcERQQzb0/iJRhhO8FogvMcfnZVDo6j2fkIzQHcGDwbE
- h7yxN0ZQtkHn+KxS57pIRbNgtIyvz9II/IBzROhCCz7V8BXdAgSKWj67v16nLsDakJXTsE2c
- QWxG2AyIHuyhgrSfcS8F0ZvtmiVIVE471CBFE557cz8nifnCC4VYbhhxxIUuPeQsfq3QLUis
- LnlKScNIKCPw/gmWq1uGIu9Wa/3lBe0Gp8CVRIyHSzOd+8jcntLT7d+MtqKd6wAsg8eh1DEW
- jlRR5Opd8rKQLB922sFh4R/splMJr4ZWAYQ/2nyaN/Pj/kXetBOe2pfg3uwnBO586qYeVmMt
- jOJJAQTHR/pcfCkMIEWKsisErcxzo4BVsD6M4UVTuJTU+uPGVzR3i7NrLBOUmvRfwee+ECxr
- DV2VPrzq7HNGL/JDdPs2JWAEa/W7tuM3RolFW/sYT2PofFVDoEnI+/gzQQ9g4nkslQR78kfw
- 8Rv0gYE6dMVdNdLgLAoYG5y4GLSPwfTryhhD4e6irN6lnfYTecKeILNnwO6Oge97NAQKJzif
- EFbNmEm6YiR9VUN4Sh/C7ej0QXvUwwqKeQI9f52GxNYsDDTAA4Fq4Q6EYxOD7IuaCF7hXh88
- gR/axHvqTl2V4xFZ5MdixpxXi9EFD6iJfc7pOCPi743or2O2EuR2l3POmEfFLON4KAgJlPJo
- AFRbfCwRgmL1P8pgQWHHQbuvE4a323rPNS7Wy6+glwJcbXGbHYwZfvJ7C14sdHMYMHHfKxa1
- MZPyqm49EXVTcp78poXgPKsda4nE+r2i3wgM2ePy3bHqXm+R+sfJ93o/bXxp7jOsMMYMwl07
- d3XV9F2dZ9WAd1fhpgs7w1E3sKvVC88a9PTAvb7rkSwUrHSqyg4QipT4m4y4Ah+psHYPbpLm
- wJYJXDrbqxSMKSiDU1ISqszc+9xyv29nwk5ReHXC5eHTNeYMuyW9XVt0laI5MjrHORr/My3h
- c65hkUlYjbQ0rPUF3qo9RkED9xR2IoxRAZao/InqrOdZcR8VLI10Ds1FvBHg8lHGEUw/SsjO
- IsxeG5EWc2hJWK4p5Q8P+WsCKVUvAgqt3V3B2sXg8cgpKsCPDP3v9OZStL4BLAiYReIHXmsP
- 3ge8a9C+4fg4wYGo2YATZMV0X/9sDJVjwVyhONA0AnsgOgCWg1obfEWdnwsNT+rD/jjHtJnN
- x6AiH++3AJGgphN6rw1mBCfx7mNB1+FI0KsgWiA9GLAgtpUJ/dylK2aPWPgiIgagaUIxHsee
- wxODIfm6/CTiOnpF59N8XV4/NMsugtgZcARueFJxaIjS3I1217ibH1KZQ6t3622+2h7NdJ+n
- 7bzmRnySl9zHWnChlBJcVMP2yewOY/2/Twr1z4XLkEuwHk8IHZ2XpsEL/qzMtUhI/Gbda65E
- 3pRCjOejE722WBu3woPFaP50AkpPtcvT1QPh9Qm+otAi5bJdzk+uclDLK49nj9Ht25RwYNZO
- 2xlIQIkIImM8DaHzZQ2B5uS9508+N/dRpLJo8Z14Hh+/R6/rcvDGamrKYb8QxYSK28dg+lVl
- hKG0hgSXqBFM+DdPNSYGvm/RcNpQ5/d7m7kln306YyR9UUNASR8I0egDIXuAjE+g56/TBHS2
- eTvvGp6QyBFaRiD7oiaG11Z+9ATiNonRhXQHeKzrtulaQRLoS2LXWhQ61Fznef/W5zDDby+v
- Cb+hLT0NjDXzZavnRYZFiUjGQsSThfFdf3TGMAUb6aNp0jyDQ3vs/+/7tPFyxUKu5++VC4+a
- 7MaxbyuRAoPxNbnOx1N5vbNnfzizL40CevC3/PWnJ5vuuqQy2ud9fv7Y0KNFq/v9MmTB2YPA
- BJMlBKVpgqXUr4h9NLNHdoU0D18b+7MVWvW0HWabO9p8+OlgtpIBoe43PDr0vwyPH7hoRnQi
- kKXkwvOvFxisX/XebbX4xNEnenCiqv6wH0+/HJqSoa//pwrxuhcbJLOY/NKDSlvqNcy0lKlj
- UWZw5sG/RWAz7fGGzHmqLE112fZVXh8R/WfVFbDOXhF435/+ytrPr6rShBXdpFsFLvVfXizU
- o+T+lx9ojI/fr4/lOC6PrddzYPq68kkh7y8Gvu/QXKiKnSt7rLD12sRI+prmFXf7KfT8DZqH
- smwGlzAe5hc1MbyqyBOI2yTOlyzeBf4pqq9Djj1/5d+SpWPD4Rjov4T8J9s01FVZNe20mr/j
- +FvFmKqWv97YL/OP+PP69BfGo7k4rfk/M5Rpkt5OfEhkPX//4PtcuFJ8yp+pZjjyI+xb+60i
- GNLAYjlrwYnZ+P0ik4T9f6/X7vPYdiMFdXRI+ti1w/R83fY3Pi3X1hfVcAVj3tbNfhm+lqED
- Xty/VEoh9dNm9lo7wQRwUv58MUufCSFkBudR/aWF/uBe0U6/91H7T/6Ta8kFz9zRKf/J98Mr
- eQKftfkf46B1FgNN0KAAAAAASUVORK5CYII='
- 	) base64Decoded asByteArray readStream
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansOblique9Data (in category 'dejaVu font data') -----
- dejaVuSansOblique9Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Oblique 9. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 9 11 3 0 255 13 0 0 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 11 16 22 32 40 51 60 63 68 73 79 89 93 97 101 108 116 124 132 140 148 156 164 172 180 188 192 196 206 216 226 232 244 253 261 269 278 286 293 302 311 315 321 329 336 346 355 364 371 380 388 396 404 413 421 433 442 449 458 463 467 472 482 488 494 501 509 516 524 531 536 544 552 555 560 567 570 582 590 597 605 613 618 624 629 637 644 654 662 670 677 685 689 697 707 707 717 723 733 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 747 752 760 768 776 784 788 794 800 812 818 825 835 839 851 857 863 873 878 883 889 897 905 909 915 920 926 933 945 957 969 975 984 993 1002 1011 1020 1029 1042 1050 1058 1066 1074 1082 1086 1090 1094 1098 1107 1116 1125 1134 1143 1152 1161 1171 1182 1191 1200 1209 1218 1225 1232 1240 1247 1254 1261 1268 1275 1282 1294 1301 1308 1315 1322 1329 1332 1336 1340 1344 1351 1359 1366 1373 1380 1387 1394 1404 1
 412 1420 1428 1436 1444 1452 1460 1468
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansOblique9Form (in category 'dejaVu font data') -----
- dejaVuSansOblique9Form
- 	<generated>
- 	" Form data for DejaVu Sans Oblique 9. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^Form fromBinaryStream: (
- 'iVBORw0KGgoAAAANSUhEUgAABbwAAAAOCAIAAABrfk3AAAArCElEQVR4AexbrZ70Kg/niriH
- XkFvoLq6trausq6uqqqqCoVBYTAYDKKmBoHAIBD7Tpgtw8x0553zPHs+f/tXOyRACCEJKYs+
- fvCDPx8/+MEPfvCDH/zgBz8IO0EI1as+I3raFxfqyPeHdtJhFFEv9x0twyihEC7vJGGsnq4N
- Qqiz992GCw1joHP7l6wuX9r5ul5L7tQEP5iBWQyvYLl9MKxEV5SGAjdRoJB3RJVjgRJa9kDd
- 4txkD2eL3KLUNTf3VKfaY7xl8znF0DbbpSmnOTnAWhmrkxjfhsA6kFP5051iBahteFii38ih
- l0red9RziRBmCra4oeahF4YeE6jkHw2ztLCKdhZ/SNIf/OAvLZpYrXZ/f2KdtdbdH9ZLQ8Z0
- cLnUeIpgBRfX/lqIzYW8N/z6axC8u8C/zw7r90/ieQft3yD2oWH/5lA+cZ/J+Q/INL5JL+8r
- I9+d7x8/afvfhaSZ7+dP+5yO/L8fbpMcIJ+c1nZpFZyr3f3aPiw1QvX8/zo7ybm24RclV/tr
- Hrspzvlr5yzZmQBu41zdz2XO+RPzD74TwWjJr6oOhhGibqmuU4JzoS6U/x5SVPw2f2jzsBR2
- JeRmvdFC6j+UPCSh/jI4aw64FOv9HwlJ3uVC+9MAvVO4EP5FO+veiajhgsc9NC68z3O+2MTz
- FnY6Das6vY2PbUe1e9otNXYD370Ry/Bw2fM759pdKIw9RROnOJObNYpTrsO9CC1Ci/mQPUYd
- /95kYKPTsMjHZq/HtiPaPQg4tH1c19zPPGQEyai4Ss5uV361DiPRID2buoFYmGvsRuY+HBl6
- bxSlwnorKHvr9iy53J3bJGPSnRzKfW7qOVEyGD6VVfdM8Wqp60GanY7Dw0rDLghTm+Ir4fax
- 27bOq9w2QZnMdvBt15GOYdBS+0eGfe4HcebNo+ro83yajP3Ew4ddh4HdX9uuGjbOCMqU8U+9
- mH/HbIyGCHMvql4ahOpcpdkKaAnJjrrpn40I4butcWoeBqrtzuf5qMq56I69N1LIJKwTA9T0
- yIBQwd3Hb2IjHUIVs6fmxWuEylGkBismjNDATZ4HCqF9cEqI3QUxVgh3W0hrWgqErguuEGpm
- FdwuhLLeaSGOETRn/LpLedq8sWUYifVmGec04E47hEpmTpO5KO3AsxM4Y4T6nNtvyzCs0li1
- TkQfbncTQrm4hO03L2gWCqAd3b8izw1GRX9H9qotUNnTe86rPr2B/T/ZYzk3CBVkD+c5Z4Zd
- CXUMdOFAdGzrJkPdEn02wQgLAUG9rBCa1L5UqBzlvT9cMG4uWlRTXfb8OUD3l4463AsNwC3x
- x56VCJWzysYkFTpQze5TRdOFK6umu6UG8tVIu1iIjoqAudSAUS+PX98J1mFUjC7zPqnYP7A9
- CxJ1UQClnrIDL+YqcSM8UH3s/owytIt8CrR9pgrwkA3KkbkAI/rbHAXdw/WW9YBiEFfVk/5G
- qwfqs4ps2gCy+b8rzRVTezOEkec0tyuyTH3XtW03zGQ7M33LB1hsR1OLnCp0A6771d58zZTt
- Dirb+Zm/6Zd0UMK2AntO7thZe/G5iWKpM0JRd1TbY4rsg4CXJULNoq9DgV0Je38kWzhPDx2t
- aAsYNlrHkvfKF46b1d9a6rjOMU604LiALb+ZV/OhmTu77Vd1okxcQcR6n79I/NEOhzrX2KKc
- GEp0hmNbc1cAn86Kgau5fvxCYijEnqAaiAriCGAjykKaiz8jL3iRRfvcUzWr5vCVrLpNt9MS
- +ANtMXpEGtZPn+IXlnUID/YWkKbE+egVy16/9lfZCD0zL5k4eMRf+ZDo5xI+iL3gUEuDIl5H
- wVMB9FxlHT14Tzx+xb8tNRyffzzSnYeA8fyjwcCYAeAfHMf512YvqyPmvrmMXzDglOhiYKff
- Xp/xG52Jfm68+d5mfakfnJ9WMVZggWGbup6mOOjVLcjiITbZPuqNDmDQWdGPdXVxOLyOpeCR
- PM+BWbnvK9ey/utJo6gJRZ6StYt6Z/ipTBFZ5KlInvIaPoKm/8+AloxtgdGBRr02uyyIwB5l
- t4sIPAnzRq8EN0Nbs4V3eU4Xm/O8RkpIqp6dkcavToSPd5ii52exYIzHjp2GCeh1QvLLEYdH
- 6U6Cyxl6YV+kSW/nQql9gXOC3+eH9ilKC1EetzqkANFsn5EF/tbpHp6ned2UKsHXqbMLWHgj
- 1XmDVCRaOZIHUpZ3nw8YSdDrTVgyNlnm1Q5dhRDm7uNFdpRI/EtSIXwi+bFAuD8lubEAazzP
- i+AclWkjcqilRQn5BdhJkD431OxiiJrFZSUmlCJUlq4kNORzVB5f2TDWQ6Q7jNyJ/tLI5ZJ0
- 9VsIGtbTkvB0hOrru5us9HO44/EWWXr4TejwmfYYVkAnmV7uFD398PpQWW3jkmYBpEPhC1DK
- Gpw9HpJ5o0wfcEwOQhtj37O0TbRZk9WlDmmHozEQYEq619kSMGEjqIHb39Qm7fAXD6PcGkVk
- ey67GY8Em5rcVYIwPWXN2dMtvbZAZdvLHPX8vRsaMOoWQgmAUtqXkDmdR8dydNHcCvBZ21wi
- PIjHJBiP4cMPGLSZd+dzV6Qz0swWrGe9Fhd21h9X/T2a9+Kz7DOqqONKSzo17eJSeDieICa3
- OGufPairdfiY4cCOI3yMHaf2Ifu3U1Ovv5PXGhKPyZYHGNyMQvK+hGWoEBWu1wJX17xl4PmN
- t0JVt3KpxBpzuHY7Urp+mC/NStK2OMbJyn4IkNUCdwL2NSw0buG6MhOy44qqhQkp2Nj1V3Vt
- nK5r3Gu2VlmKBmEGtEX0puY48bqHw3xRt3CtaIPhQJo/fgbefEzhX7FtLcb9wpTiXXSfyQlF
- aaNZtX3fff4Y2PbY/Tj8NnnYKlobpZSs18xyUu52DyzalUutxBLv8Bk/o3Qdu+rI7VLtFvXH
- OSLrSqV5aofdOY4ryLswobVi61ggVE4qTpFJeFTQBmGPoXB6Jnowjy7728diHI4GsiqXelHz
- 9Dwh94OGfmqwZ6kqF7Xhk+ogZCbNlB3hUkrWRx303OTKIcu1wtG9z19EfpMKkWCHq1RK0LUt
- y0k6o9i6Enr5CRZYgzoPZYqxvCuOOFHGeGPFcK+usDbXi4HpMRQK86S/HERmEu1V9TUIuCaF
- 4Hb1RxGqHGV2xGrQkYBjBaCMHhePWbqUXkOXB8d1KB8+OxxNKvbFRXndj3eSbzHWRUu+oqZJ
- 2a8Esr0Ds5IvnCCYV54rnAtw/j3Hx89ut8kEZcoeAmdGm1WoP/4VMDTmZ//soomX8aSI46co
- nqqrfCjSvfEd/IIBWzlnyTP9XpXtpMYdfzZpONhCSzYPs4jPRO6kNMYeGSMc/GULqboK9Wsn
- cHZv1OBM8SJ3s4l5psdLE6mN90ZLfbhYHhPimXBxAV/jPadne/axUa0r4YzEr2jie8zw81q+
- SKW0Umzp0qQJ3h5w/iMo+B4mdgPJTJVy1hf5ktn28BHWGH3g5FrrrGpRlhkG3WLcEX0uYl5r
- ODIbClHjLasL3qxNujVtDfRm4cMtFYSZN3olOy/B4ezhfZ7TxeY85zhNSP5O0t4XL3sVdbzM
- 11lqs0rjv06TznOh726HyJ7nS1//HUiLj7SNTF2NABVE5l9Mdf5SUrDb/ddvr9V+dyojc9XP
- Qm+K9vkn2xfZ0beTTvOiI9UsFsYZZbev/Y4Xh7ffWZ/f3a6eFh9llCx5K8qOhPuWZpbe8rps
- k6cSy6q9l2ReqArZOw6lTfBG6/zBjJkbMP3v+vccr+YCP5aHWF8WzeLzckBf1SP3TjRlm6lx
- BwmD1frzlcbOhrKeL4SlKZuJh1gfLOAzpxmKIlz41R4+vJag8I30BU4xlIVMlSvVwap5nIXx
- D+8bCtyo+5XzvsTN4u7kr6qBey/bshEHQZFFGKfZMpMsk40i+eA2rfOp3oUzxuXbq7uigFOZ
- 4YjCNbeP1WdcDnsAXY0ipzkllfV+12qz/qEPlCq4eUyS3XnE2CCgOwcDwfhoKEqeDSiH8qTc
- ElSdniTEpGGUeipSZAqKUcpIvM22lE6xTL4wJmxIn8SLDsj1Sqa6nuxnHaiDmbb5QpXBk1jI
- 2e72Fs5kuWRt6W1VKhBaVlyL0ID0DgWtW/gIlqSCZrvacDdEkVKfX0GII3d7KtNicLd7KnHd
- XxIs79M14BlqKhN/DjEUedEk7ATHKAYTM5OP/HwjisWORr6ooV5H61i6SMdbN8Cx9rOC4JO7
- vMpZJTk3QdbDMVnFlnR+Mthd/a+9q1WUFFfC54nyDjwBL4BGY7E4JC4OFYVCoTAoDAaDicBg
- EAgMImLukI+iq6dDb8+ZnrM/d2rv3u0TAoSQn6+qvipKaY1lLzA/YRf0o7Tq9FN615zBmIqY
- UvBfNH9+01reRDWbe+eSF0U+7O7nBullPQ1wac0Tq7Xl7c/Mr7iMI99QOaSGhdEa2uPH18vL
- +Uv8CORd5XUaF0NN6s7iqYyg7kKBubcW64g8TjjRz+q2iA8f78oawM9CZayw6Ir91QuaIiMh
- v11wcWj1ST3Bbn0XDGJgWSiOzklaPk7+un5K9aUPpwf825jLDgFlI1Dm3pgLyxGf+7JbMbwP
- JRBrIkYyfCNZx1ld2OzR4DOm2nJVRKakuBsPprTWxWGdMo8IXFyMTn24OpcHswjuCKMJ8zfS
- K+5VCK3BnF5TkfyUXXespU/bZ5iWMx4Elw2DAx3X+sbeKjKq7xHSWqosOvh/aQxTLya5jIh8
- kKj9oZfm1HSEF+FRyzSkc5PAC6BlDbCQRSH3ywEQJKU+98PIC6txw/ghn+FaZ7sWiQUWA0YX
- sfDCJMbNfdXpVu3tBADCxVAnTfgdEY7SZaGPylFWLcStFYIuyCrzrgjjGI9jm+2JIIqsMrGP
- 6UremHhZDd4EzhIi2JfxPPTiciNKmi/CbtmBsgjVcmNnxMJLdpap8FS/EhLy8XsoYhHI47lE
- hBeyDWUgdrLurnOGnv0BmbJAhLJDufB28f0g8HeUyUEeLAKXRhN4oYPitQH4mQEMLR0ifB8r
- MF8W6+JFaiPeeDJQ5VXXsS9ouFbbbXYqu3suP2y+RdvVZVE1bZUzBwz0cDl8M30AliLrKLZ2
- fWBOXQmUBFnX2elN9vNJF/tmistsfWi7IAr9e+aCGfUELvv4k1AUNy2GEfYIWOn1QDd1iw53
- j9qg6xRup5uY3ruwA4KckvcLzdxdyguoA7AOWILxuTNQ5upGiE2qNvdfy+mA1RhWXaz8HqJB
- mhjQdBs6C1G2qR9X11nAQQl3aD2r0/E6/GEvrwNpZehBG3kGSL7+EFZmcRzCu+VevX38aOnR
- zs7kGia5sdD7yjkQGmNCC9e/51TsSgnXu7DLfw7qfOWhHfB4ey+385n5xcPqxPlQcamPo6nP
- SENP0dH7DzlwEV4EF1BilxZu8q2VIYjWtjJDL8IDeqFCQYUFCnUtA99DKfbxsxA1Y1aIirZm
- icLRFvLTkdslDm6kvKptsujozxB13JCJQyMRAhpRIW4RsMI8CQXBs1vN+CwsbOFaxIBGa4kf
- BFQ8ohSMZYzfaHkax3F0PNCw0YboxzI7fBhZdQ+BANoknovjIl7Yy/h4hDhvViqk1noJCnE6
- 9UCcs1Av2toInHBZahkf/RPFdlj1HCxhSQVYel7uJ9WJtAMvYvUrQzoXyh+Q0gykxEAyB4GO
- +jL0QtntRhNuX+nSe6MJ3RWKOv5QSdpMS6fSvJmIHnMDioQX9w4cDOWaiqqpy/y0v1eS/Xqw
- NJEgr1XI+V33UQ8Ba5Exlo6RpJgABnSdR+dt2i59mXqcBHYX6jL4++LySc8W9oyknjkPKiY+
- 2Mb9yWwDGM1FqJ5FUbdQj7audqO41TTy7kb0Ap7qJUxCZFjxOT1yvidXC+IkVnp1mB4YA2q0
- 1u44r9o6D5AXikJCEjLn1LGAcku03nQFtrbMmvFmNNS1Aj5EGEvejat9sDoMgvAHCfwExN1t
- agoZ0gsLE9n0D4B57UFYUv1CdqtIU5QgSTCYNffI7A0mhZ2Tm0XMatjOQhHJpiGyg5do880O
- J1GxvZoNKiIWQYCk05YIC76qa3hFKHKYyquaSEBgUngO8xmahMiopgZlQYaCDHMr6Cgbt3kB
- XjMSHdQ2qoOzHgj2QAZqb5rS34wdTlCPd8suTomL2sb+TDBQ2vEGpkazPIRviIzQxozxa2dd
- XMXCXd876kflaO1FbSRoJzY6PJbjshtYaCQb1XitDssRkc6gFYAqQpWnlMhceEAYy0p7crlz
- vgoMb+5FQSDPo8Pc6OKKSA9+o42zXRhKg1mE3PvANI6wR51FEWfzmrndS+rxdW9HlUapqvqh
- r/MYKii52na2XdvV1osFfGyQkC9I8qZtVBLEhcZyav17TVfLG+Nxu9HWmiK1aHn43r5yn41C
- 7gzF9mQwJapuK3but62MjgY0bZ34RHpH6Fk1cjs46luedbksvW24yJsR1tu4nvjjNE0REhwq
- 2zoLTl6eKVEn4HeEe8Gi0barZEQrtqkTDzOn7ZosFKAf40a8K9A8OwhRvaiKAqgxkmXXd7VK
- 42yn0SbCNqlp9m6BPT1paNbG2BrGMsKPc0r6WUcK+Qp13b7BDaqslwHWHx6CdapZ9r5NBdhB
- TkUIkWVmaKqyqpumxCYRFZqHO4FNcG00sSbp11kPnxrA6zjOc/e9xXJYZq352lXG0BDMq6Gy
- H+lM0Q12O7TehTwLwnzhT433y51atFWdsZ8GCSdTzGY/9I8ht0/3lXXUNrCQ0ezKvrM0iYir
- bl9xYUIyyONWRyKuZ+KKe8286YpHBc5FLD68fJoaHwkX97D8R2n7cXHe9COsvt9Lio+0WzG/
- OvOtwU0vra4ZgGyGt7aNRZ7nSuVYOOJMKZXnsmgnYBcLNQOQpW0GEPjAED3htG2xqElM6mqC
- IwESFa0KsDUcCULGaTFPmW4w5QCrFMOyDIWwawVQiq+GdZCcAEJnrTDiWJJ5T9BlWjZ3nVD1
- xqx6GPQ43z0sQs7Hq+sQDEAw7BNA8vWHluby0A74LePJdD5QRVNXVoDlLmGSGwu9s5yAEIdk
- l7/HvvQsS3SaptUQisBy+imo85WHkKoRO28zTrCYxOXAbSuECSdpQXjT1z5Wp+fo6M2H3LiI
- wTyCRoE6Mu8KqQe+ULjRy5cVWpymojhvur5vKGTNi6tuj3CA8uuETG5o9MuFgEYcIwGb0S7P
- f08ygG8gy5IQTf0pCPRbCm+iY/FoNNlArkrKtrYKLCbgBVh6Y7kbKbHu4iDwsv5LRhP4aatn
- tEPsH75GDpGwfIydhk2xaAgEmQkqsgjSUtk8JFJGtiL4SAY6pLBFB4ljYq540pqYyxqyklmh
- U1mlly7zRNotutq5uKvOsyyTMot95JKQUmZZqh6A3baSbMbh37B3nXmGbVAw2Etq16e6610U
- btCwDHws24Pfb4xFGeTb4dqKzuYOpZRF3fetSgJMORYgLfK6H1rls8A/hl0wuyArxu4p1Uze
- KjuS+nGsZchehNFd0xG/YxraphuNNQCFZNaN05xbPWCPlGma/SBpyvJZkM2lkBHZnNNK37NM
- w2bczn1d9hvwSpQ309RniCjeh7E4aVBlSAqz6X3aTbFBcgmKvRxb8iPiQ32l7zEHzBZY+Jig
- t3k5MTvY9TFQYWcUYbeyJjFB5CHt9B3nLpHtjJ3o58ZhZegeWVrVOCTfG1/ZqRmXXRkfujRO
- UdpYOKhGoylbSir4KGJvJCzOBvi+dxJEM++ifqD4kxJd1h3cm7czt1YQtYcbgDCMOcGKmZmi
- EgZB5gPEZCzWpbHnTnqPM8wXO9Tv+mrddTmX2mZgBchwX1YfOlYxrO5sULAUAIvzGKuwMG+L
- uZj7ttnjLCtJRJspFYisxIROsH8AKIf3mxkKQTjipl545PJ+3vbsvPqMb9IsjBzmA1jxyAKV
- jGdABJ4RE1PIFfeiCUUO/xj1U0EqrJf0C6NF7JWnRJxXg6oMlinS0FCYp3DcsUk9FsW9yoO6
- Mme2fxbqH2A+NA+PgxshfxDKo1Jzv2Xa3FnVdswVVTwK5oQRLdJkoLugqJCPTptDIZfDNoMh
- efwG3YzFv0CsXRuilbWAGMwIsrCQNFnAs1Ss09DWuU9ryxOjSYwsUD29JLN7hzxKw1S2wzSN
- VRYgf9nn5TQVMamO+/gylzKTJFmaqXG7yOy6Gb4obUaHAoOTbawkzEOzKfuGDCLqmXOoKsoy
- T9CMvKzKotoVRjP44KgegzZZLOAWCNNwSZt4sJl4cuDlY0HRQ9uQ+Oeqt7PNt7FBlqkoDi16
- L2YDZ4xDgH84YsFNw3KC8nnucIbd9AVBLgzhCY/8sjtvSdC60TJrk+zXCHsZrMwXF6xj2Mc5
- 12nbvW70avK2jXczxEb1gYLcbbtX0raKaG4J5R8dbZqASFXK+nvqaWNneaqtI5oFwMQARQ91
- QFWwrCgkp1P69rC+nJY+dF3ndIsVaQbQcgVI/p5DET/EVZ1l37KE3bMGifd7Slw+g0luLPTW
- cgAhDsme/KaTGf8C7Gk1fA7qfOWhc6DH9AJSpqcAPabtaiPgsG6cjOnlOTp69yE3LsKLKACf
- AAOCgtbbehly+D62a/TydYWwEA9dbUutiVhU42JD8HRioYILMrmh0S8WntDo/EEduB/lv8F3
- Y5hzBSH3pyDQ7yi0ul6WSSZM0aZMfMu3DTZBLCYXYOmN5ZdIaUpdIPCq/ktGEyDa6TJ1cBZG
- EbwxQRyD+vO9pLwpD2a0mTuwy8SERHmymTjfWxfmTVce2FfRwg3eo0jKvk4JaDK8ReF/3CLA
- uSd7IuVmOnPOecLzd4FBBj8FACWX9PojZOCVgGnmCh3csGmO1x5yiK5SuNWH9TLYGyoiIHRS
- Nl0LMOkV7SNtBQ7Jjq2nC2W34jGr0PaxUvOMjEJ1E5Kq+Md1EOoSfXB5lr8AmgD5fpt+2R5y
- GLSPAuMLFzPrTqUBD51ge6E5/wTVpc+8D1+hdJD77+93SomBSfajQOa5TMOTitnzV2amjGyx
- vutN8fp8mIGdYUamzDNxlksPPDQ8Z19VMHFGw4ZbMJYsxUa5LoXKYb+dTFovjgMLEIcrKwM/
- UQNO7eI169bE9vFxIygwCPmRdREdMNe77xn0LXYRNCDdPZK5KmpE4V7X16ivmq5r7FzBvstk
- W6bOpnrBrZkt8i7GbeWsq5OLGx7gtcVWsQ0BlChO+wpkub/yaDrGj6xkwFRT8j9TmmqXzTRb
- ednhERKl5sVYDahJZLLx857ZfPHnG2Ss0mPKBLA72aVybfkKuR7MWAyDSJvLQY6WY5WQvivH
- LYYQLSOd9Nh73HKf+nxBA5YzqhEb5FjFuBePBEF9ulvMrdKojMfBDgV/AjRAnoADdwS243eU
- thSVb/E+a4fKvH+a5Zgmg+HNUxuazSapmdtInOEP+WgOtlRA05CZe+4dIBvuu5ghZ6TFOd3Z
- zl26T/yd8heXdSrug0/7DKMSbeB3Kcf5tL+QLEUkCG2zt2zFNvfaaLINqEcXBJgQWVHVZQ6j
- NloCy+bnhd+a5JZhNAh8JsJzxJwyQwblSuvNt0n98FHPqS/9fWvKu75v236hnST3TnvHFO2T
- dbQhUYkfhDusQTOiMEwrMh4ZnkwtzJrNmt6ujCZzE3tJ3cr9NhMuYO0aTSyiej4iXISweMTz
- 43I7Ht9rp97uWOr2oPdiAdvuE/oBseCmH1GD/MpJ06vgcLq0uOnPioG1d/vBUDUv32WebUD6
- uszjqMdpdiMEPunuJzVk3pMy+s1QCTa/uiJNoFY5c5N8l2XB3fs82m07WJ3OgCx8ktaXTYnU
- hyOdta5zH8MJxGyR2E2u6sA2izRP9LArmNTu61jBBIdN8BqQfPmh/vLQWMaY9bnKk9AjLM3F
- DZM4UPmCcr5bXf1GpDC/DLQJ2a+fgzpfeegh3bIox+2HrkgKuwb5GYZbnXgwRD5DR+8/5MZF
- iPDKm0H3jYxAP54s5sH+uIFLiJxoTvTyZYXGfpgGKmHgO5P69y7I5IZGv1hI0OgeI62Eo/hv
- N6rpfgoC/Y7CTZf+oV3b2IIg4Ip2Z6Ganhq7jDRtHgC5ucHS28qvkdLaOkGgs/4LRhOIWaZ5
- vaZ0qjSNENGV2rkRpVnKMsyjVvgRjRvLZUAPEdqSRdvcYzbWCflKpIftH4icNLykNg/eBjwt
- T22Fte9nQQCXZZrGaZrGkfEsWR5NoHOSLiOEDZooGB/MowROBL8I2OQ+cJhLjCajCSAUE3fi
- LnC8ZQ+DAkt0sqQCc4a1n0eI4PreSVKYIk5qAFRDDnzsMc/FLENbss8ExKru5s1wk4pLAUP+
- vDZPSQcRfqZqzUbdOpRxDJxPNgshN8xALNxrH9tJ2NGXU2Bw3d2i4T5pd/xNkSCgXW1MlcU7
- zcgtz7DZXovVh0mr8Mg+OtWJI4eQOwmrw0VThEcJkrk+ZIFd/yILLJ1oYB0jSz+dxQwBrPIG
- Y8ExYJZTMcONcEqb3kX8JoJ6gJkV0M/nNbmkrvpw8PLGL01KYbFcMG4xzi9j3DSR7fmUiauR
- gXKBfOKcSIy9HLiEODtwUNY8HTfAx6AC3vNk5qfKHJp/BPXkTvhHZhFoaDS5eLqTd4j1mlaG
- nhGvBkCHFh9T0NLfSw/4hokt/EgXatuJ5yTa/DRNLDbChcWOwd53n9V1SmltaRJ4PyCArbf6
- SRpRcCL/Ttn91baOfZoOXOv6yR35hoK1KG1m/OD9g5X8qit4s/lHNxsZHsv1VLHMguC/0BCd
- qxtdGQmJU5X6mP4cH2NarYrm3zl6zVh5KGPTnMdjMms+EXd5eh2eWQmtvbZc2JF/l6be7Nna
- 3B9cfavRBIUaSzde71PhtB1yb07fljrys/6+4uCTTQTC+9yPEwteMKLwmfCuAklH1V3Xtp3G
- NhZ7PsXlbcypgFhXl+ykNqGaGuwZzy6M81yfo3SddD+QjAt9+nHneFZFQmuaW7p0NyI6EItl
- 0lXTrPyPbDDfVhvjk6UCN/1JQfYZOWy//qK5LwcbBLMGpn2bIQvsz4i7D4FYzmxFaTX8+IEG
- YhsNdh+pGmXfiHHVIZ8/xcSx3HZPrzN3kWBegStA8s85tHY+QtLCvRT47PGtu2HSNRZ6azm2
- Y46XLn9X8Z0av+rKB3j+JNT50kO7EAlLVnXqMx4rC4fxkpKYy4q4yU/R0fsPuXGRCu9gflZa
- /hfbH8FIhRfHhV6+rBDpIyNKB1yQa5+LGzIRNHpjIWEM9oOhGv77Ry/s1ucAIT8FgX5HIQfA
- Moq4W4W7bYJd9ZtjDNprsPSecjdSQpkbBLrrv2Q02Ybd/fIX7lC7p+4pEjIePIJZISJZV9m+
- emUR5YWGLLmPBQ5bpt/Oa4fwE3M4W2Tdad2XtKjxcFxgC87sPc3kSKL7TFYXUFsan39Am6uv
- 0OvAKn84cW4ssinacahC9lGVbacS1EiVH+Vl3RyvRVHen6ptm7qu6uNySRAVdafHsavzgJK5
- uJPLWCmTPQmJHsceHnts3mSE9pNynPApHHQImpo6OGYpchP00zSoxD+WQnxpX9WD1o1KsBxv
- JyfNy1iaSQYsGMLuKgWH5F8ngkVcN+IIs8IVpL2qUCAVEPskRzLjiSiMiySoxw1t4ws090Ic
- zPO9//HpHEzgI0eMn6h+HJETHuN5ry+O+kgQdaZxBsUuLesz/BaZbKHkPzjzA/uQeaf361f5
- vkXCVXhmL+PxorSpX2eBxYkpThztjitgZEXDsrJu6l2qul3MXhkcM7OMfT+sZGfFsoI284CL
- 0w2OngnSYhjHHukkMK5YA7g46+cP9Sn5aw21P5JF22s9tDLyKWEbZHmMcUML/VjZWyj/0Db5
- UW6V468ANbnPTZSEhQvGMgWIFHHNV4mzuyABkcLbpq4OaabtmG/MLEJbLz3FQsbNtwg+bqfn
- qckDPPZCU8CLlZ4RYQedkDjkRTtNY1vmeU2oaB/J/Ty2ETTzm9E2KDs9TbqrVQJT79JwxXss
- rZlDVl2jMBVlR7khuUWfTuE+Z1wqu9WPJ5bljlVmV+MJv2kURaW+viOoi1Gjp7FFjtJsJrKA
- Fyk9T+ifEyBC0ZrHNqSu4C2BRFHW9HqivlV6Q6vivO66YTFHt8hGj33lkV+LqVt2to7mToHH
- DMUMArmPZ7/y0gn7JhkQ+fdHOKMKZwd5s69kfT/OG584sAk6LRec+4M7/F7ht+ZidBbG7fzX
- TdCKcUvxaYZE5eGHSHKlmgMJd00how97aN9zq4MQN6ArM5nGUZzKLOKpFnng7WVr8V6QJulK
- 8CmQrKhBrizz56aQ01QXaMsDxb5wZSzQ83Z1U8zxed22belKuunrso52RUNOrtL+2qXpf97u
- glGHtWgaawk3m5o5nTmmLLDvkDr2IoUkvgGWYwiAAZuJK9fuAAPu68D6oWBon1bz4nU2XSIX
- DsbwU0DyTzmEFIE04JfMs7BvnzBW6h5HTpg0TPPIYJIbC72xnAEhjiKufqe2/RZmVxLGM8TC
- fwrqfOkh9kFo2bJscdjy8G0sK1nVT+NQq4SC+56jo7cfusRFeBGGEgDxL1fIsu6GcRr7LMBG
- 5kQvX1eIb27UetJtQfazuN5bqNtKJrI1J2Qqu2WZAJnc0OhXCwljsB8M1dz/xhVE3OwtVx6+
- iflTEOj3FEJwd2F1/h/2a5jR9DwAjINC5QZLbyt3IyW0xwkC3fVfMZpAbYCi/nQ79Hu4r4mv
- dRIsfe/2GXHVjExXZ19jRmAeS6O46SoULI2rRAqUELOUJ0MKuRkJVqsXgJrPoQ/D/QBMjjQQ
- zLxNHcZZ0B61NMIeSYObCaVB8XkhW3oiXubHDQe1zNyIRRON4fU5MujU7WLsexBjQvPqTpYu
- Zm1KVGfYHn9mkD6fOmfeUenTcz1BdWjYUzHz0Pbjk5RvmYCZgEd1EVlAt1VZ9eM8VHle3QYI
- jzSmkxCecP8KRCDLnqqtVRbyY5FszP0rE36QqptH6oeXjCGEclcim7Wm60OCWPb2WhSGx3EM
- SL8Pl5pKnnCBnwgXJYw1PzQMeoXPLcHMJohlhaIq+Hd2zvG2IGj8HOfVsDw0gMty35NBpVdX
- /a2MDppPStnLyQrRGTbTIwcleENnuqfM1llHu8tuxcAxjCaCjRPo6vzrA+g6qk9ubVb/QWDt
- wtIBmzczmpD3YKB0J2+RLg95Nm4o3kCfWEfZ92WQUkrwSHUKn3Y9ha4CVu6ntTn6wcNQwgXz
- yL99BwWkaHhLfLWd2wRlZAzYAObMOFbf1KmP2YTK/CiZqoNhI8QGNeD6jmaqg9uMT4eV+MxM
- kE7L2RUw1/Nms1fPl9kJG9WhbM+Nf/YbdyGeCdsJ37Md2m8WGqhstYfGrzeas3wSIVyZGkmz
- jAsss9wgG+pnlosxwnfQv0CwF//al+zYHmTaPOapEFby6TFhOQ6WoW7HOz9M029sEcaVnR3V
- KNXqadYNBcY+k2WoIv+kUUblK3YHY174GP8LN4V4uOlPmjlcgof9WYFDi0TQ117XUz8MVasC
- wDmnLG2Fqfx5wYLvNB71NvndRZ2Vxg/m9UvXSQVPIv4ckPxTDtFewLN6cUmmpzDJjYXeWw4g
- xFHE9W9+GeEFaV4Bin4O6nztIZjqyqLjjEJdqHqlrSdMZRIIBn/ycXsBHb35kBsXuWEh0JQX
- RbfZFJTD6kQvX1m49sq7wZuSTEIQxLwD4XgcMrmh0a8WEsZgPziq4b/PdAoc1fwUBPo9hVzM
- 9pAYlDof4isa4W6w9K7ya6RUxcINAp31YTSpF1gDje1uD0aT90qbiIjPn5Pf+0OQ7Hcx9yXL
- cw4wUoVlJzEPVpjPSYgp9FQIbDkETf1VALla0vPLIMlsl/URcvzyldB+qs+v//QiLHjsq0WX
- MVgb/Tgvy9RVeUBcx18V9Cp16/tlw2D5DLndbJOKBJTSrxaMB5ts8PX66zIg6Xi3vDyg+cLw
- 4hlo0j9LiCzgRwhzAKMKDKk4CGyvFG9s93XExObsIdfiYXgRL38+JfDVbNDrEuIEvShIszp+
- iYK+3o/eTIDdah77B4Ub5bvV5tnou+oWVFlmvJXfJPQRkFeT48Ag6+VVO63m0XIxDn0pyRf9
- zxeE1hPjmgW+Bd3y/k7nHNWbAuHF3XNGzB9B2kgvX7+ZZV42rCg05fClm6zt4usgIBC534BO
- zTov6xfUwXdbFrONXRknBar+t2RRYvfQ/wefjEOdrz/0guhhxI/nGxBHR+8/9Hkhzc6JXr68
- EA92j3wMQXTXR1EWNzR6R+EnZMMb+QQE+p2Fl1JVPbR991sAWHp7+TVSSq9BoLP+x6MHJu1+
- g9FEJmDgvF3M3Ep5MOtVJlv8+pT07V8/+Q8j44+0/fx34uUOhEaIiNICNM7/sOBRke7h3yJm
- 7pTMm3H99n8mU1vumfakYkmxN2yPeSZziY93/rUU5b3U/T/tSfO7fSSop1fXyYCHUH25iKck
- Svad7Pwfu+5DdQd/8EXBZ854nCm3BQTkOv78I3/lAF5b8UiK2fo4Ur8HcOiQfQBrexks/pEU
- PO1rLG/o/x8E/HkiWv9LhNMlBEKb/0OC5EEUQvuflz/yRxZ8jx3xRP8y+SPXSAkg8PX6H9u2
- cgGV5l8kf+SPmG3b/m9GbdO0w/T/ZX34Ix/CYyJEqP5hDcSHbG3ig6b/KQd/XZZN/7eBkLoo
- EBz3RMa2qof5n7sglEVZtb9MdJgy3y/09i8cwGaZ53++qfyPdFXR6OWz73jSwzDO/66NbxuH
- vh80iDX/NTGLHgY9/r8wrP7IH7GLEFJI/dvkj1wjJYDA1+v/D9zl5E2hmavNAAAAAElFTkSu
- QmCC'
- 	) base64Decoded asByteArray readStream
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansObliqueDark12Data (in category 'dejaVu font data') -----
- dejaVuSansObliqueDark12Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Oblique Dark 12. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 12 15 4 0 255 17 0 0 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 10 15 21 28 41 51 66 78 82 88 95 103 116 121 127 132 140 150 160 170 180 190 200 210 220 230 240 245 250 263 276 289 297 313 325 336 347 359 369 378 390 402 407 416 427 436 450 462 475 485 498 509 519 529 541 552 568 581 591 603 609 614 621 634 642 650 660 670 679 689 699 706 716 726 730 737 746 750 766 776 786 796 806 813 821 827 837 846 859 869 879 888 898 903 913 926 926 939 947 960 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 973 978 984 994 1004 1014 1024 1029 1037 1045 1061 1069 1079 1092 1098 1114 1122 1130 1143 1149 1155 1163 1173 1183 1188 1196 1202 1210 1220 1236 1252 1268 1276 1288 1300 1312 1324 1336 1348 1365 1376 1386 1396 1406 1416 1421 1427 1433 1439 1451 1463 1476 1489 1502 1515 1528 1541 1555 1567 1579 1591 1603 1613 1623 1633 1643 1653 1663 1673 1683 1693 1709 1718 1728 1738 174
 8 1758 1762 1768 1773 1778 1788 1798 1808 1818 1828 1838 1848 1861 1871 1881 1891 1901 1911 1921 1931 1941
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansObliqueDark12Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansObliqueDark14Data (in category 'dejaVu font data') -----
- dejaVuSansObliqueDark14Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Oblique Dark 14. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 14 18 4 0 255 21 0 0 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 11 17 25 34 50 62 80 95 100 107 114 124 140 146 153 159 169 181 193 205 217 229 241 253 265 277 289 295 301 317 333 349 359 378 391 404 417 432 444 455 470 484 490 500 513 524 540 554 569 580 595 608 620 632 646 659 678 693 705 719 726 732 740 756 766 776 788 800 810 822 834 842 854 866 871 880 891 896 915 927 939 951 963 971 981 988 1000 1011 1027 1039 1051 1061 1073 1079 1091 1107 1107 1123 1133 1149 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1165 1171 1179 1191 1203 1215 1227 1233 1243 1253 1272 1281 1293 1309 1316 1335 1345 1355 1371 1379 1387 1397 1409 1421 1427 1437 1445 1454 1466 1484 1502 1520 1530 1543 1556 1569 1582 1595 1608 1629 1642 1654 1666 1678 1690 1696 1703 1710 1717 1732 1746 1761 1776 1791 1806 1821 1837 1854 1868 1882 1896 1910 1922 1934 1946 1958
  1970 1982 1994 2006 2018 2037 2047 2059 2071 2083 2095 2100 2107 2113 2119 2131 2143 2155 2167 2179 2191 2203 2219 2231 2243 2255 2267 2279 2291 2303 2315
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansObliqueDark14Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansObliqueDark17Data (in category 'dejaVu font data') -----
- dejaVuSansObliqueDark17Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Oblique Dark 17. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 17 21 5 0 255 24 0 0 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 14 21 30 41 60 75 97 115 121 130 138 150 169 176 184 191 203 218 233 248 263 278 293 308 323 338 353 361 369 388 407 426 438 461 477 493 509 527 542 555 573 590 597 610 626 639 659 676 694 708 726 742 757 772 789 805 828 846 860 877 886 894 904 923 935 947 961 976 989 1004 1018 1027 1042 1057 1063 1074 1087 1093 1115 1130 1144 1159 1174 1184 1196 1205 1220 1234 1253 1268 1283 1296 1311 1319 1334 1353 1353 1372 1384 1403 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1422 1429 1438 1453 1468 1483 1498 1506 1518 1530 1553 1564 1578 1597 1605 1628 1640 1652 1671 1680 1689 1701 1716 1731 1738 1750 1759 1770 1784 1806 1828 1850 1862 1878 1894 1910 1926 1942 1958 1982 1998 2013 2028 2043 2058 2065 2073 2081 2089 2107 2124 2142 2160 2178 2196 2214 2233 2253 2270 2287 2304 2321 2
 335 2349 2363 2377 2391 2405 2419 2433 2447 2470 2483 2497 2511 2525 2539 2545 2553 2560 2568 2582 2597 2611 2625 2639 2653 2667 2686 2701 2716 2731 2746 2761 2776 2791 2806
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansObliqueDark17Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansObliqueDark20Data (in category 'dejaVu font data') -----
- dejaVuSansObliqueDark20Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Oblique Dark 20. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 20 25 6 0 255 28 0 0 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 16 25 36 48 71 88 114 135 142 153 163 177 200 209 219 228 242 259 276 293 310 327 344 361 378 395 412 421 430 453 476 499 513 540 558 577 596 617 634 650 671 691 699 714 733 748 771 791 812 828 849 868 885 902 922 940 967 987 1004 1024 1035 1044 1054 1077 1091 1105 1122 1139 1154 1171 1188 1199 1216 1233 1241 1254 1270 1278 1304 1321 1338 1355 1372 1384 1398 1409 1426 1442 1464 1482 1500 1515 1532 1541 1558 1581 1581 1604 1618 1641 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1664 1673 1684 1701 1718 1735 1752 1761 1775 1789 1816 1829 1846 1869 1879 1906 1920 1934 1957 1968 1979 1993 2010 2027 2036 2050 2061 2074 2091 2117 2143 2169 2183 2201 2219 2237 2256 2274 2292 2320 2339 2356 2373 2390 2407 2415 2425 2435 2445 2466 2486 2507 2528 2549 2570 2591 2614 2638 2658 2678
  2698 2718 2735 2751 2768 2785 2802 2819 2836 2853 2870 2897 2912 2929 2946 2963 2980 2988 2998 3007 3016 3033 3050 3067 3084 3101 3118 3135 3158 3176 3193 3210 3227 3244 3262 3279 3297
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansObliqueDark20Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansObliqueDark7Data (in category 'dejaVu font data') -----
- dejaVuSansObliqueDark7Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Oblique Dark 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 7 8 2 0 255 10 0 0 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 6 9 13 18 26 32 41 49 52 56 60 65 73 76 80 83 89 95 101 107 113 119 125 131 137 143 149 153 157 165 173 181 186 195 202 209 216 223 229 235 242 249 252 257 264 270 278 285 293 299 307 314 320 326 333 340 349 357 363 370 374 378 382 390 395 400 406 412 417 423 429 433 439 445 448 452 458 461 470 476 482 488 494 498 503 507 513 519 527 533 539 544 550 554 560 568 568 576 581 589 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 597 600 604 610 616 622 628 632 637 642 651 656 662 670 674 683 688 693 701 705 709 714 720 726 729 734 738 743 749 758 767 776 781 788 795 802 809 816 823 833 840 846 852 858 864 867 871 875 879 886 893 901 909 917 925 933 941 949 956 963 970 977 983 989 995 1001 1007 1013 1019 1025 1031 1040 1045 1051 1057 1063 1069 1072 1076 1079 1082 1088 1094 1100 1106 1112 1118 1124 1132 1138 1144 1150 1156 1162 1168 1174 1
 180
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansObliqueDark7Form (in category 'dejaVu font data') -----
- dejaVuSansObliqueDark7Form
- 	<generated>
- 	" Form data for DejaVu Sans Oblique Dark 7. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^Form fromBinaryStream: (
- 'iVBORw0KGgoAAAANSUhEUgAABJwAAAAKCAYAAADxXkSRAAAABGdBTUEAALGPC/xhBQAAACBj
- SFJNAAB6JgAAgIQAAPoAAACA6AAAdTAAAOpgAAA6mAAAF3CculE8AAAABmJLR0QA/wD/AP+g
- vaeTAAAAB3RJTUUH4AYPCTYCZXCfAgAALIdJREFUeNrtfX1oVFfe//njwh1kcG6IhUtC6CUk
- OmmarFOtdciKmbpZd9xacRoNTkNDpiH7JLa2PuOG+ptd63boVjqElRqptCMVO1IJkXbdHepK
- B1tx2qfSUVbqSMs6gxImGIYJhMBl4MLn+ePcc+6985JETdbu8+sXgs55ufecc8/5ns/5vh2C
- R0C5XG7Z36FpKtLpNADgXjaDXE59FF39mX6mn+ln+rdQsVBAOp3mfK+UspkM0uk0cvkH54X5
- O0n4/X6kJmcWLHsvk0Emc+/++1EsIJPJLFhOzeeQSqUWbkP2XsW66fTtiu8szatW52daekqn
- 0/x7lc7Ve1k6f1VNe9TN/I8nTVORyWRQKBSQyWQfdXPuiwqFAgqFAlR1+efB5KUJ+P39j7rL
- P1mauhFHs9KO5J18Wd53p8NQlHVI3Jy2pE9nE2hXmhEYCMDleh6FYtHyPL/fj91eLzyel5BT
- jfWfv5OEx+NB+EgYHs8LlrzJ6xOwExn9/V5ISveS91NVc9jqdCIc/c6Sns8n0SrXIXz8Mk/T
- NBU7n3TC17cHTzrXIpGd5umDXi9Cf/oTtrg7ePqZET9cvxwCAHx5LARFeQbJW3lMfj2BZuUJ
- 9Pf74Vr3EqZuxOF2b0b4SBhu985FtfvMwSD8/hex2e3GcOh0xX5tqpMxPHqlYv3pbALNUg2C
- RxMV87ufUODZtsPST/M4DPh88Pv9cLu3IHmrfI7s6/IgsG8fvF5v2TxZ/LfR+PtyOes7jg35
- 4OrcV7Hevi4XnO7+sv3kzIgfSnMnnt/ogn/kjCXvy2MhuN09ONDng29g1JKXvRiFLCmIJe4u
- qt3FYqFsjysWC3h9eBgTl36oWGdmMgW/34/Ed8ZYzc1lMDw8jPi3U5ay38bjSCRu4loyicy9
- OaOdnO8bGEvTVGxTJEg1EsTHNlnW5INQsVjAgUAA0fPfV8yfnU3jRb/f0k9VzWHv8DAmLk1a
- ymZM7VU1DZOXJjA8vNey/pMfReD37wcAnP1TCMHg+1DzOeRyOWRN/ayGf+98k0Q8fhm3kkkk
- v7lj7cN45T7MzWUwEAggFr9V1odY4pal7M1EAvH4t7iWTCJ9e7Zq3x52zEeGhy3tqTTm5nnC
- 2ls6d7LztIuNy9jp/wFQHWMDQD6XQy6fRy6XQ6FYBLkcDcPpdMLlcsHlcsHpdCIcvVxW8dZ4
- GCvE1UjNzGDy+gQeExuwd68fzqcHLeVmZlJ42vkkEjcTcDufRPyGtSP5O0k8oTzBmVOxWEB3
- uwJCCMTHNiGnqpiby6BFIPAd+NhSd7TPB4EQEEKgdAzx9MnrE6gltZi4bkzUvnYJxNEBADjW
- 7waxd0DVNNzLZKCqOWxxb0FOVR/oQLQYujI6DHHFL/ii+P58FLJA9H5uRGaOMoA/9/mwcoUI
- QhyIXblbNiaEEEhKJ3KqimKxgF81SDxdrPkFUjMzlvcObnJanvX2TjcvTwiBf2SCfqfJFDY1
- ykZ6aAJ3UzE4TGUJIZCadwAAToeGYWPptnrOFE4cCPB0pb37oRnVUlCxWMDOVqNvnj3v8DxN
- U3E8HEaH2w2n0wmvtxepH2fKnvH7bS4QIlvm74ev+UxjI8C95RW+GIvFAn73G/NY2xA4cAoA
- 0LfO+JZEcMDfH+L1LHmEgMgdFd5FIK+loHd2Ko2uJ8x17BxI7G6V4dz6Bm/v6x0KpPY+nufa
- FuJ5MzMpNIorEDp1lX7HQS/ExzZRhv71BOoF49sff9kDsc5Txnho24119+O5COyEQHlmwMi3
- KUjm82Xt0TQVQ9s8pnGpRfj4PyqPteBAaPRzXs8yzvPWq+X1AOCDEdMc1udF/1p9nggCBMEY
- 02KxAJfdyoN69fG9m4rBXsJvPn7NB0IUXDSt+2KxgE2PiZDXUx45nU1AJgIAyrMcxIbIuR9N
- 7a5F/MYUIj1uEPsGzjvOjPhBSC1UNYcNDtNcEQTL3Bg/SPsuNXTgbioGWV6L9OwsH7fd+prw
- vnKKt/v2Z2Nw6Ot8MRtesVhAh4NAbO1dsKy/iYA0+RezZC30t4M+ENI0b5nbn43p31JYsA2V
- 2nr6d24Q0sJ/x/Z5+Ds/2e8FEdosgMac/p9Eo30++Pr+/KibsSAViwVsbRDpunzhMFQ1hxZC
- 4Bk6ycscfoHyC7ae7ofud54DlEe2rhQt+8dS0vkjYUTHr1rSkh9FjD3Y7qpal/ISO8YuUAHo
- rdNhCKQWmqZiv9+PyEdJXvbz0RDsbD9voesx+1UUhNixfbsbxGa854sTETQrCpxOJ8WCJt7K
- voEsy7ARW9VD6MPQFycieFJ/t6I0l73fjFHEuk3QNJVjJWXdnkW9Y/L6BOpWiBD0PeD6mQjq
- ZBk2ImD4nb/yct9fjMJOCDwvzf/9PxgZhlwjYcUKEYTYEPrgywXbMDOTQouNgNgMPnP4BQ9E
- kT5jvrGtVHd2No0WgcDdG1l0mUr9Li2zEL2x3Q0i1JfhfHNeqSACAN55wUPzpivk7fGACAZu
- KM+rL8srFgvY+BjlH97+o2X1rn4QomcHQeBnCHqOeJ3XXwi/iSKdM6S2oyR9RXm6INDyAp2n
- LF0UV1RMd/e8DYDiALnxOc6jxg/Q34wmRvyQGrbx33s3OU14wA7fnoO8bu9aGcTewjHASOfi
- 8VdZvk2umM/H0l6PyIkvyvIZ3hJXNlTMF6rkL0SlOFBapUBx0L1hPuy2qLyDf+N5/Wur5w2t
- U+Dc+kYZXpvQ8Rqg4+o6T1n7r5+JcJ5MiA3h04Ygc3CjDGLfUHaWmplMoUUgkNq7LecOj75v
- iqsNISTFqOz5Do5V8/kkagmBb48PhNTz86Oq5rChRoJ3uxfiitYy7PMgNNKlVMRRs7NptNkJ
- xNXP8T4WiwXsaNbPtvXG/J6by0AhBN7dXgjEgfi/pjA7m0YTIXDufBMAFQISQjB8eBxnDwV4
- n/tXixBXe9AiED5nNtfS88QqqQaBQ5/ScZ1Jod7EE0IfGHvyG1udIEILP6+b2+WyE4iNW3kf
- NE01zp1yFy87+cOE6VxtR/SrLH9GEyHw9m6HQOyW88SD0qubZBDBVTbmbD+QWrotY84wl9i4
- 01K2ns+RWguvLRYLeK5RBLG3IT1F+Uo1nF8sFrDBRuDq6oKdEIxdug3y8Ws+uLe/gUwmg0wm
- g8MveOAdPFFW+ZP9XhDSgpyq4m4qBhtxYHevF/IaK5j/8YsIRPEX+OpqFKLYalk0b2y3Cj/C
- p7/D5UgAhCjIzGWwWlyB6PdZ9DSKEFf3WJ5L30kQPPp35K8lEYudK8mz8Q/5zftBENNvlh+7
- chevdygg9lqsFFdCdljBq6rm4LIR+A6MP9RHLxYL2GA3FgQToImNO3Ezm4BMCHwH6TuOhUJ4
- 1u0EITLXEs3OpqkUO3kT/3OWHqxYmxKJBNLpKdxKUOBlbuuJQa8+tk18gXQrElzPh5DL5SzS
- 3W31BERoQfJOHjcTCSQSN7lVWDqdxunDw3QRv/NXTGcTqCUE7p63MTOTQpN+EMh+FYWNEHgH
- j+L2BdrO4PsPBkJvXIwjGl3cuM9OpTE2NlaVKVItwItIz05hZ6MIYt9A0xkIIwL8/SP4JBZD
- W62VIQPg/SJEsGwEvatFkPou5PI5vNHjttR7vVMBIQKC756Bpqk41OOGpHTTb08I3L2HkM1m
- sG8H3cR9r31s5PUcQka3PmECUPYuc7qmqdgsExBSi1g8hWKhgEM9bogNO/mzmDBB01R0OAhc
- 3UeMvP2f8L7cvjQGQV8T7H1i638hq4NsqWUHX7s9q0WIq63rfG4ugzabsY45MycE7v6IJT/w
- 9gW+Jtz9x+h4ddDxCh8/D1XNYbM+H9k35f2/l6F5trb7qpeeSqNDJiA2ynypBpTANzQKVVPx
- 2fExRN6L61Y4GcpETePN5jzbfNgB2Lv/lJ4nIDx+i8+rekLg6n4Lty+NYYVIN+ybp0KWDfRI
- twtEMIQc2+oJxNZ+ZK9GIRAC32sfAjDxupM39O9E5wtgWCllshk8t1qkY6ErCF7dKENcTYVP
- U/+Kw0FsGLt02/LNFCJwIeO0zouUdR2QCYG8cXEH+embCYRCf7LwdjWXs1hKFIsFyksPfox7
- mUwZeGIWRebDv5rLIZdX8fZvnRAbDf5fLJRbPL26UQaRt1nS5rIZZLIGMFDVHNpsVJg+V9IG
- NZ+zKBvMvweeksrmO08vEV5lTM/NZjIVtWfZCv2n78uiEmUqlJ/LVrcWM49NtsSqrKdRhNL1
- x0V910dJd1MxCERA9CodE1XNoU2g681Mb2+1zo3F0IPM82KxgC7ZwCpmQcRS0W6nE6FTN/lv
- TVPRYacHh7yaQyKRwKUPxxA7Z2gsz0UiiF+e4vxW8YYpbxIIlK6RioI6fxMBqd9lsfquRLfG
- wyDEjlAoBJ9umSAQwvkFAJwJB+Fyuei+/8opLCXR9xN4t+9GJBLBe+/RQ5n5/aWUvRoFIQ5k
- 5u6hVVxp4XcL4bngRpmPy9njY1Bs1j6d/UMIoT+dnbfN350OG8KLZ7xYK8uWNsxHV0+FINU8
- ZcHU8ampMv63UF1Ax3P12+6rTKV+V3pO1bGvgpMeVZ5dP7wzJQ4jhr+dTz8NGxEQOnaW41zm
- +bAgfivBaEudzvhcbwnWmu8345HuHootR3op/ve8fPy+8NfcXKYMRz3q/KPBIKLns7zfh0ss
- X4z6/8B0NoF6gYAQBenZ2UVgt6XNmw+v9bVLIESA0+mEe3O/FVO39nOM4u7/kPctfysJn29X
- mZDjy9EQPJ4hS9rMTAqBwADiF+MIh49wPKVpKlKpFD0vmixqAIYRyi1Xkh9FUCc/XmaVVIrt
- qFXOwnhuZiYFn89XJhz+LhqGx/OSpezsbBqBQACJRALhcNiCfyj2sT77bjyGcDgKAPggFOLC
- ymOhECYu/YDT4TA0TYWqaVD1OTX0jALikGEnBO7eY/xZ1DIuh+8SCcTjN6zjO5nCLp+vzLCD
- 9cFM7NyeTCYtfWDfIplMIp22fot7mepW24VCoapyjOHV6ZsJPg5sXoZCIS5kZvT9eBTDw4fL
- +hYMHsTtqTRCoT9Y8XGVs3X+TtJiXWbg/PGKOF9TVUsfyMev+eAbMqS99PeHZS8aeEoCUXYB
- gH5AsuOFPR5uvqqqOQz4fGhukECIA2saZRBih8ezA8k7ef0ARPDkWiekhk5EIhEkb+URG/JA
- bOhBPp9EnfgYfvMbN4hjQ9lAT/4wARshZZuJ0R4B0a+yKBYL2FxLuCSfta1dqsHYpdumQzsB
- qd1sGaBisaCD3E/wMESFaIb0mAnAYlfuVgTSsSEPiM1V0Toon09aBFSM7l6JWcAYfUctujpd
- EB/z6AuNMkV5/W4kk0k+pnevUAYZOBhBPB63mFsCJkmwDjwoQxUwduE2B7eeoZO6ELKJW3Ow
- dAB4bygAf/8R/szP/hyCz3fA8p5isYBoOIzGGiplJU27+PtzuVzZX6FQ4O1hmhH35p1IJG6i
- ErFNV3pqLwDK5Im9Dclr1xCPx5FMfoNvvkliU50I1/Nv8XpdMoHU/iu02Qk8L5/kc6hNIPAM
- xQBQzRMhMpJ5OrdrCbE8A6AMg4+dCYR2yQTi6p6KedZ3nbSkXxylQsDg+99Y0nO5HH9WJP4j
- 73sTIQhELli+H6Nx3YokMzfHgbm8Zg1shMC17fcLtoVqUATIqyT4DvwNqUgAhAhUWzp6Uc+3
- oXWNDKmlDzMzKch626duUF5g1qKyw451jdB1eHSPC0Rou496nwEA3v6tk68r2l9HRS0Cm+/O
- 377J036MRyxaByqwMtaAeQ2PdCkghGpB6FjbEZ+agp9pbGxtyKk5Kqh9+Th/x9VTVOtqK7HY
- BAB/iwSx4RdQbIYW1kyh510gRODadE1TsdlhAEozz2NEwZChJWoRDK3Y3SuxsrFdDBWLBfxK
- MawupeZtKBSL/JBvaFAVbjL/QWjY0L7pgsTRAWaZZtOtCug4ndgXMLSgdZuQmZvDp1yLRUBq
- qTA53Ovl9VeuEOEdPGG0QbcEI8TQtu9eI1u0nH3tCryDJ7gFl3f/Z7ibiEEWCOTW3VyA6xk6
- STVsNgJi05/raMKzTzNNM7WKnJ1No0kgEFesKHu30VZjvObmMrpFgtHWia8nS8ZGwAqR9q20
- DbOzaXSYvoO8ftBq3epw6Xsw1bBpmoptDRK8r5xC9qsoVooNhiVipwIid+FuKoZVUjPSs7NU
- i6tr+t7c6oTU4qd8w07g7jlG55OdQF7frx/+jP4OdSgQG7Zy6xRxhW4RICh8/K+MDlsUJWyf
- KRU49bVIkJ4aWPT8fNB5fvWDEGqkGgiEQFpVA/nxX1vyLx8Pw+8PYTH047kICHFwK5AbZ8dQ
- a9J4xlJU6D89TQ814fOGgGlwvQwiyPB6vfB6vfQwo2OBI90uEMcG9G91cv5TCV/sUui8LLWm
- KqXuZgWebV1wEAKlUYHS7MVfQtSiQtU03L4wBoEI8Pv9cOhW0YzOxWJIz85iPBqt6DqzGNrZ
- KMM/cgQbZRnOJ50QV6zGyH7j/ZWIWer6fD6sEBstB4NSJYyZjg35IIp13PXhRX39mvdIMxWL
- BWyqEfm4RnrdkFt7dRxAv6V3tw91cmsZ2K9Gn+33Qm6lws/bl8YgSe1QNQ0D7RKcW9+EquYQ
- iURQLBYQiUQsY/DZfi+kFroO3nreVVELX16mrQxjsn5Hv8/iSJXnAAwvWPMq4aSfRF4JVnnz
- t3R9jI4Oc6GEme4XvwFY+nQTrmDtX+g3tVYxMB8A7FAMbPmg+OtR5xeLBd2Sm1qyMUU64zdG
- /WN0D3KYeOmVu/Nit+XIAyrjNbY/io814EknXWfu3gjf2/wjb1FLn5rViI5fLcNS8hpqAVQN
- YxWLBfza5KWirNsDVdMe6DmW8q07K6YrTzyDVt2KkBAbdyOthOcq4TYA+Mtef8X09/YFDCvc
- 5l9xgUa15+x5QuHz4cW1Tu65MzeXQbu0CrHUXbr3S6u44clfBv1w6t+B2KjlH8dpK1cYOLUC
- TpNbn+NtsqSvMdL/bPbAWmdYEi3mOexbMFLZeWFfDKVkrsesk8zYDgDHdiydYQxrugMTP9D5
- vHONbC1/5W4ZRrQTmVukvq5jujKcr+NWVp4Z0TAMSEoFTJUETqUHMub/ny/R0n4bj6PJRuDZ
- M0SltjtfQSKRQKFYxOR1KjCSVtXA1WUcrhgAlGok2GwUGEUiEfj9fkx8fp2XG2Smo7qp7XQ2
- Ab+/HzlV5e1RNU0Hd3ZuuQEwCwQ7xi7dxuEdHrg3b8Hj8uPYstkN9/Y3oKo5xONxnDwZhUwI
- nM/2Ix6PI5GwalEWQ0yT4Oo2hC0DT0lceFPpAN9bwYKEtbvNTk3r2UL79JBpAeradupSKCB8
- /hb6V4uQNwUBUM3uGlnmGkkmYPuYuR3ZZcgO62EIAD4+4AMxMVcmvOCTSjcfpQKnWiRuTuPY
- EH3m8OhFAKDjvN1w7zq8wwP3b/bz573UpZvbCna4O36DWOwcB1ST1yegSBJkWeZ/K1eIcHUZ
- vthT6TQOBYNYU0cZrljTgPBfzvP86ZsJ1BMCscGDnKpyS7rEzQQUgUBuXAOHQEBsG3B0vxdi
- A9UoUqGOA4npaew3WTowUEIIgU13vXJ1U4BCQWd9mRQcAC6UCB8BYK8uvE0cDfKDJDWlr6Ub
- suldgkAPizlVRW+ryOfRD59PIBAIYHh4GLF4iguj2LOoexgVsFRqw6sbZf6sqX/FOdMotW5k
- guLw+Hfl/RKa0L/dDWWdF60rRfj69sCuMzf6zhacPh0GIQrGL0Zh09tz6hUvCKm3AL/sV4bQ
- mPVfae9C3y7KxN29EX2+Vapns9QjDgW/3Oii2r2D9IAwdSOua8EIxJV1CB58nz9jdjYNhRD4
- 3zIOUPSbGho3KtCV+TrpXS1CemovJiep5VTg7QuUn+kCp+h4FHZiQ3Q8ijp5I957OwBCZMs3
- YCCQ1HaUHQTo4Y6a5pYetqiwiSB07MuSPhjWS0zzYD54/u2gj5s4F4uFsvhHc9nMA8UouhyP
- I5FI4P1wEET/hj+ei0AgBN7+d/mh3zN0kguLQsc+Q7FYQDKZxETIT02Nz2d1/k0tJWm6gMhH
- X2D6Jt3YApELhsv1wY8t/Cp6MYtbusVB4O0LvA2+16hApFG3gGAm2YHIBc6PWvTvPzOTgkII
- nGudtK4ep4HuIQLC49/xb+N77UOudVc6h/hzPEMnTWWs7zb6+r0OnOkhhD3Hs+cdLij3DJ20
- jA2zAAkc+hTZi9QqzvPSYaga48VUqMFiQ1BQbMPYBaq1uzJmHLiYVV7w/W8w+YMOni9RYM2s
- FtnaiiU+gaID+olLE5BNfJ5+TxscNsprC8UiV5IET97Qrfyswu5z71K+x1zV7mUz2NEiWcy6
- KwmcuNXm87+3Hr6Pj8Hv92N4eATp9G3cuBhHJPIRXwcPOs+ZAqpU2fN3vf1iwybE43HLXyUL
- t+nvEohE3oOqaVxR5OvbBafTjUQigcy9OcxMprCny6MrUbYgHKZu0tT1lsA/OILuZxQQOxWg
- s1AIzOLD6XQiNPp5mYXTxdFhEJuCfUMBPncq0exsGpvdW7CjQ4HSOWKM1VwGbufTSM/O4vaF
- MdiJDa51Li4om7uXwY51Cgixo7FRBrG18LALdaIISZL43wpRhKvr91Xf/7TTjUKxgA5FgafL
- o/PLf6LTtXFeIU42maAKTD32RqXQANQCiQpf/O30EOX65fNIXsvjRb8fL/b7LZinlOicNqxa
- dzaKUDpHTHu4Df4X/VB0N/TZ2TTcVcJTAMClD8dQbyMgjjYkb+WRzyfRXCPB5XJBltdg4utJ
- 7pKtrOuAYidQOgagappRV96Ad0LDFrw78EsX3NvfqFDGgYlLn+JZpxOKoiCw7wTvt0Bq8XqV
- 5zD6fDQE7/b9fN1Vw0k/tTymXB0eu47Yy7qLGHOf13HVfPitGkZbqnQzNuNYS7feWuh3vc1w
- pWM4Z+9TEsTVPQ+Fvx51Pls/G+uoBTchBP79hqKO1m9ChllxOTbg/MUobHr9+bDbcuQBlfEa
- +17Bk3T/3aUQEGWXvi870DdEXZbMbqWVsNRPJV0gBEpHHwrFAnX7U3bNg+fKcdtSpZvxWymW
- o9+BKlXN/6cutQKGR8ZwJRFDrW79f784bbnTmSxiYmICL/r9CAbDFlkErScjfjkOl53yk+jV
- bFVst1Tp1TAdw9iluLVa+UUJnFQ1h/WyXGbGaqbPR0Nwu92wEwL58UbqlrOqAcMjH/AyP3w+
- gfZVEmX2JT6qV89H4SB2+Pb4IIoNGBjwcRPL+Ft+ypQn/0kl37UuPLdWtvhJMqoUf4O7D+lS
- Pk1TEQ6HDcZwI452RUFjox4bx+ZAo6LAs+P/lT3f0K5X9tWvdLjvaze0ssz80nwwrGRBcuMs
- izmxzdIXTVOhqio9dOrjs8FOBXHBYBC1OhAuBWjUAqUWiew0dTty0JhW2e+jVMOlMxg2UZgw
- BaDgitRvRvr2FEaHaKya1MwMZiZT2Pi4DCLYYdcFHJX89Utp6oYh4HBv6UXqn1aQNzuVRigU
- svwFg0FEIucs5bhJuJ354xuCzOAmGcSxmf8eXCvDMxTDiT0ubq5+otsFeWMQH/a7Ia7uMZkh
- 2+Dz+VCrb2aFYhFXT4VAiAOxxC3ux8rcPo90u6paqFEttCFQYAzS1f0Wr5eZm+OBUAFY3mVO
- 728VQeqpFdi/LsfRt8vHD9f0WW3I3LsHVdVw4hUv10iWtoELkPV4T9+dDkMgNjQ0SPzAwNfl
- qRCfN5Z+Pe8Ckbfhr2O6oKt2M07pICczN0fza7swN5dBoyjCvcXN40mMdCk8phqjkU4FhDQh
- PTurW/4I8Hq3IxAIIHqSChLf3OqsUo++k7bVhuHXR/Bsq1wm4AGAb5JJ9G93WzZVfrA2CakH
- 18sWt95jvW7LNz7S7YLUvAPd7RJIrQEyqGTfjrVrZIgNO3H3Vgyy3IgmB7Ec5IrFAjx1TFsk
- l42vWQhgpkO61YpZ2MTea9M3V0b9rbJFu//qRvm+3ZEWojP7qcZKrmtEvYNw3sD4MNOUufSN
- iAnqzNRrEpIz69mJ65N6fC0bFzpL0iqEo5e5IIXx8/L6NgNY21w0LtkPtE70q6w+VsbhkgkJ
- Y6m7JrcNguD7hnk13UPoOvhkv5fPBar5pJaO7FAaif9oKWN+d1+LxF3cqMCRAh8qDGzhCpQN
- pvFifaOWnbTf5ucDwNS3cbSsogdp+fGNSE3O6Acxw2roSLcLYsNzZf1hShD/W8ex2UH4XjUz
- k0KztArup52QlA142umE2+3kewdAQbWdEC4IASh/6aolcD0/gDabdd6f3O/XBcFn+TtadA11
- 6KxhqVpJ4GRovgUuCMx+FcUqScbw8DDWNSv8UOcbMkzmH5SqWVlRdw4CYq/lcS9pzKH2irFs
- Ql0uOJ/9bwA6PnF04foXEbjWDVne5WkQQWwKIpEIolEq0Lt7Kwa7jidunAzyNXWk30/xlkAF
- gW73Fm5B+M9Uigu+6BywIXTsA2yWrYowM1HB0pPo2emG+NgmZO5lkU6nkc8n0SivRWZuDuOh
- YawURUg1NVCau5BTVezdIIGQeuzoUEBDI8zxOcDCNNC/LELdxt5biqPm5jJYKzciNfMjOl3r
- 8NIeGlPtmun990tMUcasPhn9U3dvYMK+eDyOWCyGdHqq6rPoOqcWF0yox5QMP1yagCI1YMcO
- D5yb6HfO30nC5/NVDYQ8qbu7JBIJ5PIqTodoHCiBEChPGHHGRl/ygBA7urpcXCDG6n7Awx5c
- hKapeOmXVBHh7v+wYhmAWu0MrqeHRdbvRJwK6AJvXyh7DvuWHXZD4TwfTvop5Wmaiq56yls8
- Hg9kG4G8theqplpw1YL4rQJGW9J0HZsxrMX28IV+v6W76Kd+/NHwaBAov30Y/PWo8xkdZwJC
- fX/l/HSbC8ShoN5OQz8AwB9NVubzYbflyAMq4zXmbuvdPYiX9HhYwaMJbs2bYzxft4quhqV+
- CukNuheKVLMKsiyjpkaCq2tfRTxXDbctVboZv5ViOTMuMv+/d7UIeSPFUWbcdb84bbnTmSzC
- HFdbMcki+lokyOt/jV/UiPDseIELzqphu6VKr4bpzKGWzLi1WvlFCZzy15IYGzs+b7DNe9kM
- /tjvBRGacEAXSkxMTHBhwsloFOnbaXS61mFw0GikeQPzDB3HSKcCpTOMW/8IQ9RjoVDpMmVG
- xoHAxs3BzPTJfi/EuucsaWYBy3ykaaqu0fybJX36uwTGxj6sWP9fl+MYG6PaSG7dtMcK6npX
- iyDKDhoXop7wtmiqih++phrM4NG/8/KjurWQa9s+yzuZW5yq5mjMGX2jCgeDCAaD3K3DvXkn
- UpMzSKVSKBSLUNUcdrRIXMg30qXwQ/LRfq9FoDDwlFRmVt1iMn89oWsnUjMzyOpWZbNTaWyo
- NeJhsfnCmPHcXAZjY2NlrnuXPp3A9g63brElwNv7Ll2AkyluvcP+AoEAQn+gwD9/J4l2/XBF
- 7DKG94YssVs0TcV+rxfBsCGg8jdL8OyL4cN+N4jQhIMHg3QeORwQxTpMfD2JSK8bhNTqgD+K
- 3u1u3teTQx4+LneuJdFmNw5mVOrs4LcDXP98AqHQn6FqmiUe2aVPJ+jhSqBzmeUxAMRu26Dv
- Kg+29+pGGcTexm8IoxsaZbY9jaIlvsxIp8ItmHoaRUjthhtKqUUPfZ8LBX3+EocRAJH1Oz07
- awFKPY2UgU9PJ7BGrsPYhdv4Y6cCUr/DyF//KgA9CCIx3FyZextzZzhxkB4+/KEzlv6XAkA+
- ziX1WOwjc73Z2TTqTe4U0WiUzxEaoNsQzvzN5F7IaKBdApGpRSCzljO73F18h1mU2SzWG3Nz
- GbQJLLbVLVPwRsOdT9NUun5JE9KzU+hwEMgbX7X0tZLg+p09Hm61pXHQXDT6UDJnBtol/t2Z
- kNHsu74URK05aZDW5xpFkNrNUDWNHmp0gEuDnlPteV+LxGPosNhGfS0SlI7XaWDztTLvBy1L
- x4XGCLhnGhvje1HQ00cDT7ZIvL65/2aXrdKxuvC2ISgdP+gDsbVgT5cLZsvPcb1OoVjEwFMS
- n8unXvGC2KkLOLVAoofSgXYj3pP53T2rRSid1OT+0E7DTe31ToX/n40XBz76Zj3QYZQxtwEA
- t+LhGv3Ri/jkFa9FGEr3IRqzhu4HBmDmwfN1sAkYMXCoduoC5Q3EcOmdztJ1QV1xBUuwzUiP
- 7s5nM/YSehGDrczqgx2UmNWUOc0s7KHaN7miJcJyUDWBk6ap6F0rQ6zbuuAzzMJWAPo32Yw/
- 9nv14OhGzA0aK88qEGYCOuPPgbHPbqBQKODS2THYiIBw9B/I5XIcG5TGLfriRES3mG2ZV3Bz
- YtALcWUDPB6PDnY3okWW4HlplLeR7QFsH1DVHDbLBPL6neiQrcLFUvryWAiebcH531/TiOFh
- 6qq4r8ulW90exf1SoVBAPp/DgUAAkRPxh77VjoUPyMzN4a/vWK2B7t6KQVHWwduuPHD8T41j
- ANUqjLA3YVMrDf5sFl6x2C9sT/qvX9Bg4/UOQ/FWWkZVc9jRrkBSOi2uq21C9eeoag7bmiUL
- L5wPJ/2U8ihesCF48BD+9AcaON87eMIYa50vLga/lWK0pUxne1Qp7lvo90C7xPHWtxfjejxS
- yr8fBn896nzAvFeMo3e9TC3C9NvfqIUTgdROAxWfKqk/H3ZbjjygMl6j7XTweHixc/QmwLee
- d3Grdh6g+eB4VSz1k0k3YQPmUUQFORTP3TPhuUq4banSzfitFMuZ42ya/+834aiQyXX4fnHa
- cqeb9wMaG8kqixhcL+tnnmMYfdkDItD2VsN2S5UOVMZ01OW/HLdWK18Ww2liv79M4GTebOej
- ky97IK9/Fade8UJutV4l+9waw9eUCLUW96edpkO54RpEeDsmv54wzEcJgdLcTAN/6Tc7mIla
- QxltrWTSX42qBZnc+5RUVQPS3ypySytuiVUCiC9Hw6Yb3po4cGCTh8cAeIW6Mzn4OOn91Sem
- 3Qw87U1lVxnSvho+6m22yuXvJmImv0s7QsfoTV63P6PmhaUxgpi7nHF7B21nX7vZ79e4caB0
- vrANZj7rp/Mno5bgZ/NR/hYNylZqGcWICVSYBhLQbyp0dEDVVBwKBOD39+OFLg/cm3t5O2Vi
- jfdA44ZRiffQM4rlW8mNm3isCk1TsafktjnmOtBmNx8WBLg2Ps+j+1vz6A0CbFwrulhOptDm
- sD7PowslzQcjTVOxtU7kG2KLUB4wnJgsRMzvy+eTUEwxTwZK+k3slLnTWySt66S7WbK8k+V/
- o5uTs4ND+XjZLFf2Vuv//dbra5e4Rt3qZ2xDYN97vNybW51l1pI39FutDF/tX5ddw+wg5bGX
- mN8+kemmzdw72E1yAPDfzzopgNf5ADXPdlisI471uvnGz8hBrPPFDCJHOhUeMJzRJ/u9kJop
- KGPa/tK1/bAU2uaytEfpops6j5Onj3fwXSr8HT88bLoliB7aSg/VDAD8XTfj5s/WxzrS47a4
- X10+Hqa80WajZfWbuDbYjTVx/GUP19yMdCqQWvqs318H7ua87haJWg3OzVnSNziM55qtV6n1
- ClUmmMuY3/33d819quUBOq3jJWD4MF07ZQIHZUdZGwCYYgIZt5pejoa5sDN25S6O8ksl9HKm
- WEgMxJtdrngMisad1MqhlljmZIuN3pgD6FY/JqvlK/o+bhZCsf1rRcmtrExLGZ+yXtdbKuw5
- 2u0qCxS/nLQUl4gwtwpm0cxuAGXfgMWeKN0LRP1mqlN/oAFRNc0UTFe/ppnu91btf+m4nYvF
- kLx2C0OdyqKUbif2BSDrbviyLMM/+JdFjVM6PcX/fRhi71cUBbJcZ+HTiyXLDU08fps1ruf9
- 0lCHUsZ7WTy+eMgP5YlOrFOUqgHDZ2+nEY9/e1/vvJ1Oo1As0puVS74bDe5t7Fn3Mhl8fWkC
- iiRznlJahgkexJWPIfju3xf1nL52CcTeZsH+8+Gkn1Jek0Dg7qGKUnOYAvbH8jRN5bGs5sdv
- BkZbqnQzNutrt15KsdDvDbXWPcO5ditXRj4M/vop5L/m8yHy0XWedsDnQ+QMvXnTQWiMuWr1
- 58Nuy5EHVMZr9HtZMRkADKxTIK2qMXh9Hb21vBqW+imky2vWm+I3ES6APhcOmm5+pnt6Ndy2
- VOlmLFaK5cy4yPx/K+40cNf94rTlTjevgU8nJpC8dseSbpEBkFqMfUat8Kthu6VKBypjuo4S
- HsRwa7Xy5NQrXjjdL3Lz3oFOV8Vb6paCLkcCUCps+rlczvI7r99WVKmcOTp+JfDE4qIMj1Fp
- cj25/0C4pVRbYsVQjfbogWcrUbFQKOvn/RILps00YIuhauXZsxZ7RTRrf2n50m9SicwHv0dF
- xWKB3/AWCoXQ7/fDIRhuZUtBqh7cfLFj+qDEgqg/CF2Ox7FBJhWvXf13k1lTfj9ULBRw7DUf
- yCLXpfl99/N9jOD1DxYE999J23TXAfNtWp8eCsD5NAU8su56sxRXr5ZSfh4eUGm8i8Xy76BW
- GWeD51WfqyejUSST3+CDP4cs8bQWQ3euJdFiq+5qtBxUrDDv63VXPLXCeKm5HArFgkWgW22s
- F5qr+VyO38y0XHTrWhIux+IP+NSllcD1y24ujC8Nfj3g89EYV6ag+/8JxNyjza6us7NpNEvy
- sqxFHmxUt6ja/bQToihCqlEWDBr+M1UnGg/vBIr6ujVbyHx6MADfrj54PF0VY03dy2ZwZD9V
- hC7FdeMAFrWPVSujmdqw0HPaBAKp5Vc4dDAIl6vrgVwb/xNI01Td0qb232ZB+ahpIfz1qPOr
- EYu/V5jnTDUfdluOvAehfIVnVcNSjzLd3MbSs4emqTh3Qo/7aLrsohpuW6r0B6H7PYMXq8zP
- 5U6fj+Lxy3xMSqkatluK9GqYTq6CW6uVJ1fHo/wGFPa3XMBkKp1+aA3YYuie6Xrq+a4B/pn+
- /6OPIhHDxDWWeNTN+bdTZ4MEqeEpxC8v/zpcbspmMst+eP5Poax+vWq18aDXQC9eOFer37Am
- STTmnnPT3kXX/XfTjicUag0q2O/bIsLlIBDr1nHN8KOiVZIyrwWoquawUZYtbmc/VaolBFJD
- x6IPp5qm4uzYGILBoEXgZL4unMbw+2jJhfnLPc8vR8Pwevstwn1NU5FIJJZFMaFpKkZDIe4e
- 9DMtDa1TFEQvZh+o7pfHQlglreKW4f9JdP4vYTQrChSl2XLRxv81un4mgjpZhte3f9kVhj/T
- z/R/haZuxLFGluHe8rtHrsD+mZaPqmG6ari1Wvn/BfVPwmrlF3m0AAAAJXRFWHRkYXRlOmNy
- ZWF0ZQAyMDE2LTA2LTE1VDA5OjU0OjAyKzAyOjAwqhTHewAAACV0RVh0ZGF0ZTptb2RpZnkA
- MjAxNi0wNi0xNVQwOTo1NDowMiswMjowMNtJf8cAAAAASUVORK5CYII='
- 	) base64Decoded asByteArray readStream
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansObliqueDark9Data (in category 'dejaVu font data') -----
- dejaVuSansObliqueDark9Data
- 	<generated>
- 	" Font meta data for DejaVu Sans Oblique Dark 9. Generated with StrikeFont generateDejaVuMethods: 'DejaVu'"
- 	^ #(0 9 11 3 0 255 13 0 0 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 7 11 16 22 32 40 51 60 63 68 73 79 89 93 97 101 108 116 124 132 140 148 156 164 172 180 188 192 196 206 216 226 232 244 253 261 269 278 286 293 302 311 315 321 329 336 346 355 364 371 380 388 396 404 413 421 433 442 449 458 463 467 472 482 488 494 501 509 516 524 531 536 544 552 555 560 567 570 582 590 597 605 613 618 624 629 637 644 654 662 670 677 685 689 697 707 707 717 723 733 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 743 747 752 760 768 776 784 788 794 800 812 818 825 835 839 851 857 863 873 878 883 889 897 905 909 915 920 926 933 945 957 969 975 984 993 1002 1011 1020 1029 1042 1050 1058 1066 1074 1082 1086 1090 1094 1098 1107 1116 1125 1134 1143 1152 1161 1171 1182 1191 1200 1209 1218 1225 1232 1240 1247 1254 1261 1268 1275 1282 1294 1301 1308 1315 1322 1329 1332 1336 1340 1344 1351 1359 1366 1373 1380 1387 1394 1404 1
 412 1420 1428 1436 1444 1452 1460 1468
- )
- !

Item was removed:
- ----- Method: StrikeFont class>>dejaVuSansObliqueDark9Form (in category 'dejaVu font data') -----
(excessive size, no diff calculated)

Item was removed:
- ----- Method: StrikeFont class>>example (in category 'examples') -----
- example
- 	"Displays a line of text on the display screen at the location of the cursor.
- 	Example depends on the strike font file, 'TimesRoman10.strike'. existing."
- 
- 	(StrikeFont new readFromStrike2: 'NewYork12.sf2')
- 		displayLine: 'A line of 12-pt text in New York style' at: Sensor cursorPoint
- 	 
- 	"StrikeFont example."!

Item was removed:
- ----- Method: StrikeFont class>>familyName:pointSize: (in category 'accessing') -----
- familyName: aName pointSize: aSize
- 	"Answer a font (or the default font if the name is unknown) in the specified size."
- 
- 	^ ((TextStyle named: aName asSymbol) ifNil: [TextStyle default]) fontOfPointSize: aSize!

Item was removed:
- ----- Method: StrikeFont class>>familyName:pointSize:emphasized: (in category 'instance creation') -----
- familyName: aName pointSize: aSize emphasized: emphasisCode
- 	"Create the font with this emphasis"
- 
- 	^ (self familyName: aName pointSize: aSize) emphasized: emphasisCode!

Item was removed:
- ----- Method: StrikeFont class>>familyName:size: (in category 'accessing') -----
- familyName: aName size: aSize
- 	"Answer a font (or the default font if the name is unknown) in the specified size."
- 	| style |
- 	style := TextStyle named: aName asSymbol.
- 	style ifNil: [^(MissingFont forFamilyName: aName pixelSize: aSize)
- 			signal: 'missing font' ].
- 	^style fontOfSize: aSize!

Item was removed:
- ----- Method: StrikeFont class>>familyName:size:emphasized: (in category 'instance creation') -----
- familyName: aName size: aSize emphasized: emphasisCode
- 	"Create the font with this emphasis"
- 
- 	^ (self familyName: aName size: aSize) emphasized: emphasisCode!

Item was removed:
- ----- Method: StrikeFont class>>familyNames (in category 'accessing') -----
- familyNames
- 	^ (TextConstants select: [:each | each isKindOf: TextStyle]) keys asArray sort!

Item was removed:
- ----- Method: StrikeFont class>>fixAccuISO8859From: (in category 'instance creation') -----
- fixAccuISO8859From: aStrikeFont
- 
- 	^aStrikeFont copy fixAccuISO8859From: aStrikeFont.
- !

Item was removed:
- ----- Method: StrikeFont class>>fixDejaVuPointSIze: (in category 'font creation') -----
- fixDejaVuPointSIze: pointSize
- 	"Maps the given pointSize to 96 ppi."
- 	
- 	^ (Dictionary newFrom: {
- 		7 -> 7.5.
- 		9 -> 10.5.
- 		12 -> 14.5.
- 		14 -> 16.5.
- 		17 -> 19.5.
- 		20 -> 23.5}) at: pointSize
- 	!

Item was removed:
- ----- Method: StrikeFont class>>fromHostFont:size:flags:weight: (in category 'font creation') -----
- fromHostFont: fontName size: fontSize flags: fontFlags weight: fontWeight
- 	"
- 		^StrikeFont fromHostFont: (StrikeFont hostFontFromUser)
- 					size: 12 flags: 0 weight: 4.
- 	"
- 	| fontHandle glyphs xTable xStart maxWidth w glyphForm ascent descent fontHeight |
- 	fontHandle := self primitiveCreateFont: fontName size: fontSize flags: fontFlags weight: fontWeight.
- 	ascent := self primitiveFontAscent: fontHandle.
- 	descent := self primitiveFontDescent: fontHandle.
- 	fontHeight := ascent + descent.
- 	xTable := Array new: 258.
- 	xStart := maxWidth := 0.
- 	0 to: 255 do:[:i|
- 		xTable at: i+1 put: xStart.
- 		w := self primitiveFont: fontHandle widthOfChar: i.
- 		w > maxWidth ifTrue:[maxWidth := w].
- 		xStart := xStart + w].
- 	xTable at: 256 put: xStart.
- 	xTable at: 257 put: xStart.
- 	xTable at: 258 put: xStart.
- 	glyphs := Form extent: xTable last @ fontHeight depth: 1.
- 	glyphForm := Form extent: maxWidth @ fontHeight depth: 1.
- 	0 to: 255 do:[:i|
- 		glyphForm fillWhite.
- 		self primitiveFont: fontHandle glyphOfChar: i into: glyphForm.
- 		xStart := xTable at: i+1.
- 		glyphForm displayOn: glyphs at: xStart at 0.
- 		glyphForm displayOn: Display at: xStart at 0.
- 	].
- 	self primitiveDestroyFont: fontHandle.
- 	^Array with: glyphs with: xTable!

Item was removed:
- ----- Method: StrikeFont class>>fromStrike: (in category 'instance creation') -----
- fromStrike: fileName 
- 	"Read a font from disk in the old ST-80 'strike' format.
- 	Note: this is an old format; use strike2 format instead"
- 
- 	^self new newFromStrike: fileName!

Item was removed:
- ----- Method: StrikeFont class>>generateDejaVuMethods: (in category 'font creation') -----
- generateDejaVuMethods: directory
- 	"StrikeFont generateDejaVuMethods: 'DejaVu'."
- 	| dir formTemplate dataTemplate methodCategory |
- 	methodCategory := #'dejaVu font data'.
- 	formTemplate := '{1}
- 	<generated>
- 	" Form data for {2}. Generated with StrikeFont generateDejaVuMethods: ''{3}''"
- 	^Form fromBinaryStream: (
- ''{4}''
- 	) base64Decoded asByteArray readStream
- '.
- 	dataTemplate := '{1}
- 	<generated>
- 	" Font meta data for {2}. Generated with StrikeFont generateDejaVuMethods: ''{3}''"
- 	^ #({4})
- '.
- 	dir := FileDirectory default / directory.
- 	#('*.txt' 'Data' '*.png' 'Form') pairsDo: 
- 		[:match :suffix | (dir fileNamesMatching: match)
- 			do: 
- 				[:local | | selector source stringContent|
- 					" .txt and .png have both length 4"
- 					selector := (local allButLast: 4) asLegalSelector, suffix.
- 					stringContent := dir readOnlyFileNamed: local do:
- 						[:stream | suffix = 'Data'
- 							ifTrue: [stream contentsOfEntireFile]
- 							ifFalse: [(stream binary; contentsOfEntireFile) base64Encoded]].
- 					source := (suffix = 'Data' ifTrue: [dataTemplate] ifFalse: [formTemplate])
- 						format: {selector . (local allButLast: 4) . directory . stringContent }.
- 					self class compile: source classified: methodCategory]
- 			displayingProgress: [:local | 'Generating {1}' translated format: {local}]].!

Item was removed:
- ----- Method: StrikeFont class>>hostFontFromUser (in category 'font creation') -----
- hostFontFromUser
- 	"StrikeFont hostFontFromUser"
- 	| fontNames index labels |
- 	fontNames := self listFontNames sort.
- 	labels := WriteStream on: (String new: 100).
- 	fontNames
- 		do:
- 			[:fn|
- 			labels nextPutAll: fn]
- 		separatedBy:[labels cr].
- 	index := (Project uiManager
- 				chooseOptionFrom: (labels contents substrings) 
- 				title: 'Choose your font').
- 	index = 0 ifTrue:[^nil].
- 	^fontNames at: index!

Item was removed:
- ----- Method: StrikeFont class>>initialize (in category 'class initialization') -----
- initialize
- 	StrikeFont
- 		installDejaVuDark;
- 		installDejaVu!

Item was removed:
- ----- Method: StrikeFont class>>installDejaVu (in category 'font creation') -----
- installDejaVu
- 	"You have to re-create UI themes after doing this.
- 	StrikeFont installDejaVu
- 	"
- 
- 	TextConstants
- 		at: 'Bitmap DejaVu Sans' 
- 		put: (TextStyle fontArray: (#(7 9 12 14 17 20) collect: [:size | self createDejaVu: size])).
- !

Item was removed:
- ----- Method: StrikeFont class>>installDejaVuDark (in category 'font creation') -----
- installDejaVuDark
- 	" This is a Version of dejaVu renderd for light text on dark background. You have to re-create UI themes after doing this.
- 	StrikeFont installDejaVuDark
- 	"
- 
- 	TextConstants
- 		at: 'Darkmap DejaVu Sans' 
- 		put: (TextStyle fontArray: (#(7 9 12 14 17 20) collect: [:size | self createDejaVuDark: size])).
- !

Item was removed:
- ----- Method: StrikeFont class>>limitTo16Bits (in category 'removing') -----
- limitTo16Bits
- 	"Limit glyph depth to 16 bits (it is usually 16 or 32).
- 	
- 	StrikeFont limitTo16Bits
- 	"
- 	StrikeFont allInstances do: [ :f | f
- 		setGlyphsDepthAtMost: 16 ].!

Item was removed:
- ----- Method: StrikeFont class>>listFont: (in category 'font creation') -----
- listFont: index
- 	<primitive:'primitiveListFont' module:'FontPlugin'>
- 	^nil!

Item was removed:
- ----- Method: StrikeFont class>>listFontNames (in category 'font creation') -----
- listFontNames
- 	"StrikeFont listFontNames"
- 	"List all the OS font names"
- 	| font fontNames index |
- 	fontNames := WriteStream on: Array new.
- 	index := 0.
- 	[font := self listFont: index.
- 	font == nil] whileFalse:[
- 		fontNames nextPut: font.
- 		index := index + 1].
- 	^fontNames contents!

Item was removed:
- ----- Method: StrikeFont class>>makeControlCharsVisible (in category 'character shapes') -----
- makeControlCharsVisible
- 	"
- 	Make normally not visible characters, visible
- 	StrikeFont makeControlCharsVisible
- 	"
- 	self allInstances do: [ :font | font makeControlCharsVisible ]!

Item was removed:
- ----- Method: StrikeFont class>>makeLfInvisible (in category 'character shapes') -----
- makeLfInvisible
- 	"
- 	Make line feed characters invisible
- 	StrikeFont makeLfInvisible
- 	"
- 	self allInstances do: [ :font | font makeLfInvisible ]!

Item was removed:
- ----- Method: StrikeFont class>>makeLfVisible (in category 'character shapes') -----
- makeLfVisible
- 	"
- 	Make line feed characters visible
- 	StrikeFont makeLfVisible
- 	"
- 	self allInstances do: [ :font | font makeLfVisible ]!

Item was removed:
- ----- Method: StrikeFont class>>makeTabInvisible (in category 'character shapes') -----
- makeTabInvisible
- 	"
- 	Make tab characters invisible
- 	StrikeFont makeTabInvisible
- 	"
- 	self allInstances do: [ :font | font makeTabInvisible ]!

Item was removed:
- ----- Method: StrikeFont class>>makeTabVisible (in category 'character shapes') -----
- makeTabVisible
- 	"
- 	Make tab characters visible
- 	StrikeFont makeTabVisible
- 	"
- 	self allInstances do: [ :font | font makeTabVisible ]!

Item was removed:
- ----- Method: StrikeFont class>>newFromBDFFile:name: (in category 'instance creation') -----
- newFromBDFFile: aFileName name: aString  "StrikeFont newFromBDFFile: 'helvR12.bdf' name: 'Helvetica12'"
- 	"Read a font from disk in the X11 Bitmap Distribution Format."
- 
- 	| n |
- 	n := self new.
- 	n readBDFFromFile: aFileName name: aString.
- 	^n.
- 
- 	"TextConstants at: #Helvetica put: (TextStyle fontArray: {StrikeFont newFromBDFFile: 'helvR12.bdf' name: 'Helvetica12'})"
- 	"TextConstants at: #Lucida put: (TextStyle fontArray: {StrikeFont newFromBDFFile: 'luRS12.bdf' name: 'Lucida'})"
- 	"TextStyle default fontAt: 5 put: (StrikeFont new readFromStrike2: 'helv12.sf2')."
- 
- !

Item was removed:
- ----- Method: StrikeFont class>>passwordFont (in category 'instance creation') -----
- passwordFont
- 
- 	^ self passwordFontPointSize: TextStyle defaultFont pointSize!

Item was removed:
- ----- Method: StrikeFont class>>passwordFontPointSize: (in category 'instance creation') -----
- passwordFontPointSize: pointSize
- 
- 	^ FixedFaceFont new passwordFont fontPointSize: pointSize!

Item was removed:
- ----- Method: StrikeFont class>>passwordFontSize: (in category 'instance creation') -----
- passwordFontSize: aSize 
- 	^ FixedFaceFont new passwordFont fontSize: aSize!

Item was removed:
- ----- Method: StrikeFont class>>primitiveCreateFont:size:flags:weight: (in category 'font creation') -----
- primitiveCreateFont: fontName size: fontSize flags: fontFlags weight: fontWeight
- 	<primitive:'primitiveCreateFont' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: StrikeFont class>>primitiveDestroyFont: (in category 'font creation') -----
- primitiveDestroyFont: fontHandle
- 	<primitive:'primitiveDestroyFont' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: StrikeFont class>>primitiveFont:glyphOfChar:into: (in category 'font creation') -----
- primitiveFont: fontHandle glyphOfChar: charIndex into: glyphForm
- 	<primitive:'primitiveFontGlyphOfChar' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: StrikeFont class>>primitiveFont:widthOfChar: (in category 'font creation') -----
- primitiveFont: fontHandle widthOfChar: charIndex
- 	<primitive:'primitiveFontWidthOfChar' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: StrikeFont class>>primitiveFontAscent: (in category 'font creation') -----
- primitiveFontAscent: fontHandle
- 	<primitive:'primitiveFontAscent' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: StrikeFont class>>primitiveFontDescent: (in category 'font creation') -----
- primitiveFontDescent: fontHandle
- 	<primitive:'primitiveFontDescent' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: StrikeFont class>>primitiveFontEncoding: (in category 'font creation') -----
- primitiveFontEncoding: fontHandle
- 	<primitive:'primitiveFontEncoding' module:'FontPlugin'>
- 	^self primitiveFailed!

Item was removed:
- ----- Method: StrikeFont class>>readStrikeFont2Family: (in category 'examples') -----
- readStrikeFont2Family: familyName 
- 	"StrikeFont readStrikeFont2Family: 'Lucida'"
- 
- 	^self readStrikeFont2Family: familyName fromDirectory: FileDirectory default!

Item was removed:
- ----- Method: StrikeFont class>>readStrikeFont2Family:fromDirectory: (in category 'examples') -----
- readStrikeFont2Family: familyName fromDirectory: aDirectory
- 	"StrikeFont readStrikeFont2Family: 'Lucida' fromDirectory: FileDirectory default"
- 	"This utility reads all available .sf2 StrikeFont files for a given family from  
- 	the current directory. It returns an Array, sorted by size, suitable for handing 
- 	to TextStyle newFontArray: ."
- 	"For this utility to work as is, the .sf2 files must be named 'familyNN.sf2'."
- 	| fileNames strikeFonts |
- 	fileNames := aDirectory fileNamesMatching: familyName , '##.sf2'.
- 	strikeFonts := fileNames collect: [:fname | StrikeFont new readFromStrike2: (aDirectory fullNameFor: fname)].
- 	strikeFonts do: [ :font | font reset ].
- 	^strikeFonts asArray sort: [:a :b | a height < b height].
- 
- 	"TextConstants at: #Lucida put: (TextStyle fontArray: (StrikeFont  readStrikeFont2Family: 'Lucida' fromDirectory: FileDirectory default))."!

Item was removed:
- ----- Method: StrikeFont class>>saveSpace (in category 'removing') -----
- saveSpace
- 	"Removes glyphs over 128, leaving only lower ascii.
- 	Also limit glyph depth to 4 bits (it is usually 16 or 32).
- 	This effectively turns off subpixel rendering, as glyphs will only have 16 shades of gray.
- 	
- 	StrikeFont saveSpace
- 	"
- 	StrikeFont allInstances do: [ :f | f
- 		stripHighGlyphs;
- 		setGlyphsDepthAtMost: 4 ].!

Item was removed:
- ----- Method: StrikeFont class>>shutDown (in category 'derivative font caching') -----
- shutDown  "StrikeFont shutDown"
- 	"Deallocate synthetically derived copies of base fonts to save space"
- 	self allSubInstancesDo: [:sf | sf reset].
- 	DefaultStringScanner := nil.
- !

Item was removed:
- ----- Method: StrikeFont class>>unload (in category 'class initialization') -----
- unload
- 	Smalltalk removeFromShutDownList: self.
- !

Item was removed:
- ----- Method: StrikeFont class>>useUnderscoreIfOver1bpp (in category 'character shapes') -----
- useUnderscoreIfOver1bpp
- 	"Sets underscore and caret glyphs for chars 95 and 94. 
- 	Only for enhanced StrikeFonts, i.e. those with glyphs of more than 1bpp.
- 	ASCII standard glyphs"
- 	"
- 	StrikeFont useUnderscoreIfOver1bpp
- 	"
- 	self allInstances do: [ :font | font useUnderscoreIfOver1bpp ]!

Item was removed:
- ----- Method: StrikeFont>>aComment (in category 'Mac reader') -----
- aComment
- 	"To read Mac font resources.  
- 1) Use ResEdit in the Fonts folder in the System Folder.  Open the file of the Font you want.  (A screen font, not a TrueType outline font).
- 2) Open the FOND resource and scroll down to the list of sizes and resource numbers. Note the resource number of the size you want.
- 3) Open the NFNT resource.  Click on the number you have noted.
- 4) Choose 'Open Using Hex Editor' from the resource editor.
- 5) Copy all of the hex numbers and paste into a text editor.  Save the file into the Smalltalk folder under the name 'FontName 12 hex' (or other size).
- 6) Enter the fileName below and execute: 
- 
- TextStyle default fontAt: 8 put: (StrikeFont new readMacFontHex: 'fileName').
- 
- Select text and type Command-7 to change it to your new font.
- 
- (There is some problem in the ParagraphEditor with the large size of Cairo 18.  Its line heights are not the right.)
- 	"!

Item was removed:
- ----- Method: StrikeFont>>alter:formBlock: (in category 'character shapes') -----
- alter: char formBlock: formBlock
- 	self characterFormAt: char 
- 		put: (formBlock value: (self characterFormAt: char))!

Item was removed:
- ----- Method: StrikeFont>>asFontSet (in category 'converting') -----
- asFontSet
- 
- 	^ StrikeFontSet newFontArray: {self}!

Item was removed:
- ----- Method: StrikeFont>>ascent (in category 'accessing') -----
- ascent
- 	"Answer the receiver's maximum extent of characters above the baseline."
- 
- 	^ascent!

Item was removed:
- ----- Method: StrikeFont>>ascentKern (in category 'accessing') -----
- ascentKern
- 	"Return the kern delta for ascenders."
- 	
- 	self depth > 1 ifTrue: [^ 0].
- 	
- 	"Optimization for traditional 1-bit fonts."
- 	^ (emphasis allMask: 2)
- 		ifFalse: [0]
- 		ifTrue: [(self ascent-5+4)//4 max: 0]  "See makeItalicGlyphs"
- 
- !

Item was removed:
- ----- Method: StrikeFont>>ascentOf: (in category 'accessing') -----
- ascentOf: aCharacter
- 
- 	(self hasGlyphOf: aCharacter) ifFalse: [
- 		fallbackFont ifNotNil: [
- 			^ fallbackFont ascentOf: aCharacter.
- 		].
- 	].
- 	^ self ascent.
- !

Item was removed:
- ----- Method: StrikeFont>>baseKern (in category 'accessing') -----
- baseKern
- 	"Return the base kern value to be used for all characters."
- 	
- 	self depth > 1 ifTrue: [^ 0].
- 	
- 	"Optimization for traditional 1-bit fonts."
- 	^ (emphasis allMask: 2)
- 		ifFalse: [0]
- 		ifTrue: [((self height-1-self ascent+4)//4 max: 0)  "See makeItalicGlyphs"
- 			+ (((self ascent-5+4)//4 max: 0))]!

Item was removed:
- ----- Method: StrikeFont>>basicHasGlyphOf: (in category 'private') -----
- basicHasGlyphOf: aCharacter
- 
- 	^ self hasGlyphForCode: (self codeForCharacter: aCharacter)
- !

Item was removed:
- ----- Method: StrikeFont>>bonk:with: (in category 'emphasis') -----
- bonk: glyphForm with: bonkForm
- 	"Bonking means to run through the glyphs clearing out black pixels
- 	between characters to prevent them from straying into an adjacent
- 	character as a result of, eg, bolding or italicizing"
- 	"Uses the bonkForm to erase at every character boundary in glyphs."
- 	| bb offset x |
- 	offset := bonkForm offset x.
- 	bb := BitBlt toForm: glyphForm.
- 	bb sourceForm: bonkForm; sourceRect: bonkForm boundingBox;
- 		combinationRule: Form erase; destY: 0.
- 	x := self xTable.
- 	(x isMemberOf: SparseLargeTable) ifTrue: [
- 		x base to: x size-1 do: [:i | bb destX: (x at: i) + offset; copyBits].
- 	] ifFalse: [
- 		1 to: x size-1 do: [:i | bb destX: (x at: i) + offset; copyBits].
- 	].
- !

Item was removed:
- ----- Method: StrikeFont>>buildFromForm:data:name: (in category 'building') -----
- buildFromForm: allGlyphs data: data name: aString
- 
- 	| x formMetadata glyphsXStart |
- 	data first = 0 ifFalse: [^ self buildLimitedFromForm: allGlyphs data: data name: aString].
- 	formMetadata := data readStream.
- 	type := formMetadata next.
- 	pointSize := formMetadata next.
- 	ascent := formMetadata next.
- 	descent := formMetadata next.
- 	
- 	minAscii := formMetadata next.
- 	maxAscii := formMetadata next.
- 	maxWidth := formMetadata next.
- 	emphasis := formMetadata next.
- 	glyphsXStart := formMetadata upToEnd.
- 	name := aString.
- 
- 	superscript := ascent - descent // 3.	
- 	subscript := descent - ascent // 3.	
- 
- 	xTable := maxAscii > 1024
- 		ifFalse: [Array new: maxAscii + 3 withAll: 0]
- 		ifTrue: [ | mostCommon |
- 			mostCommon := glyphsXStart asBag sortedCounts first value.
- 			SparseLargeTable new: maxAscii + 3
- 			chunkSize: 256 arrayClass: Array base: 1
- 			defaultValue: mostCommon].
- 	glyphs := allGlyphs.
- 	x := 0.
- 	minAscii to: maxAscii + 1 do: [ :i |
- 		x := (glyphsXStart at: i - minAscii + 1).
- 		xTable at: i + 1 put: x].
- 	self reset.
- 	derivativeFonts := Array new: 32!

Item was removed:
- ----- Method: StrikeFont>>buildLimitedFromForm:data:name: (in category 'building') -----
- buildLimitedFromForm: allGlyphs data: data name: aString
- 
- 	| x |
- 	pointSize := data first.
- 	ascent := data second.
- 	descent := data third.
- 	
- 	minAscii := 32.
- 	maxAscii := 255.
- 	name := aString.
- 	type := 0.  "ignored for now"
- 	superscript := ascent - descent // 3.	
- 	subscript := descent - ascent // 3.	
- 	emphasis := 0.
- 
- 	xTable := (Array new: 258) atAllPut: 0.
- 	maxWidth := 0.
- 	glyphs := allGlyphs.
- 	x := 0.
- 	minAscii to: maxAscii+1 do: [ :i |
- 		x := (data at: i-minAscii+4).
- 		xTable at: i+1 put: x].
- 	xTable at: 258 put: x.
- 	self reset.
- 	derivativeFonts := Array new: 32!

Item was removed:
- ----- Method: StrikeFont>>buildfontNamed:fromForms:startingAtAscii:ascent:descent:maxWid: (in category 'file in/out') -----
- buildfontNamed: nm fromForms: forms startingAtAscii: startAscii
- 	ascent: a descent: d maxWid: m
- 	"This builds a StrikeFont instance from existing forms."
- 
- 	| lastAscii width ascii charForm missingForm tempGlyphs |
- 	name := nm.
- 	ascent := 11.
- 	descent := 3.
- 	maxWidth := 16.
- 	pointSize := 8.
- 	name := (name copyWithout: Character space) ,
- 				(pointSize < 10
- 					ifTrue: ['0' , pointSize printString]
- 					ifFalse: [pointSize printString]).
- 	minAscii := 258.
- 	maxAscii := 0.
- 	superscript := ascent - descent // 3.	
- 	subscript := descent - ascent // 3.	
- 	emphasis := 0.
- 	type := 0.  "ignored for now"
- 
- 	tempGlyphs := Form extent: (maxWidth*257) @ self height.
- 	xTable := (Array new: 258) atAllPut: 0.
- 	xTable at: 1 put: 0.
- 
- 	"Read character forms and blt into tempGlyphs"
- 	lastAscii := -1.
- 	1 to: forms size do:
- 		[:i | charForm := forms at: i. width := charForm width.
- 		ascii := startAscii-1+i.
- 		self displayChar: ascii form: charForm.
- 		ascii = 256
- 			ifTrue: [missingForm := charForm deepCopy]
- 			ifFalse:
- 			[minAscii := minAscii min: ascii.
- 			maxAscii := maxAscii max: ascii.
- 			lastAscii+1 to: ascii-1 do: [:as | xTable at: as+2 put: (xTable at: as+1)].
- 			tempGlyphs copy: ((xTable at: ascii+1)@0
- 									extent: charForm extent)
- 						from: 0 at 0 in: charForm rule: Form over.
- 			xTable at: ascii+2 put: (xTable at: ascii+1) + width.
- 			lastAscii := ascii]].
- 	lastAscii+1 to: maxAscii+1 do: [:as | xTable at: as+2 put: (xTable at: as+1)].
- 	missingForm == nil ifFalse:
- 		[tempGlyphs copy: missingForm boundingBox from: missingForm
- 				to: (xTable at: maxAscii+2)@0 rule: Form over.
- 		xTable at: maxAscii+3 put: (xTable at: maxAscii+2) + missingForm width].
- 	glyphs := Form extent: (xTable at: maxAscii+3) @ self height.
- 	glyphs copy: glyphs boundingBox from: 0 at 0 in: tempGlyphs rule: Form over.
- 	xTable := xTable copyFrom: 1 to: maxAscii+3.
- 	characterToGlyphMap := nil.!

Item was removed:
- ----- Method: StrikeFont>>characterForm:pixelValueAt:put: (in category 'character shapes') -----
- characterForm: char pixelValueAt: pt put: val
- 	| f |
- 	f := self characterFormAt: char.
- 	f pixelAt: pt put: val.
- 	self characterFormAt: char put: val!

Item was removed:
- ----- Method: StrikeFont>>characterFormAt: (in category 'character shapes') -----
- characterFormAt: character 
- 	"Answer a Form copied out of the glyphs for the argument, character."
- 
- 	| ascii leftX rightX |
- 	ascii := self codeForCharacter: character.
- 	leftX := xTable at: ascii + 1.
- 	rightX := xTable at: ascii + 2.
- 	leftX < 0 ifTrue: [^ glyphs copy: (0 at 0 corner: 0 at self height)].
- 	^ glyphs copy: (leftX @ 0 corner: rightX @ self height)!

Item was removed:
- ----- Method: StrikeFont>>characterFormAt:put: (in category 'character shapes') -----
- characterFormAt: character put: characterForm
- 	"Copy characterForm over the glyph for the argument, character."
- 	| ascii leftX rightX widthDif newGlyphs |
- 	ascii := character asciiValue.
- 	ascii < minAscii ifTrue: [^ self error: 'Cant store characters below min ascii'].
- 	ascii > maxAscii ifTrue:
- 		[(self confirm:
- 'This font does not accomodate ascii values higher than ' , maxAscii printString , '.
- Do you wish to extend it permanently to handle values up to ' , ascii printString)
- 			ifTrue: [self extendMaxAsciiTo: ascii]
- 			ifFalse: [^ self error: 'No change made']].
- 	leftX := xTable at: ascii + 1.
- 	rightX := xTable at: ascii + 2.
- 	widthDif := characterForm width - (rightX - leftX).
- 	widthDif ~= 0 ifTrue:
- 		["Make new glyphs with more or less space for this char"
- 		newGlyphs := Form extent: (glyphs width + widthDif) @ glyphs height depth: glyphs depth.
- 		newGlyphs copy: (0 at 0 corner: leftX at glyphs height)
- 			from: 0 at 0 in: glyphs rule: Form over.
- 		newGlyphs copy: ((rightX+widthDif)@0 corner: newGlyphs width at glyphs height)
- 			from: rightX at 0 in: glyphs rule: Form over.
- 		glyphs := newGlyphs.
- 		"adjust further entries on xTable"
- 		xTable := xTable copy.
- 		ascii+2 to: xTable size
- 			do: [:i | xTable at: i put: (xTable at: i) + widthDif]].
- 	glyphs copy: (leftX @ 0 extent: characterForm extent)
- 		from: 0 at 0 in: characterForm rule: Form over
- "
- | f |  f := TextStyle defaultFont.
- f characterFormAt: $  put: (Form extent: (f widthOf: $ )+10 at f height)
- "!

Item was removed:
- ----- Method: StrikeFont>>characterToGlyphMap (in category 'accessing') -----
- characterToGlyphMap
- 	^characterToGlyphMap ifNil:[characterToGlyphMap := self createCharacterToGlyphMap].!

Item was removed:
- ----- Method: StrikeFont>>characterToGlyphMap: (in category 'accessing') -----
- characterToGlyphMap: anArray
- 	characterToGlyphMap := anArray.!

Item was removed:
- ----- Method: StrikeFont>>characters:in:displayAt:clippedBy:rule:fillColor:kernDelta:on: (in category 'displaying') -----
- characters: anInterval in: sourceString displayAt: aPoint clippedBy: clippingRectangle rule: ruleInteger fillColor: aForm kernDelta: kernDelta on: aBitBlt
- 	"Simple, slow, primitive method for displaying a line of characters.
- 	No wrap-around is provided."
- 	| destPoint |
- 	destPoint := aPoint.
- 	anInterval do: 
- 		[:i | | sourceRect leftX ascii rightX |
- 		self flag: #yoDisplay.
- 		"if the char is not supported, fall back to the specified fontset."
- 		ascii := self codeForCharacter: (sourceString at: i).
- 		(ascii < minAscii or: [ascii > maxAscii])
- 			ifTrue: [ascii := maxAscii].
- 		leftX := xTable at: ascii + 1.
- 		rightX := xTable at: ascii + 2.
- 		sourceRect := leftX at 0 extent: (rightX-leftX) @ self height.
- 		aBitBlt copyFrom: sourceRect in: glyphs to: destPoint.
- 		destPoint := destPoint + ((rightX-leftX+kernDelta)@0).
- 		"destPoint printString displayAt: 0@(i*20)"].
- 	^ destPoint!

Item was removed:
- ----- Method: StrikeFont>>checkCharacter: (in category 'testing') -----
- checkCharacter: character 
- 	"Answer a Character that is within the ascii range of the receiver--either 
- 	character or the last character in the receiver."
- 
- 	| ascii |  
- 	ascii := character asciiValue.
- 	((ascii < minAscii) or: [ascii > maxAscii])
- 			ifTrue: [^maxAscii asCharacter]
- 			ifFalse:	[^character]
- !

Item was removed:
- ----- Method: StrikeFont>>closeHtmlOn: (in category 'html') -----
- closeHtmlOn: aStream 
- 
- 	aStream nextPutAll: '</font>'.!

Item was removed:
- ----- Method: StrikeFont>>codeForCharacter: (in category 'private') -----
- codeForCharacter: aCharacter
- 	| code |
- 	code := aCharacter charCode.
- 	(self characterToGlyphMap isNil
- 		or: [	characterToGlyphMap size <= code ])
- 			ifTrue: [^code].
- 	^characterToGlyphMap at: code + 1!

Item was removed:
- ----- Method: StrikeFont>>createCharacterToGlyphMap (in category 'private') -----
- createCharacterToGlyphMap
-         "Private. Create the character to glyph mapping for a font that didn't have any before. This is basically equivalent to what the former setStopCondition did, only based on indexes."
- 
-         maxAscii < 256 ifTrue: [^ (1 to: 256) collect: [:i | i - 1]].
-         ^ nil.
- !

Item was removed:
- ----- Method: StrikeFont>>deepCopy (in category 'copying') -----
- deepCopy
-  " there is a circular reference from the derivative fonts back to the receiver. It is therefore not possible to make a deep copy. We make a sahllow copy. The method postCopy can be used to modify the shallow copy. " 
-   ^self copy!

Item was removed:
- ----- Method: StrikeFont>>depth (in category 'accessing') -----
- depth
- 
- 	^ self glyphs depth!

Item was removed:
- ----- Method: StrikeFont>>derivativeFont:at: (in category 'emphasis') -----
- derivativeFont: aStrikeFont at: index
- 
- 	| newDeriv |
- 	(aStrikeFont isNil and: [ index = 0 ]) 
- 		ifTrue: [derivativeFonts := nil. ^ self].
- 	derivativeFonts ifNil: [derivativeFonts := Array new: 32].
- 	derivativeFonts size < 32 ifTrue: [
- 		newDeriv := Array new: 32.
- 		newDeriv replaceFrom: 1 to: derivativeFonts size with: derivativeFonts.
- 		derivativeFonts := newDeriv.
- 	].
- 	derivativeFonts at: index put: aStrikeFont.!

Item was removed:
- ----- Method: StrikeFont>>derivativeFonts (in category 'accessing') -----
- derivativeFonts
- 	derivativeFonts ifNil: [^#()].
- 	^derivativeFonts copyWithout: nil!

Item was removed:
- ----- Method: StrikeFont>>descent (in category 'accessing') -----
- descent
- 	"Answer the receiver's maximum extent of characters below the baseline."
- 
- 	^descent!

Item was removed:
- ----- Method: StrikeFont>>descentKern (in category 'accessing') -----
- descentKern
- 	"Return the kern delta for descenders."
- 
- 	self depth > 1 ifTrue: [^ 0].
- 
- 	"Optimization for traditional 1-bit fonts."
- 	^ (emphasis allMask: 2)
- 		ifFalse: [0]
- 		ifTrue: [(self height-1-self ascent+4)//4 max: 0]  "See makeItalicGlyphs"
- 
- !

Item was removed:
- ----- Method: StrikeFont>>descentOf: (in category 'accessing') -----
- descentOf: aCharacter
- 
- 	(self hasGlyphOf: aCharacter) ifFalse: [
- 		fallbackFont ifNotNil: [
- 			^ fallbackFont descentOf: aCharacter.
- 		].
- 	].
- 	^ self descent.
- !

Item was removed:
- ----- Method: StrikeFont>>displayChar:form: (in category 'file in/out') -----
- displayChar: ascii form: charForm
- 	"Convenience utility used during conversion of BitFont files"
- 	| m bigForm |
- 	Display fillBlack: (0 at 0 extent: 20 at 14).
- 	ascii printString displayAt: 0 at 2.
- 	charForm width > 0 ifTrue:
- 		[m := 5.
- 		bigForm := charForm magnify: charForm boundingBox by: m at m.
- 		Display border: ((bigForm boundingBox expandBy: m) translateBy: 50 at 2) width: m.
- 		bigForm displayAt: 50 at 2.
- 		Display fillBlack: ((50 at 2)+((m*charForm width)@0) extent: 1@(m*self height))].!

Item was removed:
- ----- Method: StrikeFont>>displayLine:at: (in category 'displaying') -----
- displayLine: aString at: aPoint 
- 	"Display the characters in aString, starting at position aPoint."
- 
- 	self characters: (1 to: aString size)
- 		in: aString
- 		displayAt: aPoint
- 		clippedBy: Display boundingBox
- 		rule: Form over
- 		fillColor: nil
- 		kernDelta: 0
- 		on: (BitBlt toForm: Display).
- !

Item was removed:
- ----- Method: StrikeFont>>displayMultiString:on:from:to:at:kern:baselineY: (in category 'displaying') -----
- displayMultiString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY
- "display a multi-byte character string"
- 	| leftX rightX glyphInfo char destY form gfont destX destPt |
- 	destX := aPoint x.
- 	glyphInfo := Array new: 5.
- 	startIndex to: stopIndex do:[:charIndex|
- 		char := aString at: charIndex.
- 		(self hasGlyphOf: char) ifTrue: [
- 			"I have that character ok, so display it and move on"
- 			self glyphInfoOf: char into: glyphInfo.
- 			form := glyphInfo at: 1.
- 			leftX := glyphInfo at: 2.
- 			rightX := glyphInfo at: 3.
- 			destY := glyphInfo at: 4.
- 			gfont := glyphInfo at: 5.
- 			(gfont == aBitBlt lastFont) ifFalse: [gfont installOn: aBitBlt].
- 			destY := baselineY - destY. 
- 			aBitBlt displayGlyph: form at: destX @ destY left: leftX right: rightX font: self.
- 			destX := destX + (rightX - leftX + kernDelta).
- 		] ifFalse:[
- 			"I'm missing that character so pass the job off to my fallback font; if one wasn't previously setup a default fixedfacefont will get used and show question-mark char(s). We pass the entire job to the font since we must not expect it to be a StrikeFont"
- 			destPt := self fallbackFont displayString: aString on: aBitBlt from: charIndex to: charIndex at: destX @ aPoint y kern: kernDelta from: self baselineY: baselineY.
- 			destPt x = destX ifTrue:[
- 				"In some situations BitBlt doesn't return the advance width from the primitive.
- 				Work around the situation"
- 				destX := destX + (self widthOfString: aString from: charIndex to: charIndex) + kernDelta.
- 			] ifFalse:[destX := destPt x].
- 		].
- 	].
- 	^destX @ aPoint y
- !

Item was removed:
- ----- Method: StrikeFont>>displayString:on:from:to:at:kern: (in category 'displaying') -----
- displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta
- 	"Draw the given string from startIndex to stopIndex 
- 	at aPoint on the (already prepared) BitBlt."
- 	
- 	| pt |
- 	(aString isByteString) ifFalse: [^ self displayMultiString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: aPoint y + self ascent.].
- 
- 	pt := aBitBlt displayString: aString 
- 			from: startIndex 
- 			to: stopIndex 
- 			at: aPoint 
- 			strikeFont: self
- 			kern: kernDelta.
- 	pt = aPoint ifFalse:[^pt].
- 	"In some situations BitBlt doesn't return the advance width from the primitive.
- 	Work around the situation"
- 	^aPoint x + (self widthOfString: aString from: startIndex to: stopIndex) + (stopIndex-startIndex+1*kernDelta) @ aPoint y
- !

Item was removed:
- ----- Method: StrikeFont>>displayString:on:from:to:at:kern:baselineY: (in category 'displaying') -----
- displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY
- 	"Draw the given string from startIndex to stopIndex 
- 	at aPoint on the (already prepared) BitBlt."
- 	
- 	(aString isByteString) ifFalse:[^ self displayMultiString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY.].
- 
- 	^ aBitBlt displayString: aString 
- 			from: startIndex 
- 			to: stopIndex 
- 			at: aPoint 
- 			strikeFont: self
- 			kern: kernDelta.!

Item was removed:
- ----- Method: StrikeFont>>displayString:on:from:to:at:kern:from:baselineY: (in category 'displaying') -----
- displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta from: fromFont baselineY: baselineY
- 	"I am used as a fallback for fromFont, which is most likely a StrikeFont."
- 	
- 	aBitBlt installStrikeFont: self.
- 	^ self displayString: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta baselineY: baselineY!

Item was removed:
- ----- Method: StrikeFont>>displayStringR2L:on:from:to:at:kern: (in category 'displaying') -----
- displayStringR2L: aString on: aBitBlt from: startIndex to: stopIndex at: aPoint kern: kernDelta
- 	"You are screwed if you reach this method."
- 	self halt.
- 	aBitBlt displayString: aString 
- 			from: startIndex 
- 			to: stopIndex 
- 			at: aPoint 
- 			strikeFont: self
- 			kern: kernDelta.!

Item was removed:
- ----- Method: StrikeFont>>edit: (in category 'character shapes') -----
- edit: character 
- 	"Open a Bit Editor on the given character. Note that you must do an accept 
- 	(in the option menu of the bit editor) if you want this work. 
- 	Accepted edits will not take effect in the font until you leave or close the bit editor. 
- 	Also note that unaccepted edits will be lost when you leave or close."
- 	"Note that BitEditor only works in MVC currently."
- 
- 	"(TextStyle default fontAt: 1) edit: $="
- 
- 	Project current editCharacter: character ofFont: self!

Item was removed:
- ----- Method: StrikeFont>>emphasis (in category 'emphasis') -----
- emphasis
- 	"Answer the integer code for synthetic bold, italic, underline, and 
- 	strike-out."
- 
- 	^emphasis!

Item was removed:
- ----- Method: StrikeFont>>emphasis: (in category 'emphasis') -----
- emphasis: code 
- 	"Set the integer code for synthetic bold, itallic, underline, and strike-out, 
- 	where bold=1, italic=2, underlined=4, and struck out=8."
- 
- 	emphasis := code!

Item was removed:
- ----- Method: StrikeFont>>emphasized: (in category 'emphasis') -----
- emphasized: code 
- 	"Answer a copy of the receiver with emphasis set to include code."
- 	| derivative addedEmphasis base safeCode |
- 	code = 0 ifTrue: [^ self].
- 	code = self emphasis ifTrue: [^ self].
- 	(derivativeFonts == nil or: [derivativeFonts size = 0]) ifTrue: [^ self].
- 	derivative := derivativeFonts at: (safeCode := code min: derivativeFonts size).
- 	derivative == nil ifFalse: [^ derivative].  "Already have this style"
- 
- 	"Dont have it -- derive from another with one with less emphasis"
- 	addedEmphasis := 1 bitShift: safeCode highBit - 1.
- 	base := self emphasized: safeCode - addedEmphasis.  "Order is Bold, Ital, Under, Narrow"
- 	addedEmphasis = 1 ifTrue:   "Compute synthetic bold version of the font"
- 		[derivative := (base copy ensureCleanBold name: base name , 'B') makeBoldGlyphs].
- 	addedEmphasis = 2 ifTrue:   "Compute synthetic italic version of the font"
- 		[ derivative := (base copy name: base name , 'I') makeItalicGlyphs].
- 	addedEmphasis = 4 ifTrue:   "Compute underlined version of the font"
- 		[derivative := (base copy name: base name , 'U') makeUnderlinedGlyphs].
- 	addedEmphasis = 8 ifTrue:   "Compute narrow version of the font"
- 		[derivative := (base copy name: base name , 'N') makeCondensedGlyphs].
- 	addedEmphasis = 16 ifTrue:   "Compute struck-out version of the font"
- 		[derivative := (base copy name: base name , 'X') makeStruckOutGlyphs].
- 	derivative emphasis: safeCode.
- 	derivativeFonts at: safeCode put: derivative.
- 	^ derivative!

Item was removed:
- ----- Method: StrikeFont>>ensureCleanBold (in category 'character shapes') -----
- ensureCleanBold 
- 	"This ensures that all character glyphs have at least one pixel of white space on the right
- 	so as not to cause artifacts in neighboring characters in bold or italic."
- 
- 	| wider glyph |
- 	emphasis = 0 ifFalse: [^ self].
- 	minAscii to: maxAscii do:
- 		[:i | glyph := self characterFormAt: (Character value: i).
- 		(glyph copy: (glyph boundingBox topRight - (1 at 0)
- 					corner: glyph boundingBox bottomRight)) isAllWhite ifFalse: [
- 			wider := Form extent: (glyph width + 1)@glyph height depth: glyph depth.
- 			glyph depth > 1 ifTrue: [wider fillWhite].
- 			glyph displayOn: wider.
- 			self characterFormAt: (Character value: i) put: wider]].
- "
- StrikeFont allInstancesDo: [:f | f ensureCleanBold].
- (StrikeFont familyName: 'NewYork' size: 21) ensureCleanBold.
- StrikeFont shutDown.  'Flush synthetic fonts'.
- "
- !

Item was removed:
- ----- Method: StrikeFont>>extendMaxAsciiTo: (in category 'character shapes') -----
- extendMaxAsciiTo: newMax
- 	"Extend the range of this font so that it can display glyphs up to newMax."
- 
- 	(newMax+3) <= xTable size ifTrue: [^ self].  "No need to extend."
- 	xTable size = (maxAscii+3) ifFalse:
- 		[^ self error: 'This font is not well-formed.'].
- 
- 	"Insert a bunch of zero-width characters..."
- 	xTable := (xTable copyFrom: 1 to: maxAscii+2) ,
- 			((maxAscii+1 to: newMax) collect: [:i | xTable at: maxAscii+2]) ,
- 			{ xTable at: maxAscii+3 }.
- 	maxAscii := newMax.
- 	self fillZeroWidthSlots.
- 	characterToGlyphMap := nil.!

Item was removed:
- ----- Method: StrikeFont>>fallbackFont (in category 'accessing') -----
- fallbackFont
- 	"Overwritten to add a cache."
- 	
- 	^ fallbackFont ifNil: [fallbackFont := super fallbackFont]!

Item was removed:
- ----- Method: StrikeFont>>fallbackFont: (in category 'accessing') -----
- fallbackFont: aFont
- 
- 	fallbackFont := aFont == self ifFalse: [aFont].!

Item was removed:
- ----- Method: StrikeFont>>familyName (in category 'accessing') -----
- familyName
- 	^self name withoutJustTrailingDigits!

Item was removed:
- ----- Method: StrikeFont>>familySizeFace (in category 'accessing') -----
- familySizeFace
- 	"Answer an array with familyName, a String, pointSize, an Integer, and
- 	faceCode, an Integer."
- 
- 	^Array with: name
- 		with: self height
- 		with: emphasis
- 
- 	"(1 to: 12) collect: [:x | (TextStyle default fontAt: x) familySizeFace]"!

Item was removed:
- ----- Method: StrikeFont>>fillZeroWidthSlots (in category 'character shapes') -----
- fillZeroWidthSlots
- 	| nullGlyph |
- 	"Note: this is slow because it copies the font once for every replacement."
- 
- 	nullGlyph := (Form extent: 1 at glyphs height) fillGray.
- 	"Now fill the empty slots with narrow box characters."
- 	minAscii to: maxAscii do:
- 		[:i | (self widthOf: (Character value: i)) = 0 ifTrue:
- 			[self characterFormAt: (Character value: i) put: nullGlyph]].
- !

Item was removed:
- ----- Method: StrikeFont>>fixAccuISO8859From: (in category 'multibyte character methods') -----
- fixAccuISO8859From: aStrikeFont
- 
- 	| f |
- 	self reset.
- 	xTable := aStrikeFont xTable copy.
- 	glyphs := Form extent: aStrikeFont glyphs extent.
- 	maxAscii := 255.
- 	minAscii := 0.
- 	"stopConditions := nil."
- 
- 	0 to: 127 do: [:i |
- 		f := aStrikeFont characterFormAt: (Character value: i).
- 		f width  = 0 ifTrue: [f := Form extent: 1 at f height].
- 		
- 		self characterFormAt: (Character value: i) put: f.
- 	].
- 	128 to: 159 do: [:i |
- 		f := Form extent: 1 at f height.
- 		self characterFormAt: (Character value: i) put: f.
- 	].
- 	160 to: 255 do: [:i |
- 		f := aStrikeFont characterFormAt: (Character value: i).
- 		f width  = 0 ifTrue: [f := Form extent: 1 at f height].
- 		
- 		self characterFormAt: (Character value: i) put: f.
- 	].
- 		
- 	^ self.	
- !

Item was removed:
- ----- Method: StrikeFont>>fixAscent:andDescent:head: (in category 'multibyte character methods') -----
- fixAscent: a andDescent: d head: h
- 
- 	| bb newGlyphs |
- 	"(a + d) = (ascent + descent) ifTrue: ["
- 		ascent := a.
- 		descent := d.
- 		newGlyphs := Form extent: (glyphs width@(h + glyphs height)).
- 		bb := BitBlt toForm: newGlyphs.
- 		bb copy: (0 at h extent: (glyphs extent)) from: 0 at 0 in: glyphs
- 			fillColor: nil rule: Form over.
- 		glyphs := newGlyphs.
- 	"]."
- !

Item was removed:
- ----- Method: StrikeFont>>fixKerning: (in category 'Mac reader') -----
- fixKerning: extraWidth
- 	"Insert one pixel (extraWidth) between each character.  And add the bits for the space character"
- 	"Create a space character Form.  Estimate width by ascent / 2 - 1"
- 	| characterForm char leftX |
- 	characterForm := Form extent: (ascent//2 - 1) @ self height.
- 	self characterFormAt: $  put: characterForm.
- 
- 	"Put one pixel of space after every character.  Mac fonts have no space in the bitmap."
- 	extraWidth <= 0 ifTrue: [^ self].
- 	minAscii to: maxAscii do: [:ascii |
- 		char := Character value: ascii.
- 		leftX := xTable at: ascii + 1.
- 		characterForm := Form extent: 
- 			((self widthOf: char) + extraWidth) @ self height.
- 		characterForm 
- 			copy: (characterForm boundingBox extendBy: 
- 				(0-extraWidth at 0))
- 			from: leftX at 0 in: glyphs rule: Form over.
- 		self characterFormAt: char put: characterForm.
- 		].	!

Item was removed:
- ----- Method: StrikeFont>>fixOneWideChars (in category 'character shapes') -----
- fixOneWideChars 
- 	"This fixes all 1-wide characters to be 2 wide with blank on the right
- 	so as not to cause artifacts in neighboring characters in bold or italic."
- 	| twoWide |
- 	minAscii to: maxAscii do:
- 		[:i | (self widthOf: (Character value: i)) = 1 ifTrue:
- 			[twoWide := Form extent: 2 at glyphs height.
- 			(self characterFormAt: (Character value: i)) displayOn: twoWide at: 0 at 0.
- 			self characterFormAt: (Character value: i) put: twoWide]].
- "
- StrikeFont allInstancesDo: [:f | f fixOneWideChars].
- StrikeFont shutDown.  'Flush synthetic fonts'.
- "
- !

Item was removed:
- ----- Method: StrikeFont>>fixXTable (in category 'multibyte character methods') -----
- fixXTable
- 
- 	| newXTable val |
- 	xTable size >= 258 ifTrue: [
- 		^ self.
- 	].
- 
- 	newXTable := Array new: 258.
- 	1 to: xTable size do: [:i |
- 		newXTable at: i put: (xTable at: i).
- 	].
- 
- 	val := xTable at: (xTable size).
- 	
- 	xTable size + 1 to: 258 do: [:i |
- 		newXTable at: i put: val.
- 	].
- 	minAscii := 0.
- 	maxAscii := 255.
- 	xTable := newXTable.
- !

Item was removed:
- ----- Method: StrikeFont>>fontDisplay (in category 'displaying') -----
- fontDisplay
- 	"TextStyle default defaultFont fontDisplay."
- 
- 	Display restoreAfter:
- 		[(Form extent: 440 at 400) displayAt: 90 at 90.
- 		 0 to: 15 do:
- 			[:i |
- 			i storeStringHex displayAt: 100 @ (20 * i + 100).
- 			0 to: 15 do:
- 				[:j |
- 				((16*i+j) between: 1 and: (self xTable size - 2)) ifTrue:
- 					[(self characterFormAt: (16 * i + j) asCharacter)
- 						displayAt: (20 * j + 150) @ (20 * i + 100)]]].
- 			'Click to continue...' asDisplayText displayAt: 100 at 450]!

Item was removed:
- ----- Method: StrikeFont>>fontNameWithPointSize (in category 'accessing') -----
- fontNameWithPointSize
- 	^self name withoutTrailingDigits, ' ', self pointSize printString!

Item was removed:
- ----- Method: StrikeFont>>formOf: (in category 'private') -----
- formOf: aCharacter
- 	"Like #characterFormAt: but checks for #hasGlyphOf: and supports #fallbackFont."
- 
- 	(self hasGlyphOf: aCharacter)
- 		ifFalse: [^ self fallbackFont formOf: aCharacter].
- 		
- 	^ self characterFormAt: aCharacter!

Item was removed:
- ----- Method: StrikeFont>>glyphInfoOf:into: (in category 'accessing') -----
- glyphInfoOf: aCharacter into: glyphInfoArray 
- 	"Answer the glyph info for aCharacter. If I don't have such a character use my fallback font."
- 
- 	| code |
- 	(self hasGlyphOf: aCharacter) ifFalse: [
- 		^ self fallbackFont
- 			foregroundColor: self foregroundColor;
- 			glyphInfoOf: aCharacter into: glyphInfoArray].
- 	
- 	code := self codeForCharacter: aCharacter.
- 	glyphInfoArray at: 1 put: glyphs;
- 		at: 2 put: (xTable at: code + 1);
- 		at: 3 put: (xTable at: code + 2);
- 		at: 4 put: self ascent "(self ascentOf: aCharacter)";
- 		at: 5 put: self.
- 	^ glyphInfoArray!

Item was removed:
- ----- Method: StrikeFont>>glyphOf: (in category 'private') -----
- glyphOf: aCharacter 
- 
- 	self flag: #deprecated.
- 	^ self formOf: aCharacter!

Item was removed:
- ----- Method: StrikeFont>>glyphs (in category 'accessing') -----
- glyphs
- 	"Answer a Form containing the bits representing the characters of the 
- 	receiver."
- 
- 	^glyphs!

Item was removed:
- ----- Method: StrikeFont>>hasGlyphForCode: (in category 'private') -----
- hasGlyphForCode: aCharacterCode
- 	"Note that missing glyphs are encoded as -1 in the xTable but to speed up the #widthOf: check, the next offset must be adjacent and thus be duplicated. For example: #(-1 -1 0 24 -1 -1 -1 24 48 -1 ...). Since aCharacterCode is 0-based, that codes offset is at +1 while its width needs to consult +2, too. See #widthOf:." 
- 
- 	(aCharacterCode between: self minAscii and: self maxAscii)
- 		ifFalse: [^ false].
- 	(xTable at: aCharacterCode + 1) >= 0
- 		ifFalse: [^ false].
- 	(xTable at: aCharacterCode + 2) >= 0
- 		ifFalse: [^ false].
- 	^ true!

Item was removed:
- ----- Method: StrikeFont>>height (in category 'accessing') -----
- height
- 	"Answer the height of the receiver, total of maximum extents of 
- 	characters above and below the baseline."
- 
- 	^self ascent + self descent!

Item was removed:
- ----- Method: StrikeFont>>heightOf: (in category 'accessing') -----
- heightOf: aCharacter
- 
- 	(self hasGlyphOf: aCharacter) ifFalse: [
- 		fallbackFont ifNotNil: [
- 			^ fallbackFont heightOf: aCharacter.
- 		].
- 	].
- 	^ self height.
- !

Item was removed:
- ----- Method: StrikeFont>>installOn: (in category 'displaying') -----
- installOn: aDisplayContext
- 
- 	^aDisplayContext installStrikeFont: self.
- !

Item was removed:
- ----- Method: StrikeFont>>installOn:foregroundColor:backgroundColor: (in category 'displaying') -----
- installOn: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor
- 	^aDisplayContext 
- 		installStrikeFont: self
- 		foregroundColor: foregroundColor 
- 		backgroundColor: backgroundColor!

Item was removed:
- ----- Method: StrikeFont>>isSynthetic (in category 'emphasis') -----
- isSynthetic
- 	^type = 3!

Item was removed:
- ----- Method: StrikeFont>>isSynthetic: (in category 'emphasis') -----
- isSynthetic: aBoolean
- 	type := aBoolean ifTrue: [3] ifFalse: [0]!

Item was removed:
- ----- Method: StrikeFont>>lineGap (in category 'accessing') -----
- lineGap
- 	"Historical. The #lineGap has been 2 pixels for all fonts in the system for a very long time. Since the #referenceHeight is 14 pixels, use that to compute a #lineGap relative to the receivers #pointSize/#pixelSize. Also see TTCFont >> #lineGap."
- 	
- 	^ lineGap ifNil: [lineGap := ((self height asFloat / self class referenceHeight) * 2 "pixels") rounded]!

Item was removed:
- ----- Method: StrikeFont>>lineGapSlice (in category 'accessing') -----
- lineGapSlice
- 	"Cached portion of the receiver's #lineGap, which can be used to center one-liners in text fields. Also see TTCFont >> #lineGapSlice."
- 	
- 	^ lineGapSlice ifNil: [lineGapSlice := (self lineGap asFloat / 2) rounded]!

Item was removed:
- ----- Method: StrikeFont>>makeAssignArrow (in category 'make arrows') -----
- makeAssignArrow
- "Replace the underline character with an arrow for this font"
- 
- 	| arrowForm arrowCanvas arrowY arrowLeft arrowRight arrowHeadLength |
- 
- 	arrowForm := (self characterFormAt: $_) copy.
- 	arrowCanvas := arrowForm getCanvas.
- 	arrowCanvas fillColor: Color white.
- 	arrowY := arrowForm height // 2.
- 	arrowLeft := 0. 
- 	arrowRight := arrowForm width - 2.
- 	arrowHeadLength := (arrowRight - arrowLeft) * 2 // 5.
- 	"Draw the lines"
- 	arrowCanvas line: (arrowLeft at arrowY) to: (arrowRight at arrowY) color: Color black.
- 	arrowCanvas 
- 		line: (arrowLeft at arrowY) 
- 		to: ((arrowLeft + arrowHeadLength)@(arrowY - arrowHeadLength)) 
- 		color: Color black.
- 	arrowCanvas 
- 		line: (arrowLeft at arrowY) 
- 		to: ((arrowLeft + arrowHeadLength)@(arrowY + arrowHeadLength)) 
- 		color: Color black.
- 
- 	"Replace the glyph"
- 	self characterFormAt: $_ put: arrowForm.
- 
- !

Item was removed:
- ----- Method: StrikeFont>>makeBoldGlyphs (in category 'emphasis') -----
- makeBoldGlyphs
- 	"Make a bold set of glyphs with same widths by ORing 1 bit to the right
- 		(requires at least 1 pixel of intercharacter space)"
- 	| g bonkForm |
- 	g := glyphs deepCopy.
- 	bonkForm := (Form extent: 1 at 16) fillBlack offset: -1 at 0.
- 	self bonk: g with: bonkForm.
- 	glyphs depth = 1 ifTrue: [
- 		g copyBits: g boundingBox from: g at: (1 at 0)
- 			clippingBox: g boundingBox rule: Form under fillColor: nil]
- 		ifFalse: [
- 			0 to: g width - 2 do: [ :x | 0 to: g height-1 do: [ :y |
- 				(glyphs colorAt:  x at y) = Color white ifFalse: [
- 					g colorAt: x+1 at y put: 
- 						((glyphs colorAt: x+1 at y) = Color white 
- 							ifTrue: [glyphs colorAt:  x at y]
- 							ifFalse: [Color black])]]]].
- 	glyphs := g.
- 	self isSynthetic: true.
- 	fallbackFont ifNotNil: [
- 		fallbackFont := fallbackFont emphasized: 1
- 	].!

Item was removed:
- ----- Method: StrikeFont>>makeCarriageReturnsWhite (in category 'character shapes') -----
- makeCarriageReturnsWhite
- 	| crForm |
- 	"Some larger fonts have a gray carriage return (from the zero wide fixup) make it white so it doesn't show"
- 
- 	crForm := self characterFormAt: 13 asCharacter.
- 	crForm fillWhite.
- 	self characterFormAt: 13 asCharacter put: crForm.
- !

Item was removed:
- ----- Method: StrikeFont>>makeCondensedGlyphs (in category 'emphasis') -----
- makeCondensedGlyphs
- 	"Make a condensed set of glyphs with same widths.
- 	NOTE: this has been superceded by kerning -- should not get called"
- 	| g newXTable x x1 w |
- 	g := glyphs deepCopy.
- 	newXTable := Array new: xTable size.
- 	newXTable at: 1 put: (x := xTable at: 1).
- 	1 to: xTable size-1 do:
- 		[:i | x1 := xTable at: i.  w := (xTable at: i+1) - x1.
- 		w > 1 ifTrue: [w := w-1].  "Shrink every character wider than 1"
- 		g copy: (x at 0 extent: w at g height) from: x1 at 0 in: glyphs rule: Form over.
- 		newXTable at: i+1 put: (x := x + w)].
- 	xTable := newXTable.
- 	glyphs := g.
- 	self isSynthetic: true.
- 	fallbackFont ifNotNil: [
- 		fallbackFont emphasized: 8
- 	].
- 
- "
- (TextStyle default fontAt: 1) copy makeCondensedGlyphs
- 	displayLine: 'The quick brown fox jumps over the lazy dog'
- 	at: Sensor cursorPoint
- "!

Item was removed:
- ----- Method: StrikeFont>>makeControlCharsVisible (in category 'character shapes') -----
- makeControlCharsVisible
- 	| glyph d|
- 	self characterToGlyphMap.
- 	glyph := self characterFormAt: (Character space).
- 	glyph border: glyph boundingBox width: 1 fillColor: Color blue.
- 	self characterFormAt: (Character value: 133) put: glyph.
- 	
- 	"Keep tab(9), lf(10), cr(13) and space(32) transparent or whatever the user chose"
- 	#(0 1 2 3 4 5 6 7 8 11 12 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31)
- 		do: [ :ascii |
- 			characterToGlyphMap at: ascii + 1 put: 133 ]!

Item was removed:
- ----- Method: StrikeFont>>makeItalicGlyphs (in category 'emphasis') -----
- makeItalicGlyphs
- 	"Make an italic set of glyphs with same widths by skewing left and right.
- 	In the process, characters would overlap, so we widen them all first.
- 	"
- 	| extraWidth newGlyphs newXTable x newX w extraOnLeft |  
- 	extraOnLeft := (self height-1-self ascent+4)//4 max: 0.
- 	extraWidth := ((self ascent-5+4)//4 max: 0) + extraOnLeft.
- 	newGlyphs := Form extent: (glyphs width + (maxAscii + 1 - minAscii*extraWidth)) @ glyphs height depth: glyphs depth.
- 	newGlyphs fillWhite.
- 	newXTable := xTable copy.
- 
- 	"Copy glyphs into newGlyphs with room on left and right for overlap."
- 	minAscii to: maxAscii+1 do:
- 		[:ascii | x := xTable at: ascii+1.  w := (xTable at: ascii+2) - x.
- 		newX := newXTable at: ascii+1.
- 		newGlyphs copy: ((newX + extraOnLeft) @ 0 extent: w @ glyphs height)
- 			from: x @ 0 in: glyphs rule: Form over.
- 		newXTable at: ascii+2 put: newX + w + extraWidth].		
- 	glyphs := newGlyphs. 
- 	xTable := newXTable.
- 	"Slide the bitmaps left and right for synthetic italic effect."
- 	4 to: self ascent-1 by: 4 do:
- 		[:y | 		"Slide ascenders right..."
- 		glyphs copy: (1 at 0 extent: glyphs width @ (self ascent - y))
- 			from: 0 at 0 in: glyphs rule: Form over].
- 	self ascent to: self height-1 by: 4 do:
- 		[:y | 		"Slide descenders left..."
- 		glyphs copy: (0 at y extent: glyphs width @ glyphs height)
- 			from: 1 at y in: glyphs rule: Form over].
- 	self isSynthetic: true.
- 	fallbackFont ifNotNil: [
- 		fallbackFont := fallbackFont emphasized: 2
- 	].
- 
- !

Item was removed:
- ----- Method: StrikeFont>>makeLfInvisible (in category 'character shapes') -----
- makeLfInvisible
- 	self characterToGlyphMap.
- 	characterToGlyphMap at: 11 put: (11 < minAscii ifFalse: [11] ifTrue: [maxAscii+1])!

Item was removed:
- ----- Method: StrikeFont>>makeLfVisible (in category 'character shapes') -----
- makeLfVisible
- 	| glyph |
- 	self characterToGlyphMap.
- 	glyph := self characterFormAt: (Character value: 163).
- 	glyph border: glyph boundingBox width: 1 fillColor: Color blue.
- "	glyph := glyph reverse."
- 	self characterFormAt: (Character value: 132) put: glyph.
- 	characterToGlyphMap at: 11 put: 132!

Item was removed:
- ----- Method: StrikeFont>>makeReturnArrow (in category 'make arrows') -----
- makeReturnArrow
- "Replace the caret character with an arrow"
- 
- 	| arrowForm arrowCanvas arrowHeadLength arrowX arrowTop arrowBottom |
- 
- 	arrowForm := (self characterFormAt: $^) copy.
- 	arrowCanvas := arrowForm getCanvas.
- 	arrowCanvas fillColor: Color white.
- 
- 	arrowHeadLength := ((arrowForm width - 2)// 2).
- 	arrowX := (arrowHeadLength max: (arrowForm width // 2)).
- 	arrowTop := arrowForm height // 4. 
- 	arrowBottom := (arrowTop + (arrowForm width * 4 // 5 )).
- 	arrowBottom := (arrowBottom min: arrowForm height) max: (arrowForm height * 2 // 3).
- 
- 	"Draw the lines"
- 	arrowCanvas line: (arrowX at arrowTop) to: (arrowX at arrowBottom) color: Color black.
- 	arrowCanvas 
- 		line: (arrowX at arrowTop) 
- 		to: ((arrowX - arrowHeadLength)@(arrowTop + arrowHeadLength)) 
- 		color: Color black.
- 	arrowCanvas 
- 		line: (arrowX at arrowTop) 
- 		to: ((arrowX + arrowHeadLength)@(arrowTop + arrowHeadLength)) 
- 		color: Color black.
- 
- 	"Replace the glyph"
- 	self characterFormAt: $^ put: arrowForm.
- 
- !

Item was removed:
- ----- Method: StrikeFont>>makeStruckOutGlyphs (in category 'emphasis') -----
- makeStruckOutGlyphs
- 	"Make a struck-out set of glyphs with same widths"
- 	| g |
- 	g := glyphs deepCopy.
- 	g fillBlack: (0 @ (self ascent - (self ascent//3)) extent: g width @ 1).
- 	glyphs := g.
- 	self isSynthetic: true.
- 	fallbackFont ifNotNil: [
- 		fallbackFont := fallbackFont emphasized: 16
- 	].
- !

Item was removed:
- ----- Method: StrikeFont>>makeTabInvisible (in category 'character shapes') -----
- makeTabInvisible
- 	self characterToGlyphMap.
- 	characterToGlyphMap at: 10 put: (10 < minAscii ifFalse: [10] ifTrue:[maxAscii+1])!

Item was removed:
- ----- Method: StrikeFont>>makeTabVisible (in category 'character shapes') -----
- makeTabVisible
- 	self characterToGlyphMap.
- 	characterToGlyphMap at: 10 put: 172!

Item was removed:
- ----- Method: StrikeFont>>makeUnderlinedGlyphs (in category 'emphasis') -----
- makeUnderlinedGlyphs
- 	"Make an underlined set of glyphs with same widths"
- 	| g |
- 	g := glyphs deepCopy.
- 	g fillBlack: (0 @ (self ascent+1) extent: g width @ 1).
- 	glyphs := g.
- 	self isSynthetic: true.
- 	fallbackFont ifNotNil: [
- 		fallbackFont := fallbackFont emphasized: 4
- 	].
- !

Item was removed:
- ----- Method: StrikeFont>>maxCodePoint (in category 'accessing') -----
- maxCodePoint
- 	"Overwritten to configure ranges of glyphs per pre-rendered font."
- 
- 	^maxAscii!

Item was removed:
- ----- Method: StrikeFont>>maxWidth (in category 'accessing') -----
- maxWidth
- 	"Answer the integer that is the width of the receiver's widest character."
- 
- 	^maxWidth!

Item was removed:
- ----- Method: StrikeFont>>minCodePoint (in category 'accessing') -----
- minCodePoint
- 	"Overwritten to configure ranges of glyphs per pre-rendered font."
- 
- 	^minAscii!

Item was removed:
- ----- Method: StrikeFont>>name (in category 'accessing') -----
- name
- 	"Answer the receiver's name."
- 
- 	^name ifNil: ['(unnamed)']!

Item was removed:
- ----- Method: StrikeFont>>name: (in category 'accessing') -----
- name: aString
- 	"Set the receiver's name."
- 
- 	name := aString!

Item was removed:
- ----- Method: StrikeFont>>newFromStrike: (in category 'file in/out') -----
- newFromStrike: fileName
- 	"Build an instance from the strike font file name. The '.strike' extension
- 	is optional."
- 
- 	| strike startName raster16 |
- 	name := fileName copyUpTo: $..	"assumes extension (if any) is '.strike'"
- 	strike := FileStream readOnlyFileNamed: name, '.strike.'.
- 	strike binary.
- 
- 	"strip off direcory name if any"
- 	startName := name size.
- 	[startName > 0 and: [((name at: startName) ~= $>) & ((name at: startName) ~= $])]]
- 		whileTrue: [startName := startName - 1].
- 	name := name copyFrom: startName+1 to: name size.
- 
- 	type			:=		strike nextWord.		"type is ignored now -- simplest
- 												assumed.  Kept here to make
- 												writing and consistency more
- 												straightforward."
- 	minAscii		:=		strike nextWord.
- 	maxAscii		:=		strike nextWord.
- 	maxWidth		:=		strike nextWord.
- 	strikeLength	:=		strike nextWord.
- 	ascent			:=		strike nextWord.
- 	descent			:=		strike nextWord.
- 	"xOffset			:="		strike nextWord. 	
- 	raster16			:=		strike nextWord.	
- 	superscript		:=		ascent - descent // 3.	
- 	subscript		:=		descent - ascent // 3.	
- 	emphasis		:=		0.
- 	glyphs			:=	Form extent: (raster16 * 16) @ (self height)  
- 							offset: 0 at 0.
- 		glyphs bits fromByteStream: strike.
- 
- 	xTable := (Array new: maxAscii + 3) atAllPut: 0.
- 	(minAscii + 1 to: maxAscii + 3) do:
- 		[:index | xTable at: index put: strike nextWord].
- 
- 	"Set up space character"
- 	((xTable at: (Space asciiValue + 2))  = 0 or:
- 			[(xTable at: (Space asciiValue + 2)) = (xTable at: (Space asciiValue + 1))])
- 		ifTrue:	[(Space asciiValue + 2) to: xTable size do:
- 					[:index | xTable at: index put: ((xTable at: index) + 4 "DefaultSpace")]].
- 	strike close.
- 	characterToGlyphMap := nil.!

Item was removed:
- ----- Method: StrikeFont>>objectForDataStream: (in category 'file in/out') -----
- objectForDataStream: refStrm
- 	| dp |
- 	"I am about to be written on an object file.  Write a reference to a known Font in the other system instead.  "
- 
- 	"A path to me"
- 	(TextConstants at: #forceFontWriting ifAbsent: [false]) ifTrue: [^ self].
- 		"special case for saving the default fonts on the disk.  See collectionFromFileNamed:"
- 
- 	dp := DiskProxy global: #StrikeFont selector: #familyName:size:emphasized:
- 			args: (Array with: self familyName   with: self height
- 					with: self emphasis).
- 	refStrm replace: self with: dp.
- 	^ dp!

Item was removed:
- ----- Method: StrikeFont>>openHtmlOn: (in category 'html') -----
- openHtmlOn: aStream 
- 
- 	aStream
- 		nextPutAll: '<font face="';
- 		nextPutAll: self familyName;
- 		nextPutAll: '" size="';
- 		nextPutAll: self pointSize asString;
- 		nextPutAll: '">'.!

Item was removed:
- ----- Method: StrikeFont>>pixelSize (in category 'accessing') -----
- pixelSize
- 	"Overwritten because the receiver is pre-rendered using a fixed pixels-per-inch (PPI) value, usually 96 PPI. Note that you can change the #pointSize to match 96 PPI (see TextStyle class >> #pixelsPerInch) as follows:
- 	
- 	self pointSize: ((72 * self pixelSize / 96) roundTo: 0.5).
- 	self derivativeFonts do: [:d | d pointSize: font pointSize].
- 	
- 	Note that a line gap (similar to a TTCFont's #lineGap) for pre-rendered fonts is managed via TextStyle's #lineGrid.
- 	
- 	Also see StrikeFont class >> #referenceHeight."
- 	
- 	^ self height!

Item was removed:
- ----- Method: StrikeFont>>pointSize (in category 'accessing') -----
- pointSize
- 	^ pointSize!

Item was removed:
- ----- Method: StrikeFont>>pointSize: (in category 'accessing') -----
- pointSize: anInteger
- 	pointSize := anInteger!

Item was removed:
- ----- Method: StrikeFont>>postCopy (in category 'copying') -----
- postCopy
- 	"The receiver is a just created shallow copy. This method gives it the final touch."
- 	
- 	glyphs := glyphs copy.
- 	xTable := xTable copy.
- 	characterToGlyphMap := characterToGlyphMap copy.
- 	derivativeFonts := derivativeFonts copy.
- 	
- 	self reset.  " takes care of the derivative fonts "!

Item was removed:
- ----- Method: StrikeFont>>printOn: (in category 'file in/out') -----
- printOn: aStream
- 
- 	super printOn: aStream.
- 
- 	aStream nextPut: $(.
- 	self printShortDescriptionOn: aStream.
- 	aStream nextPut: $).!

Item was removed:
- ----- Method: StrikeFont>>printShortDescriptionOn: (in category 'printing') -----
- printShortDescriptionOn: aStream
- 	
- 	aStream
- 		nextPutAll: self familyName;
- 		space; print: self pointSize; nextPutAll: 'pt';
- 		space; print: self pixelsPerInch; nextPutAll: 'ppi';
- 		space; print: self height; nextPutAll: 'px';
- 		space; nextPutAll: self emphasisString.!

Item was removed:
- ----- Method: StrikeFont>>raster (in category 'accessing') -----
- raster
- 	"Answer an integer that specifies the layout of the glyphs' form."
- 
- 	^raster!

Item was removed:
- ----- Method: StrikeFont>>readBDFFromFile:name: (in category 'file in/out') -----
- readBDFFromFile: fileName name: aString 
- 	"This builds a StrikeFont instance by reading the X11 Binary 
- 	Distribution Format font source file.  See the BDFFontReader class
- 	comment."
- 
- 	"StrikeFont new readBDFFromFile: 'helvR12' name: 'Helvetica12'."
- 
- 	| fontReader stream |
- 	fontReader := BDFFontReader openFileNamed: fileName.
- 	stream := ReadStream on: fontReader read.
- 	xTable := stream next.
- 	glyphs := stream next.
- 	minAscii := stream next.
- 	maxAscii := stream next.
- 	maxWidth := stream next.
- 	ascent := stream next.
- 	descent := stream next.
- 	pointSize := stream next.
- 	name := aString.
- "	xTable size <= 256 ifTrue: [self setStopConditions]."
- 	type := 0.	"no one see this"
- 	superscript := (ascent - descent) // 3.
- 	subscript := (descent - ascent) // 3.
- 	emphasis := 0.
- 	self reset!

Item was removed:
- ----- Method: StrikeFont>>readBFHeaderFrom: (in category 'file in/out') -----
- readBFHeaderFrom: f
- 	name := self restOfLine: 'Font name = ' from: f.
- 	ascent := (self restOfLine: 'Ascent = ' from: f) asNumber.
- 	descent := (self restOfLine: 'Descent = ' from: f) asNumber.
- 	maxWidth := (self restOfLine: 'Maximum width = ' from: f) asNumber.
- 	pointSize := (self restOfLine: 'Font size = ' from: f) asNumber.
- 	name := (name copyWithout: Character space) ,
- 				(pointSize < 10
- 					ifTrue: ['0' , pointSize printString]
- 					ifFalse: [pointSize printString]).
- 	minAscii := 258.
- 	maxAscii := 0.
- 	superscript := ascent - descent // 3.	
- 	subscript := descent - ascent // 3.	
- 	emphasis := 0.
- 	type := 0.  "ignored for now"
- !

Item was removed:
- ----- Method: StrikeFont>>readCharacter:from: (in category 'multibyte character methods') -----
- readCharacter: aBits from: aStream
- 
- 	| pos |
- 	pos := 0.
- 	12 timesRepeat: [
- 		1 to: 2 do: [ :w |
- 			aBits byteAt: (pos+w) put: (aStream next ). 
- 		].
- 		pos := pos + 4.
- 	].
- !

Item was removed:
- ----- Method: StrikeFont>>readFromBitFont: (in category 'file in/out') -----
- readFromBitFont: fileName
- 	"This builds a StrikeFont instance by reading the data file format
- 	produced by BitFont, a widely available font conversion utility
- 	written by Peter DiCamillo at Brown University"
- 	"StrikeFont new readFromBitFont: 'Palatino10.BF' "
- 	| f lastAscii charLine width ascii charForm line missingForm tempGlyphs iRect p rectLine left tokens right |
- 	f := FileStream readOnlyFileNamed: fileName.
- 	self readBFHeaderFrom: f.
- 
- 	"NOTE: if font has been scaled (and in any case),
- 	the REAL bitmap dimensions come after the header."
- 	self restOfLine: 'Extent information for entire font' from: f.
- 	"Parse the following line (including mispelling!!)"
- 	"Image rectange: left = -2, right = 8, bottom = -2, top = 7"
- 	tokens := f nextLine  findTokens: ' '.
- 	iRect := Rectangle left: (tokens at: 5) asNumber right: (tokens at: 8) asNumber
- 				top: (tokens at: 14) asNumber bottom: (tokens at: 11) asNumber.
- 	ascent := iRect top.
- 	descent := iRect bottom negated.
- 	
- 	tempGlyphs := Form extent: (maxWidth*257) @ self height.
- 	xTable := (Array new: 258) atAllPut: 0.
- 	xTable at: 1 put: 0.
- 
- 	"Read character forms and blt into tempGlyphs"
- 	lastAscii := -1.
- 	[charLine := self restOfLine: 'Character: ' from: f.
- 	charLine == nil ifFalse:
- 		[p := f position.
- 		rectLine := f nextLine.
- 		(rectLine beginsWith: 'Image rectange: left = ')
- 			ifTrue: [tokens := rectLine findTokens: ' '.
- 					left := (tokens at: 5) asNumber. right := (tokens at: 8) asNumber]
- 			ifFalse: [left := right := 0. f position: p].
- 		width:= (self restOfLine: 'Width (final pen position) = ' from: f) asNumber - left
- 					max: (right-left+1).
- 		(charLine beginsWith: 'Missing character') ifTrue: [ascii := 256].
- 		('x''*' match: charLine) ifTrue:
- 			[ascii := Number readFrom: (charLine copyFrom: 3 to: 4) asUppercase base: 16].
- 		charForm := Form extent: width at self height.
- 		('*[all blank]' match: charLine) ifFalse:
- 			[self restOfLine: '  +' from: f.
- 			1 to: self height do:
- 				[:y | line := f nextLine.
- 				4 to: (width + 3 min: line size + iRect left - left) do:
- 					[:x | (line at: x - iRect left + left) = $*
- 						ifTrue: [charForm pixelValueAt: (x-4)@(y-1) put: 1]]]]].
- 	charLine == nil]
- 		whileFalse:
- 			[self displayChar: ascii form: charForm.
- 			ascii = 256
- 				ifTrue: [missingForm := charForm deepCopy]
- 				ifFalse:
- 				[minAscii := minAscii min: ascii.
- 				maxAscii := maxAscii max: ascii.
- 				lastAscii+1 to: ascii-1 do: [:a | xTable at: a+2 put: (xTable at: a+1)].
- 				tempGlyphs copy: ((xTable at: ascii+1)@0
- 										extent: charForm extent)
- 							from: 0 at 0 in: charForm rule: Form over.
- 				xTable at: ascii+2 put: (xTable at: ascii+1) + width.
- 				lastAscii := ascii]].
- 	f close.
- 	lastAscii+1 to: maxAscii+1 do: [:a | xTable at: a+2 put: (xTable at: a+1)].
- 	missingForm == nil ifFalse:
- 		[tempGlyphs copy: missingForm boundingBox from: missingForm
- 				to: (xTable at: maxAscii+2)@0 rule: Form over.
- 		xTable at: maxAscii+3 put: (xTable at: maxAscii+2) + missingForm width].
- 	glyphs := Form extent: (xTable at: maxAscii+3) @ self height.
- 	glyphs copy: glyphs boundingBox from: 0 at 0 in: tempGlyphs rule: Form over.
- 	xTable := xTable copyFrom: 1 to: maxAscii+3.
- 	characterToGlyphMap := nil.!

Item was removed:
- ----- Method: StrikeFont>>readFromStrike2: (in category 'file in/out') -----
- readFromStrike2: fileName  "StrikeFont new readFromStrike2: 'Palatino14.sf2'"
- 	"Build an instance from the strike font stored in strike2 format.
- 	fileName is of the form: <family name><pointSize>.sf2"
- 	| file |
- 	('*.sf2' match: fileName) ifFalse: [self halt.  "likely incompatible"].
- 	name := FileDirectory baseNameFor: ( FileDirectory localNameFor: fileName).  "Drop filename extension"
- 	file := FileStream readOnlyFileNamed: fileName.
- 	file binary.
- 	[self readFromStrike2Stream: file] ensure: [file close]!

Item was removed:
- ----- Method: StrikeFont>>readFromStrike2Stream: (in category 'file in/out') -----
- readFromStrike2Stream: file 
- 	"Build an instance from the supplied binary stream on data in strike2 format"
- 	type := file nextInt32.  type = 2 ifFalse: [file close. self error: 'not strike2 format'].
- 	minAscii := file nextInt32.
- 	maxAscii := file nextInt32.
- 	maxWidth := file nextInt32.
- 	ascent := file nextInt32.
- 	descent := file nextInt32.
- 	pointSize := file nextInt32.
- 	superscript := ascent - descent // 3.	
- 	subscript := descent - ascent // 3.	
- 	emphasis := file nextInt32.
- 	xTable := (Array new: maxAscii + 3) atAllPut: 0.
- 	(minAscii + 1 to: maxAscii + 3) do:
- 		[:index | xTable at: index put: file nextInt32].
- 	glyphs := Form new readFrom: file.
- 
- 	"Set up space character"
- 	((xTable at: (Space asciiValue + 2))  = 0 or:
- 			[(xTable at: (Space asciiValue + 2)) = (xTable at: (Space asciiValue + 1))])
- 		ifTrue:	[(Space asciiValue + 2) to: xTable size do:
- 					[:index | xTable at: index put: ((xTable at: index) + 4 "DefaultSpace")]].
- 	characterToGlyphMap := nil.!

Item was removed:
- ----- Method: StrikeFont>>readMacFontHex: (in category 'Mac reader') -----
- readMacFontHex: fileName
- 	"Read the hex version of a Mac FONT type resource.  See the method aComment for how to prepare the input file. 4/26/96 tk"
- 	| file hh fRectWidth |
- 	name := fileName.	"Palatino 12"
- 	file := FileStream readOnlyFileNamed: fileName, ' hex'.
- 
- 	"See Inside Macintosh page IV-42 for this record"
- 	"FontType := " Number readFrom: (file next: 4) base: 16.
- 	emphasis		:=		0.
- 	minAscii := Number readFrom: (file next: 4) base: 16.
- 	maxAscii := Number readFrom: (file next: 4) base: 16.
- 	maxWidth		:= Number readFrom: (file next: 4) base: 16.
- 	"kernMax := " Number readFrom: (file next: 4) base: 16.
- 	"NDescent := " Number readFrom: (file next: 4) base: 16.
- 	fRectWidth :=  Number readFrom: (file next: 4) base: 16.
- 	hh :=  Number readFrom: (file next: 4) base: 16.
- 	"OWTLoc := " Number readFrom: (file next: 4) base: 16.
- 	ascent			:= Number readFrom: (file next: 4) base: 16.
- 	descent			:= Number readFrom: (file next: 4) base: 16.
- 	"leading := " Number readFrom: (file next: 4) base: 16.
- 	xOffset			:=		0. 	
- 	raster			:= Number readFrom: (file next: 4) base: 16.
- 
- 	strikeLength	:=		raster*16.
- 	superscript		:=		ascent - descent // 3.	
- 	subscript		:=		descent - ascent // 3.	
- 	self strikeFromHex: file width: raster height: hh.
- 	self xTableFromHex: file.
- 	file close.
- 
- 	"Insert one pixel between each character.  And add space character."
- 	self fixKerning: (fRectWidth - maxWidth).	
- 
- 	"Recompute character to glyph mapping"
- 	characterToGlyphMap := nil.!

Item was removed:
- ----- Method: StrikeFont>>releaseCachedState (in category 'emphasis') -----
- releaseCachedState
- 
- 	self reset.!

Item was removed:
- ----- Method: StrikeFont>>reset (in category 'emphasis') -----
- reset
- 	"Reset the cache of derivative emphasized fonts"
- 
- 	lineGap := lineGapSlice := nil.
- 
- 	fallbackFont class = FixedFaceFont
- 		ifTrue: [fallbackFont := nil].
- 		
- 	derivativeFonts notNil ifTrue: [
- 		derivativeFonts withIndexDo: [ :f :i |
- 			(f notNil and: [f isSynthetic]) ifTrue: [derivativeFonts at: i put: nil]]].
- 	"
- 	derivativeFonts := Array new: 32.
- 	#('B' 'I' 'BI') doWithIndex:
- 		[:tag :index | 
- 		(style := TextStyle named: self familyName) ifNotNil:
- 			[(font := style fontArray
- 				detect: [:each | each name = (self name , tag)]
- 				ifNone: [nil]) ifNotNil: [derivativeFonts at: index put: font]]]
- 	"!

Item was removed:
- ----- Method: StrikeFont>>restOfLine:from: (in category 'file in/out') -----
- restOfLine: leadString from: file
- 	"Utility method to assist reading of BitFont data files"
- 	| line |
- 	[line := file nextLine.
- 	line size < leadString size or: [leadString ~= (line copyFrom: 1 to: leadString size)]]
- 	whileTrue: [file atEnd ifTrue: [^ nil]].
- 	^ line copyFrom: leadString size+1 to: line size!

Item was removed:
- ----- Method: StrikeFont>>setGlyphs: (in category 'accessing') -----
- setGlyphs: newGlyphs
- 	"Replace the glyphs form.  Used to make a synthetic bold or italic font quickly."
- 
- 	glyphs := newGlyphs!

Item was removed:
- ----- Method: StrikeFont>>setGlyphsDepthAtMost: (in category 'building') -----
- setGlyphsDepthAtMost: aNumber
- 	glyphs depth > aNumber ifTrue: [
- 		glyphs := glyphs asFormOfDepth: aNumber ]!

Item was removed:
- ----- Method: StrikeFont>>strikeFromHex:width:height: (in category 'Mac reader') -----
- strikeFromHex: file width: w height: h
- 	"read in just the raw strike bits from a hex file.  No spaces or returns.  W is in words (2 bytes), h in pixels." 
- 	| newForm theBits offsetX offsetY str num cnt |
- 	offsetX  := 0.
- 	offsetY := 0.
- 	offsetX > 32767 ifTrue: [offsetX := offsetX - 65536]. "stored two's-complement"
- 	offsetY > 32767 ifTrue: [offsetY := offsetY - 65536]. "stored two's-complement"
- 	newForm := Form extent: strikeLength @ h offset: offsetX @ offsetY.
- 	theBits := newForm bits.
- 	cnt := 0.		"raster may be 16 bits, but theBits width is 32" 
- 	1 to: theBits size do: [:i | 
- 		(cnt := cnt + 32) > strikeLength 
- 		  ifTrue: [cnt := 0.
- 			num := Number readFrom: (str := file next: 4) base: 16]
- 		  ifFalse: [
- 			cnt = strikeLength ifTrue: [cnt := 0].
- 			num := Number readFrom: (str := file next: 8) base: 16].
- 		theBits at: i put: num].
- 	glyphs := newForm.!

Item was removed:
- ----- Method: StrikeFont>>stripHighGlyphs (in category 'building') -----
- stripHighGlyphs
- 	"Remove glyphs for characters above 128"
- 	| i |
- 	maxAscii := 127.
- 	
- 	xTable := xTable copyFrom: 1 to: maxAscii + 3.
- 	i := xTable at: maxAscii + 1.
- 	xTable at: maxAscii + 2 put: i.
- 	xTable at: maxAscii + 3 put: i.
- 	glyphs := glyphs copy: (0 at 0 extent: i at glyphs height).
- 	maxWidth := 0.
- 	2 to: xTable size do: [ :ii |
- 		maxWidth := maxWidth max: (xTable at: ii) - (xTable at: ii-1)-1 ].
- 	characterToGlyphMap := nil.
- 	self reset!

Item was removed:
- ----- Method: StrikeFont>>subscript (in category 'accessing') -----
- subscript
- 	"Answer an integer that is the further vertical offset relative to the 
- 	baseline for positioning characters as subscripts."
- 
- 	^subscript!

Item was removed:
- ----- Method: StrikeFont>>superscript (in category 'accessing') -----
- superscript
- 	"Answer an integer that is the further vertical offset relative to the 
- 	baseline for positioning characters as superscripts."
- 
- 	^superscript!

Item was removed:
- ----- Method: StrikeFont>>textStyle (in category 'accessing') -----
- textStyle
- 	"Overwritten to not create a new style for orphaned fonts."
- 
- 	^ self textStyleOrNil!

Item was removed:
- ----- Method: StrikeFont>>useLeftArrow (in category 'character shapes') -----
- useLeftArrow
- 	self characterToGlyphMap.
- 	characterToGlyphMap at: 96 put: 95.
- 	characterToGlyphMap at: 95 put: 94!

Item was removed:
- ----- Method: StrikeFont>>useUnderscore (in category 'character shapes') -----
- useUnderscore
- 	self characterToGlyphMap.
- 	characterToGlyphMap at: 96 put: 129.
- 	characterToGlyphMap at: 95 put: 128!

Item was removed:
- ----- Method: StrikeFont>>useUnderscoreIfOver1bpp (in category 'character shapes') -----
- useUnderscoreIfOver1bpp
- 
- 	glyphs depth = 1 ifTrue: [
- 		characterToGlyphMap ifNotNil: [	
- 			characterToGlyphMap at: 96 put: 95.
- 			characterToGlyphMap at: 95 put: 94 ].
- 		^self ].
- 	
- 	self characterToGlyphMap.
- 	characterToGlyphMap at: 96 put: 129.
- 	characterToGlyphMap at: 95 put: 128!

Item was removed:
- ----- Method: StrikeFont>>veryDeepCopyWith: (in category 'copying') -----
- veryDeepCopyWith: deepCopier
- 	"Return self.  I am shared.  Do not record me."!

Item was removed:
- ----- Method: StrikeFont>>widen:by: (in category 'character shapes') -----
- widen: char by: delta
- 	^ self alter: char formBlock:  "Make a new form, wider or narrower..."
- 		[:charForm |
- 		| newForm |
- 		newForm := Form extent: charForm extent + (delta at 0).
- 		charForm displayOn: newForm.  "Copy this image into it"
- 		newForm]    "and substitute it in the font"!

Item was removed:
- ----- Method: StrikeFont>>widthOf: (in category 'accessing') -----
- widthOf: aCharacter 
- 	"Answer the width of the argument as a character in the receiver."
- 	| code |
- 	code := aCharacter charCode.
- 	(self characterToGlyphMap notNil and: [ 
- 		characterToGlyphMap size > code ]) ifTrue: [
- 			code := characterToGlyphMap at: code + 1 ].
- 	((code < minAscii or: [maxAscii < code]) 
- 		or: [(xTable at: code + 1) < 0])
- 			ifTrue: [^ self fallbackFont widthOf: aCharacter].
- 	^ (xTable at: code + 2) - (xTable at: code + 1)!

Item was removed:
- ----- Method: StrikeFont>>writeAsStrike2On: (in category 'file in/out') -----
- writeAsStrike2On: file
- 	"Write me onto a file in strike2 format.
- 	fileName should be of the form: <family name><pointSize>.sf2"
- 	file binary.
- 	file nextInt32Put: 2.
- 	file nextInt32Put: minAscii.
- 	file nextInt32Put: maxAscii.
- 	file nextInt32Put: maxWidth.
- 	file nextInt32Put: ascent.
- 	file nextInt32Put: descent.
- 	file nextInt32Put: pointSize.
- 	superscript := ascent - descent // 3.	
- 	subscript := descent - ascent // 3.	
- 	file nextInt32Put: emphasis.
- 	(minAscii + 1 to: maxAscii + 3) do:
- 		[:index | file nextInt32Put: (xTable at: index)].
- 	glyphs writeOn: file.
- 	file close.
- !

Item was removed:
- ----- Method: StrikeFont>>writeAsStrike2named: (in category 'file in/out') -----
- writeAsStrike2named: fileName
- 	"Write me onto a file in strike2 format.
- 	fileName should be of the form: <family name><pointSize>.sf2"
- 	| file |
- 	file := FileStream fileNamed: fileName.
- 	self writeAsStrike2On: file.
- 	file close.!

Item was removed:
- ----- Method: StrikeFont>>xTable (in category 'accessing') -----
- xTable
- 	"Answer an Array of the left x-coordinate of characters in glyphs."
- 
- 	^xTable!

Item was removed:
- ----- Method: StrikeFont>>xTable: (in category 'accessing') -----
- xTable: anObject
- 
- 	xTable := anObject.
- !

Item was removed:
- ----- Method: StrikeFont>>xTableFromHex: (in category 'Mac reader') -----
- xTableFromHex: file
- 
- 	| strike num wid |
- 	strike := file.
- 	xTable := (Array new: maxAscii + 3) atAllPut: 0.
- 	minAscii + 1 to: maxAscii + 3 do:
- 		[:index | 
- 			num := Number readFrom: (strike next: 4) base: 16. 
- 			xTable at: index put: num].
- 
- 	1 to: xTable size - 1 do: [:ind |
- 		wid := (xTable at: ind+1) - (xTable at: ind).
- 		(wid < 0) | (wid > 40) ifTrue: [
- 			file close.
- 			self error: 'illegal character width']].
- !

Item was removed:
- Object subclass: #TextComposer
- 	instanceVariableNames: 'lines maxRightX currentY scanner possibleSlide nowSliding prevIndex prevLines currCharIndex startCharIndex stopCharIndex deltaCharIndex theText theContainer isFirstLine theTextStyle defaultLineHeight actualHeight wantsColumnBreaks'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Text'!

Item was removed:
- ----- Method: TextComposer class>>characterForColumnBreak (in category 'as yet unclassified') -----
- characterForColumnBreak
- 
- 	^Character characterForColumnBreak!

Item was removed:
- ----- Method: TextComposer>>addNullLineForIndex: (in category 'private') -----
- addNullLineForIndex: index
- "This awful bit is to ensure that if we have scanned all the text and the last character is a CR that there is a null line at the end of lines. Sometimes this was not happening which caused anomalous selections when selecting all the text. This is implemented as a post-composition fixup because I couldn't figure out where to put it in the main logic."
- 
- 	| oldLastLine r |
- 
- 	oldLastLine := lines last.
- 	oldLastLine last - oldLastLine first >= 0 ifFalse: [^self].
- 	oldLastLine last = (index - 1) ifFalse: [^self].
- 
- 	r := oldLastLine left @ oldLastLine bottom 
- 				extent: 0@(oldLastLine bottom - oldLastLine top).
- 	"Even though we may be below the bottom of the container,
- 	it is still necessary to compose the last line for consistency..."
- 
- 	self addNullLineWithIndex: index andRectangle: r.
- !

Item was removed:
- ----- Method: TextComposer>>addNullLineWithIndex:andRectangle: (in category 'private') -----
- addNullLineWithIndex: index andRectangle: r
- 	"TextEditor has emphasisHere, which encodes the emphasis of future input. We don't have that info here. Therefore we just use the height of the last text line if there is any."
- 	
- 	lines addLast: (
- 		(
- 			TextLine 
- 				start: index 
- 				stop: index - 1
- 				internalSpaces: 0 
- 				paddingWidth: 0
- 		)
- 			rectangle: r;
- 			lineHeight: (lines
- 				ifEmpty: [defaultLineHeight]
- 				ifNotEmpty: [lines last lineHeight])
- 			baseline: (lines
- 				ifEmpty: [theTextStyle baseline]
- 				ifNotEmpty: [lines last baseline])
- 	)
- !

Item was removed:
- ----- Method: TextComposer>>checkIfReadyToSlide (in category 'private') -----
- checkIfReadyToSlide
- 
- 	"Check whether we are now in sync with previously composed lines"
- 
- 	(possibleSlide and: [currCharIndex > stopCharIndex]) ifFalse: [^self].
- 
- 	[prevIndex < prevLines size
- 		and: [(prevLines at: prevIndex) first < (currCharIndex - deltaCharIndex)]]
- 			whileTrue: [prevIndex := prevIndex + 1].
- 
- 	(prevLines at: prevIndex) first = (currCharIndex - deltaCharIndex) ifTrue: [
- 		"Yes -- next line will have same start as prior line."
- 		prevIndex := prevIndex - 1.
- 		possibleSlide := false.
- 		nowSliding := true
- 	] ifFalse: [
- 		prevIndex = prevLines size ifTrue: [
- 			"Weve reached the end of prevLines, so no use to keep looking for lines to slide."
- 			possibleSlide := false
- 		]
- 	]!

Item was removed:
- ----- Method: TextComposer>>composeAllLines (in category 'private') -----
- composeAllLines
- 
- 	[currCharIndex <= theText size and: 
- 			[(currentY + defaultLineHeight) <= theContainer bottom]] whileTrue: [
- 
- 		nowSliding ifTrue: [
- 			self slideOneLineDown ifNil: [^nil].
- 		] ifFalse: [
- 			self composeOneLine ifNil: [^nil].
- 		]
- 	].
- !

Item was removed:
- ----- Method: TextComposer>>composeAllRectangles: (in category 'private') -----
- composeAllRectangles: rectangles
- 
- 	| charIndexBeforeLine numberOfLinesBefore reasonForStopping |
- 
- 	actualHeight := 0.
- 	charIndexBeforeLine := currCharIndex.
- 	numberOfLinesBefore := lines size.
- 	reasonForStopping := self composeEachRectangleIn: rectangles.
- 
- 	currentY := currentY + actualHeight.
- 	currentY > theContainer bottom ifTrue: [
- 		"Oops -- the line is really too high to fit -- back out"
- 		currCharIndex := charIndexBeforeLine.
- 		lines size - numberOfLinesBefore timesRepeat: [lines removeLast].
- 		^self
- 	].
- 	
- 	"It's OK -- the line still fits."
- 	maxRightX := maxRightX max: scanner rightX.
- 	1 to: rectangles size - 1 do: [ :i | |lineIndex|
- 		"Adjust heights across rectangles if necessary"
- 		lineIndex:=lines size - rectangles size + i.
- 		(lines size between: 1 and: lineIndex) ifTrue: 
- 			[(lines at: lineIndex)
- 				lineHeight: lines last lineHeight
- 				baseline: lines last baseline] 
- 	].
- 	isFirstLine := false.
- 	reasonForStopping == #columnBreak ifTrue: [^nil].
- 	currCharIndex > theText size ifTrue: [
- 		^nil		"we are finished composing"
- 	].
- 	!

Item was removed:
- ----- Method: TextComposer>>composeEachRectangleIn: (in category 'private') -----
- composeEachRectangleIn: rectangles
- 
- 	| myLine lastChar |
- 
- 	1 to: rectangles size do: [:i | 
- 		currCharIndex <= theText size ifFalse: [^false].
- 		myLine := scanner 
- 			composeFrom: currCharIndex 
- 			inRectangle: (rectangles at: i)				
- 			firstLine: isFirstLine 
- 			leftSide: i=1 
- 			rightSide: i=rectangles size.
- 		lines addLast: myLine.
- 		myLine moveByTopMargin.
- 		actualHeight := actualHeight max: myLine lineHeightWithMargins.  "includes font changes and text style's #lineSpacing"
- 		currCharIndex := myLine last + 1.
- 		lastChar := theText at: myLine last.
- 		(CharacterSet crlf includes: lastChar) ifTrue: [^#cr].
- 		wantsColumnBreaks ifTrue: [
- 			lastChar = Character characterForColumnBreak ifTrue: [^#columnBreak].
- 		].
- 	].
- 	^false!

Item was removed:
- ----- Method: TextComposer>>composeLinesFrom:to:delta:into:priorLines:atY:textStyle:text:container:wantsColumnBreaks: (in category 'composing') -----
- composeLinesFrom: argStart to: argStop delta: argDelta into: argLinesCollection priorLines: argPriorLines atY: argStartY textStyle: argTextStyle text: argText container: argContainer wantsColumnBreaks: argWantsColumnBreaks
- 
- 	wantsColumnBreaks := argWantsColumnBreaks.
- 	lines := argLinesCollection.
- 	theTextStyle := argTextStyle.
- 	theText := argText.
- 	theContainer := argContainer.
- 	deltaCharIndex := argDelta.
- 	currCharIndex := startCharIndex := argStart.
- 	stopCharIndex := argStop.
- 	prevLines := argPriorLines.
- 	currentY := argStartY.
- 	maxRightX := theContainer left.
- 	possibleSlide := stopCharIndex < theText size and: [theContainer isMemberOf: Rectangle].
- 	nowSliding := false.
- 	prevIndex := 1.
- 	"choose an appropriate scanner - should go away soon, when they can be unified"
- 	scanner := CompositionScanner new.
- 	scanner text: theText textStyle: theTextStyle.
- 	scanner wantsColumnBreaks: wantsColumnBreaks.
- 	defaultLineHeight := scanner computeDefaultLineHeight.
- 	isFirstLine := true.
- 	self composeAllLines.
- 	isFirstLine ifTrue: ["No space in container or empty text"
- 		self 
- 			addNullLineWithIndex: startCharIndex
- 			andRectangle: (theContainer left @ theContainer top extent: 0 at defaultLineHeight)
- 	] ifFalse: [
- 		self doesLineBreakAfterLastChar
- 			ifTrue: [self addNullLineForIndex: theText size + 1]
- 	].
- 	^{lines asArray. maxRightX}
- !

Item was removed:
- ----- Method: TextComposer>>composeOneLine (in category 'private') -----
- composeOneLine
- 	| rectangles |
- 	rectangles := theContainer rectanglesAt: currentY height: defaultLineHeight.
- 	rectangles notEmpty 
- 		ifTrue: [(self composeAllRectangles: rectangles) ifNil: [^nil]]
- 		ifFalse: [currentY := currentY + defaultLineHeight].
- 	self checkIfReadyToSlide!

Item was removed:
- ----- Method: TextComposer>>doesLineBreakAfterLastChar (in category 'private') -----
- doesLineBreakAfterLastChar
- 	"Answer whether we should insert a null-line at the end because theText ends with a line-break character. After a full composition, we can ask the scanner. After a partial re-composition, however, we re-use most of prevLines and thus miss any trailing null-line."
- 
- 	^ scanner atEnd
- 		ifTrue: [scanner doesTheLineBreakAfterLastChar]
- 		ifFalse: [prevLines notEmpty and: [prevLines last first > prevLines last last]]!

Item was removed:
- ----- Method: TextComposer>>slideOneLineDown (in category 'private') -----
- slideOneLineDown
- 
- 	| priorLine |
- 
- 	"Having detected the end of rippling recoposition, we are only sliding old lines"
- 	prevIndex < prevLines size ifFalse: [
- 		"There are no more prevLines to slide."
- 		^nowSliding := possibleSlide := false
- 	].
- 
- 	"Adjust and re-use previously composed line"
- 	prevIndex := prevIndex + 1.
- 	priorLine := (prevLines at: prevIndex)
- 				slideIndexBy: deltaCharIndex andMoveTopTo: currentY.
- 	lines addLast: priorLine.
- 	currentY := priorLine bottom.
- 	currCharIndex := priorLine last + 1.
- 	wantsColumnBreaks ifTrue: [
- 		priorLine first to: priorLine last do: [ :i |
- 			(theText at: i) = Character characterForColumnBreak ifTrue: [
- 				nowSliding := possibleSlide := false.
- 				^nil
- 			].
- 		].
- 	].
- !

Item was removed:
- Object subclass: #TextLine
- 	instanceVariableNames: 'left right top bottom firstIndex lastIndex internalSpaces paddingWidth baseline leftMargin topMargin bottomMargin'
- 	classVariableNames: ''
- 	poolDictionaries: 'TextConstants'
- 	category: 'Graphics-Text'!
- 
- !TextLine commentStamp: '<historical>' prior: 0!
- A TextLine embodies the layout of a line of composed text.
- 	left right top bottom		The full line rectangle
- 	firstIndex lastIndex		Starting and stopping indices in the full text
- 	internalSpaces		Number of spaces to share paddingWidth
- 	paddingWidth		Number of pixels of extra space in full line
- 	baseline				Distance of baseline below the top of the line
- 	leftMargin			Left margin due to paragraph indentation
- TextLine's rather verbose message protocol is required for compatibility with the old CharacterScanners.!

Item was removed:
- ----- Method: TextLine class>>start:stop:internalSpaces:paddingWidth: (in category 'instance creation') -----
- start: startInteger stop: stopInteger internalSpaces: spacesInteger paddingWidth: padWidthInteger
- 	"Answer an instance of me with the arguments as the start, stop points, 
- 	number of spaces in the line, and width of the padding."
- 	| line |
- 	line := self new firstIndex: startInteger lastIndex: stopInteger.
- 	^ line internalSpaces: spacesInteger paddingWidth: padWidthInteger!

Item was removed:
- ----- Method: TextLine>>= (in category 'comparing') -----
- = line
- 
- 	self species = line species
- 		ifTrue: [^((firstIndex = line first and: [lastIndex = line last])
- 				and: [internalSpaces = line internalSpaces])
- 				and: [paddingWidth = line paddingWidth]]
- 		ifFalse: [^false]!

Item was removed:
- ----- Method: TextLine>>baseline (in category 'accessing') -----
- baseline
- 	^ baseline!

Item was removed:
- ----- Method: TextLine>>bottom (in category 'accessing') -----
- bottom
- 	^ bottom!

Item was removed:
- ----- Method: TextLine>>bottomMargin (in category 'accessing') -----
- bottomMargin
- 
- 	^ bottomMargin!

Item was removed:
- ----- Method: TextLine>>bottomRight (in category 'accessing') -----
- bottomRight
- 	^ right at bottom!

Item was removed:
- ----- Method: TextLine>>first (in category 'accessing') -----
- first
- 	^ firstIndex!

Item was removed:
- ----- Method: TextLine>>firstIndex:lastIndex: (in category 'private') -----
- firstIndex: firstInteger lastIndex: lastInteger
- 	firstIndex := firstInteger.
- 	lastIndex := lastInteger!

Item was removed:
- ----- Method: TextLine>>hash (in category 'comparing') -----
- hash
- 	"#hash is re-implemented because #= is re-implemented"
- 	^firstIndex hash bitXor: lastIndex hash!

Item was removed:
- ----- Method: TextLine>>internalSpaces (in category 'accessing') -----
- internalSpaces
- 	"Answer the number of spaces in the line."
- 
- 	^internalSpaces!

Item was removed:
- ----- Method: TextLine>>internalSpaces: (in category 'accessing') -----
- internalSpaces: spacesInteger 
- 	"Set the number of spaces in the line to be spacesInteger."
- 
- 	internalSpaces := spacesInteger!

Item was removed:
- ----- Method: TextLine>>internalSpaces:paddingWidth: (in category 'private') -----
- internalSpaces: spacesInteger paddingWidth: padWidthInteger
- 
- 	internalSpaces := spacesInteger.
- 	paddingWidth := padWidthInteger!

Item was removed:
- ----- Method: TextLine>>justifiedPadFor:font: (in category 'scanning') -----
- justifiedPadFor: spaceIndex font: aFont
- 	"Compute the width of pad for a given space in a line of justified text."
- 
- 	| pad |
- 	internalSpaces = 0 ifTrue: [^0].
- 	^(aFont notNil and:[aFont isSubPixelPositioned])
- 		ifTrue:[paddingWidth * 1.0 / internalSpaces]
- 		ifFalse:[
- 			pad := paddingWidth // internalSpaces.
- 			spaceIndex <= (paddingWidth \\ internalSpaces)
- 				ifTrue: [pad + 1]
- 				ifFalse: [pad]]
- 		!

Item was removed:
- ----- Method: TextLine>>justifiedTabDeltaFor: (in category 'scanning') -----
- justifiedTabDeltaFor: spaceIndex 
- 	"Compute the delta for a tab in a line of justified text, so tab falls 
- 	somewhere plausible when line is justified."
- 
- 	| pad extraPad |
- 	internalSpaces = 0 ifTrue: [^0].
- 	pad := paddingWidth // internalSpaces.
- 	extraPad := paddingWidth \\ internalSpaces.
- 	spaceIndex <= extraPad
- 		ifTrue: [^spaceIndex * (pad + 1)]
- 		ifFalse: [^extraPad * (pad + 1) + (spaceIndex - extraPad * pad)]!

Item was removed:
- ----- Method: TextLine>>last (in category 'accessing') -----
- last
- 	^ lastIndex!

Item was removed:
- ----- Method: TextLine>>left (in category 'accessing') -----
- left
- 	^ left!

Item was removed:
- ----- Method: TextLine>>leftMargin (in category 'accessing') -----
- leftMargin
- 	"This has to get fixed -- store during composition"
- 	^ self left!

Item was removed:
- ----- Method: TextLine>>leftMargin: (in category 'accessing') -----
- leftMargin: lm
- 	left := lm!

Item was removed:
- ----- Method: TextLine>>leftMarginForAlignment: (in category 'accessing') -----
- leftMarginForAlignment: alignmentCode
- 	alignmentCode = RightFlush ifTrue: [^ self left + paddingWidth].
- 	alignmentCode = Centered ifTrue: [^ self left + (paddingWidth//2)].
- 	^ self left  "leftFlush and justified"!

Item was removed:
- ----- Method: TextLine>>lineHeight (in category 'accessing') -----
- lineHeight
- 	^ bottom - top!

Item was removed:
- ----- Method: TextLine>>lineHeight:baseline: (in category 'private') -----
- lineHeight: height baseline: ascent
- 	bottom := top + height.
- 	baseline := ascent!

Item was removed:
- ----- Method: TextLine>>lineHeightWithMargins (in category 'accessing') -----
- lineHeightWithMargins
- 
- 	^ bottom - top + topMargin + bottomMargin!

Item was removed:
- ----- Method: TextLine>>moveBy: (in category 'updating') -----
- moveBy: delta 
- 	"Move my rectangle by the given delta"
- 	left := left + delta x.
- 	right := right + delta x.
- 	top := top + delta y.
- 	bottom := bottom + delta y.
- !

Item was removed:
- ----- Method: TextLine>>moveByTopMargin (in category 'updating') -----
- moveByTopMargin
- 
- 	top := top + topMargin.
- 	bottom := bottom + topMargin.
- !

Item was removed:
- ----- Method: TextLine>>paddingWidth (in category 'accessing') -----
- paddingWidth
- 	"Answer the amount of space to be added to the font."
- 
- 	^paddingWidth!

Item was removed:
- ----- Method: TextLine>>paddingWidth: (in category 'accessing') -----
- paddingWidth: padWidthInteger 
- 	"Set the amount of space to be added to the font to be padWidthInteger."
- 
- 	paddingWidth := padWidthInteger!

Item was removed:
- ----- Method: TextLine>>printOn: (in category 'printing') -----
- printOn: aStream
- 	super printOn: aStream.
- 	aStream space; print: firstIndex; nextPutAll: ' to: '; print: lastIndex!

Item was removed:
- ----- Method: TextLine>>rectangle (in category 'accessing') -----
- rectangle
- 	^ self topLeft corner: self bottomRight!

Item was removed:
- ----- Method: TextLine>>rectangle: (in category 'accessing') -----
- rectangle: lineRectangle
- 	left := lineRectangle left.
- 	right := lineRectangle right.
- 	top := lineRectangle top.
- 	bottom := lineRectangle bottom!

Item was removed:
- ----- Method: TextLine>>right (in category 'accessing') -----
- right
- 	^ right!

Item was removed:
- ----- Method: TextLine>>rightMargin (in category 'accessing') -----
- rightMargin
- 	"This has to get fixed -- store during composition"
- 	^ self right!

Item was removed:
- ----- Method: TextLine>>setRight: (in category 'accessing') -----
- setRight: x
- 	right := x!

Item was removed:
- ----- Method: TextLine>>slide: (in category 'updating') -----
- slide: delta 
- 	"Change the starting and stopping points of the line by delta."
- 
- 	firstIndex := firstIndex + delta.
- 	lastIndex := lastIndex + delta!

Item was removed:
- ----- Method: TextLine>>slideIndexBy:andMoveTopTo: (in category 'updating') -----
- slideIndexBy: delta andMoveTopTo: newTop
- 	"Relocate my character indices and y-values.
- 	Used to slide constant text up or down in the wake of a text replacement."
- 
- 	firstIndex := firstIndex + delta.
- 	lastIndex := lastIndex + delta.
- 	bottom := bottom + (newTop - top).
- 	top := newTop.
- !

Item was removed:
- ----- Method: TextLine>>stop: (in category 'accessing') -----
- stop: stopInteger 
- 	"Set the stopping point in the string of the line to be stopInteger."
- 
- 	lastIndex := stopInteger!

Item was removed:
- ----- Method: TextLine>>top (in category 'accessing') -----
- top
- 	^ top!

Item was removed:
- ----- Method: TextLine>>topLeft (in category 'accessing') -----
- topLeft
- 	^ left @ top!

Item was removed:
- ----- Method: TextLine>>topMargin (in category 'accessing') -----
- topMargin
- 
- 	^ topMargin!

Item was removed:
- ----- Method: TextLine>>topMargin:bottomMargin: (in category 'private') -----
- topMargin: tm bottomMargin: bm
- 	topMargin := tm.
- 	bottomMargin := bm.!

Item was removed:
- ----- Method: TextLine>>width (in category 'accessing') -----
- width
- 	^ right - left!

Item was removed:
- Object subclass: #TextPrinter
- 	instanceVariableNames: 'form para paperSize landscape resolution depth offset columns docTitle noHeader noFooter'
- 	classVariableNames: 'DefaultPaperSize DefaultTextPrinter'
- 	poolDictionaries: ''
- 	category: 'Graphics-Text'!

Item was removed:
- ----- Method: TextPrinter class>>defaultPaperSize (in category 'accessing') -----
- defaultPaperSize
- 	^DefaultPaperSize!

Item was removed:
- ----- Method: TextPrinter class>>defaultPaperSize: (in category 'accessing') -----
- defaultPaperSize: aPoint
- 	DefaultPaperSize := aPoint!

Item was removed:
- ----- Method: TextPrinter class>>defaultTextPrinter (in category 'accessing') -----
- defaultTextPrinter
- 	"This is the global default TextPrinter instance."
- 	DefaultTextPrinter isNil ifTrue: [DefaultTextPrinter := self new].
- 	^DefaultTextPrinter!

Item was removed:
- ----- Method: TextPrinter class>>initialize (in category 'class initialization') -----
- initialize
- 	"TextPrinter initialize"
- 	self defaultPaperSize: self paperSizeA4.!

Item was removed:
- ----- Method: TextPrinter class>>mm2in: (in category 'paper sizes') -----
- mm2in: aPoint
- 	"Convert aPoint from millimeters to inches"
- 	^aPoint / 25.4!

Item was removed:
- ----- Method: TextPrinter class>>paperSize10x14 (in category 'paper sizes') -----
- paperSize10x14
- 	^10.0 at 14.0!

Item was removed:
- ----- Method: TextPrinter class>>paperSize11x17 (in category 'paper sizes') -----
- paperSize11x17
- 	^11.0 at 17.0!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeA3 (in category 'paper sizes') -----
- paperSizeA3
- 	^self mm2in: 297 at 420!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeA4 (in category 'paper sizes') -----
- paperSizeA4
- 	^self mm2in: 210 at 297!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeA5 (in category 'paper sizes') -----
- paperSizeA5
- 	^self mm2in: 148 at 210!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeB4 (in category 'paper sizes') -----
- paperSizeB4
- 	^self mm2in: 250 at 354!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeB5 (in category 'paper sizes') -----
- paperSizeB5
- 	^self mm2in: 182 at 257!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeCSheet (in category 'paper sizes') -----
- paperSizeCSheet
- 	^17.0 at 22.0!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeDSheet (in category 'paper sizes') -----
- paperSizeDSheet
- 	^22.0 at 34.0!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeESheet (in category 'paper sizes') -----
- paperSizeESheet
- 	^34.0 at 44.0!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeEnvelope10 (in category 'paper sizes') -----
- paperSizeEnvelope10
- 	^4.125 at 9.5
- !

Item was removed:
- ----- Method: TextPrinter class>>paperSizeEnvelope11 (in category 'paper sizes') -----
- paperSizeEnvelope11
- 	^4.5 at 10.375!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeEnvelope12 (in category 'paper sizes') -----
- paperSizeEnvelope12
- 	^4.75 at 11!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeEnvelope14 (in category 'paper sizes') -----
- paperSizeEnvelope14
- 	^5.0 at 11.5!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeEnvelope9 (in category 'paper sizes') -----
- paperSizeEnvelope9
- 	^3.875 at 8.875!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeEnvelopeB4 (in category 'paper sizes') -----
- paperSizeEnvelopeB4
- 	^self mm2in: 250 at 353!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeEnvelopeB5 (in category 'paper sizes') -----
- paperSizeEnvelopeB5
- 	^self mm2in: 176 at 250!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeEnvelopeB6 (in category 'paper sizes') -----
- paperSizeEnvelopeB6
- 	^self mm2in: 176 at 125!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeEnvelopeC3 (in category 'paper sizes') -----
- paperSizeEnvelopeC3
- 	^self mm2in: 324 at 458!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeEnvelopeC4 (in category 'paper sizes') -----
- paperSizeEnvelopeC4
- 	^self mm2in: 229 at 324!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeEnvelopeC5 (in category 'paper sizes') -----
- paperSizeEnvelopeC5
- 	^self mm2in: 162 at 229!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeEnvelopeC6 (in category 'paper sizes') -----
- paperSizeEnvelopeC6
- 	^self mm2in: 114 at 162!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeEnvelopeC65 (in category 'paper sizes') -----
- paperSizeEnvelopeC65
- 	^self mm2in: 114 at 229!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeFanfoldGerman (in category 'paper sizes') -----
- paperSizeFanfoldGerman
- 	"German standard fanfold"
- 	^8.5 at 12.0!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeFanfoldLegalGerman (in category 'paper sizes') -----
- paperSizeFanfoldLegalGerman
- 	"German legal fanfold"
- 	^8.5 at 13.0!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeFanfoldUS (in category 'paper sizes') -----
- paperSizeFanfoldUS
- 	"US standard fanfold"
- 	^14.875 at 11.0!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeFolio (in category 'paper sizes') -----
- paperSizeFolio
- 	^8.5 at 13.0!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeLegal (in category 'paper sizes') -----
- paperSizeLegal
- 	^8.5 at 14.0!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeLetter (in category 'paper sizes') -----
- paperSizeLetter
- 	^8.5 at 11.0!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeNote (in category 'paper sizes') -----
- paperSizeNote
- 	^8.5 at 11.0!

Item was removed:
- ----- Method: TextPrinter class>>paperSizeTabloid (in category 'paper sizes') -----
- paperSizeTabloid
- 	^11.0 at 17.0!

Item was removed:
- ----- Method: TextPrinter>>bestColor (in category 'accessing') -----
- bestColor
- 	"Set the reproduction quality to true color"
- 	depth := 32.!

Item was removed:
- ----- Method: TextPrinter>>blackAndWhite (in category 'accessing') -----
- blackAndWhite
- 	"Set the reproduction quality to black and white"
- 	depth := 1.!

Item was removed:
- ----- Method: TextPrinter>>columnRect: (in category 'formatting') -----
- columnRect: n
- 	"Return a rectangle describing the n-th column"
- 	| area left right |
- 	area := self textArea.
- 	left := area left + ((n-1) * self columnWidth).
- 	left := left + ((n-1) * self columnSkip).
- 	right := left + self columnWidth.
- 	^(self in2pix: left @ area top) corner: 
- 		(self in2pix: right @ area bottom)!

Item was removed:
- ----- Method: TextPrinter>>columnSkip (in category 'formatting') -----
- columnSkip
- 	"Return the separating space between two columns in inches"
- 	^0.2!

Item was removed:
- ----- Method: TextPrinter>>columnWidth (in category 'formatting') -----
- columnWidth
- 	^(self textWidth - ((self columns-1) * self columnSkip)) / self columns!

Item was removed:
- ----- Method: TextPrinter>>columns (in category 'accessing') -----
- columns
- 	^columns!

Item was removed:
- ----- Method: TextPrinter>>columns: (in category 'accessing') -----
- columns: aNumber
- 	columns := aNumber asInteger max: 1.!

Item was removed:
- ----- Method: TextPrinter>>defaultPaperSize (in category 'initialize') -----
- defaultPaperSize
- 	"Return the default paper size (inches) for printing"
- 	^self class defaultPaperSize!

Item was removed:
- ----- Method: TextPrinter>>defaultResolution (in category 'initialize') -----
- defaultResolution
- 	"Return the default resolution (DPI) for printing"
- 	^TextStyle pixelsPerInch asPoint!

Item was removed:
- ----- Method: TextPrinter>>documentTitle (in category 'accessing') -----
- documentTitle
- 	^docTitle!

Item was removed:
- ----- Method: TextPrinter>>documentTitle: (in category 'accessing') -----
- documentTitle: aString
- 	docTitle := aString!

Item was removed:
- ----- Method: TextPrinter>>flushPage (in category 'printing') -----
- flushPage
- 	"The current page has been set up. Send it to the printer."
- 	form primPrintHScale: self resolution x vScale: self resolution y landscape: self landscape.
- 	"Uncomment the following for testing"
- 	"form displayOn: Display. (Delay forSeconds: 5) wait."
- !

Item was removed:
- ----- Method: TextPrinter>>footerHeight (in category 'footer') -----
- footerHeight
- 	"Return the (additional) height of the footer in inches."
- 	self noFooter ifTrue:[^0.0].
- 	^(self pix2in: 0 at TextStyle default lineGrid) y * 2!

Item was removed:
- ----- Method: TextPrinter>>footerParagraph (in category 'footer') -----
- footerParagraph
- 	"Return a paragraph for the footer"
- 	| fPara rect paragraphClass |
- 	paragraphClass := Smalltalk at: #Paragraph
- 				ifAbsent: [^ self notify: 'MVC class Paragraph not present'].
- 	fPara := paragraphClass new.
- 	fPara destinationForm: form.
- 	rect := (self in2pix: self textArea bottomLeft) corner: 
- 				(self in2pix: self textArea bottomRight + (0.0 at self footerHeight)).
- 	fPara clippingRectangle: rect.
- 	fPara compositionRectangle: rect.
- 	^fPara!

Item was removed:
- ----- Method: TextPrinter>>formatColumn:startingWith: (in category 'formatting') -----
- formatColumn: columnNum startingWith: anIndex
- 	"Format a new column starting at the given string index. Return the string index indicating the start of the next column or nil if no more columns need printing."
- 	| colRect blk |
- 	colRect := self columnRect: columnNum.
- 	anIndex > 1 ifTrue:[para text: (para text copyFrom: anIndex to: para text size)].
- 	para compositionRectangle: colRect.
- 	para clippingRectangle: colRect.
- 	para composeAll.
- 	para displayOn: form.
- 	para visibleRectangle corner y <= colRect extent y ifTrue:[^nil].
- 	"More columns -- find the character block of the last line and adjust clip rect"
- 	blk := para characterBlockAtPoint: para visibleRectangle bottomLeft.
- 	para clearVisibleRectangle. "Make sure that the background is clean"
- 	para clippingRectangle: (colRect topLeft corner: colRect right at blk top).
- 	para displayOn: form.
- 	^blk stringIndex.!

Item was removed:
- ----- Method: TextPrinter>>formatPage:startingWith: (in category 'formatting') -----
- formatPage: pageNum startingWith: anIndex
- 	"Format a new page starting at the given string index. Return the string index indicating the start of the next page or nil if no more pages need printing."
- 	| nextIndex |
- 	nextIndex := anIndex.
- 	1 to: self columns do:[:i|
- 		nextIndex := self formatColumn: i startingWith: nextIndex.
- 		nextIndex isNil ifTrue:[^nil].
- 	].
- 	^nextIndex!

Item was removed:
- ----- Method: TextPrinter>>goodColor (in category 'accessing') -----
- goodColor
- 	"Set the reproduction quality to 8 bit color depth"
- 	depth := 8.!

Item was removed:
- ----- Method: TextPrinter>>headerHeight (in category 'header') -----
- headerHeight
- 	"Return the (additional) height of the header in inches."
- 	self noHeader ifTrue:[^0.0].
- 	^(self pix2in: 0 at TextStyle default lineGrid) y * 2!

Item was removed:
- ----- Method: TextPrinter>>headerParagraph (in category 'header') -----
- headerParagraph
- 	"Return a paragraph for the footer"
- 	| hPara rect paragraphClass |
- 	paragraphClass := Smalltalk at: #Paragraph
- 				ifAbsent: [^ self notify: 'MVC class Paragraph not present'].
- 	hPara := paragraphClass new.
- 	hPara destinationForm: form.
- 	rect := (self in2pix: self textArea topLeft - (0.0 at self headerHeight)) corner: 
- 				(self in2pix: self textArea topRight).
- 	hPara clippingRectangle: rect.
- 	hPara compositionRectangle: rect.
- 	^hPara!

Item was removed:
- ----- Method: TextPrinter>>in2mm: (in category 'other') -----
- in2mm: aPoint
- 	"Convert aPoint from millimeters to inches"
- 	^aPoint * 25.4!

Item was removed:
- ----- Method: TextPrinter>>in2pix: (in category 'other') -----
- in2pix: aPoint
- 	"Convert aPoint from inches to actual pixels"
- 	^(aPoint * self resolution) rounded!

Item was removed:
- ----- Method: TextPrinter>>initialize (in category 'initialize') -----
- initialize
- 	self paperSize: self defaultPaperSize.
- 	self resolution: self defaultResolution.
- 	self blackAndWhite.
- 	self landscape: false.
- 	self offsetRect: (1.0 at 1.0 corner: 1.0 at 1.0).
- 	self columns: 1.
- 	self noHeader: false.
- 	self noFooter: false.
- 	self documentTitle: 'Squeak Document (from ', Date today printString,')'.!

Item was removed:
- ----- Method: TextPrinter>>landscape (in category 'accessing') -----
- landscape
- 	^landscape!

Item was removed:
- ----- Method: TextPrinter>>landscape: (in category 'accessing') -----
- landscape: aBoolean
- 	landscape := aBoolean!

Item was removed:
- ----- Method: TextPrinter>>mm2in: (in category 'other') -----
- mm2in: aPoint
- 	"Convert aPoint from millimeters to inches"
- 	^aPoint / 25.4!

Item was removed:
- ----- Method: TextPrinter>>mm2pix: (in category 'other') -----
- mm2pix: aPoint
- 	"Convert aPoint from millimeters to actual pixels"
- 	^self in2pix: (self mm2in: aPoint)!

Item was removed:
- ----- Method: TextPrinter>>noFooter (in category 'accessing') -----
- noFooter
- 	^noFooter!

Item was removed:
- ----- Method: TextPrinter>>noFooter: (in category 'accessing') -----
- noFooter: aBoolean
- 	"Turn off footer printing"
- 	noFooter := aBoolean.!

Item was removed:
- ----- Method: TextPrinter>>noHeader (in category 'accessing') -----
- noHeader
- 	^noHeader!

Item was removed:
- ----- Method: TextPrinter>>noHeader: (in category 'accessing') -----
- noHeader: aBoolean
- 	"Turn off header printing"
- 	noHeader := aBoolean.!

Item was removed:
- ----- Method: TextPrinter>>offsetRect (in category 'accessing') -----
- offsetRect
- 	^offset!

Item was removed:
- ----- Method: TextPrinter>>offsetRect: (in category 'accessing') -----
- offsetRect: aRectangle
- 	"Set the offset rectangle"
- 	offset := aRectangle!

Item was removed:
- ----- Method: TextPrinter>>paperSize (in category 'accessing') -----
- paperSize
- 	^paperSize!

Item was removed:
- ----- Method: TextPrinter>>paperSize: (in category 'accessing') -----
- paperSize: aPoint
- 	paperSize := aPoint!

Item was removed:
- ----- Method: TextPrinter>>pix2in: (in category 'other') -----
- pix2in: aPoint
- 	"Convert aPoint from a pixel value to inches"
- 	^aPoint / self resolution!

Item was removed:
- ----- Method: TextPrinter>>pix2mm: (in category 'other') -----
- pix2mm: aPoint
- 	"Convert aPoint from a pixel value to millimeters"
- 	^self in2mm: (self pix2in: aPoint)!

Item was removed:
- ----- Method: TextPrinter>>pixelSize (in category 'private') -----
- pixelSize
- 	"Return the size of the page in pixels"
- 	^self in2pix: (self realPaperSize)!

Item was removed:
- ----- Method: TextPrinter>>printFooter: (in category 'footer') -----
- printFooter: pageNumber
- 	"Print the footer for the given page number"
- 	| fPara |
- 	self noFooter ifTrue:[^self].
- 	fPara := self footerParagraph.
- 	fPara centered.
- 	fPara text: ('Page ', pageNumber printString) asText.
- 	fPara displayOn: form.!

Item was removed:
- ----- Method: TextPrinter>>printHeader: (in category 'header') -----
- printHeader: pageNumber
- 	"Print the header for the given page number"
- 	| fPara |
- 	self noHeader ifTrue:[^self].
- 	fPara := self headerParagraph.
- 	fPara centered.
- 	fPara text: self documentTitle asText.
- 	fPara displayOn: form.!

Item was removed:
- ----- Method: TextPrinter>>printParagraph (in category 'printing') -----
- printParagraph
- 	| pageNum nextIndex |
- 	para destinationForm: form.
- 	pageNum := 1.
- 	nextIndex := 1.
- 	[form fillColor: Color white.
- 	self printHeader: pageNum.
- 	self printFooter: pageNum.
- 	nextIndex := self formatPage: pageNum startingWith: nextIndex.
- 	self flushPage.
- 	nextIndex isNil] whileFalse:[pageNum := pageNum + 1].!

Item was removed:
- ----- Method: TextPrinter>>printText: (in category 'printing') -----
- printText: aText
- 	"Print aText"
- 	| paragraphClass |
- 	form isNil ifTrue:[
- 		form := Form extent: self pixelSize depth: depth.
- 	].
- 	paragraphClass := Smalltalk at: #Paragraph
- 				ifAbsent: [^ self notify: 'MVC class Paragraph not present'].
- 	para := paragraphClass withText: aText asText.
- 	Cursor wait showWhile:[
- 		self printParagraph.
- 	].!

Item was removed:
- ----- Method: TextPrinter>>realPaperSize (in category 'private') -----
- realPaperSize
- 	^self landscape
- 		ifTrue:[self paperSize y @ self paperSize x]
- 		ifFalse:[self paperSize]!

Item was removed:
- ----- Method: TextPrinter>>resolution (in category 'accessing') -----
- resolution
- 	^resolution!

Item was removed:
- ----- Method: TextPrinter>>resolution: (in category 'accessing') -----
- resolution: aPoint
- 	resolution := aPoint!

Item was removed:
- ----- Method: TextPrinter>>textArea (in category 'formatting') -----
- textArea
- 	^(self offsetRect origin + (0.0 at self headerHeight)) corner:
- 		(self realPaperSize - self offsetRect corner - (0.0 at self footerHeight))!

Item was removed:
- ----- Method: TextPrinter>>textWidth (in category 'formatting') -----
- textWidth
- 	^self textArea extent x!

Item was removed:
- Object subclass: #TextStyle
- 	instanceVariableNames: 'fontArray alignment firstIndent restIndent rightIndent tabsArray marginTabsArray defaultFontIndex lineSpacing normalizedCharacterWidth'
- 	classVariableNames: 'NumSpacesPerTab'
- 	poolDictionaries: 'TextConstants'
- 	category: 'Graphics-Text'!
- 
- !TextStyle commentStamp: 'mt 2/21/2022 10:55' prior: 0!
- A text style comprises the formatting information for composing and displaying a unit (usually a paragraph) of text. It provides a #defaultFont to use, but text attributes can change that per character (see CompositionScanner and DisplayScanner). It also has a default #alignment that attributes can override. Those defaults make it possible to compose and display (unformatted) strings in paragraphs without having to style them first as texts (i.e., string+attributes).
- 
- NOTE THAT for each use you *must* make a copy of a font's master text style (e.g., "TextStyle default copy") or create a fresh one with at least a single font (see TextStyle class >> #fontArray: and AbstractFont >> #asNewTextStyle). That specific instance is typically altered in the process of editing: change default font size, change default alignment, ... and you wouldn't want to change that properties for other applications by accident.
- 
- A text style also drives the interpretation of Character tab. Both tabsArray and marginTabsArray are initialized for the #defaultFont(Index:). When you change a style's default font size, those "tab positions" will be recomputed for fast access during composition. See the preference #numSpacesPerTab(:).
- 
- While each text style looks like it could handle an arbitrary array of fonts, it is *best practice* to only store fonts of the same font family. A font's master style thus collects all known point sizes at a single place (i.e. "TextStyle named: aFamilyName"). Copies will share that array. The attribute TextFontChange makes it possible to switch to any index in that array, but this is not portable and hence discouraged. TextFontReference adds an explicit reference to font, which is also not good. (February 2022: We plan to add TextFont(Point)Size and TextFontFamily as a portable way to change the font per character.).
- 
- There are some legacy information, which should no longer be used:
- 	- #baseline: ... used to prescribe baseline info but is now completely derived from #defaultFont
- 	- #lineGrid: ... same as #baseLine:
- 	- #leading(:) ... is replaced by #lineSpacing(:) and denotes the extra spacing relative to the respective line's height in the composition
- 
- The #lineSpacing is noticeable in a paragraph's text selection. Line spacing < 0.0 will appear as overlaps between (translucent) selection rectangles. Lince spacing > 0.0 will appear as gaps between selection rectangles.
- 
- Here are some example styles to explore:
- 	- TextStyle default
- 	- TextStyle defaultFixes!

Item was removed:
- ----- Method: TextStyle class>>actualTextStyles (in category 'TextConstants access') -----
- actualTextStyles
- 	| aDict |
- 	"TextStyle actualTextStyles"
- 
- 	"Answer dictionary whose keys are the names of styles in the system and whose values are the actual styles"
- 
- 	aDict := TextConstants select: [:thang | thang isKindOf: self ].
- 	self defaultFamilyNames do: [ :sym | aDict removeKey: sym ifAbsent: [] ].
- 	^ aDict!

Item was removed:
- ----- Method: TextStyle class>>changeDefaultFontSizeBy: (in category 'instance creation') -----
- changeDefaultFontSizeBy: delta      "TextStyle changeDefaultFontSizeBy: 1"
- 	"This sample method recreates the default textStyle, with font 1 being a size
- 	larger than the smallest.  It then initializes most references in the system
- 	as well, although most windows will have to beclosed and reopened to get the effect."
- 	| allFonts |
- 	allFonts := TextStyle default fontArray sorted: [:a :b | a height < b height].
- 	TextConstants at: #DefaultTextStyle put:
- 		(TextStyle fontArray: ((1 to: allFonts size) collect: [:i | allFonts atWrap: i+delta])).
- 	#(ListParagraph PopUpMenu StandardSystemView) do:[:className|
- 		Smalltalk at: className ifPresent:[:aClass| aClass initialize].
- 	].!

Item was removed:
- ----- Method: TextStyle class>>collectionFromCompressedMIMEString: (in category 'mime file in/out') -----
- collectionFromCompressedMIMEString: aString
- 	"aString holds a compressed, Base64 representation of a SmartRefStream storage of a TextStyle.
- 	Install the TextStyle."
- 
- 	| this newName style data |
- 	data := (Base64MimeConverter mimeDecode: aString as: String) unzipped.
- 	(RWBinaryOrTextStream with: data) reset; fileIn.
- 	this := SmartRefStream scannedObject.
- 
- 	"now install it"
- 
- 	newName := this fontArray first familyName.
- 	this fontArray do: [:aFont | aFont familyName = newName ifFalse: [
- 		self error: 'All must be same family']].
- 	style := TextConstants at: newName asSymbol ifAbsent: [
- 		^ TextConstants at: newName asSymbol put: this].		"new family"
- 	this fontArray do: [:aFont | | heights | "add new fonts"
- 		heights := style fontArray collect: [:bFont | bFont height].
- 		(heights includes: aFont height) ifFalse: [
- 			style fontAt: style fontArray size + 1 put: aFont]].
- !

Item was removed:
- ----- Method: TextStyle class>>decodeStyleName: (in category 'utilities') -----
- decodeStyleName: styleName 
- 	"Given a string styleName, return a collection with: 
- 	 
- 	* [1] the probable Squeak emphasis code, which is a bit combination of: 
- 	1	bold 
- 	2	italic 
- 	4	underlined 
- 	8	narrow 
- 	16	strikeout 
- 	 
- 	* [2] the base style name without the modifiers (can be empty)
- 	* [3] the modifiers in the order they were found 
- 	* [4] the codes for those modifiers, in the same order
- 	"
- 	| decoder keys modifiers modifierCodes baseName styleCode matchedKey |
- 
- 	decoder := self styleDecoder.
- 
- 	modifiers := OrderedCollection new.
- 	modifierCodes := OrderedCollection new.
- 	keys := decoder keys asArray
- 				sort: [:a :b | a size > b size].
- 	styleCode := 0.
- 	baseName := styleName asString.
- 	[matchedKey := keys
- 				detect: [:k | baseName endsWith: k]
- 				ifNone: [].
- 	matchedKey notNil]
- 		whileTrue: [| last code | 
- 			last := baseName size - matchedKey size.
- 			last > 0
- 				ifTrue: [('- ' includes: (baseName at: last))
- 						ifTrue: [last := last - 1]].
- 			baseName := baseName copyFrom: 1 to: last.
- 			code := decoder at: matchedKey.
- 			styleCode := styleCode + code.
- 			modifiers addFirst: matchedKey.
- 			modifierCodes addFirst: code.
- 	].
- 	^ {styleCode. baseName. modifiers. modifierCodes }!

Item was removed:
- ----- Method: TextStyle class>>default (in category 'constants') -----
- default
- 	"Answer the system default text style."
- 
- 	^DefaultTextStyle!

Item was removed:
- ----- Method: TextStyle class>>defaultFallback (in category 'constants') -----
- defaultFallback
- 
- 	^ (TextConstants at: #DefaultFallbackTextStyle ifAbsent: [])
- 		ifNil: [self default]!

Item was removed:
- ----- Method: TextStyle class>>defaultFallbackFont (in category 'constants') -----
- defaultFallbackFont
- 
- 	^ self defaultFallback defaultFont!

Item was removed:
- ----- Method: TextStyle class>>defaultFamilyNames (in category 'TextConstants access') -----
- defaultFamilyNames
- 	^#(DefaultTextStyle DefaultFixedTextStyle DefaultMultiStyle DefaultFallbackTextStyle)!

Item was removed:
- ----- Method: TextStyle class>>defaultFixed (in category 'constants') -----
- defaultFixed
- 
- 	^DefaultFixedTextStyle!

Item was removed:
- ----- Method: TextStyle class>>defaultFixedFont (in category 'constants') -----
- defaultFixedFont
- 
- 	^ DefaultFixedTextStyle defaultFont!

Item was removed:
- ----- Method: TextStyle class>>defaultFont (in category 'constants') -----
- defaultFont
- 	"Answer the default system font"
- 
- 	^ DefaultTextStyle defaultFont!

Item was removed:
- ----- Method: TextStyle class>>defaultTT (in category 'constants') -----
- defaultTT
- 	"Answer the default TrueType text style."
- 
- 	^ self default isTTCStyle
- 		ifTrue: [self default]
- 		ifFalse: [self named: #BitstreamVeraSans]!

Item was removed:
- ----- Method: TextStyle class>>defaultTTFont (in category 'constants') -----
- defaultTTFont
- 
- 	^ self defaultTT defaultFont!

Item was removed:
- ----- Method: TextStyle class>>fontArray: (in category 'instance creation') -----
- fontArray: anArray 
- 	"Answer an instance of me with fonts those in the argument, anArray."
- 
- 	^self new newFontArray: anArray!

Item was removed:
- ----- Method: TextStyle class>>fontArrayForStyle: (in category 'TextConstants access') -----
- fontArrayForStyle: aName
- 	"Answer the fonts in the style named aName,
- 	or an empty Array if no such named style."
- 
- 	"TextStyle fontArrayForStyle: #Atlanta"
- 	"TextStyle fontPointSizesFor: 'NewYork'"
- 
- 	^ ((self named: aName) ifNil: [ ^#() ]) fontArray
- !

Item was removed:
- ----- Method: TextStyle class>>fontPointSizesFor: (in category 'TextConstants access') -----
- fontPointSizesFor: aName
- 	"Answer the point sizes for all the fonts in the given text style"
- 
- 	"TextStyle fontPointSizesFor: 'Arial'"
- 	"TextStyle fontPointSizesFor: 'NewYork'"
- 
- 	^ (self fontArrayForStyle: aName) collect: [:f | f pointSize]
- !

Item was removed:
- ----- Method: TextStyle class>>fontSizeSummary (in category 'utilities') -----
- fontSizeSummary
- 	"Open a text window with a simple summary of the available sizes in each of the fonts in the system."
- 
- 	"TextStyle fontSizeSummary"
- 
- 	(StringHolder new contents: self fontSizeSummaryContents)
- 		openLabel: 'Font styles and sizes' translated!

Item was removed:
- ----- Method: TextStyle class>>fontSizeSummaryContents (in category 'utilities') -----
- fontSizeSummaryContents
- 
- 	^ Text streamContents: [:aStream |
- 			| knownStyles knownTTCStyles knownLegacyStyles defaultStyles printBlock |
- 			knownStyles := self knownTextStylesWithoutDefault sorted.
- 			defaultStyles := self defaultFamilyNames sorted.
- 			
- 			aStream nextPutAll: ('This page lists all known text styles and for each style''s font the available point sizes. Most text fields offer the {1} where you can choose a different font or point size. Note that you can use any new point size for TrueType fonts. This is, however, not possible for our pre-rendred legacy fonts. If you need more fonts, use the {2} to import TrueType fonts from your current platform. Click {3} to browse all styles by example.\\'
- 				translated withCRs asText format: {
- 					'FontChooserTool' asText
- 						addAttribute: (PluggableTextAttribute evalBlock: [FontChooserTool open]); yourself.
- 					'FontImporterTool' asText
- 						addAttribute: (PluggableTextAttribute evalBlock: [FontImporterTool open]); yourself.
- 					'here' asText
- 						addAttribute: (PluggableTextAttribute evalBlock: [TextStyle browseAllStyles])}).
- 			
- 			defaultStyles do: [:styleName |
- 				| style prefix |
- 				style := self named: styleName.
- 				prefix := (style isNil or: [(self named: style defaultFamilyName) == style]) ifTrue: [''] ifFalse: [' !! '].
- 				aStream
- 					nextPutAll: (((styleName padded: #left to: 24 with: Character space), ': ', prefix) asText addAttribute: (TextFontReference toFont: TextStyle defaultFixedFont); yourself);
- 					nextPutAll: (style ifNil: ['-'] ifNotNil: [(style defaultFamilyName asText addAttribute: (TextFontReference toFont: style defaultFont); addAttribute: (PluggableTextAttribute evalBlock: [style explore]); yourself)]);
- 					cr].
- 			
- 			printBlock :=  [:styleName |
- 					| style defaultFont preferredPointSize exampleFont |
- 					style := self named: styleName.
- 					preferredPointSize := TextStyle defaultFont pointSize. "system's current default"
- 					defaultFont := style defaultFont. "style's current default"
- 					exampleFont := defaultFont isSymbolFont
- 						ifTrue: [TextStyle defaultFont "famiyl name should be legible"]
- 						ifFalse: [defaultFont asPointSize: preferredPointSize].
- 					aStream
- 						nextPutAll: (styleName asText addAttribute: (TextFontReference toFont: exampleFont)).
- 					styleName ~= style defaultFamilyName ifTrue: ["style alias"
- 						aStream nextPutAll: ' (', style defaultFamilyName, ')'].
- 					aStream
- 						nextPutAll: ((Text new,
- 							((style isTTCStyle ifFalse: [''] ifTrue: [' TrueType', (defaultFont isRemoteFont ifFalse: [''] ifTrue: [' (remote)']), (defaultFont isSymbolFont ifFalse: [''] ifTrue: [' (symbols)'])])
- 								asText addAttribute: (TextColor color: ((self userInterfaceTheme get: #balloonTextColor for: #PluggableTextMorphPlus) ifNil: [Color gray])); yourself),
- 							(style isTTCStyle ifFalse: [''] ifTrue: [ | eg |
- 								'  ... ' asText,
- 								((' ', (defaultFont extraGlyphScale * 100) rounded asString, '%') asText addAttribute: (PluggableTextAttribute evalBlock: [style chooseExtraScale]); yourself),
- 								(('  ', ((eg := defaultFont extraLineGap) >= 0 ifTrue: ['+', eg asString] ifFalse: [eg asString])) asText addAttribute: (PluggableTextAttribute evalBlock: [style chooseExtraGap]); yourself) ]),
- 							'  ...  ',
- 							('explore' translated asText addAttribute: (PluggableTextAttribute evalBlock: [style explore]); yourself),
- 							'  ',
- 							('browse' translated asText addAttribute: (PluggableTextAttribute evalBlock: [defaultFont browseAllGlyphs; browseAllGlyphsByCategory]); yourself),
- 							
- 							'  ') addAttribute: (TextFontReference toFont: Preferences standardButtonFont); yourself);
- 						cr.
- 					aStream nextPutAll:	 (((self fontPointSizesFor: styleName) inject: '    ' asText into: [:text :pointSize |
- 							pointSize = defaultFont pointSize
- 								ifFalse: [text, ((pointSize asFloat printShowingDecimalPlaces: 1) padded: #left to: 5 with: Character space)]
- 								ifTrue: [text, (((pointSize asFloat printShowingDecimalPlaces: 1) padded: #left to: 5 with: Character space) asText addAttribute: TextEmphasis bold; yourself)]]) addAttribute: (TextFontReference toFont: TextStyle defaultFixedFont); yourself).
- 					aStream cr; cr].
- 			
- 			knownTTCStyles := knownStyles select: [:ea | (self named: ea) isTTCStyle].
- 			knownLegacyStyles := knownStyles reject: [:ea | (self named: ea) isTTCStyle].
- 			
- 			aStream cr.
- 			knownTTCStyles do: printBlock.
- 			aStream nextPutAll: ('The following pre-rendered legacy fonts are still available. Note that you can only choose from the point sizes that are listed here. Each point size has a pixel size for 96 PPI. The system scales currently for {1} PPI.' translated format: {TextStyle pixelsPerInch}) ; cr; cr.
- 			knownLegacyStyles do: printBlock.
- 				].!

Item was removed:
- ----- Method: TextStyle class>>fontSizesFor: (in category 'TextConstants access') -----
- fontSizesFor: aName
- 	"Answer the pixel sizes for all the fonts in the given text style"
- 
- 	"TextStyle fontSizesFor: 'Arial'"
- 	"TextStyle fontSizesFor: 'NewYork'"
- 
- 	^ (self fontArrayForStyle: aName) collect: [:f | f height ]
- !

Item was removed:
- ----- Method: TextStyle class>>fontWidthsFor: (in category 'TextConstants access') -----
- fontWidthsFor: aName
- 	"Answer the widths for all the fonts in the given text style"
- 
- 	"TextStyle fontWidthsFor: 'ComicPlain'"
- 	^ (self fontArrayForStyle: aName) collect: [:f | f maxWidth]
- !

Item was removed:
- ----- Method: TextStyle class>>importFontsFromStyleFiles (in category 'user interface') -----
- importFontsFromStyleFiles
- 	"Import any and all of the fonts found in the default directory in files named ComicBold.style, ComicPlain.style, NewYork.style, Palatino.style, Courier.style"
- 
- 	
- 	#('ComicBold' 'ComicPlain' 'NewYork' 'Palatino' 'Courier') do:
- 		[:frag | | aName |
- 			(TextStyle knownTextStyles includes: frag) ifFalse:
- 				[(FileDirectory default fileExists: (aName := frag, '.style'))
- 						ifTrue:
- 							[TextStyle default collectionFromFileNamed: aName]]].!

Item was removed:
- ----- Method: TextStyle class>>initDefaultFontsAndStyle (in category 'instance creation') -----
- initDefaultFontsAndStyle
- 	"This provides the system with 10 and 12-pt basal fonts.
- 	Bold and italic versions will be automatically generated as needed"
- 	| fontArray |	
- 	fontArray := Array new: 2.
- 	fontArray at: 1 put: (StrikeFont new readFromStrike2: 'NewYork10.sf2').
- 	fontArray at: 2 put: (StrikeFont new readFromStrike2: 'NewYork12.sf2').
- 	TextConstants at: #DefaultTextStyle put:
- 		(TextStyle fontArray: fontArray).
- 
- 	"TextStyle initDefaultFontsAndStyle."!

Item was removed:
- ----- Method: TextStyle class>>initialize (in category 'class initialization') -----
- initialize
- 	self initializeStyleDecoder.!

Item was removed:
- ----- Method: TextStyle class>>initializeStyleDecoder (in category 'class initialization') -----
- initializeStyleDecoder
- 	TextConstants at: #StyleDecoder put: nil.
- 	self styleDecoder.!

Item was removed:
- ----- Method: TextStyle class>>installDefaultFallbackTextStyle (in category 'utilities') -----
- installDefaultFallbackTextStyle
- 
- 	| defaultStyle |
- 	defaultStyle := self defaultFallback.
- 	self knownTextStylesWithoutDefault do: [:styleName |
- 		(self named: styleName) defaultFont fallbackTextStyle: defaultStyle].!

Item was removed:
- ----- Method: TextStyle class>>knownTextStyles (in category 'TextConstants access') -----
- knownTextStyles
- 	"Answer the names of the known text styles, sorted in alphabetical order"
- 
- 	"TextStyle knownTextStyles"
- 	^ (TextConstants select: [:thang | thang isKindOf: TextStyle]) keys asArray sort
- 
- !

Item was removed:
- ----- Method: TextStyle class>>knownTextStylesWithoutDefault (in category 'TextConstants access') -----
- knownTextStylesWithoutDefault
- 	"Answer the names of the known text styles, sorted in alphabetical order without default"
- 
- 	"TextStyle knownTextStylesWithoutDefault"
- 	| result |
- 	result := self knownTextStyles asOrderedCollection.
- 	^ result copyWithoutAll: self defaultFamilyNames
- 
- !

Item was removed:
- ----- Method: TextStyle class>>looseFontsFromFamily: (in category 'mime file in/out') -----
- looseFontsFromFamily: familyName
- 	"
- 	TextStyle looseFontsFromFamily: 'Accuny'
- 	TextStyle looseFontsFromFamily: 'Accujen'
- 	TextStyle actualTextStyles keys collect: [ :k | TextStyle looseFontsFromFamily: k ]
- 	"
- 
- 	| looseFonts realStyle classes |
- 	realStyle := TextStyle named: familyName.
- 	classes := ((realStyle fontArray copyWithout: nil) collect: [ :f | f class ]) asSet.
- 	classes do: [ :cls | cls allSubInstancesDo: [ :f | f releaseCachedState ]].
- 	Smalltalk garbageCollect.
- 	looseFonts := IdentitySet new.
- 	classes do: [ :cls |
- 		looseFonts addAll: ((cls allSubInstances select: [ :ea | ea familyName = familyName ])
- 			reject: [ :f | realStyle fontArray anySatisfy: [ :fn | fn == f or: [ fn derivativeFonts includes: f ] ]]) ].
- 	^looseFonts!

Item was removed:
- ----- Method: TextStyle class>>named: (in category 'constants') -----
- named: familyName
- 	"Answer the TextStyle with the given name, or nil."
- 	"TextStyle named: 'NewYork'"
- 	| textStyle |
- 	textStyle := TextConstants at: familyName ifAbsent: [ ^nil ].
- 	(textStyle isKindOf: self) ifFalse: [ ^nil ].
- 	^textStyle!

Item was removed:
- ----- Method: TextStyle class>>numSpacesPerTab (in category 'preferences') -----
- numSpacesPerTab
- 	<preference: 'Tab width (i.e., number of spaces)'
- 		categoryList: #(tools visuals Accessibility)
- 		description: 'Amount of spaces to be used when calculating the width of a tab character for a specific font face and point size.'
- 		type: #Number>
- 	^ NumSpacesPerTab ifNil: [6]!

Item was removed:
- ----- Method: TextStyle class>>numSpacesPerTab: (in category 'preferences') -----
- numSpacesPerTab: anInteger
- 
- 	anInteger = NumSpacesPerTab ifTrue: [^ self].
- 	NumSpacesPerTab := anInteger ifNotNil: [anInteger truncated max: 1].
- 	TextStyle allInstancesDo: [:ea | ea initializeTabsArray].
- 
- 	"Avoid dependency to Morphic project..."
- 	(self environment classNamed: #TextMorph)
- 		ifNotNil: [:tmClass | tmClass allSubInstancesDo: [:tm |
- 			tm releaseParagraph; changed]].!

Item was removed:
- ----- Method: TextStyle class>>pixelsPerInch (in category 'utilities') -----
- pixelsPerInch
- 	"Answer the nominal resolution of the screen."
- 
- 	^TextConstants at: #pixelsPerInch ifAbsentPut: [ 96.0 ].!

Item was removed:
- ----- Method: TextStyle class>>pixelsPerInch: (in category 'utilities') -----
- pixelsPerInch: aNumber
- 	"Set the nominal number of pixels per inch to aNumber."
- 
- 	self pixelsPerInch = aNumber ifTrue: [^ self].
- 	TextConstants at: #pixelsPerInch put: aNumber.
- 	AbstractFont allSubInstancesDo: [ :font | font pixelsPerInchChanged ].
- 	TextStyle allInstancesDo: [ :style | style pixelsPerInchChanged ].!

Item was removed:
- ----- Method: TextStyle class>>pixelsToPoints: (in category 'utilities') -----
- pixelsToPoints: pixels
- 	^pixels * 72.0 / self pixelsPerInch!

Item was removed:
- ----- Method: TextStyle class>>pointSizesFor: (in category 'TextConstants access') -----
- pointSizesFor: aName
- 	"Answer all the point sizes for the given text style name"
- 
- 	"TextStyle pointSizesFor: 'NewYork'"
- 	^ (self fontArrayForStyle: aName) collect: [:f | f pointSize]
- !

Item was removed:
- ----- Method: TextStyle class>>pointsToPixels: (in category 'utilities') -----
- pointsToPixels: points
- 	^points * self pixelsPerInch / 72.0!

Item was removed:
- ----- Method: TextStyle class>>referenceHeight (in category 'utilities') -----
- referenceHeight
- 	"See commentary in RealEstateAgent class >> #scaleFactor."
- 	
- 	^ self default isTTCStyle
- 		ifTrue: [self pointsToPixels: TTCFont referencePointSize]
- 		ifFalse: [self defaultFont height]!

Item was removed:
- ----- Method: TextStyle class>>replaceFontsIn:with: (in category 'mime file in/out') -----
- replaceFontsIn: oldFontArray with: newStyle
- 	"
- 	TextStyle replaceFontsIn: (TextStyle looseFontsFromFamily: #Accuny) with: (TextStyle named: #Accuny)
- 	"
- 	"Try to find corresponding fonts in newStyle and substitute them for the fonts in oldFontArray"
- 
- 	newStyle fontArray do: [ :newFont | newFont releaseCachedState ].
- 
- 	oldFontArray do: [ :oldFont | | newFont |
- 		oldFont reset.
- 		newFont := (newStyle fontOfPointSize: oldFont pointSize) emphasis: oldFont emphasis.
- 		oldFont becomeForward: newFont ].
- 
- 	Smalltalk at: #StringMorph ifPresent:[:cls| cls allSubInstancesDo: [ :s | s layoutChanged]].
- 	Smalltalk at: #TextMorph ifPresent:[:cls| cls allSubInstancesDo: [ :s | s layoutChanged]].
- 	Smalltalk at: #SystemWindow ifPresent:[:cls| 
- 		cls allInstancesDo: [ :w | [ w update: #relabel ] on: Error do: [ :ex | ] ]].
- 	Project current world ifNotNil: [ :w | w changed ].!

Item was removed:
- ----- Method: TextStyle class>>replaceStyle:with: (in category 'mime file in/out') -----
- replaceStyle: oldStyle with: newStyle
- 	"
- 	TextStyle replaceStyle: (TextStyle named: #AccunyOLD) with: (TextStyle named: #Accuny)
- 	"
- 	"Try to find corresponding fonts in newStyle and substitute the fonts in oldStyle for them."
- 	| oldKeys |
- 	oldKeys := Set new.
- 	TextConstants keysAndValuesDo: [ :k :v | v = oldStyle ifTrue: [ oldKeys add: k ]].
- 	oldKeys removeAllFoundIn: self defaultFamilyNames.
- 
- 	self replaceFontsIn: oldStyle fontArray with: newStyle.
- 
- 	oldStyle becomeForward: newStyle.
- 	oldKeys do: [ :k | TextConstants removeKey: k ].
- !

Item was removed:
- ----- Method: TextStyle class>>setDefault: (in category 'constants') -----
- setDefault: aTextStyle
- 	"Answer the system default text style."
- 
- 	DefaultTextStyle := aTextStyle.!

Item was removed:
- ----- Method: TextStyle class>>setDefaultFallback: (in category 'constants') -----
- setDefaultFallback: aTextStyle
- 	"
- 	TextStyle setDefaultFallback: (TextStyle named: #MSGothic).
- 	TextStyle setDefaultFallback: nil.
- 	
- 	self installDefaultFallbackTextStyle.
- 	"
- 	TextConstants at: #DefaultFallbackTextStyle put: aTextStyle.!

Item was removed:
- ----- Method: TextStyle class>>setDefaultFixed: (in category 'constants') -----
- setDefaultFixed: aTextStyle
- 
- 	DefaultFixedTextStyle := aTextStyle.!

Item was removed:
- ----- Method: TextStyle class>>styleDecoder (in category 'class initialization') -----
- styleDecoder
- 	TextConstants at: #StyleDecoder ifPresent: [ :dict | dict ifNotNil: [ ^dict ]].
- 	^TextConstants at: #StyleDecoder put: (
- 		Dictionary new at: 'Regular' put: 0;
- 				 at: 'Roman' put: 0;
- 				 at: 'Medium' put: 0;
- 				 at: 'Light' put: 0;
- 				 at: 'Normal' put: 0;
- 				 at: 'Plain' put: 0;
- 				 at: 'Book' put: 0;
- 				 at: 'Demi' put: 0;
- 				 at: 'Demibold' put: 0;
- 				 at: 'Semibold' put: 0;
- 				 at: 'SemiBold' put: 0;
- 				 at: 'ExtraBold' put: 1;
- 				 at: 'SuperBold' put: 1;
- 				 at: 'Negreta' put: 1;
- 				 at: 'B' put: 1;
- 				 at: 'I' put: 2;
- 				 at: 'U' put: 4;
- 				 at: 'X' put: 16;
- 				 at: 'N' put: 8;
- 				 at: 'Bold' put: 1;
- 				 at: 'Italic' put: 2;
- 				 at: 'Oblique' put: 2;
- 				 at: 'Narrow' put: 8;
- 				 at: 'Condensed' put: 8;
- 				 at: 'Underlined' put: 4;
- 				 yourself )!

Item was removed:
- ----- Method: TextStyle>>= (in category 'comparing') -----
- = other
- 
- 	self species == other species ifFalse: [^ false].
- 	1 to: self class instSize do:
- 		[:i | (self instVarAt: i) == (other instVarAt: i) ifFalse: [^ false]].
- 	^ true!

Item was removed:
- ----- Method: TextStyle>>alignment (in category 'accessing') -----
- alignment
- 	"Answer the code for the current setting of the alignment."
- 
- 	^alignment!

Item was removed:
- ----- Method: TextStyle>>alignment: (in category 'accessing') -----
- alignment: anInteger 
- 	"Set the current setting of the alignment to be anInteger:
- 	0=left flush, 1=right flush, 2=centered, 3=justified."
- 
- 	alignment := anInteger \\ (Justified + 1)!

Item was removed:
- ----- Method: TextStyle>>alignmentSymbol (in category 'accessing') -----
- alignmentSymbol
- 	"Answer the symbol for the current setting of the alignment."
- 	alignment = LeftFlush ifTrue:[^#leftFlush].
- 	alignment = Centered ifTrue:[^#centered].
- 	alignment = RightFlush ifTrue:[^#rightFlush].
- 	alignment = Justified ifTrue:[^#justified].
- 	^#leftFlush!

Item was removed:
- ----- Method: TextStyle>>asStringOrText (in category 'converting') -----
- asStringOrText
- 	"be fancy"
- 	^ self defaultFont familyName asText
- 		addAttribute: (TextFontReference toFont: self defaultFont);
- 		yourself!

Item was removed:
- ----- Method: TextStyle>>baseline (in category 'accessing - default font') -----
- baseline
- 	"Answer the distance from the top of the line to the bottom of most of the 
- 	characters (by convention, bottom of the letter 'A')."
- 
- 	^ self defaultFont ascent!

Item was removed:
- ----- Method: TextStyle>>baseline: (in category 'accessing - default font') -----
- baseline: anInteger 
- 
- 	self flag: #deprecated. "Either change #defaultFont in this style or use custom fonts via text attributes."!

Item was removed:
- ----- Method: TextStyle>>centered (in category 'accessing') -----
- centered
- 	alignment := 2!

Item was removed:
- ----- Method: TextStyle>>clearIndents (in category 'tabs and margins') -----
- clearIndents
- 	"Reset all the margin (index) settings to be 0."
- 
- 	self firstIndent: 0.
- 	self restIndent: 0.
- 	self rightIndent: 0!

Item was removed:
- ----- Method: TextStyle>>collectionFromFileNamed: (in category 'fonts and font indexes') -----
- collectionFromFileNamed: fileName
- 	"Read the file.  It is an TextStyle whose StrikeFonts are to be added to the system.  (Written by fooling SmartRefStream, so it won't write a DiskProxy!!)  These fonts will be added to the master TextSytle for this font family.  
- 	To write out fonts: 
- 		| ff | ff := ReferenceStream fileNamed: 'new fonts'.
- 		TextConstants at: #forceFontWriting put: true.
- 		ff nextPut: (TextConstants at: #AFontName).
- 			'do not mix font families in the TextStyle written out'.
- 		TextConstants at: #forceFontWriting put: false.
- 		ff close.
- 
- 	To read: (TextStyle default collectionFromFileNamed: 'new fonts')
- *** Do not remove this method *** "
- 
- 	| ff this newName style |
- 	ff := ReferenceStream fileNamed: fileName.
- 	this := ff nextAndClose.	"Only works if file created by special code above"
- 	newName := this fontArray first familyName.
- 	this fontArray do: [:aFont | aFont familyName = newName ifFalse: [
- 		self error: 'All must be same family']].
- 	style := TextConstants at: newName asSymbol ifAbsent: [
- 		^ TextConstants at: newName asSymbol put: this].		"new family"
- 	this fontArray do: [:aFont | | heights | "add new fonts"
- 		heights := style fontArray collect: [:bFont | bFont height].
- 		(heights includes: aFont height) ifFalse: [
- 			style fontAt: style fontArray size + 1 put: aFont]].
- !

Item was removed:
- ----- Method: TextStyle>>compositionWidthFor: (in category 'text composition') -----
- compositionWidthFor: aNumber
- 	"Answer the width of the composition rectangle in pixels using the receiver's #defaultFont.
- 		- Positive numbers are used as number of characters per line
- 		- Negative numbers are used as factor of #typoTypeSize
- 		- Zero will try to approximate 66 characters per line
- 	See commentaries in both #compositionWidthForTypeFactor and #compositionWidthForNumChars."
- 
- 	aNumber = 0 ifTrue: [^ self compositionWidthForNumChars].
- 
- 	^ aNumber > 0
- 		ifTrue: [self compositionWidthForNumChars: aNumber]
- 		ifFalse: [self compositionWidthForTypeFactor: aNumber negated]!

Item was removed:
- ----- Method: TextStyle>>compositionWidthForNumChars (in category 'text composition') -----
- compositionWidthForNumChars
- 	"Constant is based on the book
- 		The Elements of Typographic Style (version 3.0)
- 		by Robert Bringhurst
- 		
- 	Excerpts from Section 2.1.2 Choose a comfortable measure, page 26:
- 		[...] Anything from 45 to 75 characters is widely regarded as a satisfactory length of a line for a single-column page set in a serifed text face in a text size. The 66-character line (counting both letters and spaces) is widely regarded as ideal. For multiple-column work, a better average is 40 to 50 characters. [...]
- 
- 	Note that these numbers consider continuous text in English."
- 
- 	^ self compositionWidthForNumChars: 66!

Item was removed:
- ----- Method: TextStyle>>compositionWidthForNumChars: (in category 'text composition') -----
- compositionWidthForNumChars: numChars
- 	"Answer the width of the composition rectangle in pixels for numChars
- using the receiver's #defaultFont.
- 	
- 	You can compare this with other ways to prescribe a 'sheet of paper' for
- arbitrary content as follows:
- 	
- 	| sample style font |
- 	sample := 'the quick brown fox jumps over the lazy dog'.
- 	style := TextStyle default.
- 	font := style defaultFont.
- 	((1 to: sample size) collect: [:i | {
- 		font widthOfString: (sample first: i).
- 		style compositionWidthForNumChars: i.
- 		(font widthOf: $x) * i.
- 		(font widthOf: $m) * i }]) explore
- 	
- 	As you can see, using $x or $m will typically overshoot the values of
- #widthOfString: and #compositionWidthForNumChars:.
- 	"
- 	
- 	^ (self normalizedCharacterWidth * numChars) truncated!

Item was removed:
- ----- Method: TextStyle>>compositionWidthForTypeFactor (in category 'text composition') -----
- compositionWidthForTypeFactor
- 	"Constant is based on the book
- 		The Elements of Typographic Style (version 3.0)
- 		by Robert Bringhurst
- 		
- 	Excerpt from Section 2.1.2 Choose a comfortable measure, page 27:
- 		[...] On a conventional book page, the measure, or length of line, is usually around 30 times the size of the type, but lines as little as 20 or as much as 40 times the type size fall within the expectable range. [...]
- 
- 	Note that these numbers consider continuous text in English."
- 	
- 	^ self compositionWidthForTypeFactor: 30!

Item was removed:
- ----- Method: TextStyle>>compositionWidthForTypeFactor: (in category 'text composition') -----
- compositionWidthForTypeFactor: typeFactor
- 	"Answers a default composition width for the given typeFactor."
- 	
- 	^ (self typoTypeSize * typeFactor) truncated!

Item was removed:
- ----- Method: TextStyle>>compressedMIMEEncoded (in category 'mime file in/out') -----
- compressedMIMEEncoded
- 	"Answer a String with my compressed, stored representation as Base64"
- 
- 	| s ff |
- 	self fontArray do: [:f | f releaseCachedState].
- 	s := RWBinaryOrTextStream on: ''.
- 	ff := SmartRefStream on: s reset.
- 	TextConstants at: #forceFontWriting put: true.
- 	[ff nextPut: self] 
- 		ensure: [TextConstants at: #forceFontWriting put: false].
- 	^s contents asByteArray zipped base64Encoded!

Item was removed:
- ----- Method: TextStyle>>consistOnlyOf: (in category 'fonts and font indexes') -----
- consistOnlyOf: aFont
- 
- 	self deprecated.
- 	^ self newFontArray: {aFont}!

Item was removed:
- ----- Method: TextStyle>>consolidate (in category 'private') -----
- consolidate
- 	"If this style includes any fonts that are also in the default style,
- 	then replace them with references to the default ones."
- "
- 	TextStyle allInstancesDo: [:s | s == TextStyle default ifFalse: [s consolidate]]
- "
- 	| defFonts font |
- 	defFonts := TextStyle default fontArray.
- 	1 to: fontArray size do:
- 		[:i | font := fontArray at: i.
- 		1 to: defFonts size do:
- 			[:j | (font name asUppercase copyWithout: $ )
- 			= ((defFonts at: j) name asUppercase copyWithout: $ )
- 			ifTrue: [fontArray at: i put: (defFonts at: j)]]]!

Item was removed:
- ----- Method: TextStyle>>defaultFamilyName (in category 'accessing - default font') -----
- defaultFamilyName
- 	^ self defaultFont familyName!

Item was removed:
- ----- Method: TextStyle>>defaultFont (in category 'accessing - default font') -----
- defaultFont
- 	^ fontArray at: self defaultFontIndex!

Item was removed:
- ----- Method: TextStyle>>defaultFontIndex (in category 'accessing - default font') -----
- defaultFontIndex
- 	^ defaultFontIndex ifNil: [defaultFontIndex := 1]!

Item was removed:
- ----- Method: TextStyle>>defaultFontIndex: (in category 'accessing - default font') -----
- defaultFontIndex: anIndex
- 
- 	defaultFontIndex := anIndex.
- 	
- 	self initializeTabsArray.
- 	self initializeNormalizedCharacterWIdth.!

Item was removed:
- ----- Method: TextStyle>>firstIndent (in category 'accessing') -----
- firstIndent
- 	"Answer the horizontal indenting of the first line of a paragraph in the 
- 	style of the receiver."
- 
- 	^firstIndent!

Item was removed:
- ----- Method: TextStyle>>firstIndent: (in category 'accessing') -----
- firstIndent: anInteger 
- 	"Set the horizontal indenting of the first line of a paragraph in the style 
- 	of the receiver to be the argument, anInteger."
- 
- 	firstIndent := anInteger!

Item was removed:
- ----- Method: TextStyle>>fontArray (in category 'private') -----
- fontArray
- 	"Only for writing out fonts, etc.  8/16/96 tk"
- 	^ fontArray!

Item was removed:
- ----- Method: TextStyle>>fontAt: (in category 'private') -----
- fontAt: index 
- 	"This is private because no object outside TextStyle should depend on the 
- 	representation of the font family in fontArray."
- 
- 	^ fontArray atPin: index!

Item was removed:
- ----- Method: TextStyle>>fontAt:put: (in category 'private') -----
- fontAt: index put: font
- 	"Automatically grow the array.  8/20/96 tk"
- 	index > fontArray size ifTrue: [
- 		fontArray := fontArray, (Array new: index - fontArray size)].
- 	fontArray at: index put: font!

Item was removed:
- ----- Method: TextStyle>>fontIndexOf: (in category 'fonts and font indexes') -----
- fontIndexOf: aFont
- 	^ fontArray indexOf: aFont ifAbsent: [nil]!

Item was removed:
- ----- Method: TextStyle>>fontIndexOfPointSize: (in category 'fonts and font indexes') -----
- fontIndexOfPointSize: desiredPointSize
- 	"Returns an index in fontArray of the font with pointSize <= desiredPointSize"
- 	"Leading is not inluded in the comparison"
- 	| bestMatch bestIndex d |
- 	bestMatch := 9999.  bestIndex := 1.
- 	1 to: fontArray size do:
- 		[:i | d := desiredPointSize - (fontArray at: i) pointSize.
- 		d = 0 ifTrue: [^ i].
- 		(d > 0 and: [d < bestMatch]) ifTrue: [bestIndex := i. bestMatch := d]].
- 	^ bestIndex!

Item was removed:
- ----- Method: TextStyle>>fontIndexOfSize: (in category 'fonts and font indexes') -----
- fontIndexOfSize: desiredHeight
- 	"Returns an index in fontArray of the font with height <= desiredHeight"
- 	"Leading is not inluded in the comparison"
- 	| bestMatch bestIndex d |
- 	bestMatch := 9999.  bestIndex := 1.
- 	1 to: fontArray size do:
- 		[:i | d := desiredHeight - (fontArray at: i) height.
- 		d = 0 ifTrue: [^ i].
- 		(d > 0 and: [d < bestMatch]) ifTrue: [bestIndex := i. bestMatch := d]].
- 	^ bestIndex!

Item was removed:
- ----- Method: TextStyle>>fontNamed: (in category 'accessing') -----
- fontNamed: fontName  "TextStyle default fontNamed: 'TimesRoman10'"
- 	^ fontArray detect: [:x | x name sameAs: fontName]!

Item was removed:
- ----- Method: TextStyle>>fontNames (in category 'accessing') -----
- fontNames  "TextStyle default fontNames"
- 	^ fontArray collect: [:x | x name]!

Item was removed:
- ----- Method: TextStyle>>fontNamesAndSizes (in category 'accessing') -----
- fontNamesAndSizes  "TextStyle default fontNames"
- 	^ fontArray collect: [:x | x name, ' ', x height printString]!

Item was removed:
- ----- Method: TextStyle>>fontNamesWithPointSizes (in category 'accessing') -----
- fontNamesWithPointSizes
- 	^ fontArray collect:
- 		[:x | x fontNameWithPointSize]
- 
-   "TextStyle default fontNamesWithPointSizes"!

Item was removed:
- ----- Method: TextStyle>>fontOfPointSize: (in category 'fonts and font indexes') -----
- fontOfPointSize: aPointSize
- 	^ fontArray at: (self fontIndexOfPointSize: aPointSize)!

Item was removed:
- ----- Method: TextStyle>>fontOfSize: (in category 'fonts and font indexes') -----
- fontOfSize: aHeight
- 	"See fontIndexOfSize.
- 	Returns the actual font.  Leading not considered."
- 
- 	^ fontArray at: (self fontIndexOfSize: aHeight)!

Item was removed:
- ----- Method: TextStyle>>fonts (in category 'accessing') -----
- fonts
- 	"Return a collection of fonts contained in this text style"
- 	^fontArray!

Item was removed:
- ----- Method: TextStyle>>gridForFont:withLead: (in category 'private') -----
- gridForFont: fontIndex withLead: leadInteger 
- 	"Force whole style to suit one of its fonts. Assumes only one font referred
- 	to by runs."
- 
- 	self flag: #deprecated.
- 	self defaultFontIndex: fontIndex.!

Item was removed:
- ----- Method: TextStyle>>hash (in category 'comparing') -----
- hash
- 	"#hash is re-implemented because #= is re-implemented"
- 	^fontArray hash
- !

Item was removed:
- ----- Method: TextStyle>>initializeNormalizedCharacterWIdth (in category 'initialize-release') -----
- initializeNormalizedCharacterWIdth
- 
- 	normalizedCharacterWidth := nil.!

Item was removed:
- ----- Method: TextStyle>>initializeTabsArray (in category 'initialize-release') -----
- initializeTabsArray
- 
- 	| fontToUse numSpacesPerTab tabWidth maxWidth |
- 	self flag: #discuss. "mt: Add cache per font and pointSize? Maybe it is not worth it..."
- 	
- 	numSpacesPerTab := self class numSpacesPerTab.
- 	fontToUse := self defaultFont.
- 	maxWidth := Display width max: 3840.	
- 	tabWidth := ((fontToUse widthOf: Character space) max: 1 "For tiny point sizes...") * numSpacesPerTab.
- 	
- 	"Note that using Interval via #to:by: and #asArray would be about 4x slower."
- 	tabsArray := Array new: maxWidth // tabWidth.
- 	1 to: tabsArray size do: [:i | tabsArray at: i put: tabWidth * i].
- 	
- 	marginTabsArray := Array new: (maxWidth // tabWidth) // 2.
- 	1 to: marginTabsArray size do: [:i | | offset |
- 		marginTabsArray at: i put: (Array with: (offset := tabWidth * i) with: offset)].!

Item was removed:
- ----- Method: TextStyle>>isTTCStyle (in category 'accessing') -----
- isTTCStyle
- 
- 	^ fontArray first isTTCFont.
- !

Item was removed:
- ----- Method: TextStyle>>justified (in category 'accessing') -----
- justified
- 	alignment := 3!

Item was removed:
- ----- Method: TextStyle>>leading (in category 'accessing - default font') -----
- leading
- 	"Leading (from typographers historical use of extra lead (type metal))
- 	is the extra spacing above and beyond that needed just to accomodate
- 	the various font heights in the set."
- 
- 	self flag: #deprecated. "mt: Fonts provide their #lineGap (and #lineGapSlice) in the CompositionScanner to accommodate various font heights in a set. Use #lineSpacing to define a factor that moves the lines further apart."
- 	^ 0!

Item was removed:
- ----- Method: TextStyle>>leading: (in category 'accessing - default font') -----
- leading: yDelta
- 
- 	self flag: #deprecated. "See commentary in #leading."!

Item was removed:
- ----- Method: TextStyle>>leftFlush (in category 'accessing') -----
- leftFlush
- 	alignment := 0!

Item was removed:
- ----- Method: TextStyle>>leftMarginTabAt: (in category 'tabs and margins') -----
- leftMarginTabAt: marginIndex 
- 	"Set the 'nesting' level of left margin indents of the paragraph in the 
- 	style of the receiver to be the argument, marginIndex."
- 
- 	(marginIndex > 0 and: [marginIndex < marginTabsArray size])
- 		ifTrue: [^(marginTabsArray at: marginIndex) at: 1]
- 		ifFalse: [^0]	
- 	"The marginTabsArray is an Array of tuples.  The Array is indexed according 
- 	to the marginIndex, the 'nesting' level of the requestor."
- !

Item was removed:
- ----- Method: TextStyle>>lineGrid (in category 'accessing - default font') -----
- lineGrid
- 	"Answer the relative space between lines of a paragraph in the style of 
- 	the receiver."
- 
- 	^ self defaultFont lineGrid!

Item was removed:
- ----- Method: TextStyle>>lineGrid: (in category 'accessing - default font') -----
- lineGrid: anInteger 
- 
- 	self flag: #deprecated. "Either change #defaultFont in this style or use custom fonts via text attributes."!

Item was removed:
- ----- Method: TextStyle>>lineSpacing (in category 'accessing') -----
- lineSpacing
- 	"Answer the factor that is used to compute extra spacing between text lines. The default is 0.0, which means that the CompositionScanner will just rely on the various font metrics in a line. There will be 0% of extra spacing. Use the current line height as blank space with a factor of 1.0 and so on (i.e. the common misnomer 'double line space')."
- 	
- 	^ lineSpacing ifNil: [0.0]!

Item was removed:
- ----- Method: TextStyle>>lineSpacing: (in category 'accessing') -----
- lineSpacing: aFactor
- 
- 	lineSpacing := aFactor.!

Item was removed:
- ----- Method: TextStyle>>makeArrows (in category 'make arrows') -----
- makeArrows
- "
- TextStyle default makeArrows.
- "
- 	fontArray do: [ :font |
- 		(font isKindOf: StrikeFont) ifTrue:[ 
- 			font 
- 				makeAssignArrow; 
- 				makeReturnArrow.
- 		]
- 	].
- !

Item was removed:
- ----- Method: TextStyle>>marginTabAt:side: (in category 'private') -----
- marginTabAt: marginIndex side: sideIndex 
- 	"The marginTabsArray is an Array of tuples.  The Array is indexed
- 	according to the marginIndex, the 'nesting' level of the requestor.
- 	sideIndex is 1 for left, 2 for right."
- 
- 	(marginIndex > 0 and: [marginIndex < marginTabsArray size])
- 		ifTrue: [^(marginTabsArray at: marginIndex) at: sideIndex]
- 		ifFalse: [^0]!

Item was removed:
- ----- Method: TextStyle>>maxDepth (in category 'accessing') -----
- maxDepth
- 
- 	^ (self fonts collect: [:font | font depth]) max!

Item was removed:
- ----- Method: TextStyle>>newFontArray: (in category 'private') -----
- newFontArray: anArray
- 	"Currently there is no supporting protocol for changing these arrays. If an editor wishes to implement margin setting, then a copy of the default should be stored with these instance variables.  
- 	, Make size depend on first font."
- 
- 	fontArray := anArray.
- 	self defaultFontIndex: 1.
- 	alignment := 0.
- 	firstIndent := 0.
- 	restIndent := 0.
- 	rightIndent := 0.
- "
- TextStyle allInstancesDo: [:ts | ts newFontArray: TextStyle default fontArray].
- "!

Item was removed:
- ----- Method: TextStyle>>nextTabXFrom:leftMargin:rightMargin: (in category 'tabs and margins') -----
- nextTabXFrom: anX leftMargin: leftMargin rightMargin: rightMargin 
- 	"Tab stops are distances from the left margin. Set the distance into the 
- 	argument, anX, normalized for the paragraph's left margin."
- 
- 	| normalizedX tabX |
- 	normalizedX := anX - leftMargin.
- 	1 to: tabsArray size do: 
- 		[:i | (tabX := tabsArray at: i) > normalizedX 
- 				ifTrue: [^leftMargin + tabX min: rightMargin]].
- 	^rightMargin!

Item was removed:
- ----- Method: TextStyle>>normalizedCharacterWidth (in category 'text composition') -----
- normalizedCharacterWidth
- 	"Answer the normalized character width to compute a pixel-based box for text composition that follows what you specify via #compositionWidthForNumChars:. Cached for performance.
- 
- 	Alphabet-divide constant is based on the book (table on page 29):
- 		The Elements of Typographic Style (version 3.0)
- 		by Robert Bringhurst"
- 
- 	^ normalizedCharacterWidth ifNil: [
- 		normalizedCharacterWidth := self defaultFont hasFixedWidth
- 			ifTrue: [ self defaultFont widthOf: $M "often ~= #typoTypeSize!!"]
- 			ifFalse: [ self typoAlphabetLength asFloat * 0.036 ]]!

Item was removed:
- ----- Method: TextStyle>>pixelsPerInchChanged (in category 'notifications') -----
- pixelsPerInchChanged
- 
- 	self reset.!

Item was removed:
- ----- Method: TextStyle>>pointSizes (in category 'accessing') -----
- pointSizes
- 	^ fontArray collect:
- 		[:x | x pointSize]
- 
-   "TextStyle default fontNamesWithPointSizes"!

Item was removed:
- ----- Method: TextStyle>>printOn: (in category 'printing') -----
- printOn: aStream
- 
- 	super printOn: aStream.
- 	aStream nextPut: $(.
- 	aStream print: fontArray size.
- 	aStream nextPut: $).
- 	aStream space.
- 	self defaultFont printShortDescriptionOn: aStream.
- !

Item was removed:
- ----- Method: TextStyle>>reset (in category 'initialize-release') -----
- reset
- 	"Reset values cached from the receiver's default font."
- 	
- 	self defaultFontIndex: self defaultFontIndex.!

Item was removed:
- ----- Method: TextStyle>>restIndent (in category 'accessing') -----
- restIndent
- 	"Answer the indent for all but the first line of a paragraph in the style 
- 	of the receiver."
- 
- 	^restIndent!

Item was removed:
- ----- Method: TextStyle>>restIndent: (in category 'accessing') -----
- restIndent: anInteger 
- 	"Set the indent for all but the first line of a paragraph in the style of the 
- 	receiver to be the argument, anInteger."
- 
- 	restIndent := anInteger!

Item was removed:
- ----- Method: TextStyle>>rightFlush (in category 'accessing') -----
- rightFlush
- 	alignment := 1!

Item was removed:
- ----- Method: TextStyle>>rightIndent (in category 'accessing') -----
- rightIndent
- 	"Answer the right margin indent for the lines of a paragraph in the style 
- 	of the receiver."
- 
- 	^rightIndent!

Item was removed:
- ----- Method: TextStyle>>rightIndent: (in category 'accessing') -----
- rightIndent: anInteger 
- 	"Answer the right margin indent for the lines of a paragraph in the style 
- 	of the receiver to be the argument, anInteger."
- 
- 	rightIndent := anInteger!

Item was removed:
- ----- Method: TextStyle>>rightMarginTabAt: (in category 'tabs and margins') -----
- rightMarginTabAt: marginIndex 
- 	"Set the 'nesting' level of right margin indents of the paragraph in the 
- 	style of the receiver to be marginIndex."
- 
- 	(marginIndex > 0 and: [marginIndex < marginTabsArray size])
- 		ifTrue: [^(marginTabsArray at: marginIndex) at: 2]
- 		ifFalse: [^0]
- 	"The marginTabsArray is an Array of tuples.  The Array is indexed according 
- 	to the marginIndex, the 'nesting' level of the requestor."
- !

Item was removed:
- ----- Method: TextStyle>>species (in category 'comparing') -----
- species
- 
- 	^TextStyle!

Item was removed:
- ----- Method: TextStyle>>storeDataOn: (in category 'object from disk') -----
- storeDataOn: aDataStream
- 	"The shared arrays in tabsArray and marginTabsArray are the globals DefaultTabsArray and DefaultMarginTabsArray.  DiskProxies will be substituted for these in (Array objectForDataStream:)."
- 
- 	^ super storeDataOn: aDataStream!

Item was removed:
- ----- Method: TextStyle>>tabWidth (in category 'tabs and margins') -----
- tabWidth
- 	"Answer the width of a tab."
- 
- 	^ tabsArray at: 1 ifAbsent: [24]!

Item was removed:
- ----- Method: TextStyle>>textStyleName (in category 'accessing - default font') -----
- textStyleName
- 	^ self defaultFont textStyleName!

Item was removed:
- ----- Method: TextStyle>>typoAlphabetLength (in category 'text composition') -----
- typoAlphabetLength
- 	"
- 	TextStyle default typoAlphabetLength.
- 	TextStyle defaultFixed typoAlphabetLength.
- 	"	
- 	| font |
- 	font := self defaultFont.
- 	^ ($a to: $z) inject: 0 into: [:sum :char | sum + (font widthOf: char)]!

Item was removed:
- ----- Method: TextStyle>>typoTypeSize (in category 'text composition') -----
- typoTypeSize
- 	"
- 	TextStyle default typoTypeSize.
- 	TextStyle defaultFixed typoTypeSize.	
- 	"
- 	^ self defaultFont height!

Item was removed:
- ----- Method: TextStyle>>veryDeepCopyWith: (in category 'copying') -----
- veryDeepCopyWith: deepCopier
- 	"All inst vars are meant to be shared"
- 
- 	self == #veryDeepCopyWith:.	"to satisfy checkVariables"
- 	^ deepCopier references at: self ifAbsentPut: [self shallowCopy].	"remember"!

Item was removed:
- Color subclass: #TranslucentColor
- 	instanceVariableNames: 'alpha'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Primitives'!
- 
- !TranslucentColor commentStamp: '<historical>' prior: 0!
- A TranslucentColor behaves just like a normal color, except that it will pack its alpha value into the high byte of a 32-bit pixelValue.  This allows creating forms with translucency for use with the alpha blend function of BitBlt.  An alpha of zero is transparent, and 1.0 is opaque.!

Item was removed:
- ----- Method: TranslucentColor>>addName: (in category 'other') -----
- addName: aSymbol
- 	"private - associate a name to this color.
- 	Don't do it, Translucent colors are not uniquely identified by their rgb components"
- 	
- 	^self!

Item was removed:
- ----- Method: TranslucentColor>>alpha (in category 'accessing') -----
- alpha
- 	"Return my alpha value, a number between 0.0 and 1.0 where 0.0 is completely transparent and 1.0 is completely opaque."
- 
- 	^ alpha asFloat / 255.0
- !

Item was removed:
- ----- Method: TranslucentColor>>alpha: (in category 'conversions') -----
- alpha: alphaValue
- 	alphaValue = 1.0 ifTrue:
- 		[^ Color basicNew
- 			setPrivateRed: self privateRed
- 			green: self privateGreen
- 			blue: self privateBlue].
- 	^ super alpha: alphaValue!

Item was removed:
- ----- Method: TranslucentColor>>asHTMLColor (in category 'conversions') -----
- asHTMLColor
- 
- 	^ super asHTMLColor 
- 		, (Character digitValue: ((alpha bitShift: -4) bitAnd: 15))
- 		, (Character digitValue: (alpha bitAnd: 15))!

Item was removed:
- ----- Method: TranslucentColor>>asNontranslucentColor (in category 'conversions') -----
- asNontranslucentColor
- 	^ self alpha: 1.0!

Item was removed:
- ----- Method: TranslucentColor>>balancedPatternForDepth: (in category 'conversions') -----
- balancedPatternForDepth: depth
- 	"Return an appropriate bit pattern or stipple.  This will almost never be meaningful for tranlucentColors, except for the degenerate case of tranparency."
- 
- 	alpha = 0 ifTrue: [^ Bitmap with: 0].
- 	^ super balancedPatternForDepth: depth!

Item was removed:
- ----- Method: TranslucentColor>>bitPatternForDepth: (in category 'conversions') -----
- bitPatternForDepth: depth
- 	"Return an appropriate bit pattern or stipple.  This will almost never be meaningful for tranlucentColors, except for the degenerate case of tranparency."
- 
- 	alpha = 0 ifTrue: [^ Bitmap with: 0].
- 	^ super bitPatternForDepth: depth!

Item was removed:
- ----- Method: TranslucentColor>>convertToCurrentVersion:refStream: (in category 'object fileIn') -----
- convertToCurrentVersion: varDict refStream: smartRefStrm
- 	
- 	"1/13/1999 -- old versions did not have alpha??"
- 	varDict at: 'alpha' ifAbsent: [^ Color transparent].
- 
- 	^super convertToCurrentVersion: varDict refStream: smartRefStrm.
- 	!

Item was removed:
- ----- Method: TranslucentColor>>hash (in category 'comparing') -----
- hash
- 
- 	^ rgb bitXor: alpha
- !

Item was removed:
- ----- Method: TranslucentColor>>isOpaque (in category 'testing') -----
- isOpaque
- 	^alpha = 255!

Item was removed:
- ----- Method: TranslucentColor>>isTranslucent (in category 'testing') -----
- isTranslucent
- 	^ alpha < 255!

Item was removed:
- ----- Method: TranslucentColor>>isTranslucentColor (in category 'testing') -----
- isTranslucentColor
- 	"This means: self isTranslucent, but isTransparent not"
- 	^ alpha > 0!

Item was removed:
- ----- Method: TranslucentColor>>isTransparent (in category 'testing') -----
- isTransparent
- 	^ alpha = 0!

Item was removed:
- ----- Method: TranslucentColor>>name (in category 'other') -----
- name
- 	self = Color transparent ifTrue: [^#transparent].
- 	^nil!

Item was removed:
- ----- Method: TranslucentColor>>pixelValueForDepth: (in category 'conversions') -----
- pixelValueForDepth: d
- 	"Return the pixel value for this color at the given depth. Translucency only works in RGB; this color will appear either opaque or transparent at all other depths."
- 	| basicPixelWord |
- 	alpha = 0 ifTrue: [^ 0].
- 	basicPixelWord := super pixelValueForDepth: d.
- 	d < 32
- 		ifTrue: [^ basicPixelWord]
- 		ifFalse: [^ (basicPixelWord bitAnd: 16rFFFFFF) bitOr: (alpha bitShift: 24)].
- !

Item was removed:
- ----- Method: TranslucentColor>>pixelWordForDepth: (in category 'conversions') -----
- pixelWordForDepth: depth
- 	"Return the pixel value for this color at the given depth. Translucency only works in RGB; this color will appear either opaque or transparent at all other depths."
- 
- 	| basicPixelWord |
- 	alpha = 0 ifTrue: [^ 0].
- 	basicPixelWord := super pixelWordForDepth: depth.
- 	depth < 32
- 		ifTrue: [^ basicPixelWord]
- 		ifFalse: [^ (basicPixelWord bitAnd: 16rFFFFFF) bitOr: (alpha bitShift: 24)].
- !

Item was removed:
- ----- Method: TranslucentColor>>printOn: (in category 'printing') -----
- printOn: aStream
- 	| name |
- 	self isTransparent ifTrue: [^ aStream nextPutAll: 'Color transparent'].
- 	(name := self asNontranslucentColor name) ifNil: [^self storeOn: aStream].
- 	aStream
- 		nextPutAll: '(Color ';
- 		nextPutAll: name;
- 		nextPutAll: ' alpha: ';
- 		print: self alpha maxDecimalPlaces: 3;
- 		nextPut: $)
- 	!

Item was removed:
- ----- Method: TranslucentColor>>privateAlpha (in category 'private') -----
- privateAlpha
- 	"Return my raw alpha value, an integer in the range 0..255. Used for fast equality testing."
- 
- 	^ alpha
- !

Item was removed:
- ----- Method: TranslucentColor>>scaledPixelValue32 (in category 'conversions') -----
- scaledPixelValue32
- 	"Return the alpha scaled pixel value for depth 32"
- 	| pv32 a b g r |
- 	pv32 := super scaledPixelValue32.
- 	a := (self alpha * 255.0) rounded.
- 	b := (pv32 bitAnd: 255) * a // 256.
- 	g := ((pv32 bitShift: -8) bitAnd: 255) * a // 256.
- 	r := ((pv32 bitShift: -16) bitAnd: 255) * a // 256.
- 	^b + (g bitShift: 8) + (r bitShift: 16) + (a bitShift: 24)!

Item was removed:
- ----- Method: TranslucentColor>>setAlpha: (in category 'private') -----
- setAlpha: alphaValue
- 
- 	alpha := (255.0 * alphaValue) asInteger min: 255 max: 0.!

Item was removed:
- ----- Method: TranslucentColor>>setRgb:alpha: (in category 'private') -----
- setRgb: rgbValue alpha: alphaValue
- 	"Set the state of this translucent color. Alpha is represented internally by an integer in the range 0..255."
- 
- 	rgb == nil ifFalse: [self attemptToMutateError].
- 	rgb := rgbValue.
- 	alpha := (255.0 * alphaValue) asInteger min: 255 max: 0.
- !

Item was removed:
- ----- Method: TranslucentColor>>storeArrayValuesOn: (in category 'printing') -----
- storeArrayValuesOn: aStream
- 
- 	self isTransparent ifTrue: [
- 		^ aStream space].
- 	super storeArrayValuesOn: aStream.
- 	aStream
- 		space;
- 		print: self alpha maxDecimalPlaces: 3.!

Item was removed:
- ----- Method: TranslucentColor>>storeOn: (in category 'printing') -----
- storeOn: aStream
- 
- 	self isTransparent ifTrue: [^ aStream nextPutAll: 'Color transparent'].
- 	super storeOn: aStream.
- 	aStream
- 		skip: -1;	  "get rid of trailing )"
- 		nextPutAll: ' alpha: ';
- 		print: self alpha maxDecimalPlaces: 3;
- 		nextPutAll: ')'.
- !

Item was removed:
- HostWindowProxy subclass: #UnixX11WindowProxy
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-External-Ffenestri'!

Item was removed:
- ----- Method: UnixX11WindowProxy class>>isActiveHostWindowProxyClass (in category 'as yet unclassified') -----
- isActiveHostWindowProxyClass
- "Am I active?"
- 	^Smalltalk platformName = 'unix' !

Item was removed:
- ----- Method: UnixX11WindowProxy>>defaultWindowType (in category 'window decorations') -----
- defaultWindowType!

Item was removed:
- BitBlt subclass: #WarpBlt
- 	instanceVariableNames: 'p1x p1y p1z p2x p2y p2z p3x p3y p3z p4x p4y p4z cellSize sourceRGBmap'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-Primitives'!
- 
- !WarpBlt commentStamp: '<historical>' prior: 0!
- WarpBlt is a little warp-drive added on to BitBlt.  It takes a quadrilateral as its source specification, while its destination is traversed and combined just like any other call to copyBits.
- 
- The source quadrilateral is specified as an array of points starting with the corner that wants to end up in the topLeft, and proceding to the successive points that want to follow CCW around the destination rectangle.  Note that in specifying a plain old rectangle source, its non topLeft points must be actual pixels, not outside by 1, as with rectangle bottmRight, eg.  See the method Rectangle asQuad.
- 
- WarpBlt does a fast job of rotation, reflection and scaling, and it can even produce a semblance of perspective.  Depth parameters are included for future improvements in this direction. but the primitve does not support this yet.!

Item was removed:
- ----- Method: WarpBlt class>>current (in category 'instance creation') -----
- current
- 	"Return the class currently to be used for WarpBlt"
- 	^self!

Item was removed:
- ----- Method: WarpBlt class>>rotate:degrees:center:scaleBy:smoothing: (in category 'form rotation') -----
- rotate: srcForm degrees: angleInDegrees center: rotationCenter scaleBy: scalePoint smoothing: cellSize 
- 	"Rotate the given Form angleInDegrees about the given rotationCenter and scale its width and height by x and y of the given scale
- 	point. Smooth using the given cell size, an integer between 1 and 3, where 1 means no smoothing. 
- 	Return a pair where the first element is the rotated Form and the second is the position offset required to align the center of the rotated Form with that of the original. 
- 	Note that the dimensions of the resulting Form generally differ from those of the original."
- 	| srcRect srcCenter radians dstOrigin dstCorner p dstRect inverseScale quad dstForm warpSrc newRotationPoint oldOffset |
- 	srcRect := srcForm boundingBox.
- 	srcCenter := srcRect center.
- 	radians := angleInDegrees degreesToRadians.
- 	dstOrigin := dstCorner := srcCenter.
- 	srcRect corners
- 		do: [:corner | 
- 			"find the limits of a rectangle that just encloses the rotated
- 			original; in general, this rectangle will be larger than the
- 			original (e.g., consider a square rotated by 45 degrees)"
- 			p := (corner - srcCenter scaleBy: scalePoint) + srcCenter.
- 			p := (p rotateBy: radians about: srcCenter) rounded.
- 			dstOrigin := dstOrigin min: p.
- 			dstCorner := dstCorner max: p].
- 	"rotate the enclosing rectangle back to get the source quadrilateral"
- 	dstRect := dstOrigin corner: dstCorner.
- 	inverseScale := 1.0 / scalePoint x @ (1.0 / scalePoint y).
- 	quad := dstRect innerCorners
- 				collect: [:corner | 
- 					p := corner rotateBy: radians negated about: srcCenter.
- 					(p - srcCenter scaleBy: inverseScale) + srcCenter].
- 
- 	"make a Form to hold the result and do the rotation"
- 	warpSrc := srcForm.
- 	srcForm isColorForm
- 		ifTrue: [warpSrc := Form extent: srcForm extent depth: 16.
- 			srcForm displayOn: warpSrc.
- 			dstForm := Form extent: dstRect extent depth: 16
- 			"use 16-bit depth to allow smoothing"]
- 		ifFalse: [dstForm := srcForm species extent: dstRect extent depth: srcForm depth].
- 	(WarpBlt toForm: dstForm)
- 		sourceForm: warpSrc;
- 		colorMap: (warpSrc colormapIfNeededFor: dstForm);
- 		 cellSize: cellSize;
- 		 combinationRule: Form paint;
- 		 copyQuad: quad toRect: dstForm boundingBox.
- 
- 	"installs a new colormap if cellSize > 1"
- 	dstForm isColorForm
- 		ifTrue: [dstForm colors: srcForm colors copy].
- 
- 	oldOffset := rotationCenter - srcCenter truncated * scalePoint.
- 	newRotationPoint := dstForm extent / 2.0 + (oldOffset rotateBy: radians about: 0 @ 0).
- 
- 	^ Array with: dstForm with: newRotationPoint - rotationCenter!

Item was removed:
- ----- Method: WarpBlt class>>test1 (in category 'examples') -----
- test1   "Display restoreAfter: [WarpBlt test1]"
- 	"Demonstrates variable scale and rotate"
- 	| warp pts r1 p0 p ext |
- 	UIManager default informUser: 'Choose a rectangle with interesting stuff'
- 		during: [r1 := Rectangle originFromUser: 50 at 50.
- 				Sensor waitNoButton].
- 	UIManager default informUser: 'Now click down and up
- and move the mouse around the dot'
- 		during: [p0 := Sensor waitClickButton.
- 				(Form dotOfSize: 8) displayAt: p0].
- 	warp := (self toForm: Display)
- 		clipRect: (0 at 0 extent: r1 extent*5);
- 		sourceForm: Display;
- 		combinationRule: Form over.
- 	[Sensor anyButtonPressed] whileFalse:
- 		[p := Sensor cursorPoint.
- 		pts := {r1 topLeft. r1 bottomLeft. r1 bottomRight. r1 topRight}
- 			collect: [:pt | pt rotateBy: (p-p0) theta about: r1 center].
- 		ext := (r1 extent*((p-p0) r / 20.0 max: 0.1)) asIntegerPoint.
- 		warp copyQuad: pts toRect: (r1 extent*5-ext//2 extent: ext)]!

Item was removed:
- ----- Method: WarpBlt class>>test12 (in category 'examples') -----
- test12   "Display restoreAfter: [WarpBlt test12]"
- 	"Just like test1, but comparing smooth to non-smooth warps"
- 	| warp pts r1 p0 p ext warp2 |
- 	UIManager default informUser: 'Choose a rectangle with interesting stuff'
- 		during: [r1 := Rectangle originFromUser: 50 at 50.
- 				Sensor waitNoButton].
- 	UIManager default informUser: 'Now click down and up
- and move the mouse around the dot'
- 		during: [p0 := Sensor waitClickButton.
- 				(Form dotOfSize: 8) displayAt: p0].
- 	warp := (self toForm: Display)
- 		cellSize: 2;  "installs a colormap"
- 		clipRect: (0 at 0 extent: r1 extent*5);
- 		sourceForm: Display;
- 		combinationRule: Form over.
- 	warp2 := (self toForm: Display)
- 		clipRect: ((0 at 0 extent: r1 extent*5) translateBy: 250 at 0);
- 		sourceForm: Display;
- 		combinationRule: Form over.
- 	[Sensor anyButtonPressed] whileFalse:
- 		[p := Sensor cursorPoint.
- 		pts := {r1 topLeft. r1 bottomLeft. r1 bottomRight. r1 topRight}
- 			collect: [:pt | pt rotateBy: (p-p0) theta about: r1 center].
- 		ext := (r1 extent*((p-p0) r / 20.0 max: 0.1)) asIntegerPoint.
- 		warp copyQuad: pts toRect: (r1 extent*5-ext//2 extent: ext).
- 		warp2 copyQuad: pts toRect: ((r1 extent*5-ext//2 extent: ext) translateBy: 250 at 0).
- 		]!

Item was removed:
- ----- Method: WarpBlt class>>test3 (in category 'examples') -----
- test3   "Display restoreAfter: [WarpBlt test3]"
- 
- 	"The Squeak Release Mandala - 9/23/96 di"
- 
- 	"Move the mouse near the center of the square.
- 	Up and down affects shrink/grow
- 	Left and right affect rotation angle"
- 	| warp pts p0 box map d p |
- 	box := 100 at 100 extent: 300 at 300.
- 	Display border: (box expandBy: 2) width: 2.
- 
- 	"Make a color map that steps through the color space"
- 	map := (Display depth > 8
- 		ifTrue: ["RGB is a bit messy..."
- 				d := Display depth = 16 ifTrue: [5] ifFalse: [8].
- 				(1 to: 512) collect: [:i | | t |
- 					t := i bitAnd: 511.
- 					((t bitAnd: 16r7) bitShift: d-3)
- 					+ ((t bitAnd: 16r38) bitShift: d-3*2)
- 					+ ((t bitAnd: 16r1C0) bitShift: d-3*3)]]
- 		ifFalse: ["otherwise simple"
- 				1 to: (1 bitShift: Display depth)])
- 			as: Bitmap.
- 	warp := (WarpBlt toForm: Display)
- 		clipRect: box;
- 		sourceForm: Display;
- 		colorMap: map;
- 		combinationRule: Form over.
- 	p0 := box center.
- 	[Sensor anyButtonPressed] whileFalse:
- 		[p := Sensor cursorPoint.
- 		pts := (box insetBy: p y - p0 y) innerCorners
- 			collect: [:pt | pt rotateBy: p x - p0 x / 50.0 about: p0].
- 		warp copyQuad: pts toRect: box]!

Item was removed:
- ----- Method: WarpBlt class>>test4 (in category 'examples') -----
- test4   "Display restoreAfter: [WarpBlt test4]"
- 
- 	"The Squeak Release Mandala - 9/23/96 di
- 	This version does smoothing"
- 
- 	"Move the mouse near the center ofhe square.
- 	Up and dn affects shrink/grow
- 	Left and right affect rotation angle"
- 	| warp pts p0 p box |
- 	box := 100 at 100 extent: 300 at 300.
- 	Display border: (box expandBy: 2) width: 2.
- 
- 	warp := (WarpBlt toForm: Display)
- 		clipRect: box;
- 		sourceForm: Display;
- 		cellSize: 2;  "installs a colormap"
- 		combinationRule: Form over.
- 	p0 := box center.
- 	[Sensor anyButtonPressed] whileFalse:
- 		[p := Sensor cursorPoint.
- 		pts := (box insetBy: p y - p0 y) innerCorners
- 			collect: [:pt | pt rotateBy: p x - p0 x / 50.0 about: p0].
- 		warp copyQuad: pts toRect: box]!

Item was removed:
- ----- Method: WarpBlt class>>test5 (in category 'examples') -----
- test5   "Display restoreAfter: [WarpBlt test5]"
- 	"Demonstrates variable scale and rotate"
- 	| warp pts r1 p0 p |
- 	UIManager default informUser: 'Choose a rectangle with interesting stuff'
- 		during: [r1 := Rectangle fromUser.
- 				Sensor waitNoButton].
- 	UIManager default informUser: 'Now click down and up
- and move the mouse around the dot'
- 		during: [p0 := Sensor waitClickButton.
- 				(Form dotOfSize: 8) displayAt: p0].
- 	warp := (self toForm: Display)
- 		cellSize: 1;
- 		sourceForm: Display;
- 		cellSize: 2;  "installs a colormap"
- 		combinationRule: Form over.
- 	[Sensor anyButtonPressed] whileFalse:
- 		[p := Sensor cursorPoint.
- 		pts := {r1 topLeft. r1 bottomLeft. r1 bottomRight. r1 topRight}
- 			collect: [:pt | pt rotateBy: (p-p0) theta about: r1 center].
- 		warp copyQuad: pts toRect: (r1 translateBy: r1 width at 0)]!

Item was removed:
- ----- Method: WarpBlt class>>toForm: (in category 'initialization') -----
- toForm: destinationForm
- 	"Default cell size is 1 (no pixel smoothing)"
- 	^ (super toForm: destinationForm) cellSize: 1!

Item was removed:
- ----- Method: WarpBlt>>cellSize (in category 'setup') -----
- cellSize
- 	^ cellSize!

Item was removed:
- ----- Method: WarpBlt>>cellSize: (in category 'setup') -----
- cellSize: s
- 	"Set the number of samples used for averaging"
- 	cellSize := s.
- 	cellSize = 1 ifTrue: [^ self].
- 	"Install the colorMap to used for mapping the averaged RGBA 32bit pixels to the
- 	destination depth. Note that we need to install the 32->32 color map explicitly because
- 	the VM will substitute a colorMap derived from sourceForm->destForm mapping which
- 	is just plain wrong for <32 source and 32bit dest depth"
- 	(destForm depth = 32 and: [sourceForm notNil and: [sourceForm depth < 32]])
- 		ifTrue:[colorMap := ColorMap shifts: #(0 0 0 0) masks:#(16rFF0000 16rFF00 16rFF 16rFF000000) colors: nil]
- 		ifFalse:[colorMap := Color colorMapIfNeededFrom: 32 to: destForm depth].
- !

Item was removed:
- ----- Method: WarpBlt>>copyQuad:toRect: (in category 'primitives') -----
- copyQuad: pts toRect: destRect
- 	self sourceQuad: pts destRect: destRect.
- 	self warpBits!

Item was removed:
- ----- Method: WarpBlt>>deltaFrom:to:nSteps: (in category 'primitives') -----
- deltaFrom: x1 to: x2 nSteps: n
- 	"Utility routine for computing Warp increments.
- 	x1 is starting pixel, x2 is ending pixel;  assumes n >= 1"
- 	| fixedPtOne |
- 	fixedPtOne := 16384.  "1.0 in fixed-pt representation"
- 	x2 > x1
- 		ifTrue: [^ x2 - x1 + fixedPtOne // (n+1) + 1]
- 		ifFalse: [x2 = x1 ifTrue: [^ 0].
- 				^ 0 - (x1 - x2 + fixedPtOne // (n+1) + 1)]!

Item was removed:
- ----- Method: WarpBlt>>mixPix:sourceMap:destMap: (in category 'smoothing') -----
- mixPix: pix sourceMap: sourceMap destMap: destMap
- 	"Average the pixels in array pix to produce a destination pixel.
- 	First average the RGB values either from the pixels directly,
- 	or as supplied in the sourceMap.  Then return either the resulting
- 	RGB value directly, or use it to index the destination color map." 
- 	| r g b rgb nPix bitsPerColor d |
- 	nPix := pix size.
- 	r := 0. g := 0. b := 0.
- 	1 to: nPix do:
- 		[:i |   "Sum R, G, B values for each pixel"
- 		rgb := sourceForm depth <= 8
- 				ifTrue: [sourceMap at: (pix at: i) + 1]
- 				ifFalse: [sourceForm depth = 32
- 						ifTrue: [pix at: i]
- 						ifFalse: [self rgbMap: (pix at: i) from: 5 to: 8]].
- 		r := r + ((rgb bitShift: -16) bitAnd: 16rFF).
- 		g := g + ((rgb bitShift: -8) bitAnd: 16rFF).
- 		b := b + ((rgb bitShift: 0) bitAnd: 16rFF)].
- 	destMap == nil
- 		ifTrue: [bitsPerColor := 3.  "just in case eg depth <= 8 and no map"
- 				destForm depth = 16 ifTrue: [bitsPerColor := 5].
- 				destForm depth = 32 ifTrue: [bitsPerColor := 8]]
- 		ifFalse: [destMap size = 512 ifTrue: [bitsPerColor := 3].
- 				destMap size = 4096 ifTrue: [bitsPerColor := 4].
- 				destMap size = 32768 ifTrue: [bitsPerColor := 5]].
- 	d := bitsPerColor - 8.
- 	rgb := ((r // nPix bitShift: d) bitShift: bitsPerColor*2)
- 		+ ((g // nPix bitShift: d) bitShift: bitsPerColor)
- 		+ ((b // nPix bitShift: d) bitShift: 0).
- 	destMap == nil
- 		ifTrue: [^ rgb]
- 		ifFalse: [^ destMap at: rgb+1]!

Item was removed:
- ----- Method: WarpBlt>>rgbMap:from:to: (in category 'smoothing') -----
- rgbMap: sourcePixel from: nBitsIn to: nBitsOut
- 	"NOTE: This code is copied verbatim from BitBltSimulation so that it
- 	may be removed from the system"
- 	"Convert the given pixel value with nBitsIn bits for each color component to a pixel value with nBitsOut bits for each color component. Typical values for nBitsIn/nBitsOut are 3, 5, or 8."
- 	| mask d srcPix destPix |
- 	<inline: true>
- 	(d := nBitsOut - nBitsIn) > 0
- 		ifTrue:
- 			["Expand to more bits by zero-fill"
- 			mask := (1 << nBitsIn) - 1.  "Transfer mask"
- 			srcPix := sourcePixel << d.
- 			mask := mask << d.
- 			destPix := srcPix bitAnd: mask.
- 			mask := mask << nBitsOut.
- 			srcPix := srcPix << d.
- 			^ destPix + (srcPix bitAnd: mask)
- 				 	+ (srcPix << d bitAnd: mask << nBitsOut)]
- 		ifFalse:
- 			["Compress to fewer bits by truncation"
- 			d = 0 ifTrue: [^ sourcePixel].  "no compression"
- 			sourcePixel = 0 ifTrue: [^ sourcePixel].  "always map 0 (transparent) to 0"
- 			d := nBitsIn - nBitsOut.
- 			mask := (1 << nBitsOut) - 1.  "Transfer mask"
- 			srcPix := sourcePixel >> d.
- 			destPix := srcPix bitAnd: mask.
- 			mask := mask << nBitsOut.
- 			srcPix := srcPix >> d.
- 			destPix := destPix + (srcPix bitAnd: mask)
- 					+ (srcPix >> d bitAnd: mask << nBitsOut).
- 			destPix = 0 ifTrue: [^ 1].  "Dont fall into transparent by truncation"
- 			^ destPix]!

Item was removed:
- ----- Method: WarpBlt>>sourceForm:destRect: (in category 'primitives') -----
- sourceForm: srcForm destRect: dstRectangle
- 	"Set up a WarpBlt from the entire source Form to the given destination rectangle."
- 
- 	| w h |
- 	sourceForm := srcForm.
- 	sourceX := sourceY := 0.
- 	destX := dstRectangle left.
- 	destY := dstRectangle top.
- 	width := dstRectangle width.
- 	height := dstRectangle height.
- 	w := 16384 * (srcForm width - 1).
- 	h := 16384 * (srcForm height - 1).
- 	p1x := 0.
- 	p2x := 0.
- 	p3x := w.
- 	p4x := w.
- 	p1y := 0.
- 	p2y := h.
- 	p3y := h.
- 	p4y := 0.
- 	p1z := p2z := p3z := p4z := 16384.  "z-warp ignored for now"
- !

Item was removed:
- ----- Method: WarpBlt>>sourceQuad:destRect: (in category 'primitives') -----
- sourceQuad: pts destRect: aRectangle
- 	| fixedPt1 |
- 	sourceX := sourceY := 0.
- 	self destRect: aRectangle.
- 	fixedPt1 := (pts at: 1) x isInteger ifTrue: [16384] ifFalse: [16384.0].
- 	p1x := (pts at: 1) x * fixedPt1.
- 	p2x := (pts at: 2) x * fixedPt1.
- 	p3x := (pts at: 3) x * fixedPt1.
- 	p4x := (pts at: 4) x * fixedPt1.
- 	p1y := (pts at: 1) y * fixedPt1.
- 	p2y := (pts at: 2) y * fixedPt1.
- 	p3y := (pts at: 3) y * fixedPt1.
- 	p4y := (pts at: 4) y * fixedPt1.
- 	p1z := p2z := p3z := p4z := 16384.  "z-warp ignored for now"
- !

Item was removed:
- ----- Method: WarpBlt>>startFrom:to:offset: (in category 'primitives') -----
- startFrom: x1 to: x2 offset: sumOfDeltas
- 	"Utility routine for computing Warp increments."
- 	x2 >= x1
- 		ifTrue: [^ x1]
- 		ifFalse: [^ x2 - sumOfDeltas]!

Item was removed:
- ----- Method: WarpBlt>>warpBits (in category 'primitives') -----
- warpBits
- 	"Move those pixels!!"
- 
- 	cellSize < 1 ifTrue: [ ^self error: 'cellSize must be >= 1' ].
- 
- 	self warpBitsSmoothing: cellSize
- 		sourceMap: (sourceForm colormapIfNeededForDepth: 32).
- !

Item was removed:
- ----- Method: WarpBlt>>warpBitsSmoothing:sourceMap: (in category 'primitives') -----
- warpBitsSmoothing: n sourceMap: sourceMap
- 	| deltaP12 deltaP43 pA pB deltaPAB sp fixedPtOne poker pix nSteps |
- 	<primitive: 'primitiveWarpBits' module: 'BitBltPlugin' error: ec>
- 
- 	"Check for compressed source, destination or halftone forms"
- 	"Check for object movement during a surface callback, compressed source, destination or halftone forms.
- 	 Simply retry."
- 	(ec == #'object moved'
- 	 or: [(sourceForm isForm and: [sourceForm unhibernate])
- 	 or: [(destForm isForm and: [destForm unhibernate])
- 	 or: [halftoneForm isForm and: [halftoneForm unhibernate]]]]) ifTrue:
- 		[^self warpBitsSmoothing: n sourceMap: sourceMap].
- 
- 	(width < 1) | (height < 1) ifTrue: [^ self].
- 	fixedPtOne := 16384.  "1.0 in fixed-pt representation"
- 	n > 1 ifTrue:
- 		[(destForm depth < 16 and: [colorMap == nil])
- 			ifTrue: ["color map is required to smooth non-RGB dest"
- 					^ self primitiveFailed].
- 		pix := Array new: n*n].
- 
- 	nSteps := height-1 max: 1.
- 	deltaP12 := (self deltaFrom: p1x to: p2x nSteps: nSteps)
- 			@ (self deltaFrom: p1y to: p2y nSteps: nSteps).
- 	pA := (self startFrom: p1x to: p2x offset: nSteps*deltaP12 x)
- 		@ (self startFrom: p1y to: p2y offset: nSteps*deltaP12 y).
- 	deltaP43 := (self deltaFrom: p4x to: p3x nSteps: nSteps)
- 			@ (self deltaFrom: p4y to: p3y nSteps: nSteps).
- 	pB := (self startFrom: p4x to: p3x offset: nSteps*deltaP43 x)
- 		@ (self startFrom: p4y to: p3y offset: nSteps*deltaP43 y).
- 
- 	poker := BitBlt bitPokerToForm: destForm.
- 	poker clipRect: self clipRect.
- 	nSteps := width-1 max: 1.
- 	destY to: destY+height-1 do:
- 		[:y |
- 		deltaPAB := (self deltaFrom: pA x to: pB x nSteps: nSteps)
- 				@ (self deltaFrom: pA y to: pB y nSteps: nSteps).
- 		sp := (self startFrom: pA x to: pB x offset: nSteps*deltaPAB x)
- 			@ (self startFrom: pA y to: pB y offset: nSteps*deltaPAB x).
- 		destX to: destX+width-1 do:
- 			[:x | 
- 			n = 1
- 			ifTrue:
- 				[poker pixelAt: x at y
- 						put: (sourceForm pixelValueAt: sp // fixedPtOne asPoint)]
- 			ifFalse:
- 				[0 to: n-1 do:
- 					[:dx | 0 to: n-1 do:
- 						[:dy |
- 						pix at: dx*n+dy+1 put:
- 								(sourceForm pixelValueAt: sp
- 									+ (deltaPAB*dx//n)
- 									+ (deltaP12*dy//n)
- 										// fixedPtOne asPoint)]].
- 				poker pixelAt: x at y put: (self mixPix: pix
- 											sourceMap: sourceMap
- 											destMap: colorMap)].
- 			sp := sp + deltaPAB].
- 		pA := pA + deltaP12.
- 		pB := pB + deltaP43]!

Item was removed:
- ----- Method: WideString>>scanCharactersFrom:to:with:rightX:font: (in category '*Graphics-Text') -----
- scanCharactersFrom: startIndex to: stopIndex with: aCharacterScanner rightX: rightX  font: aFont
- 	"NB: strongly consider getting almost all these parameters from the scanner"
- 	"Since I'm a wide char string, I know that we have to scan multi-byte characters and handle encodings etc"
- 	| charSet |
- 	startIndex > stopIndex
- 		ifTrue: [^aCharacterScanner handleEndOfRunAt: stopIndex].
- 	charSet := self encodedCharSetAt: startIndex.
- 	^charSet scanMultibyteCharactersFrom: startIndex to: stopIndex in: self with: aCharacterScanner rightX: rightX font: aFont	!

Item was removed:
- ----- Method: WideSymbol>>scanCharactersFrom:to:with:rightX:font: (in category '*Graphics-Text') -----
- scanCharactersFrom: startIndex to: stopIndex with: aCharacterScanner rightX: rightX  font: aFont
- 	"NB: strongly consider getting almost all these parameters from the scanner"
- 	"Since I'm a wide char string, I know that we have to scan multi-byte characters and handle encodings etc"
- 	| charSet |
- 	startIndex > stopIndex
- 		ifTrue: [^aCharacterScanner handleEndOfRunAt: stopIndex].
- 	charSet := self encodedCharSetAt: startIndex.
- 	^charSet scanMultibyteCharactersFrom: startIndex to: stopIndex in: self with: aCharacterScanner rightX: rightX font: aFont	!

Item was removed:
- HostWindowProxy subclass: #Win32WindowProxy
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Graphics-External-Ffenestri'!

Item was removed:
- ----- Method: Win32WindowProxy class>>isActiveHostWindowProxyClass (in category 'as yet unclassified') -----
- isActiveHostWindowProxyClass
- "Am I active?"
- 	^Smalltalk platformName  = 'Win32'!

Item was removed:
- ----- Method: Win32WindowProxy>>defaultWindowType (in category 'window decorations') -----
- defaultWindowType!

Item was removed:
- ImageReadWriter subclass: #XBMReadWriter
- 	instanceVariableNames: 'width height'
- 	classVariableNames: 'Flipbits'
- 	poolDictionaries: ''
- 	category: 'Graphics-Files'!

Item was removed:
- ----- Method: XBMReadWriter class>>initialize (in category 'class initialization') -----
- initialize
- 	"XBMReadWriter initialize"
- 	Flipbits := (0 to: 255) collect:
- 		[:n |  "Compute the bit-reversal of the 8-bit value, n"
- 		| flippedByte |
- 		flippedByte := 0.
- 		0 to: 7 do: 
- 			[:i | 
- 			flippedByte := flippedByte bitOr: ((n >> i bitAnd: 1) << (7-i))].
- 			flippedByte]!

Item was removed:
- ----- Method: XBMReadWriter class>>typicalFileExtensions (in category 'class initialization') -----
- typicalFileExtensions
- 	"Answer a collection of file extensions (lowercase) which files that I can read might commonly have"
- 	^#('xbm')!

Item was removed:
- ----- Method: XBMReadWriter>>nextImage (in category 'accessing') -----
- nextImage
- 	"Read in the next xbm image from the stream."
- 	| form long incount chunks byteWidth pad fourway outcount total |
- 	stream reset.
- 	stream ascii.
- 	self readHeader.
- 	form := ColorForm extent: width at height depth: 1.
- 	incount := 0.	outcount :=1.
- 	chunks := Array new: 4.	byteWidth := width + 7 // 8.
- 	total := byteWidth * height.
- 	byteWidth > 4
- 		ifTrue: [ pad := byteWidth \\ 4]
- 		ifFalse: [ pad := 4 - byteWidth ].
- 	fourway := 0.
- 	[(incount = total)] whileFalse: [
- 		incount := incount + 1.
- 		fourway := fourway + 1.
- 		chunks at: fourway put: (Flipbits at: ((self parseByteValue) +1)).
- 		(pad > 0 and: [(incount \\ byteWidth) = 0]) ifTrue: [
- 			1 to: pad do:
- 				[:q |	
-   			fourway := fourway + 1.	
- 			chunks at: fourway put: 0]
- 		].
- 		fourway = 4 ifTrue: [
- 			long := Integer
- 				byte1: (chunks at: 4)
- 				byte2: (chunks at: 3)
- 				byte3: (chunks at: 2)
- 				byte4: (chunks at: 1).
- 			(form bits) at: outcount put: long.
- 			fourway := 0.
- 			outcount := outcount + 1].
- 		].
- 	 ^ form !

Item was removed:
- ----- Method: XBMReadWriter>>parseByteValue (in category 'private') -----
- parseByteValue
- 	"skip over separators and return next bytevalue parsed as a C language number:
- 		0ddd is an octal digit.
- 		0xddd is a hex digit.
- 		ddd is decimal."
- 	| source mybase |
- 	stream skipSeparators.
- 	source := stream upToAnyOf: CharacterSet separators.
- 	source = '0' ifTrue: [^0]..
- 	mybase := 10. "Base 10 default"
- 	source := source asUppercase readStream.
- 	(source peekFor: $0) ifTrue: [
- 		mybase := 8. "Octal or Hex, say its Octal unless overridden."
- 		(source peekFor: $X) ifTrue: [
- 			mybase := 16. "Ah.  It's Hex."
- 			]
- 		].
- 	^ Integer readFrom: source base: mybase!

Item was removed:
- ----- Method: XBMReadWriter>>readHeader (in category 'private') -----
- readHeader
- 	"Set width and height, and position stream at start of bytes"
- 	| number setwidth setheight fieldName |
- 	setwidth := setheight := false.
- 		[((stream atEnd) or: [setwidth and: [setheight]])]
- 		whileFalse: [
- 	  	self skipCComments.
- 		(stream nextMatchAll: '#define ') ifFalse: [^ false].
- 		(stream skipTo: $_) ifFalse: [^ false].
- 		fieldName := String streamContents:
- 			[:source |
- 			[(stream atEnd) or: [ stream peek isSeparator ]]
- 				whileFalse: [ source nextPut: stream next]].
- 	  	(fieldName = 'width') ifTrue: [
- 			stream skipSeparators.
- 			number := Integer readFrom: stream.
- 			(number > 0) ifTrue: [setwidth := true].
- 	  		width := number.].
- 		(fieldName = 'height') ifTrue: [
- 			stream skipSeparators.
- 			number := Integer readFrom: stream.
- 			(number > 0) ifTrue: [setheight := true].
- 			height := number.
- 			].
- 		].
- 	(setwidth & setheight) ifFalse: [^ false].
- 	^ stream skipTo: ${
- !

Item was removed:
- ----- Method: XBMReadWriter>>skipCComments (in category 'private') -----
- skipCComments
- 	[ stream skipSeparators.
- 	stream peekFor: $/ ] whileTrue: [
- 		stream next.		"skip next *"
- 		[ (stream skipTo: $*) ifFalse: [ ^false ].
- 			stream peekFor: $/ ] whileFalse ]!

Item was removed:
- ----- Method: XBMReadWriter>>understandsImageFormat (in category 'accessing') -----
- understandsImageFormat
- 	"Test to see if the image stream format is understood by this decoder.	This should be implemented in each subclass of ImageReadWriter so that	a proper decoder can be selected without ImageReadWriter having to know about all possible image file types."
- 	| first |
- 	stream ascii.
- 	self skipCComments.
- 	first := (stream next: 7) asString.
- 	stream binary.
- 	^ (first = '#define')!

Item was removed:
- (PackageInfo named: 'Graphics') postscript: '"Compute the correct tab widths per style using its current default font."
- TextStyle allInstancesDo: [:ea | ea initializeTabsArray].'!



More information about the Squeak-dev mailing list