{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Structs.IOExtensionPoint
(
IOExtensionPoint(..) ,
#if defined(ENABLE_OVERLOADING)
ResolveIOExtensionPointMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
IOExtensionPointGetExtensionByNameMethodInfo,
#endif
iOExtensionPointGetExtensionByName ,
#if defined(ENABLE_OVERLOADING)
IOExtensionPointGetExtensionsMethodInfo ,
#endif
iOExtensionPointGetExtensions ,
#if defined(ENABLE_OVERLOADING)
IOExtensionPointGetRequiredTypeMethodInfo,
#endif
iOExtensionPointGetRequiredType ,
iOExtensionPointImplement ,
iOExtensionPointLookup ,
iOExtensionPointRegister ,
#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.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.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 {-# SOURCE #-} qualified GI.Gio.Structs.IOExtension as Gio.IOExtension
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
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
foreign import ccall "g_io_extension_point_get_extension_by_name" g_io_extension_point_get_extension_by_name ::
Ptr IOExtensionPoint ->
CString ->
IO (Ptr Gio.IOExtension.IOExtension)
iOExtensionPointGetExtensionByName ::
(B.CallStack.HasCallStack, MonadIO m) =>
IOExtensionPoint
-> T.Text
-> m Gio.IOExtension.IOExtension
iOExtensionPointGetExtensionByName :: 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.MethodInfo IOExtensionPointGetExtensionByNameMethodInfo IOExtensionPoint signature where
overloadedMethod = iOExtensionPointGetExtensionByName
#endif
foreign import ccall "g_io_extension_point_get_extensions" g_io_extension_point_get_extensions ::
Ptr IOExtensionPoint ->
IO (Ptr (GList (Ptr Gio.IOExtension.IOExtension)))
iOExtensionPointGetExtensions ::
(B.CallStack.HasCallStack, MonadIO m) =>
IOExtensionPoint
-> m [Gio.IOExtension.IOExtension]
iOExtensionPointGetExtensions :: 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.MethodInfo IOExtensionPointGetExtensionsMethodInfo IOExtensionPoint signature where
overloadedMethod = iOExtensionPointGetExtensions
#endif
foreign import ccall "g_io_extension_point_get_required_type" g_io_extension_point_get_required_type ::
Ptr IOExtensionPoint ->
IO CGType
iOExtensionPointGetRequiredType ::
(B.CallStack.HasCallStack, MonadIO m) =>
IOExtensionPoint
-> m GType
iOExtensionPointGetRequiredType :: 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.MethodInfo IOExtensionPointGetRequiredTypeMethodInfo IOExtensionPoint signature where
overloadedMethod = iOExtensionPointGetRequiredType
#endif
foreign import ccall "g_io_extension_point_set_required_type" g_io_extension_point_set_required_type ::
Ptr IOExtensionPoint ->
CGType ->
IO ()
iOExtensionPointSetRequiredType ::
(B.CallStack.HasCallStack, MonadIO m) =>
IOExtensionPoint
-> GType
-> m ()
iOExtensionPointSetRequiredType :: 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.MethodInfo IOExtensionPointSetRequiredTypeMethodInfo IOExtensionPoint signature where
overloadedMethod = iOExtensionPointSetRequiredType
#endif
foreign import ccall "g_io_extension_point_implement" g_io_extension_point_implement ::
CString ->
CGType ->
CString ->
Int32 ->
IO (Ptr Gio.IOExtension.IOExtension)
iOExtensionPointImplement ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> GType
-> T.Text
-> Int32
-> m Gio.IOExtension.IOExtension
iOExtensionPointImplement :: 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
foreign import ccall "g_io_extension_point_lookup" g_io_extension_point_lookup ::
CString ->
IO (Ptr IOExtensionPoint)
iOExtensionPointLookup ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m IOExtensionPoint
iOExtensionPointLookup :: 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
foreign import ccall "g_io_extension_point_register" g_io_extension_point_register ::
CString ->
IO (Ptr IOExtensionPoint)
iOExtensionPointRegister ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m IOExtensionPoint
iOExtensionPointRegister :: 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.MethodInfo 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
#endif