{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An IBusEngineDesc stores description data of IBusEngine.
-- The description data can either be passed to 'GI.IBus.Objects.EngineDesc.engineDescNew',
-- or loaded from an XML node through 'GI.IBus.Objects.EngineDesc.engineDescNewFromXmlNode'
-- to construct IBusEngineDesc.
-- 
-- However, the recommended way to load engine description data is
-- using 'GI.IBus.Objects.Component.componentNewFromFile' to load a component file,
-- which also includes engine description data.
-- 
-- see_also: t'GI.IBus.Objects.Component.Component', t'GI.IBus.Objects.Engine.Engine'

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

module GI.IBus.Objects.EngineDesc
    ( 

-- * Exported types
    EngineDesc(..)                          ,
    IsEngineDesc                            ,
    toEngineDesc                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [copy]("GI.IBus.Objects.Serializable#g:method:copy"), [destroy]("GI.IBus.Objects.Object#g:method:destroy"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [output]("GI.IBus.Objects.EngineDesc#g:method:output"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeQattachment]("GI.IBus.Objects.Serializable#g:method:removeQattachment"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [serializeObject]("GI.IBus.Objects.Serializable#g:method:serializeObject"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAuthor]("GI.IBus.Objects.EngineDesc#g:method:getAuthor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDescription]("GI.IBus.Objects.EngineDesc#g:method:getDescription"), [getHotkeys]("GI.IBus.Objects.EngineDesc#g:method:getHotkeys"), [getIcon]("GI.IBus.Objects.EngineDesc#g:method:getIcon"), [getIconPropKey]("GI.IBus.Objects.EngineDesc#g:method:getIconPropKey"), [getLanguage]("GI.IBus.Objects.EngineDesc#g:method:getLanguage"), [getLayout]("GI.IBus.Objects.EngineDesc#g:method:getLayout"), [getLayoutOption]("GI.IBus.Objects.EngineDesc#g:method:getLayoutOption"), [getLayoutVariant]("GI.IBus.Objects.EngineDesc#g:method:getLayoutVariant"), [getLicense]("GI.IBus.Objects.EngineDesc#g:method:getLicense"), [getLongname]("GI.IBus.Objects.EngineDesc#g:method:getLongname"), [getName]("GI.IBus.Objects.EngineDesc#g:method:getName"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQattachment]("GI.IBus.Objects.Serializable#g:method:getQattachment"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRank]("GI.IBus.Objects.EngineDesc#g:method:getRank"), [getSetup]("GI.IBus.Objects.EngineDesc#g:method:getSetup"), [getSymbol]("GI.IBus.Objects.EngineDesc#g:method:getSymbol"), [getTextdomain]("GI.IBus.Objects.EngineDesc#g:method:getTextdomain"), [getVersion]("GI.IBus.Objects.EngineDesc#g:method:getVersion").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setQattachment]("GI.IBus.Objects.Serializable#g:method:setQattachment").

#if defined(ENABLE_OVERLOADING)
    ResolveEngineDescMethod                 ,
#endif

-- ** getAuthor #method:getAuthor#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetAuthorMethodInfo           ,
#endif
    engineDescGetAuthor                     ,


-- ** getDescription #method:getDescription#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetDescriptionMethodInfo      ,
#endif
    engineDescGetDescription                ,


-- ** getHotkeys #method:getHotkeys#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetHotkeysMethodInfo          ,
#endif
    engineDescGetHotkeys                    ,


-- ** getIcon #method:getIcon#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetIconMethodInfo             ,
#endif
    engineDescGetIcon                       ,


-- ** getIconPropKey #method:getIconPropKey#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetIconPropKeyMethodInfo      ,
#endif
    engineDescGetIconPropKey                ,


-- ** getLanguage #method:getLanguage#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetLanguageMethodInfo         ,
#endif
    engineDescGetLanguage                   ,


-- ** getLayout #method:getLayout#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetLayoutMethodInfo           ,
#endif
    engineDescGetLayout                     ,


-- ** getLayoutOption #method:getLayoutOption#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetLayoutOptionMethodInfo     ,
#endif
    engineDescGetLayoutOption               ,


-- ** getLayoutVariant #method:getLayoutVariant#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetLayoutVariantMethodInfo    ,
#endif
    engineDescGetLayoutVariant              ,


-- ** getLicense #method:getLicense#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetLicenseMethodInfo          ,
#endif
    engineDescGetLicense                    ,


-- ** getLongname #method:getLongname#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetLongnameMethodInfo         ,
#endif
    engineDescGetLongname                   ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetNameMethodInfo             ,
#endif
    engineDescGetName                       ,


-- ** getRank #method:getRank#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetRankMethodInfo             ,
#endif
    engineDescGetRank                       ,


-- ** getSetup #method:getSetup#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetSetupMethodInfo            ,
#endif
    engineDescGetSetup                      ,


-- ** getSymbol #method:getSymbol#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetSymbolMethodInfo           ,
#endif
    engineDescGetSymbol                     ,


-- ** getTextdomain #method:getTextdomain#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetTextdomainMethodInfo       ,
#endif
    engineDescGetTextdomain                 ,


-- ** getVersion #method:getVersion#

#if defined(ENABLE_OVERLOADING)
    EngineDescGetVersionMethodInfo          ,
#endif
    engineDescGetVersion                    ,


-- ** new #method:new#

    engineDescNew                           ,


-- ** newFromXmlNode #method:newFromXmlNode#

    engineDescNewFromXmlNode                ,


-- ** output #method:output#

#if defined(ENABLE_OVERLOADING)
    EngineDescOutputMethodInfo              ,
#endif
    engineDescOutput                        ,




 -- * Properties


-- ** author #attr:author#
-- | The author of engine description

#if defined(ENABLE_OVERLOADING)
    EngineDescAuthorPropertyInfo            ,
#endif
    constructEngineDescAuthor               ,
#if defined(ENABLE_OVERLOADING)
    engineDescAuthor                        ,
#endif
    getEngineDescAuthor                     ,


-- ** description #attr:description#
-- | The description of engine description

#if defined(ENABLE_OVERLOADING)
    EngineDescDescriptionPropertyInfo       ,
#endif
    constructEngineDescDescription          ,
#if defined(ENABLE_OVERLOADING)
    engineDescDescription                   ,
#endif
    getEngineDescDescription                ,


-- ** hotkeys #attr:hotkeys#
-- | The hotkeys of engine description

#if defined(ENABLE_OVERLOADING)
    EngineDescHotkeysPropertyInfo           ,
#endif
    constructEngineDescHotkeys              ,
#if defined(ENABLE_OVERLOADING)
    engineDescHotkeys                       ,
#endif
    getEngineDescHotkeys                    ,


-- ** icon #attr:icon#
-- | The icon of engine description

#if defined(ENABLE_OVERLOADING)
    EngineDescIconPropertyInfo              ,
#endif
    constructEngineDescIcon                 ,
#if defined(ENABLE_OVERLOADING)
    engineDescIcon                          ,
#endif
    getEngineDescIcon                       ,


-- ** iconPropKey #attr:iconPropKey#
-- | The key of IBusProperty to change panel icon dynamically.

#if defined(ENABLE_OVERLOADING)
    EngineDescIconPropKeyPropertyInfo       ,
#endif
    constructEngineDescIconPropKey          ,
#if defined(ENABLE_OVERLOADING)
    engineDescIconPropKey                   ,
#endif
    getEngineDescIconPropKey                ,


-- ** language #attr:language#
-- | The language of engine description

#if defined(ENABLE_OVERLOADING)
    EngineDescLanguagePropertyInfo          ,
#endif
    constructEngineDescLanguage             ,
#if defined(ENABLE_OVERLOADING)
    engineDescLanguage                      ,
#endif
    getEngineDescLanguage                   ,


-- ** layout #attr:layout#
-- | The layout of engine description

#if defined(ENABLE_OVERLOADING)
    EngineDescLayoutPropertyInfo            ,
#endif
    constructEngineDescLayout               ,
#if defined(ENABLE_OVERLOADING)
    engineDescLayout                        ,
#endif
    getEngineDescLayout                     ,


-- ** layoutOption #attr:layoutOption#
-- | The keyboard option of engine description

#if defined(ENABLE_OVERLOADING)
    EngineDescLayoutOptionPropertyInfo      ,
#endif
    constructEngineDescLayoutOption         ,
#if defined(ENABLE_OVERLOADING)
    engineDescLayoutOption                  ,
#endif
    getEngineDescLayoutOption               ,


-- ** layoutVariant #attr:layoutVariant#
-- | The keyboard variant of engine description

#if defined(ENABLE_OVERLOADING)
    EngineDescLayoutVariantPropertyInfo     ,
#endif
    constructEngineDescLayoutVariant        ,
#if defined(ENABLE_OVERLOADING)
    engineDescLayoutVariant                 ,
#endif
    getEngineDescLayoutVariant              ,


-- ** license #attr:license#
-- | The license of engine description

#if defined(ENABLE_OVERLOADING)
    EngineDescLicensePropertyInfo           ,
#endif
    constructEngineDescLicense              ,
#if defined(ENABLE_OVERLOADING)
    engineDescLicense                       ,
#endif
    getEngineDescLicense                    ,


-- ** longname #attr:longname#
-- | The longname of engine description

#if defined(ENABLE_OVERLOADING)
    EngineDescLongnamePropertyInfo          ,
#endif
    constructEngineDescLongname             ,
#if defined(ENABLE_OVERLOADING)
    engineDescLongname                      ,
#endif
    getEngineDescLongname                   ,


-- ** name #attr:name#
-- | The name of engine description

#if defined(ENABLE_OVERLOADING)
    EngineDescNamePropertyInfo              ,
#endif
    constructEngineDescName                 ,
#if defined(ENABLE_OVERLOADING)
    engineDescName                          ,
#endif
    getEngineDescName                       ,


-- ** rank #attr:rank#
-- | The rank of engine description

#if defined(ENABLE_OVERLOADING)
    EngineDescRankPropertyInfo              ,
#endif
    constructEngineDescRank                 ,
#if defined(ENABLE_OVERLOADING)
    engineDescRank                          ,
#endif
    getEngineDescRank                       ,


-- ** setup #attr:setup#
-- | The exec lists of the engine setup command

#if defined(ENABLE_OVERLOADING)
    EngineDescSetupPropertyInfo             ,
#endif
    constructEngineDescSetup                ,
#if defined(ENABLE_OVERLOADING)
    engineDescSetup                         ,
#endif
    getEngineDescSetup                      ,


-- ** symbol #attr:symbol#
-- | The symbol chars of engine description instead of icon image

#if defined(ENABLE_OVERLOADING)
    EngineDescSymbolPropertyInfo            ,
#endif
    constructEngineDescSymbol               ,
#if defined(ENABLE_OVERLOADING)
    engineDescSymbol                        ,
#endif
    getEngineDescSymbol                     ,


-- ** textdomain #attr:textdomain#
-- | The textdomain of engine description

#if defined(ENABLE_OVERLOADING)
    EngineDescTextdomainPropertyInfo        ,
#endif
    constructEngineDescTextdomain           ,
#if defined(ENABLE_OVERLOADING)
    engineDescTextdomain                    ,
#endif
    getEngineDescTextdomain                 ,


-- ** version #attr:version#
-- | The version number of engine description

#if defined(ENABLE_OVERLOADING)
    EngineDescVersionPropertyInfo           ,
#endif
    constructEngineDescVersion              ,
#if defined(ENABLE_OVERLOADING)
    engineDescVersion                       ,
#endif
    getEngineDescVersion                    ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GLib.Structs.String as GLib.String
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.IBus.Objects.Object as IBus.Object
import {-# SOURCE #-} qualified GI.IBus.Objects.Serializable as IBus.Serializable
import {-# SOURCE #-} qualified GI.IBus.Structs.XML as IBus.XML

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

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

foreign import ccall "ibus_engine_desc_get_type"
    c_ibus_engine_desc_get_type :: IO B.Types.GType

instance B.Types.TypedObject EngineDesc where
    glibType :: IO GType
glibType = IO GType
c_ibus_engine_desc_get_type

instance B.Types.GObject EngineDesc

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

instance O.HasParentTypes EngineDesc
type instance O.ParentTypes EngineDesc = '[IBus.Serializable.Serializable, IBus.Object.Object, GObject.Object.Object]

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

-- | Convert 'EngineDesc' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe EngineDesc) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ibus_engine_desc_get_type
    gvalueSet_ :: Ptr GValue -> Maybe EngineDesc -> IO ()
gvalueSet_ Ptr GValue
gv Maybe EngineDesc
P.Nothing = Ptr GValue -> Ptr EngineDesc -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr EngineDesc
forall a. Ptr a
FP.nullPtr :: FP.Ptr EngineDesc)
    gvalueSet_ Ptr GValue
gv (P.Just EngineDesc
obj) = EngineDesc -> (Ptr EngineDesc -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr EngineDesc
obj (Ptr GValue -> Ptr EngineDesc -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe EngineDesc)
gvalueGet_ Ptr GValue
gv = do
        Ptr EngineDesc
ptr <- Ptr GValue -> IO (Ptr EngineDesc)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr EngineDesc)
        if Ptr EngineDesc
ptr Ptr EngineDesc -> Ptr EngineDesc -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr EngineDesc
forall a. Ptr a
FP.nullPtr
        then EngineDesc -> Maybe EngineDesc
forall a. a -> Maybe a
P.Just (EngineDesc -> Maybe EngineDesc)
-> IO EngineDesc -> IO (Maybe EngineDesc)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr EngineDesc -> EngineDesc)
-> Ptr EngineDesc -> IO EngineDesc
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr EngineDesc -> EngineDesc
EngineDesc Ptr EngineDesc
ptr
        else Maybe EngineDesc -> IO (Maybe EngineDesc)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe EngineDesc
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveEngineDescMethod (t :: Symbol) (o :: *) :: * where
    ResolveEngineDescMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveEngineDescMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveEngineDescMethod "copy" o = IBus.Serializable.SerializableCopyMethodInfo
    ResolveEngineDescMethod "destroy" o = IBus.Object.ObjectDestroyMethodInfo
    ResolveEngineDescMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveEngineDescMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveEngineDescMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveEngineDescMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveEngineDescMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveEngineDescMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveEngineDescMethod "output" o = EngineDescOutputMethodInfo
    ResolveEngineDescMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveEngineDescMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveEngineDescMethod "removeQattachment" o = IBus.Serializable.SerializableRemoveQattachmentMethodInfo
    ResolveEngineDescMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveEngineDescMethod "serializeObject" o = IBus.Serializable.SerializableSerializeObjectMethodInfo
    ResolveEngineDescMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveEngineDescMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveEngineDescMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveEngineDescMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveEngineDescMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveEngineDescMethod "getAuthor" o = EngineDescGetAuthorMethodInfo
    ResolveEngineDescMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveEngineDescMethod "getDescription" o = EngineDescGetDescriptionMethodInfo
    ResolveEngineDescMethod "getHotkeys" o = EngineDescGetHotkeysMethodInfo
    ResolveEngineDescMethod "getIcon" o = EngineDescGetIconMethodInfo
    ResolveEngineDescMethod "getIconPropKey" o = EngineDescGetIconPropKeyMethodInfo
    ResolveEngineDescMethod "getLanguage" o = EngineDescGetLanguageMethodInfo
    ResolveEngineDescMethod "getLayout" o = EngineDescGetLayoutMethodInfo
    ResolveEngineDescMethod "getLayoutOption" o = EngineDescGetLayoutOptionMethodInfo
    ResolveEngineDescMethod "getLayoutVariant" o = EngineDescGetLayoutVariantMethodInfo
    ResolveEngineDescMethod "getLicense" o = EngineDescGetLicenseMethodInfo
    ResolveEngineDescMethod "getLongname" o = EngineDescGetLongnameMethodInfo
    ResolveEngineDescMethod "getName" o = EngineDescGetNameMethodInfo
    ResolveEngineDescMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveEngineDescMethod "getQattachment" o = IBus.Serializable.SerializableGetQattachmentMethodInfo
    ResolveEngineDescMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveEngineDescMethod "getRank" o = EngineDescGetRankMethodInfo
    ResolveEngineDescMethod "getSetup" o = EngineDescGetSetupMethodInfo
    ResolveEngineDescMethod "getSymbol" o = EngineDescGetSymbolMethodInfo
    ResolveEngineDescMethod "getTextdomain" o = EngineDescGetTextdomainMethodInfo
    ResolveEngineDescMethod "getVersion" o = EngineDescGetVersionMethodInfo
    ResolveEngineDescMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveEngineDescMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveEngineDescMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveEngineDescMethod "setQattachment" o = IBus.Serializable.SerializableSetQattachmentMethodInfo
    ResolveEngineDescMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveEngineDescMethod t EngineDesc, O.OverloadedMethod info EngineDesc p, R.HasField t EngineDesc p) => R.HasField t EngineDesc p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveEngineDescMethod t EngineDesc, O.OverloadedMethodInfo info EngineDesc) => OL.IsLabel t (O.MethodProxy info EngineDesc) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "author"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@author@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #author
-- @
getEngineDescAuthor :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescAuthor :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescAuthor o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescAuthor" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"author"

-- | Construct a `GValueConstruct` with valid value for the “@author@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescAuthor :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescAuthor :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescAuthor Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"author" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescAuthorPropertyInfo
instance AttrInfo EngineDescAuthorPropertyInfo where
    type AttrAllowedOps EngineDescAuthorPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescAuthorPropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescAuthorPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescAuthorPropertyInfo = (~) T.Text
    type AttrTransferType EngineDescAuthorPropertyInfo = T.Text
    type AttrGetType EngineDescAuthorPropertyInfo = T.Text
    type AttrLabel EngineDescAuthorPropertyInfo = "author"
    type AttrOrigin EngineDescAuthorPropertyInfo = EngineDesc
    attrGet = getEngineDescAuthor
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescAuthor
    attrClear = undefined
#endif

-- VVV Prop "description"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@description@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #description
-- @
getEngineDescDescription :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescDescription :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescDescription o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescDescription" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"description"

-- | Construct a `GValueConstruct` with valid value for the “@description@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescDescription :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescDescription :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescDescription Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"description" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescDescriptionPropertyInfo
instance AttrInfo EngineDescDescriptionPropertyInfo where
    type AttrAllowedOps EngineDescDescriptionPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescDescriptionPropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescDescriptionPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescDescriptionPropertyInfo = (~) T.Text
    type AttrTransferType EngineDescDescriptionPropertyInfo = T.Text
    type AttrGetType EngineDescDescriptionPropertyInfo = T.Text
    type AttrLabel EngineDescDescriptionPropertyInfo = "description"
    type AttrOrigin EngineDescDescriptionPropertyInfo = EngineDesc
    attrGet = getEngineDescDescription
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescDescription
    attrClear = undefined
#endif

-- VVV Prop "hotkeys"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@hotkeys@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #hotkeys
-- @
getEngineDescHotkeys :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescHotkeys :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescHotkeys o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescHotkeys" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"hotkeys"

-- | Construct a `GValueConstruct` with valid value for the “@hotkeys@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescHotkeys :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescHotkeys :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescHotkeys Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"hotkeys" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescHotkeysPropertyInfo
instance AttrInfo EngineDescHotkeysPropertyInfo where
    type AttrAllowedOps EngineDescHotkeysPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescHotkeysPropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescHotkeysPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescHotkeysPropertyInfo = (~) T.Text
    type AttrTransferType EngineDescHotkeysPropertyInfo = T.Text
    type AttrGetType EngineDescHotkeysPropertyInfo = T.Text
    type AttrLabel EngineDescHotkeysPropertyInfo = "hotkeys"
    type AttrOrigin EngineDescHotkeysPropertyInfo = EngineDesc
    attrGet = getEngineDescHotkeys
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescHotkeys
    attrClear = undefined
#endif

-- VVV Prop "icon"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@icon@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #icon
-- @
getEngineDescIcon :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescIcon :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescIcon o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescIcon" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"icon"

-- | Construct a `GValueConstruct` with valid value for the “@icon@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescIcon :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescIcon :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescIcon Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"icon" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescIconPropertyInfo
instance AttrInfo EngineDescIconPropertyInfo where
    type AttrAllowedOps EngineDescIconPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescIconPropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescIconPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescIconPropertyInfo = (~) T.Text
    type AttrTransferType EngineDescIconPropertyInfo = T.Text
    type AttrGetType EngineDescIconPropertyInfo = T.Text
    type AttrLabel EngineDescIconPropertyInfo = "icon"
    type AttrOrigin EngineDescIconPropertyInfo = EngineDesc
    attrGet = getEngineDescIcon
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescIcon
    attrClear = undefined
#endif

-- VVV Prop "icon-prop-key"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@icon-prop-key@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #iconPropKey
-- @
getEngineDescIconPropKey :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescIconPropKey :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescIconPropKey o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescIconPropKey" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"icon-prop-key"

-- | Construct a `GValueConstruct` with valid value for the “@icon-prop-key@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescIconPropKey :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescIconPropKey :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescIconPropKey Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"icon-prop-key" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescIconPropKeyPropertyInfo
instance AttrInfo EngineDescIconPropKeyPropertyInfo where
    type AttrAllowedOps EngineDescIconPropKeyPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescIconPropKeyPropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescIconPropKeyPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescIconPropKeyPropertyInfo = (~) T.Text
    type AttrTransferType EngineDescIconPropKeyPropertyInfo = T.Text
    type AttrGetType EngineDescIconPropKeyPropertyInfo = T.Text
    type AttrLabel EngineDescIconPropKeyPropertyInfo = "icon-prop-key"
    type AttrOrigin EngineDescIconPropKeyPropertyInfo = EngineDesc
    attrGet = getEngineDescIconPropKey
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescIconPropKey
    attrClear = undefined
#endif

-- VVV Prop "language"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@language@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #language
-- @
getEngineDescLanguage :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescLanguage :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescLanguage o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescLanguage" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"language"

-- | Construct a `GValueConstruct` with valid value for the “@language@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescLanguage :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescLanguage :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescLanguage Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"language" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescLanguagePropertyInfo
instance AttrInfo EngineDescLanguagePropertyInfo where
    type AttrAllowedOps EngineDescLanguagePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescLanguagePropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescLanguagePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescLanguagePropertyInfo = (~) T.Text
    type AttrTransferType EngineDescLanguagePropertyInfo = T.Text
    type AttrGetType EngineDescLanguagePropertyInfo = T.Text
    type AttrLabel EngineDescLanguagePropertyInfo = "language"
    type AttrOrigin EngineDescLanguagePropertyInfo = EngineDesc
    attrGet = getEngineDescLanguage
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescLanguage
    attrClear = undefined
#endif

-- VVV Prop "layout"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@layout@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #layout
-- @
getEngineDescLayout :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescLayout :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescLayout o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescLayout" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"layout"

-- | Construct a `GValueConstruct` with valid value for the “@layout@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescLayout :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescLayout :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescLayout Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"layout" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescLayoutPropertyInfo
instance AttrInfo EngineDescLayoutPropertyInfo where
    type AttrAllowedOps EngineDescLayoutPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescLayoutPropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescLayoutPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescLayoutPropertyInfo = (~) T.Text
    type AttrTransferType EngineDescLayoutPropertyInfo = T.Text
    type AttrGetType EngineDescLayoutPropertyInfo = T.Text
    type AttrLabel EngineDescLayoutPropertyInfo = "layout"
    type AttrOrigin EngineDescLayoutPropertyInfo = EngineDesc
    attrGet = getEngineDescLayout
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescLayout
    attrClear = undefined
#endif

-- VVV Prop "layout-option"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@layout-option@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #layoutOption
-- @
getEngineDescLayoutOption :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescLayoutOption :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescLayoutOption o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescLayoutOption" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"layout-option"

-- | Construct a `GValueConstruct` with valid value for the “@layout-option@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescLayoutOption :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescLayoutOption :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescLayoutOption Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"layout-option" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescLayoutOptionPropertyInfo
instance AttrInfo EngineDescLayoutOptionPropertyInfo where
    type AttrAllowedOps EngineDescLayoutOptionPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescLayoutOptionPropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescLayoutOptionPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescLayoutOptionPropertyInfo = (~) T.Text
    type AttrTransferType EngineDescLayoutOptionPropertyInfo = T.Text
    type AttrGetType EngineDescLayoutOptionPropertyInfo = T.Text
    type AttrLabel EngineDescLayoutOptionPropertyInfo = "layout-option"
    type AttrOrigin EngineDescLayoutOptionPropertyInfo = EngineDesc
    attrGet = getEngineDescLayoutOption
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescLayoutOption
    attrClear = undefined
#endif

-- VVV Prop "layout-variant"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@layout-variant@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #layoutVariant
-- @
getEngineDescLayoutVariant :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescLayoutVariant :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescLayoutVariant o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescLayoutVariant" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"layout-variant"

-- | Construct a `GValueConstruct` with valid value for the “@layout-variant@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescLayoutVariant :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescLayoutVariant :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescLayoutVariant Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"layout-variant" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescLayoutVariantPropertyInfo
instance AttrInfo EngineDescLayoutVariantPropertyInfo where
    type AttrAllowedOps EngineDescLayoutVariantPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescLayoutVariantPropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescLayoutVariantPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescLayoutVariantPropertyInfo = (~) T.Text
    type AttrTransferType EngineDescLayoutVariantPropertyInfo = T.Text
    type AttrGetType EngineDescLayoutVariantPropertyInfo = T.Text
    type AttrLabel EngineDescLayoutVariantPropertyInfo = "layout-variant"
    type AttrOrigin EngineDescLayoutVariantPropertyInfo = EngineDesc
    attrGet = getEngineDescLayoutVariant
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescLayoutVariant
    attrClear = undefined
#endif

-- VVV Prop "license"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@license@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #license
-- @
getEngineDescLicense :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescLicense :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescLicense o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescLicense" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"license"

-- | Construct a `GValueConstruct` with valid value for the “@license@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescLicense :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescLicense :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescLicense Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"license" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescLicensePropertyInfo
instance AttrInfo EngineDescLicensePropertyInfo where
    type AttrAllowedOps EngineDescLicensePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescLicensePropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescLicensePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescLicensePropertyInfo = (~) T.Text
    type AttrTransferType EngineDescLicensePropertyInfo = T.Text
    type AttrGetType EngineDescLicensePropertyInfo = T.Text
    type AttrLabel EngineDescLicensePropertyInfo = "license"
    type AttrOrigin EngineDescLicensePropertyInfo = EngineDesc
    attrGet = getEngineDescLicense
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescLicense
    attrClear = undefined
#endif

-- VVV Prop "longname"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@longname@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #longname
-- @
getEngineDescLongname :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescLongname :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescLongname o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescLongname" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"longname"

-- | Construct a `GValueConstruct` with valid value for the “@longname@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescLongname :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescLongname :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescLongname Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"longname" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescLongnamePropertyInfo
instance AttrInfo EngineDescLongnamePropertyInfo where
    type AttrAllowedOps EngineDescLongnamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescLongnamePropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescLongnamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescLongnamePropertyInfo = (~) T.Text
    type AttrTransferType EngineDescLongnamePropertyInfo = T.Text
    type AttrGetType EngineDescLongnamePropertyInfo = T.Text
    type AttrLabel EngineDescLongnamePropertyInfo = "longname"
    type AttrOrigin EngineDescLongnamePropertyInfo = EngineDesc
    attrGet = getEngineDescLongname
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescLongname
    attrClear = undefined
#endif

-- VVV Prop "name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #name
-- @
getEngineDescName :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescName :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescName o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescName" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"name"

-- | Construct a `GValueConstruct` with valid value for the “@name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescName :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescName :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescNamePropertyInfo
instance AttrInfo EngineDescNamePropertyInfo where
    type AttrAllowedOps EngineDescNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescNamePropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescNamePropertyInfo = (~) T.Text
    type AttrTransferType EngineDescNamePropertyInfo = T.Text
    type AttrGetType EngineDescNamePropertyInfo = T.Text
    type AttrLabel EngineDescNamePropertyInfo = "name"
    type AttrOrigin EngineDescNamePropertyInfo = EngineDesc
    attrGet = getEngineDescName
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescName
    attrClear = undefined
#endif

-- VVV Prop "rank"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@rank@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #rank
-- @
getEngineDescRank :: (MonadIO m, IsEngineDesc o) => o -> m Word32
getEngineDescRank :: forall (m :: * -> *) o.
(MonadIO m, IsEngineDesc o) =>
o -> m Word32
getEngineDescRank o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"rank"

-- | Construct a `GValueConstruct` with valid value for the “@rank@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescRank :: (IsEngineDesc o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructEngineDescRank :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructEngineDescRank Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"rank" Word32
val

#if defined(ENABLE_OVERLOADING)
data EngineDescRankPropertyInfo
instance AttrInfo EngineDescRankPropertyInfo where
    type AttrAllowedOps EngineDescRankPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint EngineDescRankPropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescRankPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint EngineDescRankPropertyInfo = (~) Word32
    type AttrTransferType EngineDescRankPropertyInfo = Word32
    type AttrGetType EngineDescRankPropertyInfo = Word32
    type AttrLabel EngineDescRankPropertyInfo = "rank"
    type AttrOrigin EngineDescRankPropertyInfo = EngineDesc
    attrGet = getEngineDescRank
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescRank
    attrClear = undefined
#endif

-- VVV Prop "setup"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@setup@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #setup
-- @
getEngineDescSetup :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescSetup :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescSetup o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescSetup" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"setup"

-- | Construct a `GValueConstruct` with valid value for the “@setup@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescSetup :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescSetup :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescSetup Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"setup" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescSetupPropertyInfo
instance AttrInfo EngineDescSetupPropertyInfo where
    type AttrAllowedOps EngineDescSetupPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescSetupPropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescSetupPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescSetupPropertyInfo = (~) T.Text
    type AttrTransferType EngineDescSetupPropertyInfo = T.Text
    type AttrGetType EngineDescSetupPropertyInfo = T.Text
    type AttrLabel EngineDescSetupPropertyInfo = "setup"
    type AttrOrigin EngineDescSetupPropertyInfo = EngineDesc
    attrGet = getEngineDescSetup
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescSetup
    attrClear = undefined
#endif

-- VVV Prop "symbol"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@symbol@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #symbol
-- @
getEngineDescSymbol :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescSymbol :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescSymbol o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescSymbol" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"symbol"

-- | Construct a `GValueConstruct` with valid value for the “@symbol@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescSymbol :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescSymbol :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescSymbol Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"symbol" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescSymbolPropertyInfo
instance AttrInfo EngineDescSymbolPropertyInfo where
    type AttrAllowedOps EngineDescSymbolPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescSymbolPropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescSymbolPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescSymbolPropertyInfo = (~) T.Text
    type AttrTransferType EngineDescSymbolPropertyInfo = T.Text
    type AttrGetType EngineDescSymbolPropertyInfo = T.Text
    type AttrLabel EngineDescSymbolPropertyInfo = "symbol"
    type AttrOrigin EngineDescSymbolPropertyInfo = EngineDesc
    attrGet = getEngineDescSymbol
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescSymbol
    attrClear = undefined
#endif

-- VVV Prop "textdomain"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@textdomain@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #textdomain
-- @
getEngineDescTextdomain :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescTextdomain :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescTextdomain o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescTextdomain" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"textdomain"

-- | Construct a `GValueConstruct` with valid value for the “@textdomain@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescTextdomain :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescTextdomain :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescTextdomain Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"textdomain" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescTextdomainPropertyInfo
instance AttrInfo EngineDescTextdomainPropertyInfo where
    type AttrAllowedOps EngineDescTextdomainPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescTextdomainPropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescTextdomainPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescTextdomainPropertyInfo = (~) T.Text
    type AttrTransferType EngineDescTextdomainPropertyInfo = T.Text
    type AttrGetType EngineDescTextdomainPropertyInfo = T.Text
    type AttrLabel EngineDescTextdomainPropertyInfo = "textdomain"
    type AttrOrigin EngineDescTextdomainPropertyInfo = EngineDesc
    attrGet = getEngineDescTextdomain
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescTextdomain
    attrClear = undefined
#endif

-- VVV Prop "version"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@version@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' engineDesc #version
-- @
getEngineDescVersion :: (MonadIO m, IsEngineDesc o) => o -> m T.Text
getEngineDescVersion :: forall (m :: * -> *) o. (MonadIO m, IsEngineDesc o) => o -> m Text
getEngineDescVersion o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getEngineDescVersion" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"version"

-- | Construct a `GValueConstruct` with valid value for the “@version@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructEngineDescVersion :: (IsEngineDesc o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructEngineDescVersion :: forall o (m :: * -> *).
(IsEngineDesc o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructEngineDescVersion Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"version" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data EngineDescVersionPropertyInfo
instance AttrInfo EngineDescVersionPropertyInfo where
    type AttrAllowedOps EngineDescVersionPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint EngineDescVersionPropertyInfo = IsEngineDesc
    type AttrSetTypeConstraint EngineDescVersionPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint EngineDescVersionPropertyInfo = (~) T.Text
    type AttrTransferType EngineDescVersionPropertyInfo = T.Text
    type AttrGetType EngineDescVersionPropertyInfo = T.Text
    type AttrLabel EngineDescVersionPropertyInfo = "version"
    type AttrOrigin EngineDescVersionPropertyInfo = EngineDesc
    attrGet = getEngineDescVersion
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructEngineDescVersion
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EngineDesc
type instance O.AttributeList EngineDesc = EngineDescAttributeList
type EngineDescAttributeList = ('[ '("author", EngineDescAuthorPropertyInfo), '("description", EngineDescDescriptionPropertyInfo), '("hotkeys", EngineDescHotkeysPropertyInfo), '("icon", EngineDescIconPropertyInfo), '("iconPropKey", EngineDescIconPropKeyPropertyInfo), '("language", EngineDescLanguagePropertyInfo), '("layout", EngineDescLayoutPropertyInfo), '("layoutOption", EngineDescLayoutOptionPropertyInfo), '("layoutVariant", EngineDescLayoutVariantPropertyInfo), '("license", EngineDescLicensePropertyInfo), '("longname", EngineDescLongnamePropertyInfo), '("name", EngineDescNamePropertyInfo), '("rank", EngineDescRankPropertyInfo), '("setup", EngineDescSetupPropertyInfo), '("symbol", EngineDescSymbolPropertyInfo), '("textdomain", EngineDescTextdomainPropertyInfo), '("version", EngineDescVersionPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
engineDescAuthor :: AttrLabelProxy "author"
engineDescAuthor = AttrLabelProxy

engineDescDescription :: AttrLabelProxy "description"
engineDescDescription = AttrLabelProxy

engineDescHotkeys :: AttrLabelProxy "hotkeys"
engineDescHotkeys = AttrLabelProxy

engineDescIcon :: AttrLabelProxy "icon"
engineDescIcon = AttrLabelProxy

engineDescIconPropKey :: AttrLabelProxy "iconPropKey"
engineDescIconPropKey = AttrLabelProxy

engineDescLanguage :: AttrLabelProxy "language"
engineDescLanguage = AttrLabelProxy

engineDescLayout :: AttrLabelProxy "layout"
engineDescLayout = AttrLabelProxy

engineDescLayoutOption :: AttrLabelProxy "layoutOption"
engineDescLayoutOption = AttrLabelProxy

engineDescLayoutVariant :: AttrLabelProxy "layoutVariant"
engineDescLayoutVariant = AttrLabelProxy

engineDescLicense :: AttrLabelProxy "license"
engineDescLicense = AttrLabelProxy

engineDescLongname :: AttrLabelProxy "longname"
engineDescLongname = AttrLabelProxy

engineDescName :: AttrLabelProxy "name"
engineDescName = AttrLabelProxy

engineDescRank :: AttrLabelProxy "rank"
engineDescRank = AttrLabelProxy

engineDescSetup :: AttrLabelProxy "setup"
engineDescSetup = AttrLabelProxy

engineDescSymbol :: AttrLabelProxy "symbol"
engineDescSymbol = AttrLabelProxy

engineDescTextdomain :: AttrLabelProxy "textdomain"
engineDescTextdomain = AttrLabelProxy

engineDescVersion :: AttrLabelProxy "version"
engineDescVersion = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList EngineDesc = EngineDescSignalList
type EngineDescSignalList = ('[ '("destroy", IBus.Object.ObjectDestroySignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method EngineDesc::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of the engine."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "longname"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Long name of the input method engine."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "description"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Input method engine description."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "language"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Language (e.g. zh, jp) supported by this input method engine."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "license"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "License of the input method engine."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "author"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Author of the input method engine."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Icon file of this engine."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "layout"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Keyboard layout" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "IBus" , name = "EngineDesc" })
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_new" ibus_engine_desc_new :: 
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- longname : TBasicType TUTF8
    CString ->                              -- description : TBasicType TUTF8
    CString ->                              -- language : TBasicType TUTF8
    CString ->                              -- license : TBasicType TUTF8
    CString ->                              -- author : TBasicType TUTF8
    CString ->                              -- icon : TBasicType TUTF8
    CString ->                              -- layout : TBasicType TUTF8
    IO (Ptr EngineDesc)

-- | Creates a new t'GI.IBus.Objects.EngineDesc.EngineDesc'.
-- If layout is \"default\", the engine inherits the current layout and
-- does not change the layout. The layouts \"default\" and \"\" are same.
-- E.g. If you switch JP XKB engine and an input method engine (IME),
-- the IME inherits the JP layout.
engineDescNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@name@/: Name of the engine.
    -> T.Text
    -- ^ /@longname@/: Long name of the input method engine.
    -> T.Text
    -- ^ /@description@/: Input method engine description.
    -> T.Text
    -- ^ /@language@/: Language (e.g. zh, jp) supported by this input method engine.
    -> T.Text
    -- ^ /@license@/: License of the input method engine.
    -> T.Text
    -- ^ /@author@/: Author of the input method engine.
    -> T.Text
    -- ^ /@icon@/: Icon file of this engine.
    -> T.Text
    -- ^ /@layout@/: Keyboard layout
    -> m EngineDesc
    -- ^ __Returns:__ A newly allocated IBusEngineDesc.
engineDescNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> m EngineDesc
engineDescNew Text
name Text
longname Text
description Text
language Text
license Text
author Text
icon Text
layout = IO EngineDesc -> m EngineDesc
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EngineDesc -> m EngineDesc) -> IO EngineDesc -> m EngineDesc
forall a b. (a -> b) -> a -> b
$ do
    CString
name' <- Text -> IO CString
textToCString Text
name
    CString
longname' <- Text -> IO CString
textToCString Text
longname
    CString
description' <- Text -> IO CString
textToCString Text
description
    CString
language' <- Text -> IO CString
textToCString Text
language
    CString
license' <- Text -> IO CString
textToCString Text
license
    CString
author' <- Text -> IO CString
textToCString Text
author
    CString
icon' <- Text -> IO CString
textToCString Text
icon
    CString
layout' <- Text -> IO CString
textToCString Text
layout
    Ptr EngineDesc
result <- CString
-> CString
-> CString
-> CString
-> CString
-> CString
-> CString
-> CString
-> IO (Ptr EngineDesc)
ibus_engine_desc_new CString
name' CString
longname' CString
description' CString
language' CString
license' CString
author' CString
icon' CString
layout'
    Text -> Ptr EngineDesc -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescNew" Ptr EngineDesc
result
    EngineDesc
result' <- ((ManagedPtr EngineDesc -> EngineDesc)
-> Ptr EngineDesc -> IO EngineDesc
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr EngineDesc -> EngineDesc
EngineDesc) Ptr EngineDesc
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
longname'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
description'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
language'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
license'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
author'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
icon'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
layout'
    EngineDesc -> IO EngineDesc
forall (m :: * -> *) a. Monad m => a -> m a
return EngineDesc
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method EngineDesc::new_from_xml_node
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "node"
--           , argType = TInterface Name { namespace = "IBus" , name = "XML" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An XML node" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "IBus" , name = "EngineDesc" })
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_new_from_xml_node" ibus_engine_desc_new_from_xml_node :: 
    Ptr IBus.XML.XML ->                     -- node : TInterface (Name {namespace = "IBus", name = "XML"})
    IO (Ptr EngineDesc)

-- | Creates a new IBusEngineDesc from an XML node.
-- \<note>\<para>This function is called by 'GI.IBus.Objects.Component.componentNewFromFile',
--  so developers normally do not need to call it directly.
-- \<\/para>\<\/note>
engineDescNewFromXmlNode ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    IBus.XML.XML
    -- ^ /@node@/: An XML node
    -> m EngineDesc
    -- ^ __Returns:__ A newly allocated IBusEngineDesc that contains description from
    -- /@node@/.
engineDescNewFromXmlNode :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
XML -> m EngineDesc
engineDescNewFromXmlNode XML
node = IO EngineDesc -> m EngineDesc
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EngineDesc -> m EngineDesc) -> IO EngineDesc -> m EngineDesc
forall a b. (a -> b) -> a -> b
$ do
    Ptr XML
node' <- XML -> IO (Ptr XML)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr XML
node
    Ptr EngineDesc
result <- Ptr XML -> IO (Ptr EngineDesc)
ibus_engine_desc_new_from_xml_node Ptr XML
node'
    Text -> Ptr EngineDesc -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescNewFromXmlNode" Ptr EngineDesc
result
    EngineDesc
result' <- ((ManagedPtr EngineDesc -> EngineDesc)
-> Ptr EngineDesc -> IO EngineDesc
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr EngineDesc -> EngineDesc
EngineDesc) Ptr EngineDesc
result
    XML -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr XML
node
    EngineDesc -> IO EngineDesc
forall (m :: * -> *) a. Monad m => a -> m a
return EngineDesc
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method EngineDesc::get_author
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_author" ibus_engine_desc_get_author :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the author property in IBusEngineDesc. It should not be freed.
engineDescGetAuthor ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ author property in IBusEngineDesc
engineDescGetAuthor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetAuthor a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_author Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetAuthor" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetAuthorMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetAuthorMethodInfo a signature where
    overloadedMethod = engineDescGetAuthor

instance O.OverloadedMethodInfo EngineDescGetAuthorMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetAuthor",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetAuthor"
        }


#endif

-- method EngineDesc::get_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_description" ibus_engine_desc_get_description :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the description property in IBusEngineDesc. It should not be freed.
engineDescGetDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ description property in IBusEngineDesc
engineDescGetDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetDescription a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_description Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetDescription" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetDescriptionMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetDescriptionMethodInfo a signature where
    overloadedMethod = engineDescGetDescription

instance O.OverloadedMethodInfo EngineDescGetDescriptionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetDescription",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetDescription"
        }


#endif

-- method EngineDesc::get_hotkeys
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_hotkeys" ibus_engine_desc_get_hotkeys :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the hotkeys property in IBusEngineDesc. It should not be freed.
engineDescGetHotkeys ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ hotkeys property in IBusEngineDesc
engineDescGetHotkeys :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetHotkeys a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_hotkeys Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetHotkeys" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetHotkeysMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetHotkeysMethodInfo a signature where
    overloadedMethod = engineDescGetHotkeys

instance O.OverloadedMethodInfo EngineDescGetHotkeysMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetHotkeys",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetHotkeys"
        }


#endif

-- method EngineDesc::get_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_icon" ibus_engine_desc_get_icon :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the icon property in IBusEngineDesc. It should not be freed.
engineDescGetIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ icon property in IBusEngineDesc
engineDescGetIcon :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetIcon a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_icon Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetIcon" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetIconMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetIconMethodInfo a signature where
    overloadedMethod = engineDescGetIcon

instance O.OverloadedMethodInfo EngineDescGetIconMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetIcon",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetIcon"
        }


#endif

-- method EngineDesc::get_icon_prop_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_icon_prop_key" ibus_engine_desc_get_icon_prop_key :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the key of IBusProperty to load the panel icon dynamically
-- in IBusEngineDesc. It should not be freed.
engineDescGetIconPropKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ IBusProperty.key for dynamic panel icon in IBusEngineDesc
engineDescGetIconPropKey :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetIconPropKey a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_icon_prop_key Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetIconPropKey" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetIconPropKeyMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetIconPropKeyMethodInfo a signature where
    overloadedMethod = engineDescGetIconPropKey

instance O.OverloadedMethodInfo EngineDescGetIconPropKeyMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetIconPropKey",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetIconPropKey"
        }


#endif

-- method EngineDesc::get_language
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_language" ibus_engine_desc_get_language :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the language property in IBusEngineDesc. It should not be freed.
engineDescGetLanguage ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ language property in IBusEngineDesc
engineDescGetLanguage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetLanguage a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_language Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetLanguage" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetLanguageMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetLanguageMethodInfo a signature where
    overloadedMethod = engineDescGetLanguage

instance O.OverloadedMethodInfo EngineDescGetLanguageMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetLanguage",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetLanguage"
        }


#endif

-- method EngineDesc::get_layout
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_layout" ibus_engine_desc_get_layout :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the layout property in IBusEngineDesc. It should not be freed.
engineDescGetLayout ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ layout property in IBusEngineDesc
engineDescGetLayout :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetLayout a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_layout Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetLayout" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetLayoutMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetLayoutMethodInfo a signature where
    overloadedMethod = engineDescGetLayout

instance O.OverloadedMethodInfo EngineDescGetLayoutMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetLayout",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetLayout"
        }


#endif

-- method EngineDesc::get_layout_option
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_layout_option" ibus_engine_desc_get_layout_option :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the keyboard option property in IBusEngineDesc. It should not be freed.
engineDescGetLayoutOption ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ keyboard option property in IBusEngineDesc
engineDescGetLayoutOption :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetLayoutOption a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_layout_option Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetLayoutOption" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetLayoutOptionMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetLayoutOptionMethodInfo a signature where
    overloadedMethod = engineDescGetLayoutOption

instance O.OverloadedMethodInfo EngineDescGetLayoutOptionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetLayoutOption",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetLayoutOption"
        }


#endif

-- method EngineDesc::get_layout_variant
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_layout_variant" ibus_engine_desc_get_layout_variant :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the keyboard variant property in IBusEngineDesc. It should not be freed.
engineDescGetLayoutVariant ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ keyboard variant property in IBusEngineDesc
engineDescGetLayoutVariant :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetLayoutVariant a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_layout_variant Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetLayoutVariant" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetLayoutVariantMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetLayoutVariantMethodInfo a signature where
    overloadedMethod = engineDescGetLayoutVariant

instance O.OverloadedMethodInfo EngineDescGetLayoutVariantMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetLayoutVariant",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetLayoutVariant"
        }


#endif

-- method EngineDesc::get_license
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_license" ibus_engine_desc_get_license :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the license property in IBusEngineDesc. It should not be freed.
engineDescGetLicense ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ license property in IBusEngineDesc
engineDescGetLicense :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetLicense a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_license Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetLicense" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetLicenseMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetLicenseMethodInfo a signature where
    overloadedMethod = engineDescGetLicense

instance O.OverloadedMethodInfo EngineDescGetLicenseMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetLicense",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetLicense"
        }


#endif

-- method EngineDesc::get_longname
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_longname" ibus_engine_desc_get_longname :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the longname property in IBusEngineDesc. It should not be freed.
engineDescGetLongname ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ longname property in IBusEngineDesc
engineDescGetLongname :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetLongname a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_longname Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetLongname" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetLongnameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetLongnameMethodInfo a signature where
    overloadedMethod = engineDescGetLongname

instance O.OverloadedMethodInfo EngineDescGetLongnameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetLongname",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetLongname"
        }


#endif

-- method EngineDesc::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_name" ibus_engine_desc_get_name :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the name property in IBusEngineDesc. It should not be freed.
engineDescGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ name property in IBusEngineDesc
engineDescGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetName a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_name Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetNameMethodInfo a signature where
    overloadedMethod = engineDescGetName

instance O.OverloadedMethodInfo EngineDescGetNameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetName",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetName"
        }


#endif

-- method EngineDesc::get_rank
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , 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 "ibus_engine_desc_get_rank" ibus_engine_desc_get_rank :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO Word32

-- | Gets the rank property in IBusEngineDesc.
engineDescGetRank ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m Word32
    -- ^ __Returns:__ rank property in IBusEngineDesc
engineDescGetRank :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Word32
engineDescGetRank a
info = 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 EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Word32
result <- Ptr EngineDesc -> IO Word32
ibus_engine_desc_get_rank Ptr EngineDesc
info'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data EngineDescGetRankMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetRankMethodInfo a signature where
    overloadedMethod = engineDescGetRank

instance O.OverloadedMethodInfo EngineDescGetRankMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetRank",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetRank"
        }


#endif

-- method EngineDesc::get_setup
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_setup" ibus_engine_desc_get_setup :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the setup property in IBusEngineDesc. It should not be freed.
engineDescGetSetup ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ setup property in IBusEngineDesc
engineDescGetSetup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetSetup a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_setup Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetSetup" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetSetupMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetSetupMethodInfo a signature where
    overloadedMethod = engineDescGetSetup

instance O.OverloadedMethodInfo EngineDescGetSetupMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetSetup",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetSetup"
        }


#endif

-- method EngineDesc::get_symbol
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_symbol" ibus_engine_desc_get_symbol :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the symbol property in IBusEngineDesc. It should not be freed.
engineDescGetSymbol ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ symbol property in IBusEngineDesc
engineDescGetSymbol :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetSymbol a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_symbol Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetSymbol" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetSymbolMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetSymbolMethodInfo a signature where
    overloadedMethod = engineDescGetSymbol

instance O.OverloadedMethodInfo EngineDescGetSymbolMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetSymbol",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetSymbol"
        }


#endif

-- method EngineDesc::get_textdomain
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_textdomain" ibus_engine_desc_get_textdomain :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the textdomain property in IBusEngineDesc. It should not be freed.
engineDescGetTextdomain ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ textdomain in IBusEngineDesc
engineDescGetTextdomain :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetTextdomain a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_textdomain Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetTextdomain" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetTextdomainMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetTextdomainMethodInfo a signature where
    overloadedMethod = engineDescGetTextdomain

instance O.OverloadedMethodInfo EngineDescGetTextdomainMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetTextdomain",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetTextdomain"
        }


#endif

-- method EngineDesc::get_version
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_get_version" ibus_engine_desc_get_version :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO CString

-- | Gets the version property in IBusEngineDesc. It should not be freed.
engineDescGetVersion ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> m T.Text
    -- ^ __Returns:__ version in IBusEngineDesc
engineDescGetVersion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> m Text
engineDescGetVersion a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr EngineDesc -> IO CString
ibus_engine_desc_get_version Ptr EngineDesc
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"engineDescGetVersion" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data EngineDescGetVersionMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescGetVersionMethodInfo a signature where
    overloadedMethod = engineDescGetVersion

instance O.OverloadedMethodInfo EngineDescGetVersionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescGetVersion",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescGetVersion"
        }


#endif

-- method EngineDesc::output
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An IBusEngineDesc" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "output"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "String" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "XML-formatted Input method engine description."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "indent"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Number of indent (showed as 4 spaces)."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ibus_engine_desc_output" ibus_engine_desc_output :: 
    Ptr EngineDesc ->                       -- info : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    Ptr GLib.String.String ->               -- output : TInterface (Name {namespace = "GLib", name = "String"})
    Int32 ->                                -- indent : TBasicType TInt
    IO ()

-- | Output XML-formatted input method engine description.
-- The result will be append to GString specified in /@output@/.
engineDescOutput ::
    (B.CallStack.HasCallStack, MonadIO m, IsEngineDesc a) =>
    a
    -- ^ /@info@/: An IBusEngineDesc
    -> GLib.String.String
    -- ^ /@output@/: XML-formatted Input method engine description.
    -> Int32
    -- ^ /@indent@/: Number of indent (showed as 4 spaces).
    -> m ()
engineDescOutput :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsEngineDesc a) =>
a -> String -> Int32 -> m ()
engineDescOutput a
info String
output Int32
indent = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr EngineDesc
info' <- a -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr String
output' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
output
    Ptr EngineDesc -> Ptr String -> Int32 -> IO ()
ibus_engine_desc_output Ptr EngineDesc
info' Ptr String
output' Int32
indent
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
output
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data EngineDescOutputMethodInfo
instance (signature ~ (GLib.String.String -> Int32 -> m ()), MonadIO m, IsEngineDesc a) => O.OverloadedMethod EngineDescOutputMethodInfo a signature where
    overloadedMethod = engineDescOutput

instance O.OverloadedMethodInfo EngineDescOutputMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.IBus.Objects.EngineDesc.engineDescOutput",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-ibus-1.5.3/docs/GI-IBus-Objects-EngineDesc.html#v:engineDescOutput"
        }


#endif