{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Bookkeeping information about a loadable input method.

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

module GI.Gtk.Structs.IMContextInfo
    ( 

-- * Exported types
    IMContextInfo(..)                       ,
    newZeroIMContextInfo                    ,
    noIMContextInfo                         ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveIMContextInfoMethod              ,
#endif




 -- * Properties
-- ** contextId #attr:contextId#
-- | The unique identification string of the input method.

    clearIMContextInfoContextId             ,
    getIMContextInfoContextId               ,
#if defined(ENABLE_OVERLOADING)
    iMContextInfo_contextId                 ,
#endif
    setIMContextInfoContextId               ,


-- ** contextName #attr:contextName#
-- | The human-readable name of the input method.

    clearIMContextInfoContextName           ,
    getIMContextInfoContextName             ,
#if defined(ENABLE_OVERLOADING)
    iMContextInfo_contextName               ,
#endif
    setIMContextInfoContextName             ,


-- ** defaultLocales #attr:defaultLocales#
-- | A colon-separated list of locales where this input method
--   should be the default. The asterisk “*” sets the default for all locales.

    clearIMContextInfoDefaultLocales        ,
    getIMContextInfoDefaultLocales          ,
#if defined(ENABLE_OVERLOADING)
    iMContextInfo_defaultLocales            ,
#endif
    setIMContextInfoDefaultLocales          ,


-- ** domain #attr:domain#
-- | Translation domain to be used with @/dgettext()/@

    clearIMContextInfoDomain                ,
    getIMContextInfoDomain                  ,
#if defined(ENABLE_OVERLOADING)
    iMContextInfo_domain                    ,
#endif
    setIMContextInfoDomain                  ,


-- ** domainDirname #attr:domainDirname#
-- | Name of locale directory for use with @/bindtextdomain()/@

    clearIMContextInfoDomainDirname         ,
    getIMContextInfoDomainDirname           ,
#if defined(ENABLE_OVERLOADING)
    iMContextInfo_domainDirname             ,
#endif
    setIMContextInfoDomainDirname           ,




    ) 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.GI.Base.Signals as B.Signals
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 IMContextInfo = IMContextInfo (ManagedPtr IMContextInfo)
    deriving (IMContextInfo -> IMContextInfo -> Bool
(IMContextInfo -> IMContextInfo -> Bool)
-> (IMContextInfo -> IMContextInfo -> Bool) -> Eq IMContextInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IMContextInfo -> IMContextInfo -> Bool
$c/= :: IMContextInfo -> IMContextInfo -> Bool
== :: IMContextInfo -> IMContextInfo -> Bool
$c== :: IMContextInfo -> IMContextInfo -> Bool
Eq)
instance WrappedPtr IMContextInfo where
    wrappedPtrCalloc :: IO (Ptr IMContextInfo)
wrappedPtrCalloc = Int -> IO (Ptr IMContextInfo)
forall a. Int -> IO (Ptr a)
callocBytes 40
    wrappedPtrCopy :: IMContextInfo -> IO IMContextInfo
wrappedPtrCopy = \p :: IMContextInfo
p -> IMContextInfo
-> (Ptr IMContextInfo -> IO IMContextInfo) -> IO IMContextInfo
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr IMContextInfo
p (Int -> Ptr IMContextInfo -> IO (Ptr IMContextInfo)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 40 (Ptr IMContextInfo -> IO (Ptr IMContextInfo))
-> (Ptr IMContextInfo -> IO IMContextInfo)
-> Ptr IMContextInfo
-> IO IMContextInfo
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr IMContextInfo -> IMContextInfo)
-> Ptr IMContextInfo -> IO IMContextInfo
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr IMContextInfo -> IMContextInfo
IMContextInfo)
    wrappedPtrFree :: Maybe (GDestroyNotify IMContextInfo)
wrappedPtrFree = GDestroyNotify IMContextInfo
-> Maybe (GDestroyNotify IMContextInfo)
forall a. a -> Maybe a
Just GDestroyNotify IMContextInfo
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

-- | Construct a `IMContextInfo` struct initialized to zero.
newZeroIMContextInfo :: MonadIO m => m IMContextInfo
newZeroIMContextInfo :: m IMContextInfo
newZeroIMContextInfo = IO IMContextInfo -> m IMContextInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IMContextInfo -> m IMContextInfo)
-> IO IMContextInfo -> m IMContextInfo
forall a b. (a -> b) -> a -> b
$ IO (Ptr IMContextInfo)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr IMContextInfo)
-> (Ptr IMContextInfo -> IO IMContextInfo) -> IO IMContextInfo
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr IMContextInfo -> IMContextInfo)
-> Ptr IMContextInfo -> IO IMContextInfo
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr IMContextInfo -> IMContextInfo
IMContextInfo

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


-- | A convenience alias for `Nothing` :: `Maybe` `IMContextInfo`.
noIMContextInfo :: Maybe IMContextInfo
noIMContextInfo :: Maybe IMContextInfo
noIMContextInfo = Maybe IMContextInfo
forall a. Maybe a
Nothing

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

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

#if defined(ENABLE_OVERLOADING)
data IMContextInfoContextIdFieldInfo
instance AttrInfo IMContextInfoContextIdFieldInfo where
    type AttrBaseTypeConstraint IMContextInfoContextIdFieldInfo = (~) IMContextInfo
    type AttrAllowedOps IMContextInfoContextIdFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint IMContextInfoContextIdFieldInfo = (~) CString
    type AttrTransferTypeConstraint IMContextInfoContextIdFieldInfo = (~)CString
    type AttrTransferType IMContextInfoContextIdFieldInfo = CString
    type AttrGetType IMContextInfoContextIdFieldInfo = Maybe T.Text
    type AttrLabel IMContextInfoContextIdFieldInfo = "context_id"
    type AttrOrigin IMContextInfoContextIdFieldInfo = IMContextInfo
    attrGet = getIMContextInfoContextId
    attrSet = setIMContextInfoContextId
    attrConstruct = undefined
    attrClear = clearIMContextInfoContextId
    attrTransfer _ v = do
        return v

iMContextInfo_contextId :: AttrLabelProxy "contextId"
iMContextInfo_contextId = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data IMContextInfoContextNameFieldInfo
instance AttrInfo IMContextInfoContextNameFieldInfo where
    type AttrBaseTypeConstraint IMContextInfoContextNameFieldInfo = (~) IMContextInfo
    type AttrAllowedOps IMContextInfoContextNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint IMContextInfoContextNameFieldInfo = (~) CString
    type AttrTransferTypeConstraint IMContextInfoContextNameFieldInfo = (~)CString
    type AttrTransferType IMContextInfoContextNameFieldInfo = CString
    type AttrGetType IMContextInfoContextNameFieldInfo = Maybe T.Text
    type AttrLabel IMContextInfoContextNameFieldInfo = "context_name"
    type AttrOrigin IMContextInfoContextNameFieldInfo = IMContextInfo
    attrGet = getIMContextInfoContextName
    attrSet = setIMContextInfoContextName
    attrConstruct = undefined
    attrClear = clearIMContextInfoContextName
    attrTransfer _ v = do
        return v

iMContextInfo_contextName :: AttrLabelProxy "contextName"
iMContextInfo_contextName = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data IMContextInfoDomainFieldInfo
instance AttrInfo IMContextInfoDomainFieldInfo where
    type AttrBaseTypeConstraint IMContextInfoDomainFieldInfo = (~) IMContextInfo
    type AttrAllowedOps IMContextInfoDomainFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint IMContextInfoDomainFieldInfo = (~) CString
    type AttrTransferTypeConstraint IMContextInfoDomainFieldInfo = (~)CString
    type AttrTransferType IMContextInfoDomainFieldInfo = CString
    type AttrGetType IMContextInfoDomainFieldInfo = Maybe T.Text
    type AttrLabel IMContextInfoDomainFieldInfo = "domain"
    type AttrOrigin IMContextInfoDomainFieldInfo = IMContextInfo
    attrGet = getIMContextInfoDomain
    attrSet = setIMContextInfoDomain
    attrConstruct = undefined
    attrClear = clearIMContextInfoDomain
    attrTransfer _ v = do
        return v

iMContextInfo_domain :: AttrLabelProxy "domain"
iMContextInfo_domain = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data IMContextInfoDomainDirnameFieldInfo
instance AttrInfo IMContextInfoDomainDirnameFieldInfo where
    type AttrBaseTypeConstraint IMContextInfoDomainDirnameFieldInfo = (~) IMContextInfo
    type AttrAllowedOps IMContextInfoDomainDirnameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint IMContextInfoDomainDirnameFieldInfo = (~) CString
    type AttrTransferTypeConstraint IMContextInfoDomainDirnameFieldInfo = (~)CString
    type AttrTransferType IMContextInfoDomainDirnameFieldInfo = CString
    type AttrGetType IMContextInfoDomainDirnameFieldInfo = Maybe T.Text
    type AttrLabel IMContextInfoDomainDirnameFieldInfo = "domain_dirname"
    type AttrOrigin IMContextInfoDomainDirnameFieldInfo = IMContextInfo
    attrGet = getIMContextInfoDomainDirname
    attrSet = setIMContextInfoDomainDirname
    attrConstruct = undefined
    attrClear = clearIMContextInfoDomainDirname
    attrTransfer _ v = do
        return v

iMContextInfo_domainDirname :: AttrLabelProxy "domainDirname"
iMContextInfo_domainDirname = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data IMContextInfoDefaultLocalesFieldInfo
instance AttrInfo IMContextInfoDefaultLocalesFieldInfo where
    type AttrBaseTypeConstraint IMContextInfoDefaultLocalesFieldInfo = (~) IMContextInfo
    type AttrAllowedOps IMContextInfoDefaultLocalesFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint IMContextInfoDefaultLocalesFieldInfo = (~) CString
    type AttrTransferTypeConstraint IMContextInfoDefaultLocalesFieldInfo = (~)CString
    type AttrTransferType IMContextInfoDefaultLocalesFieldInfo = CString
    type AttrGetType IMContextInfoDefaultLocalesFieldInfo = Maybe T.Text
    type AttrLabel IMContextInfoDefaultLocalesFieldInfo = "default_locales"
    type AttrOrigin IMContextInfoDefaultLocalesFieldInfo = IMContextInfo
    attrGet = getIMContextInfoDefaultLocales
    attrSet = setIMContextInfoDefaultLocales
    attrConstruct = undefined
    attrClear = clearIMContextInfoDefaultLocales
    attrTransfer _ v = do
        return v

iMContextInfo_defaultLocales :: AttrLabelProxy "defaultLocales"
iMContextInfo_defaultLocales = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList IMContextInfo
type instance O.AttributeList IMContextInfo = IMContextInfoAttributeList
type IMContextInfoAttributeList = ('[ '("contextId", IMContextInfoContextIdFieldInfo), '("contextName", IMContextInfoContextNameFieldInfo), '("domain", IMContextInfoDomainFieldInfo), '("domainDirname", IMContextInfoDomainDirnameFieldInfo), '("defaultLocales", IMContextInfoDefaultLocalesFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif