{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.HarfBuzz.Structs.AatLayoutFeatureSelectorInfoT
(
AatLayoutFeatureSelectorInfoT(..) ,
newZeroAatLayoutFeatureSelectorInfoT ,
#if defined(ENABLE_OVERLOADING)
ResolveAatLayoutFeatureSelectorInfoTMethod,
#endif
#if defined(ENABLE_OVERLOADING)
aatLayoutFeatureSelectorInfoT_disable ,
#endif
getAatLayoutFeatureSelectorInfoTDisable ,
setAatLayoutFeatureSelectorInfoTDisable ,
#if defined(ENABLE_OVERLOADING)
aatLayoutFeatureSelectorInfoT_enable ,
#endif
getAatLayoutFeatureSelectorInfoTEnable ,
setAatLayoutFeatureSelectorInfoTEnable ,
#if defined(ENABLE_OVERLOADING)
aatLayoutFeatureSelectorInfoT_nameId ,
#endif
getAatLayoutFeatureSelectorInfoTNameId ,
setAatLayoutFeatureSelectorInfoTNameId ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import {-# SOURCE #-} qualified GI.HarfBuzz.Enums as HarfBuzz.Enums
newtype AatLayoutFeatureSelectorInfoT = AatLayoutFeatureSelectorInfoT (SP.ManagedPtr AatLayoutFeatureSelectorInfoT)
deriving (AatLayoutFeatureSelectorInfoT
-> AatLayoutFeatureSelectorInfoT -> Bool
(AatLayoutFeatureSelectorInfoT
-> AatLayoutFeatureSelectorInfoT -> Bool)
-> (AatLayoutFeatureSelectorInfoT
-> AatLayoutFeatureSelectorInfoT -> Bool)
-> Eq AatLayoutFeatureSelectorInfoT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AatLayoutFeatureSelectorInfoT
-> AatLayoutFeatureSelectorInfoT -> Bool
$c/= :: AatLayoutFeatureSelectorInfoT
-> AatLayoutFeatureSelectorInfoT -> Bool
== :: AatLayoutFeatureSelectorInfoT
-> AatLayoutFeatureSelectorInfoT -> Bool
$c== :: AatLayoutFeatureSelectorInfoT
-> AatLayoutFeatureSelectorInfoT -> Bool
Eq)
instance SP.ManagedPtrNewtype AatLayoutFeatureSelectorInfoT where
toManagedPtr :: AatLayoutFeatureSelectorInfoT
-> ManagedPtr AatLayoutFeatureSelectorInfoT
toManagedPtr (AatLayoutFeatureSelectorInfoT ManagedPtr AatLayoutFeatureSelectorInfoT
p) = ManagedPtr AatLayoutFeatureSelectorInfoT
p
instance BoxedPtr AatLayoutFeatureSelectorInfoT where
boxedPtrCopy :: AatLayoutFeatureSelectorInfoT -> IO AatLayoutFeatureSelectorInfoT
boxedPtrCopy = \AatLayoutFeatureSelectorInfoT
p -> AatLayoutFeatureSelectorInfoT
-> (Ptr AatLayoutFeatureSelectorInfoT
-> IO AatLayoutFeatureSelectorInfoT)
-> IO AatLayoutFeatureSelectorInfoT
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AatLayoutFeatureSelectorInfoT
p (Int
-> Ptr AatLayoutFeatureSelectorInfoT
-> IO (Ptr AatLayoutFeatureSelectorInfoT)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
16 (Ptr AatLayoutFeatureSelectorInfoT
-> IO (Ptr AatLayoutFeatureSelectorInfoT))
-> (Ptr AatLayoutFeatureSelectorInfoT
-> IO AatLayoutFeatureSelectorInfoT)
-> Ptr AatLayoutFeatureSelectorInfoT
-> IO AatLayoutFeatureSelectorInfoT
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr AatLayoutFeatureSelectorInfoT
-> AatLayoutFeatureSelectorInfoT)
-> Ptr AatLayoutFeatureSelectorInfoT
-> IO AatLayoutFeatureSelectorInfoT
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr AatLayoutFeatureSelectorInfoT
-> AatLayoutFeatureSelectorInfoT
AatLayoutFeatureSelectorInfoT)
boxedPtrFree :: AatLayoutFeatureSelectorInfoT -> IO ()
boxedPtrFree = \AatLayoutFeatureSelectorInfoT
x -> AatLayoutFeatureSelectorInfoT
-> (Ptr AatLayoutFeatureSelectorInfoT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr AatLayoutFeatureSelectorInfoT
x Ptr AatLayoutFeatureSelectorInfoT -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr AatLayoutFeatureSelectorInfoT where
boxedPtrCalloc :: IO (Ptr AatLayoutFeatureSelectorInfoT)
boxedPtrCalloc = Int -> IO (Ptr AatLayoutFeatureSelectorInfoT)
forall a. Int -> IO (Ptr a)
callocBytes Int
16
newZeroAatLayoutFeatureSelectorInfoT :: MonadIO m => m AatLayoutFeatureSelectorInfoT
newZeroAatLayoutFeatureSelectorInfoT :: forall (m :: * -> *). MonadIO m => m AatLayoutFeatureSelectorInfoT
newZeroAatLayoutFeatureSelectorInfoT = IO AatLayoutFeatureSelectorInfoT -> m AatLayoutFeatureSelectorInfoT
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AatLayoutFeatureSelectorInfoT
-> m AatLayoutFeatureSelectorInfoT)
-> IO AatLayoutFeatureSelectorInfoT
-> m AatLayoutFeatureSelectorInfoT
forall a b. (a -> b) -> a -> b
$ IO (Ptr AatLayoutFeatureSelectorInfoT)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr AatLayoutFeatureSelectorInfoT)
-> (Ptr AatLayoutFeatureSelectorInfoT
-> IO AatLayoutFeatureSelectorInfoT)
-> IO AatLayoutFeatureSelectorInfoT
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr AatLayoutFeatureSelectorInfoT
-> AatLayoutFeatureSelectorInfoT)
-> Ptr AatLayoutFeatureSelectorInfoT
-> IO AatLayoutFeatureSelectorInfoT
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr AatLayoutFeatureSelectorInfoT
-> AatLayoutFeatureSelectorInfoT
AatLayoutFeatureSelectorInfoT
instance tag ~ 'AttrSet => Constructible AatLayoutFeatureSelectorInfoT tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr AatLayoutFeatureSelectorInfoT
-> AatLayoutFeatureSelectorInfoT)
-> [AttrOp AatLayoutFeatureSelectorInfoT tag]
-> m AatLayoutFeatureSelectorInfoT
new ManagedPtr AatLayoutFeatureSelectorInfoT
-> AatLayoutFeatureSelectorInfoT
_ [AttrOp AatLayoutFeatureSelectorInfoT tag]
attrs = do
AatLayoutFeatureSelectorInfoT
o <- m AatLayoutFeatureSelectorInfoT
forall (m :: * -> *). MonadIO m => m AatLayoutFeatureSelectorInfoT
newZeroAatLayoutFeatureSelectorInfoT
AatLayoutFeatureSelectorInfoT
-> [AttrOp AatLayoutFeatureSelectorInfoT 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set AatLayoutFeatureSelectorInfoT
o [AttrOp AatLayoutFeatureSelectorInfoT tag]
[AttrOp AatLayoutFeatureSelectorInfoT 'AttrSet]
attrs
AatLayoutFeatureSelectorInfoT -> m AatLayoutFeatureSelectorInfoT
forall (m :: * -> *) a. Monad m => a -> m a
return AatLayoutFeatureSelectorInfoT
o
getAatLayoutFeatureSelectorInfoTNameId :: MonadIO m => AatLayoutFeatureSelectorInfoT -> m Word32
getAatLayoutFeatureSelectorInfoTNameId :: forall (m :: * -> *).
MonadIO m =>
AatLayoutFeatureSelectorInfoT -> m Word32
getAatLayoutFeatureSelectorInfoTNameId AatLayoutFeatureSelectorInfoT
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
$ AatLayoutFeatureSelectorInfoT
-> (Ptr AatLayoutFeatureSelectorInfoT -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AatLayoutFeatureSelectorInfoT
s ((Ptr AatLayoutFeatureSelectorInfoT -> IO Word32) -> IO Word32)
-> (Ptr AatLayoutFeatureSelectorInfoT -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr AatLayoutFeatureSelectorInfoT
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr AatLayoutFeatureSelectorInfoT
ptr Ptr AatLayoutFeatureSelectorInfoT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setAatLayoutFeatureSelectorInfoTNameId :: MonadIO m => AatLayoutFeatureSelectorInfoT -> Word32 -> m ()
setAatLayoutFeatureSelectorInfoTNameId :: forall (m :: * -> *).
MonadIO m =>
AatLayoutFeatureSelectorInfoT -> Word32 -> m ()
setAatLayoutFeatureSelectorInfoTNameId AatLayoutFeatureSelectorInfoT
s 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
$ AatLayoutFeatureSelectorInfoT
-> (Ptr AatLayoutFeatureSelectorInfoT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AatLayoutFeatureSelectorInfoT
s ((Ptr AatLayoutFeatureSelectorInfoT -> IO ()) -> IO ())
-> (Ptr AatLayoutFeatureSelectorInfoT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AatLayoutFeatureSelectorInfoT
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AatLayoutFeatureSelectorInfoT
ptr Ptr AatLayoutFeatureSelectorInfoT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data AatLayoutFeatureSelectorInfoTNameIdFieldInfo
instance AttrInfo AatLayoutFeatureSelectorInfoTNameIdFieldInfo where
type AttrBaseTypeConstraint AatLayoutFeatureSelectorInfoTNameIdFieldInfo = (~) AatLayoutFeatureSelectorInfoT
type AttrAllowedOps AatLayoutFeatureSelectorInfoTNameIdFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint AatLayoutFeatureSelectorInfoTNameIdFieldInfo = (~) Word32
type AttrTransferTypeConstraint AatLayoutFeatureSelectorInfoTNameIdFieldInfo = (~)Word32
type AttrTransferType AatLayoutFeatureSelectorInfoTNameIdFieldInfo = Word32
type AttrGetType AatLayoutFeatureSelectorInfoTNameIdFieldInfo = Word32
type AttrLabel AatLayoutFeatureSelectorInfoTNameIdFieldInfo = "name_id"
type AttrOrigin AatLayoutFeatureSelectorInfoTNameIdFieldInfo = AatLayoutFeatureSelectorInfoT
attrGet = getAatLayoutFeatureSelectorInfoTNameId
attrSet = setAatLayoutFeatureSelectorInfoTNameId
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.HarfBuzz.Structs.AatLayoutFeatureSelectorInfoT.nameId"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-harfbuzz-0.0.5/docs/GI-HarfBuzz-Structs-AatLayoutFeatureSelectorInfoT.html#g:attr:nameId"
})
aatLayoutFeatureSelectorInfoT_nameId :: AttrLabelProxy "nameId"
aatLayoutFeatureSelectorInfoT_nameId = AttrLabelProxy
#endif
getAatLayoutFeatureSelectorInfoTEnable :: MonadIO m => AatLayoutFeatureSelectorInfoT -> m HarfBuzz.Enums.AatLayoutFeatureSelectorT
getAatLayoutFeatureSelectorInfoTEnable :: forall (m :: * -> *).
MonadIO m =>
AatLayoutFeatureSelectorInfoT -> m AatLayoutFeatureSelectorT
getAatLayoutFeatureSelectorInfoTEnable AatLayoutFeatureSelectorInfoT
s = IO AatLayoutFeatureSelectorT -> m AatLayoutFeatureSelectorT
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AatLayoutFeatureSelectorT -> m AatLayoutFeatureSelectorT)
-> IO AatLayoutFeatureSelectorT -> m AatLayoutFeatureSelectorT
forall a b. (a -> b) -> a -> b
$ AatLayoutFeatureSelectorInfoT
-> (Ptr AatLayoutFeatureSelectorInfoT
-> IO AatLayoutFeatureSelectorT)
-> IO AatLayoutFeatureSelectorT
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AatLayoutFeatureSelectorInfoT
s ((Ptr AatLayoutFeatureSelectorInfoT
-> IO AatLayoutFeatureSelectorT)
-> IO AatLayoutFeatureSelectorT)
-> (Ptr AatLayoutFeatureSelectorInfoT
-> IO AatLayoutFeatureSelectorT)
-> IO AatLayoutFeatureSelectorT
forall a b. (a -> b) -> a -> b
$ \Ptr AatLayoutFeatureSelectorInfoT
ptr -> do
CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr AatLayoutFeatureSelectorInfoT
ptr Ptr AatLayoutFeatureSelectorInfoT -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) :: IO CUInt
let val' :: AatLayoutFeatureSelectorT
val' = (Int -> AatLayoutFeatureSelectorT
forall a. Enum a => Int -> a
toEnum (Int -> AatLayoutFeatureSelectorT)
-> (CUInt -> Int) -> CUInt -> AatLayoutFeatureSelectorT
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
AatLayoutFeatureSelectorT -> IO AatLayoutFeatureSelectorT
forall (m :: * -> *) a. Monad m => a -> m a
return AatLayoutFeatureSelectorT
val'
setAatLayoutFeatureSelectorInfoTEnable :: MonadIO m => AatLayoutFeatureSelectorInfoT -> HarfBuzz.Enums.AatLayoutFeatureSelectorT -> m ()
setAatLayoutFeatureSelectorInfoTEnable :: forall (m :: * -> *).
MonadIO m =>
AatLayoutFeatureSelectorInfoT -> AatLayoutFeatureSelectorT -> m ()
setAatLayoutFeatureSelectorInfoTEnable AatLayoutFeatureSelectorInfoT
s AatLayoutFeatureSelectorT
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ AatLayoutFeatureSelectorInfoT
-> (Ptr AatLayoutFeatureSelectorInfoT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AatLayoutFeatureSelectorInfoT
s ((Ptr AatLayoutFeatureSelectorInfoT -> IO ()) -> IO ())
-> (Ptr AatLayoutFeatureSelectorInfoT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AatLayoutFeatureSelectorInfoT
ptr -> do
let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (AatLayoutFeatureSelectorT -> Int)
-> AatLayoutFeatureSelectorT
-> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AatLayoutFeatureSelectorT -> Int
forall a. Enum a => a -> Int
fromEnum) AatLayoutFeatureSelectorT
val
Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AatLayoutFeatureSelectorInfoT
ptr Ptr AatLayoutFeatureSelectorInfoT -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) (CUInt
val' :: CUInt)
#if defined(ENABLE_OVERLOADING)
data AatLayoutFeatureSelectorInfoTEnableFieldInfo
instance AttrInfo AatLayoutFeatureSelectorInfoTEnableFieldInfo where
type AttrBaseTypeConstraint AatLayoutFeatureSelectorInfoTEnableFieldInfo = (~) AatLayoutFeatureSelectorInfoT
type AttrAllowedOps AatLayoutFeatureSelectorInfoTEnableFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint AatLayoutFeatureSelectorInfoTEnableFieldInfo = (~) HarfBuzz.Enums.AatLayoutFeatureSelectorT
type AttrTransferTypeConstraint AatLayoutFeatureSelectorInfoTEnableFieldInfo = (~)HarfBuzz.Enums.AatLayoutFeatureSelectorT
type AttrTransferType AatLayoutFeatureSelectorInfoTEnableFieldInfo = HarfBuzz.Enums.AatLayoutFeatureSelectorT
type AttrGetType AatLayoutFeatureSelectorInfoTEnableFieldInfo = HarfBuzz.Enums.AatLayoutFeatureSelectorT
type AttrLabel AatLayoutFeatureSelectorInfoTEnableFieldInfo = "enable"
type AttrOrigin AatLayoutFeatureSelectorInfoTEnableFieldInfo = AatLayoutFeatureSelectorInfoT
attrGet = getAatLayoutFeatureSelectorInfoTEnable
attrSet = setAatLayoutFeatureSelectorInfoTEnable
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.HarfBuzz.Structs.AatLayoutFeatureSelectorInfoT.enable"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-harfbuzz-0.0.5/docs/GI-HarfBuzz-Structs-AatLayoutFeatureSelectorInfoT.html#g:attr:enable"
})
aatLayoutFeatureSelectorInfoT_enable :: AttrLabelProxy "enable"
aatLayoutFeatureSelectorInfoT_enable = AttrLabelProxy
#endif
getAatLayoutFeatureSelectorInfoTDisable :: MonadIO m => AatLayoutFeatureSelectorInfoT -> m HarfBuzz.Enums.AatLayoutFeatureSelectorT
getAatLayoutFeatureSelectorInfoTDisable :: forall (m :: * -> *).
MonadIO m =>
AatLayoutFeatureSelectorInfoT -> m AatLayoutFeatureSelectorT
getAatLayoutFeatureSelectorInfoTDisable AatLayoutFeatureSelectorInfoT
s = IO AatLayoutFeatureSelectorT -> m AatLayoutFeatureSelectorT
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AatLayoutFeatureSelectorT -> m AatLayoutFeatureSelectorT)
-> IO AatLayoutFeatureSelectorT -> m AatLayoutFeatureSelectorT
forall a b. (a -> b) -> a -> b
$ AatLayoutFeatureSelectorInfoT
-> (Ptr AatLayoutFeatureSelectorInfoT
-> IO AatLayoutFeatureSelectorT)
-> IO AatLayoutFeatureSelectorT
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AatLayoutFeatureSelectorInfoT
s ((Ptr AatLayoutFeatureSelectorInfoT
-> IO AatLayoutFeatureSelectorT)
-> IO AatLayoutFeatureSelectorT)
-> (Ptr AatLayoutFeatureSelectorInfoT
-> IO AatLayoutFeatureSelectorT)
-> IO AatLayoutFeatureSelectorT
forall a b. (a -> b) -> a -> b
$ \Ptr AatLayoutFeatureSelectorInfoT
ptr -> do
CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr AatLayoutFeatureSelectorInfoT
ptr Ptr AatLayoutFeatureSelectorInfoT -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO CUInt
let val' :: AatLayoutFeatureSelectorT
val' = (Int -> AatLayoutFeatureSelectorT
forall a. Enum a => Int -> a
toEnum (Int -> AatLayoutFeatureSelectorT)
-> (CUInt -> Int) -> CUInt -> AatLayoutFeatureSelectorT
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
AatLayoutFeatureSelectorT -> IO AatLayoutFeatureSelectorT
forall (m :: * -> *) a. Monad m => a -> m a
return AatLayoutFeatureSelectorT
val'
setAatLayoutFeatureSelectorInfoTDisable :: MonadIO m => AatLayoutFeatureSelectorInfoT -> HarfBuzz.Enums.AatLayoutFeatureSelectorT -> m ()
setAatLayoutFeatureSelectorInfoTDisable :: forall (m :: * -> *).
MonadIO m =>
AatLayoutFeatureSelectorInfoT -> AatLayoutFeatureSelectorT -> m ()
setAatLayoutFeatureSelectorInfoTDisable AatLayoutFeatureSelectorInfoT
s AatLayoutFeatureSelectorT
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ AatLayoutFeatureSelectorInfoT
-> (Ptr AatLayoutFeatureSelectorInfoT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AatLayoutFeatureSelectorInfoT
s ((Ptr AatLayoutFeatureSelectorInfoT -> IO ()) -> IO ())
-> (Ptr AatLayoutFeatureSelectorInfoT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AatLayoutFeatureSelectorInfoT
ptr -> do
let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (AatLayoutFeatureSelectorT -> Int)
-> AatLayoutFeatureSelectorT
-> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AatLayoutFeatureSelectorT -> Int
forall a. Enum a => a -> Int
fromEnum) AatLayoutFeatureSelectorT
val
Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AatLayoutFeatureSelectorInfoT
ptr Ptr AatLayoutFeatureSelectorInfoT -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CUInt
val' :: CUInt)
#if defined(ENABLE_OVERLOADING)
data AatLayoutFeatureSelectorInfoTDisableFieldInfo
instance AttrInfo AatLayoutFeatureSelectorInfoTDisableFieldInfo where
type AttrBaseTypeConstraint AatLayoutFeatureSelectorInfoTDisableFieldInfo = (~) AatLayoutFeatureSelectorInfoT
type AttrAllowedOps AatLayoutFeatureSelectorInfoTDisableFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint AatLayoutFeatureSelectorInfoTDisableFieldInfo = (~) HarfBuzz.Enums.AatLayoutFeatureSelectorT
type AttrTransferTypeConstraint AatLayoutFeatureSelectorInfoTDisableFieldInfo = (~)HarfBuzz.Enums.AatLayoutFeatureSelectorT
type AttrTransferType AatLayoutFeatureSelectorInfoTDisableFieldInfo = HarfBuzz.Enums.AatLayoutFeatureSelectorT
type AttrGetType AatLayoutFeatureSelectorInfoTDisableFieldInfo = HarfBuzz.Enums.AatLayoutFeatureSelectorT
type AttrLabel AatLayoutFeatureSelectorInfoTDisableFieldInfo = "disable"
type AttrOrigin AatLayoutFeatureSelectorInfoTDisableFieldInfo = AatLayoutFeatureSelectorInfoT
attrGet = getAatLayoutFeatureSelectorInfoTDisable
attrSet = setAatLayoutFeatureSelectorInfoTDisable
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.HarfBuzz.Structs.AatLayoutFeatureSelectorInfoT.disable"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-harfbuzz-0.0.5/docs/GI-HarfBuzz-Structs-AatLayoutFeatureSelectorInfoT.html#g:attr:disable"
})
aatLayoutFeatureSelectorInfoT_disable :: AttrLabelProxy "disable"
aatLayoutFeatureSelectorInfoT_disable = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AatLayoutFeatureSelectorInfoT
type instance O.AttributeList AatLayoutFeatureSelectorInfoT = AatLayoutFeatureSelectorInfoTAttributeList
type AatLayoutFeatureSelectorInfoTAttributeList = ('[ '("nameId", AatLayoutFeatureSelectorInfoTNameIdFieldInfo), '("enable", AatLayoutFeatureSelectorInfoTEnableFieldInfo), '("disable", AatLayoutFeatureSelectorInfoTDisableFieldInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveAatLayoutFeatureSelectorInfoTMethod (t :: Symbol) (o :: *) :: * where
ResolveAatLayoutFeatureSelectorInfoTMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveAatLayoutFeatureSelectorInfoTMethod t AatLayoutFeatureSelectorInfoT, O.OverloadedMethod info AatLayoutFeatureSelectorInfoT p) => OL.IsLabel t (AatLayoutFeatureSelectorInfoT -> 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 ~ ResolveAatLayoutFeatureSelectorInfoTMethod t AatLayoutFeatureSelectorInfoT, O.OverloadedMethod info AatLayoutFeatureSelectorInfoT p, R.HasField t AatLayoutFeatureSelectorInfoT p) => R.HasField t AatLayoutFeatureSelectorInfoT p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveAatLayoutFeatureSelectorInfoTMethod t AatLayoutFeatureSelectorInfoT, O.OverloadedMethodInfo info AatLayoutFeatureSelectorInfoT) => OL.IsLabel t (O.MethodProxy info AatLayoutFeatureSelectorInfoT) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif