{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (inaki@blueleaf.cc)

The 'GI.Pango.Structs.GlyphInfo.GlyphInfo' structure represents a single glyph together with
positioning information and visual attributes.
It contains the following fields.
-}

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

module GI.Pango.Structs.GlyphInfo
    (

-- * Exported types
    GlyphInfo(..)                           ,
    newZeroGlyphInfo                        ,
    noGlyphInfo                             ,


 -- * Properties
-- ** attr #attr:attr#
{- | the visual attributes of the glyph.
-}
    getGlyphInfoAttr                        ,
#if ENABLE_OVERLOADING
    glyphInfo_attr                          ,
#endif


-- ** geometry #attr:geometry#
{- | the positional information about the glyph.
-}
    getGlyphInfoGeometry                    ,
#if ENABLE_OVERLOADING
    glyphInfo_geometry                      ,
#endif


-- ** glyph #attr:glyph#
{- | the glyph itself.
-}
    getGlyphInfoGlyph                       ,
#if ENABLE_OVERLOADING
    glyphInfo_glyph                         ,
#endif
    setGlyphInfoGlyph                       ,




    ) 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.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 {-# SOURCE #-} qualified GI.Pango.Structs.GlyphGeometry as Pango.GlyphGeometry
import {-# SOURCE #-} qualified GI.Pango.Structs.GlyphVisAttr as Pango.GlyphVisAttr

-- | Memory-managed wrapper type.
newtype GlyphInfo = GlyphInfo (ManagedPtr GlyphInfo)
instance WrappedPtr GlyphInfo where
    wrappedPtrCalloc = callocBytes 20
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 20 >=> wrapPtr GlyphInfo)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `GlyphInfo` struct initialized to zero.
newZeroGlyphInfo :: MonadIO m => m GlyphInfo
newZeroGlyphInfo = liftIO $ wrappedPtrCalloc >>= wrapPtr GlyphInfo

instance tag ~ 'AttrSet => Constructible GlyphInfo tag where
    new _ attrs = do
        o <- newZeroGlyphInfo
        GI.Attributes.set o attrs
        return o


-- | A convenience alias for `Nothing` :: `Maybe` `GlyphInfo`.
noGlyphInfo :: Maybe GlyphInfo
noGlyphInfo = Nothing

{- |
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' glyphInfo #glyph
@
-}
getGlyphInfoGlyph :: MonadIO m => GlyphInfo -> m Word32
getGlyphInfoGlyph s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Word32
    return 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' glyphInfo [ #glyph 'Data.GI.Base.Attributes.:=' value ]
@
-}
setGlyphInfoGlyph :: MonadIO m => GlyphInfo -> Word32 -> m ()
setGlyphInfoGlyph s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Word32)

#if ENABLE_OVERLOADING
data GlyphInfoGlyphFieldInfo
instance AttrInfo GlyphInfoGlyphFieldInfo where
    type AttrAllowedOps GlyphInfoGlyphFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GlyphInfoGlyphFieldInfo = (~) Word32
    type AttrBaseTypeConstraint GlyphInfoGlyphFieldInfo = (~) GlyphInfo
    type AttrGetType GlyphInfoGlyphFieldInfo = Word32
    type AttrLabel GlyphInfoGlyphFieldInfo = "glyph"
    type AttrOrigin GlyphInfoGlyphFieldInfo = GlyphInfo
    attrGet _ = getGlyphInfoGlyph
    attrSet _ = setGlyphInfoGlyph
    attrConstruct = undefined
    attrClear _ = undefined

glyphInfo_glyph :: AttrLabelProxy "glyph"
glyphInfo_glyph = AttrLabelProxy

#endif


{- |
Get the value of the “@geometry@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' glyphInfo #geometry
@
-}
getGlyphInfoGeometry :: MonadIO m => GlyphInfo -> m Pango.GlyphGeometry.GlyphGeometry
getGlyphInfoGeometry s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 4 :: (Ptr Pango.GlyphGeometry.GlyphGeometry)
    val' <- (newPtr Pango.GlyphGeometry.GlyphGeometry) val
    return val'

#if ENABLE_OVERLOADING
data GlyphInfoGeometryFieldInfo
instance AttrInfo GlyphInfoGeometryFieldInfo where
    type AttrAllowedOps GlyphInfoGeometryFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint GlyphInfoGeometryFieldInfo = (~) (Ptr Pango.GlyphGeometry.GlyphGeometry)
    type AttrBaseTypeConstraint GlyphInfoGeometryFieldInfo = (~) GlyphInfo
    type AttrGetType GlyphInfoGeometryFieldInfo = Pango.GlyphGeometry.GlyphGeometry
    type AttrLabel GlyphInfoGeometryFieldInfo = "geometry"
    type AttrOrigin GlyphInfoGeometryFieldInfo = GlyphInfo
    attrGet _ = getGlyphInfoGeometry
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

glyphInfo_geometry :: AttrLabelProxy "geometry"
glyphInfo_geometry = AttrLabelProxy

#endif


{- |
Get the value of the “@attr@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' glyphInfo #attr
@
-}
getGlyphInfoAttr :: MonadIO m => GlyphInfo -> m Pango.GlyphVisAttr.GlyphVisAttr
getGlyphInfoAttr s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 16 :: (Ptr Pango.GlyphVisAttr.GlyphVisAttr)
    val' <- (newPtr Pango.GlyphVisAttr.GlyphVisAttr) val
    return val'

#if ENABLE_OVERLOADING
data GlyphInfoAttrFieldInfo
instance AttrInfo GlyphInfoAttrFieldInfo where
    type AttrAllowedOps GlyphInfoAttrFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint GlyphInfoAttrFieldInfo = (~) (Ptr Pango.GlyphVisAttr.GlyphVisAttr)
    type AttrBaseTypeConstraint GlyphInfoAttrFieldInfo = (~) GlyphInfo
    type AttrGetType GlyphInfoAttrFieldInfo = Pango.GlyphVisAttr.GlyphVisAttr
    type AttrLabel GlyphInfoAttrFieldInfo = "attr"
    type AttrOrigin GlyphInfoAttrFieldInfo = GlyphInfo
    attrGet _ = getGlyphInfoAttr
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

glyphInfo_attr :: AttrLabelProxy "attr"
glyphInfo_attr = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList GlyphInfo
type instance O.AttributeList GlyphInfo = GlyphInfoAttributeList
type GlyphInfoAttributeList = ('[ '("glyph", GlyphInfoGlyphFieldInfo), '("geometry", GlyphInfoGeometryFieldInfo), '("attr", GlyphInfoAttrFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif