{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Using t'GI.Gtk.Structs.TextAttributes.TextAttributes' directly should rarely be necessary.
-- It’s primarily useful with 'GI.Gtk.Structs.TextIter.textIterGetAttributes'.
-- As with most GTK+ structs, the fields in this struct should only
-- be read, never modified directly.

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

module GI.Gtk.Structs.TextAttributes
    ( 

-- * Exported types
    TextAttributes(..)                      ,
    newZeroTextAttributes                   ,
    noTextAttributes                        ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveTextAttributesMethod             ,
#endif


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    TextAttributesCopyMethodInfo            ,
#endif
    textAttributesCopy                      ,


-- ** copyValues #method:copyValues#

#if defined(ENABLE_OVERLOADING)
    TextAttributesCopyValuesMethodInfo      ,
#endif
    textAttributesCopyValues                ,


-- ** new #method:new#

    textAttributesNew                       ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    TextAttributesRefMethodInfo             ,
#endif
    textAttributesRef                       ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    TextAttributesUnrefMethodInfo           ,
#endif
    textAttributesUnref                     ,




 -- * Properties
-- ** appearance #attr:appearance#
-- | t'GI.Gtk.Structs.TextAppearance.TextAppearance' for text.

    getTextAttributesAppearance             ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_appearance               ,
#endif


-- ** bgFullHeight #attr:bgFullHeight#
-- | Background is fit to full line height rather than
--    baseline +\/- ascent\/descent (font height).

    getTextAttributesBgFullHeight           ,
    setTextAttributesBgFullHeight           ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_bgFullHeight             ,
#endif


-- ** direction #attr:direction#
-- | t'GI.Gtk.Enums.TextDirection' for text.

    getTextAttributesDirection              ,
    setTextAttributesDirection              ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_direction                ,
#endif


-- ** editable #attr:editable#
-- | Can edit this text.

    getTextAttributesEditable               ,
    setTextAttributesEditable               ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_editable                 ,
#endif


-- ** font #attr:font#
-- | t'GI.Pango.Structs.FontDescription.FontDescription' for text.

    clearTextAttributesFont                 ,
    getTextAttributesFont                   ,
    setTextAttributesFont                   ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_font                     ,
#endif


-- ** fontScale #attr:fontScale#
-- | Font scale factor.

    getTextAttributesFontScale              ,
    setTextAttributesFontScale              ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_fontScale                ,
#endif


-- ** indent #attr:indent#
-- | Amount to indent the paragraph, in pixels.

    getTextAttributesIndent                 ,
    setTextAttributesIndent                 ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_indent                   ,
#endif


-- ** invisible #attr:invisible#
-- | Hide the text.

    getTextAttributesInvisible              ,
    setTextAttributesInvisible              ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_invisible                ,
#endif


-- ** justification #attr:justification#
-- | t'GI.Gtk.Enums.Justification' for text.

    getTextAttributesJustification          ,
    setTextAttributesJustification          ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_justification            ,
#endif


-- ** language #attr:language#
-- | t'GI.Pango.Structs.Language.Language' for text.

    clearTextAttributesLanguage             ,
    getTextAttributesLanguage               ,
    setTextAttributesLanguage               ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_language                 ,
#endif


-- ** leftMargin #attr:leftMargin#
-- | Width of the left margin in pixels.

    getTextAttributesLeftMargin             ,
    setTextAttributesLeftMargin             ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_leftMargin               ,
#endif


-- ** letterSpacing #attr:letterSpacing#
-- | Extra space to insert between graphemes, in Pango units

    getTextAttributesLetterSpacing          ,
    setTextAttributesLetterSpacing          ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_letterSpacing            ,
#endif


-- ** noFallback #attr:noFallback#
-- | Whether to disable font fallback.

    getTextAttributesNoFallback             ,
    setTextAttributesNoFallback             ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_noFallback               ,
#endif


-- ** pixelsAboveLines #attr:pixelsAboveLines#
-- | Pixels of blank space above paragraphs.

    getTextAttributesPixelsAboveLines       ,
    setTextAttributesPixelsAboveLines       ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_pixelsAboveLines         ,
#endif


-- ** pixelsBelowLines #attr:pixelsBelowLines#
-- | Pixels of blank space below paragraphs.

    getTextAttributesPixelsBelowLines       ,
    setTextAttributesPixelsBelowLines       ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_pixelsBelowLines         ,
#endif


-- ** pixelsInsideWrap #attr:pixelsInsideWrap#
-- | Pixels of blank space between wrapped lines in
--   a paragraph.

    getTextAttributesPixelsInsideWrap       ,
    setTextAttributesPixelsInsideWrap       ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_pixelsInsideWrap         ,
#endif


-- ** rightMargin #attr:rightMargin#
-- | Width of the right margin in pixels.

    getTextAttributesRightMargin            ,
    setTextAttributesRightMargin            ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_rightMargin              ,
#endif


-- ** tabs #attr:tabs#
-- | Custom t'GI.Pango.Structs.TabArray.TabArray' for this text.

    clearTextAttributesTabs                 ,
    getTextAttributesTabs                   ,
    setTextAttributesTabs                   ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_tabs                     ,
#endif


-- ** wrapMode #attr:wrapMode#
-- | t'GI.Gtk.Enums.WrapMode' for text.

    getTextAttributesWrapMode               ,
    setTextAttributesWrapMode               ,
#if defined(ENABLE_OVERLOADING)
    textAttributes_wrapMode                 ,
#endif




    ) where

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

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

import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Structs.TextAppearance as Gtk.TextAppearance
import qualified GI.Pango.Structs.FontDescription as Pango.FontDescription
import qualified GI.Pango.Structs.Language as Pango.Language
import qualified GI.Pango.Structs.TabArray as Pango.TabArray

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

instance BoxedObject TextAttributes where
    boxedType :: TextAttributes -> IO GType
boxedType _ = IO GType
c_gtk_text_attributes_get_type

-- | Convert 'TextAttributes' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue TextAttributes where
    toGValue :: TextAttributes -> IO GValue
toGValue o :: TextAttributes
o = do
        GType
gtype <- IO GType
c_gtk_text_attributes_get_type
        TextAttributes -> (Ptr TextAttributes -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TextAttributes
o (GType
-> (GValue -> Ptr TextAttributes -> IO ())
-> Ptr TextAttributes
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr TextAttributes -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO TextAttributes
fromGValue gv :: GValue
gv = do
        Ptr TextAttributes
ptr <- GValue -> IO (Ptr TextAttributes)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr TextAttributes)
        (ManagedPtr TextAttributes -> TextAttributes)
-> Ptr TextAttributes -> IO TextAttributes
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr TextAttributes -> TextAttributes
TextAttributes Ptr TextAttributes
ptr
        
    

-- | Construct a `TextAttributes` struct initialized to zero.
newZeroTextAttributes :: MonadIO m => m TextAttributes
newZeroTextAttributes :: m TextAttributes
newZeroTextAttributes = IO TextAttributes -> m TextAttributes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextAttributes -> m TextAttributes)
-> IO TextAttributes -> m TextAttributes
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr TextAttributes)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 168 IO (Ptr TextAttributes)
-> (Ptr TextAttributes -> IO TextAttributes) -> IO TextAttributes
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr TextAttributes -> TextAttributes)
-> Ptr TextAttributes -> IO TextAttributes
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextAttributes -> TextAttributes
TextAttributes

instance tag ~ 'AttrSet => Constructible TextAttributes tag where
    new :: (ManagedPtr TextAttributes -> TextAttributes)
-> [AttrOp TextAttributes tag] -> m TextAttributes
new _ attrs :: [AttrOp TextAttributes tag]
attrs = do
        TextAttributes
o <- m TextAttributes
forall (m :: * -> *). MonadIO m => m TextAttributes
newZeroTextAttributes
        TextAttributes -> [AttrOp TextAttributes 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set TextAttributes
o [AttrOp TextAttributes tag]
[AttrOp TextAttributes 'AttrSet]
attrs
        TextAttributes -> m TextAttributes
forall (m :: * -> *) a. Monad m => a -> m a
return TextAttributes
o


-- | A convenience alias for `Nothing` :: `Maybe` `TextAttributes`.
noTextAttributes :: Maybe TextAttributes
noTextAttributes :: Maybe TextAttributes
noTextAttributes = Maybe TextAttributes
forall a. Maybe a
Nothing

-- | Get the value of the “@appearance@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #appearance
-- @
getTextAttributesAppearance :: MonadIO m => TextAttributes -> m Gtk.TextAppearance.TextAppearance
getTextAttributesAppearance :: TextAttributes -> m TextAppearance
getTextAttributesAppearance s :: TextAttributes
s = IO TextAppearance -> m TextAppearance
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextAppearance -> m TextAppearance)
-> IO TextAppearance -> m TextAppearance
forall a b. (a -> b) -> a -> b
$ TextAttributes
-> (Ptr TextAttributes -> IO TextAppearance) -> IO TextAppearance
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO TextAppearance) -> IO TextAppearance)
-> (Ptr TextAttributes -> IO TextAppearance) -> IO TextAppearance
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    let val :: Ptr TextAppearance
val = Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr TextAppearance
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: (Ptr Gtk.TextAppearance.TextAppearance)
    TextAppearance
val' <- ((ManagedPtr TextAppearance -> TextAppearance)
-> Ptr TextAppearance -> IO TextAppearance
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TextAppearance -> TextAppearance
Gtk.TextAppearance.TextAppearance) Ptr TextAppearance
val
    TextAppearance -> IO TextAppearance
forall (m :: * -> *) a. Monad m => a -> m a
return TextAppearance
val'

#if defined(ENABLE_OVERLOADING)
data TextAttributesAppearanceFieldInfo
instance AttrInfo TextAttributesAppearanceFieldInfo where
    type AttrBaseTypeConstraint TextAttributesAppearanceFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesAppearanceFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint TextAttributesAppearanceFieldInfo = (~) (Ptr Gtk.TextAppearance.TextAppearance)
    type AttrTransferTypeConstraint TextAttributesAppearanceFieldInfo = (~)(Ptr Gtk.TextAppearance.TextAppearance)
    type AttrTransferType TextAttributesAppearanceFieldInfo = (Ptr Gtk.TextAppearance.TextAppearance)
    type AttrGetType TextAttributesAppearanceFieldInfo = Gtk.TextAppearance.TextAppearance
    type AttrLabel TextAttributesAppearanceFieldInfo = "appearance"
    type AttrOrigin TextAttributesAppearanceFieldInfo = TextAttributes
    attrGet = getTextAttributesAppearance
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined

textAttributes_appearance :: AttrLabelProxy "appearance"
textAttributes_appearance = AttrLabelProxy

#endif


-- | Get the value of the “@justification@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #justification
-- @
getTextAttributesJustification :: MonadIO m => TextAttributes -> m Gtk.Enums.Justification
getTextAttributesJustification :: TextAttributes -> m Justification
getTextAttributesJustification s :: TextAttributes
s = 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
$ TextAttributes
-> (Ptr TextAttributes -> IO Justification) -> IO Justification
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO Justification) -> IO Justification)
-> (Ptr TextAttributes -> IO Justification) -> IO Justification
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52) :: IO CUInt
    let val' :: Justification
val' = (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
val
    Justification -> IO Justification
forall (m :: * -> *) a. Monad m => a -> m a
return Justification
val'

-- | Set the value of the “@justification@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #justification 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesJustification :: MonadIO m => TextAttributes -> Gtk.Enums.Justification -> m ()
setTextAttributesJustification :: TextAttributes -> Justification -> m ()
setTextAttributesJustification s :: TextAttributes
s val :: Justification
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    let val' :: CUInt
val' = (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
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52) (CUInt
val' :: CUInt)

#if defined(ENABLE_OVERLOADING)
data TextAttributesJustificationFieldInfo
instance AttrInfo TextAttributesJustificationFieldInfo where
    type AttrBaseTypeConstraint TextAttributesJustificationFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesJustificationFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesJustificationFieldInfo = (~) Gtk.Enums.Justification
    type AttrTransferTypeConstraint TextAttributesJustificationFieldInfo = (~)Gtk.Enums.Justification
    type AttrTransferType TextAttributesJustificationFieldInfo = Gtk.Enums.Justification
    type AttrGetType TextAttributesJustificationFieldInfo = Gtk.Enums.Justification
    type AttrLabel TextAttributesJustificationFieldInfo = "justification"
    type AttrOrigin TextAttributesJustificationFieldInfo = TextAttributes
    attrGet = getTextAttributesJustification
    attrSet = setTextAttributesJustification
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_justification :: AttrLabelProxy "justification"
textAttributes_justification = AttrLabelProxy

#endif


-- | Get the value of the “@direction@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #direction
-- @
getTextAttributesDirection :: MonadIO m => TextAttributes -> m Gtk.Enums.TextDirection
getTextAttributesDirection :: TextAttributes -> m TextDirection
getTextAttributesDirection s :: TextAttributes
s = IO TextDirection -> m TextDirection
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextDirection -> m TextDirection)
-> IO TextDirection -> m TextDirection
forall a b. (a -> b) -> a -> b
$ TextAttributes
-> (Ptr TextAttributes -> IO TextDirection) -> IO TextDirection
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO TextDirection) -> IO TextDirection)
-> (Ptr TextAttributes -> IO TextDirection) -> IO TextDirection
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56) :: IO CUInt
    let val' :: TextDirection
val' = (Int -> TextDirection
forall a. Enum a => Int -> a
toEnum (Int -> TextDirection) -> (CUInt -> Int) -> CUInt -> TextDirection
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
    TextDirection -> IO TextDirection
forall (m :: * -> *) a. Monad m => a -> m a
return TextDirection
val'

-- | Set the value of the “@direction@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #direction 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesDirection :: MonadIO m => TextAttributes -> Gtk.Enums.TextDirection -> m ()
setTextAttributesDirection :: TextAttributes -> TextDirection -> m ()
setTextAttributesDirection s :: TextAttributes
s val :: TextDirection
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (TextDirection -> Int) -> TextDirection -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextDirection -> Int
forall a. Enum a => a -> Int
fromEnum) TextDirection
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56) (CUInt
val' :: CUInt)

#if defined(ENABLE_OVERLOADING)
data TextAttributesDirectionFieldInfo
instance AttrInfo TextAttributesDirectionFieldInfo where
    type AttrBaseTypeConstraint TextAttributesDirectionFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesDirectionFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesDirectionFieldInfo = (~) Gtk.Enums.TextDirection
    type AttrTransferTypeConstraint TextAttributesDirectionFieldInfo = (~)Gtk.Enums.TextDirection
    type AttrTransferType TextAttributesDirectionFieldInfo = Gtk.Enums.TextDirection
    type AttrGetType TextAttributesDirectionFieldInfo = Gtk.Enums.TextDirection
    type AttrLabel TextAttributesDirectionFieldInfo = "direction"
    type AttrOrigin TextAttributesDirectionFieldInfo = TextAttributes
    attrGet = getTextAttributesDirection
    attrSet = setTextAttributesDirection
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_direction :: AttrLabelProxy "direction"
textAttributes_direction = AttrLabelProxy

#endif


-- | Get the value of the “@font@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #font
-- @
getTextAttributesFont :: MonadIO m => TextAttributes -> m (Maybe Pango.FontDescription.FontDescription)
getTextAttributesFont :: TextAttributes -> m (Maybe FontDescription)
getTextAttributesFont s :: TextAttributes
s = IO (Maybe FontDescription) -> m (Maybe FontDescription)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FontDescription) -> m (Maybe FontDescription))
-> IO (Maybe FontDescription) -> m (Maybe FontDescription)
forall a b. (a -> b) -> a -> b
$ TextAttributes
-> (Ptr TextAttributes -> IO (Maybe FontDescription))
-> IO (Maybe FontDescription)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO (Maybe FontDescription))
 -> IO (Maybe FontDescription))
-> (Ptr TextAttributes -> IO (Maybe FontDescription))
-> IO (Maybe FontDescription)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr FontDescription
val <- Ptr (Ptr FontDescription) -> IO (Ptr FontDescription)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr (Ptr FontDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64) :: IO (Ptr Pango.FontDescription.FontDescription)
    Maybe FontDescription
result <- Ptr FontDescription
-> (Ptr FontDescription -> IO FontDescription)
-> IO (Maybe FontDescription)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr FontDescription
val ((Ptr FontDescription -> IO FontDescription)
 -> IO (Maybe FontDescription))
-> (Ptr FontDescription -> IO FontDescription)
-> IO (Maybe FontDescription)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr FontDescription
val' -> do
        FontDescription
val'' <- ((ManagedPtr FontDescription -> FontDescription)
-> Ptr FontDescription -> IO FontDescription
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr FontDescription -> FontDescription
Pango.FontDescription.FontDescription) Ptr FontDescription
val'
        FontDescription -> IO FontDescription
forall (m :: * -> *) a. Monad m => a -> m a
return FontDescription
val''
    Maybe FontDescription -> IO (Maybe FontDescription)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FontDescription
result

-- | Set the value of the “@font@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #font 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesFont :: MonadIO m => TextAttributes -> Ptr Pango.FontDescription.FontDescription -> m ()
setTextAttributesFont :: TextAttributes -> Ptr FontDescription -> m ()
setTextAttributesFont s :: TextAttributes
s val :: Ptr FontDescription
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr (Ptr FontDescription) -> Ptr FontDescription -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr (Ptr FontDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64) (Ptr FontDescription
val :: Ptr Pango.FontDescription.FontDescription)

-- | Set the value of the “@font@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #font
-- @
clearTextAttributesFont :: MonadIO m => TextAttributes -> m ()
clearTextAttributesFont :: TextAttributes -> m ()
clearTextAttributesFont s :: TextAttributes
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr (Ptr FontDescription) -> Ptr FontDescription -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr (Ptr FontDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64) (Ptr FontDescription
forall a. Ptr a
FP.nullPtr :: Ptr Pango.FontDescription.FontDescription)

#if defined(ENABLE_OVERLOADING)
data TextAttributesFontFieldInfo
instance AttrInfo TextAttributesFontFieldInfo where
    type AttrBaseTypeConstraint TextAttributesFontFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesFontFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TextAttributesFontFieldInfo = (~) (Ptr Pango.FontDescription.FontDescription)
    type AttrTransferTypeConstraint TextAttributesFontFieldInfo = (~)(Ptr Pango.FontDescription.FontDescription)
    type AttrTransferType TextAttributesFontFieldInfo = (Ptr Pango.FontDescription.FontDescription)
    type AttrGetType TextAttributesFontFieldInfo = Maybe Pango.FontDescription.FontDescription
    type AttrLabel TextAttributesFontFieldInfo = "font"
    type AttrOrigin TextAttributesFontFieldInfo = TextAttributes
    attrGet = getTextAttributesFont
    attrSet = setTextAttributesFont
    attrConstruct = undefined
    attrClear = clearTextAttributesFont
    attrTransfer _ v = do
        return v

textAttributes_font :: AttrLabelProxy "font"
textAttributes_font = AttrLabelProxy

#endif


-- | Get the value of the “@font_scale@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #fontScale
-- @
getTextAttributesFontScale :: MonadIO m => TextAttributes -> m Double
getTextAttributesFontScale :: TextAttributes -> m Double
getTextAttributesFontScale s :: TextAttributes
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO Double) -> IO Double)
-> (Ptr TextAttributes -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@font_scale@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #fontScale 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesFontScale :: MonadIO m => TextAttributes -> Double -> m ()
setTextAttributesFontScale :: TextAttributes -> Double -> m ()
setTextAttributesFontScale s :: TextAttributes
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data TextAttributesFontScaleFieldInfo
instance AttrInfo TextAttributesFontScaleFieldInfo where
    type AttrBaseTypeConstraint TextAttributesFontScaleFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesFontScaleFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesFontScaleFieldInfo = (~) Double
    type AttrTransferTypeConstraint TextAttributesFontScaleFieldInfo = (~)Double
    type AttrTransferType TextAttributesFontScaleFieldInfo = Double
    type AttrGetType TextAttributesFontScaleFieldInfo = Double
    type AttrLabel TextAttributesFontScaleFieldInfo = "font_scale"
    type AttrOrigin TextAttributesFontScaleFieldInfo = TextAttributes
    attrGet = getTextAttributesFontScale
    attrSet = setTextAttributesFontScale
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_fontScale :: AttrLabelProxy "fontScale"
textAttributes_fontScale = AttrLabelProxy

#endif


-- | Get the value of the “@left_margin@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #leftMargin
-- @
getTextAttributesLeftMargin :: MonadIO m => TextAttributes -> m Int32
getTextAttributesLeftMargin :: TextAttributes -> m Int32
getTextAttributesLeftMargin s :: TextAttributes
s = 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
$ TextAttributes -> (Ptr TextAttributes -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO Int32) -> IO Int32)
-> (Ptr TextAttributes -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@left_margin@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #leftMargin 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesLeftMargin :: MonadIO m => TextAttributes -> Int32 -> m ()
setTextAttributesLeftMargin :: TextAttributes -> Int32 -> m ()
setTextAttributesLeftMargin s :: TextAttributes
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data TextAttributesLeftMarginFieldInfo
instance AttrInfo TextAttributesLeftMarginFieldInfo where
    type AttrBaseTypeConstraint TextAttributesLeftMarginFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesLeftMarginFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesLeftMarginFieldInfo = (~) Int32
    type AttrTransferTypeConstraint TextAttributesLeftMarginFieldInfo = (~)Int32
    type AttrTransferType TextAttributesLeftMarginFieldInfo = Int32
    type AttrGetType TextAttributesLeftMarginFieldInfo = Int32
    type AttrLabel TextAttributesLeftMarginFieldInfo = "left_margin"
    type AttrOrigin TextAttributesLeftMarginFieldInfo = TextAttributes
    attrGet = getTextAttributesLeftMargin
    attrSet = setTextAttributesLeftMargin
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_leftMargin :: AttrLabelProxy "leftMargin"
textAttributes_leftMargin = AttrLabelProxy

#endif


-- | Get the value of the “@right_margin@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #rightMargin
-- @
getTextAttributesRightMargin :: MonadIO m => TextAttributes -> m Int32
getTextAttributesRightMargin :: TextAttributes -> m Int32
getTextAttributesRightMargin s :: TextAttributes
s = 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
$ TextAttributes -> (Ptr TextAttributes -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO Int32) -> IO Int32)
-> (Ptr TextAttributes -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@right_margin@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #rightMargin 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesRightMargin :: MonadIO m => TextAttributes -> Int32 -> m ()
setTextAttributesRightMargin :: TextAttributes -> Int32 -> m ()
setTextAttributesRightMargin s :: TextAttributes
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data TextAttributesRightMarginFieldInfo
instance AttrInfo TextAttributesRightMarginFieldInfo where
    type AttrBaseTypeConstraint TextAttributesRightMarginFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesRightMarginFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesRightMarginFieldInfo = (~) Int32
    type AttrTransferTypeConstraint TextAttributesRightMarginFieldInfo = (~)Int32
    type AttrTransferType TextAttributesRightMarginFieldInfo = Int32
    type AttrGetType TextAttributesRightMarginFieldInfo = Int32
    type AttrLabel TextAttributesRightMarginFieldInfo = "right_margin"
    type AttrOrigin TextAttributesRightMarginFieldInfo = TextAttributes
    attrGet = getTextAttributesRightMargin
    attrSet = setTextAttributesRightMargin
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_rightMargin :: AttrLabelProxy "rightMargin"
textAttributes_rightMargin = AttrLabelProxy

#endif


-- | Get the value of the “@indent@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #indent
-- @
getTextAttributesIndent :: MonadIO m => TextAttributes -> m Int32
getTextAttributesIndent :: TextAttributes -> m Int32
getTextAttributesIndent s :: TextAttributes
s = 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
$ TextAttributes -> (Ptr TextAttributes -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO Int32) -> IO Int32)
-> (Ptr TextAttributes -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@indent@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #indent 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesIndent :: MonadIO m => TextAttributes -> Int32 -> m ()
setTextAttributesIndent :: TextAttributes -> Int32 -> m ()
setTextAttributesIndent s :: TextAttributes
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data TextAttributesIndentFieldInfo
instance AttrInfo TextAttributesIndentFieldInfo where
    type AttrBaseTypeConstraint TextAttributesIndentFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesIndentFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesIndentFieldInfo = (~) Int32
    type AttrTransferTypeConstraint TextAttributesIndentFieldInfo = (~)Int32
    type AttrTransferType TextAttributesIndentFieldInfo = Int32
    type AttrGetType TextAttributesIndentFieldInfo = Int32
    type AttrLabel TextAttributesIndentFieldInfo = "indent"
    type AttrOrigin TextAttributesIndentFieldInfo = TextAttributes
    attrGet = getTextAttributesIndent
    attrSet = setTextAttributesIndent
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_indent :: AttrLabelProxy "indent"
textAttributes_indent = AttrLabelProxy

#endif


-- | Get the value of the “@pixels_above_lines@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #pixelsAboveLines
-- @
getTextAttributesPixelsAboveLines :: MonadIO m => TextAttributes -> m Int32
getTextAttributesPixelsAboveLines :: TextAttributes -> m Int32
getTextAttributesPixelsAboveLines s :: TextAttributes
s = 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
$ TextAttributes -> (Ptr TextAttributes -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO Int32) -> IO Int32)
-> (Ptr TextAttributes -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@pixels_above_lines@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #pixelsAboveLines 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesPixelsAboveLines :: MonadIO m => TextAttributes -> Int32 -> m ()
setTextAttributesPixelsAboveLines :: TextAttributes -> Int32 -> m ()
setTextAttributesPixelsAboveLines s :: TextAttributes
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data TextAttributesPixelsAboveLinesFieldInfo
instance AttrInfo TextAttributesPixelsAboveLinesFieldInfo where
    type AttrBaseTypeConstraint TextAttributesPixelsAboveLinesFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesPixelsAboveLinesFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesPixelsAboveLinesFieldInfo = (~) Int32
    type AttrTransferTypeConstraint TextAttributesPixelsAboveLinesFieldInfo = (~)Int32
    type AttrTransferType TextAttributesPixelsAboveLinesFieldInfo = Int32
    type AttrGetType TextAttributesPixelsAboveLinesFieldInfo = Int32
    type AttrLabel TextAttributesPixelsAboveLinesFieldInfo = "pixels_above_lines"
    type AttrOrigin TextAttributesPixelsAboveLinesFieldInfo = TextAttributes
    attrGet = getTextAttributesPixelsAboveLines
    attrSet = setTextAttributesPixelsAboveLines
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_pixelsAboveLines :: AttrLabelProxy "pixelsAboveLines"
textAttributes_pixelsAboveLines = AttrLabelProxy

#endif


-- | Get the value of the “@pixels_below_lines@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #pixelsBelowLines
-- @
getTextAttributesPixelsBelowLines :: MonadIO m => TextAttributes -> m Int32
getTextAttributesPixelsBelowLines :: TextAttributes -> m Int32
getTextAttributesPixelsBelowLines s :: TextAttributes
s = 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
$ TextAttributes -> (Ptr TextAttributes -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO Int32) -> IO Int32)
-> (Ptr TextAttributes -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@pixels_below_lines@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #pixelsBelowLines 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesPixelsBelowLines :: MonadIO m => TextAttributes -> Int32 -> m ()
setTextAttributesPixelsBelowLines :: TextAttributes -> Int32 -> m ()
setTextAttributesPixelsBelowLines s :: TextAttributes
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data TextAttributesPixelsBelowLinesFieldInfo
instance AttrInfo TextAttributesPixelsBelowLinesFieldInfo where
    type AttrBaseTypeConstraint TextAttributesPixelsBelowLinesFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesPixelsBelowLinesFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesPixelsBelowLinesFieldInfo = (~) Int32
    type AttrTransferTypeConstraint TextAttributesPixelsBelowLinesFieldInfo = (~)Int32
    type AttrTransferType TextAttributesPixelsBelowLinesFieldInfo = Int32
    type AttrGetType TextAttributesPixelsBelowLinesFieldInfo = Int32
    type AttrLabel TextAttributesPixelsBelowLinesFieldInfo = "pixels_below_lines"
    type AttrOrigin TextAttributesPixelsBelowLinesFieldInfo = TextAttributes
    attrGet = getTextAttributesPixelsBelowLines
    attrSet = setTextAttributesPixelsBelowLines
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_pixelsBelowLines :: AttrLabelProxy "pixelsBelowLines"
textAttributes_pixelsBelowLines = AttrLabelProxy

#endif


-- | Get the value of the “@pixels_inside_wrap@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #pixelsInsideWrap
-- @
getTextAttributesPixelsInsideWrap :: MonadIO m => TextAttributes -> m Int32
getTextAttributesPixelsInsideWrap :: TextAttributes -> m Int32
getTextAttributesPixelsInsideWrap s :: TextAttributes
s = 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
$ TextAttributes -> (Ptr TextAttributes -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO Int32) -> IO Int32)
-> (Ptr TextAttributes -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@pixels_inside_wrap@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #pixelsInsideWrap 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesPixelsInsideWrap :: MonadIO m => TextAttributes -> Int32 -> m ()
setTextAttributesPixelsInsideWrap :: TextAttributes -> Int32 -> m ()
setTextAttributesPixelsInsideWrap s :: TextAttributes
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data TextAttributesPixelsInsideWrapFieldInfo
instance AttrInfo TextAttributesPixelsInsideWrapFieldInfo where
    type AttrBaseTypeConstraint TextAttributesPixelsInsideWrapFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesPixelsInsideWrapFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesPixelsInsideWrapFieldInfo = (~) Int32
    type AttrTransferTypeConstraint TextAttributesPixelsInsideWrapFieldInfo = (~)Int32
    type AttrTransferType TextAttributesPixelsInsideWrapFieldInfo = Int32
    type AttrGetType TextAttributesPixelsInsideWrapFieldInfo = Int32
    type AttrLabel TextAttributesPixelsInsideWrapFieldInfo = "pixels_inside_wrap"
    type AttrOrigin TextAttributesPixelsInsideWrapFieldInfo = TextAttributes
    attrGet = getTextAttributesPixelsInsideWrap
    attrSet = setTextAttributesPixelsInsideWrap
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_pixelsInsideWrap :: AttrLabelProxy "pixelsInsideWrap"
textAttributes_pixelsInsideWrap = AttrLabelProxy

#endif


-- | Get the value of the “@tabs@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #tabs
-- @
getTextAttributesTabs :: MonadIO m => TextAttributes -> m (Maybe Pango.TabArray.TabArray)
getTextAttributesTabs :: TextAttributes -> m (Maybe TabArray)
getTextAttributesTabs s :: TextAttributes
s = IO (Maybe TabArray) -> m (Maybe TabArray)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TabArray) -> m (Maybe TabArray))
-> IO (Maybe TabArray) -> m (Maybe TabArray)
forall a b. (a -> b) -> a -> b
$ TextAttributes
-> (Ptr TextAttributes -> IO (Maybe TabArray))
-> IO (Maybe TabArray)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO (Maybe TabArray))
 -> IO (Maybe TabArray))
-> (Ptr TextAttributes -> IO (Maybe TabArray))
-> IO (Maybe TabArray)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr TabArray
val <- Ptr (Ptr TabArray) -> IO (Ptr TabArray)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr (Ptr TabArray)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104) :: IO (Ptr Pango.TabArray.TabArray)
    Maybe TabArray
result <- Ptr TabArray
-> (Ptr TabArray -> IO TabArray) -> IO (Maybe TabArray)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr TabArray
val ((Ptr TabArray -> IO TabArray) -> IO (Maybe TabArray))
-> (Ptr TabArray -> IO TabArray) -> IO (Maybe TabArray)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr TabArray
val' -> do
        TabArray
val'' <- ((ManagedPtr TabArray -> TabArray) -> Ptr TabArray -> IO TabArray
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr TabArray -> TabArray
Pango.TabArray.TabArray) Ptr TabArray
val'
        TabArray -> IO TabArray
forall (m :: * -> *) a. Monad m => a -> m a
return TabArray
val''
    Maybe TabArray -> IO (Maybe TabArray)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TabArray
result

-- | Set the value of the “@tabs@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #tabs 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesTabs :: MonadIO m => TextAttributes -> Ptr Pango.TabArray.TabArray -> m ()
setTextAttributesTabs :: TextAttributes -> Ptr TabArray -> m ()
setTextAttributesTabs s :: TextAttributes
s val :: Ptr TabArray
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr (Ptr TabArray) -> Ptr TabArray -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr (Ptr TabArray)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104) (Ptr TabArray
val :: Ptr Pango.TabArray.TabArray)

-- | Set the value of the “@tabs@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #tabs
-- @
clearTextAttributesTabs :: MonadIO m => TextAttributes -> m ()
clearTextAttributesTabs :: TextAttributes -> m ()
clearTextAttributesTabs s :: TextAttributes
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr (Ptr TabArray) -> Ptr TabArray -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr (Ptr TabArray)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104) (Ptr TabArray
forall a. Ptr a
FP.nullPtr :: Ptr Pango.TabArray.TabArray)

#if defined(ENABLE_OVERLOADING)
data TextAttributesTabsFieldInfo
instance AttrInfo TextAttributesTabsFieldInfo where
    type AttrBaseTypeConstraint TextAttributesTabsFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesTabsFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TextAttributesTabsFieldInfo = (~) (Ptr Pango.TabArray.TabArray)
    type AttrTransferTypeConstraint TextAttributesTabsFieldInfo = (~)(Ptr Pango.TabArray.TabArray)
    type AttrTransferType TextAttributesTabsFieldInfo = (Ptr Pango.TabArray.TabArray)
    type AttrGetType TextAttributesTabsFieldInfo = Maybe Pango.TabArray.TabArray
    type AttrLabel TextAttributesTabsFieldInfo = "tabs"
    type AttrOrigin TextAttributesTabsFieldInfo = TextAttributes
    attrGet = getTextAttributesTabs
    attrSet = setTextAttributesTabs
    attrConstruct = undefined
    attrClear = clearTextAttributesTabs
    attrTransfer _ v = do
        return v

textAttributes_tabs :: AttrLabelProxy "tabs"
textAttributes_tabs = AttrLabelProxy

#endif


-- | Get the value of the “@wrap_mode@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #wrapMode
-- @
getTextAttributesWrapMode :: MonadIO m => TextAttributes -> m Gtk.Enums.WrapMode
getTextAttributesWrapMode :: TextAttributes -> m WrapMode
getTextAttributesWrapMode s :: TextAttributes
s = 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
$ TextAttributes
-> (Ptr TextAttributes -> IO WrapMode) -> IO WrapMode
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO WrapMode) -> IO WrapMode)
-> (Ptr TextAttributes -> IO WrapMode) -> IO WrapMode
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112) :: IO CUInt
    let val' :: WrapMode
val' = (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
val
    WrapMode -> IO WrapMode
forall (m :: * -> *) a. Monad m => a -> m a
return WrapMode
val'

-- | Set the value of the “@wrap_mode@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #wrapMode 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesWrapMode :: MonadIO m => TextAttributes -> Gtk.Enums.WrapMode -> m ()
setTextAttributesWrapMode :: TextAttributes -> WrapMode -> m ()
setTextAttributesWrapMode s :: TextAttributes
s val :: WrapMode
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    let val' :: CUInt
val' = (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
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112) (CUInt
val' :: CUInt)

#if defined(ENABLE_OVERLOADING)
data TextAttributesWrapModeFieldInfo
instance AttrInfo TextAttributesWrapModeFieldInfo where
    type AttrBaseTypeConstraint TextAttributesWrapModeFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesWrapModeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesWrapModeFieldInfo = (~) Gtk.Enums.WrapMode
    type AttrTransferTypeConstraint TextAttributesWrapModeFieldInfo = (~)Gtk.Enums.WrapMode
    type AttrTransferType TextAttributesWrapModeFieldInfo = Gtk.Enums.WrapMode
    type AttrGetType TextAttributesWrapModeFieldInfo = Gtk.Enums.WrapMode
    type AttrLabel TextAttributesWrapModeFieldInfo = "wrap_mode"
    type AttrOrigin TextAttributesWrapModeFieldInfo = TextAttributes
    attrGet = getTextAttributesWrapMode
    attrSet = setTextAttributesWrapMode
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_wrapMode :: AttrLabelProxy "wrapMode"
textAttributes_wrapMode = AttrLabelProxy

#endif


-- | Get the value of the “@language@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #language
-- @
getTextAttributesLanguage :: MonadIO m => TextAttributes -> m (Maybe Pango.Language.Language)
getTextAttributesLanguage :: TextAttributes -> m (Maybe Language)
getTextAttributesLanguage s :: TextAttributes
s = IO (Maybe Language) -> m (Maybe Language)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Language) -> m (Maybe Language))
-> IO (Maybe Language) -> m (Maybe Language)
forall a b. (a -> b) -> a -> b
$ TextAttributes
-> (Ptr TextAttributes -> IO (Maybe Language))
-> IO (Maybe Language)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO (Maybe Language))
 -> IO (Maybe Language))
-> (Ptr TextAttributes -> IO (Maybe Language))
-> IO (Maybe Language)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr Language
val <- Ptr (Ptr Language) -> IO (Ptr Language)
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr (Ptr Language)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120) :: IO (Ptr Pango.Language.Language)
    Maybe Language
result <- Ptr Language
-> (Ptr Language -> IO Language) -> IO (Maybe Language)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Language
val ((Ptr Language -> IO Language) -> IO (Maybe Language))
-> (Ptr Language -> IO Language) -> IO (Maybe Language)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr Language
val' -> do
        Language
val'' <- ((ManagedPtr Language -> Language) -> Ptr Language -> IO Language
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Language -> Language
Pango.Language.Language) Ptr Language
val'
        Language -> IO Language
forall (m :: * -> *) a. Monad m => a -> m a
return Language
val''
    Maybe Language -> IO (Maybe Language)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Language
result

-- | Set the value of the “@language@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #language 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesLanguage :: MonadIO m => TextAttributes -> Ptr Pango.Language.Language -> m ()
setTextAttributesLanguage :: TextAttributes -> Ptr Language -> m ()
setTextAttributesLanguage s :: TextAttributes
s val :: Ptr Language
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr (Ptr Language) -> Ptr Language -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr (Ptr Language)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120) (Ptr Language
val :: Ptr Pango.Language.Language)

-- | Set the value of the “@language@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #language
-- @
clearTextAttributesLanguage :: MonadIO m => TextAttributes -> m ()
clearTextAttributesLanguage :: TextAttributes -> m ()
clearTextAttributesLanguage s :: TextAttributes
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr (Ptr Language) -> Ptr Language -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr (Ptr Language)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120) (Ptr Language
forall a. Ptr a
FP.nullPtr :: Ptr Pango.Language.Language)

#if defined(ENABLE_OVERLOADING)
data TextAttributesLanguageFieldInfo
instance AttrInfo TextAttributesLanguageFieldInfo where
    type AttrBaseTypeConstraint TextAttributesLanguageFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesLanguageFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TextAttributesLanguageFieldInfo = (~) (Ptr Pango.Language.Language)
    type AttrTransferTypeConstraint TextAttributesLanguageFieldInfo = (~)(Ptr Pango.Language.Language)
    type AttrTransferType TextAttributesLanguageFieldInfo = (Ptr Pango.Language.Language)
    type AttrGetType TextAttributesLanguageFieldInfo = Maybe Pango.Language.Language
    type AttrLabel TextAttributesLanguageFieldInfo = "language"
    type AttrOrigin TextAttributesLanguageFieldInfo = TextAttributes
    attrGet = getTextAttributesLanguage
    attrSet = setTextAttributesLanguage
    attrConstruct = undefined
    attrClear = clearTextAttributesLanguage
    attrTransfer _ v = do
        return v

textAttributes_language :: AttrLabelProxy "language"
textAttributes_language = AttrLabelProxy

#endif


-- | Get the value of the “@invisible@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #invisible
-- @
getTextAttributesInvisible :: MonadIO m => TextAttributes -> m Word32
getTextAttributesInvisible :: TextAttributes -> m Word32
getTextAttributesInvisible s :: TextAttributes
s = 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
$ TextAttributes -> (Ptr TextAttributes -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO Word32) -> IO Word32)
-> (Ptr TextAttributes -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@invisible@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #invisible 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesInvisible :: MonadIO m => TextAttributes -> Word32 -> m ()
setTextAttributesInvisible :: TextAttributes -> Word32 -> m ()
setTextAttributesInvisible s :: TextAttributes
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data TextAttributesInvisibleFieldInfo
instance AttrInfo TextAttributesInvisibleFieldInfo where
    type AttrBaseTypeConstraint TextAttributesInvisibleFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesInvisibleFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesInvisibleFieldInfo = (~) Word32
    type AttrTransferTypeConstraint TextAttributesInvisibleFieldInfo = (~)Word32
    type AttrTransferType TextAttributesInvisibleFieldInfo = Word32
    type AttrGetType TextAttributesInvisibleFieldInfo = Word32
    type AttrLabel TextAttributesInvisibleFieldInfo = "invisible"
    type AttrOrigin TextAttributesInvisibleFieldInfo = TextAttributes
    attrGet = getTextAttributesInvisible
    attrSet = setTextAttributesInvisible
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_invisible :: AttrLabelProxy "invisible"
textAttributes_invisible = AttrLabelProxy

#endif


-- | Get the value of the “@bg_full_height@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #bgFullHeight
-- @
getTextAttributesBgFullHeight :: MonadIO m => TextAttributes -> m Word32
getTextAttributesBgFullHeight :: TextAttributes -> m Word32
getTextAttributesBgFullHeight s :: TextAttributes
s = 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
$ TextAttributes -> (Ptr TextAttributes -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO Word32) -> IO Word32)
-> (Ptr TextAttributes -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 140) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@bg_full_height@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #bgFullHeight 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesBgFullHeight :: MonadIO m => TextAttributes -> Word32 -> m ()
setTextAttributesBgFullHeight :: TextAttributes -> Word32 -> m ()
setTextAttributesBgFullHeight s :: TextAttributes
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 140) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data TextAttributesBgFullHeightFieldInfo
instance AttrInfo TextAttributesBgFullHeightFieldInfo where
    type AttrBaseTypeConstraint TextAttributesBgFullHeightFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesBgFullHeightFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesBgFullHeightFieldInfo = (~) Word32
    type AttrTransferTypeConstraint TextAttributesBgFullHeightFieldInfo = (~)Word32
    type AttrTransferType TextAttributesBgFullHeightFieldInfo = Word32
    type AttrGetType TextAttributesBgFullHeightFieldInfo = Word32
    type AttrLabel TextAttributesBgFullHeightFieldInfo = "bg_full_height"
    type AttrOrigin TextAttributesBgFullHeightFieldInfo = TextAttributes
    attrGet = getTextAttributesBgFullHeight
    attrSet = setTextAttributesBgFullHeight
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_bgFullHeight :: AttrLabelProxy "bgFullHeight"
textAttributes_bgFullHeight = AttrLabelProxy

#endif


-- | Get the value of the “@editable@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #editable
-- @
getTextAttributesEditable :: MonadIO m => TextAttributes -> m Word32
getTextAttributesEditable :: TextAttributes -> m Word32
getTextAttributesEditable s :: TextAttributes
s = 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
$ TextAttributes -> (Ptr TextAttributes -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO Word32) -> IO Word32)
-> (Ptr TextAttributes -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@editable@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #editable 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesEditable :: MonadIO m => TextAttributes -> Word32 -> m ()
setTextAttributesEditable :: TextAttributes -> Word32 -> m ()
setTextAttributesEditable s :: TextAttributes
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data TextAttributesEditableFieldInfo
instance AttrInfo TextAttributesEditableFieldInfo where
    type AttrBaseTypeConstraint TextAttributesEditableFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesEditableFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesEditableFieldInfo = (~) Word32
    type AttrTransferTypeConstraint TextAttributesEditableFieldInfo = (~)Word32
    type AttrTransferType TextAttributesEditableFieldInfo = Word32
    type AttrGetType TextAttributesEditableFieldInfo = Word32
    type AttrLabel TextAttributesEditableFieldInfo = "editable"
    type AttrOrigin TextAttributesEditableFieldInfo = TextAttributes
    attrGet = getTextAttributesEditable
    attrSet = setTextAttributesEditable
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_editable :: AttrLabelProxy "editable"
textAttributes_editable = AttrLabelProxy

#endif


-- | Get the value of the “@no_fallback@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #noFallback
-- @
getTextAttributesNoFallback :: MonadIO m => TextAttributes -> m Word32
getTextAttributesNoFallback :: TextAttributes -> m Word32
getTextAttributesNoFallback s :: TextAttributes
s = 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
$ TextAttributes -> (Ptr TextAttributes -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO Word32) -> IO Word32)
-> (Ptr TextAttributes -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 148) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@no_fallback@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #noFallback 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesNoFallback :: MonadIO m => TextAttributes -> Word32 -> m ()
setTextAttributesNoFallback :: TextAttributes -> Word32 -> m ()
setTextAttributesNoFallback s :: TextAttributes
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 148) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data TextAttributesNoFallbackFieldInfo
instance AttrInfo TextAttributesNoFallbackFieldInfo where
    type AttrBaseTypeConstraint TextAttributesNoFallbackFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesNoFallbackFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesNoFallbackFieldInfo = (~) Word32
    type AttrTransferTypeConstraint TextAttributesNoFallbackFieldInfo = (~)Word32
    type AttrTransferType TextAttributesNoFallbackFieldInfo = Word32
    type AttrGetType TextAttributesNoFallbackFieldInfo = Word32
    type AttrLabel TextAttributesNoFallbackFieldInfo = "no_fallback"
    type AttrOrigin TextAttributesNoFallbackFieldInfo = TextAttributes
    attrGet = getTextAttributesNoFallback
    attrSet = setTextAttributesNoFallback
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_noFallback :: AttrLabelProxy "noFallback"
textAttributes_noFallback = AttrLabelProxy

#endif


-- | Get the value of the “@letter_spacing@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' textAttributes #letterSpacing
-- @
getTextAttributesLetterSpacing :: MonadIO m => TextAttributes -> m Int32
getTextAttributesLetterSpacing :: TextAttributes -> m Int32
getTextAttributesLetterSpacing s :: TextAttributes
s = 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
$ TextAttributes -> (Ptr TextAttributes -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO Int32) -> IO Int32)
-> (Ptr TextAttributes -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 160) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@letter_spacing@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' textAttributes [ #letterSpacing 'Data.GI.Base.Attributes.:=' value ]
-- @
setTextAttributesLetterSpacing :: MonadIO m => TextAttributes -> Int32 -> m ()
setTextAttributesLetterSpacing :: TextAttributes -> Int32 -> m ()
setTextAttributesLetterSpacing s :: TextAttributes
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAttributes -> (Ptr TextAttributes -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAttributes
s ((Ptr TextAttributes -> IO ()) -> IO ())
-> (Ptr TextAttributes -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAttributes
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAttributes
ptr Ptr TextAttributes -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 160) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data TextAttributesLetterSpacingFieldInfo
instance AttrInfo TextAttributesLetterSpacingFieldInfo where
    type AttrBaseTypeConstraint TextAttributesLetterSpacingFieldInfo = (~) TextAttributes
    type AttrAllowedOps TextAttributesLetterSpacingFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesLetterSpacingFieldInfo = (~) Int32
    type AttrTransferTypeConstraint TextAttributesLetterSpacingFieldInfo = (~)Int32
    type AttrTransferType TextAttributesLetterSpacingFieldInfo = Int32
    type AttrGetType TextAttributesLetterSpacingFieldInfo = Int32
    type AttrLabel TextAttributesLetterSpacingFieldInfo = "letter_spacing"
    type AttrOrigin TextAttributesLetterSpacingFieldInfo = TextAttributes
    attrGet = getTextAttributesLetterSpacing
    attrSet = setTextAttributesLetterSpacing
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

textAttributes_letterSpacing :: AttrLabelProxy "letterSpacing"
textAttributes_letterSpacing = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TextAttributes
type instance O.AttributeList TextAttributes = TextAttributesAttributeList
type TextAttributesAttributeList = ('[ '("appearance", TextAttributesAppearanceFieldInfo), '("justification", TextAttributesJustificationFieldInfo), '("direction", TextAttributesDirectionFieldInfo), '("font", TextAttributesFontFieldInfo), '("fontScale", TextAttributesFontScaleFieldInfo), '("leftMargin", TextAttributesLeftMarginFieldInfo), '("rightMargin", TextAttributesRightMarginFieldInfo), '("indent", TextAttributesIndentFieldInfo), '("pixelsAboveLines", TextAttributesPixelsAboveLinesFieldInfo), '("pixelsBelowLines", TextAttributesPixelsBelowLinesFieldInfo), '("pixelsInsideWrap", TextAttributesPixelsInsideWrapFieldInfo), '("tabs", TextAttributesTabsFieldInfo), '("wrapMode", TextAttributesWrapModeFieldInfo), '("language", TextAttributesLanguageFieldInfo), '("invisible", TextAttributesInvisibleFieldInfo), '("bgFullHeight", TextAttributesBgFullHeightFieldInfo), '("editable", TextAttributesEditableFieldInfo), '("noFallback", TextAttributesNoFallbackFieldInfo), '("letterSpacing", TextAttributesLetterSpacingFieldInfo)] :: [(Symbol, *)])
#endif

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

foreign import ccall "gtk_text_attributes_new" gtk_text_attributes_new :: 
    IO (Ptr TextAttributes)

-- | Creates a t'GI.Gtk.Structs.TextAttributes.TextAttributes', which describes
-- a set of properties on some text.
textAttributesNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m TextAttributes
    -- ^ __Returns:__ a new t'GI.Gtk.Structs.TextAttributes.TextAttributes',
    --     free with 'GI.Gtk.Structs.TextAttributes.textAttributesUnref'.
textAttributesNew :: m TextAttributes
textAttributesNew  = IO TextAttributes -> m TextAttributes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextAttributes -> m TextAttributes)
-> IO TextAttributes -> m TextAttributes
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextAttributes
result <- IO (Ptr TextAttributes)
gtk_text_attributes_new
    Text -> Ptr TextAttributes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "textAttributesNew" Ptr TextAttributes
result
    TextAttributes
result' <- ((ManagedPtr TextAttributes -> TextAttributes)
-> Ptr TextAttributes -> IO TextAttributes
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextAttributes -> TextAttributes
TextAttributes) Ptr TextAttributes
result
    TextAttributes -> IO TextAttributes
forall (m :: * -> *) a. Monad m => a -> m a
return TextAttributes
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gtk_text_attributes_copy" gtk_text_attributes_copy :: 
    Ptr TextAttributes ->                   -- src : TInterface (Name {namespace = "Gtk", name = "TextAttributes"})
    IO (Ptr TextAttributes)

-- | Copies /@src@/ and returns a new t'GI.Gtk.Structs.TextAttributes.TextAttributes'.
textAttributesCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextAttributes
    -- ^ /@src@/: a t'GI.Gtk.Structs.TextAttributes.TextAttributes' to be copied
    -> m TextAttributes
    -- ^ __Returns:__ a copy of /@src@/,
    --     free with 'GI.Gtk.Structs.TextAttributes.textAttributesUnref'
textAttributesCopy :: TextAttributes -> m TextAttributes
textAttributesCopy src :: TextAttributes
src = IO TextAttributes -> m TextAttributes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextAttributes -> m TextAttributes)
-> IO TextAttributes -> m TextAttributes
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextAttributes
src' <- TextAttributes -> IO (Ptr TextAttributes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextAttributes
src
    Ptr TextAttributes
result <- Ptr TextAttributes -> IO (Ptr TextAttributes)
gtk_text_attributes_copy Ptr TextAttributes
src'
    Text -> Ptr TextAttributes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "textAttributesCopy" Ptr TextAttributes
result
    TextAttributes
result' <- ((ManagedPtr TextAttributes -> TextAttributes)
-> Ptr TextAttributes -> IO TextAttributes
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextAttributes -> TextAttributes
TextAttributes) Ptr TextAttributes
result
    TextAttributes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextAttributes
src
    TextAttributes -> IO TextAttributes
forall (m :: * -> *) a. Monad m => a -> m a
return TextAttributes
result'

#if defined(ENABLE_OVERLOADING)
data TextAttributesCopyMethodInfo
instance (signature ~ (m TextAttributes), MonadIO m) => O.MethodInfo TextAttributesCopyMethodInfo TextAttributes signature where
    overloadedMethod = textAttributesCopy

#endif

-- method TextAttributes::copy_values
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextAttributes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkTextAttributes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "TextAttributes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "another #GtkTextAttributes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_text_attributes_copy_values" gtk_text_attributes_copy_values :: 
    Ptr TextAttributes ->                   -- src : TInterface (Name {namespace = "Gtk", name = "TextAttributes"})
    Ptr TextAttributes ->                   -- dest : TInterface (Name {namespace = "Gtk", name = "TextAttributes"})
    IO ()

-- | Copies the values from /@src@/ to /@dest@/ so that /@dest@/ has
-- the same values as /@src@/. Frees existing values in /@dest@/.
textAttributesCopyValues ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextAttributes
    -- ^ /@src@/: a t'GI.Gtk.Structs.TextAttributes.TextAttributes'
    -> TextAttributes
    -- ^ /@dest@/: another t'GI.Gtk.Structs.TextAttributes.TextAttributes'
    -> m ()
textAttributesCopyValues :: TextAttributes -> TextAttributes -> m ()
textAttributesCopyValues src :: TextAttributes
src dest :: TextAttributes
dest = 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 TextAttributes
src' <- TextAttributes -> IO (Ptr TextAttributes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextAttributes
src
    Ptr TextAttributes
dest' <- TextAttributes -> IO (Ptr TextAttributes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextAttributes
dest
    Ptr TextAttributes -> Ptr TextAttributes -> IO ()
gtk_text_attributes_copy_values Ptr TextAttributes
src' Ptr TextAttributes
dest'
    TextAttributes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextAttributes
src
    TextAttributes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextAttributes
dest
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TextAttributesCopyValuesMethodInfo
instance (signature ~ (TextAttributes -> m ()), MonadIO m) => O.MethodInfo TextAttributesCopyValuesMethodInfo TextAttributes signature where
    overloadedMethod = textAttributesCopyValues

#endif

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

foreign import ccall "gtk_text_attributes_ref" gtk_text_attributes_ref :: 
    Ptr TextAttributes ->                   -- values : TInterface (Name {namespace = "Gtk", name = "TextAttributes"})
    IO (Ptr TextAttributes)

-- | Increments the reference count on /@values@/.
textAttributesRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextAttributes
    -- ^ /@values@/: a t'GI.Gtk.Structs.TextAttributes.TextAttributes'
    -> m TextAttributes
    -- ^ __Returns:__ the t'GI.Gtk.Structs.TextAttributes.TextAttributes' that were passed in
textAttributesRef :: TextAttributes -> m TextAttributes
textAttributesRef values :: TextAttributes
values = IO TextAttributes -> m TextAttributes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextAttributes -> m TextAttributes)
-> IO TextAttributes -> m TextAttributes
forall a b. (a -> b) -> a -> b
$ do
    Ptr TextAttributes
values' <- TextAttributes -> IO (Ptr TextAttributes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextAttributes
values
    Ptr TextAttributes
result <- Ptr TextAttributes -> IO (Ptr TextAttributes)
gtk_text_attributes_ref Ptr TextAttributes
values'
    Text -> Ptr TextAttributes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "textAttributesRef" Ptr TextAttributes
result
    TextAttributes
result' <- ((ManagedPtr TextAttributes -> TextAttributes)
-> Ptr TextAttributes -> IO TextAttributes
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TextAttributes -> TextAttributes
TextAttributes) Ptr TextAttributes
result
    TextAttributes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextAttributes
values
    TextAttributes -> IO TextAttributes
forall (m :: * -> *) a. Monad m => a -> m a
return TextAttributes
result'

#if defined(ENABLE_OVERLOADING)
data TextAttributesRefMethodInfo
instance (signature ~ (m TextAttributes), MonadIO m) => O.MethodInfo TextAttributesRefMethodInfo TextAttributes signature where
    overloadedMethod = textAttributesRef

#endif

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

foreign import ccall "gtk_text_attributes_unref" gtk_text_attributes_unref :: 
    Ptr TextAttributes ->                   -- values : TInterface (Name {namespace = "Gtk", name = "TextAttributes"})
    IO ()

-- | Decrements the reference count on /@values@/, freeing the structure
-- if the reference count reaches 0.
textAttributesUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextAttributes
    -- ^ /@values@/: a t'GI.Gtk.Structs.TextAttributes.TextAttributes'
    -> m ()
textAttributesUnref :: TextAttributes -> m ()
textAttributesUnref values :: TextAttributes
values = 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 TextAttributes
values' <- TextAttributes -> IO (Ptr TextAttributes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TextAttributes
values
    Ptr TextAttributes -> IO ()
gtk_text_attributes_unref Ptr TextAttributes
values'
    TextAttributes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TextAttributes
values
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TextAttributesUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo TextAttributesUnrefMethodInfo TextAttributes signature where
    overloadedMethod = textAttributesUnref

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTextAttributesMethod (t :: Symbol) (o :: *) :: * where
    ResolveTextAttributesMethod "copy" o = TextAttributesCopyMethodInfo
    ResolveTextAttributesMethod "copyValues" o = TextAttributesCopyValuesMethodInfo
    ResolveTextAttributesMethod "ref" o = TextAttributesRefMethodInfo
    ResolveTextAttributesMethod "unref" o = TextAttributesUnrefMethodInfo
    ResolveTextAttributesMethod l o = O.MethodResolutionFailed l o

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

#endif