module Graphics.UI.Gtk.Selectors.FontButton (
FontButton,
FontButtonClass,
castToFontButton, gTypeFontButton,
toFontButton,
fontButtonNew,
fontButtonNewWithFont,
fontButtonSetFontName,
fontButtonGetFontName,
fontButtonSetShowStyle,
fontButtonGetShowStyle,
fontButtonSetShowSize,
fontButtonGetShowSize,
fontButtonSetUseFont,
fontButtonGetUseFont,
fontButtonSetUseSize,
fontButtonGetUseSize,
fontButtonSetTitle,
fontButtonGetTitle,
fontButtonTitle,
fontButtonFontName,
fontButtonUseFont,
fontButtonUseSize,
fontButtonShowStyle,
fontButtonShowSize,
onFontSet,
afterFontSet,
) 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
import Graphics.UI.Gtk.Signals
fontButtonNew :: IO FontButton
fontButtonNew =
makeNewObject mkFontButton $
liftM (castPtr :: Ptr Widget -> Ptr FontButton) $
gtk_font_button_new
fontButtonNewWithFont :: GlibString string
=> string
-> IO FontButton
fontButtonNewWithFont fontname =
makeNewObject mkFontButton $
liftM (castPtr :: Ptr Widget -> Ptr FontButton) $
withUTFString fontname $ \fontnamePtr ->
gtk_font_button_new_with_font
fontnamePtr
fontButtonSetFontName :: (FontButtonClass self, GlibString string) => self
-> string
-> IO Bool
fontButtonSetFontName self fontname =
liftM toBool $
withUTFString fontname $ \fontnamePtr ->
(\(FontButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_button_set_font_name argPtr1 arg2)
(toFontButton self)
fontnamePtr
fontButtonGetFontName :: (FontButtonClass self, GlibString string) => self
-> IO string
fontButtonGetFontName self =
(\(FontButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_button_get_font_name argPtr1)
(toFontButton self)
>>= peekUTFString
fontButtonSetShowStyle :: FontButtonClass self => self
-> Bool
-> IO ()
fontButtonSetShowStyle self showStyle =
(\(FontButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_button_set_show_style argPtr1 arg2)
(toFontButton self)
(fromBool showStyle)
fontButtonGetShowStyle :: FontButtonClass self => self
-> IO Bool
fontButtonGetShowStyle self =
liftM toBool $
(\(FontButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_button_get_show_style argPtr1)
(toFontButton self)
fontButtonSetShowSize :: FontButtonClass self => self
-> Bool
-> IO ()
fontButtonSetShowSize self showSize =
(\(FontButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_button_set_show_size argPtr1 arg2)
(toFontButton self)
(fromBool showSize)
fontButtonGetShowSize :: FontButtonClass self => self
-> IO Bool
fontButtonGetShowSize self =
liftM toBool $
(\(FontButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_button_get_show_size argPtr1)
(toFontButton self)
fontButtonSetUseFont :: FontButtonClass self => self
-> Bool
-> IO ()
fontButtonSetUseFont self useFont =
(\(FontButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_button_set_use_font argPtr1 arg2)
(toFontButton self)
(fromBool useFont)
fontButtonGetUseFont :: FontButtonClass self => self
-> IO Bool
fontButtonGetUseFont self =
liftM toBool $
(\(FontButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_button_get_use_font argPtr1)
(toFontButton self)
fontButtonSetUseSize :: FontButtonClass self => self
-> Bool
-> IO ()
fontButtonSetUseSize self useSize =
(\(FontButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_button_set_use_size argPtr1 arg2)
(toFontButton self)
(fromBool useSize)
fontButtonGetUseSize :: FontButtonClass self => self
-> IO Bool
fontButtonGetUseSize self =
liftM toBool $
(\(FontButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_button_get_use_size argPtr1)
(toFontButton self)
fontButtonSetTitle :: (FontButtonClass self, GlibString string) => self
-> string
-> IO ()
fontButtonSetTitle self title =
withUTFString title $ \titlePtr ->
(\(FontButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_button_set_title argPtr1 arg2)
(toFontButton self)
titlePtr
fontButtonGetTitle :: (FontButtonClass self, GlibString string) => self
-> IO string
fontButtonGetTitle self =
(\(FontButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_font_button_get_title argPtr1)
(toFontButton self)
>>= peekUTFString
fontButtonTitle :: (FontButtonClass self, GlibString string) => Attr self string
fontButtonTitle = newAttr
fontButtonGetTitle
fontButtonSetTitle
fontButtonFontName :: (FontButtonClass self, GlibString string) => Attr self string
fontButtonFontName = newAttrFromStringProperty "font-name"
fontButtonUseFont :: FontButtonClass self => Attr self Bool
fontButtonUseFont = newAttr
fontButtonGetUseFont
fontButtonSetUseFont
fontButtonUseSize :: FontButtonClass self => Attr self Bool
fontButtonUseSize = newAttr
fontButtonGetUseSize
fontButtonSetUseSize
fontButtonShowStyle :: FontButtonClass self => Attr self Bool
fontButtonShowStyle = newAttr
fontButtonGetShowStyle
fontButtonSetShowStyle
fontButtonShowSize :: FontButtonClass self => Attr self Bool
fontButtonShowSize = newAttr
fontButtonGetShowSize
fontButtonSetShowSize
onFontSet, afterFontSet :: FontButtonClass self => self
-> IO ()
-> IO (ConnectId self)
onFontSet = connect_NONE__NONE "font-set" False
afterFontSet = connect_NONE__NONE "font-set" True
foreign import ccall safe "gtk_font_button_new"
gtk_font_button_new :: (IO (Ptr Widget))
foreign import ccall safe "gtk_font_button_new_with_font"
gtk_font_button_new_with_font :: ((Ptr CChar) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_font_button_set_font_name"
gtk_font_button_set_font_name :: ((Ptr FontButton) -> ((Ptr CChar) -> (IO CInt)))
foreign import ccall safe "gtk_font_button_get_font_name"
gtk_font_button_get_font_name :: ((Ptr FontButton) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_font_button_set_show_style"
gtk_font_button_set_show_style :: ((Ptr FontButton) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_font_button_get_show_style"
gtk_font_button_get_show_style :: ((Ptr FontButton) -> (IO CInt))
foreign import ccall safe "gtk_font_button_set_show_size"
gtk_font_button_set_show_size :: ((Ptr FontButton) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_font_button_get_show_size"
gtk_font_button_get_show_size :: ((Ptr FontButton) -> (IO CInt))
foreign import ccall safe "gtk_font_button_set_use_font"
gtk_font_button_set_use_font :: ((Ptr FontButton) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_font_button_get_use_font"
gtk_font_button_get_use_font :: ((Ptr FontButton) -> (IO CInt))
foreign import ccall safe "gtk_font_button_set_use_size"
gtk_font_button_set_use_size :: ((Ptr FontButton) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_font_button_get_use_size"
gtk_font_button_get_use_size :: ((Ptr FontButton) -> (IO CInt))
foreign import ccall safe "gtk_font_button_set_title"
gtk_font_button_set_title :: ((Ptr FontButton) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_font_button_get_title"
gtk_font_button_get_title :: ((Ptr FontButton) -> (IO (Ptr CChar)))