{-# 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                       ,
    noRcProperty                            ,
 
#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                   ,
    getRcPropertyValue                      ,
#if defined(ENABLE_OVERLOADING)
    rcProperty_value                        ,
#endif
    ) 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
import qualified GI.GLib.Structs.String as GLib.String
newtype RcProperty = RcProperty (ManagedPtr RcProperty)
    deriving (RcProperty -> RcProperty -> Bool
(RcProperty -> RcProperty -> Bool)
-> (RcProperty -> RcProperty -> Bool) -> Eq RcProperty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RcProperty -> RcProperty -> Bool
$c/= :: RcProperty -> RcProperty -> Bool
== :: RcProperty -> RcProperty -> Bool
$c== :: RcProperty -> RcProperty -> Bool
Eq)
instance WrappedPtr RcProperty where
    wrappedPtrCalloc :: IO (Ptr RcProperty)
wrappedPtrCalloc = Int -> IO (Ptr RcProperty)
forall a. Int -> IO (Ptr a)
callocBytes 40
    wrappedPtrCopy :: RcProperty -> IO RcProperty
wrappedPtrCopy = \p :: RcProperty
p -> RcProperty -> (Ptr RcProperty -> IO RcProperty) -> IO RcProperty
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RcProperty
p (Int -> Ptr RcProperty -> IO (Ptr RcProperty)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 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, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr RcProperty -> RcProperty
RcProperty)
    wrappedPtrFree :: Maybe (GDestroyNotify RcProperty)
wrappedPtrFree = GDestroyNotify RcProperty -> Maybe (GDestroyNotify RcProperty)
forall a. a -> Maybe a
Just GDestroyNotify RcProperty
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free
newZeroRcProperty :: MonadIO m => m RcProperty
newZeroRcProperty :: m RcProperty
newZeroRcProperty = IO RcProperty -> m RcProperty
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. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr RcProperty)
-> (Ptr RcProperty -> IO RcProperty) -> IO RcProperty
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr RcProperty -> RcProperty)
-> Ptr RcProperty -> IO RcProperty
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr RcProperty -> RcProperty
RcProperty
instance tag ~ 'AttrSet => Constructible RcProperty tag where
    new :: (ManagedPtr RcProperty -> RcProperty)
-> [AttrOp RcProperty tag] -> m RcProperty
new _ attrs :: [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 (m :: * -> *) a. Monad m => a -> m a
return RcProperty
o
noRcProperty :: Maybe RcProperty
noRcProperty :: Maybe RcProperty
noRcProperty = Maybe RcProperty
forall a. Maybe a
Nothing
getRcPropertyTypeName :: MonadIO m => RcProperty -> m Word32
getRcPropertyTypeName :: RcProperty -> m Word32
getRcPropertyTypeName s :: RcProperty
s = IO Word32 -> m Word32
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 :: 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` 0) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setRcPropertyTypeName :: MonadIO m => RcProperty -> Word32 -> m ()
setRcPropertyTypeName :: RcProperty -> Word32 -> m ()
setRcPropertyTypeName s :: RcProperty
s val :: Word32
val = IO () -> m ()
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 :: 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` 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
rcProperty_typeName :: AttrLabelProxy "typeName"
rcProperty_typeName = AttrLabelProxy
#endif
getRcPropertyPropertyName :: MonadIO m => RcProperty -> m Word32
getRcPropertyPropertyName :: RcProperty -> m Word32
getRcPropertyPropertyName s :: RcProperty
s = IO Word32 -> m Word32
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 :: 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` 4) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setRcPropertyPropertyName :: MonadIO m => RcProperty -> Word32 -> m ()
setRcPropertyPropertyName :: RcProperty -> Word32 -> m ()
setRcPropertyPropertyName s :: RcProperty
s val :: Word32
val = IO () -> m ()
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 :: 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` 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
rcProperty_propertyName :: AttrLabelProxy "propertyName"
rcProperty_propertyName = AttrLabelProxy
#endif
getRcPropertyOrigin :: MonadIO m => RcProperty -> m (Maybe T.Text)
getRcPropertyOrigin :: RcProperty -> m (Maybe Text)
getRcPropertyOrigin s :: RcProperty
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
$ 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 :: 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` 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
$ \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
setRcPropertyOrigin :: MonadIO m => RcProperty -> CString -> m ()
setRcPropertyOrigin :: RcProperty -> CString -> m ()
setRcPropertyOrigin s :: RcProperty
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
$ 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 :: 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` 8) (CString
val :: CString)
clearRcPropertyOrigin :: MonadIO m => RcProperty -> m ()
clearRcPropertyOrigin :: RcProperty -> m ()
clearRcPropertyOrigin s :: RcProperty
s = IO () -> m ()
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 :: 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` 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
rcProperty_origin :: AttrLabelProxy "origin"
rcProperty_origin = AttrLabelProxy
#endif
getRcPropertyValue :: MonadIO m => RcProperty -> m GValue
getRcPropertyValue :: RcProperty -> m GValue
getRcPropertyValue s :: RcProperty
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
$ RcProperty -> (Ptr RcProperty -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RcProperty
s ((Ptr RcProperty -> IO GValue) -> IO GValue)
-> (Ptr RcProperty -> IO GValue) -> IO GValue
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr RcProperty
ptr -> do
    let val :: Ptr GValue
val = Ptr RcProperty
ptr Ptr RcProperty -> Int -> Ptr GValue
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: (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 RcPropertyValueFieldInfo
instance AttrInfo RcPropertyValueFieldInfo where
    type AttrBaseTypeConstraint RcPropertyValueFieldInfo = (~) RcProperty
    type AttrAllowedOps RcPropertyValueFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint RcPropertyValueFieldInfo = (~) (Ptr GValue)
    type AttrTransferTypeConstraint RcPropertyValueFieldInfo = (~)(Ptr GValue)
    type AttrTransferType RcPropertyValueFieldInfo = (Ptr GValue)
    type AttrGetType RcPropertyValueFieldInfo = GValue
    type AttrLabel RcPropertyValueFieldInfo = "value"
    type AttrOrigin RcPropertyValueFieldInfo = RcProperty
    attrGet = getRcPropertyValue
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined
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, *)])
#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 :: GParamSpec -> String -> GValue -> m Bool
rcPropertyParseBorder pspec :: GParamSpec
pspec gstring :: String
gstring propertyValue :: GValue
propertyValue = IO Bool -> m Bool
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
/= 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 (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 :: GParamSpec -> String -> GValue -> m Bool
rcPropertyParseColor pspec :: GParamSpec
pspec gstring :: String
gstring propertyValue :: GValue
propertyValue = IO Bool -> m Bool
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
/= 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 (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 :: GParamSpec -> String -> GValue -> m Bool
rcPropertyParseEnum pspec :: GParamSpec
pspec gstring :: String
gstring propertyValue :: GValue
propertyValue = IO Bool -> m Bool
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
/= 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 (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 :: GParamSpec -> String -> GValue -> m Bool
rcPropertyParseFlags pspec :: GParamSpec
pspec gstring :: String
gstring propertyValue :: GValue
propertyValue = IO Bool -> m Bool
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
/= 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 (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 :: GParamSpec -> String -> GValue -> m Bool
rcPropertyParseRequisition pspec :: GParamSpec
pspec gstring :: String
gstring propertyValue :: GValue
propertyValue = IO Bool -> m Bool
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
/= 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 (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 :: *) :: * where
    ResolveRcPropertyMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveRcPropertyMethod t RcProperty, O.MethodInfo 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
#endif