{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Gtk.Objects.WindowGroup.WindowGroup' restricts the effect of grabs to windows
-- in the same group, thereby making window groups almost behave
-- like separate applications.
-- 
-- A window can be a member in at most one window group at a time.
-- Windows that have not been explicitly assigned to a group are
-- implicitly treated like windows of the default window group.
-- 
-- GtkWindowGroup objects are referenced by each window in the group,
-- so once you have added all windows to a GtkWindowGroup, you can drop
-- the initial reference to the window group with 'GI.GObject.Objects.Object.objectUnref'. If the
-- windows in the window group are subsequently destroyed, then they will
-- be removed from the window group and drop their references on the window
-- group; when all window have been removed, the window group will be
-- freed.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gtk.Objects.WindowGroup
    ( 

-- * Exported types
    WindowGroup(..)                         ,
    IsWindowGroup                           ,
    toWindowGroup                           ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveWindowGroupMethod                ,
#endif


-- ** addWindow #method:addWindow#

#if defined(ENABLE_OVERLOADING)
    WindowGroupAddWindowMethodInfo          ,
#endif
    windowGroupAddWindow                    ,


-- ** listWindows #method:listWindows#

#if defined(ENABLE_OVERLOADING)
    WindowGroupListWindowsMethodInfo        ,
#endif
    windowGroupListWindows                  ,


-- ** new #method:new#

    windowGroupNew                          ,


-- ** removeWindow #method:removeWindow#

#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.BasicTypes as B.Types
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 Control.Monad.IO.Class as MIO
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 {-# SOURCE #-} qualified GI.Gtk.Objects.Window as Gtk.Window

-- | Memory-managed wrapper type.
newtype WindowGroup = WindowGroup (SP.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)

instance SP.ManagedPtrNewtype WindowGroup where
    toManagedPtr :: WindowGroup -> ManagedPtr WindowGroup
toManagedPtr (WindowGroup ManagedPtr WindowGroup
p) = ManagedPtr WindowGroup
p

foreign import ccall "gtk_window_group_get_type"
    c_gtk_window_group_get_type :: IO B.Types.GType

instance B.Types.TypedObject WindowGroup where
    glibType :: IO GType
glibType = IO GType
c_gtk_window_group_get_type

instance B.Types.GObject WindowGroup

-- | Convert 'WindowGroup' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue WindowGroup where
    toGValue :: WindowGroup -> IO GValue
toGValue 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 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
        
    

-- | Type class for types which can be safely cast to `WindowGroup`, for instance with `toWindowGroup`.
class (SP.GObject o, O.IsDescendantOf WindowGroup o) => IsWindowGroup o
instance (SP.GObject o, O.IsDescendantOf WindowGroup o) => IsWindowGroup o

instance O.HasParentTypes WindowGroup
type instance O.ParentTypes WindowGroup = '[GObject.Object.Object]

-- | Cast to `WindowGroup`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
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, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr WindowGroup -> WindowGroup
WindowGroup

#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 "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

-- method WindowGroup::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "WindowGroup" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_window_group_new" gtk_window_group_new :: 
    IO (Ptr WindowGroup)

-- | Creates a new t'GI.Gtk.Objects.WindowGroup.WindowGroup' object.
-- 
-- Modality of windows only affects windows
-- within the same t'GI.Gtk.Objects.WindowGroup.WindowGroup'.
windowGroupNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m WindowGroup
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.WindowGroup.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 Text
"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

-- method WindowGroup::add_window
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "window_group"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WindowGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWindowGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "window"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GtkWindow to add"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_window_group_add_window" gtk_window_group_add_window :: 
    Ptr WindowGroup ->                      -- window_group : TInterface (Name {namespace = "Gtk", name = "WindowGroup"})
    Ptr Gtk.Window.Window ->                -- window : TInterface (Name {namespace = "Gtk", name = "Window"})
    IO ()

-- | Adds a window to a t'GI.Gtk.Objects.WindowGroup.WindowGroup'.
windowGroupAddWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowGroup a, Gtk.Window.IsWindow b) =>
    a
    -- ^ /@windowGroup@/: a t'GI.Gtk.Objects.WindowGroup.WindowGroup'
    -> b
    -- ^ /@window@/: the t'GI.Gtk.Objects.Window.Window' to add
    -> m ()
windowGroupAddWindow :: a -> b -> m ()
windowGroupAddWindow a
windowGroup 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

-- method WindowGroup::list_windows
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "window_group"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WindowGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWindowGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList (TInterface Name { namespace = "Gtk" , name = "Window" }))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_window_group_list_windows" gtk_window_group_list_windows :: 
    Ptr WindowGroup ->                      -- window_group : TInterface (Name {namespace = "Gtk", name = "WindowGroup"})
    IO (Ptr (GList (Ptr Gtk.Window.Window)))

-- | Returns a list of the @/GtkWindows/@ that belong to /@windowGroup@/.
windowGroupListWindows ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowGroup a) =>
    a
    -- ^ /@windowGroup@/: a t'GI.Gtk.Objects.WindowGroup.WindowGroup'
    -> m [Gtk.Window.Window]
    -- ^ __Returns:__ A
    --   newly-allocated list of windows inside the group.
windowGroupListWindows :: a -> m [Window]
windowGroupListWindows 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

-- method WindowGroup::remove_window
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "window_group"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WindowGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkWindowGroup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "window"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GtkWindow to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_window_group_remove_window" gtk_window_group_remove_window :: 
    Ptr WindowGroup ->                      -- window_group : TInterface (Name {namespace = "Gtk", name = "WindowGroup"})
    Ptr Gtk.Window.Window ->                -- window : TInterface (Name {namespace = "Gtk", name = "Window"})
    IO ()

-- | Removes a window from a t'GI.Gtk.Objects.WindowGroup.WindowGroup'.
windowGroupRemoveWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsWindowGroup a, Gtk.Window.IsWindow b) =>
    a
    -- ^ /@windowGroup@/: a t'GI.Gtk.Objects.WindowGroup.WindowGroup'
    -> b
    -- ^ /@window@/: the t'GI.Gtk.Objects.Window.Window' to remove
    -> m ()
windowGroupRemoveWindow :: a -> b -> m ()
windowGroupRemoveWindow a
windowGroup 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