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


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GtkLinkButton@ is a button with a hyperlink.
-- 
-- <<https://docs.gtk.org/gtk4/link-button.png An example GtkLinkButton>>
-- 
-- It is useful to show quick links to resources.
-- 
-- A link button is created by calling either 'GI.Gtk.Objects.LinkButton.linkButtonNew' or
-- 'GI.Gtk.Objects.LinkButton.linkButtonNewWithLabel'. If using the former, the URI you
-- pass to the constructor is used as a label for the widget.
-- 
-- The URI bound to a @GtkLinkButton@ can be set specifically using
-- 'GI.Gtk.Objects.LinkButton.linkButtonSetUri'.
-- 
-- By default, @GtkLinkButton@ calls 'GI.Gtk.Functions.showUri' when the button
-- is clicked. This behaviour can be overridden by connecting to the
-- [LinkButton::activateLink]("GI.Gtk.Objects.LinkButton#g:signal:activateLink") signal and returning 'P.True' from
-- the signal handler.
-- 
-- = CSS nodes
-- 
-- @GtkLinkButton@ has a single CSS node with name button. To differentiate
-- it from a plain @GtkButton@, it gets the .link style class.
-- 
-- = Accessibility
-- 
-- @GtkLinkButton@ uses the 'GI.Gtk.Enums.AccessibleRoleLink' role.

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

module GI.Gtk.Objects.LinkButton
    ( 

-- * Exported types
    LinkButton(..)                          ,
    IsLinkButton                            ,
    toLinkButton                            ,


 -- * 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"), [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"), [getChild]("GI.Gtk.Objects.Button#g:method:getChild"), [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"), [getHasFrame]("GI.Gtk.Objects.Button#g:method:getHasFrame"), [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"), [getIconName]("GI.Gtk.Objects.Button#g:method:getIconName"), [getLabel]("GI.Gtk.Objects.Button#g:method:getLabel"), [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"), [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"), [getUri]("GI.Gtk.Objects.LinkButton#g:method:getUri"), [getUseUnderline]("GI.Gtk.Objects.Button#g:method:getUseUnderline"), [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"), [getVisited]("GI.Gtk.Objects.LinkButton#g:method:getVisited"), [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"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChild]("GI.Gtk.Objects.Button#g:method:setChild"), [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"), [setHasFrame]("GI.Gtk.Objects.Button#g:method:setHasFrame"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setIconName]("GI.Gtk.Objects.Button#g:method:setIconName"), [setLabel]("GI.Gtk.Objects.Button#g:method:setLabel"), [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"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setUri]("GI.Gtk.Objects.LinkButton#g:method:setUri"), [setUseUnderline]("GI.Gtk.Objects.Button#g:method:setUseUnderline"), [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"), [setVisited]("GI.Gtk.Objects.LinkButton#g:method:setVisited").

#if defined(ENABLE_OVERLOADING)
    ResolveLinkButtonMethod                 ,
#endif

-- ** getUri #method:getUri#

#if defined(ENABLE_OVERLOADING)
    LinkButtonGetUriMethodInfo              ,
#endif
    linkButtonGetUri                        ,


-- ** getVisited #method:getVisited#

#if defined(ENABLE_OVERLOADING)
    LinkButtonGetVisitedMethodInfo          ,
#endif
    linkButtonGetVisited                    ,


-- ** new #method:new#

    linkButtonNew                           ,


-- ** newWithLabel #method:newWithLabel#

    linkButtonNewWithLabel                  ,


-- ** setUri #method:setUri#

#if defined(ENABLE_OVERLOADING)
    LinkButtonSetUriMethodInfo              ,
#endif
    linkButtonSetUri                        ,


-- ** setVisited #method:setVisited#

#if defined(ENABLE_OVERLOADING)
    LinkButtonSetVisitedMethodInfo          ,
#endif
    linkButtonSetVisited                    ,




 -- * Properties


-- ** uri #attr:uri#
-- | The URI bound to this button.

#if defined(ENABLE_OVERLOADING)
    LinkButtonUriPropertyInfo               ,
#endif
    constructLinkButtonUri                  ,
    getLinkButtonUri                        ,
#if defined(ENABLE_OVERLOADING)
    linkButtonUri                           ,
#endif
    setLinkButtonUri                        ,


-- ** visited #attr:visited#
-- | The \'visited\' state of this button.
-- 
-- A visited link is drawn in a different color.

#if defined(ENABLE_OVERLOADING)
    LinkButtonVisitedPropertyInfo           ,
#endif
    constructLinkButtonVisited              ,
    getLinkButtonVisited                    ,
#if defined(ENABLE_OVERLOADING)
    linkButtonVisited                       ,
#endif
    setLinkButtonVisited                    ,




 -- * Signals


-- ** activateLink #signal:activateLink#

    LinkButtonActivateLinkCallback          ,
#if defined(ENABLE_OVERLOADING)
    LinkButtonActivateLinkSignalInfo        ,
#endif
    afterLinkButtonActivateLink             ,
    onLinkButtonActivateLink                ,




    ) 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.Button as Gtk.Button
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "gtk_link_button_get_type"
    c_gtk_link_button_get_type :: IO B.Types.GType

instance B.Types.TypedObject LinkButton where
    glibType :: IO GType
glibType = IO GType
c_gtk_link_button_get_type

instance B.Types.GObject LinkButton

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

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

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

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

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

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

#endif

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

#endif

-- signal LinkButton::activate-link
-- | Emitted each time the @GtkLinkButton@ is clicked.
-- 
-- The default handler will call 'GI.Gtk.Functions.showUri' with the URI
-- stored inside the [LinkButton:uri]("GI.Gtk.Objects.LinkButton#g:attr:uri") property.
-- 
-- To override the default behavior, you can connect to the
-- [activateLink](#g:signal:activateLink) signal and stop the propagation of the signal
-- by returning 'P.True' from your handler.
type LinkButtonActivateLinkCallback =
    IO Bool
    -- ^ __Returns:__ 'P.True' if the signal has been handled

type C_LinkButtonActivateLinkCallback =
    Ptr LinkButton ->                       -- object
    Ptr () ->                               -- user_data
    IO CInt

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

wrap_LinkButtonActivateLinkCallback :: 
    GObject a => (a -> LinkButtonActivateLinkCallback) ->
    C_LinkButtonActivateLinkCallback
wrap_LinkButtonActivateLinkCallback :: forall a.
GObject a =>
(a -> LinkButtonActivateLinkCallback)
-> C_LinkButtonActivateLinkCallback
wrap_LinkButtonActivateLinkCallback a -> LinkButtonActivateLinkCallback
gi'cb Ptr LinkButton
gi'selfPtr Ptr ()
_ = do
    Bool
result <- Ptr LinkButton
-> (LinkButton -> LinkButtonActivateLinkCallback)
-> LinkButtonActivateLinkCallback
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr LinkButton
gi'selfPtr ((LinkButton -> LinkButtonActivateLinkCallback)
 -> LinkButtonActivateLinkCallback)
-> (LinkButton -> LinkButtonActivateLinkCallback)
-> LinkButtonActivateLinkCallback
forall a b. (a -> b) -> a -> b
$ \LinkButton
gi'self -> a -> LinkButtonActivateLinkCallback
gi'cb (LinkButton -> a
forall a b. Coercible a b => a -> b
Coerce.coerce LinkButton
gi'self) 
    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 [activateLink](#signal:activateLink) 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' linkButton #activateLink callback
-- @
-- 
-- 
onLinkButtonActivateLink :: (IsLinkButton a, MonadIO m) => a -> ((?self :: a) => LinkButtonActivateLinkCallback) -> m SignalHandlerId
onLinkButtonActivateLink :: forall a (m :: * -> *).
(IsLinkButton a, MonadIO m) =>
a
-> ((?self::a) => LinkButtonActivateLinkCallback)
-> m SignalHandlerId
onLinkButtonActivateLink a
obj (?self::a) => LinkButtonActivateLinkCallback
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 -> LinkButtonActivateLinkCallback
wrapped a
self = let ?self = a
?self::a
self in LinkButtonActivateLinkCallback
(?self::a) => LinkButtonActivateLinkCallback
cb
    let wrapped' :: C_LinkButtonActivateLinkCallback
wrapped' = (a -> LinkButtonActivateLinkCallback)
-> C_LinkButtonActivateLinkCallback
forall a.
GObject a =>
(a -> LinkButtonActivateLinkCallback)
-> C_LinkButtonActivateLinkCallback
wrap_LinkButtonActivateLinkCallback a -> LinkButtonActivateLinkCallback
wrapped
    FunPtr C_LinkButtonActivateLinkCallback
wrapped'' <- C_LinkButtonActivateLinkCallback
-> IO (FunPtr C_LinkButtonActivateLinkCallback)
mk_LinkButtonActivateLinkCallback C_LinkButtonActivateLinkCallback
wrapped'
    a
-> Text
-> FunPtr C_LinkButtonActivateLinkCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate-link" FunPtr C_LinkButtonActivateLinkCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [activateLink](#signal:activateLink) 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' linkButton #activateLink 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.
-- 
afterLinkButtonActivateLink :: (IsLinkButton a, MonadIO m) => a -> ((?self :: a) => LinkButtonActivateLinkCallback) -> m SignalHandlerId
afterLinkButtonActivateLink :: forall a (m :: * -> *).
(IsLinkButton a, MonadIO m) =>
a
-> ((?self::a) => LinkButtonActivateLinkCallback)
-> m SignalHandlerId
afterLinkButtonActivateLink a
obj (?self::a) => LinkButtonActivateLinkCallback
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 -> LinkButtonActivateLinkCallback
wrapped a
self = let ?self = a
?self::a
self in LinkButtonActivateLinkCallback
(?self::a) => LinkButtonActivateLinkCallback
cb
    let wrapped' :: C_LinkButtonActivateLinkCallback
wrapped' = (a -> LinkButtonActivateLinkCallback)
-> C_LinkButtonActivateLinkCallback
forall a.
GObject a =>
(a -> LinkButtonActivateLinkCallback)
-> C_LinkButtonActivateLinkCallback
wrap_LinkButtonActivateLinkCallback a -> LinkButtonActivateLinkCallback
wrapped
    FunPtr C_LinkButtonActivateLinkCallback
wrapped'' <- C_LinkButtonActivateLinkCallback
-> IO (FunPtr C_LinkButtonActivateLinkCallback)
mk_LinkButtonActivateLinkCallback C_LinkButtonActivateLinkCallback
wrapped'
    a
-> Text
-> FunPtr C_LinkButtonActivateLinkCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate-link" FunPtr C_LinkButtonActivateLinkCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


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

#endif

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

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

-- | Set the value of the “@uri@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' linkButton [ #uri 'Data.GI.Base.Attributes.:=' value ]
-- @
setLinkButtonUri :: (MonadIO m, IsLinkButton o) => o -> T.Text -> m ()
setLinkButtonUri :: forall (m :: * -> *) o.
(MonadIO m, IsLinkButton o) =>
o -> Text -> m ()
setLinkButtonUri o
obj Text
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 -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"uri" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@uri@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructLinkButtonUri :: (IsLinkButton o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructLinkButtonUri :: forall o (m :: * -> *).
(IsLinkButton o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructLinkButtonUri Text
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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"uri" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

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

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

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

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

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

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList LinkButton
type instance O.AttributeList LinkButton = LinkButtonAttributeList
type LinkButtonAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("actionName", Gtk.Actionable.ActionableActionNamePropertyInfo), '("actionTarget", Gtk.Actionable.ActionableActionTargetPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("child", Gtk.Button.ButtonChildPropertyInfo), '("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), '("hasFrame", Gtk.Button.ButtonHasFramePropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("iconName", Gtk.Button.ButtonIconNamePropertyInfo), '("label", Gtk.Button.ButtonLabelPropertyInfo), '("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), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("uri", LinkButtonUriPropertyInfo), '("useUnderline", Gtk.Button.ButtonUseUnderlinePropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("visited", LinkButtonVisitedPropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
linkButtonUri :: AttrLabelProxy "uri"
linkButtonUri = AttrLabelProxy

linkButtonVisited :: AttrLabelProxy "visited"
linkButtonVisited = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList LinkButton = LinkButtonSignalList
type LinkButtonSignalList = ('[ '("activate", Gtk.Button.ButtonActivateSignalInfo), '("activateLink", LinkButtonActivateLinkSignalInfo), '("clicked", Gtk.Button.ButtonClickedSignalInfo), '("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, *)])

#endif

-- method LinkButton::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "LinkButton" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_link_button_new" gtk_link_button_new :: 
    CString ->                              -- uri : TBasicType TUTF8
    IO (Ptr LinkButton)

-- | Creates a new @GtkLinkButton@ with the URI as its text.
linkButtonNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@uri@/: a valid URI
    -> m LinkButton
    -- ^ __Returns:__ a new link button widget.
linkButtonNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m LinkButton
linkButtonNew Text
uri = IO LinkButton -> m LinkButton
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO LinkButton -> m LinkButton) -> IO LinkButton -> m LinkButton
forall a b. (a -> b) -> a -> b
$ do
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    Ptr LinkButton
result <- CString -> IO (Ptr LinkButton)
gtk_link_button_new CString
uri'
    Text -> Ptr LinkButton -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"linkButtonNew" Ptr LinkButton
result
    LinkButton
result' <- ((ManagedPtr LinkButton -> LinkButton)
-> Ptr LinkButton -> IO LinkButton
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr LinkButton -> LinkButton
LinkButton) Ptr LinkButton
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    LinkButton -> IO LinkButton
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LinkButton
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method LinkButton::new_with_label
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the text of the button"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "LinkButton" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_link_button_new_with_label" gtk_link_button_new_with_label :: 
    CString ->                              -- uri : TBasicType TUTF8
    CString ->                              -- label : TBasicType TUTF8
    IO (Ptr LinkButton)

-- | Creates a new @GtkLinkButton@ containing a label.
linkButtonNewWithLabel ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@uri@/: a valid URI
    -> Maybe (T.Text)
    -- ^ /@label@/: the text of the button
    -> m LinkButton
    -- ^ __Returns:__ a new link button widget.
linkButtonNewWithLabel :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Maybe Text -> m LinkButton
linkButtonNewWithLabel Text
uri Maybe Text
label = IO LinkButton -> m LinkButton
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO LinkButton -> m LinkButton) -> IO LinkButton -> m LinkButton
forall a b. (a -> b) -> a -> b
$ do
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    CString
maybeLabel <- case Maybe Text
label of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jLabel -> do
            CString
jLabel' <- Text -> IO CString
textToCString Text
jLabel
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jLabel'
    Ptr LinkButton
result <- CString -> CString -> IO (Ptr LinkButton)
gtk_link_button_new_with_label CString
uri' CString
maybeLabel
    Text -> Ptr LinkButton -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"linkButtonNewWithLabel" Ptr LinkButton
result
    LinkButton
result' <- ((ManagedPtr LinkButton -> LinkButton)
-> Ptr LinkButton -> IO LinkButton
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr LinkButton -> LinkButton
LinkButton) Ptr LinkButton
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeLabel
    LinkButton -> IO LinkButton
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return LinkButton
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method LinkButton::get_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "link_button"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "LinkButton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkLinkButton`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_link_button_get_uri" gtk_link_button_get_uri :: 
    Ptr LinkButton ->                       -- link_button : TInterface (Name {namespace = "Gtk", name = "LinkButton"})
    IO CString

-- | Retrieves the URI of the @GtkLinkButton@.
linkButtonGetUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsLinkButton a) =>
    a
    -- ^ /@linkButton@/: a @GtkLinkButton@
    -> m T.Text
    -- ^ __Returns:__ a valid URI. The returned string is owned by the link button
    --   and should not be modified or freed.
linkButtonGetUri :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLinkButton a) =>
a -> m Text
linkButtonGetUri a
linkButton = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr LinkButton
linkButton' <- a -> IO (Ptr LinkButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
linkButton
    CString
result <- Ptr LinkButton -> IO CString
gtk_link_button_get_uri Ptr LinkButton
linkButton'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"linkButtonGetUri" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
linkButton
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data LinkButtonGetUriMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsLinkButton a) => O.OverloadedMethod LinkButtonGetUriMethodInfo a signature where
    overloadedMethod = linkButtonGetUri

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


#endif

-- method LinkButton::get_visited
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "link_button"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "LinkButton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkLinkButton`" , 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_link_button_get_visited" gtk_link_button_get_visited :: 
    Ptr LinkButton ->                       -- link_button : TInterface (Name {namespace = "Gtk", name = "LinkButton"})
    IO CInt

-- | Retrieves the “visited” state of the @GtkLinkButton@.
-- 
-- The button becomes visited when it is clicked. If the URI
-- is changed on the button, the “visited” state is unset again.
-- 
-- The state may also be changed using 'GI.Gtk.Objects.LinkButton.linkButtonSetVisited'.
linkButtonGetVisited ::
    (B.CallStack.HasCallStack, MonadIO m, IsLinkButton a) =>
    a
    -- ^ /@linkButton@/: a @GtkLinkButton@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the link has been visited, 'P.False' otherwise
linkButtonGetVisited :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLinkButton a) =>
a -> m Bool
linkButtonGetVisited a
linkButton = LinkButtonActivateLinkCallback -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (LinkButtonActivateLinkCallback -> m Bool)
-> LinkButtonActivateLinkCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr LinkButton
linkButton' <- a -> IO (Ptr LinkButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
linkButton
    CInt
result <- Ptr LinkButton -> IO CInt
gtk_link_button_get_visited Ptr LinkButton
linkButton'
    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
linkButton
    Bool -> LinkButtonActivateLinkCallback
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data LinkButtonGetVisitedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsLinkButton a) => O.OverloadedMethod LinkButtonGetVisitedMethodInfo a signature where
    overloadedMethod = linkButtonGetVisited

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


#endif

-- method LinkButton::set_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "link_button"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "LinkButton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkLinkButton`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid URI" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_link_button_set_uri" gtk_link_button_set_uri :: 
    Ptr LinkButton ->                       -- link_button : TInterface (Name {namespace = "Gtk", name = "LinkButton"})
    CString ->                              -- uri : TBasicType TUTF8
    IO ()

-- | Sets /@uri@/ as the URI where the @GtkLinkButton@ points.
-- 
-- As a side-effect this unsets the “visited” state of the button.
linkButtonSetUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsLinkButton a) =>
    a
    -- ^ /@linkButton@/: a @GtkLinkButton@
    -> T.Text
    -- ^ /@uri@/: a valid URI
    -> m ()
linkButtonSetUri :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLinkButton a) =>
a -> Text -> m ()
linkButtonSetUri a
linkButton Text
uri = 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 LinkButton
linkButton' <- a -> IO (Ptr LinkButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
linkButton
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    Ptr LinkButton -> CString -> IO ()
gtk_link_button_set_uri Ptr LinkButton
linkButton' CString
uri'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
linkButton
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LinkButtonSetUriMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsLinkButton a) => O.OverloadedMethod LinkButtonSetUriMethodInfo a signature where
    overloadedMethod = linkButtonSetUri

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


#endif

-- method LinkButton::set_visited
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "link_button"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "LinkButton" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkLinkButton`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "visited"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new \8220visited\8221 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_link_button_set_visited" gtk_link_button_set_visited :: 
    Ptr LinkButton ->                       -- link_button : TInterface (Name {namespace = "Gtk", name = "LinkButton"})
    CInt ->                                 -- visited : TBasicType TBoolean
    IO ()

-- | Sets the “visited” state of the @GtkLinkButton@.
-- 
-- See 'GI.Gtk.Objects.LinkButton.linkButtonGetVisited' for more details.
linkButtonSetVisited ::
    (B.CallStack.HasCallStack, MonadIO m, IsLinkButton a) =>
    a
    -- ^ /@linkButton@/: a @GtkLinkButton@
    -> Bool
    -- ^ /@visited@/: the new “visited” state
    -> m ()
linkButtonSetVisited :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLinkButton a) =>
a -> Bool -> m ()
linkButtonSetVisited a
linkButton Bool
visited = 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 LinkButton
linkButton' <- a -> IO (Ptr LinkButton)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
linkButton
    let visited' :: CInt
visited' = (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
visited
    Ptr LinkButton -> CInt -> IO ()
gtk_link_button_set_visited Ptr LinkButton
linkButton' CInt
visited'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
linkButton
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LinkButtonSetVisitedMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsLinkButton a) => O.OverloadedMethod LinkButtonSetVisitedMethodInfo a signature where
    overloadedMethod = linkButtonSetVisited

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


#endif