{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Glyph extent values, measured in font units.
-- 
-- Note that /@height@/ is negative, in coordinate systems that grow up.

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

module GI.HarfBuzz.Structs.GlyphExtentsT
    ( 

-- * Exported types
    GlyphExtentsT(..)                       ,
    newZeroGlyphExtentsT                    ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveGlyphExtentsTMethod              ,
#endif



 -- * Properties


-- ** height #attr:height#
-- | Distance from the top extremum of the glyph to the bottom extremum.

    getGlyphExtentsTHeight                  ,
#if defined(ENABLE_OVERLOADING)
    glyphExtentsT_height                    ,
#endif
    setGlyphExtentsTHeight                  ,


-- ** width #attr:width#
-- | Distance from the left extremum of the glyph to the right extremum.

    getGlyphExtentsTWidth                   ,
#if defined(ENABLE_OVERLOADING)
    glyphExtentsT_width                     ,
#endif
    setGlyphExtentsTWidth                   ,


-- ** xBearing #attr:xBearing#
-- | Distance from the x-origin to the left extremum of the glyph.

    getGlyphExtentsTXBearing                ,
#if defined(ENABLE_OVERLOADING)
    glyphExtentsT_xBearing                  ,
#endif
    setGlyphExtentsTXBearing                ,


-- ** yBearing #attr:yBearing#
-- | Distance from the top extremum of the glyph to the y-origin.

    getGlyphExtentsTYBearing                ,
#if defined(ENABLE_OVERLOADING)
    glyphExtentsT_yBearing                  ,
#endif
    setGlyphExtentsTYBearing                ,




    ) where

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

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


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

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

instance BoxedPtr GlyphExtentsT where
    boxedPtrCopy :: GlyphExtentsT -> IO GlyphExtentsT
boxedPtrCopy = \GlyphExtentsT
p -> GlyphExtentsT
-> (Ptr GlyphExtentsT -> IO GlyphExtentsT) -> IO GlyphExtentsT
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr GlyphExtentsT
p (Int -> Ptr GlyphExtentsT -> IO (Ptr GlyphExtentsT)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
16 (Ptr GlyphExtentsT -> IO (Ptr GlyphExtentsT))
-> (Ptr GlyphExtentsT -> IO GlyphExtentsT)
-> Ptr GlyphExtentsT
-> IO GlyphExtentsT
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr GlyphExtentsT -> GlyphExtentsT)
-> Ptr GlyphExtentsT -> IO GlyphExtentsT
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr GlyphExtentsT -> GlyphExtentsT
GlyphExtentsT)
    boxedPtrFree :: GlyphExtentsT -> IO ()
boxedPtrFree = \GlyphExtentsT
x -> GlyphExtentsT -> (Ptr GlyphExtentsT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr GlyphExtentsT
x Ptr GlyphExtentsT -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr GlyphExtentsT where
    boxedPtrCalloc :: IO (Ptr GlyphExtentsT)
boxedPtrCalloc = Int -> IO (Ptr GlyphExtentsT)
forall a. Int -> IO (Ptr a)
callocBytes Int
16


-- | Construct a `GlyphExtentsT` struct initialized to zero.
newZeroGlyphExtentsT :: MonadIO m => m GlyphExtentsT
newZeroGlyphExtentsT :: forall (m :: * -> *). MonadIO m => m GlyphExtentsT
newZeroGlyphExtentsT = IO GlyphExtentsT -> m GlyphExtentsT
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GlyphExtentsT -> m GlyphExtentsT)
-> IO GlyphExtentsT -> m GlyphExtentsT
forall a b. (a -> b) -> a -> b
$ IO (Ptr GlyphExtentsT)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr GlyphExtentsT)
-> (Ptr GlyphExtentsT -> IO GlyphExtentsT) -> IO GlyphExtentsT
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr GlyphExtentsT -> GlyphExtentsT)
-> Ptr GlyphExtentsT -> IO GlyphExtentsT
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr GlyphExtentsT -> GlyphExtentsT
GlyphExtentsT

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


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

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

#if defined(ENABLE_OVERLOADING)
data GlyphExtentsTXBearingFieldInfo
instance AttrInfo GlyphExtentsTXBearingFieldInfo where
    type AttrBaseTypeConstraint GlyphExtentsTXBearingFieldInfo = (~) GlyphExtentsT
    type AttrAllowedOps GlyphExtentsTXBearingFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GlyphExtentsTXBearingFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GlyphExtentsTXBearingFieldInfo = (~)Int32
    type AttrTransferType GlyphExtentsTXBearingFieldInfo = Int32
    type AttrGetType GlyphExtentsTXBearingFieldInfo = Int32
    type AttrLabel GlyphExtentsTXBearingFieldInfo = "x_bearing"
    type AttrOrigin GlyphExtentsTXBearingFieldInfo = GlyphExtentsT
    attrGet = getGlyphExtentsTXBearing
    attrSet = setGlyphExtentsTXBearing
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.HarfBuzz.Structs.GlyphExtentsT.xBearing"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-harfbuzz-0.0.9/docs/GI-HarfBuzz-Structs-GlyphExtentsT.html#g:attr:xBearing"
        })

glyphExtentsT_xBearing :: AttrLabelProxy "xBearing"
glyphExtentsT_xBearing = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data GlyphExtentsTYBearingFieldInfo
instance AttrInfo GlyphExtentsTYBearingFieldInfo where
    type AttrBaseTypeConstraint GlyphExtentsTYBearingFieldInfo = (~) GlyphExtentsT
    type AttrAllowedOps GlyphExtentsTYBearingFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GlyphExtentsTYBearingFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GlyphExtentsTYBearingFieldInfo = (~)Int32
    type AttrTransferType GlyphExtentsTYBearingFieldInfo = Int32
    type AttrGetType GlyphExtentsTYBearingFieldInfo = Int32
    type AttrLabel GlyphExtentsTYBearingFieldInfo = "y_bearing"
    type AttrOrigin GlyphExtentsTYBearingFieldInfo = GlyphExtentsT
    attrGet = getGlyphExtentsTYBearing
    attrSet = setGlyphExtentsTYBearing
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.HarfBuzz.Structs.GlyphExtentsT.yBearing"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-harfbuzz-0.0.9/docs/GI-HarfBuzz-Structs-GlyphExtentsT.html#g:attr:yBearing"
        })

glyphExtentsT_yBearing :: AttrLabelProxy "yBearing"
glyphExtentsT_yBearing = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data GlyphExtentsTWidthFieldInfo
instance AttrInfo GlyphExtentsTWidthFieldInfo where
    type AttrBaseTypeConstraint GlyphExtentsTWidthFieldInfo = (~) GlyphExtentsT
    type AttrAllowedOps GlyphExtentsTWidthFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GlyphExtentsTWidthFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GlyphExtentsTWidthFieldInfo = (~)Int32
    type AttrTransferType GlyphExtentsTWidthFieldInfo = Int32
    type AttrGetType GlyphExtentsTWidthFieldInfo = Int32
    type AttrLabel GlyphExtentsTWidthFieldInfo = "width"
    type AttrOrigin GlyphExtentsTWidthFieldInfo = GlyphExtentsT
    attrGet = getGlyphExtentsTWidth
    attrSet = setGlyphExtentsTWidth
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.HarfBuzz.Structs.GlyphExtentsT.width"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-harfbuzz-0.0.9/docs/GI-HarfBuzz-Structs-GlyphExtentsT.html#g:attr:width"
        })

glyphExtentsT_width :: AttrLabelProxy "width"
glyphExtentsT_width = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data GlyphExtentsTHeightFieldInfo
instance AttrInfo GlyphExtentsTHeightFieldInfo where
    type AttrBaseTypeConstraint GlyphExtentsTHeightFieldInfo = (~) GlyphExtentsT
    type AttrAllowedOps GlyphExtentsTHeightFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GlyphExtentsTHeightFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GlyphExtentsTHeightFieldInfo = (~)Int32
    type AttrTransferType GlyphExtentsTHeightFieldInfo = Int32
    type AttrGetType GlyphExtentsTHeightFieldInfo = Int32
    type AttrLabel GlyphExtentsTHeightFieldInfo = "height"
    type AttrOrigin GlyphExtentsTHeightFieldInfo = GlyphExtentsT
    attrGet = getGlyphExtentsTHeight
    attrSet = setGlyphExtentsTHeight
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.HarfBuzz.Structs.GlyphExtentsT.height"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-harfbuzz-0.0.9/docs/GI-HarfBuzz-Structs-GlyphExtentsT.html#g:attr:height"
        })

glyphExtentsT_height :: AttrLabelProxy "height"
glyphExtentsT_height = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GlyphExtentsT
type instance O.AttributeList GlyphExtentsT = GlyphExtentsTAttributeList
type GlyphExtentsTAttributeList = ('[ '("xBearing", GlyphExtentsTXBearingFieldInfo), '("yBearing", GlyphExtentsTYBearingFieldInfo), '("width", GlyphExtentsTWidthFieldInfo), '("height", GlyphExtentsTHeightFieldInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveGlyphExtentsTMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveGlyphExtentsTMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveGlyphExtentsTMethod t GlyphExtentsT, O.OverloadedMethod info GlyphExtentsT p, R.HasField t GlyphExtentsT p) => R.HasField t GlyphExtentsT p where
    getField = O.overloadedMethod @info

#endif

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

#endif