| Copyright | (c) Alastair Reid 1999-2003 | 
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) | 
| Maintainer | libraries@haskell.org | 
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
Graphics.X11.Xlib.Font
Description
A collection of FFI declarations for interfacing with Xlib Fonts.
Synopsis
- type Glyph = Word16
- queryFont :: Display -> Font -> IO FontStruct
- fontFromGC :: Display -> GC -> IO Font
- loadQueryFont :: Display -> String -> IO FontStruct
- freeFont :: Display -> FontStruct -> IO ()
- data FontStruct
- fontFromFontStruct :: FontStruct -> Font
- ascentFromFontStruct :: FontStruct -> Int32
- descentFromFontStruct :: FontStruct -> Int32
- type CharStruct = (CInt, CInt, CInt, CInt, CInt)
- textExtents :: FontStruct -> String -> (FontDirection, Int32, Int32, CharStruct)
- textWidth :: FontStruct -> String -> Int32
Documentation
queryFont :: Display -> Font -> IO FontStruct Source #
interface to the X11 library function XQueryFont().
fontFromGC :: Display -> GC -> IO Font Source #
interface to the X11 library function XGetGCValues().
loadQueryFont :: Display -> String -> IO FontStruct Source #
interface to the X11 library function XLoadQueryFont().
freeFont :: Display -> FontStruct -> IO () Source #
interface to the X11 library function XFreeFont().
data FontStruct Source #
pointer to an X11 XFontStruct structure
Instances
| Eq FontStruct Source # | |
| Defined in Graphics.X11.Xlib.Font | |
| Data FontStruct Source # | |
| Defined in Graphics.X11.Xlib.Font Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FontStruct -> c FontStruct # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FontStruct # toConstr :: FontStruct -> Constr # dataTypeOf :: FontStruct -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FontStruct) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FontStruct) # gmapT :: (forall b. Data b => b -> b) -> FontStruct -> FontStruct # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FontStruct -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FontStruct -> r # gmapQ :: (forall d. Data d => d -> u) -> FontStruct -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FontStruct -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FontStruct -> m FontStruct # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FontStruct -> m FontStruct # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FontStruct -> m FontStruct # | |
| Ord FontStruct Source # | |
| Defined in Graphics.X11.Xlib.Font Methods compare :: FontStruct -> FontStruct -> Ordering # (<) :: FontStruct -> FontStruct -> Bool # (<=) :: FontStruct -> FontStruct -> Bool # (>) :: FontStruct -> FontStruct -> Bool # (>=) :: FontStruct -> FontStruct -> Bool # max :: FontStruct -> FontStruct -> FontStruct # min :: FontStruct -> FontStruct -> FontStruct # | |
| Show FontStruct Source # | |
| Defined in Graphics.X11.Xlib.Font Methods showsPrec :: Int -> FontStruct -> ShowS # show :: FontStruct -> String # showList :: [FontStruct] -> ShowS # | |
fontFromFontStruct :: FontStruct -> Font Source #
textExtents :: FontStruct -> String -> (FontDirection, Int32, Int32, CharStruct) Source #
interface to the X11 library function XTextExtents().