{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GObject.Structs.ObjectConstructParam
(
ObjectConstructParam(..) ,
newZeroObjectConstructParam ,
noObjectConstructParam ,
#if defined(ENABLE_OVERLOADING)
ResolveObjectConstructParamMethod ,
#endif
clearObjectConstructParamPspec ,
getObjectConstructParamPspec ,
#if defined(ENABLE_OVERLOADING)
objectConstructParam_pspec ,
#endif
setObjectConstructParamPspec ,
clearObjectConstructParamValue ,
getObjectConstructParamValue ,
#if defined(ENABLE_OVERLOADING)
objectConstructParam_value ,
#endif
setObjectConstructParamValue ,
) 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 ObjectConstructParam = ObjectConstructParam (ManagedPtr ObjectConstructParam)
deriving (ObjectConstructParam -> ObjectConstructParam -> Bool
(ObjectConstructParam -> ObjectConstructParam -> Bool)
-> (ObjectConstructParam -> ObjectConstructParam -> Bool)
-> Eq ObjectConstructParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectConstructParam -> ObjectConstructParam -> Bool
$c/= :: ObjectConstructParam -> ObjectConstructParam -> Bool
== :: ObjectConstructParam -> ObjectConstructParam -> Bool
$c== :: ObjectConstructParam -> ObjectConstructParam -> Bool
Eq)
instance WrappedPtr ObjectConstructParam where
wrappedPtrCalloc :: IO (Ptr ObjectConstructParam)
wrappedPtrCalloc = Int -> IO (Ptr ObjectConstructParam)
forall a. Int -> IO (Ptr a)
callocBytes 16
wrappedPtrCopy :: ObjectConstructParam -> IO ObjectConstructParam
wrappedPtrCopy = \p :: ObjectConstructParam
p -> ObjectConstructParam
-> (Ptr ObjectConstructParam -> IO ObjectConstructParam)
-> IO ObjectConstructParam
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ObjectConstructParam
p (Int -> Ptr ObjectConstructParam -> IO (Ptr ObjectConstructParam)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 16 (Ptr ObjectConstructParam -> IO (Ptr ObjectConstructParam))
-> (Ptr ObjectConstructParam -> IO ObjectConstructParam)
-> Ptr ObjectConstructParam
-> IO ObjectConstructParam
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr ObjectConstructParam -> ObjectConstructParam)
-> Ptr ObjectConstructParam -> IO ObjectConstructParam
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr ObjectConstructParam -> ObjectConstructParam
ObjectConstructParam)
wrappedPtrFree :: Maybe (GDestroyNotify ObjectConstructParam)
wrappedPtrFree = GDestroyNotify ObjectConstructParam
-> Maybe (GDestroyNotify ObjectConstructParam)
forall a. a -> Maybe a
Just GDestroyNotify ObjectConstructParam
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free
newZeroObjectConstructParam :: MonadIO m => m ObjectConstructParam
newZeroObjectConstructParam :: m ObjectConstructParam
newZeroObjectConstructParam = IO ObjectConstructParam -> m ObjectConstructParam
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ObjectConstructParam -> m ObjectConstructParam)
-> IO ObjectConstructParam -> m ObjectConstructParam
forall a b. (a -> b) -> a -> b
$ IO (Ptr ObjectConstructParam)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr ObjectConstructParam)
-> (Ptr ObjectConstructParam -> IO ObjectConstructParam)
-> IO ObjectConstructParam
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr ObjectConstructParam -> ObjectConstructParam)
-> Ptr ObjectConstructParam -> IO ObjectConstructParam
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr ObjectConstructParam -> ObjectConstructParam
ObjectConstructParam
instance tag ~ 'AttrSet => Constructible ObjectConstructParam tag where
new :: (ManagedPtr ObjectConstructParam -> ObjectConstructParam)
-> [AttrOp ObjectConstructParam tag] -> m ObjectConstructParam
new _ attrs :: [AttrOp ObjectConstructParam tag]
attrs = do
ObjectConstructParam
o <- m ObjectConstructParam
forall (m :: * -> *). MonadIO m => m ObjectConstructParam
newZeroObjectConstructParam
ObjectConstructParam
-> [AttrOp ObjectConstructParam 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set ObjectConstructParam
o [AttrOp ObjectConstructParam tag]
[AttrOp ObjectConstructParam 'AttrSet]
attrs
ObjectConstructParam -> m ObjectConstructParam
forall (m :: * -> *) a. Monad m => a -> m a
return ObjectConstructParam
o
noObjectConstructParam :: Maybe ObjectConstructParam
noObjectConstructParam :: Maybe ObjectConstructParam
noObjectConstructParam = Maybe ObjectConstructParam
forall a. Maybe a
Nothing
getObjectConstructParamPspec :: MonadIO m => ObjectConstructParam -> m (Maybe GParamSpec)
getObjectConstructParamPspec :: ObjectConstructParam -> m (Maybe GParamSpec)
getObjectConstructParamPspec s :: ObjectConstructParam
s = IO (Maybe GParamSpec) -> m (Maybe GParamSpec)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GParamSpec) -> m (Maybe GParamSpec))
-> IO (Maybe GParamSpec) -> m (Maybe GParamSpec)
forall a b. (a -> b) -> a -> b
$ ObjectConstructParam
-> (Ptr ObjectConstructParam -> IO (Maybe GParamSpec))
-> IO (Maybe GParamSpec)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ObjectConstructParam
s ((Ptr ObjectConstructParam -> IO (Maybe GParamSpec))
-> IO (Maybe GParamSpec))
-> (Ptr ObjectConstructParam -> IO (Maybe GParamSpec))
-> IO (Maybe GParamSpec)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ObjectConstructParam
ptr -> do
Ptr GParamSpec
val <- Ptr (Ptr GParamSpec) -> IO (Ptr GParamSpec)
forall a. Storable a => Ptr a -> IO a
peek (Ptr ObjectConstructParam
ptr Ptr ObjectConstructParam -> Int -> Ptr (Ptr GParamSpec)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO (Ptr GParamSpec)
Maybe GParamSpec
result <- Ptr GParamSpec
-> (Ptr GParamSpec -> IO GParamSpec) -> IO (Maybe GParamSpec)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr GParamSpec
val ((Ptr GParamSpec -> IO GParamSpec) -> IO (Maybe GParamSpec))
-> (Ptr GParamSpec -> IO GParamSpec) -> IO (Maybe GParamSpec)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr GParamSpec
val' -> do
GParamSpec
val'' <- Ptr GParamSpec -> IO GParamSpec
B.GParamSpec.newGParamSpecFromPtr Ptr GParamSpec
val'
GParamSpec -> IO GParamSpec
forall (m :: * -> *) a. Monad m => a -> m a
return GParamSpec
val''
Maybe GParamSpec -> IO (Maybe GParamSpec)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GParamSpec
result
setObjectConstructParamPspec :: MonadIO m => ObjectConstructParam -> Ptr GParamSpec -> m ()
setObjectConstructParamPspec :: ObjectConstructParam -> Ptr GParamSpec -> m ()
setObjectConstructParamPspec s :: ObjectConstructParam
s val :: Ptr GParamSpec
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ObjectConstructParam
-> (Ptr ObjectConstructParam -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ObjectConstructParam
s ((Ptr ObjectConstructParam -> IO ()) -> IO ())
-> (Ptr ObjectConstructParam -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ObjectConstructParam
ptr -> do
Ptr (Ptr GParamSpec) -> Ptr GParamSpec -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ObjectConstructParam
ptr Ptr ObjectConstructParam -> Int -> Ptr (Ptr GParamSpec)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Ptr GParamSpec
val :: Ptr GParamSpec)
clearObjectConstructParamPspec :: MonadIO m => ObjectConstructParam -> m ()
clearObjectConstructParamPspec :: ObjectConstructParam -> m ()
clearObjectConstructParamPspec s :: ObjectConstructParam
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ObjectConstructParam
-> (Ptr ObjectConstructParam -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ObjectConstructParam
s ((Ptr ObjectConstructParam -> IO ()) -> IO ())
-> (Ptr ObjectConstructParam -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ObjectConstructParam
ptr -> do
Ptr (Ptr GParamSpec) -> Ptr GParamSpec -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ObjectConstructParam
ptr Ptr ObjectConstructParam -> Int -> Ptr (Ptr GParamSpec)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Ptr GParamSpec
forall a. Ptr a
FP.nullPtr :: Ptr GParamSpec)
#if defined(ENABLE_OVERLOADING)
data ObjectConstructParamPspecFieldInfo
instance AttrInfo ObjectConstructParamPspecFieldInfo where
type AttrBaseTypeConstraint ObjectConstructParamPspecFieldInfo = (~) ObjectConstructParam
type AttrAllowedOps ObjectConstructParamPspecFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint ObjectConstructParamPspecFieldInfo = (~) (Ptr GParamSpec)
type AttrTransferTypeConstraint ObjectConstructParamPspecFieldInfo = (~)(Ptr GParamSpec)
type AttrTransferType ObjectConstructParamPspecFieldInfo = (Ptr GParamSpec)
type AttrGetType ObjectConstructParamPspecFieldInfo = Maybe GParamSpec
type AttrLabel ObjectConstructParamPspecFieldInfo = "pspec"
type AttrOrigin ObjectConstructParamPspecFieldInfo = ObjectConstructParam
attrGet = getObjectConstructParamPspec
attrSet = setObjectConstructParamPspec
attrConstruct = undefined
attrClear = clearObjectConstructParamPspec
attrTransfer _ v = do
return v
objectConstructParam_pspec :: AttrLabelProxy "pspec"
objectConstructParam_pspec = AttrLabelProxy
#endif
getObjectConstructParamValue :: MonadIO m => ObjectConstructParam -> m (Maybe GValue)
getObjectConstructParamValue :: ObjectConstructParam -> m (Maybe GValue)
getObjectConstructParamValue s :: ObjectConstructParam
s = IO (Maybe GValue) -> m (Maybe GValue)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GValue) -> m (Maybe GValue))
-> IO (Maybe GValue) -> m (Maybe GValue)
forall a b. (a -> b) -> a -> b
$ ObjectConstructParam
-> (Ptr ObjectConstructParam -> IO (Maybe GValue))
-> IO (Maybe GValue)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ObjectConstructParam
s ((Ptr ObjectConstructParam -> IO (Maybe GValue))
-> IO (Maybe GValue))
-> (Ptr ObjectConstructParam -> IO (Maybe GValue))
-> IO (Maybe GValue)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ObjectConstructParam
ptr -> do
Ptr GValue
val <- Ptr (Ptr GValue) -> IO (Ptr GValue)
forall a. Storable a => Ptr a -> IO a
peek (Ptr ObjectConstructParam
ptr Ptr ObjectConstructParam -> Int -> Ptr (Ptr GValue)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO (Ptr GValue)
Maybe GValue
result <- Ptr GValue -> (Ptr GValue -> IO GValue) -> IO (Maybe GValue)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr GValue
val ((Ptr GValue -> IO GValue) -> IO (Maybe GValue))
-> (Ptr GValue -> IO GValue) -> IO (Maybe GValue)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr GValue
val' -> do
GValue
val'' <- ((ManagedPtr GValue -> GValue) -> Ptr GValue -> IO GValue
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr GValue -> GValue
GValue) Ptr GValue
val'
GValue -> IO GValue
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
val''
Maybe GValue -> IO (Maybe GValue)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GValue
result
setObjectConstructParamValue :: MonadIO m => ObjectConstructParam -> Ptr GValue -> m ()
setObjectConstructParamValue :: ObjectConstructParam -> Ptr GValue -> m ()
setObjectConstructParamValue s :: ObjectConstructParam
s val :: Ptr GValue
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ObjectConstructParam
-> (Ptr ObjectConstructParam -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ObjectConstructParam
s ((Ptr ObjectConstructParam -> IO ()) -> IO ())
-> (Ptr ObjectConstructParam -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ObjectConstructParam
ptr -> do
Ptr (Ptr GValue) -> Ptr GValue -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ObjectConstructParam
ptr Ptr ObjectConstructParam -> Int -> Ptr (Ptr GValue)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Ptr GValue
val :: Ptr GValue)
clearObjectConstructParamValue :: MonadIO m => ObjectConstructParam -> m ()
clearObjectConstructParamValue :: ObjectConstructParam -> m ()
clearObjectConstructParamValue s :: ObjectConstructParam
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ObjectConstructParam
-> (Ptr ObjectConstructParam -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr ObjectConstructParam
s ((Ptr ObjectConstructParam -> IO ()) -> IO ())
-> (Ptr ObjectConstructParam -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr ObjectConstructParam
ptr -> do
Ptr (Ptr GValue) -> Ptr GValue -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ObjectConstructParam
ptr Ptr ObjectConstructParam -> Int -> Ptr (Ptr GValue)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Ptr GValue
forall a. Ptr a
FP.nullPtr :: Ptr GValue)
#if defined(ENABLE_OVERLOADING)
data ObjectConstructParamValueFieldInfo
instance AttrInfo ObjectConstructParamValueFieldInfo where
type AttrBaseTypeConstraint ObjectConstructParamValueFieldInfo = (~) ObjectConstructParam
type AttrAllowedOps ObjectConstructParamValueFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint ObjectConstructParamValueFieldInfo = (~) (Ptr GValue)
type AttrTransferTypeConstraint ObjectConstructParamValueFieldInfo = (~)(Ptr GValue)
type AttrTransferType ObjectConstructParamValueFieldInfo = (Ptr GValue)
type AttrGetType ObjectConstructParamValueFieldInfo = Maybe GValue
type AttrLabel ObjectConstructParamValueFieldInfo = "value"
type AttrOrigin ObjectConstructParamValueFieldInfo = ObjectConstructParam
attrGet = getObjectConstructParamValue
attrSet = setObjectConstructParamValue
attrConstruct = undefined
attrClear = clearObjectConstructParamValue
attrTransfer _ v = do
return v
objectConstructParam_value :: AttrLabelProxy "value"
objectConstructParam_value = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ObjectConstructParam
type instance O.AttributeList ObjectConstructParam = ObjectConstructParamAttributeList
type ObjectConstructParamAttributeList = ('[ '("pspec", ObjectConstructParamPspecFieldInfo), '("value", ObjectConstructParamValueFieldInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveObjectConstructParamMethod (t :: Symbol) (o :: *) :: * where
ResolveObjectConstructParamMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveObjectConstructParamMethod t ObjectConstructParam, O.MethodInfo info ObjectConstructParam p) => OL.IsLabel t (ObjectConstructParam -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif