{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Structs.RcProperty
(
RcProperty(..) ,
newZeroRcProperty ,
#if defined(ENABLE_OVERLOADING)
ResolveRcPropertyMethod ,
#endif
rcPropertyParseBorder ,
rcPropertyParseColor ,
rcPropertyParseEnum ,
rcPropertyParseFlags ,
rcPropertyParseRequisition ,
clearRcPropertyOrigin ,
getRcPropertyOrigin ,
#if defined(ENABLE_OVERLOADING)
rcProperty_origin ,
#endif
setRcPropertyOrigin ,
getRcPropertyPropertyName ,
#if defined(ENABLE_OVERLOADING)
rcProperty_propertyName ,
#endif
setRcPropertyPropertyName ,
getRcPropertyTypeName ,
#if defined(ENABLE_OVERLOADING)
rcProperty_typeName ,
#endif
setRcPropertyTypeName ,
clearRcPropertyValue ,
getRcPropertyValue ,
#if defined(ENABLE_OVERLOADING)
rcProperty_value ,
#endif
setRcPropertyValue ,
) 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.GHashTable as B.GHT
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.Kind as DK
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 qualified GI.GLib.Structs.String as GLib.String
newtype RcProperty = RcProperty (SP.ManagedPtr RcProperty)
deriving (RcProperty -> RcProperty -> Bool
(RcProperty -> RcProperty -> Bool)
-> (RcProperty -> RcProperty -> Bool) -> Eq RcProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RcProperty -> RcProperty -> Bool
== :: RcProperty -> RcProperty -> Bool
$c/= :: RcProperty -> RcProperty -> Bool
/= :: RcProperty -> RcProperty -> Bool
Eq)
instance SP.ManagedPtrNewtype RcProperty where
toManagedPtr :: RcProperty -> ManagedPtr RcProperty
toManagedPtr (RcProperty ManagedPtr RcProperty
p) = ManagedPtr RcProperty
p
instance BoxedPtr RcProperty where
boxedPtrCopy :: RcProperty -> IO RcProperty
boxedPtrCopy = \RcProperty
p -> RcProperty -> (Ptr RcProperty -> IO RcProperty) -> IO RcProperty
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr RcProperty
p (Int -> Ptr RcProperty -> IO (Ptr RcProperty)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
40 (Ptr RcProperty -> IO (Ptr RcProperty))
-> (Ptr RcProperty -> IO RcProperty)
-> Ptr RcProperty
-> IO RcProperty
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr RcProperty -> RcProperty)
-> Ptr RcProperty -> IO RcProperty
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr RcProperty -> RcProperty
RcProperty)
boxedPtrFree :: RcProperty -> IO ()
boxedPtrFree = \RcProperty
x -> RcProperty -> (Ptr RcProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr RcProperty
x Ptr RcProperty -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr RcProperty where
boxedPtrCalloc :: IO (Ptr RcProperty)
boxedPtrCalloc = Int -> IO (Ptr RcProperty)
forall a. Int -> IO (Ptr a)
callocBytes Int
40
newZeroRcProperty :: MonadIO m => m RcProperty
newZeroRcProperty :: forall (m :: * -> *). MonadIO m => m RcProperty
newZeroRcProperty = IO RcProperty -> m RcProperty
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RcProperty -> m RcProperty) -> IO RcProperty -> m RcProperty
forall a b. (a -> b) -> a -> b
$ IO (Ptr RcProperty)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr RcProperty)
-> (Ptr RcProperty -> IO RcProperty) -> IO RcProperty
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr RcProperty -> RcProperty)
-> Ptr RcProperty -> IO RcProperty
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr RcProperty -> RcProperty
RcProperty
instance tag ~ 'AttrSet => Constructible RcProperty tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr RcProperty -> RcProperty)
-> [AttrOp RcProperty tag] -> m RcProperty
new ManagedPtr RcProperty -> RcProperty
_ [AttrOp RcProperty tag]
attrs = do
RcProperty
o <- m RcProperty
forall (m :: * -> *). MonadIO m => m RcProperty
newZeroRcProperty
RcProperty -> [AttrOp RcProperty 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set RcProperty
o [AttrOp RcProperty tag]
[AttrOp RcProperty 'AttrSet]
attrs
RcProperty -> m RcProperty
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return RcProperty
o
getRcPropertyTypeName :: MonadIO m => RcProperty -> m Word32
getRcPropertyTypeName :: forall (m :: * -> *). MonadIO m => RcProperty -> m Word32
getRcPropertyTypeName RcProperty
s = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ RcProperty -> (Ptr RcProperty -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RcProperty
s ((Ptr RcProperty -> IO Word32) -> IO Word32)
-> (Ptr RcProperty -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr RcProperty
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr RcProperty
ptr Ptr RcProperty -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Word32
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setRcPropertyTypeName :: MonadIO m => RcProperty -> Word32 -> m ()
setRcPropertyTypeName :: forall (m :: * -> *). MonadIO m => RcProperty -> Word32 -> m ()
setRcPropertyTypeName RcProperty
s Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ RcProperty -> (Ptr RcProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RcProperty
s ((Ptr RcProperty -> IO ()) -> IO ())
-> (Ptr RcProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr RcProperty
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RcProperty
ptr Ptr RcProperty -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data RcPropertyTypeNameFieldInfo
instance AttrInfo RcPropertyTypeNameFieldInfo where
type AttrBaseTypeConstraint RcPropertyTypeNameFieldInfo = (~) RcProperty
type AttrAllowedOps RcPropertyTypeNameFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint RcPropertyTypeNameFieldInfo = (~) Word32
type AttrTransferTypeConstraint RcPropertyTypeNameFieldInfo = (~)Word32
type AttrTransferType RcPropertyTypeNameFieldInfo = Word32
type AttrGetType RcPropertyTypeNameFieldInfo = Word32
type AttrLabel RcPropertyTypeNameFieldInfo = "type_name"
type AttrOrigin RcPropertyTypeNameFieldInfo = RcProperty
attrGet = getRcPropertyTypeName
attrSet = setRcPropertyTypeName
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RcProperty.typeName"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-RcProperty.html#g:attr:typeName"
})
rcProperty_typeName :: AttrLabelProxy "typeName"
rcProperty_typeName = AttrLabelProxy
#endif
getRcPropertyPropertyName :: MonadIO m => RcProperty -> m Word32
getRcPropertyPropertyName :: forall (m :: * -> *). MonadIO m => RcProperty -> m Word32
getRcPropertyPropertyName RcProperty
s = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ RcProperty -> (Ptr RcProperty -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RcProperty
s ((Ptr RcProperty -> IO Word32) -> IO Word32)
-> (Ptr RcProperty -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr RcProperty
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr RcProperty
ptr Ptr RcProperty -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) :: IO Word32
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setRcPropertyPropertyName :: MonadIO m => RcProperty -> Word32 -> m ()
setRcPropertyPropertyName :: forall (m :: * -> *). MonadIO m => RcProperty -> Word32 -> m ()
setRcPropertyPropertyName RcProperty
s Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ RcProperty -> (Ptr RcProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RcProperty
s ((Ptr RcProperty -> IO ()) -> IO ())
-> (Ptr RcProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr RcProperty
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RcProperty
ptr Ptr RcProperty -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data RcPropertyPropertyNameFieldInfo
instance AttrInfo RcPropertyPropertyNameFieldInfo where
type AttrBaseTypeConstraint RcPropertyPropertyNameFieldInfo = (~) RcProperty
type AttrAllowedOps RcPropertyPropertyNameFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint RcPropertyPropertyNameFieldInfo = (~) Word32
type AttrTransferTypeConstraint RcPropertyPropertyNameFieldInfo = (~)Word32
type AttrTransferType RcPropertyPropertyNameFieldInfo = Word32
type AttrGetType RcPropertyPropertyNameFieldInfo = Word32
type AttrLabel RcPropertyPropertyNameFieldInfo = "property_name"
type AttrOrigin RcPropertyPropertyNameFieldInfo = RcProperty
attrGet = getRcPropertyPropertyName
attrSet = setRcPropertyPropertyName
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RcProperty.propertyName"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-RcProperty.html#g:attr:propertyName"
})
rcProperty_propertyName :: AttrLabelProxy "propertyName"
rcProperty_propertyName = AttrLabelProxy
#endif
getRcPropertyOrigin :: MonadIO m => RcProperty -> m (Maybe T.Text)
getRcPropertyOrigin :: forall (m :: * -> *). MonadIO m => RcProperty -> m (Maybe Text)
getRcPropertyOrigin RcProperty
s = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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
$ RcProperty
-> (Ptr RcProperty -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RcProperty
s ((Ptr RcProperty -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr RcProperty -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr RcProperty
ptr -> do
CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr RcProperty
ptr Ptr RcProperty -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: 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
$ \CString
val' -> do
Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result
setRcPropertyOrigin :: MonadIO m => RcProperty -> CString -> m ()
setRcPropertyOrigin :: forall (m :: * -> *). MonadIO m => RcProperty -> CString -> m ()
setRcPropertyOrigin RcProperty
s CString
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ RcProperty -> (Ptr RcProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RcProperty
s ((Ptr RcProperty -> IO ()) -> IO ())
-> (Ptr RcProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr RcProperty
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RcProperty
ptr Ptr RcProperty -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
val :: CString)
clearRcPropertyOrigin :: MonadIO m => RcProperty -> m ()
clearRcPropertyOrigin :: forall (m :: * -> *). MonadIO m => RcProperty -> m ()
clearRcPropertyOrigin RcProperty
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ RcProperty -> (Ptr RcProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RcProperty
s ((Ptr RcProperty -> IO ()) -> IO ())
-> (Ptr RcProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr RcProperty
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RcProperty
ptr Ptr RcProperty -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
forall a. Ptr a
FP.nullPtr :: CString)
#if defined(ENABLE_OVERLOADING)
data RcPropertyOriginFieldInfo
instance AttrInfo RcPropertyOriginFieldInfo where
type AttrBaseTypeConstraint RcPropertyOriginFieldInfo = (~) RcProperty
type AttrAllowedOps RcPropertyOriginFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint RcPropertyOriginFieldInfo = (~) CString
type AttrTransferTypeConstraint RcPropertyOriginFieldInfo = (~)CString
type AttrTransferType RcPropertyOriginFieldInfo = CString
type AttrGetType RcPropertyOriginFieldInfo = Maybe T.Text
type AttrLabel RcPropertyOriginFieldInfo = "origin"
type AttrOrigin RcPropertyOriginFieldInfo = RcProperty
attrGet = getRcPropertyOrigin
attrSet = setRcPropertyOrigin
attrConstruct = undefined
attrClear = clearRcPropertyOrigin
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RcProperty.origin"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-RcProperty.html#g:attr:origin"
})
rcProperty_origin :: AttrLabelProxy "origin"
rcProperty_origin = AttrLabelProxy
#endif
getRcPropertyValue :: MonadIO m => RcProperty -> m (Maybe GValue)
getRcPropertyValue :: forall (m :: * -> *). MonadIO m => RcProperty -> m (Maybe GValue)
getRcPropertyValue RcProperty
s = IO (Maybe GValue) -> m (Maybe GValue)
forall a. IO a -> m a
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
$ RcProperty
-> (Ptr RcProperty -> IO (Maybe GValue)) -> IO (Maybe GValue)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RcProperty
s ((Ptr RcProperty -> IO (Maybe GValue)) -> IO (Maybe GValue))
-> (Ptr RcProperty -> IO (Maybe GValue)) -> IO (Maybe GValue)
forall a b. (a -> b) -> a -> b
$ \Ptr RcProperty
ptr -> do
Ptr GValue
val <- Ptr (Ptr GValue) -> IO (Ptr GValue)
forall a. Storable a => Ptr a -> IO a
peek (Ptr RcProperty
ptr Ptr RcProperty -> Int -> Ptr (Ptr GValue)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: 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
$ \Ptr GValue
val' -> do
GValue
val'' <- Ptr GValue -> IO GValue
B.GValue.newGValueFromPtr Ptr GValue
val'
GValue -> IO GValue
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
val''
Maybe GValue -> IO (Maybe GValue)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GValue
result
setRcPropertyValue :: MonadIO m => RcProperty -> Ptr GValue -> m ()
setRcPropertyValue :: forall (m :: * -> *). MonadIO m => RcProperty -> Ptr GValue -> m ()
setRcPropertyValue RcProperty
s Ptr GValue
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ RcProperty -> (Ptr RcProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RcProperty
s ((Ptr RcProperty -> IO ()) -> IO ())
-> (Ptr RcProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr RcProperty
ptr -> do
Ptr (Ptr GValue) -> Ptr GValue -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RcProperty
ptr Ptr RcProperty -> Int -> Ptr (Ptr GValue)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Ptr GValue
val :: Ptr GValue)
clearRcPropertyValue :: MonadIO m => RcProperty -> m ()
clearRcPropertyValue :: forall (m :: * -> *). MonadIO m => RcProperty -> m ()
clearRcPropertyValue RcProperty
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ RcProperty -> (Ptr RcProperty -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RcProperty
s ((Ptr RcProperty -> IO ()) -> IO ())
-> (Ptr RcProperty -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr RcProperty
ptr -> do
Ptr (Ptr GValue) -> Ptr GValue -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RcProperty
ptr Ptr RcProperty -> Int -> Ptr (Ptr GValue)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Ptr GValue
forall a. Ptr a
FP.nullPtr :: Ptr GValue)
#if defined(ENABLE_OVERLOADING)
data RcPropertyValueFieldInfo
instance AttrInfo RcPropertyValueFieldInfo where
type AttrBaseTypeConstraint RcPropertyValueFieldInfo = (~) RcProperty
type AttrAllowedOps RcPropertyValueFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint RcPropertyValueFieldInfo = (~) (Ptr GValue)
type AttrTransferTypeConstraint RcPropertyValueFieldInfo = (~)(Ptr GValue)
type AttrTransferType RcPropertyValueFieldInfo = (Ptr GValue)
type AttrGetType RcPropertyValueFieldInfo = Maybe GValue
type AttrLabel RcPropertyValueFieldInfo = "value"
type AttrOrigin RcPropertyValueFieldInfo = RcProperty
attrGet = getRcPropertyValue
attrSet = setRcPropertyValue
attrConstruct = undefined
attrClear = clearRcPropertyValue
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.RcProperty.value"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-RcProperty.html#g:attr:value"
})
rcProperty_value :: AttrLabelProxy "value"
rcProperty_value = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList RcProperty
type instance O.AttributeList RcProperty = RcPropertyAttributeList
type RcPropertyAttributeList = ('[ '("typeName", RcPropertyTypeNameFieldInfo), '("propertyName", RcPropertyPropertyNameFieldInfo), '("origin", RcPropertyOriginFieldInfo), '("value", RcPropertyValueFieldInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gtk_rc_property_parse_border" gtk_rc_property_parse_border ::
Ptr GParamSpec ->
Ptr GLib.String.String ->
Ptr GValue ->
IO CInt
rcPropertyParseBorder ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> GLib.String.String
-> GValue
-> m Bool
rcPropertyParseBorder :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GParamSpec -> String -> GValue -> m Bool
rcPropertyParseBorder GParamSpec
pspec String
gstring GValue
propertyValue = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr String
gstring' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
gstring
Ptr GValue
propertyValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
propertyValue
CInt
result <- Ptr GParamSpec -> Ptr String -> Ptr GValue -> IO CInt
gtk_rc_property_parse_border Ptr GParamSpec
pspec' Ptr String
gstring' Ptr GValue
propertyValue'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
gstring
GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
propertyValue
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_rc_property_parse_color" gtk_rc_property_parse_color ::
Ptr GParamSpec ->
Ptr GLib.String.String ->
Ptr GValue ->
IO CInt
rcPropertyParseColor ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> GLib.String.String
-> GValue
-> m Bool
rcPropertyParseColor :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GParamSpec -> String -> GValue -> m Bool
rcPropertyParseColor GParamSpec
pspec String
gstring GValue
propertyValue = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr String
gstring' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
gstring
Ptr GValue
propertyValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
propertyValue
CInt
result <- Ptr GParamSpec -> Ptr String -> Ptr GValue -> IO CInt
gtk_rc_property_parse_color Ptr GParamSpec
pspec' Ptr String
gstring' Ptr GValue
propertyValue'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
gstring
GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
propertyValue
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_rc_property_parse_enum" gtk_rc_property_parse_enum ::
Ptr GParamSpec ->
Ptr GLib.String.String ->
Ptr GValue ->
IO CInt
rcPropertyParseEnum ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> GLib.String.String
-> GValue
-> m Bool
rcPropertyParseEnum :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GParamSpec -> String -> GValue -> m Bool
rcPropertyParseEnum GParamSpec
pspec String
gstring GValue
propertyValue = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr String
gstring' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
gstring
Ptr GValue
propertyValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
propertyValue
CInt
result <- Ptr GParamSpec -> Ptr String -> Ptr GValue -> IO CInt
gtk_rc_property_parse_enum Ptr GParamSpec
pspec' Ptr String
gstring' Ptr GValue
propertyValue'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
gstring
GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
propertyValue
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_rc_property_parse_flags" gtk_rc_property_parse_flags ::
Ptr GParamSpec ->
Ptr GLib.String.String ->
Ptr GValue ->
IO CInt
rcPropertyParseFlags ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> GLib.String.String
-> GValue
-> m Bool
rcPropertyParseFlags :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GParamSpec -> String -> GValue -> m Bool
rcPropertyParseFlags GParamSpec
pspec String
gstring GValue
propertyValue = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr String
gstring' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
gstring
Ptr GValue
propertyValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
propertyValue
CInt
result <- Ptr GParamSpec -> Ptr String -> Ptr GValue -> IO CInt
gtk_rc_property_parse_flags Ptr GParamSpec
pspec' Ptr String
gstring' Ptr GValue
propertyValue'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
gstring
GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
propertyValue
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_rc_property_parse_requisition" gtk_rc_property_parse_requisition ::
Ptr GParamSpec ->
Ptr GLib.String.String ->
Ptr GValue ->
IO CInt
rcPropertyParseRequisition ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> GLib.String.String
-> GValue
-> m Bool
rcPropertyParseRequisition :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GParamSpec -> String -> GValue -> m Bool
rcPropertyParseRequisition GParamSpec
pspec String
gstring GValue
propertyValue = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr String
gstring' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
gstring
Ptr GValue
propertyValue' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
propertyValue
CInt
result <- Ptr GParamSpec -> Ptr String -> Ptr GValue -> IO CInt
gtk_rc_property_parse_requisition Ptr GParamSpec
pspec' Ptr String
gstring' Ptr GValue
propertyValue'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
gstring
GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
propertyValue
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveRcPropertyMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveRcPropertyMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveRcPropertyMethod t RcProperty, O.OverloadedMethod info RcProperty p) => OL.IsLabel t (RcProperty -> 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 ~ ResolveRcPropertyMethod t RcProperty, O.OverloadedMethod info RcProperty p, R.HasField t RcProperty p) => R.HasField t RcProperty p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveRcPropertyMethod t RcProperty, O.OverloadedMethodInfo info RcProperty) => OL.IsLabel t (O.MethodProxy info RcProperty) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif