{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.AppLaunchContext
    ( 
    AppLaunchContext(..)                    ,
    IsAppLaunchContext                      ,
    toAppLaunchContext                      ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveAppLaunchContextMethod           ,
#endif
#if defined(ENABLE_OVERLOADING)
    AppLaunchContextGetDisplayMethodInfo    ,
#endif
    appLaunchContextGetDisplay              ,
#if defined(ENABLE_OVERLOADING)
    AppLaunchContextGetEnvironmentMethodInfo,
#endif
    appLaunchContextGetEnvironment          ,
#if defined(ENABLE_OVERLOADING)
    AppLaunchContextGetStartupNotifyIdMethodInfo,
#endif
    appLaunchContextGetStartupNotifyId      ,
#if defined(ENABLE_OVERLOADING)
    AppLaunchContextLaunchFailedMethodInfo  ,
#endif
    appLaunchContextLaunchFailed            ,
    appLaunchContextNew                     ,
#if defined(ENABLE_OVERLOADING)
    AppLaunchContextSetenvMethodInfo        ,
#endif
    appLaunchContextSetenv                  ,
#if defined(ENABLE_OVERLOADING)
    AppLaunchContextUnsetenvMethodInfo      ,
#endif
    appLaunchContextUnsetenv                ,
 
    AppLaunchContextLaunchFailedCallback    ,
#if defined(ENABLE_OVERLOADING)
    AppLaunchContextLaunchFailedSignalInfo  ,
#endif
    C_AppLaunchContextLaunchFailedCallback  ,
    afterAppLaunchContextLaunchFailed       ,
    genClosure_AppLaunchContextLaunchFailed ,
    mk_AppLaunchContextLaunchFailedCallback ,
    noAppLaunchContextLaunchFailedCallback  ,
    onAppLaunchContextLaunchFailed          ,
    wrap_AppLaunchContextLaunchFailedCallback,
    AppLaunchContextLaunchedCallback        ,
#if defined(ENABLE_OVERLOADING)
    AppLaunchContextLaunchedSignalInfo      ,
#endif
    C_AppLaunchContextLaunchedCallback      ,
    afterAppLaunchContextLaunched           ,
    genClosure_AppLaunchContextLaunched     ,
    mk_AppLaunchContextLaunchedCallback     ,
    noAppLaunchContextLaunchedCallback      ,
    onAppLaunchContextLaunched              ,
    wrap_AppLaunchContextLaunchedCallback   ,
    ) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AppInfo as Gio.AppInfo
import {-# SOURCE #-} qualified GI.Gio.Interfaces.File as Gio.File
newtype AppLaunchContext = AppLaunchContext (SP.ManagedPtr AppLaunchContext)
    deriving (AppLaunchContext -> AppLaunchContext -> Bool
(AppLaunchContext -> AppLaunchContext -> Bool)
-> (AppLaunchContext -> AppLaunchContext -> Bool)
-> Eq AppLaunchContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AppLaunchContext -> AppLaunchContext -> Bool
$c/= :: AppLaunchContext -> AppLaunchContext -> Bool
== :: AppLaunchContext -> AppLaunchContext -> Bool
$c== :: AppLaunchContext -> AppLaunchContext -> Bool
Eq)
instance SP.ManagedPtrNewtype AppLaunchContext where
    toManagedPtr :: AppLaunchContext -> ManagedPtr AppLaunchContext
toManagedPtr (AppLaunchContext ManagedPtr AppLaunchContext
p) = ManagedPtr AppLaunchContext
p
foreign import ccall "g_app_launch_context_get_type"
    c_g_app_launch_context_get_type :: IO B.Types.GType
instance B.Types.TypedObject AppLaunchContext where
    glibType :: IO GType
glibType = IO GType
c_g_app_launch_context_get_type
instance B.Types.GObject AppLaunchContext
instance B.GValue.IsGValue AppLaunchContext where
    toGValue :: AppLaunchContext -> IO GValue
toGValue AppLaunchContext
o = do
        GType
gtype <- IO GType
c_g_app_launch_context_get_type
        AppLaunchContext
-> (Ptr AppLaunchContext -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AppLaunchContext
o (GType
-> (GValue -> Ptr AppLaunchContext -> IO ())
-> Ptr AppLaunchContext
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr AppLaunchContext -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO AppLaunchContext
fromGValue GValue
gv = do
        Ptr AppLaunchContext
ptr <- GValue -> IO (Ptr AppLaunchContext)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr AppLaunchContext)
        (ManagedPtr AppLaunchContext -> AppLaunchContext)
-> Ptr AppLaunchContext -> IO AppLaunchContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr AppLaunchContext -> AppLaunchContext
AppLaunchContext Ptr AppLaunchContext
ptr
        
    
class (SP.GObject o, O.IsDescendantOf AppLaunchContext o) => IsAppLaunchContext o
instance (SP.GObject o, O.IsDescendantOf AppLaunchContext o) => IsAppLaunchContext o
instance O.HasParentTypes AppLaunchContext
type instance O.ParentTypes AppLaunchContext = '[GObject.Object.Object]
toAppLaunchContext :: (MonadIO m, IsAppLaunchContext o) => o -> m AppLaunchContext
toAppLaunchContext :: o -> m AppLaunchContext
toAppLaunchContext = IO AppLaunchContext -> m AppLaunchContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AppLaunchContext -> m AppLaunchContext)
-> (o -> IO AppLaunchContext) -> o -> m AppLaunchContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr AppLaunchContext -> AppLaunchContext)
-> o -> IO AppLaunchContext
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr AppLaunchContext -> AppLaunchContext
AppLaunchContext
#if defined(ENABLE_OVERLOADING)
type family ResolveAppLaunchContextMethod (t :: Symbol) (o :: *) :: * where
    ResolveAppLaunchContextMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveAppLaunchContextMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveAppLaunchContextMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveAppLaunchContextMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveAppLaunchContextMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveAppLaunchContextMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveAppLaunchContextMethod "launchFailed" o = AppLaunchContextLaunchFailedMethodInfo
    ResolveAppLaunchContextMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveAppLaunchContextMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveAppLaunchContextMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveAppLaunchContextMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveAppLaunchContextMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveAppLaunchContextMethod "setenv" o = AppLaunchContextSetenvMethodInfo
    ResolveAppLaunchContextMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveAppLaunchContextMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveAppLaunchContextMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveAppLaunchContextMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveAppLaunchContextMethod "unsetenv" o = AppLaunchContextUnsetenvMethodInfo
    ResolveAppLaunchContextMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveAppLaunchContextMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveAppLaunchContextMethod "getDisplay" o = AppLaunchContextGetDisplayMethodInfo
    ResolveAppLaunchContextMethod "getEnvironment" o = AppLaunchContextGetEnvironmentMethodInfo
    ResolveAppLaunchContextMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveAppLaunchContextMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveAppLaunchContextMethod "getStartupNotifyId" o = AppLaunchContextGetStartupNotifyIdMethodInfo
    ResolveAppLaunchContextMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveAppLaunchContextMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveAppLaunchContextMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveAppLaunchContextMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveAppLaunchContextMethod t AppLaunchContext, O.MethodInfo info AppLaunchContext p) => OL.IsLabel t (AppLaunchContext -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif
#endif
type AppLaunchContextLaunchFailedCallback =
    T.Text
    
    -> IO ()
noAppLaunchContextLaunchFailedCallback :: Maybe AppLaunchContextLaunchFailedCallback
noAppLaunchContextLaunchFailedCallback :: Maybe AppLaunchContextLaunchFailedCallback
noAppLaunchContextLaunchFailedCallback = Maybe AppLaunchContextLaunchFailedCallback
forall a. Maybe a
Nothing
type C_AppLaunchContextLaunchFailedCallback =
    Ptr () ->                               
    CString ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_AppLaunchContextLaunchFailedCallback :: C_AppLaunchContextLaunchFailedCallback -> IO (FunPtr C_AppLaunchContextLaunchFailedCallback)
genClosure_AppLaunchContextLaunchFailed :: MonadIO m => AppLaunchContextLaunchFailedCallback -> m (GClosure C_AppLaunchContextLaunchFailedCallback)
genClosure_AppLaunchContextLaunchFailed :: AppLaunchContextLaunchFailedCallback
-> m (GClosure C_AppLaunchContextLaunchFailedCallback)
genClosure_AppLaunchContextLaunchFailed AppLaunchContextLaunchFailedCallback
cb = IO (GClosure C_AppLaunchContextLaunchFailedCallback)
-> m (GClosure C_AppLaunchContextLaunchFailedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_AppLaunchContextLaunchFailedCallback)
 -> m (GClosure C_AppLaunchContextLaunchFailedCallback))
-> IO (GClosure C_AppLaunchContextLaunchFailedCallback)
-> m (GClosure C_AppLaunchContextLaunchFailedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AppLaunchContextLaunchFailedCallback
cb' = AppLaunchContextLaunchFailedCallback
-> C_AppLaunchContextLaunchFailedCallback
wrap_AppLaunchContextLaunchFailedCallback AppLaunchContextLaunchFailedCallback
cb
    C_AppLaunchContextLaunchFailedCallback
-> IO (FunPtr C_AppLaunchContextLaunchFailedCallback)
mk_AppLaunchContextLaunchFailedCallback C_AppLaunchContextLaunchFailedCallback
cb' IO (FunPtr C_AppLaunchContextLaunchFailedCallback)
-> (FunPtr C_AppLaunchContextLaunchFailedCallback
    -> IO (GClosure C_AppLaunchContextLaunchFailedCallback))
-> IO (GClosure C_AppLaunchContextLaunchFailedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_AppLaunchContextLaunchFailedCallback
-> IO (GClosure C_AppLaunchContextLaunchFailedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_AppLaunchContextLaunchFailedCallback ::
    AppLaunchContextLaunchFailedCallback ->
    C_AppLaunchContextLaunchFailedCallback
wrap_AppLaunchContextLaunchFailedCallback :: AppLaunchContextLaunchFailedCallback
-> C_AppLaunchContextLaunchFailedCallback
wrap_AppLaunchContextLaunchFailedCallback AppLaunchContextLaunchFailedCallback
_cb Ptr ()
_ CString
startupNotifyId Ptr ()
_ = do
    Text
startupNotifyId' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
startupNotifyId
    AppLaunchContextLaunchFailedCallback
_cb  Text
startupNotifyId'
onAppLaunchContextLaunchFailed :: (IsAppLaunchContext a, MonadIO m) => a -> AppLaunchContextLaunchFailedCallback -> m SignalHandlerId
onAppLaunchContextLaunchFailed :: a -> AppLaunchContextLaunchFailedCallback -> m SignalHandlerId
onAppLaunchContextLaunchFailed a
obj AppLaunchContextLaunchFailedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AppLaunchContextLaunchFailedCallback
cb' = AppLaunchContextLaunchFailedCallback
-> C_AppLaunchContextLaunchFailedCallback
wrap_AppLaunchContextLaunchFailedCallback AppLaunchContextLaunchFailedCallback
cb
    FunPtr C_AppLaunchContextLaunchFailedCallback
cb'' <- C_AppLaunchContextLaunchFailedCallback
-> IO (FunPtr C_AppLaunchContextLaunchFailedCallback)
mk_AppLaunchContextLaunchFailedCallback C_AppLaunchContextLaunchFailedCallback
cb'
    a
-> Text
-> FunPtr C_AppLaunchContextLaunchFailedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"launch-failed" FunPtr C_AppLaunchContextLaunchFailedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterAppLaunchContextLaunchFailed :: (IsAppLaunchContext a, MonadIO m) => a -> AppLaunchContextLaunchFailedCallback -> m SignalHandlerId
afterAppLaunchContextLaunchFailed :: a -> AppLaunchContextLaunchFailedCallback -> m SignalHandlerId
afterAppLaunchContextLaunchFailed a
obj AppLaunchContextLaunchFailedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AppLaunchContextLaunchFailedCallback
cb' = AppLaunchContextLaunchFailedCallback
-> C_AppLaunchContextLaunchFailedCallback
wrap_AppLaunchContextLaunchFailedCallback AppLaunchContextLaunchFailedCallback
cb
    FunPtr C_AppLaunchContextLaunchFailedCallback
cb'' <- C_AppLaunchContextLaunchFailedCallback
-> IO (FunPtr C_AppLaunchContextLaunchFailedCallback)
mk_AppLaunchContextLaunchFailedCallback C_AppLaunchContextLaunchFailedCallback
cb'
    a
-> Text
-> FunPtr C_AppLaunchContextLaunchFailedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"launch-failed" FunPtr C_AppLaunchContextLaunchFailedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data AppLaunchContextLaunchFailedSignalInfo
instance SignalInfo AppLaunchContextLaunchFailedSignalInfo where
    type HaskellCallbackType AppLaunchContextLaunchFailedSignalInfo = AppLaunchContextLaunchFailedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_AppLaunchContextLaunchFailedCallback cb
        cb'' <- mk_AppLaunchContextLaunchFailedCallback cb'
        connectSignalFunPtr obj "launch-failed" cb'' connectMode detail
#endif
type AppLaunchContextLaunchedCallback =
    Gio.AppInfo.AppInfo
    
    -> GVariant
    
    -> IO ()
noAppLaunchContextLaunchedCallback :: Maybe AppLaunchContextLaunchedCallback
noAppLaunchContextLaunchedCallback :: Maybe AppLaunchContextLaunchedCallback
noAppLaunchContextLaunchedCallback = Maybe AppLaunchContextLaunchedCallback
forall a. Maybe a
Nothing
type C_AppLaunchContextLaunchedCallback =
    Ptr () ->                               
    Ptr Gio.AppInfo.AppInfo ->
    Ptr GVariant ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_AppLaunchContextLaunchedCallback :: C_AppLaunchContextLaunchedCallback -> IO (FunPtr C_AppLaunchContextLaunchedCallback)
genClosure_AppLaunchContextLaunched :: MonadIO m => AppLaunchContextLaunchedCallback -> m (GClosure C_AppLaunchContextLaunchedCallback)
genClosure_AppLaunchContextLaunched :: AppLaunchContextLaunchedCallback
-> m (GClosure C_AppLaunchContextLaunchedCallback)
genClosure_AppLaunchContextLaunched AppLaunchContextLaunchedCallback
cb = IO (GClosure C_AppLaunchContextLaunchedCallback)
-> m (GClosure C_AppLaunchContextLaunchedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_AppLaunchContextLaunchedCallback)
 -> m (GClosure C_AppLaunchContextLaunchedCallback))
-> IO (GClosure C_AppLaunchContextLaunchedCallback)
-> m (GClosure C_AppLaunchContextLaunchedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AppLaunchContextLaunchedCallback
cb' = AppLaunchContextLaunchedCallback
-> C_AppLaunchContextLaunchedCallback
wrap_AppLaunchContextLaunchedCallback AppLaunchContextLaunchedCallback
cb
    C_AppLaunchContextLaunchedCallback
-> IO (FunPtr C_AppLaunchContextLaunchedCallback)
mk_AppLaunchContextLaunchedCallback C_AppLaunchContextLaunchedCallback
cb' IO (FunPtr C_AppLaunchContextLaunchedCallback)
-> (FunPtr C_AppLaunchContextLaunchedCallback
    -> IO (GClosure C_AppLaunchContextLaunchedCallback))
-> IO (GClosure C_AppLaunchContextLaunchedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_AppLaunchContextLaunchedCallback
-> IO (GClosure C_AppLaunchContextLaunchedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_AppLaunchContextLaunchedCallback ::
    AppLaunchContextLaunchedCallback ->
    C_AppLaunchContextLaunchedCallback
wrap_AppLaunchContextLaunchedCallback :: AppLaunchContextLaunchedCallback
-> C_AppLaunchContextLaunchedCallback
wrap_AppLaunchContextLaunchedCallback AppLaunchContextLaunchedCallback
_cb Ptr ()
_ Ptr AppInfo
info Ptr GVariant
platformData Ptr ()
_ = do
    AppInfo
info' <- ((ManagedPtr AppInfo -> AppInfo) -> Ptr AppInfo -> IO AppInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr AppInfo -> AppInfo
Gio.AppInfo.AppInfo) Ptr AppInfo
info
    GVariant
platformData' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
platformData
    AppLaunchContextLaunchedCallback
_cb  AppInfo
info' GVariant
platformData'
onAppLaunchContextLaunched :: (IsAppLaunchContext a, MonadIO m) => a -> AppLaunchContextLaunchedCallback -> m SignalHandlerId
onAppLaunchContextLaunched :: a -> AppLaunchContextLaunchedCallback -> m SignalHandlerId
onAppLaunchContextLaunched a
obj AppLaunchContextLaunchedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AppLaunchContextLaunchedCallback
cb' = AppLaunchContextLaunchedCallback
-> C_AppLaunchContextLaunchedCallback
wrap_AppLaunchContextLaunchedCallback AppLaunchContextLaunchedCallback
cb
    FunPtr C_AppLaunchContextLaunchedCallback
cb'' <- C_AppLaunchContextLaunchedCallback
-> IO (FunPtr C_AppLaunchContextLaunchedCallback)
mk_AppLaunchContextLaunchedCallback C_AppLaunchContextLaunchedCallback
cb'
    a
-> Text
-> FunPtr C_AppLaunchContextLaunchedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"launched" FunPtr C_AppLaunchContextLaunchedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterAppLaunchContextLaunched :: (IsAppLaunchContext a, MonadIO m) => a -> AppLaunchContextLaunchedCallback -> m SignalHandlerId
afterAppLaunchContextLaunched :: a -> AppLaunchContextLaunchedCallback -> m SignalHandlerId
afterAppLaunchContextLaunched a
obj AppLaunchContextLaunchedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_AppLaunchContextLaunchedCallback
cb' = AppLaunchContextLaunchedCallback
-> C_AppLaunchContextLaunchedCallback
wrap_AppLaunchContextLaunchedCallback AppLaunchContextLaunchedCallback
cb
    FunPtr C_AppLaunchContextLaunchedCallback
cb'' <- C_AppLaunchContextLaunchedCallback
-> IO (FunPtr C_AppLaunchContextLaunchedCallback)
mk_AppLaunchContextLaunchedCallback C_AppLaunchContextLaunchedCallback
cb'
    a
-> Text
-> FunPtr C_AppLaunchContextLaunchedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"launched" FunPtr C_AppLaunchContextLaunchedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data AppLaunchContextLaunchedSignalInfo
instance SignalInfo AppLaunchContextLaunchedSignalInfo where
    type HaskellCallbackType AppLaunchContextLaunchedSignalInfo = AppLaunchContextLaunchedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_AppLaunchContextLaunchedCallback cb
        cb'' <- mk_AppLaunchContextLaunchedCallback cb'
        connectSignalFunPtr obj "launched" cb'' connectMode detail
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AppLaunchContext
type instance O.AttributeList AppLaunchContext = AppLaunchContextAttributeList
type AppLaunchContextAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList AppLaunchContext = AppLaunchContextSignalList
type AppLaunchContextSignalList = ('[ '("launchFailed", AppLaunchContextLaunchFailedSignalInfo), '("launched", AppLaunchContextLaunchedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_app_launch_context_new" g_app_launch_context_new :: 
    IO (Ptr AppLaunchContext)
appLaunchContextNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m AppLaunchContext
    
appLaunchContextNew :: m AppLaunchContext
appLaunchContextNew  = IO AppLaunchContext -> m AppLaunchContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AppLaunchContext -> m AppLaunchContext)
-> IO AppLaunchContext -> m AppLaunchContext
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppLaunchContext
result <- IO (Ptr AppLaunchContext)
g_app_launch_context_new
    Text -> Ptr AppLaunchContext -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"appLaunchContextNew" Ptr AppLaunchContext
result
    AppLaunchContext
result' <- ((ManagedPtr AppLaunchContext -> AppLaunchContext)
-> Ptr AppLaunchContext -> IO AppLaunchContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr AppLaunchContext -> AppLaunchContext
AppLaunchContext) Ptr AppLaunchContext
result
    AppLaunchContext -> IO AppLaunchContext
forall (m :: * -> *) a. Monad m => a -> m a
return AppLaunchContext
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_app_launch_context_get_display" g_app_launch_context_get_display :: 
    Ptr AppLaunchContext ->                 
    Ptr Gio.AppInfo.AppInfo ->              
    Ptr (GList (Ptr Gio.File.File)) ->      
    IO CString
appLaunchContextGetDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a, Gio.AppInfo.IsAppInfo b, Gio.File.IsFile c) =>
    a
    
    -> b
    
    -> [c]
    
    -> m T.Text
    
appLaunchContextGetDisplay :: a -> b -> [c] -> m Text
appLaunchContextGetDisplay a
context b
info [c]
files = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppLaunchContext
context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr AppInfo
info' <- b -> IO (Ptr AppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
info
    [Ptr File]
files' <- (c -> IO (Ptr File)) -> [c] -> IO [Ptr File]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM c -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr [c]
files
    Ptr (GList (Ptr File))
files'' <- [Ptr File] -> IO (Ptr (GList (Ptr File)))
forall a. [Ptr a] -> IO (Ptr (GList (Ptr a)))
packGList [Ptr File]
files'
    CString
result <- Ptr AppLaunchContext
-> Ptr AppInfo -> Ptr (GList (Ptr File)) -> IO CString
g_app_launch_context_get_display Ptr AppLaunchContext
context' Ptr AppInfo
info' Ptr (GList (Ptr File))
files''
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"appLaunchContextGetDisplay" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
info
    (c -> IO ()) -> [c] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [c]
files
    Ptr (GList (Ptr File)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr File))
files''
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data AppLaunchContextGetDisplayMethodInfo
instance (signature ~ (b -> [c] -> m T.Text), MonadIO m, IsAppLaunchContext a, Gio.AppInfo.IsAppInfo b, Gio.File.IsFile c) => O.MethodInfo AppLaunchContextGetDisplayMethodInfo a signature where
    overloadedMethod = appLaunchContextGetDisplay
#endif
foreign import ccall "g_app_launch_context_get_environment" g_app_launch_context_get_environment :: 
    Ptr AppLaunchContext ->                 
    IO (Ptr CString)
appLaunchContextGetEnvironment ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a) =>
    a
    
    -> m [[Char]]
    
    
appLaunchContextGetEnvironment :: a -> m [[Char]]
appLaunchContextGetEnvironment a
context = IO [[Char]] -> m [[Char]]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [[Char]] -> m [[Char]]) -> IO [[Char]] -> m [[Char]]
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppLaunchContext
context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr CString
result <- Ptr AppLaunchContext -> IO (Ptr CString)
g_app_launch_context_get_environment Ptr AppLaunchContext
context'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"appLaunchContextGetEnvironment" Ptr CString
result
    [[Char]]
result' <- HasCallStack => Ptr CString -> IO [[Char]]
Ptr CString -> IO [[Char]]
unpackZeroTerminatedFileNameArray Ptr CString
result
    (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    [[Char]] -> IO [[Char]]
forall (m :: * -> *) a. Monad m => a -> m a
return [[Char]]
result'
#if defined(ENABLE_OVERLOADING)
data AppLaunchContextGetEnvironmentMethodInfo
instance (signature ~ (m [[Char]]), MonadIO m, IsAppLaunchContext a) => O.MethodInfo AppLaunchContextGetEnvironmentMethodInfo a signature where
    overloadedMethod = appLaunchContextGetEnvironment
#endif
foreign import ccall "g_app_launch_context_get_startup_notify_id" g_app_launch_context_get_startup_notify_id :: 
    Ptr AppLaunchContext ->                 
    Ptr Gio.AppInfo.AppInfo ->              
    Ptr (GList (Ptr Gio.File.File)) ->      
    IO CString
appLaunchContextGetStartupNotifyId ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a, Gio.AppInfo.IsAppInfo b, Gio.File.IsFile c) =>
    a
    
    -> b
    
    -> [c]
    
    -> m T.Text
    
    
appLaunchContextGetStartupNotifyId :: a -> b -> [c] -> m Text
appLaunchContextGetStartupNotifyId a
context b
info [c]
files = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppLaunchContext
context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr AppInfo
info' <- b -> IO (Ptr AppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
info
    [Ptr File]
files' <- (c -> IO (Ptr File)) -> [c] -> IO [Ptr File]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM c -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr [c]
files
    Ptr (GList (Ptr File))
files'' <- [Ptr File] -> IO (Ptr (GList (Ptr File)))
forall a. [Ptr a] -> IO (Ptr (GList (Ptr a)))
packGList [Ptr File]
files'
    CString
result <- Ptr AppLaunchContext
-> Ptr AppInfo -> Ptr (GList (Ptr File)) -> IO CString
g_app_launch_context_get_startup_notify_id Ptr AppLaunchContext
context' Ptr AppInfo
info' Ptr (GList (Ptr File))
files''
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"appLaunchContextGetStartupNotifyId" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
info
    (c -> IO ()) -> [c] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [c]
files
    Ptr (GList (Ptr File)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr File))
files''
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data AppLaunchContextGetStartupNotifyIdMethodInfo
instance (signature ~ (b -> [c] -> m T.Text), MonadIO m, IsAppLaunchContext a, Gio.AppInfo.IsAppInfo b, Gio.File.IsFile c) => O.MethodInfo AppLaunchContextGetStartupNotifyIdMethodInfo a signature where
    overloadedMethod = appLaunchContextGetStartupNotifyId
#endif
foreign import ccall "g_app_launch_context_launch_failed" g_app_launch_context_launch_failed :: 
    Ptr AppLaunchContext ->                 
    CString ->                              
    IO ()
appLaunchContextLaunchFailed ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a) =>
    a
    
    -> T.Text
    
    -> m ()
appLaunchContextLaunchFailed :: a -> Text -> m ()
appLaunchContextLaunchFailed a
context Text
startupNotifyId = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppLaunchContext
context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CString
startupNotifyId' <- Text -> IO CString
textToCString Text
startupNotifyId
    Ptr AppLaunchContext -> CString -> IO ()
g_app_launch_context_launch_failed Ptr AppLaunchContext
context' CString
startupNotifyId'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
startupNotifyId'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AppLaunchContextLaunchFailedMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsAppLaunchContext a) => O.MethodInfo AppLaunchContextLaunchFailedMethodInfo a signature where
    overloadedMethod = appLaunchContextLaunchFailed
#endif
foreign import ccall "g_app_launch_context_setenv" g_app_launch_context_setenv :: 
    Ptr AppLaunchContext ->                 
    CString ->                              
    CString ->                              
    IO ()
appLaunchContextSetenv ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a) =>
    a
    
    -> [Char]
    
    -> [Char]
    
    -> m ()
appLaunchContextSetenv :: a -> [Char] -> [Char] -> m ()
appLaunchContextSetenv a
context [Char]
variable [Char]
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppLaunchContext
context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CString
variable' <- [Char] -> IO CString
stringToCString [Char]
variable
    CString
value' <- [Char] -> IO CString
stringToCString [Char]
value
    Ptr AppLaunchContext -> CString -> CString -> IO ()
g_app_launch_context_setenv Ptr AppLaunchContext
context' CString
variable' CString
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
variable'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AppLaunchContextSetenvMethodInfo
instance (signature ~ ([Char] -> [Char] -> m ()), MonadIO m, IsAppLaunchContext a) => O.MethodInfo AppLaunchContextSetenvMethodInfo a signature where
    overloadedMethod = appLaunchContextSetenv
#endif
foreign import ccall "g_app_launch_context_unsetenv" g_app_launch_context_unsetenv :: 
    Ptr AppLaunchContext ->                 
    CString ->                              
    IO ()
appLaunchContextUnsetenv ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a) =>
    a
    
    -> [Char]
    
    -> m ()
appLaunchContextUnsetenv :: a -> [Char] -> m ()
appLaunchContextUnsetenv a
context [Char]
variable = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppLaunchContext
context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CString
variable' <- [Char] -> IO CString
stringToCString [Char]
variable
    Ptr AppLaunchContext -> CString -> IO ()
g_app_launch_context_unsetenv Ptr AppLaunchContext
context' CString
variable'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
variable'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data AppLaunchContextUnsetenvMethodInfo
instance (signature ~ ([Char] -> m ()), MonadIO m, IsAppLaunchContext a) => O.MethodInfo AppLaunchContextUnsetenvMethodInfo a signature where
    overloadedMethod = appLaunchContextUnsetenv
#endif