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

An attribute in a 'GI.Secret.Structs.Schema.Schema'.
-}

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

module GI.Secret.Structs.SchemaAttribute
    (

-- * Exported types
    SchemaAttribute(..)                     ,
    newZeroSchemaAttribute                  ,
    noSchemaAttribute                       ,


 -- * Properties
-- ** name #attr:name#
{- | name of the attribute
-}
    clearSchemaAttributeName                ,
    getSchemaAttributeName                  ,
#if ENABLE_OVERLOADING
    schemaAttribute_name                    ,
#endif
    setSchemaAttributeName                  ,


-- ** type #attr:type#
{- | the type of the attribute
-}
    getSchemaAttributeType                  ,
#if ENABLE_OVERLOADING
    schemaAttribute_type                    ,
#endif
    setSchemaAttributeType                  ,




    ) 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.Secret.Enums as Secret.Enums

-- | Memory-managed wrapper type.
newtype SchemaAttribute = SchemaAttribute (ManagedPtr SchemaAttribute)
foreign import ccall "secret_schema_attribute_get_type" c_secret_schema_attribute_get_type ::
    IO GType

instance BoxedObject SchemaAttribute where
    boxedType _ = c_secret_schema_attribute_get_type

-- | Construct a `SchemaAttribute` struct initialized to zero.
newZeroSchemaAttribute :: MonadIO m => m SchemaAttribute
newZeroSchemaAttribute = liftIO $ callocBoxedBytes 16 >>= wrapBoxed SchemaAttribute

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


-- | A convenience alias for `Nothing` :: `Maybe` `SchemaAttribute`.
noSchemaAttribute :: Maybe SchemaAttribute
noSchemaAttribute = 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' schemaAttribute #name
@
-}
getSchemaAttributeName :: MonadIO m => SchemaAttribute -> m (Maybe T.Text)
getSchemaAttributeName 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' schemaAttribute [ #name 'Data.GI.Base.Attributes.:=' value ]
@
-}
setSchemaAttributeName :: MonadIO m => SchemaAttribute -> CString -> m ()
setSchemaAttributeName 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
@
-}
clearSchemaAttributeName :: MonadIO m => SchemaAttribute -> m ()
clearSchemaAttributeName s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullPtr :: CString)

#if ENABLE_OVERLOADING
data SchemaAttributeNameFieldInfo
instance AttrInfo SchemaAttributeNameFieldInfo where
    type AttrAllowedOps SchemaAttributeNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint SchemaAttributeNameFieldInfo = (~) CString
    type AttrBaseTypeConstraint SchemaAttributeNameFieldInfo = (~) SchemaAttribute
    type AttrGetType SchemaAttributeNameFieldInfo = Maybe T.Text
    type AttrLabel SchemaAttributeNameFieldInfo = "name"
    type AttrOrigin SchemaAttributeNameFieldInfo = SchemaAttribute
    attrGet _ = getSchemaAttributeName
    attrSet _ = setSchemaAttributeName
    attrConstruct = undefined
    attrClear _ = clearSchemaAttributeName

schemaAttribute_name :: AttrLabelProxy "name"
schemaAttribute_name = AttrLabelProxy

#endif


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

@
'Data.GI.Base.Attributes.get' schemaAttribute #type
@
-}
getSchemaAttributeType :: MonadIO m => SchemaAttribute -> m Secret.Enums.SchemaAttributeType
getSchemaAttributeType s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return val'

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

@
'Data.GI.Base.Attributes.set' schemaAttribute [ #type 'Data.GI.Base.Attributes.:=' value ]
@
-}
setSchemaAttributeType :: MonadIO m => SchemaAttribute -> Secret.Enums.SchemaAttributeType -> m ()
setSchemaAttributeType s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 8) (val' :: CUInt)

#if ENABLE_OVERLOADING
data SchemaAttributeTypeFieldInfo
instance AttrInfo SchemaAttributeTypeFieldInfo where
    type AttrAllowedOps SchemaAttributeTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint SchemaAttributeTypeFieldInfo = (~) Secret.Enums.SchemaAttributeType
    type AttrBaseTypeConstraint SchemaAttributeTypeFieldInfo = (~) SchemaAttribute
    type AttrGetType SchemaAttributeTypeFieldInfo = Secret.Enums.SchemaAttributeType
    type AttrLabel SchemaAttributeTypeFieldInfo = "type"
    type AttrOrigin SchemaAttributeTypeFieldInfo = SchemaAttribute
    attrGet _ = getSchemaAttributeType
    attrSet _ = setSchemaAttributeType
    attrConstruct = undefined
    attrClear _ = undefined

schemaAttribute_type :: AttrLabelProxy "type"
schemaAttribute_type = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList SchemaAttribute
type instance O.AttributeList SchemaAttribute = SchemaAttributeAttributeList
type SchemaAttributeAttributeList = ('[ '("name", SchemaAttributeNameFieldInfo), '("type", SchemaAttributeTypeFieldInfo)] :: [(Symbol, *)])
#endif

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

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