{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gtk.Objects.ThemingEngine.ThemingEngine' was the object used for rendering themed content
-- in GTK+ widgets. It used to allow overriding GTK+\'s default
-- implementation of rendering functions by allowing engines to be
-- loaded as modules.
-- 
-- t'GI.Gtk.Objects.ThemingEngine.ThemingEngine' has been deprecated in GTK+ 3.14 and will be
-- ignored for rendering. The advancements in CSS theming are good
-- enough to allow themers to achieve their goals without the need
-- to modify source code.

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

module GI.Gtk.Objects.ThemingEngine
    ( 

-- * Exported types
    ThemingEngine(..)                       ,
    IsThemingEngine                         ,
    toThemingEngine                         ,
    noThemingEngine                         ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveThemingEngineMethod              ,
#endif


-- ** getBackgroundColor #method:getBackgroundColor#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineGetBackgroundColorMethodInfo,
#endif
    themingEngineGetBackgroundColor         ,


-- ** getBorder #method:getBorder#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineGetBorderMethodInfo        ,
#endif
    themingEngineGetBorder                  ,


-- ** getBorderColor #method:getBorderColor#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineGetBorderColorMethodInfo   ,
#endif
    themingEngineGetBorderColor             ,


-- ** getColor #method:getColor#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineGetColorMethodInfo         ,
#endif
    themingEngineGetColor                   ,


-- ** getDirection #method:getDirection#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineGetDirectionMethodInfo     ,
#endif
    themingEngineGetDirection               ,


-- ** getFont #method:getFont#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineGetFontMethodInfo          ,
#endif
    themingEngineGetFont                    ,


-- ** getJunctionSides #method:getJunctionSides#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineGetJunctionSidesMethodInfo ,
#endif
    themingEngineGetJunctionSides           ,


-- ** getMargin #method:getMargin#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineGetMarginMethodInfo        ,
#endif
    themingEngineGetMargin                  ,


-- ** getPadding #method:getPadding#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineGetPaddingMethodInfo       ,
#endif
    themingEngineGetPadding                 ,


-- ** getPath #method:getPath#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineGetPathMethodInfo          ,
#endif
    themingEngineGetPath                    ,


-- ** getProperty #method:getProperty#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineGetPropertyMethodInfo      ,
#endif
    themingEngineGetProperty                ,


-- ** getScreen #method:getScreen#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineGetScreenMethodInfo        ,
#endif
    themingEngineGetScreen                  ,


-- ** getState #method:getState#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineGetStateMethodInfo         ,
#endif
    themingEngineGetState                   ,


-- ** getStyleProperty #method:getStyleProperty#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineGetStylePropertyMethodInfo ,
#endif
    themingEngineGetStyleProperty           ,


-- ** hasClass #method:hasClass#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineHasClassMethodInfo         ,
#endif
    themingEngineHasClass                   ,


-- ** hasRegion #method:hasRegion#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineHasRegionMethodInfo        ,
#endif
    themingEngineHasRegion                  ,


-- ** load #method:load#

    themingEngineLoad                       ,


-- ** lookupColor #method:lookupColor#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineLookupColorMethodInfo      ,
#endif
    themingEngineLookupColor                ,


-- ** stateIsRunning #method:stateIsRunning#

#if defined(ENABLE_OVERLOADING)
    ThemingEngineStateIsRunningMethodInfo   ,
#endif
    themingEngineStateIsRunning             ,




 -- * Properties
-- ** name #attr:name#
-- | The theming engine name, this name will be used when registering
-- custom properties, for a theming engine named \"Clearlooks\" registering
-- a \"glossy\" custom property, it could be referenced in the CSS file as
-- 
-- >
-- >-Clearlooks-glossy: true;
-- 
-- 
-- /Since: 3.0/

#if defined(ENABLE_OVERLOADING)
    ThemingEngineNamePropertyInfo           ,
#endif
    constructThemingEngineName              ,
    getThemingEngineName                    ,
#if defined(ENABLE_OVERLOADING)
    themingEngineName                       ,
#endif




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Screen as Gdk.Screen
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Structs.Border as Gtk.Border
import {-# SOURCE #-} qualified GI.Gtk.Structs.WidgetPath as Gtk.WidgetPath
import qualified GI.Pango.Structs.FontDescription as Pango.FontDescription

-- | Memory-managed wrapper type.
newtype ThemingEngine = ThemingEngine (ManagedPtr ThemingEngine)
    deriving (ThemingEngine -> ThemingEngine -> Bool
(ThemingEngine -> ThemingEngine -> Bool)
-> (ThemingEngine -> ThemingEngine -> Bool) -> Eq ThemingEngine
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ThemingEngine -> ThemingEngine -> Bool
$c/= :: ThemingEngine -> ThemingEngine -> Bool
== :: ThemingEngine -> ThemingEngine -> Bool
$c== :: ThemingEngine -> ThemingEngine -> Bool
Eq)
foreign import ccall "gtk_theming_engine_get_type"
    c_gtk_theming_engine_get_type :: IO GType

instance GObject ThemingEngine where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_theming_engine_get_type
    

-- | Convert 'ThemingEngine' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue ThemingEngine where
    toGValue :: ThemingEngine -> IO GValue
toGValue o :: ThemingEngine
o = do
        GType
gtype <- IO GType
c_gtk_theming_engine_get_type
        ThemingEngine -> (Ptr ThemingEngine -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ThemingEngine
o (GType
-> (GValue -> Ptr ThemingEngine -> IO ())
-> Ptr ThemingEngine
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr ThemingEngine -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO ThemingEngine
fromGValue gv :: GValue
gv = do
        Ptr ThemingEngine
ptr <- GValue -> IO (Ptr ThemingEngine)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr ThemingEngine)
        (ManagedPtr ThemingEngine -> ThemingEngine)
-> Ptr ThemingEngine -> IO ThemingEngine
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ThemingEngine -> ThemingEngine
ThemingEngine Ptr ThemingEngine
ptr
        
    

-- | Type class for types which can be safely cast to `ThemingEngine`, for instance with `toThemingEngine`.
class (GObject o, O.IsDescendantOf ThemingEngine o) => IsThemingEngine o
instance (GObject o, O.IsDescendantOf ThemingEngine o) => IsThemingEngine o

instance O.HasParentTypes ThemingEngine
type instance O.ParentTypes ThemingEngine = '[GObject.Object.Object]

-- | Cast to `ThemingEngine`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toThemingEngine :: (MonadIO m, IsThemingEngine o) => o -> m ThemingEngine
toThemingEngine :: o -> m ThemingEngine
toThemingEngine = IO ThemingEngine -> m ThemingEngine
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ThemingEngine -> m ThemingEngine)
-> (o -> IO ThemingEngine) -> o -> m ThemingEngine
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ThemingEngine -> ThemingEngine)
-> o -> IO ThemingEngine
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr ThemingEngine -> ThemingEngine
ThemingEngine

-- | A convenience alias for `Nothing` :: `Maybe` `ThemingEngine`.
noThemingEngine :: Maybe ThemingEngine
noThemingEngine :: Maybe ThemingEngine
noThemingEngine = Maybe ThemingEngine
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveThemingEngineMethod (t :: Symbol) (o :: *) :: * where
    ResolveThemingEngineMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveThemingEngineMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveThemingEngineMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveThemingEngineMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveThemingEngineMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveThemingEngineMethod "hasClass" o = ThemingEngineHasClassMethodInfo
    ResolveThemingEngineMethod "hasRegion" o = ThemingEngineHasRegionMethodInfo
    ResolveThemingEngineMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveThemingEngineMethod "lookupColor" o = ThemingEngineLookupColorMethodInfo
    ResolveThemingEngineMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveThemingEngineMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveThemingEngineMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveThemingEngineMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveThemingEngineMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveThemingEngineMethod "stateIsRunning" o = ThemingEngineStateIsRunningMethodInfo
    ResolveThemingEngineMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveThemingEngineMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveThemingEngineMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveThemingEngineMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveThemingEngineMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveThemingEngineMethod "getBackgroundColor" o = ThemingEngineGetBackgroundColorMethodInfo
    ResolveThemingEngineMethod "getBorder" o = ThemingEngineGetBorderMethodInfo
    ResolveThemingEngineMethod "getBorderColor" o = ThemingEngineGetBorderColorMethodInfo
    ResolveThemingEngineMethod "getColor" o = ThemingEngineGetColorMethodInfo
    ResolveThemingEngineMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveThemingEngineMethod "getDirection" o = ThemingEngineGetDirectionMethodInfo
    ResolveThemingEngineMethod "getFont" o = ThemingEngineGetFontMethodInfo
    ResolveThemingEngineMethod "getJunctionSides" o = ThemingEngineGetJunctionSidesMethodInfo
    ResolveThemingEngineMethod "getMargin" o = ThemingEngineGetMarginMethodInfo
    ResolveThemingEngineMethod "getPadding" o = ThemingEngineGetPaddingMethodInfo
    ResolveThemingEngineMethod "getPath" o = ThemingEngineGetPathMethodInfo
    ResolveThemingEngineMethod "getProperty" o = ThemingEngineGetPropertyMethodInfo
    ResolveThemingEngineMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveThemingEngineMethod "getScreen" o = ThemingEngineGetScreenMethodInfo
    ResolveThemingEngineMethod "getState" o = ThemingEngineGetStateMethodInfo
    ResolveThemingEngineMethod "getStyleProperty" o = ThemingEngineGetStylePropertyMethodInfo
    ResolveThemingEngineMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveThemingEngineMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveThemingEngineMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveThemingEngineMethod l o = O.MethodResolutionFailed l o

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

#endif

-- VVV Prop "name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' themingEngine #name
-- @
getThemingEngineName :: (MonadIO m, IsThemingEngine o) => o -> m (Maybe T.Text)
getThemingEngineName :: o -> m (Maybe Text)
getThemingEngineName obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "name"

-- | Construct a `GValueConstruct` with valid value for the “@name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructThemingEngineName :: (IsThemingEngine o) => T.Text -> IO (GValueConstruct o)
constructThemingEngineName :: Text -> IO (GValueConstruct o)
constructThemingEngineName val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

#if defined(ENABLE_OVERLOADING)
data ThemingEngineNamePropertyInfo
instance AttrInfo ThemingEngineNamePropertyInfo where
    type AttrAllowedOps ThemingEngineNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ThemingEngineNamePropertyInfo = IsThemingEngine
    type AttrSetTypeConstraint ThemingEngineNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ThemingEngineNamePropertyInfo = (~) T.Text
    type AttrTransferType ThemingEngineNamePropertyInfo = T.Text
    type AttrGetType ThemingEngineNamePropertyInfo = (Maybe T.Text)
    type AttrLabel ThemingEngineNamePropertyInfo = "name"
    type AttrOrigin ThemingEngineNamePropertyInfo = ThemingEngine
    attrGet = getThemingEngineName
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructThemingEngineName
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ThemingEngine
type instance O.AttributeList ThemingEngine = ThemingEngineAttributeList
type ThemingEngineAttributeList = ('[ '("name", ThemingEngineNamePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
themingEngineName :: AttrLabelProxy "name"
themingEngineName = AttrLabelProxy

#endif

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

#endif

-- method ThemingEngine::get_background_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ThemingEngine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkThemingEngine"
--                 , 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 color for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "color"
--           , argType = TInterface Name { namespace = "Gdk" , name = "RGBA" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return value for the background color"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_theming_engine_get_background_color" gtk_theming_engine_get_background_color :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    CUInt ->                                -- state : TInterface (Name {namespace = "Gtk", name = "StateFlags"})
    Ptr Gdk.RGBA.RGBA ->                    -- color : TInterface (Name {namespace = "Gdk", name = "RGBA"})
    IO ()

{-# DEPRECATED themingEngineGetBackgroundColor ["(Since version 3.14)"] #-}
-- | Gets the background color for a given state.
-- 
-- /Since: 3.0/
themingEngineGetBackgroundColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> [Gtk.Flags.StateFlags]
    -- ^ /@state@/: state to retrieve the color for
    -> m (Gdk.RGBA.RGBA)
themingEngineGetBackgroundColor :: a -> [StateFlags] -> m RGBA
themingEngineGetBackgroundColor engine :: a
engine state :: [StateFlags]
state = IO RGBA -> m RGBA
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RGBA -> m RGBA) -> IO RGBA -> m RGBA
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    let state' :: CUInt
state' = [StateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [StateFlags]
state
    Ptr RGBA
color <- Int -> IO (Ptr RGBA)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Gdk.RGBA.RGBA)
    Ptr ThemingEngine -> CUInt -> Ptr RGBA -> IO ()
gtk_theming_engine_get_background_color Ptr ThemingEngine
engine' CUInt
state' Ptr RGBA
color
    RGBA
color' <- ((ManagedPtr RGBA -> RGBA) -> Ptr RGBA -> IO RGBA
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr RGBA -> RGBA
Gdk.RGBA.RGBA) Ptr RGBA
color
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    RGBA -> IO RGBA
forall (m :: * -> *) a. Monad m => a -> m a
return RGBA
color'

#if defined(ENABLE_OVERLOADING)
data ThemingEngineGetBackgroundColorMethodInfo
instance (signature ~ ([Gtk.Flags.StateFlags] -> m (Gdk.RGBA.RGBA)), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineGetBackgroundColorMethodInfo a signature where
    overloadedMethod = themingEngineGetBackgroundColor

#endif

-- method ThemingEngine::get_border
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ThemingEngine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkThemingEngine"
--                 , 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 border for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "border"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Border" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return value for the border settings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_theming_engine_get_border" gtk_theming_engine_get_border :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    CUInt ->                                -- state : TInterface (Name {namespace = "Gtk", name = "StateFlags"})
    Ptr Gtk.Border.Border ->                -- border : TInterface (Name {namespace = "Gtk", name = "Border"})
    IO ()

{-# DEPRECATED themingEngineGetBorder ["(Since version 3.14)"] #-}
-- | Gets the border for a given state as a t'GI.Gtk.Structs.Border.Border'.
-- 
-- /Since: 3.0/
themingEngineGetBorder ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> [Gtk.Flags.StateFlags]
    -- ^ /@state@/: state to retrieve the border for
    -> m (Gtk.Border.Border)
themingEngineGetBorder :: a -> [StateFlags] -> m Border
themingEngineGetBorder engine :: a
engine state :: [StateFlags]
state = IO Border -> m Border
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Border -> m Border) -> IO Border -> m Border
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    let state' :: CUInt
state' = [StateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [StateFlags]
state
    Ptr Border
border <- Int -> IO (Ptr Border)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 8 :: IO (Ptr Gtk.Border.Border)
    Ptr ThemingEngine -> CUInt -> Ptr Border -> IO ()
gtk_theming_engine_get_border Ptr ThemingEngine
engine' CUInt
state' Ptr Border
border
    Border
border' <- ((ManagedPtr Border -> Border) -> Ptr Border -> IO Border
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Border -> Border
Gtk.Border.Border) Ptr Border
border
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    Border -> IO Border
forall (m :: * -> *) a. Monad m => a -> m a
return Border
border'

#if defined(ENABLE_OVERLOADING)
data ThemingEngineGetBorderMethodInfo
instance (signature ~ ([Gtk.Flags.StateFlags] -> m (Gtk.Border.Border)), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineGetBorderMethodInfo a signature where
    overloadedMethod = themingEngineGetBorder

#endif

-- method ThemingEngine::get_border_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ThemingEngine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkThemingEngine"
--                 , 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 color for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "color"
--           , argType = TInterface Name { namespace = "Gdk" , name = "RGBA" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return value for the border color"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_theming_engine_get_border_color" gtk_theming_engine_get_border_color :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    CUInt ->                                -- state : TInterface (Name {namespace = "Gtk", name = "StateFlags"})
    Ptr Gdk.RGBA.RGBA ->                    -- color : TInterface (Name {namespace = "Gdk", name = "RGBA"})
    IO ()

{-# DEPRECATED themingEngineGetBorderColor ["(Since version 3.14)"] #-}
-- | Gets the border color for a given state.
-- 
-- /Since: 3.0/
themingEngineGetBorderColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> [Gtk.Flags.StateFlags]
    -- ^ /@state@/: state to retrieve the color for
    -> m (Gdk.RGBA.RGBA)
themingEngineGetBorderColor :: a -> [StateFlags] -> m RGBA
themingEngineGetBorderColor engine :: a
engine state :: [StateFlags]
state = IO RGBA -> m RGBA
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RGBA -> m RGBA) -> IO RGBA -> m RGBA
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    let state' :: CUInt
state' = [StateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [StateFlags]
state
    Ptr RGBA
color <- Int -> IO (Ptr RGBA)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Gdk.RGBA.RGBA)
    Ptr ThemingEngine -> CUInt -> Ptr RGBA -> IO ()
gtk_theming_engine_get_border_color Ptr ThemingEngine
engine' CUInt
state' Ptr RGBA
color
    RGBA
color' <- ((ManagedPtr RGBA -> RGBA) -> Ptr RGBA -> IO RGBA
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr RGBA -> RGBA
Gdk.RGBA.RGBA) Ptr RGBA
color
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    RGBA -> IO RGBA
forall (m :: * -> *) a. Monad m => a -> m a
return RGBA
color'

#if defined(ENABLE_OVERLOADING)
data ThemingEngineGetBorderColorMethodInfo
instance (signature ~ ([Gtk.Flags.StateFlags] -> m (Gdk.RGBA.RGBA)), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineGetBorderColorMethodInfo a signature where
    overloadedMethod = themingEngineGetBorderColor

#endif

-- method ThemingEngine::get_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ThemingEngine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkThemingEngine"
--                 , 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 color for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "color"
--           , argType = TInterface Name { namespace = "Gdk" , name = "RGBA" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return value for the foreground color"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_theming_engine_get_color" gtk_theming_engine_get_color :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    CUInt ->                                -- state : TInterface (Name {namespace = "Gtk", name = "StateFlags"})
    Ptr Gdk.RGBA.RGBA ->                    -- color : TInterface (Name {namespace = "Gdk", name = "RGBA"})
    IO ()

{-# DEPRECATED themingEngineGetColor ["(Since version 3.14)"] #-}
-- | Gets the foreground color for a given state.
-- 
-- /Since: 3.0/
themingEngineGetColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> [Gtk.Flags.StateFlags]
    -- ^ /@state@/: state to retrieve the color for
    -> m (Gdk.RGBA.RGBA)
themingEngineGetColor :: a -> [StateFlags] -> m RGBA
themingEngineGetColor engine :: a
engine state :: [StateFlags]
state = IO RGBA -> m RGBA
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RGBA -> m RGBA) -> IO RGBA -> m RGBA
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    let state' :: CUInt
state' = [StateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [StateFlags]
state
    Ptr RGBA
color <- Int -> IO (Ptr RGBA)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Gdk.RGBA.RGBA)
    Ptr ThemingEngine -> CUInt -> Ptr RGBA -> IO ()
gtk_theming_engine_get_color Ptr ThemingEngine
engine' CUInt
state' Ptr RGBA
color
    RGBA
color' <- ((ManagedPtr RGBA -> RGBA) -> Ptr RGBA -> IO RGBA
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr RGBA -> RGBA
Gdk.RGBA.RGBA) Ptr RGBA
color
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    RGBA -> IO RGBA
forall (m :: * -> *) a. Monad m => a -> m a
return RGBA
color'

#if defined(ENABLE_OVERLOADING)
data ThemingEngineGetColorMethodInfo
instance (signature ~ ([Gtk.Flags.StateFlags] -> m (Gdk.RGBA.RGBA)), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineGetColorMethodInfo a signature where
    overloadedMethod = themingEngineGetColor

#endif

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

foreign import ccall "gtk_theming_engine_get_direction" gtk_theming_engine_get_direction :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    IO CUInt

{-# DEPRECATED themingEngineGetDirection ["(Since version 3.8)","Use 'GI.Gtk.Objects.ThemingEngine.themingEngineGetState' and","  check for @/GTK_STATE_FLAG_DIR_LTR/@ and","  @/GTK_STATE_FLAG_DIR_RTL/@ instead."] #-}
-- | Returns the widget direction used for rendering.
-- 
-- /Since: 3.0/
themingEngineGetDirection ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> m Gtk.Enums.TextDirection
    -- ^ __Returns:__ the widget direction
themingEngineGetDirection :: a -> m TextDirection
themingEngineGetDirection engine :: a
engine = IO TextDirection -> m TextDirection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextDirection -> m TextDirection)
-> IO TextDirection -> m TextDirection
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    CUInt
result <- Ptr ThemingEngine -> IO CUInt
gtk_theming_engine_get_direction Ptr ThemingEngine
engine'
    let result' :: TextDirection
result' = (Int -> TextDirection
forall a. Enum a => Int -> a
toEnum (Int -> TextDirection) -> (CUInt -> Int) -> CUInt -> TextDirection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    TextDirection -> IO TextDirection
forall (m :: * -> *) a. Monad m => a -> m a
return TextDirection
result'

#if defined(ENABLE_OVERLOADING)
data ThemingEngineGetDirectionMethodInfo
instance (signature ~ (m Gtk.Enums.TextDirection), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineGetDirectionMethodInfo a signature where
    overloadedMethod = themingEngineGetDirection

#endif

-- method ThemingEngine::get_font
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ThemingEngine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkThemingEngine"
--                 , 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 font for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Pango" , name = "FontDescription" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_theming_engine_get_font" gtk_theming_engine_get_font :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    CUInt ->                                -- state : TInterface (Name {namespace = "Gtk", name = "StateFlags"})
    IO (Ptr Pango.FontDescription.FontDescription)

{-# DEPRECATED themingEngineGetFont ["(Since version 3.8)","Use @/gtk_theming_engine_get()/@"] #-}
-- | Returns the font description for a given state.
-- 
-- /Since: 3.0/
themingEngineGetFont ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> [Gtk.Flags.StateFlags]
    -- ^ /@state@/: state to retrieve the font for
    -> m Pango.FontDescription.FontDescription
    -- ^ __Returns:__ the t'GI.Pango.Structs.FontDescription.FontDescription' for the given
    --          state. This object is owned by GTK+ and should not be
    --          freed.
themingEngineGetFont :: a -> [StateFlags] -> m FontDescription
themingEngineGetFont engine :: a
engine state :: [StateFlags]
state = IO FontDescription -> m FontDescription
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FontDescription -> m FontDescription)
-> IO FontDescription -> m FontDescription
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    let state' :: CUInt
state' = [StateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [StateFlags]
state
    Ptr FontDescription
result <- Ptr ThemingEngine -> CUInt -> IO (Ptr FontDescription)
gtk_theming_engine_get_font Ptr ThemingEngine
engine' CUInt
state'
    Text -> Ptr FontDescription -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "themingEngineGetFont" Ptr FontDescription
result
    FontDescription
result' <- ((ManagedPtr FontDescription -> FontDescription)
-> Ptr FontDescription -> IO FontDescription
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr FontDescription -> FontDescription
Pango.FontDescription.FontDescription) Ptr FontDescription
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    FontDescription -> IO FontDescription
forall (m :: * -> *) a. Monad m => a -> m a
return FontDescription
result'

#if defined(ENABLE_OVERLOADING)
data ThemingEngineGetFontMethodInfo
instance (signature ~ ([Gtk.Flags.StateFlags] -> m Pango.FontDescription.FontDescription), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineGetFontMethodInfo a signature where
    overloadedMethod = themingEngineGetFont

#endif

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

foreign import ccall "gtk_theming_engine_get_junction_sides" gtk_theming_engine_get_junction_sides :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    IO CUInt

{-# DEPRECATED themingEngineGetJunctionSides ["(Since version 3.14)"] #-}
-- | Returns the widget direction used for rendering.
-- 
-- /Since: 3.0/
themingEngineGetJunctionSides ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> m [Gtk.Flags.JunctionSides]
    -- ^ __Returns:__ the widget direction
themingEngineGetJunctionSides :: a -> m [JunctionSides]
themingEngineGetJunctionSides engine :: a
engine = IO [JunctionSides] -> m [JunctionSides]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [JunctionSides] -> m [JunctionSides])
-> IO [JunctionSides] -> m [JunctionSides]
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    CUInt
result <- Ptr ThemingEngine -> IO CUInt
gtk_theming_engine_get_junction_sides Ptr ThemingEngine
engine'
    let result' :: [JunctionSides]
result' = CUInt -> [JunctionSides]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    [JunctionSides] -> IO [JunctionSides]
forall (m :: * -> *) a. Monad m => a -> m a
return [JunctionSides]
result'

#if defined(ENABLE_OVERLOADING)
data ThemingEngineGetJunctionSidesMethodInfo
instance (signature ~ (m [Gtk.Flags.JunctionSides]), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineGetJunctionSidesMethodInfo a signature where
    overloadedMethod = themingEngineGetJunctionSides

#endif

-- method ThemingEngine::get_margin
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ThemingEngine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkThemingEngine"
--                 , 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 border for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "margin"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Border" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return value for the margin settings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_theming_engine_get_margin" gtk_theming_engine_get_margin :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    CUInt ->                                -- state : TInterface (Name {namespace = "Gtk", name = "StateFlags"})
    Ptr Gtk.Border.Border ->                -- margin : TInterface (Name {namespace = "Gtk", name = "Border"})
    IO ()

{-# DEPRECATED themingEngineGetMargin ["(Since version 3.14)"] #-}
-- | Gets the margin for a given state as a t'GI.Gtk.Structs.Border.Border'.
-- 
-- /Since: 3.0/
themingEngineGetMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> [Gtk.Flags.StateFlags]
    -- ^ /@state@/: state to retrieve the border for
    -> m (Gtk.Border.Border)
themingEngineGetMargin :: a -> [StateFlags] -> m Border
themingEngineGetMargin engine :: a
engine state :: [StateFlags]
state = IO Border -> m Border
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Border -> m Border) -> IO Border -> m Border
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    let state' :: CUInt
state' = [StateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [StateFlags]
state
    Ptr Border
margin <- Int -> IO (Ptr Border)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 8 :: IO (Ptr Gtk.Border.Border)
    Ptr ThemingEngine -> CUInt -> Ptr Border -> IO ()
gtk_theming_engine_get_margin Ptr ThemingEngine
engine' CUInt
state' Ptr Border
margin
    Border
margin' <- ((ManagedPtr Border -> Border) -> Ptr Border -> IO Border
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Border -> Border
Gtk.Border.Border) Ptr Border
margin
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    Border -> IO Border
forall (m :: * -> *) a. Monad m => a -> m a
return Border
margin'

#if defined(ENABLE_OVERLOADING)
data ThemingEngineGetMarginMethodInfo
instance (signature ~ ([Gtk.Flags.StateFlags] -> m (Gtk.Border.Border)), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineGetMarginMethodInfo a signature where
    overloadedMethod = themingEngineGetMargin

#endif

-- method ThemingEngine::get_padding
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ThemingEngine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkThemingEngine"
--                 , 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 padding for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "padding"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Border" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return value for the padding settings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_theming_engine_get_padding" gtk_theming_engine_get_padding :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    CUInt ->                                -- state : TInterface (Name {namespace = "Gtk", name = "StateFlags"})
    Ptr Gtk.Border.Border ->                -- padding : TInterface (Name {namespace = "Gtk", name = "Border"})
    IO ()

{-# DEPRECATED themingEngineGetPadding ["(Since version 3.14)"] #-}
-- | Gets the padding for a given state as a t'GI.Gtk.Structs.Border.Border'.
-- 
-- /Since: 3.0/
themingEngineGetPadding ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> [Gtk.Flags.StateFlags]
    -- ^ /@state@/: state to retrieve the padding for
    -> m (Gtk.Border.Border)
themingEngineGetPadding :: a -> [StateFlags] -> m Border
themingEngineGetPadding engine :: a
engine state :: [StateFlags]
state = IO Border -> m Border
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Border -> m Border) -> IO Border -> m Border
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    let state' :: CUInt
state' = [StateFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [StateFlags]
state
    Ptr Border
padding <- Int -> IO (Ptr Border)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 8 :: IO (Ptr Gtk.Border.Border)
    Ptr ThemingEngine -> CUInt -> Ptr Border -> IO ()
gtk_theming_engine_get_padding Ptr ThemingEngine
engine' CUInt
state' Ptr Border
padding
    Border
padding' <- ((ManagedPtr Border -> Border) -> Ptr Border -> IO Border
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Border -> Border
Gtk.Border.Border) Ptr Border
padding
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    Border -> IO Border
forall (m :: * -> *) a. Monad m => a -> m a
return Border
padding'

#if defined(ENABLE_OVERLOADING)
data ThemingEngineGetPaddingMethodInfo
instance (signature ~ ([Gtk.Flags.StateFlags] -> m (Gtk.Border.Border)), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineGetPaddingMethodInfo a signature where
    overloadedMethod = themingEngineGetPadding

#endif

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

foreign import ccall "gtk_theming_engine_get_path" gtk_theming_engine_get_path :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    IO (Ptr Gtk.WidgetPath.WidgetPath)

{-# DEPRECATED themingEngineGetPath ["(Since version 3.14)"] #-}
-- | Returns the widget path used for style matching.
-- 
-- /Since: 3.0/
themingEngineGetPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> m Gtk.WidgetPath.WidgetPath
    -- ^ __Returns:__ A t'GI.Gtk.Structs.WidgetPath.WidgetPath'
themingEngineGetPath :: a -> m WidgetPath
themingEngineGetPath engine :: a
engine = IO WidgetPath -> m WidgetPath
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WidgetPath -> m WidgetPath) -> IO WidgetPath -> m WidgetPath
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    Ptr WidgetPath
result <- Ptr ThemingEngine -> IO (Ptr WidgetPath)
gtk_theming_engine_get_path Ptr ThemingEngine
engine'
    Text -> Ptr WidgetPath -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "themingEngineGetPath" Ptr WidgetPath
result
    WidgetPath
result' <- ((ManagedPtr WidgetPath -> WidgetPath)
-> Ptr WidgetPath -> IO WidgetPath
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr WidgetPath -> WidgetPath
Gtk.WidgetPath.WidgetPath) Ptr WidgetPath
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    WidgetPath -> IO WidgetPath
forall (m :: * -> *) a. Monad m => a -> m a
return WidgetPath
result'

#if defined(ENABLE_OVERLOADING)
data ThemingEngineGetPathMethodInfo
instance (signature ~ (m Gtk.WidgetPath.WidgetPath), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineGetPathMethodInfo a signature where
    overloadedMethod = themingEngineGetPath

#endif

-- method ThemingEngine::get_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ThemingEngine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkThemingEngine"
--                 , 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 "the 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 value for"
--                 , 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,\n        you must free this memory using g_value_unset() once you are\n        done with it."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_theming_engine_get_property" gtk_theming_engine_get_property :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    CString ->                              -- property : TBasicType TUTF8
    CUInt ->                                -- state : TInterface (Name {namespace = "Gtk", name = "StateFlags"})
    Ptr GValue ->                           -- value : TInterface (Name {namespace = "GObject", name = "Value"})
    IO ()

{-# DEPRECATED themingEngineGetProperty ["(Since version 3.14)"] #-}
-- | Gets a property value as retrieved from the style settings that apply
-- to the currently rendered element.
-- 
-- /Since: 3.0/
themingEngineGetProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> T.Text
    -- ^ /@property@/: the property name
    -> [Gtk.Flags.StateFlags]
    -- ^ /@state@/: state to retrieve the value for
    -> m (GValue)
themingEngineGetProperty :: a -> Text -> [StateFlags] -> m GValue
themingEngineGetProperty engine :: a
engine property :: Text
property state :: [StateFlags]
state = 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 ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    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. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 24 :: IO (Ptr GValue)
    Ptr ThemingEngine -> CString -> CUInt -> Ptr GValue -> IO ()
gtk_theming_engine_get_property Ptr ThemingEngine
engine' CString
property' CUInt
state' Ptr GValue
value
    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
engine
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
    GValue -> IO GValue
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
value'

#if defined(ENABLE_OVERLOADING)
data ThemingEngineGetPropertyMethodInfo
instance (signature ~ (T.Text -> [Gtk.Flags.StateFlags] -> m (GValue)), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineGetPropertyMethodInfo a signature where
    overloadedMethod = themingEngineGetProperty

#endif

-- method ThemingEngine::get_screen
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ThemingEngine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkThemingEngine"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Screen" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_theming_engine_get_screen" gtk_theming_engine_get_screen :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    IO (Ptr Gdk.Screen.Screen)

{-# DEPRECATED themingEngineGetScreen ["(Since version 3.14)"] #-}
-- | Returns the t'GI.Gdk.Objects.Screen.Screen' to which /@engine@/ currently rendering to.
themingEngineGetScreen ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> m (Maybe Gdk.Screen.Screen)
    -- ^ __Returns:__ a t'GI.Gdk.Objects.Screen.Screen', or 'P.Nothing'.
themingEngineGetScreen :: a -> m (Maybe Screen)
themingEngineGetScreen engine :: a
engine = IO (Maybe Screen) -> m (Maybe Screen)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Screen) -> m (Maybe Screen))
-> IO (Maybe Screen) -> m (Maybe Screen)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    Ptr Screen
result <- Ptr ThemingEngine -> IO (Ptr Screen)
gtk_theming_engine_get_screen Ptr ThemingEngine
engine'
    Maybe Screen
maybeResult <- Ptr Screen -> (Ptr Screen -> IO Screen) -> IO (Maybe Screen)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Screen
result ((Ptr Screen -> IO Screen) -> IO (Maybe Screen))
-> (Ptr Screen -> IO Screen) -> IO (Maybe Screen)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Screen
result' -> do
        Screen
result'' <- ((ManagedPtr Screen -> Screen) -> Ptr Screen -> IO Screen
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Screen -> Screen
Gdk.Screen.Screen) Ptr Screen
result'
        Screen -> IO Screen
forall (m :: * -> *) a. Monad m => a -> m a
return Screen
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    Maybe Screen -> IO (Maybe Screen)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Screen
maybeResult

#if defined(ENABLE_OVERLOADING)
data ThemingEngineGetScreenMethodInfo
instance (signature ~ (m (Maybe Gdk.Screen.Screen)), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineGetScreenMethodInfo a signature where
    overloadedMethod = themingEngineGetScreen

#endif

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

foreign import ccall "gtk_theming_engine_get_state" gtk_theming_engine_get_state :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    IO CUInt

{-# DEPRECATED themingEngineGetState ["(Since version 3.14)"] #-}
-- | returns the state used when rendering.
-- 
-- /Since: 3.0/
themingEngineGetState ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> m [Gtk.Flags.StateFlags]
    -- ^ __Returns:__ the state flags
themingEngineGetState :: a -> m [StateFlags]
themingEngineGetState engine :: a
engine = IO [StateFlags] -> m [StateFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [StateFlags] -> m [StateFlags])
-> IO [StateFlags] -> m [StateFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    CUInt
result <- Ptr ThemingEngine -> IO CUInt
gtk_theming_engine_get_state Ptr ThemingEngine
engine'
    let result' :: [StateFlags]
result' = CUInt -> [StateFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    [StateFlags] -> IO [StateFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [StateFlags]
result'

#if defined(ENABLE_OVERLOADING)
data ThemingEngineGetStateMethodInfo
instance (signature ~ (m [Gtk.Flags.StateFlags]), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineGetStateMethodInfo a signature where
    overloadedMethod = themingEngineGetState

#endif

-- method ThemingEngine::get_style_property
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ThemingEngine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkThemingEngine"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "property_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the widget style property"
--                 , 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, free with\n        g_value_unset() after use."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_theming_engine_get_style_property" gtk_theming_engine_get_style_property :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    CString ->                              -- property_name : TBasicType TUTF8
    Ptr GValue ->                           -- value : TInterface (Name {namespace = "GObject", name = "Value"})
    IO ()

{-# DEPRECATED themingEngineGetStyleProperty ["(Since version 3.14)"] #-}
-- | Gets the value for a widget style property.
-- 
-- /Since: 3.0/
themingEngineGetStyleProperty ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> T.Text
    -- ^ /@propertyName@/: the name of the widget style property
    -> m (GValue)
themingEngineGetStyleProperty :: a -> Text -> m GValue
themingEngineGetStyleProperty engine :: a
engine propertyName :: 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 ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
    Ptr GValue
value <- Int -> IO (Ptr GValue)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 24 :: IO (Ptr GValue)
    Ptr ThemingEngine -> CString -> Ptr GValue -> IO ()
gtk_theming_engine_get_style_property Ptr ThemingEngine
engine' CString
propertyName' Ptr GValue
value
    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
engine
    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 ThemingEngineGetStylePropertyMethodInfo
instance (signature ~ (T.Text -> m (GValue)), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineGetStylePropertyMethodInfo a signature where
    overloadedMethod = themingEngineGetStyleProperty

#endif

-- method ThemingEngine::has_class
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ThemingEngine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkThemingEngine"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "style_class"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "class name to look up"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_theming_engine_has_class" gtk_theming_engine_has_class :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    CString ->                              -- style_class : TBasicType TUTF8
    IO CInt

{-# DEPRECATED themingEngineHasClass ["(Since version 3.14)"] #-}
-- | Returns 'P.True' if the currently rendered contents have
-- defined the given class name.
-- 
-- /Since: 3.0/
themingEngineHasClass ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> T.Text
    -- ^ /@styleClass@/: class name to look up
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@engine@/ has /@className@/ defined
themingEngineHasClass :: a -> Text -> m Bool
themingEngineHasClass engine :: a
engine styleClass :: Text
styleClass = 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 ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    CString
styleClass' <- Text -> IO CString
textToCString Text
styleClass
    CInt
result <- Ptr ThemingEngine -> CString -> IO CInt
gtk_theming_engine_has_class Ptr ThemingEngine
engine' CString
styleClass'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
styleClass'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ThemingEngineHasClassMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineHasClassMethodInfo a signature where
    overloadedMethod = themingEngineHasClass

#endif

-- method ThemingEngine::has_region
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ThemingEngine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkThemingEngine"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "style_region"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a region name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "RegionFlags" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for region flags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_theming_engine_has_region" gtk_theming_engine_has_region :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    CString ->                              -- style_region : TBasicType TUTF8
    Ptr CUInt ->                            -- flags : TInterface (Name {namespace = "Gtk", name = "RegionFlags"})
    IO CInt

{-# DEPRECATED themingEngineHasRegion ["(Since version 3.14)"] #-}
-- | Returns 'P.True' if the currently rendered contents have the
-- region defined. If /@flagsReturn@/ is not 'P.Nothing', it is set
-- to the flags affecting the region.
-- 
-- /Since: 3.0/
themingEngineHasRegion ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> T.Text
    -- ^ /@styleRegion@/: a region name
    -> m ((Bool, [Gtk.Flags.RegionFlags]))
    -- ^ __Returns:__ 'P.True' if region is defined
themingEngineHasRegion :: a -> Text -> m (Bool, [RegionFlags])
themingEngineHasRegion engine :: a
engine styleRegion :: Text
styleRegion = IO (Bool, [RegionFlags]) -> m (Bool, [RegionFlags])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, [RegionFlags]) -> m (Bool, [RegionFlags]))
-> IO (Bool, [RegionFlags]) -> m (Bool, [RegionFlags])
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    CString
styleRegion' <- Text -> IO CString
textToCString Text
styleRegion
    Ptr CUInt
flags <- IO (Ptr CUInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CUInt)
    CInt
result <- Ptr ThemingEngine -> CString -> Ptr CUInt -> IO CInt
gtk_theming_engine_has_region Ptr ThemingEngine
engine' CString
styleRegion' Ptr CUInt
flags
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    CUInt
flags' <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CUInt
flags
    let flags'' :: [RegionFlags]
flags'' = CUInt -> [RegionFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
flags'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
styleRegion'
    Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
flags
    (Bool, [RegionFlags]) -> IO (Bool, [RegionFlags])
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', [RegionFlags]
flags'')

#if defined(ENABLE_OVERLOADING)
data ThemingEngineHasRegionMethodInfo
instance (signature ~ (T.Text -> m ((Bool, [Gtk.Flags.RegionFlags]))), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineHasRegionMethodInfo a signature where
    overloadedMethod = themingEngineHasRegion

#endif

-- method ThemingEngine::lookup_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ThemingEngine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkThemingEngine"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "color_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
--           }
--       , Arg
--           { argCName = "color"
--           , argType = TInterface Name { namespace = "Gdk" , name = "RGBA" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Return location for the looked up color"
--                 , 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_theming_engine_lookup_color" gtk_theming_engine_lookup_color :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    CString ->                              -- color_name : TBasicType TUTF8
    Ptr Gdk.RGBA.RGBA ->                    -- color : TInterface (Name {namespace = "Gdk", name = "RGBA"})
    IO CInt

{-# DEPRECATED themingEngineLookupColor ["(Since version 3.14)"] #-}
-- | Looks up and resolves a color name in the current style’s color map.
-- 
-- /Since: 3.0/
themingEngineLookupColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> T.Text
    -- ^ /@colorName@/: color name to lookup
    -> m ((Bool, Gdk.RGBA.RGBA))
    -- ^ __Returns:__ 'P.True' if /@colorName@/ was found and resolved, 'P.False' otherwise
themingEngineLookupColor :: a -> Text -> m (Bool, RGBA)
themingEngineLookupColor engine :: a
engine colorName :: Text
colorName = IO (Bool, RGBA) -> m (Bool, RGBA)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, RGBA) -> m (Bool, RGBA))
-> IO (Bool, RGBA) -> m (Bool, RGBA)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    CString
colorName' <- Text -> IO CString
textToCString Text
colorName
    Ptr RGBA
color <- Int -> IO (Ptr RGBA)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 :: IO (Ptr Gdk.RGBA.RGBA)
    CInt
result <- Ptr ThemingEngine -> CString -> Ptr RGBA -> IO CInt
gtk_theming_engine_lookup_color Ptr ThemingEngine
engine' CString
colorName' Ptr RGBA
color
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    RGBA
color' <- ((ManagedPtr RGBA -> RGBA) -> Ptr RGBA -> IO RGBA
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr RGBA -> RGBA
Gdk.RGBA.RGBA) Ptr RGBA
color
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
colorName'
    (Bool, RGBA) -> IO (Bool, RGBA)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', RGBA
color')

#if defined(ENABLE_OVERLOADING)
data ThemingEngineLookupColorMethodInfo
instance (signature ~ (T.Text -> m ((Bool, Gdk.RGBA.RGBA))), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineLookupColorMethodInfo a signature where
    overloadedMethod = themingEngineLookupColor

#endif

-- method ThemingEngine::state_is_running
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ThemingEngine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkThemingEngine"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StateType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a widget state" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "progress"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the transition progress"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_theming_engine_state_is_running" gtk_theming_engine_state_is_running :: 
    Ptr ThemingEngine ->                    -- engine : TInterface (Name {namespace = "Gtk", name = "ThemingEngine"})
    CUInt ->                                -- state : TInterface (Name {namespace = "Gtk", name = "StateType"})
    Ptr CDouble ->                          -- progress : TBasicType TDouble
    IO CInt

{-# DEPRECATED themingEngineStateIsRunning ["(Since version 3.6)","Always returns 'P.False'"] #-}
-- | Returns 'P.True' if there is a transition animation running for the
-- current region (see 'GI.Gtk.Objects.StyleContext.styleContextPushAnimatableRegion').
-- 
-- If /@progress@/ is not 'P.Nothing', the animation progress will be returned
-- there, 0.0 means the state is closest to being 'P.False', while 1.0 means
-- it’s closest to being 'P.True'. This means transition animations will
-- run from 0 to 1 when /@state@/ is being set to 'P.True' and from 1 to 0 when
-- it’s being set to 'P.False'.
-- 
-- /Since: 3.0/
themingEngineStateIsRunning ::
    (B.CallStack.HasCallStack, MonadIO m, IsThemingEngine a) =>
    a
    -- ^ /@engine@/: a t'GI.Gtk.Objects.ThemingEngine.ThemingEngine'
    -> Gtk.Enums.StateType
    -- ^ /@state@/: a widget state
    -> m ((Bool, Double))
    -- ^ __Returns:__ 'P.True' if there is a running transition animation for /@state@/.
themingEngineStateIsRunning :: a -> StateType -> m (Bool, Double)
themingEngineStateIsRunning engine :: a
engine state :: StateType
state = IO (Bool, Double) -> m (Bool, Double)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Double) -> m (Bool, Double))
-> IO (Bool, Double) -> m (Bool, Double)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ThemingEngine
engine' <- a -> IO (Ptr ThemingEngine)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
engine
    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 CDouble
progress <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    CInt
result <- Ptr ThemingEngine -> CUInt -> Ptr CDouble -> IO CInt
gtk_theming_engine_state_is_running Ptr ThemingEngine
engine' CUInt
state' Ptr CDouble
progress
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    CDouble
progress' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
progress
    let progress'' :: Double
progress'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
progress'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
engine
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
progress
    (Bool, Double) -> IO (Bool, Double)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Double
progress'')

#if defined(ENABLE_OVERLOADING)
data ThemingEngineStateIsRunningMethodInfo
instance (signature ~ (Gtk.Enums.StateType -> m ((Bool, Double))), MonadIO m, IsThemingEngine a) => O.MethodInfo ThemingEngineStateIsRunningMethodInfo a signature where
    overloadedMethod = themingEngineStateIsRunning

#endif

-- method ThemingEngine::load
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Theme engine name to load"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "ThemingEngine" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_theming_engine_load" gtk_theming_engine_load :: 
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr ThemingEngine)

{-# DEPRECATED themingEngineLoad ["(Since version 3.14)"] #-}
-- | Loads and initializes a theming engine module from the
-- standard directories.
themingEngineLoad ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@name@/: Theme engine name to load
    -> m (Maybe ThemingEngine)
    -- ^ __Returns:__ A theming engine, or 'P.Nothing' if
    -- the engine /@name@/ doesn’t exist.
themingEngineLoad :: Text -> m (Maybe ThemingEngine)
themingEngineLoad name :: Text
name = IO (Maybe ThemingEngine) -> m (Maybe ThemingEngine)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ThemingEngine) -> m (Maybe ThemingEngine))
-> IO (Maybe ThemingEngine) -> m (Maybe ThemingEngine)
forall a b. (a -> b) -> a -> b
$ do
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr ThemingEngine
result <- CString -> IO (Ptr ThemingEngine)
gtk_theming_engine_load CString
name'
    Maybe ThemingEngine
maybeResult <- Ptr ThemingEngine
-> (Ptr ThemingEngine -> IO ThemingEngine)
-> IO (Maybe ThemingEngine)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr ThemingEngine
result ((Ptr ThemingEngine -> IO ThemingEngine)
 -> IO (Maybe ThemingEngine))
-> (Ptr ThemingEngine -> IO ThemingEngine)
-> IO (Maybe ThemingEngine)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr ThemingEngine
result' -> do
        ThemingEngine
result'' <- ((ManagedPtr ThemingEngine -> ThemingEngine)
-> Ptr ThemingEngine -> IO ThemingEngine
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ThemingEngine -> ThemingEngine
ThemingEngine) Ptr ThemingEngine
result'
        ThemingEngine -> IO ThemingEngine
forall (m :: * -> *) a. Monad m => a -> m a
return ThemingEngine
result''
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    Maybe ThemingEngine -> IO (Maybe ThemingEngine)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ThemingEngine
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif