{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- This class is the base object class for a factory used to create an
-- accessible object for a specific GType. The function
-- 'GI.Atk.Objects.Registry.registrySetFactoryType' is normally called to store in the
-- registry the factory type to be used to create an accessible of a
-- particular GType.

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

module GI.Atk.Objects.ObjectFactory
    ( 

-- * Exported types
    ObjectFactory(..)                       ,
    IsObjectFactory                         ,
    toObjectFactory                         ,


 -- * 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"), [createAccessible]("GI.Atk.Objects.ObjectFactory#g:method:createAccessible"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [invalidate]("GI.Atk.Objects.ObjectFactory#g:method:invalidate"), [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
-- [getAccessibleType]("GI.Atk.Objects.ObjectFactory#g:method:getAccessibleType"), [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)
    ResolveObjectFactoryMethod              ,
#endif

-- ** createAccessible #method:createAccessible#

#if defined(ENABLE_OVERLOADING)
    ObjectFactoryCreateAccessibleMethodInfo ,
#endif
    objectFactoryCreateAccessible           ,


-- ** getAccessibleType #method:getAccessibleType#

#if defined(ENABLE_OVERLOADING)
    ObjectFactoryGetAccessibleTypeMethodInfo,
#endif
    objectFactoryGetAccessibleType          ,


-- ** invalidate #method:invalidate#

#if defined(ENABLE_OVERLOADING)
    ObjectFactoryInvalidateMethodInfo       ,
#endif
    objectFactoryInvalidate                 ,




    ) 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.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 {-# SOURCE #-} qualified GI.Atk.Objects.Object as Atk.Object
import qualified GI.GObject.Objects.Object as GObject.Object

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

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

foreign import ccall "atk_object_factory_get_type"
    c_atk_object_factory_get_type :: IO B.Types.GType

instance B.Types.TypedObject ObjectFactory where
    glibType :: IO GType
glibType = IO GType
c_atk_object_factory_get_type

instance B.Types.GObject ObjectFactory

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

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

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

-- | Convert 'ObjectFactory' 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 ObjectFactory) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_atk_object_factory_get_type
    gvalueSet_ :: Ptr GValue -> Maybe ObjectFactory -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ObjectFactory
P.Nothing = Ptr GValue -> Ptr ObjectFactory -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr ObjectFactory
forall a. Ptr a
FP.nullPtr :: FP.Ptr ObjectFactory)
    gvalueSet_ Ptr GValue
gv (P.Just ObjectFactory
obj) = ObjectFactory -> (Ptr ObjectFactory -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ObjectFactory
obj (Ptr GValue -> Ptr ObjectFactory -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe ObjectFactory)
gvalueGet_ Ptr GValue
gv = do
        Ptr ObjectFactory
ptr <- Ptr GValue -> IO (Ptr ObjectFactory)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr ObjectFactory)
        if Ptr ObjectFactory
ptr Ptr ObjectFactory -> Ptr ObjectFactory -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr ObjectFactory
forall a. Ptr a
FP.nullPtr
        then ObjectFactory -> Maybe ObjectFactory
forall a. a -> Maybe a
P.Just (ObjectFactory -> Maybe ObjectFactory)
-> IO ObjectFactory -> IO (Maybe ObjectFactory)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr ObjectFactory -> ObjectFactory)
-> Ptr ObjectFactory -> IO ObjectFactory
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ObjectFactory -> ObjectFactory
ObjectFactory Ptr ObjectFactory
ptr
        else Maybe ObjectFactory -> IO (Maybe ObjectFactory)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ObjectFactory
forall a. Maybe a
P.Nothing
        
    

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

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

#endif

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method ObjectFactory::create_accessible
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "factory"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "ObjectFactory" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #AtkObjectFactory associated with @obj's\nobject type"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "obj"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GObject" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Atk" , name = "Object" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_factory_create_accessible" atk_object_factory_create_accessible :: 
    Ptr ObjectFactory ->                    -- factory : TInterface (Name {namespace = "Atk", name = "ObjectFactory"})
    Ptr GObject.Object.Object ->            -- obj : TInterface (Name {namespace = "GObject", name = "Object"})
    IO (Ptr Atk.Object.Object)

-- | Provides an t'GI.Atk.Objects.Object.Object' that implements an accessibility interface
-- on behalf of /@obj@/
objectFactoryCreateAccessible ::
    (B.CallStack.HasCallStack, MonadIO m, IsObjectFactory a, GObject.Object.IsObject b) =>
    a
    -- ^ /@factory@/: The t'GI.Atk.Objects.ObjectFactory.ObjectFactory' associated with /@obj@/\'s
    -- object type
    -> b
    -- ^ /@obj@/: a t'GI.GObject.Objects.Object.Object'
    -> m Atk.Object.Object
    -- ^ __Returns:__ an t'GI.Atk.Objects.Object.Object' that implements an accessibility
    -- interface on behalf of /@obj@/
objectFactoryCreateAccessible :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsObjectFactory a, IsObject b) =>
a -> b -> m Object
objectFactoryCreateAccessible a
factory b
obj = IO Object -> m Object
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Object -> m Object) -> IO Object -> m Object
forall a b. (a -> b) -> a -> b
$ do
    Ptr ObjectFactory
factory' <- a -> IO (Ptr ObjectFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    Ptr Object
obj' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
obj
    Ptr Object
result <- Ptr ObjectFactory -> Ptr Object -> IO (Ptr Object)
atk_object_factory_create_accessible Ptr ObjectFactory
factory' Ptr Object
obj'
    Text -> Ptr Object -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"objectFactoryCreateAccessible" Ptr Object
result
    Object
result' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Object -> Object
Atk.Object.Object) Ptr Object
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
factory
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
obj
    Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result'

#if defined(ENABLE_OVERLOADING)
data ObjectFactoryCreateAccessibleMethodInfo
instance (signature ~ (b -> m Atk.Object.Object), MonadIO m, IsObjectFactory a, GObject.Object.IsObject b) => O.OverloadedMethod ObjectFactoryCreateAccessibleMethodInfo a signature where
    overloadedMethod = objectFactoryCreateAccessible

instance O.OverloadedMethodInfo ObjectFactoryCreateAccessibleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Objects.ObjectFactory.objectFactoryCreateAccessible",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Objects-ObjectFactory.html#v:objectFactoryCreateAccessible"
        })


#endif

-- method ObjectFactory::get_accessible_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "factory"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "ObjectFactory" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkObjectFactory"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TGType)
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_factory_get_accessible_type" atk_object_factory_get_accessible_type :: 
    Ptr ObjectFactory ->                    -- factory : TInterface (Name {namespace = "Atk", name = "ObjectFactory"})
    IO CGType

-- | Gets the GType of the accessible which is created by the factory.
objectFactoryGetAccessibleType ::
    (B.CallStack.HasCallStack, MonadIO m, IsObjectFactory a) =>
    a
    -- ^ /@factory@/: an t'GI.Atk.Objects.ObjectFactory.ObjectFactory'
    -> m GType
    -- ^ __Returns:__ the type of the accessible which is created by the /@factory@/.
    -- The value G_TYPE_INVALID is returned if no type if found.
objectFactoryGetAccessibleType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObjectFactory a) =>
a -> m GType
objectFactoryGetAccessibleType a
factory = IO GType -> m GType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ do
    Ptr ObjectFactory
factory' <- a -> IO (Ptr ObjectFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    CGType
result <- Ptr ObjectFactory -> IO CGType
atk_object_factory_get_accessible_type Ptr ObjectFactory
factory'
    let result' :: GType
result' = CGType -> GType
GType CGType
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
factory
    GType -> IO GType
forall (m :: * -> *) a. Monad m => a -> m a
return GType
result'

#if defined(ENABLE_OVERLOADING)
data ObjectFactoryGetAccessibleTypeMethodInfo
instance (signature ~ (m GType), MonadIO m, IsObjectFactory a) => O.OverloadedMethod ObjectFactoryGetAccessibleTypeMethodInfo a signature where
    overloadedMethod = objectFactoryGetAccessibleType

instance O.OverloadedMethodInfo ObjectFactoryGetAccessibleTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Objects.ObjectFactory.objectFactoryGetAccessibleType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Objects-ObjectFactory.html#v:objectFactoryGetAccessibleType"
        })


#endif

-- method ObjectFactory::invalidate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "factory"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "ObjectFactory" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkObjectFactory to invalidate"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_factory_invalidate" atk_object_factory_invalidate :: 
    Ptr ObjectFactory ->                    -- factory : TInterface (Name {namespace = "Atk", name = "ObjectFactory"})
    IO ()

-- | Inform /@factory@/ that it is no longer being used to create
-- accessibles. When called, /@factory@/ may need to inform
-- @/AtkObjects/@ which it has created that they need to be re-instantiated.
-- Note: primarily used for runtime replacement of @/AtkObjectFactorys/@
-- in object registries.
objectFactoryInvalidate ::
    (B.CallStack.HasCallStack, MonadIO m, IsObjectFactory a) =>
    a
    -- ^ /@factory@/: an t'GI.Atk.Objects.ObjectFactory.ObjectFactory' to invalidate
    -> m ()
objectFactoryInvalidate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObjectFactory a) =>
a -> m ()
objectFactoryInvalidate a
factory = 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 ObjectFactory
factory' <- a -> IO (Ptr ObjectFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
factory
    Ptr ObjectFactory -> IO ()
atk_object_factory_invalidate Ptr ObjectFactory
factory'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
factory
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ObjectFactoryInvalidateMethodInfo
instance (signature ~ (m ()), MonadIO m, IsObjectFactory a) => O.OverloadedMethod ObjectFactoryInvalidateMethodInfo a signature where
    overloadedMethod = objectFactoryInvalidate

instance O.OverloadedMethodInfo ObjectFactoryInvalidateMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Objects.ObjectFactory.objectFactoryInvalidate",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Objects-ObjectFactory.html#v:objectFactoryInvalidate"
        })


#endif