ListView.st
changeset 2557 dabeb8404df8
parent 2513 c480b6ee5cc7
child 2558 4c10bec1117d
--- a/ListView.st	Thu Jul 18 11:25:22 2002 +0200
+++ b/ListView.st	Tue Jul 23 14:40:29 2002 +0200
@@ -1538,11 +1538,11 @@
     sH := lineSpacing // 2.
 
     backgroundAlreadyClearedColor == bg ifFalse:[
-	self paint:bg.
-	self fillRectangleX:margin 
-			  y:y-sH
-		      width:(width - (margin * 2))
-		     height:(endVisLineNr - startVisLineNr + 1) * fontHeight + (lineSpacing - sH).
+        self paint:bg.
+        self fillRectangleX:margin 
+                          y:y-sH
+                      width:(width - (margin * 2))
+                     height:(endVisLineNr - startVisLineNr + 1) * fontHeight + (lineSpacing - sH).
     ].
     list isNil ifTrue:[^ self].
 
@@ -1552,28 +1552,28 @@
     startLine := startVisLineNr + firstLineShown - 1.
     endLine := endVisLineNr + firstLineShown - 1.
     (startLine == 0) ifTrue:[
-	y := y + fontHeight.
-	startLine := startLine + 1
+        y := y + fontHeight.
+        startLine := startLine + 1
     ].
 
     (endLine > listSize) ifTrue:[
-	e := listSize
+        e := listSize
     ] ifFalse:[
-	e := endLine
+        e := endLine
     ].
 
     (startLine <= e) ifTrue:[
-	x := textStartLeft - viewOrigin x.
-	self paint:fg on:bg.
-	self from:startLine to:e do:[:line |
-	    line notNil ifTrue:[
-		"/ remove lines color emphasis, to enforce color.
-		"/ otherwise blue text is not visible if selection-bg is blue
-		l := self withoutColorEmphasis:line ifFg:fg andBg:bg.
-		self displayOpaqueString:l x:x y:y
-	    ].
-	    y := y + fontHeight
-	]
+        x := textStartLeft - viewOrigin x.
+        self paint:fg on:bg.
+        self from:startLine to:e do:[:line |
+            line notNil ifTrue:[
+                "/ remove lines color emphasis, to enforce color.
+                "/ otherwise blue text is not visible if selection-bg is blue
+                l := self withoutColorEmphasis:line ifFg:fg andBg:bg.
+                self displayOpaqueString:l x:x y:y
+            ].
+            y := y + fontHeight
+        ]
     ]
 
     "Modified: / 15.12.1999 / 23:19:39 / cg"
@@ -1630,20 +1630,14 @@
     "Modified: / 15.12.1999 / 23:19:55 / cg"
 !
 
-drawLine:line inVisible:visLineNr with:fg and:bg
-    "draw a given string at visible lines position in fg/bg"
-
-    self drawLine:line atX:(textStartLeft - viewOrigin x) inVisible:visLineNr with:fg and:bg
-!
-
-drawVisibleLine:visLineNr col:col with:fg and:bg
+drawLine:lineStringArg inVisible:visLineNr col:col with:fg and:bg
     "draw single character at col index of visible line in fg/bg"
 
-    |y yf x lineString characterString em w clr|
-
-    lineString := self visibleAt:visLineNr.
+    |y yf x lineString characterString w|
+
+    lineString := lineStringArg.
     (lineString notNil and:[lineString isString not]) ifTrue:[
-	^ self drawVisibleLine:visLineNr with:fg and:bg
+        ^ self drawVisibleLine:visLineNr with:fg and:bg
     ].
 
     x := (self xOfCol:col inVisibleLine:visLineNr) - viewOrigin x.
@@ -1652,128 +1646,161 @@
 
     yf := y - (lineSpacing // 2).
     col > lineString size ifTrue:[
-	self fillRectangleX:x y:yf width:(font width) height:fontHeight.
-	self paint:fg
+        self fillRectangleX:x y:yf width:(font width) height:fontHeight.
+        self paint:fg
     ] ifFalse:[
-	characterString := lineString copyFrom:col to:col.
-
-	"/ remove lines color emphasis, to enforce color.
-	"/ otherwise blue text is not visible if selection-bg is blue
-	characterString := self withoutColorEmphasis:characterString ifFg:fg andBg:bg.
-	w := characterString widthOn:self.
-
-	self fillRectangleX:x y:yf 
-		      width:w
-		     height:fontHeight.
-	self paint:fg.
-	self displayString:characterString x:x y:(y + fontAscent)
+        characterString := lineString copyFrom:col to:col.
+
+        "/ remove lines color emphasis, to enforce color.
+        "/ otherwise blue text is not visible if selection-bg is blue
+        characterString := self withoutColorEmphasis:characterString ifFg:fg andBg:bg.
+        w := characterString widthOn:self.
+
+        self fillRectangleX:x y:yf 
+                      width:w
+                     height:fontHeight.
+        self paint:fg.
+        self displayString:characterString x:x y:(y + fontAscent)
     ]
 
     "Modified: / 15.12.1999 / 23:21:12 / cg"
 !
 
-drawVisibleLine:visLineNr from:startCol to:endCol with:fg and:bg
+drawLine:lineStringArg inVisible:visLineNr from:startCol to:endCol with:fg and:bg
     "draw part of a visible line in fg/bg"
 
     |y yf x lineString len characterString w sCol eCol|
 
     (endCol >= startCol) ifTrue:[
-	sCol := startCol max:1.
-
-	lineString := self visibleAt:visLineNr.
-
-	(lineString notNil and:[lineString isString not])
-	ifTrue:[
-	    self drawVisibleLine:visLineNr with:fg and:bg.
-	] ifFalse:[
-	    x := (self xOfCol:sCol inVisibleLine:visLineNr) - viewOrigin x.
-	    y := (self yOfVisibleLine:visLineNr).
-	    yf := y - (lineSpacing // 2).
-	    len := lineString size.
-
-	    (sCol > len) ifTrue:[
-		backgroundAlreadyClearedColor == bg ifFalse:[
-		    len := endCol - sCol + 1.
-		    self paint:bg.
-		    self fillRectangleX:x y:yf 
-				   width:(fontWidth * len) 
-				  height:fontHeight
-		]
-	    ] ifFalse:[
-		eCol := endCol.
-		(endCol > len) ifTrue:[
-		    backgroundAlreadyClearedColor == bg ifFalse:[
-			characterString := lineString species new:endCol.
-			characterString replaceFrom:1 to:len with:lineString startingAt:1.
-			lineString := characterString.
-		    ] ifTrue:[
-			eCol := len.
-		    ].
-		].
-
-		"/ remove any color emphasis, to enforce drawing in fg/bg
-
-		lineString := self withoutColorEmphasis:lineString ifFg:fg andBg:bg.
-		backgroundAlreadyClearedColor == bg ifFalse:[
-		    (lineString isMemberOf:String) ifTrue:[
-			fontIsFixedWidth ifTrue:[
-			    w := (eCol - sCol + 1) * fontWidth
-			] ifFalse:[
-			    w := font widthOf:lineString from:sCol to:eCol
-			]
-		    ] ifFalse:[
-			w := (lineString copyFrom:sCol to:eCol) widthOn:self
-		    ].
-		    self paint:bg.
-		    self fillRectangleX:x y:yf 
-				  width:w
-				  height:fontHeight.
-		].
-		self paint:fg on:bg.
-		self displayOpaqueString:lineString from:sCol to:eCol x:x y:(y + fontAscent)
-	    ]
-	]
+        sCol := startCol max:1.
+
+        lineString := lineStringArg.
+
+        (lineString notNil and:[lineString isString not])
+        ifTrue:[
+            self drawVisibleLine:visLineNr with:fg and:bg.
+        ] ifFalse:[
+            x := (self xOfCol:sCol inVisibleLine:visLineNr) - viewOrigin x.
+            y := (self yOfVisibleLine:visLineNr).
+            yf := y - (lineSpacing // 2).
+            len := lineString size.
+
+            (sCol > len) ifTrue:[
+                backgroundAlreadyClearedColor == bg ifFalse:[
+                    len := endCol - sCol + 1.
+                    self paint:bg.
+                    self fillRectangleX:x y:yf 
+                                   width:(fontWidth * len) 
+                                  height:fontHeight
+                ]
+            ] ifFalse:[
+                eCol := endCol.
+                (endCol > len) ifTrue:[
+                    backgroundAlreadyClearedColor == bg ifFalse:[
+                        characterString := lineString species new:endCol.
+                        characterString replaceFrom:1 to:len with:lineString startingAt:1.
+                        lineString := characterString.
+                    ] ifTrue:[
+                        eCol := len.
+                    ].
+                ].
+
+                "/ remove any color emphasis, to enforce drawing in fg/bg
+
+                lineString := self withoutColorEmphasis:lineString ifFg:fg andBg:bg.
+                backgroundAlreadyClearedColor == bg ifFalse:[
+                    (lineString isMemberOf:String) ifTrue:[
+                        fontIsFixedWidth ifTrue:[
+                            w := (eCol - sCol + 1) * fontWidth
+                        ] ifFalse:[
+                            w := font widthOf:lineString from:sCol to:eCol
+                        ]
+                    ] ifFalse:[
+                        w := (lineString copyFrom:sCol to:eCol) widthOn:self
+                    ].
+                    self paint:bg.
+                    self fillRectangleX:x y:yf 
+                                  width:w
+                                  height:fontHeight.
+                ].
+                self paint:fg on:bg.
+                self displayOpaqueString:lineString from:sCol to:eCol x:x y:(y + fontAscent)
+            ]
+        ]
     ]
 
     "Modified: / 15.12.1999 / 23:21:43 / cg"
 !
 
-drawVisibleLine:visLineNr from:startCol with:fg and:bg
+drawLine:lineString inVisible:visLineNr from:startCol with:fg and:bg
     "draw right part of a visible line from startCol to end of line in fg/bg"
 
-    |y x lineString index1 index2|
+    |y x index1 index2 lineWithoutColor|
 
     (startCol < 1) ifTrue:[
-	index1 := 1
+        index1 := 1
     ] ifFalse:[
-	index1 := startCol
+        index1 := startCol
     ].
     y := self yOfVisibleLine:visLineNr.
     x := (self xOfCol:index1 inVisibleLine:visLineNr) - viewOrigin x.
     backgroundAlreadyClearedColor == bg ifFalse:[
-	self paint:bg.
-	self fillRectangleX:x y:y - (lineSpacing // 2)
-		      width:(width + viewOrigin x - x)
-		     height:fontHeight.
+        self paint:bg.
+        self fillRectangleX:x y:y - (lineSpacing // 2)
+                      width:(width + viewOrigin x - x)
+                     height:fontHeight.
     ].
-    lineString := self visibleAt:visLineNr.
     lineString notNil ifTrue:[
-	lineString isString ifFalse:[
-	    self drawVisibleLine:visLineNr with:fg and:bg.
-	] ifTrue:[
-	    lineString := self withoutColorEmphasis:lineString ifFg:fg andBg:bg.
-	    index2 := lineString size.
-	    (index2 < index1) ifTrue:[^ self].
-	    (index1 <= index2) ifTrue:[
-		self paint:fg on:bg.
-		self displayOpaqueString:lineString from:index1 to:index2 x:x y:(y + fontAscent)
-	    ]
-	]
+        lineString isString ifFalse:[
+            self drawVisibleLine:visLineNr with:fg and:bg.
+        ] ifTrue:[
+            lineWithoutColor := self withoutColorEmphasis:lineString ifFg:fg andBg:bg.
+            index2 := lineWithoutColor size.
+            (index2 < index1) ifTrue:[^ self].
+            (index1 <= index2) ifTrue:[
+                self paint:fg on:bg.
+                self displayOpaqueString:lineWithoutColor from:index1 to:index2 x:x y:(y + fontAscent)
+            ]
+        ]
     ]
 
     "Modified: / 15.12.1999 / 23:24:40 / cg"
 !
 
+drawLine:line inVisible:visLineNr with:fg and:bg
+    "draw a given string at visible lines position in fg/bg"
+
+    self drawLine:line atX:(textStartLeft - viewOrigin x) inVisible:visLineNr with:fg and:bg
+!
+
+drawVisibleLine:visLineNr col:col with:fg and:bg
+    "draw single character at col index of visible line in fg/bg"
+
+    self
+        drawLine:(self visibleAt:visLineNr)
+        inVisible:visLineNr 
+        col:col 
+        with:fg and:bg
+!
+
+drawVisibleLine:visLineNr from:startCol to:endCol with:fg and:bg
+    "draw part of a visible line in fg/bg"
+
+    self
+        drawLine:(self visibleAt:visLineNr) 
+        inVisible:visLineNr 
+        from:startCol to:endCol 
+        with:fg and:bg
+!
+
+drawVisibleLine:visLineNr from:startCol with:fg and:bg
+    "draw right part of a visible line from startCol to end of line in fg/bg"
+
+    self
+        drawLine:(self visibleAt:visLineNr) 
+        inVisible:visLineNr from:startCol with:fg and:bg
+!
+
 drawVisibleLine:visLineNr with:fg and:bg
     "draw a visible line in fg/bg"
 
@@ -2461,6 +2488,33 @@
     "Modified: 5.3.1997 / 16:14:44 / cg"
 !
 
+line:line withoutEmphasis:which 
+    |l|
+
+    l := line.
+
+    (line notNil 
+    and:[line isString
+    and:[line hasChangeOfEmphasis]]) ifTrue:[
+        l := line copyFrom:1 to:line size.
+        1 to:line size do:[:col |
+            |em newem|
+
+            em := (l emphasis) at:col.
+            em notNil ifTrue:[
+                newem := Text removeEmphasis:which from:em.
+                newem ~~ em ifTrue:[
+                    l emphasisAt:col put:newem
+                ]
+            ].
+        ].
+    ].
+    ^ l
+
+    "Modified: / 15.12.1999 / 23:17:30 / cg"
+    "Created: / 15.12.1999 / 23:19:30 / cg"
+!
+
 lineOfCharacterPosition:charPos
     "given a character index within the contents-string,
      return the lineNumber where the character is
@@ -2724,61 +2778,28 @@
     ^ max
 !
 
+withoutAnyColorEmphasis:line
+    ^ self withoutBackgroundColorEmphasis:(self withoutColorEmphasis:line)
+!
+
+withoutBackgroundColorEmphasis:line
+    ^ self line:line withoutEmphasis:#backgroundColor
+!
+
 withoutColorEmphasis:line
-    |l|
-
-    l := line.
-
-    "/ remove lines color emphasis, to enforce color.
-    "/ otherwise blue text is not visible if selection-bg is blue
-    (line notNil 
-    and:[line isString
-    and:[line hasChangeOfEmphasis]]) ifTrue:[
-	l := line copyFrom:1 to:line size.
-	1 to:line size do:[:col |
-	    |em clr|
-
-	    em := (l emphasis) at:col.
-	    em notNil ifTrue:[
-		clr := Text extractEmphasis:#color from:em.
-		clr notNil ifTrue:[
-		    em := Text removeEmphasis:(#color->clr) from:em.
-		    l emphasisAt:col put:em
-		]
-	    ].
-	].
-    ].
-    ^ l
-
-    "Modified: / 15.12.1999 / 23:17:30 / cg"
+    ^ self line:line withoutEmphasis:#color
 !
 
 withoutColorEmphasis:line ifFg:fg andBg:bg
-    |l|
-
-    l := line.
-
     "/ remove lines color emphasis, to enforce color.
     "/ otherwise blue text is not visible if selection-bg is blue
     (line notNil 
     and:[line isString
     and:[line hasChangeOfEmphasis
     and:[fg ~= fgColor or:[bg ~= bgColor]]]]) ifTrue:[
-	l := line copyFrom:1 to:line size.
-	1 to:line size do:[:col |
-	    |em clr|
-
-	    em := (l emphasis) at:col.
-	    em notNil ifTrue:[
-		clr := Text extractEmphasis:#color from:em.
-		clr notNil ifTrue:[
-		    em := Text removeEmphasis:(#color->clr) from:em.
-		    l emphasisAt:col put:em
-		]
-	    ].
-	].
+        ^ self line:line withoutEmphasis:#color
     ].
-    ^ l
+    ^ line
 
     "Modified: / 15.12.1999 / 23:17:30 / cg"
     "Created: / 15.12.1999 / 23:19:30 / cg"
@@ -4415,5 +4436,5 @@
 !ListView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg/ListView.st,v 1.263 2002-02-11 09:59:37 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg/ListView.st,v 1.264 2002-07-23 12:40:29 cg Exp $'
 ! !