module Graphics.UI.Gtk.Gdk.AppLaunchContext (
AppLaunchContext,
AppLaunchContextClass,
castToAppLaunchContext,
gTypeAppLaunchContext,
toAppLaunchContext,
appLaunchContextNew,
appLaunchContextSetDisplay,
appLaunchContextSetScreen,
appLaunchContextSetDesktop,
appLaunchContextSetTimestamp,
appLaunchContextSetIconName,
appLaunchContextSetIcon,
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.GObject (wrapNewGObject)
import Graphics.UI.Gtk.Gdk.EventM (TimeStamp)
import Graphics.UI.Gtk.Types
import System.GIO.Types (Icon (..), IconClass, toIcon)
appLaunchContextNew :: IO AppLaunchContext
appLaunchContextNew =
wrapNewGObject mkAppLaunchContext $
gdk_app_launch_context_new
appLaunchContextSetDesktop :: AppLaunchContext -> Int -> IO ()
appLaunchContextSetDesktop self desktop =
(\(AppLaunchContext arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_app_launch_context_set_desktop argPtr1 arg2)
self
(fromIntegral desktop)
appLaunchContextSetDisplay :: AppLaunchContext -> Display -> IO ()
appLaunchContextSetDisplay self display =
(\(AppLaunchContext arg1) (Display arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_app_launch_context_set_display argPtr1 argPtr2)
self
display
appLaunchContextSetIcon :: IconClass icon => AppLaunchContext -> icon -> IO ()
appLaunchContextSetIcon self icon =
(\(AppLaunchContext arg1) (Icon arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_app_launch_context_set_icon argPtr1 argPtr2)
self
(toIcon icon)
appLaunchContextSetIconName :: AppLaunchContext -> String -> IO ()
appLaunchContextSetIconName self iconName =
withUTFString iconName $ \iconNamePtr ->
(\(AppLaunchContext arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_app_launch_context_set_icon_name argPtr1 arg2)
self
iconNamePtr
appLaunchContextSetScreen :: AppLaunchContext -> Screen -> IO ()
appLaunchContextSetScreen self screen =
(\(AppLaunchContext arg1) (Screen arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_app_launch_context_set_screen argPtr1 argPtr2)
self
screen
appLaunchContextSetTimestamp :: AppLaunchContext -> TimeStamp -> IO ()
appLaunchContextSetTimestamp self timestamp =
(\(AppLaunchContext arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_app_launch_context_set_timestamp argPtr1 arg2)
self
(fromIntegral timestamp)
foreign import ccall safe "gdk_app_launch_context_new"
gdk_app_launch_context_new :: (IO (Ptr AppLaunchContext))
foreign import ccall safe "gdk_app_launch_context_set_desktop"
gdk_app_launch_context_set_desktop :: ((Ptr AppLaunchContext) -> (CInt -> (IO ())))
foreign import ccall safe "gdk_app_launch_context_set_display"
gdk_app_launch_context_set_display :: ((Ptr AppLaunchContext) -> ((Ptr Display) -> (IO ())))
foreign import ccall safe "gdk_app_launch_context_set_icon"
gdk_app_launch_context_set_icon :: ((Ptr AppLaunchContext) -> ((Ptr Icon) -> (IO ())))
foreign import ccall safe "gdk_app_launch_context_set_icon_name"
gdk_app_launch_context_set_icon_name :: ((Ptr AppLaunchContext) -> ((Ptr CChar) -> (IO ())))
foreign import ccall safe "gdk_app_launch_context_set_screen"
gdk_app_launch_context_set_screen :: ((Ptr AppLaunchContext) -> ((Ptr Screen) -> (IO ())))
foreign import ccall safe "gdk_app_launch_context_set_timestamp"
gdk_app_launch_context_set_timestamp :: ((Ptr AppLaunchContext) -> (CUInt -> (IO ())))