{-# LINE 1 "Graphics/X11/Xlib/Font.hsc" #-}
{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Graphics.X11.Xlib.Font
-- Copyright   :  (c) Alastair Reid, 1999-2003
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  provisional
-- Portability :  portable
--
-- A collection of FFI declarations for interfacing with Xlib Fonts.
--
-----------------------------------------------------------------------------

module Graphics.X11.Xlib.Font(

        Glyph,
        queryFont,
        fontFromGC,
        loadQueryFont,
        freeFont,
        FontStruct,
        fontFromFontStruct,
        ascentFromFontStruct,
        descentFromFontStruct,
        CharStruct,
        textExtents,
        textWidth,

        ) where



import Graphics.X11.Types
import Graphics.X11.Xlib.Types

import Foreign (Ptr, Int32, alloca, allocaBytes, peekByteOff, Word16, Word64, peek, throwIfNull)
{-# LINE 39 "Graphics/X11/Xlib/Font.hsc" #-}
import Foreign.C

import System.IO.Unsafe


{-# LINE 44 "Graphics/X11/Xlib/Font.hsc" #-}
import Data.Data

{-# LINE 46 "Graphics/X11/Xlib/Font.hsc" #-}

----------------------------------------------------------------
-- Fonts
----------------------------------------------------------------

-- A glyph (or Char2b) is a 16 bit character identification.
-- The top 8 bits are zero in many fonts.
type Glyph = Word16

-- | pointer to an X11 @XFontStruct@ structure
newtype FontStruct = FontStruct (Ptr FontStruct)

{-# LINE 58 "Graphics/X11/Xlib/Font.hsc" #-}
        deriving (FontStruct -> FontStruct -> Bool
(FontStruct -> FontStruct -> Bool)
-> (FontStruct -> FontStruct -> Bool) -> Eq FontStruct
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontStruct -> FontStruct -> Bool
$c/= :: FontStruct -> FontStruct -> Bool
== :: FontStruct -> FontStruct -> Bool
$c== :: FontStruct -> FontStruct -> Bool
Eq, Eq FontStruct
Eq FontStruct
-> (FontStruct -> FontStruct -> Ordering)
-> (FontStruct -> FontStruct -> Bool)
-> (FontStruct -> FontStruct -> Bool)
-> (FontStruct -> FontStruct -> Bool)
-> (FontStruct -> FontStruct -> Bool)
-> (FontStruct -> FontStruct -> FontStruct)
-> (FontStruct -> FontStruct -> FontStruct)
-> Ord FontStruct
FontStruct -> FontStruct -> Bool
FontStruct -> FontStruct -> Ordering
FontStruct -> FontStruct -> FontStruct
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FontStruct -> FontStruct -> FontStruct
$cmin :: FontStruct -> FontStruct -> FontStruct
max :: FontStruct -> FontStruct -> FontStruct
$cmax :: FontStruct -> FontStruct -> FontStruct
>= :: FontStruct -> FontStruct -> Bool
$c>= :: FontStruct -> FontStruct -> Bool
> :: FontStruct -> FontStruct -> Bool
$c> :: FontStruct -> FontStruct -> Bool
<= :: FontStruct -> FontStruct -> Bool
$c<= :: FontStruct -> FontStruct -> Bool
< :: FontStruct -> FontStruct -> Bool
$c< :: FontStruct -> FontStruct -> Bool
compare :: FontStruct -> FontStruct -> Ordering
$ccompare :: FontStruct -> FontStruct -> Ordering
$cp1Ord :: Eq FontStruct
Ord, Int -> FontStruct -> ShowS
[FontStruct] -> ShowS
FontStruct -> String
(Int -> FontStruct -> ShowS)
-> (FontStruct -> String)
-> ([FontStruct] -> ShowS)
-> Show FontStruct
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontStruct] -> ShowS
$cshowList :: [FontStruct] -> ShowS
show :: FontStruct -> String
$cshow :: FontStruct -> String
showsPrec :: Int -> FontStruct -> ShowS
$cshowsPrec :: Int -> FontStruct -> ShowS
Show, Typeable, Typeable FontStruct
DataType
Constr
Typeable FontStruct
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> FontStruct -> c FontStruct)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c FontStruct)
-> (FontStruct -> Constr)
-> (FontStruct -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c FontStruct))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c FontStruct))
-> ((forall b. Data b => b -> b) -> FontStruct -> FontStruct)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> FontStruct -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> FontStruct -> r)
-> (forall u. (forall d. Data d => d -> u) -> FontStruct -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> FontStruct -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> FontStruct -> m FontStruct)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> FontStruct -> m FontStruct)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> FontStruct -> m FontStruct)
-> Data FontStruct
FontStruct -> DataType
FontStruct -> Constr
(forall b. Data b => b -> b) -> FontStruct -> FontStruct
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FontStruct -> c FontStruct
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FontStruct
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> FontStruct -> u
forall u. (forall d. Data d => d -> u) -> FontStruct -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FontStruct -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FontStruct -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FontStruct -> m FontStruct
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FontStruct -> m FontStruct
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FontStruct
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FontStruct -> c FontStruct
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FontStruct)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FontStruct)
$cFontStruct :: Constr
$tFontStruct :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> FontStruct -> m FontStruct
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FontStruct -> m FontStruct
gmapMp :: (forall d. Data d => d -> m d) -> FontStruct -> m FontStruct
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FontStruct -> m FontStruct
gmapM :: (forall d. Data d => d -> m d) -> FontStruct -> m FontStruct
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FontStruct -> m FontStruct
gmapQi :: Int -> (forall d. Data d => d -> u) -> FontStruct -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FontStruct -> u
gmapQ :: (forall d. Data d => d -> u) -> FontStruct -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FontStruct -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FontStruct -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FontStruct -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FontStruct -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FontStruct -> r
gmapT :: (forall b. Data b => b -> b) -> FontStruct -> FontStruct
$cgmapT :: (forall b. Data b => b -> b) -> FontStruct -> FontStruct
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FontStruct)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FontStruct)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c FontStruct)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FontStruct)
dataTypeOf :: FontStruct -> DataType
$cdataTypeOf :: FontStruct -> DataType
toConstr :: FontStruct -> Constr
$ctoConstr :: FontStruct -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FontStruct
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FontStruct
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FontStruct -> c FontStruct
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FontStruct -> c FontStruct
$cp1Data :: Typeable FontStruct
Data)

{-# LINE 62 "Graphics/X11/Xlib/Font.hsc" #-}

-- Disnae exist: %fun LoadFont       :: Display -> String -> IO Font
-- Disnae exist: %fun UnloadFont     :: Display -> Font -> IO ()

-- Argument can be a Font or a GContext.
-- But, if it's a GContext, the fontStruct will use the GContext as the
-- FontID - which will cause most things to break so it's probably
-- safer using XGetGCValues to get a genuine font ID

-- | interface to the X11 library function @XQueryFont()@.
foreign import ccall unsafe "HsXlib.h XQueryFont"
        queryFont     :: Display -> Font -> IO FontStruct

-- Note that this _WILL NOT WORK_ unless you have explicitly set the font.
-- I'm slowly but surely coming to the conclusion that Xlib is a pile of
-- steaming shit.

-- | interface to the X11 library function @XGetGCValues()@.
fontFromGC :: Display -> GC -> IO Font
fontFromGC :: Display -> GC -> IO Font
fontFromGC Display
display GC
gc =
        Int -> (Ptr GCValues -> IO Font) -> IO Font
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (Int
128) ((Ptr GCValues -> IO Font) -> IO Font)
-> (Ptr GCValues -> IO Font) -> IO Font
forall a b. (a -> b) -> a -> b
$ \ Ptr GCValues
values -> do
{-# LINE 83 "Graphics/X11/Xlib/Font.hsc" #-}
        String -> IO Status -> IO ()
throwIfZero String
"fontFromGC" (IO Status -> IO ()) -> IO Status -> IO ()
forall a b. (a -> b) -> a -> b
$
                Display -> GC -> Font -> Ptr GCValues -> IO Status
xGetGCValues Display
display GC
gc Font
16384 Ptr GCValues
values
{-# LINE 85 "Graphics/X11/Xlib/Font.hsc" #-}
        (\Ptr GCValues
hsc_ptr -> Ptr GCValues -> Int -> IO Font
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr GCValues
hsc_ptr Int
88) Ptr GCValues
values
{-# LINE 86 "Graphics/X11/Xlib/Font.hsc" #-}
foreign import ccall unsafe "HsXlib.h XGetGCValues"
        xGetGCValues :: Display -> GC -> ValueMask -> Ptr GCValues -> IO CInt

type ValueMask = Word64
{-# LINE 90 "Graphics/X11/Xlib/Font.hsc" #-}

-- | interface to the X11 library function @XLoadQueryFont()@.
loadQueryFont :: Display -> String -> IO FontStruct
loadQueryFont :: Display -> String -> IO FontStruct
loadQueryFont Display
display String
name =
        String -> (CString -> IO FontStruct) -> IO FontStruct
forall a. String -> (CString -> IO a) -> IO a
withCString String
name ((CString -> IO FontStruct) -> IO FontStruct)
-> (CString -> IO FontStruct) -> IO FontStruct
forall a b. (a -> b) -> a -> b
$ \ CString
c_name -> do
        Ptr FontStruct
fs <- String -> IO (Ptr FontStruct) -> IO (Ptr FontStruct)
forall a. String -> IO (Ptr a) -> IO (Ptr a)
throwIfNull String
"loadQueryFont" (IO (Ptr FontStruct) -> IO (Ptr FontStruct))
-> IO (Ptr FontStruct) -> IO (Ptr FontStruct)
forall a b. (a -> b) -> a -> b
$ Display -> CString -> IO (Ptr FontStruct)
xLoadQueryFont Display
display CString
c_name
        FontStruct -> IO FontStruct
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr FontStruct -> FontStruct
FontStruct Ptr FontStruct
fs)
foreign import ccall unsafe "HsXlib.h XLoadQueryFont"
        xLoadQueryFont :: Display -> CString -> IO (Ptr FontStruct)

-- | interface to the X11 library function @XFreeFont()@.
foreign import ccall unsafe "HsXlib.h XFreeFont"
        freeFont      :: Display -> FontStruct -> IO ()
-- %fun XSetFontPath  :: Display -> ListString  -> IO () using XSetFontPath(arg1,arg2,arg2_size)

fontFromFontStruct :: FontStruct -> Font
fontFromFontStruct :: FontStruct -> Font
fontFromFontStruct (FontStruct Ptr FontStruct
fs) = IO Font -> Font
forall a. IO a -> a
unsafePerformIO (IO Font -> Font) -> IO Font -> Font
forall a b. (a -> b) -> a -> b
$
        (\Ptr FontStruct
hsc_ptr -> Ptr FontStruct -> Int -> IO Font
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr FontStruct
hsc_ptr Int
8) Ptr FontStruct
fs
{-# LINE 108 "Graphics/X11/Xlib/Font.hsc" #-}

ascentFromFontStruct :: FontStruct -> Int32
ascentFromFontStruct :: FontStruct -> Int32
ascentFromFontStruct (FontStruct Ptr FontStruct
fs) = IO Int32 -> Int32
forall a. IO a -> a
unsafePerformIO (IO Int32 -> Int32) -> IO Int32 -> Int32
forall a b. (a -> b) -> a -> b
$
        (\Ptr FontStruct
hsc_ptr -> Ptr FontStruct -> Int -> IO Int32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr FontStruct
hsc_ptr Int
88) Ptr FontStruct
fs
{-# LINE 112 "Graphics/X11/Xlib/Font.hsc" #-}

descentFromFontStruct :: FontStruct -> Int32
descentFromFontStruct :: FontStruct -> Int32
descentFromFontStruct (FontStruct Ptr FontStruct
fs) = IO Int32 -> Int32
forall a. IO a -> a
unsafePerformIO (IO Int32 -> Int32) -> IO Int32 -> Int32
forall a b. (a -> b) -> a -> b
$
        (\Ptr FontStruct
hsc_ptr -> Ptr FontStruct -> Int -> IO Int32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr FontStruct
hsc_ptr Int
92) Ptr FontStruct
fs
{-# LINE 116 "Graphics/X11/Xlib/Font.hsc" #-}

-- %prim XGetFontPath :: Display -> IO ListString
--Int r_size;
--String* r = XGetFontPath(arg1,&r_size);
-- %update(r);
--XFreeFontPath(r);
--return;

-- %prim XListFonts :: Display -> String -> Int -> IO ListString
--Int r_size;
--String *r = XListFonts(arg1,arg2,arg3,&r_size);
-- %update(r);
--XFreeFontNames(r);
--return;

-- XListFontsWithInfo omitted (no support for FontStruct yet)

-- XQueryTextExtents omitted (no support for CharStruct yet)
-- XQueryTextExtents16 omitted (no support for CharStruct yet)

-- We marshall this across right away because it's usually one-off info
type CharStruct =
        ( CInt            -- lbearing (origin to left edge of raster)
        , CInt            -- rbearing (origin to right edge of raster)
        , CInt            -- width    (advance to next char's origin)
        , CInt            -- ascent   (baseline to top edge of raster)
        , CInt            -- descent  (baseline to bottom edge of raster)
        -- attributes omitted
        )

peekCharStruct :: Ptr CharStruct -> IO CharStruct
peekCharStruct :: Ptr CharStruct -> IO CharStruct
peekCharStruct Ptr CharStruct
p = do
        CShort
lbearing <- (\Ptr CharStruct
hsc_ptr -> Ptr CharStruct -> Int -> IO CShort
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CharStruct
hsc_ptr Int
0) Ptr CharStruct
p
{-# LINE 149 "Graphics/X11/Xlib/Font.hsc" #-}
        CShort
rbearing <- (\Ptr CharStruct
hsc_ptr -> Ptr CharStruct -> Int -> IO CShort
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CharStruct
hsc_ptr Int
2) Ptr CharStruct
p
{-# LINE 150 "Graphics/X11/Xlib/Font.hsc" #-}
        CShort
width    <- (\Ptr CharStruct
hsc_ptr -> Ptr CharStruct -> Int -> IO CShort
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CharStruct
hsc_ptr Int
4) Ptr CharStruct
p
{-# LINE 151 "Graphics/X11/Xlib/Font.hsc" #-}
        CShort
ascent   <- (\Ptr CharStruct
hsc_ptr -> Ptr CharStruct -> Int -> IO CShort
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CharStruct
hsc_ptr Int
6) Ptr CharStruct
p
{-# LINE 152 "Graphics/X11/Xlib/Font.hsc" #-}
        CShort
descent  <- (\Ptr CharStruct
hsc_ptr -> Ptr CharStruct -> Int -> IO CShort
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr CharStruct
hsc_ptr Int
8) Ptr CharStruct
p
{-# LINE 153 "Graphics/X11/Xlib/Font.hsc" #-}
        CharStruct -> IO CharStruct
forall (m :: * -> *) a. Monad m => a -> m a
return (CShort -> Status
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CShort
lbearing::CShort),
                CShort -> Status
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CShort
rbearing::CShort),
                CShort -> Status
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CShort
width::CShort),
                CShort -> Status
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CShort
ascent::CShort),
                CShort -> Status
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CShort
descent::CShort))

-- No need to put this in the IO monad - this info is essentially constant

-- | interface to the X11 library function @XTextExtents()@.
textExtents :: FontStruct -> String -> (FontDirection, Int32, Int32, CharStruct)
textExtents :: FontStruct -> String -> (Status, Int32, Int32, CharStruct)
textExtents FontStruct
font_struct String
string = IO (Status, Int32, Int32, CharStruct)
-> (Status, Int32, Int32, CharStruct)
forall a. IO a -> a
unsafePerformIO (IO (Status, Int32, Int32, CharStruct)
 -> (Status, Int32, Int32, CharStruct))
-> IO (Status, Int32, Int32, CharStruct)
-> (Status, Int32, Int32, CharStruct)
forall a b. (a -> b) -> a -> b
$
        String
-> (CStringLen -> IO (Status, Int32, Int32, CharStruct))
-> IO (Status, Int32, Int32, CharStruct)
forall a. String -> (CStringLen -> IO a) -> IO a
withCStringLen String
string ((CStringLen -> IO (Status, Int32, Int32, CharStruct))
 -> IO (Status, Int32, Int32, CharStruct))
-> (CStringLen -> IO (Status, Int32, Int32, CharStruct))
-> IO (Status, Int32, Int32, CharStruct)
forall a b. (a -> b) -> a -> b
$ \ (CString
c_string, Int
nchars) ->
        (Ptr Status -> IO (Status, Int32, Int32, CharStruct))
-> IO (Status, Int32, Int32, CharStruct)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Status -> IO (Status, Int32, Int32, CharStruct))
 -> IO (Status, Int32, Int32, CharStruct))
-> (Ptr Status -> IO (Status, Int32, Int32, CharStruct))
-> IO (Status, Int32, Int32, CharStruct)
forall a b. (a -> b) -> a -> b
$ \ Ptr Status
direction_return ->
        (Ptr Int32 -> IO (Status, Int32, Int32, CharStruct))
-> IO (Status, Int32, Int32, CharStruct)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Int32 -> IO (Status, Int32, Int32, CharStruct))
 -> IO (Status, Int32, Int32, CharStruct))
-> (Ptr Int32 -> IO (Status, Int32, Int32, CharStruct))
-> IO (Status, Int32, Int32, CharStruct)
forall a b. (a -> b) -> a -> b
$ \ Ptr Int32
font_ascent_return ->
        (Ptr Int32 -> IO (Status, Int32, Int32, CharStruct))
-> IO (Status, Int32, Int32, CharStruct)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Int32 -> IO (Status, Int32, Int32, CharStruct))
 -> IO (Status, Int32, Int32, CharStruct))
-> (Ptr Int32 -> IO (Status, Int32, Int32, CharStruct))
-> IO (Status, Int32, Int32, CharStruct)
forall a b. (a -> b) -> a -> b
$ \ Ptr Int32
font_descent_return ->
        Int
-> (Ptr CharStruct -> IO (Status, Int32, Int32, CharStruct))
-> IO (Status, Int32, Int32, CharStruct)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (Int
12) ((Ptr CharStruct -> IO (Status, Int32, Int32, CharStruct))
 -> IO (Status, Int32, Int32, CharStruct))
-> (Ptr CharStruct -> IO (Status, Int32, Int32, CharStruct))
-> IO (Status, Int32, Int32, CharStruct)
forall a b. (a -> b) -> a -> b
$ \ Ptr CharStruct
overall_return -> do
{-# LINE 169 "Graphics/X11/Xlib/Font.hsc" #-}
        _ <- xTextExtents font_struct c_string (fromIntegral nchars) direction_return
                font_ascent_return font_descent_return overall_return
        direction <- peek direction_return
        ascent <- peek font_ascent_return
        descent <- peek font_descent_return
        cs <- peekCharStruct overall_return
        return (direction, ascent, descent, cs)
foreign import ccall unsafe "HsXlib.h XTextExtents"
        xTextExtents :: FontStruct -> CString -> CInt ->
                Ptr FontDirection -> Ptr Int32 -> Ptr Int32 ->
                Ptr CharStruct -> IO CInt

-- No need to put ths in the IO monad - this info is essentially constant

-- | interface to the X11 library function @XTextWidth()@.
textWidth :: FontStruct -> String -> Int32
textWidth :: FontStruct -> String -> Int32
textWidth FontStruct
font_struct String
string = IO Int32 -> Int32
forall a. IO a -> a
unsafePerformIO (IO Int32 -> Int32) -> IO Int32 -> Int32
forall a b. (a -> b) -> a -> b
$
        String -> (CStringLen -> IO Int32) -> IO Int32
forall a. String -> (CStringLen -> IO a) -> IO a
withCStringLen String
string ((CStringLen -> IO Int32) -> IO Int32)
-> (CStringLen -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ (CString
c_string, Int
len) ->
        FontStruct -> CString -> Status -> IO Int32
xTextWidth FontStruct
font_struct CString
c_string (Int -> Status
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
foreign import ccall unsafe "HsXlib.h XTextWidth"
        xTextWidth :: FontStruct -> CString -> CInt -> IO Int32

-- XTextExtents16 omitted
-- XTextWidth16 omitted

-- XGetFontProperty omitted
-- XFreeFontInfo omitted
-- XFreeFontNames omitted

-- XCreateFontSet omitted (no documentation available)
-- XFreeFontSet omitted (no documentation available)
-- XFontsOfFontSet omitted (no documentation available)
-- XBaseFontNameListOfFontSet omitted (no documentation available)
-- XLocaleOfFontSet omitted (no documentation available)
-- XExtentsOfFontSet omitted (no documentation available)

-- XContextDependentDrawing omitted
-- XDirectionalDependentDrawing omitted
-- XContextualDrawing omitted

-- XmbTextEscapement omitted
-- XwcTextEscapement omitted
-- XmbTextExtents omitted
-- XwcTextExtents omitted
-- XmbTextPerCharExtents omitted
-- XwcTextPerCharExtents omitted
-- XmbDrawText omitted
-- XwcDrawText omitted
-- XmbDrawString omitted
-- XwcDrawString omitted
-- XmbDrawImageString omitted
-- XwcDrawImageString omitted

-- XOpenIM omitted
-- XCloseIM omitted
-- XGetIMValues omitted
-- XSetIMValues omitted
-- DisplayOfIM omitted
-- XLocaleOfIM omitted

-- XCreateIC omitted
-- XDestroyIC omitted
-- XSetICFocus omitted
-- XUnsetICFocus omitted
-- XwcResetIC omitted
-- XmbResetIC omitted
-- XSetICValues omitted
-- XGetICValues omitted
-- XIMOfIC omitted

-- XRegisterIMInstantiateCallback omitted
-- XUnregisterIMInstantiateCallback omitted

-- XInternalConnectionNumbers omitted
-- XProcessInternalConnection omitted
-- XAddConnectionWatch omitted
-- XRemoveConnectionWatch omitted

-- XmbLookupString omitted
-- XwcLookupString omitted

----------------------------------------------------------------
-- End
----------------------------------------------------------------