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


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkSwitch@ is a \"light switch\" that has two states: on or off.
-- 
-- <<https://docs.gtk.org/gtk4/switch.png An example GtkSwitch>>
-- 
-- The user can control which state should be active by clicking the
-- empty area, or by dragging the handle.
-- 
-- @GtkSwitch@ can also handle situations where the underlying state
-- changes with a delay. See [signal/@gtkSwitch@/[stateSet](#g:signal:stateSet)] for details.
-- 
-- = CSS nodes
-- 
-- >switch
-- >├── label
-- >├── label
-- >╰── slider
-- 
-- 
-- @GtkSwitch@ has four css nodes, the main node with the name switch and
-- subnodes for the slider and the on and off labels. Neither of them is
-- using any style classes.
-- 
-- = Accessibility
-- 
-- @GtkSwitch@ uses the 'GI.Gtk.Enums.AccessibleRoleSwitch' role.

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

module GI.Gtk.Objects.Switch
    ( 

-- * Exported types
    Switch(..)                              ,
    IsSwitch                                ,
    toSwitch                                ,


 -- * 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"), [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
-- [getAccessibleRole]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleRole"), [getActionName]("GI.Gtk.Interfaces.Actionable#g:method:getActionName"), [getActionTargetValue]("GI.Gtk.Interfaces.Actionable#g:method:getActionTargetValue"), [getActive]("GI.Gtk.Objects.Switch#g:method:getActive"), [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"), [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"), [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"), [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"), [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"), [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"), [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"), [getState]("GI.Gtk.Objects.Switch#g:method:getState"), [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
-- [setActionName]("GI.Gtk.Interfaces.Actionable#g:method:setActionName"), [setActionTargetValue]("GI.Gtk.Interfaces.Actionable#g:method:setActionTargetValue"), [setActive]("GI.Gtk.Objects.Switch#g:method:setActive"), [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"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setState]("GI.Gtk.Objects.Switch#g:method:setState"), [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)
    ResolveSwitchMethod                     ,
#endif

-- ** getActive #method:getActive#

#if defined(ENABLE_OVERLOADING)
    SwitchGetActiveMethodInfo               ,
#endif
    switchGetActive                         ,


-- ** getState #method:getState#

#if defined(ENABLE_OVERLOADING)
    SwitchGetStateMethodInfo                ,
#endif
    switchGetState                          ,


-- ** new #method:new#

    switchNew                               ,


-- ** setActive #method:setActive#

#if defined(ENABLE_OVERLOADING)
    SwitchSetActiveMethodInfo               ,
#endif
    switchSetActive                         ,


-- ** setState #method:setState#

#if defined(ENABLE_OVERLOADING)
    SwitchSetStateMethodInfo                ,
#endif
    switchSetState                          ,




 -- * Properties


-- ** active #attr:active#
-- | Whether the @GtkSwitch@ widget is in its on or off state.

#if defined(ENABLE_OVERLOADING)
    SwitchActivePropertyInfo                ,
#endif
    constructSwitchActive                   ,
    getSwitchActive                         ,
    setSwitchActive                         ,
#if defined(ENABLE_OVERLOADING)
    switchActive                            ,
#endif


-- ** state #attr:state#
-- | The backend state that is controlled by the switch.
-- 
-- See [signal/@gtkSwitch@/[stateSet](#g:signal:stateSet)] for details.

#if defined(ENABLE_OVERLOADING)
    SwitchStatePropertyInfo                 ,
#endif
    constructSwitchState                    ,
    getSwitchState                          ,
    setSwitchState                          ,
#if defined(ENABLE_OVERLOADING)
    switchState                             ,
#endif




 -- * Signals


-- ** activate #signal:activate#

    SwitchActivateCallback                  ,
#if defined(ENABLE_OVERLOADING)
    SwitchActivateSignalInfo                ,
#endif
    afterSwitchActivate                     ,
    onSwitchActivate                        ,


-- ** stateSet #signal:stateSet#

    SwitchStateSetCallback                  ,
#if defined(ENABLE_OVERLOADING)
    SwitchStateSetSignalInfo                ,
#endif
    afterSwitchStateSet                     ,
    onSwitchStateSet                        ,




    ) where

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

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

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

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

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

foreign import ccall "gtk_switch_get_type"
    c_gtk_switch_get_type :: IO B.Types.GType

instance B.Types.TypedObject Switch where
    glibType :: IO GType
glibType = IO GType
c_gtk_switch_get_type

instance B.Types.GObject Switch

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

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

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

-- | Convert 'Switch' 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 Switch) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_switch_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Switch -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Switch
P.Nothing = Ptr GValue -> Ptr Switch -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Switch
forall a. Ptr a
FP.nullPtr :: FP.Ptr Switch)
    gvalueSet_ Ptr GValue
gv (P.Just Switch
obj) = Switch -> (Ptr Switch -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Switch
obj (Ptr GValue -> Ptr Switch -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Switch)
gvalueGet_ Ptr GValue
gv = do
        Ptr Switch
ptr <- Ptr GValue -> IO (Ptr Switch)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Switch)
        if Ptr Switch
ptr Ptr Switch -> Ptr Switch -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Switch
forall a. Ptr a
FP.nullPtr
        then Switch -> Maybe Switch
forall a. a -> Maybe a
P.Just (Switch -> Maybe Switch) -> IO Switch -> IO (Maybe Switch)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Switch -> Switch) -> Ptr Switch -> IO Switch
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Switch -> Switch
Switch Ptr Switch
ptr
        else Maybe Switch -> IO (Maybe Switch)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Switch
forall a. Maybe a
P.Nothing
        
    

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

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

#endif

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

#endif

-- signal Switch::activate
-- | Emitted to animate the switch.
-- 
-- Applications should never connect to this signal,
-- but use the [Switch:active]("GI.Gtk.Objects.Switch#g:attr:active") property.
type SwitchActivateCallback =
    IO ()

type C_SwitchActivateCallback =
    Ptr Switch ->                           -- object
    Ptr () ->                               -- user_data
    IO ()

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

wrap_SwitchActivateCallback :: 
    GObject a => (a -> SwitchActivateCallback) ->
    C_SwitchActivateCallback
wrap_SwitchActivateCallback :: forall a. GObject a => (a -> IO ()) -> C_SwitchActivateCallback
wrap_SwitchActivateCallback a -> IO ()
gi'cb Ptr Switch
gi'selfPtr Ptr ()
_ = do
    Ptr Switch -> (Switch -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Switch
gi'selfPtr ((Switch -> IO ()) -> IO ()) -> (Switch -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Switch
gi'self -> a -> IO ()
gi'cb (Switch -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Switch
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' switch #activate callback
-- @
-- 
-- 
onSwitchActivate :: (IsSwitch a, MonadIO m) => a -> ((?self :: a) => SwitchActivateCallback) -> m SignalHandlerId
onSwitchActivate :: forall a (m :: * -> *).
(IsSwitch a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onSwitchActivate 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_SwitchActivateCallback
wrapped' = (a -> IO ()) -> C_SwitchActivateCallback
forall a. GObject a => (a -> IO ()) -> C_SwitchActivateCallback
wrap_SwitchActivateCallback a -> IO ()
wrapped
    FunPtr C_SwitchActivateCallback
wrapped'' <- C_SwitchActivateCallback -> IO (FunPtr C_SwitchActivateCallback)
mk_SwitchActivateCallback C_SwitchActivateCallback
wrapped'
    a
-> Text
-> FunPtr C_SwitchActivateCallback
-> 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_SwitchActivateCallback
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' switch #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.
-- 
afterSwitchActivate :: (IsSwitch a, MonadIO m) => a -> ((?self :: a) => SwitchActivateCallback) -> m SignalHandlerId
afterSwitchActivate :: forall a (m :: * -> *).
(IsSwitch a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterSwitchActivate 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_SwitchActivateCallback
wrapped' = (a -> IO ()) -> C_SwitchActivateCallback
forall a. GObject a => (a -> IO ()) -> C_SwitchActivateCallback
wrap_SwitchActivateCallback a -> IO ()
wrapped
    FunPtr C_SwitchActivateCallback
wrapped'' <- C_SwitchActivateCallback -> IO (FunPtr C_SwitchActivateCallback)
mk_SwitchActivateCallback C_SwitchActivateCallback
wrapped'
    a
-> Text
-> FunPtr C_SwitchActivateCallback
-> 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_SwitchActivateCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data SwitchActivateSignalInfo
instance SignalInfo SwitchActivateSignalInfo where
    type HaskellCallbackType SwitchActivateSignalInfo = SwitchActivateCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_SwitchActivateCallback cb
        cb'' <- mk_SwitchActivateCallback cb'
        connectSignalFunPtr obj "activate" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Switch::activate"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Switch.html#g:signal:activate"})

#endif

-- signal Switch::state-set
-- | Emitted to change the underlying state.
-- 
-- The [stateSet](#g:signal:stateSet) signal is emitted when the user changes the switch
-- position. The default handler keeps the state in sync with the
-- [Switch:active]("GI.Gtk.Objects.Switch#g:attr:active") property.
-- 
-- To implement delayed state change, applications can connect to this
-- signal, initiate the change of the underlying state, and call
-- 'GI.Gtk.Objects.Switch.switchSetState' when the underlying state change is
-- complete. The signal handler should return 'P.True' to prevent the
-- default handler from running.
-- 
-- Visually, the underlying state is represented by the trough color of
-- the switch, while the [Switch:active]("GI.Gtk.Objects.Switch#g:attr:active") property is
-- represented by the position of the switch.
type SwitchStateSetCallback =
    Bool
    -- ^ /@state@/: the new state of the switch
    -> IO Bool
    -- ^ __Returns:__ 'P.True' to stop the signal emission

type C_SwitchStateSetCallback =
    Ptr Switch ->                           -- object
    CInt ->
    Ptr () ->                               -- user_data
    IO CInt

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

wrap_SwitchStateSetCallback :: 
    GObject a => (a -> SwitchStateSetCallback) ->
    C_SwitchStateSetCallback
wrap_SwitchStateSetCallback :: forall a.
GObject a =>
(a -> SwitchStateSetCallback) -> C_SwitchStateSetCallback
wrap_SwitchStateSetCallback a -> SwitchStateSetCallback
gi'cb Ptr Switch
gi'selfPtr CInt
state Ptr ()
_ = do
    let state' :: Bool
state' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
state
    Bool
result <- Ptr Switch -> (Switch -> IO Bool) -> IO Bool
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Switch
gi'selfPtr ((Switch -> IO Bool) -> IO Bool) -> (Switch -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Switch
gi'self -> a -> SwitchStateSetCallback
gi'cb (Switch -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Switch
gi'self)  Bool
state'
    let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
result
    CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- | Connect a signal handler for the [stateSet](#signal:stateSet) 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' switch #stateSet callback
-- @
-- 
-- 
onSwitchStateSet :: (IsSwitch a, MonadIO m) => a -> ((?self :: a) => SwitchStateSetCallback) -> m SignalHandlerId
onSwitchStateSet :: forall a (m :: * -> *).
(IsSwitch a, MonadIO m) =>
a -> ((?self::a) => SwitchStateSetCallback) -> m SignalHandlerId
onSwitchStateSet a
obj (?self::a) => SwitchStateSetCallback
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 -> SwitchStateSetCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SwitchStateSetCallback
SwitchStateSetCallback
cb
    let wrapped' :: C_SwitchStateSetCallback
wrapped' = (a -> SwitchStateSetCallback) -> C_SwitchStateSetCallback
forall a.
GObject a =>
(a -> SwitchStateSetCallback) -> C_SwitchStateSetCallback
wrap_SwitchStateSetCallback a -> SwitchStateSetCallback
wrapped
    FunPtr C_SwitchStateSetCallback
wrapped'' <- C_SwitchStateSetCallback -> IO (FunPtr C_SwitchStateSetCallback)
mk_SwitchStateSetCallback C_SwitchStateSetCallback
wrapped'
    a
-> Text
-> FunPtr C_SwitchStateSetCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"state-set" FunPtr C_SwitchStateSetCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [stateSet](#signal:stateSet) 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' switch #stateSet 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.
-- 
afterSwitchStateSet :: (IsSwitch a, MonadIO m) => a -> ((?self :: a) => SwitchStateSetCallback) -> m SignalHandlerId
afterSwitchStateSet :: forall a (m :: * -> *).
(IsSwitch a, MonadIO m) =>
a -> ((?self::a) => SwitchStateSetCallback) -> m SignalHandlerId
afterSwitchStateSet a
obj (?self::a) => SwitchStateSetCallback
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 -> SwitchStateSetCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => SwitchStateSetCallback
SwitchStateSetCallback
cb
    let wrapped' :: C_SwitchStateSetCallback
wrapped' = (a -> SwitchStateSetCallback) -> C_SwitchStateSetCallback
forall a.
GObject a =>
(a -> SwitchStateSetCallback) -> C_SwitchStateSetCallback
wrap_SwitchStateSetCallback a -> SwitchStateSetCallback
wrapped
    FunPtr C_SwitchStateSetCallback
wrapped'' <- C_SwitchStateSetCallback -> IO (FunPtr C_SwitchStateSetCallback)
mk_SwitchStateSetCallback C_SwitchStateSetCallback
wrapped'
    a
-> Text
-> FunPtr C_SwitchStateSetCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"state-set" FunPtr C_SwitchStateSetCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data SwitchStateSetSignalInfo
instance SignalInfo SwitchStateSetSignalInfo where
    type HaskellCallbackType SwitchStateSetSignalInfo = SwitchStateSetCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_SwitchStateSetCallback cb
        cb'' <- mk_SwitchStateSetCallback cb'
        connectSignalFunPtr obj "state-set" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Switch::state-set"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Switch.html#g:signal:stateSet"})

#endif

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

-- | Get the value of the “@active@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' switch #active
-- @
getSwitchActive :: (MonadIO m, IsSwitch o) => o -> m Bool
getSwitchActive :: forall (m :: * -> *) o. (MonadIO m, IsSwitch o) => o -> m Bool
getSwitchActive 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
"active"

-- | Set the value of the “@active@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' switch [ #active 'Data.GI.Base.Attributes.:=' value ]
-- @
setSwitchActive :: (MonadIO m, IsSwitch o) => o -> Bool -> m ()
setSwitchActive :: forall (m :: * -> *) o.
(MonadIO m, IsSwitch o) =>
o -> Bool -> m ()
setSwitchActive 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
"active" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@active@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSwitchActive :: (IsSwitch o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSwitchActive :: forall o (m :: * -> *).
(IsSwitch o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructSwitchActive 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
"active" Bool
val

#if defined(ENABLE_OVERLOADING)
data SwitchActivePropertyInfo
instance AttrInfo SwitchActivePropertyInfo where
    type AttrAllowedOps SwitchActivePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SwitchActivePropertyInfo = IsSwitch
    type AttrSetTypeConstraint SwitchActivePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SwitchActivePropertyInfo = (~) Bool
    type AttrTransferType SwitchActivePropertyInfo = Bool
    type AttrGetType SwitchActivePropertyInfo = Bool
    type AttrLabel SwitchActivePropertyInfo = "active"
    type AttrOrigin SwitchActivePropertyInfo = Switch
    attrGet = getSwitchActive
    attrSet = setSwitchActive
    attrTransfer _ v = do
        return v
    attrConstruct = constructSwitchActive
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Switch.active"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Switch.html#g:attr:active"
        })
#endif

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

-- | Get the value of the “@state@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' switch #state
-- @
getSwitchState :: (MonadIO m, IsSwitch o) => o -> m Bool
getSwitchState :: forall (m :: * -> *) o. (MonadIO m, IsSwitch o) => o -> m Bool
getSwitchState 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
"state"

-- | Set the value of the “@state@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' switch [ #state 'Data.GI.Base.Attributes.:=' value ]
-- @
setSwitchState :: (MonadIO m, IsSwitch o) => o -> Bool -> m ()
setSwitchState :: forall (m :: * -> *) o.
(MonadIO m, IsSwitch o) =>
o -> Bool -> m ()
setSwitchState 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
"state" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@state@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSwitchState :: (IsSwitch o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructSwitchState :: forall o (m :: * -> *).
(IsSwitch o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructSwitchState 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
"state" Bool
val

#if defined(ENABLE_OVERLOADING)
data SwitchStatePropertyInfo
instance AttrInfo SwitchStatePropertyInfo where
    type AttrAllowedOps SwitchStatePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SwitchStatePropertyInfo = IsSwitch
    type AttrSetTypeConstraint SwitchStatePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint SwitchStatePropertyInfo = (~) Bool
    type AttrTransferType SwitchStatePropertyInfo = Bool
    type AttrGetType SwitchStatePropertyInfo = Bool
    type AttrLabel SwitchStatePropertyInfo = "state"
    type AttrOrigin SwitchStatePropertyInfo = Switch
    attrGet = getSwitchState
    attrSet = setSwitchState
    attrTransfer _ v = do
        return v
    attrConstruct = constructSwitchState
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Switch.state"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-Switch.html#g:attr:state"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Switch
type instance O.AttributeList Switch = SwitchAttributeList
type SwitchAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("actionName", Gtk.Actionable.ActionableActionNamePropertyInfo), '("actionTarget", Gtk.Actionable.ActionableActionTargetPropertyInfo), '("active", SwitchActivePropertyInfo), '("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), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("state", SwitchStatePropertyInfo), '("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, *)])
#endif

#if defined(ENABLE_OVERLOADING)
switchActive :: AttrLabelProxy "active"
switchActive = AttrLabelProxy

switchState :: AttrLabelProxy "state"
switchState = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Switch = SwitchSignalList
type SwitchSignalList = ('[ '("activate", SwitchActivateSignalInfo), '("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), '("stateSet", SwitchStateSetSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "gtk_switch_new" gtk_switch_new :: 
    IO (Ptr Switch)

-- | Creates a new @GtkSwitch@ widget.
switchNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Switch
    -- ^ __Returns:__ the newly created @GtkSwitch@ instance
switchNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Switch
switchNew  = IO Switch -> m Switch
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Switch -> m Switch) -> IO Switch -> m Switch
forall a b. (a -> b) -> a -> b
$ do
    Ptr Switch
result <- IO (Ptr Switch)
gtk_switch_new
    Text -> Ptr Switch -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"switchNew" Ptr Switch
result
    Switch
result' <- ((ManagedPtr Switch -> Switch) -> Ptr Switch -> IO Switch
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Switch -> Switch
Switch) Ptr Switch
result
    Switch -> IO Switch
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Switch
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Switch::get_active
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Switch" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkSwitch`" , 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_switch_get_active" gtk_switch_get_active :: 
    Ptr Switch ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Switch"})
    IO CInt

-- | Gets whether the @GtkSwitch@ is in its “on” or “off” state.
switchGetActive ::
    (B.CallStack.HasCallStack, MonadIO m, IsSwitch a) =>
    a
    -- ^ /@self@/: a @GtkSwitch@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the @GtkSwitch@ is active, and 'P.False' otherwise
switchGetActive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSwitch a) =>
a -> m Bool
switchGetActive 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 Switch
self' <- a -> IO (Ptr Switch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr Switch -> IO CInt
gtk_switch_get_active Ptr Switch
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
    SwitchStateSetCallback
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SwitchGetActiveMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSwitch a) => O.OverloadedMethod SwitchGetActiveMethodInfo a signature where
    overloadedMethod = switchGetActive

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


#endif

-- method Switch::get_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Switch" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkSwitch`" , 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_switch_get_state" gtk_switch_get_state :: 
    Ptr Switch ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Switch"})
    IO CInt

-- | Gets the underlying state of the @GtkSwitch@.
switchGetState ::
    (B.CallStack.HasCallStack, MonadIO m, IsSwitch a) =>
    a
    -- ^ /@self@/: a @GtkSwitch@
    -> m Bool
    -- ^ __Returns:__ the underlying state
switchGetState :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSwitch a) =>
a -> m Bool
switchGetState 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 Switch
self' <- a -> IO (Ptr Switch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr Switch -> IO CInt
gtk_switch_get_state Ptr Switch
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
    SwitchStateSetCallback
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data SwitchGetStateMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSwitch a) => O.OverloadedMethod SwitchGetStateMethodInfo a signature where
    overloadedMethod = switchGetState

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


#endif

-- method Switch::set_active
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Switch" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkSwitch`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "is_active"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "%TRUE if @self should be active, and %FALSE otherwise"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_switch_set_active" gtk_switch_set_active :: 
    Ptr Switch ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Switch"})
    CInt ->                                 -- is_active : TBasicType TBoolean
    IO ()

-- | Changes the state of /@self@/ to the desired one.
switchSetActive ::
    (B.CallStack.HasCallStack, MonadIO m, IsSwitch a) =>
    a
    -- ^ /@self@/: a @GtkSwitch@
    -> Bool
    -- ^ /@isActive@/: 'P.True' if /@self@/ should be active, and 'P.False' otherwise
    -> m ()
switchSetActive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSwitch a) =>
a -> Bool -> m ()
switchSetActive a
self Bool
isActive = 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 Switch
self' <- a -> IO (Ptr Switch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let isActive' :: CInt
isActive' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
isActive
    Ptr Switch -> CInt -> IO ()
gtk_switch_set_active Ptr Switch
self' CInt
isActive'
    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 SwitchSetActiveMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsSwitch a) => O.OverloadedMethod SwitchSetActiveMethodInfo a signature where
    overloadedMethod = switchSetActive

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


#endif

-- method Switch::set_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Switch" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkSwitch`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "state"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new state" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_switch_set_state" gtk_switch_set_state :: 
    Ptr Switch ->                           -- self : TInterface (Name {namespace = "Gtk", name = "Switch"})
    CInt ->                                 -- state : TBasicType TBoolean
    IO ()

-- | Sets the underlying state of the @GtkSwitch@.
-- 
-- Normally, this is the same as [Switch:active]("GI.Gtk.Objects.Switch#g:attr:active"), unless
-- the switch is set up for delayed state changes. This function is
-- typically called from a [Switch::stateSet]("GI.Gtk.Objects.Switch#g:signal:stateSet") signal handler.
-- 
-- See [Switch::stateSet]("GI.Gtk.Objects.Switch#g:signal:stateSet") for details.
switchSetState ::
    (B.CallStack.HasCallStack, MonadIO m, IsSwitch a) =>
    a
    -- ^ /@self@/: a @GtkSwitch@
    -> Bool
    -- ^ /@state@/: the new state
    -> m ()
switchSetState :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSwitch a) =>
a -> Bool -> m ()
switchSetState a
self Bool
state = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Switch
self' <- a -> IO (Ptr Switch)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let state' :: CInt
state' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
state
    Ptr Switch -> CInt -> IO ()
gtk_switch_set_state Ptr Switch
self' CInt
state'
    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 SwitchSetStateMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsSwitch a) => O.OverloadedMethod SwitchSetStateMethodInfo a signature where
    overloadedMethod = switchSetState

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


#endif