{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An IBusComponent is an executable program.
-- It provides services such as user interface, configuration,
-- and input method engine (IME).
-- 
-- It is recommended that IME developers provide
-- a component XML file and
-- load the XML file by 'GI.IBus.Objects.Component.componentNewFromFile'.
-- 
-- The format of a component XML file is described  at
-- \<ulink url=\"https:\/\/github.com\/ibus\/ibus\/wiki\/DevXML\">https:\/\/github.com\/ibus\/ibus\/wiki\/DevXML\<\/ulink>

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

module GI.IBus.Objects.Component
    ( 

-- * Exported types
    Component(..)                           ,
    IsComponent                             ,
    toComponent                             ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addEngine]("GI.IBus.Objects.Component#g:method:addEngine"), [addObservedPath]("GI.IBus.Objects.Component#g:method:addObservedPath"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [checkModification]("GI.IBus.Objects.Component#g:method:checkModification"), [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.Component#g:method:output"), [outputEngines]("GI.IBus.Objects.Component#g:method:outputEngines"), [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.Component#g:method:getAuthor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDescription]("GI.IBus.Objects.Component#g:method:getDescription"), [getEngines]("GI.IBus.Objects.Component#g:method:getEngines"), [getExec]("GI.IBus.Objects.Component#g:method:getExec"), [getHomepage]("GI.IBus.Objects.Component#g:method:getHomepage"), [getLicense]("GI.IBus.Objects.Component#g:method:getLicense"), [getName]("GI.IBus.Objects.Component#g:method:getName"), [getObservedPaths]("GI.IBus.Objects.Component#g:method:getObservedPaths"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQattachment]("GI.IBus.Objects.Serializable#g:method:getQattachment"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getTextdomain]("GI.IBus.Objects.Component#g:method:getTextdomain"), [getVersion]("GI.IBus.Objects.Component#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)
    ResolveComponentMethod                  ,
#endif

-- ** addEngine #method:addEngine#

#if defined(ENABLE_OVERLOADING)
    ComponentAddEngineMethodInfo            ,
#endif
    componentAddEngine                      ,


-- ** addObservedPath #method:addObservedPath#

#if defined(ENABLE_OVERLOADING)
    ComponentAddObservedPathMethodInfo      ,
#endif
    componentAddObservedPath                ,


-- ** checkModification #method:checkModification#

#if defined(ENABLE_OVERLOADING)
    ComponentCheckModificationMethodInfo    ,
#endif
    componentCheckModification              ,


-- ** getAuthor #method:getAuthor#

#if defined(ENABLE_OVERLOADING)
    ComponentGetAuthorMethodInfo            ,
#endif
    componentGetAuthor                      ,


-- ** getDescription #method:getDescription#

#if defined(ENABLE_OVERLOADING)
    ComponentGetDescriptionMethodInfo       ,
#endif
    componentGetDescription                 ,


-- ** getEngines #method:getEngines#

#if defined(ENABLE_OVERLOADING)
    ComponentGetEnginesMethodInfo           ,
#endif
    componentGetEngines                     ,


-- ** getExec #method:getExec#

#if defined(ENABLE_OVERLOADING)
    ComponentGetExecMethodInfo              ,
#endif
    componentGetExec                        ,


-- ** getHomepage #method:getHomepage#

#if defined(ENABLE_OVERLOADING)
    ComponentGetHomepageMethodInfo          ,
#endif
    componentGetHomepage                    ,


-- ** getLicense #method:getLicense#

#if defined(ENABLE_OVERLOADING)
    ComponentGetLicenseMethodInfo           ,
#endif
    componentGetLicense                     ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    ComponentGetNameMethodInfo              ,
#endif
    componentGetName                        ,


-- ** getObservedPaths #method:getObservedPaths#

#if defined(ENABLE_OVERLOADING)
    ComponentGetObservedPathsMethodInfo     ,
#endif
    componentGetObservedPaths               ,


-- ** getTextdomain #method:getTextdomain#

#if defined(ENABLE_OVERLOADING)
    ComponentGetTextdomainMethodInfo        ,
#endif
    componentGetTextdomain                  ,


-- ** getVersion #method:getVersion#

#if defined(ENABLE_OVERLOADING)
    ComponentGetVersionMethodInfo           ,
#endif
    componentGetVersion                     ,


-- ** new #method:new#

    componentNew                            ,


-- ** newFromFile #method:newFromFile#

    componentNewFromFile                    ,


-- ** newFromXmlNode #method:newFromXmlNode#

    componentNewFromXmlNode                 ,


-- ** output #method:output#

#if defined(ENABLE_OVERLOADING)
    ComponentOutputMethodInfo               ,
#endif
    componentOutput                         ,


-- ** outputEngines #method:outputEngines#

#if defined(ENABLE_OVERLOADING)
    ComponentOutputEnginesMethodInfo        ,
#endif
    componentOutputEngines                  ,




 -- * Properties


-- ** author #attr:author#
-- | The author of component

#if defined(ENABLE_OVERLOADING)
    ComponentAuthorPropertyInfo             ,
#endif
#if defined(ENABLE_OVERLOADING)
    componentAuthor                         ,
#endif
    constructComponentAuthor                ,
    getComponentAuthor                      ,


-- ** commandLine #attr:commandLine#
-- | The exec path of component

#if defined(ENABLE_OVERLOADING)
    ComponentCommandLinePropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    componentCommandLine                    ,
#endif
    constructComponentCommandLine           ,
    getComponentCommandLine                 ,


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

#if defined(ENABLE_OVERLOADING)
    ComponentDescriptionPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    componentDescription                    ,
#endif
    constructComponentDescription           ,
    getComponentDescription                 ,


-- ** homepage #attr:homepage#
-- | The homepage of component

#if defined(ENABLE_OVERLOADING)
    ComponentHomepagePropertyInfo           ,
#endif
#if defined(ENABLE_OVERLOADING)
    componentHomepage                       ,
#endif
    constructComponentHomepage              ,
    getComponentHomepage                    ,


-- ** license #attr:license#
-- | The license of component

#if defined(ENABLE_OVERLOADING)
    ComponentLicensePropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    componentLicense                        ,
#endif
    constructComponentLicense               ,
    getComponentLicense                     ,


-- ** name #attr:name#
-- | The name of component

#if defined(ENABLE_OVERLOADING)
    ComponentNamePropertyInfo               ,
#endif
#if defined(ENABLE_OVERLOADING)
    componentName                           ,
#endif
    constructComponentName                  ,
    getComponentName                        ,


-- ** textdomain #attr:textdomain#
-- | The textdomain of component

#if defined(ENABLE_OVERLOADING)
    ComponentTextdomainPropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    componentTextdomain                     ,
#endif
    constructComponentTextdomain            ,
    getComponentTextdomain                  ,


-- ** version #attr:version#
-- | The version of component

#if defined(ENABLE_OVERLOADING)
    ComponentVersionPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    componentVersion                        ,
#endif
    constructComponentVersion               ,
    getComponentVersion                     ,




    ) where

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

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

import qualified GI.GLib.Structs.String as GLib.String
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.IBus.Objects.EngineDesc as IBus.EngineDesc
import {-# SOURCE #-} qualified GI.IBus.Objects.Object as IBus.Object
import {-# SOURCE #-} qualified GI.IBus.Objects.ObservedPath as IBus.ObservedPath
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 Component = Component (SP.ManagedPtr Component)
    deriving (Component -> Component -> Bool
(Component -> Component -> Bool)
-> (Component -> Component -> Bool) -> Eq Component
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Component -> Component -> Bool
== :: Component -> Component -> Bool
$c/= :: Component -> Component -> Bool
/= :: Component -> Component -> Bool
Eq)

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

foreign import ccall "ibus_component_get_type"
    c_ibus_component_get_type :: IO B.Types.GType

instance B.Types.TypedObject Component where
    glibType :: IO GType
glibType = IO GType
c_ibus_component_get_type

instance B.Types.GObject Component

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

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

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

-- | Convert 'Component' 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 Component) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ibus_component_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Component -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Component
P.Nothing = Ptr GValue -> Ptr Component -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Component
forall a. Ptr a
FP.nullPtr :: FP.Ptr Component)
    gvalueSet_ Ptr GValue
gv (P.Just Component
obj) = Component -> (Ptr Component -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Component
obj (Ptr GValue -> Ptr Component -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Component)
gvalueGet_ Ptr GValue
gv = do
        Ptr Component
ptr <- Ptr GValue -> IO (Ptr Component)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Component)
        if Ptr Component
ptr Ptr Component -> Ptr Component -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Component
forall a. Ptr a
FP.nullPtr
        then Component -> Maybe Component
forall a. a -> Maybe a
P.Just (Component -> Maybe Component)
-> IO Component -> IO (Maybe Component)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Component -> Component)
-> Ptr Component -> IO Component
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Component -> Component
Component Ptr Component
ptr
        else Maybe Component -> IO (Maybe Component)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Component
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveComponentMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveComponentMethod "addEngine" o = ComponentAddEngineMethodInfo
    ResolveComponentMethod "addObservedPath" o = ComponentAddObservedPathMethodInfo
    ResolveComponentMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveComponentMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveComponentMethod "checkModification" o = ComponentCheckModificationMethodInfo
    ResolveComponentMethod "copy" o = IBus.Serializable.SerializableCopyMethodInfo
    ResolveComponentMethod "destroy" o = IBus.Object.ObjectDestroyMethodInfo
    ResolveComponentMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveComponentMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveComponentMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveComponentMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveComponentMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveComponentMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveComponentMethod "output" o = ComponentOutputMethodInfo
    ResolveComponentMethod "outputEngines" o = ComponentOutputEnginesMethodInfo
    ResolveComponentMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveComponentMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveComponentMethod "removeQattachment" o = IBus.Serializable.SerializableRemoveQattachmentMethodInfo
    ResolveComponentMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveComponentMethod "serializeObject" o = IBus.Serializable.SerializableSerializeObjectMethodInfo
    ResolveComponentMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveComponentMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveComponentMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveComponentMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveComponentMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveComponentMethod "getAuthor" o = ComponentGetAuthorMethodInfo
    ResolveComponentMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveComponentMethod "getDescription" o = ComponentGetDescriptionMethodInfo
    ResolveComponentMethod "getEngines" o = ComponentGetEnginesMethodInfo
    ResolveComponentMethod "getExec" o = ComponentGetExecMethodInfo
    ResolveComponentMethod "getHomepage" o = ComponentGetHomepageMethodInfo
    ResolveComponentMethod "getLicense" o = ComponentGetLicenseMethodInfo
    ResolveComponentMethod "getName" o = ComponentGetNameMethodInfo
    ResolveComponentMethod "getObservedPaths" o = ComponentGetObservedPathsMethodInfo
    ResolveComponentMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveComponentMethod "getQattachment" o = IBus.Serializable.SerializableGetQattachmentMethodInfo
    ResolveComponentMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveComponentMethod "getTextdomain" o = ComponentGetTextdomainMethodInfo
    ResolveComponentMethod "getVersion" o = ComponentGetVersionMethodInfo
    ResolveComponentMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveComponentMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveComponentMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveComponentMethod "setQattachment" o = IBus.Serializable.SerializableSetQattachmentMethodInfo
    ResolveComponentMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveComponentMethod t Component, O.OverloadedMethod info Component p) => OL.IsLabel t (Component -> 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 ~ ResolveComponentMethod t Component, O.OverloadedMethod info Component p, R.HasField t Component p) => R.HasField t Component p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveComponentMethod t Component, O.OverloadedMethodInfo info Component) => OL.IsLabel t (O.MethodProxy info Component) 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' component #author
-- @
getComponentAuthor :: (MonadIO m, IsComponent o) => o -> m T.Text
getComponentAuthor :: forall (m :: * -> *) o. (MonadIO m, IsComponent o) => o -> m Text
getComponentAuthor o
obj = IO Text -> m Text
forall a. IO a -> m a
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
"getComponentAuthor" (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`.
constructComponentAuthor :: (IsComponent o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructComponentAuthor :: forall o (m :: * -> *).
(IsComponent o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructComponentAuthor Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> 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 ComponentAuthorPropertyInfo
instance AttrInfo ComponentAuthorPropertyInfo where
    type AttrAllowedOps ComponentAuthorPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ComponentAuthorPropertyInfo = IsComponent
    type AttrSetTypeConstraint ComponentAuthorPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ComponentAuthorPropertyInfo = (~) T.Text
    type AttrTransferType ComponentAuthorPropertyInfo = T.Text
    type AttrGetType ComponentAuthorPropertyInfo = T.Text
    type AttrLabel ComponentAuthorPropertyInfo = "author"
    type AttrOrigin ComponentAuthorPropertyInfo = Component
    attrGet = getComponentAuthor
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructComponentAuthor
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.author"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#g:attr:author"
        })
#endif

-- VVV Prop "command-line"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@command-line@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' component #commandLine
-- @
getComponentCommandLine :: (MonadIO m, IsComponent o) => o -> m (Maybe T.Text)
getComponentCommandLine :: forall (m :: * -> *) o.
(MonadIO m, IsComponent o) =>
o -> m (Maybe Text)
getComponentCommandLine o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe 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
"command-line"

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

#if defined(ENABLE_OVERLOADING)
data ComponentCommandLinePropertyInfo
instance AttrInfo ComponentCommandLinePropertyInfo where
    type AttrAllowedOps ComponentCommandLinePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ComponentCommandLinePropertyInfo = IsComponent
    type AttrSetTypeConstraint ComponentCommandLinePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ComponentCommandLinePropertyInfo = (~) T.Text
    type AttrTransferType ComponentCommandLinePropertyInfo = T.Text
    type AttrGetType ComponentCommandLinePropertyInfo = (Maybe T.Text)
    type AttrLabel ComponentCommandLinePropertyInfo = "command-line"
    type AttrOrigin ComponentCommandLinePropertyInfo = Component
    attrGet = getComponentCommandLine
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructComponentCommandLine
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.commandLine"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#g:attr:commandLine"
        })
#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' component #description
-- @
getComponentDescription :: (MonadIO m, IsComponent o) => o -> m T.Text
getComponentDescription :: forall (m :: * -> *) o. (MonadIO m, IsComponent o) => o -> m Text
getComponentDescription o
obj = IO Text -> m Text
forall a. IO a -> m a
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
"getComponentDescription" (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`.
constructComponentDescription :: (IsComponent o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructComponentDescription :: forall o (m :: * -> *).
(IsComponent o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructComponentDescription Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> 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 ComponentDescriptionPropertyInfo
instance AttrInfo ComponentDescriptionPropertyInfo where
    type AttrAllowedOps ComponentDescriptionPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ComponentDescriptionPropertyInfo = IsComponent
    type AttrSetTypeConstraint ComponentDescriptionPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ComponentDescriptionPropertyInfo = (~) T.Text
    type AttrTransferType ComponentDescriptionPropertyInfo = T.Text
    type AttrGetType ComponentDescriptionPropertyInfo = T.Text
    type AttrLabel ComponentDescriptionPropertyInfo = "description"
    type AttrOrigin ComponentDescriptionPropertyInfo = Component
    attrGet = getComponentDescription
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructComponentDescription
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.description"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#g:attr:description"
        })
#endif

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

-- | Get the value of the “@homepage@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' component #homepage
-- @
getComponentHomepage :: (MonadIO m, IsComponent o) => o -> m T.Text
getComponentHomepage :: forall (m :: * -> *) o. (MonadIO m, IsComponent o) => o -> m Text
getComponentHomepage o
obj = IO Text -> m Text
forall a. IO a -> m a
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
"getComponentHomepage" (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
"homepage"

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

#if defined(ENABLE_OVERLOADING)
data ComponentHomepagePropertyInfo
instance AttrInfo ComponentHomepagePropertyInfo where
    type AttrAllowedOps ComponentHomepagePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ComponentHomepagePropertyInfo = IsComponent
    type AttrSetTypeConstraint ComponentHomepagePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ComponentHomepagePropertyInfo = (~) T.Text
    type AttrTransferType ComponentHomepagePropertyInfo = T.Text
    type AttrGetType ComponentHomepagePropertyInfo = T.Text
    type AttrLabel ComponentHomepagePropertyInfo = "homepage"
    type AttrOrigin ComponentHomepagePropertyInfo = Component
    attrGet = getComponentHomepage
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructComponentHomepage
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.homepage"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#g:attr:homepage"
        })
#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' component #license
-- @
getComponentLicense :: (MonadIO m, IsComponent o) => o -> m T.Text
getComponentLicense :: forall (m :: * -> *) o. (MonadIO m, IsComponent o) => o -> m Text
getComponentLicense o
obj = IO Text -> m Text
forall a. IO a -> m a
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
"getComponentLicense" (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`.
constructComponentLicense :: (IsComponent o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructComponentLicense :: forall o (m :: * -> *).
(IsComponent o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructComponentLicense Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> 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 ComponentLicensePropertyInfo
instance AttrInfo ComponentLicensePropertyInfo where
    type AttrAllowedOps ComponentLicensePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ComponentLicensePropertyInfo = IsComponent
    type AttrSetTypeConstraint ComponentLicensePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ComponentLicensePropertyInfo = (~) T.Text
    type AttrTransferType ComponentLicensePropertyInfo = T.Text
    type AttrGetType ComponentLicensePropertyInfo = T.Text
    type AttrLabel ComponentLicensePropertyInfo = "license"
    type AttrOrigin ComponentLicensePropertyInfo = Component
    attrGet = getComponentLicense
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructComponentLicense
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.license"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#g:attr:license"
        })
#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' component #name
-- @
getComponentName :: (MonadIO m, IsComponent o) => o -> m T.Text
getComponentName :: forall (m :: * -> *) o. (MonadIO m, IsComponent o) => o -> m Text
getComponentName o
obj = IO Text -> m Text
forall a. IO a -> m a
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
"getComponentName" (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`.
constructComponentName :: (IsComponent o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructComponentName :: forall o (m :: * -> *).
(IsComponent o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructComponentName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> 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 ComponentNamePropertyInfo
instance AttrInfo ComponentNamePropertyInfo where
    type AttrAllowedOps ComponentNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ComponentNamePropertyInfo = IsComponent
    type AttrSetTypeConstraint ComponentNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ComponentNamePropertyInfo = (~) T.Text
    type AttrTransferType ComponentNamePropertyInfo = T.Text
    type AttrGetType ComponentNamePropertyInfo = T.Text
    type AttrLabel ComponentNamePropertyInfo = "name"
    type AttrOrigin ComponentNamePropertyInfo = Component
    attrGet = getComponentName
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructComponentName
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.name"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#g:attr:name"
        })
#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' component #textdomain
-- @
getComponentTextdomain :: (MonadIO m, IsComponent o) => o -> m T.Text
getComponentTextdomain :: forall (m :: * -> *) o. (MonadIO m, IsComponent o) => o -> m Text
getComponentTextdomain o
obj = IO Text -> m Text
forall a. IO a -> m a
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
"getComponentTextdomain" (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`.
constructComponentTextdomain :: (IsComponent o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructComponentTextdomain :: forall o (m :: * -> *).
(IsComponent o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructComponentTextdomain Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> 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 ComponentTextdomainPropertyInfo
instance AttrInfo ComponentTextdomainPropertyInfo where
    type AttrAllowedOps ComponentTextdomainPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ComponentTextdomainPropertyInfo = IsComponent
    type AttrSetTypeConstraint ComponentTextdomainPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ComponentTextdomainPropertyInfo = (~) T.Text
    type AttrTransferType ComponentTextdomainPropertyInfo = T.Text
    type AttrGetType ComponentTextdomainPropertyInfo = T.Text
    type AttrLabel ComponentTextdomainPropertyInfo = "textdomain"
    type AttrOrigin ComponentTextdomainPropertyInfo = Component
    attrGet = getComponentTextdomain
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructComponentTextdomain
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.textdomain"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#g:attr:textdomain"
        })
#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' component #version
-- @
getComponentVersion :: (MonadIO m, IsComponent o) => o -> m T.Text
getComponentVersion :: forall (m :: * -> *) o. (MonadIO m, IsComponent o) => o -> m Text
getComponentVersion o
obj = IO Text -> m Text
forall a. IO a -> m a
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
"getComponentVersion" (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`.
constructComponentVersion :: (IsComponent o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructComponentVersion :: forall o (m :: * -> *).
(IsComponent o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructComponentVersion Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> 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 ComponentVersionPropertyInfo
instance AttrInfo ComponentVersionPropertyInfo where
    type AttrAllowedOps ComponentVersionPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ComponentVersionPropertyInfo = IsComponent
    type AttrSetTypeConstraint ComponentVersionPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ComponentVersionPropertyInfo = (~) T.Text
    type AttrTransferType ComponentVersionPropertyInfo = T.Text
    type AttrGetType ComponentVersionPropertyInfo = T.Text
    type AttrLabel ComponentVersionPropertyInfo = "version"
    type AttrOrigin ComponentVersionPropertyInfo = Component
    attrGet = getComponentVersion
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructComponentVersion
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.version"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#g:attr:version"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Component
type instance O.AttributeList Component = ComponentAttributeList
type ComponentAttributeList = ('[ '("author", ComponentAuthorPropertyInfo), '("commandLine", ComponentCommandLinePropertyInfo), '("description", ComponentDescriptionPropertyInfo), '("homepage", ComponentHomepagePropertyInfo), '("license", ComponentLicensePropertyInfo), '("name", ComponentNamePropertyInfo), '("textdomain", ComponentTextdomainPropertyInfo), '("version", ComponentVersionPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

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

componentCommandLine :: AttrLabelProxy "commandLine"
componentCommandLine = AttrLabelProxy

componentDescription :: AttrLabelProxy "description"
componentDescription = AttrLabelProxy

componentHomepage :: AttrLabelProxy "homepage"
componentHomepage = AttrLabelProxy

componentLicense :: AttrLabelProxy "license"
componentLicense = AttrLabelProxy

componentName :: AttrLabelProxy "name"
componentName = AttrLabelProxy

componentTextdomain :: AttrLabelProxy "textdomain"
componentTextdomain = AttrLabelProxy

componentVersion :: AttrLabelProxy "version"
componentVersion = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Component = ComponentSignalList
type ComponentSignalList = ('[ '("destroy", IBus.Object.ObjectDestroySignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method Component::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Name of the component."
--                 , 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 "Detailed description of component."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "version"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Component version." , 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 "Distribution license of this component."
--                 , 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(s) of the component."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "homepage"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Homepage of the component."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "command_line"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "path to component executable."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "textdomain"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Domain name for dgettext()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "IBus" , name = "Component" })
-- throws : False
-- Skip return : False

foreign import ccall "ibus_component_new" ibus_component_new :: 
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- description : TBasicType TUTF8
    CString ->                              -- version : TBasicType TUTF8
    CString ->                              -- license : TBasicType TUTF8
    CString ->                              -- author : TBasicType TUTF8
    CString ->                              -- homepage : TBasicType TUTF8
    CString ->                              -- command_line : TBasicType TUTF8
    CString ->                              -- textdomain : TBasicType TUTF8
    IO (Ptr Component)

-- | Creates a new t'GI.IBus.Objects.Component.Component'.
componentNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@name@/: Name of the component.
    -> T.Text
    -- ^ /@description@/: Detailed description of component.
    -> T.Text
    -- ^ /@version@/: Component version.
    -> T.Text
    -- ^ /@license@/: Distribution license of this component.
    -> T.Text
    -- ^ /@author@/: Author(s) of the component.
    -> T.Text
    -- ^ /@homepage@/: Homepage of the component.
    -> T.Text
    -- ^ /@commandLine@/: path to component executable.
    -> T.Text
    -- ^ /@textdomain@/: Domain name for @/dgettext()/@
    -> m Component
    -- ^ __Returns:__ A newly allocated t'GI.IBus.Objects.Component.Component'.
componentNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> m Component
componentNew Text
name Text
description Text
version Text
license Text
author Text
homepage Text
commandLine Text
textdomain = IO Component -> m Component
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Component -> m Component) -> IO Component -> m Component
forall a b. (a -> b) -> a -> b
$ do
    CString
name' <- Text -> IO CString
textToCString Text
name
    CString
description' <- Text -> IO CString
textToCString Text
description
    CString
version' <- Text -> IO CString
textToCString Text
version
    CString
license' <- Text -> IO CString
textToCString Text
license
    CString
author' <- Text -> IO CString
textToCString Text
author
    CString
homepage' <- Text -> IO CString
textToCString Text
homepage
    CString
commandLine' <- Text -> IO CString
textToCString Text
commandLine
    CString
textdomain' <- Text -> IO CString
textToCString Text
textdomain
    Ptr Component
result <- CString
-> CString
-> CString
-> CString
-> CString
-> CString
-> CString
-> CString
-> IO (Ptr Component)
ibus_component_new CString
name' CString
description' CString
version' CString
license' CString
author' CString
homepage' CString
commandLine' CString
textdomain'
    Text -> Ptr Component -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"componentNew" Ptr Component
result
    Component
result' <- ((ManagedPtr Component -> Component)
-> Ptr Component -> IO Component
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Component -> Component
Component) Ptr Component
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
description'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
version'
    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
homepage'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
commandLine'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
textdomain'
    Component -> IO Component
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Component
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Component::new_from_file
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "filename"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "An XML file that contains component information."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "IBus" , name = "Component" })
-- throws : False
-- Skip return : False

foreign import ccall "ibus_component_new_from_file" ibus_component_new_from_file :: 
    CString ->                              -- filename : TBasicType TUTF8
    IO (Ptr Component)

-- | Creates a new t'GI.IBus.Objects.Component.Component' from an XML file.
-- Note that a component file usually contains engine descriptions,
-- if it does, 'GI.IBus.Objects.EngineDesc.engineDescNewFromXmlNode' will be called
-- to load the engine descriptions.
componentNewFromFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@filename@/: An XML file that contains component information.
    -> m Component
    -- ^ __Returns:__ A newly allocated t'GI.IBus.Objects.Component.Component'.
componentNewFromFile :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m Component
componentNewFromFile Text
filename = IO Component -> m Component
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Component -> m Component) -> IO Component -> m Component
forall a b. (a -> b) -> a -> b
$ do
    CString
filename' <- Text -> IO CString
textToCString Text
filename
    Ptr Component
result <- CString -> IO (Ptr Component)
ibus_component_new_from_file CString
filename'
    Text -> Ptr Component -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"componentNewFromFile" Ptr Component
result
    Component
result' <- ((ManagedPtr Component -> Component)
-> Ptr Component -> IO Component
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Component -> Component
Component) Ptr Component
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
    Component -> IO Component
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Component
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Component::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 "Root node of component XML tree."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "IBus" , name = "Component" })
-- throws : False
-- Skip return : False

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

-- | Creates a new t'GI.IBus.Objects.Component.Component' from an XML tree.
componentNewFromXmlNode ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    IBus.XML.XML
    -- ^ /@node@/: Root node of component XML tree.
    -> m Component
    -- ^ __Returns:__ A newly allocated t'GI.IBus.Objects.Component.Component'.
componentNewFromXmlNode :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
XML -> m Component
componentNewFromXmlNode XML
node = IO Component -> m Component
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Component -> m Component) -> IO Component -> m Component
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 Component
result <- Ptr XML -> IO (Ptr Component)
ibus_component_new_from_xml_node Ptr XML
node'
    Text -> Ptr Component -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"componentNewFromXmlNode" Ptr Component
result
    Component
result' <- ((ManagedPtr Component -> Component)
-> Ptr Component -> IO Component
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Component -> Component
Component) Ptr Component
result
    XML -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr XML
node
    Component -> IO Component
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Component
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Component::add_engine
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #IBusComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "engine"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "EngineDesc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A description of an engine."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ibus_component_add_engine" ibus_component_add_engine :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "IBus", name = "Component"})
    Ptr IBus.EngineDesc.EngineDesc ->       -- engine : TInterface (Name {namespace = "IBus", name = "EngineDesc"})
    IO ()

-- | Add an engine to t'GI.IBus.Objects.Component.Component' according to the description in /@engine@/.
componentAddEngine ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a, IBus.EngineDesc.IsEngineDesc b) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'
    -> b
    -- ^ /@engine@/: A description of an engine.
    -> m ()
componentAddEngine :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsComponent a, IsEngineDesc b) =>
a -> b -> m ()
componentAddEngine a
component b
engine = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    Ptr EngineDesc
engine' <- b -> IO (Ptr EngineDesc)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
engine
    Ptr Component -> Ptr EngineDesc -> IO ()
ibus_component_add_engine Ptr Component
component' Ptr EngineDesc
engine'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
engine
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ComponentAddEngineMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsComponent a, IBus.EngineDesc.IsEngineDesc b) => O.OverloadedMethod ComponentAddEngineMethodInfo a signature where
    overloadedMethod = componentAddEngine

instance O.OverloadedMethodInfo ComponentAddEngineMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentAddEngine",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentAddEngine"
        })


#endif

-- method Component::add_observed_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #IBusComponent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Observed path to be added."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "access_fs"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "%TRUE for filling the file status; %FALSE otherwise."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ibus_component_add_observed_path" ibus_component_add_observed_path :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "IBus", name = "Component"})
    CString ->                              -- path : TBasicType TUTF8
    CInt ->                                 -- access_fs : TBasicType TBoolean
    IO ()

-- | Add an observed path to t'GI.IBus.Objects.Component.Component'.
componentAddObservedPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'
    -> T.Text
    -- ^ /@path@/: Observed path to be added.
    -> Bool
    -- ^ /@accessFs@/: 'P.True' for filling the file status; 'P.False' otherwise.
    -> m ()
componentAddObservedPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComponent a) =>
a -> Text -> Bool -> m ()
componentAddObservedPath a
component Text
path Bool
accessFs = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    CString
path' <- Text -> IO CString
textToCString Text
path
    let accessFs' :: CInt
accessFs' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
accessFs
    Ptr Component -> CString -> CInt -> IO ()
ibus_component_add_observed_path Ptr Component
component' CString
path' CInt
accessFs'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ComponentAddObservedPathMethodInfo
instance (signature ~ (T.Text -> Bool -> m ()), MonadIO m, IsComponent a) => O.OverloadedMethod ComponentAddObservedPathMethodInfo a signature where
    overloadedMethod = componentAddObservedPath

instance O.OverloadedMethodInfo ComponentAddObservedPathMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentAddObservedPath",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentAddObservedPath"
        })


#endif

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

foreign import ccall "ibus_component_check_modification" ibus_component_check_modification :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "IBus", name = "Component"})
    IO CInt

-- | Check whether the observed paths of component is modified.
componentCheckModification ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if at least one of the observed paths is modified;
    -- 'P.False' otherwise.
componentCheckModification :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComponent a) =>
a -> m Bool
componentCheckModification a
component = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    CInt
result <- Ptr Component -> IO CInt
ibus_component_check_modification Ptr Component
component'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ComponentCheckModificationMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsComponent a) => O.OverloadedMethod ComponentCheckModificationMethodInfo a signature where
    overloadedMethod = componentCheckModification

instance O.OverloadedMethodInfo ComponentCheckModificationMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentCheckModification",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentCheckModification"
        })


#endif

-- method Component::get_author
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #IBusComponent" , 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_component_get_author" ibus_component_get_author :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "IBus", name = "Component"})
    IO CString

-- | Gets the author property in t'GI.IBus.Objects.Component.Component'. It should not be freed.
componentGetAuthor ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'
    -> m T.Text
    -- ^ __Returns:__ author property in t'GI.IBus.Objects.Component.Component'
componentGetAuthor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComponent a) =>
a -> m Text
componentGetAuthor a
component = IO Text -> m Text
forall a. IO a -> m a
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 Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    CString
result <- Ptr Component -> IO CString
ibus_component_get_author Ptr Component
component'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"componentGetAuthor" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ComponentGetAuthorMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsComponent a) => O.OverloadedMethod ComponentGetAuthorMethodInfo a signature where
    overloadedMethod = componentGetAuthor

instance O.OverloadedMethodInfo ComponentGetAuthorMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentGetAuthor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentGetAuthor"
        })


#endif

-- method Component::get_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #IBusComponent" , 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_component_get_description" ibus_component_get_description :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "IBus", name = "Component"})
    IO CString

-- | Gets the description property in t'GI.IBus.Objects.Component.Component'. It should not be freed.
componentGetDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'
    -> m T.Text
    -- ^ __Returns:__ description property in t'GI.IBus.Objects.Component.Component'
componentGetDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComponent a) =>
a -> m Text
componentGetDescription a
component = IO Text -> m Text
forall a. IO a -> m a
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 Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    CString
result <- Ptr Component -> IO CString
ibus_component_get_description Ptr Component
component'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"componentGetDescription" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ComponentGetDescriptionMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsComponent a) => O.OverloadedMethod ComponentGetDescriptionMethodInfo a signature where
    overloadedMethod = componentGetDescription

instance O.OverloadedMethodInfo ComponentGetDescriptionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentGetDescription",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentGetDescription"
        })


#endif

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

foreign import ccall "ibus_component_get_engines" ibus_component_get_engines :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "IBus", name = "Component"})
    IO (Ptr (GList (Ptr IBus.EngineDesc.EngineDesc)))

-- | Gets the engines of this component.
componentGetEngines ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'.
    -> m [IBus.EngineDesc.EngineDesc]
    -- ^ __Returns:__ 
    -- A newly allocated GList that contains engines.
componentGetEngines :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComponent a) =>
a -> m [EngineDesc]
componentGetEngines a
component = IO [EngineDesc] -> m [EngineDesc]
forall a. IO a -> m a
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 Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    Ptr (GList (Ptr EngineDesc))
result <- Ptr Component -> IO (Ptr (GList (Ptr EngineDesc)))
ibus_component_get_engines Ptr Component
component'
    [Ptr EngineDesc]
result' <- Ptr (GList (Ptr EngineDesc)) -> IO [Ptr EngineDesc]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr EngineDesc))
result
    [EngineDesc]
result'' <- (Ptr EngineDesc -> IO EngineDesc)
-> [Ptr EngineDesc] -> IO [EngineDesc]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((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
IBus.EngineDesc.EngineDesc) [Ptr EngineDesc]
result'
    Ptr (GList (Ptr EngineDesc)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr EngineDesc))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    [EngineDesc] -> IO [EngineDesc]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [EngineDesc]
result''

#if defined(ENABLE_OVERLOADING)
data ComponentGetEnginesMethodInfo
instance (signature ~ (m [IBus.EngineDesc.EngineDesc]), MonadIO m, IsComponent a) => O.OverloadedMethod ComponentGetEnginesMethodInfo a signature where
    overloadedMethod = componentGetEngines

instance O.OverloadedMethodInfo ComponentGetEnginesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentGetEngines",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentGetEngines"
        })


#endif

-- method Component::get_exec
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #IBusComponent" , 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_component_get_exec" ibus_component_get_exec :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "IBus", name = "Component"})
    IO CString

-- | Gets the exec property in t'GI.IBus.Objects.Component.Component'. It should not be freed.
componentGetExec ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'
    -> m T.Text
    -- ^ __Returns:__ exec property in t'GI.IBus.Objects.Component.Component'
componentGetExec :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComponent a) =>
a -> m Text
componentGetExec a
component = IO Text -> m Text
forall a. IO a -> m a
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 Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    CString
result <- Ptr Component -> IO CString
ibus_component_get_exec Ptr Component
component'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"componentGetExec" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ComponentGetExecMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsComponent a) => O.OverloadedMethod ComponentGetExecMethodInfo a signature where
    overloadedMethod = componentGetExec

instance O.OverloadedMethodInfo ComponentGetExecMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentGetExec",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentGetExec"
        })


#endif

-- method Component::get_homepage
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #IBusComponent" , 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_component_get_homepage" ibus_component_get_homepage :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "IBus", name = "Component"})
    IO CString

-- | Gets the homepage property in t'GI.IBus.Objects.Component.Component'. It should not be freed.
componentGetHomepage ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'
    -> m T.Text
    -- ^ __Returns:__ homepage property in t'GI.IBus.Objects.Component.Component'
componentGetHomepage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComponent a) =>
a -> m Text
componentGetHomepage a
component = IO Text -> m Text
forall a. IO a -> m a
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 Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    CString
result <- Ptr Component -> IO CString
ibus_component_get_homepage Ptr Component
component'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"componentGetHomepage" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ComponentGetHomepageMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsComponent a) => O.OverloadedMethod ComponentGetHomepageMethodInfo a signature where
    overloadedMethod = componentGetHomepage

instance O.OverloadedMethodInfo ComponentGetHomepageMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentGetHomepage",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentGetHomepage"
        })


#endif

-- method Component::get_license
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #IBusComponent" , 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_component_get_license" ibus_component_get_license :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "IBus", name = "Component"})
    IO CString

-- | Gets the license property in t'GI.IBus.Objects.Component.Component'. It should not be freed.
componentGetLicense ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'
    -> m T.Text
    -- ^ __Returns:__ license property in t'GI.IBus.Objects.Component.Component'
componentGetLicense :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComponent a) =>
a -> m Text
componentGetLicense a
component = IO Text -> m Text
forall a. IO a -> m a
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 Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    CString
result <- Ptr Component -> IO CString
ibus_component_get_license Ptr Component
component'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"componentGetLicense" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ComponentGetLicenseMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsComponent a) => O.OverloadedMethod ComponentGetLicenseMethodInfo a signature where
    overloadedMethod = componentGetLicense

instance O.OverloadedMethodInfo ComponentGetLicenseMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentGetLicense",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentGetLicense"
        })


#endif

-- method Component::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #IBusComponent" , 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_component_get_name" ibus_component_get_name :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "IBus", name = "Component"})
    IO CString

-- | Gets the name property in t'GI.IBus.Objects.Component.Component'. It should not be freed.
componentGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'
    -> m T.Text
    -- ^ __Returns:__ name property in t'GI.IBus.Objects.Component.Component'
componentGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComponent a) =>
a -> m Text
componentGetName a
component = IO Text -> m Text
forall a. IO a -> m a
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 Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    CString
result <- Ptr Component -> IO CString
ibus_component_get_name Ptr Component
component'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"componentGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ComponentGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsComponent a) => O.OverloadedMethod ComponentGetNameMethodInfo a signature where
    overloadedMethod = componentGetName

instance O.OverloadedMethodInfo ComponentGetNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentGetName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentGetName"
        })


#endif

-- method Component::get_observed_paths
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #IBusComponent." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList
--                  (TInterface Name { namespace = "IBus" , name = "ObservedPath" }))
-- throws : False
-- Skip return : False

foreign import ccall "ibus_component_get_observed_paths" ibus_component_get_observed_paths :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "IBus", name = "Component"})
    IO (Ptr (GList (Ptr IBus.ObservedPath.ObservedPath)))

-- | Gets the observed paths of this component.
componentGetObservedPaths ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'.
    -> m [IBus.ObservedPath.ObservedPath]
    -- ^ __Returns:__ A
    -- newly allocated GList that contains observed paths.
componentGetObservedPaths :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComponent a) =>
a -> m [ObservedPath]
componentGetObservedPaths a
component = IO [ObservedPath] -> m [ObservedPath]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ObservedPath] -> m [ObservedPath])
-> IO [ObservedPath] -> m [ObservedPath]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    Ptr (GList (Ptr ObservedPath))
result <- Ptr Component -> IO (Ptr (GList (Ptr ObservedPath)))
ibus_component_get_observed_paths Ptr Component
component'
    [Ptr ObservedPath]
result' <- Ptr (GList (Ptr ObservedPath)) -> IO [Ptr ObservedPath]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr ObservedPath))
result
    [ObservedPath]
result'' <- (Ptr ObservedPath -> IO ObservedPath)
-> [Ptr ObservedPath] -> IO [ObservedPath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((ManagedPtr ObservedPath -> ObservedPath)
-> Ptr ObservedPath -> IO ObservedPath
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ObservedPath -> ObservedPath
IBus.ObservedPath.ObservedPath) [Ptr ObservedPath]
result'
    Ptr (GList (Ptr ObservedPath)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr ObservedPath))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    [ObservedPath] -> IO [ObservedPath]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [ObservedPath]
result''

#if defined(ENABLE_OVERLOADING)
data ComponentGetObservedPathsMethodInfo
instance (signature ~ (m [IBus.ObservedPath.ObservedPath]), MonadIO m, IsComponent a) => O.OverloadedMethod ComponentGetObservedPathsMethodInfo a signature where
    overloadedMethod = componentGetObservedPaths

instance O.OverloadedMethodInfo ComponentGetObservedPathsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentGetObservedPaths",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentGetObservedPaths"
        })


#endif

-- method Component::get_textdomain
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #IBusComponent" , 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_component_get_textdomain" ibus_component_get_textdomain :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "IBus", name = "Component"})
    IO CString

-- | Gets the textdomain property in t'GI.IBus.Objects.Component.Component'. It should not be freed.
componentGetTextdomain ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'
    -> m T.Text
    -- ^ __Returns:__ textdomain property in t'GI.IBus.Objects.Component.Component'
componentGetTextdomain :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComponent a) =>
a -> m Text
componentGetTextdomain a
component = IO Text -> m Text
forall a. IO a -> m a
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 Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    CString
result <- Ptr Component -> IO CString
ibus_component_get_textdomain Ptr Component
component'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"componentGetTextdomain" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ComponentGetTextdomainMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsComponent a) => O.OverloadedMethod ComponentGetTextdomainMethodInfo a signature where
    overloadedMethod = componentGetTextdomain

instance O.OverloadedMethodInfo ComponentGetTextdomainMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentGetTextdomain",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentGetTextdomain"
        })


#endif

-- method Component::get_version
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #IBusComponent" , 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_component_get_version" ibus_component_get_version :: 
    Ptr Component ->                        -- component : TInterface (Name {namespace = "IBus", name = "Component"})
    IO CString

-- | Gets the version property in t'GI.IBus.Objects.Component.Component'. It should not be freed.
componentGetVersion ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'
    -> m T.Text
    -- ^ __Returns:__ version property in t'GI.IBus.Objects.Component.Component'
componentGetVersion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComponent a) =>
a -> m Text
componentGetVersion a
component = IO Text -> m Text
forall a. IO a -> m a
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 Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    CString
result <- Ptr Component -> IO CString
ibus_component_get_version Ptr Component
component'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"componentGetVersion" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ComponentGetVersionMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsComponent a) => O.OverloadedMethod ComponentGetVersionMethodInfo a signature where
    overloadedMethod = componentGetVersion

instance O.OverloadedMethodInfo ComponentGetVersionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentGetVersion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentGetVersion"
        })


#endif

-- method Component::output
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #IBusComponent." , 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 "GString that holds the result."
--                 , 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 "level of indent." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Output t'GI.IBus.Objects.Component.Component' as an XML-formatted string.
-- The output string can be then shown on the screen or written to file.
componentOutput ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'.
    -> GLib.String.String
    -- ^ /@output@/: GString that holds the result.
    -> Int32
    -- ^ /@indent@/: level of indent.
    -> m ()
componentOutput :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComponent a) =>
a -> String -> Int32 -> m ()
componentOutput a
component String
output Int32
indent = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    Ptr String
output' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
output
    Ptr Component -> Ptr String -> Int32 -> IO ()
ibus_component_output Ptr Component
component' Ptr String
output' Int32
indent
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
output
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo ComponentOutputMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentOutput",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentOutput"
        })


#endif

-- method Component::output_engines
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "component"
--           , argType =
--               TInterface Name { namespace = "IBus" , name = "Component" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #IBusComponent." , 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 "GString that holds the result."
--                 , 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 "level of indent." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Output engine description  as an XML-formatted string.
-- The output string can be then shown on the screen or written to file.
componentOutputEngines ::
    (B.CallStack.HasCallStack, MonadIO m, IsComponent a) =>
    a
    -- ^ /@component@/: An t'GI.IBus.Objects.Component.Component'.
    -> GLib.String.String
    -- ^ /@output@/: GString that holds the result.
    -> Int32
    -- ^ /@indent@/: level of indent.
    -> m ()
componentOutputEngines :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsComponent a) =>
a -> String -> Int32 -> m ()
componentOutputEngines a
component String
output Int32
indent = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Component
component' <- a -> IO (Ptr Component)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
component
    Ptr String
output' <- String -> IO (Ptr String)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr String
output
    Ptr Component -> Ptr String -> Int32 -> IO ()
ibus_component_output_engines Ptr Component
component' Ptr String
output' Int32
indent
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
component
    String -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr String
output
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo ComponentOutputEnginesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.IBus.Objects.Component.componentOutputEngines",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ibus-1.5.7/docs/GI-IBus-Objects-Component.html#v:componentOutputEngines"
        })


#endif