{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Atk.Structs.PropertyValues
(
PropertyValues(..) ,
newZeroPropertyValues ,
noPropertyValues ,
#if defined(ENABLE_OVERLOADING)
ResolvePropertyValuesMethod ,
#endif
getPropertyValuesNewValue ,
#if defined(ENABLE_OVERLOADING)
propertyValues_newValue ,
#endif
getPropertyValuesOldValue ,
#if defined(ENABLE_OVERLOADING)
propertyValues_oldValue ,
#endif
clearPropertyValuesPropertyName ,
getPropertyValuesPropertyName ,
#if defined(ENABLE_OVERLOADING)
propertyValues_propertyName ,
#endif
setPropertyValuesPropertyName ,
) 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 PropertyValues = PropertyValues (ManagedPtr PropertyValues)
deriving (PropertyValues -> PropertyValues -> Bool
(PropertyValues -> PropertyValues -> Bool)
-> (PropertyValues -> PropertyValues -> Bool) -> Eq PropertyValues
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PropertyValues -> PropertyValues -> Bool
$c/= :: PropertyValues -> PropertyValues -> Bool
== :: PropertyValues -> PropertyValues -> Bool
$c== :: PropertyValues -> PropertyValues -> Bool
Eq)
instance WrappedPtr PropertyValues where
wrappedPtrCalloc :: IO (Ptr PropertyValues)
wrappedPtrCalloc = Int -> IO (Ptr PropertyValues)
forall a. Int -> IO (Ptr a)
callocBytes 56
wrappedPtrCopy :: PropertyValues -> IO PropertyValues
wrappedPtrCopy = \p :: PropertyValues
p -> PropertyValues
-> (Ptr PropertyValues -> IO PropertyValues) -> IO PropertyValues
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PropertyValues
p (Int -> Ptr PropertyValues -> IO (Ptr PropertyValues)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 56 (Ptr PropertyValues -> IO (Ptr PropertyValues))
-> (Ptr PropertyValues -> IO PropertyValues)
-> Ptr PropertyValues
-> IO PropertyValues
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr PropertyValues -> PropertyValues)
-> Ptr PropertyValues -> IO PropertyValues
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr PropertyValues -> PropertyValues
PropertyValues)
wrappedPtrFree :: Maybe (GDestroyNotify PropertyValues)
wrappedPtrFree = GDestroyNotify PropertyValues
-> Maybe (GDestroyNotify PropertyValues)
forall a. a -> Maybe a
Just GDestroyNotify PropertyValues
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free
newZeroPropertyValues :: MonadIO m => m PropertyValues
newZeroPropertyValues :: m PropertyValues
newZeroPropertyValues = IO PropertyValues -> m PropertyValues
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PropertyValues -> m PropertyValues)
-> IO PropertyValues -> m PropertyValues
forall a b. (a -> b) -> a -> b
$ IO (Ptr PropertyValues)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr PropertyValues)
-> (Ptr PropertyValues -> IO PropertyValues) -> IO PropertyValues
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr PropertyValues -> PropertyValues)
-> Ptr PropertyValues -> IO PropertyValues
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr PropertyValues -> PropertyValues
PropertyValues
instance tag ~ 'AttrSet => Constructible PropertyValues tag where
new :: (ManagedPtr PropertyValues -> PropertyValues)
-> [AttrOp PropertyValues tag] -> m PropertyValues
new _ attrs :: [AttrOp PropertyValues tag]
attrs = do
PropertyValues
o <- m PropertyValues
forall (m :: * -> *). MonadIO m => m PropertyValues
newZeroPropertyValues
PropertyValues -> [AttrOp PropertyValues 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set PropertyValues
o [AttrOp PropertyValues tag]
[AttrOp PropertyValues 'AttrSet]
attrs
PropertyValues -> m PropertyValues
forall (m :: * -> *) a. Monad m => a -> m a
return PropertyValues
o
noPropertyValues :: Maybe PropertyValues
noPropertyValues :: Maybe PropertyValues
noPropertyValues = Maybe PropertyValues
forall a. Maybe a
Nothing
getPropertyValuesPropertyName :: MonadIO m => PropertyValues -> m (Maybe T.Text)
getPropertyValuesPropertyName :: PropertyValues -> m (Maybe Text)
getPropertyValuesPropertyName s :: PropertyValues
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ PropertyValues
-> (Ptr PropertyValues -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PropertyValues
s ((Ptr PropertyValues -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr PropertyValues -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr PropertyValues
ptr -> do
CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr PropertyValues
ptr Ptr PropertyValues -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO CString
Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \val' :: CString
val' -> do
Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result
setPropertyValuesPropertyName :: MonadIO m => PropertyValues -> CString -> m ()
setPropertyValuesPropertyName :: PropertyValues -> CString -> m ()
setPropertyValuesPropertyName s :: PropertyValues
s val :: CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ PropertyValues -> (Ptr PropertyValues -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PropertyValues
s ((Ptr PropertyValues -> IO ()) -> IO ())
-> (Ptr PropertyValues -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr PropertyValues
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PropertyValues
ptr Ptr PropertyValues -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (CString
val :: CString)
clearPropertyValuesPropertyName :: MonadIO m => PropertyValues -> m ()
clearPropertyValuesPropertyName :: PropertyValues -> m ()
clearPropertyValuesPropertyName s :: PropertyValues
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ PropertyValues -> (Ptr PropertyValues -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PropertyValues
s ((Ptr PropertyValues -> IO ()) -> IO ())
-> (Ptr PropertyValues -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr PropertyValues
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PropertyValues
ptr Ptr PropertyValues -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (CString
forall a. Ptr a
FP.nullPtr :: CString)
#if defined(ENABLE_OVERLOADING)
data PropertyValuesPropertyNameFieldInfo
instance AttrInfo PropertyValuesPropertyNameFieldInfo where
type AttrBaseTypeConstraint PropertyValuesPropertyNameFieldInfo = (~) PropertyValues
type AttrAllowedOps PropertyValuesPropertyNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint PropertyValuesPropertyNameFieldInfo = (~) CString
type AttrTransferTypeConstraint PropertyValuesPropertyNameFieldInfo = (~)CString
type AttrTransferType PropertyValuesPropertyNameFieldInfo = CString
type AttrGetType PropertyValuesPropertyNameFieldInfo = Maybe T.Text
type AttrLabel PropertyValuesPropertyNameFieldInfo = "property_name"
type AttrOrigin PropertyValuesPropertyNameFieldInfo = PropertyValues
attrGet = getPropertyValuesPropertyName
attrSet = setPropertyValuesPropertyName
attrConstruct = undefined
attrClear = clearPropertyValuesPropertyName
attrTransfer _ v = do
return v
propertyValues_propertyName :: AttrLabelProxy "propertyName"
propertyValues_propertyName = AttrLabelProxy
#endif
getPropertyValuesOldValue :: MonadIO m => PropertyValues -> m GValue
getPropertyValuesOldValue :: PropertyValues -> m GValue
getPropertyValuesOldValue s :: PropertyValues
s = IO GValue -> m GValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GValue -> m GValue) -> IO GValue -> m GValue
forall a b. (a -> b) -> a -> b
$ PropertyValues -> (Ptr PropertyValues -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PropertyValues
s ((Ptr PropertyValues -> IO GValue) -> IO GValue)
-> (Ptr PropertyValues -> IO GValue) -> IO GValue
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr PropertyValues
ptr -> do
let val :: Ptr GValue
val = Ptr PropertyValues
ptr Ptr PropertyValues -> Int -> Ptr GValue
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: (Ptr GValue)
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'
#if defined(ENABLE_OVERLOADING)
data PropertyValuesOldValueFieldInfo
instance AttrInfo PropertyValuesOldValueFieldInfo where
type AttrBaseTypeConstraint PropertyValuesOldValueFieldInfo = (~) PropertyValues
type AttrAllowedOps PropertyValuesOldValueFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint PropertyValuesOldValueFieldInfo = (~) (Ptr GValue)
type AttrTransferTypeConstraint PropertyValuesOldValueFieldInfo = (~)(Ptr GValue)
type AttrTransferType PropertyValuesOldValueFieldInfo = (Ptr GValue)
type AttrGetType PropertyValuesOldValueFieldInfo = GValue
type AttrLabel PropertyValuesOldValueFieldInfo = "old_value"
type AttrOrigin PropertyValuesOldValueFieldInfo = PropertyValues
attrGet = getPropertyValuesOldValue
attrSet = undefined
attrConstruct = undefined
attrClear = undefined
attrTransfer = undefined
propertyValues_oldValue :: AttrLabelProxy "oldValue"
propertyValues_oldValue = AttrLabelProxy
#endif
getPropertyValuesNewValue :: MonadIO m => PropertyValues -> m GValue
getPropertyValuesNewValue :: PropertyValues -> m GValue
getPropertyValuesNewValue s :: PropertyValues
s = IO GValue -> m GValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GValue -> m GValue) -> IO GValue -> m GValue
forall a b. (a -> b) -> a -> b
$ PropertyValues -> (Ptr PropertyValues -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PropertyValues
s ((Ptr PropertyValues -> IO GValue) -> IO GValue)
-> (Ptr PropertyValues -> IO GValue) -> IO GValue
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr PropertyValues
ptr -> do
let val :: Ptr GValue
val = Ptr PropertyValues
ptr Ptr PropertyValues -> Int -> Ptr GValue
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: (Ptr GValue)
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'
#if defined(ENABLE_OVERLOADING)
data PropertyValuesNewValueFieldInfo
instance AttrInfo PropertyValuesNewValueFieldInfo where
type AttrBaseTypeConstraint PropertyValuesNewValueFieldInfo = (~) PropertyValues
type AttrAllowedOps PropertyValuesNewValueFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint PropertyValuesNewValueFieldInfo = (~) (Ptr GValue)
type AttrTransferTypeConstraint PropertyValuesNewValueFieldInfo = (~)(Ptr GValue)
type AttrTransferType PropertyValuesNewValueFieldInfo = (Ptr GValue)
type AttrGetType PropertyValuesNewValueFieldInfo = GValue
type AttrLabel PropertyValuesNewValueFieldInfo = "new_value"
type AttrOrigin PropertyValuesNewValueFieldInfo = PropertyValues
attrGet = getPropertyValuesNewValue
attrSet = undefined
attrConstruct = undefined
attrClear = undefined
attrTransfer = undefined
propertyValues_newValue :: AttrLabelProxy "newValue"
propertyValues_newValue = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PropertyValues
type instance O.AttributeList PropertyValues = PropertyValuesAttributeList
type PropertyValuesAttributeList = ('[ '("propertyName", PropertyValuesPropertyNameFieldInfo), '("oldValue", PropertyValuesOldValueFieldInfo), '("newValue", PropertyValuesNewValueFieldInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolvePropertyValuesMethod (t :: Symbol) (o :: *) :: * where
ResolvePropertyValuesMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolvePropertyValuesMethod t PropertyValues, O.MethodInfo info PropertyValues p) => OL.IsLabel t (PropertyValues -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif