{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Structs.IOExtensionPoint.IOExtensionPoint' is an opaque data structure and can only be accessed
-- using the following functions.

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

module GI.Gio.Structs.IOExtensionPoint
    ( 

-- * Exported types
    IOExtensionPoint(..)                    ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- /None/.
-- 
-- ==== Getters
-- [getExtensionByName]("GI.Gio.Structs.IOExtensionPoint#g:method:getExtensionByName"), [getExtensions]("GI.Gio.Structs.IOExtensionPoint#g:method:getExtensions"), [getRequiredType]("GI.Gio.Structs.IOExtensionPoint#g:method:getRequiredType").
-- 
-- ==== Setters
-- [setRequiredType]("GI.Gio.Structs.IOExtensionPoint#g:method:setRequiredType").

#if defined(ENABLE_OVERLOADING)
    ResolveIOExtensionPointMethod           ,
#endif

-- ** getExtensionByName #method:getExtensionByName#

#if defined(ENABLE_OVERLOADING)
    IOExtensionPointGetExtensionByNameMethodInfo,
#endif
    iOExtensionPointGetExtensionByName      ,


-- ** getExtensions #method:getExtensions#

#if defined(ENABLE_OVERLOADING)
    IOExtensionPointGetExtensionsMethodInfo ,
#endif
    iOExtensionPointGetExtensions           ,


-- ** getRequiredType #method:getRequiredType#

#if defined(ENABLE_OVERLOADING)
    IOExtensionPointGetRequiredTypeMethodInfo,
#endif
    iOExtensionPointGetRequiredType         ,


-- ** implement #method:implement#

    iOExtensionPointImplement               ,


-- ** lookup #method:lookup#

    iOExtensionPointLookup                  ,


-- ** register #method:register#

    iOExtensionPointRegister                ,


-- ** setRequiredType #method:setRequiredType#

#if defined(ENABLE_OVERLOADING)
    IOExtensionPointSetRequiredTypeMethodInfo,
#endif
    iOExtensionPointSetRequiredType         ,




    ) 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.Gio.Structs.IOExtension as Gio.IOExtension

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

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

-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance BoxedPtr IOExtensionPoint where
    boxedPtrCopy :: IOExtensionPoint -> IO IOExtensionPoint
boxedPtrCopy = IOExtensionPoint -> IO IOExtensionPoint
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: IOExtensionPoint -> IO ()
boxedPtrFree = \IOExtensionPoint
_x -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()


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

-- method IOExtensionPoint::get_extension_by_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "extension_point"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "IOExtensionPoint" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIOExtensionPoint"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the extension to get"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "IOExtension" })
-- throws : False
-- Skip return : False

foreign import ccall "g_io_extension_point_get_extension_by_name" g_io_extension_point_get_extension_by_name :: 
    Ptr IOExtensionPoint ->                 -- extension_point : TInterface (Name {namespace = "Gio", name = "IOExtensionPoint"})
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr Gio.IOExtension.IOExtension)

-- | Finds a t'GI.Gio.Structs.IOExtension.IOExtension' for an extension point by name.
iOExtensionPointGetExtensionByName ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    IOExtensionPoint
    -- ^ /@extensionPoint@/: a t'GI.Gio.Structs.IOExtensionPoint.IOExtensionPoint'
    -> T.Text
    -- ^ /@name@/: the name of the extension to get
    -> m Gio.IOExtension.IOExtension
    -- ^ __Returns:__ the t'GI.Gio.Structs.IOExtension.IOExtension' for /@extensionPoint@/ that has the
    --    given name, or 'P.Nothing' if there is no extension with that name
iOExtensionPointGetExtensionByName :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
IOExtensionPoint -> Text -> m IOExtension
iOExtensionPointGetExtensionByName IOExtensionPoint
extensionPoint Text
name = IO IOExtension -> m IOExtension
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IOExtension -> m IOExtension)
-> IO IOExtension -> m IOExtension
forall a b. (a -> b) -> a -> b
$ do
    Ptr IOExtensionPoint
extensionPoint' <- IOExtensionPoint -> IO (Ptr IOExtensionPoint)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IOExtensionPoint
extensionPoint
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr IOExtension
result <- Ptr IOExtensionPoint -> CString -> IO (Ptr IOExtension)
g_io_extension_point_get_extension_by_name Ptr IOExtensionPoint
extensionPoint' CString
name'
    Text -> Ptr IOExtension -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iOExtensionPointGetExtensionByName" Ptr IOExtension
result
    IOExtension
result' <- ((ManagedPtr IOExtension -> IOExtension)
-> Ptr IOExtension -> IO IOExtension
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr IOExtension -> IOExtension
Gio.IOExtension.IOExtension) Ptr IOExtension
result
    IOExtensionPoint -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IOExtensionPoint
extensionPoint
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    IOExtension -> IO IOExtension
forall (m :: * -> *) a. Monad m => a -> m a
return IOExtension
result'

#if defined(ENABLE_OVERLOADING)
data IOExtensionPointGetExtensionByNameMethodInfo
instance (signature ~ (T.Text -> m Gio.IOExtension.IOExtension), MonadIO m) => O.OverloadedMethod IOExtensionPointGetExtensionByNameMethodInfo IOExtensionPoint signature where
    overloadedMethod = iOExtensionPointGetExtensionByName

instance O.OverloadedMethodInfo IOExtensionPointGetExtensionByNameMethodInfo IOExtensionPoint where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.IOExtensionPoint.iOExtensionPointGetExtensionByName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Structs-IOExtensionPoint.html#v:iOExtensionPointGetExtensionByName"
        })


#endif

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

foreign import ccall "g_io_extension_point_get_extensions" g_io_extension_point_get_extensions :: 
    Ptr IOExtensionPoint ->                 -- extension_point : TInterface (Name {namespace = "Gio", name = "IOExtensionPoint"})
    IO (Ptr (GList (Ptr Gio.IOExtension.IOExtension)))

-- | Gets a list of all extensions that implement this extension point.
-- The list is sorted by priority, beginning with the highest priority.
iOExtensionPointGetExtensions ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    IOExtensionPoint
    -- ^ /@extensionPoint@/: a t'GI.Gio.Structs.IOExtensionPoint.IOExtensionPoint'
    -> m [Gio.IOExtension.IOExtension]
    -- ^ __Returns:__ a t'GI.GLib.Structs.List.List' of
    --     @/GIOExtensions/@. The list is owned by GIO and should not be
    --     modified.
iOExtensionPointGetExtensions :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
IOExtensionPoint -> m [IOExtension]
iOExtensionPointGetExtensions IOExtensionPoint
extensionPoint = IO [IOExtension] -> m [IOExtension]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [IOExtension] -> m [IOExtension])
-> IO [IOExtension] -> m [IOExtension]
forall a b. (a -> b) -> a -> b
$ do
    Ptr IOExtensionPoint
extensionPoint' <- IOExtensionPoint -> IO (Ptr IOExtensionPoint)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IOExtensionPoint
extensionPoint
    Ptr (GList (Ptr IOExtension))
result <- Ptr IOExtensionPoint -> IO (Ptr (GList (Ptr IOExtension)))
g_io_extension_point_get_extensions Ptr IOExtensionPoint
extensionPoint'
    [Ptr IOExtension]
result' <- Ptr (GList (Ptr IOExtension)) -> IO [Ptr IOExtension]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr IOExtension))
result
    [IOExtension]
result'' <- (Ptr IOExtension -> IO IOExtension)
-> [Ptr IOExtension] -> IO [IOExtension]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr IOExtension -> IOExtension)
-> Ptr IOExtension -> IO IOExtension
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr IOExtension -> IOExtension
Gio.IOExtension.IOExtension) [Ptr IOExtension]
result'
    IOExtensionPoint -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IOExtensionPoint
extensionPoint
    [IOExtension] -> IO [IOExtension]
forall (m :: * -> *) a. Monad m => a -> m a
return [IOExtension]
result''

#if defined(ENABLE_OVERLOADING)
data IOExtensionPointGetExtensionsMethodInfo
instance (signature ~ (m [Gio.IOExtension.IOExtension]), MonadIO m) => O.OverloadedMethod IOExtensionPointGetExtensionsMethodInfo IOExtensionPoint signature where
    overloadedMethod = iOExtensionPointGetExtensions

instance O.OverloadedMethodInfo IOExtensionPointGetExtensionsMethodInfo IOExtensionPoint where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.IOExtensionPoint.iOExtensionPointGetExtensions",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Structs-IOExtensionPoint.html#v:iOExtensionPointGetExtensions"
        })


#endif

-- method IOExtensionPoint::get_required_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "extension_point"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "IOExtensionPoint" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIOExtensionPoint"
--                 , 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 "g_io_extension_point_get_required_type" g_io_extension_point_get_required_type :: 
    Ptr IOExtensionPoint ->                 -- extension_point : TInterface (Name {namespace = "Gio", name = "IOExtensionPoint"})
    IO CGType

-- | Gets the required type for /@extensionPoint@/.
iOExtensionPointGetRequiredType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    IOExtensionPoint
    -- ^ /@extensionPoint@/: a t'GI.Gio.Structs.IOExtensionPoint.IOExtensionPoint'
    -> m GType
    -- ^ __Returns:__ the t'GType' that all implementations must have,
    --     or @/G_TYPE_INVALID/@ if the extension point has no required type
iOExtensionPointGetRequiredType :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
IOExtensionPoint -> m GType
iOExtensionPointGetRequiredType IOExtensionPoint
extensionPoint = 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 IOExtensionPoint
extensionPoint' <- IOExtensionPoint -> IO (Ptr IOExtensionPoint)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IOExtensionPoint
extensionPoint
    CGType
result <- Ptr IOExtensionPoint -> IO CGType
g_io_extension_point_get_required_type Ptr IOExtensionPoint
extensionPoint'
    let result' :: GType
result' = CGType -> GType
GType CGType
result
    IOExtensionPoint -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IOExtensionPoint
extensionPoint
    GType -> IO GType
forall (m :: * -> *) a. Monad m => a -> m a
return GType
result'

#if defined(ENABLE_OVERLOADING)
data IOExtensionPointGetRequiredTypeMethodInfo
instance (signature ~ (m GType), MonadIO m) => O.OverloadedMethod IOExtensionPointGetRequiredTypeMethodInfo IOExtensionPoint signature where
    overloadedMethod = iOExtensionPointGetRequiredType

instance O.OverloadedMethodInfo IOExtensionPointGetRequiredTypeMethodInfo IOExtensionPoint where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.IOExtensionPoint.iOExtensionPointGetRequiredType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Structs-IOExtensionPoint.html#v:iOExtensionPointGetRequiredType"
        })


#endif

-- method IOExtensionPoint::set_required_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "extension_point"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "IOExtensionPoint" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIOExtensionPoint"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GType to require"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_io_extension_point_set_required_type" g_io_extension_point_set_required_type :: 
    Ptr IOExtensionPoint ->                 -- extension_point : TInterface (Name {namespace = "Gio", name = "IOExtensionPoint"})
    CGType ->                               -- type : TBasicType TGType
    IO ()

-- | Sets the required type for /@extensionPoint@/ to /@type@/.
-- All implementations must henceforth have this type.
iOExtensionPointSetRequiredType ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    IOExtensionPoint
    -- ^ /@extensionPoint@/: a t'GI.Gio.Structs.IOExtensionPoint.IOExtensionPoint'
    -> GType
    -- ^ /@type@/: the t'GType' to require
    -> m ()
iOExtensionPointSetRequiredType :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
IOExtensionPoint -> GType -> m ()
iOExtensionPointSetRequiredType IOExtensionPoint
extensionPoint GType
type_ = 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 IOExtensionPoint
extensionPoint' <- IOExtensionPoint -> IO (Ptr IOExtensionPoint)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IOExtensionPoint
extensionPoint
    let type_' :: CGType
type_' = GType -> CGType
gtypeToCGType GType
type_
    Ptr IOExtensionPoint -> CGType -> IO ()
g_io_extension_point_set_required_type Ptr IOExtensionPoint
extensionPoint' CGType
type_'
    IOExtensionPoint -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IOExtensionPoint
extensionPoint
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IOExtensionPointSetRequiredTypeMethodInfo
instance (signature ~ (GType -> m ()), MonadIO m) => O.OverloadedMethod IOExtensionPointSetRequiredTypeMethodInfo IOExtensionPoint signature where
    overloadedMethod = iOExtensionPointSetRequiredType

instance O.OverloadedMethodInfo IOExtensionPointSetRequiredTypeMethodInfo IOExtensionPoint where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.IOExtensionPoint.iOExtensionPointSetRequiredType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Structs-IOExtensionPoint.html#v:iOExtensionPointSetRequiredType"
        })


#endif

-- method IOExtensionPoint::implement
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "extension_point_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the extension point"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GType to register as extension"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "extension_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name for the extension"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "priority"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the priority for the extension"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "IOExtension" })
-- throws : False
-- Skip return : False

foreign import ccall "g_io_extension_point_implement" g_io_extension_point_implement :: 
    CString ->                              -- extension_point_name : TBasicType TUTF8
    CGType ->                               -- type : TBasicType TGType
    CString ->                              -- extension_name : TBasicType TUTF8
    Int32 ->                                -- priority : TBasicType TInt
    IO (Ptr Gio.IOExtension.IOExtension)

-- | Registers /@type@/ as extension for the extension point with name
-- /@extensionPointName@/.
-- 
-- If /@type@/ has already been registered as an extension for this
-- extension point, the existing t'GI.Gio.Structs.IOExtension.IOExtension' object is returned.
iOExtensionPointImplement ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@extensionPointName@/: the name of the extension point
    -> GType
    -- ^ /@type@/: the t'GType' to register as extension
    -> T.Text
    -- ^ /@extensionName@/: the name for the extension
    -> Int32
    -- ^ /@priority@/: the priority for the extension
    -> m Gio.IOExtension.IOExtension
    -- ^ __Returns:__ a t'GI.Gio.Structs.IOExtension.IOExtension' object for t'GType'
iOExtensionPointImplement :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> GType -> Text -> Int32 -> m IOExtension
iOExtensionPointImplement Text
extensionPointName GType
type_ Text
extensionName Int32
priority = IO IOExtension -> m IOExtension
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IOExtension -> m IOExtension)
-> IO IOExtension -> m IOExtension
forall a b. (a -> b) -> a -> b
$ do
    CString
extensionPointName' <- Text -> IO CString
textToCString Text
extensionPointName
    let type_' :: CGType
type_' = GType -> CGType
gtypeToCGType GType
type_
    CString
extensionName' <- Text -> IO CString
textToCString Text
extensionName
    Ptr IOExtension
result <- CString -> CGType -> CString -> Int32 -> IO (Ptr IOExtension)
g_io_extension_point_implement CString
extensionPointName' CGType
type_' CString
extensionName' Int32
priority
    Text -> Ptr IOExtension -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iOExtensionPointImplement" Ptr IOExtension
result
    IOExtension
result' <- ((ManagedPtr IOExtension -> IOExtension)
-> Ptr IOExtension -> IO IOExtension
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr IOExtension -> IOExtension
Gio.IOExtension.IOExtension) Ptr IOExtension
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
extensionPointName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
extensionName'
    IOExtension -> IO IOExtension
forall (m :: * -> *) a. Monad m => a -> m a
return IOExtension
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method IOExtensionPoint::lookup
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the extension point"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "IOExtensionPoint" })
-- throws : False
-- Skip return : False

foreign import ccall "g_io_extension_point_lookup" g_io_extension_point_lookup :: 
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr IOExtensionPoint)

-- | Looks up an existing extension point.
iOExtensionPointLookup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@name@/: the name of the extension point
    -> m IOExtensionPoint
    -- ^ __Returns:__ the t'GI.Gio.Structs.IOExtensionPoint.IOExtensionPoint', or 'P.Nothing' if there
    --    is no registered extension point with the given name.
iOExtensionPointLookup :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m IOExtensionPoint
iOExtensionPointLookup Text
name = IO IOExtensionPoint -> m IOExtensionPoint
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IOExtensionPoint -> m IOExtensionPoint)
-> IO IOExtensionPoint -> m IOExtensionPoint
forall a b. (a -> b) -> a -> b
$ do
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr IOExtensionPoint
result <- CString -> IO (Ptr IOExtensionPoint)
g_io_extension_point_lookup CString
name'
    Text -> Ptr IOExtensionPoint -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iOExtensionPointLookup" Ptr IOExtensionPoint
result
    IOExtensionPoint
result' <- ((ManagedPtr IOExtensionPoint -> IOExtensionPoint)
-> Ptr IOExtensionPoint -> IO IOExtensionPoint
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr IOExtensionPoint -> IOExtensionPoint
IOExtensionPoint) Ptr IOExtensionPoint
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    IOExtensionPoint -> IO IOExtensionPoint
forall (m :: * -> *) a. Monad m => a -> m a
return IOExtensionPoint
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method IOExtensionPoint::register
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The name of the extension point"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "IOExtensionPoint" })
-- throws : False
-- Skip return : False

foreign import ccall "g_io_extension_point_register" g_io_extension_point_register :: 
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr IOExtensionPoint)

-- | Registers an extension point.
iOExtensionPointRegister ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@name@/: The name of the extension point
    -> m IOExtensionPoint
    -- ^ __Returns:__ the new t'GI.Gio.Structs.IOExtensionPoint.IOExtensionPoint'. This object is
    --    owned by GIO and should not be freed.
iOExtensionPointRegister :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m IOExtensionPoint
iOExtensionPointRegister Text
name = IO IOExtensionPoint -> m IOExtensionPoint
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IOExtensionPoint -> m IOExtensionPoint)
-> IO IOExtensionPoint -> m IOExtensionPoint
forall a b. (a -> b) -> a -> b
$ do
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr IOExtensionPoint
result <- CString -> IO (Ptr IOExtensionPoint)
g_io_extension_point_register CString
name'
    Text -> Ptr IOExtensionPoint -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iOExtensionPointRegister" Ptr IOExtensionPoint
result
    IOExtensionPoint
result' <- ((ManagedPtr IOExtensionPoint -> IOExtensionPoint)
-> Ptr IOExtensionPoint -> IO IOExtensionPoint
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr IOExtensionPoint -> IOExtensionPoint
IOExtensionPoint) Ptr IOExtensionPoint
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    IOExtensionPoint -> IO IOExtensionPoint
forall (m :: * -> *) a. Monad m => a -> m a
return IOExtensionPoint
result'

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveIOExtensionPointMethod (t :: Symbol) (o :: *) :: * where
    ResolveIOExtensionPointMethod "getExtensionByName" o = IOExtensionPointGetExtensionByNameMethodInfo
    ResolveIOExtensionPointMethod "getExtensions" o = IOExtensionPointGetExtensionsMethodInfo
    ResolveIOExtensionPointMethod "getRequiredType" o = IOExtensionPointGetRequiredTypeMethodInfo
    ResolveIOExtensionPointMethod "setRequiredType" o = IOExtensionPointSetRequiredTypeMethodInfo
    ResolveIOExtensionPointMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif