{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.WindowGroup
    ( 
    WindowGroup(..)                         ,
    IsWindowGroup                           ,
    toWindowGroup                           ,
    noWindowGroup                           ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveWindowGroupMethod                ,
#endif
#if defined(ENABLE_OVERLOADING)
    WindowGroupAddWindowMethodInfo          ,
#endif
    windowGroupAddWindow                    ,
#if defined(ENABLE_OVERLOADING)
    WindowGroupGetCurrentDeviceGrabMethodInfo,
#endif
    windowGroupGetCurrentDeviceGrab         ,
#if defined(ENABLE_OVERLOADING)
    WindowGroupGetCurrentGrabMethodInfo     ,
#endif
    windowGroupGetCurrentGrab               ,
#if defined(ENABLE_OVERLOADING)
    WindowGroupListWindowsMethodInfo        ,
#endif
    windowGroupListWindows                  ,
    windowGroupNew                          ,
#if defined(ENABLE_OVERLOADING)
    WindowGroupRemoveWindowMethodInfo       ,
#endif
    windowGroupRemoveWindow                 ,
    ) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Device as Gdk.Device
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Objects.Window as Gtk.Window
newtype WindowGroup = WindowGroup (ManagedPtr WindowGroup)
    deriving (WindowGroup -> WindowGroup -> Bool
(WindowGroup -> WindowGroup -> Bool)
-> (WindowGroup -> WindowGroup -> Bool) -> Eq WindowGroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowGroup -> WindowGroup -> Bool
$c/= :: WindowGroup -> WindowGroup -> Bool
== :: WindowGroup -> WindowGroup -> Bool
$c== :: WindowGroup -> WindowGroup -> Bool
Eq)
foreign import ccall "gtk_window_group_get_type"
    c_gtk_window_group_get_type :: IO GType
instance GObject WindowGroup where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_window_group_get_type
    
instance B.GValue.IsGValue WindowGroup where
    toGValue :: WindowGroup -> IO GValue
toGValue o :: WindowGroup
o = do
        GType
gtype <- IO GType
c_gtk_window_group_get_type
        WindowGroup -> (Ptr WindowGroup -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr WindowGroup
o (GType
-> (GValue -> Ptr WindowGroup -> IO ())
-> Ptr WindowGroup
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr WindowGroup -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO WindowGroup
fromGValue gv :: GValue
gv = do
        Ptr WindowGroup
ptr <- GValue -> IO (Ptr WindowGroup)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr WindowGroup)
        (ManagedPtr WindowGroup -> WindowGroup)
-> Ptr WindowGroup -> IO WindowGroup
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr WindowGroup -> WindowGroup
WindowGroup Ptr WindowGroup
ptr
        
    
class (GObject o, O.IsDescendantOf WindowGroup o) => IsWindowGroup o
instance (GObject o, O.IsDescendantOf WindowGroup o) => IsWindowGroup o
instance O.HasParentTypes WindowGroup
type instance O.ParentTypes WindowGroup = '[GObject.Object.Object]
toWindowGroup :: (MonadIO m, IsWindowGroup o) => o -> m WindowGroup
toWindowGroup :: o -> m WindowGroup
toWindowGroup = IO WindowGroup -> m WindowGroup
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WindowGroup -> m WindowGroup)
-> (o -> IO WindowGroup) -> o -> m WindowGroup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr WindowGroup -> WindowGroup) -> o -> IO WindowGroup
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr WindowGroup -> WindowGroup
WindowGroup
noWindowGroup :: Maybe WindowGroup
noWindowGroup :: Maybe WindowGroup
noWindowGroup = Maybe WindowGroup
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveWindowGroupMethod (t :: Symbol) (o :: *) :: * where
    ResolveWindowGroupMethod "addWindow" o = WindowGroupAddWindowMethodInfo
    ResolveWindowGroupMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveWindowGroupMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveWindowGroupMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveWindowGroupMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveWindowGroupMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveWindowGroupMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveWindowGroupMethod "listWindows" o = WindowGroupListWindowsMethodInfo
    ResolveWindowGroupMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveWindowGroupMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveWindowGroupMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveWindowGroupMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveWindowGroupMethod "removeWindow" o = WindowGroupRemoveWindowMethodInfo
    ResolveWindowGroupMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveWindowGroupMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveWindowGroupMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveWindowGroupMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveWindowGroupMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveWindowGroupMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveWindowGroupMethod "getCurrentDeviceGrab" o = WindowGroupGetCurrentDeviceGrabMethodInfo
    ResolveWindowGroupMethod "getCurrentGrab" o = WindowGroupGetCurrentGrabMethodInfo
    ResolveWindowGroupMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveWindowGroupMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveWindowGroupMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveWindowGroupMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveWindowGroupMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveWindowGroupMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveWindowGroupMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveWindowGroupMethod t WindowGroup, O.MethodInfo info WindowGroup p) => OL.IsLabel t (WindowGroup -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList WindowGroup
type instance O.AttributeList WindowGroup = WindowGroupAttributeList
type WindowGroupAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList WindowGroup = WindowGroupSignalList
type WindowGroupSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_window_group_new" gtk_window_group_new :: 
    IO (Ptr WindowGroup)
windowGroupNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m WindowGroup
    
windowGroupNew :: m WindowGroup
windowGroupNew  = IO WindowGroup -> m WindowGroup
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WindowGroup -> m WindowGroup)
-> IO WindowGroup -> m WindowGroup
forall a b. (a -> b) -> a -> b
$ do
    Ptr WindowGroup
result <- IO (Ptr WindowGroup)
gtk_window_group_new
    Text -> Ptr WindowGroup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "windowGroupNew" Ptr WindowGroup
result
    WindowGroup
result' <- ((ManagedPtr WindowGroup -> WindowGroup)
-> Ptr WindowGroup -> IO WindowGroup
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr WindowGroup -> WindowGroup
WindowGroup) Ptr WindowGroup
result
    WindowGroup -> IO WindowGroup
forall (m :: * -> *) a. Monad m => a -> m a
return WindowGroup
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_window_group_add_window" gtk_window_group_add_window :: 
    Ptr WindowGroup ->                      
    Ptr Gtk.Window.Window ->                
    IO ()
windowGroupAddWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowGroup a, Gtk.Window.IsWindow b) =>
    a
    
    -> b
    
    -> m ()
windowGroupAddWindow :: a -> b -> m ()
windowGroupAddWindow windowGroup :: a
windowGroup window :: b
window = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr WindowGroup
windowGroup' <- a -> IO (Ptr WindowGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
windowGroup
    Ptr Window
window' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
window
    Ptr WindowGroup -> Ptr Window -> IO ()
gtk_window_group_add_window Ptr WindowGroup
windowGroup' Ptr Window
window'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
windowGroup
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
window
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data WindowGroupAddWindowMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsWindowGroup a, Gtk.Window.IsWindow b) => O.MethodInfo WindowGroupAddWindowMethodInfo a signature where
    overloadedMethod = windowGroupAddWindow
#endif
foreign import ccall "gtk_window_group_get_current_device_grab" gtk_window_group_get_current_device_grab :: 
    Ptr WindowGroup ->                      
    Ptr Gdk.Device.Device ->                
    IO (Ptr Gtk.Widget.Widget)
windowGroupGetCurrentDeviceGrab ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowGroup a, Gdk.Device.IsDevice b) =>
    a
    
    -> b
    
    -> m (Maybe Gtk.Widget.Widget)
    
windowGroupGetCurrentDeviceGrab :: a -> b -> m (Maybe Widget)
windowGroupGetCurrentDeviceGrab windowGroup :: a
windowGroup device :: b
device = IO (Maybe Widget) -> m (Maybe Widget)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Widget) -> m (Maybe Widget))
-> IO (Maybe Widget) -> m (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ do
    Ptr WindowGroup
windowGroup' <- a -> IO (Ptr WindowGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
windowGroup
    Ptr Device
device' <- b -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
device
    Ptr Widget
result <- Ptr WindowGroup -> Ptr Device -> IO (Ptr Widget)
gtk_window_group_get_current_device_grab Ptr WindowGroup
windowGroup' Ptr Device
device'
    Maybe Widget
maybeResult <- Ptr Widget -> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Widget
result ((Ptr Widget -> IO Widget) -> IO (Maybe Widget))
-> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Widget
result' -> do
        Widget
result'' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result'
        Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
windowGroup
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
device
    Maybe Widget -> IO (Maybe Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Widget
maybeResult
#if defined(ENABLE_OVERLOADING)
data WindowGroupGetCurrentDeviceGrabMethodInfo
instance (signature ~ (b -> m (Maybe Gtk.Widget.Widget)), MonadIO m, IsWindowGroup a, Gdk.Device.IsDevice b) => O.MethodInfo WindowGroupGetCurrentDeviceGrabMethodInfo a signature where
    overloadedMethod = windowGroupGetCurrentDeviceGrab
#endif
foreign import ccall "gtk_window_group_get_current_grab" gtk_window_group_get_current_grab :: 
    Ptr WindowGroup ->                      
    IO (Ptr Gtk.Widget.Widget)
windowGroupGetCurrentGrab ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowGroup a) =>
    a
    
    -> m Gtk.Widget.Widget
    
windowGroupGetCurrentGrab :: a -> m Widget
windowGroupGetCurrentGrab windowGroup :: a
windowGroup = IO Widget -> m Widget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
    Ptr WindowGroup
windowGroup' <- a -> IO (Ptr WindowGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
windowGroup
    Ptr Widget
result <- Ptr WindowGroup -> IO (Ptr Widget)
gtk_window_group_get_current_grab Ptr WindowGroup
windowGroup'
    Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "windowGroupGetCurrentGrab" Ptr Widget
result
    Widget
result' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
windowGroup
    Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'
#if defined(ENABLE_OVERLOADING)
data WindowGroupGetCurrentGrabMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsWindowGroup a) => O.MethodInfo WindowGroupGetCurrentGrabMethodInfo a signature where
    overloadedMethod = windowGroupGetCurrentGrab
#endif
foreign import ccall "gtk_window_group_list_windows" gtk_window_group_list_windows :: 
    Ptr WindowGroup ->                      
    IO (Ptr (GList (Ptr Gtk.Window.Window)))
windowGroupListWindows ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowGroup a) =>
    a
    
    -> m [Gtk.Window.Window]
    
    
windowGroupListWindows :: a -> m [Window]
windowGroupListWindows windowGroup :: a
windowGroup = IO [Window] -> m [Window]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Window] -> m [Window]) -> IO [Window] -> m [Window]
forall a b. (a -> b) -> a -> b
$ do
    Ptr WindowGroup
windowGroup' <- a -> IO (Ptr WindowGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
windowGroup
    Ptr (GList (Ptr Window))
result <- Ptr WindowGroup -> IO (Ptr (GList (Ptr Window)))
gtk_window_group_list_windows Ptr WindowGroup
windowGroup'
    [Ptr Window]
result' <- Ptr (GList (Ptr Window)) -> IO [Ptr Window]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr Window))
result
    [Window]
result'' <- (Ptr Window -> IO Window) -> [Ptr Window] -> IO [Window]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gtk.Window.Window) [Ptr Window]
result'
    Ptr (GList (Ptr Window)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr Window))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
windowGroup
    [Window] -> IO [Window]
forall (m :: * -> *) a. Monad m => a -> m a
return [Window]
result''
#if defined(ENABLE_OVERLOADING)
data WindowGroupListWindowsMethodInfo
instance (signature ~ (m [Gtk.Window.Window]), MonadIO m, IsWindowGroup a) => O.MethodInfo WindowGroupListWindowsMethodInfo a signature where
    overloadedMethod = windowGroupListWindows
#endif
foreign import ccall "gtk_window_group_remove_window" gtk_window_group_remove_window :: 
    Ptr WindowGroup ->                      
    Ptr Gtk.Window.Window ->                
    IO ()
windowGroupRemoveWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowGroup a, Gtk.Window.IsWindow b) =>
    a
    
    -> b
    
    -> m ()
windowGroupRemoveWindow :: a -> b -> m ()
windowGroupRemoveWindow windowGroup :: a
windowGroup window :: b
window = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr WindowGroup
windowGroup' <- a -> IO (Ptr WindowGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
windowGroup
    Ptr Window
window' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
window
    Ptr WindowGroup -> Ptr Window -> IO ()
gtk_window_group_remove_window Ptr WindowGroup
windowGroup' Ptr Window
window'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
windowGroup
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
window
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data WindowGroupRemoveWindowMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsWindowGroup a, Gtk.Window.IsWindow b) => O.MethodInfo WindowGroupRemoveWindowMethodInfo a signature where
    overloadedMethod = windowGroupRemoveWindow
#endif