module Graphics.UI.Gtk.Windows.AboutDialog (
AboutDialog,
AboutDialogClass,
castToAboutDialog, gTypeAboutDialog,
toAboutDialog,
aboutDialogNew,
aboutDialogSetEmailHook,
aboutDialogSetUrlHook,
aboutDialogProgramName,
aboutDialogName,
aboutDialogVersion,
aboutDialogCopyright,
aboutDialogComments,
aboutDialogLicense,
aboutDialogWebsite,
aboutDialogWebsiteLabel,
aboutDialogAuthors,
aboutDialogDocumenters,
aboutDialogArtists,
aboutDialogTranslatorCredits,
aboutDialogLogo,
aboutDialogLogoIconName,
aboutDialogWrapLicense,
aboutDialogGetName,
aboutDialogSetName,
aboutDialogGetVersion,
aboutDialogSetVersion,
aboutDialogGetCopyright,
aboutDialogSetCopyright,
aboutDialogGetComments,
aboutDialogSetComments,
aboutDialogGetLicense,
aboutDialogSetLicense,
aboutDialogGetWebsite,
aboutDialogSetWebsite,
aboutDialogGetWebsiteLabel,
aboutDialogSetWebsiteLabel,
aboutDialogSetAuthors,
aboutDialogGetAuthors,
aboutDialogSetArtists,
aboutDialogGetArtists,
aboutDialogSetDocumenters,
aboutDialogGetDocumenters,
aboutDialogGetTranslatorCredits,
aboutDialogSetTranslatorCredits,
aboutDialogGetLogo,
aboutDialogSetLogo,
aboutDialogGetLogoIconName,
aboutDialogSetLogoIconName,
aboutDialogGetWrapLicense,
aboutDialogSetWrapLicense,
) where
import Control.Monad (liftM)
import Data.Maybe (fromMaybe)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.Attributes
import System.Glib.Properties
import System.Glib.GObject (makeNewGObject, destroyFunPtr)
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Types
aboutDialogNew :: IO AboutDialog
aboutDialogNew =
makeNewObject mkAboutDialog $
liftM (castPtr :: Ptr Widget -> Ptr AboutDialog) $
gtk_about_dialog_new
aboutDialogGetName :: AboutDialogClass self => self
-> IO String
aboutDialogGetName self =
(\(AboutDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_get_program_name argPtr1)
(toAboutDialog self)
>>= peekUTFString
aboutDialogSetName :: AboutDialogClass self => self
-> String
-> IO ()
aboutDialogSetName self name =
withUTFString name $ \namePtr ->
(\(AboutDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_set_program_name argPtr1 arg2)
(toAboutDialog self)
namePtr
aboutDialogGetVersion :: AboutDialogClass self => self -> IO String
aboutDialogGetVersion self =
(\(AboutDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_get_version argPtr1)
(toAboutDialog self)
>>= peekUTFString
aboutDialogSetVersion :: AboutDialogClass self => self -> String -> IO ()
aboutDialogSetVersion self version =
withUTFString version $ \versionPtr ->
(\(AboutDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_set_version argPtr1 arg2)
(toAboutDialog self)
versionPtr
aboutDialogGetCopyright :: AboutDialogClass self => self -> IO String
aboutDialogGetCopyright self =
(\(AboutDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_get_copyright argPtr1)
(toAboutDialog self)
>>= peekUTFString
aboutDialogSetCopyright :: AboutDialogClass self => self -> String -> IO ()
aboutDialogSetCopyright self copyright =
withUTFString copyright $ \copyrightPtr ->
(\(AboutDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_set_copyright argPtr1 arg2)
(toAboutDialog self)
copyrightPtr
aboutDialogGetComments :: AboutDialogClass self => self -> IO String
aboutDialogGetComments self =
(\(AboutDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_get_comments argPtr1)
(toAboutDialog self)
>>= peekUTFString
aboutDialogSetComments :: AboutDialogClass self => self -> String -> IO ()
aboutDialogSetComments self comments =
withUTFString comments $ \commentsPtr ->
(\(AboutDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_set_comments argPtr1 arg2)
(toAboutDialog self)
commentsPtr
aboutDialogGetLicense :: AboutDialogClass self => self -> IO (Maybe String)
aboutDialogGetLicense self =
(\(AboutDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_get_license argPtr1)
(toAboutDialog self)
>>= maybePeek peekUTFString
aboutDialogSetLicense :: AboutDialogClass self => self
-> Maybe String
-> IO ()
aboutDialogSetLicense self license =
maybeWith withUTFString license $ \licensePtr ->
(\(AboutDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_set_license argPtr1 arg2)
(toAboutDialog self)
licensePtr
aboutDialogGetWebsite :: AboutDialogClass self => self -> IO String
aboutDialogGetWebsite self =
(\(AboutDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_get_website argPtr1)
(toAboutDialog self)
>>= peekUTFString
aboutDialogSetWebsite :: AboutDialogClass self => self
-> String
-> IO ()
aboutDialogSetWebsite self website =
withUTFString website $ \websitePtr ->
(\(AboutDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_set_website argPtr1 arg2)
(toAboutDialog self)
websitePtr
aboutDialogGetWebsiteLabel :: AboutDialogClass self => self -> IO String
aboutDialogGetWebsiteLabel self =
(\(AboutDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_get_website_label argPtr1)
(toAboutDialog self)
>>= peekUTFString
aboutDialogSetWebsiteLabel :: AboutDialogClass self => self -> String -> IO ()
aboutDialogSetWebsiteLabel self websiteLabel =
withUTFString websiteLabel $ \websiteLabelPtr ->
(\(AboutDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_set_website_label argPtr1 arg2)
(toAboutDialog self)
websiteLabelPtr
aboutDialogSetAuthors :: AboutDialogClass self => self
-> [String]
-> IO ()
aboutDialogSetAuthors self authors =
withUTFStringArray0 authors $ \authorsPtr ->
(\(AboutDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_set_authors argPtr1 arg2)
(toAboutDialog self)
authorsPtr
aboutDialogGetAuthors :: AboutDialogClass self => self -> IO [String]
aboutDialogGetAuthors self =
(\(AboutDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_get_authors argPtr1)
(toAboutDialog self)
>>= peekUTFStringArray0
aboutDialogSetArtists :: AboutDialogClass self => self
-> [String]
-> IO ()
aboutDialogSetArtists self artists =
withUTFStringArray0 artists $ \artistsPtr ->
(\(AboutDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_set_artists argPtr1 arg2)
(toAboutDialog self)
artistsPtr
aboutDialogGetArtists :: AboutDialogClass self => self -> IO [String]
aboutDialogGetArtists self =
(\(AboutDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_get_artists argPtr1)
(toAboutDialog self)
>>= peekUTFStringArray0
aboutDialogSetDocumenters :: AboutDialogClass self => self
-> [String]
-> IO ()
aboutDialogSetDocumenters self documenters =
withUTFStringArray0 documenters $ \documentersPtr ->
(\(AboutDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_set_documenters argPtr1 arg2)
(toAboutDialog self)
documentersPtr
aboutDialogGetDocumenters :: AboutDialogClass self => self -> IO [String]
aboutDialogGetDocumenters self =
(\(AboutDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_get_documenters argPtr1)
(toAboutDialog self)
>>= peekUTFStringArray0
aboutDialogGetTranslatorCredits :: AboutDialogClass self => self -> IO String
aboutDialogGetTranslatorCredits self =
(\(AboutDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_get_translator_credits argPtr1)
(toAboutDialog self)
>>= peekUTFString
aboutDialogSetTranslatorCredits :: AboutDialogClass self => self -> String -> IO ()
aboutDialogSetTranslatorCredits self translatorCredits =
withUTFString translatorCredits $ \translatorCreditsPtr ->
(\(AboutDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_set_translator_credits argPtr1 arg2)
(toAboutDialog self)
translatorCreditsPtr
aboutDialogGetLogo :: AboutDialogClass self => self -> IO Pixbuf
aboutDialogGetLogo self =
makeNewGObject mkPixbuf $
(\(AboutDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_get_logo argPtr1)
(toAboutDialog self)
aboutDialogSetLogo :: AboutDialogClass self => self
-> Maybe Pixbuf
-> IO ()
aboutDialogSetLogo self logo =
(\(AboutDialog arg1) (Pixbuf arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_about_dialog_set_logo argPtr1 argPtr2)
(toAboutDialog self)
(fromMaybe (Pixbuf nullForeignPtr) logo)
aboutDialogGetLogoIconName :: AboutDialogClass self => self -> IO String
aboutDialogGetLogoIconName self =
(\(AboutDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_get_logo_icon_name argPtr1)
(toAboutDialog self)
>>= peekUTFString
aboutDialogSetLogoIconName :: AboutDialogClass self => self
-> Maybe String
-> IO ()
aboutDialogSetLogoIconName self iconName =
maybeWith withUTFString iconName $ \iconNamePtr ->
(\(AboutDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_set_logo_icon_name argPtr1 arg2)
(toAboutDialog self)
iconNamePtr
aboutDialogSetEmailHook ::
(String -> IO ())
-> IO ()
aboutDialogSetEmailHook func = do
funcPtr <- mkAboutDialogActivateLinkFunc (\_ linkPtr _ -> do
link <- peekUTFString linkPtr
func link
)
gtk_about_dialog_set_email_hook
funcPtr
(castFunPtrToPtr funcPtr)
destroyFunPtr
return ()
aboutDialogSetUrlHook ::
(String -> IO ())
-> IO ()
aboutDialogSetUrlHook func = do
funcPtr <- mkAboutDialogActivateLinkFunc (\_ linkPtr _ -> do
link <- peekUTFString linkPtr
func link
)
gtk_about_dialog_set_url_hook
funcPtr
(castFunPtrToPtr funcPtr)
destroyFunPtr
return ()
type AboutDialogActivateLinkFunc = FunPtr (((Ptr AboutDialog) -> ((Ptr CChar) -> ((Ptr ()) -> (IO ())))))
foreign import ccall "wrapper" mkAboutDialogActivateLinkFunc ::
(Ptr AboutDialog -> CString -> Ptr () -> IO ()) -> IO AboutDialogActivateLinkFunc
aboutDialogGetWrapLicense :: AboutDialogClass self => self
-> IO Bool
aboutDialogGetWrapLicense self =
liftM toBool $
(\(AboutDialog arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_get_wrap_license argPtr1)
(toAboutDialog self)
aboutDialogSetWrapLicense :: AboutDialogClass self => self
-> Bool
-> IO ()
aboutDialogSetWrapLicense self wrapLicense =
(\(AboutDialog arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_about_dialog_set_wrap_license argPtr1 arg2)
(toAboutDialog self)
(fromBool wrapLicense)
aboutDialogName :: AboutDialogClass self => Attr self String
aboutDialogName = newAttrFromStringProperty "name"
aboutDialogProgramName :: AboutDialogClass self => Attr self String
aboutDialogProgramName = newAttrFromStringProperty "program-name"
aboutDialogVersion :: AboutDialogClass self => Attr self String
aboutDialogVersion = newAttrFromStringProperty "version"
aboutDialogCopyright :: AboutDialogClass self => Attr self String
aboutDialogCopyright = newAttrFromStringProperty "copyright"
aboutDialogComments :: AboutDialogClass self => Attr self String
aboutDialogComments = newAttrFromStringProperty "comments"
aboutDialogLicense :: AboutDialogClass self => Attr self (Maybe String)
aboutDialogLicense = newAttrFromMaybeStringProperty "license"
aboutDialogWebsite :: AboutDialogClass self => Attr self String
aboutDialogWebsite = newAttrFromStringProperty "website"
aboutDialogWebsiteLabel :: AboutDialogClass self => Attr self String
aboutDialogWebsiteLabel = newAttrFromStringProperty "website-label"
aboutDialogAuthors :: AboutDialogClass self => Attr self [String]
aboutDialogAuthors = newAttr
aboutDialogGetAuthors
aboutDialogSetAuthors
aboutDialogDocumenters :: AboutDialogClass self => Attr self [String]
aboutDialogDocumenters = newAttr
aboutDialogGetDocumenters
aboutDialogSetDocumenters
aboutDialogArtists :: AboutDialogClass self => Attr self [String]
aboutDialogArtists = newAttr
aboutDialogGetArtists
aboutDialogSetArtists
aboutDialogTranslatorCredits :: AboutDialogClass self => Attr self String
aboutDialogTranslatorCredits = newAttrFromStringProperty "translator-credits"
aboutDialogLogo :: AboutDialogClass self => ReadWriteAttr self Pixbuf (Maybe Pixbuf)
aboutDialogLogo = newAttr
aboutDialogGetLogo
aboutDialogSetLogo
aboutDialogLogoIconName :: AboutDialogClass self => ReadWriteAttr self String (Maybe String)
aboutDialogLogoIconName = newAttr
aboutDialogGetLogoIconName
aboutDialogSetLogoIconName
aboutDialogWrapLicense :: AboutDialogClass self => Attr self Bool
aboutDialogWrapLicense = newAttrFromBoolProperty "wrap-license"
foreign import ccall safe "gtk_about_dialog_new"
gtk_about_dialog_new :: (IO (Ptr Widget))
foreign import ccall safe "gtk_about_dialog_get_program_name"
gtk_about_dialog_get_program_name :: ((Ptr AboutDialog) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_about_dialog_set_program_name"
gtk_about_dialog_set_program_name :: ((Ptr AboutDialog) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_about_dialog_get_version"
gtk_about_dialog_get_version :: ((Ptr AboutDialog) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_about_dialog_set_version"
gtk_about_dialog_set_version :: ((Ptr AboutDialog) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_about_dialog_get_copyright"
gtk_about_dialog_get_copyright :: ((Ptr AboutDialog) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_about_dialog_set_copyright"
gtk_about_dialog_set_copyright :: ((Ptr AboutDialog) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_about_dialog_get_comments"
gtk_about_dialog_get_comments :: ((Ptr AboutDialog) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_about_dialog_set_comments"
gtk_about_dialog_set_comments :: ((Ptr AboutDialog) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_about_dialog_get_license"
gtk_about_dialog_get_license :: ((Ptr AboutDialog) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_about_dialog_set_license"
gtk_about_dialog_set_license :: ((Ptr AboutDialog) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_about_dialog_get_website"
gtk_about_dialog_get_website :: ((Ptr AboutDialog) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_about_dialog_set_website"
gtk_about_dialog_set_website :: ((Ptr AboutDialog) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_about_dialog_get_website_label"
gtk_about_dialog_get_website_label :: ((Ptr AboutDialog) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_about_dialog_set_website_label"
gtk_about_dialog_set_website_label :: ((Ptr AboutDialog) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_about_dialog_set_authors"
gtk_about_dialog_set_authors :: ((Ptr AboutDialog) -> ((Ptr (Ptr CChar)) -> (IO ())))
foreign import ccall safe "gtk_about_dialog_get_authors"
gtk_about_dialog_get_authors :: ((Ptr AboutDialog) -> (IO (Ptr (Ptr CChar))))
foreign import ccall safe "gtk_about_dialog_set_artists"
gtk_about_dialog_set_artists :: ((Ptr AboutDialog) -> ((Ptr (Ptr CChar)) -> (IO ())))
foreign import ccall safe "gtk_about_dialog_get_artists"
gtk_about_dialog_get_artists :: ((Ptr AboutDialog) -> (IO (Ptr (Ptr CChar))))
foreign import ccall safe "gtk_about_dialog_set_documenters"
gtk_about_dialog_set_documenters :: ((Ptr AboutDialog) -> ((Ptr (Ptr CChar)) -> (IO ())))
foreign import ccall safe "gtk_about_dialog_get_documenters"
gtk_about_dialog_get_documenters :: ((Ptr AboutDialog) -> (IO (Ptr (Ptr CChar))))
foreign import ccall safe "gtk_about_dialog_get_translator_credits"
gtk_about_dialog_get_translator_credits :: ((Ptr AboutDialog) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_about_dialog_set_translator_credits"
gtk_about_dialog_set_translator_credits :: ((Ptr AboutDialog) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_about_dialog_get_logo"
gtk_about_dialog_get_logo :: ((Ptr AboutDialog) -> (IO (Ptr Pixbuf)))
foreign import ccall safe "gtk_about_dialog_set_logo"
gtk_about_dialog_set_logo :: ((Ptr AboutDialog) -> ((Ptr Pixbuf) -> (IO ())))
foreign import ccall safe "gtk_about_dialog_get_logo_icon_name"
gtk_about_dialog_get_logo_icon_name :: ((Ptr AboutDialog) -> (IO (Ptr CChar)))
foreign import ccall safe "gtk_about_dialog_set_logo_icon_name"
gtk_about_dialog_set_logo_icon_name :: ((Ptr AboutDialog) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gtk_about_dialog_set_email_hook"
gtk_about_dialog_set_email_hook :: ((FunPtr ((Ptr AboutDialog) -> ((Ptr CChar) -> ((Ptr ()) -> (IO ()))))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO (FunPtr ((Ptr AboutDialog) -> ((Ptr CChar) -> ((Ptr ()) -> (IO ())))))))))
foreign import ccall safe "gtk_about_dialog_set_url_hook"
gtk_about_dialog_set_url_hook :: ((FunPtr ((Ptr AboutDialog) -> ((Ptr CChar) -> ((Ptr ()) -> (IO ()))))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO (FunPtr ((Ptr AboutDialog) -> ((Ptr CChar) -> ((Ptr ()) -> (IO ())))))))))
foreign import ccall safe "gtk_about_dialog_get_wrap_license"
gtk_about_dialog_get_wrap_license :: ((Ptr AboutDialog) -> (IO CInt))
foreign import ccall safe "gtk_about_dialog_set_wrap_license"
gtk_about_dialog_set_wrap_license :: ((Ptr AboutDialog) -> (CInt -> (IO ())))