{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A preview widget for [class/@styleScheme@/].
-- 
-- This widget provides a convenient t'GI.Gtk.Objects.Widget.Widget' to preview a [class/@styleScheme@/].
-- 
-- The [property/@styleSchemePreview@/:selected] property can be used to manage
-- the selection state of a single preview widget.
-- 
-- /Since: 5.4/

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

module GI.GtkSource.Objects.StyleSchemePreview
    ( 

-- * Exported types
    StyleSchemePreview(..)                  ,
    IsStyleSchemePreview                    ,
    toStyleSchemePreview                    ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actionSetEnabled]("GI.Gtk.Objects.Widget#g:method:actionSetEnabled"), [activate]("GI.Gtk.Objects.Widget#g:method:activate"), [activateAction]("GI.Gtk.Objects.Widget#g:method:activateAction"), [activateDefault]("GI.Gtk.Objects.Widget#g:method:activateDefault"), [addController]("GI.Gtk.Objects.Widget#g:method:addController"), [addCssClass]("GI.Gtk.Objects.Widget#g:method:addCssClass"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [allocate]("GI.Gtk.Objects.Widget#g:method:allocate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [childFocus]("GI.Gtk.Objects.Widget#g:method:childFocus"), [computeBounds]("GI.Gtk.Objects.Widget#g:method:computeBounds"), [computeExpand]("GI.Gtk.Objects.Widget#g:method:computeExpand"), [computePoint]("GI.Gtk.Objects.Widget#g:method:computePoint"), [computeTransform]("GI.Gtk.Objects.Widget#g:method:computeTransform"), [contains]("GI.Gtk.Objects.Widget#g:method:contains"), [createPangoContext]("GI.Gtk.Objects.Widget#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.Widget#g:method:createPangoLayout"), [disposeTemplate]("GI.Gtk.Objects.Widget#g:method:disposeTemplate"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [hasCssClass]("GI.Gtk.Objects.Widget#g:method:hasCssClass"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [insertAfter]("GI.Gtk.Objects.Widget#g:method:insertAfter"), [insertBefore]("GI.Gtk.Objects.Widget#g:method:insertBefore"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [isDrawable]("GI.Gtk.Objects.Widget#g:method:isDrawable"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isFocus]("GI.Gtk.Objects.Widget#g:method:isFocus"), [isSensitive]("GI.Gtk.Objects.Widget#g:method:isSensitive"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [measure]("GI.Gtk.Objects.Widget#g:method:measure"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [observeChildren]("GI.Gtk.Objects.Widget#g:method:observeChildren"), [observeControllers]("GI.Gtk.Objects.Widget#g:method:observeControllers"), [pick]("GI.Gtk.Objects.Widget#g:method:pick"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeController]("GI.Gtk.Objects.Widget#g:method:removeController"), [removeCssClass]("GI.Gtk.Objects.Widget#g:method:removeCssClass"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [resetProperty]("GI.Gtk.Interfaces.Accessible#g:method:resetProperty"), [resetRelation]("GI.Gtk.Interfaces.Accessible#g:method:resetRelation"), [resetState]("GI.Gtk.Interfaces.Accessible#g:method:resetState"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [shouldLayout]("GI.Gtk.Objects.Widget#g:method:shouldLayout"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [snapshotChild]("GI.Gtk.Objects.Widget#g:method:snapshotChild"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [translateCoordinates]("GI.Gtk.Objects.Widget#g:method:translateCoordinates"), [triggerTooltipQuery]("GI.Gtk.Objects.Widget#g:method:triggerTooltipQuery"), [unmap]("GI.Gtk.Objects.Widget#g:method:unmap"), [unparent]("GI.Gtk.Objects.Widget#g:method:unparent"), [unrealize]("GI.Gtk.Objects.Widget#g:method:unrealize"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [updateNextAccessibleSibling]("GI.Gtk.Interfaces.Accessible#g:method:updateNextAccessibleSibling"), [updateProperty]("GI.Gtk.Interfaces.Accessible#g:method:updateProperty"), [updateRelation]("GI.Gtk.Interfaces.Accessible#g:method:updateRelation"), [updateState]("GI.Gtk.Interfaces.Accessible#g:method:updateState"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessibleParent]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleParent"), [getAccessibleRole]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleRole"), [getActionName]("GI.Gtk.Interfaces.Actionable#g:method:getActionName"), [getActionTargetValue]("GI.Gtk.Interfaces.Actionable#g:method:getActionTargetValue"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getAtContext]("GI.Gtk.Interfaces.Accessible#g:method:getAtContext"), [getBounds]("GI.Gtk.Interfaces.Accessible#g:method:getBounds"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getColor]("GI.Gtk.Objects.Widget#g:method:getColor"), [getCssClasses]("GI.Gtk.Objects.Widget#g:method:getCssClasses"), [getCssName]("GI.Gtk.Objects.Widget#g:method:getCssName"), [getCursor]("GI.Gtk.Objects.Widget#g:method:getCursor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getFirstAccessibleChild]("GI.Gtk.Interfaces.Accessible#g:method:getFirstAccessibleChild"), [getFirstChild]("GI.Gtk.Objects.Widget#g:method:getFirstChild"), [getFocusChild]("GI.Gtk.Objects.Widget#g:method:getFocusChild"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusable]("GI.Gtk.Objects.Widget#g:method:getFocusable"), [getFontMap]("GI.Gtk.Objects.Widget#g:method:getFontMap"), [getFontOptions]("GI.Gtk.Objects.Widget#g:method:getFontOptions"), [getFrameClock]("GI.Gtk.Objects.Widget#g:method:getFrameClock"), [getHalign]("GI.Gtk.Objects.Widget#g:method:getHalign"), [getHasTooltip]("GI.Gtk.Objects.Widget#g:method:getHasTooltip"), [getHeight]("GI.Gtk.Objects.Widget#g:method:getHeight"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getLastChild]("GI.Gtk.Objects.Widget#g:method:getLastChild"), [getLayoutManager]("GI.Gtk.Objects.Widget#g:method:getLayoutManager"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNative]("GI.Gtk.Objects.Widget#g:method:getNative"), [getNextAccessibleSibling]("GI.Gtk.Interfaces.Accessible#g:method:getNextAccessibleSibling"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPlatformState]("GI.Gtk.Interfaces.Accessible#g:method:getPlatformState"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealized]("GI.Gtk.Objects.Widget#g:method:getRealized"), [getReceivesDefault]("GI.Gtk.Objects.Widget#g:method:getReceivesDefault"), [getRequestMode]("GI.Gtk.Objects.Widget#g:method:getRequestMode"), [getRoot]("GI.Gtk.Objects.Widget#g:method:getRoot"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getScheme]("GI.GtkSource.Objects.StyleSchemePreview#g:method:getScheme"), [getSelected]("GI.GtkSource.Objects.StyleSchemePreview#g:method:getSelected"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSize]("GI.Gtk.Objects.Widget#g:method:getSize"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getValign]("GI.Gtk.Objects.Widget#g:method:getValign"), [getVexpand]("GI.Gtk.Objects.Widget#g:method:getVexpand"), [getVexpandSet]("GI.Gtk.Objects.Widget#g:method:getVexpandSet"), [getVisible]("GI.Gtk.Objects.Widget#g:method:getVisible"), [getWidth]("GI.Gtk.Objects.Widget#g:method:getWidth").
-- 
-- ==== Setters
-- [setAccessibleParent]("GI.Gtk.Interfaces.Accessible#g:method:setAccessibleParent"), [setActionName]("GI.Gtk.Interfaces.Actionable#g:method:setActionName"), [setActionTargetValue]("GI.Gtk.Interfaces.Actionable#g:method:setActionTargetValue"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDetailedActionName]("GI.Gtk.Interfaces.Actionable#g:method:setDetailedActionName"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setFocusChild]("GI.Gtk.Objects.Widget#g:method:setFocusChild"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusable]("GI.Gtk.Objects.Widget#g:method:setFocusable"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setLayoutManager]("GI.Gtk.Objects.Widget#g:method:setLayoutManager"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setOverflow]("GI.Gtk.Objects.Widget#g:method:setOverflow"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setSelected]("GI.GtkSource.Objects.StyleSchemePreview#g:method:setSelected"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setValign]("GI.Gtk.Objects.Widget#g:method:setValign"), [setVexpand]("GI.Gtk.Objects.Widget#g:method:setVexpand"), [setVexpandSet]("GI.Gtk.Objects.Widget#g:method:setVexpandSet"), [setVisible]("GI.Gtk.Objects.Widget#g:method:setVisible").

#if defined(ENABLE_OVERLOADING)
    ResolveStyleSchemePreviewMethod         ,
#endif

-- ** getScheme #method:getScheme#

#if defined(ENABLE_OVERLOADING)
    StyleSchemePreviewGetSchemeMethodInfo   ,
#endif
    styleSchemePreviewGetScheme             ,


-- ** getSelected #method:getSelected#

#if defined(ENABLE_OVERLOADING)
    StyleSchemePreviewGetSelectedMethodInfo ,
#endif
    styleSchemePreviewGetSelected           ,


-- ** new #method:new#

    styleSchemePreviewNew                   ,


-- ** setSelected #method:setSelected#

#if defined(ENABLE_OVERLOADING)
    StyleSchemePreviewSetSelectedMethodInfo ,
#endif
    styleSchemePreviewSetSelected           ,




 -- * Properties


-- ** scheme #attr:scheme#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    StyleSchemePreviewSchemePropertyInfo    ,
#endif
    constructStyleSchemePreviewScheme       ,
    getStyleSchemePreviewScheme             ,
#if defined(ENABLE_OVERLOADING)
    styleSchemePreviewScheme                ,
#endif


-- ** selected #attr:selected#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    StyleSchemePreviewSelectedPropertyInfo  ,
#endif
    constructStyleSchemePreviewSelected     ,
    getStyleSchemePreviewSelected           ,
    setStyleSchemePreviewSelected           ,
#if defined(ENABLE_OVERLOADING)
    styleSchemePreviewSelected              ,
#endif




 -- * Signals


-- ** activate #signal:activate#

    StyleSchemePreviewActivateCallback      ,
#if defined(ENABLE_OVERLOADING)
    StyleSchemePreviewActivateSignalInfo    ,
#endif
    afterStyleSchemePreviewActivate         ,
    onStyleSchemePreviewActivate            ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import qualified GI.Gtk.Interfaces.Actionable as Gtk.Actionable
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.GtkSource.Objects.StyleScheme as GtkSource.StyleScheme

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

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

foreign import ccall "gtk_source_style_scheme_preview_get_type"
    c_gtk_source_style_scheme_preview_get_type :: IO B.Types.GType

instance B.Types.TypedObject StyleSchemePreview where
    glibType :: IO GType
glibType = IO GType
c_gtk_source_style_scheme_preview_get_type

instance B.Types.GObject StyleSchemePreview

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

instance O.HasParentTypes StyleSchemePreview
type instance O.ParentTypes StyleSchemePreview = '[Gtk.Widget.Widget, GObject.Object.Object, Gtk.Accessible.Accessible, Gtk.Actionable.Actionable, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveStyleSchemePreviewMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveStyleSchemePreviewMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveStyleSchemePreviewMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveStyleSchemePreviewMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveStyleSchemePreviewMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveStyleSchemePreviewMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveStyleSchemePreviewMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveStyleSchemePreviewMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveStyleSchemePreviewMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveStyleSchemePreviewMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveStyleSchemePreviewMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveStyleSchemePreviewMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveStyleSchemePreviewMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveStyleSchemePreviewMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveStyleSchemePreviewMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveStyleSchemePreviewMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveStyleSchemePreviewMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveStyleSchemePreviewMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveStyleSchemePreviewMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveStyleSchemePreviewMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveStyleSchemePreviewMethod "disposeTemplate" o = Gtk.Widget.WidgetDisposeTemplateMethodInfo
    ResolveStyleSchemePreviewMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveStyleSchemePreviewMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveStyleSchemePreviewMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveStyleSchemePreviewMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveStyleSchemePreviewMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveStyleSchemePreviewMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveStyleSchemePreviewMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveStyleSchemePreviewMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveStyleSchemePreviewMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveStyleSchemePreviewMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveStyleSchemePreviewMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveStyleSchemePreviewMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveStyleSchemePreviewMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveStyleSchemePreviewMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveStyleSchemePreviewMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveStyleSchemePreviewMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveStyleSchemePreviewMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveStyleSchemePreviewMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveStyleSchemePreviewMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveStyleSchemePreviewMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveStyleSchemePreviewMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveStyleSchemePreviewMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveStyleSchemePreviewMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveStyleSchemePreviewMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveStyleSchemePreviewMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveStyleSchemePreviewMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveStyleSchemePreviewMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveStyleSchemePreviewMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveStyleSchemePreviewMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveStyleSchemePreviewMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveStyleSchemePreviewMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveStyleSchemePreviewMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveStyleSchemePreviewMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveStyleSchemePreviewMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveStyleSchemePreviewMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveStyleSchemePreviewMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveStyleSchemePreviewMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveStyleSchemePreviewMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveStyleSchemePreviewMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveStyleSchemePreviewMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveStyleSchemePreviewMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveStyleSchemePreviewMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveStyleSchemePreviewMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveStyleSchemePreviewMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveStyleSchemePreviewMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveStyleSchemePreviewMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveStyleSchemePreviewMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveStyleSchemePreviewMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveStyleSchemePreviewMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveStyleSchemePreviewMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveStyleSchemePreviewMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveStyleSchemePreviewMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveStyleSchemePreviewMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveStyleSchemePreviewMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveStyleSchemePreviewMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveStyleSchemePreviewMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveStyleSchemePreviewMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveStyleSchemePreviewMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveStyleSchemePreviewMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveStyleSchemePreviewMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveStyleSchemePreviewMethod "updateNextAccessibleSibling" o = Gtk.Accessible.AccessibleUpdateNextAccessibleSiblingMethodInfo
    ResolveStyleSchemePreviewMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveStyleSchemePreviewMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveStyleSchemePreviewMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveStyleSchemePreviewMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveStyleSchemePreviewMethod "getAccessibleParent" o = Gtk.Accessible.AccessibleGetAccessibleParentMethodInfo
    ResolveStyleSchemePreviewMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    ResolveStyleSchemePreviewMethod "getActionName" o = Gtk.Actionable.ActionableGetActionNameMethodInfo
    ResolveStyleSchemePreviewMethod "getActionTargetValue" o = Gtk.Actionable.ActionableGetActionTargetValueMethodInfo
    ResolveStyleSchemePreviewMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveStyleSchemePreviewMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveStyleSchemePreviewMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveStyleSchemePreviewMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveStyleSchemePreviewMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveStyleSchemePreviewMethod "getAtContext" o = Gtk.Accessible.AccessibleGetAtContextMethodInfo
    ResolveStyleSchemePreviewMethod "getBounds" o = Gtk.Accessible.AccessibleGetBoundsMethodInfo
    ResolveStyleSchemePreviewMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveStyleSchemePreviewMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveStyleSchemePreviewMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveStyleSchemePreviewMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveStyleSchemePreviewMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveStyleSchemePreviewMethod "getColor" o = Gtk.Widget.WidgetGetColorMethodInfo
    ResolveStyleSchemePreviewMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveStyleSchemePreviewMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveStyleSchemePreviewMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveStyleSchemePreviewMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveStyleSchemePreviewMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveStyleSchemePreviewMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveStyleSchemePreviewMethod "getFirstAccessibleChild" o = Gtk.Accessible.AccessibleGetFirstAccessibleChildMethodInfo
    ResolveStyleSchemePreviewMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveStyleSchemePreviewMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveStyleSchemePreviewMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveStyleSchemePreviewMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveStyleSchemePreviewMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveStyleSchemePreviewMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveStyleSchemePreviewMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveStyleSchemePreviewMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveStyleSchemePreviewMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveStyleSchemePreviewMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveStyleSchemePreviewMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveStyleSchemePreviewMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveStyleSchemePreviewMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveStyleSchemePreviewMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveStyleSchemePreviewMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveStyleSchemePreviewMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveStyleSchemePreviewMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveStyleSchemePreviewMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveStyleSchemePreviewMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveStyleSchemePreviewMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveStyleSchemePreviewMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveStyleSchemePreviewMethod "getNextAccessibleSibling" o = Gtk.Accessible.AccessibleGetNextAccessibleSiblingMethodInfo
    ResolveStyleSchemePreviewMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveStyleSchemePreviewMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveStyleSchemePreviewMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveStyleSchemePreviewMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveStyleSchemePreviewMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveStyleSchemePreviewMethod "getPlatformState" o = Gtk.Accessible.AccessibleGetPlatformStateMethodInfo
    ResolveStyleSchemePreviewMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveStyleSchemePreviewMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveStyleSchemePreviewMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveStyleSchemePreviewMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveStyleSchemePreviewMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveStyleSchemePreviewMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveStyleSchemePreviewMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveStyleSchemePreviewMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveStyleSchemePreviewMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveStyleSchemePreviewMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveStyleSchemePreviewMethod "getScheme" o = StyleSchemePreviewGetSchemeMethodInfo
    ResolveStyleSchemePreviewMethod "getSelected" o = StyleSchemePreviewGetSelectedMethodInfo
    ResolveStyleSchemePreviewMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveStyleSchemePreviewMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveStyleSchemePreviewMethod "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveStyleSchemePreviewMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveStyleSchemePreviewMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveStyleSchemePreviewMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveStyleSchemePreviewMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveStyleSchemePreviewMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveStyleSchemePreviewMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveStyleSchemePreviewMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveStyleSchemePreviewMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveStyleSchemePreviewMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveStyleSchemePreviewMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveStyleSchemePreviewMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveStyleSchemePreviewMethod "setAccessibleParent" o = Gtk.Accessible.AccessibleSetAccessibleParentMethodInfo
    ResolveStyleSchemePreviewMethod "setActionName" o = Gtk.Actionable.ActionableSetActionNameMethodInfo
    ResolveStyleSchemePreviewMethod "setActionTargetValue" o = Gtk.Actionable.ActionableSetActionTargetValueMethodInfo
    ResolveStyleSchemePreviewMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveStyleSchemePreviewMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveStyleSchemePreviewMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveStyleSchemePreviewMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveStyleSchemePreviewMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveStyleSchemePreviewMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveStyleSchemePreviewMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveStyleSchemePreviewMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveStyleSchemePreviewMethod "setDetailedActionName" o = Gtk.Actionable.ActionableSetDetailedActionNameMethodInfo
    ResolveStyleSchemePreviewMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveStyleSchemePreviewMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveStyleSchemePreviewMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveStyleSchemePreviewMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveStyleSchemePreviewMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveStyleSchemePreviewMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveStyleSchemePreviewMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveStyleSchemePreviewMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveStyleSchemePreviewMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveStyleSchemePreviewMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveStyleSchemePreviewMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveStyleSchemePreviewMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveStyleSchemePreviewMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveStyleSchemePreviewMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveStyleSchemePreviewMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveStyleSchemePreviewMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveStyleSchemePreviewMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveStyleSchemePreviewMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveStyleSchemePreviewMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveStyleSchemePreviewMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveStyleSchemePreviewMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveStyleSchemePreviewMethod "setSelected" o = StyleSchemePreviewSetSelectedMethodInfo
    ResolveStyleSchemePreviewMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveStyleSchemePreviewMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveStyleSchemePreviewMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveStyleSchemePreviewMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveStyleSchemePreviewMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveStyleSchemePreviewMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveStyleSchemePreviewMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveStyleSchemePreviewMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveStyleSchemePreviewMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveStyleSchemePreviewMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveStyleSchemePreviewMethod t StyleSchemePreview, O.OverloadedMethod info StyleSchemePreview p, R.HasField t StyleSchemePreview p) => R.HasField t StyleSchemePreview p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- signal StyleSchemePreview::activate
-- | /No description available in the introspection data./
type StyleSchemePreviewActivateCallback =
    IO ()

type C_StyleSchemePreviewActivateCallback =
    Ptr StyleSchemePreview ->               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_StyleSchemePreviewActivateCallback`.
foreign import ccall "wrapper"
    mk_StyleSchemePreviewActivateCallback :: C_StyleSchemePreviewActivateCallback -> IO (FunPtr C_StyleSchemePreviewActivateCallback)

wrap_StyleSchemePreviewActivateCallback :: 
    GObject a => (a -> StyleSchemePreviewActivateCallback) ->
    C_StyleSchemePreviewActivateCallback
wrap_StyleSchemePreviewActivateCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_StyleSchemePreviewActivateCallback
wrap_StyleSchemePreviewActivateCallback a -> IO ()
gi'cb Ptr StyleSchemePreview
gi'selfPtr Ptr ()
_ = do
    Ptr StyleSchemePreview -> (StyleSchemePreview -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr StyleSchemePreview
gi'selfPtr ((StyleSchemePreview -> IO ()) -> IO ())
-> (StyleSchemePreview -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \StyleSchemePreview
gi'self -> a -> IO ()
gi'cb (StyleSchemePreview -> a
forall a b. Coercible a b => a -> b
Coerce.coerce StyleSchemePreview
gi'self) 


-- | Connect a signal handler for the [activate](#signal:activate) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' styleSchemePreview #activate callback
-- @
-- 
-- 
onStyleSchemePreviewActivate :: (IsStyleSchemePreview a, MonadIO m) => a -> ((?self :: a) => StyleSchemePreviewActivateCallback) -> m SignalHandlerId
onStyleSchemePreviewActivate :: forall a (m :: * -> *).
(IsStyleSchemePreview a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onStyleSchemePreviewActivate a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_StyleSchemePreviewActivateCallback
wrapped' = (a -> IO ()) -> C_StyleSchemePreviewActivateCallback
forall a.
GObject a =>
(a -> IO ()) -> C_StyleSchemePreviewActivateCallback
wrap_StyleSchemePreviewActivateCallback a -> IO ()
wrapped
    FunPtr C_StyleSchemePreviewActivateCallback
wrapped'' <- C_StyleSchemePreviewActivateCallback
-> IO (FunPtr C_StyleSchemePreviewActivateCallback)
mk_StyleSchemePreviewActivateCallback C_StyleSchemePreviewActivateCallback
wrapped'
    a
-> Text
-> FunPtr C_StyleSchemePreviewActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate" FunPtr C_StyleSchemePreviewActivateCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [activate](#signal:activate) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' styleSchemePreview #activate callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterStyleSchemePreviewActivate :: (IsStyleSchemePreview a, MonadIO m) => a -> ((?self :: a) => StyleSchemePreviewActivateCallback) -> m SignalHandlerId
afterStyleSchemePreviewActivate :: forall a (m :: * -> *).
(IsStyleSchemePreview a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterStyleSchemePreviewActivate a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_StyleSchemePreviewActivateCallback
wrapped' = (a -> IO ()) -> C_StyleSchemePreviewActivateCallback
forall a.
GObject a =>
(a -> IO ()) -> C_StyleSchemePreviewActivateCallback
wrap_StyleSchemePreviewActivateCallback a -> IO ()
wrapped
    FunPtr C_StyleSchemePreviewActivateCallback
wrapped'' <- C_StyleSchemePreviewActivateCallback
-> IO (FunPtr C_StyleSchemePreviewActivateCallback)
mk_StyleSchemePreviewActivateCallback C_StyleSchemePreviewActivateCallback
wrapped'
    a
-> Text
-> FunPtr C_StyleSchemePreviewActivateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate" FunPtr C_StyleSchemePreviewActivateCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data StyleSchemePreviewActivateSignalInfo
instance SignalInfo StyleSchemePreviewActivateSignalInfo where
    type HaskellCallbackType StyleSchemePreviewActivateSignalInfo = StyleSchemePreviewActivateCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_StyleSchemePreviewActivateCallback cb
        cb'' <- mk_StyleSchemePreviewActivateCallback cb'
        connectSignalFunPtr obj "activate" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleSchemePreview::activate"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-5.0.0/docs/GI-GtkSource-Objects-StyleSchemePreview.html#g:signal:activate"})

#endif

-- VVV Prop "scheme"
   -- Type: TInterface (Name {namespace = "GtkSource", name = "StyleScheme"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@scheme@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' styleSchemePreview #scheme
-- @
getStyleSchemePreviewScheme :: (MonadIO m, IsStyleSchemePreview o) => o -> m GtkSource.StyleScheme.StyleScheme
getStyleSchemePreviewScheme :: forall (m :: * -> *) o.
(MonadIO m, IsStyleSchemePreview o) =>
o -> m StyleScheme
getStyleSchemePreviewScheme o
obj = IO StyleScheme -> m StyleScheme
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO StyleScheme -> m StyleScheme)
-> IO StyleScheme -> m StyleScheme
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe StyleScheme) -> IO StyleScheme
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getStyleSchemePreviewScheme" (IO (Maybe StyleScheme) -> IO StyleScheme)
-> IO (Maybe StyleScheme) -> IO StyleScheme
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr StyleScheme -> StyleScheme)
-> IO (Maybe StyleScheme)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"scheme" ManagedPtr StyleScheme -> StyleScheme
GtkSource.StyleScheme.StyleScheme

-- | Construct a `GValueConstruct` with valid value for the “@scheme@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructStyleSchemePreviewScheme :: (IsStyleSchemePreview o, MIO.MonadIO m, GtkSource.StyleScheme.IsStyleScheme a) => a -> m (GValueConstruct o)
constructStyleSchemePreviewScheme :: forall o (m :: * -> *) a.
(IsStyleSchemePreview o, MonadIO m, IsStyleScheme a) =>
a -> m (GValueConstruct o)
constructStyleSchemePreviewScheme a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"scheme" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data StyleSchemePreviewSchemePropertyInfo
instance AttrInfo StyleSchemePreviewSchemePropertyInfo where
    type AttrAllowedOps StyleSchemePreviewSchemePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint StyleSchemePreviewSchemePropertyInfo = IsStyleSchemePreview
    type AttrSetTypeConstraint StyleSchemePreviewSchemePropertyInfo = GtkSource.StyleScheme.IsStyleScheme
    type AttrTransferTypeConstraint StyleSchemePreviewSchemePropertyInfo = GtkSource.StyleScheme.IsStyleScheme
    type AttrTransferType StyleSchemePreviewSchemePropertyInfo = GtkSource.StyleScheme.StyleScheme
    type AttrGetType StyleSchemePreviewSchemePropertyInfo = GtkSource.StyleScheme.StyleScheme
    type AttrLabel StyleSchemePreviewSchemePropertyInfo = "scheme"
    type AttrOrigin StyleSchemePreviewSchemePropertyInfo = StyleSchemePreview
    attrGet = getStyleSchemePreviewScheme
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo GtkSource.StyleScheme.StyleScheme v
    attrConstruct = constructStyleSchemePreviewScheme
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleSchemePreview.scheme"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-5.0.0/docs/GI-GtkSource-Objects-StyleSchemePreview.html#g:attr:scheme"
        })
#endif

-- VVV Prop "selected"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@selected@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' styleSchemePreview #selected
-- @
getStyleSchemePreviewSelected :: (MonadIO m, IsStyleSchemePreview o) => o -> m Bool
getStyleSchemePreviewSelected :: forall (m :: * -> *) o.
(MonadIO m, IsStyleSchemePreview o) =>
o -> m Bool
getStyleSchemePreviewSelected o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"selected"

-- | Set the value of the “@selected@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' styleSchemePreview [ #selected 'Data.GI.Base.Attributes.:=' value ]
-- @
setStyleSchemePreviewSelected :: (MonadIO m, IsStyleSchemePreview o) => o -> Bool -> m ()
setStyleSchemePreviewSelected :: forall (m :: * -> *) o.
(MonadIO m, IsStyleSchemePreview o) =>
o -> Bool -> m ()
setStyleSchemePreviewSelected o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"selected" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@selected@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructStyleSchemePreviewSelected :: (IsStyleSchemePreview o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructStyleSchemePreviewSelected :: forall o (m :: * -> *).
(IsStyleSchemePreview o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructStyleSchemePreviewSelected Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"selected" Bool
val

#if defined(ENABLE_OVERLOADING)
data StyleSchemePreviewSelectedPropertyInfo
instance AttrInfo StyleSchemePreviewSelectedPropertyInfo where
    type AttrAllowedOps StyleSchemePreviewSelectedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint StyleSchemePreviewSelectedPropertyInfo = IsStyleSchemePreview
    type AttrSetTypeConstraint StyleSchemePreviewSelectedPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint StyleSchemePreviewSelectedPropertyInfo = (~) Bool
    type AttrTransferType StyleSchemePreviewSelectedPropertyInfo = Bool
    type AttrGetType StyleSchemePreviewSelectedPropertyInfo = Bool
    type AttrLabel StyleSchemePreviewSelectedPropertyInfo = "selected"
    type AttrOrigin StyleSchemePreviewSelectedPropertyInfo = StyleSchemePreview
    attrGet = getStyleSchemePreviewSelected
    attrSet = setStyleSchemePreviewSelected
    attrTransfer _ v = do
        return v
    attrConstruct = constructStyleSchemePreviewSelected
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleSchemePreview.selected"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-5.0.0/docs/GI-GtkSource-Objects-StyleSchemePreview.html#g:attr:selected"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList StyleSchemePreview
type instance O.AttributeList StyleSchemePreview = StyleSchemePreviewAttributeList
type StyleSchemePreviewAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("actionName", Gtk.Actionable.ActionableActionNamePropertyInfo), '("actionTarget", Gtk.Actionable.ActionableActionTargetPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("scheme", StyleSchemePreviewSchemePropertyInfo), '("selected", StyleSchemePreviewSelectedPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
styleSchemePreviewScheme :: AttrLabelProxy "scheme"
styleSchemePreviewScheme = AttrLabelProxy

styleSchemePreviewSelected :: AttrLabelProxy "selected"
styleSchemePreviewSelected = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList StyleSchemePreview = StyleSchemePreviewSignalList
type StyleSchemePreviewSignalList = ('[ '("activate", StyleSchemePreviewActivateSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method StyleSchemePreview::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "scheme"
--           , argType =
--               TInterface Name { namespace = "GtkSource" , name = "StyleScheme" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceStyleScheme"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GtkSource" , name = "StyleSchemePreview" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_style_scheme_preview_new" gtk_source_style_scheme_preview_new :: 
    Ptr GtkSource.StyleScheme.StyleScheme -> -- scheme : TInterface (Name {namespace = "GtkSource", name = "StyleScheme"})
    IO (Ptr StyleSchemePreview)

-- | Creates a new t'GI.GtkSource.Objects.StyleSchemePreview.StyleSchemePreview' to preview the style scheme
-- provided in /@scheme@/.
-- 
-- /Since: 5.4/
styleSchemePreviewNew ::
    (B.CallStack.HasCallStack, MonadIO m, GtkSource.StyleScheme.IsStyleScheme a) =>
    a
    -- ^ /@scheme@/: a t'GI.GtkSource.Objects.StyleScheme.StyleScheme'
    -> m StyleSchemePreview
    -- ^ __Returns:__ a t'GI.Gtk.Objects.Widget.Widget'
styleSchemePreviewNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleScheme a) =>
a -> m StyleSchemePreview
styleSchemePreviewNew a
scheme = IO StyleSchemePreview -> m StyleSchemePreview
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StyleSchemePreview -> m StyleSchemePreview)
-> IO StyleSchemePreview -> m StyleSchemePreview
forall a b. (a -> b) -> a -> b
$ do
    Ptr StyleScheme
scheme' <- a -> IO (Ptr StyleScheme)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
scheme
    Ptr StyleSchemePreview
result <- Ptr StyleScheme -> IO (Ptr StyleSchemePreview)
gtk_source_style_scheme_preview_new Ptr StyleScheme
scheme'
    Text -> Ptr StyleSchemePreview -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"styleSchemePreviewNew" Ptr StyleSchemePreview
result
    StyleSchemePreview
result' <- ((ManagedPtr StyleSchemePreview -> StyleSchemePreview)
-> Ptr StyleSchemePreview -> IO StyleSchemePreview
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr StyleSchemePreview -> StyleSchemePreview
StyleSchemePreview) Ptr StyleSchemePreview
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
scheme
    StyleSchemePreview -> IO StyleSchemePreview
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return StyleSchemePreview
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method StyleSchemePreview::get_scheme
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "GtkSource" , name = "StyleSchemePreview" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkSourceStyleSchemePreview"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "GtkSource" , name = "StyleScheme" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_style_scheme_preview_get_scheme" gtk_source_style_scheme_preview_get_scheme :: 
    Ptr StyleSchemePreview ->               -- self : TInterface (Name {namespace = "GtkSource", name = "StyleSchemePreview"})
    IO (Ptr GtkSource.StyleScheme.StyleScheme)

-- | Gets the t'GI.GtkSource.Objects.StyleScheme.StyleScheme' previewed by the widget.
-- 
-- /Since: 5.4/
styleSchemePreviewGetScheme ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleSchemePreview a) =>
    a
    -- ^ /@self@/: a t'GI.GtkSource.Objects.StyleSchemePreview.StyleSchemePreview'
    -> m GtkSource.StyleScheme.StyleScheme
    -- ^ __Returns:__ a t'GI.GtkSource.Objects.StyleScheme.StyleScheme'
styleSchemePreviewGetScheme :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleSchemePreview a) =>
a -> m StyleScheme
styleSchemePreviewGetScheme a
self = IO StyleScheme -> m StyleScheme
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StyleScheme -> m StyleScheme)
-> IO StyleScheme -> m StyleScheme
forall a b. (a -> b) -> a -> b
$ do
    Ptr StyleSchemePreview
self' <- a -> IO (Ptr StyleSchemePreview)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr StyleScheme
result <- Ptr StyleSchemePreview -> IO (Ptr StyleScheme)
gtk_source_style_scheme_preview_get_scheme Ptr StyleSchemePreview
self'
    Text -> Ptr StyleScheme -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"styleSchemePreviewGetScheme" Ptr StyleScheme
result
    StyleScheme
result' <- ((ManagedPtr StyleScheme -> StyleScheme)
-> Ptr StyleScheme -> IO StyleScheme
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr StyleScheme -> StyleScheme
GtkSource.StyleScheme.StyleScheme) Ptr StyleScheme
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    StyleScheme -> IO StyleScheme
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return StyleScheme
result'

#if defined(ENABLE_OVERLOADING)
data StyleSchemePreviewGetSchemeMethodInfo
instance (signature ~ (m GtkSource.StyleScheme.StyleScheme), MonadIO m, IsStyleSchemePreview a) => O.OverloadedMethod StyleSchemePreviewGetSchemeMethodInfo a signature where
    overloadedMethod = styleSchemePreviewGetScheme

instance O.OverloadedMethodInfo StyleSchemePreviewGetSchemeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleSchemePreview.styleSchemePreviewGetScheme",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-5.0.0/docs/GI-GtkSource-Objects-StyleSchemePreview.html#v:styleSchemePreviewGetScheme"
        })


#endif

-- method StyleSchemePreview::get_selected
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "GtkSource" , name = "StyleSchemePreview" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_style_scheme_preview_get_selected" gtk_source_style_scheme_preview_get_selected :: 
    Ptr StyleSchemePreview ->               -- self : TInterface (Name {namespace = "GtkSource", name = "StyleSchemePreview"})
    IO CInt

-- | /No description available in the introspection data./
styleSchemePreviewGetSelected ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleSchemePreview a) =>
    a
    -> m Bool
styleSchemePreviewGetSelected :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleSchemePreview a) =>
a -> m Bool
styleSchemePreviewGetSelected a
self = IO Bool -> m Bool
forall a. IO a -> m a
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 StyleSchemePreview
self' <- a -> IO (Ptr StyleSchemePreview)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr StyleSchemePreview -> IO CInt
gtk_source_style_scheme_preview_get_selected Ptr StyleSchemePreview
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data StyleSchemePreviewGetSelectedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsStyleSchemePreview a) => O.OverloadedMethod StyleSchemePreviewGetSelectedMethodInfo a signature where
    overloadedMethod = styleSchemePreviewGetSelected

instance O.OverloadedMethodInfo StyleSchemePreviewGetSelectedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleSchemePreview.styleSchemePreviewGetSelected",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-5.0.0/docs/GI-GtkSource-Objects-StyleSchemePreview.html#v:styleSchemePreviewGetSelected"
        })


#endif

-- method StyleSchemePreview::set_selected
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "GtkSource" , name = "StyleSchemePreview" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "selected"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_source_style_scheme_preview_set_selected" gtk_source_style_scheme_preview_set_selected :: 
    Ptr StyleSchemePreview ->               -- self : TInterface (Name {namespace = "GtkSource", name = "StyleSchemePreview"})
    CInt ->                                 -- selected : TBasicType TBoolean
    IO ()

-- | /No description available in the introspection data./
styleSchemePreviewSetSelected ::
    (B.CallStack.HasCallStack, MonadIO m, IsStyleSchemePreview a) =>
    a
    -> Bool
    -> m ()
styleSchemePreviewSetSelected :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStyleSchemePreview a) =>
a -> Bool -> m ()
styleSchemePreviewSetSelected a
self Bool
selected = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr StyleSchemePreview
self' <- a -> IO (Ptr StyleSchemePreview)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let selected' :: CInt
selected' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
selected
    Ptr StyleSchemePreview -> CInt -> IO ()
gtk_source_style_scheme_preview_set_selected Ptr StyleSchemePreview
self' CInt
selected'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StyleSchemePreviewSetSelectedMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsStyleSchemePreview a) => O.OverloadedMethod StyleSchemePreviewSetSelectedMethodInfo a signature where
    overloadedMethod = styleSchemePreviewSetSelected

instance O.OverloadedMethodInfo StyleSchemePreviewSetSelectedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GtkSource.Objects.StyleSchemePreview.styleSchemePreviewSetSelected",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtksource-5.0.0/docs/GI-GtkSource-Objects-StyleSchemePreview.html#v:styleSchemePreviewSetSelected"
        })


#endif