{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.IMContextSimple
(
IMContextSimple(..) ,
IsIMContextSimple ,
toIMContextSimple ,
#if defined(ENABLE_OVERLOADING)
ResolveIMContextSimpleMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
IMContextSimpleAddComposeFileMethodInfo ,
#endif
iMContextSimpleAddComposeFile ,
iMContextSimpleNew ,
) 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 GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Objects.IMContext as Gtk.IMContext
newtype IMContextSimple = IMContextSimple (SP.ManagedPtr IMContextSimple)
deriving (IMContextSimple -> IMContextSimple -> Bool
(IMContextSimple -> IMContextSimple -> Bool)
-> (IMContextSimple -> IMContextSimple -> Bool)
-> Eq IMContextSimple
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IMContextSimple -> IMContextSimple -> Bool
$c/= :: IMContextSimple -> IMContextSimple -> Bool
== :: IMContextSimple -> IMContextSimple -> Bool
$c== :: IMContextSimple -> IMContextSimple -> Bool
Eq)
instance SP.ManagedPtrNewtype IMContextSimple where
toManagedPtr :: IMContextSimple -> ManagedPtr IMContextSimple
toManagedPtr (IMContextSimple ManagedPtr IMContextSimple
p) = ManagedPtr IMContextSimple
p
foreign import ccall "gtk_im_context_simple_get_type"
c_gtk_im_context_simple_get_type :: IO B.Types.GType
instance B.Types.TypedObject IMContextSimple where
glibType :: IO GType
glibType = IO GType
c_gtk_im_context_simple_get_type
instance B.Types.GObject IMContextSimple
instance B.GValue.IsGValue IMContextSimple where
toGValue :: IMContextSimple -> IO GValue
toGValue IMContextSimple
o = do
GType
gtype <- IO GType
c_gtk_im_context_simple_get_type
IMContextSimple -> (Ptr IMContextSimple -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr IMContextSimple
o (GType
-> (GValue -> Ptr IMContextSimple -> IO ())
-> Ptr IMContextSimple
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr IMContextSimple -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO IMContextSimple
fromGValue GValue
gv = do
Ptr IMContextSimple
ptr <- GValue -> IO (Ptr IMContextSimple)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr IMContextSimple)
(ManagedPtr IMContextSimple -> IMContextSimple)
-> Ptr IMContextSimple -> IO IMContextSimple
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr IMContextSimple -> IMContextSimple
IMContextSimple Ptr IMContextSimple
ptr
class (SP.GObject o, O.IsDescendantOf IMContextSimple o) => IsIMContextSimple o
instance (SP.GObject o, O.IsDescendantOf IMContextSimple o) => IsIMContextSimple o
instance O.HasParentTypes IMContextSimple
type instance O.ParentTypes IMContextSimple = '[Gtk.IMContext.IMContext, GObject.Object.Object]
toIMContextSimple :: (MonadIO m, IsIMContextSimple o) => o -> m IMContextSimple
toIMContextSimple :: o -> m IMContextSimple
toIMContextSimple = IO IMContextSimple -> m IMContextSimple
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IMContextSimple -> m IMContextSimple)
-> (o -> IO IMContextSimple) -> o -> m IMContextSimple
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr IMContextSimple -> IMContextSimple)
-> o -> IO IMContextSimple
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr IMContextSimple -> IMContextSimple
IMContextSimple
#if defined(ENABLE_OVERLOADING)
type family ResolveIMContextSimpleMethod (t :: Symbol) (o :: *) :: * where
ResolveIMContextSimpleMethod "addComposeFile" o = IMContextSimpleAddComposeFileMethodInfo
ResolveIMContextSimpleMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveIMContextSimpleMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveIMContextSimpleMethod "deleteSurrounding" o = Gtk.IMContext.IMContextDeleteSurroundingMethodInfo
ResolveIMContextSimpleMethod "filterKeypress" o = Gtk.IMContext.IMContextFilterKeypressMethodInfo
ResolveIMContextSimpleMethod "focusIn" o = Gtk.IMContext.IMContextFocusInMethodInfo
ResolveIMContextSimpleMethod "focusOut" o = Gtk.IMContext.IMContextFocusOutMethodInfo
ResolveIMContextSimpleMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveIMContextSimpleMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveIMContextSimpleMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveIMContextSimpleMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveIMContextSimpleMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveIMContextSimpleMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveIMContextSimpleMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveIMContextSimpleMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveIMContextSimpleMethod "reset" o = Gtk.IMContext.IMContextResetMethodInfo
ResolveIMContextSimpleMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveIMContextSimpleMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveIMContextSimpleMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveIMContextSimpleMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveIMContextSimpleMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveIMContextSimpleMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveIMContextSimpleMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveIMContextSimpleMethod "getPreeditString" o = Gtk.IMContext.IMContextGetPreeditStringMethodInfo
ResolveIMContextSimpleMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveIMContextSimpleMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveIMContextSimpleMethod "getSurrounding" o = Gtk.IMContext.IMContextGetSurroundingMethodInfo
ResolveIMContextSimpleMethod "setClientWindow" o = Gtk.IMContext.IMContextSetClientWindowMethodInfo
ResolveIMContextSimpleMethod "setCursorLocation" o = Gtk.IMContext.IMContextSetCursorLocationMethodInfo
ResolveIMContextSimpleMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveIMContextSimpleMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveIMContextSimpleMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveIMContextSimpleMethod "setSurrounding" o = Gtk.IMContext.IMContextSetSurroundingMethodInfo
ResolveIMContextSimpleMethod "setUsePreedit" o = Gtk.IMContext.IMContextSetUsePreeditMethodInfo
ResolveIMContextSimpleMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveIMContextSimpleMethod t IMContextSimple, O.MethodInfo info IMContextSimple p) => OL.IsLabel t (IMContextSimple -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList IMContextSimple
type instance O.AttributeList IMContextSimple = IMContextSimpleAttributeList
type IMContextSimpleAttributeList = ('[ '("inputHints", Gtk.IMContext.IMContextInputHintsPropertyInfo), '("inputPurpose", Gtk.IMContext.IMContextInputPurposePropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList IMContextSimple = IMContextSimpleSignalList
type IMContextSimpleSignalList = ('[ '("commit", Gtk.IMContext.IMContextCommitSignalInfo), '("deleteSurrounding", Gtk.IMContext.IMContextDeleteSurroundingSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("preeditChanged", Gtk.IMContext.IMContextPreeditChangedSignalInfo), '("preeditEnd", Gtk.IMContext.IMContextPreeditEndSignalInfo), '("preeditStart", Gtk.IMContext.IMContextPreeditStartSignalInfo), '("retrieveSurrounding", Gtk.IMContext.IMContextRetrieveSurroundingSignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_im_context_simple_new" gtk_im_context_simple_new ::
IO (Ptr IMContextSimple)
iMContextSimpleNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m IMContextSimple
iMContextSimpleNew :: m IMContextSimple
iMContextSimpleNew = IO IMContextSimple -> m IMContextSimple
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IMContextSimple -> m IMContextSimple)
-> IO IMContextSimple -> m IMContextSimple
forall a b. (a -> b) -> a -> b
$ do
Ptr IMContextSimple
result <- IO (Ptr IMContextSimple)
gtk_im_context_simple_new
Text -> Ptr IMContextSimple -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"iMContextSimpleNew" Ptr IMContextSimple
result
IMContextSimple
result' <- ((ManagedPtr IMContextSimple -> IMContextSimple)
-> Ptr IMContextSimple -> IO IMContextSimple
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr IMContextSimple -> IMContextSimple
IMContextSimple) Ptr IMContextSimple
result
IMContextSimple -> IO IMContextSimple
forall (m :: * -> *) a. Monad m => a -> m a
return IMContextSimple
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_im_context_simple_add_compose_file" gtk_im_context_simple_add_compose_file ::
Ptr IMContextSimple ->
CString ->
IO ()
iMContextSimpleAddComposeFile ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContextSimple a) =>
a
-> T.Text
-> m ()
iMContextSimpleAddComposeFile :: a -> Text -> m ()
iMContextSimpleAddComposeFile a
contextSimple Text
composeFile = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr IMContextSimple
contextSimple' <- a -> IO (Ptr IMContextSimple)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
contextSimple
CString
composeFile' <- Text -> IO CString
textToCString Text
composeFile
Ptr IMContextSimple -> CString -> IO ()
gtk_im_context_simple_add_compose_file Ptr IMContextSimple
contextSimple' CString
composeFile'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
contextSimple
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
composeFile'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data IMContextSimpleAddComposeFileMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsIMContextSimple a) => O.MethodInfo IMContextSimpleAddComposeFileMethodInfo a signature where
overloadedMethod = iMContextSimpleAddComposeFile
#endif