{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A set of ATK utility functions which are used to support event
-- registration of various types, and obtaining the \'root\' accessible
-- of a process and information about the current ATK implementation
-- and toolkit version.

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

module GI.Atk.Objects.Util
    ( 

-- * Exported types
    Util(..)                                ,
    IsUtil                                  ,
    toUtil                                  ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveUtilMethod                       ,
#endif



    ) 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.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

-- | Memory-managed wrapper type.
newtype Util = Util (SP.ManagedPtr Util)
    deriving (Util -> Util -> Bool
(Util -> Util -> Bool) -> (Util -> Util -> Bool) -> Eq Util
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Util -> Util -> Bool
== :: Util -> Util -> Bool
$c/= :: Util -> Util -> Bool
/= :: Util -> Util -> Bool
Eq)

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

foreign import ccall "atk_util_get_type"
    c_atk_util_get_type :: IO B.Types.GType

instance B.Types.TypedObject Util where
    glibType :: IO GType
glibType = IO GType
c_atk_util_get_type

instance B.Types.GObject Util

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

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

-- | Cast to `Util`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toUtil :: (MIO.MonadIO m, IsUtil o) => o -> m Util
toUtil :: forall (m :: * -> *) o. (MonadIO m, IsUtil o) => o -> m Util
toUtil = IO Util -> m Util
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Util -> m Util) -> (o -> IO Util) -> o -> m Util
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Util -> Util) -> o -> IO Util
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Util -> Util
Util

-- | Convert 'Util' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Util) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_atk_util_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Util -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Util
P.Nothing = Ptr GValue -> Ptr Util -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Util
forall a. Ptr a
FP.nullPtr :: FP.Ptr Util)
    gvalueSet_ Ptr GValue
gv (P.Just Util
obj) = Util -> (Ptr Util -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Util
obj (Ptr GValue -> Ptr Util -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Util)
gvalueGet_ Ptr GValue
gv = do
        Ptr Util
ptr <- Ptr GValue -> IO (Ptr Util)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Util)
        if Ptr Util
ptr Ptr Util -> Ptr Util -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Util
forall a. Ptr a
FP.nullPtr
        then Util -> Maybe Util
forall a. a -> Maybe a
P.Just (Util -> Maybe Util) -> IO Util -> IO (Maybe Util)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Util -> Util) -> Ptr Util -> IO Util
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Util -> Util
Util Ptr Util
ptr
        else Maybe Util -> IO (Maybe Util)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Util
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveUtilMethod (t :: Symbol) (o :: *) :: * where
    ResolveUtilMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveUtilMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveUtilMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveUtilMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveUtilMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveUtilMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveUtilMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveUtilMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveUtilMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveUtilMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveUtilMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveUtilMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveUtilMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveUtilMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveUtilMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveUtilMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveUtilMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveUtilMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveUtilMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveUtilMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveUtilMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveUtilMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveUtilMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveUtilMethod t Util, O.OverloadedMethod info Util p) => OL.IsLabel t (Util -> 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 ~ ResolveUtilMethod t Util, O.OverloadedMethod info Util p, R.HasField t Util p) => R.HasField t Util p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveUtilMethod t Util, O.OverloadedMethodInfo info Util) => OL.IsLabel t (O.MethodProxy info Util) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Util
type instance O.AttributeList Util = UtilAttributeList
type UtilAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Util = UtilSignalList
type UtilSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif