module Graphics.UI.Gtk.Selectors.FileChooserButton (
FileChooserButton,
FileChooserButtonClass,
castToFileChooserButton, gTypeFileChooserButton,
toFileChooserButton,
fileChooserButtonNew,
fileChooserButtonNewWithDialog,
fileChooserButtonGetTitle,
fileChooserButtonSetTitle,
fileChooserButtonGetWidthChars,
fileChooserButtonSetWidthChars,
fileChooserButtonDialog,
fileChooserButtonTitle,
fileChooserButtonWidthChars,
) 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.Selectors.FileChooser (FileChooserAction)
instance FileChooserClass FileChooserButton
fileChooserButtonNew :: GlibString string
=> string
-> FileChooserAction
-> IO FileChooserButton
fileChooserButtonNew title action =
makeNewObject mkFileChooserButton $
liftM (castPtr :: Ptr Widget -> Ptr FileChooserButton) $
withUTFString title $ \titlePtr ->
gtk_file_chooser_button_new
titlePtr
((fromIntegral . fromEnum) action)
fileChooserButtonNewWithDialog :: FileChooserDialogClass dialog =>
dialog
-> IO FileChooserButton
fileChooserButtonNewWithDialog dialog =
makeNewObject mkFileChooserButton $
liftM (castPtr :: Ptr Widget -> Ptr FileChooserButton) $
(\(Widget arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_button_new_with_dialog argPtr1)
(toWidget dialog)
fileChooserButtonGetTitle :: (FileChooserButtonClass self, GlibString string) => self
-> IO string
fileChooserButtonGetTitle self =
(\(FileChooserButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_button_get_title argPtr1)
(toFileChooserButton self)
>>= peekUTFString
fileChooserButtonSetTitle :: (FileChooserButtonClass self, GlibString string) => self
-> string
-> IO ()
fileChooserButtonSetTitle self title =
withUTFString title $ \titlePtr ->
(\(FileChooserButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_button_set_title argPtr1 arg2)
(toFileChooserButton self)
titlePtr
fileChooserButtonGetWidthChars :: FileChooserButtonClass self => self
-> IO Int
fileChooserButtonGetWidthChars self =
liftM fromIntegral $
(\(FileChooserButton arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_button_get_width_chars argPtr1)
(toFileChooserButton self)
fileChooserButtonSetWidthChars :: FileChooserButtonClass self => self
-> Int
-> IO ()
fileChooserButtonSetWidthChars self nChars =
(\(FileChooserButton arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_file_chooser_button_set_width_chars argPtr1 arg2)
(toFileChooserButton self)
(fromIntegral nChars)
fileChooserButtonDialog :: (FileChooserButtonClass self, FileChooserDialogClass fileChooserDialog) => WriteAttr self fileChooserDialog
fileChooserButtonDialog = writeAttrFromObjectProperty "dialog"
gtk_file_chooser_dialog_get_type
fileChooserButtonTitle :: (FileChooserButtonClass self, GlibString string) => Attr self string
fileChooserButtonTitle = newAttr
fileChooserButtonGetTitle
fileChooserButtonSetTitle
fileChooserButtonWidthChars :: FileChooserButtonClass self => Attr self Int
fileChooserButtonWidthChars = newAttr
fileChooserButtonGetWidthChars
fileChooserButtonSetWidthChars
foreign import ccall safe "gtk_file_chooser_button_new"
gtk_file_chooser_button_new :: ((Ptr CChar) -> (CInt -> (IO (Ptr Widget))))
foreign import ccall safe "gtk_file_chooser_button_new_with_dialog"
gtk_file_chooser_button_new_with_dialog :: ((Ptr Widget) -> (IO (Ptr Widget)))
foreign import ccall safe "gtk_file_chooser_button_get_title"
gtk_file_chooser_button_get_title :: ((Ptr FileChooserButton) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_file_chooser_button_set_title"
gtk_file_chooser_button_set_title :: ((Ptr FileChooserButton) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_file_chooser_button_get_width_chars"
gtk_file_chooser_button_get_width_chars :: ((Ptr FileChooserButton) -> (IO CInt))
foreign import ccall safe "gtk_file_chooser_button_set_width_chars"
gtk_file_chooser_button_set_width_chars :: ((Ptr FileChooserButton) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_file_chooser_dialog_get_type"
gtk_file_chooser_dialog_get_type :: CULong