{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Struct used in 'GI.Gio.Functions.dbusErrorRegisterErrorDomain'.
-- 
-- /Since: 2.26/

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

module GI.Gio.Structs.DBusErrorEntry
    ( 

-- * Exported types
    DBusErrorEntry(..)                      ,
    newZeroDBusErrorEntry                   ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveDBusErrorEntryMethod             ,
#endif




 -- * Properties
-- ** dbusErrorName #attr:dbusErrorName#
-- | The D-Bus error name to associate with /@errorCode@/.

    clearDBusErrorEntryDbusErrorName        ,
#if defined(ENABLE_OVERLOADING)
    dBusErrorEntry_dbusErrorName            ,
#endif
    getDBusErrorEntryDbusErrorName          ,
    setDBusErrorEntryDbusErrorName          ,


-- ** errorCode #attr:errorCode#
-- | An error code.

#if defined(ENABLE_OVERLOADING)
    dBusErrorEntry_errorCode                ,
#endif
    getDBusErrorEntryErrorCode              ,
    setDBusErrorEntryErrorCode              ,




    ) 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.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


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

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

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


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

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


-- | Get the value of the “@error_code@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusErrorEntry #errorCode
-- @
getDBusErrorEntryErrorCode :: MonadIO m => DBusErrorEntry -> m Int32
getDBusErrorEntryErrorCode :: DBusErrorEntry -> m Int32
getDBusErrorEntryErrorCode DBusErrorEntry
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ DBusErrorEntry -> (Ptr DBusErrorEntry -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusErrorEntry
s ((Ptr DBusErrorEntry -> IO Int32) -> IO Int32)
-> (Ptr DBusErrorEntry -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr DBusErrorEntry
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusErrorEntry
ptr Ptr DBusErrorEntry -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@error_code@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dBusErrorEntry [ #errorCode 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusErrorEntryErrorCode :: MonadIO m => DBusErrorEntry -> Int32 -> m ()
setDBusErrorEntryErrorCode :: DBusErrorEntry -> Int32 -> m ()
setDBusErrorEntryErrorCode DBusErrorEntry
s Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusErrorEntry -> (Ptr DBusErrorEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusErrorEntry
s ((Ptr DBusErrorEntry -> IO ()) -> IO ())
-> (Ptr DBusErrorEntry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusErrorEntry
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusErrorEntry
ptr Ptr DBusErrorEntry -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data DBusErrorEntryErrorCodeFieldInfo
instance AttrInfo DBusErrorEntryErrorCodeFieldInfo where
    type AttrBaseTypeConstraint DBusErrorEntryErrorCodeFieldInfo = (~) DBusErrorEntry
    type AttrAllowedOps DBusErrorEntryErrorCodeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DBusErrorEntryErrorCodeFieldInfo = (~) Int32
    type AttrTransferTypeConstraint DBusErrorEntryErrorCodeFieldInfo = (~)Int32
    type AttrTransferType DBusErrorEntryErrorCodeFieldInfo = Int32
    type AttrGetType DBusErrorEntryErrorCodeFieldInfo = Int32
    type AttrLabel DBusErrorEntryErrorCodeFieldInfo = "error_code"
    type AttrOrigin DBusErrorEntryErrorCodeFieldInfo = DBusErrorEntry
    attrGet = getDBusErrorEntryErrorCode
    attrSet = setDBusErrorEntryErrorCode
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

dBusErrorEntry_errorCode :: AttrLabelProxy "errorCode"
dBusErrorEntry_errorCode = AttrLabelProxy

#endif


-- | Get the value of the “@dbus_error_name@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dBusErrorEntry #dbusErrorName
-- @
getDBusErrorEntryDbusErrorName :: MonadIO m => DBusErrorEntry -> m (Maybe T.Text)
getDBusErrorEntryDbusErrorName :: DBusErrorEntry -> m (Maybe Text)
getDBusErrorEntryDbusErrorName DBusErrorEntry
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
$ DBusErrorEntry
-> (Ptr DBusErrorEntry -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusErrorEntry
s ((Ptr DBusErrorEntry -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr DBusErrorEntry -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr DBusErrorEntry
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr DBusErrorEntry
ptr Ptr DBusErrorEntry -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: 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 “@dbus_error_name@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' dBusErrorEntry [ #dbusErrorName 'Data.GI.Base.Attributes.:=' value ]
-- @
setDBusErrorEntryDbusErrorName :: MonadIO m => DBusErrorEntry -> CString -> m ()
setDBusErrorEntryDbusErrorName :: DBusErrorEntry -> CString -> m ()
setDBusErrorEntryDbusErrorName DBusErrorEntry
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
$ DBusErrorEntry -> (Ptr DBusErrorEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusErrorEntry
s ((Ptr DBusErrorEntry -> IO ()) -> IO ())
-> (Ptr DBusErrorEntry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusErrorEntry
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusErrorEntry
ptr Ptr DBusErrorEntry -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
val :: CString)

-- | Set the value of the “@dbus_error_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' #dbusErrorName
-- @
clearDBusErrorEntryDbusErrorName :: MonadIO m => DBusErrorEntry -> m ()
clearDBusErrorEntryDbusErrorName :: DBusErrorEntry -> m ()
clearDBusErrorEntryDbusErrorName DBusErrorEntry
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ DBusErrorEntry -> (Ptr DBusErrorEntry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DBusErrorEntry
s ((Ptr DBusErrorEntry -> IO ()) -> IO ())
-> (Ptr DBusErrorEntry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DBusErrorEntry
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DBusErrorEntry
ptr Ptr DBusErrorEntry -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data DBusErrorEntryDbusErrorNameFieldInfo
instance AttrInfo DBusErrorEntryDbusErrorNameFieldInfo where
    type AttrBaseTypeConstraint DBusErrorEntryDbusErrorNameFieldInfo = (~) DBusErrorEntry
    type AttrAllowedOps DBusErrorEntryDbusErrorNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint DBusErrorEntryDbusErrorNameFieldInfo = (~) CString
    type AttrTransferTypeConstraint DBusErrorEntryDbusErrorNameFieldInfo = (~)CString
    type AttrTransferType DBusErrorEntryDbusErrorNameFieldInfo = CString
    type AttrGetType DBusErrorEntryDbusErrorNameFieldInfo = Maybe T.Text
    type AttrLabel DBusErrorEntryDbusErrorNameFieldInfo = "dbus_error_name"
    type AttrOrigin DBusErrorEntryDbusErrorNameFieldInfo = DBusErrorEntry
    attrGet = getDBusErrorEntryDbusErrorName
    attrSet = setDBusErrorEntryDbusErrorName
    attrConstruct = undefined
    attrClear = clearDBusErrorEntryDbusErrorName
    attrTransfer _ v = do
        return v

dBusErrorEntry_dbusErrorName :: AttrLabelProxy "dbusErrorName"
dBusErrorEntry_dbusErrorName = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DBusErrorEntry
type instance O.AttributeList DBusErrorEntry = DBusErrorEntryAttributeList
type DBusErrorEntryAttributeList = ('[ '("errorCode", DBusErrorEntryErrorCodeFieldInfo), '("dbusErrorName", DBusErrorEntryDbusErrorNameFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif