{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)

Using '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.
-}

module GI.Gtk.Structs.TextAttributes
    ( 

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


 -- * Methods
-- ** copy #method:copy#
    TextAttributesCopyMethodInfo            ,
    textAttributesCopy                      ,


-- ** copyValues #method:copyValues#
    TextAttributesCopyValuesMethodInfo      ,
    textAttributesCopyValues                ,


-- ** new #method:new#
    textAttributesNew                       ,


-- ** ref #method:ref#
    TextAttributesRefMethodInfo             ,
    textAttributesRef                       ,


-- ** unref #method:unref#
    TextAttributesUnrefMethodInfo           ,
    textAttributesUnref                     ,




 -- * Properties
-- ** appearance #attr:appearance#
    getTextAttributesAppearance             ,
    textAttributes_appearance               ,


-- ** bgFullHeight #attr:bgFullHeight#
    getTextAttributesBgFullHeight           ,
    setTextAttributesBgFullHeight           ,
    textAttributes_bgFullHeight             ,


-- ** direction #attr:direction#
    getTextAttributesDirection              ,
    setTextAttributesDirection              ,
    textAttributes_direction                ,


-- ** editable #attr:editable#
    getTextAttributesEditable               ,
    setTextAttributesEditable               ,
    textAttributes_editable                 ,


-- ** font #attr:font#
    clearTextAttributesFont                 ,
    getTextAttributesFont                   ,
    setTextAttributesFont                   ,
    textAttributes_font                     ,


-- ** fontScale #attr:fontScale#
    getTextAttributesFontScale              ,
    setTextAttributesFontScale              ,
    textAttributes_fontScale                ,


-- ** indent #attr:indent#
    getTextAttributesIndent                 ,
    setTextAttributesIndent                 ,
    textAttributes_indent                   ,


-- ** invisible #attr:invisible#
    getTextAttributesInvisible              ,
    setTextAttributesInvisible              ,
    textAttributes_invisible                ,


-- ** justification #attr:justification#
    getTextAttributesJustification          ,
    setTextAttributesJustification          ,
    textAttributes_justification            ,


-- ** language #attr:language#
    clearTextAttributesLanguage             ,
    getTextAttributesLanguage               ,
    setTextAttributesLanguage               ,
    textAttributes_language                 ,


-- ** leftMargin #attr:leftMargin#
    getTextAttributesLeftMargin             ,
    setTextAttributesLeftMargin             ,
    textAttributes_leftMargin               ,


-- ** letterSpacing #attr:letterSpacing#
    getTextAttributesLetterSpacing          ,
    setTextAttributesLetterSpacing          ,
    textAttributes_letterSpacing            ,


-- ** noFallback #attr:noFallback#
    getTextAttributesNoFallback             ,
    setTextAttributesNoFallback             ,
    textAttributes_noFallback               ,


-- ** pixelsAboveLines #attr:pixelsAboveLines#
    getTextAttributesPixelsAboveLines       ,
    setTextAttributesPixelsAboveLines       ,
    textAttributes_pixelsAboveLines         ,


-- ** pixelsBelowLines #attr:pixelsBelowLines#
    getTextAttributesPixelsBelowLines       ,
    setTextAttributesPixelsBelowLines       ,
    textAttributes_pixelsBelowLines         ,


-- ** pixelsInsideWrap #attr:pixelsInsideWrap#
    getTextAttributesPixelsInsideWrap       ,
    setTextAttributesPixelsInsideWrap       ,
    textAttributes_pixelsInsideWrap         ,


-- ** rightMargin #attr:rightMargin#
    getTextAttributesRightMargin            ,
    setTextAttributesRightMargin            ,
    textAttributes_rightMargin              ,


-- ** tabs #attr:tabs#
    clearTextAttributesTabs                 ,
    getTextAttributesTabs                   ,
    setTextAttributesTabs                   ,
    textAttributes_tabs                     ,


-- ** wrapMode #attr:wrapMode#
    getTextAttributesWrapMode               ,
    setTextAttributesWrapMode               ,
    textAttributes_wrapMode                 ,




    ) 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.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
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 {-# 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

newtype TextAttributes = TextAttributes (ManagedPtr TextAttributes)
foreign import ccall "gtk_text_attributes_get_type" c_gtk_text_attributes_get_type :: 
    IO GType

instance BoxedObject TextAttributes where
    boxedType _ = c_gtk_text_attributes_get_type

-- | Construct a `TextAttributes` struct initialized to zero.
newZeroTextAttributes :: MonadIO m => m TextAttributes
newZeroTextAttributes = liftIO $ callocBoxedBytes 168 >>= wrapBoxed TextAttributes

instance tag ~ 'AttrSet => Constructible TextAttributes tag where
    new _ attrs = do
        o <- newZeroTextAttributes
        GI.Attributes.set o attrs
        return o


noTextAttributes :: Maybe TextAttributes
noTextAttributes = Nothing

getTextAttributesAppearance :: MonadIO m => TextAttributes -> m Gtk.TextAppearance.TextAppearance
getTextAttributesAppearance s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 4 :: (Ptr Gtk.TextAppearance.TextAppearance)
    val' <- (newPtr Gtk.TextAppearance.TextAppearance) val
    return val'

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

textAttributes_appearance :: AttrLabelProxy "appearance"
textAttributes_appearance = AttrLabelProxy


getTextAttributesJustification :: MonadIO m => TextAttributes -> m Gtk.Enums.Justification
getTextAttributesJustification s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 52) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

setTextAttributesJustification :: MonadIO m => TextAttributes -> Gtk.Enums.Justification -> m ()
setTextAttributesJustification s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 52) (val' :: CUInt)

data TextAttributesJustificationFieldInfo
instance AttrInfo TextAttributesJustificationFieldInfo where
    type AttrAllowedOps TextAttributesJustificationFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesJustificationFieldInfo = (~) Gtk.Enums.Justification
    type AttrBaseTypeConstraint TextAttributesJustificationFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesJustificationFieldInfo = Gtk.Enums.Justification
    type AttrLabel TextAttributesJustificationFieldInfo = "justification"
    type AttrOrigin TextAttributesJustificationFieldInfo = TextAttributes
    attrGet _ = getTextAttributesJustification
    attrSet _ = setTextAttributesJustification
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_justification :: AttrLabelProxy "justification"
textAttributes_justification = AttrLabelProxy


getTextAttributesDirection :: MonadIO m => TextAttributes -> m Gtk.Enums.TextDirection
getTextAttributesDirection s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 56) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

setTextAttributesDirection :: MonadIO m => TextAttributes -> Gtk.Enums.TextDirection -> m ()
setTextAttributesDirection s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 56) (val' :: CUInt)

data TextAttributesDirectionFieldInfo
instance AttrInfo TextAttributesDirectionFieldInfo where
    type AttrAllowedOps TextAttributesDirectionFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesDirectionFieldInfo = (~) Gtk.Enums.TextDirection
    type AttrBaseTypeConstraint TextAttributesDirectionFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesDirectionFieldInfo = Gtk.Enums.TextDirection
    type AttrLabel TextAttributesDirectionFieldInfo = "direction"
    type AttrOrigin TextAttributesDirectionFieldInfo = TextAttributes
    attrGet _ = getTextAttributesDirection
    attrSet _ = setTextAttributesDirection
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_direction :: AttrLabelProxy "direction"
textAttributes_direction = AttrLabelProxy


getTextAttributesFont :: MonadIO m => TextAttributes -> m (Maybe Pango.FontDescription.FontDescription)
getTextAttributesFont s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 64) :: IO (Ptr Pango.FontDescription.FontDescription)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newBoxed Pango.FontDescription.FontDescription) val'
        return val''
    return result

setTextAttributesFont :: MonadIO m => TextAttributes -> Ptr Pango.FontDescription.FontDescription -> m ()
setTextAttributesFont s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 64) (val :: Ptr Pango.FontDescription.FontDescription)

clearTextAttributesFont :: MonadIO m => TextAttributes -> m ()
clearTextAttributesFont s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 64) (FP.nullPtr :: Ptr Pango.FontDescription.FontDescription)

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

textAttributes_font :: AttrLabelProxy "font"
textAttributes_font = AttrLabelProxy


getTextAttributesFontScale :: MonadIO m => TextAttributes -> m Double
getTextAttributesFontScale s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 72) :: IO CDouble
    let val' = realToFrac val
    return val'

setTextAttributesFontScale :: MonadIO m => TextAttributes -> Double -> m ()
setTextAttributesFontScale s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = realToFrac val
    poke (ptr `plusPtr` 72) (val' :: CDouble)

data TextAttributesFontScaleFieldInfo
instance AttrInfo TextAttributesFontScaleFieldInfo where
    type AttrAllowedOps TextAttributesFontScaleFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesFontScaleFieldInfo = (~) Double
    type AttrBaseTypeConstraint TextAttributesFontScaleFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesFontScaleFieldInfo = Double
    type AttrLabel TextAttributesFontScaleFieldInfo = "font_scale"
    type AttrOrigin TextAttributesFontScaleFieldInfo = TextAttributes
    attrGet _ = getTextAttributesFontScale
    attrSet _ = setTextAttributesFontScale
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_fontScale :: AttrLabelProxy "fontScale"
textAttributes_fontScale = AttrLabelProxy


getTextAttributesLeftMargin :: MonadIO m => TextAttributes -> m Int32
getTextAttributesLeftMargin s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 80) :: IO Int32
    return val

setTextAttributesLeftMargin :: MonadIO m => TextAttributes -> Int32 -> m ()
setTextAttributesLeftMargin s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 80) (val :: Int32)

data TextAttributesLeftMarginFieldInfo
instance AttrInfo TextAttributesLeftMarginFieldInfo where
    type AttrAllowedOps TextAttributesLeftMarginFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesLeftMarginFieldInfo = (~) Int32
    type AttrBaseTypeConstraint TextAttributesLeftMarginFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesLeftMarginFieldInfo = Int32
    type AttrLabel TextAttributesLeftMarginFieldInfo = "left_margin"
    type AttrOrigin TextAttributesLeftMarginFieldInfo = TextAttributes
    attrGet _ = getTextAttributesLeftMargin
    attrSet _ = setTextAttributesLeftMargin
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_leftMargin :: AttrLabelProxy "leftMargin"
textAttributes_leftMargin = AttrLabelProxy


getTextAttributesRightMargin :: MonadIO m => TextAttributes -> m Int32
getTextAttributesRightMargin s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 84) :: IO Int32
    return val

setTextAttributesRightMargin :: MonadIO m => TextAttributes -> Int32 -> m ()
setTextAttributesRightMargin s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 84) (val :: Int32)

data TextAttributesRightMarginFieldInfo
instance AttrInfo TextAttributesRightMarginFieldInfo where
    type AttrAllowedOps TextAttributesRightMarginFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesRightMarginFieldInfo = (~) Int32
    type AttrBaseTypeConstraint TextAttributesRightMarginFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesRightMarginFieldInfo = Int32
    type AttrLabel TextAttributesRightMarginFieldInfo = "right_margin"
    type AttrOrigin TextAttributesRightMarginFieldInfo = TextAttributes
    attrGet _ = getTextAttributesRightMargin
    attrSet _ = setTextAttributesRightMargin
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_rightMargin :: AttrLabelProxy "rightMargin"
textAttributes_rightMargin = AttrLabelProxy


getTextAttributesIndent :: MonadIO m => TextAttributes -> m Int32
getTextAttributesIndent s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 88) :: IO Int32
    return val

setTextAttributesIndent :: MonadIO m => TextAttributes -> Int32 -> m ()
setTextAttributesIndent s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 88) (val :: Int32)

data TextAttributesIndentFieldInfo
instance AttrInfo TextAttributesIndentFieldInfo where
    type AttrAllowedOps TextAttributesIndentFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesIndentFieldInfo = (~) Int32
    type AttrBaseTypeConstraint TextAttributesIndentFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesIndentFieldInfo = Int32
    type AttrLabel TextAttributesIndentFieldInfo = "indent"
    type AttrOrigin TextAttributesIndentFieldInfo = TextAttributes
    attrGet _ = getTextAttributesIndent
    attrSet _ = setTextAttributesIndent
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_indent :: AttrLabelProxy "indent"
textAttributes_indent = AttrLabelProxy


getTextAttributesPixelsAboveLines :: MonadIO m => TextAttributes -> m Int32
getTextAttributesPixelsAboveLines s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 92) :: IO Int32
    return val

setTextAttributesPixelsAboveLines :: MonadIO m => TextAttributes -> Int32 -> m ()
setTextAttributesPixelsAboveLines s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 92) (val :: Int32)

data TextAttributesPixelsAboveLinesFieldInfo
instance AttrInfo TextAttributesPixelsAboveLinesFieldInfo where
    type AttrAllowedOps TextAttributesPixelsAboveLinesFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesPixelsAboveLinesFieldInfo = (~) Int32
    type AttrBaseTypeConstraint TextAttributesPixelsAboveLinesFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesPixelsAboveLinesFieldInfo = Int32
    type AttrLabel TextAttributesPixelsAboveLinesFieldInfo = "pixels_above_lines"
    type AttrOrigin TextAttributesPixelsAboveLinesFieldInfo = TextAttributes
    attrGet _ = getTextAttributesPixelsAboveLines
    attrSet _ = setTextAttributesPixelsAboveLines
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_pixelsAboveLines :: AttrLabelProxy "pixelsAboveLines"
textAttributes_pixelsAboveLines = AttrLabelProxy


getTextAttributesPixelsBelowLines :: MonadIO m => TextAttributes -> m Int32
getTextAttributesPixelsBelowLines s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 96) :: IO Int32
    return val

setTextAttributesPixelsBelowLines :: MonadIO m => TextAttributes -> Int32 -> m ()
setTextAttributesPixelsBelowLines s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 96) (val :: Int32)

data TextAttributesPixelsBelowLinesFieldInfo
instance AttrInfo TextAttributesPixelsBelowLinesFieldInfo where
    type AttrAllowedOps TextAttributesPixelsBelowLinesFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesPixelsBelowLinesFieldInfo = (~) Int32
    type AttrBaseTypeConstraint TextAttributesPixelsBelowLinesFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesPixelsBelowLinesFieldInfo = Int32
    type AttrLabel TextAttributesPixelsBelowLinesFieldInfo = "pixels_below_lines"
    type AttrOrigin TextAttributesPixelsBelowLinesFieldInfo = TextAttributes
    attrGet _ = getTextAttributesPixelsBelowLines
    attrSet _ = setTextAttributesPixelsBelowLines
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_pixelsBelowLines :: AttrLabelProxy "pixelsBelowLines"
textAttributes_pixelsBelowLines = AttrLabelProxy


getTextAttributesPixelsInsideWrap :: MonadIO m => TextAttributes -> m Int32
getTextAttributesPixelsInsideWrap s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 100) :: IO Int32
    return val

setTextAttributesPixelsInsideWrap :: MonadIO m => TextAttributes -> Int32 -> m ()
setTextAttributesPixelsInsideWrap s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 100) (val :: Int32)

data TextAttributesPixelsInsideWrapFieldInfo
instance AttrInfo TextAttributesPixelsInsideWrapFieldInfo where
    type AttrAllowedOps TextAttributesPixelsInsideWrapFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesPixelsInsideWrapFieldInfo = (~) Int32
    type AttrBaseTypeConstraint TextAttributesPixelsInsideWrapFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesPixelsInsideWrapFieldInfo = Int32
    type AttrLabel TextAttributesPixelsInsideWrapFieldInfo = "pixels_inside_wrap"
    type AttrOrigin TextAttributesPixelsInsideWrapFieldInfo = TextAttributes
    attrGet _ = getTextAttributesPixelsInsideWrap
    attrSet _ = setTextAttributesPixelsInsideWrap
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_pixelsInsideWrap :: AttrLabelProxy "pixelsInsideWrap"
textAttributes_pixelsInsideWrap = AttrLabelProxy


getTextAttributesTabs :: MonadIO m => TextAttributes -> m (Maybe Pango.TabArray.TabArray)
getTextAttributesTabs s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 104) :: IO (Ptr Pango.TabArray.TabArray)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newBoxed Pango.TabArray.TabArray) val'
        return val''
    return result

setTextAttributesTabs :: MonadIO m => TextAttributes -> Ptr Pango.TabArray.TabArray -> m ()
setTextAttributesTabs s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 104) (val :: Ptr Pango.TabArray.TabArray)

clearTextAttributesTabs :: MonadIO m => TextAttributes -> m ()
clearTextAttributesTabs s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 104) (FP.nullPtr :: Ptr Pango.TabArray.TabArray)

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

textAttributes_tabs :: AttrLabelProxy "tabs"
textAttributes_tabs = AttrLabelProxy


getTextAttributesWrapMode :: MonadIO m => TextAttributes -> m Gtk.Enums.WrapMode
getTextAttributesWrapMode s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 112) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

setTextAttributesWrapMode :: MonadIO m => TextAttributes -> Gtk.Enums.WrapMode -> m ()
setTextAttributesWrapMode s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 112) (val' :: CUInt)

data TextAttributesWrapModeFieldInfo
instance AttrInfo TextAttributesWrapModeFieldInfo where
    type AttrAllowedOps TextAttributesWrapModeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesWrapModeFieldInfo = (~) Gtk.Enums.WrapMode
    type AttrBaseTypeConstraint TextAttributesWrapModeFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesWrapModeFieldInfo = Gtk.Enums.WrapMode
    type AttrLabel TextAttributesWrapModeFieldInfo = "wrap_mode"
    type AttrOrigin TextAttributesWrapModeFieldInfo = TextAttributes
    attrGet _ = getTextAttributesWrapMode
    attrSet _ = setTextAttributesWrapMode
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_wrapMode :: AttrLabelProxy "wrapMode"
textAttributes_wrapMode = AttrLabelProxy


getTextAttributesLanguage :: MonadIO m => TextAttributes -> m (Maybe Pango.Language.Language)
getTextAttributesLanguage s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 120) :: IO (Ptr Pango.Language.Language)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newBoxed Pango.Language.Language) val'
        return val''
    return result

setTextAttributesLanguage :: MonadIO m => TextAttributes -> Ptr Pango.Language.Language -> m ()
setTextAttributesLanguage s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 120) (val :: Ptr Pango.Language.Language)

clearTextAttributesLanguage :: MonadIO m => TextAttributes -> m ()
clearTextAttributesLanguage s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 120) (FP.nullPtr :: Ptr Pango.Language.Language)

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

textAttributes_language :: AttrLabelProxy "language"
textAttributes_language = AttrLabelProxy


getTextAttributesInvisible :: MonadIO m => TextAttributes -> m Word32
getTextAttributesInvisible s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 136) :: IO Word32
    return val

setTextAttributesInvisible :: MonadIO m => TextAttributes -> Word32 -> m ()
setTextAttributesInvisible s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 136) (val :: Word32)

data TextAttributesInvisibleFieldInfo
instance AttrInfo TextAttributesInvisibleFieldInfo where
    type AttrAllowedOps TextAttributesInvisibleFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesInvisibleFieldInfo = (~) Word32
    type AttrBaseTypeConstraint TextAttributesInvisibleFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesInvisibleFieldInfo = Word32
    type AttrLabel TextAttributesInvisibleFieldInfo = "invisible"
    type AttrOrigin TextAttributesInvisibleFieldInfo = TextAttributes
    attrGet _ = getTextAttributesInvisible
    attrSet _ = setTextAttributesInvisible
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_invisible :: AttrLabelProxy "invisible"
textAttributes_invisible = AttrLabelProxy


getTextAttributesBgFullHeight :: MonadIO m => TextAttributes -> m Word32
getTextAttributesBgFullHeight s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 140) :: IO Word32
    return val

setTextAttributesBgFullHeight :: MonadIO m => TextAttributes -> Word32 -> m ()
setTextAttributesBgFullHeight s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 140) (val :: Word32)

data TextAttributesBgFullHeightFieldInfo
instance AttrInfo TextAttributesBgFullHeightFieldInfo where
    type AttrAllowedOps TextAttributesBgFullHeightFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesBgFullHeightFieldInfo = (~) Word32
    type AttrBaseTypeConstraint TextAttributesBgFullHeightFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesBgFullHeightFieldInfo = Word32
    type AttrLabel TextAttributesBgFullHeightFieldInfo = "bg_full_height"
    type AttrOrigin TextAttributesBgFullHeightFieldInfo = TextAttributes
    attrGet _ = getTextAttributesBgFullHeight
    attrSet _ = setTextAttributesBgFullHeight
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_bgFullHeight :: AttrLabelProxy "bgFullHeight"
textAttributes_bgFullHeight = AttrLabelProxy


getTextAttributesEditable :: MonadIO m => TextAttributes -> m Word32
getTextAttributesEditable s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 144) :: IO Word32
    return val

setTextAttributesEditable :: MonadIO m => TextAttributes -> Word32 -> m ()
setTextAttributesEditable s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 144) (val :: Word32)

data TextAttributesEditableFieldInfo
instance AttrInfo TextAttributesEditableFieldInfo where
    type AttrAllowedOps TextAttributesEditableFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesEditableFieldInfo = (~) Word32
    type AttrBaseTypeConstraint TextAttributesEditableFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesEditableFieldInfo = Word32
    type AttrLabel TextAttributesEditableFieldInfo = "editable"
    type AttrOrigin TextAttributesEditableFieldInfo = TextAttributes
    attrGet _ = getTextAttributesEditable
    attrSet _ = setTextAttributesEditable
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_editable :: AttrLabelProxy "editable"
textAttributes_editable = AttrLabelProxy


getTextAttributesNoFallback :: MonadIO m => TextAttributes -> m Word32
getTextAttributesNoFallback s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 148) :: IO Word32
    return val

setTextAttributesNoFallback :: MonadIO m => TextAttributes -> Word32 -> m ()
setTextAttributesNoFallback s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 148) (val :: Word32)

data TextAttributesNoFallbackFieldInfo
instance AttrInfo TextAttributesNoFallbackFieldInfo where
    type AttrAllowedOps TextAttributesNoFallbackFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesNoFallbackFieldInfo = (~) Word32
    type AttrBaseTypeConstraint TextAttributesNoFallbackFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesNoFallbackFieldInfo = Word32
    type AttrLabel TextAttributesNoFallbackFieldInfo = "no_fallback"
    type AttrOrigin TextAttributesNoFallbackFieldInfo = TextAttributes
    attrGet _ = getTextAttributesNoFallback
    attrSet _ = setTextAttributesNoFallback
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_noFallback :: AttrLabelProxy "noFallback"
textAttributes_noFallback = AttrLabelProxy


getTextAttributesLetterSpacing :: MonadIO m => TextAttributes -> m Int32
getTextAttributesLetterSpacing s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 160) :: IO Int32
    return val

setTextAttributesLetterSpacing :: MonadIO m => TextAttributes -> Int32 -> m ()
setTextAttributesLetterSpacing s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 160) (val :: Int32)

data TextAttributesLetterSpacingFieldInfo
instance AttrInfo TextAttributesLetterSpacingFieldInfo where
    type AttrAllowedOps TextAttributesLetterSpacingFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint TextAttributesLetterSpacingFieldInfo = (~) Int32
    type AttrBaseTypeConstraint TextAttributesLetterSpacingFieldInfo = (~) TextAttributes
    type AttrGetType TextAttributesLetterSpacingFieldInfo = Int32
    type AttrLabel TextAttributesLetterSpacingFieldInfo = "letter_spacing"
    type AttrOrigin TextAttributesLetterSpacingFieldInfo = TextAttributes
    attrGet _ = getTextAttributesLetterSpacing
    attrSet _ = setTextAttributesLetterSpacing
    attrConstruct = undefined
    attrClear _ = undefined

textAttributes_letterSpacing :: AttrLabelProxy "letterSpacing"
textAttributes_letterSpacing = AttrLabelProxy



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, *)])

-- 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 '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 'GI.Gtk.Structs.TextAttributes.TextAttributes',
    free with 'GI.Gtk.Structs.TextAttributes.textAttributesUnref'. -}
textAttributesNew  = liftIO $ do
    result <- gtk_text_attributes_new
    checkUnexpectedReturnNULL "textAttributesNew" result
    result' <- (wrapBoxed TextAttributes) result
    return result'

-- 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 'GI.Gtk.Structs.TextAttributes.TextAttributes'.
-}
textAttributesCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TextAttributes
    {- ^ /@src@/: a 'GI.Gtk.Structs.TextAttributes.TextAttributes' to be copied -}
    -> m TextAttributes
    {- ^ __Returns:__ a copy of /@src@/,
    free with 'GI.Gtk.Structs.TextAttributes.textAttributesUnref' -}
textAttributesCopy src = liftIO $ do
    src' <- unsafeManagedPtrGetPtr src
    result <- gtk_text_attributes_copy src'
    checkUnexpectedReturnNULL "textAttributesCopy" result
    result' <- (wrapBoxed TextAttributes) result
    touchManagedPtr src
    return result'

data TextAttributesCopyMethodInfo
instance (signature ~ (m TextAttributes), MonadIO m) => O.MethodInfo TextAttributesCopyMethodInfo TextAttributes signature where
    overloadedMethod _ = textAttributesCopy

-- 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 'GI.Gtk.Structs.TextAttributes.TextAttributes' -}
    -> TextAttributes
    {- ^ /@dest@/: another 'GI.Gtk.Structs.TextAttributes.TextAttributes' -}
    -> m ()
textAttributesCopyValues src dest = liftIO $ do
    src' <- unsafeManagedPtrGetPtr src
    dest' <- unsafeManagedPtrGetPtr dest
    gtk_text_attributes_copy_values src' dest'
    touchManagedPtr src
    touchManagedPtr dest
    return ()

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

-- 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 'GI.Gtk.Structs.TextAttributes.TextAttributes' -}
    -> m TextAttributes
    {- ^ __Returns:__ the 'GI.Gtk.Structs.TextAttributes.TextAttributes' that were passed in -}
textAttributesRef values = liftIO $ do
    values' <- unsafeManagedPtrGetPtr values
    result <- gtk_text_attributes_ref values'
    checkUnexpectedReturnNULL "textAttributesRef" result
    result' <- (wrapBoxed TextAttributes) result
    touchManagedPtr values
    return result'

data TextAttributesRefMethodInfo
instance (signature ~ (m TextAttributes), MonadIO m) => O.MethodInfo TextAttributesRefMethodInfo TextAttributes signature where
    overloadedMethod _ = textAttributesRef

-- 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 'GI.Gtk.Structs.TextAttributes.TextAttributes' -}
    -> m ()
textAttributesUnref values = liftIO $ do
    values' <- unsafeManagedPtrGetPtr values
    gtk_text_attributes_unref values'
    touchManagedPtr values
    return ()

data TextAttributesUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo TextAttributesUnrefMethodInfo TextAttributes signature where
    overloadedMethod _ = textAttributesUnref

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) => O.IsLabelProxy t (TextAttributes -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveTextAttributesMethod t TextAttributes, O.MethodInfo info TextAttributes p) => O.IsLabel t (TextAttributes -> p) where
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif