{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Pairs of glyph and color index.
-- 
-- /Since: 2.1.0/

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

module GI.HarfBuzz.Structs.OtColorLayerT
    ( 

-- * Exported types
    OtColorLayerT(..)                       ,
    newZeroOtColorLayerT                    ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveOtColorLayerTMethod              ,
#endif




 -- * Properties
-- ** colorIndex #attr:colorIndex#
-- | /No description available in the introspection data./

    getOtColorLayerTColorIndex              ,
#if defined(ENABLE_OVERLOADING)
    otColorLayerT_colorIndex                ,
#endif
    setOtColorLayerTColorIndex              ,


-- ** glyph #attr:glyph#
-- | /No description available in the introspection data./

    getOtColorLayerTGlyph                   ,
#if defined(ENABLE_OVERLOADING)
    otColorLayerT_glyph                     ,
#endif
    setOtColorLayerTGlyph                   ,




    ) 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.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


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

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

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


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

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


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

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

#if defined(ENABLE_OVERLOADING)
data OtColorLayerTGlyphFieldInfo
instance AttrInfo OtColorLayerTGlyphFieldInfo where
    type AttrBaseTypeConstraint OtColorLayerTGlyphFieldInfo = (~) OtColorLayerT
    type AttrAllowedOps OtColorLayerTGlyphFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint OtColorLayerTGlyphFieldInfo = (~) Word32
    type AttrTransferTypeConstraint OtColorLayerTGlyphFieldInfo = (~)Word32
    type AttrTransferType OtColorLayerTGlyphFieldInfo = Word32
    type AttrGetType OtColorLayerTGlyphFieldInfo = Word32
    type AttrLabel OtColorLayerTGlyphFieldInfo = "glyph"
    type AttrOrigin OtColorLayerTGlyphFieldInfo = OtColorLayerT
    attrGet = getOtColorLayerTGlyph
    attrSet = setOtColorLayerTGlyph
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

otColorLayerT_glyph :: AttrLabelProxy "glyph"
otColorLayerT_glyph = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data OtColorLayerTColorIndexFieldInfo
instance AttrInfo OtColorLayerTColorIndexFieldInfo where
    type AttrBaseTypeConstraint OtColorLayerTColorIndexFieldInfo = (~) OtColorLayerT
    type AttrAllowedOps OtColorLayerTColorIndexFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint OtColorLayerTColorIndexFieldInfo = (~) Word32
    type AttrTransferTypeConstraint OtColorLayerTColorIndexFieldInfo = (~)Word32
    type AttrTransferType OtColorLayerTColorIndexFieldInfo = Word32
    type AttrGetType OtColorLayerTColorIndexFieldInfo = Word32
    type AttrLabel OtColorLayerTColorIndexFieldInfo = "color_index"
    type AttrOrigin OtColorLayerTColorIndexFieldInfo = OtColorLayerT
    attrGet = getOtColorLayerTColorIndex
    attrSet = setOtColorLayerTColorIndex
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

otColorLayerT_colorIndex :: AttrLabelProxy "colorIndex"
otColorLayerT_colorIndex = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList OtColorLayerT
type instance O.AttributeList OtColorLayerT = OtColorLayerTAttributeList
type OtColorLayerTAttributeList = ('[ '("glyph", OtColorLayerTGlyphFieldInfo), '("colorIndex", OtColorLayerTColorIndexFieldInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveOtColorLayerTMethod (t :: Symbol) (o :: *) :: * where
    ResolveOtColorLayerTMethod l o = O.MethodResolutionFailed l o

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

#endif