XftFontDescription.st
branchdelegated_gc_jv
changeset 6819 f91377f97414
parent 6800 f4acb46ba42e
parent 6712 76690799863c
child 6821 0e2fb9a04314
--- a/XftFontDescription.st	Thu Feb 19 06:21:17 2015 +0000
+++ b/XftFontDescription.st	Tue Mar 03 03:55:48 2015 +0000
@@ -1,7 +1,8 @@
 "{ Package: 'stx:libview' }"
 
 FontDescription subclass:#XftFontDescription
-	instanceVariableNames:'device fontId sharedDrawId closestFont minCode maxCode'
+	instanceVariableNames:'device fontId sharedDrawId closestFont minCode maxCode ascent
+		descent height'
 	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
@@ -152,6 +153,19 @@
     [see also:]
 
 "
+!
+
+version
+    ^ '$Header: /cvs/stx/stx/libview/XftFontDescription.st,v 1.68 2014-12-22 00:44:58 cg Exp $'
+!
+
+version_CVS
+    ^ '$Header: /cvs/stx/stx/libview/XftFontDescription.st,v 1.68 2014-12-22 00:44:58 cg Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
 !XftFontDescription class methodsFor:'initialization'!
@@ -309,6 +323,21 @@
 
     |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 |
@@ -534,15 +563,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'!
@@ -551,41 +580,48 @@
     "display a partial string at some position in aGC."
 
     |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 drawId drawIdIsShared error stringLen|
+     bg bgR bgG bgB bgA bgPixel drawX drawY displayId screen drawableId drawId drawIdIsShared error stringLen drawPnt clipPnt |
+
 
     "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 deviceClippingBoundsOrNil.
     clipR notNil ifTrue:[
-        clipX := clipR left.
-        clipY := clipR top.
-        clipW := clipR width.
-        clipH := clipR height.
+	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.
-        ].
+	"/ 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 := (transformation applyToX:clipX) ceiling.
+"/            clipY := (transformation applyToY:clipY) ceiling.
+	].
     ].
 
     transformation isNil ifTrue:[
-        drawX := xArg.
-        drawY := yArg.
+	drawX := xArg.
+	drawY := yArg.
     ] ifFalse:[
-        drawX := (transformation applyToX:xArg) ceiling.
-        drawY := (transformation applyToY:yArg) ceiling.
+	drawPnt := transformation transformPoint:(xArg @ yArg).
+	drawX := drawPnt x ceiling.
+	drawY := drawPnt y ceiling.
+"/        drawX := (transformation applyToX:xArg) ceiling.
+"/        drawY := (transformation applyToY:yArg) ceiling.
     ].
 
     fg  :=  aGC paint.
@@ -593,58 +629,58 @@
     fgA := fg scaledAlpha.
     fgR := fg scaledRed.
     fgR notNil ifTrue:[
-        fgG := fg scaledGreen.
-        fgB := fg scaledBlue.
+	fgG := fg scaledGreen.
+	fgB := fg scaledBlue.
     ] ifFalse:[
-        "/ when drawing into a pixmap...
-        fgPixel == 0 ifTrue:[
-            fgR := fgG := fgB := 0.
-        ] ifFalse:[
-            fgR := fgG := fgB := 16rFFFF.
-        ]
+	"/ 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.
-        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.
-            ]
-        ].
+	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.
 
     aGC class == XGraphicsContext ifTrue:[
-        "/ TODO: Following should be done atomically together with drawing...    
-        drawId := aGC xftDrawId.
-        drawIdIsShared := false. 
-        drawId isNil ifTrue:[ 
+	"/ TODO: Following should be done atomically together with drawing...
+	drawId := aGC xftDrawId.
+	drawIdIsShared := false.
+	drawId isNil ifTrue:[
 %{
-            drawId = XFT_DRAW_HANDLE_NEW ( XftDrawCreate ( DISPLAY( displayId ) ,
-                                          DRAWABLE( drawableId ) ,
-                                          DefaultVisual( DISPLAY( displayId), SCREEN (screen) ) ,
-                                          DefaultColormap( DISPLAY( displayId), SCREEN (screen) ) ) );
+	    drawId = XFT_DRAW_HANDLE_NEW ( XftDrawCreate ( DISPLAY( displayId ) ,
+					  DRAWABLE( drawableId ) ,
+					  DefaultVisual( DISPLAY( displayId), SCREEN (screen) ) ,
+					  DefaultColormap( DISPLAY( displayId), SCREEN (screen) ) ) );
 %}.
-            aGC xftDrawId: drawId.
-        ].
-    ] ifFalse:[ 
-        Logger log: 'GC passed to XftGraphicsContext is not an XGraphicsContext!!' severity: #error.
-        drawId := sharedDrawId.
-        drawIdIsShared := true. 
+	    aGC xftDrawId: drawId.
+	].
+    ] ifFalse:[
+	Logger log: 'GC passed to XftGraphicsContext is not an XGraphicsContext!!' severity: #error.
+	drawId := sharedDrawId.
+	drawIdIsShared := true.
     ].
 
 %{
@@ -659,100 +695,100 @@
     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 (drawIdIsShared == true) {
-        if ( __INST(sharedDrawId) == nil ) {
-            drawId = __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 ) );
-        }
+	if ( __INST(sharedDrawId) == nil ) {
+	    drawId = __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 ) );
+	}
     }
 
     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( drawId  ) , 0, 0, &clipRX, 1);
+	clipRX.x = __intVal(clipX);
+	clipRX.y = __intVal(clipY);
+	clipRX.width = __intVal(clipW);
+	clipRX.height = __intVal(clipH);
+	XftDrawSetClipRectangles( XFT_DRAW( drawId  ) , 0, 0, &clipRX, 1);
     } else {
-        XftDrawSetClip( XFT_DRAW( drawId  ) , 0);
+	XftDrawSetClip( XFT_DRAW( drawId  ) , 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 ( drawId ), &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;
+	}
+	XftDrawRect( XFT_DRAW ( drawId ), &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 ( drawId ), &color, XFT_FONT( __INST( fontId ) ),
-                        __intVal(drawX),
-                        __intVal(drawY),
-                        (FcChar8*)string,
-                        len);
-        RETURN ( self );
-        break;
+	XftDrawString8( XFT_DRAW ( drawId ), &color, XFT_FONT( __INST( fontId ) ),
+			__intVal(drawX),
+			__intVal(drawY),
+			(FcChar8*)string,
+			len);
+	RETURN ( self );
+	break;
     case 2:
-        XftDrawString16( XFT_DRAW ( drawId ), &color, XFT_FONT( __INST( fontId ) ),
-                        __intVal(drawX),
-                        __intVal(drawY),
-                        (FcChar16*)string,
-                        len);
-        RETURN ( self );
-        break;
+	XftDrawString16( XFT_DRAW ( drawId ), &color, XFT_FONT( __INST( fontId ) ),
+			__intVal(drawX),
+			__intVal(drawY),
+			(FcChar16*)string,
+			len);
+	RETURN ( self );
+	break;
     case 4:
-        XftDrawString32( XFT_DRAW ( drawId ), &color, XFT_FONT( __INST( fontId ) ),
-                        __intVal(drawX),
-                        __intVal(drawY),
-                        (FcChar32*)string,
-                        len);
-        RETURN ( self );
-        break;
+	XftDrawString32( XFT_DRAW ( drawId ), &color, XFT_FONT( __INST( fontId ) ),
+			__intVal(drawX),
+			__intVal(drawY),
+			(FcChar32*)string,
+			len);
+	RETURN ( self );
+	break;
     }
 #endif
     err:;
@@ -801,101 +837,101 @@
     (device == aGraphicsDevice) ifTrue:[^ self].
 
     (aGraphicsDevice isNil and:[device notNil]) ifTrue:[
-        ^ self
+	^ self
     ].
     aGraphicsDevice supportsXFTFonts ifFalse:[
-        ^ super onDevice:aGraphicsDevice
+	^ super onDevice:aGraphicsDevice
     ].
 
     (closestFont notNil and:[closestFont graphicsDevice == aGraphicsDevice]) ifTrue:[
-        ^ closestFont onDevice: aGraphicsDevice.
+	^ closestFont onDevice: aGraphicsDevice.
     ].
 
     RecentlyUsedFonts isNil ifTrue:[
-        RecentlyUsedFonts := OrderedCollection new:10.
+	RecentlyUsedFonts := OrderedCollection new:10.
     ].
 
     RecentlyUsedFonts keysAndValuesDo:[:index :aFont |
-        ((aFont class == self class) and:[(self sameDeviceFontAs:aFont) and:[aFont getFontId notNil]]) ifTrue:[
-            "/ Transcript showCR:'hit'.
-            RecentlyUsedFonts removeIndex:index.
-            RecentlyUsedFonts addFirst:aFont.
-            ^ aFont
-        ]
+	((aFont class == self class) and:[(self sameDeviceFontAs:aFont) and:[aFont getFontId notNil]]) ifTrue:[
+	    "/ Transcript showCR:'hit'.
+	    RecentlyUsedFonts removeIndex:index.
+	    RecentlyUsedFonts addFirst:aFont.
+	    ^ aFont
+	]
     ].
 
     RecentlyUsedFonts size > 20 ifTrue:[
-        RecentlyUsedFonts removeLast.
+	RecentlyUsedFonts removeLast.
     ].
 
     aGraphicsDevice deviceFonts do:[:aFont |
-        ((aFont class == self class) and:[self sameDeviceFontAs:aFont]) ifTrue:[
-            RecentlyUsedFonts addFirst:aFont.
-            ^ aFont
-        ].
+	((aFont class == self class) and:[self sameDeviceFontAs:aFont]) ifTrue:[
+	    RecentlyUsedFonts addFirst:aFont.
+	    ^ aFont
+	].
     ].
 
     [
-        Error handle:[:ex |
-            ^ self asNonXftFont onDevice:aGraphicsDevice
-        ] do:[
-            myPatternId := self xftPatternCreate.
-        ].
-        self xftPatternAdd: myPatternId attribute: FC_FAMILY  value: family.
-        pixelSize notNil ifTrue:[
-            self xftPatternAdd: myPatternId attribute: FC_PIXEL_SIZE value: pixelSize.
-        ] ifFalse:[
-            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]).
+	Error handle:[:ex |
+	    ^ self asNonXftFont onDevice:aGraphicsDevice
+	] do:[
+	    myPatternId := self xftPatternCreate.
+	].
+	self xftPatternAdd: myPatternId attribute: FC_FAMILY  value: family.
+	pixelSize notNil ifTrue:[
+	    self xftPatternAdd: myPatternId attribute: FC_PIXEL_SIZE value: pixelSize.
+	] ifFalse:[
+	    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]).
 
-        newFontId := self xftFontOpenPattern: aGraphicsDevice displayId pattern: myPatternId.
-        newFontId notNil ifTrue:[
-            "/ Good, this font exists!!
-            fontId := newFontId.
-            device := aGraphicsDevice.
-            aGraphicsDevice registerFont:self.
-            RecentlyUsedFonts addFirst:self.
-            ^ self.
-        ] ifFalse:[
-            closestPatternId1 := self xftFontMatch: aGraphicsDevice displayId screen: aGraphicsDevice screen pattern: myPatternId.
-            closestPatternId1 isNil ifTrue:[
-                self error: 'No font matches'.
-            ].
-            "
-            self xftPatternGet: closestPatternId attribute: 'family' index: 0.
-            self xftPatternGet: closestPatternId attribute: 'size' index: 0.
-            "
-            closestPatternId2 := self xftPatternDuplicate: closestPatternId1.
-            newFontId := self xftFontOpenPattern: aGraphicsDevice displayId pattern: closestPatternId1.
-            "/ !!!!!!!! closestPatternId is no longer valid !!!!!!!!
-            closestPatternId1 :=  nil.
-            newFontId isNil ifTrue:[
-                self error: 'Pattern matched, but font could not be opened (should not happen)'.
-            ].
+	newFontId := self xftFontOpenPattern: aGraphicsDevice displayId pattern: myPatternId.
+	newFontId notNil ifTrue:[
+	    "/ Good, this font exists!!
+	    fontId := newFontId.
+	    device := aGraphicsDevice.
+	    aGraphicsDevice registerFont:self.
+	    RecentlyUsedFonts addFirst:self.
+	    ^ self.
+	] ifFalse:[
+	    closestPatternId1 := self xftFontMatch: aGraphicsDevice displayId screen: aGraphicsDevice screen pattern: myPatternId.
+	    closestPatternId1 isNil ifTrue:[
+		self error: 'No font matches'.
+	    ].
+	    "
+	    self xftPatternGet: closestPatternId attribute: 'family' index: 0.
+	    self xftPatternGet: closestPatternId attribute: 'size' index: 0.
+	    "
+	    closestPatternId2 := self xftPatternDuplicate: closestPatternId1.
+	    newFontId := self xftFontOpenPattern: aGraphicsDevice displayId pattern: closestPatternId1.
+	    "/ !!!!!!!! closestPatternId is no longer valid !!!!!!!!
+	    closestPatternId1 :=  nil.
+	    newFontId isNil ifTrue:[
+		self error: 'Pattern matched, but font could not be opened (should not happen)'.
+	    ].
 
-            "/ Search for existing registered font. Note, that XftFont instances
-            "/ are shared (and refcounted) so newFontId = aFont getFontId is enough
-            "/ to check whether some other font instance represents the same font...
-            aGraphicsDevice deviceFonts do:[:aFont |
-                ((self class == aFont class) and:[newFontId = aFont getFontId]) ifTrue:[
-                    closestFont := aFont.
-                    ^ closestFont
-                ].
-            ].
+	    "/ Search for existing registered font. Note, that XftFont instances
+	    "/ are shared (and refcounted) so newFontId = aFont getFontId is enough
+	    "/ to check whether some other font instance represents the same font...
+	    aGraphicsDevice deviceFonts do:[:aFont |
+		((self class == aFont class) and:[newFontId = aFont getFontId]) ifTrue:[
+		    closestFont := aFont.
+		    ^ closestFont
+		].
+	    ].
 
-            closestFont := self shallowCopy
-                                setDevice: aGraphicsDevice patternId: closestPatternId2 fontId: newFontId;
-                                yourself.
-            aGraphicsDevice registerFont: closestFont.
-            RecentlyUsedFonts addFirst:closestFont.
-            ^ closestFont
-        ].
+	    closestFont := self shallowCopy
+				setDevice: aGraphicsDevice patternId: closestPatternId2 fontId: newFontId;
+				yourself.
+	    aGraphicsDevice registerFont: closestFont.
+	    RecentlyUsedFonts addFirst:closestFont.
+	    ^ closestFont
+	].
     ] ensure:[
-        myPatternId notNil ifTrue:[self xftPatternDestroy: myPatternId].
-        closestPatternId1 notNil ifTrue:[self xftPatternDestroy: closestPatternId1].
-        closestPatternId2 notNil ifTrue:[self xftPatternDestroy: closestPatternId2].
+	myPatternId notNil ifTrue:[self xftPatternDestroy: myPatternId].
+	closestPatternId1 notNil ifTrue:[self xftPatternDestroy: closestPatternId1].
+	closestPatternId2 notNil ifTrue:[self xftPatternDestroy: closestPatternId2].
     ].
 
     "
@@ -923,17 +959,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 notNil ifTrue:[encoding := encoding asSymbol].
+	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>"
@@ -1126,7 +1162,7 @@
 %{
 #ifdef XFT
     int _start, _stop;
-    int _x, _y;
+    int __x, __y;
     XftColor clr;
     if ( ! __isExternalAddressLike(drawIdArg) ) {
 	error = @symbol(BadArg1);
@@ -1140,12 +1176,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) ) {
@@ -1167,7 +1203,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 {
@@ -1633,8 +1669,10 @@
 
 ascent
     "return the ascent - the number of pixels above the baseLine."
-
-    ^ self xftFontGetAscent: fontId
+    ascent isNil ifTrue:[
+	ascent := self xftFontGetAscent: fontId
+    ].
+    ^ ascent
 
     "Created: / 21-12-2013 / 01:19:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -1642,7 +1680,10 @@
 descent
     "return the descent - the number of pixels below the baseLine."
 
-    ^ self xftFontGetDescent: fontId
+    descent isNil ifTrue:[
+	 descent := self xftFontGetDescent: fontId
+    ].
+    ^ descent
 
     "Created: / 21-12-2013 / 01:20:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -1673,7 +1714,10 @@
 height
     "return the height - the number of pixels above plus below the baseLine."
 
-    ^ self xftFontGetHeight: fontId
+    height isNil ifTrue:[
+	height := self xftFontGetHeight: fontId
+    ].
+    ^ height
 
     "Created: / 21-12-2013 / 01:20:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -1724,18 +1768,18 @@
     "xOff from XFTTextExtents is a signed short.
      Work arond for long strings"
     (stop - start + 1) * maxWidthOfSingleGlyph > 32767 ifTrue:[
-        |total chunkSize|
+	|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.
-    ].    
+	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.
@@ -1814,51 +1858,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,20 +2144,5 @@
     ^ (lineStream upTo:$").
 ! !
 
-!XftFontDescription class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/libview/XftFontDescription.st,v 1.51.2.2 2015-01-29 09:54:04 stefan Exp $'
-!
-
-version_CVS
-    ^ '$Header: /cvs/stx/stx/libview/XftFontDescription.st,v 1.51.2.2 2015-01-29 09:54:04 stefan Exp $'
-!
-
-version_HG
-
-    ^ '$Changeset: <not expanded> $'
-! !
-
 
 XftFontDescription initialize!