{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Wnck.Objects.Handle
    ( 
    Handle(..)                              ,
    IsHandle                                ,
    toHandle                                ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveHandleMethod                     ,
#endif
#if defined(ENABLE_OVERLOADING)
    HandleGetApplicationMethodInfo          ,
#endif
    handleGetApplication                    ,
#if defined(ENABLE_OVERLOADING)
    HandleGetClassGroupMethodInfo           ,
#endif
    handleGetClassGroup                     ,
#if defined(ENABLE_OVERLOADING)
    HandleGetDefaultScreenMethodInfo        ,
#endif
    handleGetDefaultScreen                  ,
#if defined(ENABLE_OVERLOADING)
    HandleGetScreenMethodInfo               ,
#endif
    handleGetScreen                         ,
#if defined(ENABLE_OVERLOADING)
    HandleGetScreenForRootMethodInfo        ,
#endif
    handleGetScreenForRoot                  ,
#if defined(ENABLE_OVERLOADING)
    HandleGetWindowMethodInfo               ,
#endif
    handleGetWindow                         ,
    handleNew                               ,
#if defined(ENABLE_OVERLOADING)
    HandleSetDefaultIconSizeMethodInfo      ,
#endif
    handleSetDefaultIconSize                ,
#if defined(ENABLE_OVERLOADING)
    HandleSetDefaultMiniIconSizeMethodInfo  ,
#endif
    handleSetDefaultMiniIconSize            ,
 
#if defined(ENABLE_OVERLOADING)
    HandleClientTypePropertyInfo            ,
#endif
    constructHandleClientType               ,
    getHandleClientType                     ,
#if defined(ENABLE_OVERLOADING)
    handleClientType                        ,
#endif
    setHandleClientType                     ,
    ) 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.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 GHC.Records as R
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Wnck.Enums as Wnck.Enums
import {-# SOURCE #-} qualified GI.Wnck.Objects.Application as Wnck.Application
import {-# SOURCE #-} qualified GI.Wnck.Objects.ClassGroup as Wnck.ClassGroup
import {-# SOURCE #-} qualified GI.Wnck.Objects.Screen as Wnck.Screen
import {-# SOURCE #-} qualified GI.Wnck.Objects.Window as Wnck.Window
newtype Handle = Handle (SP.ManagedPtr Handle)
    deriving (Handle -> Handle -> Bool
(Handle -> Handle -> Bool)
-> (Handle -> Handle -> Bool) -> Eq Handle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Handle -> Handle -> Bool
== :: Handle -> Handle -> Bool
$c/= :: Handle -> Handle -> Bool
/= :: Handle -> Handle -> Bool
Eq)
instance SP.ManagedPtrNewtype Handle where
    toManagedPtr :: Handle -> ManagedPtr Handle
toManagedPtr (Handle ManagedPtr Handle
p) = ManagedPtr Handle
p
foreign import ccall "wnck_handle_get_type"
    c_wnck_handle_get_type :: IO B.Types.GType
instance B.Types.TypedObject Handle where
    glibType :: IO GType
glibType = IO GType
c_wnck_handle_get_type
instance B.Types.GObject Handle
class (SP.GObject o, O.IsDescendantOf Handle o) => IsHandle o
instance (SP.GObject o, O.IsDescendantOf Handle o) => IsHandle o
instance O.HasParentTypes Handle
type instance O.ParentTypes Handle = '[GObject.Object.Object]
toHandle :: (MIO.MonadIO m, IsHandle o) => o -> m Handle
toHandle :: forall (m :: * -> *) o. (MonadIO m, IsHandle o) => o -> m Handle
toHandle = IO Handle -> m Handle
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Handle -> m Handle) -> (o -> IO Handle) -> o -> m Handle
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Handle -> Handle) -> o -> IO Handle
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Handle -> Handle
Handle
instance B.GValue.IsGValue (Maybe Handle) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_wnck_handle_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Handle -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Handle
P.Nothing = Ptr GValue -> Ptr Handle -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Handle
forall a. Ptr a
FP.nullPtr :: FP.Ptr Handle)
    gvalueSet_ Ptr GValue
gv (P.Just Handle
obj) = Handle -> (Ptr Handle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Handle
obj (Ptr GValue -> Ptr Handle -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Handle)
gvalueGet_ Ptr GValue
gv = do
        Ptr Handle
ptr <- Ptr GValue -> IO (Ptr Handle)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Handle)
        if Ptr Handle
ptr Ptr Handle -> Ptr Handle -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Handle
forall a. Ptr a
FP.nullPtr
        then Handle -> Maybe Handle
forall a. a -> Maybe a
P.Just (Handle -> Maybe Handle) -> IO Handle -> IO (Maybe Handle)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Handle -> Handle) -> Ptr Handle -> IO Handle
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Handle -> Handle
Handle Ptr Handle
ptr
        else Maybe Handle -> IO (Maybe Handle)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Handle
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolveHandleMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveHandleMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveHandleMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveHandleMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveHandleMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveHandleMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveHandleMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveHandleMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveHandleMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveHandleMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveHandleMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveHandleMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveHandleMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveHandleMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveHandleMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveHandleMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveHandleMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveHandleMethod "getApplication" o = HandleGetApplicationMethodInfo
    ResolveHandleMethod "getClassGroup" o = HandleGetClassGroupMethodInfo
    ResolveHandleMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveHandleMethod "getDefaultScreen" o = HandleGetDefaultScreenMethodInfo
    ResolveHandleMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveHandleMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveHandleMethod "getScreen" o = HandleGetScreenMethodInfo
    ResolveHandleMethod "getScreenForRoot" o = HandleGetScreenForRootMethodInfo
    ResolveHandleMethod "getWindow" o = HandleGetWindowMethodInfo
    ResolveHandleMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveHandleMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveHandleMethod "setDefaultIconSize" o = HandleSetDefaultIconSizeMethodInfo
    ResolveHandleMethod "setDefaultMiniIconSize" o = HandleSetDefaultMiniIconSizeMethodInfo
    ResolveHandleMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveHandleMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveHandleMethod t Handle, O.OverloadedMethod info Handle p) => OL.IsLabel t (Handle -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveHandleMethod t Handle, O.OverloadedMethod info Handle p, R.HasField t Handle p) => R.HasField t Handle p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveHandleMethod t Handle, O.OverloadedMethodInfo info Handle) => OL.IsLabel t (O.MethodProxy info Handle) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
   
   
   
getHandleClientType :: (MonadIO m, IsHandle o) => o -> m Wnck.Enums.ClientType
getHandleClientType :: forall (m :: * -> *) o.
(MonadIO m, IsHandle o) =>
o -> m ClientType
getHandleClientType o
obj = IO ClientType -> m ClientType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ClientType -> m ClientType) -> IO ClientType -> m ClientType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO ClientType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"client-type"
setHandleClientType :: (MonadIO m, IsHandle o) => o -> Wnck.Enums.ClientType -> m ()
setHandleClientType :: forall (m :: * -> *) o.
(MonadIO m, IsHandle o) =>
o -> ClientType -> m ()
setHandleClientType o
obj ClientType
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> ClientType -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"client-type" ClientType
val
constructHandleClientType :: (IsHandle o, MIO.MonadIO m) => Wnck.Enums.ClientType -> m (GValueConstruct o)
constructHandleClientType :: forall o (m :: * -> *).
(IsHandle o, MonadIO m) =>
ClientType -> m (GValueConstruct o)
constructHandleClientType ClientType
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> ClientType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"client-type" ClientType
val
#if defined(ENABLE_OVERLOADING)
data HandleClientTypePropertyInfo
instance AttrInfo HandleClientTypePropertyInfo where
    type AttrAllowedOps HandleClientTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint HandleClientTypePropertyInfo = IsHandle
    type AttrSetTypeConstraint HandleClientTypePropertyInfo = (~) Wnck.Enums.ClientType
    type AttrTransferTypeConstraint HandleClientTypePropertyInfo = (~) Wnck.Enums.ClientType
    type AttrTransferType HandleClientTypePropertyInfo = Wnck.Enums.ClientType
    type AttrGetType HandleClientTypePropertyInfo = Wnck.Enums.ClientType
    type AttrLabel HandleClientTypePropertyInfo = "client-type"
    type AttrOrigin HandleClientTypePropertyInfo = Handle
    attrGet = getHandleClientType
    attrSet = setHandleClientType
    attrTransfer _ v = do
        return v
    attrConstruct = constructHandleClientType
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Objects.Handle.clientType"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Objects-Handle.html#g:attr:clientType"
        })
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Handle
type instance O.AttributeList Handle = HandleAttributeList
type HandleAttributeList = ('[ '("clientType", HandleClientTypePropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
handleClientType :: AttrLabelProxy "clientType"
handleClientType = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Handle = HandleSignalList
type HandleSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "wnck_handle_new" wnck_handle_new :: 
    CUInt ->                                
    IO (Ptr Handle)
handleNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Wnck.Enums.ClientType
    
    -> m Handle
    
handleNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ClientType -> m Handle
handleNew ClientType
clientType = IO Handle -> m Handle
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Handle -> m Handle) -> IO Handle -> m Handle
forall a b. (a -> b) -> a -> b
$ do
    let clientType' :: CUInt
clientType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (ClientType -> Int) -> ClientType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ClientType -> Int
forall a. Enum a => a -> Int
fromEnum) ClientType
clientType
    Ptr Handle
result <- CUInt -> IO (Ptr Handle)
wnck_handle_new CUInt
clientType'
    Text -> Ptr Handle -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"handleNew" Ptr Handle
result
    Handle
result' <- ((ManagedPtr Handle -> Handle) -> Ptr Handle -> IO Handle
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Handle -> Handle
Handle) Ptr Handle
result
    Handle -> IO Handle
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Handle
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "wnck_handle_get_application" wnck_handle_get_application :: 
    Ptr Handle ->                           
    CULong ->                               
    IO (Ptr Wnck.Application.Application)
handleGetApplication ::
    (B.CallStack.HasCallStack, MonadIO m, IsHandle a) =>
    a
    
    -> CULong
    
    -> m Wnck.Application.Application
    
    
    
    
handleGetApplication :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsHandle a) =>
a -> CULong -> m Application
handleGetApplication a
self CULong
xwindow = IO Application -> m Application
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Application -> m Application)
-> IO Application -> m Application
forall a b. (a -> b) -> a -> b
$ do
    Ptr Handle
self' <- a -> IO (Ptr Handle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Application
result <- Ptr Handle -> CULong -> IO (Ptr Application)
wnck_handle_get_application Ptr Handle
self' CULong
xwindow
    Text -> Ptr Application -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"handleGetApplication" Ptr Application
result
    Application
result' <- ((ManagedPtr Application -> Application)
-> Ptr Application -> IO Application
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Application -> Application
Wnck.Application.Application) Ptr Application
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Application -> IO Application
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Application
result'
#if defined(ENABLE_OVERLOADING)
data HandleGetApplicationMethodInfo
instance (signature ~ (CULong -> m Wnck.Application.Application), MonadIO m, IsHandle a) => O.OverloadedMethod HandleGetApplicationMethodInfo a signature where
    overloadedMethod = handleGetApplication
instance O.OverloadedMethodInfo HandleGetApplicationMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Objects.Handle.handleGetApplication",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Objects-Handle.html#v:handleGetApplication"
        })
#endif
foreign import ccall "wnck_handle_get_class_group" wnck_handle_get_class_group :: 
    Ptr Handle ->                           
    CString ->                              
    IO (Ptr Wnck.ClassGroup.ClassGroup)
handleGetClassGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsHandle a) =>
    a
    
    -> T.Text
    
    -> m Wnck.ClassGroup.ClassGroup
    
    
    
    
handleGetClassGroup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsHandle a) =>
a -> Text -> m ClassGroup
handleGetClassGroup a
self Text
id = IO ClassGroup -> m ClassGroup
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ClassGroup -> m ClassGroup) -> IO ClassGroup -> m ClassGroup
forall a b. (a -> b) -> a -> b
$ do
    Ptr Handle
self' <- a -> IO (Ptr Handle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
id' <- Text -> IO CString
textToCString Text
id
    Ptr ClassGroup
result <- Ptr Handle -> CString -> IO (Ptr ClassGroup)
wnck_handle_get_class_group Ptr Handle
self' CString
id'
    Text -> Ptr ClassGroup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"handleGetClassGroup" Ptr ClassGroup
result
    ClassGroup
result' <- ((ManagedPtr ClassGroup -> ClassGroup)
-> Ptr ClassGroup -> IO ClassGroup
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ClassGroup -> ClassGroup
Wnck.ClassGroup.ClassGroup) Ptr ClassGroup
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
id'
    ClassGroup -> IO ClassGroup
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ClassGroup
result'
#if defined(ENABLE_OVERLOADING)
data HandleGetClassGroupMethodInfo
instance (signature ~ (T.Text -> m Wnck.ClassGroup.ClassGroup), MonadIO m, IsHandle a) => O.OverloadedMethod HandleGetClassGroupMethodInfo a signature where
    overloadedMethod = handleGetClassGroup
instance O.OverloadedMethodInfo HandleGetClassGroupMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Objects.Handle.handleGetClassGroup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Objects-Handle.html#v:handleGetClassGroup"
        })
#endif
foreign import ccall "wnck_handle_get_default_screen" wnck_handle_get_default_screen :: 
    Ptr Handle ->                           
    IO (Ptr Wnck.Screen.Screen)
handleGetDefaultScreen ::
    (B.CallStack.HasCallStack, MonadIO m, IsHandle a) =>
    a
    
    -> m (Maybe Wnck.Screen.Screen)
    
    
    
handleGetDefaultScreen :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsHandle a) =>
a -> m (Maybe Screen)
handleGetDefaultScreen a
self = IO (Maybe Screen) -> m (Maybe Screen)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Screen) -> m (Maybe Screen))
-> IO (Maybe Screen) -> m (Maybe Screen)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Handle
self' <- a -> IO (Ptr Handle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Screen
result <- Ptr Handle -> IO (Ptr Screen)
wnck_handle_get_default_screen Ptr Handle
self'
    Maybe Screen
maybeResult <- Ptr Screen -> (Ptr Screen -> IO Screen) -> IO (Maybe Screen)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Screen
result ((Ptr Screen -> IO Screen) -> IO (Maybe Screen))
-> (Ptr Screen -> IO Screen) -> IO (Maybe Screen)
forall a b. (a -> b) -> a -> b
$ \Ptr Screen
result' -> do
        Screen
result'' <- ((ManagedPtr Screen -> Screen) -> Ptr Screen -> IO Screen
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Screen -> Screen
Wnck.Screen.Screen) Ptr Screen
result'
        Screen -> IO Screen
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Screen
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Screen -> IO (Maybe Screen)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Screen
maybeResult
#if defined(ENABLE_OVERLOADING)
data HandleGetDefaultScreenMethodInfo
instance (signature ~ (m (Maybe Wnck.Screen.Screen)), MonadIO m, IsHandle a) => O.OverloadedMethod HandleGetDefaultScreenMethodInfo a signature where
    overloadedMethod = handleGetDefaultScreen
instance O.OverloadedMethodInfo HandleGetDefaultScreenMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Objects.Handle.handleGetDefaultScreen",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Objects-Handle.html#v:handleGetDefaultScreen"
        })
#endif
foreign import ccall "wnck_handle_get_screen" wnck_handle_get_screen :: 
    Ptr Handle ->                           
    Int32 ->                                
    IO (Ptr Wnck.Screen.Screen)
handleGetScreen ::
    (B.CallStack.HasCallStack, MonadIO m, IsHandle a) =>
    a
    
    -> Int32
    
    -> m Wnck.Screen.Screen
    
    
    
handleGetScreen :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsHandle a) =>
a -> Int32 -> m Screen
handleGetScreen a
self Int32
index = IO Screen -> m Screen
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Screen -> m Screen) -> IO Screen -> m Screen
forall a b. (a -> b) -> a -> b
$ do
    Ptr Handle
self' <- a -> IO (Ptr Handle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Screen
result <- Ptr Handle -> Int32 -> IO (Ptr Screen)
wnck_handle_get_screen Ptr Handle
self' Int32
index
    Text -> Ptr Screen -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"handleGetScreen" Ptr Screen
result
    Screen
result' <- ((ManagedPtr Screen -> Screen) -> Ptr Screen -> IO Screen
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Screen -> Screen
Wnck.Screen.Screen) Ptr Screen
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Screen -> IO Screen
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Screen
result'
#if defined(ENABLE_OVERLOADING)
data HandleGetScreenMethodInfo
instance (signature ~ (Int32 -> m Wnck.Screen.Screen), MonadIO m, IsHandle a) => O.OverloadedMethod HandleGetScreenMethodInfo a signature where
    overloadedMethod = handleGetScreen
instance O.OverloadedMethodInfo HandleGetScreenMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Objects.Handle.handleGetScreen",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Objects-Handle.html#v:handleGetScreen"
        })
#endif
foreign import ccall "wnck_handle_get_screen_for_root" wnck_handle_get_screen_for_root :: 
    Ptr Handle ->                           
    CULong ->                               
    IO (Ptr Wnck.Screen.Screen)
handleGetScreenForRoot ::
    (B.CallStack.HasCallStack, MonadIO m, IsHandle a) =>
    a
    
    -> CULong
    
    -> m Wnck.Screen.Screen
    
    
    
handleGetScreenForRoot :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsHandle a) =>
a -> CULong -> m Screen
handleGetScreenForRoot a
self CULong
rootWindowId = IO Screen -> m Screen
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Screen -> m Screen) -> IO Screen -> m Screen
forall a b. (a -> b) -> a -> b
$ do
    Ptr Handle
self' <- a -> IO (Ptr Handle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Screen
result <- Ptr Handle -> CULong -> IO (Ptr Screen)
wnck_handle_get_screen_for_root Ptr Handle
self' CULong
rootWindowId
    Text -> Ptr Screen -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"handleGetScreenForRoot" Ptr Screen
result
    Screen
result' <- ((ManagedPtr Screen -> Screen) -> Ptr Screen -> IO Screen
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Screen -> Screen
Wnck.Screen.Screen) Ptr Screen
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Screen -> IO Screen
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Screen
result'
#if defined(ENABLE_OVERLOADING)
data HandleGetScreenForRootMethodInfo
instance (signature ~ (CULong -> m Wnck.Screen.Screen), MonadIO m, IsHandle a) => O.OverloadedMethod HandleGetScreenForRootMethodInfo a signature where
    overloadedMethod = handleGetScreenForRoot
instance O.OverloadedMethodInfo HandleGetScreenForRootMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Objects.Handle.handleGetScreenForRoot",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Objects-Handle.html#v:handleGetScreenForRoot"
        })
#endif
foreign import ccall "wnck_handle_get_window" wnck_handle_get_window :: 
    Ptr Handle ->                           
    CULong ->                               
    IO (Ptr Wnck.Window.Window)
handleGetWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsHandle a) =>
    a
    
    -> CULong
    
    -> m Wnck.Window.Window
    
    
handleGetWindow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsHandle a) =>
a -> CULong -> m Window
handleGetWindow a
self CULong
xwindow = IO Window -> m Window
forall a. IO a -> m a
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 Handle
self' <- a -> IO (Ptr Handle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Window
result <- Ptr Handle -> CULong -> IO (Ptr Window)
wnck_handle_get_window Ptr Handle
self' CULong
xwindow
    Text -> Ptr Window -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"handleGetWindow" Ptr Window
result
    Window
result' <- ((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
Wnck.Window.Window) Ptr Window
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Window -> IO Window
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Window
result'
#if defined(ENABLE_OVERLOADING)
data HandleGetWindowMethodInfo
instance (signature ~ (CULong -> m Wnck.Window.Window), MonadIO m, IsHandle a) => O.OverloadedMethod HandleGetWindowMethodInfo a signature where
    overloadedMethod = handleGetWindow
instance O.OverloadedMethodInfo HandleGetWindowMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Objects.Handle.handleGetWindow",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Objects-Handle.html#v:handleGetWindow"
        })
#endif
foreign import ccall "wnck_handle_set_default_icon_size" wnck_handle_set_default_icon_size :: 
    Ptr Handle ->                           
    Word64 ->                               
    IO ()
handleSetDefaultIconSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsHandle a) =>
    a
    
    -> Word64
    
    -> m ()
handleSetDefaultIconSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsHandle a) =>
a -> Word64 -> m ()
handleSetDefaultIconSize a
self Word64
iconSize = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Handle
self' <- a -> IO (Ptr Handle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Handle -> Word64 -> IO ()
wnck_handle_set_default_icon_size Ptr Handle
self' Word64
iconSize
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data HandleSetDefaultIconSizeMethodInfo
instance (signature ~ (Word64 -> m ()), MonadIO m, IsHandle a) => O.OverloadedMethod HandleSetDefaultIconSizeMethodInfo a signature where
    overloadedMethod = handleSetDefaultIconSize
instance O.OverloadedMethodInfo HandleSetDefaultIconSizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Objects.Handle.handleSetDefaultIconSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Objects-Handle.html#v:handleSetDefaultIconSize"
        })
#endif
foreign import ccall "wnck_handle_set_default_mini_icon_size" wnck_handle_set_default_mini_icon_size :: 
    Ptr Handle ->                           
    Word64 ->                               
    IO ()
handleSetDefaultMiniIconSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsHandle a) =>
    a
    
    -> Word64
    
    -> m ()
handleSetDefaultMiniIconSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsHandle a) =>
a -> Word64 -> m ()
handleSetDefaultMiniIconSize a
self Word64
iconSize = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Handle
self' <- a -> IO (Ptr Handle)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Handle -> Word64 -> IO ()
wnck_handle_set_default_mini_icon_size Ptr Handle
self' Word64
iconSize
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data HandleSetDefaultMiniIconSizeMethodInfo
instance (signature ~ (Word64 -> m ()), MonadIO m, IsHandle a) => O.OverloadedMethod HandleSetDefaultMiniIconSizeMethodInfo a signature where
    overloadedMethod = handleSetDefaultMiniIconSize
instance O.OverloadedMethodInfo HandleSetDefaultMiniIconSizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Wnck.Objects.Handle.handleSetDefaultMiniIconSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-wnck-3.0.14/docs/GI-Wnck-Objects-Handle.html#v:handleSetDefaultMiniIconSize"
        })
#endif