{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GObject.Structs.ParamSpecPool
(
ParamSpecPool(..) ,
noParamSpecPool ,
#if defined(ENABLE_OVERLOADING)
ResolveParamSpecPoolMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ParamSpecPoolInsertMethodInfo ,
#endif
paramSpecPoolInsert ,
#if defined(ENABLE_OVERLOADING)
ParamSpecPoolListOwnedMethodInfo ,
#endif
paramSpecPoolListOwned ,
#if defined(ENABLE_OVERLOADING)
ParamSpecPoolLookupMethodInfo ,
#endif
paramSpecPoolLookup ,
paramSpecPoolNew ,
#if defined(ENABLE_OVERLOADING)
ParamSpecPoolRemoveMethodInfo ,
#endif
paramSpecPoolRemove ,
) 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
newtype ParamSpecPool = ParamSpecPool (ManagedPtr ParamSpecPool)
deriving (ParamSpecPool -> ParamSpecPool -> Bool
(ParamSpecPool -> ParamSpecPool -> Bool)
-> (ParamSpecPool -> ParamSpecPool -> Bool) -> Eq ParamSpecPool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParamSpecPool -> ParamSpecPool -> Bool
$c/= :: ParamSpecPool -> ParamSpecPool -> Bool
== :: ParamSpecPool -> ParamSpecPool -> Bool
$c== :: ParamSpecPool -> ParamSpecPool -> Bool
Eq)
instance WrappedPtr ParamSpecPool where
wrappedPtrCalloc :: IO (Ptr ParamSpecPool)
wrappedPtrCalloc = Ptr ParamSpecPool -> IO (Ptr ParamSpecPool)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ParamSpecPool
forall a. Ptr a
nullPtr
wrappedPtrCopy :: ParamSpecPool -> IO ParamSpecPool
wrappedPtrCopy = ParamSpecPool -> IO ParamSpecPool
forall (m :: * -> *) a. Monad m => a -> m a
return
wrappedPtrFree :: Maybe (GDestroyNotify ParamSpecPool)
wrappedPtrFree = Maybe (GDestroyNotify ParamSpecPool)
forall a. Maybe a
Nothing
noParamSpecPool :: Maybe ParamSpecPool
noParamSpecPool :: Maybe ParamSpecPool
noParamSpecPool = Maybe ParamSpecPool
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ParamSpecPool
type instance O.AttributeList ParamSpecPool = ParamSpecPoolAttributeList
type ParamSpecPoolAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "g_param_spec_pool_insert" g_param_spec_pool_insert ::
Ptr ParamSpecPool ->
Ptr GParamSpec ->
CGType ->
IO ()
paramSpecPoolInsert ::
(B.CallStack.HasCallStack, MonadIO m) =>
ParamSpecPool
-> GParamSpec
-> GType
-> m ()
paramSpecPoolInsert :: ParamSpecPool -> GParamSpec -> GType -> m ()
paramSpecPoolInsert pool :: ParamSpecPool
pool pspec :: GParamSpec
pspec ownerType :: GType
ownerType = 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 ParamSpecPool
pool' <- ParamSpecPool -> IO (Ptr ParamSpecPool)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ParamSpecPool
pool
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
let ownerType' :: CGType
ownerType' = GType -> CGType
gtypeToCGType GType
ownerType
Ptr ParamSpecPool -> Ptr GParamSpec -> CGType -> IO ()
g_param_spec_pool_insert Ptr ParamSpecPool
pool' Ptr GParamSpec
pspec' CGType
ownerType'
ParamSpecPool -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ParamSpecPool
pool
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ParamSpecPoolInsertMethodInfo
instance (signature ~ (GParamSpec -> GType -> m ()), MonadIO m) => O.MethodInfo ParamSpecPoolInsertMethodInfo ParamSpecPool signature where
overloadedMethod = paramSpecPoolInsert
#endif
foreign import ccall "g_param_spec_pool_list_owned" g_param_spec_pool_list_owned ::
Ptr ParamSpecPool ->
CGType ->
IO (Ptr (GList (Ptr GParamSpec)))
paramSpecPoolListOwned ::
(B.CallStack.HasCallStack, MonadIO m) =>
ParamSpecPool
-> GType
-> m [GParamSpec]
paramSpecPoolListOwned :: ParamSpecPool -> GType -> m [GParamSpec]
paramSpecPoolListOwned pool :: ParamSpecPool
pool ownerType :: GType
ownerType = IO [GParamSpec] -> m [GParamSpec]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [GParamSpec] -> m [GParamSpec])
-> IO [GParamSpec] -> m [GParamSpec]
forall a b. (a -> b) -> a -> b
$ do
Ptr ParamSpecPool
pool' <- ParamSpecPool -> IO (Ptr ParamSpecPool)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ParamSpecPool
pool
let ownerType' :: CGType
ownerType' = GType -> CGType
gtypeToCGType GType
ownerType
Ptr (GList (Ptr GParamSpec))
result <- Ptr ParamSpecPool -> CGType -> IO (Ptr (GList (Ptr GParamSpec)))
g_param_spec_pool_list_owned Ptr ParamSpecPool
pool' CGType
ownerType'
[Ptr GParamSpec]
result' <- Ptr (GList (Ptr GParamSpec)) -> IO [Ptr GParamSpec]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr GParamSpec))
result
[GParamSpec]
result'' <- (Ptr GParamSpec -> IO GParamSpec)
-> [Ptr GParamSpec] -> IO [GParamSpec]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Ptr GParamSpec -> IO GParamSpec
B.GParamSpec.newGParamSpecFromPtr [Ptr GParamSpec]
result'
Ptr (GList (Ptr GParamSpec)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr GParamSpec))
result
ParamSpecPool -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ParamSpecPool
pool
[GParamSpec] -> IO [GParamSpec]
forall (m :: * -> *) a. Monad m => a -> m a
return [GParamSpec]
result''
#if defined(ENABLE_OVERLOADING)
data ParamSpecPoolListOwnedMethodInfo
instance (signature ~ (GType -> m [GParamSpec]), MonadIO m) => O.MethodInfo ParamSpecPoolListOwnedMethodInfo ParamSpecPool signature where
overloadedMethod = paramSpecPoolListOwned
#endif
foreign import ccall "g_param_spec_pool_lookup" g_param_spec_pool_lookup ::
Ptr ParamSpecPool ->
CString ->
CGType ->
CInt ->
IO (Ptr GParamSpec)
paramSpecPoolLookup ::
(B.CallStack.HasCallStack, MonadIO m) =>
ParamSpecPool
-> T.Text
-> GType
-> Bool
-> m GParamSpec
paramSpecPoolLookup :: ParamSpecPool -> Text -> GType -> Bool -> m GParamSpec
paramSpecPoolLookup pool :: ParamSpecPool
pool paramName :: Text
paramName ownerType :: GType
ownerType walkAncestors :: Bool
walkAncestors = IO GParamSpec -> m GParamSpec
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec
forall a b. (a -> b) -> a -> b
$ do
Ptr ParamSpecPool
pool' <- ParamSpecPool -> IO (Ptr ParamSpecPool)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ParamSpecPool
pool
CString
paramName' <- Text -> IO CString
textToCString Text
paramName
let ownerType' :: CGType
ownerType' = GType -> CGType
gtypeToCGType GType
ownerType
let walkAncestors' :: CInt
walkAncestors' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
walkAncestors
Ptr GParamSpec
result <- Ptr ParamSpecPool
-> CString -> CGType -> CInt -> IO (Ptr GParamSpec)
g_param_spec_pool_lookup Ptr ParamSpecPool
pool' CString
paramName' CGType
ownerType' CInt
walkAncestors'
Text -> Ptr GParamSpec -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "paramSpecPoolLookup" Ptr GParamSpec
result
GParamSpec
result' <- Ptr GParamSpec -> IO GParamSpec
B.GParamSpec.newGParamSpecFromPtr Ptr GParamSpec
result
ParamSpecPool -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ParamSpecPool
pool
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
paramName'
GParamSpec -> IO GParamSpec
forall (m :: * -> *) a. Monad m => a -> m a
return GParamSpec
result'
#if defined(ENABLE_OVERLOADING)
data ParamSpecPoolLookupMethodInfo
instance (signature ~ (T.Text -> GType -> Bool -> m GParamSpec), MonadIO m) => O.MethodInfo ParamSpecPoolLookupMethodInfo ParamSpecPool signature where
overloadedMethod = paramSpecPoolLookup
#endif
foreign import ccall "g_param_spec_pool_remove" g_param_spec_pool_remove ::
Ptr ParamSpecPool ->
Ptr GParamSpec ->
IO ()
paramSpecPoolRemove ::
(B.CallStack.HasCallStack, MonadIO m) =>
ParamSpecPool
-> GParamSpec
-> m ()
paramSpecPoolRemove :: ParamSpecPool -> GParamSpec -> m ()
paramSpecPoolRemove pool :: ParamSpecPool
pool pspec :: GParamSpec
pspec = 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 ParamSpecPool
pool' <- ParamSpecPool -> IO (Ptr ParamSpecPool)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr ParamSpecPool
pool
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr ParamSpecPool -> Ptr GParamSpec -> IO ()
g_param_spec_pool_remove Ptr ParamSpecPool
pool' Ptr GParamSpec
pspec'
ParamSpecPool -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr ParamSpecPool
pool
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ParamSpecPoolRemoveMethodInfo
instance (signature ~ (GParamSpec -> m ()), MonadIO m) => O.MethodInfo ParamSpecPoolRemoveMethodInfo ParamSpecPool signature where
overloadedMethod = paramSpecPoolRemove
#endif
foreign import ccall "g_param_spec_pool_new" g_param_spec_pool_new ::
CInt ->
IO (Ptr ParamSpecPool)
paramSpecPoolNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bool
-> m ParamSpecPool
paramSpecPoolNew :: Bool -> m ParamSpecPool
paramSpecPoolNew typePrefixing :: Bool
typePrefixing = IO ParamSpecPool -> m ParamSpecPool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ParamSpecPool -> m ParamSpecPool)
-> IO ParamSpecPool -> m ParamSpecPool
forall a b. (a -> b) -> a -> b
$ do
let typePrefixing' :: CInt
typePrefixing' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
typePrefixing
Ptr ParamSpecPool
result <- CInt -> IO (Ptr ParamSpecPool)
g_param_spec_pool_new CInt
typePrefixing'
Text -> Ptr ParamSpecPool -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "paramSpecPoolNew" Ptr ParamSpecPool
result
ParamSpecPool
result' <- ((ManagedPtr ParamSpecPool -> ParamSpecPool)
-> Ptr ParamSpecPool -> IO ParamSpecPool
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr ParamSpecPool -> ParamSpecPool
ParamSpecPool) Ptr ParamSpecPool
result
ParamSpecPool -> IO ParamSpecPool
forall (m :: * -> *) a. Monad m => a -> m a
return ParamSpecPool
result'
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveParamSpecPoolMethod (t :: Symbol) (o :: *) :: * where
ResolveParamSpecPoolMethod "insert" o = ParamSpecPoolInsertMethodInfo
ResolveParamSpecPoolMethod "listOwned" o = ParamSpecPoolListOwnedMethodInfo
ResolveParamSpecPoolMethod "lookup" o = ParamSpecPoolLookupMethodInfo
ResolveParamSpecPoolMethod "remove" o = ParamSpecPoolRemoveMethodInfo
ResolveParamSpecPoolMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveParamSpecPoolMethod t ParamSpecPool, O.MethodInfo info ParamSpecPool p) => OL.IsLabel t (ParamSpecPool -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif