{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- GtkStyleProperties provides the storage for style information
-- that is used by t'GI.Gtk.Objects.StyleContext.StyleContext' and other t'GI.Gtk.Interfaces.StyleProvider.StyleProvider'
-- implementations.
-- 
-- Before style properties can be stored in GtkStyleProperties, they
-- must be registered with @/gtk_style_properties_register_property()/@.
-- 
-- Unless you are writing a t'GI.Gtk.Interfaces.StyleProvider.StyleProvider' implementation, you
-- are unlikely to use this API directly, as @/gtk_style_context_get()/@
-- and its variants are the preferred way to access styling information
-- from widget implementations and theming engine implementations
-- should use the APIs provided by t'GI.Gtk.Objects.ThemingEngine.ThemingEngine' instead.
-- 
-- t'GI.Gtk.Objects.StyleProperties.StyleProperties' has been deprecated in GTK 3.16. The CSS
-- machinery does not use it anymore and all users of this object
-- have been deprecated.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gtk.Objects.StyleProperties
    ( 

-- * Exported types
    StyleProperties(..)                     ,
    IsStyleProperties                       ,
    toStyleProperties                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [clear]("GI.Gtk.Objects.StyleProperties#g:method:clear"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [lookupColor]("GI.Gtk.Objects.StyleProperties#g:method:lookupColor"), [mapColor]("GI.Gtk.Objects.StyleProperties#g:method:mapColor"), [merge]("GI.Gtk.Objects.StyleProperties#g:method:merge"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetProperty]("GI.Gtk.Objects.StyleProperties#g:method:unsetProperty"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getIconFactory]("GI.Gtk.Interfaces.StyleProvider#g:method:getIconFactory"), [getProperty]("GI.Gtk.Objects.StyleProperties#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getStyle]("GI.Gtk.Interfaces.StyleProvider#g:method:getStyle"), [getStyleProperty]("GI.Gtk.Interfaces.StyleProvider#g:method:getStyleProperty").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.Gtk.Objects.StyleProperties#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveStylePropertiesMethod            ,
#endif

-- ** clear #method:clear#

#if defined(ENABLE_OVERLOADING)
    StylePropertiesClearMethodInfo          ,
#endif
    stylePropertiesClear                    ,


-- ** getProperty #method:getProperty#

#if defined(ENABLE_OVERLOADING)
    StylePropertiesGetPropertyMethodInfo    ,
#endif
    stylePropertiesGetProperty              ,


-- ** lookupColor #method:lookupColor#

#if defined(ENABLE_OVERLOADING)
    StylePropertiesLookupColorMethodInfo    ,
#endif
    stylePropertiesLookupColor              ,


-- ** mapColor #method:mapColor#

#if defined(ENABLE_OVERLOADING)
    StylePropertiesMapColorMethodInfo       ,
#endif
    stylePropertiesMapColor                 ,


-- ** merge #method:merge#

#if defined(ENABLE_OVERLOADING)
    StylePropertiesMergeMethodInfo          ,
#endif
    stylePropertiesMerge                    ,


-- ** new #method:new#

    stylePropertiesNew                      ,


-- ** setProperty #method:setProperty#

#if defined(ENABLE_OVERLOADING)
    StylePropertiesSetPropertyMethodInfo    ,
#endif
    stylePropertiesSetProperty              ,


-- ** unsetProperty #method:unsetProperty#

#if defined(ENABLE_OVERLOADING)
    StylePropertiesUnsetPropertyMethodInfo  ,
#endif
    stylePropertiesUnsetProperty            ,




    ) 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.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.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.StyleProvider as Gtk.StyleProvider
import {-# SOURCE #-} qualified GI.Gtk.Structs.SymbolicColor as Gtk.SymbolicColor

-- | Memory-managed wrapper type.
newtype StyleProperties = StyleProperties (SP.ManagedPtr StyleProperties)
    deriving (StyleProperties -> StyleProperties -> Bool
(StyleProperties -> StyleProperties -> Bool)
-> (StyleProperties -> StyleProperties -> Bool)
-> Eq StyleProperties
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StyleProperties -> StyleProperties -> Bool
== :: StyleProperties -> StyleProperties -> Bool
$c/= :: StyleProperties -> StyleProperties -> Bool
/= :: StyleProperties -> StyleProperties -> Bool
Eq)

instance SP.ManagedPtrNewtype StyleProperties where
    toManagedPtr :: StyleProperties -> ManagedPtr StyleProperties
toManagedPtr (StyleProperties ManagedPtr StyleProperties
p) = ManagedPtr StyleProperties
p

foreign import ccall "gtk_style_properties_get_type"
    c_gtk_style_properties_get_type :: IO B.Types.GType

instance B.Types.TypedObject StyleProperties where
    glibType :: IO GType
glibType = IO GType
c_gtk_style_properties_get_type

instance B.Types.GObject StyleProperties

-- | Type class for types which can be safely cast to `StyleProperties`, for instance with `toStyleProperties`.
class (SP.GObject o, O.IsDescendantOf StyleProperties o) => IsStyleProperties o
instance (SP.GObject o, O.IsDescendantOf StyleProperties o) => IsStyleProperties o

instance O.HasParentTypes StyleProperties
type instance O.ParentTypes StyleProperties = '[GObject.Object.Object, Gtk.StyleProvider.StyleProvider]

-- | Cast to `StyleProperties`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toStyleProperties :: (MIO.MonadIO m, IsStyleProperties o) => o -> m StyleProperties
toStyleProperties :: forall (m :: * -> *) o.
(MonadIO m, IsStyleProperties o) =>
o -> m StyleProperties
toStyleProperties = IO StyleProperties -> m StyleProperties
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO StyleProperties -> m StyleProperties)
-> (o -> IO StyleProperties) -> o -> m StyleProperties
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr StyleProperties -> StyleProperties)
-> o -> IO StyleProperties
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr StyleProperties -> StyleProperties
StyleProperties

-- | Convert 'StyleProperties' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe StyleProperties) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_style_properties_get_type
    gvalueSet_ :: Ptr GValue -> Maybe StyleProperties -> IO ()
gvalueSet_ Ptr GValue
gv Maybe StyleProperties
P.Nothing = Ptr GValue -> Ptr StyleProperties -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr StyleProperties
forall a. Ptr a
FP.nullPtr :: FP.Ptr StyleProperties)
    gvalueSet_ Ptr GValue
gv (P.Just StyleProperties
obj) = StyleProperties -> (Ptr StyleProperties -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr StyleProperties
obj (Ptr GValue -> Ptr StyleProperties -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe StyleProperties)
gvalueGet_ Ptr GValue
gv = do
        Ptr StyleProperties
ptr <- Ptr GValue -> IO (Ptr StyleProperties)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr StyleProperties)
        if Ptr StyleProperties
ptr Ptr StyleProperties -> Ptr StyleProperties -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr StyleProperties
forall a. Ptr a
FP.nullPtr
        then StyleProperties -> Maybe StyleProperties
forall a. a -> Maybe a
P.Just (StyleProperties -> Maybe StyleProperties)
-> IO StyleProperties -> IO (Maybe StyleProperties)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr StyleProperties -> StyleProperties)
-> Ptr StyleProperties -> IO StyleProperties
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr StyleProperties -> StyleProperties
StyleProperties Ptr StyleProperties
ptr
        else Maybe StyleProperties -> IO (Maybe StyleProperties)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe StyleProperties
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveStylePropertiesMethod (t :: Symbol) (o :: *) :: * where
    ResolveStylePropertiesMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveStylePropertiesMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveStylePropertiesMethod "clear" o = StylePropertiesClearMethodInfo
    ResolveStylePropertiesMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveStylePropertiesMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveStylePropertiesMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveStylePropertiesMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveStylePropertiesMethod "lookupColor" o = StylePropertiesLookupColorMethodInfo
    ResolveStylePropertiesMethod "mapColor" o = StylePropertiesMapColorMethodInfo
    ResolveStylePropertiesMethod "merge" o = StylePropertiesMergeMethodInfo
    ResolveStylePropertiesMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveStylePropertiesMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveStylePropertiesMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveStylePropertiesMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveStylePropertiesMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveStylePropertiesMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveStylePropertiesMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveStylePropertiesMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveStylePropertiesMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveStylePropertiesMethod "unsetProperty" o = StylePropertiesUnsetPropertyMethodInfo
    ResolveStylePropertiesMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveStylePropertiesMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveStylePropertiesMethod "getIconFactory" o = Gtk.StyleProvider.StyleProviderGetIconFactoryMethodInfo
    ResolveStylePropertiesMethod "getProperty" o = StylePropertiesGetPropertyMethodInfo
    ResolveStylePropertiesMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveStylePropertiesMethod "getStyle" o = Gtk.StyleProvider.StyleProviderGetStyleMethodInfo
    ResolveStylePropertiesMethod "getStyleProperty" o = Gtk.StyleProvider.StyleProviderGetStylePropertyMethodInfo
    ResolveStylePropertiesMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveStylePropertiesMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveStylePropertiesMethod "setProperty" o = StylePropertiesSetPropertyMethodInfo
    ResolveStylePropertiesMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveStylePropertiesMethod t StyleProperties, O.OverloadedMethod info StyleProperties p) => OL.IsLabel t (StyleProperties -> 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 ~ ResolveStylePropertiesMethod t StyleProperties, O.OverloadedMethod info StyleProperties p, R.HasField t StyleProperties p) => R.HasField t StyleProperties p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveStylePropertiesMethod t StyleProperties, O.OverloadedMethodInfo info StyleProperties) => OL.IsLabel t (O.MethodProxy info StyleProperties) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList StyleProperties
type instance O.AttributeList StyleProperties = StylePropertiesAttributeList
type StylePropertiesAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList StyleProperties = StylePropertiesSignalList
type StylePropertiesSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method StyleProperties::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "StyleProperties" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_style_properties_new" gtk_style_properties_new :: 
    IO (Ptr StyleProperties)

{-# DEPRECATED stylePropertiesNew ["(Since version 3.16)","t'GI.Gtk.Objects.StyleProperties.StyleProperties' are deprecated."] #-}
-- | Returns a newly created t'GI.Gtk.Objects.StyleProperties.StyleProperties'
stylePropertiesNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m StyleProperties
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.StyleProperties.StyleProperties'
stylePropertiesNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m StyleProperties
stylePropertiesNew  = IO StyleProperties -> m StyleProperties
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StyleProperties -> m StyleProperties)
-> IO StyleProperties -> m StyleProperties
forall a b. (a -> b) -> a -> b
$ do
    Ptr StyleProperties
result <- IO (Ptr StyleProperties)
gtk_style_properties_new
    Text -> Ptr StyleProperties -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stylePropertiesNew" Ptr StyleProperties
result
    StyleProperties
result' <- ((ManagedPtr StyleProperties -> StyleProperties)
-> Ptr StyleProperties -> IO StyleProperties
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr StyleProperties -> StyleProperties
StyleProperties) Ptr StyleProperties
result
    StyleProperties -> IO StyleProperties
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return StyleProperties
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method StyleProperties::clear
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "props"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StyleProperties" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStyleProperties"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_style_properties_clear" gtk_style_properties_clear :: 
    Ptr StyleProperties ->                  -- props : TInterface (Name {namespace = "Gtk", name = "StyleProperties"})
    IO ()

{-# DEPRECATED stylePropertiesClear ["(Since version 3.16)","t'GI.Gtk.Objects.StyleProperties.StyleProperties' are deprecated."] #-}
-- | Clears all style information from /@props@/.
stylePropertiesClear ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleProperties a) =>
    a
    -- ^ /@props@/: a t'GI.Gtk.Objects.StyleProperties.StyleProperties'
    -> m ()
stylePropertiesClear :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleProperties a) =>
a -> m ()
stylePropertiesClear a
props = 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
$ do
    Ptr StyleProperties
props' <- a -> IO (Ptr StyleProperties)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
props
    Ptr StyleProperties -> IO ()
gtk_style_properties_clear Ptr StyleProperties
props'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
props
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StylePropertiesClearMethodInfo
instance (signature ~ (m ()), MonadIO m, IsStyleProperties a) => O.OverloadedMethod StylePropertiesClearMethodInfo a signature where
    overloadedMethod = stylePropertiesClear

instance O.OverloadedMethodInfo StylePropertiesClearMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StyleProperties.stylePropertiesClear",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.39/docs/GI-Gtk-Objects-StyleProperties.html#v:stylePropertiesClear"
        })


#endif

-- method StyleProperties::get_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "props"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StyleProperties" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStyleProperties"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "style property name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StateFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "state to retrieve the property value for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TGValue
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the style property value."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_style_properties_get_property" gtk_style_properties_get_property :: 
    Ptr StyleProperties ->                  -- props : TInterface (Name {namespace = "Gtk", name = "StyleProperties"})
    CString ->                              -- property : TBasicType TUTF8
    CUInt ->                                -- state : TInterface (Name {namespace = "Gtk", name = "StateFlags"})
    Ptr GValue ->                           -- value : TGValue
    IO CInt

{-# DEPRECATED stylePropertiesGetProperty ["(Since version 3.16)","t'GI.Gtk.Objects.StyleProperties.StyleProperties' are deprecated."] #-}
-- | Gets a style property from /@props@/ for the given state. When done with /@value@/,
-- 'GI.GObject.Structs.Value.valueUnset' needs to be called to free any allocated memory.
-- 
-- /Since: 3.0/
stylePropertiesGetProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleProperties a) =>
    a
    -- ^ /@props@/: a t'GI.Gtk.Objects.StyleProperties.StyleProperties'
    -> T.Text
    -- ^ /@property@/: style property name
    -> [Gtk.Flags.StateFlags]
    -- ^ /@state@/: state to retrieve the property value for
    -> m ((Bool, GValue))
    -- ^ __Returns:__ 'P.True' if the property exists in /@props@/, 'P.False' otherwise
stylePropertiesGetProperty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleProperties a) =>
a -> Text -> [StateFlags] -> m (Bool, GValue)
stylePropertiesGetProperty a
props Text
property [StateFlags]
state = IO (Bool, GValue) -> m (Bool, GValue)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, GValue) -> m (Bool, GValue))
-> IO (Bool, GValue) -> m (Bool, GValue)
forall a b. (a -> b) -> a -> b
$ do
    Ptr StyleProperties
props' <- a -> IO (Ptr StyleProperties)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
props
    CString
property' <- Text -> IO CString
textToCString Text
property
    let state' :: CUInt
state' = [StateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [StateFlags]
state
    Ptr GValue
value <- Int -> IO (Ptr GValue)
forall a. Int -> IO (Ptr a)
SP.callocBytes Int
24 :: IO (Ptr GValue)
    CInt
result <- Ptr StyleProperties -> CString -> CUInt -> Ptr GValue -> IO CInt
gtk_style_properties_get_property Ptr StyleProperties
props' CString
property' CUInt
state' Ptr GValue
value
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    GValue
value' <- Ptr GValue -> IO GValue
B.GValue.wrapGValuePtr Ptr GValue
value
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
props
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    (Bool, GValue) -> IO (Bool, GValue)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', GValue
value')

#if defined(ENABLE_OVERLOADING)
data StylePropertiesGetPropertyMethodInfo
instance (signature ~ (T.Text -> [Gtk.Flags.StateFlags] -> m ((Bool, GValue))), MonadIO m, IsStyleProperties a) => O.OverloadedMethod StylePropertiesGetPropertyMethodInfo a signature where
    overloadedMethod = stylePropertiesGetProperty

instance O.OverloadedMethodInfo StylePropertiesGetPropertyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StyleProperties.stylePropertiesGetProperty",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.39/docs/GI-Gtk-Objects-StyleProperties.html#v:stylePropertiesGetProperty"
        })


#endif

-- method StyleProperties::lookup_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "props"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StyleProperties" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStyleProperties"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "color name to lookup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "SymbolicColor" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_style_properties_lookup_color" gtk_style_properties_lookup_color :: 
    Ptr StyleProperties ->                  -- props : TInterface (Name {namespace = "Gtk", name = "StyleProperties"})
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr Gtk.SymbolicColor.SymbolicColor)

{-# DEPRECATED stylePropertiesLookupColor ["(Since version 3.8)","t'GI.Gtk.Structs.SymbolicColor.SymbolicColor' is deprecated."] #-}
-- | Returns the symbolic color that is mapped
-- to /@name@/.
-- 
-- /Since: 3.0/
stylePropertiesLookupColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleProperties a) =>
    a
    -- ^ /@props@/: a t'GI.Gtk.Objects.StyleProperties.StyleProperties'
    -> T.Text
    -- ^ /@name@/: color name to lookup
    -> m Gtk.SymbolicColor.SymbolicColor
    -- ^ __Returns:__ The mapped color
stylePropertiesLookupColor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleProperties a) =>
a -> Text -> m SymbolicColor
stylePropertiesLookupColor a
props Text
name = IO SymbolicColor -> m SymbolicColor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SymbolicColor -> m SymbolicColor)
-> IO SymbolicColor -> m SymbolicColor
forall a b. (a -> b) -> a -> b
$ do
    Ptr StyleProperties
props' <- a -> IO (Ptr StyleProperties)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
props
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr SymbolicColor
result <- Ptr StyleProperties -> CString -> IO (Ptr SymbolicColor)
gtk_style_properties_lookup_color Ptr StyleProperties
props' CString
name'
    Text -> Ptr SymbolicColor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stylePropertiesLookupColor" Ptr SymbolicColor
result
    SymbolicColor
result' <- ((ManagedPtr SymbolicColor -> SymbolicColor)
-> Ptr SymbolicColor -> IO SymbolicColor
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr SymbolicColor -> SymbolicColor
Gtk.SymbolicColor.SymbolicColor) Ptr SymbolicColor
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
props
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    SymbolicColor -> IO SymbolicColor
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SymbolicColor
result'

#if defined(ENABLE_OVERLOADING)
data StylePropertiesLookupColorMethodInfo
instance (signature ~ (T.Text -> m Gtk.SymbolicColor.SymbolicColor), MonadIO m, IsStyleProperties a) => O.OverloadedMethod StylePropertiesLookupColorMethodInfo a signature where
    overloadedMethod = stylePropertiesLookupColor

instance O.OverloadedMethodInfo StylePropertiesLookupColorMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StyleProperties.stylePropertiesLookupColor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.39/docs/GI-Gtk-Objects-StyleProperties.html#v:stylePropertiesLookupColor"
        })


#endif

-- method StyleProperties::map_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "props"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StyleProperties" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStyleProperties"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "color name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "color"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "SymbolicColor" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GtkSymbolicColor to map @name to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_style_properties_map_color" gtk_style_properties_map_color :: 
    Ptr StyleProperties ->                  -- props : TInterface (Name {namespace = "Gtk", name = "StyleProperties"})
    CString ->                              -- name : TBasicType TUTF8
    Ptr Gtk.SymbolicColor.SymbolicColor ->  -- color : TInterface (Name {namespace = "Gtk", name = "SymbolicColor"})
    IO ()

{-# DEPRECATED stylePropertiesMapColor ["(Since version 3.8)","t'GI.Gtk.Structs.SymbolicColor.SymbolicColor' is deprecated."] #-}
-- | Maps /@color@/ so it can be referenced by /@name@/. See
-- 'GI.Gtk.Objects.StyleProperties.stylePropertiesLookupColor'
-- 
-- /Since: 3.0/
stylePropertiesMapColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleProperties a) =>
    a
    -- ^ /@props@/: a t'GI.Gtk.Objects.StyleProperties.StyleProperties'
    -> T.Text
    -- ^ /@name@/: color name
    -> Gtk.SymbolicColor.SymbolicColor
    -- ^ /@color@/: t'GI.Gtk.Structs.SymbolicColor.SymbolicColor' to map /@name@/ to
    -> m ()
stylePropertiesMapColor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleProperties a) =>
a -> Text -> SymbolicColor -> m ()
stylePropertiesMapColor a
props Text
name SymbolicColor
color = 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
$ do
    Ptr StyleProperties
props' <- a -> IO (Ptr StyleProperties)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
props
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr SymbolicColor
color' <- SymbolicColor -> IO (Ptr SymbolicColor)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SymbolicColor
color
    Ptr StyleProperties -> CString -> Ptr SymbolicColor -> IO ()
gtk_style_properties_map_color Ptr StyleProperties
props' CString
name' Ptr SymbolicColor
color'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
props
    SymbolicColor -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SymbolicColor
color
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StylePropertiesMapColorMethodInfo
instance (signature ~ (T.Text -> Gtk.SymbolicColor.SymbolicColor -> m ()), MonadIO m, IsStyleProperties a) => O.OverloadedMethod StylePropertiesMapColorMethodInfo a signature where
    overloadedMethod = stylePropertiesMapColor

instance O.OverloadedMethodInfo StylePropertiesMapColorMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StyleProperties.stylePropertiesMapColor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.39/docs/GI-Gtk-Objects-StyleProperties.html#v:stylePropertiesMapColor"
        })


#endif

-- method StyleProperties::merge
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "props"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StyleProperties" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStyleProperties"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "props_to_merge"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StyleProperties" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a second #GtkStyleProperties"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "replace"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to replace values or not"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_style_properties_merge" gtk_style_properties_merge :: 
    Ptr StyleProperties ->                  -- props : TInterface (Name {namespace = "Gtk", name = "StyleProperties"})
    Ptr StyleProperties ->                  -- props_to_merge : TInterface (Name {namespace = "Gtk", name = "StyleProperties"})
    CInt ->                                 -- replace : TBasicType TBoolean
    IO ()

{-# DEPRECATED stylePropertiesMerge ["(Since version 3.16)","t'GI.Gtk.Objects.StyleProperties.StyleProperties' are deprecated."] #-}
-- | Merges into /@props@/ all the style information contained
-- in /@propsToMerge@/. If /@replace@/ is 'P.True', the values
-- will be overwritten, if it is 'P.False', the older values
-- will prevail.
-- 
-- /Since: 3.0/
stylePropertiesMerge ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleProperties a, IsStyleProperties b) =>
    a
    -- ^ /@props@/: a t'GI.Gtk.Objects.StyleProperties.StyleProperties'
    -> b
    -- ^ /@propsToMerge@/: a second t'GI.Gtk.Objects.StyleProperties.StyleProperties'
    -> Bool
    -- ^ /@replace@/: whether to replace values or not
    -> m ()
stylePropertiesMerge :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsStyleProperties a,
 IsStyleProperties b) =>
a -> b -> Bool -> m ()
stylePropertiesMerge a
props b
propsToMerge Bool
replace = 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
$ do
    Ptr StyleProperties
props' <- a -> IO (Ptr StyleProperties)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
props
    Ptr StyleProperties
propsToMerge' <- b -> IO (Ptr StyleProperties)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
propsToMerge
    let replace' :: CInt
replace' = (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
replace
    Ptr StyleProperties -> Ptr StyleProperties -> CInt -> IO ()
gtk_style_properties_merge Ptr StyleProperties
props' Ptr StyleProperties
propsToMerge' CInt
replace'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
props
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
propsToMerge
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StylePropertiesMergeMethodInfo
instance (signature ~ (b -> Bool -> m ()), MonadIO m, IsStyleProperties a, IsStyleProperties b) => O.OverloadedMethod StylePropertiesMergeMethodInfo a signature where
    overloadedMethod = stylePropertiesMerge

instance O.OverloadedMethodInfo StylePropertiesMergeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StyleProperties.stylePropertiesMerge",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.39/docs/GI-Gtk-Objects-StyleProperties.html#v:stylePropertiesMerge"
        })


#endif

-- method StyleProperties::set_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "props"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StyleProperties" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStyleProperties"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "styling property to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StateFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "state to set the value for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "new value for the property"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_style_properties_set_property" gtk_style_properties_set_property :: 
    Ptr StyleProperties ->                  -- props : TInterface (Name {namespace = "Gtk", name = "StyleProperties"})
    CString ->                              -- property : TBasicType TUTF8
    CUInt ->                                -- state : TInterface (Name {namespace = "Gtk", name = "StateFlags"})
    Ptr GValue ->                           -- value : TGValue
    IO ()

{-# DEPRECATED stylePropertiesSetProperty ["(Since version 3.16)","t'GI.Gtk.Objects.StyleProperties.StyleProperties' are deprecated."] #-}
-- | Sets a styling property in /@props@/.
-- 
-- /Since: 3.0/
stylePropertiesSetProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleProperties a) =>
    a
    -- ^ /@props@/: a t'GI.Gtk.Objects.StyleProperties.StyleProperties'
    -> T.Text
    -- ^ /@property@/: styling property to set
    -> [Gtk.Flags.StateFlags]
    -- ^ /@state@/: state to set the value for
    -> GValue
    -- ^ /@value@/: new value for the property
    -> m ()
stylePropertiesSetProperty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleProperties a) =>
a -> Text -> [StateFlags] -> GValue -> m ()
stylePropertiesSetProperty a
props Text
property [StateFlags]
state GValue
value = 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
$ do
    Ptr StyleProperties
props' <- a -> IO (Ptr StyleProperties)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
props
    CString
property' <- Text -> IO CString
textToCString Text
property
    let state' :: CUInt
state' = [StateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [StateFlags]
state
    Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
    Ptr StyleProperties -> CString -> CUInt -> Ptr GValue -> IO ()
gtk_style_properties_set_property Ptr StyleProperties
props' CString
property' CUInt
state' Ptr GValue
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
props
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StylePropertiesSetPropertyMethodInfo
instance (signature ~ (T.Text -> [Gtk.Flags.StateFlags] -> GValue -> m ()), MonadIO m, IsStyleProperties a) => O.OverloadedMethod StylePropertiesSetPropertyMethodInfo a signature where
    overloadedMethod = stylePropertiesSetProperty

instance O.OverloadedMethodInfo StylePropertiesSetPropertyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StyleProperties.stylePropertiesSetProperty",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.39/docs/GI-Gtk-Objects-StyleProperties.html#v:stylePropertiesSetProperty"
        })


#endif

-- method StyleProperties::unset_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "props"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StyleProperties" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStyleProperties"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "property to unset" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StateFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "state to unset" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_style_properties_unset_property" gtk_style_properties_unset_property :: 
    Ptr StyleProperties ->                  -- props : TInterface (Name {namespace = "Gtk", name = "StyleProperties"})
    CString ->                              -- property : TBasicType TUTF8
    CUInt ->                                -- state : TInterface (Name {namespace = "Gtk", name = "StateFlags"})
    IO ()

{-# DEPRECATED stylePropertiesUnsetProperty ["(Since version 3.16)","t'GI.Gtk.Objects.StyleProperties.StyleProperties' are deprecated."] #-}
-- | Unsets a style property in /@props@/.
-- 
-- /Since: 3.0/
stylePropertiesUnsetProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleProperties a) =>
    a
    -- ^ /@props@/: a t'GI.Gtk.Objects.StyleProperties.StyleProperties'
    -> T.Text
    -- ^ /@property@/: property to unset
    -> [Gtk.Flags.StateFlags]
    -- ^ /@state@/: state to unset
    -> m ()
stylePropertiesUnsetProperty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleProperties a) =>
a -> Text -> [StateFlags] -> m ()
stylePropertiesUnsetProperty a
props Text
property [StateFlags]
state = 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
$ do
    Ptr StyleProperties
props' <- a -> IO (Ptr StyleProperties)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
props
    CString
property' <- Text -> IO CString
textToCString Text
property
    let state' :: CUInt
state' = [StateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [StateFlags]
state
    Ptr StyleProperties -> CString -> CUInt -> IO ()
gtk_style_properties_unset_property Ptr StyleProperties
props' CString
property' CUInt
state'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
props
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StylePropertiesUnsetPropertyMethodInfo
instance (signature ~ (T.Text -> [Gtk.Flags.StateFlags] -> m ()), MonadIO m, IsStyleProperties a) => O.OverloadedMethod StylePropertiesUnsetPropertyMethodInfo a signature where
    overloadedMethod = stylePropertiesUnsetProperty

instance O.OverloadedMethodInfo StylePropertiesUnsetPropertyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StyleProperties.stylePropertiesUnsetProperty",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.39/docs/GI-Gtk-Objects-StyleProperties.html#v:stylePropertiesUnsetProperty"
        })


#endif