'From Squeak2.9alpha of 8 July 2000 [latest update: #2447] on 26 August 2000 at 12:03:46 pm'! !AbstractFont commentStamp: 'hg 6/16/2000 13:18' prior: 0! AbstractFont defines the generic interface that all fonts need to implement to work properly with DisplayScanner for drawing to the screen (etc.).! Object subclass: #OutlineFont instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Text'! StrikeFont subclass: #AntialiasedFont instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Text'! !AntialiasedFont commentStamp: '' prior: 0! Implements antialiased grayscale bitmap fonts as a subclass of StrikeFont, and thereby works together with existing text functionality all the way down to the primitives & BitBlt level, including paragraph composition and general text editing. This is done at virtually no loss of speed compared to plain StrikeFonts, once the AntialiasedFont has been generated (although using more memory -- which means storing Forms of greater bit depths than 1). This however means that there is no support for fractional character widths here. Most of this class deals with setting up characters and rendering their bitmaps from an OutlineFont. Note that an AntialiasedFont, once generated, may be used without having either the font nor the code that was used to generate it. Just file it out, move it to another image, and go!! ! ]style[(622 11 187)f3,f3LOutlineFont Comment;,f3! AntialiasedFont subclass: #SubPixelRenderedFont instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Text'! !SubPixelRenderedFont commentStamp: '' prior: 0! Implements a refinement of antialiasing known as sub-pixel rendering, yielding much better perceived resolution on color LCD screens (resolution is increased 3 x horisontally). This is done by applying image processing, which is quite fast even though it is written in 100% Smalltalk (with heavy use of BitBlt, and one WarpBlt). See implementation in the 'sub-pixel rendering' method category of class Form. Also try Form>>subPixelInverse on *small* patches of rendered type to see what is done. *Sub*-pixel refers to that you take the 3 sub-elements that make up an LCD-screen pixel, and manipulate each of these 3 individually, as if they were three gray-scale pixels. RR GG BB \ RR GG BB | -- Each color LCD pixel has 3 elements/"sub-pixels" RR GG BB | -- with R,G and B colors lined up horizontally. RR GG BB / Ordinary antialiasing uses gray levels instead of just black & white, thereby using grayscale to create a perceived increase in B&W resolution. (Like Balloon, WarpBlt, etc.) *Sub-pixel* antialiasing manipulates the intensity levels (gray = B&W intensity) of each R, G, and B sub-element separately. (This is why you only get 3x horizontally.) See http://www.grc.com/ctwhat.htm for a better but still simple explanation.! ]style[(402 4 773 29 43)f3,f3LForm Definition;,f3,f3Rhttp://www.grc.com/ctwhat.htm;,f3! OutlineFont subclass: #TTFontDescription instanceVariableNames: 'glyphTable glyphs kernPairs copyright familyName fullName subfamilyName uniqueName versionName postscriptName trademark bounds unitsPerEm ascender descender lineGap ' classVariableNames: '' poolDictionaries: '' category: 'Balloon-TrueType Fonts'! !AbstractFont methodsFor: 'display parameters' stamp: 'hg 6/17/2000 16:02'! paintDisplayRule "This is the Blt rule used to draw an instance of this font with color, transparency, etc. " ^Form paint! ! !AbstractFont methodsFor: 'display parameters' stamp: 'hg 6/16/2000 17:42'! setupDisplayTarget: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor "adjust the display context's Blt parameters to render this font properly" ^self subclassResponsibility! ! !AbstractFont methodsFor: 'display parameters' stamp: 'hg 6/17/2000 16:03'! simpleDisplayRule "This is the default Blt rule used to draw an instance of this font in plain b&w" ^Form over! ! !BitBlt methodsFor: 'private' stamp: 'hg 6/17/2000 17:16'! copySim: destRectangle from: sourcePt in: srcForm rule: aRule | destOrigin | sourceForm _ srcForm. destOrigin _ destRectangle origin. destX _ destOrigin x. destY _ destOrigin y. sourceX _ sourcePt x. sourceY _ sourcePt y. width _ destRectangle width. height _ destRectangle height. combinationRule _ aRule. self copyBitsSimulated! ! !BitBlt class methodsFor: 'benchmarks' stamp: 'hg 6/16/2000 20:49'! aaBenchmark "BitBlt aaBenchmark" "Run a benchmark on different combinations rules, as used for antialiased font rendering. hg 6/16/2000 20:39" | bb source dest destRect log t | log _ WriteStream on: String new. destRect _ 0@0 extent: 600@600. #("1 2 4" 8 16 32) do:[:destDepth| Transcript cr;crtab: 2; nextPutAll: 'paint';tab; nextPutAll: 'rgbMin'; tab; nextPutAll: 'rgbMul'. log cr;crtab: 2; nextPutAll: 'paint';tab; nextPutAll: 'rgbMin'; tab; nextPutAll: 'rgbMul'. dest _ nil. dest _ Form extent: destRect extent depth: destDepth. #("1 2 4" 8 16 32) do:[:sourceDepth| Transcript cr; show: sourceDepth printString, ' => ', destDepth printString. log cr; nextPutAll: sourceDepth printString, ' => ', destDepth printString. "Form paint/Form rgbMin / Form rgbMul" #( 25 28 35 ) do:[:rule| 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 colormapIfNeededForDepth: dest depth). bb combinationRule: rule. "Measure speed of copyBits" t _ Time millisecondsToRun:[bb copyBits]. Transcript tab; nextPutAll: t printString. log tab; nextPutAll: t printString. bb sourceForm: source destRect: source boundingBox. ]. ]. ]. Transcript show: ' ';cr. ^log contents! ! !BitBltSimulation methodsFor: 'translation support' stamp: 'hg 6/17/2000 17:04'! initBBOpTable self cCode: 'opTable[0+1] = (int)clearWordwith'. self cCode: 'opTable[1+1] = (int)bitAndwith'. self cCode: 'opTable[2+1] = (int)bitAndInvertwith'. self cCode: 'opTable[3+1] = (int)sourceWordwith'. self cCode: 'opTable[4+1] = (int)bitInvertAndwith'. self cCode: 'opTable[5+1] = (int)destinationWordwith'. self cCode: 'opTable[6+1] = (int)bitXorwith'. self cCode: 'opTable[7+1] = (int)bitOrwith'. self cCode: 'opTable[8+1] = (int)bitInvertAndInvertwith'. self cCode: 'opTable[9+1] = (int)bitInvertXorwith'. self cCode: 'opTable[10+1] = (int)bitInvertDestinationwith'. self cCode: 'opTable[11+1] = (int)bitOrInvertwith'. self cCode: 'opTable[12+1] = (int)bitInvertSourcewith'. self cCode: 'opTable[13+1] = (int)bitInvertOrwith'. self cCode: 'opTable[14+1] = (int)bitInvertOrInvertwith'. self cCode: 'opTable[15+1] = (int)destinationWordwith'. self cCode: 'opTable[16+1] = (int)destinationWordwith'. self cCode: 'opTable[17+1] = (int)destinationWordwith'. self cCode: 'opTable[18+1] = (int)addWordwith'. self cCode: 'opTable[19+1] = (int)subWordwith'. self cCode: 'opTable[20+1] = (int)rgbAddwith'. self cCode: 'opTable[21+1] = (int)rgbSubwith'. self cCode: 'opTable[22+1] = (int)OLDrgbDiffwith'. self cCode: 'opTable[23+1] = (int)OLDtallyIntoMapwith'. self cCode: 'opTable[24+1] = (int)alphaBlendwith'. self cCode: 'opTable[25+1] = (int)pixPaintwith'. self cCode: 'opTable[26+1] = (int)pixMaskwith'. self cCode: 'opTable[27+1] = (int)rgbMaxwith'. self cCode: 'opTable[28+1] = (int)rgbMinwith'. self cCode: 'opTable[29+1] = (int)rgbMinInvertwith'. self cCode: 'opTable[30+1] = (int)alphaBlendConstwith'. self cCode: 'opTable[31+1] = (int)alphaPaintConstwith'. self cCode: 'opTable[32+1] = (int)rgbDiffwith'. self cCode: 'opTable[33+1] = (int)tallyIntoMapwith'. self cCode: 'opTable[34+1] = (int)alphaBlendScaledwith'. self cCode: 'opTable[35+1] = (int)rgbMulwith'. self cCode: 'opTable[36+1] = (int)rgbMulTwicewith'.! ! !BitBltSimulation methodsFor: 'AA type combination rules' stamp: 'hg 6/17/2000 18:41'! alphaVersion: sourceWord with: destinationWord "this mode multiplies a foreground color RGB value (in halftoneForm) with the source's gray level value, and then multiplies the result with dest color" | intensity | self inline: false. intensity _ (sourceWord bitAnd: 255) + ((sourceWord >> 8 bitAnd: 255) * 2) + (sourceWord >> 16 bitAnd: 255). sourceAlpha _ 255 - (intensity>>1bitAnd: 255). " same as // 4" ^self alphaPaintConst: (halftoneForm at: 1) with: destinationWord! ! !BitBltSimulation methodsFor: 'AA type combination rules' stamp: 'hg 6/17/2000 19:45'! max: word1 with: word2 ^word1>word2 ifTrue: [word1] ifFalse: [word2]! ! !BitBltSimulation methodsFor: 'AA type combination rules' stamp: 'hg 5/10/2000 17:37'! partitionedMul1: word1 with: word2 nBits: nBits nPartitions: nParts "Multiply word1 with word2 as nParts partitions of nBits each. This is useful for packed pixels, or packed colors" | sMask product result dMask | sMask _ maskTable at: nBits. "partition mask starts at the right" dMask _ sMask << nBits. result _ (((word1 bitAnd: sMask)+1) * ((word2 bitAnd: sMask)+1) - 1 bitAnd: dMask) >> nBits. "optimized first step" nBits to: nBits * (nParts-1) do: [:ofs | product _ (((word1>>ofs bitAnd: sMask)+1) * ((word2>>ofs bitAnd: sMask)+1) - 1 bitAnd: dMask). result _ result bitOr: (product bitAnd: dMask) << (ofs-nBits)]. ^ result ! ! !BitBltSimulation methodsFor: 'AA type combination rules' stamp: 'hg 5/10/2000 17:55'! partitionedMul: word1 with: word2 nBits: nBits nPartitions: nParts "Multiply word1 with word2 as nParts partitions of nBits each. This is useful for packed pixels, or packed colors. Loop removed, I can't believe the other doesn't work!!" | sMask product result dMask | sMask _ maskTable at: nBits. "partition mask starts at the right" dMask _ sMask << nBits. result _ (((word1 bitAnd: sMask)+1) * ((word2 bitAnd: sMask)+1) - 1 bitAnd: dMask) >> nBits. "optimized first step" product _ (((word1>>nBits bitAnd: sMask)+1) * ((word2>>nBits bitAnd: sMask)+1) - 1 bitAnd: dMask). result _ result bitOr: (product bitAnd: dMask)<< 0. product _ (((word1>>(2*nBits) bitAnd: sMask)+1) * ((word2>>(2*nBits) bitAnd: sMask)+1) - 1 bitAnd: dMask). result _ result bitOr: (product bitAnd: dMask) << (nBits). ^ result ! ! !BitBltSimulation methodsFor: 'AA type combination rules' stamp: 'hg 6/16/2000 18:12'! rgbMul1: sourceWord with: destinationWord self inline: false. destPixSize < 16 ifTrue: ["Mul each pixel separately" ^ self partitionedMul1: sourceWord with: destinationWord nBits: destPixSize nPartitions: pixPerWord]. destPixSize = 16 ifTrue: ["Mul RGB components of each pixel separately" ^ (self partitionedMul1: sourceWord with: destinationWord nBits: 5 nPartitions: 3) + ((self partitionedMul1: sourceWord>>16 with: destinationWord>>16 nBits: 5 nPartitions: 3) << 16)] ifFalse: ["Mul RGB components of the pixel separately" ^ self partitionedMul1: sourceWord with: destinationWord nBits: 8 nPartitions: 3]! ! !BitBltSimulation methodsFor: 'AA type combination rules' stamp: 'hg 8/24/2000 14:41'! rgbMul: sourceWord with: destinationWord self inline: false. destPixSize < 16 ifTrue: ["Mul each pixel separately" ^ self partitionedMul: sourceWord with: destinationWord nBits: destPixSize nPartitions: pixPerWord]. destPixSize = 16 ifTrue: ["Mul RGB components of each pixel separately" ^ (self partitionedMul: sourceWord with: destinationWord nBits: 5 nPartitions: 3) + ((self partitionedMul: sourceWord>>16 with: destinationWord>>16 nBits: 5 nPartitions: 3) << 16)] ifFalse: ["Mul RGB components of the pixel separately" ^ self partitionedMul: sourceWord with: destinationWord nBits: 8 nPartitions: 3] " | scanner | Display repaintMorphicDisplay. scanner _ DisplayScanner quickPrintOn: Display. MessageTally time: [0 to: 760 by: 4 do: [:y |scanner drawString: 'qwrepoiuasfd=)(/&()=#!!�lkjzxv.,mn124+09857907QROIYTOAFDJZXNBNB,M-.,Mqwrepoiuasfd=)(/&()=#!!�lkjzxv.,mn124+09857907QROIYTOAFDJZXNBNB,M-.,M1234124356785678' at: 0@y]]. "! ! !BitBltSimulation methodsFor: 'AA type combination rules' stamp: 'hg 6/17/2000 20:06'! rgbMulTwice: sourceWord with: destinationWord "this mode multiplies a foreground color RGB value (in halftoneForm) with the source's gray level value, and then multiplies the result with dest color [Sensor anyButtonPressed] whileFalse: []. (BitBlt new setDestForm: Display) fillColor: Color red; copySim:( Sensor cursorPoint extent: originalForm extent) from: 0@0 in: originalForm rule: 36" | val intensity | self inline: false. val _ self rgbSub: sourceWord with: (self rgbSub: AllOnes with: (halftoneForm at: 1)). intensity _ (val bitAnd: 255) + (val >> 8 bitAnd: 255) + (val >> 16 bitAnd: 255). sourceAlpha _ 255 - (intensity//3 bitAnd: 255). " same as // 4" ^self alphaPaintConst: (halftoneForm at: 1) with: destinationWord! ! !BitBltSimulation methodsFor: 'AA type combination rules' stamp: 'hg 6/17/2000 19:27'! rgbPaint: sourceWord with: destinationWord "this mode alpha blends the fill color onto the background with the sourceWord's intensity level as alpha, where the intensity is computed as R + 2G + B" | val intensity | self inline: false. "the fill color has already been applied to background, remove it" val _ self rgbSub: (halftoneForm at: 1) with: (self rgbSub: AllOnes with: sourceWord). intensity _ (val bitAnd: 255) + (val >> 8 bitAnd: 255) + (val >> 16 bitAnd: 255). sourceAlpha _ 255 - (intensity*2//3). ^self alphaPaintConst: (halftoneForm at: 1) with: destinationWord! ! !BitBltSimulation class methodsFor: 'initialization' stamp: 'hg 6/17/2000 17:01'! initializeRuleTable "BitBltSimulation initializeRuleTable" "**WARNING** You MUST change initBBOpTable if you change this" OpTable _ #( "0" clearWord:with: "1" bitAnd:with: "2" bitAndInvert:with: "3" sourceWord:with: "4" bitInvertAnd:with: "5" destinationWord:with: "6" bitXor:with: "7" bitOr:with: "8" bitInvertAndInvert:with: "9" bitInvertXor:with: "10" bitInvertDestination:with: "11" bitOrInvert:with: "12" bitInvertSource:with: "13" bitInvertOr:with: "14" bitInvertOrInvert:with: "15" destinationWord:with: "16" destinationWord:with: "unused - was old paint" "17" destinationWord:with: "unused - was old mask" "18" addWord:with: "19" subWord:with: "20" rgbAdd:with: "21" rgbSub:with: "22" OLDrgbDiff:with: "23" OLDtallyIntoMap:with: "24" alphaBlend:with: "25" pixPaint:with: "26" pixMask:with: "27" rgbMax:with: "28" rgbMin:with: "29" rgbMinInvert:with: "30" alphaBlendConst:with: "31" alphaPaintConst:with: "32" rgbDiff:with: "33" tallyIntoMap:with: "34" alphaBlendScaled:with: "35" rgbMul:with: "36" rgbMulTwice:with: ). OpTableSize _ OpTable size + 1. "0-origin indexing" ! ! !BitBltSimulation class methodsFor: 'system simulation' stamp: 'hg 6/17/2000 17:12'! copyBitsFrom: aBitBlt "Simulate the copyBits primitive" | proxy bb | proxy _ InterpreterProxy new. proxy loadStackFrom: thisContext sender. bb _ self simulatorClass new. bb setInterpreter: proxy. proxy success: (bb loadBitBltFrom: aBitBlt). bb copyBits. proxy failed ifFalse:[ proxy showDisplayBits: aBitBlt destForm Left: bb affectedLeft Top: bb affectedTop Right: bb affectedRight Bottom: bb affectedBottom]. ^proxy stackValue: 0! ! !BitBltSimulator methodsFor: 'as yet unclassified' stamp: 'hg 6/17/2000 17:11'! initBBOpTable opTable _ OpTable. maskTable _ Array new: 32. #(1 2 4 8 16 32) do:[:i| maskTable at: i put: (1 << i)-1]. self initializeDitherTables. warpBitShiftTable _ CArrayAccessor on: (Array new: 32).! ! !BitBltSimulator class methodsFor: 'instance creation' stamp: 'hg 6/17/2000 17:11'! new ^super new initBBOpTable! ! !DisplayScanner methodsFor: 'private' stamp: 'hg 6/16/2000 14:41'! initializeFromParagraph: aParagraph clippedBy: clippingRectangle super initializeFromParagraph: aParagraph clippedBy: clippingRectangle. bitBlt _ BitBlt current toForm: aParagraph destinationForm. bitBlt fillColor: aParagraph fillColor. "sets halftoneForm" bitBlt combinationRule: aParagraph rule. bitBlt clipRect: clippingRectangle. ! ! !DisplayScanner methodsFor: 'private' stamp: 'hg 6/16/2000 17:52'! text: t textStyle: ts foreground: foreColor background: backColor fillBlt: blt ignoreColorChanges: shadowMode text _ t. textStyle _ ts. foregroundColor _ paragraphColor _ foreColor. (backgroundColor _ backColor) isTransparent ifFalse: [fillBlt _ blt. fillBlt fillColor: backgroundColor]. ignoreColorChanges _ shadowMode. textStyle defaultFont setupDisplayTarget: blt foregroundColor: foreColor backgroundColor: backColor.! ! !DisplayScanner methodsFor: 'quick print' stamp: 'hg 6/16/2000 17:44'! quickPrintOn: aForm box: aRectangle font: aStrikeFont color: textColor | | "Initialize myself." bitBlt _ BitBlt current toForm: aForm. backgroundColor _ Color transparent. paragraphColor _ textColor. font _ aStrikeFont ifNil: [TextStyle defaultFont]. emphasisCode _ 0. kern _ 0. indentationLevel _ 0. self setFont. font setupDisplayTarget: bitBlt foregroundColor: textColor backgroundColor: backgroundColor. bitBlt clipRect: aRectangle. ! ! !DisplayScanner class methodsFor: 'examples' stamp: 'hg 6/16/2000 16:05'! example "This will quickly print all the numbers from 1 to 100 on the display, and then answer the default width and height of the string 'hello world'." "DisplayScanner example" | scanner | scanner _ self quickPrintOn: Display. 0 to: 99 do: [: i | scanner drawString: i printString at: (i//10*20) @ (i\\10*12) ]. ^ (scanner stringWidth: 'hello world') @ (scanner lineHeight)! ! !DisplayText methodsFor: 'displaying' stamp: 'hg 6/17/2000 16:05'! displayOn: aDisplayMedium at: aDisplayPoint clippingBox: clipRectangle rule: ruleInteger fillColor: aForm "Refer to the comment in DisplayObject|displayOn:at:clippingBox:rule:mask:." self form displayOn: aDisplayMedium at: aDisplayPoint + offset clippingBox: clipRectangle rule: ((ruleInteger = Form over and: [backColor isTransparent]) ifTrue: [textStyle first paintDisplayRule] ifFalse: [ruleInteger]) fillColor: aForm! ! !DisplayText methodsFor: 'converting' stamp: 'hg 6/17/2000 16:05'! asParagraph "Answer a Paragraph whose text and style are identical to that of the receiver." | para | para _ Paragraph withText: text style: textStyle. para foregroundColor: foreColor backgroundColor: backColor. backColor isTransparent ifTrue: [para rule: textStyle defaultFont paintDisplayRule]. ^ para! ! !DisplayTransform methodsFor: 'composing'! composedWith: aTransform "Return a new transform that has the effect of transforming points first by the receiver and then by the argument." ^ self composedWithLocal: aTransform! ! !FXBltSimulation methodsFor: 'initialize' stamp: 'hg 6/18/2000 14:13'! initBBOpTable self cCode: 'opTable[0+1] = (int)clearWordwith'. self cCode: 'opTable[1+1] = (int)bitAndwith'. self cCode: 'opTable[2+1] = (int)bitAndInvertwith'. self cCode: 'opTable[3+1] = (int)sourceWordwith'. self cCode: 'opTable[4+1] = (int)bitInvertAndwith'. self cCode: 'opTable[5+1] = (int)destinationWordwith'. self cCode: 'opTable[6+1] = (int)bitXorwith'. self cCode: 'opTable[7+1] = (int)bitOrwith'. self cCode: 'opTable[8+1] = (int)bitInvertAndInvertwith'. self cCode: 'opTable[9+1] = (int)bitInvertXorwith'. self cCode: 'opTable[10+1] = (int)bitInvertDestinationwith'. self cCode: 'opTable[11+1] = (int)bitOrInvertwith'. self cCode: 'opTable[12+1] = (int)bitInvertSourcewith'. self cCode: 'opTable[13+1] = (int)bitInvertOrwith'. self cCode: 'opTable[14+1] = (int)bitInvertOrInvertwith'. self cCode: 'opTable[15+1] = (int)destinationWordwith'. self cCode: 'opTable[16+1] = (int)destinationWordwith'. self cCode: 'opTable[17+1] = (int)destinationWordwith'. self cCode: 'opTable[18+1] = (int)addWordwith'. self cCode: 'opTable[19+1] = (int)subWordwith'. self cCode: 'opTable[20+1] = (int)rgbAddwith'. self cCode: 'opTable[21+1] = (int)rgbSubwith'. self cCode: 'opTable[22+1] = (int)OLDrgbDiffwith'. self cCode: 'opTable[23+1] = (int)OLDtallyIntoMapwith'. self cCode: 'opTable[24+1] = (int)alphaBlendwith'. self cCode: 'opTable[25+1] = (int)pixPaintwith'. self cCode: 'opTable[26+1] = (int)pixMaskwith'. self cCode: 'opTable[27+1] = (int)rgbMaxwith'. self cCode: 'opTable[28+1] = (int)rgbMinwith'. self cCode: 'opTable[29+1] = (int)rgbMinInvertwith'. self cCode: 'opTable[30+1] = (int)alphaBlendConstwith'. self cCode: 'opTable[31+1] = (int)alphaPaintConstwith'. self cCode: 'opTable[32+1] = (int)rgbDiffwith'. self cCode: 'opTable[33+1] = (int)tallyIntoMapwith'. self cCode: 'opTable[34+1] = (int)alphaBlendScaledwith'. self cCode: 'opTable[35+1] = (int)srcPaintwith'. self cCode: 'opTable[36+1] = (int)dstPaintwith'. self cCode: 'opTable[37+1] = (int)rgbMulwith'. ! ! !FXBltSimulation methodsFor: 'AA type combination rules' stamp: 'hg 6/18/2000 14:08'! partitionedMul: word1 with: word2 nBits: nBits nPartitions: nParts "Multiply word1 with word2 as nParts partitions of nBits each. This is useful for packed pixels, or packed colors. Loop removed, I can't believe the other doesn't work!!" | sMask product result dMask | sMask _ maskTable at: nBits. "partition mask starts at the right" dMask _ sMask << nBits. result _ (((word1 bitAnd: sMask)+1) * ((word2 bitAnd: sMask)+1) - 1 bitAnd: dMask) >> nBits. "optimized first step" product _ (((word1>>nBits bitAnd: sMask)+1) * ((word2>>nBits bitAnd: sMask)+1) - 1 bitAnd: dMask). result _ result bitOr: (product bitAnd: dMask)<< 0. product _ (((word1>>(2*nBits) bitAnd: sMask)+1) * ((word2>>(2*nBits) bitAnd: sMask)+1) - 1 bitAnd: dMask). result _ result bitOr: (product bitAnd: dMask) << (nBits). ^ result ! ! !FXBltSimulation methodsFor: 'AA type combination rules' stamp: 'hg 6/18/2000 14:10'! rgbMul: sourceWord with: destinationWord self inline: false. pixelDepth < 16 ifTrue: ["Mul each pixel separately" ^ self partitionedMul: sourceWord with: destinationWord nBits: pixelDepth nPartitions: destPPW]. pixelDepth = 16 ifTrue: ["Mul RGB components of each pixel separately" ^ (self partitionedMul: sourceWord with: destinationWord nBits: 5 nPartitions: 3) + ((self partitionedMul: sourceWord>>16 with: destinationWord>>16 nBits: 5 nPartitions: 3) << 16)] ifFalse: ["Mul RGB components of the pixel separately" ^ self partitionedMul: sourceWord with: destinationWord nBits: 8 nPartitions: 3]! ! !FXBltSimulation class methodsFor: 'initialization' stamp: 'hg 6/18/2000 14:13'! initializeRuleTable "FXBltSimulation initializeRuleTable" "**WARNING** You MUST change initBBOpTable if you change this" OpTable _ #( "0" clearWord:with: "1" bitAnd:with: "2" bitAndInvert:with: "3" sourceWord:with: "4" bitInvertAnd:with: "5" destinationWord:with: "6" bitXor:with: "7" bitOr:with: "8" bitInvertAndInvert:with: "9" bitInvertXor:with: "10" bitInvertDestination:with: "11" bitOrInvert:with: "12" bitInvertSource:with: "13" bitInvertOr:with: "14" bitInvertOrInvert:with: "15" destinationWord:with: "16" destinationWord:with: "unused - was old paint" "17" destinationWord:with: "unused - was old mask" "18" addWord:with: "19" subWord:with: "20" rgbAdd:with: "21" rgbSub:with: "22" OLDrgbDiff:with: "23" OLDtallyIntoMap:with: "24" alphaBlend:with: "25" pixPaint:with: "26" pixMask:with: "27" rgbMax:with: "28" rgbMin:with: "29" rgbMinInvert:with: "30" alphaBlendConst:with: "31" alphaPaintConst:with: "32" rgbDiff:with: "33" tallyIntoMap:with: "34" alphaBlendScaled:with: "35" srcPaint:with: "36" dstPaint:with: "37" rgbMul:with: ). OpTableSize _ OpTable size + 1. "0-origin indexing" ! ! !FileList methodsFor: 'file list menu' stamp: 'hg 8/6/2000 20:42'! itemsForFileEnding: suffix | services | services _ OrderedCollection new. self fileReaders do: [:reader | reader ifNotNil: [services addAll: (reader fileReaderServicesForSuffix: suffix)]]. ^services, (self myServicesForFileEnding: suffix). ! ! !Form methodsFor: 'sub-pixel' stamp: 'hg 3/4/2000 19:03'! balanceInNsteps: n "This is the color balancing algorithm that removes color artifacts due to manipulating individual R, G, and B elements. NB: destructive for memory conservation. uses subRgb. hg 1/5/2000 09:43" | intensityDelta sourceForm | self fill: self boundingBox rule: Form blend fillColor: (Color white alpha: 1 - (1/(n+1))). sourceForm _ self deepCopy reverse. 1 to: n do: [:step | intensityDelta _ 1/(n + 2 - step). sourceForm fadeTo: Color black byRatio: intensityDelta. self copyBitsSubRgb: sourceForm at: (0 - step)@ 0; copyBitsSubRgb: sourceForm at: (0 + step)@ 0]. ^ self ! ! !Form methodsFor: 'sub-pixel' stamp: 'hg 3/4/2000 19:04'! copyBitsSubRgb: sourceForm at: destOrigin "Make up a BitBlt table and copy the bits with rule 21 (subRgb). Could be sped up by posing as 8 bits deep and doing a regular sub." self copyBits: sourceForm boundingBox from: sourceForm at: destOrigin clippingBox: self boundingBox rule: Form rgbSub fillColor: nil. ! ! !Form methodsFor: 'sub-pixel' stamp: 'hg 1/5/2000 16:09'! fadeTo: color byRatio: ratio self fill: self boundingBox rule: Form blend fillColor: (color alpha: ratio) ! ! !Form methodsFor: 'sub-pixel' stamp: 'hg 3/4/2000 19:06'! mergeToSubPixels "derived from Andreas Raab's suggestion of using 8bit bitblt on 32bit pixels for merging and shrinking the width in the same step by taking every third byte. hg 1/4/2000 16:44" | merged | self poseAsDepth: 8. merged _ self magnify: self boundingBox by: 1/3.0 @ 1.0. ^merged poseAsDepth: 32. "If you take every third byte (ie. shrinking to 1/3), you get: ArgB arGb aRgb ArgB -> ABGR ABGR etc. instead of ARGB ARGB ..., but since B=G=R for each of these, BGR is equivalent to if RGB were extracted instead!! Note how ArgB picks both alpha and the first color component from the first of every three pixels. The marvels of plain arithmetic!!" ! ! !Form methodsFor: 'sub-pixel' stamp: 'hg 1/4/2000 19:25'! poseAsDepth: d "set up my instvars to look like I have a different depth. hg 1/4/2000 19:14" | newWidth ratio | ratio _ depth/d. newWidth _ width * ratio. newWidth truncated ~= newWidth ifTrue: [self error: 'new width is not an integer']. width _ newWidth truncated. depth _ d ! ! !Form methodsFor: 'sub-pixel' stamp: 'hg 2/23/2000 10:48'! sourceForSubpixelMerge " A Form to be 'sub-pixelled' should be destructible, 32 bits deep and have a width of a multiple of 3. If already so, it needn't be sent this message, which serves to ensure these conditions. hg 1/5/2000 15:49" | destructibleSource | destructibleSource _ Form extent: (width alignedTo: 3) @ height depth: 32. destructibleSource fillWhite; copyBits: self boundingBox from: self at: 0@0 clippingBox: destructibleSource boundingBox rule: Form over fillColor: nil. ^destructibleSource ! ! !Form methodsFor: 'sub-pixel' stamp: 'hg 3/4/2000 19:07'! subPixelInverse "inverse sub-pixel rendering, eg. for pedagogical, demo, and testing purposes. Tip: use a MagnifierMorph on result. Note: this version is very slow!! Use small source forms. Doesn't work right for all Forms. hg 1/2/2000 18:00" | destForm r g b pixel | destForm _ Form extent: self extent *3 depth: self depth. 0 to: self height-1 do: [:y | 0 to: self width -1 do: [:x | pixel _ self colorAt: x@y. r _ Color r: pixel red g: 0 b: 0. g _ Color r: 0 g: pixel green b: 0. b _ Color r: 0 g: 0 b: pixel blue. 0 to: 2 do: [:row | destForm colorAt: x*3@(y*3+row) put: r. destForm colorAt: x*3+1@(y*3+row) put: g. destForm colorAt: x*3+2@(y*3+row) put: b]]]. ^destForm! ! !Form methodsFor: 'sub-pixel' stamp: 'hg 3/3/2000 19:12'! subPixelInverse2 "inverse sub-pixel rendering for translucent pixel values Tip: use a MagnifierMorph on result. Note: this version is very slow!! Use small source forms. hg 1/2/2000 18:00" | destForm r g b pixel | destForm _ Form extent: self extent *3 depth: self depth. 0 to: self height-1 do: [:y | 0 to: self width -1 do: [:x | pixel _ self colorAt: x@y. r _ Color r: 1- pixel red g: 0 b: 0 alpha: 1. g _ Color r: 0 g: 1- pixel green b: 0 alpha: 1. b _ Color r: 0 g: 0 b: 1- pixel blue alpha: 1. 0 to: 2 do: [:row | destForm colorAt: x*3@(y*3+row) put: r. destForm colorAt: x*3+1@(y*3+row) put: g. destForm colorAt: x*3+2@(y*3+row) put: b]]]. ^destForm! ! !Form methodsFor: 'sub-pixel' stamp: 'hg 3/4/2000 19:07'! subPixelRender "a Form to be 'sub-pixelled' should be destructible, 32 bits deep and have a width of a multiple of 3. If so, it needn't be sent #sourceForSubpixelMerge like below, which ensures this. hg 1/2/2000 22:59" | balancedForm result | balancedForm _ self sourceForSubpixelMerge balanceInNsteps: 2. result _ balancedForm mergeToSubPixels. ^result! ! !Form methodsFor: 'sub-pixel' stamp: 'hg 2/23/2000 10:53'! subPixelRenderNoPrepare "a Form to be 'sub-pixelled' *must* be destructible, 32 bits deep and have a width of a multiple of 3. hg 1/2/2000 22:59" | balancedForm result | balancedForm _ self balanceInNsteps: 2. result _ balancedForm mergeToSubPixels. ^result! ! !DisplayScreen methodsFor: 'blitter defaults' stamp: 'hg 6/18/2000 14:41'! defaultBitBltClass "Return the BitBlt version to use when I am active" ^BitBlt! ! !Form class methodsFor: 'mode constants' stamp: 'hg 3/3/2000 19:03'! rgbAdd "Answer the integer denoting BitBlt's 'Add each color component' rule." ^ 20! ! !Form class methodsFor: 'mode constants' stamp: 'hg 2/19/2000 10:25'! rgbMin "Answer the integer denoting BitBlt's 'Min of each color component' rule." ^ 28! ! !Form class methodsFor: 'mode constants' stamp: 'hg 6/18/2000 14:15'! rgbMul "Answer the integer denoting 'Multiply each color component, their values regarded as fractions of 1' rule." ^ BitBlt current == BitBlt ifTrue: [35] ifFalse: [37]! ! !Form class methodsFor: 'mode constants' stamp: 'hg 3/3/2000 19:02'! rgbSub "Answer the integer denoting BitBlt's 'Subtract each color component' rule." ^ 21! ! !FormCanvas methodsFor: 'private' stamp: 'hg 6/16/2000 17:10'! setPaintColor: aColor "Install a new color used for filling." | paintColor screen patternWord | port isFXBlt ifTrue:[port sourceMap: nil; destMap: nil; colorMap: nil; sourceKey: nil]. paintColor _ self shadowColor ifNil:[aColor]. paintColor ifNil:[paintColor _ Color transparent]. port fillPattern: paintColor; combinationRule: Form paint. paintColor isColor ifFalse:[ (paintColor isKindOf: InfiniteForm) ifFalse:[^self error:'Cannot install color']. ^self]. "Okay, so paintColor really *is* a color" port sourceForm: nil. (paintColor isTranslucent) ifFalse:[ self depth = 8 ifTrue:[ port fillColor: (paintColor balancedPatternForDepth: 8)]. ^self]. "paintColor is translucent color" (port isFXBlt and:[self depth >= 8]) ifTrue:[ "FXBlt setup for alpha mapped transfer" port fillColor: (paintColor bitPatternForDepth: 32). port destMap: form colormapToARGB. port colorMap: form colormapFromARGB. port combinationRule: Form blend. ^self]. self depth > 8 ifTrue:[ "BitBlt setup for alpha mapped transfer" self depth = 16 ifTrue:[port alphaBits: paintColor privateAlpha; combinationRule: 31] ifFalse:[port combinationRule: Form blend]. ^self]. "Can't represent actual transparency -- use stipple pattern" screen _ Color translucentMaskFor: paintColor alpha depth: self depth. patternWord _ paintColor pixelWordForDepth: self depth. port fillPattern: (screen collect: [:maskWord | maskWord bitAnd: patternWord]). ! ! !NewParagraph methodsFor: 'display' stamp: 'hg 6/16/2000 14:21'! insertionPointColor ^ Display depth <= 2 ifTrue: [Color black] ifFalse: [self selectionColor darker]! ! !OutlineFont class methodsFor: 'initialize-release' stamp: 'hg 8/3/2000 12:37'! initialize FileList registerFileReader: self! ! !OutlineFont class methodsFor: 'testing' stamp: 'hg 2/23/2000 17:50'! isFreeTypeAvailable ^(Smalltalk at: #FTLibrary ifAbsent: [^false]) notNil! ! !OutlineFont class methodsFor: 'read from file' stamp: 'hg 8/3/2000 15:44'! fileReaderServicesForSuffix: suffix ^(self isFontFileSuffix: suffix) | (suffix = '*') ifTrue: [ {SimpleServiceEntry provider: self label: 'install outline font as TextStyle' selector: #installTextStyleFromOutlineFile:}] ifFalse: [#()] ! ! !OutlineFont class methodsFor: 'read from file' stamp: 'hg 2/23/2000 13:09'! fromFile: fileName ^self isFreeTypeAvailable ifTrue: [FreeTypeFont fromFile: fileName] ifFalse: [TTFontReader parseFileNamed: fileName]! ! !OutlineFont class methodsFor: 'read from file' stamp: 'hg 8/3/2000 16:03'! installTextStyleFromOutlineFile: fullFileName AntialiasedFont installTextStyleFromOutline: (self fromFile: fullFileName)! ! !OutlineFont class methodsFor: 'read from file' stamp: 'hg 4/11/2000 14:07'! isFontFileSuffix: suffix ^#(ttf pfb) includes: suffix! ! !Paragraph methodsFor: 'private' stamp: 'hg 6/17/2000 16:03'! compositionRectangle: compositionRect text: aText style: aTextStyle offset: aPoint compositionRectangle _ compositionRect copy. text _ aText. textStyle _ aTextStyle. rule _ textStyle defaultFont simpleDisplayRule. mask _ nil. "was DefaultMask " marginTabsLevel _ 0. destinationForm _ Display. offset _ aPoint. ^self composeAll! ! !Preferences class methodsFor: 'initial values' stamp: 'hg 3/4/2000 13:48'! initialOutlineTypeValues ^ #((betterAntialiasedFonts true (morphic))) "Preferences resetCategoryInfo" ! ! !StrikeFont methodsFor: 'accessing' stamp: 'hg 3/1/2000 13:44'! badCharWidth ^7! ! !StrikeFont methodsFor: 'displaying' stamp: 'ar 5/19/2000 15:08'! installOn: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor ^aDisplayContext installStrikeFont: self foregroundColor: foregroundColor backgroundColor: backgroundColor! ! !StrikeFont methodsFor: 'displaying' stamp: 'hg 6/17/2000 16:05'! setupDisplayTarget: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor "adjust the display context's Blt parameters to render this font properly" aDisplayContext colorMap: (self colorMap: foregroundColor forDepth: aDisplayContext destForm depth); combinationRule: self paintDisplayRule. ! ! !StrikeFont methodsFor: 'display parameters' stamp: 'hg 6/17/2000 15:50'! colorMap: textColor forDepth: depth "This is the color map used to draw an instance of this font in color" ^Bitmap with: 0 with: (textColor pixelValueForDepth: depth)! ! !AntialiasedFont methodsFor: 'accessing' stamp: 'hg 2/23/2000 09:56'! species ^self class instanceSpecies! ! !AntialiasedFont methodsFor: 'display parameters' stamp: 'hg 6/17/2000 16:00'! colorMap: textColor forDepth: depth "This is the color map used to draw an instance of this font in color" ^nil "not implemented yet"! ! !AntialiasedFont methodsFor: 'converting' stamp: 'hg 8/1/2000 18:38'! from: outlineFont size: points "render myself from the given outline font and size. Calculate font parameters plus glyph offsets for xTable, then have outline font render glyphs and add badChar glyph" | string offsets scale badChar | name _ outlineFont name. pointSize _ points. type _ 2. subscript _ superscript _ emphasis _ 0. scale _ points / outlineFont unitsPerEM. ascent _ outlineFont ascender * scale roundUpTo: 1. descent _ outlineFont descender * scale roundUpTo: 1. maxWidth _ outlineFont maxAdvanceWidth * scale roundUpTo: 1. string _ outlineFont allCharactersString. minAscii _ string first asciiValue. maxAscii _ minAscii + string size - 1. "set outline font size for width calculations." (outlineFont setRenderingSize: points scaledTo: 1@1) ifFalse: [self error: 'Could not set outline font size.'. ^nil]. offsets _ self calculateOffsets: string forOutlineFont: outlineFont. xTable _ (Array new: minAscii + 1 withAll: 0) , offsets, {self badCharWidth}. self renderGlyphs: string withOutlineFont: outlineFont offsets: offsets. badChar _ (Form extent: self badCharWidth@(ascent + descent)) borderWidth: 1. badChar displayOn: glyphs at: offsets last@0. characterToGlyphMap _ nil.! ! !AntialiasedFont methodsFor: 'converting' stamp: 'hg 8/1/2000 14:31'! postProcess "Just set he bit depth of the glyph Form holding the final character bitmaps. 8 should be OK for plain grayscale anti-aliasing (current 8bit color map has 37 gray levels), which thus needs half the memory of SPR Fonts." glyphs _ glyphs as8BitColorForm! ! !AntialiasedFont methodsFor: 'converting' stamp: 'hg 8/1/2000 15:58'! renderGlyphs: string withOutlineFont: outlineFont offsets: offsets "have outline font render glyphs" | extent scale | scale _ pointSize / outlineFont unitsPerEM. extent _ (offsets last + self badCharWidth @ (outlineFont height * scale)) rounded. glyphs _ (Form extent: extent depth: 16) fillWhite. "NB: Not final depth. see postProcess" outlineFont renderString: string offsets: offsets into: glyphs. self postProcess. ! ! !AntialiasedFont methodsFor: 'width calculation' stamp: 'hg 8/1/2000 13:59'! calculateOffsets: string forOutlineFont: font "calculation of used bitmap width for characters. Point size, scaling etc. should be set before this method is invoked. NB. Each value is for position after where 1st char *ends*, and 2nd char begins. Ie. first value is not 0." | totalWidth width | totalWidth _ 0. ^string collect: [:char | width _ self totalWidthForChar: char ofOutlineFont: font. Transcript nextPut: char; space; print: width; space. " char = $f ifTrue: [self halt]." totalWidth _ totalWidth + width]. ! ! !AntialiasedFont methodsFor: 'width calculation' stamp: 'hg 8/1/2000 17:17'! totalWidthForChar: char ofOutlineFont: outlineFont "calculation of used bitmap width for character in a glyph table. use advance width except when actual width is greater (eg. overhanging chars like f, j)" ^ ((outlineFont gridFittedGlyphWidth: char) max: (outlineFont gridFittedAdvanceWidth: char)) "+ 1" roundUpTo: 1 ! ! !AntialiasedFont methodsFor: 'file in/out' stamp: 'hg 3/5/2000 17:17'! storeAllSizesOnFile "files out the whole text style of this font on a .font file" "(TextStyle named: 'Futura Regular' asSymbol) fileOut" (TextStyle named: name asSymbol) fileOut! ! !AntialiasedFont methodsFor: 'file in/out' stamp: 'hg 3/5/2000 15:57'! storeOn: aStream aStream nextPutAll: self class name, ' new', ' name: ', name storeString, ' pointSize: ', pointSize printString, ' minAscii: ', minAscii printString, ' maxAscii: ', maxAscii printString, ' maxWidth: ', maxWidth printString, ' ascent: ', ascent printString, ' descent: ', descent printString, ' pointSize: ', pointSize printString, ' xTable: '; store: xTable; nextPutAll: ' glyphs: '. glyphs storeOn: aStream. ! ! !AntialiasedFont methodsFor: 'printing' stamp: 'hg 3/5/2000 16:41'! printOn: aStream aStream nextPutAll: self class name, ' ', self name, ' ', self pointSize printString! ! !AntialiasedFont methodsFor: 'private' stamp: 'hg 3/2/2000 19:49'! reset "Does not support synthetic styles (yet?)"! ! !AntialiasedFont class methodsFor: 'initialize-release' stamp: 'hg 2/23/2000 09:50'! initialize self initializeSubPixelPreference! ! !AntialiasedFont class methodsFor: 'instance creation' stamp: 'hg 2/23/2000 09:57'! from: outlineFont size: points ^self instanceSpecies new from: outlineFont size: points! ! !AntialiasedFont class methodsFor: 'TextStyle creation' stamp: 'hg 8/3/2000 15:45'! createTextStyleFromOutline: outlineFont sizes: sizeArray "Renders outline font into AntialiasedFonts with the given sizes, and returns these as a TextStyle." | index font array | index _ 0. 'Creating TextStyle ''', outlineFont name, ''' with ', self instanceSpecies name, 's' displayProgressAt: Sensor cursorPoint from: 0 to: sizeArray size during: [:bar | array _ sizeArray collect: [:s | font _ self from: outlineFont size: s. bar value: (index _ index + 1). font]]. ^array isEmpty ifFalse:[TextStyle fontArray: array]! ! !AntialiasedFont class methodsFor: 'TextStyle creation' stamp: 'hg 8/3/2000 15:46'! installTextStyleFromOutline: outlineFont | sizes string newStyle | string _ FillInTheBlank request: 'Create point sizes: ' initialAnswer: self textStyleSizes. sizes _ (string findTokens: ' ') collect: [:token | token asNumber asInteger]. sizes isEmpty ifFalse: [ newStyle _ self createTextStyleFromOutline: outlineFont sizes: sizes. TextConstants at: outlineFont name asSymbol put: newStyle. " oldStyle _ TextConstants at: outlineFont name asSymbol ifAbsent: [nil]. oldStyle ifNil: [TextConstants at: outlineFont name asSymbol put: newStyle] ifNotNil: [oldStyle becomeForward: newStyle. World restoreDisplay]." outlineFont done]! ! !AntialiasedFont class methodsFor: 'TextStyle creation' stamp: 'hg 3/3/2000 15:59'! textStyleSizes "the default sizes to include when creating a TextStyle" ^'10 11 12 13'! ! !AntialiasedFont class methodsFor: 'sub-pixel preference' stamp: 'hg 3/5/2000 11:52'! initializeSubPixelPreference Preferences enable: #betterAntialiasedFonts; setHelpFor: #betterAntialiasedFonts toString: 'This makes anti-aliased outline fonts look much better on color LCD screens, in particular for small sizes, by using sub-pixel rendering, but uses more memory. Does not affect previously created anti-aliased fonts.'; resetCategoryInfo "to utilize factored prefs panel" ! ! !AntialiasedFont class methodsFor: 'sub-pixel preference' stamp: 'hg 2/23/2000 09:55'! instanceSpecies ^self useSubPixelRendering ifTrue: [SubPixelRenderedFont] ifFalse: [self].! ! !AntialiasedFont class methodsFor: 'sub-pixel preference' stamp: 'hg 3/4/2000 13:46'! useSubPixelRendering ^Preferences valueOfFlag: #betterAntialiasedFonts! ! !SubPixelRenderedFont methodsFor: 'display' stamp: 'hg 6/27/2000 13:04'! paintDisplayRule "This is the Blt rule used to draw an instance of this font with color, transparency, etc" ^Form rgbMul! ! !SubPixelRenderedFont methodsFor: 'display' stamp: 'hg 6/16/2000 18:01'! setupDisplayTarget: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor "adjust the display context's Blt parameters to render this font properly" aDisplayContext fillColor: nil. ^super setupDisplayTarget: aDisplayContext foregroundColor: foregroundColor backgroundColor: backgroundColor ! ! !SubPixelRenderedFont methodsFor: 'display' stamp: 'hg 6/17/2000 16:04'! simpleDisplayRule ^self paintDisplayRule! ! !SubPixelRenderedFont methodsFor: 'converting' stamp: 'hg 6/17/2000 15:47'! finalDepth "The bit depth of the glyph Form holding the final character bitmaps. One might want to set this differently for SPR fonts than regular AA fonts." ^16! ! !SubPixelRenderedFont methodsFor: 'converting' stamp: 'hg 3/5/2000 18:45'! postProcess "Do the actual sub-pixel rendering, and then set the bit depth of the glyph Form holding the final character bitmaps. 16 seems good enough for SPR." glyphs _ glyphs subPixelRender asFormOfDepth: 16! ! !SubPixelRenderedFont methodsFor: 'converting' stamp: 'hg 3/5/2000 11:27'! renderGlyphs: string withOutlineFont: outlineFont offsets: offsets "alter rendering parameters for sub-pixel rendering before having outline font render glyphs. afterward, apply sub-pixel rendering to the glyphs" | stretchedOffsets | stretchedOffsets _ offsets collect: [:offset | offset * 3]. outlineFont setRenderingSize: pointSize scaledTo: 3@1. super renderGlyphs: string withOutlineFont: outlineFont offsets: stretchedOffsets! ! !TTFontDescription methodsFor: 'accessing' stamp: 'hg 2/22/2000 20:14'! fullName ^fullName! ! !TTFontDescription methodsFor: 'accessing' stamp: 'hg 2/23/2000 10:38'! name "generic message to get name for OutlineFont" ^fullName! ! !TTFontDescription methodsFor: 'converting' stamp: 'hg 2/23/2000 10:31'! renderFont: aFont scale: scale "Generate an AntialiasedFont for this TTF font at a given size" | forms | forms _ (0 to: 255) collect: [:i | (self at: i) asFormWithScale: scale ascender: ascender descender: descender]. aFont fromFormArray: forms asciiStart: 0 ascent: (ascender * scale x) rounded! ! !TTFontDescription methodsFor: 'converting' stamp: 'hg 2/23/2000 09:36'! renderFont: aFont size: points scaledTo: scalePoint self renderFont: aFont scale: points/unitsPerEm * scalePoint! ! !TTFontReader class methodsFor: 'class initialization' stamp: 'hg 8/1/2000 20:09'! initialize FileList registerFileReader: self! ! !TTFontReader class methodsFor: 'instance creation' stamp: 'hg 8/3/2000 16:01'! fileReaderServicesForSuffix: suffix ^(suffix = 'ttf') | (suffix = '*') ifTrue: [ {SimpleServiceEntry provider: self label: 'open true type font as Morph' selector: #parseFileNamed:}] ifFalse: [#()] ! ! !TextStyle methodsFor: 'Disk I/O' stamp: 'hg 3/5/2000 16:51'! 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 heights | ff _ FileStream fileNamed: fileName. this _ ff fileInObjectAndCode. "Only works if file created by special code above" newName _ this fontArray first name. this fontArray do: [:aFont | aFont name = 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 | "add new fonts" heights _ style fontArray collect: [:bFont | bFont height]. (heights includes: aFont height) ifFalse: [ style fontAt: style fontArray size + 1 put: aFont]]. ! ! !TextStyle methodsFor: 'Disk I/O' stamp: 'hg 3/5/2000 16:52'! fileOut "cf. collectionFromFileNamed:" | ff | ff _ SmartRefStream fileNamed: (fontArray first name, '.font'). TextConstants at: #forceFontWriting put: true. ff nextPut: self. TextConstants at: #forceFontWriting put: false. ff close. ! ! !TextStyle class methodsFor: 'initialize-release' stamp: 'hg 8/3/2000 12:43'! initialize FileList registerFileReader: self! ! !TextStyle class methodsFor: 'fileIn' stamp: 'hg 8/3/2000 16:03'! fileReaderServicesForSuffix: suffix ^(suffix = 'font') ifTrue: [ SimpleServiceEntry provider: self default label: 'install antialiased font as TextStyle' selector: #collectionFromFileNamed:] ifFalse: [#()] ! ! !Utilities class methodsFor: 'text styles and fonts' stamp: 'hg 2/19/2000 11:14'! mvcPromptForFont: aPrompt andSendTo: aTarget withSelector: aSelector | aMenu aChoice aStyle namesAndSizes aFont | "Utilities mvcPromptForFont: 'Choose system font style' andSendTo: Utilities withSelector: #setSystemFontTo:" aMenu _ CustomMenu new. Utilities actualTextStyles keys asSortedCollection do: [:styleName | aMenu add: styleName action: styleName]. aChoice _ aMenu startUpWithCaption: aPrompt. aChoice ifNil: [^ self]. aMenu _ CustomMenu new. aStyle _ TextStyle named: aChoice. (namesAndSizes _ aStyle fontNamesWithPointSizes) do: [:aString | aMenu add: aString action: aString]. aChoice _ aMenu startUpWithCaption: nil. aChoice ifNil: [^ self]. aFont _ aStyle fontAt: (namesAndSizes indexOf: aChoice). aTarget perform: aSelector with: aFont! ! !Utilities class methodsFor: 'text styles and fonts' stamp: 'hg 7/8/2000 11:15'! promptForFont: aPrompt andSendTo: aTarget withSelector: aSelector "Utilities promptForFont: 'Choose system font:' andSendTo: Utilities withSelector: #setSystemFontTo:" "NOTE: Morphic ONLY!!!!. Derived from a method written by Robin Gibson" | menu subMenu | menu _ MenuMorph entitled: aPrompt. Utilities actualTextStyles keys asSortedCollection do: [:styleName| subMenu _ self fontMenuForStyle: styleName target: aTarget selector: aSelector. menu add: styleName subMenu: subMenu. menu lastItem font: ((TextStyle named: styleName) fontOfSize: 18)]. menu popUpForHand: self currentHand! ! TextStyle initialize! TextStyle class removeSelector: #installTextStyleFromFontFile:! TTFontReader initialize! SubPixelRenderedFont removeSelector: #defaultDisplayRule! SubPixelRenderedFont removeSelector: #quickPrintDisplayRule! SubPixelRenderedFont removeSelector: #transparencyDisplayRule! !SubPixelRenderedFont reorganize! ('display' paintDisplayRule setupDisplayTarget:foregroundColor:backgroundColor: simpleDisplayRule) ('converting' finalDepth postProcess renderGlyphs:withOutlineFont:offsets:) ! AntialiasedFont class removeSelector: #createTextStyleFromOutlineFile:! AntialiasedFont initialize! AntialiasedFont class removeSelector: #installTextStyleFromOutlineFile:! !AntialiasedFont class reorganize! ('initialize-release' initialize) ('instance creation' from:size:) ('TextStyle creation' createTextStyleFromOutline:sizes: installTextStyleFromOutline: textStyleSizes) ('sub-pixel preference' initializeSubPixelPreference instanceSpecies useSubPixelRendering) ! AntialiasedFont removeSelector: #quickPrintColorMap:forBlt:! !AntialiasedFont reorganize! ('accessing' species) ('display parameters' colorMap:forDepth:) ('converting' from:size: postProcess renderGlyphs:withOutlineFont:offsets:) ('width calculation' calculateOffsets:forOutlineFont: totalWidthForChar:ofOutlineFont:) ('file in/out' storeAllSizesOnFile storeOn:) ('printing' printOn:) ('private' reset) ! StrikeFont removeSelector: #quickPrintColorMap:forBlt:! OutlineFont initialize! !OutlineFont class reorganize! ('initialize-release' initialize) ('testing' isFreeTypeAvailable) ('read from file' fileReaderServicesForSuffix: fromFile: installTextStyleFromOutlineFile: isFontFileSuffix:) ! DisplayScanner removeSelector: #newOn:box:font:color:! AbstractFont removeSelector: #defaultBltRule! AbstractFont removeSelector: #defaultDisplayRule! AbstractFont removeSelector: #quickPrintColorMap:forBlt:! AbstractFont removeSelector: #quickPrintDisplayRule! AbstractFont removeSelector: #transparencyDisplayRule!