{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Atk.Objects.Misc
(
Misc(..) ,
IsMisc ,
toMisc ,
noMisc ,
#if defined(ENABLE_OVERLOADING)
ResolveMiscMethod ,
#endif
miscGetInstance ,
#if defined(ENABLE_OVERLOADING)
MiscThreadsEnterMethodInfo ,
#endif
miscThreadsEnter ,
#if defined(ENABLE_OVERLOADING)
MiscThreadsLeaveMethodInfo ,
#endif
miscThreadsLeave ,
) 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
newtype Misc = Misc (ManagedPtr Misc)
deriving (Misc -> Misc -> Bool
(Misc -> Misc -> Bool) -> (Misc -> Misc -> Bool) -> Eq Misc
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Misc -> Misc -> Bool
$c/= :: Misc -> Misc -> Bool
== :: Misc -> Misc -> Bool
$c== :: Misc -> Misc -> Bool
Eq)
foreign import ccall "atk_misc_get_type"
c_atk_misc_get_type :: IO GType
instance GObject Misc where
gobjectType :: IO GType
gobjectType = IO GType
c_atk_misc_get_type
instance B.GValue.IsGValue Misc where
toGValue :: Misc -> IO GValue
toGValue o :: Misc
o = do
GType
gtype <- IO GType
c_atk_misc_get_type
Misc -> (Ptr Misc -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Misc
o (GType -> (GValue -> Ptr Misc -> IO ()) -> Ptr Misc -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Misc -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO Misc
fromGValue gv :: GValue
gv = do
Ptr Misc
ptr <- GValue -> IO (Ptr Misc)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Misc)
(ManagedPtr Misc -> Misc) -> Ptr Misc -> IO Misc
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Misc -> Misc
Misc Ptr Misc
ptr
class (GObject o, O.IsDescendantOf Misc o) => IsMisc o
instance (GObject o, O.IsDescendantOf Misc o) => IsMisc o
instance O.HasParentTypes Misc
type instance O.ParentTypes Misc = '[GObject.Object.Object]
toMisc :: (MonadIO m, IsMisc o) => o -> m Misc
toMisc :: o -> m Misc
toMisc = IO Misc -> m Misc
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Misc -> m Misc) -> (o -> IO Misc) -> o -> m Misc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Misc -> Misc) -> o -> IO Misc
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Misc -> Misc
Misc
noMisc :: Maybe Misc
noMisc :: Maybe Misc
noMisc = Maybe Misc
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveMiscMethod (t :: Symbol) (o :: *) :: * where
ResolveMiscMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveMiscMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveMiscMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveMiscMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveMiscMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveMiscMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveMiscMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveMiscMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveMiscMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveMiscMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveMiscMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveMiscMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveMiscMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveMiscMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveMiscMethod "threadsEnter" o = MiscThreadsEnterMethodInfo
ResolveMiscMethod "threadsLeave" o = MiscThreadsLeaveMethodInfo
ResolveMiscMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveMiscMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveMiscMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveMiscMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveMiscMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveMiscMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveMiscMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveMiscMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveMiscMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveMiscMethod t Misc, O.MethodInfo info Misc p) => OL.IsLabel t (Misc -> 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 Misc
type instance O.AttributeList Misc = MiscAttributeList
type MiscAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Misc = MiscSignalList
type MiscSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "atk_misc_threads_enter" atk_misc_threads_enter ::
Ptr Misc ->
IO ()
{-# DEPRECATED miscThreadsEnter ["Since 2.12."] #-}
miscThreadsEnter ::
(B.CallStack.HasCallStack, MonadIO m, IsMisc a) =>
a
-> m ()
miscThreadsEnter :: a -> m ()
miscThreadsEnter misc :: a
misc = 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 Misc
misc' <- a -> IO (Ptr Misc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
misc
Ptr Misc -> IO ()
atk_misc_threads_enter Ptr Misc
misc'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
misc
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data MiscThreadsEnterMethodInfo
instance (signature ~ (m ()), MonadIO m, IsMisc a) => O.MethodInfo MiscThreadsEnterMethodInfo a signature where
overloadedMethod = miscThreadsEnter
#endif
foreign import ccall "atk_misc_threads_leave" atk_misc_threads_leave ::
Ptr Misc ->
IO ()
{-# DEPRECATED miscThreadsLeave ["Since 2.12."] #-}
miscThreadsLeave ::
(B.CallStack.HasCallStack, MonadIO m, IsMisc a) =>
a
-> m ()
miscThreadsLeave :: a -> m ()
miscThreadsLeave misc :: a
misc = 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 Misc
misc' <- a -> IO (Ptr Misc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
misc
Ptr Misc -> IO ()
atk_misc_threads_leave Ptr Misc
misc'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
misc
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data MiscThreadsLeaveMethodInfo
instance (signature ~ (m ()), MonadIO m, IsMisc a) => O.MethodInfo MiscThreadsLeaveMethodInfo a signature where
overloadedMethod = miscThreadsLeave
#endif
foreign import ccall "atk_misc_get_instance" atk_misc_get_instance ::
IO (Ptr Misc)
{-# DEPRECATED miscGetInstance ["Since 2.12."] #-}
miscGetInstance ::
(B.CallStack.HasCallStack, MonadIO m) =>
m Misc
miscGetInstance :: m Misc
miscGetInstance = IO Misc -> m Misc
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Misc -> m Misc) -> IO Misc -> m Misc
forall a b. (a -> b) -> a -> b
$ do
Ptr Misc
result <- IO (Ptr Misc)
atk_misc_get_instance
Text -> Ptr Misc -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "miscGetInstance" Ptr Misc
result
Misc
result' <- ((ManagedPtr Misc -> Misc) -> Ptr Misc -> IO Misc
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Misc -> Misc
Misc) Ptr Misc
result
Misc -> IO Misc
forall (m :: * -> *) a. Monad m => a -> m a
return Misc
result'
#if defined(ENABLE_OVERLOADING)
#endif