{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- GtkStyleProvider is an interface used to provide style information to a t'GI.Gtk.Objects.StyleContext.StyleContext'.
-- See 'GI.Gtk.Objects.StyleContext.styleContextAddProvider' and 'GI.Gtk.Objects.StyleContext.styleContextAddProviderForScreen'.

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

module GI.Gtk.Interfaces.StyleProvider
    ( 

-- * Exported types
    StyleProvider(..)                       ,
    IsStyleProvider                         ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveStyleProviderMethod              ,
#endif


-- ** getIconFactory #method:getIconFactory#

#if defined(ENABLE_OVERLOADING)
    StyleProviderGetIconFactoryMethodInfo   ,
#endif
    styleProviderGetIconFactory             ,


-- ** getStyle #method:getStyle#

#if defined(ENABLE_OVERLOADING)
    StyleProviderGetStyleMethodInfo         ,
#endif
    styleProviderGetStyle                   ,


-- ** getStyleProperty #method:getStyleProperty#

#if defined(ENABLE_OVERLOADING)
    StyleProviderGetStylePropertyMethodInfo ,
#endif
    styleProviderGetStyleProperty           ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified 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 {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Objects.IconFactory as Gtk.IconFactory
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleProperties as Gtk.StyleProperties
import {-# SOURCE #-} qualified GI.Gtk.Structs.WidgetPath as Gtk.WidgetPath

-- interface StyleProvider 
-- | Memory-managed wrapper type.
newtype StyleProvider = StyleProvider (ManagedPtr StyleProvider)
    deriving (StyleProvider -> StyleProvider -> Bool
(StyleProvider -> StyleProvider -> Bool)
-> (StyleProvider -> StyleProvider -> Bool) -> Eq StyleProvider
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StyleProvider -> StyleProvider -> Bool
$c/= :: StyleProvider -> StyleProvider -> Bool
== :: StyleProvider -> StyleProvider -> Bool
$c== :: StyleProvider -> StyleProvider -> Bool
Eq)
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList StyleProvider = StyleProviderSignalList
type StyleProviderSignalList = ('[ ] :: [(Symbol, *)])

#endif

-- | Type class for types which implement `StyleProvider`.
class (ManagedPtrNewtype o, O.IsDescendantOf StyleProvider o) => IsStyleProvider o
instance (ManagedPtrNewtype o, O.IsDescendantOf StyleProvider o) => IsStyleProvider o
-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance WrappedPtr StyleProvider where
    wrappedPtrCalloc :: IO (Ptr StyleProvider)
wrappedPtrCalloc = Ptr StyleProvider -> IO (Ptr StyleProvider)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr StyleProvider
forall a. Ptr a
nullPtr
    wrappedPtrCopy :: StyleProvider -> IO StyleProvider
wrappedPtrCopy = StyleProvider -> IO StyleProvider
forall (m :: * -> *) a. Monad m => a -> m a
return
    wrappedPtrFree :: Maybe (GDestroyNotify StyleProvider)
wrappedPtrFree = Maybe (GDestroyNotify StyleProvider)
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
type family ResolveStyleProviderMethod (t :: Symbol) (o :: *) :: * where
    ResolveStyleProviderMethod "getIconFactory" o = StyleProviderGetIconFactoryMethodInfo
    ResolveStyleProviderMethod "getStyle" o = StyleProviderGetStyleMethodInfo
    ResolveStyleProviderMethod "getStyleProperty" o = StyleProviderGetStylePropertyMethodInfo
    ResolveStyleProviderMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveStyleProviderMethod t StyleProvider, O.MethodInfo info StyleProvider p) => OL.IsLabel t (StyleProvider -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- method StyleProvider::get_icon_factory
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "provider"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StyleProvider" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStyleProvider"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GtkWidgetPath to query"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "IconFactory" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_style_provider_get_icon_factory" gtk_style_provider_get_icon_factory :: 
    Ptr StyleProvider ->                    -- provider : TInterface (Name {namespace = "Gtk", name = "StyleProvider"})
    Ptr Gtk.WidgetPath.WidgetPath ->        -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    IO (Ptr Gtk.IconFactory.IconFactory)

{-# DEPRECATED styleProviderGetIconFactory ["(Since version 3.8)","Will always return 'P.Nothing' for all GTK-provided style providers."] #-}
-- | Returns the t'GI.Gtk.Objects.IconFactory.IconFactory' defined to be in use for /@path@/, or 'P.Nothing' if none
-- is defined.
-- 
-- /Since: 3.0/
styleProviderGetIconFactory ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleProvider a) =>
    a
    -- ^ /@provider@/: a t'GI.Gtk.Interfaces.StyleProvider.StyleProvider'
    -> Gtk.WidgetPath.WidgetPath
    -- ^ /@path@/: t'GI.Gtk.Structs.WidgetPath.WidgetPath' to query
    -> m (Maybe Gtk.IconFactory.IconFactory)
    -- ^ __Returns:__ The icon factory to use for /@path@/, or 'P.Nothing'
styleProviderGetIconFactory :: a -> WidgetPath -> m (Maybe IconFactory)
styleProviderGetIconFactory a
provider WidgetPath
path = IO (Maybe IconFactory) -> m (Maybe IconFactory)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe IconFactory) -> m (Maybe IconFactory))
-> IO (Maybe IconFactory) -> m (Maybe IconFactory)
forall a b. (a -> b) -> a -> b
$ do
    Ptr StyleProvider
provider' <- a -> IO (Ptr StyleProvider)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
provider
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Ptr IconFactory
result <- Ptr StyleProvider -> Ptr WidgetPath -> IO (Ptr IconFactory)
gtk_style_provider_get_icon_factory Ptr StyleProvider
provider' Ptr WidgetPath
path'
    Maybe IconFactory
maybeResult <- Ptr IconFactory
-> (Ptr IconFactory -> IO IconFactory) -> IO (Maybe IconFactory)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr IconFactory
result ((Ptr IconFactory -> IO IconFactory) -> IO (Maybe IconFactory))
-> (Ptr IconFactory -> IO IconFactory) -> IO (Maybe IconFactory)
forall a b. (a -> b) -> a -> b
$ \Ptr IconFactory
result' -> do
        IconFactory
result'' <- ((ManagedPtr IconFactory -> IconFactory)
-> Ptr IconFactory -> IO IconFactory
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr IconFactory -> IconFactory
Gtk.IconFactory.IconFactory) Ptr IconFactory
result'
        IconFactory -> IO IconFactory
forall (m :: * -> *) a. Monad m => a -> m a
return IconFactory
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
provider
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    Maybe IconFactory -> IO (Maybe IconFactory)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe IconFactory
maybeResult

#if defined(ENABLE_OVERLOADING)
data StyleProviderGetIconFactoryMethodInfo
instance (signature ~ (Gtk.WidgetPath.WidgetPath -> m (Maybe Gtk.IconFactory.IconFactory)), MonadIO m, IsStyleProvider a) => O.MethodInfo StyleProviderGetIconFactoryMethodInfo a signature where
    overloadedMethod = styleProviderGetIconFactory

#endif

-- method StyleProvider::get_style
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "provider"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StyleProvider" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStyleProvider"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GtkWidgetPath to query"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "StyleProperties" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_style_provider_get_style" gtk_style_provider_get_style :: 
    Ptr StyleProvider ->                    -- provider : TInterface (Name {namespace = "Gtk", name = "StyleProvider"})
    Ptr Gtk.WidgetPath.WidgetPath ->        -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    IO (Ptr Gtk.StyleProperties.StyleProperties)

{-# DEPRECATED styleProviderGetStyle ["(Since version 3.8)","Will always return 'P.Nothing' for all GTK-provided style providers","    as the interface cannot correctly work the way CSS is specified."] #-}
-- | Returns the style settings affecting a widget defined by /@path@/, or 'P.Nothing' if
-- /@provider@/ doesn’t contemplate styling /@path@/.
-- 
-- /Since: 3.0/
styleProviderGetStyle ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleProvider a) =>
    a
    -- ^ /@provider@/: a t'GI.Gtk.Interfaces.StyleProvider.StyleProvider'
    -> Gtk.WidgetPath.WidgetPath
    -- ^ /@path@/: t'GI.Gtk.Structs.WidgetPath.WidgetPath' to query
    -> m (Maybe Gtk.StyleProperties.StyleProperties)
    -- ^ __Returns:__ a t'GI.Gtk.Objects.StyleProperties.StyleProperties' containing the
    -- style settings affecting /@path@/
styleProviderGetStyle :: a -> WidgetPath -> m (Maybe StyleProperties)
styleProviderGetStyle a
provider WidgetPath
path = IO (Maybe StyleProperties) -> m (Maybe StyleProperties)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe StyleProperties) -> m (Maybe StyleProperties))
-> IO (Maybe StyleProperties) -> m (Maybe StyleProperties)
forall a b. (a -> b) -> a -> b
$ do
    Ptr StyleProvider
provider' <- a -> IO (Ptr StyleProvider)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
provider
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    Ptr StyleProperties
result <- Ptr StyleProvider -> Ptr WidgetPath -> IO (Ptr StyleProperties)
gtk_style_provider_get_style Ptr StyleProvider
provider' Ptr WidgetPath
path'
    Maybe StyleProperties
maybeResult <- Ptr StyleProperties
-> (Ptr StyleProperties -> IO StyleProperties)
-> IO (Maybe StyleProperties)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr StyleProperties
result ((Ptr StyleProperties -> IO StyleProperties)
 -> IO (Maybe StyleProperties))
-> (Ptr StyleProperties -> IO StyleProperties)
-> IO (Maybe StyleProperties)
forall a b. (a -> b) -> a -> b
$ \Ptr StyleProperties
result' -> do
        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
Gtk.StyleProperties.StyleProperties) Ptr StyleProperties
result'
        StyleProperties -> IO StyleProperties
forall (m :: * -> *) a. Monad m => a -> m a
return StyleProperties
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
provider
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    Maybe StyleProperties -> IO (Maybe StyleProperties)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe StyleProperties
maybeResult

#if defined(ENABLE_OVERLOADING)
data StyleProviderGetStyleMethodInfo
instance (signature ~ (Gtk.WidgetPath.WidgetPath -> m (Maybe Gtk.StyleProperties.StyleProperties)), MonadIO m, IsStyleProvider a) => O.MethodInfo StyleProviderGetStyleMethodInfo a signature where
    overloadedMethod = styleProviderGetStyle

#endif

-- method StyleProvider::get_style_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "provider"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StyleProvider" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStyleProvider"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "WidgetPath" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GtkWidgetPath to query"
--                 , 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 query the style property for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pspec"
--           , argType = TParamSpec
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The #GParamSpec to query"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "Value" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the property value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_style_provider_get_style_property" gtk_style_provider_get_style_property :: 
    Ptr StyleProvider ->                    -- provider : TInterface (Name {namespace = "Gtk", name = "StyleProvider"})
    Ptr Gtk.WidgetPath.WidgetPath ->        -- path : TInterface (Name {namespace = "Gtk", name = "WidgetPath"})
    CUInt ->                                -- state : TInterface (Name {namespace = "Gtk", name = "StateFlags"})
    Ptr GParamSpec ->                       -- pspec : TParamSpec
    Ptr GValue ->                           -- value : TInterface (Name {namespace = "GObject", name = "Value"})
    IO CInt

-- | Looks up a widget style property as defined by /@provider@/ for
-- the widget represented by /@path@/.
-- 
-- /Since: 3.0/
styleProviderGetStyleProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleProvider a) =>
    a
    -- ^ /@provider@/: a t'GI.Gtk.Interfaces.StyleProvider.StyleProvider'
    -> Gtk.WidgetPath.WidgetPath
    -- ^ /@path@/: t'GI.Gtk.Structs.WidgetPath.WidgetPath' to query
    -> [Gtk.Flags.StateFlags]
    -- ^ /@state@/: state to query the style property for
    -> GParamSpec
    -- ^ /@pspec@/: The t'GI.GObject.Objects.ParamSpec.ParamSpec' to query
    -> m ((Bool, GValue))
    -- ^ __Returns:__ 'P.True' if the property was found and has a value, 'P.False' otherwise
styleProviderGetStyleProperty :: a -> WidgetPath -> [StateFlags] -> GParamSpec -> m (Bool, GValue)
styleProviderGetStyleProperty a
provider WidgetPath
path [StateFlags]
state GParamSpec
pspec = IO (Bool, GValue) -> m (Bool, GValue)
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 StyleProvider
provider' <- a -> IO (Ptr StyleProvider)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
provider
    Ptr WidgetPath
path' <- WidgetPath -> IO (Ptr WidgetPath)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr WidgetPath
path
    let state' :: CUInt
state' = [StateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [StateFlags]
state
    Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
    Ptr GValue
value <- Int -> IO (Ptr GValue)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes Int
24 :: IO (Ptr GValue)
    CInt
result <- Ptr StyleProvider
-> Ptr WidgetPath
-> CUInt
-> Ptr GParamSpec
-> Ptr GValue
-> IO CInt
gtk_style_provider_get_style_property Ptr StyleProvider
provider' Ptr WidgetPath
path' CUInt
state' Ptr GParamSpec
pspec' Ptr GValue
value
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    GValue
value' <- ((ManagedPtr GValue -> GValue) -> Ptr GValue -> IO GValue
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr GValue -> GValue
GValue) Ptr GValue
value
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
provider
    WidgetPath -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr WidgetPath
path
    GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
    (Bool, GValue) -> IO (Bool, GValue)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', GValue
value')

#if defined(ENABLE_OVERLOADING)
data StyleProviderGetStylePropertyMethodInfo
instance (signature ~ (Gtk.WidgetPath.WidgetPath -> [Gtk.Flags.StateFlags] -> GParamSpec -> m ((Bool, GValue))), MonadIO m, IsStyleProvider a) => O.MethodInfo StyleProviderGetStylePropertyMethodInfo a signature where
    overloadedMethod = styleProviderGetStyleProperty

#endif