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

The 'GI.Pango.Structs.AttrFontDesc.AttrFontDesc' structure is used to store an attribute that
sets all aspects of the font description at once.
-}

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

module GI.Pango.Structs.AttrFontDesc
    (

-- * Exported types
    AttrFontDesc(..)                        ,
    newZeroAttrFontDesc                     ,
    noAttrFontDesc                          ,


 -- * Methods
-- ** new #method:new#

    attrFontDescNew                         ,




 -- * Properties
-- ** attr #attr:attr#
{- | the common portion of the attribute
-}
#if ENABLE_OVERLOADING
    attrFontDesc_attr                       ,
#endif
    getAttrFontDescAttr                     ,


-- ** desc #attr:desc#
{- | the font description which is the value of this attribute
-}
#if ENABLE_OVERLOADING
    attrFontDesc_desc                       ,
#endif
    clearAttrFontDescDesc                   ,
    getAttrFontDescDesc                     ,
    setAttrFontDescDesc                     ,




    ) 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.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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP

import {-# SOURCE #-} qualified GI.Pango.Structs.Attribute as Pango.Attribute
import {-# SOURCE #-} qualified GI.Pango.Structs.FontDescription as Pango.FontDescription

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `AttrFontDesc`.
noAttrFontDesc :: Maybe AttrFontDesc
noAttrFontDesc = Nothing

{- |
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' attrFontDesc #attr
@
-}
getAttrFontDescAttr :: MonadIO m => AttrFontDesc -> m Pango.Attribute.Attribute
getAttrFontDescAttr s = liftIO $ withManagedPtr s $ \ptr -> do
    let val = ptr `plusPtr` 0 :: (Ptr Pango.Attribute.Attribute)
    val' <- (newPtr Pango.Attribute.Attribute) val
    return val'

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

attrFontDesc_attr :: AttrLabelProxy "attr"
attrFontDesc_attr = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' attrFontDesc #desc
@
-}
getAttrFontDescDesc :: MonadIO m => AttrFontDesc -> m (Maybe Pango.FontDescription.FontDescription)
getAttrFontDescDesc s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO (Ptr Pango.FontDescription.FontDescription)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newBoxed Pango.FontDescription.FontDescription) val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' attrFontDesc [ #desc 'Data.GI.Base.Attributes.:=' value ]
@
-}
setAttrFontDescDesc :: MonadIO m => AttrFontDesc -> Ptr Pango.FontDescription.FontDescription -> m ()
setAttrFontDescDesc s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Ptr Pango.FontDescription.FontDescription)

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

@
'Data.GI.Base.Attributes.clear' #desc
@
-}
clearAttrFontDescDesc :: MonadIO m => AttrFontDesc -> m ()
clearAttrFontDescDesc s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (FP.nullPtr :: Ptr Pango.FontDescription.FontDescription)

#if ENABLE_OVERLOADING
data AttrFontDescDescFieldInfo
instance AttrInfo AttrFontDescDescFieldInfo where
    type AttrAllowedOps AttrFontDescDescFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint AttrFontDescDescFieldInfo = (~) (Ptr Pango.FontDescription.FontDescription)
    type AttrBaseTypeConstraint AttrFontDescDescFieldInfo = (~) AttrFontDesc
    type AttrGetType AttrFontDescDescFieldInfo = Maybe Pango.FontDescription.FontDescription
    type AttrLabel AttrFontDescDescFieldInfo = "desc"
    type AttrOrigin AttrFontDescDescFieldInfo = AttrFontDesc
    attrGet _ = getAttrFontDescDesc
    attrSet _ = setAttrFontDescDesc
    attrConstruct = undefined
    attrClear _ = clearAttrFontDescDesc

attrFontDesc_desc :: AttrLabelProxy "desc"
attrFontDesc_desc = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList AttrFontDesc
type instance O.AttributeList AttrFontDesc = AttrFontDescAttributeList
type AttrFontDescAttributeList = ('[ '("attr", AttrFontDescAttrFieldInfo), '("desc", AttrFontDescDescFieldInfo)] :: [(Symbol, *)])
#endif

-- method AttrFontDesc::new
-- method type : MemberFunction
-- Args : [Arg {argCName = "desc", argType = TInterface (Name {namespace = "Pango", name = "FontDescription"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the font description", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TInterface (Name {namespace = "Pango", name = "Attribute"}))
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_font_desc_new" pango_attr_font_desc_new ::
    Ptr Pango.FontDescription.FontDescription -> -- desc : TInterface (Name {namespace = "Pango", name = "FontDescription"})
    IO (Ptr Pango.Attribute.Attribute)

{- |
Create a new font description attribute. This attribute
allows setting family, style, weight, variant, stretch,
and size simultaneously.
-}
attrFontDescNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Pango.FontDescription.FontDescription
    {- ^ /@desc@/: the font description -}
    -> m Pango.Attribute.Attribute
    {- ^ __Returns:__ the newly allocated 'GI.Pango.Structs.Attribute.Attribute',
              which should be freed with 'GI.Pango.Structs.Attribute.attributeDestroy'. -}
attrFontDescNew desc = liftIO $ do
    desc' <- unsafeManagedPtrGetPtr desc
    result <- pango_attr_font_desc_new desc'
    checkUnexpectedReturnNULL "attrFontDescNew" result
    result' <- (wrapPtr Pango.Attribute.Attribute) result
    touchManagedPtr desc
    return result'

#if ENABLE_OVERLOADING
#endif

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

instance (info ~ ResolveAttrFontDescMethod t AttrFontDesc, O.MethodInfo info AttrFontDesc p) => O.IsLabelProxy t (AttrFontDesc -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveAttrFontDescMethod t AttrFontDesc, O.MethodInfo info AttrFontDesc p) => O.IsLabel t (AttrFontDesc -> 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

#endif