{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The GParameter struct is an auxiliary structure used
-- to hand parameter name\/value pairs to 'GI.GObject.Objects.Object.objectNewv'.

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

module GI.GObject.Structs.Parameter
    ( 

-- * Exported types
    Parameter(..)                           ,
    newZeroParameter                        ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveParameterMethod                  ,
#endif



 -- * Properties


-- ** name #attr:name#
-- | the parameter name

    clearParameterName                      ,
    getParameterName                        ,
#if defined(ENABLE_OVERLOADING)
    parameter_name                          ,
#endif
    setParameterName                        ,


-- ** value #attr:value#
-- | the parameter value

    clearParameterValue                     ,
    getParameterValue                       ,
#if defined(ENABLE_OVERLOADING)
    parameter_value                         ,
#endif
    setParameterValue                       ,




    ) 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
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.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
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 qualified GHC.Records as R


-- | Memory-managed wrapper type.
newtype Parameter = Parameter (SP.ManagedPtr Parameter)
    deriving (Parameter -> Parameter -> Bool
(Parameter -> Parameter -> Bool)
-> (Parameter -> Parameter -> Bool) -> Eq Parameter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Parameter -> Parameter -> Bool
$c/= :: Parameter -> Parameter -> Bool
== :: Parameter -> Parameter -> Bool
$c== :: Parameter -> Parameter -> Bool
Eq)

instance SP.ManagedPtrNewtype Parameter where
    toManagedPtr :: Parameter -> ManagedPtr Parameter
toManagedPtr (Parameter ManagedPtr Parameter
p) = ManagedPtr Parameter
p

instance BoxedPtr Parameter where
    boxedPtrCopy :: Parameter -> IO Parameter
boxedPtrCopy = \Parameter
p -> Parameter -> (Ptr Parameter -> IO Parameter) -> IO Parameter
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Parameter
p (Int -> Ptr Parameter -> IO (Ptr Parameter)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
32 (Ptr Parameter -> IO (Ptr Parameter))
-> (Ptr Parameter -> IO Parameter) -> Ptr Parameter -> IO Parameter
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr Parameter -> Parameter)
-> Ptr Parameter -> IO Parameter
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr Parameter -> Parameter
Parameter)
    boxedPtrFree :: Parameter -> IO ()
boxedPtrFree = \Parameter
x -> Parameter -> (Ptr Parameter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr Parameter
x Ptr Parameter -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr Parameter where
    boxedPtrCalloc :: IO (Ptr Parameter)
boxedPtrCalloc = Int -> IO (Ptr Parameter)
forall a. Int -> IO (Ptr a)
callocBytes Int
32


-- | Construct a `Parameter` struct initialized to zero.
newZeroParameter :: MonadIO m => m Parameter
newZeroParameter :: forall (m :: * -> *). MonadIO m => m Parameter
newZeroParameter = IO Parameter -> m Parameter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Parameter -> m Parameter) -> IO Parameter -> m Parameter
forall a b. (a -> b) -> a -> b
$ IO (Ptr Parameter)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr Parameter)
-> (Ptr Parameter -> IO Parameter) -> IO Parameter
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Parameter -> Parameter)
-> Ptr Parameter -> IO Parameter
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Parameter -> Parameter
Parameter

instance tag ~ 'AttrSet => Constructible Parameter tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr Parameter -> Parameter)
-> [AttrOp Parameter tag] -> m Parameter
new ManagedPtr Parameter -> Parameter
_ [AttrOp Parameter tag]
attrs = do
        Parameter
o <- m Parameter
forall (m :: * -> *). MonadIO m => m Parameter
newZeroParameter
        Parameter -> [AttrOp Parameter 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set Parameter
o [AttrOp Parameter tag]
[AttrOp Parameter 'AttrSet]
attrs
        Parameter -> m Parameter
forall (m :: * -> *) a. Monad m => a -> m a
return Parameter
o


-- | 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' parameter #name
-- @
getParameterName :: MonadIO m => Parameter -> m (Maybe T.Text)
getParameterName :: forall (m :: * -> *). MonadIO m => Parameter -> m (Maybe Text)
getParameterName Parameter
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Parameter -> (Ptr Parameter -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Parameter
s ((Ptr Parameter -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr Parameter -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr Parameter
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr Parameter
ptr Ptr Parameter -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
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' parameter [ #name 'Data.GI.Base.Attributes.:=' value ]
-- @
setParameterName :: MonadIO m => Parameter -> CString -> m ()
setParameterName :: forall (m :: * -> *). MonadIO m => Parameter -> CString -> m ()
setParameterName Parameter
s CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Parameter -> (Ptr Parameter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Parameter
s ((Ptr Parameter -> IO ()) -> IO ())
-> (Ptr Parameter -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Parameter
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Parameter
ptr Ptr Parameter -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CString
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
-- @
clearParameterName :: MonadIO m => Parameter -> m ()
clearParameterName :: forall (m :: * -> *). MonadIO m => Parameter -> m ()
clearParameterName Parameter
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Parameter -> (Ptr Parameter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Parameter
s ((Ptr Parameter -> IO ()) -> IO ())
-> (Ptr Parameter -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Parameter
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Parameter
ptr Ptr Parameter -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data ParameterNameFieldInfo
instance AttrInfo ParameterNameFieldInfo where
    type AttrBaseTypeConstraint ParameterNameFieldInfo = (~) Parameter
    type AttrAllowedOps ParameterNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ParameterNameFieldInfo = (~) CString
    type AttrTransferTypeConstraint ParameterNameFieldInfo = (~)CString
    type AttrTransferType ParameterNameFieldInfo = CString
    type AttrGetType ParameterNameFieldInfo = Maybe T.Text
    type AttrLabel ParameterNameFieldInfo = "name"
    type AttrOrigin ParameterNameFieldInfo = Parameter
    attrGet = getParameterName
    attrSet = setParameterName
    attrConstruct = undefined
    attrClear = clearParameterName
    attrTransfer _ v = do
        return v

parameter_name :: AttrLabelProxy "name"
parameter_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' parameter #value
-- @
getParameterValue :: MonadIO m => Parameter -> m (Maybe GValue)
getParameterValue :: forall (m :: * -> *). MonadIO m => Parameter -> m (Maybe GValue)
getParameterValue Parameter
s = IO (Maybe GValue) -> m (Maybe GValue)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GValue) -> m (Maybe GValue))
-> IO (Maybe GValue) -> m (Maybe GValue)
forall a b. (a -> b) -> a -> b
$ Parameter
-> (Ptr Parameter -> IO (Maybe GValue)) -> IO (Maybe GValue)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Parameter
s ((Ptr Parameter -> IO (Maybe GValue)) -> IO (Maybe GValue))
-> (Ptr Parameter -> IO (Maybe GValue)) -> IO (Maybe GValue)
forall a b. (a -> b) -> a -> b
$ \Ptr Parameter
ptr -> do
    Ptr GValue
val <- Ptr (Ptr GValue) -> IO (Ptr GValue)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Parameter
ptr Ptr Parameter -> Int -> Ptr (Ptr GValue)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO (Ptr GValue)
    Maybe GValue
result <- Ptr GValue -> (Ptr GValue -> IO GValue) -> IO (Maybe GValue)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr GValue
val ((Ptr GValue -> IO GValue) -> IO (Maybe GValue))
-> (Ptr GValue -> IO GValue) -> IO (Maybe GValue)
forall a b. (a -> b) -> a -> b
$ \Ptr GValue
val' -> do
        GValue
val'' <- Ptr GValue -> IO GValue
B.GValue.newGValueFromPtr Ptr GValue
val'
        GValue -> IO GValue
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
val''
    Maybe GValue -> IO (Maybe GValue)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GValue
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' parameter [ #value 'Data.GI.Base.Attributes.:=' value ]
-- @
setParameterValue :: MonadIO m => Parameter -> Ptr GValue -> m ()
setParameterValue :: forall (m :: * -> *). MonadIO m => Parameter -> Ptr GValue -> m ()
setParameterValue Parameter
s Ptr GValue
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Parameter -> (Ptr Parameter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Parameter
s ((Ptr Parameter -> IO ()) -> IO ())
-> (Ptr Parameter -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Parameter
ptr -> do
    Ptr (Ptr GValue) -> Ptr GValue -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Parameter
ptr Ptr Parameter -> Int -> Ptr (Ptr GValue)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr GValue
val :: Ptr GValue)

-- | 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
-- @
clearParameterValue :: MonadIO m => Parameter -> m ()
clearParameterValue :: forall (m :: * -> *). MonadIO m => Parameter -> m ()
clearParameterValue Parameter
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Parameter -> (Ptr Parameter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Parameter
s ((Ptr Parameter -> IO ()) -> IO ())
-> (Ptr Parameter -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Parameter
ptr -> do
    Ptr (Ptr GValue) -> Ptr GValue -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Parameter
ptr Ptr Parameter -> Int -> Ptr (Ptr GValue)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr GValue
forall a. Ptr a
FP.nullPtr :: Ptr GValue)

#if defined(ENABLE_OVERLOADING)
data ParameterValueFieldInfo
instance AttrInfo ParameterValueFieldInfo where
    type AttrBaseTypeConstraint ParameterValueFieldInfo = (~) Parameter
    type AttrAllowedOps ParameterValueFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint ParameterValueFieldInfo = (~) (Ptr GValue)
    type AttrTransferTypeConstraint ParameterValueFieldInfo = (~)(Ptr GValue)
    type AttrTransferType ParameterValueFieldInfo = (Ptr GValue)
    type AttrGetType ParameterValueFieldInfo = Maybe GValue
    type AttrLabel ParameterValueFieldInfo = "value"
    type AttrOrigin ParameterValueFieldInfo = Parameter
    attrGet = getParameterValue
    attrSet = setParameterValue
    attrConstruct = undefined
    attrClear = clearParameterValue
    attrTransfer _ v = do
        return v

parameter_value :: AttrLabelProxy "value"
parameter_value = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Parameter
type instance O.AttributeList Parameter = ParameterAttributeList
type ParameterAttributeList = ('[ '("name", ParameterNameFieldInfo), '("value", ParameterValueFieldInfo)] :: [(Symbol, *)])
#endif

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

instance (info ~ ResolveParameterMethod t Parameter, O.OverloadedMethod info Parameter p) => OL.IsLabel t (Parameter -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveParameterMethod t Parameter, O.OverloadedMethod info Parameter p, R.HasField t Parameter p) => R.HasField t Parameter p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveParameterMethod t Parameter, O.OverloadedMethodInfo info Parameter) => OL.IsLabel t (O.MethodProxy info Parameter) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif