{-# LINE 1 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
module Graphics.Rendering.Cairo.Internal.Fonts.FontOptions where
import Graphics.Rendering.Cairo.Types
{-# LINE 16 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
import Foreign
import Foreign.C
{-# LINE 21 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsCreate :: IO (FontOptions)
fontOptionsCreate =
fontOptionsCreate'_ >>= \res ->
mkFontOptions res >>= \res' ->
return (res')
{-# LINE 23 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsCopy :: FontOptions -> IO (FontOptions)
fontOptionsCopy a1 =
withFontOptions a1 $ \a1' ->
fontOptionsCopy'_ a1' >>= \res ->
mkFontOptions res >>= \res' ->
return (res')
{-# LINE 24 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsDestroy :: FontOptions -> IO ()
fontOptionsDestroy a1 =
withFontOptions a1 $ \a1' ->
fontOptionsDestroy'_ a1' >>= \res ->
return ()
{-# LINE 25 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsStatus :: FontOptions -> IO (Status)
fontOptionsStatus a1 =
withFontOptions a1 $ \a1' ->
fontOptionsStatus'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 26 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsMerge :: FontOptions -> FontOptions -> IO ()
fontOptionsMerge a1 a2 =
withFontOptions a1 $ \a1' ->
withFontOptions a2 $ \a2' ->
fontOptionsMerge'_ a1' a2' >>= \res ->
return ()
{-# LINE 27 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsHash :: FontOptions -> IO (Int)
fontOptionsHash a1 =
withFontOptions a1 $ \a1' ->
fontOptionsHash'_ a1' >>= \res ->
let {res' = cIntConv res} in
return (res')
{-# LINE 28 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsEqual :: FontOptions -> FontOptions -> IO (Bool)
fontOptionsEqual a1 a2 =
withFontOptions a1 $ \a1' ->
withFontOptions a2 $ \a2' ->
fontOptionsEqual'_ a1' a2' >>= \res ->
let {res' = cToBool res} in
return (res')
{-# LINE 29 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsSetAntialias :: FontOptions -> Antialias -> IO ()
fontOptionsSetAntialias a1 a2 =
withFontOptions a1 $ \a1' ->
let {a2' = cFromEnum a2} in
fontOptionsSetAntialias'_ a1' a2' >>= \res ->
return ()
{-# LINE 30 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsGetAntialias :: FontOptions -> IO (Antialias)
fontOptionsGetAntialias a1 =
withFontOptions a1 $ \a1' ->
fontOptionsGetAntialias'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 31 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsSetSubpixelOrder :: FontOptions -> SubpixelOrder -> IO ()
fontOptionsSetSubpixelOrder a1 a2 =
withFontOptions a1 $ \a1' ->
let {a2' = cFromEnum a2} in
fontOptionsSetSubpixelOrder'_ a1' a2' >>= \res ->
return ()
{-# LINE 32 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsGetSubpixelOrder :: FontOptions -> IO (SubpixelOrder)
fontOptionsGetSubpixelOrder a1 =
withFontOptions a1 $ \a1' ->
fontOptionsGetSubpixelOrder'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 33 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsSetHintStyle :: FontOptions -> HintStyle -> IO ()
fontOptionsSetHintStyle a1 a2 =
withFontOptions a1 $ \a1' ->
let {a2' = cFromEnum a2} in
fontOptionsSetHintStyle'_ a1' a2' >>= \res ->
return ()
{-# LINE 34 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsGetHintStyle :: FontOptions -> IO (HintStyle)
fontOptionsGetHintStyle a1 =
withFontOptions a1 $ \a1' ->
fontOptionsGetHintStyle'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 35 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsSetHintMetrics :: FontOptions -> HintMetrics -> IO ()
fontOptionsSetHintMetrics a1 a2 =
withFontOptions a1 $ \a1' ->
let {a2' = cFromEnum a2} in
fontOptionsSetHintMetrics'_ a1' a2' >>= \res ->
return ()
{-# LINE 36 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
fontOptionsGetHintMetrics :: FontOptions -> IO (HintMetrics)
fontOptionsGetHintMetrics a1 =
withFontOptions a1 $ \a1' ->
fontOptionsGetHintMetrics'_ a1' >>= \res ->
let {res' = cToEnum res} in
return (res')
{-# LINE 37 "./Graphics/Rendering/Cairo/Internal/Fonts/FontOptions.chs" #-}
foreign import ccall safe "cairo_font_options_create"
fontOptionsCreate'_ :: (IO (Ptr FontOptions))
foreign import ccall safe "cairo_font_options_copy"
fontOptionsCopy'_ :: ((Ptr FontOptions) -> (IO (Ptr FontOptions)))
foreign import ccall safe "cairo_font_options_destroy"
fontOptionsDestroy'_ :: ((Ptr FontOptions) -> (IO ()))
foreign import ccall safe "cairo_font_options_status"
fontOptionsStatus'_ :: ((Ptr FontOptions) -> (IO CInt))
foreign import ccall safe "cairo_font_options_merge"
fontOptionsMerge'_ :: ((Ptr FontOptions) -> ((Ptr FontOptions) -> (IO ())))
foreign import ccall safe "cairo_font_options_hash"
fontOptionsHash'_ :: ((Ptr FontOptions) -> (IO CULong))
foreign import ccall safe "cairo_font_options_equal"
fontOptionsEqual'_ :: ((Ptr FontOptions) -> ((Ptr FontOptions) -> (IO CInt)))
foreign import ccall safe "cairo_font_options_set_antialias"
fontOptionsSetAntialias'_ :: ((Ptr FontOptions) -> (CInt -> (IO ())))
foreign import ccall safe "cairo_font_options_get_antialias"
fontOptionsGetAntialias'_ :: ((Ptr FontOptions) -> (IO CInt))
foreign import ccall safe "cairo_font_options_set_subpixel_order"
fontOptionsSetSubpixelOrder'_ :: ((Ptr FontOptions) -> (CInt -> (IO ())))
foreign import ccall safe "cairo_font_options_get_subpixel_order"
fontOptionsGetSubpixelOrder'_ :: ((Ptr FontOptions) -> (IO CInt))
foreign import ccall safe "cairo_font_options_set_hint_style"
fontOptionsSetHintStyle'_ :: ((Ptr FontOptions) -> (CInt -> (IO ())))
foreign import ccall safe "cairo_font_options_get_hint_style"
fontOptionsGetHintStyle'_ :: ((Ptr FontOptions) -> (IO CInt))
foreign import ccall safe "cairo_font_options_set_hint_metrics"
fontOptionsSetHintMetrics'_ :: ((Ptr FontOptions) -> (CInt -> (IO ())))
foreign import ccall safe "cairo_font_options_get_hint_metrics"
fontOptionsGetHintMetrics'_ :: ((Ptr FontOptions) -> (IO CInt))