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

AtkAttribute is a string name\/value pair representing a generic
attribute. This can be used to expose additional information from
an accessible object as a whole (see 'GI.Atk.Objects.Object.objectGetAttributes')
or an document (see 'GI.Atk.Interfaces.Document.documentGetAttributes'). In the case of
text attributes (see 'GI.Atk.Interfaces.Text.textGetDefaultAttributes'),
'GI.Atk.Enums.TextAttribute' enum defines all the possible text attribute
names. You can use 'GI.Atk.Functions.textAttributeGetName' to get the string
name from the enum value. See also 'GI.Atk.Functions.textAttributeForName'
and 'GI.Atk.Functions.textAttributeGetValue' for more information.

A string name\/value pair representing a generic attribute.
-}

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

module GI.Atk.Structs.Attribute
    (

-- * Exported types
    Attribute(..)                           ,
    newZeroAttribute                        ,
    noAttribute                             ,


 -- * Methods
-- ** setFree #method:setFree#

    attributeSetFree                        ,




 -- * Properties
-- ** name #attr:name#
{- | The attribute name.
-}
#if ENABLE_OVERLOADING
    attribute_name                          ,
#endif
    clearAttributeName                      ,
    getAttributeName                        ,
    setAttributeName                        ,


-- ** value #attr:value#
{- | the value of the attribute, represented as a string.
-}
#if ENABLE_OVERLOADING
    attribute_value                         ,
#endif
    clearAttributeValue                     ,
    getAttributeValue                       ,
    setAttributeValue                       ,




    ) 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


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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `Attribute`.
noAttribute :: Maybe Attribute
noAttribute = Nothing

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

@
'Data.GI.Base.Attributes.get' attribute #name
@
-}
getAttributeName :: MonadIO m => Attribute -> m (Maybe T.Text)
getAttributeName s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' attribute [ #name 'Data.GI.Base.Attributes.:=' value ]
@
-}
setAttributeName :: MonadIO m => Attribute -> CString -> m ()
setAttributeName s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: CString)

{- |
Set the value of the “@name@” 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' #name
@
-}
clearAttributeName :: MonadIO m => Attribute -> m ()
clearAttributeName s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data AttributeNameFieldInfo
instance AttrInfo AttributeNameFieldInfo where
    type AttrAllowedOps AttributeNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint AttributeNameFieldInfo = (~) CString
    type AttrBaseTypeConstraint AttributeNameFieldInfo = (~) Attribute
    type AttrGetType AttributeNameFieldInfo = Maybe T.Text
    type AttrLabel AttributeNameFieldInfo = "name"
    type AttrOrigin AttributeNameFieldInfo = Attribute
    attrGet _ = getAttributeName
    attrSet _ = setAttributeName
    attrConstruct = undefined
    attrClear _ = clearAttributeName

attribute_name :: AttrLabelProxy "name"
attribute_name = 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' attribute #value
@
-}
getAttributeValue :: MonadIO m => Attribute -> m (Maybe T.Text)
getAttributeValue s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CString
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- cstringToText val'
        return val''
    return result

{- |
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' attribute [ #value 'Data.GI.Base.Attributes.:=' value ]
@
-}
setAttributeValue :: MonadIO m => Attribute -> CString -> m ()
setAttributeValue s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: CString)

{- |
Set the value of the “@value@” 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' #value
@
-}
clearAttributeValue :: MonadIO m => Attribute -> m ()
clearAttributeValue s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data AttributeValueFieldInfo
instance AttrInfo AttributeValueFieldInfo where
    type AttrAllowedOps AttributeValueFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint AttributeValueFieldInfo = (~) CString
    type AttrBaseTypeConstraint AttributeValueFieldInfo = (~) Attribute
    type AttrGetType AttributeValueFieldInfo = Maybe T.Text
    type AttrLabel AttributeValueFieldInfo = "value"
    type AttrOrigin AttributeValueFieldInfo = Attribute
    attrGet _ = getAttributeValue
    attrSet _ = setAttributeValue
    attrConstruct = undefined
    attrClear _ = clearAttributeValue

attribute_value :: AttrLabelProxy "value"
attribute_value = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList Attribute
type instance O.AttributeList Attribute = AttributeAttributeList
type AttributeAttributeList = ('[ '("name", AttributeNameFieldInfo), '("value", AttributeValueFieldInfo)] :: [(Symbol, *)])
#endif

-- method Attribute::set_free
-- method type : MemberFunction
-- Args : [Arg {argCName = "attrib_set", argType = TGSList (TBasicType TPtr), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "The #AtkAttributeSet to free", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_attribute_set_free" atk_attribute_set_free ::
    Ptr (GSList (Ptr ())) ->                -- attrib_set : TGSList (TBasicType TPtr)
    IO ()

{- |
Frees the memory used by an @/AtkAttributeSet/@, including all its
@/AtkAttributes/@.
-}
attributeSetFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Ptr ()]
    {- ^ /@attribSet@/: The @/AtkAttributeSet/@ to free -}
    -> m ()
attributeSetFree attribSet = liftIO $ do
    attribSet' <- packGSList attribSet
    atk_attribute_set_free attribSet'
    g_slist_free attribSet'
    return ()

#if ENABLE_OVERLOADING
#endif

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

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