emphasis handling cleanup
authorClaus Gittinger <cg@exept.de>
Thu, 29 Oct 2009 15:44:48 +0100
changeset 2322 3dc982ce8487
parent 2321 6f4cc7b644db
child 2323 f9c28c6c7295
emphasis handling cleanup
Text.st
--- a/Text.st	Wed Oct 28 21:59:16 2009 +0100
+++ b/Text.st	Thu Oct 29 15:44:48 2009 +0100
@@ -11,9 +11,14 @@
 "
 "{ Package: 'stx:libbasic2' }"
 
-CharacterArray subclass:#Text
+CharacterArray variableByteSubclass:#Text
 	instanceVariableNames:'string runs'
-	classVariableNames:''
+	classVariableNames:'BackgroundColorEmphasis ColorEmphasis ItalicEmphasis BoldEmphasis
+		UnderlineEmphasis UnderwaveEmphasis OverlineEmphasis
+		StrikeoutEmphasis ReverseEmphasis BoldUnderlineEmphasis
+		BoldOverlineEmphasis BoldUnderwaveEmphasis
+		ItalicUnderlineEmphasis ItalicUnderwaveEmphasis
+		UnderlineColorEmphasis StrikeoutColorEmphasis EtchColorEmphasis'
 	poolDictionaries:''
 	category:'Collections-Text'
 !
@@ -160,7 +165,25 @@
      its implementation (indexed access).
     "
 
-    self flags:(Behavior flagRegular)
+    self flags:(Behavior flagRegular).
+
+    BackgroundColorEmphasis := #backgroundColor.
+    ColorEmphasis := #color.
+    ItalicEmphasis := #italic.
+    BoldEmphasis := #bold.
+    UnderlineEmphasis := #underline.
+    UnderwaveEmphasis := #underwave.
+    OverlineEmphasis := #overline. 
+    StrikeoutEmphasis := #strikeout.
+    ReverseEmphasis := #reverse.
+    BoldUnderlineEmphasis := #boldUnderline.
+    BoldOverlineEmphasis := #boldOverline. 
+    BoldUnderwaveEmphasis := #boldUnderwave.
+    ItalicUnderlineEmphasis := #italicUnderline. 
+    ItalicUnderwaveEmphasis := #italicUnderwave.
+    UnderlineColorEmphasis := #underlineColor. 
+    StrikeoutColorEmphasis := #strikeoutColor. 
+    EtchColorEmphasis := #etchColor.
 
     "
      Text initialize
@@ -322,6 +345,16 @@
     ^ TextStream on:(self new:100)
 ! !
 
+!Text class methodsFor:'emphasis constants'!
+
+backgroundColorEmphasis
+    ^ BackgroundColorEmphasis
+!
+
+foregroundColorEmphasis
+    ^ ColorEmphasis
+! !
+
 !Text class methodsFor:'emphasis helper'!
 
 addEmphasis:e1 to:e2
@@ -704,38 +737,38 @@
         bgPaint := savedBgPaint.
 
         emphasis isSymbol ifTrue:[
-            emphasis == #bold ifTrue:[bold := true]
-            ifFalse:[emphasis == #italic ifTrue:[italic := true]
-            ifFalse:[emphasis == #underline ifTrue:[underline := true]
-            ifFalse:[emphasis == #overline ifTrue:[overline := true]   "MB:added"
-            ifFalse:[emphasis == #underwave ifTrue:[underwave := true]
-            ifFalse:[emphasis == #strikeout ifTrue:[strikeout := true]
-            ifFalse:[emphasis == #reverse ifTrue:[reverse := true]
-            ifFalse:[emphasis == #boldUnderline ifTrue:[bold := underline := true]
-            ifFalse:[emphasis == #boldOverline ifTrue:[bold := overline := true]     "MB:added"
-            ifFalse:[emphasis == #boldUnderwave ifTrue:[bold := underwave := true]
-            ifFalse:[emphasis == #italicUnderline ifTrue:[italic := underline := true]
-            ifFalse:[emphasis == #italicUnderwave ifTrue:[italic := underwave := true]
+            emphasis == BoldEmphasis ifTrue:[bold := true]
+            ifFalse:[emphasis == ItalicEmphasis ifTrue:[italic := true]
+            ifFalse:[emphasis == UnderlineEmphasis ifTrue:[underline := true]
+            ifFalse:[emphasis == OverlineEmphasis ifTrue:[overline := true]   "MB:added"
+            ifFalse:[emphasis == UnderwaveEmphasis ifTrue:[underwave := true]
+            ifFalse:[emphasis == StrikeoutEmphasis ifTrue:[strikeout := true]
+            ifFalse:[emphasis == ReverseEmphasis ifTrue:[reverse := true]
+            ifFalse:[emphasis == BoldUnderlineEmphasis ifTrue:[bold := underline := true]
+            ifFalse:[emphasis == BoldOverlineEmphasis ifTrue:[bold := overline := true]     "MB:added"
+            ifFalse:[emphasis == BoldUnderwaveEmphasis ifTrue:[bold := underwave := true]
+            ifFalse:[emphasis == ItalicUnderlineEmphasis ifTrue:[italic := underline := true]
+            ifFalse:[emphasis == ItalicUnderwaveEmphasis ifTrue:[italic := underwave := true]
             ]]]]]]]]]]]
         ] ifFalse:[
             (emphasis isMemberOf:Association) ifTrue:[
                 value := emphasis value.
                 value notNil ifTrue:[
                     k := emphasis key.
-                    k == #color ifTrue:[
+                    k == ColorEmphasis ifTrue:[
                         color := value onDevice:device.
                         emphasis value:color.
-                    ] ifFalse:[k == #backgroundColor ifTrue:[
+                    ] ifFalse:[k == BackgroundColorEmphasis ifTrue:[
                         bgPaint := value onDevice:device.
                         emphasis value:bgPaint.
                         opaque := true.
-                    ] ifFalse:[k == #underlineColor ifTrue:[
+                    ] ifFalse:[k == UnderlineColorEmphasis ifTrue:[
                         ulPaint := value onDevice:device.
                         emphasis value:ulPaint.
-                    ] ifFalse:[k == #strikeoutColor ifTrue:[
+                    ] ifFalse:[k == StrikeoutColorEmphasis ifTrue:[
                         strikePaint := value onDevice:device.
                         emphasis value:strikePaint.
-                    ] ifFalse:[k == #etchColor ifTrue:[
+                    ] ifFalse:[k == EtchColorEmphasis ifTrue:[
                         etchColor := value onDevice:device.
                         emphasis value:etchColor.
                     ]]]]]
@@ -743,41 +776,42 @@
             ] ifFalse:[
                 emphasis notNil ifTrue:[
                     emphasis do:[:entry |
-                        entry == #bold ifTrue:[bold := true]
-                        ifFalse:[entry == #italic ifTrue:[italic := true]
-                        ifFalse:[entry == #underline ifTrue:[underline := true]
-                        ifFalse:[entry == #underwave ifTrue:[underwave := true]
-                        ifFalse:[entry == #strikeout ifTrue:[strikeout := true]
-                        ifFalse:[entry == #reverse ifTrue:[reverse := true]
-                        ifFalse:[entry == #boldUnderline ifTrue:[bold := underline := true]
-                        ifFalse:[emphasis == #boldUnderwave ifTrue:[bold := underwave := true]
-                        ifFalse:[entry == #italicUnderline ifTrue:[italic := underline := true]
-                        ifFalse:[emphasis == #italicUnderwave ifTrue:[italic := underwave := true]
+                        entry == BoldEmphasis ifTrue:[bold := true]
+                        ifFalse:[entry == ItalicEmphasis ifTrue:[italic := true]
+                        ifFalse:[entry == UnderlineEmphasis ifTrue:[underline := true]
+                        ifFalse:[entry == OverlineEmphasis ifTrue:[overline := true] 
+                        ifFalse:[entry == UnderwaveEmphasis ifTrue:[underwave := true]
+                        ifFalse:[entry == StrikeoutEmphasis ifTrue:[strikeout := true]
+                        ifFalse:[entry == ReverseEmphasis ifTrue:[reverse := true]
+                        ifFalse:[entry == BoldUnderlineEmphasis ifTrue:[bold := underline := true]
+                        ifFalse:[emphasis == BoldUnderwaveEmphasis ifTrue:[bold := underwave := true]
+                        ifFalse:[entry == ItalicUnderlineEmphasis ifTrue:[italic := underline := true]
+                        ifFalse:[emphasis == ItalicUnderwaveEmphasis ifTrue:[italic := underwave := true]
                         ifFalse:[
                             (entry isMemberOf:Association) ifTrue:[
                                 value := entry value.
                                 value notNil ifTrue:[
                                     k := entry key.
-                                    k == #color ifTrue:[
+                                    k == ColorEmphasis ifTrue:[
                                         color := value onDevice:device.
                                         entry value:color.
-                                    ] ifFalse:[k == #backgroundColor ifTrue:[
+                                    ] ifFalse:[k == BackgroundColorEmphasis ifTrue:[
                                         bgPaint := value onDevice:device.
                                         entry value:bgPaint.
                                         opaque := true.
-                                    ] ifFalse:[k == #underlineColor ifTrue:[
+                                    ] ifFalse:[k == UnderlineColorEmphasis ifTrue:[
                                         ulPaint := value onDevice:device.
                                         entry value:ulPaint.
-                                    ] ifFalse:[k == #strikeoutColor ifTrue:[
+                                    ] ifFalse:[k == StrikeoutColorEmphasis ifTrue:[
                                         strikePaint := value onDevice:device.
                                         entry value:strikePaint.
-                                    ] ifFalse:[k == #etchColor ifTrue:[
+                                    ] ifFalse:[k == EtchColorEmphasis ifTrue:[
                                         etchColor := value onDevice:device.
                                         entry value:etchColor.
                                     ]]]]]
                                 ]
                             ]
-                        ]]]]]]]]]]
+                        ]]]]]]]]]]]
                     ]
                 ]
             ]
@@ -850,7 +884,7 @@
             ulPaint notNil ifTrue:[aGC paint:ulPaint].
             yL := y-(font heightOf: string) + 2.
             aGC displayLineFromX:x y:yL toX:x+l-1 y:yL
-        ].                                                 "MB:added ^"
+        ].                                               "MB:added ^"
         underwave ifTrue:[
             ulPaint notNil ifTrue:[aGC paint:ulPaint].
             yL := y+1.
@@ -896,7 +930,7 @@
 allBold
     "make all characters bold"
 
-    self emphasizeAllWith:#bold
+    self emphasizeAllWith:BoldEmphasis
 
     "
      (Text string:'hello') allBold
@@ -907,15 +941,15 @@
 !
 
 allBoldOverline
-    "make all characters overline"
+    "make all characters bold and overline"
 
-    self emphasizeAllWith:#boldOverline
+    self emphasizeAllWith:BoldOverlineEmphasis
 !
 
 allItalic
     "make all characters italic"
 
-    self emphasizeAllWith:#italic
+    self emphasizeAllWith:ItalicEmphasis
 
     "
      (Text string:'hello') allItalic
@@ -928,13 +962,17 @@
 allOverline
     "make all characters overline"
 
-    self emphasizeAllWith:#overline
+    self emphasizeAllWith:OverlineEmphasis
+
+    "
+     Transcript showCR: ('hello' asText allOverline)   
+    "
 !
 
 allStrikedOut
     "strikeOut all characters"
 
-    self emphasisAllAdd:#strikeout.
+    self emphasisAllAdd:StrikeoutEmphasis.
 
     "
      Transcript showCR: ('hello' allStrikedOut)   
@@ -944,17 +982,27 @@
 allUnderlined
     "underline all characters"
 
-    self emphasisAllAdd:#underline.
+    self emphasisAllAdd:UnderlineEmphasis.
 
     "
      Transcript showCR:('hello' allUnderlined) 
     "
 !
 
+allUnderwaved
+    "underwave all characters"
+
+    self emphasisAllAdd:UnderwaveEmphasis.
+
+    "
+     Transcript showCR:('hello' asText allUnderwaved) 
+    "
+!
+
 backgroundColorizeAllWith:aColor
     "change the bc-color of all characters"
 
-    self emphasisAllAdd:(#backgroundColor -> aColor).
+    self emphasisAllAdd:(BackgroundColorEmphasis -> aColor).
 
     "
      Transcript showCR:
@@ -974,7 +1022,7 @@
 colorizeAllWith:aColor
     "change the color of all characters"
 
-    self emphasisAllAdd:(#color -> aColor).
+    self emphasisAllAdd:(ColorEmphasis -> aColor).
 
     "
      Transcript showCR:
@@ -997,8 +1045,8 @@
 colorizeAllWith:fgColor on:bgColor
     "change the color and bg-color of all characters"
 
-    self emphasisAllAdd:(#color -> fgColor).
-    self emphasisAllAdd:(#backgroundColor -> bgColor).
+    self emphasisAllAdd:(ColorEmphasis -> fgColor).
+    self emphasisAllAdd:(BackgroundColorEmphasis -> bgColor).
 
     "
      Transcript showCR:
@@ -1290,7 +1338,7 @@
 strikeoutAll
     "strikeout all characters"
 
-    self emphasisAllAdd:(#strikeout).
+    self emphasisAllAdd:StrikeoutEmphasis.
 
     "
      Transcript showCR:
@@ -1298,11 +1346,20 @@
     "
 !
 
+withoutAnyColorEmphasis
+    ^ (self withoutEmphasis:BackgroundColorEmphasis) withoutEmphasis:ColorEmphasis
+!
+
+withoutBackgroundColorEmphasis
+    ^ self withoutEmphasis:BackgroundColorEmphasis
+!
+
 withoutEmphasis:emphasisToRemove 
-    |newText|
+    |newText anyEmphasis|
 
     self hasChangeOfEmphasis ifTrue:[
         newText := self copyFrom:1 to:self size.
+        anyEmphasis := false.
         1 to:newText size do:[:col |
             |em newem|
 
@@ -1310,13 +1367,19 @@
             em notNil ifTrue:[
                 newem := Text removeEmphasis:emphasisToRemove from:em.
                 newem ~~ em ifTrue:[
-                    newText emphasisAt:col put:newem
+                    newText emphasisAt:col put:newem.
+                    newem notNil ifTrue:[ anyEmphasis := true ].
                 ]
             ].
         ].
+        anyEmphasis ifFalse:[^ newText string].
         ^ newText
     ].
     ^ self
+!
+
+withoutForegroundColorEmphasis
+    ^ self withoutEmphasis:ColorEmphasis
 ! !
 
 
@@ -1682,11 +1745,11 @@
 !Text class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic2/Text.st,v 1.104 2009-10-22 17:33:36 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic2/Text.st,v 1.105 2009-10-29 14:44:48 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic2/Text.st,v 1.104 2009-10-22 17:33:36 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic2/Text.st,v 1.105 2009-10-29 14:44:48 cg Exp $'
 ! !
 
 Text initialize!