{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Structs.IMContextInfo
(
IMContextInfo(..) ,
newZeroIMContextInfo ,
#if defined(ENABLE_OVERLOADING)
ResolveIMContextInfoMethod ,
#endif
clearIMContextInfoContextId ,
getIMContextInfoContextId ,
#if defined(ENABLE_OVERLOADING)
iMContextInfo_contextId ,
#endif
setIMContextInfoContextId ,
clearIMContextInfoContextName ,
getIMContextInfoContextName ,
#if defined(ENABLE_OVERLOADING)
iMContextInfo_contextName ,
#endif
setIMContextInfoContextName ,
clearIMContextInfoDefaultLocales ,
getIMContextInfoDefaultLocales ,
#if defined(ENABLE_OVERLOADING)
iMContextInfo_defaultLocales ,
#endif
setIMContextInfoDefaultLocales ,
clearIMContextInfoDomain ,
getIMContextInfoDomain ,
#if defined(ENABLE_OVERLOADING)
iMContextInfo_domain ,
#endif
setIMContextInfoDomain ,
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.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.GHashTable as B.GHT
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.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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
newtype IMContextInfo = IMContextInfo (SP.ManagedPtr IMContextInfo)
deriving (IMContextInfo -> IMContextInfo -> Bool
(IMContextInfo -> IMContextInfo -> Bool)
-> (IMContextInfo -> IMContextInfo -> Bool) -> Eq IMContextInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IMContextInfo -> IMContextInfo -> Bool
== :: IMContextInfo -> IMContextInfo -> Bool
$c/= :: IMContextInfo -> IMContextInfo -> Bool
/= :: IMContextInfo -> IMContextInfo -> Bool
Eq)
instance SP.ManagedPtrNewtype IMContextInfo where
toManagedPtr :: IMContextInfo -> ManagedPtr IMContextInfo
toManagedPtr (IMContextInfo ManagedPtr IMContextInfo
p) = ManagedPtr IMContextInfo
p
instance BoxedPtr IMContextInfo where
boxedPtrCopy :: IMContextInfo -> IO IMContextInfo
boxedPtrCopy = \IMContextInfo
p -> IMContextInfo
-> (Ptr IMContextInfo -> IO IMContextInfo) -> IO IMContextInfo
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr IMContextInfo
p (Int -> Ptr IMContextInfo -> IO (Ptr IMContextInfo)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
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, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr IMContextInfo -> IMContextInfo
IMContextInfo)
boxedPtrFree :: IMContextInfo -> IO ()
boxedPtrFree = \IMContextInfo
x -> IMContextInfo -> (Ptr IMContextInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr IMContextInfo
x Ptr IMContextInfo -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr IMContextInfo where
boxedPtrCalloc :: IO (Ptr IMContextInfo)
boxedPtrCalloc = Int -> IO (Ptr IMContextInfo)
forall a. Int -> IO (Ptr a)
callocBytes Int
40
newZeroIMContextInfo :: MonadIO m => m IMContextInfo
newZeroIMContextInfo :: forall (m :: * -> *). MonadIO m => m IMContextInfo
newZeroIMContextInfo = IO IMContextInfo -> m IMContextInfo
forall a. IO a -> m a
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. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr IMContextInfo)
-> (Ptr IMContextInfo -> IO IMContextInfo) -> IO IMContextInfo
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr IMContextInfo -> IMContextInfo)
-> Ptr IMContextInfo -> IO IMContextInfo
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr IMContextInfo -> IMContextInfo
IMContextInfo
instance tag ~ 'AttrSet => Constructible IMContextInfo tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr IMContextInfo -> IMContextInfo)
-> [AttrOp IMContextInfo tag] -> m IMContextInfo
new ManagedPtr IMContextInfo -> IMContextInfo
_ [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 a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return IMContextInfo
o
getIMContextInfoContextId :: MonadIO m => IMContextInfo -> m (Maybe T.Text)
getIMContextInfoContextId :: forall (m :: * -> *). MonadIO m => IMContextInfo -> m (Maybe Text)
getIMContextInfoContextId IMContextInfo
s = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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 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` 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result
setIMContextInfoContextId :: MonadIO m => IMContextInfo -> CString -> m ()
setIMContextInfoContextId :: forall (m :: * -> *). MonadIO m => IMContextInfo -> CString -> m ()
setIMContextInfoContextId IMContextInfo
s CString
val = IO () -> m ()
forall a. IO a -> m a
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 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` Int
0) (CString
val :: CString)
clearIMContextInfoContextId :: MonadIO m => IMContextInfo -> m ()
clearIMContextInfoContextId :: forall (m :: * -> *). MonadIO m => IMContextInfo -> m ()
clearIMContextInfoContextId IMContextInfo
s = IO () -> m ()
forall a. IO a -> m a
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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.IMContextInfo.contextId"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-IMContextInfo.html#g:attr:contextId"
})
iMContextInfo_contextId :: AttrLabelProxy "contextId"
iMContextInfo_contextId = AttrLabelProxy
#endif
getIMContextInfoContextName :: MonadIO m => IMContextInfo -> m (Maybe T.Text)
getIMContextInfoContextName :: forall (m :: * -> *). MonadIO m => IMContextInfo -> m (Maybe Text)
getIMContextInfoContextName IMContextInfo
s = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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 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` 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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result
setIMContextInfoContextName :: MonadIO m => IMContextInfo -> CString -> m ()
setIMContextInfoContextName :: forall (m :: * -> *). MonadIO m => IMContextInfo -> CString -> m ()
setIMContextInfoContextName IMContextInfo
s CString
val = IO () -> m ()
forall a. IO a -> m a
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 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` Int
8) (CString
val :: CString)
clearIMContextInfoContextName :: MonadIO m => IMContextInfo -> m ()
clearIMContextInfoContextName :: forall (m :: * -> *). MonadIO m => IMContextInfo -> m ()
clearIMContextInfoContextName IMContextInfo
s = IO () -> m ()
forall a. IO a -> m a
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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.IMContextInfo.contextName"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-IMContextInfo.html#g:attr:contextName"
})
iMContextInfo_contextName :: AttrLabelProxy "contextName"
iMContextInfo_contextName = AttrLabelProxy
#endif
getIMContextInfoDomain :: MonadIO m => IMContextInfo -> m (Maybe T.Text)
getIMContextInfoDomain :: forall (m :: * -> *). MonadIO m => IMContextInfo -> m (Maybe Text)
getIMContextInfoDomain IMContextInfo
s = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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 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` Int
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
$ \CString
val' -> do
Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result
setIMContextInfoDomain :: MonadIO m => IMContextInfo -> CString -> m ()
setIMContextInfoDomain :: forall (m :: * -> *). MonadIO m => IMContextInfo -> CString -> m ()
setIMContextInfoDomain IMContextInfo
s CString
val = IO () -> m ()
forall a. IO a -> m a
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 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` Int
16) (CString
val :: CString)
clearIMContextInfoDomain :: MonadIO m => IMContextInfo -> m ()
clearIMContextInfoDomain :: forall (m :: * -> *). MonadIO m => IMContextInfo -> m ()
clearIMContextInfoDomain IMContextInfo
s = IO () -> m ()
forall a. IO a -> m a
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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.IMContextInfo.domain"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-IMContextInfo.html#g:attr:domain"
})
iMContextInfo_domain :: AttrLabelProxy "domain"
iMContextInfo_domain = AttrLabelProxy
#endif
getIMContextInfoDomainDirname :: MonadIO m => IMContextInfo -> m (Maybe T.Text)
getIMContextInfoDomainDirname :: forall (m :: * -> *). MonadIO m => IMContextInfo -> m (Maybe Text)
getIMContextInfoDomainDirname IMContextInfo
s = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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 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` Int
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
$ \CString
val' -> do
Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result
setIMContextInfoDomainDirname :: MonadIO m => IMContextInfo -> CString -> m ()
setIMContextInfoDomainDirname :: forall (m :: * -> *). MonadIO m => IMContextInfo -> CString -> m ()
setIMContextInfoDomainDirname IMContextInfo
s CString
val = IO () -> m ()
forall a. IO a -> m a
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 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` Int
24) (CString
val :: CString)
clearIMContextInfoDomainDirname :: MonadIO m => IMContextInfo -> m ()
clearIMContextInfoDomainDirname :: forall (m :: * -> *). MonadIO m => IMContextInfo -> m ()
clearIMContextInfoDomainDirname IMContextInfo
s = IO () -> m ()
forall a. IO a -> m a
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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.IMContextInfo.domainDirname"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-IMContextInfo.html#g:attr:domainDirname"
})
iMContextInfo_domainDirname :: AttrLabelProxy "domainDirname"
iMContextInfo_domainDirname = AttrLabelProxy
#endif
getIMContextInfoDefaultLocales :: MonadIO m => IMContextInfo -> m (Maybe T.Text)
getIMContextInfoDefaultLocales :: forall (m :: * -> *). MonadIO m => IMContextInfo -> m (Maybe Text)
getIMContextInfoDefaultLocales IMContextInfo
s = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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 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` Int
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
$ \CString
val' -> do
Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result
setIMContextInfoDefaultLocales :: MonadIO m => IMContextInfo -> CString -> m ()
setIMContextInfoDefaultLocales :: forall (m :: * -> *). MonadIO m => IMContextInfo -> CString -> m ()
setIMContextInfoDefaultLocales IMContextInfo
s CString
val = IO () -> m ()
forall a. IO a -> m a
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 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` Int
32) (CString
val :: CString)
clearIMContextInfoDefaultLocales :: MonadIO m => IMContextInfo -> m ()
clearIMContextInfoDefaultLocales :: forall (m :: * -> *). MonadIO m => IMContextInfo -> m ()
clearIMContextInfoDefaultLocales IMContextInfo
s = IO () -> m ()
forall a. IO a -> m a
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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.IMContextInfo.defaultLocales"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-IMContextInfo.html#g:attr:defaultLocales"
})
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, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveIMContextInfoMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveIMContextInfoMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveIMContextInfoMethod t IMContextInfo, O.OverloadedMethod 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
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveIMContextInfoMethod t IMContextInfo, O.OverloadedMethod info IMContextInfo p, R.HasField t IMContextInfo p) => R.HasField t IMContextInfo p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveIMContextInfoMethod t IMContextInfo, O.OverloadedMethodInfo info IMContextInfo) => OL.IsLabel t (O.MethodProxy info IMContextInfo) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif