{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.IMContext
(
IMContext(..) ,
IsIMContext ,
toIMContext ,
#if defined(ENABLE_OVERLOADING)
ResolveIMContextMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
IMContextDeleteSurroundingMethodInfo ,
#endif
iMContextDeleteSurrounding ,
#if defined(ENABLE_OVERLOADING)
IMContextFilterKeypressMethodInfo ,
#endif
iMContextFilterKeypress ,
#if defined(ENABLE_OVERLOADING)
IMContextFocusInMethodInfo ,
#endif
iMContextFocusIn ,
#if defined(ENABLE_OVERLOADING)
IMContextFocusOutMethodInfo ,
#endif
iMContextFocusOut ,
#if defined(ENABLE_OVERLOADING)
IMContextGetPreeditStringMethodInfo ,
#endif
iMContextGetPreeditString ,
#if defined(ENABLE_OVERLOADING)
IMContextGetSurroundingMethodInfo ,
#endif
iMContextGetSurrounding ,
#if defined(ENABLE_OVERLOADING)
IMContextResetMethodInfo ,
#endif
iMContextReset ,
#if defined(ENABLE_OVERLOADING)
IMContextSetClientWindowMethodInfo ,
#endif
iMContextSetClientWindow ,
#if defined(ENABLE_OVERLOADING)
IMContextSetCursorLocationMethodInfo ,
#endif
iMContextSetCursorLocation ,
#if defined(ENABLE_OVERLOADING)
IMContextSetSurroundingMethodInfo ,
#endif
iMContextSetSurrounding ,
#if defined(ENABLE_OVERLOADING)
IMContextSetUsePreeditMethodInfo ,
#endif
iMContextSetUsePreedit ,
#if defined(ENABLE_OVERLOADING)
IMContextInputHintsPropertyInfo ,
#endif
constructIMContextInputHints ,
getIMContextInputHints ,
#if defined(ENABLE_OVERLOADING)
iMContextInputHints ,
#endif
setIMContextInputHints ,
#if defined(ENABLE_OVERLOADING)
IMContextInputPurposePropertyInfo ,
#endif
constructIMContextInputPurpose ,
getIMContextInputPurpose ,
#if defined(ENABLE_OVERLOADING)
iMContextInputPurpose ,
#endif
setIMContextInputPurpose ,
C_IMContextCommitCallback ,
IMContextCommitCallback ,
#if defined(ENABLE_OVERLOADING)
IMContextCommitSignalInfo ,
#endif
afterIMContextCommit ,
genClosure_IMContextCommit ,
mk_IMContextCommitCallback ,
noIMContextCommitCallback ,
onIMContextCommit ,
wrap_IMContextCommitCallback ,
C_IMContextDeleteSurroundingCallback ,
IMContextDeleteSurroundingCallback ,
#if defined(ENABLE_OVERLOADING)
IMContextDeleteSurroundingSignalInfo ,
#endif
afterIMContextDeleteSurrounding ,
genClosure_IMContextDeleteSurrounding ,
mk_IMContextDeleteSurroundingCallback ,
noIMContextDeleteSurroundingCallback ,
onIMContextDeleteSurrounding ,
wrap_IMContextDeleteSurroundingCallback ,
C_IMContextPreeditChangedCallback ,
IMContextPreeditChangedCallback ,
#if defined(ENABLE_OVERLOADING)
IMContextPreeditChangedSignalInfo ,
#endif
afterIMContextPreeditChanged ,
genClosure_IMContextPreeditChanged ,
mk_IMContextPreeditChangedCallback ,
noIMContextPreeditChangedCallback ,
onIMContextPreeditChanged ,
wrap_IMContextPreeditChangedCallback ,
C_IMContextPreeditEndCallback ,
IMContextPreeditEndCallback ,
#if defined(ENABLE_OVERLOADING)
IMContextPreeditEndSignalInfo ,
#endif
afterIMContextPreeditEnd ,
genClosure_IMContextPreeditEnd ,
mk_IMContextPreeditEndCallback ,
noIMContextPreeditEndCallback ,
onIMContextPreeditEnd ,
wrap_IMContextPreeditEndCallback ,
C_IMContextPreeditStartCallback ,
IMContextPreeditStartCallback ,
#if defined(ENABLE_OVERLOADING)
IMContextPreeditStartSignalInfo ,
#endif
afterIMContextPreeditStart ,
genClosure_IMContextPreeditStart ,
mk_IMContextPreeditStartCallback ,
noIMContextPreeditStartCallback ,
onIMContextPreeditStart ,
wrap_IMContextPreeditStartCallback ,
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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import 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
newtype IMContext = IMContext (SP.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)
instance SP.ManagedPtrNewtype IMContext where
toManagedPtr :: IMContext -> ManagedPtr IMContext
toManagedPtr (IMContext ManagedPtr IMContext
p) = ManagedPtr IMContext
p
foreign import ccall "gtk_im_context_get_type"
c_gtk_im_context_get_type :: IO B.Types.GType
instance B.Types.TypedObject IMContext where
glibType :: IO GType
glibType = IO GType
c_gtk_im_context_get_type
instance B.Types.GObject IMContext
instance B.GValue.IsGValue IMContext where
toGValue :: IMContext -> IO GValue
toGValue 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 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
class (SP.GObject o, O.IsDescendantOf IMContext o) => IsIMContext o
instance (SP.GObject o, O.IsDescendantOf IMContext o) => IsIMContext o
instance O.HasParentTypes IMContext
type instance O.ParentTypes IMContext = '[GObject.Object.Object]
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, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr IMContext -> IMContext
IMContext
#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
type IMContextCommitCallback =
T.Text
-> IO ()
noIMContextCommitCallback :: Maybe IMContextCommitCallback
noIMContextCommitCallback :: Maybe IMContextCommitCallback
noIMContextCommitCallback = Maybe IMContextCommitCallback
forall a. Maybe a
Nothing
type C_IMContextCommitCallback =
Ptr () ->
CString ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_IMContextCommitCallback :: C_IMContextCommitCallback -> IO (FunPtr C_IMContextCommitCallback)
genClosure_IMContextCommit :: MonadIO m => IMContextCommitCallback -> m (GClosure C_IMContextCommitCallback)
genClosure_IMContextCommit :: IMContextCommitCallback -> m (GClosure C_IMContextCommitCallback)
genClosure_IMContextCommit 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_IMContextCommitCallback ::
IMContextCommitCallback ->
C_IMContextCommitCallback
wrap_IMContextCommitCallback :: IMContextCommitCallback -> C_IMContextCommitCallback
wrap_IMContextCommitCallback IMContextCommitCallback
_cb Ptr ()
_ CString
str Ptr ()
_ = do
Text
str' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
str
IMContextCommitCallback
_cb Text
str'
onIMContextCommit :: (IsIMContext a, MonadIO m) => a -> IMContextCommitCallback -> m SignalHandlerId
onIMContextCommit :: a -> IMContextCommitCallback -> m SignalHandlerId
onIMContextCommit a
obj 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 Text
"commit" FunPtr C_IMContextCommitCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterIMContextCommit :: (IsIMContext a, MonadIO m) => a -> IMContextCommitCallback -> m SignalHandlerId
afterIMContextCommit :: a -> IMContextCommitCallback -> m SignalHandlerId
afterIMContextCommit a
obj 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 Text
"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
type IMContextDeleteSurroundingCallback =
Int32
-> Int32
-> IO Bool
noIMContextDeleteSurroundingCallback :: Maybe IMContextDeleteSurroundingCallback
noIMContextDeleteSurroundingCallback :: Maybe IMContextDeleteSurroundingCallback
noIMContextDeleteSurroundingCallback = Maybe IMContextDeleteSurroundingCallback
forall a. Maybe a
Nothing
type C_IMContextDeleteSurroundingCallback =
Ptr () ->
Int32 ->
Int32 ->
Ptr () ->
IO CInt
foreign import ccall "wrapper"
mk_IMContextDeleteSurroundingCallback :: C_IMContextDeleteSurroundingCallback -> IO (FunPtr C_IMContextDeleteSurroundingCallback)
genClosure_IMContextDeleteSurrounding :: MonadIO m => IMContextDeleteSurroundingCallback -> m (GClosure C_IMContextDeleteSurroundingCallback)
genClosure_IMContextDeleteSurrounding :: IMContextDeleteSurroundingCallback
-> m (GClosure C_IMContextDeleteSurroundingCallback)
genClosure_IMContextDeleteSurrounding 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_IMContextDeleteSurroundingCallback ::
IMContextDeleteSurroundingCallback ->
C_IMContextDeleteSurroundingCallback
wrap_IMContextDeleteSurroundingCallback :: IMContextDeleteSurroundingCallback
-> C_IMContextDeleteSurroundingCallback
wrap_IMContextDeleteSurroundingCallback IMContextDeleteSurroundingCallback
_cb Ptr ()
_ Int32
offset Int32
nChars Ptr ()
_ = 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'
onIMContextDeleteSurrounding :: (IsIMContext a, MonadIO m) => a -> IMContextDeleteSurroundingCallback -> m SignalHandlerId
onIMContextDeleteSurrounding :: a -> IMContextDeleteSurroundingCallback -> m SignalHandlerId
onIMContextDeleteSurrounding a
obj 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 Text
"delete-surrounding" FunPtr C_IMContextDeleteSurroundingCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterIMContextDeleteSurrounding :: (IsIMContext a, MonadIO m) => a -> IMContextDeleteSurroundingCallback -> m SignalHandlerId
afterIMContextDeleteSurrounding :: a -> IMContextDeleteSurroundingCallback -> m SignalHandlerId
afterIMContextDeleteSurrounding a
obj 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 Text
"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
type IMContextPreeditChangedCallback =
IO ()
noIMContextPreeditChangedCallback :: Maybe IMContextPreeditChangedCallback
noIMContextPreeditChangedCallback :: Maybe (IO ())
noIMContextPreeditChangedCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_IMContextPreeditChangedCallback =
Ptr () ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_IMContextPreeditChangedCallback :: C_IMContextPreeditChangedCallback -> IO (FunPtr C_IMContextPreeditChangedCallback)
genClosure_IMContextPreeditChanged :: MonadIO m => IMContextPreeditChangedCallback -> m (GClosure C_IMContextPreeditChangedCallback)
genClosure_IMContextPreeditChanged :: IO () -> m (GClosure C_IMContextPreeditChangedCallback)
genClosure_IMContextPreeditChanged 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_IMContextPreeditChangedCallback ::
IMContextPreeditChangedCallback ->
C_IMContextPreeditChangedCallback
wrap_IMContextPreeditChangedCallback :: IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditChangedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
IO ()
_cb
onIMContextPreeditChanged :: (IsIMContext a, MonadIO m) => a -> IMContextPreeditChangedCallback -> m SignalHandlerId
onIMContextPreeditChanged :: a -> IO () -> m SignalHandlerId
onIMContextPreeditChanged a
obj 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 Text
"preedit-changed" FunPtr C_IMContextPreeditChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterIMContextPreeditChanged :: (IsIMContext a, MonadIO m) => a -> IMContextPreeditChangedCallback -> m SignalHandlerId
afterIMContextPreeditChanged :: a -> IO () -> m SignalHandlerId
afterIMContextPreeditChanged a
obj 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 Text
"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
type IMContextPreeditEndCallback =
IO ()
noIMContextPreeditEndCallback :: Maybe IMContextPreeditEndCallback
noIMContextPreeditEndCallback :: Maybe (IO ())
noIMContextPreeditEndCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_IMContextPreeditEndCallback =
Ptr () ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_IMContextPreeditEndCallback :: C_IMContextPreeditEndCallback -> IO (FunPtr C_IMContextPreeditEndCallback)
genClosure_IMContextPreeditEnd :: MonadIO m => IMContextPreeditEndCallback -> m (GClosure C_IMContextPreeditEndCallback)
genClosure_IMContextPreeditEnd :: IO () -> m (GClosure C_IMContextPreeditChangedCallback)
genClosure_IMContextPreeditEnd 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_IMContextPreeditEndCallback ::
IMContextPreeditEndCallback ->
C_IMContextPreeditEndCallback
wrap_IMContextPreeditEndCallback :: IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditEndCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
IO ()
_cb
onIMContextPreeditEnd :: (IsIMContext a, MonadIO m) => a -> IMContextPreeditEndCallback -> m SignalHandlerId
onIMContextPreeditEnd :: a -> IO () -> m SignalHandlerId
onIMContextPreeditEnd a
obj 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 Text
"preedit-end" FunPtr C_IMContextPreeditChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterIMContextPreeditEnd :: (IsIMContext a, MonadIO m) => a -> IMContextPreeditEndCallback -> m SignalHandlerId
afterIMContextPreeditEnd :: a -> IO () -> m SignalHandlerId
afterIMContextPreeditEnd a
obj 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 Text
"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
type IMContextPreeditStartCallback =
IO ()
noIMContextPreeditStartCallback :: Maybe IMContextPreeditStartCallback
noIMContextPreeditStartCallback :: Maybe (IO ())
noIMContextPreeditStartCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_IMContextPreeditStartCallback =
Ptr () ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_IMContextPreeditStartCallback :: C_IMContextPreeditStartCallback -> IO (FunPtr C_IMContextPreeditStartCallback)
genClosure_IMContextPreeditStart :: MonadIO m => IMContextPreeditStartCallback -> m (GClosure C_IMContextPreeditStartCallback)
genClosure_IMContextPreeditStart :: IO () -> m (GClosure C_IMContextPreeditChangedCallback)
genClosure_IMContextPreeditStart 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_IMContextPreeditStartCallback ::
IMContextPreeditStartCallback ->
C_IMContextPreeditStartCallback
wrap_IMContextPreeditStartCallback :: IO () -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditStartCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
IO ()
_cb
onIMContextPreeditStart :: (IsIMContext a, MonadIO m) => a -> IMContextPreeditStartCallback -> m SignalHandlerId
onIMContextPreeditStart :: a -> IO () -> m SignalHandlerId
onIMContextPreeditStart a
obj 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 Text
"preedit-start" FunPtr C_IMContextPreeditChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterIMContextPreeditStart :: (IsIMContext a, MonadIO m) => a -> IMContextPreeditStartCallback -> m SignalHandlerId
afterIMContextPreeditStart :: a -> IO () -> m SignalHandlerId
afterIMContextPreeditStart a
obj 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 Text
"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
type IMContextRetrieveSurroundingCallback =
IO Bool
noIMContextRetrieveSurroundingCallback :: Maybe IMContextRetrieveSurroundingCallback
noIMContextRetrieveSurroundingCallback :: Maybe IMContextRetrieveSurroundingCallback
noIMContextRetrieveSurroundingCallback = Maybe IMContextRetrieveSurroundingCallback
forall a. Maybe a
Nothing
type C_IMContextRetrieveSurroundingCallback =
Ptr () ->
Ptr () ->
IO CInt
foreign import ccall "wrapper"
mk_IMContextRetrieveSurroundingCallback :: C_IMContextRetrieveSurroundingCallback -> IO (FunPtr C_IMContextRetrieveSurroundingCallback)
genClosure_IMContextRetrieveSurrounding :: MonadIO m => IMContextRetrieveSurroundingCallback -> m (GClosure C_IMContextRetrieveSurroundingCallback)
genClosure_IMContextRetrieveSurrounding :: IMContextRetrieveSurroundingCallback
-> m (GClosure C_IMContextRetrieveSurroundingCallback)
genClosure_IMContextRetrieveSurrounding 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_IMContextRetrieveSurroundingCallback ::
IMContextRetrieveSurroundingCallback ->
C_IMContextRetrieveSurroundingCallback
wrap_IMContextRetrieveSurroundingCallback :: IMContextRetrieveSurroundingCallback
-> C_IMContextRetrieveSurroundingCallback
wrap_IMContextRetrieveSurroundingCallback IMContextRetrieveSurroundingCallback
_cb Ptr ()
_ Ptr ()
_ = 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'
onIMContextRetrieveSurrounding :: (IsIMContext a, MonadIO m) => a -> IMContextRetrieveSurroundingCallback -> m SignalHandlerId
onIMContextRetrieveSurrounding :: a -> IMContextRetrieveSurroundingCallback -> m SignalHandlerId
onIMContextRetrieveSurrounding a
obj 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 Text
"retrieve-surrounding" FunPtr C_IMContextRetrieveSurroundingCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterIMContextRetrieveSurrounding :: (IsIMContext a, MonadIO m) => a -> IMContextRetrieveSurroundingCallback -> m SignalHandlerId
afterIMContextRetrieveSurrounding :: a -> IMContextRetrieveSurroundingCallback -> m SignalHandlerId
afterIMContextRetrieveSurrounding a
obj 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 Text
"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
getIMContextInputHints :: (MonadIO m, IsIMContext o) => o -> m [Gtk.Flags.InputHints]
getIMContextInputHints :: o -> m [InputHints]
getIMContextInputHints 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 String
"input-hints"
setIMContextInputHints :: (MonadIO m, IsIMContext o) => o -> [Gtk.Flags.InputHints] -> m ()
setIMContextInputHints :: o -> [InputHints] -> m ()
setIMContextInputHints o
obj [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 String
"input-hints" [InputHints]
val
constructIMContextInputHints :: (IsIMContext o, MIO.MonadIO m) => [Gtk.Flags.InputHints] -> m (GValueConstruct o)
constructIMContextInputHints :: [InputHints] -> m (GValueConstruct o)
constructIMContextInputHints [InputHints]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> [InputHints] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"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
getIMContextInputPurpose :: (MonadIO m, IsIMContext o) => o -> m Gtk.Enums.InputPurpose
getIMContextInputPurpose :: o -> m InputPurpose
getIMContextInputPurpose 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 String
"input-purpose"
setIMContextInputPurpose :: (MonadIO m, IsIMContext o) => o -> Gtk.Enums.InputPurpose -> m ()
setIMContextInputPurpose :: o -> InputPurpose -> m ()
setIMContextInputPurpose o
obj 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 String
"input-purpose" InputPurpose
val
constructIMContextInputPurpose :: (IsIMContext o, MIO.MonadIO m) => Gtk.Enums.InputPurpose -> m (GValueConstruct o)
constructIMContextInputPurpose :: InputPurpose -> m (GValueConstruct o)
constructIMContextInputPurpose InputPurpose
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> InputPurpose -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"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
foreign import ccall "gtk_im_context_delete_surrounding" gtk_im_context_delete_surrounding ::
Ptr IMContext ->
Int32 ->
Int32 ->
IO CInt
iMContextDeleteSurrounding ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
a
-> Int32
-> Int32
-> m Bool
iMContextDeleteSurrounding :: a -> Int32 -> Int32 -> m Bool
iMContextDeleteSurrounding a
context Int32
offset 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
/= CInt
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
foreign import ccall "gtk_im_context_filter_keypress" gtk_im_context_filter_keypress ::
Ptr IMContext ->
Ptr Gdk.EventKey.EventKey ->
IO CInt
iMContextFilterKeypress ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
a
-> Gdk.EventKey.EventKey
-> m Bool
iMContextFilterKeypress :: a -> EventKey -> m Bool
iMContextFilterKeypress a
context 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
/= CInt
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
foreign import ccall "gtk_im_context_focus_in" gtk_im_context_focus_in ::
Ptr IMContext ->
IO ()
iMContextFocusIn ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
a
-> m ()
iMContextFocusIn :: a -> m ()
iMContextFocusIn 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
foreign import ccall "gtk_im_context_focus_out" gtk_im_context_focus_out ::
Ptr IMContext ->
IO ()
iMContextFocusOut ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
a
-> m ()
iMContextFocusOut :: a -> m ()
iMContextFocusOut 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
foreign import ccall "gtk_im_context_get_preedit_string" gtk_im_context_get_preedit_string ::
Ptr IMContext ->
Ptr CString ->
Ptr (Ptr Pango.AttrList.AttrList) ->
Ptr Int32 ->
IO ()
iMContextGetPreeditString ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
a
-> m ((T.Text, Pango.AttrList.AttrList, Int32))
iMContextGetPreeditString :: a -> m (Text, AttrList, Int32)
iMContextGetPreeditString 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)
callocMem :: IO (Ptr CString)
Ptr (Ptr AttrList)
attrs <- IO (Ptr (Ptr AttrList))
forall a. Storable a => IO (Ptr a)
callocMem :: 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, GBoxed 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
foreign import ccall "gtk_im_context_get_surrounding" gtk_im_context_get_surrounding ::
Ptr IMContext ->
Ptr CString ->
Ptr Int32 ->
IO CInt
iMContextGetSurrounding ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
a
-> m ((Bool, T.Text, Int32))
iMContextGetSurrounding :: a -> m (Bool, Text, Int32)
iMContextGetSurrounding 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)
callocMem :: 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
/= CInt
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
foreign import ccall "gtk_im_context_reset" gtk_im_context_reset ::
Ptr IMContext ->
IO ()
iMContextReset ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
a
-> m ()
iMContextReset :: a -> m ()
iMContextReset 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
foreign import ccall "gtk_im_context_set_client_window" gtk_im_context_set_client_window ::
Ptr IMContext ->
Ptr Gdk.Window.Window ->
IO ()
iMContextSetClientWindow ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a, Gdk.Window.IsWindow b) =>
a
-> Maybe (b)
-> m ()
iMContextSetClientWindow :: a -> Maybe b -> m ()
iMContextSetClientWindow a
context 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
Maybe b
Nothing -> Ptr Window -> IO (Ptr Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
forall a. Ptr a
nullPtr
Just 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
foreign import ccall "gtk_im_context_set_cursor_location" gtk_im_context_set_cursor_location ::
Ptr IMContext ->
Ptr Gdk.Rectangle.Rectangle ->
IO ()
iMContextSetCursorLocation ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
a
-> Gdk.Rectangle.Rectangle
-> m ()
iMContextSetCursorLocation :: a -> Rectangle -> m ()
iMContextSetCursorLocation a
context 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
foreign import ccall "gtk_im_context_set_surrounding" gtk_im_context_set_surrounding ::
Ptr IMContext ->
CString ->
Int32 ->
Int32 ->
IO ()
iMContextSetSurrounding ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
a
-> T.Text
-> Int32
-> Int32
-> m ()
iMContextSetSurrounding :: a -> Text -> Int32 -> Int32 -> m ()
iMContextSetSurrounding a
context Text
text Int32
len 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
foreign import ccall "gtk_im_context_set_use_preedit" gtk_im_context_set_use_preedit ::
Ptr IMContext ->
CInt ->
IO ()
iMContextSetUsePreedit ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
a
-> Bool
-> m ()
iMContextSetUsePreedit :: a -> Bool -> m ()
iMContextSetUsePreedit a
context 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