{-# LANGUAGE ImplicitParams, RankNTypes, 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)
IMContextActivateOskMethodInfo ,
#endif
iMContextActivateOsk ,
#if defined(ENABLE_OVERLOADING)
IMContextDeleteSurroundingMethodInfo ,
#endif
iMContextDeleteSurrounding ,
#if defined(ENABLE_OVERLOADING)
IMContextFilterKeyMethodInfo ,
#endif
iMContextFilterKey ,
#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)
IMContextGetSurroundingWithSelectionMethodInfo,
#endif
iMContextGetSurroundingWithSelection ,
#if defined(ENABLE_OVERLOADING)
IMContextResetMethodInfo ,
#endif
iMContextReset ,
#if defined(ENABLE_OVERLOADING)
IMContextSetClientWidgetMethodInfo ,
#endif
iMContextSetClientWidget ,
#if defined(ENABLE_OVERLOADING)
IMContextSetCursorLocationMethodInfo ,
#endif
iMContextSetCursorLocation ,
#if defined(ENABLE_OVERLOADING)
IMContextSetSurroundingMethodInfo ,
#endif
iMContextSetSurrounding ,
#if defined(ENABLE_OVERLOADING)
IMContextSetSurroundingWithSelectionMethodInfo,
#endif
iMContextSetSurroundingWithSelection ,
#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 ,
IMContextCommitCallback ,
#if defined(ENABLE_OVERLOADING)
IMContextCommitSignalInfo ,
#endif
afterIMContextCommit ,
onIMContextCommit ,
IMContextDeleteSurroundingCallback ,
#if defined(ENABLE_OVERLOADING)
IMContextDeleteSurroundingSignalInfo ,
#endif
afterIMContextDeleteSurrounding ,
onIMContextDeleteSurrounding ,
IMContextPreeditChangedCallback ,
#if defined(ENABLE_OVERLOADING)
IMContextPreeditChangedSignalInfo ,
#endif
afterIMContextPreeditChanged ,
onIMContextPreeditChanged ,
IMContextPreeditEndCallback ,
#if defined(ENABLE_OVERLOADING)
IMContextPreeditEndSignalInfo ,
#endif
afterIMContextPreeditEnd ,
onIMContextPreeditEnd ,
IMContextPreeditStartCallback ,
#if defined(ENABLE_OVERLOADING)
IMContextPreeditStartSignalInfo ,
#endif
afterIMContextPreeditStart ,
onIMContextPreeditStart ,
IMContextRetrieveSurroundingCallback ,
#if defined(ENABLE_OVERLOADING)
IMContextRetrieveSurroundingSignalInfo ,
#endif
afterIMContextRetrieveSurrounding ,
onIMContextRetrieveSurrounding ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gdk.Interfaces.Paintable as Gdk.Paintable
import qualified GI.Gdk.Objects.Clipboard as Gdk.Clipboard
import qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import qualified GI.Gdk.Objects.Device as Gdk.Device
import qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gdk.Objects.Event as Gdk.Event
import qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import qualified GI.Gdk.Objects.Snapshot as Gdk.Snapshot
import qualified GI.Gdk.Objects.Surface as Gdk.Surface
import qualified GI.Gdk.Objects.Texture as Gdk.Texture
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.Gio.Interfaces.ActionGroup as Gio.ActionGroup
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Graphene.Structs.Matrix as Graphene.Matrix
import qualified GI.Graphene.Structs.Point as Graphene.Point
import qualified GI.Graphene.Structs.Point3D as Graphene.Point3D
import qualified GI.Graphene.Structs.Rect as Graphene.Rect
import qualified GI.Graphene.Structs.Size as Graphene.Size
import qualified GI.Graphene.Structs.Vec3 as Graphene.Vec3
import qualified GI.Graphene.Structs.Vec4 as Graphene.Vec4
import qualified GI.Gsk.Enums as Gsk.Enums
import qualified GI.Gsk.Objects.GLShader as Gsk.GLShader
import qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode
import qualified GI.Gsk.Objects.Renderer as Gsk.Renderer
import qualified GI.Gsk.Structs.ColorStop as Gsk.ColorStop
import qualified GI.Gsk.Structs.Path as Gsk.Path
import qualified GI.Gsk.Structs.RoundedRect as Gsk.RoundedRect
import qualified GI.Gsk.Structs.Shadow as Gsk.Shadow
import qualified GI.Gsk.Structs.Stroke as Gsk.Stroke
import qualified GI.Gsk.Structs.Transform as Gsk.Transform
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Native as Gtk.Native
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Root as Gtk.Root
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.StyleProvider as Gtk.StyleProvider
import {-# SOURCE #-} qualified GI.Gtk.Objects.ATContext as Gtk.ATContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.EventController as Gtk.EventController
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutChild as Gtk.LayoutChild
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutManager as Gtk.LayoutManager
import {-# SOURCE #-} qualified GI.Gtk.Objects.Settings as Gtk.Settings
import {-# SOURCE #-} qualified GI.Gtk.Objects.Snapshot as Gtk.Snapshot
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.Tooltip as Gtk.Tooltip
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Structs.Border as Gtk.Border
import {-# SOURCE #-} qualified GI.Gtk.Structs.Requisition as Gtk.Requisition
import qualified GI.Pango.Enums as Pango.Enums
import qualified GI.Pango.Objects.Context as Pango.Context
import qualified GI.Pango.Objects.FontMap as Pango.FontMap
import qualified GI.Pango.Objects.Layout as Pango.Layout
import qualified GI.Pango.Structs.AttrList as Pango.AttrList
#else
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gdk.Objects.Device as Gdk.Device
import qualified GI.Gdk.Objects.Event as Gdk.Event
import qualified GI.Gdk.Objects.Surface as Gdk.Surface
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 {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import qualified GI.Pango.Structs.AttrList as Pango.AttrList
#endif
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
$c== :: IMContext -> IMContext -> Bool
== :: IMContext -> IMContext -> Bool
$c/= :: IMContext -> IMContext -> Bool
/= :: 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
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 :: (MIO.MonadIO m, IsIMContext o) => o -> m IMContext
toIMContext :: forall (m :: * -> *) o.
(MonadIO m, IsIMContext o) =>
o -> m IMContext
toIMContext = IO IMContext -> m IMContext
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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'
B.ManagedPtr.unsafeCastTo ManagedPtr IMContext -> IMContext
IMContext
instance B.GValue.IsGValue (Maybe IMContext) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_im_context_get_type
gvalueSet_ :: Ptr GValue -> Maybe IMContext -> IO ()
gvalueSet_ Ptr GValue
gv Maybe IMContext
P.Nothing = Ptr GValue -> Ptr IMContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr IMContext
forall a. Ptr a
FP.nullPtr :: FP.Ptr IMContext)
gvalueSet_ Ptr GValue
gv (P.Just IMContext
obj) = IMContext -> (Ptr IMContext -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr IMContext
obj (Ptr GValue -> Ptr IMContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe IMContext)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr IMContext)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr IMContext)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newObject IMContext ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveIMContextMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveIMContextMethod "activateOsk" o = IMContextActivateOskMethodInfo
ResolveIMContextMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveIMContextMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveIMContextMethod "deleteSurrounding" o = IMContextDeleteSurroundingMethodInfo
ResolveIMContextMethod "filterKey" o = IMContextFilterKeyMethodInfo
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 "getSurroundingWithSelection" o = IMContextGetSurroundingWithSelectionMethodInfo
ResolveIMContextMethod "setClientWidget" o = IMContextSetClientWidgetMethodInfo
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 "setSurroundingWithSelection" o = IMContextSetSurroundingWithSelectionMethodInfo
ResolveIMContextMethod "setUsePreedit" o = IMContextSetUsePreeditMethodInfo
ResolveIMContextMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveIMContextMethod t IMContext, O.OverloadedMethod 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
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveIMContextMethod t IMContext, O.OverloadedMethod info IMContext p, R.HasField t IMContext p) => R.HasField t IMContext p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveIMContextMethod t IMContext, O.OverloadedMethodInfo info IMContext) => OL.IsLabel t (O.MethodProxy info IMContext) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type IMContextCommitCallback =
T.Text
-> IO ()
type C_IMContextCommitCallback =
Ptr IMContext ->
CString ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_IMContextCommitCallback :: C_IMContextCommitCallback -> IO (FunPtr C_IMContextCommitCallback)
wrap_IMContextCommitCallback ::
GObject a => (a -> IMContextCommitCallback) ->
C_IMContextCommitCallback
wrap_IMContextCommitCallback :: forall a.
GObject a =>
(a -> IMContextCommitCallback) -> C_IMContextCommitCallback
wrap_IMContextCommitCallback a -> IMContextCommitCallback
gi'cb Ptr IMContext
gi'selfPtr CString
str Ptr ()
_ = do
str' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
str
B.ManagedPtr.withNewObject gi'selfPtr $ \IMContext
gi'self -> a -> IMContextCommitCallback
gi'cb (IMContext -> a
forall a b. Coercible a b => a -> b
Coerce.coerce IMContext
gi'self) Text
str'
onIMContextCommit :: (IsIMContext a, MonadIO m) => a -> ((?self :: a) => IMContextCommitCallback) -> m SignalHandlerId
onIMContextCommit :: forall a (m :: * -> *).
(IsIMContext a, MonadIO m) =>
a -> ((?self::a) => IMContextCommitCallback) -> m SignalHandlerId
onIMContextCommit a
obj (?self::a) => IMContextCommitCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IMContextCommitCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => IMContextCommitCallback
IMContextCommitCallback
cb
let wrapped' :: C_IMContextCommitCallback
wrapped' = (a -> IMContextCommitCallback) -> C_IMContextCommitCallback
forall a.
GObject a =>
(a -> IMContextCommitCallback) -> C_IMContextCommitCallback
wrap_IMContextCommitCallback a -> IMContextCommitCallback
wrapped
wrapped'' <- C_IMContextCommitCallback -> IO (FunPtr C_IMContextCommitCallback)
mk_IMContextCommitCallback C_IMContextCommitCallback
wrapped'
connectSignalFunPtr obj "commit" wrapped'' SignalConnectBefore Nothing
afterIMContextCommit :: (IsIMContext a, MonadIO m) => a -> ((?self :: a) => IMContextCommitCallback) -> m SignalHandlerId
afterIMContextCommit :: forall a (m :: * -> *).
(IsIMContext a, MonadIO m) =>
a -> ((?self::a) => IMContextCommitCallback) -> m SignalHandlerId
afterIMContextCommit a
obj (?self::a) => IMContextCommitCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IMContextCommitCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => IMContextCommitCallback
IMContextCommitCallback
cb
let wrapped' :: C_IMContextCommitCallback
wrapped' = (a -> IMContextCommitCallback) -> C_IMContextCommitCallback
forall a.
GObject a =>
(a -> IMContextCommitCallback) -> C_IMContextCommitCallback
wrap_IMContextCommitCallback a -> IMContextCommitCallback
wrapped
wrapped'' <- C_IMContextCommitCallback -> IO (FunPtr C_IMContextCommitCallback)
mk_IMContextCommitCallback C_IMContextCommitCallback
wrapped'
connectSignalFunPtr obj "commit" wrapped'' SignalConnectAfter 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext::commit"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#g:signal:commit"})
#endif
type IMContextDeleteSurroundingCallback =
Int32
-> Int32
-> IO Bool
type C_IMContextDeleteSurroundingCallback =
Ptr IMContext ->
Int32 ->
Int32 ->
Ptr () ->
IO CInt
foreign import ccall "wrapper"
mk_IMContextDeleteSurroundingCallback :: C_IMContextDeleteSurroundingCallback -> IO (FunPtr C_IMContextDeleteSurroundingCallback)
wrap_IMContextDeleteSurroundingCallback ::
GObject a => (a -> IMContextDeleteSurroundingCallback) ->
C_IMContextDeleteSurroundingCallback
wrap_IMContextDeleteSurroundingCallback :: forall a.
GObject a =>
(a -> IMContextDeleteSurroundingCallback)
-> C_IMContextDeleteSurroundingCallback
wrap_IMContextDeleteSurroundingCallback a -> IMContextDeleteSurroundingCallback
gi'cb Ptr IMContext
gi'selfPtr Int32
offset Int32
nChars Ptr ()
_ = do
result <- Ptr IMContext -> (IMContext -> IO Bool) -> IO Bool
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr IMContext
gi'selfPtr ((IMContext -> IO Bool) -> IO Bool)
-> (IMContext -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \IMContext
gi'self -> a -> IMContextDeleteSurroundingCallback
gi'cb (IMContext -> a
forall a b. Coercible a b => a -> b
Coerce.coerce IMContext
gi'self) Int32
offset Int32
nChars
let result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
result
return result'
onIMContextDeleteSurrounding :: (IsIMContext a, MonadIO m) => a -> ((?self :: a) => IMContextDeleteSurroundingCallback) -> m SignalHandlerId
onIMContextDeleteSurrounding :: forall a (m :: * -> *).
(IsIMContext a, MonadIO m) =>
a
-> ((?self::a) => IMContextDeleteSurroundingCallback)
-> m SignalHandlerId
onIMContextDeleteSurrounding a
obj (?self::a) => IMContextDeleteSurroundingCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IMContextDeleteSurroundingCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => IMContextDeleteSurroundingCallback
IMContextDeleteSurroundingCallback
cb
let wrapped' :: C_IMContextDeleteSurroundingCallback
wrapped' = (a -> IMContextDeleteSurroundingCallback)
-> C_IMContextDeleteSurroundingCallback
forall a.
GObject a =>
(a -> IMContextDeleteSurroundingCallback)
-> C_IMContextDeleteSurroundingCallback
wrap_IMContextDeleteSurroundingCallback a -> IMContextDeleteSurroundingCallback
wrapped
wrapped'' <- C_IMContextDeleteSurroundingCallback
-> IO (FunPtr C_IMContextDeleteSurroundingCallback)
mk_IMContextDeleteSurroundingCallback C_IMContextDeleteSurroundingCallback
wrapped'
connectSignalFunPtr obj "delete-surrounding" wrapped'' SignalConnectBefore Nothing
afterIMContextDeleteSurrounding :: (IsIMContext a, MonadIO m) => a -> ((?self :: a) => IMContextDeleteSurroundingCallback) -> m SignalHandlerId
afterIMContextDeleteSurrounding :: forall a (m :: * -> *).
(IsIMContext a, MonadIO m) =>
a
-> ((?self::a) => IMContextDeleteSurroundingCallback)
-> m SignalHandlerId
afterIMContextDeleteSurrounding a
obj (?self::a) => IMContextDeleteSurroundingCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IMContextDeleteSurroundingCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => IMContextDeleteSurroundingCallback
IMContextDeleteSurroundingCallback
cb
let wrapped' :: C_IMContextDeleteSurroundingCallback
wrapped' = (a -> IMContextDeleteSurroundingCallback)
-> C_IMContextDeleteSurroundingCallback
forall a.
GObject a =>
(a -> IMContextDeleteSurroundingCallback)
-> C_IMContextDeleteSurroundingCallback
wrap_IMContextDeleteSurroundingCallback a -> IMContextDeleteSurroundingCallback
wrapped
wrapped'' <- C_IMContextDeleteSurroundingCallback
-> IO (FunPtr C_IMContextDeleteSurroundingCallback)
mk_IMContextDeleteSurroundingCallback C_IMContextDeleteSurroundingCallback
wrapped'
connectSignalFunPtr obj "delete-surrounding" wrapped'' SignalConnectAfter 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext::delete-surrounding"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#g:signal:deleteSurrounding"})
#endif
type IMContextPreeditChangedCallback =
IO ()
type C_IMContextPreeditChangedCallback =
Ptr IMContext ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_IMContextPreeditChangedCallback :: C_IMContextPreeditChangedCallback -> IO (FunPtr C_IMContextPreeditChangedCallback)
wrap_IMContextPreeditChangedCallback ::
GObject a => (a -> IMContextPreeditChangedCallback) ->
C_IMContextPreeditChangedCallback
wrap_IMContextPreeditChangedCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditChangedCallback a -> IO ()
gi'cb Ptr IMContext
gi'selfPtr Ptr ()
_ = do
Ptr IMContext -> (IMContext -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr IMContext
gi'selfPtr ((IMContext -> IO ()) -> IO ()) -> (IMContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \IMContext
gi'self -> a -> IO ()
gi'cb (IMContext -> a
forall a b. Coercible a b => a -> b
Coerce.coerce IMContext
gi'self)
onIMContextPreeditChanged :: (IsIMContext a, MonadIO m) => a -> ((?self :: a) => IMContextPreeditChangedCallback) -> m SignalHandlerId
onIMContextPreeditChanged :: forall a (m :: * -> *).
(IsIMContext a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onIMContextPreeditChanged a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_IMContextPreeditChangedCallback
wrapped' = (a -> IO ()) -> C_IMContextPreeditChangedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditChangedCallback a -> IO ()
wrapped
wrapped'' <- C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditChangedCallback C_IMContextPreeditChangedCallback
wrapped'
connectSignalFunPtr obj "preedit-changed" wrapped'' SignalConnectBefore Nothing
afterIMContextPreeditChanged :: (IsIMContext a, MonadIO m) => a -> ((?self :: a) => IMContextPreeditChangedCallback) -> m SignalHandlerId
afterIMContextPreeditChanged :: forall a (m :: * -> *).
(IsIMContext a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterIMContextPreeditChanged a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_IMContextPreeditChangedCallback
wrapped' = (a -> IO ()) -> C_IMContextPreeditChangedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditChangedCallback a -> IO ()
wrapped
wrapped'' <- C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditChangedCallback C_IMContextPreeditChangedCallback
wrapped'
connectSignalFunPtr obj "preedit-changed" wrapped'' SignalConnectAfter 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext::preedit-changed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#g:signal:preeditChanged"})
#endif
type IMContextPreeditEndCallback =
IO ()
type C_IMContextPreeditEndCallback =
Ptr IMContext ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_IMContextPreeditEndCallback :: C_IMContextPreeditEndCallback -> IO (FunPtr C_IMContextPreeditEndCallback)
wrap_IMContextPreeditEndCallback ::
GObject a => (a -> IMContextPreeditEndCallback) ->
C_IMContextPreeditEndCallback
wrap_IMContextPreeditEndCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditEndCallback a -> IO ()
gi'cb Ptr IMContext
gi'selfPtr Ptr ()
_ = do
Ptr IMContext -> (IMContext -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr IMContext
gi'selfPtr ((IMContext -> IO ()) -> IO ()) -> (IMContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \IMContext
gi'self -> a -> IO ()
gi'cb (IMContext -> a
forall a b. Coercible a b => a -> b
Coerce.coerce IMContext
gi'self)
onIMContextPreeditEnd :: (IsIMContext a, MonadIO m) => a -> ((?self :: a) => IMContextPreeditEndCallback) -> m SignalHandlerId
onIMContextPreeditEnd :: forall a (m :: * -> *).
(IsIMContext a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onIMContextPreeditEnd a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_IMContextPreeditChangedCallback
wrapped' = (a -> IO ()) -> C_IMContextPreeditChangedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditEndCallback a -> IO ()
wrapped
wrapped'' <- C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditEndCallback C_IMContextPreeditChangedCallback
wrapped'
connectSignalFunPtr obj "preedit-end" wrapped'' SignalConnectBefore Nothing
afterIMContextPreeditEnd :: (IsIMContext a, MonadIO m) => a -> ((?self :: a) => IMContextPreeditEndCallback) -> m SignalHandlerId
afterIMContextPreeditEnd :: forall a (m :: * -> *).
(IsIMContext a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterIMContextPreeditEnd a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_IMContextPreeditChangedCallback
wrapped' = (a -> IO ()) -> C_IMContextPreeditChangedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditEndCallback a -> IO ()
wrapped
wrapped'' <- C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditEndCallback C_IMContextPreeditChangedCallback
wrapped'
connectSignalFunPtr obj "preedit-end" wrapped'' SignalConnectAfter 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext::preedit-end"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#g:signal:preeditEnd"})
#endif
type IMContextPreeditStartCallback =
IO ()
type C_IMContextPreeditStartCallback =
Ptr IMContext ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_IMContextPreeditStartCallback :: C_IMContextPreeditStartCallback -> IO (FunPtr C_IMContextPreeditStartCallback)
wrap_IMContextPreeditStartCallback ::
GObject a => (a -> IMContextPreeditStartCallback) ->
C_IMContextPreeditStartCallback
wrap_IMContextPreeditStartCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditStartCallback a -> IO ()
gi'cb Ptr IMContext
gi'selfPtr Ptr ()
_ = do
Ptr IMContext -> (IMContext -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr IMContext
gi'selfPtr ((IMContext -> IO ()) -> IO ()) -> (IMContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \IMContext
gi'self -> a -> IO ()
gi'cb (IMContext -> a
forall a b. Coercible a b => a -> b
Coerce.coerce IMContext
gi'self)
onIMContextPreeditStart :: (IsIMContext a, MonadIO m) => a -> ((?self :: a) => IMContextPreeditStartCallback) -> m SignalHandlerId
onIMContextPreeditStart :: forall a (m :: * -> *).
(IsIMContext a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onIMContextPreeditStart a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_IMContextPreeditChangedCallback
wrapped' = (a -> IO ()) -> C_IMContextPreeditChangedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditStartCallback a -> IO ()
wrapped
wrapped'' <- C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditStartCallback C_IMContextPreeditChangedCallback
wrapped'
connectSignalFunPtr obj "preedit-start" wrapped'' SignalConnectBefore Nothing
afterIMContextPreeditStart :: (IsIMContext a, MonadIO m) => a -> ((?self :: a) => IMContextPreeditStartCallback) -> m SignalHandlerId
afterIMContextPreeditStart :: forall a (m :: * -> *).
(IsIMContext a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterIMContextPreeditStart a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_IMContextPreeditChangedCallback
wrapped' = (a -> IO ()) -> C_IMContextPreeditChangedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_IMContextPreeditChangedCallback
wrap_IMContextPreeditStartCallback a -> IO ()
wrapped
wrapped'' <- C_IMContextPreeditChangedCallback
-> IO (FunPtr C_IMContextPreeditChangedCallback)
mk_IMContextPreeditStartCallback C_IMContextPreeditChangedCallback
wrapped'
connectSignalFunPtr obj "preedit-start" wrapped'' SignalConnectAfter 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext::preedit-start"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#g:signal:preeditStart"})
#endif
type IMContextRetrieveSurroundingCallback =
IO Bool
type C_IMContextRetrieveSurroundingCallback =
Ptr IMContext ->
Ptr () ->
IO CInt
foreign import ccall "wrapper"
mk_IMContextRetrieveSurroundingCallback :: C_IMContextRetrieveSurroundingCallback -> IO (FunPtr C_IMContextRetrieveSurroundingCallback)
wrap_IMContextRetrieveSurroundingCallback ::
GObject a => (a -> IMContextRetrieveSurroundingCallback) ->
C_IMContextRetrieveSurroundingCallback
wrap_IMContextRetrieveSurroundingCallback :: forall a.
GObject a =>
(a -> IO Bool) -> C_IMContextRetrieveSurroundingCallback
wrap_IMContextRetrieveSurroundingCallback a -> IO Bool
gi'cb Ptr IMContext
gi'selfPtr Ptr ()
_ = do
result <- Ptr IMContext -> (IMContext -> IO Bool) -> IO Bool
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr IMContext
gi'selfPtr ((IMContext -> IO Bool) -> IO Bool)
-> (IMContext -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \IMContext
gi'self -> a -> IO Bool
gi'cb (IMContext -> a
forall a b. Coercible a b => a -> b
Coerce.coerce IMContext
gi'self)
let result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
result
return result'
onIMContextRetrieveSurrounding :: (IsIMContext a, MonadIO m) => a -> ((?self :: a) => IMContextRetrieveSurroundingCallback) -> m SignalHandlerId
onIMContextRetrieveSurrounding :: forall a (m :: * -> *).
(IsIMContext a, MonadIO m) =>
a -> ((?self::a) => IO Bool) -> m SignalHandlerId
onIMContextRetrieveSurrounding a
obj (?self::a) => IO Bool
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO Bool
wrapped a
self = let ?self = a
?self::a
self in IO Bool
(?self::a) => IO Bool
cb
let wrapped' :: C_IMContextRetrieveSurroundingCallback
wrapped' = (a -> IO Bool) -> C_IMContextRetrieveSurroundingCallback
forall a.
GObject a =>
(a -> IO Bool) -> C_IMContextRetrieveSurroundingCallback
wrap_IMContextRetrieveSurroundingCallback a -> IO Bool
wrapped
wrapped'' <- C_IMContextRetrieveSurroundingCallback
-> IO (FunPtr C_IMContextRetrieveSurroundingCallback)
mk_IMContextRetrieveSurroundingCallback C_IMContextRetrieveSurroundingCallback
wrapped'
connectSignalFunPtr obj "retrieve-surrounding" wrapped'' SignalConnectBefore Nothing
afterIMContextRetrieveSurrounding :: (IsIMContext a, MonadIO m) => a -> ((?self :: a) => IMContextRetrieveSurroundingCallback) -> m SignalHandlerId
afterIMContextRetrieveSurrounding :: forall a (m :: * -> *).
(IsIMContext a, MonadIO m) =>
a -> ((?self::a) => IO Bool) -> m SignalHandlerId
afterIMContextRetrieveSurrounding a
obj (?self::a) => IO Bool
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> IO Bool
wrapped a
self = let ?self = a
?self::a
self in IO Bool
(?self::a) => IO Bool
cb
let wrapped' :: C_IMContextRetrieveSurroundingCallback
wrapped' = (a -> IO Bool) -> C_IMContextRetrieveSurroundingCallback
forall a.
GObject a =>
(a -> IO Bool) -> C_IMContextRetrieveSurroundingCallback
wrap_IMContextRetrieveSurroundingCallback a -> IO Bool
wrapped
wrapped'' <- C_IMContextRetrieveSurroundingCallback
-> IO (FunPtr C_IMContextRetrieveSurroundingCallback)
mk_IMContextRetrieveSurroundingCallback C_IMContextRetrieveSurroundingCallback
wrapped'
connectSignalFunPtr obj "retrieve-surrounding" wrapped'' SignalConnectAfter 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
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext::retrieve-surrounding"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#g:signal:retrieveSurrounding"})
#endif
getIMContextInputHints :: (MonadIO m, IsIMContext o) => o -> m [Gtk.Flags.InputHints]
getIMContextInputHints :: forall (m :: * -> *) o.
(MonadIO m, IsIMContext o) =>
o -> m [InputHints]
getIMContextInputHints o
obj = IO [InputHints] -> m [InputHints]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 :: forall (m :: * -> *) o.
(MonadIO m, IsIMContext o) =>
o -> [InputHints] -> m ()
setIMContextInputHints o
obj [InputHints]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
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 :: forall o (m :: * -> *).
(IsIMContext o, MonadIO m) =>
[InputHints] -> m (GValueConstruct o)
constructIMContextInputHints [InputHints]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.inputHints"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#g:attr:inputHints"
})
#endif
getIMContextInputPurpose :: (MonadIO m, IsIMContext o) => o -> m Gtk.Enums.InputPurpose
getIMContextInputPurpose :: forall (m :: * -> *) o.
(MonadIO m, IsIMContext o) =>
o -> m InputPurpose
getIMContextInputPurpose o
obj = IO InputPurpose -> m InputPurpose
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 :: forall (m :: * -> *) o.
(MonadIO m, IsIMContext o) =>
o -> InputPurpose -> m ()
setIMContextInputPurpose o
obj InputPurpose
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
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 :: forall o (m :: * -> *).
(IsIMContext o, MonadIO m) =>
InputPurpose -> m (GValueConstruct o)
constructIMContextInputPurpose InputPurpose
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.inputPurpose"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#g:attr:inputPurpose"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList IMContext
type instance O.AttributeList IMContext = IMContextAttributeList
type IMContextAttributeList = ('[ '("inputHints", IMContextInputHintsPropertyInfo), '("inputPurpose", IMContextInputPurposePropertyInfo)] :: [(Symbol, DK.Type)])
#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, DK.Type)])
#endif
foreign import ccall "gtk_im_context_activate_osk" gtk_im_context_activate_osk ::
Ptr IMContext ->
Ptr Gdk.Event.Event ->
IO CInt
iMContextActivateOsk ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a, Gdk.Event.IsEvent b) =>
a
-> Maybe (b)
-> m Bool
iMContextActivateOsk :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIMContext a, IsEvent b) =>
a -> Maybe b -> m Bool
iMContextActivateOsk a
context Maybe b
event = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
maybeEvent <- case event of
Maybe b
Nothing -> Ptr Event -> IO (Ptr Event)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Event
forall a. Ptr a
FP.nullPtr
Just b
jEvent -> do
jEvent' <- b -> IO (Ptr Event)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jEvent
return jEvent'
result <- gtk_im_context_activate_osk context' maybeEvent
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr context
whenJust event touchManagedPtr
return result'
#if defined(ENABLE_OVERLOADING)
data IMContextActivateOskMethodInfo
instance (signature ~ (Maybe (b) -> m Bool), MonadIO m, IsIMContext a, Gdk.Event.IsEvent b) => O.OverloadedMethod IMContextActivateOskMethodInfo a signature where
overloadedMethod = iMContextActivateOsk
instance O.OverloadedMethodInfo IMContextActivateOskMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextActivateOsk",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v:iMContextActivateOsk"
})
#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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIMContext a) =>
a -> Int32 -> Int32 -> m Bool
iMContextDeleteSurrounding a
context Int32
offset Int32
nChars = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
result <- gtk_im_context_delete_surrounding context' offset nChars
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr context
return result'
#if defined(ENABLE_OVERLOADING)
data IMContextDeleteSurroundingMethodInfo
instance (signature ~ (Int32 -> Int32 -> m Bool), MonadIO m, IsIMContext a) => O.OverloadedMethod IMContextDeleteSurroundingMethodInfo a signature where
overloadedMethod = iMContextDeleteSurrounding
instance O.OverloadedMethodInfo IMContextDeleteSurroundingMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextDeleteSurrounding",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v:iMContextDeleteSurrounding"
})
#endif
foreign import ccall "gtk_im_context_filter_key" gtk_im_context_filter_key ::
Ptr IMContext ->
CInt ->
Ptr Gdk.Surface.Surface ->
Ptr Gdk.Device.Device ->
Word32 ->
Word32 ->
CUInt ->
Int32 ->
IO CInt
iMContextFilterKey ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a, Gdk.Surface.IsSurface b, Gdk.Device.IsDevice c) =>
a
-> Bool
-> b
-> c
-> Word32
-> Word32
-> [Gdk.Flags.ModifierType]
-> Int32
-> m Bool
iMContextFilterKey :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsIMContext a, IsSurface b,
IsDevice c) =>
a
-> Bool
-> b
-> c
-> Word32
-> Word32
-> [ModifierType]
-> Int32
-> m Bool
iMContextFilterKey a
context Bool
press b
surface c
device Word32
time Word32
keycode [ModifierType]
state Int32
group = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
let press' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
press
surface' <- unsafeManagedPtrCastPtr surface
device' <- unsafeManagedPtrCastPtr device
let state' = [ModifierType] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ModifierType]
state
result <- gtk_im_context_filter_key context' press' surface' device' time keycode state' group
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr context
touchManagedPtr surface
touchManagedPtr device
return result'
#if defined(ENABLE_OVERLOADING)
data IMContextFilterKeyMethodInfo
instance (signature ~ (Bool -> b -> c -> Word32 -> Word32 -> [Gdk.Flags.ModifierType] -> Int32 -> m Bool), MonadIO m, IsIMContext a, Gdk.Surface.IsSurface b, Gdk.Device.IsDevice c) => O.OverloadedMethod IMContextFilterKeyMethodInfo a signature where
overloadedMethod = iMContextFilterKey
instance O.OverloadedMethodInfo IMContextFilterKeyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextFilterKey",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v:iMContextFilterKey"
})
#endif
foreign import ccall "gtk_im_context_filter_keypress" gtk_im_context_filter_keypress ::
Ptr IMContext ->
Ptr Gdk.Event.Event ->
IO CInt
iMContextFilterKeypress ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a, Gdk.Event.IsEvent b) =>
a
-> b
-> m Bool
iMContextFilterKeypress :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIMContext a, IsEvent b) =>
a -> b -> m Bool
iMContextFilterKeypress a
context b
event = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
event' <- unsafeManagedPtrCastPtr event
result <- gtk_im_context_filter_keypress context' event'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr context
touchManagedPtr event
return result'
#if defined(ENABLE_OVERLOADING)
data IMContextFilterKeypressMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsIMContext a, Gdk.Event.IsEvent b) => O.OverloadedMethod IMContextFilterKeypressMethodInfo a signature where
overloadedMethod = iMContextFilterKeypress
instance O.OverloadedMethodInfo IMContextFilterKeypressMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextFilterKeypress",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIMContext a) =>
a -> m ()
iMContextFocusIn a
context = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
gtk_im_context_focus_in context'
touchManagedPtr context
return ()
#if defined(ENABLE_OVERLOADING)
data IMContextFocusInMethodInfo
instance (signature ~ (m ()), MonadIO m, IsIMContext a) => O.OverloadedMethod IMContextFocusInMethodInfo a signature where
overloadedMethod = iMContextFocusIn
instance O.OverloadedMethodInfo IMContextFocusInMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextFocusIn",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIMContext a) =>
a -> m ()
iMContextFocusOut a
context = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
gtk_im_context_focus_out context'
touchManagedPtr context
return ()
#if defined(ENABLE_OVERLOADING)
data IMContextFocusOutMethodInfo
instance (signature ~ (m ()), MonadIO m, IsIMContext a) => O.OverloadedMethod IMContextFocusOutMethodInfo a signature where
overloadedMethod = iMContextFocusOut
instance O.OverloadedMethodInfo IMContextFocusOutMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextFocusOut",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIMContext a) =>
a -> m (Text, AttrList, Int32)
iMContextGetPreeditString a
context = IO (Text, AttrList, Int32) -> m (Text, AttrList, Int32)
forall a. IO a -> m a
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
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
str <- callocMem :: IO (Ptr CString)
attrs <- callocMem :: IO (Ptr (Ptr Pango.AttrList.AttrList))
cursorPos <- allocMem :: IO (Ptr Int32)
gtk_im_context_get_preedit_string context' str attrs cursorPos
str' <- peek str
str'' <- cstringToText str'
freeMem str'
attrs' <- peek attrs
attrs'' <- (wrapBoxed Pango.AttrList.AttrList) attrs'
cursorPos' <- peek cursorPos
touchManagedPtr context
freeMem str
freeMem attrs
freeMem cursorPos
return (str'', attrs'', cursorPos')
#if defined(ENABLE_OVERLOADING)
data IMContextGetPreeditStringMethodInfo
instance (signature ~ (m ((T.Text, Pango.AttrList.AttrList, Int32))), MonadIO m, IsIMContext a) => O.OverloadedMethod IMContextGetPreeditStringMethodInfo a signature where
overloadedMethod = iMContextGetPreeditString
instance O.OverloadedMethodInfo IMContextGetPreeditStringMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextGetPreeditString",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v:iMContextGetPreeditString"
})
#endif
foreign import ccall "gtk_im_context_get_surrounding" gtk_im_context_get_surrounding ::
Ptr IMContext ->
Ptr CString ->
Ptr Int32 ->
IO CInt
{-# DEPRECATED iMContextGetSurrounding ["(Since version 4.2)","Use 'GI.Gtk.Objects.IMContext.iMContextGetSurroundingWithSelection' instead."] #-}
iMContextGetSurrounding ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
a
-> m ((Bool, T.Text, Int32))
iMContextGetSurrounding :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIMContext a) =>
a -> m (Bool, Text, Int32)
iMContextGetSurrounding a
context = IO (Bool, Text, Int32) -> m (Bool, Text, Int32)
forall a. IO a -> m a
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
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
text <- callocMem :: IO (Ptr CString)
cursorIndex <- allocMem :: IO (Ptr Int32)
result <- gtk_im_context_get_surrounding context' text cursorIndex
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
text' <- peek text
text'' <- cstringToText text'
freeMem text'
cursorIndex' <- peek cursorIndex
touchManagedPtr context
freeMem text
freeMem cursorIndex
return (result', text'', cursorIndex')
#if defined(ENABLE_OVERLOADING)
data IMContextGetSurroundingMethodInfo
instance (signature ~ (m ((Bool, T.Text, Int32))), MonadIO m, IsIMContext a) => O.OverloadedMethod IMContextGetSurroundingMethodInfo a signature where
overloadedMethod = iMContextGetSurrounding
instance O.OverloadedMethodInfo IMContextGetSurroundingMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextGetSurrounding",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v:iMContextGetSurrounding"
})
#endif
foreign import ccall "gtk_im_context_get_surrounding_with_selection" gtk_im_context_get_surrounding_with_selection ::
Ptr IMContext ->
Ptr CString ->
Ptr Int32 ->
Ptr Int32 ->
IO CInt
iMContextGetSurroundingWithSelection ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
a
-> m ((Bool, T.Text, Int32, Int32))
iMContextGetSurroundingWithSelection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIMContext a) =>
a -> m (Bool, Text, Int32, Int32)
iMContextGetSurroundingWithSelection a
context = IO (Bool, Text, Int32, Int32) -> m (Bool, Text, Int32, Int32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Text, Int32, Int32) -> m (Bool, Text, Int32, Int32))
-> IO (Bool, Text, Int32, Int32) -> m (Bool, Text, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
text <- callocMem :: IO (Ptr CString)
cursorIndex <- allocMem :: IO (Ptr Int32)
anchorIndex <- allocMem :: IO (Ptr Int32)
result <- gtk_im_context_get_surrounding_with_selection context' text cursorIndex anchorIndex
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
text' <- peek text
text'' <- cstringToText text'
freeMem text'
cursorIndex' <- peek cursorIndex
anchorIndex' <- peek anchorIndex
touchManagedPtr context
freeMem text
freeMem cursorIndex
freeMem anchorIndex
return (result', text'', cursorIndex', anchorIndex')
#if defined(ENABLE_OVERLOADING)
data IMContextGetSurroundingWithSelectionMethodInfo
instance (signature ~ (m ((Bool, T.Text, Int32, Int32))), MonadIO m, IsIMContext a) => O.OverloadedMethod IMContextGetSurroundingWithSelectionMethodInfo a signature where
overloadedMethod = iMContextGetSurroundingWithSelection
instance O.OverloadedMethodInfo IMContextGetSurroundingWithSelectionMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextGetSurroundingWithSelection",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v:iMContextGetSurroundingWithSelection"
})
#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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIMContext a) =>
a -> m ()
iMContextReset a
context = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
gtk_im_context_reset context'
touchManagedPtr context
return ()
#if defined(ENABLE_OVERLOADING)
data IMContextResetMethodInfo
instance (signature ~ (m ()), MonadIO m, IsIMContext a) => O.OverloadedMethod IMContextResetMethodInfo a signature where
overloadedMethod = iMContextReset
instance O.OverloadedMethodInfo IMContextResetMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextReset",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v:iMContextReset"
})
#endif
foreign import ccall "gtk_im_context_set_client_widget" gtk_im_context_set_client_widget ::
Ptr IMContext ->
Ptr Gtk.Widget.Widget ->
IO ()
iMContextSetClientWidget ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a, Gtk.Widget.IsWidget b) =>
a
-> Maybe (b)
-> m ()
iMContextSetClientWidget :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsIMContext a, IsWidget b) =>
a -> Maybe b -> m ()
iMContextSetClientWidget a
context Maybe b
widget = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
maybeWidget <- case widget of
Maybe b
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
FP.nullPtr
Just b
jWidget -> do
jWidget' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jWidget
return jWidget'
gtk_im_context_set_client_widget context' maybeWidget
touchManagedPtr context
whenJust widget touchManagedPtr
return ()
#if defined(ENABLE_OVERLOADING)
data IMContextSetClientWidgetMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsIMContext a, Gtk.Widget.IsWidget b) => O.OverloadedMethod IMContextSetClientWidgetMethodInfo a signature where
overloadedMethod = iMContextSetClientWidget
instance O.OverloadedMethodInfo IMContextSetClientWidgetMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextSetClientWidget",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v:iMContextSetClientWidget"
})
#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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIMContext a) =>
a -> Rectangle -> m ()
iMContextSetCursorLocation a
context Rectangle
area = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
area' <- unsafeManagedPtrGetPtr area
gtk_im_context_set_cursor_location context' area'
touchManagedPtr context
touchManagedPtr area
return ()
#if defined(ENABLE_OVERLOADING)
data IMContextSetCursorLocationMethodInfo
instance (signature ~ (Gdk.Rectangle.Rectangle -> m ()), MonadIO m, IsIMContext a) => O.OverloadedMethod IMContextSetCursorLocationMethodInfo a signature where
overloadedMethod = iMContextSetCursorLocation
instance O.OverloadedMethodInfo IMContextSetCursorLocationMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextSetCursorLocation",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v:iMContextSetCursorLocation"
})
#endif
foreign import ccall "gtk_im_context_set_surrounding" gtk_im_context_set_surrounding ::
Ptr IMContext ->
CString ->
Int32 ->
Int32 ->
IO ()
{-# DEPRECATED iMContextSetSurrounding ["(Since version 4.2)","Use 'GI.Gtk.Objects.IMContext.iMContextSetSurroundingWithSelection' instead"] #-}
iMContextSetSurrounding ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
a
-> T.Text
-> Int32
-> Int32
-> m ()
iMContextSetSurrounding :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIMContext a) =>
a -> Text -> Int32 -> Int32 -> m ()
iMContextSetSurrounding a
context Text
text Int32
len Int32
cursorIndex = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
text' <- textToCString text
gtk_im_context_set_surrounding context' text' len cursorIndex
touchManagedPtr context
freeMem text'
return ()
#if defined(ENABLE_OVERLOADING)
data IMContextSetSurroundingMethodInfo
instance (signature ~ (T.Text -> Int32 -> Int32 -> m ()), MonadIO m, IsIMContext a) => O.OverloadedMethod IMContextSetSurroundingMethodInfo a signature where
overloadedMethod = iMContextSetSurrounding
instance O.OverloadedMethodInfo IMContextSetSurroundingMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextSetSurrounding",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v:iMContextSetSurrounding"
})
#endif
foreign import ccall "gtk_im_context_set_surrounding_with_selection" gtk_im_context_set_surrounding_with_selection ::
Ptr IMContext ->
CString ->
Int32 ->
Int32 ->
Int32 ->
IO ()
iMContextSetSurroundingWithSelection ::
(B.CallStack.HasCallStack, MonadIO m, IsIMContext a) =>
a
-> T.Text
-> Int32
-> Int32
-> Int32
-> m ()
iMContextSetSurroundingWithSelection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIMContext a) =>
a -> Text -> Int32 -> Int32 -> Int32 -> m ()
iMContextSetSurroundingWithSelection a
context Text
text Int32
len Int32
cursorIndex Int32
anchorIndex = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
text' <- textToCString text
gtk_im_context_set_surrounding_with_selection context' text' len cursorIndex anchorIndex
touchManagedPtr context
freeMem text'
return ()
#if defined(ENABLE_OVERLOADING)
data IMContextSetSurroundingWithSelectionMethodInfo
instance (signature ~ (T.Text -> Int32 -> Int32 -> Int32 -> m ()), MonadIO m, IsIMContext a) => O.OverloadedMethod IMContextSetSurroundingWithSelectionMethodInfo a signature where
overloadedMethod = iMContextSetSurroundingWithSelection
instance O.OverloadedMethodInfo IMContextSetSurroundingWithSelectionMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextSetSurroundingWithSelection",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v:iMContextSetSurroundingWithSelection"
})
#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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsIMContext a) =>
a -> Bool -> m ()
iMContextSetUsePreedit a
context Bool
usePreedit = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
context' <- a -> IO (Ptr IMContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
let usePreedit' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
usePreedit
gtk_im_context_set_use_preedit context' usePreedit'
touchManagedPtr context
return ()
#if defined(ENABLE_OVERLOADING)
data IMContextSetUsePreeditMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsIMContext a) => O.OverloadedMethod IMContextSetUsePreeditMethodInfo a signature where
overloadedMethod = iMContextSetUsePreedit
instance O.OverloadedMethodInfo IMContextSetUsePreeditMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.IMContext.iMContextSetUsePreedit",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-IMContext.html#v:iMContextSetUsePreedit"
})
#endif