module Graphics.UI.Gtk.Selectors.FontSelectionDialog (
FontSelectionDialog,
FontSelectionDialogClass,
castToFontSelectionDialog, gTypeFontSelectionDialog,
toFontSelectionDialog,
fontSelectionDialogNew,
fontSelectionDialogGetFontName,
fontSelectionDialogSetFontName,
fontSelectionDialogGetPreviewText,
fontSelectionDialogSetPreviewText,
fontSelectionDialogGetCancelButton,
fontSelectionDialogGetOkButton,
fontSelectionDialogGetFontSelection,
fontSelectionDialogPreviewText,
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.Attributes
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Types
fontSelectionDialogNew :: GlibString string
=> string
-> IO FontSelectionDialog
fontSelectionDialogNew title =
makeNewObject mkFontSelectionDialog $
liftM (castPtr :: Ptr Widget -> Ptr FontSelectionDialog) $
withUTFString title $ \titlePtr ->
gtk_font_selection_dialog_new
titlePtr
fontSelectionDialogGetFontName :: (FontSelectionDialogClass self, GlibString string) => self
-> IO (Maybe string)
fontSelectionDialogGetFontName self =
(\(FontSelectionDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_selection_dialog_get_font_name argPtr1)
(toFontSelectionDialog self)
>>= maybePeek readUTFString
fontSelectionDialogSetFontName :: (FontSelectionDialogClass self, GlibString string) => self
-> string
-> IO Bool
fontSelectionDialogSetFontName self fontname =
liftM toBool $
withUTFString fontname $ \fontnamePtr ->
(\(FontSelectionDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_selection_dialog_set_font_name argPtr1 arg2)
(toFontSelectionDialog self)
fontnamePtr
fontSelectionDialogGetPreviewText :: (FontSelectionDialogClass self, GlibString string) => self -> IO string
fontSelectionDialogGetPreviewText self =
(\(FontSelectionDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_selection_dialog_get_preview_text argPtr1)
(toFontSelectionDialog self)
>>= peekUTFString
fontSelectionDialogSetPreviewText :: (FontSelectionDialogClass self, GlibString string) => self -> string -> IO ()
fontSelectionDialogSetPreviewText self text =
withUTFString text $ \textPtr ->
(\(FontSelectionDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_selection_dialog_set_preview_text argPtr1 arg2)
(toFontSelectionDialog self)
textPtr
fontSelectionDialogGetCancelButton :: FontSelectionDialogClass self => self
-> IO Widget
fontSelectionDialogGetCancelButton self =
makeNewObject mkWidget $
(\(FontSelectionDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_selection_dialog_get_cancel_button argPtr1)
(toFontSelectionDialog self)
fontSelectionDialogGetOkButton :: FontSelectionDialogClass self => self
-> IO Widget
fontSelectionDialogGetOkButton self =
makeNewObject mkWidget $
(\(FontSelectionDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_selection_dialog_get_ok_button argPtr1)
(toFontSelectionDialog self)
fontSelectionDialogGetFontSelection :: FontSelectionDialogClass self => self
-> IO FontSelection
fontSelectionDialogGetFontSelection self =
makeNewObject mkFontSelection $
liftM (castPtr :: Ptr Widget -> Ptr FontSelection) $
(\(FontSelectionDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_selection_dialog_get_font_selection argPtr1)
(toFontSelectionDialog self)
fontSelectionDialogPreviewText :: (FontSelectionDialogClass self, GlibString string) => Attr self string
fontSelectionDialogPreviewText = newAttr
fontSelectionDialogGetPreviewText
fontSelectionDialogSetPreviewText
foreign import ccall unsafe "gtk_font_selection_dialog_new"
gtk_font_selection_dialog_new :: ((Ptr CChar) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_font_selection_dialog_get_font_name"
gtk_font_selection_dialog_get_font_name :: ((Ptr FontSelectionDialog) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_font_selection_dialog_set_font_name"
gtk_font_selection_dialog_set_font_name :: ((Ptr FontSelectionDialog) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall unsafe "gtk_font_selection_dialog_get_preview_text"
gtk_font_selection_dialog_get_preview_text :: ((Ptr FontSelectionDialog) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_font_selection_dialog_set_preview_text"
gtk_font_selection_dialog_set_preview_text :: ((Ptr FontSelectionDialog) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_font_selection_dialog_get_cancel_button"
gtk_font_selection_dialog_get_cancel_button :: ((Ptr FontSelectionDialog) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_font_selection_dialog_get_ok_button"
gtk_font_selection_dialog_get_ok_button :: ((Ptr FontSelectionDialog) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_font_selection_dialog_get_font_selection"
gtk_font_selection_dialog_get_font_selection :: ((Ptr FontSelectionDialog) -> (IO (Ptr Widget)))