{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.HarfBuzz.Structs.GlyphInfoT.GlyphInfoT' is the structure that holds information about the
-- glyphs and their relation to input text.

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

module GI.HarfBuzz.Structs.GlyphInfoT
    ( 

-- * Exported types
    GlyphInfoT(..)                          ,
    newZeroGlyphInfoT                       ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveGlyphInfoTMethod                 ,
#endif



 -- * Properties


-- ** cluster #attr:cluster#
-- | the index of the character in the original text that corresponds
--           to this t'GI.HarfBuzz.Structs.GlyphInfoT.GlyphInfoT', or whatever the client passes to
--           'GI.HarfBuzz.Functions.bufferAdd'. More than one t'GI.HarfBuzz.Structs.GlyphInfoT.GlyphInfoT' can have the same
--           /@cluster@/ value, if they resulted from the same character (e.g. one
--           to many glyph substitution), and when more than one character gets
--           merged in the same glyph (e.g. many to one glyph substitution) the
--           t'GI.HarfBuzz.Structs.GlyphInfoT.GlyphInfoT' will have the smallest cluster value of them.
--           By default some characters are merged into the same cluster
--           (e.g. combining marks have the same cluster as their bases)
--           even if they are separate glyphs, 'GI.HarfBuzz.Functions.bufferSetClusterLevel'
--           allow selecting more fine-grained cluster handling.

    getGlyphInfoTCluster                    ,
#if defined(ENABLE_OVERLOADING)
    glyphInfoT_cluster                      ,
#endif
    setGlyphInfoTCluster                    ,


-- ** codepoint #attr:codepoint#
-- | either a Unicode code point (before shaping) or a glyph index
--             (after shaping).

    getGlyphInfoTCodepoint                  ,
#if defined(ENABLE_OVERLOADING)
    glyphInfoT_codepoint                    ,
#endif
    setGlyphInfoTCodepoint                  ,




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

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

foreign import ccall "hb_gobject_glyph_info_get_type" c_hb_gobject_glyph_info_get_type :: 
    IO GType

type instance O.ParentTypes GlyphInfoT = '[]
instance O.HasParentTypes GlyphInfoT

instance B.Types.TypedObject GlyphInfoT where
    glibType :: IO GType
glibType = IO GType
c_hb_gobject_glyph_info_get_type

instance B.Types.GBoxed GlyphInfoT

-- | Convert 'GlyphInfoT' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe GlyphInfoT) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_hb_gobject_glyph_info_get_type
    gvalueSet_ :: Ptr GValue -> Maybe GlyphInfoT -> IO ()
gvalueSet_ Ptr GValue
gv Maybe GlyphInfoT
P.Nothing = Ptr GValue -> Ptr GlyphInfoT -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr GlyphInfoT
forall a. Ptr a
FP.nullPtr :: FP.Ptr GlyphInfoT)
    gvalueSet_ Ptr GValue
gv (P.Just GlyphInfoT
obj) = GlyphInfoT -> (Ptr GlyphInfoT -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr GlyphInfoT
obj (Ptr GValue -> Ptr GlyphInfoT -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe GlyphInfoT)
gvalueGet_ Ptr GValue
gv = do
        Ptr GlyphInfoT
ptr <- Ptr GValue -> IO (Ptr GlyphInfoT)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr GlyphInfoT)
        if Ptr GlyphInfoT
ptr Ptr GlyphInfoT -> Ptr GlyphInfoT -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr GlyphInfoT
forall a. Ptr a
FP.nullPtr
        then GlyphInfoT -> Maybe GlyphInfoT
forall a. a -> Maybe a
P.Just (GlyphInfoT -> Maybe GlyphInfoT)
-> IO GlyphInfoT -> IO (Maybe GlyphInfoT)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr GlyphInfoT -> GlyphInfoT)
-> Ptr GlyphInfoT -> IO GlyphInfoT
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr GlyphInfoT -> GlyphInfoT
GlyphInfoT Ptr GlyphInfoT
ptr
        else Maybe GlyphInfoT -> IO (Maybe GlyphInfoT)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GlyphInfoT
forall a. Maybe a
P.Nothing
        
    

-- | Construct a `GlyphInfoT` struct initialized to zero.
newZeroGlyphInfoT :: MonadIO m => m GlyphInfoT
newZeroGlyphInfoT :: forall (m :: * -> *). MonadIO m => m GlyphInfoT
newZeroGlyphInfoT = IO GlyphInfoT -> m GlyphInfoT
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GlyphInfoT -> m GlyphInfoT) -> IO GlyphInfoT -> m GlyphInfoT
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr GlyphInfoT)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
20 IO (Ptr GlyphInfoT)
-> (Ptr GlyphInfoT -> IO GlyphInfoT) -> IO GlyphInfoT
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr GlyphInfoT -> GlyphInfoT)
-> Ptr GlyphInfoT -> IO GlyphInfoT
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr GlyphInfoT -> GlyphInfoT
GlyphInfoT

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


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

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

glyphInfoT_codepoint :: AttrLabelProxy "codepoint"
glyphInfoT_codepoint = AttrLabelProxy

#endif


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

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

glyphInfoT_cluster :: AttrLabelProxy "cluster"
glyphInfoT_cluster = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GlyphInfoT
type instance O.AttributeList GlyphInfoT = GlyphInfoTAttributeList
type GlyphInfoTAttributeList = ('[ '("codepoint", GlyphInfoTCodepointFieldInfo), '("cluster", GlyphInfoTClusterFieldInfo)] :: [(Symbol, DK.Type)])
#endif

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

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

#endif

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

#endif