{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The PangoGlyphVisAttr is used to communicate information between
-- the shaping phase and the rendering phase.  More attributes may be
-- added in the future.

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

module GI.Pango.Structs.GlyphVisAttr
    ( 

-- * Exported types
    GlyphVisAttr(..)                        ,
    newZeroGlyphVisAttr                     ,
    noGlyphVisAttr                          ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveGlyphVisAttrMethod               ,
#endif




 -- * Properties
-- ** isClusterStart #attr:isClusterStart#
-- | set for the first logical glyph in each cluster. (Clusters
-- are stored in visual order, within the cluster, glyphs
-- are always ordered in logical order, since visual
-- order is meaningless; that is, in Arabic text, accent glyphs
-- follow the glyphs for the base character.)

    getGlyphVisAttrIsClusterStart           ,
#if defined(ENABLE_OVERLOADING)
    glyphVisAttr_isClusterStart             ,
#endif
    setGlyphVisAttrIsClusterStart           ,




    ) 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.ManagedPtr as B.ManagedPtr
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 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 GlyphVisAttr = GlyphVisAttr (ManagedPtr GlyphVisAttr)
    deriving (GlyphVisAttr -> GlyphVisAttr -> Bool
(GlyphVisAttr -> GlyphVisAttr -> Bool)
-> (GlyphVisAttr -> GlyphVisAttr -> Bool) -> Eq GlyphVisAttr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GlyphVisAttr -> GlyphVisAttr -> Bool
$c/= :: GlyphVisAttr -> GlyphVisAttr -> Bool
== :: GlyphVisAttr -> GlyphVisAttr -> Bool
$c== :: GlyphVisAttr -> GlyphVisAttr -> Bool
Eq)
instance WrappedPtr GlyphVisAttr where
    wrappedPtrCalloc :: IO (Ptr GlyphVisAttr)
wrappedPtrCalloc = Int -> IO (Ptr GlyphVisAttr)
forall a. Int -> IO (Ptr a)
callocBytes 4
    wrappedPtrCopy :: GlyphVisAttr -> IO GlyphVisAttr
wrappedPtrCopy = \p :: GlyphVisAttr
p -> GlyphVisAttr
-> (Ptr GlyphVisAttr -> IO GlyphVisAttr) -> IO GlyphVisAttr
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphVisAttr
p (Int -> Ptr GlyphVisAttr -> IO (Ptr GlyphVisAttr)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 4 (Ptr GlyphVisAttr -> IO (Ptr GlyphVisAttr))
-> (Ptr GlyphVisAttr -> IO GlyphVisAttr)
-> Ptr GlyphVisAttr
-> IO GlyphVisAttr
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr GlyphVisAttr -> GlyphVisAttr)
-> Ptr GlyphVisAttr -> IO GlyphVisAttr
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr GlyphVisAttr -> GlyphVisAttr
GlyphVisAttr)
    wrappedPtrFree :: Maybe (GDestroyNotify GlyphVisAttr)
wrappedPtrFree = GDestroyNotify GlyphVisAttr -> Maybe (GDestroyNotify GlyphVisAttr)
forall a. a -> Maybe a
Just GDestroyNotify GlyphVisAttr
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

-- | Construct a `GlyphVisAttr` struct initialized to zero.
newZeroGlyphVisAttr :: MonadIO m => m GlyphVisAttr
newZeroGlyphVisAttr :: m GlyphVisAttr
newZeroGlyphVisAttr = IO GlyphVisAttr -> m GlyphVisAttr
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GlyphVisAttr -> m GlyphVisAttr)
-> IO GlyphVisAttr -> m GlyphVisAttr
forall a b. (a -> b) -> a -> b
$ IO (Ptr GlyphVisAttr)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr GlyphVisAttr)
-> (Ptr GlyphVisAttr -> IO GlyphVisAttr) -> IO GlyphVisAttr
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr GlyphVisAttr -> GlyphVisAttr)
-> Ptr GlyphVisAttr -> IO GlyphVisAttr
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr GlyphVisAttr -> GlyphVisAttr
GlyphVisAttr

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


-- | A convenience alias for `Nothing` :: `Maybe` `GlyphVisAttr`.
noGlyphVisAttr :: Maybe GlyphVisAttr
noGlyphVisAttr :: Maybe GlyphVisAttr
noGlyphVisAttr = Maybe GlyphVisAttr
forall a. Maybe a
Nothing

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

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

#if defined(ENABLE_OVERLOADING)
data GlyphVisAttrIsClusterStartFieldInfo
instance AttrInfo GlyphVisAttrIsClusterStartFieldInfo where
    type AttrBaseTypeConstraint GlyphVisAttrIsClusterStartFieldInfo = (~) GlyphVisAttr
    type AttrAllowedOps GlyphVisAttrIsClusterStartFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GlyphVisAttrIsClusterStartFieldInfo = (~) Word32
    type AttrTransferTypeConstraint GlyphVisAttrIsClusterStartFieldInfo = (~)Word32
    type AttrTransferType GlyphVisAttrIsClusterStartFieldInfo = Word32
    type AttrGetType GlyphVisAttrIsClusterStartFieldInfo = Word32
    type AttrLabel GlyphVisAttrIsClusterStartFieldInfo = "is_cluster_start"
    type AttrOrigin GlyphVisAttrIsClusterStartFieldInfo = GlyphVisAttr
    attrGet = getGlyphVisAttrIsClusterStart
    attrSet = setGlyphVisAttrIsClusterStart
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

glyphVisAttr_isClusterStart :: AttrLabelProxy "isClusterStart"
glyphVisAttr_isClusterStart = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GlyphVisAttr
type instance O.AttributeList GlyphVisAttr = GlyphVisAttrAttributeList
type GlyphVisAttrAttributeList = ('[ '("isClusterStart", GlyphVisAttrIsClusterStartFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif