Tobias Pape uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-topa.784.mcz ==================== Summary ==================== Name: Morphic-topa.784 Author: topa Time: 19 March 2015, 11:40:04.459 am UUID: 4213f9dc-bbed-4cbd-9a7e-816a07234bd8 Ancestors: Morphic-topa.783 Add a Font Importer Tool. You can now easily import available font into the image, either by actually embedding them or by referencing the font file on disk. =============== Diff against Morphic-topa.783 =============== Item was changed: ----- Method: FontChooserTool>>fontList (in category 'font list') ----- fontList "List of available font family names" + ^fontList ifNil:[fontList := TextStyle knownTextStyles]! - ^fontList ifNil:[fontList := (TextConstants select: [:each | each isKindOf: TextStyle]) keys asArray sort]! Item was added: + Object subclass: #FontImporterFontDescription + instanceVariableNames: 'fontname filename children parent' + classVariableNames: '' + poolDictionaries: '' + category: 'Morphic-Support'! Item was added: + ----- Method: FontImporterFontDescription>><= (in category 'comparing') ----- + <= other + + ^ self fontname asString <= other fontname asString! Item was added: + ----- Method: FontImporterFontDescription>>addChild: (in category 'accessing') ----- + addChild: aChild + + ^ self children add: aChild! Item was added: + ----- Method: FontImporterFontDescription>>allFilenames (in category 'accessing') ----- + allFilenames + + ^ self filename + ifNil: [ + (self children + select: [:child | child filename notNil] + thenCollect: [:child | child filename]) + asSet asArray] + ifNotNil: [:f | {f}] ! Item was added: + ----- Method: FontImporterFontDescription>>children (in category 'accessing') ----- + children + + ^ children ifNil: [children := OrderedCollection new].! Item was added: + ----- Method: FontImporterFontDescription>>children: (in category 'accessing') ----- + children: anObject + + children := anObject! Item was added: + ----- Method: FontImporterFontDescription>>filename (in category 'accessing') ----- + filename + + ^ filename! Item was added: + ----- Method: FontImporterFontDescription>>filename: (in category 'accessing') ----- + filename: anObject + + filename := anObject! Item was added: + ----- Method: FontImporterFontDescription>>fontname (in category 'accessing') ----- + fontname + + ^ fontname! Item was added: + ----- Method: FontImporterFontDescription>>fontname: (in category 'accessing') ----- + fontname: anObject + + fontname := anObject! Item was added: + ----- Method: FontImporterFontDescription>>hasChildren (in category 'testing') ----- + hasChildren + + ^ self children notNil and: [self children notEmpty]! Item was added: + ----- Method: FontImporterFontDescription>>normalize (in category 'actions') ----- + normalize + + self children size = 1 ifTrue: [ | pseudoChild | + pseudoChild := self children removeFirst. + (self filename notNil and: [pseudoChild filename ~= self filename]) + ifTrue: [self error: 'Inconsistent state']. + self filename: pseudoChild filename]! Item was added: + ----- Method: FontImporterFontDescription>>parent (in category 'accessing') ----- + parent + + ^ parent! Item was added: + ----- Method: FontImporterFontDescription>>parent: (in category 'accessing') ----- + parent: anObject + + parent := anObject! Item was added: + ----- Method: FontImporterFontDescription>>printOn: (in category 'printing') ----- + printOn: aStream + + self parent ifNotNil: [:p | aStream nextPutAll: p fontname; nextPut: $ ]. + aStream nextPutAll: self fontname. + self children notEmpty ifTrue: [aStream nextPut: $ ]. + self children + do: [:subfont | aStream nextPutAll: subfont fontname] + separatedBy: [aStream nextPut: $/]. + aStream nextPut: $ ; nextPut: $(. + self allFilenames + do: [:filename | aStream nextPutAll: filename] + separatedBy: [aStream nextPut: $,; nextPut: $ ]. + aStream nextPut: $). + ! Item was added: + Model subclass: #FontImporterTool + instanceVariableNames: 'title allFonts emphasis window currentSelection currentParent warningSeen' + classVariableNames: '' + poolDictionaries: '' + category: 'Morphic-Support'! + + !FontImporterTool commentStamp: 'topa 3/9/2015 18:56' prior: 0! + A tool to import platform (native) fonts into the image! Item was added: + ----- Method: FontImporterTool class>>default (in category 'accessing') ----- + default + "Answer the default font imporer tool, ie me + (polymorphic with font chooser) + " + ^ self! Item was added: + ----- Method: FontImporterTool class>>initialize (in category 'class initialization') ----- + initialize + + self registerInOpenMenu.! Item was added: + ----- Method: FontImporterTool class>>open (in category 'opening') ----- + open + " + FontChooserTool open. + " + ^self new open! Item was added: + ----- Method: FontImporterTool class>>openWithWindowTitle:for:setSelector:getSelector: (in category 'opening') ----- + openWithWindowTitle: titleString for: anObject setSelector: setSelector getSelector: getSelector + " + FontChooserTool + openWithWindowTitle: 'Choose the Menu Font' + for: Preferences + setSelector: #setMenuFontTo: + getSelector: #standardMenuFont. + " + ^(self withTitle: titleString for: anObject setSelector: setSelector getSelector: getSelector) open! Item was added: + ----- Method: FontImporterTool class>>registerInOpenMenu (in category 'class initialization') ----- + registerInOpenMenu + (TheWorldMenu respondsTo: #registerOpenCommand:) ifTrue: [ + TheWorldMenu unregisterOpenCommand: 'Font Importer'. + TheWorldMenu registerOpenCommand: {'Font Importer'. {self. #open}}]. + ! Item was added: + ----- Method: FontImporterTool class>>unload (in category 'class initialization') ----- + unload + + self unregisterFromOpenMenu.! Item was added: + ----- Method: FontImporterTool class>>unregisterFromOpenMenu (in category 'class initialization') ----- + unregisterFromOpenMenu + (TheWorldMenu respondsTo: #registerOpenCommand:) + ifTrue: [TheWorldMenu unregisterOpenCommand: 'Font Importer']. + ! Item was added: + ----- Method: FontImporterTool class>>windowTitle:for:setSelector:getSelector: (in category 'opening') ----- + windowTitle: titleString for: anObject setSelector: setSelector getSelector: getSelector + | instance | + + instance := self new. + instance + title: titleString; + target: anObject; + setSelector: setSelector; + getSelector: getSelector. + ^instance open! Item was added: + ----- Method: FontImporterTool class>>withTitle:for:setSelector:getSelector: (in category 'opening') ----- + withTitle: titleString for: anObject setSelector: setSelector getSelector: getSelector + " + (FontChooserTool + withTitle: 'Choose the Menu Font' + for: Preferences + setSelector: #setMenuFontTo: + getSelector: #standardMenuFont) open. + " + | instance | + instance := self new. + instance + title: titleString; + target: anObject; + setSelector: setSelector; + getSelector: getSelector. + ^instance! Item was added: + ----- Method: FontImporterTool>>allFonts (in category 'accessing') ----- + allFonts + ^ allFonts ifNil: [ | fonts | + fonts := Dictionary new. + Cursor wait showWhile: [ + TTFileDescription fontPathsDo:[:path | + TTFileDescription fontFilesIn: path do:[:font| | fontDesc filename fname | + filename := path, FileDirectory slash, font fileName. + fname := self textForFamily: font familyName subfamily: nil. + fontDesc := fonts + at: font familyName + ifAbsentPut: (FontImporterFontDescription new fontname: fname; yourself). + font subfamilyName + ifNil: [fontDesc filename: filename] + ifNotNil: [ |subfontDesc sname | + sname := self textForFamily: font familyName subfamily: font subfamilyName. + subfontDesc := FontImporterFontDescription new fontname: sname; yourself. + subfontDesc + parent: fontDesc; + filename: filename. + fontDesc addChild: subfontDesc]]]]. + allFonts := fonts values sorted. + allFonts do: [:fontDesc | fontDesc normalize]. + allFonts]. + + ! Item was added: + ----- Method: FontImporterTool>>allFonts: (in category 'accessing') ----- + allFonts: anObject + + allFonts := anObject. + self changed: #allFonts.! Item was added: + ----- Method: FontImporterTool>>buildButtonBarWith: (in category 'toolbuilder') ----- + buildButtonBarWith: builder + "Build the button bar" + | panelSpec buttonSpec | + panelSpec := builder pluggablePanelSpec new. + panelSpec children: OrderedCollection new. + + buttonSpec := builder pluggableButtonSpec new + model: self; + label: ' Import ' translated; + action: #import; + frame: (0@0 corner: (1/3)@1); + yourself. + panelSpec children addLast: buttonSpec. + + buttonSpec := builder pluggableButtonSpec new + model: self; + label: ' Install ' translated; + action: #install; + frame: ((1/3)@0 corner: (2/3)@1); + yourself. + panelSpec children addLast: buttonSpec. + + + buttonSpec := builder pluggableButtonSpec new + model: self; + label: ' Close ' translated; + action: #close; + frame: ((2/3)@0 corner: 1@1); + yourself. + panelSpec children addLast: buttonSpec. + + + ^panelSpec! Item was added: + ----- Method: FontImporterTool>>buildFontListWith: (in category 'toolbuilder') ----- + buildFontListWith: builder + "Build the font choosers list of font names" + + ^ builder pluggableTreeSpec new + model: self; + roots: #allFonts; + label: #labelOf: ; + getChildren: #childrenOf: ; + getSelected: #currentSelection; + setSelected: #currentSelection:; + setSelectedParent: #currentParent:; + autoDeselect: false; + yourself + ! Item was added: + ----- Method: FontImporterTool>>buildPreviewPaneWith: (in category 'toolbuilder') ----- + buildPreviewPaneWith: builder + "Build the preview panel" + + ^ builder pluggablePanelSpec new + children: { + builder pluggableTextSpec new + model: self; + getText: #filename; + frame: (LayoutFrame + fractions: (0@0 corner: 1@0) + offsets: (0@0 corner: 0@ -25)); + yourself. + + builder pluggableTextSpec new + name: #preview; + model: self; + getText: #contents; + frame: (LayoutFrame + fractions: (0@0 corner: 1@0.75) + offsets: (0@ 30 corner: 0@0)); + yourself. + + builder pluggableTextSpec new + model: self; + getText: #copyright; + frame: (LayoutFrame + fractions: (0@0.75 corner: 1@1)); + yourself + + }; + yourself! Item was added: + ----- Method: FontImporterTool>>buildWindowWith: (in category 'toolbuilder') ----- + buildWindowWith: builder + + ^ builder pluggableWindowSpec new + model: self; + label: #windowTitle; + children: OrderedCollection new; + yourself + ! Item was added: + ----- Method: FontImporterTool>>buildWindowWith:specs: (in category 'toolbuilder') ----- + buildWindowWith: builder specs: specs + | windowSpec | + windowSpec := self buildWindowWith: builder. + specs do:[:assoc| | action widgetSpec rect | + rect := assoc key. + action := assoc value. + widgetSpec := action value. + widgetSpec ifNotNil:[ + widgetSpec frame: rect. + windowSpec children add: widgetSpec]]. + ^windowSpec! Item was added: + ----- Method: FontImporterTool>>buildWith: (in category 'toolbuilder') ----- + buildWith: builder + "Create the ui for the browser" + "ToolBuilder open: self" + | windowSpec | + windowSpec := self buildWindowWith: builder specs: { + (self fontListFrame) -> [self buildFontListWith: builder]. + (self previewFrame) -> [self buildPreviewPaneWith: builder]. + (self buttonsFrame) -> [self buildButtonBarWith: builder]. + }. + windowSpec extent: self initialExtent. + window := builder build: windowSpec. + "Yes, that's a hack. But it looks ugly with line breaks." + (builder widgetAt: #preview) textMorph wrapFlag: false. + ^window! Item was added: + ----- Method: FontImporterTool>>buttonHeight (in category 'toolbuilder') ----- + buttonHeight + ^Preferences standardButtonFont height + 25! Item was added: + ----- Method: FontImporterTool>>buttonsFrame (in category 'toolbuilder') ----- + buttonsFrame + + ^ LayoutFrame + fractions: (0@1 corner: 1@1) + offsets: (0@ self buttonHeight negated corner: 0@0) + ! Item was added: + ----- Method: FontImporterTool>>childrenOf: (in category 'accessing') ----- + childrenOf: aFontDescription + + ^ aFontDescription children! Item was added: + ----- Method: FontImporterTool>>close (in category 'actions') ----- + close + ToolBuilder default close: window.! Item was added: + ----- Method: FontImporterTool>>contents (in category 'toolbuilder') ----- + contents + | sample i c f | + sample := WriteStream on: ''. + f := self selectedFont ifNil:[^Text new]. + (f isSymbolFont or: [(self font: f hasGlyphOf: $a) not]) ifFalse:[ + sample + nextPutAll: 'the quick brown fox jumps over the lazy dog' ;cr; + nextPutAll: 'THE QUICK BROWN FOX JUMPS OVER THE LAZY DOG.' ;cr;cr; + nextPutAll: '0123456789'; cr; cr; + nextPutAll: + 'Lorem ipsum dolor sit amet, consectetur adipisicing elit, + sed do eiusmod tempor incididunt ut labore et dolore + magna aliqua. Ut enim ad minim veniam, quis nostrud + exercitation ullamco laboris nisi ut aliquip ex ea commodo + consequat. Duis aute irure dolor in reprehenderit in voluptate + velit esse cillum dolore eu fugiat nulla pariatur. Excepteur + sint occaecat cupidatat non proident, sunt in culpa qui + officia deserunt mollit anim id est laborum.' + ] ifTrue:[ + i := 0. + 33 to: 255 do:[:ci | + sample nextPut: (c:=Character value: ci). + i := i + 1. + (('@Z`z' includes:c) or:[i = 30]) + ifTrue:[i :=0. sample cr]]. + ]. + sample := sample contents asText. + sample addAttribute: (TextFontReference toFont: f). + ^sample! Item was added: + ----- Method: FontImporterTool>>copyright (in category 'toolbuilder') ----- + copyright + | f | + f := self selectedFont ifNil:[^ '']. + ^ f isTTCFont + ifTrue: [f ttcDescription copyright ifNil: ['']] + ifFalse: ['']! Item was added: + ----- Method: FontImporterTool>>currentParent (in category 'accessing') ----- + currentParent + + ^ currentParent! Item was added: + ----- Method: FontImporterTool>>currentParent: (in category 'accessing') ----- + currentParent: anObject + + anObject = currentParent ifTrue: [^ self]. + currentParent := anObject. + self changed: #currentParent. + ! Item was added: + ----- Method: FontImporterTool>>currentSelection (in category 'accessing') ----- + currentSelection + + ^ currentSelection! Item was added: + ----- Method: FontImporterTool>>currentSelection: (in category 'accessing') ----- + currentSelection: anObject + + anObject = currentSelection ifTrue: [^ self]. + currentSelection := anObject. + self changed: #currentSelection. + self changed: #contents. + self changed: #filename. + self changed: #copyright.! Item was added: + ----- Method: FontImporterTool>>emphasis (in category 'accessing') ----- + emphasis + + ^ emphasis! Item was added: + ----- Method: FontImporterTool>>emphasis: (in category 'accessing') ----- + emphasis: anObject + + emphasis := anObject! Item was added: + ----- Method: FontImporterTool>>filename (in category 'toolbuilder') ----- + filename + + ^ self currentSelection + ifNil: [''] + ifNotNil: [:sel | + String streamContents: [:stream | + sel allFilenames + do: [:filename | stream nextPutAll: filename] + separatedBy: [stream nextPut: $,;nextPut: $ ]]]! Item was added: + ----- Method: FontImporterTool>>font:hasGlyphOf: (in category 'toolbuilder') ----- + font: f hasGlyphOf: aCharacter + + ^ f isTTCFont + ifFalse: [f hasGlyphOf: aCharacter] + ifTrue: [ + " [(f hasGlyphOf: aCharacter) not] does not work, the fallback glyph is always found instead. + So we fake. if aCharacter is the same form as Character null aka 0, we assume absence." + (f formOf: aCharacter) bits ~= f fallbackForm bits] + ! Item was added: + ----- Method: FontImporterTool>>fontFromFamily: (in category 'helper') ----- + fontFromFamily: aFamily + + | readFonts | + aFamily ifNil: [^ TextStyle default fonts first]. + readFonts := TTFileDescription readFontsFrom: aFamily allFilenames anyOne. + ^ (readFonts size > 1 + ifTrue: [ + | ftArray | + " see TTCFontSet>>newTextStyleFromTT: " + ftArray := readFonts collect: [:ttc | |f| + ttc ifNil: [nil] ifNotNil: [ + f := TTCFont new. + f ttcDescription: ttc. + f pointSize: 11.0 . + f]]. + TTCFontSet newFontArray: ftArray] + ifFalse: [ |f| + f := TTCFont new. + f ttcDescription: readFonts anyOne. + f pointSize: 11.0 . + f])! Item was added: + ----- Method: FontImporterTool>>fontListFrame (in category 'toolbuilder') ----- + fontListFrame + + ^ LayoutFrame + fractions: (0@0 corner: 0.4@1) + offsets: (0@0 corner: 0@ self buttonHeight negated + 4)! Item was added: + ----- Method: FontImporterTool>>import (in category 'actions') ----- + import + | megaSize filenames fonts | + fonts := self currentSelection. + filenames := fonts allFilenames. + megaSize := ((filenames inject: 0 into: [ :sum :fn | + sum + (FileStream readOnlyFileNamed: fn do: [:file | file size])]) / (1024 * 1024)) asFloat. + (UIManager default confirm: ( + 'About to import {1}{2}.\\This is at least {3} MB of space required int the image.\ + Please respect the copyright and embedding restrictions of the font.\ + Proceed?' + withCRs format: { + self currentParent + ifNotNil: [:p| p fontname, ' ', self currentSelection fontname] + ifNil: [self currentSelection fontname]. + filenames size > 1 ifTrue: [' (', filenames size, ' font files)'] ifFalse: ['']. + megaSize printShowingDecimalPlaces: 2})) + ifTrue: [ + filenames do: [:filename | | readFonts | + readFonts := TTCFontDescription addFromTTFile: filename. + readFonts isCollection + ifFalse: [TTCFont newTextStyleFromTT: readFonts] + ifTrue: [self importFontFamily: readFonts]]]. + self allFonts: nil. "force redraw" + ! Item was added: + ----- Method: FontImporterTool>>importFontFamily: (in category 'helper') ----- + importFontFamily: readFonts + + |r rest array | + r := readFonts detect: [:f | + [f isRegular] on: Error do: [false] "hack for unknown emphases" + ] ifNone: [^ TTCFont newTextStyleFromTT: readFonts first]. + rest := readFonts copyWithout: r. + array :=TTCFont pointSizes collect: [:pt | | f | + f := TTCFont new ttcDescription: r; pointSize: pt; yourself. + rest do: [:rf | + (self isStyleNameSupported: rf subfamilyName) + ifTrue: [f derivativeFont: (TTCFont new ttcDescription: rf; pointSize: pt; yourself)] + ifFalse: [ + Transcript show: 'Cannot import unknown style ', rf subfamilyName, ' from Font family ', f name]]. + f]. + ^ TTCFont reorganizeForNewFontArray: array name: array first name asSymbol.! Item was added: + ----- Method: FontImporterTool>>initialExtent (in category 'initialize') ----- + initialExtent + + ^ 600@400.! Item was added: + ----- Method: FontImporterTool>>initialize (in category 'initialize') ----- + initialize + super initialize. + title := 'Choose a Font to import'. + emphasis := 0. + ! Item was added: + ----- Method: FontImporterTool>>install (in category 'actions') ----- + install + | filenames fonts | + fonts := self currentSelection. + self warningSeen ifFalse: [ + (UIManager default confirm: ( + 'Note that installing a font instead of importing may make the + image un-portable, since the installed font must be present on + the system the next time the image is run. + + This warning is only shown once per session.' ) trueChoice: 'Proceed' falseChoice: 'Cancel') + ifFalse: [^ self]. + self warningSeen: true].. + filenames := fonts allFilenames. + filenames do: [:filename | | readFonts | + readFonts := TTFileDescription readFontsFrom: filename. + readFonts isCollection + ifFalse: [TTCFont newTextStyleFromTT: readFonts] + ifTrue: [self importFontFamily: readFonts]]. + self allFonts: nil. "force redraw"! Item was added: + ----- Method: FontImporterTool>>isStyleNameSupported: (in category 'helper') ----- + isStyleNameSupported: subfamilyName + + ^ (TextStyle decodeStyleName: subfamilyName) second isEmpty! Item was added: + ----- Method: FontImporterTool>>labelOf: (in category 'accessing') ----- + labelOf: aFontDescription + + ^ aFontDescription fontname + + ! Item was added: + ----- Method: FontImporterTool>>open (in category 'toolbuilder') ----- + open + ^ToolBuilder open: self! Item was added: + ----- Method: FontImporterTool>>previewFrame (in category 'toolbuilder') ----- + previewFrame + + ^ LayoutFrame + fractions: (0.4@0 corner: 1@1) + offsets: (0@0 corner: 0@ self buttonHeight negated + 4)! Item was added: + ----- Method: FontImporterTool>>selectedFont (in category 'font list') ----- + selectedFont + | fontDesc font | + fontDesc := self currentSelection. + font := self fontFromFamily: fontDesc. + font isFontSet ifTrue: [ + font := (self currentParent isNil or: [self currentParent = self currentSelection]) + ifTrue: [font fontArray anyOne] + ifFalse: [ "we have selected a leaf " + font fontArray + detect: [:subfont | subfont subfamilyName = fontDesc fontname] + ifNone: [font]]]. + ^font emphasized: emphasis! Item was added: + ----- Method: FontImporterTool>>textForFamily:subfamily: (in category 'accessing') ----- + textForFamily: familyName subfamily: subfamilyName + + subfamilyName ifNil: [ + ^ (TextStyle named: familyName) + ifNil: [familyName] + ifNotNil: [:style | style isTTCStyle + ifTrue: ["we are already present " + Text string: familyName attribute: TextEmphasis underlined] + ifFalse: [familyName]]]. + + " frome here on it is only about subfamilies" + + (self isStyleNameSupported: subfamilyName) + ifFalse: [^ Text string: subfamilyName attribute: TextColor gray]. + + ^ (TextStyle named: familyName) + ifNil: ["importable" subfamilyName] + ifNotNil: [:style | + (style isTTCStyle and: [ | regular emph | + regular := style fonts anyOne. + emph := TTCFont indexOfSubfamilyName: subfamilyName. + " detect if this style is already imported " + regular emphasis = emph or: [(regular emphasis: emph) ~= regular]]) + ifFalse: ["again importable" subfamilyName] + ifTrue: [Text string: subfamilyName attribute: TextEmphasis underlined]]! Item was added: + ----- Method: FontImporterTool>>title (in category 'accessing') ----- + title + + ^ title! Item was added: + ----- Method: FontImporterTool>>title: (in category 'accessing') ----- + title: anObject + "Set the value of title" + + title := anObject! Item was added: + ----- Method: FontImporterTool>>warningSeen (in category 'accessing') ----- + warningSeen + + ^ warningSeen ifNil: [false]! Item was added: + ----- Method: FontImporterTool>>warningSeen: (in category 'accessing') ----- + warningSeen: anObject + + warningSeen := anObject! Item was added: + ----- Method: FontImporterTool>>window (in category 'accessing') ----- + window + ^window! Item was added: + ----- Method: FontImporterTool>>window: (in category 'accessing') ----- + window: anObject + + window := anObject! Item was added: + ----- Method: FontImporterTool>>windowTitle (in category 'initialize') ----- + windowTitle + ^ title translated! Item was added: + ----- Method: TTCFont>>fallbackForm (in category '*Morphic-Multilingual') ----- + fallbackForm + "Compute the glyph form for the fallback glyph" + ^ttcDescription renderFallbackGlyphOfHeight: self height fgColor: foregroundColor bgColor: Color transparent depth: self depth! Item was added: + ----- Method: TTGlyph>>asFormWithScale:ascender:descender: (in category '*Morphic-Multilingual') ----- + asFormWithScale: scale ascender: ascender descender: descender + ^ self + asFormWithScale: scale + ascender: ascender + descender: descender + fgColor: Color black + bgColor: Color white + depth: 8 + replaceColor: true. + ! Item was added: + ----- Method: TTGlyph>>asFormWithScale:ascender:descender:fgColor:bgColor:depth: (in category '*Morphic-Multilingual') ----- + asFormWithScale: scale ascender: ascender descender: descender fgColor: fgColor bgColor: bgColor depth: depth + + ^ self + asFormWithScale: scale + ascender: ascender + descender: descender + fgColor: fgColor + bgColor: bgColor + depth: depth + replaceColor: false. + ! Item was added: + ----- Method: TTGlyph>>asFormWithScale:ascender:descender:fgColor:bgColor:depth:replaceColor: (in category '*Morphic-Multilingual') ----- + asFormWithScale: scale ascender: ascender descender: descender fgColor: fgColor bgColor: bgColor depth: depth replaceColor: replaceColorFlag + + ^ self + asFormWithScale: scale + ascender: ascender + descender: descender + fgColor: fgColor + bgColor: bgColor + depth: depth + replaceColor: replaceColorFlag + lineGlyph: nil + lingGlyphWidth: 0 + emphasis: 0.! |
Free forum by Nabble | Edit this page |