*** empty log message *** delegated_gc
authorStefan Vogel <sv@exept.de>
Wed, 16 Mar 2016 17:26:17 +0100
branchdelegated_gc
changeset 7215 53d6c2df7b06
parent 7056 9792ad4eab13
child 7412 d4b5f3114373
*** empty log message ***
XftFontDescription.st
--- a/XftFontDescription.st	Wed Nov 11 14:12:03 2015 +0100
+++ b/XftFontDescription.st	Wed Mar 16 17:26:17 2016 +0100
@@ -1,10 +1,9 @@
+'From Smalltalk/X, Version:6.2.5.0 on 17-12-2014 at 18:03:00'                   !
+
 "{ Package: 'stx:libview' }"
 
-"{ NameSpace: Smalltalk }"
-
 FontDescription subclass:#XftFontDescription
-	instanceVariableNames:'device fontId sharedDrawId closestFont minCode maxCode ascent
-		descent height'
+	instanceVariableNames:'device fontId sharedDrawId closestFont minCode maxCode'
 	classVariableNames:'FC_FAMILY FC_STYLE FC_SLANT FC_WEIGHT FC_SIZE FC_ASPECT
 		FC_PIXEL_SIZE FC_SPACING FC_FOUNDRY FC_ANTIALIAS FC_HINTING
 		FC_HINT_STYLE FC_VERTICAL_LAYOUT FC_AUTOHINT FC_WIDTH FC_FILE
@@ -312,21 +311,6 @@
 
     |proto|
 
-    RecentlyUsedFonts notNil ifTrue:[
-	proto := RecentlyUsedFonts
-		detect:[:fn |
-		    fn family = familyString
-		    and:[ fn size = size and:[fn sizeUnit = sizeUnit
-		    and:[ fn face = faceString
-		    and:[ (fn style = styleString
-			  or:[ (fn style = 'oblique' and:[styleString = 'italic'])
-			  or:[ (fn style = 'italic' and:[styleString = 'oblique']) ]]) ]]]]]
-		ifNone:nil.
-	proto notNil ifTrue:[
-	    ^ proto
-	].
-    ].
-
     CachedFontList notNil ifTrue:[
 	proto := CachedFontList
 		detect:[:fn |
@@ -439,7 +423,7 @@
 !XftFontDescription methodsFor:'accessing'!
 
 encoding
-    ^ encoding ? 'iso10646-1'
+    ^ encoding ? #'iso10646-1'
 !
 
 face
@@ -552,15 +536,15 @@
 asNonXftFont
     |newFont|
 
-    newFont := FontDescription
-		    family:family
-		    face:face
-		    style:style
-		    size:(sizeUnit == #px ifTrue:[pixelSize] ifFalse:[size])
-		    sizeUnit:sizeUnit
-		    encoding:encoding.
+    newFont := FontDescription 
+                    family:family 
+                    face:face 
+                    style:style 
+                    size:(sizeUnit == #px ifTrue:[pixelSize] ifFalse:[size]) 
+                    sizeUnit:sizeUnit
+                    encoding:encoding.
 
-    ^ newFont
+    ^ newFont 
 ! !
 
 !XftFontDescription methodsFor:'displaying'!
@@ -568,88 +552,80 @@
 displayString:aString from:index1 to:index2Arg x:xArg y:yArg in:aGC opaque:opaque
     "display a partial string at some position in aGC."
 
-    |index2 bytesPerCharacter transformation
-     clipR clipX clipY clipW clipH clipPnt
-     fg fgR fgG fgB fgA fgPixel bg bgR bgG bgB bgA bgPixel
-     drawX drawY drawPnt displayId screen drawableId error  stringLen|
+    |index2 bytesPerCharacter transformation clipR clipX clipY clipW clipH fg fgR fgG fgB fgA fgPixel
+     bg bgR bgG bgB bgA bgPixel drawX drawY displayId screen drawableId error stringLen|
 
     "limit the string len, otherwise bad output is generated"
     stringLen := index2Arg - index1 + 1.
     stringLen > 8000 ifTrue:[
-	index2 := index1 + 8000 - 1.
+        index2 := index1 + 8000 - 1.
     ]  ifFalse:[
-	stringLen <= 0 ifTrue:[^ self].
-	index2 := index2Arg.
+        stringLen <= 0 ifTrue:[^ self].
+        index2 := index2Arg.
     ].
     bytesPerCharacter := aString bitsPerCharacter // 8.
     transformation := aGC transformation.
 
-    clipR := aGC clippingBoundsOrNil.
+    clipR := aGC deviceClippingBoundsOrNil.
     clipR notNil ifTrue:[
-	clipX := clipR left.
-	clipY := clipR top.
-	clipW := clipR width.
-	clipH := clipR height.
-	"/ YES YES YES: this MUST be transformed!!
-	"/ (see htmlView) fix the notebook, please.
-	transformation notNil ifTrue:[
-	    clipPnt := transformation transformPoint:(clipX @ clipY).
-	    clipX := clipPnt x ceiling.
-	    clipY := clipPnt y ceiling.
+        clipX := clipR left.
+        clipY := clipR top.
+        clipW := clipR width.
+        clipH := clipR height.
+clipW > 32767 ifTrue:['clipW > 32767 ' errorPrintCR. clipW errorPrintCR. self halt. clipW := 32767].
+(clipX > 16384 or:[clipX < -16384]) ifTrue:['clipX < 16384 ' errorPrintCR. clipX errorPrintCR.].
+        "/ YES YES YES: this MUST be transformed!!
+        "/ (see htmlView) fix the notebook, please.
+"/        transformation notNil ifTrue:[
 "/            clipX := (transformation applyToX:clipX) ceiling.
 "/            clipY := (transformation applyToY:clipY) ceiling.
-	].
+"/        ].
     ].
 
     transformation isNil ifTrue:[
-	drawX := xArg.
-	drawY := yArg.
+        drawX := xArg.
+        drawY := yArg.
     ] ifFalse:[
-	drawPnt := transformation transformPoint:(xArg @ yArg).
-	drawX := drawPnt x ceiling.
-	drawY := drawPnt y ceiling.
-"/        drawX := (transformation applyToX:xArg) ceiling.
-"/        drawY := (transformation applyToY:yArg) ceiling.
+        drawX := (transformation applyToX:xArg) ceiling.
+        drawY := (transformation applyToY:yArg) ceiling.
     ].
 
     fg  :=  aGC paint.
     fgPixel := fg colorId.
-    "/ fgPixel notNil ifTrue:[
-	fgR := fg scaledRed.
-	fgG := fg scaledGreen.
-	fgB := fg scaledBlue.
-	fgA := (fg alpha * 65535) rounded.
-    "/].
-    fgR isNil ifTrue:[
-	"/ when drawing into a pixmap...
-	fg colorId == 0 ifTrue:[
-	    fgR := fgG := fgB := 0.
-	] ifFalse:[
-	    fgR := fgG := fgB := 16rFFFF.
-	]
+    fgA := fg scaledAlpha.
+    fgR := fg scaledRed.
+    fgR notNil ifTrue:[
+        fgG := fg scaledGreen.
+        fgB := fg scaledBlue.
+    ] ifFalse:[
+        "/ when drawing into a pixmap...
+        fgPixel == 0 ifTrue:[
+            fgR := fgG := fgB := 0.
+        ] ifFalse:[
+            fgR := fgG := fgB := 16rFFFF.
+        ]
     ].
 
     opaque ifTrue:[
-	bg  := aGC backgroundPaint.
-	bgPixel := bg colorId.
-	"/bgPixel notNil ifTrue:[
-	    bgR := bg scaledRed.
-	    bgG := bg scaledGreen.
-	    bgB := bg scaledBlue.
-	    bgA := (bg alpha * 65535) rounded.
-	"/].
-	bgR isNil ifTrue:[
-	    "/ when drawing into a pixmap...
-	    bg colorId == 0 ifTrue:[
-		bgR := bgG := bgB := 0.
-	    ] ifFalse:[
-		bgR := bgG := bgB := 16rFFFF.
-	    ]
-	].
+        bg  := aGC backgroundPaint.
+        bgPixel := bg colorId.
+        bgA := bg scaledAlpha.
+        bgR := bg scaledRed.
+        bgR notNil ifTrue:[
+            bgG := bg scaledGreen.
+            bgB := bg scaledBlue.
+        ] ifFalse:[
+            "/ when drawing into a pixmap...
+            bgPixel == 0 ifTrue:[
+                bgR := bgG := bgB := 0.
+            ] ifFalse:[
+                bgR := bgG := bgB := 16rFFFF.
+            ]
+        ].
     ].
     displayId := device displayIdOrErrorIfBroken.
     displayId isNil ifTrue:[
-	^ self.
+        ^ self.
     ].
     screen := device screen.
     drawableId := aGC drawableId.
@@ -666,102 +642,103 @@
     int __bytesPerCharacter;
 
     if (!(__bothSmallInteger(drawX, drawY)
-	  && __bothSmallInteger(index1, index2)
-	  && __isSmallInteger(bytesPerCharacter)
-	  && (__isSmallInteger(fgPixel) || (__bothSmallInteger(fgR, fgG) && __bothSmallInteger(fgB, fgA)))
-	  && (opaque == false || __isSmallInteger(bgPixel) || (__bothSmallInteger(bgR, bgG) && __bothSmallInteger(bgB, bgA)))
-	  && __isNonNilObject(aString)
+          && __bothSmallInteger(index1, index2)
+          && __isSmallInteger(bytesPerCharacter)
+          && (__isSmallInteger(fgPixel) || (__bothSmallInteger(fgR, fgG) && __bothSmallInteger(fgB, fgA)))
+          && (opaque == false || __isSmallInteger(bgPixel) || (__bothSmallInteger(bgR, bgG) && __bothSmallInteger(bgB, bgA)))
+          && __isNonNilObject(aString)
     )) {
-	goto err;
+        goto err;
     }
 
     __bytesPerCharacter = __intVal(bytesPerCharacter);
 
     if ( __INST(sharedDrawId) == nil ) {
-	__INST(sharedDrawId) = XFT_DRAW_HANDLE_NEW ( XftDrawCreate ( DISPLAY( displayId ) ,
-					       DRAWABLE( drawableId ) ,
-					       DefaultVisual( DISPLAY( displayId), SCREEN (screen) ) ,
-					       DefaultColormap( DISPLAY( displayId), SCREEN (screen) ) ) );
-	__STORE(self, __INST(sharedDrawId));
+        __INST(sharedDrawId) = XFT_DRAW_HANDLE_NEW ( XftDrawCreate ( DISPLAY( displayId ) ,
+                                               DRAWABLE( drawableId ) ,
+                                               DefaultVisual( DISPLAY( displayId), SCREEN (screen) ) ,
+                                               DefaultColormap( DISPLAY( displayId), SCREEN (screen) ) ) );
+        __STORE(self, __INST(sharedDrawId));
     }
 
     if ( XftDrawDrawable ( XFT_DRAW ( __INST(sharedDrawId) ) ) != DRAWABLE( drawableId ) ) {
-	XftDrawChange( XFT_DRAW( __INST(sharedDrawId) ) , DRAWABLE( drawableId ) );
+        XftDrawChange( XFT_DRAW( __INST(sharedDrawId) ) , DRAWABLE( drawableId ) );
     }
 
     string = __stringVal( aString ) + (( __intVal(index1) - 1 ) * __bytesPerCharacter);
     len = __intVal(index2) - __intVal(index1) + 1;
 
     if (clipR != nil) {
-	clipRX.x = __intVal(clipX);
-	clipRX.y = __intVal(clipY);
-	clipRX.width = __intVal(clipW);
-	clipRX.height = __intVal(clipH);
-	XftDrawSetClipRectangles( XFT_DRAW( __INST( sharedDrawId ) ) , 0, 0, &clipRX, 1);
+        clipRX.x = __intVal(clipX);
+        clipRX.y = __intVal(clipY);
+        clipRX.width = __intVal(clipW);
+        clipRX.height = __intVal(clipH);
+        XftDrawSetClipRectangles( XFT_DRAW( __INST( sharedDrawId ) ) , 0, 0, &clipRX, 1);
     } else {
-	XftDrawSetClip( XFT_DRAW( __INST( sharedDrawId ) ) , 0);
+        XftDrawSetClip( XFT_DRAW( __INST( sharedDrawId ) ) , 0);
     }
 
     if (opaque == true) {
-	if (bgPixel != nil) {
-	    color.pixel = (unsigned long)__intVal(bgPixel);
-	}
-	// else {
-	    color.color.red = __intVal(bgR);
-	    color.color.green = __intVal(bgG);
-	    color.color.blue = __intVal(bgB);
-	    color.color.alpha = __intVal(bgA);
-	// }
-	switch (__bytesPerCharacter) {
-	case 1:
-	    XftTextExtents8( DISPLAY( displayId ), XFT_FONT( __INST( fontId ) ), (FcChar8*)string, len, &extents);
-	    break;
-	case 2:
-	    XftTextExtents16( DISPLAY( displayId ), XFT_FONT( __INST( fontId ) ), (FcChar16*)string, len, &extents);
-	    break;
-	case 4:
-	    XftTextExtents32( DISPLAY( displayId ), XFT_FONT( __INST( fontId ) ), (FcChar32*)string, len, &extents);
-	    break;
-	}
-	XftDrawRect( XFT_DRAW ( __INST( sharedDrawId ) ), &color, __intVal(drawX) - extents.x, __intVal(drawY) - XFT_FONT( __INST( fontId ) )->ascent, extents.width, XFT_FONT(__INST (fontId ) )->height);
+        if (bgPixel != nil) {
+            color.pixel = (unsigned long)__intVal(bgPixel);
+        }
+        // else {
+            color.color.red = __intVal(bgR);
+            color.color.green = __intVal(bgG);
+            color.color.blue = __intVal(bgB);
+            color.color.alpha = __intVal(bgA);
+        // }
+        switch (__bytesPerCharacter) {
+        case 1:
+            XftTextExtents8( DISPLAY( displayId ), XFT_FONT( __INST( fontId ) ), (FcChar8*)string, len, &extents);
+            break;
+        case 2:
+            XftTextExtents16( DISPLAY( displayId ), XFT_FONT( __INST( fontId ) ), (FcChar16*)string, len, &extents);
+            break;
+        case 4:
+            XftTextExtents32( DISPLAY( displayId ), XFT_FONT( __INST( fontId ) ), (FcChar32*)string, len, &extents);
+            break;
+        }
+if (extents.width < 0) printf("width: %d  < 0\n", extents.width);
+        XftDrawRect( XFT_DRAW ( __INST( sharedDrawId ) ), &color, __intVal(drawX) - extents.x, __intVal(drawY) - XFT_FONT( __INST( fontId ) )->ascent, extents.width, XFT_FONT(__INST (fontId ) )->height);
     }
     if (fgPixel != nil) {
-	color.pixel = (unsigned long)__intVal(fgPixel);
+        color.pixel = (unsigned long)__intVal(fgPixel);
     }
     // else {
-	color.color.red = __intVal(fgR);
-	color.color.green = __intVal(fgG);
-	color.color.blue = __intVal(fgB);
-	color.color.alpha = __intVal(fgA);
+        color.color.red = __intVal(fgR);
+        color.color.green = __intVal(fgG);
+        color.color.blue = __intVal(fgB);
+        color.color.alpha = __intVal(fgA);
     // }
     switch (__bytesPerCharacter) {
     case 1:
-	XftDrawString8( XFT_DRAW ( __INST( sharedDrawId ) ), &color, XFT_FONT( __INST( fontId ) ),
-			__intVal(drawX),
-			__intVal(drawY),
-			(FcChar8*)string,
-			len);
-	RETURN ( self );
-	break;
+        XftDrawString8( XFT_DRAW ( __INST( sharedDrawId ) ), &color, XFT_FONT( __INST( fontId ) ),
+                        __intVal(drawX),
+                        __intVal(drawY),
+                        (FcChar8*)string,
+                        len);
+        RETURN ( self );
+        break;
     case 2:
-	XftDrawString16( XFT_DRAW ( __INST( sharedDrawId ) ), &color, XFT_FONT( __INST( fontId ) ),
-			__intVal(drawX),
-			__intVal(drawY),
-			(FcChar16*)string,
-			len);
-	RETURN ( self );
-	break;
+        XftDrawString16( XFT_DRAW ( __INST( sharedDrawId ) ), &color, XFT_FONT( __INST( fontId ) ),
+                        __intVal(drawX),
+                        __intVal(drawY),
+                        (FcChar16*)string,
+                        len);
+        RETURN ( self );
+        break;
     case 4:
-	XftDrawString32( XFT_DRAW ( __INST( sharedDrawId ) ), &color, XFT_FONT( __INST( fontId ) ),
-			__intVal(drawX),
-			__intVal(drawY),
-			(FcChar32*)string,
-			len);
-	RETURN ( self );
-	break;
+        XftDrawString32( XFT_DRAW ( __INST( sharedDrawId ) ), &color, XFT_FONT( __INST( fontId ) ),
+                        __intVal(drawX),
+                        __intVal(drawY),
+                        (FcChar32*)string,
+                        len);
+        RETURN ( self );
+        break;
     }
+#endif
     err:;
-#endif
 %}.
     self primitiveFailed: error.
 
@@ -841,6 +818,8 @@
         ].
     ].
 
+^ self asNonXftFont onDevice:aGraphicsDevice.
+
     [
         Error handle:[:ex |
             ^ self asNonXftFont onDevice:aGraphicsDevice
@@ -851,7 +830,7 @@
         pixelSize notNil ifTrue:[
             self xftPatternAdd: myPatternId attribute: FC_PIXEL_SIZE value: pixelSize.
         ] ifFalse:[
-            self xftPatternAdd: myPatternId attribute: FC_SIZE value: (size isNil ifTrue:[nil] ifFalse:[size rounded]).
+            self xftPatternAdd: myPatternId attribute: FC_SIZE value: size.
         ].
         self xftPatternAdd: myPatternId attribute: FC_WEIGHT value: (StXFace2FCWeightMap at: (face ? 'regular')).
         self xftPatternAdd: myPatternId attribute: FC_SLANT value: (StXStyle2FCSlantMap at: (style ? 'roman') ifAbsent:[StXStyle2FCSlantMap at: (style ? 'roman') asLowercase]).
@@ -929,16 +908,17 @@
     device := deviceArg.
     fontId := fontIdArg.
     patternIdArg notNil ifTrue:[
-	family  := self xftPatternGet: patternIdArg attribute: FC_FAMILY index: 0.
-	size    := self xftPatternGet: patternIdArg attribute: FC_SIZE index: 0.
-	face    := self xftPatternGet: patternIdArg attribute: FC_WEIGHT index: 0.
-	face    := StXFace2FCWeightMap keyAtValue: face.
-	style   := self xftPatternGet: patternIdArg attribute: FC_SLANT index: 0.
-	style   := StXStyle2FCSlantMap keyAtValue: style.
+        family  := self xftPatternGet: patternIdArg attribute: FC_FAMILY index: 0.
+        size    := self xftPatternGet: patternIdArg attribute: FC_SIZE index: 0.
+        face    := self xftPatternGet: patternIdArg attribute: FC_WEIGHT index: 0.
+        face    := StXFace2FCWeightMap keyAtValue: face.
+        style   := self xftPatternGet: patternIdArg attribute: FC_SLANT index: 0.
+        style   := StXStyle2FCSlantMap keyAtValue: style.
 
-	name:= self xftPatternGet: patternIdArg attribute: 'fullname' index: 0.
+        name:= self xftPatternGet: patternIdArg attribute: 'fullname' index: 0.
 
-	encoding:= self xftPatternGet: patternIdArg attribute: 'encoding' index: 0.
+        encoding:= self xftPatternGet: patternIdArg attribute: 'encoding' index: 0.
+        encoding notNil ifTrue:[encoding := encoding asSymbol].
     ].
 
     "Created: / 21-12-2013 / 00:46:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -1131,7 +1111,7 @@
 %{
 #ifdef XFT
     int _start, _stop;
-    int __x, __y;
+    int _x, _y;
     XftColor clr;
     if ( ! __isExternalAddressLike(drawIdArg) ) {
 	error = @symbol(BadArg1);
@@ -1145,12 +1125,12 @@
 	error = @symbol(BadArg4);
 	goto err;
     }
-    __x = __intVal(x);
+    _x = __intVal(x);
     if ( ! __isSmallInteger(y) ) {
 	error = @symbol(BadArg5);
 	goto err;
     }
-    __y = __intVal(y);
+    _y = __intVal(y);
 
 
     if ( ! __isSmallInteger(start) ) {
@@ -1172,7 +1152,7 @@
 
     if ( __isStringLike(text) ) {
 	XftDrawString8(XFT_DRAW(drawIdArg), &clr, XFT_FONT(fontIdArg),
-			__x, __y,
+			_x, _y,
 			__stringVal(text) + (_start - 1), _stop - _start + 1);
 	RETURN ( self );
     } else {
@@ -1638,10 +1618,8 @@
 
 ascent
     "return the ascent - the number of pixels above the baseLine."
-    ascent isNil ifTrue:[
-	ascent := self xftFontGetAscent: fontId
-    ].
-    ^ ascent
+
+    ^ self xftFontGetAscent: fontId
 
     "Created: / 21-12-2013 / 01:19:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -1649,10 +1627,7 @@
 descent
     "return the descent - the number of pixels below the baseLine."
 
-    descent isNil ifTrue:[
-	 descent := self xftFontGetDescent: fontId
-    ].
-    ^ descent
+    ^ self xftFontGetDescent: fontId
 
     "Created: / 21-12-2013 / 01:20:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -1683,10 +1658,7 @@
 height
     "return the height - the number of pixels above plus below the baseLine."
 
-    height isNil ifTrue:[
-	height := self xftFontGetHeight: fontId
-    ].
-    ^ height
+    ^ self xftFontGetHeight: fontId
 
     "Created: / 21-12-2013 / 01:20:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -1730,10 +1702,26 @@
 widthOf:aString from:start to:stop
     "return the width of a sub string"
 
-    | extents |
+    |extents maxWidthOfSingleGlyph|
 
     (stop < start) ifTrue:[^ 0].
-    extents := self xftTextExtents: device displayId font: fontId string: aString from: start to: stop.
+    maxWidthOfSingleGlyph := self maxWidth.
+    "xOff from XFTTextExtents is a signed short.
+     Work arond for long strings"
+    (stop - start + 1) * maxWidthOfSingleGlyph > 32767 ifTrue:[
+        |total chunkSize|
+
+        chunkSize := (32767 // maxWidthOfSingleGlyph) - 1.
+        total := 0.
+        start to:stop by:chunkSize do:[:eachChunkStart|
+            extents := self xftTextExtents:device displayId font:fontId string:aString 
+                            from:eachChunkStart to:((eachChunkStart+chunkSize-1) min:stop).
+            "/ extents --> #(width height x y xOff yOff)
+            total := total + extents fifth.
+        ].
+        ^ total.
+    ].    
+    extents := self xftTextExtents: device displayId font:fontId string:aString from:start to:stop.
     "/ extents --> #(width height x y xOff yOff)
     ^ extents fifth.
 
@@ -1811,51 +1799,51 @@
     list := OrderedCollection new.
 
     readEntry :=
-	[
-	    |key|
+        [
+            |key|
 
-	    [l startsWith:'Pattern has'] whileFalse:[
-	      l := pipeStream nextLine. Transcript showCR:l.
-	    ].
+            [l startsWith:'Pattern has'] whileFalse:[
+              l := pipeStream nextLine. Transcript showCR:l.
+            ].
 
-	    currentDescription := XftFontDescription new.
-	    [ l := pipeStream nextLine. l notEmptyOrNil ] whileTrue:[
-		"/ Transcript showCR:l.
-		lineStream := l readStream. lineStream skipSeparators.
-		key := lineStream upToSeparator.
-		(
-		    #('family:' 'style:' 'slant:' 'weight:' 'width:'
-		      'pixelsize:' 'spacing:' 'foundry:' 'antialias:'
-		      'file:' 'outline' 'scalable:' 'charset:' 'lang:'
-		      'fontversion:' 'fontformat:' 'decorative:' 'index:'
-		      'outline:' 'familylang:' 'stylelang:' 'fullname:'
-		      'fullnamelang:' 'capability:' 'hash:' 'postscriptname:'
-		    ) includes:key
-		) ifTrue:[
-		    self perform:('fc_',(key allButLast)) asSymbol
-		] ifFalse:[
-		    Transcript show:'Xft ignored line: '; showCR:l.
-		    self breakPoint:#cg.
-		].
-	    ].
-	    list add:currentDescription
-	].
+            currentDescription := XftFontDescription new.
+            [ l := pipeStream nextLine. l notEmptyOrNil ] whileTrue:[
+                "/ Transcript showCR:l.
+                lineStream := l readStream. lineStream skipSeparators.
+                key := lineStream upToSeparator.
+                (
+                    #('family:' 'style:' 'slant:' 'weight:' 'width:'
+                      'pixelsize:' 'spacing:' 'foundry:' 'antialias:'
+                      'file:' 'outline' 'scalable:' 'charset:' 'lang:'
+                      'fontversion:' 'fontformat:' 'decorative:' 'index:'
+                      'outline:' 'familylang:' 'stylelang:' 'fullname:'
+                      'fullnamelang:' 'capability:' 'hash:' 'postscriptname:'
+                    ) includes:key
+                ) ifTrue:[
+                    self perform:('fc_',(key allButLast)) asSymbol
+                ] ifFalse:[
+                    Transcript show:'Xft ignored line: '; showCR:l.
+                    self breakPoint:#cg.
+                ].
+            ].
+            list add:currentDescription
+        ].
 
     fcListProg := #('/usr/bin/fc-list' '/usr/X11/bin/fc-list') detect:[:eachProg|
-			eachProg asFilename isExecutableProgram
-		    ] ifNone:[
-			'XftFontDescription [warning]: fc-list program not found - no XFT fonts' errorPrintCR.
-			^ list.
-		    ].
+                        eachProg asFilename isExecutableProgram
+                    ] ifNone:[
+                        'XftFontDescription [warning]: fc-list program not found - no XFT fonts' errorPrintCR.
+                        ^ list.
+                    ].
 
     pipeStream := PipeStream readingFrom:fcListProg, ' -v'.
     [
-	[pipeStream atEnd] whileFalse:[
-	    l := pipeStream nextLine.
-	    readEntry value.
-	]
+        [pipeStream atEnd] whileFalse:[
+            l := pipeStream nextLine.
+            readEntry value.
+        ]
     ] ensure:[
-	pipeStream close
+        pipeStream close
     ].
     ^ list
 
@@ -2100,11 +2088,11 @@
 !XftFontDescription class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/XftFontDescription.st,v 1.69 2015-03-28 11:52:01 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libview/XftFontDescription.st,v 1.69 2015-03-28 11:52:01 cg Exp $'
+    ^ '$Header$'
 ! !