{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Gdk.Objects.Keymap.Keymap' defines the translation from keyboard state
-- (including a hardware key, a modifier mask, and active keyboard group)
-- to a keyval. This translation has two phases. The first phase is
-- to determine the effective keyboard group and level for the keyboard
-- state; the second phase is to look up the keycode\/group\/level triplet
-- in the keymap and see what keyval it corresponds to.

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

module GI.Gdk.Objects.Keymap
    ( 

-- * Exported types
    Keymap(..)                              ,
    IsKeymap                                ,
    toKeymap                                ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveKeymapMethod                     ,
#endif


-- ** addVirtualModifiers #method:addVirtualModifiers#

#if defined(ENABLE_OVERLOADING)
    KeymapAddVirtualModifiersMethodInfo     ,
#endif
    keymapAddVirtualModifiers               ,


-- ** getCapsLockState #method:getCapsLockState#

#if defined(ENABLE_OVERLOADING)
    KeymapGetCapsLockStateMethodInfo        ,
#endif
    keymapGetCapsLockState                  ,


-- ** getDefault #method:getDefault#

    keymapGetDefault                        ,


-- ** getDirection #method:getDirection#

#if defined(ENABLE_OVERLOADING)
    KeymapGetDirectionMethodInfo            ,
#endif
    keymapGetDirection                      ,


-- ** getEntriesForKeycode #method:getEntriesForKeycode#

#if defined(ENABLE_OVERLOADING)
    KeymapGetEntriesForKeycodeMethodInfo    ,
#endif
    keymapGetEntriesForKeycode              ,


-- ** getEntriesForKeyval #method:getEntriesForKeyval#

#if defined(ENABLE_OVERLOADING)
    KeymapGetEntriesForKeyvalMethodInfo     ,
#endif
    keymapGetEntriesForKeyval               ,


-- ** getForDisplay #method:getForDisplay#

    keymapGetForDisplay                     ,


-- ** getModifierMask #method:getModifierMask#

#if defined(ENABLE_OVERLOADING)
    KeymapGetModifierMaskMethodInfo         ,
#endif
    keymapGetModifierMask                   ,


-- ** getModifierState #method:getModifierState#

#if defined(ENABLE_OVERLOADING)
    KeymapGetModifierStateMethodInfo        ,
#endif
    keymapGetModifierState                  ,


-- ** getNumLockState #method:getNumLockState#

#if defined(ENABLE_OVERLOADING)
    KeymapGetNumLockStateMethodInfo         ,
#endif
    keymapGetNumLockState                   ,


-- ** getScrollLockState #method:getScrollLockState#

#if defined(ENABLE_OVERLOADING)
    KeymapGetScrollLockStateMethodInfo      ,
#endif
    keymapGetScrollLockState                ,


-- ** haveBidiLayouts #method:haveBidiLayouts#

#if defined(ENABLE_OVERLOADING)
    KeymapHaveBidiLayoutsMethodInfo         ,
#endif
    keymapHaveBidiLayouts                   ,


-- ** lookupKey #method:lookupKey#

#if defined(ENABLE_OVERLOADING)
    KeymapLookupKeyMethodInfo               ,
#endif
    keymapLookupKey                         ,


-- ** mapVirtualModifiers #method:mapVirtualModifiers#

#if defined(ENABLE_OVERLOADING)
    KeymapMapVirtualModifiersMethodInfo     ,
#endif
    keymapMapVirtualModifiers               ,


-- ** translateKeyboardState #method:translateKeyboardState#

#if defined(ENABLE_OVERLOADING)
    KeymapTranslateKeyboardStateMethodInfo  ,
#endif
    keymapTranslateKeyboardState            ,




 -- * Signals
-- ** directionChanged #signal:directionChanged#

    C_KeymapDirectionChangedCallback        ,
    KeymapDirectionChangedCallback          ,
#if defined(ENABLE_OVERLOADING)
    KeymapDirectionChangedSignalInfo        ,
#endif
    afterKeymapDirectionChanged             ,
    genClosure_KeymapDirectionChanged       ,
    mk_KeymapDirectionChangedCallback       ,
    noKeymapDirectionChangedCallback        ,
    onKeymapDirectionChanged                ,
    wrap_KeymapDirectionChangedCallback     ,


-- ** keysChanged #signal:keysChanged#

    C_KeymapKeysChangedCallback             ,
    KeymapKeysChangedCallback               ,
#if defined(ENABLE_OVERLOADING)
    KeymapKeysChangedSignalInfo             ,
#endif
    afterKeymapKeysChanged                  ,
    genClosure_KeymapKeysChanged            ,
    mk_KeymapKeysChangedCallback            ,
    noKeymapKeysChangedCallback             ,
    onKeymapKeysChanged                     ,
    wrap_KeymapKeysChangedCallback          ,


-- ** stateChanged #signal:stateChanged#

    C_KeymapStateChangedCallback            ,
    KeymapStateChangedCallback              ,
#if defined(ENABLE_OVERLOADING)
    KeymapStateChangedSignalInfo            ,
#endif
    afterKeymapStateChanged                 ,
    genClosure_KeymapStateChanged           ,
    mk_KeymapStateChangedCallback           ,
    noKeymapStateChangedCallback            ,
    onKeymapStateChanged                    ,
    wrap_KeymapStateChangedCallback         ,




    ) 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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Structs.KeymapKey as Gdk.KeymapKey
import qualified GI.Pango.Enums as Pango.Enums

-- | Memory-managed wrapper type.
newtype Keymap = Keymap (SP.ManagedPtr Keymap)
    deriving (Keymap -> Keymap -> Bool
(Keymap -> Keymap -> Bool)
-> (Keymap -> Keymap -> Bool) -> Eq Keymap
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Keymap -> Keymap -> Bool
$c/= :: Keymap -> Keymap -> Bool
== :: Keymap -> Keymap -> Bool
$c== :: Keymap -> Keymap -> Bool
Eq)

instance SP.ManagedPtrNewtype Keymap where
    toManagedPtr :: Keymap -> ManagedPtr Keymap
toManagedPtr (Keymap ManagedPtr Keymap
p) = ManagedPtr Keymap
p

foreign import ccall "gdk_keymap_get_type"
    c_gdk_keymap_get_type :: IO B.Types.GType

instance B.Types.TypedObject Keymap where
    glibType :: IO GType
glibType = IO GType
c_gdk_keymap_get_type

instance B.Types.GObject Keymap

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

-- | Type class for types which can be safely cast to `Keymap`, for instance with `toKeymap`.
class (SP.GObject o, O.IsDescendantOf Keymap o) => IsKeymap o
instance (SP.GObject o, O.IsDescendantOf Keymap o) => IsKeymap o

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveKeymapMethod (t :: Symbol) (o :: *) :: * where
    ResolveKeymapMethod "addVirtualModifiers" o = KeymapAddVirtualModifiersMethodInfo
    ResolveKeymapMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveKeymapMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveKeymapMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveKeymapMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveKeymapMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveKeymapMethod "haveBidiLayouts" o = KeymapHaveBidiLayoutsMethodInfo
    ResolveKeymapMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveKeymapMethod "lookupKey" o = KeymapLookupKeyMethodInfo
    ResolveKeymapMethod "mapVirtualModifiers" o = KeymapMapVirtualModifiersMethodInfo
    ResolveKeymapMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveKeymapMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveKeymapMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveKeymapMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveKeymapMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveKeymapMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveKeymapMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveKeymapMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveKeymapMethod "translateKeyboardState" o = KeymapTranslateKeyboardStateMethodInfo
    ResolveKeymapMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveKeymapMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveKeymapMethod "getCapsLockState" o = KeymapGetCapsLockStateMethodInfo
    ResolveKeymapMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveKeymapMethod "getDirection" o = KeymapGetDirectionMethodInfo
    ResolveKeymapMethod "getEntriesForKeycode" o = KeymapGetEntriesForKeycodeMethodInfo
    ResolveKeymapMethod "getEntriesForKeyval" o = KeymapGetEntriesForKeyvalMethodInfo
    ResolveKeymapMethod "getModifierMask" o = KeymapGetModifierMaskMethodInfo
    ResolveKeymapMethod "getModifierState" o = KeymapGetModifierStateMethodInfo
    ResolveKeymapMethod "getNumLockState" o = KeymapGetNumLockStateMethodInfo
    ResolveKeymapMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveKeymapMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveKeymapMethod "getScrollLockState" o = KeymapGetScrollLockStateMethodInfo
    ResolveKeymapMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveKeymapMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveKeymapMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveKeymapMethod l o = O.MethodResolutionFailed l o

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

#endif

-- signal Keymap::direction-changed
-- | The [directionChanged](#g:signal:directionChanged) signal gets emitted when the direction of
-- the keymap changes.
-- 
-- /Since: 2.0/
type KeymapDirectionChangedCallback =
    IO ()

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

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_KeymapDirectionChanged :: MonadIO m => KeymapDirectionChangedCallback -> m (GClosure C_KeymapDirectionChangedCallback)
genClosure_KeymapDirectionChanged :: IO () -> m (GClosure C_KeymapDirectionChangedCallback)
genClosure_KeymapDirectionChanged IO ()
cb = IO (GClosure C_KeymapDirectionChangedCallback)
-> m (GClosure C_KeymapDirectionChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_KeymapDirectionChangedCallback)
 -> m (GClosure C_KeymapDirectionChangedCallback))
-> IO (GClosure C_KeymapDirectionChangedCallback)
-> m (GClosure C_KeymapDirectionChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_KeymapDirectionChangedCallback
cb' = IO () -> C_KeymapDirectionChangedCallback
wrap_KeymapDirectionChangedCallback IO ()
cb
    C_KeymapDirectionChangedCallback
-> IO (FunPtr C_KeymapDirectionChangedCallback)
mk_KeymapDirectionChangedCallback C_KeymapDirectionChangedCallback
cb' IO (FunPtr C_KeymapDirectionChangedCallback)
-> (FunPtr C_KeymapDirectionChangedCallback
    -> IO (GClosure C_KeymapDirectionChangedCallback))
-> IO (GClosure C_KeymapDirectionChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_KeymapDirectionChangedCallback
-> IO (GClosure C_KeymapDirectionChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `KeymapDirectionChangedCallback` into a `C_KeymapDirectionChangedCallback`.
wrap_KeymapDirectionChangedCallback ::
    KeymapDirectionChangedCallback ->
    C_KeymapDirectionChangedCallback
wrap_KeymapDirectionChangedCallback :: IO () -> C_KeymapDirectionChangedCallback
wrap_KeymapDirectionChangedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [directionChanged](#signal:directionChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' keymap #directionChanged callback
-- @
-- 
-- 
onKeymapDirectionChanged :: (IsKeymap a, MonadIO m) => a -> KeymapDirectionChangedCallback -> m SignalHandlerId
onKeymapDirectionChanged :: a -> IO () -> m SignalHandlerId
onKeymapDirectionChanged 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_KeymapDirectionChangedCallback
cb' = IO () -> C_KeymapDirectionChangedCallback
wrap_KeymapDirectionChangedCallback IO ()
cb
    FunPtr C_KeymapDirectionChangedCallback
cb'' <- C_KeymapDirectionChangedCallback
-> IO (FunPtr C_KeymapDirectionChangedCallback)
mk_KeymapDirectionChangedCallback C_KeymapDirectionChangedCallback
cb'
    a
-> Text
-> FunPtr C_KeymapDirectionChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"direction-changed" FunPtr C_KeymapDirectionChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [directionChanged](#signal:directionChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' keymap #directionChanged callback
-- @
-- 
-- 
afterKeymapDirectionChanged :: (IsKeymap a, MonadIO m) => a -> KeymapDirectionChangedCallback -> m SignalHandlerId
afterKeymapDirectionChanged :: a -> IO () -> m SignalHandlerId
afterKeymapDirectionChanged 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_KeymapDirectionChangedCallback
cb' = IO () -> C_KeymapDirectionChangedCallback
wrap_KeymapDirectionChangedCallback IO ()
cb
    FunPtr C_KeymapDirectionChangedCallback
cb'' <- C_KeymapDirectionChangedCallback
-> IO (FunPtr C_KeymapDirectionChangedCallback)
mk_KeymapDirectionChangedCallback C_KeymapDirectionChangedCallback
cb'
    a
-> Text
-> FunPtr C_KeymapDirectionChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"direction-changed" FunPtr C_KeymapDirectionChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data KeymapDirectionChangedSignalInfo
instance SignalInfo KeymapDirectionChangedSignalInfo where
    type HaskellCallbackType KeymapDirectionChangedSignalInfo = KeymapDirectionChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_KeymapDirectionChangedCallback cb
        cb'' <- mk_KeymapDirectionChangedCallback cb'
        connectSignalFunPtr obj "direction-changed" cb'' connectMode detail

#endif

-- signal Keymap::keys-changed
-- | The [keysChanged](#g:signal:keysChanged) signal is emitted when the mapping represented by
-- /@keymap@/ changes.
-- 
-- /Since: 2.2/
type KeymapKeysChangedCallback =
    IO ()

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

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_KeymapKeysChanged :: MonadIO m => KeymapKeysChangedCallback -> m (GClosure C_KeymapKeysChangedCallback)
genClosure_KeymapKeysChanged :: IO () -> m (GClosure C_KeymapDirectionChangedCallback)
genClosure_KeymapKeysChanged IO ()
cb = IO (GClosure C_KeymapDirectionChangedCallback)
-> m (GClosure C_KeymapDirectionChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_KeymapDirectionChangedCallback)
 -> m (GClosure C_KeymapDirectionChangedCallback))
-> IO (GClosure C_KeymapDirectionChangedCallback)
-> m (GClosure C_KeymapDirectionChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_KeymapDirectionChangedCallback
cb' = IO () -> C_KeymapDirectionChangedCallback
wrap_KeymapKeysChangedCallback IO ()
cb
    C_KeymapDirectionChangedCallback
-> IO (FunPtr C_KeymapDirectionChangedCallback)
mk_KeymapKeysChangedCallback C_KeymapDirectionChangedCallback
cb' IO (FunPtr C_KeymapDirectionChangedCallback)
-> (FunPtr C_KeymapDirectionChangedCallback
    -> IO (GClosure C_KeymapDirectionChangedCallback))
-> IO (GClosure C_KeymapDirectionChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_KeymapDirectionChangedCallback
-> IO (GClosure C_KeymapDirectionChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `KeymapKeysChangedCallback` into a `C_KeymapKeysChangedCallback`.
wrap_KeymapKeysChangedCallback ::
    KeymapKeysChangedCallback ->
    C_KeymapKeysChangedCallback
wrap_KeymapKeysChangedCallback :: IO () -> C_KeymapDirectionChangedCallback
wrap_KeymapKeysChangedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [keysChanged](#signal:keysChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' keymap #keysChanged callback
-- @
-- 
-- 
onKeymapKeysChanged :: (IsKeymap a, MonadIO m) => a -> KeymapKeysChangedCallback -> m SignalHandlerId
onKeymapKeysChanged :: a -> IO () -> m SignalHandlerId
onKeymapKeysChanged 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_KeymapDirectionChangedCallback
cb' = IO () -> C_KeymapDirectionChangedCallback
wrap_KeymapKeysChangedCallback IO ()
cb
    FunPtr C_KeymapDirectionChangedCallback
cb'' <- C_KeymapDirectionChangedCallback
-> IO (FunPtr C_KeymapDirectionChangedCallback)
mk_KeymapKeysChangedCallback C_KeymapDirectionChangedCallback
cb'
    a
-> Text
-> FunPtr C_KeymapDirectionChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"keys-changed" FunPtr C_KeymapDirectionChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [keysChanged](#signal:keysChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' keymap #keysChanged callback
-- @
-- 
-- 
afterKeymapKeysChanged :: (IsKeymap a, MonadIO m) => a -> KeymapKeysChangedCallback -> m SignalHandlerId
afterKeymapKeysChanged :: a -> IO () -> m SignalHandlerId
afterKeymapKeysChanged 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_KeymapDirectionChangedCallback
cb' = IO () -> C_KeymapDirectionChangedCallback
wrap_KeymapKeysChangedCallback IO ()
cb
    FunPtr C_KeymapDirectionChangedCallback
cb'' <- C_KeymapDirectionChangedCallback
-> IO (FunPtr C_KeymapDirectionChangedCallback)
mk_KeymapKeysChangedCallback C_KeymapDirectionChangedCallback
cb'
    a
-> Text
-> FunPtr C_KeymapDirectionChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"keys-changed" FunPtr C_KeymapDirectionChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data KeymapKeysChangedSignalInfo
instance SignalInfo KeymapKeysChangedSignalInfo where
    type HaskellCallbackType KeymapKeysChangedSignalInfo = KeymapKeysChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_KeymapKeysChangedCallback cb
        cb'' <- mk_KeymapKeysChangedCallback cb'
        connectSignalFunPtr obj "keys-changed" cb'' connectMode detail

#endif

-- signal Keymap::state-changed
-- | The [stateChanged](#g:signal:stateChanged) signal is emitted when the state of the
-- keyboard changes, e.g when Caps Lock is turned on or off.
-- See 'GI.Gdk.Objects.Keymap.keymapGetCapsLockState'.
-- 
-- /Since: 2.16/
type KeymapStateChangedCallback =
    IO ()

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

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_KeymapStateChanged :: MonadIO m => KeymapStateChangedCallback -> m (GClosure C_KeymapStateChangedCallback)
genClosure_KeymapStateChanged :: IO () -> m (GClosure C_KeymapDirectionChangedCallback)
genClosure_KeymapStateChanged IO ()
cb = IO (GClosure C_KeymapDirectionChangedCallback)
-> m (GClosure C_KeymapDirectionChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_KeymapDirectionChangedCallback)
 -> m (GClosure C_KeymapDirectionChangedCallback))
-> IO (GClosure C_KeymapDirectionChangedCallback)
-> m (GClosure C_KeymapDirectionChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_KeymapDirectionChangedCallback
cb' = IO () -> C_KeymapDirectionChangedCallback
wrap_KeymapStateChangedCallback IO ()
cb
    C_KeymapDirectionChangedCallback
-> IO (FunPtr C_KeymapDirectionChangedCallback)
mk_KeymapStateChangedCallback C_KeymapDirectionChangedCallback
cb' IO (FunPtr C_KeymapDirectionChangedCallback)
-> (FunPtr C_KeymapDirectionChangedCallback
    -> IO (GClosure C_KeymapDirectionChangedCallback))
-> IO (GClosure C_KeymapDirectionChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_KeymapDirectionChangedCallback
-> IO (GClosure C_KeymapDirectionChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `KeymapStateChangedCallback` into a `C_KeymapStateChangedCallback`.
wrap_KeymapStateChangedCallback ::
    KeymapStateChangedCallback ->
    C_KeymapStateChangedCallback
wrap_KeymapStateChangedCallback :: IO () -> C_KeymapDirectionChangedCallback
wrap_KeymapStateChangedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [stateChanged](#signal:stateChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' keymap #stateChanged callback
-- @
-- 
-- 
onKeymapStateChanged :: (IsKeymap a, MonadIO m) => a -> KeymapStateChangedCallback -> m SignalHandlerId
onKeymapStateChanged :: a -> IO () -> m SignalHandlerId
onKeymapStateChanged 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_KeymapDirectionChangedCallback
cb' = IO () -> C_KeymapDirectionChangedCallback
wrap_KeymapStateChangedCallback IO ()
cb
    FunPtr C_KeymapDirectionChangedCallback
cb'' <- C_KeymapDirectionChangedCallback
-> IO (FunPtr C_KeymapDirectionChangedCallback)
mk_KeymapStateChangedCallback C_KeymapDirectionChangedCallback
cb'
    a
-> Text
-> FunPtr C_KeymapDirectionChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"state-changed" FunPtr C_KeymapDirectionChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [stateChanged](#signal:stateChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' keymap #stateChanged callback
-- @
-- 
-- 
afterKeymapStateChanged :: (IsKeymap a, MonadIO m) => a -> KeymapStateChangedCallback -> m SignalHandlerId
afterKeymapStateChanged :: a -> IO () -> m SignalHandlerId
afterKeymapStateChanged 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_KeymapDirectionChangedCallback
cb' = IO () -> C_KeymapDirectionChangedCallback
wrap_KeymapStateChangedCallback IO ()
cb
    FunPtr C_KeymapDirectionChangedCallback
cb'' <- C_KeymapDirectionChangedCallback
-> IO (FunPtr C_KeymapDirectionChangedCallback)
mk_KeymapStateChangedCallback C_KeymapDirectionChangedCallback
cb'
    a
-> Text
-> FunPtr C_KeymapDirectionChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"state-changed" FunPtr C_KeymapDirectionChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data KeymapStateChangedSignalInfo
instance SignalInfo KeymapStateChangedSignalInfo where
    type HaskellCallbackType KeymapStateChangedSignalInfo = KeymapStateChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_KeymapStateChangedCallback cb
        cb'' <- mk_KeymapStateChangedCallback cb'
        connectSignalFunPtr obj "state-changed" cb'' connectMode detail

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Keymap
type instance O.AttributeList Keymap = KeymapAttributeList
type KeymapAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Keymap = KeymapSignalList
type KeymapSignalList = ('[ '("directionChanged", KeymapDirectionChangedSignalInfo), '("keysChanged", KeymapKeysChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("stateChanged", KeymapStateChangedSignalInfo)] :: [(Symbol, *)])

#endif

-- method Keymap::add_virtual_modifiers
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "keymap"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Keymap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkKeymap" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ModifierType" }
--           , direction = DirectionInout
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer to the modifier mask to change"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_add_virtual_modifiers" gdk_keymap_add_virtual_modifiers :: 
    Ptr Keymap ->                           -- keymap : TInterface (Name {namespace = "Gdk", name = "Keymap"})
    Ptr CUInt ->                            -- state : TInterface (Name {namespace = "Gdk", name = "ModifierType"})
    IO ()

-- | Maps the non-virtual modifiers (i.e Mod2, Mod3, ...) which are set
-- in /@state@/ to the virtual modifiers (i.e. Super, Hyper and Meta) and
-- set the corresponding bits in /@state@/.
-- 
-- GDK already does this before delivering key events, but for
-- compatibility reasons, it only sets the first virtual modifier
-- it finds, whereas this function sets all matching virtual modifiers.
-- 
-- This function is useful when matching key events against
-- accelerators.
-- 
-- /Since: 2.20/
keymapAddVirtualModifiers ::
    (B.CallStack.HasCallStack, MonadIO m, IsKeymap a) =>
    a
    -- ^ /@keymap@/: a t'GI.Gdk.Objects.Keymap.Keymap'
    -> [Gdk.Flags.ModifierType]
    -- ^ /@state@/: pointer to the modifier mask to change
    -> m ([Gdk.Flags.ModifierType])
keymapAddVirtualModifiers :: a -> [ModifierType] -> m [ModifierType]
keymapAddVirtualModifiers a
keymap [ModifierType]
state = IO [ModifierType] -> m [ModifierType]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ModifierType] -> m [ModifierType])
-> IO [ModifierType] -> m [ModifierType]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Keymap
keymap' <- a -> IO (Ptr Keymap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
keymap
    let state' :: CUInt
state' = [ModifierType] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ModifierType]
state
    Ptr CUInt
state'' <- IO (Ptr CUInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CUInt)
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CUInt
state'' CUInt
state'
    Ptr Keymap -> Ptr CUInt -> IO ()
gdk_keymap_add_virtual_modifiers Ptr Keymap
keymap' Ptr CUInt
state''
    CUInt
state''' <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CUInt
state''
    let state'''' :: [ModifierType]
state'''' = CUInt -> [ModifierType]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
state'''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
keymap
    Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
state''
    [ModifierType] -> IO [ModifierType]
forall (m :: * -> *) a. Monad m => a -> m a
return [ModifierType]
state''''

#if defined(ENABLE_OVERLOADING)
data KeymapAddVirtualModifiersMethodInfo
instance (signature ~ ([Gdk.Flags.ModifierType] -> m ([Gdk.Flags.ModifierType])), MonadIO m, IsKeymap a) => O.MethodInfo KeymapAddVirtualModifiersMethodInfo a signature where
    overloadedMethod = keymapAddVirtualModifiers

#endif

-- method Keymap::get_caps_lock_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "keymap"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Keymap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkKeymap" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_get_caps_lock_state" gdk_keymap_get_caps_lock_state :: 
    Ptr Keymap ->                           -- keymap : TInterface (Name {namespace = "Gdk", name = "Keymap"})
    IO CInt

-- | Returns whether the Caps Lock modifer is locked.
-- 
-- /Since: 2.16/
keymapGetCapsLockState ::
    (B.CallStack.HasCallStack, MonadIO m, IsKeymap a) =>
    a
    -- ^ /@keymap@/: a t'GI.Gdk.Objects.Keymap.Keymap'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if Caps Lock is on
keymapGetCapsLockState :: a -> m Bool
keymapGetCapsLockState a
keymap = IO Bool -> m Bool
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
    Ptr Keymap
keymap' <- a -> IO (Ptr Keymap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
keymap
    CInt
result <- Ptr Keymap -> IO CInt
gdk_keymap_get_caps_lock_state Ptr Keymap
keymap'
    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
keymap
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data KeymapGetCapsLockStateMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsKeymap a) => O.MethodInfo KeymapGetCapsLockStateMethodInfo a signature where
    overloadedMethod = keymapGetCapsLockState

#endif

-- method Keymap::get_direction
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "keymap"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Keymap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkKeymap" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "Direction" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_get_direction" gdk_keymap_get_direction :: 
    Ptr Keymap ->                           -- keymap : TInterface (Name {namespace = "Gdk", name = "Keymap"})
    IO CUInt

-- | Returns the direction of effective layout of the keymap.
keymapGetDirection ::
    (B.CallStack.HasCallStack, MonadIO m, IsKeymap a) =>
    a
    -- ^ /@keymap@/: a t'GI.Gdk.Objects.Keymap.Keymap'
    -> m Pango.Enums.Direction
    -- ^ __Returns:__ 'GI.Pango.Enums.DirectionLtr' or 'GI.Pango.Enums.DirectionRtl'
    --   if it can determine the direction. 'GI.Pango.Enums.DirectionNeutral'
    --   otherwise.
keymapGetDirection :: a -> m Direction
keymapGetDirection a
keymap = IO Direction -> m Direction
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Direction -> m Direction) -> IO Direction -> m Direction
forall a b. (a -> b) -> a -> b
$ do
    Ptr Keymap
keymap' <- a -> IO (Ptr Keymap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
keymap
    CUInt
result <- Ptr Keymap -> IO CUInt
gdk_keymap_get_direction Ptr Keymap
keymap'
    let result' :: Direction
result' = (Int -> Direction
forall a. Enum a => Int -> a
toEnum (Int -> Direction) -> (CUInt -> Int) -> CUInt -> Direction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
keymap
    Direction -> IO Direction
forall (m :: * -> *) a. Monad m => a -> m a
return Direction
result'

#if defined(ENABLE_OVERLOADING)
data KeymapGetDirectionMethodInfo
instance (signature ~ (m Pango.Enums.Direction), MonadIO m, IsKeymap a) => O.MethodInfo KeymapGetDirectionMethodInfo a signature where
    overloadedMethod = keymapGetDirection

#endif

-- method Keymap::get_entries_for_keycode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "keymap"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Keymap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkKeymap" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "hardware_keycode"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a keycode" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "keys"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 4
--                 (TInterface Name { namespace = "Gdk" , name = "KeymapKey" })
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return\n    location for array of #GdkKeymapKey, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "keyvals"
--           , argType = TCArray False (-1) 4 (TBasicType TUInt)
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return\n    location for array of keyvals, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "n_entries"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "length of @keys and @keyvals"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_entries"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "length of @keys and @keyvals"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          , Arg
--              { argCName = "n_entries"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "length of @keys and @keyvals"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_get_entries_for_keycode" gdk_keymap_get_entries_for_keycode :: 
    Ptr Keymap ->                           -- keymap : TInterface (Name {namespace = "Gdk", name = "Keymap"})
    Word32 ->                               -- hardware_keycode : TBasicType TUInt
    Ptr (Ptr Gdk.KeymapKey.KeymapKey) ->    -- keys : TCArray False (-1) 4 (TInterface (Name {namespace = "Gdk", name = "KeymapKey"}))
    Ptr (Ptr Word32) ->                     -- keyvals : TCArray False (-1) 4 (TBasicType TUInt)
    Ptr Int32 ->                            -- n_entries : TBasicType TInt
    IO CInt

-- | Returns the keyvals bound to /@hardwareKeycode@/.
-- The Nth t'GI.Gdk.Structs.KeymapKey.KeymapKey' in /@keys@/ is bound to the Nth
-- keyval in /@keyvals@/. Free the returned arrays with 'GI.GLib.Functions.free'.
-- When a keycode is pressed by the user, the keyval from
-- this list of entries is selected by considering the effective
-- keyboard group and level. See 'GI.Gdk.Objects.Keymap.keymapTranslateKeyboardState'.
keymapGetEntriesForKeycode ::
    (B.CallStack.HasCallStack, MonadIO m, IsKeymap a) =>
    a
    -- ^ /@keymap@/: a t'GI.Gdk.Objects.Keymap.Keymap'
    -> Word32
    -- ^ /@hardwareKeycode@/: a keycode
    -> m ((Bool, [Gdk.KeymapKey.KeymapKey], [Word32]))
    -- ^ __Returns:__ 'P.True' if there were any entries
keymapGetEntriesForKeycode :: a -> Word32 -> m (Bool, [KeymapKey], [Word32])
keymapGetEntriesForKeycode a
keymap Word32
hardwareKeycode = IO (Bool, [KeymapKey], [Word32]) -> m (Bool, [KeymapKey], [Word32])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, [KeymapKey], [Word32])
 -> m (Bool, [KeymapKey], [Word32]))
-> IO (Bool, [KeymapKey], [Word32])
-> m (Bool, [KeymapKey], [Word32])
forall a b. (a -> b) -> a -> b
$ do
    Ptr Keymap
keymap' <- a -> IO (Ptr Keymap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
keymap
    Ptr (Ptr KeymapKey)
keys <- IO (Ptr (Ptr KeymapKey))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr Gdk.KeymapKey.KeymapKey))
    Ptr (Ptr Word32)
keyvals <- IO (Ptr (Ptr Word32))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr Word32))
    Ptr Int32
nEntries <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CInt
result <- Ptr Keymap
-> Word32
-> Ptr (Ptr KeymapKey)
-> Ptr (Ptr Word32)
-> Ptr Int32
-> IO CInt
gdk_keymap_get_entries_for_keycode Ptr Keymap
keymap' Word32
hardwareKeycode Ptr (Ptr KeymapKey)
keys Ptr (Ptr Word32)
keyvals Ptr Int32
nEntries
    Int32
nEntries' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
nEntries
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Ptr KeymapKey
keys' <- Ptr (Ptr KeymapKey) -> IO (Ptr KeymapKey)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr KeymapKey)
keys
    [Ptr KeymapKey]
keys'' <- (Int -> Int32 -> Ptr KeymapKey -> IO [Ptr KeymapKey]
forall a b. Integral a => Int -> a -> Ptr b -> IO [Ptr b]
unpackBlockArrayWithLength Int
12 Int32
nEntries') Ptr KeymapKey
keys'
    [KeymapKey]
keys''' <- (Ptr KeymapKey -> IO KeymapKey)
-> [Ptr KeymapKey] -> IO [KeymapKey]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr KeymapKey -> KeymapKey)
-> Ptr KeymapKey -> IO KeymapKey
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr KeymapKey -> KeymapKey
Gdk.KeymapKey.KeymapKey) [Ptr KeymapKey]
keys''
    Ptr KeymapKey -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr KeymapKey
keys'
    Ptr Word32
keyvals' <- Ptr (Ptr Word32) -> IO (Ptr Word32)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Word32)
keyvals
    [Word32]
keyvals'' <- (Int32 -> Ptr Word32 -> IO [Word32]
forall a b. (Integral a, Storable b) => a -> Ptr b -> IO [b]
unpackStorableArrayWithLength Int32
nEntries') Ptr Word32
keyvals'
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
keyvals'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
keymap
    Ptr (Ptr KeymapKey) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr KeymapKey)
keys
    Ptr (Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Word32)
keyvals
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
nEntries
    (Bool, [KeymapKey], [Word32]) -> IO (Bool, [KeymapKey], [Word32])
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', [KeymapKey]
keys''', [Word32]
keyvals'')

#if defined(ENABLE_OVERLOADING)
data KeymapGetEntriesForKeycodeMethodInfo
instance (signature ~ (Word32 -> m ((Bool, [Gdk.KeymapKey.KeymapKey], [Word32]))), MonadIO m, IsKeymap a) => O.MethodInfo KeymapGetEntriesForKeycodeMethodInfo a signature where
    overloadedMethod = keymapGetEntriesForKeycode

#endif

-- method Keymap::get_entries_for_keyval
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "keymap"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Keymap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkKeymap" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "keyval"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a keyval, such as %GDK_KEY_a, %GDK_KEY_Up, %GDK_KEY_Return, etc."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "keys"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 3
--                 (TInterface Name { namespace = "Gdk" , name = "KeymapKey" })
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location\n    for an array of #GdkKeymapKey"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "n_keys"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for number of elements in returned array"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_keys"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "return location for number of elements in returned array"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_get_entries_for_keyval" gdk_keymap_get_entries_for_keyval :: 
    Ptr Keymap ->                           -- keymap : TInterface (Name {namespace = "Gdk", name = "Keymap"})
    Word32 ->                               -- keyval : TBasicType TUInt
    Ptr (Ptr Gdk.KeymapKey.KeymapKey) ->    -- keys : TCArray False (-1) 3 (TInterface (Name {namespace = "Gdk", name = "KeymapKey"}))
    Ptr Int32 ->                            -- n_keys : TBasicType TInt
    IO CInt

-- | Obtains a list of keycode\/group\/level combinations that will
-- generate /@keyval@/. Groups and levels are two kinds of keyboard mode;
-- in general, the level determines whether the top or bottom symbol
-- on a key is used, and the group determines whether the left or
-- right symbol is used. On US keyboards, the shift key changes the
-- keyboard level, and there are no groups. A group switch key might
-- convert a keyboard between Hebrew to English modes, for example.
-- t'GI.Gdk.Structs.EventKey.EventKey' contains a @/group/@ field that indicates the active
-- keyboard group. The level is computed from the modifier mask.
-- The returned array should be freed
-- with 'GI.GLib.Functions.free'.
keymapGetEntriesForKeyval ::
    (B.CallStack.HasCallStack, MonadIO m, IsKeymap a) =>
    a
    -- ^ /@keymap@/: a t'GI.Gdk.Objects.Keymap.Keymap'
    -> Word32
    -- ^ /@keyval@/: a keyval, such as 'GI.Gdk.Constants.KEY_a', 'GI.Gdk.Constants.KEY_Up', 'GI.Gdk.Constants.KEY_Return', etc.
    -> m ((Bool, [Gdk.KeymapKey.KeymapKey]))
    -- ^ __Returns:__ 'P.True' if keys were found and returned
keymapGetEntriesForKeyval :: a -> Word32 -> m (Bool, [KeymapKey])
keymapGetEntriesForKeyval a
keymap Word32
keyval = IO (Bool, [KeymapKey]) -> m (Bool, [KeymapKey])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, [KeymapKey]) -> m (Bool, [KeymapKey]))
-> IO (Bool, [KeymapKey]) -> m (Bool, [KeymapKey])
forall a b. (a -> b) -> a -> b
$ do
    Ptr Keymap
keymap' <- a -> IO (Ptr Keymap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
keymap
    Ptr (Ptr KeymapKey)
keys <- IO (Ptr (Ptr KeymapKey))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr Gdk.KeymapKey.KeymapKey))
    Ptr Int32
nKeys <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    CInt
result <- Ptr Keymap -> Word32 -> Ptr (Ptr KeymapKey) -> Ptr Int32 -> IO CInt
gdk_keymap_get_entries_for_keyval Ptr Keymap
keymap' Word32
keyval Ptr (Ptr KeymapKey)
keys Ptr Int32
nKeys
    Int32
nKeys' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
nKeys
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Ptr KeymapKey
keys' <- Ptr (Ptr KeymapKey) -> IO (Ptr KeymapKey)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr KeymapKey)
keys
    [Ptr KeymapKey]
keys'' <- (Int -> Int32 -> Ptr KeymapKey -> IO [Ptr KeymapKey]
forall a b. Integral a => Int -> a -> Ptr b -> IO [Ptr b]
unpackBlockArrayWithLength Int
12 Int32
nKeys') Ptr KeymapKey
keys'
    [KeymapKey]
keys''' <- (Ptr KeymapKey -> IO KeymapKey)
-> [Ptr KeymapKey] -> IO [KeymapKey]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr KeymapKey -> KeymapKey)
-> Ptr KeymapKey -> IO KeymapKey
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr KeymapKey -> KeymapKey
Gdk.KeymapKey.KeymapKey) [Ptr KeymapKey]
keys''
    Ptr KeymapKey -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr KeymapKey
keys'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
keymap
    Ptr (Ptr KeymapKey) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr KeymapKey)
keys
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
nKeys
    (Bool, [KeymapKey]) -> IO (Bool, [KeymapKey])
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', [KeymapKey]
keys''')

#if defined(ENABLE_OVERLOADING)
data KeymapGetEntriesForKeyvalMethodInfo
instance (signature ~ (Word32 -> m ((Bool, [Gdk.KeymapKey.KeymapKey]))), MonadIO m, IsKeymap a) => O.MethodInfo KeymapGetEntriesForKeyvalMethodInfo a signature where
    overloadedMethod = keymapGetEntriesForKeyval

#endif

-- method Keymap::get_modifier_mask
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "keymap"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Keymap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkKeymap" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "intent"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ModifierIntent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the use case for the modifier mask"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gdk" , name = "ModifierType" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_get_modifier_mask" gdk_keymap_get_modifier_mask :: 
    Ptr Keymap ->                           -- keymap : TInterface (Name {namespace = "Gdk", name = "Keymap"})
    CUInt ->                                -- intent : TInterface (Name {namespace = "Gdk", name = "ModifierIntent"})
    IO CUInt

-- | Returns the modifier mask the /@keymap@/’s windowing system backend
-- uses for a particular purpose.
-- 
-- Note that this function always returns real hardware modifiers, not
-- virtual ones (e.g. it will return @/GDK_MOD1_MASK/@ rather than
-- @/GDK_META_MASK/@ if the backend maps MOD1 to META), so there are use
-- cases where the return value of this function has to be transformed
-- by 'GI.Gdk.Objects.Keymap.keymapAddVirtualModifiers' in order to contain the
-- expected result.
-- 
-- /Since: 3.4/
keymapGetModifierMask ::
    (B.CallStack.HasCallStack, MonadIO m, IsKeymap a) =>
    a
    -- ^ /@keymap@/: a t'GI.Gdk.Objects.Keymap.Keymap'
    -> Gdk.Enums.ModifierIntent
    -- ^ /@intent@/: the use case for the modifier mask
    -> m [Gdk.Flags.ModifierType]
    -- ^ __Returns:__ the modifier mask used for /@intent@/.
keymapGetModifierMask :: a -> ModifierIntent -> m [ModifierType]
keymapGetModifierMask a
keymap ModifierIntent
intent = IO [ModifierType] -> m [ModifierType]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ModifierType] -> m [ModifierType])
-> IO [ModifierType] -> m [ModifierType]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Keymap
keymap' <- a -> IO (Ptr Keymap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
keymap
    let intent' :: CUInt
intent' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (ModifierIntent -> Int) -> ModifierIntent -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModifierIntent -> Int
forall a. Enum a => a -> Int
fromEnum) ModifierIntent
intent
    CUInt
result <- Ptr Keymap -> CUInt -> IO CUInt
gdk_keymap_get_modifier_mask Ptr Keymap
keymap' CUInt
intent'
    let result' :: [ModifierType]
result' = CUInt -> [ModifierType]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
keymap
    [ModifierType] -> IO [ModifierType]
forall (m :: * -> *) a. Monad m => a -> m a
return [ModifierType]
result'

#if defined(ENABLE_OVERLOADING)
data KeymapGetModifierMaskMethodInfo
instance (signature ~ (Gdk.Enums.ModifierIntent -> m [Gdk.Flags.ModifierType]), MonadIO m, IsKeymap a) => O.MethodInfo KeymapGetModifierMaskMethodInfo a signature where
    overloadedMethod = keymapGetModifierMask

#endif

-- method Keymap::get_modifier_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "keymap"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Keymap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkKeymap" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_get_modifier_state" gdk_keymap_get_modifier_state :: 
    Ptr Keymap ->                           -- keymap : TInterface (Name {namespace = "Gdk", name = "Keymap"})
    IO Word32

-- | Returns the current modifier state.
-- 
-- /Since: 3.4/
keymapGetModifierState ::
    (B.CallStack.HasCallStack, MonadIO m, IsKeymap a) =>
    a
    -- ^ /@keymap@/: a t'GI.Gdk.Objects.Keymap.Keymap'
    -> m Word32
    -- ^ __Returns:__ the current modifier state.
keymapGetModifierState :: a -> m Word32
keymapGetModifierState a
keymap = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Keymap
keymap' <- a -> IO (Ptr Keymap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
keymap
    Word32
result <- Ptr Keymap -> IO Word32
gdk_keymap_get_modifier_state Ptr Keymap
keymap'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
keymap
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data KeymapGetModifierStateMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsKeymap a) => O.MethodInfo KeymapGetModifierStateMethodInfo a signature where
    overloadedMethod = keymapGetModifierState

#endif

-- method Keymap::get_num_lock_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "keymap"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Keymap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkKeymap" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_get_num_lock_state" gdk_keymap_get_num_lock_state :: 
    Ptr Keymap ->                           -- keymap : TInterface (Name {namespace = "Gdk", name = "Keymap"})
    IO CInt

-- | Returns whether the Num Lock modifer is locked.
-- 
-- /Since: 3.0/
keymapGetNumLockState ::
    (B.CallStack.HasCallStack, MonadIO m, IsKeymap a) =>
    a
    -- ^ /@keymap@/: a t'GI.Gdk.Objects.Keymap.Keymap'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if Num Lock is on
keymapGetNumLockState :: a -> m Bool
keymapGetNumLockState a
keymap = IO Bool -> m Bool
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
    Ptr Keymap
keymap' <- a -> IO (Ptr Keymap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
keymap
    CInt
result <- Ptr Keymap -> IO CInt
gdk_keymap_get_num_lock_state Ptr Keymap
keymap'
    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
keymap
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data KeymapGetNumLockStateMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsKeymap a) => O.MethodInfo KeymapGetNumLockStateMethodInfo a signature where
    overloadedMethod = keymapGetNumLockState

#endif

-- method Keymap::get_scroll_lock_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "keymap"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Keymap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkKeymap" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_get_scroll_lock_state" gdk_keymap_get_scroll_lock_state :: 
    Ptr Keymap ->                           -- keymap : TInterface (Name {namespace = "Gdk", name = "Keymap"})
    IO CInt

-- | Returns whether the Scroll Lock modifer is locked.
-- 
-- /Since: 3.18/
keymapGetScrollLockState ::
    (B.CallStack.HasCallStack, MonadIO m, IsKeymap a) =>
    a
    -- ^ /@keymap@/: a t'GI.Gdk.Objects.Keymap.Keymap'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if Scroll Lock is on
keymapGetScrollLockState :: a -> m Bool
keymapGetScrollLockState a
keymap = IO Bool -> m Bool
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
    Ptr Keymap
keymap' <- a -> IO (Ptr Keymap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
keymap
    CInt
result <- Ptr Keymap -> IO CInt
gdk_keymap_get_scroll_lock_state Ptr Keymap
keymap'
    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
keymap
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data KeymapGetScrollLockStateMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsKeymap a) => O.MethodInfo KeymapGetScrollLockStateMethodInfo a signature where
    overloadedMethod = keymapGetScrollLockState

#endif

-- method Keymap::have_bidi_layouts
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "keymap"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Keymap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkKeymap" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_have_bidi_layouts" gdk_keymap_have_bidi_layouts :: 
    Ptr Keymap ->                           -- keymap : TInterface (Name {namespace = "Gdk", name = "Keymap"})
    IO CInt

-- | Determines if keyboard layouts for both right-to-left and left-to-right
-- languages are in use.
-- 
-- /Since: 2.12/
keymapHaveBidiLayouts ::
    (B.CallStack.HasCallStack, MonadIO m, IsKeymap a) =>
    a
    -- ^ /@keymap@/: a t'GI.Gdk.Objects.Keymap.Keymap'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if there are layouts in both directions, 'P.False' otherwise
keymapHaveBidiLayouts :: a -> m Bool
keymapHaveBidiLayouts a
keymap = IO Bool -> m Bool
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
    Ptr Keymap
keymap' <- a -> IO (Ptr Keymap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
keymap
    CInt
result <- Ptr Keymap -> IO CInt
gdk_keymap_have_bidi_layouts Ptr Keymap
keymap'
    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
keymap
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data KeymapHaveBidiLayoutsMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsKeymap a) => O.MethodInfo KeymapHaveBidiLayoutsMethodInfo a signature where
    overloadedMethod = keymapHaveBidiLayouts

#endif

-- method Keymap::lookup_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "keymap"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Keymap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkKeymap" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "KeymapKey" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GdkKeymapKey with keycode, group, and level initialized"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_lookup_key" gdk_keymap_lookup_key :: 
    Ptr Keymap ->                           -- keymap : TInterface (Name {namespace = "Gdk", name = "Keymap"})
    Ptr Gdk.KeymapKey.KeymapKey ->          -- key : TInterface (Name {namespace = "Gdk", name = "KeymapKey"})
    IO Word32

-- | Looks up the keyval mapped to a keycode\/group\/level triplet.
-- If no keyval is bound to /@key@/, returns 0. For normal user input,
-- you want to use 'GI.Gdk.Objects.Keymap.keymapTranslateKeyboardState' instead of
-- this function, since the effective group\/level may not be
-- the same as the current keyboard state.
keymapLookupKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsKeymap a) =>
    a
    -- ^ /@keymap@/: a t'GI.Gdk.Objects.Keymap.Keymap'
    -> Gdk.KeymapKey.KeymapKey
    -- ^ /@key@/: a t'GI.Gdk.Structs.KeymapKey.KeymapKey' with keycode, group, and level initialized
    -> m Word32
    -- ^ __Returns:__ a keyval, or 0 if none was mapped to the given /@key@/
keymapLookupKey :: a -> KeymapKey -> m Word32
keymapLookupKey a
keymap KeymapKey
key = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Keymap
keymap' <- a -> IO (Ptr Keymap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
keymap
    Ptr KeymapKey
key' <- KeymapKey -> IO (Ptr KeymapKey)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeymapKey
key
    Word32
result <- Ptr Keymap -> Ptr KeymapKey -> IO Word32
gdk_keymap_lookup_key Ptr Keymap
keymap' Ptr KeymapKey
key'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
keymap
    KeymapKey -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeymapKey
key
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data KeymapLookupKeyMethodInfo
instance (signature ~ (Gdk.KeymapKey.KeymapKey -> m Word32), MonadIO m, IsKeymap a) => O.MethodInfo KeymapLookupKeyMethodInfo a signature where
    overloadedMethod = keymapLookupKey

#endif

-- method Keymap::map_virtual_modifiers
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "keymap"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Keymap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkKeymap" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ModifierType" }
--           , direction = DirectionInout
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer to the modifier state to map"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_map_virtual_modifiers" gdk_keymap_map_virtual_modifiers :: 
    Ptr Keymap ->                           -- keymap : TInterface (Name {namespace = "Gdk", name = "Keymap"})
    Ptr CUInt ->                            -- state : TInterface (Name {namespace = "Gdk", name = "ModifierType"})
    IO CInt

-- | Maps the virtual modifiers (i.e. Super, Hyper and Meta) which
-- are set in /@state@/ to their non-virtual counterparts (i.e. Mod2,
-- Mod3,...) and set the corresponding bits in /@state@/.
-- 
-- This function is useful when matching key events against
-- accelerators.
-- 
-- /Since: 2.20/
keymapMapVirtualModifiers ::
    (B.CallStack.HasCallStack, MonadIO m, IsKeymap a) =>
    a
    -- ^ /@keymap@/: a t'GI.Gdk.Objects.Keymap.Keymap'
    -> [Gdk.Flags.ModifierType]
    -- ^ /@state@/: pointer to the modifier state to map
    -> m ((Bool, [Gdk.Flags.ModifierType]))
    -- ^ __Returns:__ 'P.False' if two virtual modifiers were mapped to the
    --     same non-virtual modifier. Note that 'P.False' is also returned
    --     if a virtual modifier is mapped to a non-virtual modifier that
    --     was already set in /@state@/.
keymapMapVirtualModifiers :: a -> [ModifierType] -> m (Bool, [ModifierType])
keymapMapVirtualModifiers a
keymap [ModifierType]
state = IO (Bool, [ModifierType]) -> m (Bool, [ModifierType])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, [ModifierType]) -> m (Bool, [ModifierType]))
-> IO (Bool, [ModifierType]) -> m (Bool, [ModifierType])
forall a b. (a -> b) -> a -> b
$ do
    Ptr Keymap
keymap' <- a -> IO (Ptr Keymap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
keymap
    let state' :: CUInt
state' = [ModifierType] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ModifierType]
state
    Ptr CUInt
state'' <- IO (Ptr CUInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CUInt)
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CUInt
state'' CUInt
state'
    CInt
result <- Ptr Keymap -> Ptr CUInt -> IO CInt
gdk_keymap_map_virtual_modifiers Ptr Keymap
keymap' Ptr CUInt
state''
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    CUInt
state''' <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CUInt
state''
    let state'''' :: [ModifierType]
state'''' = CUInt -> [ModifierType]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
state'''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
keymap
    Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
state''
    (Bool, [ModifierType]) -> IO (Bool, [ModifierType])
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', [ModifierType]
state'''')

#if defined(ENABLE_OVERLOADING)
data KeymapMapVirtualModifiersMethodInfo
instance (signature ~ ([Gdk.Flags.ModifierType] -> m ((Bool, [Gdk.Flags.ModifierType]))), MonadIO m, IsKeymap a) => O.MethodInfo KeymapMapVirtualModifiersMethodInfo a signature where
    overloadedMethod = keymapMapVirtualModifiers

#endif

-- method Keymap::translate_keyboard_state
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "keymap"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Keymap" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkKeymap" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "hardware_keycode"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a keycode" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "state"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ModifierType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a modifier state" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "active keyboard group"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "keyval"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for keyval, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "effective_group"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for effective\n    group, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "level"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for level, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "consumed_modifiers"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ModifierType" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for modifiers\n    that were used to determine the group or level, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_translate_keyboard_state" gdk_keymap_translate_keyboard_state :: 
    Ptr Keymap ->                           -- keymap : TInterface (Name {namespace = "Gdk", name = "Keymap"})
    Word32 ->                               -- hardware_keycode : TBasicType TUInt
    CUInt ->                                -- state : TInterface (Name {namespace = "Gdk", name = "ModifierType"})
    Int32 ->                                -- group : TBasicType TInt
    Ptr Word32 ->                           -- keyval : TBasicType TUInt
    Ptr Int32 ->                            -- effective_group : TBasicType TInt
    Ptr Int32 ->                            -- level : TBasicType TInt
    Ptr CUInt ->                            -- consumed_modifiers : TInterface (Name {namespace = "Gdk", name = "ModifierType"})
    IO CInt

-- | Translates the contents of a t'GI.Gdk.Structs.EventKey.EventKey' into a keyval, effective
-- group, and level. Modifiers that affected the translation and
-- are thus unavailable for application use are returned in
-- /@consumedModifiers@/.
-- See [Groups][key-group-explanation] for an explanation of
-- groups and levels. The /@effectiveGroup@/ is the group that was
-- actually used for the translation; some keys such as Enter are not
-- affected by the active keyboard group. The /@level@/ is derived from
-- /@state@/. For convenience, t'GI.Gdk.Structs.EventKey.EventKey' already contains the translated
-- keyval, so this function isn’t as useful as you might think.
-- 
-- /@consumedModifiers@/ gives modifiers that should be masked outfrom /@state@/
-- when comparing this key press to a hot key. For instance, on a US keyboard,
-- the @plus@ symbol is shifted, so when comparing a key press to a
-- @\<Control>plus@ accelerator @\<Shift>@ should be masked out.
-- 
-- 
-- === /C code/
-- >
-- >// We want to ignore irrelevant modifiers like ScrollLock
-- >#define ALL_ACCELS_MASK (GDK_CONTROL_MASK | GDK_SHIFT_MASK | GDK_MOD1_MASK)
-- >gdk_keymap_translate_keyboard_state (keymap, event->hardware_keycode,
-- >                                     event->state, event->group,
-- >                                     &keyval, NULL, NULL, &consumed);
-- >if (keyval == GDK_PLUS &&
-- >    (event->state & ~consumed & ALL_ACCELS_MASK) == GDK_CONTROL_MASK)
-- >  // Control was pressed
-- 
-- 
-- An older interpretation /@consumedModifiers@/ was that it contained
-- all modifiers that might affect the translation of the key;
-- this allowed accelerators to be stored with irrelevant consumed
-- modifiers, by doing:
-- 
-- === /C code/
-- >
-- >// XXX Don’t do this XXX
-- >if (keyval == accel_keyval &&
-- >    (event->state & ~consumed & ALL_ACCELS_MASK) == (accel_mods & ~consumed))
-- >  // Accelerator was pressed
-- 
-- 
-- However, this did not work if multi-modifier combinations were
-- used in the keymap, since, for instance, @\<Control>@ would be
-- masked out even if only @\<Control>\<Alt>@ was used in the keymap.
-- To support this usage as well as well as possible, all single
-- modifier combinations that could affect the key for any combination
-- of modifiers will be returned in /@consumedModifiers@/; multi-modifier
-- combinations are returned only when actually found in /@state@/. When
-- you store accelerators, you should always store them with consumed
-- modifiers removed. Store @\<Control>plus@, not @\<Control>\<Shift>plus@,
keymapTranslateKeyboardState ::
    (B.CallStack.HasCallStack, MonadIO m, IsKeymap a) =>
    a
    -- ^ /@keymap@/: a t'GI.Gdk.Objects.Keymap.Keymap'
    -> Word32
    -- ^ /@hardwareKeycode@/: a keycode
    -> [Gdk.Flags.ModifierType]
    -- ^ /@state@/: a modifier state
    -> Int32
    -- ^ /@group@/: active keyboard group
    -> m ((Bool, Word32, Int32, Int32, [Gdk.Flags.ModifierType]))
    -- ^ __Returns:__ 'P.True' if there was a keyval bound to the keycode\/state\/group
keymapTranslateKeyboardState :: a
-> Word32
-> [ModifierType]
-> Int32
-> m (Bool, Word32, Int32, Int32, [ModifierType])
keymapTranslateKeyboardState a
keymap Word32
hardwareKeycode [ModifierType]
state Int32
group = IO (Bool, Word32, Int32, Int32, [ModifierType])
-> m (Bool, Word32, Int32, Int32, [ModifierType])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Word32, Int32, Int32, [ModifierType])
 -> m (Bool, Word32, Int32, Int32, [ModifierType]))
-> IO (Bool, Word32, Int32, Int32, [ModifierType])
-> m (Bool, Word32, Int32, Int32, [ModifierType])
forall a b. (a -> b) -> a -> b
$ do
    Ptr Keymap
keymap' <- a -> IO (Ptr Keymap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
keymap
    let state' :: CUInt
state' = [ModifierType] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ModifierType]
state
    Ptr Word32
keyval <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    Ptr Int32
effectiveGroup <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
level <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr CUInt
consumedModifiers <- IO (Ptr CUInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CUInt)
    CInt
result <- Ptr Keymap
-> Word32
-> CUInt
-> Int32
-> Ptr Word32
-> Ptr Int32
-> Ptr Int32
-> Ptr CUInt
-> IO CInt
gdk_keymap_translate_keyboard_state Ptr Keymap
keymap' Word32
hardwareKeycode CUInt
state' Int32
group Ptr Word32
keyval Ptr Int32
effectiveGroup Ptr Int32
level Ptr CUInt
consumedModifiers
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Word32
keyval' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
keyval
    Int32
effectiveGroup' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
effectiveGroup
    Int32
level' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
level
    CUInt
consumedModifiers' <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CUInt
consumedModifiers
    let consumedModifiers'' :: [ModifierType]
consumedModifiers'' = CUInt -> [ModifierType]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
consumedModifiers'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
keymap
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
keyval
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
effectiveGroup
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
level
    Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
consumedModifiers
    (Bool, Word32, Int32, Int32, [ModifierType])
-> IO (Bool, Word32, Int32, Int32, [ModifierType])
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Word32
keyval', Int32
effectiveGroup', Int32
level', [ModifierType]
consumedModifiers'')

#if defined(ENABLE_OVERLOADING)
data KeymapTranslateKeyboardStateMethodInfo
instance (signature ~ (Word32 -> [Gdk.Flags.ModifierType] -> Int32 -> m ((Bool, Word32, Int32, Int32, [Gdk.Flags.ModifierType]))), MonadIO m, IsKeymap a) => O.MethodInfo KeymapTranslateKeyboardStateMethodInfo a signature where
    overloadedMethod = keymapTranslateKeyboardState

#endif

-- method Keymap::get_default
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Keymap" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_get_default" gdk_keymap_get_default :: 
    IO (Ptr Keymap)

{-# DEPRECATED keymapGetDefault ["(Since version 3.22)","Use 'GI.Gdk.Objects.Keymap.keymapGetForDisplay' instead"] #-}
-- | Returns the t'GI.Gdk.Objects.Keymap.Keymap' attached to the default display.
keymapGetDefault ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Keymap
    -- ^ __Returns:__ the t'GI.Gdk.Objects.Keymap.Keymap' attached to the default display.
keymapGetDefault :: m Keymap
keymapGetDefault  = IO Keymap -> m Keymap
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Keymap -> m Keymap) -> IO Keymap -> m Keymap
forall a b. (a -> b) -> a -> b
$ do
    Ptr Keymap
result <- IO (Ptr Keymap)
gdk_keymap_get_default
    Text -> Ptr Keymap -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keymapGetDefault" Ptr Keymap
result
    Keymap
result' <- ((ManagedPtr Keymap -> Keymap) -> Ptr Keymap -> IO Keymap
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Keymap -> Keymap
Keymap) Ptr Keymap
result
    Keymap -> IO Keymap
forall (m :: * -> *) a. Monad m => a -> m a
return Keymap
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Keymap::get_for_display
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GdkDisplay." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Keymap" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_keymap_get_for_display" gdk_keymap_get_for_display :: 
    Ptr Gdk.Display.Display ->              -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO (Ptr Keymap)

-- | Returns the t'GI.Gdk.Objects.Keymap.Keymap' attached to /@display@/.
-- 
-- /Since: 2.2/
keymapGetForDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, Gdk.Display.IsDisplay a) =>
    a
    -- ^ /@display@/: the t'GI.Gdk.Objects.Display.Display'.
    -> m Keymap
    -- ^ __Returns:__ the t'GI.Gdk.Objects.Keymap.Keymap' attached to /@display@/.
keymapGetForDisplay :: a -> m Keymap
keymapGetForDisplay a
display = IO Keymap -> m Keymap
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Keymap -> m Keymap) -> IO Keymap -> m Keymap
forall a b. (a -> b) -> a -> b
$ do
    Ptr Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
    Ptr Keymap
result <- Ptr Display -> IO (Ptr Keymap)
gdk_keymap_get_for_display Ptr Display
display'
    Text -> Ptr Keymap -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keymapGetForDisplay" Ptr Keymap
result
    Keymap
result' <- ((ManagedPtr Keymap -> Keymap) -> Ptr Keymap -> IO Keymap
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Keymap -> Keymap
Keymap) Ptr Keymap
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
    Keymap -> IO Keymap
forall (m :: * -> *) a. Monad m => a -> m a
return Keymap
result'

#if defined(ENABLE_OVERLOADING)
#endif