module Graphics.UI.Gtk.Selectors.FontSelection (
FontSelection,
FontSelectionClass,
castToFontSelection, gTypeFontSelection,
toFontSelection,
fontSelectionNew,
fontSelectionGetFontName,
fontSelectionSetFontName,
fontSelectionGetPreviewText,
fontSelectionSetPreviewText,
fontSelectionFontName,
fontSelectionPreviewText,
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.Attributes
import System.Glib.Properties
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Types
fontSelectionNew :: IO FontSelection
fontSelectionNew =
makeNewObject mkFontSelection $
liftM (castPtr :: Ptr Widget -> Ptr FontSelection) $
gtk_font_selection_new
fontSelectionGetFontName :: FontSelectionClass self => self
-> IO (Maybe String)
fontSelectionGetFontName self =
(\(FontSelection arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_selection_get_font_name argPtr1)
(toFontSelection self)
>>= maybePeek readUTFString
fontSelectionSetFontName :: FontSelectionClass self => self
-> String
-> IO Bool
fontSelectionSetFontName self fontname =
liftM toBool $
withUTFString fontname $ \fontnamePtr ->
(\(FontSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_selection_set_font_name argPtr1 arg2)
(toFontSelection self)
fontnamePtr
fontSelectionGetPreviewText :: FontSelectionClass self => self -> IO String
fontSelectionGetPreviewText self =
(\(FontSelection arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_selection_get_preview_text argPtr1)
(toFontSelection self)
>>= peekUTFString
fontSelectionSetPreviewText :: FontSelectionClass self => self -> String -> IO ()
fontSelectionSetPreviewText self text =
withUTFString text $ \textPtr ->
(\(FontSelection arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_selection_set_preview_text argPtr1 arg2)
(toFontSelection self)
textPtr
fontSelectionFontName :: FontSelectionClass self => Attr self String
fontSelectionFontName = newAttrFromStringProperty "font_name"
fontSelectionPreviewText :: FontSelectionClass self => Attr self String
fontSelectionPreviewText = newAttr
fontSelectionGetPreviewText
fontSelectionSetPreviewText
foreign import ccall unsafe "gtk_font_selection_new"
gtk_font_selection_new :: (IO (Ptr Widget))
foreign import ccall unsafe "gtk_font_selection_get_font_name"
gtk_font_selection_get_font_name :: ((Ptr FontSelection) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_font_selection_set_font_name"
gtk_font_selection_set_font_name :: ((Ptr FontSelection) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall unsafe "gtk_font_selection_get_preview_text"
gtk_font_selection_get_preview_text :: ((Ptr FontSelection) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_font_selection_set_preview_text"
gtk_font_selection_set_preview_text :: ((Ptr FontSelection) -> ((Ptr CChar) -> (IO ())))