{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gtk.Objects.IMContext.IMContext' defines the interface for GTK+ input methods. An input method
-- is used by GTK+ text input widgets like t'GI.Gtk.Objects.Entry.Entry' to map from key events to
-- Unicode character strings.
-- 
-- The default input method can be set programmatically via the
-- t'GI.Gtk.Objects.Settings.Settings':@/gtk-im-module/@ GtkSettings property. Alternatively, you may set
-- the GTK_IM_MODULE environment variable as documented in
-- [Running GTK+ Applications][gtk-running].
-- 
-- The t'GI.Gtk.Objects.Entry.Entry' t'GI.Gtk.Objects.Entry.Entry':@/im-module/@ and t'GI.Gtk.Objects.TextView.TextView' t'GI.Gtk.Objects.TextView.TextView':@/im-module/@
-- properties may also be used to set input methods for specific widget
-- instances. For instance, a certain entry widget might be expected to contain
-- certain characters which would be easier to input with a certain input
-- method.
-- 
-- An input method may consume multiple key events in sequence and finally
-- output the composed result. This is called preediting, and an input method
-- may provide feedback about this process by displaying the intermediate
-- composition states as preedit text. For instance, the default GTK+ input
-- method implements the input of arbitrary Unicode code points by holding down
-- the Control and Shift keys and then typing “U” followed by the hexadecimal
-- digits of the code point.  When releasing the Control and Shift keys,
-- preediting ends and the character is inserted as text. Ctrl+Shift+u20AC for
-- example results in the € sign.
-- 
-- Additional input methods can be made available for use by GTK+ widgets as
-- loadable modules. An input method module is a small shared library which
-- implements a subclass of t'GI.Gtk.Objects.IMContext.IMContext' or t'GI.Gtk.Objects.IMContextSimple.IMContextSimple' and exports
-- these four functions:
-- 
-- 
-- === /C code/
-- >
-- >void im_module_init(GTypeModule *module);
-- 
-- This function should register the t'GType' of the t'GI.Gtk.Objects.IMContext.IMContext' subclass which
-- implements the input method by means of 'GI.GObject.Objects.TypeModule.typeModuleRegisterType'. Note
-- that 'GI.GObject.Functions.typeRegisterStatic' cannot be used as the type needs to be
-- registered dynamically.
-- 
-- 
-- === /C code/
-- >
-- >void im_module_exit(void);
-- 
-- Here goes any cleanup code your input method might require on module unload.
-- 
-- 
-- === /C code/
-- >
-- >void im_module_list(const GtkIMContextInfo ***contexts, int *n_contexts)
-- >{
-- >  *contexts = info_list;
-- >  *n_contexts = G_N_ELEMENTS (info_list);
-- >}
-- 
-- This function returns the list of input methods provided by the module. The
-- example implementation above shows a common solution and simply returns a
-- pointer to statically defined array of t'GI.Gtk.Structs.IMContextInfo.IMContextInfo' items for each
-- provided input method.
-- 
-- 
-- === /C code/
-- >
-- >GtkIMContext * im_module_create(const gchar *context_id);
-- 
-- This function should return a pointer to a newly created instance of the
-- t'GI.Gtk.Objects.IMContext.IMContext' subclass identified by /@contextId@/. The context ID is the same
-- as specified in the t'GI.Gtk.Structs.IMContextInfo.IMContextInfo' array returned by @/im_module_list()/@.
-- 
-- After a new loadable input method module has been installed on the system,
-- the configuration file @gtk.immodules@ needs to be
-- regenerated by [gtk-query-immodules-3.0][gtk-query-immodules-3.0],
-- in order for the new input method to become available to GTK+ applications.

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

module GI.Gtk.Objects.IMContext
    ( 

-- * Exported types
    IMContext(..)                           ,
    IsIMContext                             ,
    toIMContext                             ,
    noIMContext                             ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveIMContextMethod                  ,
#endif


-- ** deleteSurrounding #method:deleteSurrounding#

#if defined(ENABLE_OVERLOADING)
    IMContextDeleteSurroundingMethodInfo    ,
#endif
    iMContextDeleteSurrounding              ,


-- ** filterKeypress #method:filterKeypress#

#if defined(ENABLE_OVERLOADING)
    IMContextFilterKeypressMethodInfo       ,
#endif
    iMContextFilterKeypress                 ,


-- ** focusIn #method:focusIn#

#if defined(ENABLE_OVERLOADING)
    IMContextFocusInMethodInfo              ,
#endif
    iMContextFocusIn                        ,


-- ** focusOut #method:focusOut#

#if defined(ENABLE_OVERLOADING)
    IMContextFocusOutMethodInfo             ,
#endif
    iMContextFocusOut                       ,


-- ** getPreeditString #method:getPreeditString#

#if defined(ENABLE_OVERLOADING)
    IMContextGetPreeditStringMethodInfo     ,
#endif
    iMContextGetPreeditString               ,


-- ** getSurrounding #method:getSurrounding#

#if defined(ENABLE_OVERLOADING)
    IMContextGetSurroundingMethodInfo       ,
#endif
    iMContextGetSurrounding                 ,


-- ** reset #method:reset#

#if defined(ENABLE_OVERLOADING)
    IMContextResetMethodInfo                ,
#endif
    iMContextReset                          ,


-- ** setClientWindow #method:setClientWindow#

#if defined(ENABLE_OVERLOADING)
    IMContextSetClientWindowMethodInfo      ,
#endif
    iMContextSetClientWindow                ,


-- ** setCursorLocation #method:setCursorLocation#

#if defined(ENABLE_OVERLOADING)
    IMContextSetCursorLocationMethodInfo    ,
#endif
    iMContextSetCursorLocation              ,


-- ** setSurrounding #method:setSurrounding#

#if defined(ENABLE_OVERLOADING)
    IMContextSetSurroundingMethodInfo       ,
#endif
    iMContextSetSurrounding                 ,


-- ** setUsePreedit #method:setUsePreedit#

#if defined(ENABLE_OVERLOADING)
    IMContextSetUsePreeditMethodInfo        ,
#endif
    iMContextSetUsePreedit                  ,




 -- * Properties
-- ** inputHints #attr:inputHints#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    IMContextInputHintsPropertyInfo         ,
#endif
    constructIMContextInputHints            ,
    getIMContextInputHints                  ,
#if defined(ENABLE_OVERLOADING)
    iMContextInputHints                     ,
#endif
    setIMContextInputHints                  ,


-- ** inputPurpose #attr:inputPurpose#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    IMContextInputPurposePropertyInfo       ,
#endif
    constructIMContextInputPurpose          ,
    getIMContextInputPurpose                ,
#if defined(ENABLE_OVERLOADING)
    iMContextInputPurpose                   ,
#endif
    setIMContextInputPurpose                ,




 -- * Signals
-- ** commit #signal:commit#

    C_IMContextCommitCallback               ,
    IMContextCommitCallback                 ,
#if defined(ENABLE_OVERLOADING)
    IMContextCommitSignalInfo               ,
#endif
    afterIMContextCommit                    ,
    genClosure_IMContextCommit              ,
    mk_IMContextCommitCallback              ,
    noIMContextCommitCallback               ,
    onIMContextCommit                       ,
    wrap_IMContextCommitCallback            ,


-- ** deleteSurrounding #signal:deleteSurrounding#

    C_IMContextDeleteSurroundingCallback    ,
    IMContextDeleteSurroundingCallback      ,
#if defined(ENABLE_OVERLOADING)
    IMContextDeleteSurroundingSignalInfo    ,
#endif
    afterIMContextDeleteSurrounding         ,
    genClosure_IMContextDeleteSurrounding   ,
    mk_IMContextDeleteSurroundingCallback   ,
    noIMContextDeleteSurroundingCallback    ,
    onIMContextDeleteSurrounding            ,
    wrap_IMContextDeleteSurroundingCallback ,


-- ** preeditChanged #signal:preeditChanged#

    C_IMContextPreeditChangedCallback       ,
    IMContextPreeditChangedCallback         ,
#if defined(ENABLE_OVERLOADING)
    IMContextPreeditChangedSignalInfo       ,
#endif
    afterIMContextPreeditChanged            ,
    genClosure_IMContextPreeditChanged      ,
    mk_IMContextPreeditChangedCallback      ,
    noIMContextPreeditChangedCallback       ,
    onIMContextPreeditChanged               ,
    wrap_IMContextPreeditChangedCallback    ,


-- ** preeditEnd #signal:preeditEnd#

    C_IMContextPreeditEndCallback           ,
    IMContextPreeditEndCallback             ,
#if defined(ENABLE_OVERLOADING)
    IMContextPreeditEndSignalInfo           ,
#endif
    afterIMContextPreeditEnd                ,
    genClosure_IMContextPreeditEnd          ,
    mk_IMContextPreeditEndCallback          ,
    noIMContextPreeditEndCallback           ,
    onIMContextPreeditEnd                   ,
    wrap_IMContextPreeditEndCallback        ,


-- ** preeditStart #signal:preeditStart#

    C_IMContextPreeditStartCallback         ,
    IMContextPreeditStartCallback           ,
#if defined(ENABLE_OVERLOADING)
    IMContextPreeditStartSignalInfo         ,
#endif
    afterIMContextPreeditStart              ,
    genClosure_IMContextPreeditStart        ,
    mk_IMContextPreeditStartCallback        ,
    noIMContextPreeditStartCallback         ,
    onIMContextPreeditStart                 ,
    wrap_IMContextPreeditStartCallback      ,


-- ** retrieveSurrounding #signal:retrieveSurrounding#

    C_IMContextRetrieveSurroundingCallback  ,
    IMContextRetrieveSurroundingCallback    ,
#if defined(ENABLE_OVERLOADING)
    IMContextRetrieveSurroundingSignalInfo  ,
#endif
    afterIMContextRetrieveSurrounding       ,
    genClosure_IMContextRetrieveSurrounding ,
    mk_IMContextRetrieveSurroundingCallback ,
    noIMContextRetrieveSurroundingCallback  ,
    onIMContextRetrieveSurrounding          ,
    wrap_IMContextRetrieveSurroundingCallback,




    ) 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

import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Window as Gdk.Window
import qualified GI.Gdk.Structs.EventKey as Gdk.EventKey
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import qualified GI.Pango.Structs.AttrList as Pango.AttrList

-- | Memory-managed wrapper type.
newtype IMContext = IMContext (ManagedPtr IMContext)
    deriving (IMContext -> IMContext -> Bool
(IMContext -> IMContext -> Bool)
-> (IMContext -> IMContext -> Bool) -> Eq IMContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IMContext -> IMContext -> Bool
$c/= :: IMContext -> IMContext -> Bool
== :: IMContext -> IMContext -> Bool
$c== :: IMContext -> IMContext -> Bool
Eq)
foreign import ccall "gtk_im_context_get_type"
    c_gtk_im_context_get_type :: IO GType

instance GObject IMContext where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_im_context_get_type
    

-- | Convert 'IMContext' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue IMContext where
    toGValue :: IMContext -> IO GValue
toGValue o :: IMContext
o = do
        GType
gtype <- IO GType
c_gtk_im_context_get_type
        IMContext -> (Ptr IMContext -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr IMContext
o (GType
-> (GValue -> Ptr IMContext -> IO ()) -> Ptr IMContext -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr IMContext -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO IMContext
fromGValue gv :: GValue
gv = do
        Ptr IMContext
ptr <- GValue -> IO (Ptr IMContext)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr IMContext)
        (ManagedPtr IMContext -> IMContext)
-> Ptr IMContext -> IO IMContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr IMContext -> IMContext
IMContext Ptr IMContext
ptr
        
    

-- | Type class for types which can be safely cast to `IMContext`, for instance with `toIMContext`.
class (GObject o, O.IsDescendantOf IMContext o) => IsIMContext o
instance (GObject o, O.IsDescendantOf IMContext o) => IsIMContext o

instance O.HasParentTypes IMContext
type instance O.ParentTypes IMContext = '[GObject.Object.Object]

-- | Cast to `IMContext`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toIMContext :: (MonadIO m, IsIMContext o) => o -> m IMContext
toIMContext :: o -> m IMContext
toIMContext = IO IMContext -> m IMContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO IMContext -> m IMContext)
-> (o -> IO IMContext) -> o -> m IMContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr IMContext -> IMContext) -> o -> IO IMContext
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr IMContext -> IMContext
IMContext

-- | A convenience alias for `Nothing` :: `Maybe` `IMContext`.
noIMContext :: Maybe IMContext
noIMContext :: Maybe IMContext
noIMContext = Maybe IMContext
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveIMContextMethod (t :: Symbol) (o :: *) :: * where
    ResolveIMContextMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveIMContextMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveIMContextMethod "deleteSurrounding" o = IMContextDeleteSurroundingMethodInfo
    ResolveIMContextMethod "filterKeypress" o = IMContextFilterKeypressMethodInfo
    ResolveIMContextMethod "focusIn" o = IMContextFocusInMethodInfo
    ResolveIMContextMethod "focusOut" o = IMContextFocusOutMethodInfo
    ResolveIMContextMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveIMContextMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveIMContextMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveIMContextMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveIMContextMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveIMContextMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveIMContextMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveIMContextMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveIMContextMethod "reset" o = IMContextResetMethodInfo
    ResolveIMContextMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveIMContextMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveIMContextMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveIMContextMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveIMContextMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveIMContextMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveIMContextMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveIMContextMethod "getPreeditString" o = IMContextGetPreeditStringMethodInfo
    ResolveIMContextMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveIMContextMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveIMContextMethod "getSurrounding" o = IMContextGetSurroundingMethodInfo
    ResolveIMContextMethod "setClientWindow" o = IMContextSetClientWindowMethodInfo
    ResolveIMContextMethod "setCursorLocation" o = IMContextSetCursorLocationMethodInfo
    ResolveIMContextMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveIMContextMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveIMContextMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveIMContextMethod "setSurrounding" o = IMContextSetSurroundingMethodInfo
    ResolveIMContextMethod "setUsePreedit" o = IMContextSetUsePreeditMethodInfo
    ResolveIMContextMethod l o = O.MethodResolutionFailed l o

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

#endif

-- signal IMContext::commit
-- | The [commit](#signal:commit) signal is emitted when a complete input sequence
-- has been entered by the user. This can be a single character
-- immediately after a key press or the final result of preediting.
type IMContextCommitCallback =
    T.Text
    -- ^ /@str@/: the completed character(s) entered by the user
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `IMContextCommitCallback`@.
noIMContextCommitCallback :: Maybe IMContextCommitCallback
noIMContextCommitCallback :: Maybe IMContextCommitCallback
noIMContextCommitCallback = Maybe IMContextCommitCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_IMContextCommitCallback =
    Ptr () ->                               -- object
    CString ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_IMContextCommitCallback`.
foreign import ccall "wrapper"
    mk_IMContextCommitCallback :: C_IMContextCommitCallback -> IO (FunPtr C_IMContextCommitCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_IMContextCommit :: MonadIO m => IMContextCommitCallback -> m (GClosure C_IMContextCommitCallback)
genClosure_IMContextCommit :: IMContextCommitCallback -> m (GClosure C_IMContextCommitCallback)
genClosure_IMContextCommit cb :: IMContextCommitCallback
cb = IO (GClosure C_IMContextCommitCallback)
-> m (GClosure C_IMContextCommitCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_IMContextCommitCallback)
 -> m (GClosure C_IMContextCommitCallback))
-> IO (GClosure C_IMContextCommitCallback)
-> m (GClosure C_IMContextCommitCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextCommitCallback
cb' = IMContextCommitCallback -> C_IMContextCommitCallback
wrap_IMContextCommitCallback IMContextCommitCallback
cb
    C_IMContextCommitCallback -> IO (FunPtr C_IMContextCommitCallback)
mk_IMContextCommitCallback C_IMContextCommitCallback
cb' IO (FunPtr C_IMContextCommitCallback)
-> (FunPtr C_IMContextCommitCallback
    -> IO (GClosure C_IMContextCommitCallback))
-> IO (GClosure C_IMContextCommitCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_IMContextCommitCallback
-> IO (GClosure C_IMContextCommitCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `IMContextCommitCallback` into a `C_IMContextCommitCallback`.
wrap_IMContextCommitCallback ::
    IMContextCommitCallback ->
    C_IMContextCommitCallback
wrap_IMContextCommitCallback :: IMContextCommitCallback -> C_IMContextCommitCallback
wrap_IMContextCommitCallback _cb :: IMContextCommitCallback
_cb _ str :: CString
str _ = do
    Text
str' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
str
    IMContextCommitCallback
_cb  Text
str'


-- | Connect a signal handler for the [commit](#signal:commit) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' iMContext #commit callback
-- @
-- 
-- 
onIMContextCommit :: (IsIMContext a, MonadIO m) => a -> IMContextCommitCallback -> m SignalHandlerId
onIMContextCommit :: a -> IMContextCommitCallback -> m SignalHandlerId
onIMContextCommit obj :: a
obj cb :: IMContextCommitCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextCommitCallback
cb' = IMContextCommitCallback -> C_IMContextCommitCallback
wrap_IMContextCommitCallback IMContextCommitCallback
cb
    FunPtr C_IMContextCommitCallback
cb'' <- C_IMContextCommitCallback -> IO (FunPtr C_IMContextCommitCallback)
mk_IMContextCommitCallback C_IMContextCommitCallback
cb'
    a
-> Text
-> FunPtr C_IMContextCommitCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "commit" FunPtr C_IMContextCommitCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [commit](#signal:commit) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' iMContext #commit callback
-- @
-- 
-- 
afterIMContextCommit :: (IsIMContext a, MonadIO m) => a -> IMContextCommitCallback -> m SignalHandlerId
afterIMContextCommit :: a -> IMContextCommitCallback -> m SignalHandlerId
afterIMContextCommit obj :: a
obj cb :: IMContextCommitCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextCommitCallback
cb' = IMContextCommitCallback -> C_IMContextCommitCallback
wrap_IMContextCommitCallback IMContextCommitCallback
cb
    FunPtr C_IMContextCommitCallback
cb'' <- C_IMContextCommitCallback -> IO (FunPtr C_IMContextCommitCallback)
mk_IMContextCommitCallback C_IMContextCommitCallback
cb'
    a
-> Text
-> FunPtr C_IMContextCommitCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "commit" FunPtr C_IMContextCommitCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data IMContextCommitSignalInfo
instance SignalInfo IMContextCommitSignalInfo where
    type HaskellCallbackType IMContextCommitSignalInfo = IMContextCommitCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_IMContextCommitCallback cb
        cb'' <- mk_IMContextCommitCallback cb'
        connectSignalFunPtr obj "commit" cb'' connectMode detail

#endif

-- signal IMContext::delete-surrounding
-- | The [deleteSurrounding](#signal:deleteSurrounding) signal is emitted when the input method
-- needs to delete all or part of the context surrounding the cursor.
type IMContextDeleteSurroundingCallback =
    Int32
    -- ^ /@offset@/: the character offset from the cursor position of the text
    --           to be deleted. A negative value indicates a position before
    --           the cursor.
    -> Int32
    -- ^ /@nChars@/: the number of characters to be deleted
    -> IO Bool
    -- ^ __Returns:__ 'P.True' if the signal was handled.

-- | A convenience synonym for @`Nothing` :: `Maybe` `IMContextDeleteSurroundingCallback`@.
noIMContextDeleteSurroundingCallback :: Maybe IMContextDeleteSurroundingCallback
noIMContextDeleteSurroundingCallback :: Maybe IMContextDeleteSurroundingCallback
noIMContextDeleteSurroundingCallback = Maybe IMContextDeleteSurroundingCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_IMContextDeleteSurroundingCallback =
    Ptr () ->                               -- object
    Int32 ->
    Int32 ->
    Ptr () ->                               -- user_data
    IO CInt

-- | Generate a function pointer callable from C code, from a `C_IMContextDeleteSurroundingCallback`.
foreign import ccall "wrapper"
    mk_IMContextDeleteSurroundingCallback :: C_IMContextDeleteSurroundingCallback -> IO (FunPtr C_IMContextDeleteSurroundingCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_IMContextDeleteSurrounding :: MonadIO m => IMContextDeleteSurroundingCallback -> m (GClosure C_IMContextDeleteSurroundingCallback)
genClosure_IMContextDeleteSurrounding :: IMContextDeleteSurroundingCallback
-> m (GClosure C_IMContextDeleteSurroundingCallback)
genClosure_IMContextDeleteSurrounding cb :: IMContextDeleteSurroundingCallback
cb = IO (GClosure C_IMContextDeleteSurroundingCallback)
-> m (GClosure C_IMContextDeleteSurroundingCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_IMContextDeleteSurroundingCallback)
 -> m (GClosure C_IMContextDeleteSurroundingCallback))
-> IO (GClosure C_IMContextDeleteSurroundingCallback)
-> m (GClosure C_IMContextDeleteSurroundingCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextDeleteSurroundingCallback
cb' = IMContextDeleteSurroundingCallback
-> C_IMContextDeleteSurroundingCallback
wrap_IMContextDeleteSurroundingCallback IMContextDeleteSurroundingCallback
cb
    C_IMContextDeleteSurroundingCallback
-> IO (FunPtr C_IMContextDeleteSurroundingCallback)
mk_IMContextDeleteSurroundingCallback C_IMContextDeleteSurroundingCallback
cb' IO (FunPtr C_IMContextDeleteSurroundingCallback)
-> (FunPtr C_IMContextDeleteSurroundingCallback
    -> IO (GClosure C_IMContextDeleteSurroundingCallback))
-> IO (GClosure C_IMContextDeleteSurroundingCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_IMContextDeleteSurroundingCallback
-> IO (GClosure C_IMContextDeleteSurroundingCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `IMContextDeleteSurroundingCallback` into a `C_IMContextDeleteSurroundingCallback`.
wrap_IMContextDeleteSurroundingCallback ::
    IMContextDeleteSurroundingCallback ->
    C_IMContextDeleteSurroundingCallback
wrap_IMContextDeleteSurroundingCallback :: IMContextDeleteSurroundingCallback
-> C_IMContextDeleteSurroundingCallback
wrap_IMContextDeleteSurroundingCallback _cb :: IMContextDeleteSurroundingCallback
_cb _ offset :: Int32
offset nChars :: Int32
nChars _ = do
    Bool
result <- IMContextDeleteSurroundingCallback
_cb  Int32
offset Int32
nChars
    let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
result
    CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- | Connect a signal handler for the [deleteSurrounding](#signal:deleteSurrounding) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' iMContext #deleteSurrounding callback
-- @
-- 
-- 
onIMContextDeleteSurrounding :: (IsIMContext a, MonadIO m) => a -> IMContextDeleteSurroundingCallback -> m SignalHandlerId
onIMContextDeleteSurrounding :: a -> IMContextDeleteSurroundingCallback -> m SignalHandlerId
onIMContextDeleteSurrounding obj :: a
obj cb :: IMContextDeleteSurroundingCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextDeleteSurroundingCallback
cb' = IMContextDeleteSurroundingCallback
-> C_IMContextDeleteSurroundingCallback
wrap_IMContextDeleteSurroundingCallback IMContextDeleteSurroundingCallback
cb
    FunPtr C_IMContextDeleteSurroundingCallback
cb'' <- C_IMContextDeleteSurroundingCallback
-> IO (FunPtr C_IMContextDeleteSurroundingCallback)
mk_IMContextDeleteSurroundingCallback C_IMContextDeleteSurroundingCallback
cb'
    a
-> Text
-> FunPtr C_IMContextDeleteSurroundingCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "delete-surrounding" FunPtr C_IMContextDeleteSurroundingCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [deleteSurrounding](#signal:deleteSurrounding) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' iMContext #deleteSurrounding callback
-- @
-- 
-- 
afterIMContextDeleteSurrounding :: (IsIMContext a, MonadIO m) => a -> IMContextDeleteSurroundingCallback -> m SignalHandlerId
afterIMContextDeleteSurrounding :: a -> IMContextDeleteSurroundingCallback -> m SignalHandlerId
afterIMContextDeleteSurrounding obj :: a
obj cb :: IMContextDeleteSurroundingCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextDeleteSurroundingCallback
cb' = IMContextDeleteSurroundingCallback
-> C_IMContextDeleteSurroundingCallback
wrap_IMContextDeleteSurroundingCallback IMContextDeleteSurroundingCallback
cb
    FunPtr C_IMContextDeleteSurroundingCallback
cb'' <- C_IMContextDeleteSurroundingCallback
-> IO (FunPtr C_IMContextDeleteSurroundingCallback)
mk_IMContextDeleteSurroundingCallback C_IMContextDeleteSurroundingCallback
cb'
    a
-> Text
-> FunPtr C_IMContextDeleteSurroundingCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "delete-surrounding" FunPtr C_IMContextDeleteSurroundingCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data IMContextDeleteSurroundingSignalInfo
instance SignalInfo IMContextDeleteSurroundingSignalInfo where
    type HaskellCallbackType IMContextDeleteSurroundingSignalInfo = IMContextDeleteSurroundingCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_IMContextDeleteSurroundingCallback cb
        cb'' <- mk_IMContextDeleteSurroundingCallback cb'
        connectSignalFunPtr obj "delete-surrounding" cb'' connectMode detail

#endif

-- signal IMContext::preedit-changed
-- | The [preeditChanged](#signal:preeditChanged) signal is emitted whenever the preedit sequence
-- currently being entered has changed.  It is also emitted at the end of
-- a preedit sequence, in which case
-- 'GI.Gtk.Objects.IMContext.iMContextGetPreeditString' returns the empty string.
type IMContextPreeditChangedCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `IMContextPreeditChangedCallback`@.
noIMContextPreeditChangedCallback :: Maybe IMContextPreeditChangedCallback
noIMContextPreeditChangedCallback :: Maybe (IO ())
noIMContextPreeditChangedCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_IMContextPreeditChangedCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_IMContextPreeditChangedCallback`.
foreign import ccall "wrapper"
    mk_IMContextPreeditChangedCallback :: C_IMContextPreeditChangedCallback -> IO (FunPtr C_IMContextPreeditChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_IMContextPreeditChanged :: MonadIO m => IMContextPreeditChangedCallback -> m (GClosure C_IMContextPreeditChangedCallback)
genClosure_IMContextPreeditChanged :: IO () -> m (GClosure C_IMContextPreeditChangedCallback)
genClosure_IMContextPreeditChanged cb :: IO ()
cb = IO (GClosure C_IMContextPreeditChangedCallback)
-> m (GClosure C_IMContextPreeditChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_IMContextPreeditChangedCallback)
 -> m (GClosure C_IMContextPreeditChangedCallback))
-> IO (GClosure C_IMContextPreeditChangedCallback)
-> m (GClosure C_IMContextPreeditChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextPreeditChangedCallback
cb' = IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditChangedCallback IO ()
cb
    C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditChangedCallback C_IMContextPreeditChangedCallback
cb' IO (FunPtr C_IMContextPreeditChangedCallback)
-> (FunPtr C_IMContextPreeditChangedCallback
    -> IO (GClosure C_IMContextPreeditChangedCallback))
-> IO (GClosure C_IMContextPreeditChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_IMContextPreeditChangedCallback
-> IO (GClosure C_IMContextPreeditChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `IMContextPreeditChangedCallback` into a `C_IMContextPreeditChangedCallback`.
wrap_IMContextPreeditChangedCallback ::
    IMContextPreeditChangedCallback ->
    C_IMContextPreeditChangedCallback
wrap_IMContextPreeditChangedCallback :: IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditChangedCallback _cb :: IO ()
_cb _ _ = do
    IO ()
_cb 


-- | Connect a signal handler for the [preeditChanged](#signal:preeditChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' iMContext #preeditChanged callback
-- @
-- 
-- 
onIMContextPreeditChanged :: (IsIMContext a, MonadIO m) => a -> IMContextPreeditChangedCallback -> m SignalHandlerId
onIMContextPreeditChanged :: a -> IO () -> m SignalHandlerId
onIMContextPreeditChanged obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextPreeditChangedCallback
cb' = IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditChangedCallback IO ()
cb
    FunPtr C_IMContextPreeditChangedCallback
cb'' <- C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditChangedCallback C_IMContextPreeditChangedCallback
cb'
    a
-> Text
-> FunPtr C_IMContextPreeditChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "preedit-changed" FunPtr C_IMContextPreeditChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [preeditChanged](#signal:preeditChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' iMContext #preeditChanged callback
-- @
-- 
-- 
afterIMContextPreeditChanged :: (IsIMContext a, MonadIO m) => a -> IMContextPreeditChangedCallback -> m SignalHandlerId
afterIMContextPreeditChanged :: a -> IO () -> m SignalHandlerId
afterIMContextPreeditChanged obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextPreeditChangedCallback
cb' = IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditChangedCallback IO ()
cb
    FunPtr C_IMContextPreeditChangedCallback
cb'' <- C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditChangedCallback C_IMContextPreeditChangedCallback
cb'
    a
-> Text
-> FunPtr C_IMContextPreeditChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "preedit-changed" FunPtr C_IMContextPreeditChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data IMContextPreeditChangedSignalInfo
instance SignalInfo IMContextPreeditChangedSignalInfo where
    type HaskellCallbackType IMContextPreeditChangedSignalInfo = IMContextPreeditChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_IMContextPreeditChangedCallback cb
        cb'' <- mk_IMContextPreeditChangedCallback cb'
        connectSignalFunPtr obj "preedit-changed" cb'' connectMode detail

#endif

-- signal IMContext::preedit-end
-- | The [preeditEnd](#signal:preeditEnd) signal is emitted when a preediting sequence
-- has been completed or canceled.
type IMContextPreeditEndCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `IMContextPreeditEndCallback`@.
noIMContextPreeditEndCallback :: Maybe IMContextPreeditEndCallback
noIMContextPreeditEndCallback :: Maybe (IO ())
noIMContextPreeditEndCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_IMContextPreeditEndCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_IMContextPreeditEndCallback`.
foreign import ccall "wrapper"
    mk_IMContextPreeditEndCallback :: C_IMContextPreeditEndCallback -> IO (FunPtr C_IMContextPreeditEndCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_IMContextPreeditEnd :: MonadIO m => IMContextPreeditEndCallback -> m (GClosure C_IMContextPreeditEndCallback)
genClosure_IMContextPreeditEnd :: IO () -> m (GClosure C_IMContextPreeditChangedCallback)
genClosure_IMContextPreeditEnd cb :: IO ()
cb = IO (GClosure C_IMContextPreeditChangedCallback)
-> m (GClosure C_IMContextPreeditChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_IMContextPreeditChangedCallback)
 -> m (GClosure C_IMContextPreeditChangedCallback))
-> IO (GClosure C_IMContextPreeditChangedCallback)
-> m (GClosure C_IMContextPreeditChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextPreeditChangedCallback
cb' = IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditEndCallback IO ()
cb
    C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditEndCallback C_IMContextPreeditChangedCallback
cb' IO (FunPtr C_IMContextPreeditChangedCallback)
-> (FunPtr C_IMContextPreeditChangedCallback
    -> IO (GClosure C_IMContextPreeditChangedCallback))
-> IO (GClosure C_IMContextPreeditChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_IMContextPreeditChangedCallback
-> IO (GClosure C_IMContextPreeditChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `IMContextPreeditEndCallback` into a `C_IMContextPreeditEndCallback`.
wrap_IMContextPreeditEndCallback ::
    IMContextPreeditEndCallback ->
    C_IMContextPreeditEndCallback
wrap_IMContextPreeditEndCallback :: IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditEndCallback _cb :: IO ()
_cb _ _ = do
    IO ()
_cb 


-- | Connect a signal handler for the [preeditEnd](#signal:preeditEnd) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' iMContext #preeditEnd callback
-- @
-- 
-- 
onIMContextPreeditEnd :: (IsIMContext a, MonadIO m) => a -> IMContextPreeditEndCallback -> m SignalHandlerId
onIMContextPreeditEnd :: a -> IO () -> m SignalHandlerId
onIMContextPreeditEnd obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextPreeditChangedCallback
cb' = IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditEndCallback IO ()
cb
    FunPtr C_IMContextPreeditChangedCallback
cb'' <- C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditEndCallback C_IMContextPreeditChangedCallback
cb'
    a
-> Text
-> FunPtr C_IMContextPreeditChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "preedit-end" FunPtr C_IMContextPreeditChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [preeditEnd](#signal:preeditEnd) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' iMContext #preeditEnd callback
-- @
-- 
-- 
afterIMContextPreeditEnd :: (IsIMContext a, MonadIO m) => a -> IMContextPreeditEndCallback -> m SignalHandlerId
afterIMContextPreeditEnd :: a -> IO () -> m SignalHandlerId
afterIMContextPreeditEnd obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextPreeditChangedCallback
cb' = IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditEndCallback IO ()
cb
    FunPtr C_IMContextPreeditChangedCallback
cb'' <- C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditEndCallback C_IMContextPreeditChangedCallback
cb'
    a
-> Text
-> FunPtr C_IMContextPreeditChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "preedit-end" FunPtr C_IMContextPreeditChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data IMContextPreeditEndSignalInfo
instance SignalInfo IMContextPreeditEndSignalInfo where
    type HaskellCallbackType IMContextPreeditEndSignalInfo = IMContextPreeditEndCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_IMContextPreeditEndCallback cb
        cb'' <- mk_IMContextPreeditEndCallback cb'
        connectSignalFunPtr obj "preedit-end" cb'' connectMode detail

#endif

-- signal IMContext::preedit-start
-- | The [preeditStart](#signal:preeditStart) signal is emitted when a new preediting sequence
-- starts.
type IMContextPreeditStartCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `IMContextPreeditStartCallback`@.
noIMContextPreeditStartCallback :: Maybe IMContextPreeditStartCallback
noIMContextPreeditStartCallback :: Maybe (IO ())
noIMContextPreeditStartCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_IMContextPreeditStartCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_IMContextPreeditStartCallback`.
foreign import ccall "wrapper"
    mk_IMContextPreeditStartCallback :: C_IMContextPreeditStartCallback -> IO (FunPtr C_IMContextPreeditStartCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_IMContextPreeditStart :: MonadIO m => IMContextPreeditStartCallback -> m (GClosure C_IMContextPreeditStartCallback)
genClosure_IMContextPreeditStart :: IO () -> m (GClosure C_IMContextPreeditChangedCallback)
genClosure_IMContextPreeditStart cb :: IO ()
cb = IO (GClosure C_IMContextPreeditChangedCallback)
-> m (GClosure C_IMContextPreeditChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_IMContextPreeditChangedCallback)
 -> m (GClosure C_IMContextPreeditChangedCallback))
-> IO (GClosure C_IMContextPreeditChangedCallback)
-> m (GClosure C_IMContextPreeditChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextPreeditChangedCallback
cb' = IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditStartCallback IO ()
cb
    C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditStartCallback C_IMContextPreeditChangedCallback
cb' IO (FunPtr C_IMContextPreeditChangedCallback)
-> (FunPtr C_IMContextPreeditChangedCallback
    -> IO (GClosure C_IMContextPreeditChangedCallback))
-> IO (GClosure C_IMContextPreeditChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_IMContextPreeditChangedCallback
-> IO (GClosure C_IMContextPreeditChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `IMContextPreeditStartCallback` into a `C_IMContextPreeditStartCallback`.
wrap_IMContextPreeditStartCallback ::
    IMContextPreeditStartCallback ->
    C_IMContextPreeditStartCallback
wrap_IMContextPreeditStartCallback :: IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditStartCallback _cb :: IO ()
_cb _ _ = do
    IO ()
_cb 


-- | Connect a signal handler for the [preeditStart](#signal:preeditStart) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' iMContext #preeditStart callback
-- @
-- 
-- 
onIMContextPreeditStart :: (IsIMContext a, MonadIO m) => a -> IMContextPreeditStartCallback -> m SignalHandlerId
onIMContextPreeditStart :: a -> IO () -> m SignalHandlerId
onIMContextPreeditStart obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextPreeditChangedCallback
cb' = IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditStartCallback IO ()
cb
    FunPtr C_IMContextPreeditChangedCallback
cb'' <- C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditStartCallback C_IMContextPreeditChangedCallback
cb'
    a
-> Text
-> FunPtr C_IMContextPreeditChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "preedit-start" FunPtr C_IMContextPreeditChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [preeditStart](#signal:preeditStart) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' iMContext #preeditStart callback
-- @
-- 
-- 
afterIMContextPreeditStart :: (IsIMContext a, MonadIO m) => a -> IMContextPreeditStartCallback -> m SignalHandlerId
afterIMContextPreeditStart :: a -> IO () -> m SignalHandlerId
afterIMContextPreeditStart obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextPreeditChangedCallback
cb' = IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditStartCallback IO ()
cb
    FunPtr C_IMContextPreeditChangedCallback
cb'' <- C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditStartCallback C_IMContextPreeditChangedCallback
cb'
    a
-> Text
-> FunPtr C_IMContextPreeditChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "preedit-start" FunPtr C_IMContextPreeditChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data IMContextPreeditStartSignalInfo
instance SignalInfo IMContextPreeditStartSignalInfo where
    type HaskellCallbackType IMContextPreeditStartSignalInfo = IMContextPreeditStartCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_IMContextPreeditStartCallback cb
        cb'' <- mk_IMContextPreeditStartCallback cb'
        connectSignalFunPtr obj "preedit-start" cb'' connectMode detail

#endif

-- signal IMContext::retrieve-surrounding
-- | The [retrieveSurrounding](#signal:retrieveSurrounding) signal is emitted when the input method
-- requires the context surrounding the cursor.  The callback should set
-- the input method surrounding context by calling the
-- 'GI.Gtk.Objects.IMContext.iMContextSetSurrounding' method.
type IMContextRetrieveSurroundingCallback =
    IO Bool
    -- ^ __Returns:__ 'P.True' if the signal was handled.

-- | A convenience synonym for @`Nothing` :: `Maybe` `IMContextRetrieveSurroundingCallback`@.
noIMContextRetrieveSurroundingCallback :: Maybe IMContextRetrieveSurroundingCallback
noIMContextRetrieveSurroundingCallback :: Maybe IMContextRetrieveSurroundingCallback
noIMContextRetrieveSurroundingCallback = Maybe IMContextRetrieveSurroundingCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_IMContextRetrieveSurroundingCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO CInt

-- | Generate a function pointer callable from C code, from a `C_IMContextRetrieveSurroundingCallback`.
foreign import ccall "wrapper"
    mk_IMContextRetrieveSurroundingCallback :: C_IMContextRetrieveSurroundingCallback -> IO (FunPtr C_IMContextRetrieveSurroundingCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_IMContextRetrieveSurrounding :: MonadIO m => IMContextRetrieveSurroundingCallback -> m (GClosure C_IMContextRetrieveSurroundingCallback)
genClosure_IMContextRetrieveSurrounding :: IMContextRetrieveSurroundingCallback
-> m (GClosure C_IMContextRetrieveSurroundingCallback)
genClosure_IMContextRetrieveSurrounding cb :: IMContextRetrieveSurroundingCallback
cb = IO (GClosure C_IMContextRetrieveSurroundingCallback)
-> m (GClosure C_IMContextRetrieveSurroundingCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_IMContextRetrieveSurroundingCallback)
 -> m (GClosure C_IMContextRetrieveSurroundingCallback))
-> IO (GClosure C_IMContextRetrieveSurroundingCallback)
-> m (GClosure C_IMContextRetrieveSurroundingCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextRetrieveSurroundingCallback
cb' = IMContextRetrieveSurroundingCallback
-> C_IMContextRetrieveSurroundingCallback
wrap_IMContextRetrieveSurroundingCallback IMContextRetrieveSurroundingCallback
cb
    C_IMContextRetrieveSurroundingCallback
-> IO (FunPtr C_IMContextRetrieveSurroundingCallback)
mk_IMContextRetrieveSurroundingCallback C_IMContextRetrieveSurroundingCallback
cb' IO (FunPtr C_IMContextRetrieveSurroundingCallback)
-> (FunPtr C_IMContextRetrieveSurroundingCallback
    -> IO (GClosure C_IMContextRetrieveSurroundingCallback))
-> IO (GClosure C_IMContextRetrieveSurroundingCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_IMContextRetrieveSurroundingCallback
-> IO (GClosure C_IMContextRetrieveSurroundingCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `IMContextRetrieveSurroundingCallback` into a `C_IMContextRetrieveSurroundingCallback`.
wrap_IMContextRetrieveSurroundingCallback ::
    IMContextRetrieveSurroundingCallback ->
    C_IMContextRetrieveSurroundingCallback
wrap_IMContextRetrieveSurroundingCallback :: IMContextRetrieveSurroundingCallback
-> C_IMContextRetrieveSurroundingCallback
wrap_IMContextRetrieveSurroundingCallback _cb :: IMContextRetrieveSurroundingCallback
_cb _ _ = do
    Bool
result <- IMContextRetrieveSurroundingCallback
_cb 
    let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
result
    CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- | Connect a signal handler for the [retrieveSurrounding](#signal:retrieveSurrounding) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' iMContext #retrieveSurrounding callback
-- @
-- 
-- 
onIMContextRetrieveSurrounding :: (IsIMContext a, MonadIO m) => a -> IMContextRetrieveSurroundingCallback -> m SignalHandlerId
onIMContextRetrieveSurrounding :: a -> IMContextRetrieveSurroundingCallback -> m SignalHandlerId
onIMContextRetrieveSurrounding obj :: a
obj cb :: IMContextRetrieveSurroundingCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextRetrieveSurroundingCallback
cb' = IMContextRetrieveSurroundingCallback
-> C_IMContextRetrieveSurroundingCallback
wrap_IMContextRetrieveSurroundingCallback IMContextRetrieveSurroundingCallback
cb
    FunPtr C_IMContextRetrieveSurroundingCallback
cb'' <- C_IMContextRetrieveSurroundingCallback
-> IO (FunPtr C_IMContextRetrieveSurroundingCallback)
mk_IMContextRetrieveSurroundingCallback C_IMContextRetrieveSurroundingCallback
cb'
    a
-> Text
-> FunPtr C_IMContextRetrieveSurroundingCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "retrieve-surrounding" FunPtr C_IMContextRetrieveSurroundingCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [retrieveSurrounding](#signal:retrieveSurrounding) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' iMContext #retrieveSurrounding callback
-- @
-- 
-- 
afterIMContextRetrieveSurrounding :: (IsIMContext a, MonadIO m) => a -> IMContextRetrieveSurroundingCallback -> m SignalHandlerId
afterIMContextRetrieveSurrounding :: a -> IMContextRetrieveSurroundingCallback -> m SignalHandlerId
afterIMContextRetrieveSurrounding obj :: a
obj cb :: IMContextRetrieveSurroundingCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_IMContextRetrieveSurroundingCallback
cb' = IMContextRetrieveSurroundingCallback
-> C_IMContextRetrieveSurroundingCallback
wrap_IMContextRetrieveSurroundingCallback IMContextRetrieveSurroundingCallback
cb
    FunPtr C_IMContextRetrieveSurroundingCallback
cb'' <- C_IMContextRetrieveSurroundingCallback
-> IO (FunPtr C_IMContextRetrieveSurroundingCallback)
mk_IMContextRetrieveSurroundingCallback C_IMContextRetrieveSurroundingCallback
cb'
    a
-> Text
-> FunPtr C_IMContextRetrieveSurroundingCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "retrieve-surrounding" FunPtr C_IMContextRetrieveSurroundingCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data IMContextRetrieveSurroundingSignalInfo
instance SignalInfo IMContextRetrieveSurroundingSignalInfo where
    type HaskellCallbackType IMContextRetrieveSurroundingSignalInfo = IMContextRetrieveSurroundingCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_IMContextRetrieveSurroundingCallback cb
        cb'' <- mk_IMContextRetrieveSurroundingCallback cb'
        connectSignalFunPtr obj "retrieve-surrounding" cb'' connectMode detail

#endif

-- VVV Prop "input-hints"
   -- Type: TInterface (Name {namespace = "Gtk", name = "InputHints"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@input-hints@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' iMContext #inputHints
-- @
getIMContextInputHints :: (MonadIO m, IsIMContext o) => o -> m [Gtk.Flags.InputHints]
getIMContextInputHints :: o -> m [InputHints]
getIMContextInputHints obj :: o
obj = IO [InputHints] -> m [InputHints]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [InputHints] -> m [InputHints])
-> IO [InputHints] -> m [InputHints]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [InputHints]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj "input-hints"

-- | Set the value of the “@input-hints@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' iMContext [ #inputHints 'Data.GI.Base.Attributes.:=' value ]
-- @
setIMContextInputHints :: (MonadIO m, IsIMContext o) => o -> [Gtk.Flags.InputHints] -> m ()
setIMContextInputHints :: o -> [InputHints] -> m ()
setIMContextInputHints obj :: o
obj val :: [InputHints]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> [InputHints] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj "input-hints" [InputHints]
val

-- | Construct a `GValueConstruct` with valid value for the “@input-hints@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructIMContextInputHints :: (IsIMContext o) => [Gtk.Flags.InputHints] -> IO (GValueConstruct o)
constructIMContextInputHints :: [InputHints] -> IO (GValueConstruct o)
constructIMContextInputHints val :: [InputHints]
val = String -> [InputHints] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags "input-hints" [InputHints]
val

#if defined(ENABLE_OVERLOADING)
data IMContextInputHintsPropertyInfo
instance AttrInfo IMContextInputHintsPropertyInfo where
    type AttrAllowedOps IMContextInputHintsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint IMContextInputHintsPropertyInfo = IsIMContext
    type AttrSetTypeConstraint IMContextInputHintsPropertyInfo = (~) [Gtk.Flags.InputHints]
    type AttrTransferTypeConstraint IMContextInputHintsPropertyInfo = (~) [Gtk.Flags.InputHints]
    type AttrTransferType IMContextInputHintsPropertyInfo = [Gtk.Flags.InputHints]
    type AttrGetType IMContextInputHintsPropertyInfo = [Gtk.Flags.InputHints]
    type AttrLabel IMContextInputHintsPropertyInfo = "input-hints"
    type AttrOrigin IMContextInputHintsPropertyInfo = IMContext
    attrGet = getIMContextInputHints
    attrSet = setIMContextInputHints
    attrTransfer _ v = do
        return v
    attrConstruct = constructIMContextInputHints
    attrClear = undefined
#endif

-- VVV Prop "input-purpose"
   -- Type: TInterface (Name {namespace = "Gtk", name = "InputPurpose"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@input-purpose@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' iMContext #inputPurpose
-- @
getIMContextInputPurpose :: (MonadIO m, IsIMContext o) => o -> m Gtk.Enums.InputPurpose
getIMContextInputPurpose :: o -> m InputPurpose
getIMContextInputPurpose obj :: o
obj = IO InputPurpose -> m InputPurpose
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputPurpose -> m InputPurpose)
-> IO InputPurpose -> m InputPurpose
forall a b. (a -> b) -> a -> b
$ o -> String -> IO InputPurpose
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj "input-purpose"

-- | Set the value of the “@input-purpose@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' iMContext [ #inputPurpose 'Data.GI.Base.Attributes.:=' value ]
-- @
setIMContextInputPurpose :: (MonadIO m, IsIMContext o) => o -> Gtk.Enums.InputPurpose -> m ()
setIMContextInputPurpose :: o -> InputPurpose -> m ()
setIMContextInputPurpose obj :: o
obj val :: InputPurpose
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> InputPurpose -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj "input-purpose" InputPurpose
val

-- | Construct a `GValueConstruct` with valid value for the “@input-purpose@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructIMContextInputPurpose :: (IsIMContext o) => Gtk.Enums.InputPurpose -> IO (GValueConstruct o)
constructIMContextInputPurpose :: InputPurpose -> IO (GValueConstruct o)
constructIMContextInputPurpose val :: InputPurpose
val = String -> InputPurpose -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum "input-purpose" InputPurpose
val

#if defined(ENABLE_OVERLOADING)
data IMContextInputPurposePropertyInfo
instance AttrInfo IMContextInputPurposePropertyInfo where
    type AttrAllowedOps IMContextInputPurposePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint IMContextInputPurposePropertyInfo = IsIMContext
    type AttrSetTypeConstraint IMContextInputPurposePropertyInfo = (~) Gtk.Enums.InputPurpose
    type AttrTransferTypeConstraint IMContextInputPurposePropertyInfo = (~) Gtk.Enums.InputPurpose
    type AttrTransferType IMContextInputPurposePropertyInfo = Gtk.Enums.InputPurpose
    type AttrGetType IMContextInputPurposePropertyInfo = Gtk.Enums.InputPurpose
    type AttrLabel IMContextInputPurposePropertyInfo = "input-purpose"
    type AttrOrigin IMContextInputPurposePropertyInfo = IMContext
    attrGet = getIMContextInputPurpose
    attrSet = setIMContextInputPurpose
    attrTransfer _ v = do
        return v
    attrConstruct = constructIMContextInputPurpose
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList IMContext
type instance O.AttributeList IMContext = IMContextAttributeList
type IMContextAttributeList = ('[ '("inputHints", IMContextInputHintsPropertyInfo), '("inputPurpose", IMContextInputPurposePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
iMContextInputHints :: AttrLabelProxy "inputHints"
iMContextInputHints = AttrLabelProxy

iMContextInputPurpose :: AttrLabelProxy "inputPurpose"
iMContextInputPurpose = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList IMContext = IMContextSignalList
type IMContextSignalList = ('[ '("commit", IMContextCommitSignalInfo), '("deleteSurrounding", IMContextDeleteSurroundingSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("preeditChanged", IMContextPreeditChangedSignalInfo), '("preeditEnd", IMContextPreeditEndSignalInfo), '("preeditStart", IMContextPreeditStartSignalInfo), '("retrieveSurrounding", IMContextRetrieveSurroundingSignalInfo)] :: [(Symbol, *)])

#endif

-- method IMContext::delete_surrounding
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IMContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIMContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "offset"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "offset from cursor position in chars;\n   a negative value means start before the cursor."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_chars"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of characters to delete."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_im_context_delete_surrounding" gtk_im_context_delete_surrounding :: 
    Ptr IMContext ->                        -- context : TInterface (Name {namespace = "Gtk", name = "IMContext"})
    Int32 ->                                -- offset : TBasicType TInt
    Int32 ->                                -- n_chars : TBasicType TInt
    IO CInt

-- | Asks the widget that the input context is attached to to delete
-- characters around the cursor position by emitting the
-- GtkIMContext[delete_surrounding](#signal:delete_surrounding) signal. Note that /@offset@/ and /@nChars@/
-- are in characters not in bytes which differs from the usage other
-- places in t'GI.Gtk.Objects.IMContext.IMContext'.
-- 
-- In order to use this function, you should first call
-- 'GI.Gtk.Objects.IMContext.iMContextGetSurrounding' to get the current context, and
-- call this function immediately afterwards to make sure that you
-- know what you are deleting. You should also account for the fact
-- that even if the signal was handled, the input context might not
-- have deleted all the characters that were requested to be deleted.
-- 
-- This function is used by an input method that wants to make
-- subsitutions in the existing text in response to new input. It is
-- not useful for applications.
iMContextDeleteSurrounding ::
    (B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.IMContext.IMContext'
    -> Int32
    -- ^ /@offset@/: offset from cursor position in chars;
    --    a negative value means start before the cursor.
    -> Int32
    -- ^ /@nChars@/: number of characters to delete.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the signal was handled.
iMContextDeleteSurrounding :: a -> Int32 -> Int32 -> m Bool
iMContextDeleteSurrounding context :: a
context offset :: Int32
offset nChars :: Int32
nChars = IMContextRetrieveSurroundingCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IMContextRetrieveSurroundingCallback -> m Bool)
-> IMContextRetrieveSurroundingCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr IMContext
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CInt
result <- Ptr IMContext -> Int32 -> Int32 -> IO CInt
gtk_im_context_delete_surrounding Ptr IMContext
context' Int32
offset Int32
nChars
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Bool -> IMContextRetrieveSurroundingCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data IMContextDeleteSurroundingMethodInfo
instance (signature ~ (Int32 -> Int32 -> m Bool), MonadIO m, IsIMContext a) => O.MethodInfo IMContextDeleteSurroundingMethodInfo a signature where
    overloadedMethod = iMContextDeleteSurrounding

#endif

-- method IMContext::filter_keypress
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IMContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIMContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "event"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "EventKey" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key event" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_im_context_filter_keypress" gtk_im_context_filter_keypress :: 
    Ptr IMContext ->                        -- context : TInterface (Name {namespace = "Gtk", name = "IMContext"})
    Ptr Gdk.EventKey.EventKey ->            -- event : TInterface (Name {namespace = "Gdk", name = "EventKey"})
    IO CInt

-- | Allow an input method to internally handle key press and release
-- events. If this function returns 'P.True', then no further processing
-- should be done for this key event.
iMContextFilterKeypress ::
    (B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.IMContext.IMContext'
    -> Gdk.EventKey.EventKey
    -- ^ /@event@/: the key event
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the input method handled the key event.
iMContextFilterKeypress :: a -> EventKey -> m Bool
iMContextFilterKeypress context :: a
context event :: EventKey
event = IMContextRetrieveSurroundingCallback -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IMContextRetrieveSurroundingCallback -> m Bool)
-> IMContextRetrieveSurroundingCallback -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr IMContext
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr EventKey
event' <- EventKey -> IO (Ptr EventKey)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr EventKey
event
    CInt
result <- Ptr IMContext -> Ptr EventKey -> IO CInt
gtk_im_context_filter_keypress Ptr IMContext
context' Ptr EventKey
event'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    EventKey -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr EventKey
event
    Bool -> IMContextRetrieveSurroundingCallback
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data IMContextFilterKeypressMethodInfo
instance (signature ~ (Gdk.EventKey.EventKey -> m Bool), MonadIO m, IsIMContext a) => O.MethodInfo IMContextFilterKeypressMethodInfo a signature where
    overloadedMethod = iMContextFilterKeypress

#endif

-- method IMContext::focus_in
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IMContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIMContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_im_context_focus_in" gtk_im_context_focus_in :: 
    Ptr IMContext ->                        -- context : TInterface (Name {namespace = "Gtk", name = "IMContext"})
    IO ()

-- | Notify the input method that the widget to which this
-- input context corresponds has gained focus. The input method
-- may, for example, change the displayed feedback to reflect
-- this change.
iMContextFocusIn ::
    (B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.IMContext.IMContext'
    -> m ()
iMContextFocusIn :: a -> m ()
iMContextFocusIn context :: a
context = 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 IMContext
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr IMContext -> IO ()
gtk_im_context_focus_in Ptr IMContext
context'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IMContextFocusInMethodInfo
instance (signature ~ (m ()), MonadIO m, IsIMContext a) => O.MethodInfo IMContextFocusInMethodInfo a signature where
    overloadedMethod = iMContextFocusIn

#endif

-- method IMContext::focus_out
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IMContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIMContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_im_context_focus_out" gtk_im_context_focus_out :: 
    Ptr IMContext ->                        -- context : TInterface (Name {namespace = "Gtk", name = "IMContext"})
    IO ()

-- | Notify the input method that the widget to which this
-- input context corresponds has lost focus. The input method
-- may, for example, change the displayed feedback or reset the contexts
-- state to reflect this change.
iMContextFocusOut ::
    (B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.IMContext.IMContext'
    -> m ()
iMContextFocusOut :: a -> m ()
iMContextFocusOut context :: a
context = 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 IMContext
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr IMContext -> IO ()
gtk_im_context_focus_out Ptr IMContext
context'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IMContextFocusOutMethodInfo
instance (signature ~ (m ()), MonadIO m, IsIMContext a) => O.MethodInfo IMContextFocusOutMethodInfo a signature where
    overloadedMethod = iMContextFocusOut

#endif

-- method IMContext::get_preedit_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IMContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIMContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "str"
--           , argType = TBasicType TUTF8
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store the retrieved\n             string. The string retrieved must be freed with g_free()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "attrs"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store the retrieved\n             attribute list.  When you are done with this list, you\n             must unreference it with pango_attr_list_unref()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "cursor_pos"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store position of cursor (in characters)\n             within the preedit string."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_im_context_get_preedit_string" gtk_im_context_get_preedit_string :: 
    Ptr IMContext ->                        -- context : TInterface (Name {namespace = "Gtk", name = "IMContext"})
    Ptr CString ->                          -- str : TBasicType TUTF8
    Ptr (Ptr Pango.AttrList.AttrList) ->    -- attrs : TInterface (Name {namespace = "Pango", name = "AttrList"})
    Ptr Int32 ->                            -- cursor_pos : TBasicType TInt
    IO ()

-- | Retrieve the current preedit string for the input context,
-- and a list of attributes to apply to the string.
-- This string should be displayed inserted at the insertion
-- point.
iMContextGetPreeditString ::
    (B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.IMContext.IMContext'
    -> m ((T.Text, Pango.AttrList.AttrList, Int32))
iMContextGetPreeditString :: a -> m (Text, AttrList, Int32)
iMContextGetPreeditString context :: a
context = IO (Text, AttrList, Int32) -> m (Text, AttrList, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Text, AttrList, Int32) -> m (Text, AttrList, Int32))
-> IO (Text, AttrList, Int32) -> m (Text, AttrList, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr IMContext
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr CString
str <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CString)
    Ptr (Ptr AttrList)
attrs <- IO (Ptr (Ptr AttrList))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr Pango.AttrList.AttrList))
    Ptr Int32
cursorPos <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr IMContext
-> Ptr CString -> Ptr (Ptr AttrList) -> Ptr Int32 -> IO ()
gtk_im_context_get_preedit_string Ptr IMContext
context' Ptr CString
str Ptr (Ptr AttrList)
attrs Ptr Int32
cursorPos
    CString
str' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
str
    Text
str'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
str'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
str'
    Ptr AttrList
attrs' <- Ptr (Ptr AttrList) -> IO (Ptr AttrList)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr AttrList)
attrs
    AttrList
attrs'' <- ((ManagedPtr AttrList -> AttrList) -> Ptr AttrList -> IO AttrList
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr AttrList -> AttrList
Pango.AttrList.AttrList) Ptr AttrList
attrs'
    Int32
cursorPos' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
cursorPos
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
str
    Ptr (Ptr AttrList) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr AttrList)
attrs
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
cursorPos
    (Text, AttrList, Int32) -> IO (Text, AttrList, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
str'', AttrList
attrs'', Int32
cursorPos')

#if defined(ENABLE_OVERLOADING)
data IMContextGetPreeditStringMethodInfo
instance (signature ~ (m ((T.Text, Pango.AttrList.AttrList, Int32))), MonadIO m, IsIMContext a) => O.MethodInfo IMContextGetPreeditStringMethodInfo a signature where
    overloadedMethod = iMContextGetPreeditString

#endif

-- method IMContext::get_surrounding
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IMContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIMContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "text"
--           , argType = TBasicType TUTF8
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store a UTF-8 encoded\n       string of text holding context around the insertion point.\n       If the function returns %TRUE, then you must free the result\n       stored in this location with g_free()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "cursor_index"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store byte index of the insertion\n       cursor within @text."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_im_context_get_surrounding" gtk_im_context_get_surrounding :: 
    Ptr IMContext ->                        -- context : TInterface (Name {namespace = "Gtk", name = "IMContext"})
    Ptr CString ->                          -- text : TBasicType TUTF8
    Ptr Int32 ->                            -- cursor_index : TBasicType TInt
    IO CInt

-- | Retrieves context around the insertion point. Input methods
-- typically want context in order to constrain input text based on
-- existing text; this is important for languages such as Thai where
-- only some sequences of characters are allowed.
-- 
-- This function is implemented by emitting the
-- GtkIMContext[retrieve_surrounding](#signal:retrieve_surrounding) signal on the input method; in
-- response to this signal, a widget should provide as much context as
-- is available, up to an entire paragraph, by calling
-- 'GI.Gtk.Objects.IMContext.iMContextSetSurrounding'. Note that there is no obligation
-- for a widget to respond to the [retrieve_surrounding](#signal:retrieve_surrounding) signal, so input
-- methods must be prepared to function without context.
iMContextGetSurrounding ::
    (B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.IMContext.IMContext'
    -> m ((Bool, T.Text, Int32))
    -- ^ __Returns:__ 'P.True' if surrounding text was provided; in this case
    --    you must free the result stored in *text.
iMContextGetSurrounding :: a -> m (Bool, Text, Int32)
iMContextGetSurrounding context :: a
context = IO (Bool, Text, Int32) -> m (Bool, Text, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Text, Int32) -> m (Bool, Text, Int32))
-> IO (Bool, Text, Int32) -> m (Bool, Text, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr IMContext
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr CString
text <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CString)
    Ptr Int32
cursorIndex <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CInt
result <- Ptr IMContext -> Ptr CString -> Ptr Int32 -> IO CInt
gtk_im_context_get_surrounding Ptr IMContext
context' Ptr CString
text Ptr Int32
cursorIndex
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    CString
text' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
text
    Text
text'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
text'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
    Int32
cursorIndex' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
cursorIndex
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
text
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
cursorIndex
    (Bool, Text, Int32) -> IO (Bool, Text, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Text
text'', Int32
cursorIndex')

#if defined(ENABLE_OVERLOADING)
data IMContextGetSurroundingMethodInfo
instance (signature ~ (m ((Bool, T.Text, Int32))), MonadIO m, IsIMContext a) => O.MethodInfo IMContextGetSurroundingMethodInfo a signature where
    overloadedMethod = iMContextGetSurrounding

#endif

-- method IMContext::reset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IMContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIMContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_im_context_reset" gtk_im_context_reset :: 
    Ptr IMContext ->                        -- context : TInterface (Name {namespace = "Gtk", name = "IMContext"})
    IO ()

-- | Notify the input method that a change such as a change in cursor
-- position has been made. This will typically cause the input
-- method to clear the preedit state.
iMContextReset ::
    (B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.IMContext.IMContext'
    -> m ()
iMContextReset :: a -> m ()
iMContextReset context :: a
context = 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 IMContext
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr IMContext -> IO ()
gtk_im_context_reset Ptr IMContext
context'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IMContextResetMethodInfo
instance (signature ~ (m ()), MonadIO m, IsIMContext a) => O.MethodInfo IMContextResetMethodInfo a signature where
    overloadedMethod = iMContextReset

#endif

-- method IMContext::set_client_window
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IMContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIMContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "window"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the client window. This may be %NULL to indicate\n          that the previous client window no longer exists."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_im_context_set_client_window" gtk_im_context_set_client_window :: 
    Ptr IMContext ->                        -- context : TInterface (Name {namespace = "Gtk", name = "IMContext"})
    Ptr Gdk.Window.Window ->                -- window : TInterface (Name {namespace = "Gdk", name = "Window"})
    IO ()

-- | Set the client window for the input context; this is the
-- t'GI.Gdk.Objects.Window.Window' in which the input appears. This window is
-- used in order to correctly position status windows, and may
-- also be used for purposes internal to the input method.
iMContextSetClientWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsIMContext a, Gdk.Window.IsWindow b) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.IMContext.IMContext'
    -> Maybe (b)
    -- ^ /@window@/: the client window. This may be 'P.Nothing' to indicate
    --           that the previous client window no longer exists.
    -> m ()
iMContextSetClientWindow :: a -> Maybe b -> m ()
iMContextSetClientWindow context :: a
context window :: Maybe b
window = 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 IMContext
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Window
maybeWindow <- case Maybe b
window of
        Nothing -> Ptr Window -> IO (Ptr Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
forall a. Ptr a
nullPtr
        Just jWindow :: b
jWindow -> do
            Ptr Window
jWindow' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jWindow
            Ptr Window -> IO (Ptr Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
jWindow'
    Ptr IMContext -> Ptr Window -> IO ()
gtk_im_context_set_client_window Ptr IMContext
context' Ptr Window
maybeWindow
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
window b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IMContextSetClientWindowMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsIMContext a, Gdk.Window.IsWindow b) => O.MethodInfo IMContextSetClientWindowMethodInfo a signature where
    overloadedMethod = iMContextSetClientWindow

#endif

-- method IMContext::set_cursor_location
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IMContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIMContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "area"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Rectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "new location" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_im_context_set_cursor_location" gtk_im_context_set_cursor_location :: 
    Ptr IMContext ->                        -- context : TInterface (Name {namespace = "Gtk", name = "IMContext"})
    Ptr Gdk.Rectangle.Rectangle ->          -- area : TInterface (Name {namespace = "Gdk", name = "Rectangle"})
    IO ()

-- | Notify the input method that a change in cursor
-- position has been made. The location is relative to the client
-- window.
iMContextSetCursorLocation ::
    (B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.IMContext.IMContext'
    -> Gdk.Rectangle.Rectangle
    -- ^ /@area@/: new location
    -> m ()
iMContextSetCursorLocation :: a -> Rectangle -> m ()
iMContextSetCursorLocation context :: a
context area :: Rectangle
area = 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 IMContext
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Rectangle
area' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
area
    Ptr IMContext -> Ptr Rectangle -> IO ()
gtk_im_context_set_cursor_location Ptr IMContext
context' Ptr Rectangle
area'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
area
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IMContextSetCursorLocationMethodInfo
instance (signature ~ (Gdk.Rectangle.Rectangle -> m ()), MonadIO m, IsIMContext a) => O.MethodInfo IMContextSetCursorLocationMethodInfo a signature where
    overloadedMethod = iMContextSetCursorLocation

#endif

-- method IMContext::set_surrounding
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IMContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIMContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "text"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "text surrounding the insertion point, as UTF-8.\n       the preedit string should not be included within\n       @text."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "len"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the length of @text, or -1 if @text is nul-terminated"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cursor_index"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the byte index of the insertion cursor within @text."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_im_context_set_surrounding" gtk_im_context_set_surrounding :: 
    Ptr IMContext ->                        -- context : TInterface (Name {namespace = "Gtk", name = "IMContext"})
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- len : TBasicType TInt
    Int32 ->                                -- cursor_index : TBasicType TInt
    IO ()

-- | Sets surrounding context around the insertion point and preedit
-- string. This function is expected to be called in response to the
-- GtkIMContext[retrieve_surrounding](#signal:retrieve_surrounding) signal, and will likely have no
-- effect if called at other times.
iMContextSetSurrounding ::
    (B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.IMContext.IMContext'
    -> T.Text
    -- ^ /@text@/: text surrounding the insertion point, as UTF-8.
    --        the preedit string should not be included within
    --        /@text@/.
    -> Int32
    -- ^ /@len@/: the length of /@text@/, or -1 if /@text@/ is nul-terminated
    -> Int32
    -- ^ /@cursorIndex@/: the byte index of the insertion cursor within /@text@/.
    -> m ()
iMContextSetSurrounding :: a -> Text -> Int32 -> Int32 -> m ()
iMContextSetSurrounding context :: a
context text :: Text
text len :: Int32
len cursorIndex :: Int32
cursorIndex = 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 IMContext
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CString
text' <- Text -> IO CString
textToCString Text
text
    Ptr IMContext -> CString -> Int32 -> Int32 -> IO ()
gtk_im_context_set_surrounding Ptr IMContext
context' CString
text' Int32
len Int32
cursorIndex
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IMContextSetSurroundingMethodInfo
instance (signature ~ (T.Text -> Int32 -> Int32 -> m ()), MonadIO m, IsIMContext a) => O.MethodInfo IMContextSetSurroundingMethodInfo a signature where
    overloadedMethod = iMContextSetSurrounding

#endif

-- method IMContext::set_use_preedit
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "IMContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkIMContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "use_preedit"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether the IM context should use the preedit string."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_im_context_set_use_preedit" gtk_im_context_set_use_preedit :: 
    Ptr IMContext ->                        -- context : TInterface (Name {namespace = "Gtk", name = "IMContext"})
    CInt ->                                 -- use_preedit : TBasicType TBoolean
    IO ()

-- | Sets whether the IM context should use the preedit string
-- to display feedback. If /@usePreedit@/ is FALSE (default
-- is TRUE), then the IM context may use some other method to display
-- feedback, such as displaying it in a child of the root window.
iMContextSetUsePreedit ::
    (B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.IMContext.IMContext'
    -> Bool
    -- ^ /@usePreedit@/: whether the IM context should use the preedit string.
    -> m ()
iMContextSetUsePreedit :: a -> Bool -> m ()
iMContextSetUsePreedit context :: a
context usePreedit :: Bool
usePreedit = 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 IMContext
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    let usePreedit' :: CInt
usePreedit' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
usePreedit
    Ptr IMContext -> CInt -> IO ()
gtk_im_context_set_use_preedit Ptr IMContext
context' CInt
usePreedit'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data IMContextSetUsePreeditMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsIMContext a) => O.MethodInfo IMContextSetUsePreeditMethodInfo a signature where
    overloadedMethod = iMContextSetUsePreedit

#endif