{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.Style
    ( 
    Style(..)                               ,
    IsStyle                                 ,
    toStyle                                 ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveStyleMethod                      ,
#endif
#if defined(ENABLE_OVERLOADING)
    StyleApplyDefaultBackgroundMethodInfo   ,
#endif
    styleApplyDefaultBackground             ,
#if defined(ENABLE_OVERLOADING)
    StyleCopyMethodInfo                     ,
#endif
    styleCopy                               ,
#if defined(ENABLE_OVERLOADING)
    StyleDetachMethodInfo                   ,
#endif
    styleDetach                             ,
#if defined(ENABLE_OVERLOADING)
    StyleGetStylePropertyMethodInfo         ,
#endif
    styleGetStyleProperty                   ,
#if defined(ENABLE_OVERLOADING)
    StyleHasContextMethodInfo               ,
#endif
    styleHasContext                         ,
#if defined(ENABLE_OVERLOADING)
    StyleLookupColorMethodInfo              ,
#endif
    styleLookupColor                        ,
#if defined(ENABLE_OVERLOADING)
    StyleLookupIconSetMethodInfo            ,
#endif
    styleLookupIconSet                      ,
    styleNew                                ,
#if defined(ENABLE_OVERLOADING)
    StyleRenderIconMethodInfo               ,
#endif
    styleRenderIcon                         ,
#if defined(ENABLE_OVERLOADING)
    StyleSetBackgroundMethodInfo            ,
#endif
    styleSetBackground                      ,
 
#if defined(ENABLE_OVERLOADING)
    StyleContextPropertyInfo                ,
#endif
    constructStyleContext                   ,
    getStyleContext                         ,
#if defined(ENABLE_OVERLOADING)
    styleContext                            ,
#endif
 
    C_StyleRealizeCallback                  ,
    StyleRealizeCallback                    ,
#if defined(ENABLE_OVERLOADING)
    StyleRealizeSignalInfo                  ,
#endif
    afterStyleRealize                       ,
    genClosure_StyleRealize                 ,
    mk_StyleRealizeCallback                 ,
    noStyleRealizeCallback                  ,
    onStyleRealize                          ,
    wrap_StyleRealizeCallback               ,
    C_StyleUnrealizeCallback                ,
    StyleUnrealizeCallback                  ,
#if defined(ENABLE_OVERLOADING)
    StyleUnrealizeSignalInfo                ,
#endif
    afterStyleUnrealize                     ,
    genClosure_StyleUnrealize               ,
    mk_StyleUnrealizeCallback               ,
    noStyleUnrealizeCallback                ,
    onStyleUnrealize                        ,
    wrap_StyleUnrealizeCallback             ,
    ) 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.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.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.Cairo.Structs.Context as Cairo.Context
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Window as Gdk.Window
import qualified GI.Gdk.Structs.Color as Gdk.Color
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Structs.IconSet as Gtk.IconSet
import {-# SOURCE #-} qualified GI.Gtk.Structs.IconSource as Gtk.IconSource
newtype Style = Style (SP.ManagedPtr Style)
    deriving (Style -> Style -> Bool
(Style -> Style -> Bool) -> (Style -> Style -> Bool) -> Eq Style
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Style -> Style -> Bool
$c/= :: Style -> Style -> Bool
== :: Style -> Style -> Bool
$c== :: Style -> Style -> Bool
Eq)
instance SP.ManagedPtrNewtype Style where
    toManagedPtr :: Style -> ManagedPtr Style
toManagedPtr (Style ManagedPtr Style
p) = ManagedPtr Style
p
foreign import ccall "gtk_style_get_type"
    c_gtk_style_get_type :: IO B.Types.GType
instance B.Types.TypedObject Style where
    glibType :: IO GType
glibType = IO GType
c_gtk_style_get_type
instance B.Types.GObject Style
class (SP.GObject o, O.IsDescendantOf Style o) => IsStyle o
instance (SP.GObject o, O.IsDescendantOf Style o) => IsStyle o
instance O.HasParentTypes Style
type instance O.ParentTypes Style = '[GObject.Object.Object]
toStyle :: (MIO.MonadIO m, IsStyle o) => o -> m Style
toStyle :: forall (m :: * -> *) o. (MonadIO m, IsStyle o) => o -> m Style
toStyle = IO Style -> m Style
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Style -> m Style) -> (o -> IO Style) -> o -> m Style
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Style -> Style) -> o -> IO Style
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Style -> Style
Style
instance B.GValue.IsGValue (Maybe Style) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_style_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Style -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Style
P.Nothing = Ptr GValue -> Ptr Style -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Style
forall a. Ptr a
FP.nullPtr :: FP.Ptr Style)
    gvalueSet_ Ptr GValue
gv (P.Just Style
obj) = Style -> (Ptr Style -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Style
obj (Ptr GValue -> Ptr Style -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Style)
gvalueGet_ Ptr GValue
gv = do
        Ptr Style
ptr <- Ptr GValue -> IO (Ptr Style)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Style)
        if Ptr Style
ptr Ptr Style -> Ptr Style -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Style
forall a. Ptr a
FP.nullPtr
        then Style -> Maybe Style
forall a. a -> Maybe a
P.Just (Style -> Maybe Style) -> IO Style -> IO (Maybe Style)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Style -> Style) -> Ptr Style -> IO Style
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Style -> Style
Style Ptr Style
ptr
        else Maybe Style -> IO (Maybe Style)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Style
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolveStyleMethod (t :: Symbol) (o :: *) :: * where
    ResolveStyleMethod "applyDefaultBackground" o = StyleApplyDefaultBackgroundMethodInfo
    ResolveStyleMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveStyleMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveStyleMethod "copy" o = StyleCopyMethodInfo
    ResolveStyleMethod "detach" o = StyleDetachMethodInfo
    ResolveStyleMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveStyleMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveStyleMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveStyleMethod "hasContext" o = StyleHasContextMethodInfo
    ResolveStyleMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveStyleMethod "lookupColor" o = StyleLookupColorMethodInfo
    ResolveStyleMethod "lookupIconSet" o = StyleLookupIconSetMethodInfo
    ResolveStyleMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveStyleMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveStyleMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveStyleMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveStyleMethod "renderIcon" o = StyleRenderIconMethodInfo
    ResolveStyleMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveStyleMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveStyleMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveStyleMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveStyleMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveStyleMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveStyleMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveStyleMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveStyleMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveStyleMethod "getStyleProperty" o = StyleGetStylePropertyMethodInfo
    ResolveStyleMethod "setBackground" o = StyleSetBackgroundMethodInfo
    ResolveStyleMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveStyleMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveStyleMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveStyleMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveStyleMethod t Style, O.OverloadedMethod info Style p) => OL.IsLabel t (Style -> 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 ~ ResolveStyleMethod t Style, O.OverloadedMethod info Style p, R.HasField t Style p) => R.HasField t Style p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveStyleMethod t Style, O.OverloadedMethodInfo info Style) => OL.IsLabel t (O.MethodProxy info Style) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
type StyleRealizeCallback =
    IO ()
noStyleRealizeCallback :: Maybe StyleRealizeCallback
noStyleRealizeCallback :: Maybe (IO ())
noStyleRealizeCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_StyleRealizeCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_StyleRealizeCallback :: C_StyleRealizeCallback -> IO (FunPtr C_StyleRealizeCallback)
genClosure_StyleRealize :: MonadIO m => StyleRealizeCallback -> m (GClosure C_StyleRealizeCallback)
genClosure_StyleRealize :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_StyleRealizeCallback)
genClosure_StyleRealize IO ()
cb = IO (GClosure C_StyleRealizeCallback)
-> m (GClosure C_StyleRealizeCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_StyleRealizeCallback)
 -> m (GClosure C_StyleRealizeCallback))
-> IO (GClosure C_StyleRealizeCallback)
-> m (GClosure C_StyleRealizeCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_StyleRealizeCallback
cb' = IO () -> C_StyleRealizeCallback
wrap_StyleRealizeCallback IO ()
cb
    C_StyleRealizeCallback -> IO (FunPtr C_StyleRealizeCallback)
mk_StyleRealizeCallback C_StyleRealizeCallback
cb' IO (FunPtr C_StyleRealizeCallback)
-> (FunPtr C_StyleRealizeCallback
    -> IO (GClosure C_StyleRealizeCallback))
-> IO (GClosure C_StyleRealizeCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_StyleRealizeCallback
-> IO (GClosure C_StyleRealizeCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_StyleRealizeCallback ::
    StyleRealizeCallback ->
    C_StyleRealizeCallback
wrap_StyleRealizeCallback :: IO () -> C_StyleRealizeCallback
wrap_StyleRealizeCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onStyleRealize :: (IsStyle a, MonadIO m) => a -> StyleRealizeCallback -> m SignalHandlerId
onStyleRealize :: forall a (m :: * -> *).
(IsStyle a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onStyleRealize a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_StyleRealizeCallback
cb' = IO () -> C_StyleRealizeCallback
wrap_StyleRealizeCallback IO ()
cb
    FunPtr C_StyleRealizeCallback
cb'' <- C_StyleRealizeCallback -> IO (FunPtr C_StyleRealizeCallback)
mk_StyleRealizeCallback C_StyleRealizeCallback
cb'
    a
-> Text
-> FunPtr C_StyleRealizeCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"realize" FunPtr C_StyleRealizeCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterStyleRealize :: (IsStyle a, MonadIO m) => a -> StyleRealizeCallback -> m SignalHandlerId
afterStyleRealize :: forall a (m :: * -> *).
(IsStyle a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterStyleRealize a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_StyleRealizeCallback
cb' = IO () -> C_StyleRealizeCallback
wrap_StyleRealizeCallback IO ()
cb
    FunPtr C_StyleRealizeCallback
cb'' <- C_StyleRealizeCallback -> IO (FunPtr C_StyleRealizeCallback)
mk_StyleRealizeCallback C_StyleRealizeCallback
cb'
    a
-> Text
-> FunPtr C_StyleRealizeCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"realize" FunPtr C_StyleRealizeCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data StyleRealizeSignalInfo
instance SignalInfo StyleRealizeSignalInfo where
    type HaskellCallbackType StyleRealizeSignalInfo = StyleRealizeCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_StyleRealizeCallback cb
        cb'' <- mk_StyleRealizeCallback cb'
        connectSignalFunPtr obj "realize" cb'' connectMode detail
#endif
type StyleUnrealizeCallback =
    IO ()
noStyleUnrealizeCallback :: Maybe StyleUnrealizeCallback
noStyleUnrealizeCallback :: Maybe (IO ())
noStyleUnrealizeCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_StyleUnrealizeCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_StyleUnrealizeCallback :: C_StyleUnrealizeCallback -> IO (FunPtr C_StyleUnrealizeCallback)
genClosure_StyleUnrealize :: MonadIO m => StyleUnrealizeCallback -> m (GClosure C_StyleUnrealizeCallback)
genClosure_StyleUnrealize :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_StyleRealizeCallback)
genClosure_StyleUnrealize IO ()
cb = IO (GClosure C_StyleRealizeCallback)
-> m (GClosure C_StyleRealizeCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_StyleRealizeCallback)
 -> m (GClosure C_StyleRealizeCallback))
-> IO (GClosure C_StyleRealizeCallback)
-> m (GClosure C_StyleRealizeCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_StyleRealizeCallback
cb' = IO () -> C_StyleRealizeCallback
wrap_StyleUnrealizeCallback IO ()
cb
    C_StyleRealizeCallback -> IO (FunPtr C_StyleRealizeCallback)
mk_StyleUnrealizeCallback C_StyleRealizeCallback
cb' IO (FunPtr C_StyleRealizeCallback)
-> (FunPtr C_StyleRealizeCallback
    -> IO (GClosure C_StyleRealizeCallback))
-> IO (GClosure C_StyleRealizeCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_StyleRealizeCallback
-> IO (GClosure C_StyleRealizeCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_StyleUnrealizeCallback ::
    StyleUnrealizeCallback ->
    C_StyleUnrealizeCallback
wrap_StyleUnrealizeCallback :: IO () -> C_StyleRealizeCallback
wrap_StyleUnrealizeCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onStyleUnrealize :: (IsStyle a, MonadIO m) => a -> StyleUnrealizeCallback -> m SignalHandlerId
onStyleUnrealize :: forall a (m :: * -> *).
(IsStyle a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onStyleUnrealize a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_StyleRealizeCallback
cb' = IO () -> C_StyleRealizeCallback
wrap_StyleUnrealizeCallback IO ()
cb
    FunPtr C_StyleRealizeCallback
cb'' <- C_StyleRealizeCallback -> IO (FunPtr C_StyleRealizeCallback)
mk_StyleUnrealizeCallback C_StyleRealizeCallback
cb'
    a
-> Text
-> FunPtr C_StyleRealizeCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"unrealize" FunPtr C_StyleRealizeCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterStyleUnrealize :: (IsStyle a, MonadIO m) => a -> StyleUnrealizeCallback -> m SignalHandlerId
afterStyleUnrealize :: forall a (m :: * -> *).
(IsStyle a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterStyleUnrealize a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_StyleRealizeCallback
cb' = IO () -> C_StyleRealizeCallback
wrap_StyleUnrealizeCallback IO ()
cb
    FunPtr C_StyleRealizeCallback
cb'' <- C_StyleRealizeCallback -> IO (FunPtr C_StyleRealizeCallback)
mk_StyleUnrealizeCallback C_StyleRealizeCallback
cb'
    a
-> Text
-> FunPtr C_StyleRealizeCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"unrealize" FunPtr C_StyleRealizeCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data StyleUnrealizeSignalInfo
instance SignalInfo StyleUnrealizeSignalInfo where
    type HaskellCallbackType StyleUnrealizeSignalInfo = StyleUnrealizeCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_StyleUnrealizeCallback cb
        cb'' <- mk_StyleUnrealizeCallback cb'
        connectSignalFunPtr obj "unrealize" cb'' connectMode detail
#endif
   
   
   
getStyleContext :: (MonadIO m, IsStyle o) => o -> m (Maybe Gtk.StyleContext.StyleContext)
getStyleContext :: forall (m :: * -> *) o.
(MonadIO m, IsStyle o) =>
o -> m (Maybe StyleContext)
getStyleContext o
obj = IO (Maybe StyleContext) -> m (Maybe StyleContext)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe StyleContext) -> m (Maybe StyleContext))
-> IO (Maybe StyleContext) -> m (Maybe StyleContext)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr StyleContext -> StyleContext)
-> IO (Maybe StyleContext)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"context" ManagedPtr StyleContext -> StyleContext
Gtk.StyleContext.StyleContext
constructStyleContext :: (IsStyle o, MIO.MonadIO m, Gtk.StyleContext.IsStyleContext a) => a -> m (GValueConstruct o)
constructStyleContext :: forall o (m :: * -> *) a.
(IsStyle o, MonadIO m, IsStyleContext a) =>
a -> m (GValueConstruct o)
constructStyleContext a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"context" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data StyleContextPropertyInfo
instance AttrInfo StyleContextPropertyInfo where
    type AttrAllowedOps StyleContextPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint StyleContextPropertyInfo = IsStyle
    type AttrSetTypeConstraint StyleContextPropertyInfo = Gtk.StyleContext.IsStyleContext
    type AttrTransferTypeConstraint StyleContextPropertyInfo = Gtk.StyleContext.IsStyleContext
    type AttrTransferType StyleContextPropertyInfo = Gtk.StyleContext.StyleContext
    type AttrGetType StyleContextPropertyInfo = (Maybe Gtk.StyleContext.StyleContext)
    type AttrLabel StyleContextPropertyInfo = "context"
    type AttrOrigin StyleContextPropertyInfo = Style
    attrGet = getStyleContext
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gtk.StyleContext.StyleContext v
    attrConstruct = constructStyleContext
    attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Style
type instance O.AttributeList Style = StyleAttributeList
type StyleAttributeList = ('[ '("context", StyleContextPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
styleContext :: AttrLabelProxy "context"
styleContext = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Style = StyleSignalList
type StyleSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("realize", StyleRealizeSignalInfo), '("unrealize", StyleUnrealizeSignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_style_new" gtk_style_new :: 
    IO (Ptr Style)
{-# DEPRECATED styleNew ["(Since version 3.0)","Use t'GI.Gtk.Objects.StyleContext.StyleContext'"] #-}
styleNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Style
    
styleNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Style
styleNew  = IO Style -> m Style
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Style -> m Style) -> IO Style -> m Style
forall a b. (a -> b) -> a -> b
$ do
    Ptr Style
result <- IO (Ptr Style)
gtk_style_new
    Text -> Ptr Style -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"styleNew" Ptr Style
result
    Style
result' <- ((ManagedPtr Style -> Style) -> Ptr Style -> IO Style
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Style -> Style
Style) Ptr Style
result
    Style -> IO Style
forall (m :: * -> *) a. Monad m => a -> m a
return Style
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_style_apply_default_background" gtk_style_apply_default_background :: 
    Ptr Style ->                            
    Ptr Cairo.Context.Context ->            
    Ptr Gdk.Window.Window ->                
    CUInt ->                                
    Int32 ->                                
    Int32 ->                                
    Int32 ->                                
    Int32 ->                                
    IO ()
{-# DEPRECATED styleApplyDefaultBackground ["(Since version 3.0)","Use t'GI.Gtk.Objects.StyleContext.StyleContext' instead"] #-}
styleApplyDefaultBackground ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyle a, Gdk.Window.IsWindow b) =>
    a
    -> Cairo.Context.Context
    -> b
    -> Gtk.Enums.StateType
    -> Int32
    -> Int32
    -> Int32
    -> Int32
    -> m ()
styleApplyDefaultBackground :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsStyle a, IsWindow b) =>
a
-> Context
-> b
-> StateType
-> Int32
-> Int32
-> Int32
-> Int32
-> m ()
styleApplyDefaultBackground a
style Context
cr b
window StateType
stateType Int32
x Int32
y Int32
width Int32
height = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Style
style' <- a -> IO (Ptr Style)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
style
    Ptr Context
cr' <- Context -> IO (Ptr Context)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Context
cr
    Ptr Window
window' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
window
    let stateType' :: CUInt
stateType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (StateType -> Int) -> StateType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateType -> Int
forall a. Enum a => a -> Int
fromEnum) StateType
stateType
    Ptr Style
-> Ptr Context
-> Ptr Window
-> CUInt
-> Int32
-> Int32
-> Int32
-> Int32
-> IO ()
gtk_style_apply_default_background Ptr Style
style' Ptr Context
cr' Ptr Window
window' CUInt
stateType' Int32
x Int32
y Int32
width Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
style
    Context -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Context
cr
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
window
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StyleApplyDefaultBackgroundMethodInfo
instance (signature ~ (Cairo.Context.Context -> b -> Gtk.Enums.StateType -> Int32 -> Int32 -> Int32 -> Int32 -> m ()), MonadIO m, IsStyle a, Gdk.Window.IsWindow b) => O.OverloadedMethod StyleApplyDefaultBackgroundMethodInfo a signature where
    overloadedMethod = styleApplyDefaultBackground
instance O.OverloadedMethodInfo StyleApplyDefaultBackgroundMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Style.styleApplyDefaultBackground",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Style.html#v:styleApplyDefaultBackground"
        }
#endif
foreign import ccall "gtk_style_copy" gtk_style_copy :: 
    Ptr Style ->                            
    IO (Ptr Style)
{-# DEPRECATED styleCopy ["(Since version 3.0)","Use t'GI.Gtk.Objects.StyleContext.StyleContext' instead"] #-}
styleCopy ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyle a) =>
    a
    
    -> m Style
    
styleCopy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyle a) =>
a -> m Style
styleCopy a
style = IO Style -> m Style
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Style -> m Style) -> IO Style -> m Style
forall a b. (a -> b) -> a -> b
$ do
    Ptr Style
style' <- a -> IO (Ptr Style)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
style
    Ptr Style
result <- Ptr Style -> IO (Ptr Style)
gtk_style_copy Ptr Style
style'
    Text -> Ptr Style -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"styleCopy" Ptr Style
result
    Style
result' <- ((ManagedPtr Style -> Style) -> Ptr Style -> IO Style
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Style -> Style
Style) Ptr Style
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
style
    Style -> IO Style
forall (m :: * -> *) a. Monad m => a -> m a
return Style
result'
#if defined(ENABLE_OVERLOADING)
data StyleCopyMethodInfo
instance (signature ~ (m Style), MonadIO m, IsStyle a) => O.OverloadedMethod StyleCopyMethodInfo a signature where
    overloadedMethod = styleCopy
instance O.OverloadedMethodInfo StyleCopyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Style.styleCopy",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Style.html#v:styleCopy"
        }
#endif
foreign import ccall "gtk_style_detach" gtk_style_detach :: 
    Ptr Style ->                            
    IO ()
{-# DEPRECATED styleDetach ["(Since version 3.0)","Use t'GI.Gtk.Objects.StyleContext.StyleContext' instead"] #-}
styleDetach ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyle a) =>
    a
    
    -> m ()
styleDetach :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyle a) =>
a -> m ()
styleDetach a
style = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Style
style' <- a -> IO (Ptr Style)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
style
    Ptr Style -> IO ()
gtk_style_detach Ptr Style
style'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
style
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StyleDetachMethodInfo
instance (signature ~ (m ()), MonadIO m, IsStyle a) => O.OverloadedMethod StyleDetachMethodInfo a signature where
    overloadedMethod = styleDetach
instance O.OverloadedMethodInfo StyleDetachMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Style.styleDetach",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Style.html#v:styleDetach"
        }
#endif
foreign import ccall "gtk_style_get_style_property" gtk_style_get_style_property :: 
    Ptr Style ->                            
    CGType ->                               
    CString ->                              
    Ptr GValue ->                           
    IO ()
styleGetStyleProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyle a) =>
    a
    
    -> GType
    
    -> T.Text
    
    -> m (GValue)
styleGetStyleProperty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyle a) =>
a -> GType -> Text -> m GValue
styleGetStyleProperty a
style GType
widgetType Text
propertyName = 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
$ do
    Ptr Style
style' <- a -> IO (Ptr Style)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
style
    let widgetType' :: CGType
widgetType' = GType -> CGType
gtypeToCGType GType
widgetType
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    Ptr GValue
value <- Int -> IO (Ptr GValue)
forall a. Int -> IO (Ptr a)
SP.callocBytes Int
24 :: IO (Ptr GValue)
    Ptr Style -> CGType -> CString -> Ptr GValue -> IO ()
gtk_style_get_style_property Ptr Style
style' CGType
widgetType' CString
propertyName' Ptr GValue
value
    GValue
value' <- Ptr GValue -> IO GValue
B.GValue.wrapGValuePtr Ptr GValue
value
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
style
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
    GValue -> IO GValue
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
value'
#if defined(ENABLE_OVERLOADING)
data StyleGetStylePropertyMethodInfo
instance (signature ~ (GType -> T.Text -> m (GValue)), MonadIO m, IsStyle a) => O.OverloadedMethod StyleGetStylePropertyMethodInfo a signature where
    overloadedMethod = styleGetStyleProperty
instance O.OverloadedMethodInfo StyleGetStylePropertyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Style.styleGetStyleProperty",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Style.html#v:styleGetStyleProperty"
        }
#endif
foreign import ccall "gtk_style_has_context" gtk_style_has_context :: 
    Ptr Style ->                            
    IO CInt
styleHasContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyle a) =>
    a
    
    -> m Bool
    
styleHasContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyle a) =>
a -> m Bool
styleHasContext a
style = 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 Style
style' <- a -> IO (Ptr Style)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
style
    CInt
result <- Ptr Style -> IO CInt
gtk_style_has_context Ptr Style
style'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
style
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data StyleHasContextMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsStyle a) => O.OverloadedMethod StyleHasContextMethodInfo a signature where
    overloadedMethod = styleHasContext
instance O.OverloadedMethodInfo StyleHasContextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Style.styleHasContext",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Style.html#v:styleHasContext"
        }
#endif
foreign import ccall "gtk_style_lookup_color" gtk_style_lookup_color :: 
    Ptr Style ->                            
    CString ->                              
    Ptr Gdk.Color.Color ->                  
    IO CInt
{-# DEPRECATED styleLookupColor ["(Since version 3.0)","Use 'GI.Gtk.Objects.StyleContext.styleContextLookupColor' instead"] #-}
styleLookupColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyle a) =>
    a
    
    -> T.Text
    
    -> m ((Bool, Gdk.Color.Color))
    
styleLookupColor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyle a) =>
a -> Text -> m (Bool, Color)
styleLookupColor a
style Text
colorName = IO (Bool, Color) -> m (Bool, Color)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Color) -> m (Bool, Color))
-> IO (Bool, Color) -> m (Bool, Color)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Style
style' <- a -> IO (Ptr Style)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
style
    CString
colorName' <- Text -> IO CString
textToCString Text
colorName
    Ptr Color
color <- Int -> IO (Ptr Color)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
12 :: IO (Ptr Gdk.Color.Color)
    CInt
result <- Ptr Style -> CString -> Ptr Color -> IO CInt
gtk_style_lookup_color Ptr Style
style' CString
colorName' Ptr Color
color
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Color
color' <- ((ManagedPtr Color -> Color) -> Ptr Color -> IO Color
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Color -> Color
Gdk.Color.Color) Ptr Color
color
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
style
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
colorName'
    (Bool, Color) -> IO (Bool, Color)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Color
color')
#if defined(ENABLE_OVERLOADING)
data StyleLookupColorMethodInfo
instance (signature ~ (T.Text -> m ((Bool, Gdk.Color.Color))), MonadIO m, IsStyle a) => O.OverloadedMethod StyleLookupColorMethodInfo a signature where
    overloadedMethod = styleLookupColor
instance O.OverloadedMethodInfo StyleLookupColorMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Style.styleLookupColor",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Style.html#v:styleLookupColor"
        }
#endif
foreign import ccall "gtk_style_lookup_icon_set" gtk_style_lookup_icon_set :: 
    Ptr Style ->                            
    CString ->                              
    IO (Ptr Gtk.IconSet.IconSet)
{-# DEPRECATED styleLookupIconSet ["(Since version 3.0)","Use 'GI.Gtk.Objects.StyleContext.styleContextLookupIconSet' instead"] #-}
styleLookupIconSet ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyle a) =>
    a
    
    -> T.Text
    
    -> m Gtk.IconSet.IconSet
    
styleLookupIconSet :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyle a) =>
a -> Text -> m IconSet
styleLookupIconSet a
style Text
stockId = IO IconSet -> m IconSet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IconSet -> m IconSet) -> IO IconSet -> m IconSet
forall a b. (a -> b) -> a -> b
$ do
    Ptr Style
style' <- a -> IO (Ptr Style)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
style
    CString
stockId' <- Text -> IO CString
textToCString Text
stockId
    Ptr IconSet
result <- Ptr Style -> CString -> IO (Ptr IconSet)
gtk_style_lookup_icon_set Ptr Style
style' CString
stockId'
    Text -> Ptr IconSet -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"styleLookupIconSet" Ptr IconSet
result
    IconSet
result' <- ((ManagedPtr IconSet -> IconSet) -> Ptr IconSet -> IO IconSet
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr IconSet -> IconSet
Gtk.IconSet.IconSet) Ptr IconSet
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
style
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
stockId'
    IconSet -> IO IconSet
forall (m :: * -> *) a. Monad m => a -> m a
return IconSet
result'
#if defined(ENABLE_OVERLOADING)
data StyleLookupIconSetMethodInfo
instance (signature ~ (T.Text -> m Gtk.IconSet.IconSet), MonadIO m, IsStyle a) => O.OverloadedMethod StyleLookupIconSetMethodInfo a signature where
    overloadedMethod = styleLookupIconSet
instance O.OverloadedMethodInfo StyleLookupIconSetMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Style.styleLookupIconSet",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Style.html#v:styleLookupIconSet"
        }
#endif
foreign import ccall "gtk_style_render_icon" gtk_style_render_icon :: 
    Ptr Style ->                            
    Ptr Gtk.IconSource.IconSource ->        
    CUInt ->                                
    CUInt ->                                
    Int32 ->                                
    Ptr Gtk.Widget.Widget ->                
    CString ->                              
    IO (Ptr GdkPixbuf.Pixbuf.Pixbuf)
{-# DEPRECATED styleRenderIcon ["(Since version 3.0)","Use 'GI.Gtk.Functions.renderIconPixbuf' instead"] #-}
styleRenderIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyle a, Gtk.Widget.IsWidget b) =>
    a
    
    -> Gtk.IconSource.IconSource
    
    -> Gtk.Enums.TextDirection
    
    -> Gtk.Enums.StateType
    
    -> Int32
    
    
    
    -> Maybe (b)
    
    -> Maybe (T.Text)
    
    -> m GdkPixbuf.Pixbuf.Pixbuf
    
    
styleRenderIcon :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsStyle a, IsWidget b) =>
a
-> IconSource
-> TextDirection
-> StateType
-> Int32
-> Maybe b
-> Maybe Text
-> m Pixbuf
styleRenderIcon a
style IconSource
source TextDirection
direction StateType
state Int32
size Maybe b
widget Maybe Text
detail = IO Pixbuf -> m Pixbuf
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pixbuf -> m Pixbuf) -> IO Pixbuf -> m Pixbuf
forall a b. (a -> b) -> a -> b
$ do
    Ptr Style
style' <- a -> IO (Ptr Style)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
style
    Ptr IconSource
source' <- IconSource -> IO (Ptr IconSource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr IconSource
source
    let direction' :: CUInt
direction' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (TextDirection -> Int) -> TextDirection -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextDirection -> Int
forall a. Enum a => a -> Int
fromEnum) TextDirection
direction
    let state' :: CUInt
state' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (StateType -> Int) -> StateType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateType -> Int
forall a. Enum a => a -> Int
fromEnum) StateType
state
    Ptr Widget
maybeWidget <- case Maybe b
widget of
        Maybe b
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just b
jWidget -> do
            Ptr Widget
jWidget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jWidget
            Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jWidget'
    CString
maybeDetail <- case Maybe Text
detail of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jDetail -> do
            CString
jDetail' <- Text -> IO CString
textToCString Text
jDetail
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jDetail'
    Ptr Pixbuf
result <- Ptr Style
-> Ptr IconSource
-> CUInt
-> CUInt
-> Int32
-> Ptr Widget
-> CString
-> IO (Ptr Pixbuf)
gtk_style_render_icon Ptr Style
style' Ptr IconSource
source' CUInt
direction' CUInt
state' Int32
size Ptr Widget
maybeWidget CString
maybeDetail
    Text -> Ptr Pixbuf -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"styleRenderIcon" Ptr Pixbuf
result
    Pixbuf
result' <- ((ManagedPtr Pixbuf -> Pixbuf) -> Ptr Pixbuf -> IO Pixbuf
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pixbuf -> Pixbuf
GdkPixbuf.Pixbuf.Pixbuf) Ptr Pixbuf
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
style
    IconSource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr IconSource
source
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
widget b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeDetail
    Pixbuf -> IO Pixbuf
forall (m :: * -> *) a. Monad m => a -> m a
return Pixbuf
result'
#if defined(ENABLE_OVERLOADING)
data StyleRenderIconMethodInfo
instance (signature ~ (Gtk.IconSource.IconSource -> Gtk.Enums.TextDirection -> Gtk.Enums.StateType -> Int32 -> Maybe (b) -> Maybe (T.Text) -> m GdkPixbuf.Pixbuf.Pixbuf), MonadIO m, IsStyle a, Gtk.Widget.IsWidget b) => O.OverloadedMethod StyleRenderIconMethodInfo a signature where
    overloadedMethod = styleRenderIcon
instance O.OverloadedMethodInfo StyleRenderIconMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Style.styleRenderIcon",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Style.html#v:styleRenderIcon"
        }
#endif
foreign import ccall "gtk_style_set_background" gtk_style_set_background :: 
    Ptr Style ->                            
    Ptr Gdk.Window.Window ->                
    CUInt ->                                
    IO ()
{-# DEPRECATED styleSetBackground ["(Since version 3.0)","Use 'GI.Gtk.Objects.StyleContext.styleContextSetBackground' instead"] #-}
styleSetBackground ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyle a, Gdk.Window.IsWindow b) =>
    a
    
    -> b
    
    -> Gtk.Enums.StateType
    
    -> m ()
styleSetBackground :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsStyle a, IsWindow b) =>
a -> b -> StateType -> m ()
styleSetBackground a
style b
window StateType
stateType = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Style
style' <- a -> IO (Ptr Style)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
style
    Ptr Window
window' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
window
    let stateType' :: CUInt
stateType' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (StateType -> Int) -> StateType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateType -> Int
forall a. Enum a => a -> Int
fromEnum) StateType
stateType
    Ptr Style -> Ptr Window -> CUInt -> IO ()
gtk_style_set_background Ptr Style
style' Ptr Window
window' CUInt
stateType'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
style
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
window
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data StyleSetBackgroundMethodInfo
instance (signature ~ (b -> Gtk.Enums.StateType -> m ()), MonadIO m, IsStyle a, Gdk.Window.IsWindow b) => O.OverloadedMethod StyleSetBackgroundMethodInfo a signature where
    overloadedMethod = styleSetBackground
instance O.OverloadedMethodInfo StyleSetBackgroundMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Style.styleSetBackground",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-3.0.37/docs/GI-Gtk-Objects-Style.html#v:styleSetBackground"
        }
#endif