The Trunk: Multilingual-nice.77.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Multilingual-nice.77.mcz

commits-2
Nicolas Cellier uploaded a new version of Multilingual to project The Trunk:
http://source.squeak.org/trunk/Multilingual-nice.77.mcz

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

Name: Multilingual-nice.77
Author: nice
Time: 26 December 2009, 11:31:39 am
UUID: 53907311-aca1-4451-b042-e3c09d362b9b
Ancestors: Multilingual-nice.76

Cosmetic: puch a few temps inside closures

=============== Diff against Multilingual-nice.76 ===============

Item was changed:
  ----- Method: ImmWin32>>keyboardFocusForAMorph: (in category 'keyboard') -----
  keyboardFocusForAMorph: aMorph
 
- | left top pos |
  aMorph ifNil: [^ self].
  [
+ | left top pos |
  pos := aMorph preferredKeyboardPosition.
  left := (pos x min: Display width max: 0) asInteger.
  top := (pos y min: Display height max: 0) asInteger.
  self setCompositionWindowPositionX: left y: top
  ] on: Error
  do: [:ex |].
  !

Item was changed:
  ----- Method: MultiCharacterScanner>>scanMultiCharactersFrom:to:in:rightX:stopConditions:kern: (in category 'scanning') -----
  scanMultiCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta
 
  | ascii encoding f nextDestX maxAscii startEncoding floatDestX widthAndKernedWidth nextChar atEndOfRun |
  lastIndex := startIndex.
  lastIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops at: EndOfRun].
  startEncoding := (sourceString at: startIndex) leadingChar.
  font ifNil: [font := (TextConstants at: #DefaultMultiStyle) fontArray at: 1].
  ((font isMemberOf: StrikeFontSet) or: [font isKindOf: TTCFontSet]) ifTrue: [
+ f := [font fontArray at: startEncoding + 1]
+ on: Exception do: [:ex | nil].
- [f := font fontArray at: startEncoding + 1]
- on: Exception do: [:ex | f := font fontArray at: 1].
  f ifNil: [ f := font fontArray at: 1].
  maxAscii := f maxAscii.
  spaceWidth := f widthOf: Space.
  ] ifFalse: [
  maxAscii := font maxAscii.
  ].
  floatDestX := destX.
  widthAndKernedWidth := Array new: 2.
  atEndOfRun := false.
  [lastIndex <= stopIndex] whileTrue: [
  encoding := (sourceString at: lastIndex) leadingChar.
  encoding ~= startEncoding ifTrue: [lastIndex := lastIndex - 1. ^ stops at: EndOfRun].
  ascii := (sourceString at: lastIndex) charCode.
  ascii > maxAscii ifTrue: [ascii := maxAscii].
  (encoding = 0 and: [ascii < stops size and: [(stops at: ascii + 1) ~~ nil]]) ifTrue: [^ stops at: ascii + 1].
  (self isBreakableAt: lastIndex in: sourceString in: Latin1Environment) ifTrue: [
  self registerBreakableIndex.
  ].
  nextChar := (lastIndex + 1 <= stopIndex)
  ifTrue:[sourceString at: lastIndex + 1]
  ifFalse:[
  atEndOfRun := true.
  "if there is a next char in sourceString, then get the kern
  and store it in pendingKernX"
  lastIndex + 1 <= sourceString size
  ifTrue:[sourceString at: lastIndex + 1]
  ifFalse:[ nil]].
  font
  widthAndKernedWidthOfLeft: (sourceString at: lastIndex)
  right: nextChar
  into: widthAndKernedWidth.
  nextDestX := floatDestX + (widthAndKernedWidth at: 1).
  nextDestX > rightX ifTrue: [destX ~= firstDestX ifTrue: [^stops at: CrossedX]].
  floatDestX := floatDestX + kernDelta + (widthAndKernedWidth at: 2).
  atEndOfRun
  ifTrue:[
  pendingKernX := (widthAndKernedWidth at: 2) - (widthAndKernedWidth at: 1).
  floatDestX := floatDestX - pendingKernX].
  destX := floatDestX .
  lastIndex := lastIndex + 1.
  ].
  lastIndex := stopIndex.
  ^ stops at: EndOfRun!

Item was changed:
  ----- Method: StrikeFontSet class>>installNewFontAtIndex:fromOld: (in category 'fileIn/Out') -----
  installNewFontAtIndex: newIndex fromOld: oldIndex
-
- | fontArray newArray |
  self allInstances do: [:set |
+ | fontArray newArray |
  fontArray := set fontArray.
  newIndex + 1 > fontArray size ifTrue: [
  newArray := Array new: newIndex + 1.
  newArray replaceFrom: 1 to: fontArray size with: fontArray startingAt: 1.
  newArray at: newIndex + 1 put: (fontArray at: oldIndex + 1).
  set initializeWithFontArray: newArray.
  ] ifFalse: [
  fontArray at: newIndex + 1 put: (fontArray at: oldIndex + 1).
  ].
  ].
 
  "
  StrikeFontSet installNewFontAtIndex: UnicodeSimplifiedChinese leadingChar fromOld: UnicodeJapanese leadingChar
  StrikeFontSet installNewFontAtIndex: UnicodeKorean leadingChar fromOld: UnicodeJapanese leadingChar
  "
  !

Item was changed:
  ----- Method: LanguageEditor>>selectNewerKeys (in category 'gui methods') -----
  selectNewerKeys
 
+ | translations |
- | translations index |
  self deselectAllTranslation.
  translations := self translations.
  newerKeys do: [:k |
+ | index |
  index := translations indexOf: k ifAbsent: [0].
  index > 0 ifTrue: [
  self selectedTranslationsAt: index put: true
  ].
  ].
  !

Item was changed:
  ----- Method: ImmX11>>keyboardFocusForAMorph: (in category 'keyboard') -----
  keyboardFocusForAMorph: aMorph
 
- | left bottom pos |
  aMorph ifNil: [^ self].
  [
+ | left bottom pos |
  pos := aMorph preferredKeyboardPosition.
  left := (pos x min: Display width max: 0) asInteger.
  bottom := (pos y min: Display height max: 0) asInteger
  + (aMorph paragraph
  characterBlockForIndex: aMorph editor selectionInterval first) height.
  self setCompositionWindowPositionX: left y: bottom
  ] on: Error
  do: [:ex |].
  !

Item was changed:
  ----- Method: MultiDisplayScanner>>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 |
  lastIndex = line last ifTrue: [^true].
  runX := destX.
+ runL!
- runLength := text runLe!

Item was changed:
  ----- Method: MultiCharacterBlockScanner>>scanMultiCharactersCombiningFrom:to:in:rightX:stopConditions:kern: (in category 'stop conditions') -----
  scanMultiCharactersCombiningFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta
 
  | encoding f nextDestX maxAscii startEncoding char charValue floatDestX widthAndKernedWidth nextChar |
  lastIndex := startIndex.
  lastIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops at: EndOfRun].
  startEncoding := (sourceString at: startIndex) leadingChar.
  font ifNil: [font := (TextConstants at: #DefaultMultiStyle) fontArray at: 1].
  ((font isMemberOf: StrikeFontSet) or: [font isKindOf: TTCFontSet]) ifTrue: [
+ f := [font fontArray at: startEncoding + 1]
+ on: Exception do: [:ex | nil].
- [f := font fontArray at: startEncoding + 1]
- on: Exception do: [:ex | f := font fontArray at: 1].
  f ifNil: [ f := font fontArray at: 1].
  maxAscii := f maxAscii.
  spaceWidth := f widthOf: Space.
  ] ifFalse: [
  maxAscii := font maxAscii.
  ].
  floatDestX := destX.
  widthAndKernedWidth := Array new: 2.
  [lastIndex <= stopIndex] whileTrue: [
  encoding := (sourceString at: lastIndex) leadingChar.
  encoding ~= startEncoding ifTrue: [lastIndex := lastIndex - 1. ^ stops at: EndOfRun].
  char := (sourceString at: lastIndex).
  charValue := char charCode.
  charValue > maxAscii ifTrue: [charValue := maxAscii].
  (encoding = 0 and: [(stops at: charValue + 1) ~~ nil]) ifTrue: [
  ^ stops at: charValue + 1
  ].
  nextChar := (lastIndex + 1 <= stopIndex)
  ifTrue:[sourceString at: lastIndex + 1]
  ifFalse:[nil].
  font
  widthAndKernedWidthOfLeft: ((char isMemberOf: CombinedChar) ifTrue:[char base] ifFalse:[char])
  right: nextChar
  into: widthAndKernedWidth.
  nextDestX := floatDestX + (widthAndKernedWidth at: 1).
  nextDestX > rightX ifTrue: [^ stops at: CrossedX].
  floatDestX := floatDestX + kernDelta + (widthAndKernedWidth at: 2).
  destX := floatDestX.
  lastIndex := lastIndex + 1.
  ].
  lastIndex := stopIndex.
  ^ stops at: EndOfRun!

Item was changed:
  ----- Method: SparseXTable>>tableFor: (in category 'as yet unclassified') -----
  tableFor: code
 
+ | div t |
- | div t table |
  div := code // 65536.
+ t := xTables at: div ifAbsent: [
+ | table |
+ table := Array new: 65536 withAll: 0.
+ xTables at: div put: table.
+ table].
- t := xTables at: div ifAbsent: [table := Array new: 65536 withAll: 0. xTables at: div put: table. table].
  ^ t.
  !

Item was changed:
  LanguageEnvironment subclass: #JapaneseEnvironment
  instanceVariableNames: ''
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Multilingual-Languages'!
-
- !JapaneseEnvironment commentStamp: '<historical>' prior: 0!
- This class provides the Japanese support.  Since it has been used most other than default 'latin-1' languages, this tends to be a good place to look at when you want to know what a typical subclass of LanguageEnvironment should do.
- !

Item was changed:
  ----- Method: MultiCharacterScanner>>scanJapaneseCharactersFrom:to:in:rightX:stopConditions:kern: (in category 'scanner methods') -----
  scanJapaneseCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta
 
  | ascii encoding f nextDestX startEncoding |
  lastIndex := startIndex.
  lastIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops at: EndOfRun].
  startEncoding := (sourceString at: startIndex) leadingChar.
  font ifNil: [font := (TextConstants at: #DefaultMultiStyle) fontArray at: 1].
  ((font isMemberOf: StrikeFontSet) or: [font isKindOf: TTCFontSet]) ifTrue: [
+ f := [font fontArray at: startEncoding + 1]
+ on: Exception do: [:ex | nil].
- [f := font fontArray at: startEncoding + 1]
- on: Exception do: [:ex | f := font fontArray at: 1].
  f ifNil: [ f := font fontArray at: 1].
  spaceWidth := f widthOf: Space.
  ] ifFalse: [
  (font isMemberOf: HostFont) ifTrue: [
  f := font.
  spaceWidth := f widthOf: Space.
  ].
  ].
  [lastIndex <= stopIndex] whileTrue: [
  "self halt."
  encoding := (sourceString at: lastIndex) leadingChar.
  encoding ~= startEncoding ifTrue: [lastIndex := lastIndex - 1. ^ stops at: EndOfRun].
  ascii := (sourceString at: lastIndex) charCode.
  (encoding = 0 and: [ascii < 256 and:[(stops at: ascii + 1) notNil]])
  ifTrue: [^ stops at: ascii + 1].
  (self isBreakableAt: lastIndex in: sourceString in: (EncodedCharSet charsetAt: encoding)) ifTrue: [
  self registerBreakableIndex.
  ].
  nextDestX := destX + (font widthOf: (sourceString at: lastIndex)).
  nextDestX > rightX ifTrue: [firstDestX ~= destX ifTrue: [^ stops at: CrossedX]].
  destX := nextDestX + kernDelta.
  lastIndex := lastIndex + 1.
  ].
  lastIndex := stopIndex.
  ^ stops at: EndOfRun!

Item was changed:
  ----- Method: Unicode class>>initializeCompositionMappings (in category 'composing') -----
  initializeCompositionMappings
  "Unicode initializeCompositionMappings"
- | stream |
  Compositions := IdentityDictionary new.
  Decompositions := IdentityDictionary new.
  UIManager default informUserDuring:[:bar|
+ | stream |
  bar value: 'Downloading Unicode data'.
  stream := HTTPClient httpGet: 'http://unicode.org/Public/UNIDATA/UnicodeData.txt'.
  (stream isKindOf: RWBinaryOrTextStream) ifFalse:[^self error: 'Download failed'].
  stream reset.
  bar value: 'Updating Composition Mappings'.
  self parseCompositionMappingFrom: stream.
  ].!

Item was changed:
  ----- Method: MultiDisplayScanner>>displayLines:in:clippedBy: (in category 'MVC-compatibility') -----
  displayLines: linesInterval in: aParagraph clippedBy: visibleRectangle
  "The central display routine. 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 |
- | runLength done stopCondition leftInRun startIndex string lastPos |
  "leftInRun is the # of characters left to scan in the current run;
  when 0, it is time to call 'self setStopConditions'"
  morphicOffset := 0@0.
  leftInRun := 0.
  self initializeFromParagraph: aParagraph clippedBy: visibleRectangle.
  ignoreColorChanges := false.
  paragraph := aParagraph.
  foregroundColor := paragraphColor := aParagraph foregroundColor.
  backgroundColor := aParagraph backgroundColor.
  aParagraph backgroundColor isTransparent
  ifTrue: [fillBlt := nil]
  ifFalse: [fillBlt := bitBlt copy.  "Blt to fill spaces, tabs, margins"
  fillBlt sourceForm: nil; sourceOrigin: 0@0.
  fillBlt fillColor: aParagraph backgroundColor].
  rightMargin := aParagraph rightMarginForDisplay.
  lineY := aParagraph topAtLineIndex: linesInterval first.
  bitBlt destForm deferUpdatesIn: visibleRectangle while: [
  linesInterval do:
  [:lineIndex |
+ | runLength done stopCondition startIndex string lastPos |
  leftMargin := aParagraph leftMarginForDisplayForLine: lineIndex alignment: (alignment ifNil:[textStyle alignment]).
  destX := (runX := leftMargin).
  line := aParagraph lines at: lineIndex.
  lineHeight := line lineHeight.
  fillBlt == nil ifFalse:
  [fillBlt destX: visibleRectangle left destY: lineY
  width: visibleRectangle width height: lineHeight; copyBits].
  lastIndex := line first.
  leftInRun <= 0
  ifTrue: [self setStopConditions.  "also sets the font"
  leftInRun := text runLengthFor: line first].
  baselineY := lineY + line baseline.
  destY := baselineY - font ascent.  "Should have happened in setFont"
  runLength := leftInRun.
  runStopIndex := lastIndex + (runLength - 1) min: line last.
  leftInRun := leftInRun - (runStopIndex - lastIndex + 1).
  spaceCount := 0.
  done := false.
  string := text string.
  self handleIndentation.
  [done] whileFalse:[
  startIndex := lastIndex.
  lastPos := destX@destY.
  stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
  in: string rightX: rightMargin stopConditions: stopConditions
  kern: kern.
  lastIndex >= startIndex ifTrue:[
  font displayString: string on: bitBlt
  from: startIndex to: lastIndex at: lastPos kern: kern baselineY: baselineY].
  "see setStopConditions for stopping conditions for displaying."
  done := self perform: stopCondition].
  fillBlt == nil ifFalse:
  [fillBlt destX: destX destY: lineY width: visibleRectangle right-destX height: lineHeight; copyBits].
  lineY := lineY + lineHeight]]!

Item was changed:
  ----- Method: StrikeFontSet class>>removeFontsForEncoding:encodingName: (in category 'fileIn/Out') -----
  removeFontsForEncoding: leadingChar encodingName: encodingSymbol
 
+ | insts |
- | insts fonts newFonts index |
  leadingChar = 0 ifTrue: [^ self error: 'you cannot delete the intrinsic fonts'].
  insts := self allInstances.
  insts do: [:inst |
+ | fonts newFonts index |
  fonts := inst fontArray.
  fonts size >= (leadingChar + 1) ifTrue: [
  leadingChar + 1 = fonts size ifTrue: [
  newFonts := fonts copyFrom: 1 to: fonts size - 1.
  index := newFonts indexOf: nil.
  index > 0 ifTrue: [newFonts := newFonts copyFrom: 1 to: index - 1].
  inst initializeWithFontArray: newFonts.
  ] ifFalse: [
  fonts at: leadingChar + 1 put: nil.
  ].
  ].
  ].
 
  TextConstants removeKey: encodingSymbol asSymbol ifAbsent: [].
  !

Item was changed:
  ----- Method: StrikeFontFixer>>storeEditedGlyphsOn: (in category 'as yet unclassified') -----
  storeEditedGlyphsOn: aStream
-
- | n |
  NoFontTable do: [:i |
+ | n |
  n := strikeFont name.
  (n beginsWith: 'NewYork') ifTrue: [n := 'NewYork'].
  aStream nextPutAll: '((StrikeFont familyName: ''', n, ''' size: ',
  strikeFont height asString, ')'.
  aStream nextPutAll: ' characterFormAt: '.
  aStream nextPutAll: '(Character value: ', i asString, ')'.
  aStream nextPutAll: ' put: '.
  (strikeFont characterFormAt: (Character value: i)) storeOn: aStream base: 2.
  aStream nextPutAll: ')!!'.
  aStream nextPut: Character cr.
  aStream nextPut: Character cr.
+ ].!
- ].
- !

Item was changed:
  ----- Method: StrikeFontSet class>>installExternalFontOn:encoding:encodingName:textStyleName: (in category 'fileIn/Out') -----
  installExternalFontOn: aStream encoding: encoding encodingName: aString textStyleName: styleName
 
+ | array encodingIndex textStyle |
- | array fonts encodingIndex textStyle |
 
  array := aStream
  untilEndWithFork: [(ReferenceStream on: aStream) next]
  displayingProgress: 'Font reading...'.
 
  TextConstants at: aString asSymbol put: array.
 
  textStyle := TextConstants at: styleName asSymbol.
  encodingIndex := encoding + 1.
  textStyle fontArray do: [:fs |
+ | fonts |
  fonts := fs fontArray.
  encodingIndex > fonts size
  ifTrue: [fonts :=  (Array new: encodingIndex)
  replaceFrom: 1 to: fonts size with: fonts startingAt: 1].
  fonts at: encodingIndex put: (self findMaximumLessThan: fs fontArray first in: array).
  fs initializeWithFontArray: fonts.
  ].
  !

Item was changed:
  ----- Method: StrikeFontSet class>>duplicateArrayElementsForLeadingCharShift (in category 'as yet unclassified') -----
  duplicateArrayElementsForLeadingCharShift
  "
  self duplicateArrayElementsForLeadingCharShift
  "
- | array font |
  self allInstances do: [:s |
+ | array font |
  s emphasis = 0 ifTrue: [
  array := s fontArray.
  2 to: (4 min: array size) do: [:i |
  font := array at: i.
  s addNewFont: font at: ((i - 1) << 2) + 1.
  ].
  ] ifFalse: [
  s reset
  ].
  ].
  !

Item was changed:
  ----- Method: MultiCharacterScanner>>scanMultiCharactersCombiningFrom:to:in:rightX:stopConditions:kern: (in category 'scanner methods') -----
  scanMultiCharactersCombiningFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta
 
  | charCode encoding f startEncoding combining combined combiningIndex c |
  lastIndex := startIndex.
  lastIndex > stopIndex ifTrue: [lastIndex := stopIndex. ^ stops at: EndOfRun].
  startEncoding := (sourceString at: startIndex) leadingChar.
  font ifNil: [font := (TextConstants at: #DefaultMultiStyle) fontArray at: 1].
  ((font isMemberOf: StrikeFontSet) or: [font isKindOf: TTCFontSet]) ifTrue: [
+ f := [font fontArray at: startEncoding + 1]
+ on: Exception do: [:ex | nil].
- [f := font fontArray at: startEncoding + 1]
- on: Exception do: [:ex | f := font fontArray at: 1].
  f ifNil: [ f := font fontArray at: 1].
  ].
 
  spaceWidth := font widthOf: Space.
  combining := nil.
  [lastIndex <= stopIndex] whileTrue: [
  charCode := (sourceString at: lastIndex) charCode.
  c := (sourceString at: lastIndex).
  combining ifNil: [
  combining := CombinedChar new.
  combining add: c.
  combiningIndex := lastIndex.
  lastIndex := lastIndex + 1.
  ] ifNotNil: [
  (combining add: c) ifFalse: [
  self addCharToPresentation: (combined := combining combined).
  combining := CombinedChar new.
  combining add: c.
  charCode := combined charCode.
  encoding := combined leadingChar.
  encoding ~= startEncoding ifTrue: [lastIndex := lastIndex - 1.
  (encoding = 0 and: [charCode < 256 and:[(stops at: charCode + 1) notNil]]) ifTrue: [
  ^ stops at: charCode + 1
  ] ifFalse: [
  ^ stops at: EndOfRun
  ].
  ].
  (encoding = 0 and: [charCode < 256 and:[(stops at: charCode + 1) notNil]]) ifTrue: [
  combining ifNotNil: [
  self addCharToPresentation: (combining combined).
  ].
  ^ stops at: charCode + 1
  ].
  (self isBreakableAt: lastIndex in: sourceString in: Latin1Environment) ifTrue: [
  self registerBreakableIndex.
  ].
  destX > rightX ifTrue: [
  destX ~= firstDestX ifTrue: [
  lastIndex := combiningIndex.
  self removeLastCharFromPresentation.
  ^ stops at: CrossedX]].
  combiningIndex := lastIndex.
  lastIndex := lastIndex + 1.
  ] ifTrue: [
  lastIndex := lastIndex + 1.
  numOfComposition := numOfComposition + 1.
  ].
  ].
  ].
  lastIndex := stopIndex.
  combining ifNotNil: [
  combined := combining combined.
  self addCharToPresentation: combined.
  "assuming that there is always enough space for at least one character".
  destX := destX + (self widthOf: combined inFont: font).
  ].
  ^ stops at: EndOfRun!

Item was changed:
  ----- Method: StrikeFontSet class>>installExternalFontFileName:inDir:encoding:encodingName:textStyleName: (in category 'fileIn/Out') -----
  installExternalFontFileName: fileName inDir: dir encoding: encoding encodingName: aString textStyleName: styleName
 
+ | array arrayFour oldStyle arrayOfFS |
- | array arrayFour oldStyle arrayOfFS fs fonts newFonts |
  array := (ReferenceStream on: (dir readOnlyFileNamed: fileName)) next.
 
  arrayFour := Array new: 4 withAll: array last.
  arrayFour replaceFrom: 1 to: array size with: array startingAt: 1.
  TextConstants at: aString asSymbol put: arrayFour.
 
  oldStyle := TextConstants at: styleName asSymbol.
  arrayOfFS := oldStyle fontArray.
  arrayOfFS := (1 to: 4) collect: [:i |
+ | fs fonts newFonts |
  fs := arrayOfFS at: i.
  fonts := fs fontArray.
  encoding + 1 > fonts size ifTrue: [
  newFonts := Array new: encoding + 1.
  newFonts replaceFrom: 1 to: fonts size with: fonts startingAt: 1.
  newFonts at: encoding + 1 put: (arrayFour at: i).
  fs initializeWithFontArray: newFonts.
  ] ifFalse: [
  fonts at: encoding + 1 put: (arrayFour at: i).
  ].
  fs.
  ].
 
  TextConstants at: styleName asSymbol put: (TextStyle fontArray: arrayOfFS).
  oldStyle becomeForward: (TextConstants at: styleName asSymbol).
 
  !