module Graphics.UI.Gtk.Windows.Assistant (
Assistant,
AssistantClass,
castToAssistant,
toAssistant,
AssistantPageType(..),
assistantNew,
assistantGetNPages,
assistantGetNthPage,
assistantPrependPage,
assistantAppendPage,
assistantInsertPage,
assistantSetForwardPageFunc,
assistantAddActionWidget,
assistantRemoveActionWidget,
assistantUpdateButtonsState,
assistantSetPageType,
assistantGetPageType,
assistantSetPageTitle,
assistantGetPageTitle,
assistantSetPageHeaderImage,
assistantGetPageHeaderImage,
assistantSetPageSideImage,
assistantGetPageSideImage,
assistantSetPageComplete,
assistantGetPageComplete,
assistantCommit,
assistantCurrentPage,
assistantChildPageType,
assistantChildTitle,
assistantChildHeaderImage,
assistantChildSidebarImage,
assistantChildComplete,
assistantCancel,
assistantPrepare,
assistantApply,
assistantClose,
) where
import Control.Monad (liftM, unless)
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
data AssistantPageType = AssistantPageContent
| AssistantPageIntro
| AssistantPageConfirm
| AssistantPageSummary
| AssistantPageProgress
deriving (Enum,Bounded,Eq,Show)
assistantNew :: IO Assistant
assistantNew =
makeNewObject mkAssistant $
liftM (castPtr :: Ptr Widget -> Ptr Assistant) $
gtk_assistant_new
assistantGetCurrentPage :: AssistantClass self => self
-> IO Int
assistantGetCurrentPage self =
liftM fromIntegral $
(\(Assistant arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_assistant_get_current_page argPtr1)
(toAssistant self)
assistantSetCurrentPage :: AssistantClass self => self
-> Int
-> IO ()
assistantSetCurrentPage self pageNum =
(\(Assistant arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_assistant_set_current_page argPtr1 arg2)
(toAssistant self)
(fromIntegral pageNum)
assistantGetNPages :: AssistantClass self => self
-> IO Int
assistantGetNPages self =
liftM fromIntegral $
(\(Assistant arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_assistant_get_n_pages argPtr1)
(toAssistant self)
assistantGetNthPage :: AssistantClass self => self
-> Int
-> IO (Maybe Widget)
assistantGetNthPage self pageNum =
maybeNull (makeNewObject mkWidget) $
(\(Assistant arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_assistant_get_nth_page argPtr1 arg2)
(toAssistant self)
(fromIntegral pageNum)
assistantPrependPage :: (AssistantClass self, WidgetClass page) => self
-> page
-> IO Int
assistantPrependPage self page =
liftM fromIntegral $
(\(Assistant arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_assistant_prepend_page argPtr1 argPtr2)
(toAssistant self)
(toWidget page)
assistantAppendPage :: (AssistantClass self, WidgetClass page) => self
-> page
-> IO Int
assistantAppendPage self page =
liftM fromIntegral $
(\(Assistant arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_assistant_append_page argPtr1 argPtr2)
(toAssistant self)
(toWidget page)
assistantInsertPage :: (AssistantClass self, WidgetClass page) => self
-> page
-> Int
-> IO Int
assistantInsertPage self page position =
liftM fromIntegral $
(\(Assistant arg1) (Widget arg2) arg3 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_assistant_insert_page argPtr1 argPtr2 arg3)
(toAssistant self)
(toWidget page)
(fromIntegral position)
assistantSetForwardPageFunc :: AssistantClass self => self
-> Maybe (Int -> IO Int)
-> IO ()
assistantSetForwardPageFunc self Nothing = do
(\(Assistant arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gtk_assistant_set_forward_page_func argPtr1 arg2 arg3 arg4)
(toAssistant self)
nullFunPtr
(castFunPtrToPtr nullFunPtr)
destroyFunPtr
assistantSetForwardPageFunc self (Just pageFunc) = do
pfPtr <- mkAssistantPageFunc $ \ c _ -> do
result <- pageFunc (fromIntegral c)
return $ fromIntegral result
(\(Assistant arg1) arg2 arg3 arg4 -> withForeignPtr arg1 $ \argPtr1 ->gtk_assistant_set_forward_page_func argPtr1 arg2 arg3 arg4)
(toAssistant self)
pfPtr
(castFunPtrToPtr pfPtr)
destroyFunPtr
type AssistantPageFunc = FunPtr ((CInt -> ((Ptr ()) -> (IO CInt))))
foreign import ccall "wrapper" mkAssistantPageFunc ::
((CInt) -> Ptr () -> IO (CInt))
-> IO AssistantPageFunc
assistantSetPageType :: (AssistantClass self, WidgetClass page) => self
-> page
-> AssistantPageType
-> IO ()
assistantSetPageType self page type_ =
(\(Assistant arg1) (Widget arg2) arg3 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_assistant_set_page_type argPtr1 argPtr2 arg3)
(toAssistant self)
(toWidget page)
((fromIntegral . fromEnum) type_)
assistantGetPageType :: (AssistantClass self, WidgetClass page) => self
-> page
-> IO AssistantPageType
assistantGetPageType self page =
liftM (toEnum . fromIntegral) $
(\(Assistant arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_assistant_get_page_type argPtr1 argPtr2)
(toAssistant self)
(toWidget page)
assistantSetPageTitle :: (AssistantClass self, WidgetClass page) => self
-> page
-> String
-> IO ()
assistantSetPageTitle self page title =
withUTFString title $ \titlePtr ->
(\(Assistant arg1) (Widget arg2) arg3 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_assistant_set_page_title argPtr1 argPtr2 arg3)
(toAssistant self)
(toWidget page)
titlePtr
assistantGetPageTitle :: (AssistantClass self, WidgetClass page) => self
-> page
-> IO String
assistantGetPageTitle self page =
(\(Assistant arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_assistant_get_page_title argPtr1 argPtr2)
(toAssistant self)
(toWidget page)
>>= peekUTFString
assistantSetPageHeaderImage :: (AssistantClass self, WidgetClass page) => self
-> page
-> Pixbuf
-> IO ()
assistantSetPageHeaderImage self page pixbuf =
(\(Assistant arg1) (Widget arg2) (Pixbuf arg3) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->withForeignPtr arg3 $ \argPtr3 ->gtk_assistant_set_page_header_image argPtr1 argPtr2 argPtr3)
(toAssistant self)
(toWidget page)
pixbuf
assistantGetPageHeaderImage :: (AssistantClass self, WidgetClass page) => self
-> page
-> IO (Maybe Pixbuf)
assistantGetPageHeaderImage self page =
maybeNull (makeNewGObject mkPixbuf) $
(\(Assistant arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_assistant_get_page_header_image argPtr1 argPtr2)
(toAssistant self)
(toWidget page)
assistantSetPageSideImage :: (AssistantClass self, WidgetClass page) => self
-> page
-> Pixbuf
-> IO ()
assistantSetPageSideImage self page pixbuf =
(\(Assistant arg1) (Widget arg2) (Pixbuf arg3) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->withForeignPtr arg3 $ \argPtr3 ->gtk_assistant_set_page_side_image argPtr1 argPtr2 argPtr3)
(toAssistant self)
(toWidget page)
pixbuf
assistantGetPageSideImage :: (AssistantClass self, WidgetClass page) => self
-> page
-> IO (Maybe Pixbuf)
assistantGetPageSideImage self page =
maybeNull (makeNewGObject mkPixbuf) $
(\(Assistant arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_assistant_get_page_side_image argPtr1 argPtr2)
(toAssistant self)
(toWidget page)
assistantSetPageComplete :: (AssistantClass self, WidgetClass page) => self
-> page
-> Bool
-> IO ()
assistantSetPageComplete self page complete =
(\(Assistant arg1) (Widget arg2) arg3 -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_assistant_set_page_complete argPtr1 argPtr2 arg3)
(toAssistant self)
(toWidget page)
(fromBool complete)
assistantGetPageComplete :: (AssistantClass self, WidgetClass page) => self
-> page
-> IO Bool
assistantGetPageComplete self page =
liftM toBool $
(\(Assistant arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_assistant_get_page_complete argPtr1 argPtr2)
(toAssistant self)
(toWidget page)
assistantCommit :: AssistantClass self => self -> IO ()
assistantCommit self =
(\(Assistant arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_assistant_commit argPtr1) (toAssistant self)
assistantAddActionWidget :: (AssistantClass self, WidgetClass child) => self
-> child
-> IO ()
assistantAddActionWidget self child =
(\(Assistant arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_assistant_add_action_widget argPtr1 argPtr2)
(toAssistant self)
(toWidget child)
assistantRemoveActionWidget :: (AssistantClass self, WidgetClass child) => self
-> child
-> IO ()
assistantRemoveActionWidget self child =
(\(Assistant arg1) (Widget arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_assistant_remove_action_widget argPtr1 argPtr2)
(toAssistant self)
(toWidget child)
assistantUpdateButtonsState :: AssistantClass self => self -> IO ()
assistantUpdateButtonsState self =
(\(Assistant arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_assistant_update_buttons_state argPtr1)
(toAssistant self)
assistantCurrentPage :: AssistantClass self => Attr self Int
assistantCurrentPage = newAttr
assistantGetCurrentPage
assistantSetCurrentPage
assistantChildPageType :: AssistantClass self => Attr self AssistantPageType
assistantChildPageType =
newAttrFromEnumProperty "page-type" gtk_assistant_page_type_get_type
assistantChildTitle :: AssistantClass self => Attr self String
assistantChildTitle = newAttrFromStringProperty "title"
assistantChildHeaderImage :: AssistantClass self => Attr self Pixbuf
assistantChildHeaderImage = newAttrFromObjectProperty "header-image"
gdk_pixbuf_get_type
assistantChildSidebarImage :: AssistantClass self => Attr self Pixbuf
assistantChildSidebarImage = newAttrFromObjectProperty "sidebar-image"
gdk_pixbuf_get_type
assistantChildComplete :: AssistantClass self => Attr self Bool
assistantChildComplete = newAttrFromBoolProperty "complete"
assistantCancel :: AssistantClass self => Signal self (IO ())
assistantCancel = Signal (connect_NONE__NONE "cancel")
assistantPrepare :: AssistantClass self => Signal self (Widget -> IO ())
assistantPrepare = Signal (connect_OBJECT__NONE "prepare")
assistantApply :: AssistantClass self => Signal self (IO ())
assistantApply = Signal (connect_NONE__NONE "apply")
assistantClose :: AssistantClass self => Signal self (IO ())
assistantClose = Signal (connect_NONE__NONE "close")
foreign import ccall safe "gtk_assistant_new"
gtk_assistant_new :: (IO (Ptr Widget))
foreign import ccall safe "gtk_assistant_get_current_page"
gtk_assistant_get_current_page :: ((Ptr Assistant) -> (IO CInt))
foreign import ccall safe "gtk_assistant_set_current_page"
gtk_assistant_set_current_page :: ((Ptr Assistant) -> (CInt -> (IO ())))
foreign import ccall safe "gtk_assistant_get_n_pages"
gtk_assistant_get_n_pages :: ((Ptr Assistant) -> (IO CInt))
foreign import ccall safe "gtk_assistant_get_nth_page"
gtk_assistant_get_nth_page :: ((Ptr Assistant) -> (CInt -> (IO (Ptr Widget))))
foreign import ccall safe "gtk_assistant_prepend_page"
gtk_assistant_prepend_page :: ((Ptr Assistant) -> ((Ptr Widget) -> (IO CInt)))
foreign import ccall safe "gtk_assistant_append_page"
gtk_assistant_append_page :: ((Ptr Assistant) -> ((Ptr Widget) -> (IO CInt)))
foreign import ccall safe "gtk_assistant_insert_page"
gtk_assistant_insert_page :: ((Ptr Assistant) -> ((Ptr Widget) -> (CInt -> (IO CInt))))
foreign import ccall safe "gtk_assistant_set_forward_page_func"
gtk_assistant_set_forward_page_func :: ((Ptr Assistant) -> ((FunPtr (CInt -> ((Ptr ()) -> (IO CInt)))) -> ((Ptr ()) -> ((FunPtr ((Ptr ()) -> (IO ()))) -> (IO ())))))
foreign import ccall safe "gtk_assistant_set_page_type"
gtk_assistant_set_page_type :: ((Ptr Assistant) -> ((Ptr Widget) -> (CInt -> (IO ()))))
foreign import ccall safe "gtk_assistant_get_page_type"
gtk_assistant_get_page_type :: ((Ptr Assistant) -> ((Ptr Widget) -> (IO CInt)))
foreign import ccall safe "gtk_assistant_set_page_title"
gtk_assistant_set_page_title :: ((Ptr Assistant) -> ((Ptr Widget) -> ((Ptr CChar) -> (IO ()))))
foreign import ccall safe "gtk_assistant_get_page_title"
gtk_assistant_get_page_title :: ((Ptr Assistant) -> ((Ptr Widget) -> (IO (Ptr CChar))))
foreign import ccall safe "gtk_assistant_set_page_header_image"
gtk_assistant_set_page_header_image :: ((Ptr Assistant) -> ((Ptr Widget) -> ((Ptr Pixbuf) -> (IO ()))))
foreign import ccall safe "gtk_assistant_get_page_header_image"
gtk_assistant_get_page_header_image :: ((Ptr Assistant) -> ((Ptr Widget) -> (IO (Ptr Pixbuf))))
foreign import ccall safe "gtk_assistant_set_page_side_image"
gtk_assistant_set_page_side_image :: ((Ptr Assistant) -> ((Ptr Widget) -> ((Ptr Pixbuf) -> (IO ()))))
foreign import ccall safe "gtk_assistant_get_page_side_image"
gtk_assistant_get_page_side_image :: ((Ptr Assistant) -> ((Ptr Widget) -> (IO (Ptr Pixbuf))))
foreign import ccall safe "gtk_assistant_set_page_complete"
gtk_assistant_set_page_complete :: ((Ptr Assistant) -> ((Ptr Widget) -> (CInt -> (IO ()))))
foreign import ccall safe "gtk_assistant_get_page_complete"
gtk_assistant_get_page_complete :: ((Ptr Assistant) -> ((Ptr Widget) -> (IO CInt)))
foreign import ccall safe "gtk_assistant_commit"
gtk_assistant_commit :: ((Ptr Assistant) -> (IO ()))
foreign import ccall safe "gtk_assistant_add_action_widget"
gtk_assistant_add_action_widget :: ((Ptr Assistant) -> ((Ptr Widget) -> (IO ())))
foreign import ccall safe "gtk_assistant_remove_action_widget"
gtk_assistant_remove_action_widget :: ((Ptr Assistant) -> ((Ptr Widget) -> (IO ())))
foreign import ccall safe "gtk_assistant_update_buttons_state"
gtk_assistant_update_buttons_state :: ((Ptr Assistant) -> (IO ()))
foreign import ccall unsafe "gtk_assistant_page_type_get_type"
gtk_assistant_page_type_get_type :: CUInt
foreign import ccall unsafe "gdk_pixbuf_get_type"
gdk_pixbuf_get_type :: CUInt