---------------------------------------------------------------------------- -- | -- Module : XMonad.Util.Font -- Copyright : (c) 2007 Andrea Rossato and Spencer Janssen -- License : BSD-style (see xmonad/LICENSE) -- -- Maintainer : andrea.rossato@unibz.it -- Stability : unstable -- Portability : unportable -- -- A module for abstracting a font facility over Core fonts and Xft -- ----------------------------------------------------------------------------- module XMonad.Util.Font ( -- * Usage: -- $usage XMonadFont(..) , initXMF , releaseXMF , initCoreFont , releaseCoreFont , Align (..) , stringPosition , textWidthXMF , textExtentsXMF , printStringXMF , stringToPixel ) where import XMonad import Foreign #ifdef XFT import Data.List import Graphics.X11.Xft import Graphics.X11.Xrender #endif -- Hide the Core Font/Xft switching here data XMonadFont = Core FontStruct #ifdef XFT | Xft XftFont #endif -- $usage -- See "Xmonad.Layout.Tabbed" or "XMonad.Prompt" for usage examples -- | Get the Pixel value for a named color: if an invalid name is -- given the black pixel will be returned. stringToPixel :: MonadIO m => Display -> String -> m Pixel stringToPixel d s = liftIO $ catch getIt fallBack where getIt = initColor d s fallBack = const $ return $ blackPixel d (defaultScreen d) -- | Given a fontname returns the font structure. If the font name is -- not valid the default font will be loaded and returned. initCoreFont :: String -> X FontStruct initCoreFont s = do d <- asks display io $ catch (getIt d) (fallBack d) where getIt d = loadQueryFont d s fallBack d = const $ loadQueryFont d "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*" releaseCoreFont :: FontStruct -> X () releaseCoreFont fs = do d <- asks display io $ freeFont d fs -- | When initXMF gets a font name that starts with 'xft:' it switchs to the Xft backend -- Example: 'xft: Sans-10' initXMF :: String -> X XMonadFont initXMF s = #ifdef XFT if xftPrefix `isPrefixOf` s then do dpy <- asks display xftdraw <- io $ xftFontOpen dpy (defaultScreenOfDisplay dpy) (drop (length xftPrefix) s) return (Xft xftdraw) else #endif (initCoreFont s >>= (return . Core)) #ifdef XFT where xftPrefix = "xft:" #endif releaseXMF :: XMonadFont -> X () releaseXMF (Core fs) = releaseCoreFont fs #ifdef XFT releaseXMF (Xft xftfont) = do dpy <- asks display io $ xftFontClose dpy xftfont #endif textWidthXMF :: MonadIO m => Display -> XMonadFont -> String -> m Int textWidthXMF _ (Core fs) s = return $ fi $ textWidth fs s #ifdef XFT textWidthXMF dpy (Xft xftdraw) s = liftIO $ do gi <- xftTextExtents dpy xftdraw s return $ xglyphinfo_width gi #endif textExtentsXMF :: MonadIO m => XMonadFont -> String -> m (FontDirection,Int32,Int32,CharStruct) textExtentsXMF (Core fs) s = return $ textExtents fs s #ifdef XFT textExtentsXMF (Xft xftfont) _ = liftIO $ do ascent <- xftfont_ascent xftfont descent <- xftfont_descent xftfont return (error "Font direction touched", fi ascent, fi descent, error "Font overall size touched") #endif -- | String position data Align = AlignCenter | AlignRight | AlignLeft -- | Return the string x and y 'Position' in a 'Rectangle', given a -- 'FontStruct' and the 'Align'ment stringPosition :: XMonadFont -> Rectangle -> Align -> String -> X (Position,Position) stringPosition fs (Rectangle _ _ w h) al s = do dpy <- asks display width <- io $ textWidthXMF dpy fs s (_,a,d,_) <- io $ textExtentsXMF fs s let y = fi $ ((h - fi (a + d)) `div` 2) + fi a; x = case al of AlignCenter -> fi (w `div` 2) - fi (width `div` 2) AlignLeft -> 1 AlignRight -> fi (w - (fi width + 1)); return (x,y) printStringXMF :: MonadIO m => Display -> Drawable -> XMonadFont -> GC -> String -> String -> Position -> Position -> String -> m () printStringXMF d p (Core fs) gc fc bc x y s = liftIO $ do setFont d gc $ fontFromFontStruct fs [fc',bc'] <- mapM (stringToPixel d) [fc,bc] setForeground d gc fc' setBackground d gc bc' drawImageString d p gc x y s #ifdef XFT printStringXMF dpy drw (Xft font) _ fc _ x y s = do let screen = defaultScreenOfDisplay dpy; colormap = defaultColormapOfScreen screen; visual = defaultVisualOfScreen screen; liftIO $ withXftDraw dpy drw visual colormap $ \draw -> withXftColorName dpy visual colormap fc $ \color -> xftDrawString draw color font x y s #endif -- | Short-hand for 'fromIntegral' fi :: (Integral a, Num b) => a -> b fi = fromIntegral