{- |
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.AttrInt.AttrInt' structure is used to represent attributes with
an integer or enumeration value.
-}

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

module GI.Pango.Structs.AttrInt
    (

-- * Exported types
    AttrInt(..)                             ,
    newZeroAttrInt                          ,
    noAttrInt                               ,


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


-- ** value #attr:value#
{- | the value of the attribute
-}
#if ENABLE_OVERLOADING
    attrInt_value                           ,
#endif
    getAttrIntValue                         ,
    setAttrIntValue                         ,




    ) 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.Attribute as Pango.Attribute

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `AttrInt`.
noAttrInt :: Maybe AttrInt
noAttrInt = 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' attrInt #attr
@
-}
getAttrIntAttr :: MonadIO m => AttrInt -> m Pango.Attribute.Attribute
getAttrIntAttr 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 AttrIntAttrFieldInfo
instance AttrInfo AttrIntAttrFieldInfo where
    type AttrAllowedOps AttrIntAttrFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint AttrIntAttrFieldInfo = (~) (Ptr Pango.Attribute.Attribute)
    type AttrBaseTypeConstraint AttrIntAttrFieldInfo = (~) AttrInt
    type AttrGetType AttrIntAttrFieldInfo = Pango.Attribute.Attribute
    type AttrLabel AttrIntAttrFieldInfo = "attr"
    type AttrOrigin AttrIntAttrFieldInfo = AttrInt
    attrGet _ = getAttrIntAttr
    attrSet _ = undefined
    attrConstruct = undefined
    attrClear _ = undefined

attrInt_attr :: AttrLabelProxy "attr"
attrInt_attr = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' attrInt #value
@
-}
getAttrIntValue :: MonadIO m => AttrInt -> m Int32
getAttrIntValue s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO Int32
    return val

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

@
'Data.GI.Base.Attributes.set' attrInt [ #value 'Data.GI.Base.Attributes.:=' value ]
@
-}
setAttrIntValue :: MonadIO m => AttrInt -> Int32 -> m ()
setAttrIntValue s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Int32)

#if ENABLE_OVERLOADING
data AttrIntValueFieldInfo
instance AttrInfo AttrIntValueFieldInfo where
    type AttrAllowedOps AttrIntValueFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint AttrIntValueFieldInfo = (~) Int32
    type AttrBaseTypeConstraint AttrIntValueFieldInfo = (~) AttrInt
    type AttrGetType AttrIntValueFieldInfo = Int32
    type AttrLabel AttrIntValueFieldInfo = "value"
    type AttrOrigin AttrIntValueFieldInfo = AttrInt
    attrGet _ = getAttrIntValue
    attrSet _ = setAttrIntValue
    attrConstruct = undefined
    attrClear _ = undefined

attrInt_value :: AttrLabelProxy "value"
attrInt_value = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList AttrInt
type instance O.AttributeList AttrInt = AttrIntAttributeList
type AttrIntAttributeList = ('[ '("attr", AttrIntAttrFieldInfo), '("value", AttrIntValueFieldInfo)] :: [(Symbol, *)])
#endif

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

instance (info ~ ResolveAttrIntMethod t AttrInt, O.MethodInfo info AttrInt p) => OL.IsLabel t (AttrInt -> 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