Again: remove RecentlyUseFont (rely on larger CachedRegistry)
authorStefan Vogel <sv@exept.de>
Wed, 28 Sep 2016 10:23:39 +0200
changeset 7589 91aab751f507
parent 7588 fde403dd9571
child 7590 3ea1659eaa70
Again: remove RecentlyUseFont (rely on larger CachedRegistry) Release device font when closed. Cache font width.
XftFontDescription.st
--- a/XftFontDescription.st	Tue Sep 27 15:10:57 2016 +0200
+++ b/XftFontDescription.st	Wed Sep 28 10:23:39 2016 +0200
@@ -1,11 +1,11 @@
-"{ Encoding: utf8 }"
+'From Smalltalk/X, Version:7.1.0.0 on 22-09-2016 at 11:18:23'                   !
 
 "{ Package: 'stx:libview' }"
 
 "{ NameSpace: Smalltalk }"
 
 FontDescription subclass:#XftFontDescription
-	instanceVariableNames:'device fontId sharedDrawId minCode maxCode ascent descent height
+	instanceVariableNames:'device fontId width minCode maxCode ascent descent height
 		fixedWidth'
 	classVariableNames:'FC_FAMILY FC_STYLE FC_SLANT FC_WEIGHT FC_SIZE FC_ASPECT
 		FC_PIXEL_SIZE FC_SPACING FC_FOUNDRY FC_ANTIALIAS FC_HINTING
@@ -30,7 +30,7 @@
 		FC_RGBA_VBGR FC_RGBA_NONE FC_HINT_NONE FC_HINT_SLIGHT
 		FC_HINT_MEDIUM FC_HINT_FULL FC_LCD_NONE FC_LCD_DEFAULT
 		FC_LCD_LIGHT FC_LCD_LEGACY StXFace2FCWeightMap
-		StXStyle2FCSlantMap Lobby FirstTimeCalled CachedFontList'
+		StXStyle2FCSlantMap FirstTimeCalled CachedFontList'
 	poolDictionaries:''
 	category:'Graphics-Support'
 !
@@ -163,10 +163,6 @@
 initialize
     "Invoked at system start or when the class is dynamically loaded."
 
-    Lobby isNil ifTrue:[
-	Lobby := Registry new.
-    ].
-
     " Taken from fontconfig,h "
 
     FC_FAMILY               := 'family'.           "/* String */
@@ -274,28 +270,28 @@
     FC_LCD_LEGACY           := 3.
 
     StXFace2FCWeightMap := Dictionary withKeysAndValues:{
-	#thin.       FC_WEIGHT_THIN.
-	#extralight. FC_WEIGHT_EXTRALIGHT.
-	#ultralight. FC_WEIGHT_ULTRALIGHT.
-	#light.      FC_WEIGHT_LIGHT.
-	#book.       FC_WEIGHT_BOOK.
-	#regular.    FC_WEIGHT_REGULAR.
-	#normal.     FC_WEIGHT_NORMAL.
-	#medium.     FC_WEIGHT_MEDIUM.
-	#demibold.   FC_WEIGHT_DEMIBOLD.
-	#semibold.   FC_WEIGHT_SEMIBOLD.
-	#bold.       FC_WEIGHT_BOLD.
-	#extrabold.  FC_WEIGHT_EXTRABOLD.
-	#ultrabold.  FC_WEIGHT_ULTRABOLD.
-	#black.      FC_WEIGHT_BLACK.
-	#heavy.      FC_WEIGHT_HEAVY.
-	#extrablack. FC_WEIGHT_EXTRABLACK.
-	#ultrablack. FC_WEIGHT_ULTRABLACK.
+        #thin.       FC_WEIGHT_THIN.
+        #extralight. FC_WEIGHT_EXTRALIGHT.
+        #ultralight. FC_WEIGHT_ULTRALIGHT.
+        #light.      FC_WEIGHT_LIGHT.
+        #book.       FC_WEIGHT_BOOK.
+        #regular.    FC_WEIGHT_REGULAR.
+        #normal.     FC_WEIGHT_NORMAL.
+        #medium.     FC_WEIGHT_MEDIUM.
+        #demibold.   FC_WEIGHT_DEMIBOLD.
+        #semibold.   FC_WEIGHT_SEMIBOLD.
+        #bold.       FC_WEIGHT_BOLD.
+        #extrabold.  FC_WEIGHT_EXTRABOLD.
+        #ultrabold.  FC_WEIGHT_ULTRABOLD.
+        #black.      FC_WEIGHT_BLACK.
+        #heavy.      FC_WEIGHT_HEAVY.
+        #extrablack. FC_WEIGHT_EXTRABLACK.
+        #ultrablack. FC_WEIGHT_ULTRABLACK.
     }.
     StXStyle2FCSlantMap := Dictionary withKeysAndValues:{
-	#roman.    FC_SLANT_ROMAN.
-	#italic.   FC_SLANT_ITALIC.
-	#oblique.  FC_SLANT_OBLIQUE.
+        #roman.    FC_SLANT_ROMAN.
+        #italic.   FC_SLANT_ITALIC.
+        #oblique.  FC_SLANT_OBLIQUE.
     }.
 
     "Modified: / 30-12-2013 / 19:48:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -303,48 +299,6 @@
 
 !XftFontDescription class methodsFor:'instance creation'!
 
-family:familyString face:faceString style:styleString size:size sizeUnit:sizeUnit encoding:encoding
-    "returns a font for given family, face, style, size and the specified encoding.
-     The returned font is not associated to a specific device"
-
-    |proto|
-
-    RecentlyUsedFonts notNil ifTrue:[
-        proto := RecentlyUsedFonts
-                detect:[:fn |
-                    |fnStyle|
-                    
-                    fn family = familyString
-                    and:[ fn size = size and:[fn sizeUnit = sizeUnit
-                    and:[ fn face = faceString
-                    and:[ ((fnStyle := fn style) = styleString
-                          or:[ (fnStyle = 'oblique' and:[styleString = 'italic'])
-                          or:[ (fnStyle = 'italic' and:[styleString = 'oblique']) ]]) ]]]]]
-                ifNone:nil.
-        proto notNil ifTrue:[
-            ^ proto
-        ].
-    ].
-
-    CachedFontList notNil ifTrue:[
-        proto := CachedFontList
-                detect:[:fn |
-                    fn family = familyString
-                    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 shallowCopy)
-                setDevice: nil patternId: nil fontId: nil;
-                family:familyString face:faceString style:styleString size:size sizeUnit:sizeUnit encoding:encoding
-        ].
-    ].
-    ^ super
-        family:familyString face:faceString style:styleString size:size sizeUnit:sizeUnit encoding:encoding
-!
-
 for:aFontOrFontDescription
     ^ self
 	family:aFontOrFontDescription family
@@ -453,6 +407,123 @@
     ^ false
 
     "Created: / 20-12-2013 / 21:10:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+xftFontClose:fontIdArg displayId:displayId
+    | error |
+
+%{ /* STACK: 64000 */
+#ifdef XFT
+    if ( ! __isExternalAddressLike(fontIdArg) ) {
+        error = @symbol(BadArg1);
+        goto err;
+    }
+    if ( ! __isExternalAddressLike(displayId) ) {
+        error = @symbol(BadArg2);
+        goto err;
+    }
+    XftFontClose (DISPLAY(displayId), XFT_FONT(fontIdArg));
+    RETURN(self);
+err:;
+#endif
+%}.
+    self primitiveFailed: error
+!
+
+xftFontGetAscent: fontIdArg
+    | error |
+
+%{ /* STACK: 64000 */
+#ifdef XFT
+    if ( ! __isExternalAddressLike(fontIdArg) ) {
+        error = @symbol(BadArg1);
+        goto err;
+    }
+    RETURN ( __MKINT( XFT_FONT(fontIdArg)->ascent ) );
+    err:;
+#endif
+%}.
+    self primitiveFailed: error
+
+    "Created: / 21-12-2013 / 00:56:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+xftFontGetDescent:fontIdArg
+    | error |
+
+%{ /* STACK: 64000 */
+#ifdef XFT
+    if ( ! __isExternalAddressLike(fontIdArg) ) {
+        error = @symbol(BadArg1);
+        goto err;
+    }
+    RETURN ( __MKINT( XFT_FONT(fontIdArg)->descent ) );
+    err:;
+#endif
+%}.
+    self primitiveFailed: error
+
+    "Created: / 21-12-2013 / 00:56:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+xftFontGetHeight: fontIdArg
+    | error |
+
+%{ /* STACK: 64000 */
+#ifdef XFT
+    if ( ! __isExternalAddressLike(fontIdArg) ) {
+        error = @symbol(BadArg1);
+        goto err;
+    }
+    RETURN ( __MKINT( XFT_FONT(fontIdArg)->height ) );
+    err:;
+#endif
+%}.
+    self primitiveFailed: error
+
+    "Created: / 21-12-2013 / 00:56:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+xftFontGetMaxAdvanceWidth: fontIdArg
+    | error |
+
+%{ /* STACK: 64000 */
+#ifdef XFT
+    if ( ! __isExternalAddressLike(fontIdArg) ) {
+        error = @symbol(BadArg1);
+        goto err;
+    }
+    RETURN ( __MKINT( XFT_FONT(fontIdArg)->max_advance_width ) );
+    err:;
+#endif
+%}.
+    self primitiveFailed: error
+
+    "Created: / 30-12-2013 / 20:02:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+xftFontGetPattern: fontIdArg
+    | error |
+
+%{ /* STACK: 64000 */
+#ifdef XFT
+    XftPattern* p;
+    if ( ! __isExternalAddressLike(fontIdArg) ) {
+	error = @symbol(BadArg1);
+	goto err;
+    }
+    p = XFT_FONT(fontIdArg)->pattern;
+    if (p == NULL) {
+	RETURN ( nil );
+    } else {
+	RETURN ( FC_PATTERN_HANDLE_NEW ( p ) );
+    }
+    err:;
+#endif
+%}.
+    self primitiveFailed: error
+
+    "Created: / 21-12-2013 / 00:55:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !XftFontDescription class methodsFor:'queries'!
@@ -584,23 +655,6 @@
     fontId := fontIdArg.
 ! !
 
-!XftFontDescription methodsFor:'change & update'!
-
-update:anAspect with:something from:changedObject
-    "I want to be informed when a view that printed something with me is destroyed.
-     Disassociate the view from the XFT drawable"
-
-    |drawableId|
-
-    anAspect == #aboutToDestroy ifTrue:[
-	drawableId := changedObject drawableId.
-	(sharedDrawId notNil and:[drawableId notNil]) ifTrue:[
-	    sharedDrawId disassociateFrom:drawableId.
-	].
-	changedObject removeDependent:self.
-    ].
-! !
-
 !XftFontDescription methodsFor:'converting'!
 
 asNonXftFont
@@ -617,243 +671,6 @@
     ^ newFont
 ! !
 
-!XftFontDescription methodsFor:'displaying'!
-
-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
-     clipRect clipX clipY clipW clipH
-     fg fgR fgG fgB fgA fgPixel bg bgR bgG bgB bgA bgPixel
-     drawX drawY displayId screen drawableId error stringLen
-     newXftDrawId pixmapDepth|
-
-    "limit the string len, otherwise bad output is generated"
-    stringLen := index2Arg - index1 + 1.
-    stringLen > 1000 "8000" ifTrue:[
-        index2 := index1 + 1000 "8000" - 1.
-    ]  ifFalse:[
-        stringLen <= 0 ifTrue:[^ self].
-        index2 := index2Arg.
-    ].
-    bytesPerCharacter := aString bitsPerCharacter // 8.
-
-    transformation := aGC transformation.
-
-    clipRect := aGC deviceClippingBoundsOrNil.
-    clipRect notNil ifTrue:[
-        clipX := clipRect left.
-        clipY := clipRect top.
-        clipW := clipRect width.
-        clipH := clipRect height.
-"/clipW > 32767 ifTrue:['clipW > 32767: ' errorPrint. clipW errorPrintCR. clipW := 32767].
-"/(clipX > 16384 or:[clipX < -16384]) ifTrue:['clipX > 16384: ' errorPrint. 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.
-    ] ifFalse:[
-        drawX := (transformation applyToX:xArg) ceiling.
-        drawY := (transformation applyToY:yArg) ceiling.
-    ].
-
-    fg  := aGC paint.
-    fgR := fg scaledRed.
-    fgG := fg scaledGreen.
-    fgB := fg scaledBlue.
-    fgA := fg scaledAlpha.
-
-    fgR isNil ifTrue:[
-        "/ when drawing into a pixmap...
-        fgPixel := fg colorId.
-        fgPixel == 0 ifTrue:[
-            fgR := fgG := fgB := 0.
-        ] ifFalse:[
-            fgR := fgG := fgB := 16rFFFF.
-        ]
-    ].
-
-    opaque ifTrue:[
-        bg := aGC backgroundPaint.
-        bg isColor ifTrue:[
-            bgR := bg scaledRed.
-            bgG := bg scaledGreen.
-            bgB := bg scaledBlue.
-            bgA := bg scaledAlpha.
-        ] ifFalse:[
-            "images are not yet implemented"
-            "/ #todo: fill background rectangle
-            bgR := bgG := bgB := bgA := 16rFFFF.
-        ].
-        bgR isNil ifTrue:[
-            "/ when drawing into a pixmap...
-            bgPixel := bg colorId.
-            bgPixel == 0 ifTrue:[
-                bgR := bgG := bgB := 0.
-            ] ifFalse:[
-                bgR := bgG := bgB := 16rFFFF.
-            ]
-        ].
-    ].
-    displayId := device displayIdOrErrorIfBroken.
-    displayId isNil ifTrue:[
-        ^ self.
-    ].
-    screen := device screen.
-    drawableId := aGC drawableId.
-    aGC isPixmap ifTrue:[
-        pixmapDepth := aGC depth.
-    ].
-
-%{ /* STACK: 64000 */
-#ifdef XFT
-    XftColor color;
-    XGlyphInfo extents;
-    XRectangle clipRX;
-    char *string;
-    int len;
-    int __bytesPerCharacter;
-    XftDraw *__sharedDrawId;
-    XftFont *__xftFont = XFT_FONT(__INST(fontId));
-
-    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)
-    )) {
-        error = @symbol(badArgument);
-        goto out;
-    }
-
-    __bytesPerCharacter = __intVal(bytesPerCharacter);
-
-    if (pixmapDepth != nil) {
-        int __pixmapDepth = __intVal(pixmapDepth);
-
-        if (__pixmapDepth == 1) {
-            __sharedDrawId = XftDrawCreateBitmap(DISPLAY(displayId), DRAWABLE(drawableId));
-        } else {
-            __sharedDrawId = XftDrawCreateAlpha(DISPLAY(displayId), DRAWABLE(drawableId), __pixmapDepth);
-        }
-    } else {
-        if (__INST(sharedDrawId) == nil) {
-            __sharedDrawId = XftDrawCreate(DISPLAY(displayId),
-                                           DRAWABLE(drawableId),
-                                           DefaultVisual(DISPLAY(displayId), SCREEN(screen)),
-                                           DefaultColormap(DISPLAY(displayId), SCREEN(screen)));
-            __INST(sharedDrawId) = newXftDrawId = XFT_DRAW_HANDLE_NEW(__sharedDrawId);
-            __STORE(self, newXftDrawId);
-        } else if (XftDrawDrawable(__sharedDrawId = XFT_DRAW(__INST(sharedDrawId))) != DRAWABLE(drawableId)) {
-            XftDrawChange(__sharedDrawId, DRAWABLE(drawableId));
-        }
-    }
-
-    string = __stringVal(aString) + ((__intVal(index1) - 1 ) * __bytesPerCharacter);
-    len = __intVal(index2) - __intVal(index1) + 1;
-
-    if (clipX != nil) {
-        clipRX.x = __intVal(clipX);
-        clipRX.y = __intVal(clipY);
-        clipRX.width = __intVal(clipW);
-        clipRX.height = __intVal(clipH);
-        XftDrawSetClipRectangles(__sharedDrawId, 0, 0, &clipRX, 1);
-    } else {
-        XftDrawSetClip(__sharedDrawId, 0);
-    }
-
-    if (opaque == true) {
-        if (bgPixel != nil) {
-            color.pixel = (unsigned long)__intVal(bgPixel);
-        }
-        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), __xftFont, (FcChar8*)string, len, &extents);
-            break;
-        case 2:
-            XftTextExtents16(DISPLAY(displayId), __xftFont, (FcChar16*)string, len, &extents);
-            break;
-        case 4:
-            XftTextExtents32(DISPLAY(displayId), __xftFont, (FcChar32*)string, len, &extents);
-            break;
-        }
-if (extents.width < 0) printf("width: %d  < 0\n", extents.width);
-
-        XftDrawRect(__sharedDrawId, &color, __intVal(drawX) - extents.x, __intVal(drawY) - __xftFont->ascent, extents.width, __xftFont->height);
-    }
-    if (fgPixel != nil) {
-        color.pixel = (unsigned long)__intVal(fgPixel);
-    }
-    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(__sharedDrawId, &color,__xftFont,
-                        __intVal(drawX),
-                        __intVal(drawY),
-                        (FcChar8*)string,
-                        len);
-        break;
-
-    case 2:
-        XftDrawString16(__sharedDrawId, &color, __xftFont,
-                        __intVal(drawX),
-                        __intVal(drawY),
-                        (FcChar16*)string,
-                        len);
-        break;
-
-    case 4:
-        XftDrawString32(__sharedDrawId, &color, __xftFont,
-                        __intVal(drawX),
-                        __intVal(drawY),
-                        (FcChar32*)string,
-                        len);
-        break;
-
-    default:
-        error = @symbol(invalidStringSize);
-        goto out;
-    }
-
-    if (pixmapDepth != nil) {
-        XftDrawDestroy(__sharedDrawId);
-    }
-
-# if 0 // this has been superseeded by receiving change messages on view destroy
-    // Have to disassociate the drawableId - otherwise we get an X11 error 'RenderBadPicture (invalid Picture parameter)'
-    // when the drawable (the window) is destroyed.
-    XftDrawChange(__sharedDrawId, None);
-# endif
-out:;
-#endif
-%}.
-    error notNil ifTrue:[
-        self primitiveFailed: error.
-    ].
-    newXftDrawId notNil ifTrue:[
-        Lobby register:self.
-    ].
-    "Created: / 21-12-2013 / 21:11:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 10-01-2014 / 11:13:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
-
 !XftFontDescription methodsFor:'error reporting'!
 
 primitiveFailed
@@ -876,15 +693,8 @@
 
 !XftFontDescription methodsFor:'finalization'!
 
-finalizationLobby
-    ^ Lobby
-!
-
 finalize
-    sharedDrawId notNil ifTrue:[
-	sharedDrawId destroy.
-	sharedDrawId := nil.
-    ].
+    self releaseFromDevice
 ! !
 
 !XftFontDescription methodsFor:'getting a device font'!
@@ -922,36 +732,12 @@
     aGraphicsDevice supportsXftFonts ifFalse:[
         ^ self asNonXftFont onDevice:aGraphicsDevice.
     ].
-    RecentlyUsedFonts isNil ifTrue:[
-        RecentlyUsedFonts := OrderedCollection new:20.
+
+    deviceFont := aGraphicsDevice deviceFonts detect:[:eachFont | self sameDeviceFontAs:eachFont] ifNone:[].
+    deviceFont notNil ifTrue:[
+        ^ deviceFont.
     ].
 
-    RecentlyUsedFonts keysAndValuesDo:[:index :aFont |
-        ((aFont class == self class) 
-         and:[(self sameDeviceFontAs:aFont) 
-         and:[device == aGraphicsDevice
-         and:[aFont getXftFontId notNil]]]) ifTrue:[
-            "/ Transcript showCR:'hit'.
-            RecentlyUsedFonts
-                removeIndex:index;
-                addFirst:aFont.
-            ^ aFont
-        ]
-    ].
-
-    RecentlyUsedFonts size >= 20 ifTrue:[
-        RecentlyUsedFonts removeLast.
-    ].
-
-    aGraphicsDevice deviceFonts do:[:aFont |
-        (self sameDeviceFontAs:aFont) ifTrue:[
-            RecentlyUsedFonts addFirst:aFont.
-            ^ aFont
-        ].
-    ].
-
-"/    ^ self asNonXftFont onDevice:aGraphicsDevice.
-
     computedWeight := weight.
     computedWeight isNil ifTrue:[
         computedWeight := StXFace2FCWeightMap at:(face ? '') asLowercase ifAbsent:[FC_WEIGHT_REGULAR].
@@ -990,7 +776,6 @@
                 closestPatternHandle := nil.
                 deviceFont setDevice:aGraphicsDevice patternId:nil fontId:newFontId.
                 aGraphicsDevice registerFont:deviceFont.
-                RecentlyUsedFonts addFirst:deviceFont.
                 ^ deviceFont.
             ].
         ].
@@ -1006,10 +791,6 @@
 
     "Modified: / 14-04-1997 / 18:22:31 / cg"
     "Modified: / 02-01-2014 / 23:43:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-sameDeviceFontAs:aFont
-    ^ (super sameDeviceFontAs:aFont) and:[device == aFont graphicsDevice]
 ! !
 
 !XftFontDescription methodsFor:'initialization'!
@@ -1053,132 +834,6 @@
 
 !XftFontDescription methodsFor:'primitives'!
 
-xftFontClose:fontIdArg displayId:displayId
-    | error |
-
-%{ /* STACK: 64000 */
-#ifdef XFT
-    int v;
-    if ( ! __isExternalAddressLike(fontIdArg) ) {
-	error = @symbol(BadArg1);
-	goto err;
-    }
-    if ( ! __isExternalAddressLike(displayId) ) {
-	error = @symbol(BadArg2);
-	goto err;
-    }
-    XftFontClose (DISPLAY(displayId), XFT_FONT(fontIdArg));
-    RETURN(self);
-err:;
-#endif
-%}.
-    self primitiveFailed: error
-!
-
-xftFontGetAscent: fontIdArg
-    | error |
-
-%{ /* STACK: 64000 */
-#ifdef XFT
-    int v;
-    if ( ! __isExternalAddressLike(fontIdArg) ) {
-	error = @symbol(BadArg1);
-	goto err;
-    }
-    v = XFT_FONT(fontIdArg)->ascent;
-    RETURN ( __MKINT( v ) );
-    err:;
-#endif
-%}.
-    self primitiveFailed: error
-
-    "Created: / 21-12-2013 / 00:56:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-xftFontGetDescent:fontIdArg
-    | error |
-
-%{ /* STACK: 64000 */
-#ifdef XFT
-    int v;
-    if ( ! __isExternalAddressLike(fontIdArg) ) {
-	error = @symbol(BadArg1);
-	goto err;
-    }
-    v = XFT_FONT(fontIdArg)->descent;
-    RETURN ( __MKINT( v ) );
-    err:;
-#endif
-%}.
-    self primitiveFailed: error
-
-    "Created: / 21-12-2013 / 00:56:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-xftFontGetHeight: fontIdArg
-    | error |
-
-%{ /* STACK: 64000 */
-#ifdef XFT
-    int v;
-    if ( ! __isExternalAddressLike(fontIdArg) ) {
-	error = @symbol(BadArg1);
-	goto err;
-    }
-    v = XFT_FONT(fontIdArg)->height;
-    RETURN ( __MKINT( v ) );
-    err:;
-#endif
-%}.
-    self primitiveFailed: error
-
-    "Created: / 21-12-2013 / 00:56:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-xftFontGetMaxAdvanceWidth: fontIdArg
-    | error |
-
-%{ /* STACK: 64000 */
-#ifdef XFT
-    int v;
-    if ( ! __isExternalAddressLike(fontIdArg) ) {
-	error = @symbol(BadArg1);
-	goto err;
-    }
-    v = XFT_FONT(fontIdArg)->max_advance_width;
-    RETURN ( __MKINT( v ) );
-    err:;
-#endif
-%}.
-    self primitiveFailed: error
-
-    "Created: / 30-12-2013 / 20:02:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
-xftFontGetPattern: fontIdArg
-    | error |
-
-%{ /* STACK: 64000 */
-#ifdef XFT
-    XftPattern* p;
-    if ( ! __isExternalAddressLike(fontIdArg) ) {
-	error = @symbol(BadArg1);
-	goto err;
-    }
-    p = XFT_FONT(fontIdArg)->pattern;
-    if (p == NULL) {
-	RETURN ( nil );
-    } else {
-	RETURN ( FC_PATTERN_HANDLE_NEW ( p ) );
-    }
-    err:;
-#endif
-%}.
-    self primitiveFailed: error
-
-    "Created: / 21-12-2013 / 00:55:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
 xftTextExtents:displayIdArg string:aString from:start to:stop into:extentsArrayOrNil
     "get the extents of aString.
      Answer thr width of aString (in reality the xOff).
@@ -1285,7 +940,7 @@
 ascent
     "return the ascent - the number of pixels above the baseLine."
     ascent isNil ifTrue:[
-	ascent := self xftFontGetAscent: fontId
+        ascent := self class xftFontGetAscent: fontId
     ].
     ^ ascent
 
@@ -1296,7 +951,7 @@
     "return the descent - the number of pixels below the baseLine."
 
     descent isNil ifTrue:[
-	 descent := self xftFontGetDescent: fontId
+         descent := self class xftFontGetDescent: fontId
     ].
     ^ descent
 
@@ -1330,7 +985,7 @@
     "return the height - the number of pixels above plus below the baseLine."
 
     height isNil ifTrue:[
-	height := self xftFontGetHeight: fontId
+        height := self class xftFontGetHeight: fontId
     ].
     ^ height
 
@@ -1342,22 +997,17 @@
      are of the same width)"
 
     fixedWidth isNil ifTrue:[
-	(device notNil and:[fontId notNil]) ifTrue:[
-	    |w|
-
-	    "/ take some obvously different chars
-	    w := self widthOf:'.'.
-	    ((self widthOf:'i') == w
-		and:[ (self widthOf:'W') == w
-		and:[ (self widthOf:' ') == w ]]
-	    ) ifTrue:[
-		fixedWidth := w.
-	    ] ifFalse:[
-		fixedWidth := false
-	    ]
-	]
+        fontId isNil ifTrue:[
+            ^ false     "we don't know yet"
+        ] ifFalse:[
+            "/ take some obvously different chars
+            width := self widthOf:' '.
+            fixedWidth := (self widthOf:'i') == width
+                                and:[(self widthOf:'W') == width
+                                and:[(self widthOf:'.') == width]]
+        ].
     ].
-    ^ fixedWidth notNil and:[fixedWidth isInteger]
+    ^ fixedWidth.
 
     "Created: / 21-12-2013 / 10:38:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -1384,10 +1034,10 @@
     "return the font's maximum-width character (i.e. the maximum of all characters);
      That is a number of units (usually pixels)."
 
-    (fixedWidth class == SmallInteger) ifTrue:[
-	^ fixedWidth
+    self isFixedWidth ifTrue:[
+        ^ width
     ].
-    ^ self xftFontGetMaxAdvanceWidth: fontId
+    ^ self class xftFontGetMaxAdvanceWidth: fontId
 
     "Created: / 30-12-2013 / 20:02:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -1422,20 +1072,21 @@
      For fixed fonts, this is the same as minWidth or maxWidth (or any character).
      The receiver must be associated to a device, for this query to be legal."
 
-    fixedWidth class == SmallInteger ifTrue:[
-	^ fixedWidth
+    width isNil ifTrue:[
+        width := self widthOf:' '.
     ].
-    ^ self widthOf:' '
-
-    "Modified: 30.4.1996 / 16:43:45 / cg"
+    ^ width
 !
 
 widthOf:aString from:start to:stop
     "return the width of a sub string"
 
     (stop < start) ifTrue:[^ 0].
-    (fixedWidth class == SmallInteger) ifTrue:[
-        ^ fixedWidth * (stop - start + 1)
+    fixedWidth == true ifTrue:[
+        ^ width * (stop - start + 1)
+    ].
+    device isNil ifTrue:[
+        self errorNoDevice.
     ].
     ^ self xftTextExtents:device displayId string:aString from:start to:stop into:nil.
 
@@ -1445,54 +1096,15 @@
 
 !XftFontDescription methodsFor:'release'!
 
-disassociateXftDrawableFrom:drawableId
-    "Disassociate the XftDrawable from drawableId.
-     This mist be done before the drawable is destroyed,
-     otherwise the XftDrawable is destroyed together with the drawable,
-     and X11 errors will be signaled."
-
-    sharedDrawId notNil ifTrue:[
-	sharedDrawId disassociateFrom:drawableId.
-    ].
-!
-
-releaseDrawIfAssociatedWith: view
-    | drawableId |
-
-    view isNil ifTrue:[ ^ self ].
-    drawableId := view id.
-    drawableId isNil ifTrue: [ ^ self ].
-%{ /* STACK: 64000 */
-#ifdef XFT
-    if ( __INST(sharedDrawId) != nil ) {
-	XftDraw *xftDrawable = XFT_DRAW(__INST(sharedDrawId));
-
-	if (XftDrawDrawable(xftDrawable) == DRAWABLE(drawableId)) {
-	    __INST(sharedDrawId) = nil;
-	    XftDrawDestroy(xftDrawable);
-	}
-    }
-    RETURN (self);
-#endif
-%}.
-    self primitiveFailed
-
-    "Created: / 12-01-2014 / 19:48:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 12-01-2014 / 22:09:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
-
 releaseFromDevice
     "I am no longer available on the device"
 
-    Lobby unregister:self.
-    "/ cg: no, xftDrawDestroy should not be done.
-    "/ (releaseFromDevice is called when either the display connection
-    "/ is lost, or a snapshot image is restarted)
-    "/ self xftDrawDestroy.
-
-    device := nil.
-    fontId := nil.
-    sharedDrawId := nil.
+    (device notNil and:[fontId notNil]) ifTrue:[
+        self class xftFontClose:fontId displayId:device displayId.
+        device := nil.
+        fontId := nil.
+        width := nil.
+    ].
 ! !
 
 !XftFontDescription methodsFor:'testing'!
@@ -1503,10 +1115,6 @@
     ^ false
 !
 
-isUsed
-    ^ sharedDrawId notNil
-!
-
 isXftFont
     ^ true
 ! !