{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.Label
    ( 
    Label(..)                               ,
    IsLabel                                 ,
    toLabel                                 ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveLabelMethod                      ,
#endif
#if defined(ENABLE_OVERLOADING)
    LabelGetAttributesMethodInfo            ,
#endif
    labelGetAttributes                      ,
#if defined(ENABLE_OVERLOADING)
    LabelGetCurrentUriMethodInfo            ,
#endif
    labelGetCurrentUri                      ,
#if defined(ENABLE_OVERLOADING)
    LabelGetEllipsizeMethodInfo             ,
#endif
    labelGetEllipsize                       ,
#if defined(ENABLE_OVERLOADING)
    LabelGetExtraMenuMethodInfo             ,
#endif
    labelGetExtraMenu                       ,
#if defined(ENABLE_OVERLOADING)
    LabelGetJustifyMethodInfo               ,
#endif
    labelGetJustify                         ,
#if defined(ENABLE_OVERLOADING)
    LabelGetLabelMethodInfo                 ,
#endif
    labelGetLabel                           ,
#if defined(ENABLE_OVERLOADING)
    LabelGetLayoutMethodInfo                ,
#endif
    labelGetLayout                          ,
#if defined(ENABLE_OVERLOADING)
    LabelGetLayoutOffsetsMethodInfo         ,
#endif
    labelGetLayoutOffsets                   ,
#if defined(ENABLE_OVERLOADING)
    LabelGetLinesMethodInfo                 ,
#endif
    labelGetLines                           ,
#if defined(ENABLE_OVERLOADING)
    LabelGetMaxWidthCharsMethodInfo         ,
#endif
    labelGetMaxWidthChars                   ,
#if defined(ENABLE_OVERLOADING)
    LabelGetMnemonicKeyvalMethodInfo        ,
#endif
    labelGetMnemonicKeyval                  ,
#if defined(ENABLE_OVERLOADING)
    LabelGetMnemonicWidgetMethodInfo        ,
#endif
    labelGetMnemonicWidget                  ,
#if defined(ENABLE_OVERLOADING)
    LabelGetSelectableMethodInfo            ,
#endif
    labelGetSelectable                      ,
#if defined(ENABLE_OVERLOADING)
    LabelGetSelectionBoundsMethodInfo       ,
#endif
    labelGetSelectionBounds                 ,
#if defined(ENABLE_OVERLOADING)
    LabelGetSingleLineModeMethodInfo        ,
#endif
    labelGetSingleLineMode                  ,
#if defined(ENABLE_OVERLOADING)
    LabelGetTextMethodInfo                  ,
#endif
    labelGetText                            ,
#if defined(ENABLE_OVERLOADING)
    LabelGetUseMarkupMethodInfo             ,
#endif
    labelGetUseMarkup                       ,
#if defined(ENABLE_OVERLOADING)
    LabelGetUseUnderlineMethodInfo          ,
#endif
    labelGetUseUnderline                    ,
#if defined(ENABLE_OVERLOADING)
    LabelGetWidthCharsMethodInfo            ,
#endif
    labelGetWidthChars                      ,
#if defined(ENABLE_OVERLOADING)
    LabelGetWrapMethodInfo                  ,
#endif
    labelGetWrap                            ,
#if defined(ENABLE_OVERLOADING)
    LabelGetWrapModeMethodInfo              ,
#endif
    labelGetWrapMode                        ,
#if defined(ENABLE_OVERLOADING)
    LabelGetXalignMethodInfo                ,
#endif
    labelGetXalign                          ,
#if defined(ENABLE_OVERLOADING)
    LabelGetYalignMethodInfo                ,
#endif
    labelGetYalign                          ,
    labelNew                                ,
    labelNewWithMnemonic                    ,
#if defined(ENABLE_OVERLOADING)
    LabelSelectRegionMethodInfo             ,
#endif
    labelSelectRegion                       ,
#if defined(ENABLE_OVERLOADING)
    LabelSetAttributesMethodInfo            ,
#endif
    labelSetAttributes                      ,
#if defined(ENABLE_OVERLOADING)
    LabelSetEllipsizeMethodInfo             ,
#endif
    labelSetEllipsize                       ,
#if defined(ENABLE_OVERLOADING)
    LabelSetExtraMenuMethodInfo             ,
#endif
    labelSetExtraMenu                       ,
#if defined(ENABLE_OVERLOADING)
    LabelSetJustifyMethodInfo               ,
#endif
    labelSetJustify                         ,
#if defined(ENABLE_OVERLOADING)
    LabelSetLabelMethodInfo                 ,
#endif
    labelSetLabel                           ,
#if defined(ENABLE_OVERLOADING)
    LabelSetLinesMethodInfo                 ,
#endif
    labelSetLines                           ,
#if defined(ENABLE_OVERLOADING)
    LabelSetMarkupMethodInfo                ,
#endif
    labelSetMarkup                          ,
#if defined(ENABLE_OVERLOADING)
    LabelSetMarkupWithMnemonicMethodInfo    ,
#endif
    labelSetMarkupWithMnemonic              ,
#if defined(ENABLE_OVERLOADING)
    LabelSetMaxWidthCharsMethodInfo         ,
#endif
    labelSetMaxWidthChars                   ,
#if defined(ENABLE_OVERLOADING)
    LabelSetMnemonicWidgetMethodInfo        ,
#endif
    labelSetMnemonicWidget                  ,
#if defined(ENABLE_OVERLOADING)
    LabelSetSelectableMethodInfo            ,
#endif
    labelSetSelectable                      ,
#if defined(ENABLE_OVERLOADING)
    LabelSetSingleLineModeMethodInfo        ,
#endif
    labelSetSingleLineMode                  ,
#if defined(ENABLE_OVERLOADING)
    LabelSetTextMethodInfo                  ,
#endif
    labelSetText                            ,
#if defined(ENABLE_OVERLOADING)
    LabelSetTextWithMnemonicMethodInfo      ,
#endif
    labelSetTextWithMnemonic                ,
#if defined(ENABLE_OVERLOADING)
    LabelSetUseMarkupMethodInfo             ,
#endif
    labelSetUseMarkup                       ,
#if defined(ENABLE_OVERLOADING)
    LabelSetUseUnderlineMethodInfo          ,
#endif
    labelSetUseUnderline                    ,
#if defined(ENABLE_OVERLOADING)
    LabelSetWidthCharsMethodInfo            ,
#endif
    labelSetWidthChars                      ,
#if defined(ENABLE_OVERLOADING)
    LabelSetWrapMethodInfo                  ,
#endif
    labelSetWrap                            ,
#if defined(ENABLE_OVERLOADING)
    LabelSetWrapModeMethodInfo              ,
#endif
    labelSetWrapMode                        ,
#if defined(ENABLE_OVERLOADING)
    LabelSetXalignMethodInfo                ,
#endif
    labelSetXalign                          ,
#if defined(ENABLE_OVERLOADING)
    LabelSetYalignMethodInfo                ,
#endif
    labelSetYalign                          ,
 
#if defined(ENABLE_OVERLOADING)
    LabelAttributesPropertyInfo             ,
#endif
    clearLabelAttributes                    ,
    constructLabelAttributes                ,
    getLabelAttributes                      ,
#if defined(ENABLE_OVERLOADING)
    labelAttributes                         ,
#endif
    setLabelAttributes                      ,
#if defined(ENABLE_OVERLOADING)
    LabelEllipsizePropertyInfo              ,
#endif
    constructLabelEllipsize                 ,
    getLabelEllipsize                       ,
#if defined(ENABLE_OVERLOADING)
    labelEllipsize                          ,
#endif
    setLabelEllipsize                       ,
#if defined(ENABLE_OVERLOADING)
    LabelExtraMenuPropertyInfo              ,
#endif
    clearLabelExtraMenu                     ,
    constructLabelExtraMenu                 ,
    getLabelExtraMenu                       ,
#if defined(ENABLE_OVERLOADING)
    labelExtraMenu                          ,
#endif
    setLabelExtraMenu                       ,
#if defined(ENABLE_OVERLOADING)
    LabelJustifyPropertyInfo                ,
#endif
    constructLabelJustify                   ,
    getLabelJustify                         ,
#if defined(ENABLE_OVERLOADING)
    labelJustify                            ,
#endif
    setLabelJustify                         ,
#if defined(ENABLE_OVERLOADING)
    LabelLabelPropertyInfo                  ,
#endif
    constructLabelLabel                     ,
    getLabelLabel                           ,
#if defined(ENABLE_OVERLOADING)
    labelLabel                              ,
#endif
    setLabelLabel                           ,
#if defined(ENABLE_OVERLOADING)
    LabelLinesPropertyInfo                  ,
#endif
    constructLabelLines                     ,
    getLabelLines                           ,
#if defined(ENABLE_OVERLOADING)
    labelLines                              ,
#endif
    setLabelLines                           ,
#if defined(ENABLE_OVERLOADING)
    LabelMaxWidthCharsPropertyInfo          ,
#endif
    constructLabelMaxWidthChars             ,
    getLabelMaxWidthChars                   ,
#if defined(ENABLE_OVERLOADING)
    labelMaxWidthChars                      ,
#endif
    setLabelMaxWidthChars                   ,
#if defined(ENABLE_OVERLOADING)
    LabelMnemonicKeyvalPropertyInfo         ,
#endif
    getLabelMnemonicKeyval                  ,
#if defined(ENABLE_OVERLOADING)
    labelMnemonicKeyval                     ,
#endif
#if defined(ENABLE_OVERLOADING)
    LabelMnemonicWidgetPropertyInfo         ,
#endif
    clearLabelMnemonicWidget                ,
    constructLabelMnemonicWidget            ,
    getLabelMnemonicWidget                  ,
#if defined(ENABLE_OVERLOADING)
    labelMnemonicWidget                     ,
#endif
    setLabelMnemonicWidget                  ,
#if defined(ENABLE_OVERLOADING)
    LabelSelectablePropertyInfo             ,
#endif
    constructLabelSelectable                ,
    getLabelSelectable                      ,
#if defined(ENABLE_OVERLOADING)
    labelSelectable                         ,
#endif
    setLabelSelectable                      ,
#if defined(ENABLE_OVERLOADING)
    LabelSingleLineModePropertyInfo         ,
#endif
    constructLabelSingleLineMode            ,
    getLabelSingleLineMode                  ,
#if defined(ENABLE_OVERLOADING)
    labelSingleLineMode                     ,
#endif
    setLabelSingleLineMode                  ,
#if defined(ENABLE_OVERLOADING)
    LabelUseMarkupPropertyInfo              ,
#endif
    constructLabelUseMarkup                 ,
    getLabelUseMarkup                       ,
#if defined(ENABLE_OVERLOADING)
    labelUseMarkup                          ,
#endif
    setLabelUseMarkup                       ,
#if defined(ENABLE_OVERLOADING)
    LabelUseUnderlinePropertyInfo           ,
#endif
    constructLabelUseUnderline              ,
    getLabelUseUnderline                    ,
#if defined(ENABLE_OVERLOADING)
    labelUseUnderline                       ,
#endif
    setLabelUseUnderline                    ,
#if defined(ENABLE_OVERLOADING)
    LabelWidthCharsPropertyInfo             ,
#endif
    constructLabelWidthChars                ,
    getLabelWidthChars                      ,
#if defined(ENABLE_OVERLOADING)
    labelWidthChars                         ,
#endif
    setLabelWidthChars                      ,
#if defined(ENABLE_OVERLOADING)
    LabelWrapPropertyInfo                   ,
#endif
    constructLabelWrap                      ,
    getLabelWrap                            ,
#if defined(ENABLE_OVERLOADING)
    labelWrap                               ,
#endif
    setLabelWrap                            ,
#if defined(ENABLE_OVERLOADING)
    LabelWrapModePropertyInfo               ,
#endif
    constructLabelWrapMode                  ,
    getLabelWrapMode                        ,
#if defined(ENABLE_OVERLOADING)
    labelWrapMode                           ,
#endif
    setLabelWrapMode                        ,
#if defined(ENABLE_OVERLOADING)
    LabelXalignPropertyInfo                 ,
#endif
    constructLabelXalign                    ,
    getLabelXalign                          ,
#if defined(ENABLE_OVERLOADING)
    labelXalign                             ,
#endif
    setLabelXalign                          ,
#if defined(ENABLE_OVERLOADING)
    LabelYalignPropertyInfo                 ,
#endif
    constructLabelYalign                    ,
    getLabelYalign                          ,
#if defined(ENABLE_OVERLOADING)
    labelYalign                             ,
#endif
    setLabelYalign                          ,
 
    C_LabelActivateCurrentLinkCallback      ,
    LabelActivateCurrentLinkCallback        ,
#if defined(ENABLE_OVERLOADING)
    LabelActivateCurrentLinkSignalInfo      ,
#endif
    afterLabelActivateCurrentLink           ,
    genClosure_LabelActivateCurrentLink     ,
    mk_LabelActivateCurrentLinkCallback     ,
    noLabelActivateCurrentLinkCallback      ,
    onLabelActivateCurrentLink              ,
    wrap_LabelActivateCurrentLinkCallback   ,
    C_LabelActivateLinkCallback             ,
    LabelActivateLinkCallback               ,
#if defined(ENABLE_OVERLOADING)
    LabelActivateLinkSignalInfo             ,
#endif
    afterLabelActivateLink                  ,
    genClosure_LabelActivateLink            ,
    mk_LabelActivateLinkCallback            ,
    noLabelActivateLinkCallback             ,
    onLabelActivateLink                     ,
    wrap_LabelActivateLinkCallback          ,
    C_LabelCopyClipboardCallback            ,
    LabelCopyClipboardCallback              ,
#if defined(ENABLE_OVERLOADING)
    LabelCopyClipboardSignalInfo            ,
#endif
    afterLabelCopyClipboard                 ,
    genClosure_LabelCopyClipboard           ,
    mk_LabelCopyClipboardCallback           ,
    noLabelCopyClipboardCallback            ,
    onLabelCopyClipboard                    ,
    wrap_LabelCopyClipboardCallback         ,
    C_LabelMoveCursorCallback               ,
    LabelMoveCursorCallback                 ,
#if defined(ENABLE_OVERLOADING)
    LabelMoveCursorSignalInfo               ,
#endif
    afterLabelMoveCursor                    ,
    genClosure_LabelMoveCursor              ,
    mk_LabelMoveCursorCallback              ,
    noLabelMoveCursorCallback               ,
    onLabelMoveCursor                       ,
    wrap_LabelMoveCursorCallback            ,
    ) 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.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Objects.MenuModel as Gio.MenuModel
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
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
import qualified GI.Pango.Enums as Pango.Enums
import qualified GI.Pango.Objects.Layout as Pango.Layout
import qualified GI.Pango.Structs.AttrList as Pango.AttrList
newtype Label = Label (SP.ManagedPtr Label)
    deriving (Label -> Label -> Bool
(Label -> Label -> Bool) -> (Label -> Label -> Bool) -> Eq Label
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Label -> Label -> Bool
$c/= :: Label -> Label -> Bool
== :: Label -> Label -> Bool
$c== :: Label -> Label -> Bool
Eq)
instance SP.ManagedPtrNewtype Label where
    toManagedPtr :: Label -> ManagedPtr Label
toManagedPtr (Label ManagedPtr Label
p) = ManagedPtr Label
p
foreign import ccall "gtk_label_get_type"
    c_gtk_label_get_type :: IO B.Types.GType
instance B.Types.TypedObject Label where
    glibType :: IO GType
glibType = IO GType
c_gtk_label_get_type
instance B.Types.GObject Label
class (SP.GObject o, O.IsDescendantOf Label o) => IsLabel o
instance (SP.GObject o, O.IsDescendantOf Label o) => IsLabel o
instance O.HasParentTypes Label
type instance O.ParentTypes Label = '[Gtk.Widget.Widget, GObject.Object.Object, Gtk.Accessible.Accessible, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget]
toLabel :: (MIO.MonadIO m, IsLabel o) => o -> m Label
toLabel :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m Label
toLabel = IO Label -> m Label
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Label -> m Label) -> (o -> IO Label) -> o -> m Label
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Label -> Label) -> o -> IO Label
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Label -> Label
Label
instance B.GValue.IsGValue (Maybe Label) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_label_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Label -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Label
P.Nothing = Ptr GValue -> Ptr Label -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Label
forall a. Ptr a
FP.nullPtr :: FP.Ptr Label)
    gvalueSet_ Ptr GValue
gv (P.Just Label
obj) = Label -> (Ptr Label -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Label
obj (Ptr GValue -> Ptr Label -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Label)
gvalueGet_ Ptr GValue
gv = do
        Ptr Label
ptr <- Ptr GValue -> IO (Ptr Label)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Label)
        if Ptr Label
ptr Ptr Label -> Ptr Label -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Label
forall a. Ptr a
FP.nullPtr
        then Label -> Maybe Label
forall a. a -> Maybe a
P.Just (Label -> Maybe Label) -> IO Label -> IO (Maybe Label)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Label -> Label) -> Ptr Label -> IO Label
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Label -> Label
Label Ptr Label
ptr
        else Maybe Label -> IO (Maybe Label)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Label
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolveLabelMethod (t :: Symbol) (o :: *) :: * where
    ResolveLabelMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveLabelMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveLabelMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveLabelMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveLabelMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveLabelMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveLabelMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveLabelMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveLabelMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveLabelMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveLabelMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveLabelMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveLabelMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveLabelMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveLabelMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveLabelMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveLabelMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveLabelMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveLabelMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveLabelMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveLabelMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveLabelMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveLabelMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveLabelMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveLabelMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveLabelMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveLabelMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveLabelMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveLabelMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveLabelMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveLabelMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveLabelMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveLabelMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveLabelMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveLabelMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveLabelMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveLabelMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveLabelMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveLabelMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveLabelMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveLabelMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveLabelMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveLabelMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveLabelMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveLabelMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveLabelMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveLabelMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveLabelMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveLabelMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveLabelMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveLabelMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveLabelMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveLabelMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveLabelMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveLabelMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveLabelMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveLabelMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveLabelMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveLabelMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveLabelMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveLabelMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveLabelMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveLabelMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveLabelMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveLabelMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveLabelMethod "selectRegion" o = LabelSelectRegionMethodInfo
    ResolveLabelMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveLabelMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveLabelMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveLabelMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveLabelMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveLabelMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveLabelMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveLabelMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveLabelMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveLabelMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveLabelMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveLabelMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveLabelMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveLabelMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveLabelMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveLabelMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveLabelMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveLabelMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveLabelMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    ResolveLabelMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveLabelMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveLabelMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveLabelMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveLabelMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveLabelMethod "getAttributes" o = LabelGetAttributesMethodInfo
    ResolveLabelMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveLabelMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveLabelMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveLabelMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveLabelMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveLabelMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveLabelMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveLabelMethod "getCurrentUri" o = LabelGetCurrentUriMethodInfo
    ResolveLabelMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveLabelMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveLabelMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveLabelMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveLabelMethod "getEllipsize" o = LabelGetEllipsizeMethodInfo
    ResolveLabelMethod "getExtraMenu" o = LabelGetExtraMenuMethodInfo
    ResolveLabelMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveLabelMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveLabelMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveLabelMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveLabelMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveLabelMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveLabelMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveLabelMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveLabelMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveLabelMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveLabelMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveLabelMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveLabelMethod "getJustify" o = LabelGetJustifyMethodInfo
    ResolveLabelMethod "getLabel" o = LabelGetLabelMethodInfo
    ResolveLabelMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveLabelMethod "getLayout" o = LabelGetLayoutMethodInfo
    ResolveLabelMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveLabelMethod "getLayoutOffsets" o = LabelGetLayoutOffsetsMethodInfo
    ResolveLabelMethod "getLines" o = LabelGetLinesMethodInfo
    ResolveLabelMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveLabelMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveLabelMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveLabelMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveLabelMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveLabelMethod "getMaxWidthChars" o = LabelGetMaxWidthCharsMethodInfo
    ResolveLabelMethod "getMnemonicKeyval" o = LabelGetMnemonicKeyvalMethodInfo
    ResolveLabelMethod "getMnemonicWidget" o = LabelGetMnemonicWidgetMethodInfo
    ResolveLabelMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveLabelMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveLabelMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveLabelMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveLabelMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveLabelMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveLabelMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveLabelMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveLabelMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveLabelMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveLabelMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveLabelMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveLabelMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveLabelMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveLabelMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveLabelMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveLabelMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveLabelMethod "getSelectable" o = LabelGetSelectableMethodInfo
    ResolveLabelMethod "getSelectionBounds" o = LabelGetSelectionBoundsMethodInfo
    ResolveLabelMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveLabelMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveLabelMethod "getSingleLineMode" o = LabelGetSingleLineModeMethodInfo
    ResolveLabelMethod "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveLabelMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveLabelMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveLabelMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveLabelMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveLabelMethod "getText" o = LabelGetTextMethodInfo
    ResolveLabelMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveLabelMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveLabelMethod "getUseMarkup" o = LabelGetUseMarkupMethodInfo
    ResolveLabelMethod "getUseUnderline" o = LabelGetUseUnderlineMethodInfo
    ResolveLabelMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveLabelMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveLabelMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveLabelMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveLabelMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveLabelMethod "getWidthChars" o = LabelGetWidthCharsMethodInfo
    ResolveLabelMethod "getWrap" o = LabelGetWrapMethodInfo
    ResolveLabelMethod "getWrapMode" o = LabelGetWrapModeMethodInfo
    ResolveLabelMethod "getXalign" o = LabelGetXalignMethodInfo
    ResolveLabelMethod "getYalign" o = LabelGetYalignMethodInfo
    ResolveLabelMethod "setAttributes" o = LabelSetAttributesMethodInfo
    ResolveLabelMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveLabelMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveLabelMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveLabelMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveLabelMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveLabelMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveLabelMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveLabelMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveLabelMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveLabelMethod "setEllipsize" o = LabelSetEllipsizeMethodInfo
    ResolveLabelMethod "setExtraMenu" o = LabelSetExtraMenuMethodInfo
    ResolveLabelMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveLabelMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveLabelMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveLabelMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveLabelMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveLabelMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveLabelMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveLabelMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveLabelMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveLabelMethod "setJustify" o = LabelSetJustifyMethodInfo
    ResolveLabelMethod "setLabel" o = LabelSetLabelMethodInfo
    ResolveLabelMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveLabelMethod "setLines" o = LabelSetLinesMethodInfo
    ResolveLabelMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveLabelMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveLabelMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveLabelMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveLabelMethod "setMarkup" o = LabelSetMarkupMethodInfo
    ResolveLabelMethod "setMarkupWithMnemonic" o = LabelSetMarkupWithMnemonicMethodInfo
    ResolveLabelMethod "setMaxWidthChars" o = LabelSetMaxWidthCharsMethodInfo
    ResolveLabelMethod "setMnemonicWidget" o = LabelSetMnemonicWidgetMethodInfo
    ResolveLabelMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveLabelMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveLabelMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveLabelMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveLabelMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveLabelMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveLabelMethod "setSelectable" o = LabelSetSelectableMethodInfo
    ResolveLabelMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveLabelMethod "setSingleLineMode" o = LabelSetSingleLineModeMethodInfo
    ResolveLabelMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveLabelMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveLabelMethod "setText" o = LabelSetTextMethodInfo
    ResolveLabelMethod "setTextWithMnemonic" o = LabelSetTextWithMnemonicMethodInfo
    ResolveLabelMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveLabelMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveLabelMethod "setUseMarkup" o = LabelSetUseMarkupMethodInfo
    ResolveLabelMethod "setUseUnderline" o = LabelSetUseUnderlineMethodInfo
    ResolveLabelMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveLabelMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveLabelMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveLabelMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveLabelMethod "setWidthChars" o = LabelSetWidthCharsMethodInfo
    ResolveLabelMethod "setWrap" o = LabelSetWrapMethodInfo
    ResolveLabelMethod "setWrapMode" o = LabelSetWrapModeMethodInfo
    ResolveLabelMethod "setXalign" o = LabelSetXalignMethodInfo
    ResolveLabelMethod "setYalign" o = LabelSetYalignMethodInfo
    ResolveLabelMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveLabelMethod t Label, O.OverloadedMethod info Label p) => OL.IsLabel t (Label -> 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 ~ ResolveLabelMethod t Label, O.OverloadedMethod info Label p, R.HasField t Label p) => R.HasField t Label p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveLabelMethod t Label, O.OverloadedMethodInfo info Label) => OL.IsLabel t (O.MethodProxy info Label) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
type LabelActivateCurrentLinkCallback =
    IO ()
noLabelActivateCurrentLinkCallback :: Maybe LabelActivateCurrentLinkCallback
noLabelActivateCurrentLinkCallback :: Maybe (IO ())
noLabelActivateCurrentLinkCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_LabelActivateCurrentLinkCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_LabelActivateCurrentLinkCallback :: C_LabelActivateCurrentLinkCallback -> IO (FunPtr C_LabelActivateCurrentLinkCallback)
genClosure_LabelActivateCurrentLink :: MonadIO m => LabelActivateCurrentLinkCallback -> m (GClosure C_LabelActivateCurrentLinkCallback)
genClosure_LabelActivateCurrentLink :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_LabelActivateCurrentLinkCallback)
genClosure_LabelActivateCurrentLink IO ()
cb = IO (GClosure C_LabelActivateCurrentLinkCallback)
-> m (GClosure C_LabelActivateCurrentLinkCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_LabelActivateCurrentLinkCallback)
 -> m (GClosure C_LabelActivateCurrentLinkCallback))
-> IO (GClosure C_LabelActivateCurrentLinkCallback)
-> m (GClosure C_LabelActivateCurrentLinkCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_LabelActivateCurrentLinkCallback
cb' = IO () -> C_LabelActivateCurrentLinkCallback
wrap_LabelActivateCurrentLinkCallback IO ()
cb
    C_LabelActivateCurrentLinkCallback
-> IO (FunPtr C_LabelActivateCurrentLinkCallback)
mk_LabelActivateCurrentLinkCallback C_LabelActivateCurrentLinkCallback
cb' IO (FunPtr C_LabelActivateCurrentLinkCallback)
-> (FunPtr C_LabelActivateCurrentLinkCallback
    -> IO (GClosure C_LabelActivateCurrentLinkCallback))
-> IO (GClosure C_LabelActivateCurrentLinkCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_LabelActivateCurrentLinkCallback
-> IO (GClosure C_LabelActivateCurrentLinkCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_LabelActivateCurrentLinkCallback ::
    LabelActivateCurrentLinkCallback ->
    C_LabelActivateCurrentLinkCallback
wrap_LabelActivateCurrentLinkCallback :: IO () -> C_LabelActivateCurrentLinkCallback
wrap_LabelActivateCurrentLinkCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onLabelActivateCurrentLink :: (IsLabel a, MonadIO m) => a -> LabelActivateCurrentLinkCallback -> m SignalHandlerId
onLabelActivateCurrentLink :: forall a (m :: * -> *).
(IsLabel a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onLabelActivateCurrentLink a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_LabelActivateCurrentLinkCallback
cb' = IO () -> C_LabelActivateCurrentLinkCallback
wrap_LabelActivateCurrentLinkCallback IO ()
cb
    FunPtr C_LabelActivateCurrentLinkCallback
cb'' <- C_LabelActivateCurrentLinkCallback
-> IO (FunPtr C_LabelActivateCurrentLinkCallback)
mk_LabelActivateCurrentLinkCallback C_LabelActivateCurrentLinkCallback
cb'
    a
-> Text
-> FunPtr C_LabelActivateCurrentLinkCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate-current-link" FunPtr C_LabelActivateCurrentLinkCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterLabelActivateCurrentLink :: (IsLabel a, MonadIO m) => a -> LabelActivateCurrentLinkCallback -> m SignalHandlerId
afterLabelActivateCurrentLink :: forall a (m :: * -> *).
(IsLabel a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterLabelActivateCurrentLink a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_LabelActivateCurrentLinkCallback
cb' = IO () -> C_LabelActivateCurrentLinkCallback
wrap_LabelActivateCurrentLinkCallback IO ()
cb
    FunPtr C_LabelActivateCurrentLinkCallback
cb'' <- C_LabelActivateCurrentLinkCallback
-> IO (FunPtr C_LabelActivateCurrentLinkCallback)
mk_LabelActivateCurrentLinkCallback C_LabelActivateCurrentLinkCallback
cb'
    a
-> Text
-> FunPtr C_LabelActivateCurrentLinkCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"activate-current-link" FunPtr C_LabelActivateCurrentLinkCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data LabelActivateCurrentLinkSignalInfo
instance SignalInfo LabelActivateCurrentLinkSignalInfo where
    type HaskellCallbackType LabelActivateCurrentLinkSignalInfo = LabelActivateCurrentLinkCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_LabelActivateCurrentLinkCallback cb
        cb'' <- mk_LabelActivateCurrentLinkCallback cb'
        connectSignalFunPtr obj "activate-current-link" cb'' connectMode detail
#endif
type LabelActivateLinkCallback =
    T.Text
    
    -> IO Bool
    
noLabelActivateLinkCallback :: Maybe LabelActivateLinkCallback
noLabelActivateLinkCallback :: Maybe LabelActivateLinkCallback
noLabelActivateLinkCallback = Maybe LabelActivateLinkCallback
forall a. Maybe a
Nothing
type C_LabelActivateLinkCallback =
    Ptr () ->                               
    CString ->
    Ptr () ->                               
    IO CInt
foreign import ccall "wrapper"
    mk_LabelActivateLinkCallback :: C_LabelActivateLinkCallback -> IO (FunPtr C_LabelActivateLinkCallback)
genClosure_LabelActivateLink :: MonadIO m => LabelActivateLinkCallback -> m (GClosure C_LabelActivateLinkCallback)
genClosure_LabelActivateLink :: forall (m :: * -> *).
MonadIO m =>
LabelActivateLinkCallback
-> m (GClosure C_LabelActivateLinkCallback)
genClosure_LabelActivateLink LabelActivateLinkCallback
cb = IO (GClosure C_LabelActivateLinkCallback)
-> m (GClosure C_LabelActivateLinkCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_LabelActivateLinkCallback)
 -> m (GClosure C_LabelActivateLinkCallback))
-> IO (GClosure C_LabelActivateLinkCallback)
-> m (GClosure C_LabelActivateLinkCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_LabelActivateLinkCallback
cb' = LabelActivateLinkCallback -> C_LabelActivateLinkCallback
wrap_LabelActivateLinkCallback LabelActivateLinkCallback
cb
    C_LabelActivateLinkCallback
-> IO (FunPtr C_LabelActivateLinkCallback)
mk_LabelActivateLinkCallback C_LabelActivateLinkCallback
cb' IO (FunPtr C_LabelActivateLinkCallback)
-> (FunPtr C_LabelActivateLinkCallback
    -> IO (GClosure C_LabelActivateLinkCallback))
-> IO (GClosure C_LabelActivateLinkCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_LabelActivateLinkCallback
-> IO (GClosure C_LabelActivateLinkCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_LabelActivateLinkCallback ::
    LabelActivateLinkCallback ->
    C_LabelActivateLinkCallback
wrap_LabelActivateLinkCallback :: LabelActivateLinkCallback -> C_LabelActivateLinkCallback
wrap_LabelActivateLinkCallback LabelActivateLinkCallback
_cb Ptr ()
_ CString
uri Ptr ()
_ = do
    Text
uri' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
uri
    Bool
result <- LabelActivateLinkCallback
_cb  Text
uri'
    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 (m :: * -> *) a. Monad m => a -> m a
return CInt
result'
onLabelActivateLink :: (IsLabel a, MonadIO m) => a -> LabelActivateLinkCallback -> m SignalHandlerId
onLabelActivateLink :: forall a (m :: * -> *).
(IsLabel a, MonadIO m) =>
a -> LabelActivateLinkCallback -> m SignalHandlerId
onLabelActivateLink a
obj LabelActivateLinkCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_LabelActivateLinkCallback
cb' = LabelActivateLinkCallback -> C_LabelActivateLinkCallback
wrap_LabelActivateLinkCallback LabelActivateLinkCallback
cb
    FunPtr C_LabelActivateLinkCallback
cb'' <- C_LabelActivateLinkCallback
-> IO (FunPtr C_LabelActivateLinkCallback)
mk_LabelActivateLinkCallback C_LabelActivateLinkCallback
cb'
    a
-> Text
-> FunPtr C_LabelActivateLinkCallback
-> 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_LabelActivateLinkCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterLabelActivateLink :: (IsLabel a, MonadIO m) => a -> LabelActivateLinkCallback -> m SignalHandlerId
afterLabelActivateLink :: forall a (m :: * -> *).
(IsLabel a, MonadIO m) =>
a -> LabelActivateLinkCallback -> m SignalHandlerId
afterLabelActivateLink a
obj LabelActivateLinkCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_LabelActivateLinkCallback
cb' = LabelActivateLinkCallback -> C_LabelActivateLinkCallback
wrap_LabelActivateLinkCallback LabelActivateLinkCallback
cb
    FunPtr C_LabelActivateLinkCallback
cb'' <- C_LabelActivateLinkCallback
-> IO (FunPtr C_LabelActivateLinkCallback)
mk_LabelActivateLinkCallback C_LabelActivateLinkCallback
cb'
    a
-> Text
-> FunPtr C_LabelActivateLinkCallback
-> 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_LabelActivateLinkCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data LabelActivateLinkSignalInfo
instance SignalInfo LabelActivateLinkSignalInfo where
    type HaskellCallbackType LabelActivateLinkSignalInfo = LabelActivateLinkCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_LabelActivateLinkCallback cb
        cb'' <- mk_LabelActivateLinkCallback cb'
        connectSignalFunPtr obj "activate-link" cb'' connectMode detail
#endif
type LabelCopyClipboardCallback =
    IO ()
noLabelCopyClipboardCallback :: Maybe LabelCopyClipboardCallback
noLabelCopyClipboardCallback :: Maybe (IO ())
noLabelCopyClipboardCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_LabelCopyClipboardCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_LabelCopyClipboardCallback :: C_LabelCopyClipboardCallback -> IO (FunPtr C_LabelCopyClipboardCallback)
genClosure_LabelCopyClipboard :: MonadIO m => LabelCopyClipboardCallback -> m (GClosure C_LabelCopyClipboardCallback)
genClosure_LabelCopyClipboard :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_LabelActivateCurrentLinkCallback)
genClosure_LabelCopyClipboard IO ()
cb = IO (GClosure C_LabelActivateCurrentLinkCallback)
-> m (GClosure C_LabelActivateCurrentLinkCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_LabelActivateCurrentLinkCallback)
 -> m (GClosure C_LabelActivateCurrentLinkCallback))
-> IO (GClosure C_LabelActivateCurrentLinkCallback)
-> m (GClosure C_LabelActivateCurrentLinkCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_LabelActivateCurrentLinkCallback
cb' = IO () -> C_LabelActivateCurrentLinkCallback
wrap_LabelCopyClipboardCallback IO ()
cb
    C_LabelActivateCurrentLinkCallback
-> IO (FunPtr C_LabelActivateCurrentLinkCallback)
mk_LabelCopyClipboardCallback C_LabelActivateCurrentLinkCallback
cb' IO (FunPtr C_LabelActivateCurrentLinkCallback)
-> (FunPtr C_LabelActivateCurrentLinkCallback
    -> IO (GClosure C_LabelActivateCurrentLinkCallback))
-> IO (GClosure C_LabelActivateCurrentLinkCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_LabelActivateCurrentLinkCallback
-> IO (GClosure C_LabelActivateCurrentLinkCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_LabelCopyClipboardCallback ::
    LabelCopyClipboardCallback ->
    C_LabelCopyClipboardCallback
wrap_LabelCopyClipboardCallback :: IO () -> C_LabelActivateCurrentLinkCallback
wrap_LabelCopyClipboardCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onLabelCopyClipboard :: (IsLabel a, MonadIO m) => a -> LabelCopyClipboardCallback -> m SignalHandlerId
onLabelCopyClipboard :: forall a (m :: * -> *).
(IsLabel a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onLabelCopyClipboard a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_LabelActivateCurrentLinkCallback
cb' = IO () -> C_LabelActivateCurrentLinkCallback
wrap_LabelCopyClipboardCallback IO ()
cb
    FunPtr C_LabelActivateCurrentLinkCallback
cb'' <- C_LabelActivateCurrentLinkCallback
-> IO (FunPtr C_LabelActivateCurrentLinkCallback)
mk_LabelCopyClipboardCallback C_LabelActivateCurrentLinkCallback
cb'
    a
-> Text
-> FunPtr C_LabelActivateCurrentLinkCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"copy-clipboard" FunPtr C_LabelActivateCurrentLinkCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterLabelCopyClipboard :: (IsLabel a, MonadIO m) => a -> LabelCopyClipboardCallback -> m SignalHandlerId
afterLabelCopyClipboard :: forall a (m :: * -> *).
(IsLabel a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterLabelCopyClipboard a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_LabelActivateCurrentLinkCallback
cb' = IO () -> C_LabelActivateCurrentLinkCallback
wrap_LabelCopyClipboardCallback IO ()
cb
    FunPtr C_LabelActivateCurrentLinkCallback
cb'' <- C_LabelActivateCurrentLinkCallback
-> IO (FunPtr C_LabelActivateCurrentLinkCallback)
mk_LabelCopyClipboardCallback C_LabelActivateCurrentLinkCallback
cb'
    a
-> Text
-> FunPtr C_LabelActivateCurrentLinkCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"copy-clipboard" FunPtr C_LabelActivateCurrentLinkCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data LabelCopyClipboardSignalInfo
instance SignalInfo LabelCopyClipboardSignalInfo where
    type HaskellCallbackType LabelCopyClipboardSignalInfo = LabelCopyClipboardCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_LabelCopyClipboardCallback cb
        cb'' <- mk_LabelCopyClipboardCallback cb'
        connectSignalFunPtr obj "copy-clipboard" cb'' connectMode detail
#endif
type LabelMoveCursorCallback =
    Gtk.Enums.MovementStep
    
    -> Int32
    
    -> Bool
    
    -> IO ()
noLabelMoveCursorCallback :: Maybe LabelMoveCursorCallback
noLabelMoveCursorCallback :: Maybe LabelMoveCursorCallback
noLabelMoveCursorCallback = Maybe LabelMoveCursorCallback
forall a. Maybe a
Nothing
type C_LabelMoveCursorCallback =
    Ptr () ->                               
    CUInt ->
    Int32 ->
    CInt ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_LabelMoveCursorCallback :: C_LabelMoveCursorCallback -> IO (FunPtr C_LabelMoveCursorCallback)
genClosure_LabelMoveCursor :: MonadIO m => LabelMoveCursorCallback -> m (GClosure C_LabelMoveCursorCallback)
genClosure_LabelMoveCursor :: forall (m :: * -> *).
MonadIO m =>
LabelMoveCursorCallback -> m (GClosure C_LabelMoveCursorCallback)
genClosure_LabelMoveCursor LabelMoveCursorCallback
cb = IO (GClosure C_LabelMoveCursorCallback)
-> m (GClosure C_LabelMoveCursorCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_LabelMoveCursorCallback)
 -> m (GClosure C_LabelMoveCursorCallback))
-> IO (GClosure C_LabelMoveCursorCallback)
-> m (GClosure C_LabelMoveCursorCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_LabelMoveCursorCallback
cb' = LabelMoveCursorCallback -> C_LabelMoveCursorCallback
wrap_LabelMoveCursorCallback LabelMoveCursorCallback
cb
    C_LabelMoveCursorCallback -> IO (FunPtr C_LabelMoveCursorCallback)
mk_LabelMoveCursorCallback C_LabelMoveCursorCallback
cb' IO (FunPtr C_LabelMoveCursorCallback)
-> (FunPtr C_LabelMoveCursorCallback
    -> IO (GClosure C_LabelMoveCursorCallback))
-> IO (GClosure C_LabelMoveCursorCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_LabelMoveCursorCallback
-> IO (GClosure C_LabelMoveCursorCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_LabelMoveCursorCallback ::
    LabelMoveCursorCallback ->
    C_LabelMoveCursorCallback
wrap_LabelMoveCursorCallback :: LabelMoveCursorCallback -> C_LabelMoveCursorCallback
wrap_LabelMoveCursorCallback LabelMoveCursorCallback
_cb Ptr ()
_ CUInt
step Int32
count CInt
extendSelection Ptr ()
_ = do
    let step' :: MovementStep
step' = (Int -> MovementStep
forall a. Enum a => Int -> a
toEnum (Int -> MovementStep) -> (CUInt -> Int) -> CUInt -> MovementStep
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
step
    let extendSelection' :: Bool
extendSelection' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
extendSelection
    LabelMoveCursorCallback
_cb  MovementStep
step' Int32
count Bool
extendSelection'
onLabelMoveCursor :: (IsLabel a, MonadIO m) => a -> LabelMoveCursorCallback -> m SignalHandlerId
onLabelMoveCursor :: forall a (m :: * -> *).
(IsLabel a, MonadIO m) =>
a -> LabelMoveCursorCallback -> m SignalHandlerId
onLabelMoveCursor a
obj LabelMoveCursorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_LabelMoveCursorCallback
cb' = LabelMoveCursorCallback -> C_LabelMoveCursorCallback
wrap_LabelMoveCursorCallback LabelMoveCursorCallback
cb
    FunPtr C_LabelMoveCursorCallback
cb'' <- C_LabelMoveCursorCallback -> IO (FunPtr C_LabelMoveCursorCallback)
mk_LabelMoveCursorCallback C_LabelMoveCursorCallback
cb'
    a
-> Text
-> FunPtr C_LabelMoveCursorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"move-cursor" FunPtr C_LabelMoveCursorCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterLabelMoveCursor :: (IsLabel a, MonadIO m) => a -> LabelMoveCursorCallback -> m SignalHandlerId
afterLabelMoveCursor :: forall a (m :: * -> *).
(IsLabel a, MonadIO m) =>
a -> LabelMoveCursorCallback -> m SignalHandlerId
afterLabelMoveCursor a
obj LabelMoveCursorCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_LabelMoveCursorCallback
cb' = LabelMoveCursorCallback -> C_LabelMoveCursorCallback
wrap_LabelMoveCursorCallback LabelMoveCursorCallback
cb
    FunPtr C_LabelMoveCursorCallback
cb'' <- C_LabelMoveCursorCallback -> IO (FunPtr C_LabelMoveCursorCallback)
mk_LabelMoveCursorCallback C_LabelMoveCursorCallback
cb'
    a
-> Text
-> FunPtr C_LabelMoveCursorCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"move-cursor" FunPtr C_LabelMoveCursorCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data LabelMoveCursorSignalInfo
instance SignalInfo LabelMoveCursorSignalInfo where
    type HaskellCallbackType LabelMoveCursorSignalInfo = LabelMoveCursorCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_LabelMoveCursorCallback cb
        cb'' <- mk_LabelMoveCursorCallback cb'
        connectSignalFunPtr obj "move-cursor" cb'' connectMode detail
#endif
   
   
   
getLabelAttributes :: (MonadIO m, IsLabel o) => o -> m (Maybe Pango.AttrList.AttrList)
getLabelAttributes :: forall (m :: * -> *) o.
(MonadIO m, IsLabel o) =>
o -> m (Maybe AttrList)
getLabelAttributes o
obj = IO (Maybe AttrList) -> m (Maybe AttrList)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe AttrList) -> m (Maybe AttrList))
-> IO (Maybe AttrList) -> m (Maybe AttrList)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr AttrList -> AttrList)
-> IO (Maybe AttrList)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"attributes" ManagedPtr AttrList -> AttrList
Pango.AttrList.AttrList
setLabelAttributes :: (MonadIO m, IsLabel o) => o -> Pango.AttrList.AttrList -> m ()
setLabelAttributes :: forall (m :: * -> *) o.
(MonadIO m, IsLabel o) =>
o -> AttrList -> m ()
setLabelAttributes o
obj AttrList
val = IO () -> m ()
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 AttrList -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"attributes" (AttrList -> Maybe AttrList
forall a. a -> Maybe a
Just AttrList
val)
constructLabelAttributes :: (IsLabel o, MIO.MonadIO m) => Pango.AttrList.AttrList -> m (GValueConstruct o)
constructLabelAttributes :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
AttrList -> m (GValueConstruct o)
constructLabelAttributes AttrList
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 AttrList -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"attributes" (AttrList -> Maybe AttrList
forall a. a -> Maybe a
P.Just AttrList
val)
clearLabelAttributes :: (MonadIO m, IsLabel o) => o -> m ()
clearLabelAttributes :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m ()
clearLabelAttributes o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe AttrList -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"attributes" (Maybe AttrList
forall a. Maybe a
Nothing :: Maybe Pango.AttrList.AttrList)
#if defined(ENABLE_OVERLOADING)
data LabelAttributesPropertyInfo
instance AttrInfo LabelAttributesPropertyInfo where
    type AttrAllowedOps LabelAttributesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint LabelAttributesPropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelAttributesPropertyInfo = (~) Pango.AttrList.AttrList
    type AttrTransferTypeConstraint LabelAttributesPropertyInfo = (~) Pango.AttrList.AttrList
    type AttrTransferType LabelAttributesPropertyInfo = Pango.AttrList.AttrList
    type AttrGetType LabelAttributesPropertyInfo = (Maybe Pango.AttrList.AttrList)
    type AttrLabel LabelAttributesPropertyInfo = "attributes"
    type AttrOrigin LabelAttributesPropertyInfo = Label
    attrGet = getLabelAttributes
    attrSet = setLabelAttributes
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelAttributes
    attrClear = clearLabelAttributes
#endif
   
   
   
getLabelEllipsize :: (MonadIO m, IsLabel o) => o -> m Pango.Enums.EllipsizeMode
getLabelEllipsize :: forall (m :: * -> *) o.
(MonadIO m, IsLabel o) =>
o -> m EllipsizeMode
getLabelEllipsize o
obj = IO EllipsizeMode -> m EllipsizeMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO EllipsizeMode -> m EllipsizeMode)
-> IO EllipsizeMode -> m EllipsizeMode
forall a b. (a -> b) -> a -> b
$ o -> String -> IO EllipsizeMode
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"ellipsize"
setLabelEllipsize :: (MonadIO m, IsLabel o) => o -> Pango.Enums.EllipsizeMode -> m ()
setLabelEllipsize :: forall (m :: * -> *) o.
(MonadIO m, IsLabel o) =>
o -> EllipsizeMode -> m ()
setLabelEllipsize o
obj EllipsizeMode
val = IO () -> m ()
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 -> EllipsizeMode -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"ellipsize" EllipsizeMode
val
constructLabelEllipsize :: (IsLabel o, MIO.MonadIO m) => Pango.Enums.EllipsizeMode -> m (GValueConstruct o)
constructLabelEllipsize :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
EllipsizeMode -> m (GValueConstruct o)
constructLabelEllipsize EllipsizeMode
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> EllipsizeMode -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"ellipsize" EllipsizeMode
val
#if defined(ENABLE_OVERLOADING)
data LabelEllipsizePropertyInfo
instance AttrInfo LabelEllipsizePropertyInfo where
    type AttrAllowedOps LabelEllipsizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint LabelEllipsizePropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelEllipsizePropertyInfo = (~) Pango.Enums.EllipsizeMode
    type AttrTransferTypeConstraint LabelEllipsizePropertyInfo = (~) Pango.Enums.EllipsizeMode
    type AttrTransferType LabelEllipsizePropertyInfo = Pango.Enums.EllipsizeMode
    type AttrGetType LabelEllipsizePropertyInfo = Pango.Enums.EllipsizeMode
    type AttrLabel LabelEllipsizePropertyInfo = "ellipsize"
    type AttrOrigin LabelEllipsizePropertyInfo = Label
    attrGet = getLabelEllipsize
    attrSet = setLabelEllipsize
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelEllipsize
    attrClear = undefined
#endif
   
   
   
getLabelExtraMenu :: (MonadIO m, IsLabel o) => o -> m (Maybe Gio.MenuModel.MenuModel)
 o
obj = IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe MenuModel) -> m (Maybe MenuModel))
-> IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr MenuModel -> MenuModel)
-> IO (Maybe MenuModel)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"extra-menu" ManagedPtr MenuModel -> MenuModel
Gio.MenuModel.MenuModel
setLabelExtraMenu :: (MonadIO m, IsLabel o, Gio.MenuModel.IsMenuModel a) => o -> a -> m ()
 o
obj a
val = IO () -> m ()
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 a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"extra-menu" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructLabelExtraMenu :: (IsLabel o, MIO.MonadIO m, Gio.MenuModel.IsMenuModel a) => a -> m (GValueConstruct o)
 a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"extra-menu" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearLabelExtraMenu :: (MonadIO m, IsLabel o) => o -> m ()
 o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe MenuModel -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"extra-menu" (Maybe MenuModel
forall a. Maybe a
Nothing :: Maybe Gio.MenuModel.MenuModel)
#if defined(ENABLE_OVERLOADING)
data LabelExtraMenuPropertyInfo
instance AttrInfo LabelExtraMenuPropertyInfo where
    type AttrAllowedOps LabelExtraMenuPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint LabelExtraMenuPropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelExtraMenuPropertyInfo = Gio.MenuModel.IsMenuModel
    type AttrTransferTypeConstraint LabelExtraMenuPropertyInfo = Gio.MenuModel.IsMenuModel
    type AttrTransferType LabelExtraMenuPropertyInfo = Gio.MenuModel.MenuModel
    type AttrGetType LabelExtraMenuPropertyInfo = (Maybe Gio.MenuModel.MenuModel)
    type AttrLabel LabelExtraMenuPropertyInfo = "extra-menu"
    type AttrOrigin LabelExtraMenuPropertyInfo = Label
    attrGet = getLabelExtraMenu
    attrSet = setLabelExtraMenu
    attrTransfer _ v = do
        unsafeCastTo Gio.MenuModel.MenuModel v
    attrConstruct = constructLabelExtraMenu
    attrClear = clearLabelExtraMenu
#endif
   
   
   
getLabelJustify :: (MonadIO m, IsLabel o) => o -> m Gtk.Enums.Justification
getLabelJustify :: forall (m :: * -> *) o.
(MonadIO m, IsLabel o) =>
o -> m Justification
getLabelJustify o
obj = IO Justification -> m Justification
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Justification -> m Justification)
-> IO Justification -> m Justification
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Justification
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"justify"
setLabelJustify :: (MonadIO m, IsLabel o) => o -> Gtk.Enums.Justification -> m ()
setLabelJustify :: forall (m :: * -> *) o.
(MonadIO m, IsLabel o) =>
o -> Justification -> m ()
setLabelJustify o
obj Justification
val = IO () -> m ()
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 -> Justification -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"justify" Justification
val
constructLabelJustify :: (IsLabel o, MIO.MonadIO m) => Gtk.Enums.Justification -> m (GValueConstruct o)
constructLabelJustify :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
Justification -> m (GValueConstruct o)
constructLabelJustify Justification
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Justification -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"justify" Justification
val
#if defined(ENABLE_OVERLOADING)
data LabelJustifyPropertyInfo
instance AttrInfo LabelJustifyPropertyInfo where
    type AttrAllowedOps LabelJustifyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint LabelJustifyPropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelJustifyPropertyInfo = (~) Gtk.Enums.Justification
    type AttrTransferTypeConstraint LabelJustifyPropertyInfo = (~) Gtk.Enums.Justification
    type AttrTransferType LabelJustifyPropertyInfo = Gtk.Enums.Justification
    type AttrGetType LabelJustifyPropertyInfo = Gtk.Enums.Justification
    type AttrLabel LabelJustifyPropertyInfo = "justify"
    type AttrOrigin LabelJustifyPropertyInfo = Label
    attrGet = getLabelJustify
    attrSet = setLabelJustify
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelJustify
    attrClear = undefined
#endif
   
   
   
getLabelLabel :: (MonadIO m, IsLabel o) => o -> m T.Text
getLabelLabel :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m Text
getLabelLabel o
obj = IO Text -> m Text
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
"getLabelLabel" (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
"label"
setLabelLabel :: (MonadIO m, IsLabel o) => o -> T.Text -> m ()
setLabelLabel :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> Text -> m ()
setLabelLabel o
obj Text
val = IO () -> m ()
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
"label" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructLabelLabel :: (IsLabel o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructLabelLabel :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructLabelLabel Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"label" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data LabelLabelPropertyInfo
instance AttrInfo LabelLabelPropertyInfo where
    type AttrAllowedOps LabelLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint LabelLabelPropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelLabelPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint LabelLabelPropertyInfo = (~) T.Text
    type AttrTransferType LabelLabelPropertyInfo = T.Text
    type AttrGetType LabelLabelPropertyInfo = T.Text
    type AttrLabel LabelLabelPropertyInfo = "label"
    type AttrOrigin LabelLabelPropertyInfo = Label
    attrGet = getLabelLabel
    attrSet = setLabelLabel
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelLabel
    attrClear = undefined
#endif
   
   
   
getLabelLines :: (MonadIO m, IsLabel o) => o -> m Int32
getLabelLines :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m Int32
getLabelLines o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"lines"
setLabelLines :: (MonadIO m, IsLabel o) => o -> Int32 -> m ()
setLabelLines :: forall (m :: * -> *) o.
(MonadIO m, IsLabel o) =>
o -> Int32 -> m ()
setLabelLines o
obj Int32
val = IO () -> m ()
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 -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"lines" Int32
val
constructLabelLines :: (IsLabel o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructLabelLines :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructLabelLines Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"lines" Int32
val
#if defined(ENABLE_OVERLOADING)
data LabelLinesPropertyInfo
instance AttrInfo LabelLinesPropertyInfo where
    type AttrAllowedOps LabelLinesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint LabelLinesPropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelLinesPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint LabelLinesPropertyInfo = (~) Int32
    type AttrTransferType LabelLinesPropertyInfo = Int32
    type AttrGetType LabelLinesPropertyInfo = Int32
    type AttrLabel LabelLinesPropertyInfo = "lines"
    type AttrOrigin LabelLinesPropertyInfo = Label
    attrGet = getLabelLines
    attrSet = setLabelLines
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelLines
    attrClear = undefined
#endif
   
   
   
getLabelMaxWidthChars :: (MonadIO m, IsLabel o) => o -> m Int32
getLabelMaxWidthChars :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m Int32
getLabelMaxWidthChars o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"max-width-chars"
setLabelMaxWidthChars :: (MonadIO m, IsLabel o) => o -> Int32 -> m ()
setLabelMaxWidthChars :: forall (m :: * -> *) o.
(MonadIO m, IsLabel o) =>
o -> Int32 -> m ()
setLabelMaxWidthChars o
obj Int32
val = IO () -> m ()
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 -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"max-width-chars" Int32
val
constructLabelMaxWidthChars :: (IsLabel o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructLabelMaxWidthChars :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructLabelMaxWidthChars Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"max-width-chars" Int32
val
#if defined(ENABLE_OVERLOADING)
data LabelMaxWidthCharsPropertyInfo
instance AttrInfo LabelMaxWidthCharsPropertyInfo where
    type AttrAllowedOps LabelMaxWidthCharsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint LabelMaxWidthCharsPropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelMaxWidthCharsPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint LabelMaxWidthCharsPropertyInfo = (~) Int32
    type AttrTransferType LabelMaxWidthCharsPropertyInfo = Int32
    type AttrGetType LabelMaxWidthCharsPropertyInfo = Int32
    type AttrLabel LabelMaxWidthCharsPropertyInfo = "max-width-chars"
    type AttrOrigin LabelMaxWidthCharsPropertyInfo = Label
    attrGet = getLabelMaxWidthChars
    attrSet = setLabelMaxWidthChars
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelMaxWidthChars
    attrClear = undefined
#endif
   
   
   
getLabelMnemonicKeyval :: (MonadIO m, IsLabel o) => o -> m Word32
getLabelMnemonicKeyval :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m Word32
getLabelMnemonicKeyval o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"mnemonic-keyval"
#if defined(ENABLE_OVERLOADING)
data LabelMnemonicKeyvalPropertyInfo
instance AttrInfo LabelMnemonicKeyvalPropertyInfo where
    type AttrAllowedOps LabelMnemonicKeyvalPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint LabelMnemonicKeyvalPropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelMnemonicKeyvalPropertyInfo = (~) ()
    type AttrTransferTypeConstraint LabelMnemonicKeyvalPropertyInfo = (~) ()
    type AttrTransferType LabelMnemonicKeyvalPropertyInfo = ()
    type AttrGetType LabelMnemonicKeyvalPropertyInfo = Word32
    type AttrLabel LabelMnemonicKeyvalPropertyInfo = "mnemonic-keyval"
    type AttrOrigin LabelMnemonicKeyvalPropertyInfo = Label
    attrGet = getLabelMnemonicKeyval
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif
   
   
   
getLabelMnemonicWidget :: (MonadIO m, IsLabel o) => o -> m (Maybe Gtk.Widget.Widget)
getLabelMnemonicWidget :: forall (m :: * -> *) o.
(MonadIO m, IsLabel o) =>
o -> m (Maybe Widget)
getLabelMnemonicWidget o
obj = IO (Maybe Widget) -> m (Maybe Widget)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Widget) -> m (Maybe Widget))
-> IO (Maybe Widget) -> m (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Widget -> Widget) -> IO (Maybe Widget)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"mnemonic-widget" ManagedPtr Widget -> Widget
Gtk.Widget.Widget
setLabelMnemonicWidget :: (MonadIO m, IsLabel o, Gtk.Widget.IsWidget a) => o -> a -> m ()
setLabelMnemonicWidget :: forall (m :: * -> *) o a.
(MonadIO m, IsLabel o, IsWidget a) =>
o -> a -> m ()
setLabelMnemonicWidget o
obj a
val = IO () -> m ()
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 a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"mnemonic-widget" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructLabelMnemonicWidget :: (IsLabel o, MIO.MonadIO m, Gtk.Widget.IsWidget a) => a -> m (GValueConstruct o)
constructLabelMnemonicWidget :: forall o (m :: * -> *) a.
(IsLabel o, MonadIO m, IsWidget a) =>
a -> m (GValueConstruct o)
constructLabelMnemonicWidget a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"mnemonic-widget" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearLabelMnemonicWidget :: (MonadIO m, IsLabel o) => o -> m ()
clearLabelMnemonicWidget :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m ()
clearLabelMnemonicWidget o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Widget -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"mnemonic-widget" (Maybe Widget
forall a. Maybe a
Nothing :: Maybe Gtk.Widget.Widget)
#if defined(ENABLE_OVERLOADING)
data LabelMnemonicWidgetPropertyInfo
instance AttrInfo LabelMnemonicWidgetPropertyInfo where
    type AttrAllowedOps LabelMnemonicWidgetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint LabelMnemonicWidgetPropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelMnemonicWidgetPropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferTypeConstraint LabelMnemonicWidgetPropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferType LabelMnemonicWidgetPropertyInfo = Gtk.Widget.Widget
    type AttrGetType LabelMnemonicWidgetPropertyInfo = (Maybe Gtk.Widget.Widget)
    type AttrLabel LabelMnemonicWidgetPropertyInfo = "mnemonic-widget"
    type AttrOrigin LabelMnemonicWidgetPropertyInfo = Label
    attrGet = getLabelMnemonicWidget
    attrSet = setLabelMnemonicWidget
    attrTransfer _ v = do
        unsafeCastTo Gtk.Widget.Widget v
    attrConstruct = constructLabelMnemonicWidget
    attrClear = clearLabelMnemonicWidget
#endif
   
   
   
getLabelSelectable :: (MonadIO m, IsLabel o) => o -> m Bool
getLabelSelectable :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m Bool
getLabelSelectable o
obj = IO Bool -> m Bool
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
"selectable"
setLabelSelectable :: (MonadIO m, IsLabel o) => o -> Bool -> m ()
setLabelSelectable :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> Bool -> m ()
setLabelSelectable o
obj Bool
val = IO () -> m ()
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
"selectable" Bool
val
constructLabelSelectable :: (IsLabel o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructLabelSelectable :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructLabelSelectable Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"selectable" Bool
val
#if defined(ENABLE_OVERLOADING)
data LabelSelectablePropertyInfo
instance AttrInfo LabelSelectablePropertyInfo where
    type AttrAllowedOps LabelSelectablePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint LabelSelectablePropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelSelectablePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint LabelSelectablePropertyInfo = (~) Bool
    type AttrTransferType LabelSelectablePropertyInfo = Bool
    type AttrGetType LabelSelectablePropertyInfo = Bool
    type AttrLabel LabelSelectablePropertyInfo = "selectable"
    type AttrOrigin LabelSelectablePropertyInfo = Label
    attrGet = getLabelSelectable
    attrSet = setLabelSelectable
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelSelectable
    attrClear = undefined
#endif
   
   
   
getLabelSingleLineMode :: (MonadIO m, IsLabel o) => o -> m Bool
getLabelSingleLineMode :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m Bool
getLabelSingleLineMode o
obj = IO Bool -> m Bool
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
"single-line-mode"
setLabelSingleLineMode :: (MonadIO m, IsLabel o) => o -> Bool -> m ()
setLabelSingleLineMode :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> Bool -> m ()
setLabelSingleLineMode o
obj Bool
val = IO () -> m ()
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
"single-line-mode" Bool
val
constructLabelSingleLineMode :: (IsLabel o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructLabelSingleLineMode :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructLabelSingleLineMode Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"single-line-mode" Bool
val
#if defined(ENABLE_OVERLOADING)
data LabelSingleLineModePropertyInfo
instance AttrInfo LabelSingleLineModePropertyInfo where
    type AttrAllowedOps LabelSingleLineModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint LabelSingleLineModePropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelSingleLineModePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint LabelSingleLineModePropertyInfo = (~) Bool
    type AttrTransferType LabelSingleLineModePropertyInfo = Bool
    type AttrGetType LabelSingleLineModePropertyInfo = Bool
    type AttrLabel LabelSingleLineModePropertyInfo = "single-line-mode"
    type AttrOrigin LabelSingleLineModePropertyInfo = Label
    attrGet = getLabelSingleLineMode
    attrSet = setLabelSingleLineMode
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelSingleLineMode
    attrClear = undefined
#endif
   
   
   
getLabelUseMarkup :: (MonadIO m, IsLabel o) => o -> m Bool
getLabelUseMarkup :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m Bool
getLabelUseMarkup o
obj = IO Bool -> m Bool
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
"use-markup"
setLabelUseMarkup :: (MonadIO m, IsLabel o) => o -> Bool -> m ()
setLabelUseMarkup :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> Bool -> m ()
setLabelUseMarkup o
obj Bool
val = IO () -> m ()
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
"use-markup" Bool
val
constructLabelUseMarkup :: (IsLabel o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructLabelUseMarkup :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructLabelUseMarkup Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"use-markup" Bool
val
#if defined(ENABLE_OVERLOADING)
data LabelUseMarkupPropertyInfo
instance AttrInfo LabelUseMarkupPropertyInfo where
    type AttrAllowedOps LabelUseMarkupPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint LabelUseMarkupPropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelUseMarkupPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint LabelUseMarkupPropertyInfo = (~) Bool
    type AttrTransferType LabelUseMarkupPropertyInfo = Bool
    type AttrGetType LabelUseMarkupPropertyInfo = Bool
    type AttrLabel LabelUseMarkupPropertyInfo = "use-markup"
    type AttrOrigin LabelUseMarkupPropertyInfo = Label
    attrGet = getLabelUseMarkup
    attrSet = setLabelUseMarkup
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelUseMarkup
    attrClear = undefined
#endif
   
   
   
getLabelUseUnderline :: (MonadIO m, IsLabel o) => o -> m Bool
getLabelUseUnderline :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m Bool
getLabelUseUnderline o
obj = IO Bool -> m Bool
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
"use-underline"
setLabelUseUnderline :: (MonadIO m, IsLabel o) => o -> Bool -> m ()
setLabelUseUnderline :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> Bool -> m ()
setLabelUseUnderline o
obj Bool
val = IO () -> m ()
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
"use-underline" Bool
val
constructLabelUseUnderline :: (IsLabel o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructLabelUseUnderline :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructLabelUseUnderline Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"use-underline" Bool
val
#if defined(ENABLE_OVERLOADING)
data LabelUseUnderlinePropertyInfo
instance AttrInfo LabelUseUnderlinePropertyInfo where
    type AttrAllowedOps LabelUseUnderlinePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint LabelUseUnderlinePropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelUseUnderlinePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint LabelUseUnderlinePropertyInfo = (~) Bool
    type AttrTransferType LabelUseUnderlinePropertyInfo = Bool
    type AttrGetType LabelUseUnderlinePropertyInfo = Bool
    type AttrLabel LabelUseUnderlinePropertyInfo = "use-underline"
    type AttrOrigin LabelUseUnderlinePropertyInfo = Label
    attrGet = getLabelUseUnderline
    attrSet = setLabelUseUnderline
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelUseUnderline
    attrClear = undefined
#endif
   
   
   
getLabelWidthChars :: (MonadIO m, IsLabel o) => o -> m Int32
getLabelWidthChars :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m Int32
getLabelWidthChars o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"width-chars"
setLabelWidthChars :: (MonadIO m, IsLabel o) => o -> Int32 -> m ()
setLabelWidthChars :: forall (m :: * -> *) o.
(MonadIO m, IsLabel o) =>
o -> Int32 -> m ()
setLabelWidthChars o
obj Int32
val = IO () -> m ()
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 -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"width-chars" Int32
val
constructLabelWidthChars :: (IsLabel o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructLabelWidthChars :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructLabelWidthChars Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"width-chars" Int32
val
#if defined(ENABLE_OVERLOADING)
data LabelWidthCharsPropertyInfo
instance AttrInfo LabelWidthCharsPropertyInfo where
    type AttrAllowedOps LabelWidthCharsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint LabelWidthCharsPropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelWidthCharsPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint LabelWidthCharsPropertyInfo = (~) Int32
    type AttrTransferType LabelWidthCharsPropertyInfo = Int32
    type AttrGetType LabelWidthCharsPropertyInfo = Int32
    type AttrLabel LabelWidthCharsPropertyInfo = "width-chars"
    type AttrOrigin LabelWidthCharsPropertyInfo = Label
    attrGet = getLabelWidthChars
    attrSet = setLabelWidthChars
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelWidthChars
    attrClear = undefined
#endif
   
   
   
getLabelWrap :: (MonadIO m, IsLabel o) => o -> m Bool
getLabelWrap :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m Bool
getLabelWrap o
obj = IO Bool -> m Bool
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
"wrap"
setLabelWrap :: (MonadIO m, IsLabel o) => o -> Bool -> m ()
setLabelWrap :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> Bool -> m ()
setLabelWrap o
obj Bool
val = IO () -> m ()
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
"wrap" Bool
val
constructLabelWrap :: (IsLabel o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructLabelWrap :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructLabelWrap Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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
"wrap" Bool
val
#if defined(ENABLE_OVERLOADING)
data LabelWrapPropertyInfo
instance AttrInfo LabelWrapPropertyInfo where
    type AttrAllowedOps LabelWrapPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint LabelWrapPropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelWrapPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint LabelWrapPropertyInfo = (~) Bool
    type AttrTransferType LabelWrapPropertyInfo = Bool
    type AttrGetType LabelWrapPropertyInfo = Bool
    type AttrLabel LabelWrapPropertyInfo = "wrap"
    type AttrOrigin LabelWrapPropertyInfo = Label
    attrGet = getLabelWrap
    attrSet = setLabelWrap
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelWrap
    attrClear = undefined
#endif
   
   
   
getLabelWrapMode :: (MonadIO m, IsLabel o) => o -> m Pango.Enums.WrapMode
getLabelWrapMode :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m WrapMode
getLabelWrapMode o
obj = IO WrapMode -> m WrapMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO WrapMode -> m WrapMode) -> IO WrapMode -> m WrapMode
forall a b. (a -> b) -> a -> b
$ o -> String -> IO WrapMode
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"wrap-mode"
setLabelWrapMode :: (MonadIO m, IsLabel o) => o -> Pango.Enums.WrapMode -> m ()
setLabelWrapMode :: forall (m :: * -> *) o.
(MonadIO m, IsLabel o) =>
o -> WrapMode -> m ()
setLabelWrapMode o
obj WrapMode
val = IO () -> m ()
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 -> WrapMode -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"wrap-mode" WrapMode
val
constructLabelWrapMode :: (IsLabel o, MIO.MonadIO m) => Pango.Enums.WrapMode -> m (GValueConstruct o)
constructLabelWrapMode :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
WrapMode -> m (GValueConstruct o)
constructLabelWrapMode WrapMode
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> WrapMode -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"wrap-mode" WrapMode
val
#if defined(ENABLE_OVERLOADING)
data LabelWrapModePropertyInfo
instance AttrInfo LabelWrapModePropertyInfo where
    type AttrAllowedOps LabelWrapModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint LabelWrapModePropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelWrapModePropertyInfo = (~) Pango.Enums.WrapMode
    type AttrTransferTypeConstraint LabelWrapModePropertyInfo = (~) Pango.Enums.WrapMode
    type AttrTransferType LabelWrapModePropertyInfo = Pango.Enums.WrapMode
    type AttrGetType LabelWrapModePropertyInfo = Pango.Enums.WrapMode
    type AttrLabel LabelWrapModePropertyInfo = "wrap-mode"
    type AttrOrigin LabelWrapModePropertyInfo = Label
    attrGet = getLabelWrapMode
    attrSet = setLabelWrapMode
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelWrapMode
    attrClear = undefined
#endif
   
   
   
getLabelXalign :: (MonadIO m, IsLabel o) => o -> m Float
getLabelXalign :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m Float
getLabelXalign o
obj = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Float
forall a. GObject a => a -> String -> IO Float
B.Properties.getObjectPropertyFloat o
obj String
"xalign"
setLabelXalign :: (MonadIO m, IsLabel o) => o -> Float -> m ()
setLabelXalign :: forall (m :: * -> *) o.
(MonadIO m, IsLabel o) =>
o -> Float -> m ()
setLabelXalign o
obj Float
val = IO () -> m ()
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 -> Float -> IO ()
forall a. GObject a => a -> String -> Float -> IO ()
B.Properties.setObjectPropertyFloat o
obj String
"xalign" Float
val
constructLabelXalign :: (IsLabel o, MIO.MonadIO m) => Float -> m (GValueConstruct o)
constructLabelXalign :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
Float -> m (GValueConstruct o)
constructLabelXalign Float
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Float -> IO (GValueConstruct o)
forall o. String -> Float -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFloat String
"xalign" Float
val
#if defined(ENABLE_OVERLOADING)
data LabelXalignPropertyInfo
instance AttrInfo LabelXalignPropertyInfo where
    type AttrAllowedOps LabelXalignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint LabelXalignPropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelXalignPropertyInfo = (~) Float
    type AttrTransferTypeConstraint LabelXalignPropertyInfo = (~) Float
    type AttrTransferType LabelXalignPropertyInfo = Float
    type AttrGetType LabelXalignPropertyInfo = Float
    type AttrLabel LabelXalignPropertyInfo = "xalign"
    type AttrOrigin LabelXalignPropertyInfo = Label
    attrGet = getLabelXalign
    attrSet = setLabelXalign
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelXalign
    attrClear = undefined
#endif
   
   
   
getLabelYalign :: (MonadIO m, IsLabel o) => o -> m Float
getLabelYalign :: forall (m :: * -> *) o. (MonadIO m, IsLabel o) => o -> m Float
getLabelYalign o
obj = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Float
forall a. GObject a => a -> String -> IO Float
B.Properties.getObjectPropertyFloat o
obj String
"yalign"
setLabelYalign :: (MonadIO m, IsLabel o) => o -> Float -> m ()
setLabelYalign :: forall (m :: * -> *) o.
(MonadIO m, IsLabel o) =>
o -> Float -> m ()
setLabelYalign o
obj Float
val = IO () -> m ()
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 -> Float -> IO ()
forall a. GObject a => a -> String -> Float -> IO ()
B.Properties.setObjectPropertyFloat o
obj String
"yalign" Float
val
constructLabelYalign :: (IsLabel o, MIO.MonadIO m) => Float -> m (GValueConstruct o)
constructLabelYalign :: forall o (m :: * -> *).
(IsLabel o, MonadIO m) =>
Float -> m (GValueConstruct o)
constructLabelYalign Float
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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 (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 -> Float -> IO (GValueConstruct o)
forall o. String -> Float -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFloat String
"yalign" Float
val
#if defined(ENABLE_OVERLOADING)
data LabelYalignPropertyInfo
instance AttrInfo LabelYalignPropertyInfo where
    type AttrAllowedOps LabelYalignPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint LabelYalignPropertyInfo = IsLabel
    type AttrSetTypeConstraint LabelYalignPropertyInfo = (~) Float
    type AttrTransferTypeConstraint LabelYalignPropertyInfo = (~) Float
    type AttrTransferType LabelYalignPropertyInfo = Float
    type AttrGetType LabelYalignPropertyInfo = Float
    type AttrLabel LabelYalignPropertyInfo = "yalign"
    type AttrOrigin LabelYalignPropertyInfo = Label
    attrGet = getLabelYalign
    attrSet = setLabelYalign
    attrTransfer _ v = do
        return v
    attrConstruct = constructLabelYalign
    attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Label
type instance O.AttributeList Label = LabelAttributeList
type LabelAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("attributes", LabelAttributesPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("ellipsize", LabelEllipsizePropertyInfo), '("extraMenu", LabelExtraMenuPropertyInfo), '("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), '("justify", LabelJustifyPropertyInfo), '("label", LabelLabelPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("lines", LabelLinesPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("maxWidthChars", LabelMaxWidthCharsPropertyInfo), '("mnemonicKeyval", LabelMnemonicKeyvalPropertyInfo), '("mnemonicWidget", LabelMnemonicWidgetPropertyInfo), '("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), '("selectable", LabelSelectablePropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("singleLineMode", LabelSingleLineModePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("useMarkup", LabelUseMarkupPropertyInfo), '("useUnderline", LabelUseUnderlinePropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthChars", LabelWidthCharsPropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo), '("wrap", LabelWrapPropertyInfo), '("wrapMode", LabelWrapModePropertyInfo), '("xalign", LabelXalignPropertyInfo), '("yalign", LabelYalignPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
labelAttributes :: AttrLabelProxy "attributes"
labelAttributes = AttrLabelProxy
labelEllipsize :: AttrLabelProxy "ellipsize"
labelEllipsize = AttrLabelProxy
labelExtraMenu :: AttrLabelProxy "extraMenu"
labelExtraMenu = AttrLabelProxy
labelJustify :: AttrLabelProxy "justify"
labelJustify = AttrLabelProxy
labelLabel :: AttrLabelProxy "label"
labelLabel = AttrLabelProxy
labelLines :: AttrLabelProxy "lines"
labelLines = AttrLabelProxy
labelMaxWidthChars :: AttrLabelProxy "maxWidthChars"
labelMaxWidthChars = AttrLabelProxy
labelMnemonicKeyval :: AttrLabelProxy "mnemonicKeyval"
labelMnemonicKeyval = AttrLabelProxy
labelMnemonicWidget :: AttrLabelProxy "mnemonicWidget"
labelMnemonicWidget = AttrLabelProxy
labelSelectable :: AttrLabelProxy "selectable"
labelSelectable = AttrLabelProxy
labelSingleLineMode :: AttrLabelProxy "singleLineMode"
labelSingleLineMode = AttrLabelProxy
labelUseMarkup :: AttrLabelProxy "useMarkup"
labelUseMarkup = AttrLabelProxy
labelUseUnderline :: AttrLabelProxy "useUnderline"
labelUseUnderline = AttrLabelProxy
labelWidthChars :: AttrLabelProxy "widthChars"
labelWidthChars = AttrLabelProxy
labelWrap :: AttrLabelProxy "wrap"
labelWrap = AttrLabelProxy
labelWrapMode :: AttrLabelProxy "wrapMode"
labelWrapMode = AttrLabelProxy
labelXalign :: AttrLabelProxy "xalign"
labelXalign = AttrLabelProxy
labelYalign :: AttrLabelProxy "yalign"
labelYalign = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Label = LabelSignalList
type LabelSignalList = ('[ '("activateCurrentLink", LabelActivateCurrentLinkSignalInfo), '("activateLink", LabelActivateLinkSignalInfo), '("copyClipboard", LabelCopyClipboardSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveCursor", LabelMoveCursorSignalInfo), '("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
foreign import ccall "gtk_label_new" gtk_label_new :: 
    CString ->                              
    IO (Ptr Label)
labelNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (T.Text)
    
    -> m Label
    
labelNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe Text -> m Label
labelNew Maybe Text
str = IO Label -> m Label
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Label -> m Label) -> IO Label -> m Label
forall a b. (a -> b) -> a -> b
$ do
    CString
maybeStr <- case Maybe Text
str of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jStr -> do
            CString
jStr' <- Text -> IO CString
textToCString Text
jStr
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jStr'
    Ptr Label
result <- CString -> IO (Ptr Label)
gtk_label_new CString
maybeStr
    Text -> Ptr Label -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"labelNew" Ptr Label
result
    Label
result' <- ((ManagedPtr Label -> Label) -> Ptr Label -> IO Label
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Label -> Label
Label) Ptr Label
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeStr
    Label -> IO Label
forall (m :: * -> *) a. Monad m => a -> m a
return Label
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_label_new_with_mnemonic" gtk_label_new_with_mnemonic :: 
    CString ->                              
    IO (Ptr Label)
labelNewWithMnemonic ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe (T.Text)
    
    
    -> m Label
    
labelNewWithMnemonic :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe Text -> m Label
labelNewWithMnemonic Maybe Text
str = IO Label -> m Label
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Label -> m Label) -> IO Label -> m Label
forall a b. (a -> b) -> a -> b
$ do
    CString
maybeStr <- case Maybe Text
str of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jStr -> do
            CString
jStr' <- Text -> IO CString
textToCString Text
jStr
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jStr'
    Ptr Label
result <- CString -> IO (Ptr Label)
gtk_label_new_with_mnemonic CString
maybeStr
    Text -> Ptr Label -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"labelNewWithMnemonic" Ptr Label
result
    Label
result' <- ((ManagedPtr Label -> Label) -> Ptr Label -> IO Label
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Label -> Label
Label) Ptr Label
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeStr
    Label -> IO Label
forall (m :: * -> *) a. Monad m => a -> m a
return Label
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_label_get_attributes" gtk_label_get_attributes :: 
    Ptr Label ->                            
    IO (Ptr Pango.AttrList.AttrList)
labelGetAttributes ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m (Maybe Pango.AttrList.AttrList)
    
    
labelGetAttributes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m (Maybe AttrList)
labelGetAttributes a
self = IO (Maybe AttrList) -> m (Maybe AttrList)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe AttrList) -> m (Maybe AttrList))
-> IO (Maybe AttrList) -> m (Maybe AttrList)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr AttrList
result <- Ptr Label -> IO (Ptr AttrList)
gtk_label_get_attributes Ptr Label
self'
    Maybe AttrList
maybeResult <- Ptr AttrList
-> (Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr AttrList
result ((Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList))
-> (Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList)
forall a b. (a -> b) -> a -> b
$ \Ptr AttrList
result' -> do
        AttrList
result'' <- ((ManagedPtr AttrList -> AttrList) -> Ptr AttrList -> IO AttrList
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr AttrList -> AttrList
Pango.AttrList.AttrList) Ptr AttrList
result'
        AttrList -> IO AttrList
forall (m :: * -> *) a. Monad m => a -> m a
return AttrList
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe AttrList -> IO (Maybe AttrList)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AttrList
maybeResult
#if defined(ENABLE_OVERLOADING)
data LabelGetAttributesMethodInfo
instance (signature ~ (m (Maybe Pango.AttrList.AttrList)), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetAttributesMethodInfo a signature where
    overloadedMethod = labelGetAttributes
instance O.OverloadedMethodInfo LabelGetAttributesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetAttributes",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetAttributes"
        }
#endif
foreign import ccall "gtk_label_get_current_uri" gtk_label_get_current_uri :: 
    Ptr Label ->                            
    IO CString
labelGetCurrentUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m (Maybe T.Text)
    
    
labelGetCurrentUri :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m (Maybe Text)
labelGetCurrentUri a
self = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr Label -> IO CString
gtk_label_get_current_uri Ptr Label
self'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data LabelGetCurrentUriMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetCurrentUriMethodInfo a signature where
    overloadedMethod = labelGetCurrentUri
instance O.OverloadedMethodInfo LabelGetCurrentUriMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetCurrentUri",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetCurrentUri"
        }
#endif
foreign import ccall "gtk_label_get_ellipsize" gtk_label_get_ellipsize :: 
    Ptr Label ->                            
    IO CUInt
labelGetEllipsize ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Pango.Enums.EllipsizeMode
    
labelGetEllipsize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m EllipsizeMode
labelGetEllipsize a
self = IO EllipsizeMode -> m EllipsizeMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EllipsizeMode -> m EllipsizeMode)
-> IO EllipsizeMode -> m EllipsizeMode
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CUInt
result <- Ptr Label -> IO CUInt
gtk_label_get_ellipsize Ptr Label
self'
    let result' :: EllipsizeMode
result' = (Int -> EllipsizeMode
forall a. Enum a => Int -> a
toEnum (Int -> EllipsizeMode) -> (CUInt -> Int) -> CUInt -> EllipsizeMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    EllipsizeMode -> IO EllipsizeMode
forall (m :: * -> *) a. Monad m => a -> m a
return EllipsizeMode
result'
#if defined(ENABLE_OVERLOADING)
data LabelGetEllipsizeMethodInfo
instance (signature ~ (m Pango.Enums.EllipsizeMode), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetEllipsizeMethodInfo a signature where
    overloadedMethod = labelGetEllipsize
instance O.OverloadedMethodInfo LabelGetEllipsizeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetEllipsize",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetEllipsize"
        }
#endif
foreign import ccall "gtk_label_get_extra_menu"  :: 
    Ptr Label ->                            
    IO (Ptr Gio.MenuModel.MenuModel)
labelGetExtraMenu ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m (Maybe Gio.MenuModel.MenuModel)
    
 a
self = IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe MenuModel) -> m (Maybe MenuModel))
-> IO (Maybe MenuModel) -> m (Maybe MenuModel)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr MenuModel
result <- Ptr Label -> IO (Ptr MenuModel)
gtk_label_get_extra_menu Ptr Label
self'
    Maybe MenuModel
maybeResult <- Ptr MenuModel
-> (Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr MenuModel
result ((Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel))
-> (Ptr MenuModel -> IO MenuModel) -> IO (Maybe MenuModel)
forall a b. (a -> b) -> a -> b
$ \Ptr MenuModel
result' -> do
        MenuModel
result'' <- ((ManagedPtr MenuModel -> MenuModel)
-> Ptr MenuModel -> IO MenuModel
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr MenuModel -> MenuModel
Gio.MenuModel.MenuModel) Ptr MenuModel
result'
        MenuModel -> IO MenuModel
forall (m :: * -> *) a. Monad m => a -> m a
return MenuModel
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe MenuModel -> IO (Maybe MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MenuModel
maybeResult
#if defined(ENABLE_OVERLOADING)
data LabelGetExtraMenuMethodInfo
instance (signature ~ (m (Maybe Gio.MenuModel.MenuModel)), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetExtraMenuMethodInfo a signature where
    overloadedMethod = labelGetExtraMenu
instance O.OverloadedMethodInfo LabelGetExtraMenuMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetExtraMenu",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetExtraMenu"
        }
#endif
foreign import ccall "gtk_label_get_justify" gtk_label_get_justify :: 
    Ptr Label ->                            
    IO CUInt
labelGetJustify ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Gtk.Enums.Justification
    
labelGetJustify :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Justification
labelGetJustify a
self = IO Justification -> m Justification
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Justification -> m Justification)
-> IO Justification -> m Justification
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CUInt
result <- Ptr Label -> IO CUInt
gtk_label_get_justify Ptr Label
self'
    let result' :: Justification
result' = (Int -> Justification
forall a. Enum a => Int -> a
toEnum (Int -> Justification) -> (CUInt -> Int) -> CUInt -> Justification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Justification -> IO Justification
forall (m :: * -> *) a. Monad m => a -> m a
return Justification
result'
#if defined(ENABLE_OVERLOADING)
data LabelGetJustifyMethodInfo
instance (signature ~ (m Gtk.Enums.Justification), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetJustifyMethodInfo a signature where
    overloadedMethod = labelGetJustify
instance O.OverloadedMethodInfo LabelGetJustifyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetJustify",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetJustify"
        }
#endif
foreign import ccall "gtk_label_get_label" gtk_label_get_label :: 
    Ptr Label ->                            
    IO CString
labelGetLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m T.Text
    
    
labelGetLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Text
labelGetLabel a
self = IO Text -> m Text
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 Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr Label -> IO CString
gtk_label_get_label Ptr Label
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"labelGetLabel" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data LabelGetLabelMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetLabelMethodInfo a signature where
    overloadedMethod = labelGetLabel
instance O.OverloadedMethodInfo LabelGetLabelMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetLabel",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetLabel"
        }
#endif
foreign import ccall "gtk_label_get_layout" gtk_label_get_layout :: 
    Ptr Label ->                            
    IO (Ptr Pango.Layout.Layout)
labelGetLayout ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Pango.Layout.Layout
    
labelGetLayout :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Layout
labelGetLayout a
self = IO Layout -> m Layout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Layout -> m Layout) -> IO Layout -> m Layout
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Layout
result <- Ptr Label -> IO (Ptr Layout)
gtk_label_get_layout Ptr Label
self'
    Text -> Ptr Layout -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"labelGetLayout" Ptr Layout
result
    Layout
result' <- ((ManagedPtr Layout -> Layout) -> Ptr Layout -> IO Layout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Layout -> Layout
Pango.Layout.Layout) Ptr Layout
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Layout -> IO Layout
forall (m :: * -> *) a. Monad m => a -> m a
return Layout
result'
#if defined(ENABLE_OVERLOADING)
data LabelGetLayoutMethodInfo
instance (signature ~ (m Pango.Layout.Layout), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetLayoutMethodInfo a signature where
    overloadedMethod = labelGetLayout
instance O.OverloadedMethodInfo LabelGetLayoutMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetLayout",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetLayout"
        }
#endif
foreign import ccall "gtk_label_get_layout_offsets" gtk_label_get_layout_offsets :: 
    Ptr Label ->                            
    Ptr Int32 ->                            
    Ptr Int32 ->                            
    IO ()
labelGetLayoutOffsets ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m ((Int32, Int32))
labelGetLayoutOffsets :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m (Int32, Int32)
labelGetLayoutOffsets a
self = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Int32
x <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
y <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Label -> Ptr Int32 -> Ptr Int32 -> IO ()
gtk_label_get_layout_offsets Ptr Label
self' Ptr Int32
x Ptr Int32
y
    Int32
x' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
x
    Int32
y' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
y
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
x
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
y
    (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
x', Int32
y')
#if defined(ENABLE_OVERLOADING)
data LabelGetLayoutOffsetsMethodInfo
instance (signature ~ (m ((Int32, Int32))), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetLayoutOffsetsMethodInfo a signature where
    overloadedMethod = labelGetLayoutOffsets
instance O.OverloadedMethodInfo LabelGetLayoutOffsetsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetLayoutOffsets",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetLayoutOffsets"
        }
#endif
foreign import ccall "gtk_label_get_lines" gtk_label_get_lines :: 
    Ptr Label ->                            
    IO Int32
labelGetLines ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Int32
    
labelGetLines :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Int32
labelGetLines a
self = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Int32
result <- Ptr Label -> IO Int32
gtk_label_get_lines Ptr Label
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data LabelGetLinesMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetLinesMethodInfo a signature where
    overloadedMethod = labelGetLines
instance O.OverloadedMethodInfo LabelGetLinesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetLines",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetLines"
        }
#endif
foreign import ccall "gtk_label_get_max_width_chars" gtk_label_get_max_width_chars :: 
    Ptr Label ->                            
    IO Int32
labelGetMaxWidthChars ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Int32
    
labelGetMaxWidthChars :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Int32
labelGetMaxWidthChars a
self = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Int32
result <- Ptr Label -> IO Int32
gtk_label_get_max_width_chars Ptr Label
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data LabelGetMaxWidthCharsMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetMaxWidthCharsMethodInfo a signature where
    overloadedMethod = labelGetMaxWidthChars
instance O.OverloadedMethodInfo LabelGetMaxWidthCharsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetMaxWidthChars",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetMaxWidthChars"
        }
#endif
foreign import ccall "gtk_label_get_mnemonic_keyval" gtk_label_get_mnemonic_keyval :: 
    Ptr Label ->                            
    IO Word32
labelGetMnemonicKeyval ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Word32
    
labelGetMnemonicKeyval :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Word32
labelGetMnemonicKeyval a
self = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Word32
result <- Ptr Label -> IO Word32
gtk_label_get_mnemonic_keyval Ptr Label
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data LabelGetMnemonicKeyvalMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetMnemonicKeyvalMethodInfo a signature where
    overloadedMethod = labelGetMnemonicKeyval
instance O.OverloadedMethodInfo LabelGetMnemonicKeyvalMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetMnemonicKeyval",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetMnemonicKeyval"
        }
#endif
foreign import ccall "gtk_label_get_mnemonic_widget" gtk_label_get_mnemonic_widget :: 
    Ptr Label ->                            
    IO (Ptr Gtk.Widget.Widget)
labelGetMnemonicWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m (Maybe Gtk.Widget.Widget)
    
    
labelGetMnemonicWidget :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m (Maybe Widget)
labelGetMnemonicWidget a
self = IO (Maybe Widget) -> m (Maybe Widget)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Widget) -> m (Maybe Widget))
-> IO (Maybe Widget) -> m (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
result <- Ptr Label -> IO (Ptr Widget)
gtk_label_get_mnemonic_widget Ptr Label
self'
    Maybe Widget
maybeResult <- Ptr Widget -> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Widget
result ((Ptr Widget -> IO Widget) -> IO (Maybe Widget))
-> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
result' -> do
        Widget
result'' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result'
        Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Widget -> IO (Maybe Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Widget
maybeResult
#if defined(ENABLE_OVERLOADING)
data LabelGetMnemonicWidgetMethodInfo
instance (signature ~ (m (Maybe Gtk.Widget.Widget)), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetMnemonicWidgetMethodInfo a signature where
    overloadedMethod = labelGetMnemonicWidget
instance O.OverloadedMethodInfo LabelGetMnemonicWidgetMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetMnemonicWidget",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetMnemonicWidget"
        }
#endif
foreign import ccall "gtk_label_get_selectable" gtk_label_get_selectable :: 
    Ptr Label ->                            
    IO CInt
labelGetSelectable ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Bool
    
labelGetSelectable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Bool
labelGetSelectable a
self = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr Label -> IO CInt
gtk_label_get_selectable Ptr Label
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data LabelGetSelectableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetSelectableMethodInfo a signature where
    overloadedMethod = labelGetSelectable
instance O.OverloadedMethodInfo LabelGetSelectableMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetSelectable",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetSelectable"
        }
#endif
foreign import ccall "gtk_label_get_selection_bounds" gtk_label_get_selection_bounds :: 
    Ptr Label ->                            
    Ptr Int32 ->                            
    Ptr Int32 ->                            
    IO CInt
labelGetSelectionBounds ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m ((Bool, Int32, Int32))
    
labelGetSelectionBounds :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m (Bool, Int32, Int32)
labelGetSelectionBounds a
self = IO (Bool, Int32, Int32) -> m (Bool, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Int32, Int32) -> m (Bool, Int32, Int32))
-> IO (Bool, Int32, Int32) -> m (Bool, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Int32
start <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
end <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CInt
result <- Ptr Label -> Ptr Int32 -> Ptr Int32 -> IO CInt
gtk_label_get_selection_bounds Ptr Label
self' Ptr Int32
start Ptr Int32
end
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Int32
start' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
start
    Int32
end' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
end
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
start
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
end
    (Bool, Int32, Int32) -> IO (Bool, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Int32
start', Int32
end')
#if defined(ENABLE_OVERLOADING)
data LabelGetSelectionBoundsMethodInfo
instance (signature ~ (m ((Bool, Int32, Int32))), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetSelectionBoundsMethodInfo a signature where
    overloadedMethod = labelGetSelectionBounds
instance O.OverloadedMethodInfo LabelGetSelectionBoundsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetSelectionBounds",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetSelectionBounds"
        }
#endif
foreign import ccall "gtk_label_get_single_line_mode" gtk_label_get_single_line_mode :: 
    Ptr Label ->                            
    IO CInt
labelGetSingleLineMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Bool
    
labelGetSingleLineMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Bool
labelGetSingleLineMode a
self = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr Label -> IO CInt
gtk_label_get_single_line_mode Ptr Label
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data LabelGetSingleLineModeMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetSingleLineModeMethodInfo a signature where
    overloadedMethod = labelGetSingleLineMode
instance O.OverloadedMethodInfo LabelGetSingleLineModeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetSingleLineMode",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetSingleLineMode"
        }
#endif
foreign import ccall "gtk_label_get_text" gtk_label_get_text :: 
    Ptr Label ->                            
    IO CString
labelGetText ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m T.Text
    
    
labelGetText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Text
labelGetText a
self = IO Text -> m Text
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 Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr Label -> IO CString
gtk_label_get_text Ptr Label
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"labelGetText" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data LabelGetTextMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetTextMethodInfo a signature where
    overloadedMethod = labelGetText
instance O.OverloadedMethodInfo LabelGetTextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetText",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetText"
        }
#endif
foreign import ccall "gtk_label_get_use_markup" gtk_label_get_use_markup :: 
    Ptr Label ->                            
    IO CInt
labelGetUseMarkup ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Bool
    
labelGetUseMarkup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Bool
labelGetUseMarkup a
self = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr Label -> IO CInt
gtk_label_get_use_markup Ptr Label
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data LabelGetUseMarkupMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetUseMarkupMethodInfo a signature where
    overloadedMethod = labelGetUseMarkup
instance O.OverloadedMethodInfo LabelGetUseMarkupMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetUseMarkup",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetUseMarkup"
        }
#endif
foreign import ccall "gtk_label_get_use_underline" gtk_label_get_use_underline :: 
    Ptr Label ->                            
    IO CInt
labelGetUseUnderline ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Bool
    
    
labelGetUseUnderline :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Bool
labelGetUseUnderline a
self = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr Label -> IO CInt
gtk_label_get_use_underline Ptr Label
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data LabelGetUseUnderlineMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetUseUnderlineMethodInfo a signature where
    overloadedMethod = labelGetUseUnderline
instance O.OverloadedMethodInfo LabelGetUseUnderlineMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetUseUnderline",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetUseUnderline"
        }
#endif
foreign import ccall "gtk_label_get_width_chars" gtk_label_get_width_chars :: 
    Ptr Label ->                            
    IO Int32
labelGetWidthChars ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Int32
    
labelGetWidthChars :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Int32
labelGetWidthChars a
self = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Int32
result <- Ptr Label -> IO Int32
gtk_label_get_width_chars Ptr Label
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data LabelGetWidthCharsMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetWidthCharsMethodInfo a signature where
    overloadedMethod = labelGetWidthChars
instance O.OverloadedMethodInfo LabelGetWidthCharsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetWidthChars",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetWidthChars"
        }
#endif
foreign import ccall "gtk_label_get_wrap" gtk_label_get_wrap :: 
    Ptr Label ->                            
    IO CInt
labelGetWrap ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Bool
    
labelGetWrap :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Bool
labelGetWrap a
self = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr Label -> IO CInt
gtk_label_get_wrap Ptr Label
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data LabelGetWrapMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetWrapMethodInfo a signature where
    overloadedMethod = labelGetWrap
instance O.OverloadedMethodInfo LabelGetWrapMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetWrap",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetWrap"
        }
#endif
foreign import ccall "gtk_label_get_wrap_mode" gtk_label_get_wrap_mode :: 
    Ptr Label ->                            
    IO CUInt
labelGetWrapMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Pango.Enums.WrapMode
    
labelGetWrapMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m WrapMode
labelGetWrapMode a
self = IO WrapMode -> m WrapMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WrapMode -> m WrapMode) -> IO WrapMode -> m WrapMode
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CUInt
result <- Ptr Label -> IO CUInt
gtk_label_get_wrap_mode Ptr Label
self'
    let result' :: WrapMode
result' = (Int -> WrapMode
forall a. Enum a => Int -> a
toEnum (Int -> WrapMode) -> (CUInt -> Int) -> CUInt -> WrapMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    WrapMode -> IO WrapMode
forall (m :: * -> *) a. Monad m => a -> m a
return WrapMode
result'
#if defined(ENABLE_OVERLOADING)
data LabelGetWrapModeMethodInfo
instance (signature ~ (m Pango.Enums.WrapMode), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetWrapModeMethodInfo a signature where
    overloadedMethod = labelGetWrapMode
instance O.OverloadedMethodInfo LabelGetWrapModeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetWrapMode",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetWrapMode"
        }
#endif
foreign import ccall "gtk_label_get_xalign" gtk_label_get_xalign :: 
    Ptr Label ->                            
    IO CFloat
labelGetXalign ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Float
    
labelGetXalign :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Float
labelGetXalign a
self = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CFloat
result <- Ptr Label -> IO CFloat
gtk_label_get_xalign Ptr Label
self'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'
#if defined(ENABLE_OVERLOADING)
data LabelGetXalignMethodInfo
instance (signature ~ (m Float), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetXalignMethodInfo a signature where
    overloadedMethod = labelGetXalign
instance O.OverloadedMethodInfo LabelGetXalignMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetXalign",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetXalign"
        }
#endif
foreign import ccall "gtk_label_get_yalign" gtk_label_get_yalign :: 
    Ptr Label ->                            
    IO CFloat
labelGetYalign ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> m Float
    
labelGetYalign :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> m Float
labelGetYalign a
self = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CFloat
result <- Ptr Label -> IO CFloat
gtk_label_get_yalign Ptr Label
self'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'
#if defined(ENABLE_OVERLOADING)
data LabelGetYalignMethodInfo
instance (signature ~ (m Float), MonadIO m, IsLabel a) => O.OverloadedMethod LabelGetYalignMethodInfo a signature where
    overloadedMethod = labelGetYalign
instance O.OverloadedMethodInfo LabelGetYalignMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelGetYalign",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelGetYalign"
        }
#endif
foreign import ccall "gtk_label_select_region" gtk_label_select_region :: 
    Ptr Label ->                            
    Int32 ->                                
    Int32 ->                                
    IO ()
labelSelectRegion ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Int32
    
    -> Int32
    
    -> m ()
labelSelectRegion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Int32 -> Int32 -> m ()
labelSelectRegion a
self Int32
startOffset Int32
endOffset = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Label -> Int32 -> Int32 -> IO ()
gtk_label_select_region Ptr Label
self' Int32
startOffset Int32
endOffset
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSelectRegionMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSelectRegionMethodInfo a signature where
    overloadedMethod = labelSelectRegion
instance O.OverloadedMethodInfo LabelSelectRegionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSelectRegion",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSelectRegion"
        }
#endif
foreign import ccall "gtk_label_set_attributes" gtk_label_set_attributes :: 
    Ptr Label ->                            
    Ptr Pango.AttrList.AttrList ->          
    IO ()
labelSetAttributes ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Maybe (Pango.AttrList.AttrList)
    
    -> m ()
labelSetAttributes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Maybe AttrList -> m ()
labelSetAttributes a
self Maybe AttrList
attrs = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr AttrList
maybeAttrs <- case Maybe AttrList
attrs of
        Maybe AttrList
Nothing -> Ptr AttrList -> IO (Ptr AttrList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AttrList
forall a. Ptr a
nullPtr
        Just AttrList
jAttrs -> do
            Ptr AttrList
jAttrs' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
jAttrs
            Ptr AttrList -> IO (Ptr AttrList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AttrList
jAttrs'
    Ptr Label -> Ptr AttrList -> IO ()
gtk_label_set_attributes Ptr Label
self' Ptr AttrList
maybeAttrs
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe AttrList -> (AttrList -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe AttrList
attrs AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetAttributesMethodInfo
instance (signature ~ (Maybe (Pango.AttrList.AttrList) -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetAttributesMethodInfo a signature where
    overloadedMethod = labelSetAttributes
instance O.OverloadedMethodInfo LabelSetAttributesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetAttributes",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetAttributes"
        }
#endif
foreign import ccall "gtk_label_set_ellipsize" gtk_label_set_ellipsize :: 
    Ptr Label ->                            
    CUInt ->                                
    IO ()
labelSetEllipsize ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Pango.Enums.EllipsizeMode
    
    -> m ()
labelSetEllipsize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> EllipsizeMode -> m ()
labelSetEllipsize a
self EllipsizeMode
mode = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let mode' :: CUInt
mode' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (EllipsizeMode -> Int) -> EllipsizeMode -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EllipsizeMode -> Int
forall a. Enum a => a -> Int
fromEnum) EllipsizeMode
mode
    Ptr Label -> CUInt -> IO ()
gtk_label_set_ellipsize Ptr Label
self' CUInt
mode'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetEllipsizeMethodInfo
instance (signature ~ (Pango.Enums.EllipsizeMode -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetEllipsizeMethodInfo a signature where
    overloadedMethod = labelSetEllipsize
instance O.OverloadedMethodInfo LabelSetEllipsizeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetEllipsize",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetEllipsize"
        }
#endif
foreign import ccall "gtk_label_set_extra_menu"  :: 
    Ptr Label ->                            
    Ptr Gio.MenuModel.MenuModel ->          
    IO ()
labelSetExtraMenu ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a, Gio.MenuModel.IsMenuModel b) =>
    a
    
    -> Maybe (b)
    
    -> m ()
 a
self Maybe b
model = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr MenuModel
maybeModel <- case Maybe b
model of
        Maybe b
Nothing -> Ptr MenuModel -> IO (Ptr MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
forall a. Ptr a
nullPtr
        Just b
jModel -> do
            Ptr MenuModel
jModel' <- b -> IO (Ptr MenuModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jModel
            Ptr MenuModel -> IO (Ptr MenuModel)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MenuModel
jModel'
    Ptr Label -> Ptr MenuModel -> IO ()
gtk_label_set_extra_menu Ptr Label
self' Ptr MenuModel
maybeModel
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
model b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetExtraMenuMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsLabel a, Gio.MenuModel.IsMenuModel b) => O.OverloadedMethod LabelSetExtraMenuMethodInfo a signature where
    overloadedMethod = labelSetExtraMenu
instance O.OverloadedMethodInfo LabelSetExtraMenuMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetExtraMenu",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetExtraMenu"
        }
#endif
foreign import ccall "gtk_label_set_justify" gtk_label_set_justify :: 
    Ptr Label ->                            
    CUInt ->                                
    IO ()
labelSetJustify ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Gtk.Enums.Justification
    
    -> m ()
labelSetJustify :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Justification -> m ()
labelSetJustify a
self Justification
jtype = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let jtype' :: CUInt
jtype' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Justification -> Int) -> Justification -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Justification -> Int
forall a. Enum a => a -> Int
fromEnum) Justification
jtype
    Ptr Label -> CUInt -> IO ()
gtk_label_set_justify Ptr Label
self' CUInt
jtype'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetJustifyMethodInfo
instance (signature ~ (Gtk.Enums.Justification -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetJustifyMethodInfo a signature where
    overloadedMethod = labelSetJustify
instance O.OverloadedMethodInfo LabelSetJustifyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetJustify",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetJustify"
        }
#endif
foreign import ccall "gtk_label_set_label" gtk_label_set_label :: 
    Ptr Label ->                            
    CString ->                              
    IO ()
labelSetLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> T.Text
    
    -> m ()
labelSetLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Text -> m ()
labelSetLabel a
self Text
str = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
str' <- Text -> IO CString
textToCString Text
str
    Ptr Label -> CString -> IO ()
gtk_label_set_label Ptr Label
self' CString
str'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetLabelMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetLabelMethodInfo a signature where
    overloadedMethod = labelSetLabel
instance O.OverloadedMethodInfo LabelSetLabelMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetLabel",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetLabel"
        }
#endif
foreign import ccall "gtk_label_set_lines" gtk_label_set_lines :: 
    Ptr Label ->                            
    Int32 ->                                
    IO ()
labelSetLines ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Int32
    
    -> m ()
labelSetLines :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Int32 -> m ()
labelSetLines a
self Int32
lines = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Label -> Int32 -> IO ()
gtk_label_set_lines Ptr Label
self' Int32
lines
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetLinesMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetLinesMethodInfo a signature where
    overloadedMethod = labelSetLines
instance O.OverloadedMethodInfo LabelSetLinesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetLines",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetLines"
        }
#endif
foreign import ccall "gtk_label_set_markup" gtk_label_set_markup :: 
    Ptr Label ->                            
    CString ->                              
    IO ()
labelSetMarkup ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> T.Text
    
    -> m ()
labelSetMarkup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Text -> m ()
labelSetMarkup a
self Text
str = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
str' <- Text -> IO CString
textToCString Text
str
    Ptr Label -> CString -> IO ()
gtk_label_set_markup Ptr Label
self' CString
str'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetMarkupMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetMarkupMethodInfo a signature where
    overloadedMethod = labelSetMarkup
instance O.OverloadedMethodInfo LabelSetMarkupMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetMarkup",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetMarkup"
        }
#endif
foreign import ccall "gtk_label_set_markup_with_mnemonic" gtk_label_set_markup_with_mnemonic :: 
    Ptr Label ->                            
    CString ->                              
    IO ()
labelSetMarkupWithMnemonic ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> T.Text
    
    
    -> m ()
labelSetMarkupWithMnemonic :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Text -> m ()
labelSetMarkupWithMnemonic a
self Text
str = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
str' <- Text -> IO CString
textToCString Text
str
    Ptr Label -> CString -> IO ()
gtk_label_set_markup_with_mnemonic Ptr Label
self' CString
str'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetMarkupWithMnemonicMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetMarkupWithMnemonicMethodInfo a signature where
    overloadedMethod = labelSetMarkupWithMnemonic
instance O.OverloadedMethodInfo LabelSetMarkupWithMnemonicMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetMarkupWithMnemonic",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetMarkupWithMnemonic"
        }
#endif
foreign import ccall "gtk_label_set_max_width_chars" gtk_label_set_max_width_chars :: 
    Ptr Label ->                            
    Int32 ->                                
    IO ()
labelSetMaxWidthChars ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Int32
    
    -> m ()
labelSetMaxWidthChars :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Int32 -> m ()
labelSetMaxWidthChars a
self Int32
nChars = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Label -> Int32 -> IO ()
gtk_label_set_max_width_chars Ptr Label
self' Int32
nChars
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetMaxWidthCharsMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetMaxWidthCharsMethodInfo a signature where
    overloadedMethod = labelSetMaxWidthChars
instance O.OverloadedMethodInfo LabelSetMaxWidthCharsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetMaxWidthChars",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetMaxWidthChars"
        }
#endif
foreign import ccall "gtk_label_set_mnemonic_widget" gtk_label_set_mnemonic_widget :: 
    Ptr Label ->                            
    Ptr Gtk.Widget.Widget ->                
    IO ()
labelSetMnemonicWidget ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a, Gtk.Widget.IsWidget b) =>
    a
    
    -> Maybe (b)
    
    -> m ()
labelSetMnemonicWidget :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsLabel a, IsWidget b) =>
a -> Maybe b -> m ()
labelSetMnemonicWidget a
self Maybe b
widget = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
maybeWidget <- case Maybe b
widget of
        Maybe b
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just b
jWidget -> do
            Ptr Widget
jWidget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jWidget
            Ptr Widget -> IO (Ptr Widget)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jWidget'
    Ptr Label -> Ptr Widget -> IO ()
gtk_label_set_mnemonic_widget Ptr Label
self' Ptr Widget
maybeWidget
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
widget b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetMnemonicWidgetMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsLabel a, Gtk.Widget.IsWidget b) => O.OverloadedMethod LabelSetMnemonicWidgetMethodInfo a signature where
    overloadedMethod = labelSetMnemonicWidget
instance O.OverloadedMethodInfo LabelSetMnemonicWidgetMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetMnemonicWidget",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetMnemonicWidget"
        }
#endif
foreign import ccall "gtk_label_set_selectable" gtk_label_set_selectable :: 
    Ptr Label ->                            
    CInt ->                                 
    IO ()
labelSetSelectable ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Bool
    
    -> m ()
labelSetSelectable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Bool -> m ()
labelSetSelectable a
self Bool
setting = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let setting' :: CInt
setting' = (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
setting
    Ptr Label -> CInt -> IO ()
gtk_label_set_selectable Ptr Label
self' CInt
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetSelectableMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetSelectableMethodInfo a signature where
    overloadedMethod = labelSetSelectable
instance O.OverloadedMethodInfo LabelSetSelectableMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetSelectable",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetSelectable"
        }
#endif
foreign import ccall "gtk_label_set_single_line_mode" gtk_label_set_single_line_mode :: 
    Ptr Label ->                            
    CInt ->                                 
    IO ()
labelSetSingleLineMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Bool
    
    -> m ()
labelSetSingleLineMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Bool -> m ()
labelSetSingleLineMode a
self Bool
singleLineMode = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let singleLineMode' :: CInt
singleLineMode' = (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
singleLineMode
    Ptr Label -> CInt -> IO ()
gtk_label_set_single_line_mode Ptr Label
self' CInt
singleLineMode'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetSingleLineModeMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetSingleLineModeMethodInfo a signature where
    overloadedMethod = labelSetSingleLineMode
instance O.OverloadedMethodInfo LabelSetSingleLineModeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetSingleLineMode",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetSingleLineMode"
        }
#endif
foreign import ccall "gtk_label_set_text" gtk_label_set_text :: 
    Ptr Label ->                            
    CString ->                              
    IO ()
labelSetText ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> T.Text
    
    -> m ()
labelSetText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Text -> m ()
labelSetText a
self Text
str = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
str' <- Text -> IO CString
textToCString Text
str
    Ptr Label -> CString -> IO ()
gtk_label_set_text Ptr Label
self' CString
str'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetTextMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetTextMethodInfo a signature where
    overloadedMethod = labelSetText
instance O.OverloadedMethodInfo LabelSetTextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetText",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetText"
        }
#endif
foreign import ccall "gtk_label_set_text_with_mnemonic" gtk_label_set_text_with_mnemonic :: 
    Ptr Label ->                            
    CString ->                              
    IO ()
labelSetTextWithMnemonic ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> T.Text
    
    -> m ()
labelSetTextWithMnemonic :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Text -> m ()
labelSetTextWithMnemonic a
self Text
str = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
str' <- Text -> IO CString
textToCString Text
str
    Ptr Label -> CString -> IO ()
gtk_label_set_text_with_mnemonic Ptr Label
self' CString
str'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetTextWithMnemonicMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetTextWithMnemonicMethodInfo a signature where
    overloadedMethod = labelSetTextWithMnemonic
instance O.OverloadedMethodInfo LabelSetTextWithMnemonicMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetTextWithMnemonic",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetTextWithMnemonic"
        }
#endif
foreign import ccall "gtk_label_set_use_markup" gtk_label_set_use_markup :: 
    Ptr Label ->                            
    CInt ->                                 
    IO ()
labelSetUseMarkup ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Bool
    
    -> m ()
labelSetUseMarkup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Bool -> m ()
labelSetUseMarkup a
self Bool
setting = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let setting' :: CInt
setting' = (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
setting
    Ptr Label -> CInt -> IO ()
gtk_label_set_use_markup Ptr Label
self' CInt
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetUseMarkupMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetUseMarkupMethodInfo a signature where
    overloadedMethod = labelSetUseMarkup
instance O.OverloadedMethodInfo LabelSetUseMarkupMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetUseMarkup",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetUseMarkup"
        }
#endif
foreign import ccall "gtk_label_set_use_underline" gtk_label_set_use_underline :: 
    Ptr Label ->                            
    CInt ->                                 
    IO ()
labelSetUseUnderline ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Bool
    
    -> m ()
labelSetUseUnderline :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Bool -> m ()
labelSetUseUnderline a
self Bool
setting = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let setting' :: CInt
setting' = (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
setting
    Ptr Label -> CInt -> IO ()
gtk_label_set_use_underline Ptr Label
self' CInt
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetUseUnderlineMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetUseUnderlineMethodInfo a signature where
    overloadedMethod = labelSetUseUnderline
instance O.OverloadedMethodInfo LabelSetUseUnderlineMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetUseUnderline",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetUseUnderline"
        }
#endif
foreign import ccall "gtk_label_set_width_chars" gtk_label_set_width_chars :: 
    Ptr Label ->                            
    Int32 ->                                
    IO ()
labelSetWidthChars ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Int32
    
    -> m ()
labelSetWidthChars :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Int32 -> m ()
labelSetWidthChars a
self Int32
nChars = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Label -> Int32 -> IO ()
gtk_label_set_width_chars Ptr Label
self' Int32
nChars
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetWidthCharsMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetWidthCharsMethodInfo a signature where
    overloadedMethod = labelSetWidthChars
instance O.OverloadedMethodInfo LabelSetWidthCharsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetWidthChars",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetWidthChars"
        }
#endif
foreign import ccall "gtk_label_set_wrap" gtk_label_set_wrap :: 
    Ptr Label ->                            
    CInt ->                                 
    IO ()
labelSetWrap ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Bool
    
    -> m ()
labelSetWrap :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Bool -> m ()
labelSetWrap a
self Bool
wrap = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let wrap' :: CInt
wrap' = (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
wrap
    Ptr Label -> CInt -> IO ()
gtk_label_set_wrap Ptr Label
self' CInt
wrap'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetWrapMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetWrapMethodInfo a signature where
    overloadedMethod = labelSetWrap
instance O.OverloadedMethodInfo LabelSetWrapMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetWrap",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetWrap"
        }
#endif
foreign import ccall "gtk_label_set_wrap_mode" gtk_label_set_wrap_mode :: 
    Ptr Label ->                            
    CUInt ->                                
    IO ()
labelSetWrapMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Pango.Enums.WrapMode
    
    -> m ()
labelSetWrapMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> WrapMode -> m ()
labelSetWrapMode a
self WrapMode
wrapMode = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let wrapMode' :: CUInt
wrapMode' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (WrapMode -> Int) -> WrapMode -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapMode -> Int
forall a. Enum a => a -> Int
fromEnum) WrapMode
wrapMode
    Ptr Label -> CUInt -> IO ()
gtk_label_set_wrap_mode Ptr Label
self' CUInt
wrapMode'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetWrapModeMethodInfo
instance (signature ~ (Pango.Enums.WrapMode -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetWrapModeMethodInfo a signature where
    overloadedMethod = labelSetWrapMode
instance O.OverloadedMethodInfo LabelSetWrapModeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetWrapMode",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetWrapMode"
        }
#endif
foreign import ccall "gtk_label_set_xalign" gtk_label_set_xalign :: 
    Ptr Label ->                            
    CFloat ->                               
    IO ()
labelSetXalign ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Float
    
    -> m ()
labelSetXalign :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Float -> m ()
labelSetXalign a
self Float
xalign = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let xalign' :: CFloat
xalign' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
xalign
    Ptr Label -> CFloat -> IO ()
gtk_label_set_xalign Ptr Label
self' CFloat
xalign'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetXalignMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetXalignMethodInfo a signature where
    overloadedMethod = labelSetXalign
instance O.OverloadedMethodInfo LabelSetXalignMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetXalign",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetXalign"
        }
#endif
foreign import ccall "gtk_label_set_yalign" gtk_label_set_yalign :: 
    Ptr Label ->                            
    CFloat ->                               
    IO ()
labelSetYalign ::
    (B.CallStack.HasCallStack, MonadIO m, IsLabel a) =>
    a
    
    -> Float
    
    -> m ()
labelSetYalign :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLabel a) =>
a -> Float -> m ()
labelSetYalign a
self Float
yalign = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Label
self' <- a -> IO (Ptr Label)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let yalign' :: CFloat
yalign' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
yalign
    Ptr Label -> CFloat -> IO ()
gtk_label_set_yalign Ptr Label
self' CFloat
yalign'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LabelSetYalignMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m, IsLabel a) => O.OverloadedMethod LabelSetYalignMethodInfo a signature where
    overloadedMethod = labelSetYalign
instance O.OverloadedMethodInfo LabelSetYalignMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.Label.labelSetYalign",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-Label.html#v:labelSetYalign"
        }
#endif