{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Use t'GI.HarfBuzz.Structs.OtVarAxisInfoT.OtVarAxisInfoT' instead.
-- 
-- /Since: 1.4.2/

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

module GI.HarfBuzz.Structs.OtVarAxisT
    ( 

-- * Exported types
    OtVarAxisT(..)                          ,
    newZeroOtVarAxisT                       ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveOtVarAxisTMethod                 ,
#endif



 -- * Properties


-- ** defaultValue #attr:defaultValue#
-- | default value of the axis

    getOtVarAxisTDefaultValue               ,
#if defined(ENABLE_OVERLOADING)
    otVarAxisT_defaultValue                 ,
#endif
    setOtVarAxisTDefaultValue               ,


-- ** maxValue #attr:maxValue#
-- | maximum value of the axis

    getOtVarAxisTMaxValue                   ,
#if defined(ENABLE_OVERLOADING)
    otVarAxisT_maxValue                     ,
#endif
    setOtVarAxisTMaxValue                   ,


-- ** minValue #attr:minValue#
-- | minimum value of the axis

    getOtVarAxisTMinValue                   ,
#if defined(ENABLE_OVERLOADING)
    otVarAxisT_minValue                     ,
#endif
    setOtVarAxisTMinValue                   ,


-- ** nameId #attr:nameId#
-- | axis name identifier

    getOtVarAxisTNameId                     ,
#if defined(ENABLE_OVERLOADING)
    otVarAxisT_nameId                       ,
#endif
    setOtVarAxisTNameId                     ,


-- ** tag #attr:tag#
-- | axis tag

    getOtVarAxisTTag                        ,
#if defined(ENABLE_OVERLOADING)
    otVarAxisT_tag                          ,
#endif
    setOtVarAxisTTag                        ,




    ) 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 OtVarAxisT = OtVarAxisT (SP.ManagedPtr OtVarAxisT)
    deriving (OtVarAxisT -> OtVarAxisT -> Bool
(OtVarAxisT -> OtVarAxisT -> Bool)
-> (OtVarAxisT -> OtVarAxisT -> Bool) -> Eq OtVarAxisT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OtVarAxisT -> OtVarAxisT -> Bool
== :: OtVarAxisT -> OtVarAxisT -> Bool
$c/= :: OtVarAxisT -> OtVarAxisT -> Bool
/= :: OtVarAxisT -> OtVarAxisT -> Bool
Eq)

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

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


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

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


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

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

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

otVarAxisT_tag :: AttrLabelProxy "tag"
otVarAxisT_tag = AttrLabelProxy

#endif


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

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

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

otVarAxisT_nameId :: AttrLabelProxy "nameId"
otVarAxisT_nameId = AttrLabelProxy

#endif


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

-- | Set the value of the “@min_value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' otVarAxisT [ #minValue 'Data.GI.Base.Attributes.:=' value ]
-- @
setOtVarAxisTMinValue :: MonadIO m => OtVarAxisT -> Float -> m ()
setOtVarAxisTMinValue :: forall (m :: * -> *). MonadIO m => OtVarAxisT -> Float -> m ()
setOtVarAxisTMinValue OtVarAxisT
s Float
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
$ OtVarAxisT -> (Ptr OtVarAxisT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OtVarAxisT
s ((Ptr OtVarAxisT -> IO ()) -> IO ())
-> (Ptr OtVarAxisT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr OtVarAxisT
ptr -> do
    let val' :: CFloat
val' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
val
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OtVarAxisT
ptr Ptr OtVarAxisT -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CFloat
val' :: CFloat)

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

otVarAxisT_minValue :: AttrLabelProxy "minValue"
otVarAxisT_minValue = AttrLabelProxy

#endif


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

-- | Set the value of the “@default_value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' otVarAxisT [ #defaultValue 'Data.GI.Base.Attributes.:=' value ]
-- @
setOtVarAxisTDefaultValue :: MonadIO m => OtVarAxisT -> Float -> m ()
setOtVarAxisTDefaultValue :: forall (m :: * -> *). MonadIO m => OtVarAxisT -> Float -> m ()
setOtVarAxisTDefaultValue OtVarAxisT
s Float
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
$ OtVarAxisT -> (Ptr OtVarAxisT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OtVarAxisT
s ((Ptr OtVarAxisT -> IO ()) -> IO ())
-> (Ptr OtVarAxisT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr OtVarAxisT
ptr -> do
    let val' :: CFloat
val' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
val
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OtVarAxisT
ptr Ptr OtVarAxisT -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) (CFloat
val' :: CFloat)

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

otVarAxisT_defaultValue :: AttrLabelProxy "defaultValue"
otVarAxisT_defaultValue = AttrLabelProxy

#endif


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

-- | Set the value of the “@max_value@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' otVarAxisT [ #maxValue 'Data.GI.Base.Attributes.:=' value ]
-- @
setOtVarAxisTMaxValue :: MonadIO m => OtVarAxisT -> Float -> m ()
setOtVarAxisTMaxValue :: forall (m :: * -> *). MonadIO m => OtVarAxisT -> Float -> m ()
setOtVarAxisTMaxValue OtVarAxisT
s Float
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
$ OtVarAxisT -> (Ptr OtVarAxisT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OtVarAxisT
s ((Ptr OtVarAxisT -> IO ()) -> IO ())
-> (Ptr OtVarAxisT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr OtVarAxisT
ptr -> do
    let val' :: CFloat
val' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
val
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OtVarAxisT
ptr Ptr OtVarAxisT -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (CFloat
val' :: CFloat)

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

otVarAxisT_maxValue :: AttrLabelProxy "maxValue"
otVarAxisT_maxValue = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList OtVarAxisT
type instance O.AttributeList OtVarAxisT = OtVarAxisTAttributeList
type OtVarAxisTAttributeList = ('[ '("tag", OtVarAxisTTagFieldInfo), '("nameId", OtVarAxisTNameIdFieldInfo), '("minValue", OtVarAxisTMinValueFieldInfo), '("defaultValue", OtVarAxisTDefaultValueFieldInfo), '("maxValue", OtVarAxisTMaxValueFieldInfo)] :: [(Symbol, DK.Type)])
#endif

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

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

#endif

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

#endif