{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.HarfBuzz.Structs.OtMathGlyphPartT
(
OtMathGlyphPartT(..) ,
newZeroOtMathGlyphPartT ,
#if defined(ENABLE_OVERLOADING)
ResolveOtMathGlyphPartTMethod ,
#endif
getOtMathGlyphPartTEndConnectorLength ,
#if defined(ENABLE_OVERLOADING)
otMathGlyphPartT_endConnectorLength ,
#endif
setOtMathGlyphPartTEndConnectorLength ,
getOtMathGlyphPartTFlags ,
#if defined(ENABLE_OVERLOADING)
otMathGlyphPartT_flags ,
#endif
setOtMathGlyphPartTFlags ,
getOtMathGlyphPartTFullAdvance ,
#if defined(ENABLE_OVERLOADING)
otMathGlyphPartT_fullAdvance ,
#endif
setOtMathGlyphPartTFullAdvance ,
getOtMathGlyphPartTGlyph ,
#if defined(ENABLE_OVERLOADING)
otMathGlyphPartT_glyph ,
#endif
setOtMathGlyphPartTGlyph ,
getOtMathGlyphPartTStartConnectorLength ,
#if defined(ENABLE_OVERLOADING)
otMathGlyphPartT_startConnectorLength ,
#endif
setOtMathGlyphPartTStartConnectorLength ,
) 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.Flags as HarfBuzz.Flags
newtype OtMathGlyphPartT = OtMathGlyphPartT (SP.ManagedPtr OtMathGlyphPartT)
deriving (OtMathGlyphPartT -> OtMathGlyphPartT -> Bool
(OtMathGlyphPartT -> OtMathGlyphPartT -> Bool)
-> (OtMathGlyphPartT -> OtMathGlyphPartT -> Bool)
-> Eq OtMathGlyphPartT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OtMathGlyphPartT -> OtMathGlyphPartT -> Bool
$c/= :: OtMathGlyphPartT -> OtMathGlyphPartT -> Bool
== :: OtMathGlyphPartT -> OtMathGlyphPartT -> Bool
$c== :: OtMathGlyphPartT -> OtMathGlyphPartT -> Bool
Eq)
instance SP.ManagedPtrNewtype OtMathGlyphPartT where
toManagedPtr :: OtMathGlyphPartT -> ManagedPtr OtMathGlyphPartT
toManagedPtr (OtMathGlyphPartT ManagedPtr OtMathGlyphPartT
p) = ManagedPtr OtMathGlyphPartT
p
foreign import ccall "hb_gobject_ot_math_glyph_part_get_type" c_hb_gobject_ot_math_glyph_part_get_type ::
IO GType
type instance O.ParentTypes OtMathGlyphPartT = '[]
instance O.HasParentTypes OtMathGlyphPartT
instance B.Types.TypedObject OtMathGlyphPartT where
glibType :: IO GType
glibType = IO GType
c_hb_gobject_ot_math_glyph_part_get_type
instance B.Types.GBoxed OtMathGlyphPartT
instance B.GValue.IsGValue (Maybe OtMathGlyphPartT) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_hb_gobject_ot_math_glyph_part_get_type
gvalueSet_ :: Ptr GValue -> Maybe OtMathGlyphPartT -> IO ()
gvalueSet_ Ptr GValue
gv Maybe OtMathGlyphPartT
P.Nothing = Ptr GValue -> Ptr OtMathGlyphPartT -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr OtMathGlyphPartT
forall a. Ptr a
FP.nullPtr :: FP.Ptr OtMathGlyphPartT)
gvalueSet_ Ptr GValue
gv (P.Just OtMathGlyphPartT
obj) = OtMathGlyphPartT -> (Ptr OtMathGlyphPartT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr OtMathGlyphPartT
obj (Ptr GValue -> Ptr OtMathGlyphPartT -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe OtMathGlyphPartT)
gvalueGet_ Ptr GValue
gv = do
Ptr OtMathGlyphPartT
ptr <- Ptr GValue -> IO (Ptr OtMathGlyphPartT)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr OtMathGlyphPartT)
if Ptr OtMathGlyphPartT
ptr Ptr OtMathGlyphPartT -> Ptr OtMathGlyphPartT -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr OtMathGlyphPartT
forall a. Ptr a
FP.nullPtr
then OtMathGlyphPartT -> Maybe OtMathGlyphPartT
forall a. a -> Maybe a
P.Just (OtMathGlyphPartT -> Maybe OtMathGlyphPartT)
-> IO OtMathGlyphPartT -> IO (Maybe OtMathGlyphPartT)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr OtMathGlyphPartT -> OtMathGlyphPartT)
-> Ptr OtMathGlyphPartT -> IO OtMathGlyphPartT
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr OtMathGlyphPartT -> OtMathGlyphPartT
OtMathGlyphPartT Ptr OtMathGlyphPartT
ptr
else Maybe OtMathGlyphPartT -> IO (Maybe OtMathGlyphPartT)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe OtMathGlyphPartT
forall a. Maybe a
P.Nothing
newZeroOtMathGlyphPartT :: MonadIO m => m OtMathGlyphPartT
newZeroOtMathGlyphPartT :: forall (m :: * -> *). MonadIO m => m OtMathGlyphPartT
newZeroOtMathGlyphPartT = IO OtMathGlyphPartT -> m OtMathGlyphPartT
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO OtMathGlyphPartT -> m OtMathGlyphPartT)
-> IO OtMathGlyphPartT -> m OtMathGlyphPartT
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr OtMathGlyphPartT)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
20 IO (Ptr OtMathGlyphPartT)
-> (Ptr OtMathGlyphPartT -> IO OtMathGlyphPartT)
-> IO OtMathGlyphPartT
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr OtMathGlyphPartT -> OtMathGlyphPartT)
-> Ptr OtMathGlyphPartT -> IO OtMathGlyphPartT
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr OtMathGlyphPartT -> OtMathGlyphPartT
OtMathGlyphPartT
instance tag ~ 'AttrSet => Constructible OtMathGlyphPartT tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr OtMathGlyphPartT -> OtMathGlyphPartT)
-> [AttrOp OtMathGlyphPartT tag] -> m OtMathGlyphPartT
new ManagedPtr OtMathGlyphPartT -> OtMathGlyphPartT
_ [AttrOp OtMathGlyphPartT tag]
attrs = do
OtMathGlyphPartT
o <- m OtMathGlyphPartT
forall (m :: * -> *). MonadIO m => m OtMathGlyphPartT
newZeroOtMathGlyphPartT
OtMathGlyphPartT -> [AttrOp OtMathGlyphPartT 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set OtMathGlyphPartT
o [AttrOp OtMathGlyphPartT tag]
[AttrOp OtMathGlyphPartT 'AttrSet]
attrs
OtMathGlyphPartT -> m OtMathGlyphPartT
forall (m :: * -> *) a. Monad m => a -> m a
return OtMathGlyphPartT
o
getOtMathGlyphPartTGlyph :: MonadIO m => OtMathGlyphPartT -> m Word32
getOtMathGlyphPartTGlyph :: forall (m :: * -> *). MonadIO m => OtMathGlyphPartT -> m Word32
getOtMathGlyphPartTGlyph OtMathGlyphPartT
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
$ OtMathGlyphPartT
-> (Ptr OtMathGlyphPartT -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OtMathGlyphPartT
s ((Ptr OtMathGlyphPartT -> IO Word32) -> IO Word32)
-> (Ptr OtMathGlyphPartT -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr OtMathGlyphPartT
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr OtMathGlyphPartT
ptr Ptr OtMathGlyphPartT -> 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
setOtMathGlyphPartTGlyph :: MonadIO m => OtMathGlyphPartT -> Word32 -> m ()
setOtMathGlyphPartTGlyph :: forall (m :: * -> *).
MonadIO m =>
OtMathGlyphPartT -> Word32 -> m ()
setOtMathGlyphPartTGlyph OtMathGlyphPartT
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
$ OtMathGlyphPartT -> (Ptr OtMathGlyphPartT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OtMathGlyphPartT
s ((Ptr OtMathGlyphPartT -> IO ()) -> IO ())
-> (Ptr OtMathGlyphPartT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr OtMathGlyphPartT
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OtMathGlyphPartT
ptr Ptr OtMathGlyphPartT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data OtMathGlyphPartTGlyphFieldInfo
instance AttrInfo OtMathGlyphPartTGlyphFieldInfo where
type AttrBaseTypeConstraint OtMathGlyphPartTGlyphFieldInfo = (~) OtMathGlyphPartT
type AttrAllowedOps OtMathGlyphPartTGlyphFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint OtMathGlyphPartTGlyphFieldInfo = (~) Word32
type AttrTransferTypeConstraint OtMathGlyphPartTGlyphFieldInfo = (~)Word32
type AttrTransferType OtMathGlyphPartTGlyphFieldInfo = Word32
type AttrGetType OtMathGlyphPartTGlyphFieldInfo = Word32
type AttrLabel OtMathGlyphPartTGlyphFieldInfo = "glyph"
type AttrOrigin OtMathGlyphPartTGlyphFieldInfo = OtMathGlyphPartT
attrGet = getOtMathGlyphPartTGlyph
attrSet = setOtMathGlyphPartTGlyph
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.HarfBuzz.Structs.OtMathGlyphPartT.glyph"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-harfbuzz-0.0.5/docs/GI-HarfBuzz-Structs-OtMathGlyphPartT.html#g:attr:glyph"
})
otMathGlyphPartT_glyph :: AttrLabelProxy "glyph"
otMathGlyphPartT_glyph = AttrLabelProxy
#endif
getOtMathGlyphPartTStartConnectorLength :: MonadIO m => OtMathGlyphPartT -> m Int32
getOtMathGlyphPartTStartConnectorLength :: forall (m :: * -> *). MonadIO m => OtMathGlyphPartT -> m Int32
getOtMathGlyphPartTStartConnectorLength OtMathGlyphPartT
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ OtMathGlyphPartT -> (Ptr OtMathGlyphPartT -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OtMathGlyphPartT
s ((Ptr OtMathGlyphPartT -> IO Int32) -> IO Int32)
-> (Ptr OtMathGlyphPartT -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr OtMathGlyphPartT
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr OtMathGlyphPartT
ptr Ptr OtMathGlyphPartT -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setOtMathGlyphPartTStartConnectorLength :: MonadIO m => OtMathGlyphPartT -> Int32 -> m ()
setOtMathGlyphPartTStartConnectorLength :: forall (m :: * -> *).
MonadIO m =>
OtMathGlyphPartT -> Int32 -> m ()
setOtMathGlyphPartTStartConnectorLength OtMathGlyphPartT
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ OtMathGlyphPartT -> (Ptr OtMathGlyphPartT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OtMathGlyphPartT
s ((Ptr OtMathGlyphPartT -> IO ()) -> IO ())
-> (Ptr OtMathGlyphPartT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr OtMathGlyphPartT
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OtMathGlyphPartT
ptr Ptr OtMathGlyphPartT -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data OtMathGlyphPartTStartConnectorLengthFieldInfo
instance AttrInfo OtMathGlyphPartTStartConnectorLengthFieldInfo where
type AttrBaseTypeConstraint OtMathGlyphPartTStartConnectorLengthFieldInfo = (~) OtMathGlyphPartT
type AttrAllowedOps OtMathGlyphPartTStartConnectorLengthFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint OtMathGlyphPartTStartConnectorLengthFieldInfo = (~) Int32
type AttrTransferTypeConstraint OtMathGlyphPartTStartConnectorLengthFieldInfo = (~)Int32
type AttrTransferType OtMathGlyphPartTStartConnectorLengthFieldInfo = Int32
type AttrGetType OtMathGlyphPartTStartConnectorLengthFieldInfo = Int32
type AttrLabel OtMathGlyphPartTStartConnectorLengthFieldInfo = "start_connector_length"
type AttrOrigin OtMathGlyphPartTStartConnectorLengthFieldInfo = OtMathGlyphPartT
attrGet = getOtMathGlyphPartTStartConnectorLength
attrSet = setOtMathGlyphPartTStartConnectorLength
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.HarfBuzz.Structs.OtMathGlyphPartT.startConnectorLength"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-harfbuzz-0.0.5/docs/GI-HarfBuzz-Structs-OtMathGlyphPartT.html#g:attr:startConnectorLength"
})
otMathGlyphPartT_startConnectorLength :: AttrLabelProxy "startConnectorLength"
otMathGlyphPartT_startConnectorLength = AttrLabelProxy
#endif
getOtMathGlyphPartTEndConnectorLength :: MonadIO m => OtMathGlyphPartT -> m Int32
getOtMathGlyphPartTEndConnectorLength :: forall (m :: * -> *). MonadIO m => OtMathGlyphPartT -> m Int32
getOtMathGlyphPartTEndConnectorLength OtMathGlyphPartT
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ OtMathGlyphPartT -> (Ptr OtMathGlyphPartT -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OtMathGlyphPartT
s ((Ptr OtMathGlyphPartT -> IO Int32) -> IO Int32)
-> (Ptr OtMathGlyphPartT -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr OtMathGlyphPartT
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr OtMathGlyphPartT
ptr Ptr OtMathGlyphPartT -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setOtMathGlyphPartTEndConnectorLength :: MonadIO m => OtMathGlyphPartT -> Int32 -> m ()
setOtMathGlyphPartTEndConnectorLength :: forall (m :: * -> *).
MonadIO m =>
OtMathGlyphPartT -> Int32 -> m ()
setOtMathGlyphPartTEndConnectorLength OtMathGlyphPartT
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ OtMathGlyphPartT -> (Ptr OtMathGlyphPartT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OtMathGlyphPartT
s ((Ptr OtMathGlyphPartT -> IO ()) -> IO ())
-> (Ptr OtMathGlyphPartT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr OtMathGlyphPartT
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OtMathGlyphPartT
ptr Ptr OtMathGlyphPartT -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data OtMathGlyphPartTEndConnectorLengthFieldInfo
instance AttrInfo OtMathGlyphPartTEndConnectorLengthFieldInfo where
type AttrBaseTypeConstraint OtMathGlyphPartTEndConnectorLengthFieldInfo = (~) OtMathGlyphPartT
type AttrAllowedOps OtMathGlyphPartTEndConnectorLengthFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint OtMathGlyphPartTEndConnectorLengthFieldInfo = (~) Int32
type AttrTransferTypeConstraint OtMathGlyphPartTEndConnectorLengthFieldInfo = (~)Int32
type AttrTransferType OtMathGlyphPartTEndConnectorLengthFieldInfo = Int32
type AttrGetType OtMathGlyphPartTEndConnectorLengthFieldInfo = Int32
type AttrLabel OtMathGlyphPartTEndConnectorLengthFieldInfo = "end_connector_length"
type AttrOrigin OtMathGlyphPartTEndConnectorLengthFieldInfo = OtMathGlyphPartT
attrGet = getOtMathGlyphPartTEndConnectorLength
attrSet = setOtMathGlyphPartTEndConnectorLength
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.HarfBuzz.Structs.OtMathGlyphPartT.endConnectorLength"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-harfbuzz-0.0.5/docs/GI-HarfBuzz-Structs-OtMathGlyphPartT.html#g:attr:endConnectorLength"
})
otMathGlyphPartT_endConnectorLength :: AttrLabelProxy "endConnectorLength"
otMathGlyphPartT_endConnectorLength = AttrLabelProxy
#endif
getOtMathGlyphPartTFullAdvance :: MonadIO m => OtMathGlyphPartT -> m Int32
getOtMathGlyphPartTFullAdvance :: forall (m :: * -> *). MonadIO m => OtMathGlyphPartT -> m Int32
getOtMathGlyphPartTFullAdvance OtMathGlyphPartT
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ OtMathGlyphPartT -> (Ptr OtMathGlyphPartT -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OtMathGlyphPartT
s ((Ptr OtMathGlyphPartT -> IO Int32) -> IO Int32)
-> (Ptr OtMathGlyphPartT -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr OtMathGlyphPartT
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr OtMathGlyphPartT
ptr Ptr OtMathGlyphPartT -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setOtMathGlyphPartTFullAdvance :: MonadIO m => OtMathGlyphPartT -> Int32 -> m ()
setOtMathGlyphPartTFullAdvance :: forall (m :: * -> *).
MonadIO m =>
OtMathGlyphPartT -> Int32 -> m ()
setOtMathGlyphPartTFullAdvance OtMathGlyphPartT
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ OtMathGlyphPartT -> (Ptr OtMathGlyphPartT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OtMathGlyphPartT
s ((Ptr OtMathGlyphPartT -> IO ()) -> IO ())
-> (Ptr OtMathGlyphPartT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr OtMathGlyphPartT
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OtMathGlyphPartT
ptr Ptr OtMathGlyphPartT -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data OtMathGlyphPartTFullAdvanceFieldInfo
instance AttrInfo OtMathGlyphPartTFullAdvanceFieldInfo where
type AttrBaseTypeConstraint OtMathGlyphPartTFullAdvanceFieldInfo = (~) OtMathGlyphPartT
type AttrAllowedOps OtMathGlyphPartTFullAdvanceFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint OtMathGlyphPartTFullAdvanceFieldInfo = (~) Int32
type AttrTransferTypeConstraint OtMathGlyphPartTFullAdvanceFieldInfo = (~)Int32
type AttrTransferType OtMathGlyphPartTFullAdvanceFieldInfo = Int32
type AttrGetType OtMathGlyphPartTFullAdvanceFieldInfo = Int32
type AttrLabel OtMathGlyphPartTFullAdvanceFieldInfo = "full_advance"
type AttrOrigin OtMathGlyphPartTFullAdvanceFieldInfo = OtMathGlyphPartT
attrGet = getOtMathGlyphPartTFullAdvance
attrSet = setOtMathGlyphPartTFullAdvance
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.HarfBuzz.Structs.OtMathGlyphPartT.fullAdvance"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-harfbuzz-0.0.5/docs/GI-HarfBuzz-Structs-OtMathGlyphPartT.html#g:attr:fullAdvance"
})
otMathGlyphPartT_fullAdvance :: AttrLabelProxy "fullAdvance"
otMathGlyphPartT_fullAdvance = AttrLabelProxy
#endif
getOtMathGlyphPartTFlags :: MonadIO m => OtMathGlyphPartT -> m [HarfBuzz.Flags.OtMathGlyphPartFlagsT]
getOtMathGlyphPartTFlags :: forall (m :: * -> *).
MonadIO m =>
OtMathGlyphPartT -> m [OtMathGlyphPartFlagsT]
getOtMathGlyphPartTFlags OtMathGlyphPartT
s = IO [OtMathGlyphPartFlagsT] -> m [OtMathGlyphPartFlagsT]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [OtMathGlyphPartFlagsT] -> m [OtMathGlyphPartFlagsT])
-> IO [OtMathGlyphPartFlagsT] -> m [OtMathGlyphPartFlagsT]
forall a b. (a -> b) -> a -> b
$ OtMathGlyphPartT
-> (Ptr OtMathGlyphPartT -> IO [OtMathGlyphPartFlagsT])
-> IO [OtMathGlyphPartFlagsT]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OtMathGlyphPartT
s ((Ptr OtMathGlyphPartT -> IO [OtMathGlyphPartFlagsT])
-> IO [OtMathGlyphPartFlagsT])
-> (Ptr OtMathGlyphPartT -> IO [OtMathGlyphPartFlagsT])
-> IO [OtMathGlyphPartFlagsT]
forall a b. (a -> b) -> a -> b
$ \Ptr OtMathGlyphPartT
ptr -> do
CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr OtMathGlyphPartT
ptr Ptr OtMathGlyphPartT -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO CUInt
let val' :: [OtMathGlyphPartFlagsT]
val' = CUInt -> [OtMathGlyphPartFlagsT]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
val
[OtMathGlyphPartFlagsT] -> IO [OtMathGlyphPartFlagsT]
forall (m :: * -> *) a. Monad m => a -> m a
return [OtMathGlyphPartFlagsT]
val'
setOtMathGlyphPartTFlags :: MonadIO m => OtMathGlyphPartT -> [HarfBuzz.Flags.OtMathGlyphPartFlagsT] -> m ()
setOtMathGlyphPartTFlags :: forall (m :: * -> *).
MonadIO m =>
OtMathGlyphPartT -> [OtMathGlyphPartFlagsT] -> m ()
setOtMathGlyphPartTFlags OtMathGlyphPartT
s [OtMathGlyphPartFlagsT]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ OtMathGlyphPartT -> (Ptr OtMathGlyphPartT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OtMathGlyphPartT
s ((Ptr OtMathGlyphPartT -> IO ()) -> IO ())
-> (Ptr OtMathGlyphPartT -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr OtMathGlyphPartT
ptr -> do
let val' :: CUInt
val' = [OtMathGlyphPartFlagsT] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [OtMathGlyphPartFlagsT]
val
Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OtMathGlyphPartT
ptr Ptr OtMathGlyphPartT -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (CUInt
val' :: CUInt)
#if defined(ENABLE_OVERLOADING)
data OtMathGlyphPartTFlagsFieldInfo
instance AttrInfo OtMathGlyphPartTFlagsFieldInfo where
type AttrBaseTypeConstraint OtMathGlyphPartTFlagsFieldInfo = (~) OtMathGlyphPartT
type AttrAllowedOps OtMathGlyphPartTFlagsFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint OtMathGlyphPartTFlagsFieldInfo = (~) [HarfBuzz.Flags.OtMathGlyphPartFlagsT]
type AttrTransferTypeConstraint OtMathGlyphPartTFlagsFieldInfo = (~)[HarfBuzz.Flags.OtMathGlyphPartFlagsT]
type AttrTransferType OtMathGlyphPartTFlagsFieldInfo = [HarfBuzz.Flags.OtMathGlyphPartFlagsT]
type AttrGetType OtMathGlyphPartTFlagsFieldInfo = [HarfBuzz.Flags.OtMathGlyphPartFlagsT]
type AttrLabel OtMathGlyphPartTFlagsFieldInfo = "flags"
type AttrOrigin OtMathGlyphPartTFlagsFieldInfo = OtMathGlyphPartT
attrGet = getOtMathGlyphPartTFlags
attrSet = setOtMathGlyphPartTFlags
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.HarfBuzz.Structs.OtMathGlyphPartT.flags"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-harfbuzz-0.0.5/docs/GI-HarfBuzz-Structs-OtMathGlyphPartT.html#g:attr:flags"
})
otMathGlyphPartT_flags :: AttrLabelProxy "flags"
otMathGlyphPartT_flags = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList OtMathGlyphPartT
type instance O.AttributeList OtMathGlyphPartT = OtMathGlyphPartTAttributeList
type OtMathGlyphPartTAttributeList = ('[ '("glyph", OtMathGlyphPartTGlyphFieldInfo), '("startConnectorLength", OtMathGlyphPartTStartConnectorLengthFieldInfo), '("endConnectorLength", OtMathGlyphPartTEndConnectorLengthFieldInfo), '("fullAdvance", OtMathGlyphPartTFullAdvanceFieldInfo), '("flags", OtMathGlyphPartTFlagsFieldInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveOtMathGlyphPartTMethod (t :: Symbol) (o :: *) :: * where
ResolveOtMathGlyphPartTMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveOtMathGlyphPartTMethod t OtMathGlyphPartT, O.OverloadedMethod info OtMathGlyphPartT p) => OL.IsLabel t (OtMathGlyphPartT -> 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 ~ ResolveOtMathGlyphPartTMethod t OtMathGlyphPartT, O.OverloadedMethod info OtMathGlyphPartT p, R.HasField t OtMathGlyphPartT p) => R.HasField t OtMathGlyphPartT p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveOtMathGlyphPartTMethod t OtMathGlyphPartT, O.OverloadedMethodInfo info OtMathGlyphPartT) => OL.IsLabel t (O.MethodProxy info OtMathGlyphPartT) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif