{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.Subprocess
(
Subprocess(..) ,
IsSubprocess ,
toSubprocess ,
noSubprocess ,
#if defined(ENABLE_OVERLOADING)
ResolveSubprocessMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
SubprocessCommunicateMethodInfo ,
#endif
subprocessCommunicate ,
#if defined(ENABLE_OVERLOADING)
SubprocessCommunicateAsyncMethodInfo ,
#endif
subprocessCommunicateAsync ,
#if defined(ENABLE_OVERLOADING)
SubprocessCommunicateFinishMethodInfo ,
#endif
subprocessCommunicateFinish ,
#if defined(ENABLE_OVERLOADING)
SubprocessCommunicateUtf8MethodInfo ,
#endif
subprocessCommunicateUtf8 ,
#if defined(ENABLE_OVERLOADING)
SubprocessCommunicateUtf8AsyncMethodInfo,
#endif
subprocessCommunicateUtf8Async ,
#if defined(ENABLE_OVERLOADING)
SubprocessCommunicateUtf8FinishMethodInfo,
#endif
subprocessCommunicateUtf8Finish ,
#if defined(ENABLE_OVERLOADING)
SubprocessForceExitMethodInfo ,
#endif
subprocessForceExit ,
#if defined(ENABLE_OVERLOADING)
SubprocessGetExitStatusMethodInfo ,
#endif
subprocessGetExitStatus ,
#if defined(ENABLE_OVERLOADING)
SubprocessGetIdentifierMethodInfo ,
#endif
subprocessGetIdentifier ,
#if defined(ENABLE_OVERLOADING)
SubprocessGetIfExitedMethodInfo ,
#endif
subprocessGetIfExited ,
#if defined(ENABLE_OVERLOADING)
SubprocessGetIfSignaledMethodInfo ,
#endif
subprocessGetIfSignaled ,
#if defined(ENABLE_OVERLOADING)
SubprocessGetStatusMethodInfo ,
#endif
subprocessGetStatus ,
#if defined(ENABLE_OVERLOADING)
SubprocessGetStderrPipeMethodInfo ,
#endif
subprocessGetStderrPipe ,
#if defined(ENABLE_OVERLOADING)
SubprocessGetStdinPipeMethodInfo ,
#endif
subprocessGetStdinPipe ,
#if defined(ENABLE_OVERLOADING)
SubprocessGetStdoutPipeMethodInfo ,
#endif
subprocessGetStdoutPipe ,
#if defined(ENABLE_OVERLOADING)
SubprocessGetSuccessfulMethodInfo ,
#endif
subprocessGetSuccessful ,
#if defined(ENABLE_OVERLOADING)
SubprocessGetTermSigMethodInfo ,
#endif
subprocessGetTermSig ,
subprocessNew ,
#if defined(ENABLE_OVERLOADING)
SubprocessSendSignalMethodInfo ,
#endif
subprocessSendSignal ,
#if defined(ENABLE_OVERLOADING)
SubprocessWaitMethodInfo ,
#endif
subprocessWait ,
#if defined(ENABLE_OVERLOADING)
SubprocessWaitAsyncMethodInfo ,
#endif
subprocessWaitAsync ,
#if defined(ENABLE_OVERLOADING)
SubprocessWaitCheckMethodInfo ,
#endif
subprocessWaitCheck ,
#if defined(ENABLE_OVERLOADING)
SubprocessWaitCheckAsyncMethodInfo ,
#endif
subprocessWaitCheckAsync ,
#if defined(ENABLE_OVERLOADING)
SubprocessWaitCheckFinishMethodInfo ,
#endif
subprocessWaitCheckFinish ,
#if defined(ENABLE_OVERLOADING)
SubprocessWaitFinishMethodInfo ,
#endif
subprocessWaitFinish ,
#if defined(ENABLE_OVERLOADING)
SubprocessArgvPropertyInfo ,
#endif
constructSubprocessArgv ,
#if defined(ENABLE_OVERLOADING)
subprocessArgv ,
#endif
#if defined(ENABLE_OVERLOADING)
SubprocessFlagsPropertyInfo ,
#endif
constructSubprocessFlags ,
#if defined(ENABLE_OVERLOADING)
subprocessFlags ,
#endif
) 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.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 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.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Initable as Gio.Initable
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
newtype Subprocess = Subprocess (ManagedPtr Subprocess)
deriving (Subprocess -> Subprocess -> Bool
(Subprocess -> Subprocess -> Bool)
-> (Subprocess -> Subprocess -> Bool) -> Eq Subprocess
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Subprocess -> Subprocess -> Bool
$c/= :: Subprocess -> Subprocess -> Bool
== :: Subprocess -> Subprocess -> Bool
$c== :: Subprocess -> Subprocess -> Bool
Eq)
foreign import ccall "g_subprocess_get_type"
c_g_subprocess_get_type :: IO GType
instance GObject Subprocess where
gobjectType :: IO GType
gobjectType = IO GType
c_g_subprocess_get_type
instance B.GValue.IsGValue Subprocess where
toGValue :: Subprocess -> IO GValue
toGValue o :: Subprocess
o = do
GType
gtype <- IO GType
c_g_subprocess_get_type
Subprocess -> (Ptr Subprocess -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Subprocess
o (GType
-> (GValue -> Ptr Subprocess -> IO ())
-> Ptr Subprocess
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Subprocess -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO Subprocess
fromGValue gv :: GValue
gv = do
Ptr Subprocess
ptr <- GValue -> IO (Ptr Subprocess)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Subprocess)
(ManagedPtr Subprocess -> Subprocess)
-> Ptr Subprocess -> IO Subprocess
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Subprocess -> Subprocess
Subprocess Ptr Subprocess
ptr
class (GObject o, O.IsDescendantOf Subprocess o) => IsSubprocess o
instance (GObject o, O.IsDescendantOf Subprocess o) => IsSubprocess o
instance O.HasParentTypes Subprocess
type instance O.ParentTypes Subprocess = '[GObject.Object.Object, Gio.Initable.Initable]
toSubprocess :: (MonadIO m, IsSubprocess o) => o -> m Subprocess
toSubprocess :: o -> m Subprocess
toSubprocess = IO Subprocess -> m Subprocess
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Subprocess -> m Subprocess)
-> (o -> IO Subprocess) -> o -> m Subprocess
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Subprocess -> Subprocess) -> o -> IO Subprocess
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Subprocess -> Subprocess
Subprocess
noSubprocess :: Maybe Subprocess
noSubprocess :: Maybe Subprocess
noSubprocess = Maybe Subprocess
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveSubprocessMethod (t :: Symbol) (o :: *) :: * where
ResolveSubprocessMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveSubprocessMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveSubprocessMethod "communicate" o = SubprocessCommunicateMethodInfo
ResolveSubprocessMethod "communicateAsync" o = SubprocessCommunicateAsyncMethodInfo
ResolveSubprocessMethod "communicateFinish" o = SubprocessCommunicateFinishMethodInfo
ResolveSubprocessMethod "communicateUtf8" o = SubprocessCommunicateUtf8MethodInfo
ResolveSubprocessMethod "communicateUtf8Async" o = SubprocessCommunicateUtf8AsyncMethodInfo
ResolveSubprocessMethod "communicateUtf8Finish" o = SubprocessCommunicateUtf8FinishMethodInfo
ResolveSubprocessMethod "forceExit" o = SubprocessForceExitMethodInfo
ResolveSubprocessMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveSubprocessMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveSubprocessMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveSubprocessMethod "init" o = Gio.Initable.InitableInitMethodInfo
ResolveSubprocessMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveSubprocessMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveSubprocessMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveSubprocessMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveSubprocessMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveSubprocessMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveSubprocessMethod "sendSignal" o = SubprocessSendSignalMethodInfo
ResolveSubprocessMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveSubprocessMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveSubprocessMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveSubprocessMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveSubprocessMethod "wait" o = SubprocessWaitMethodInfo
ResolveSubprocessMethod "waitAsync" o = SubprocessWaitAsyncMethodInfo
ResolveSubprocessMethod "waitCheck" o = SubprocessWaitCheckMethodInfo
ResolveSubprocessMethod "waitCheckAsync" o = SubprocessWaitCheckAsyncMethodInfo
ResolveSubprocessMethod "waitCheckFinish" o = SubprocessWaitCheckFinishMethodInfo
ResolveSubprocessMethod "waitFinish" o = SubprocessWaitFinishMethodInfo
ResolveSubprocessMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveSubprocessMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveSubprocessMethod "getExitStatus" o = SubprocessGetExitStatusMethodInfo
ResolveSubprocessMethod "getIdentifier" o = SubprocessGetIdentifierMethodInfo
ResolveSubprocessMethod "getIfExited" o = SubprocessGetIfExitedMethodInfo
ResolveSubprocessMethod "getIfSignaled" o = SubprocessGetIfSignaledMethodInfo
ResolveSubprocessMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveSubprocessMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveSubprocessMethod "getStatus" o = SubprocessGetStatusMethodInfo
ResolveSubprocessMethod "getStderrPipe" o = SubprocessGetStderrPipeMethodInfo
ResolveSubprocessMethod "getStdinPipe" o = SubprocessGetStdinPipeMethodInfo
ResolveSubprocessMethod "getStdoutPipe" o = SubprocessGetStdoutPipeMethodInfo
ResolveSubprocessMethod "getSuccessful" o = SubprocessGetSuccessfulMethodInfo
ResolveSubprocessMethod "getTermSig" o = SubprocessGetTermSigMethodInfo
ResolveSubprocessMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveSubprocessMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveSubprocessMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveSubprocessMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSubprocessMethod t Subprocess, O.MethodInfo info Subprocess p) => OL.IsLabel t (Subprocess -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
constructSubprocessArgv :: (IsSubprocess o) => [T.Text] -> IO (GValueConstruct o)
constructSubprocessArgv :: [Text] -> IO (GValueConstruct o)
constructSubprocessArgv val :: [Text]
val = String -> Maybe [Text] -> IO (GValueConstruct o)
forall o. String -> Maybe [Text] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyStringArray "argv" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text]
val)
#if defined(ENABLE_OVERLOADING)
data SubprocessArgvPropertyInfo
instance AttrInfo SubprocessArgvPropertyInfo where
type AttrAllowedOps SubprocessArgvPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
type AttrBaseTypeConstraint SubprocessArgvPropertyInfo = IsSubprocess
type AttrSetTypeConstraint SubprocessArgvPropertyInfo = (~) [T.Text]
type AttrTransferTypeConstraint SubprocessArgvPropertyInfo = (~) [T.Text]
type AttrTransferType SubprocessArgvPropertyInfo = [T.Text]
type AttrGetType SubprocessArgvPropertyInfo = ()
type AttrLabel SubprocessArgvPropertyInfo = "argv"
type AttrOrigin SubprocessArgvPropertyInfo = Subprocess
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructSubprocessArgv
attrClear = undefined
#endif
constructSubprocessFlags :: (IsSubprocess o) => [Gio.Flags.SubprocessFlags] -> IO (GValueConstruct o)
constructSubprocessFlags :: [SubprocessFlags] -> IO (GValueConstruct o)
constructSubprocessFlags val :: [SubprocessFlags]
val = String -> [SubprocessFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags "flags" [SubprocessFlags]
val
#if defined(ENABLE_OVERLOADING)
data SubprocessFlagsPropertyInfo
instance AttrInfo SubprocessFlagsPropertyInfo where
type AttrAllowedOps SubprocessFlagsPropertyInfo = '[ 'AttrConstruct]
type AttrBaseTypeConstraint SubprocessFlagsPropertyInfo = IsSubprocess
type AttrSetTypeConstraint SubprocessFlagsPropertyInfo = (~) [Gio.Flags.SubprocessFlags]
type AttrTransferTypeConstraint SubprocessFlagsPropertyInfo = (~) [Gio.Flags.SubprocessFlags]
type AttrTransferType SubprocessFlagsPropertyInfo = [Gio.Flags.SubprocessFlags]
type AttrGetType SubprocessFlagsPropertyInfo = ()
type AttrLabel SubprocessFlagsPropertyInfo = "flags"
type AttrOrigin SubprocessFlagsPropertyInfo = Subprocess
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructSubprocessFlags
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Subprocess
type instance O.AttributeList Subprocess = SubprocessAttributeList
type SubprocessAttributeList = ('[ '("argv", SubprocessArgvPropertyInfo), '("flags", SubprocessFlagsPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
subprocessArgv :: AttrLabelProxy "argv"
subprocessArgv = AttrLabelProxy
subprocessFlags :: AttrLabelProxy "flags"
subprocessFlags = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Subprocess = SubprocessSignalList
type SubprocessSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_subprocess_newv" g_subprocess_newv ::
Ptr CString ->
CUInt ->
Ptr (Ptr GError) ->
IO (Ptr Subprocess)
subprocessNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
[[Char]]
-> [Gio.Flags.SubprocessFlags]
-> m Subprocess
subprocessNew :: [String] -> [SubprocessFlags] -> m Subprocess
subprocessNew argv :: [String]
argv flags :: [SubprocessFlags]
flags = IO Subprocess -> m Subprocess
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Subprocess -> m Subprocess) -> IO Subprocess -> m Subprocess
forall a b. (a -> b) -> a -> b
$ do
Ptr CString
argv' <- [String] -> IO (Ptr CString)
packZeroTerminatedFileNameArray [String]
argv
let flags' :: CUInt
flags' = [SubprocessFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [SubprocessFlags]
flags
IO Subprocess -> IO () -> IO Subprocess
forall a b. IO a -> IO b -> IO a
onException (do
Ptr Subprocess
result <- (Ptr (Ptr GError) -> IO (Ptr Subprocess)) -> IO (Ptr Subprocess)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Subprocess)) -> IO (Ptr Subprocess))
-> (Ptr (Ptr GError) -> IO (Ptr Subprocess)) -> IO (Ptr Subprocess)
forall a b. (a -> b) -> a -> b
$ Ptr CString -> CUInt -> Ptr (Ptr GError) -> IO (Ptr Subprocess)
g_subprocess_newv Ptr CString
argv' CUInt
flags'
Text -> Ptr Subprocess -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "subprocessNew" Ptr Subprocess
result
Subprocess
result' <- ((ManagedPtr Subprocess -> Subprocess)
-> Ptr Subprocess -> IO Subprocess
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Subprocess -> Subprocess
Subprocess) Ptr Subprocess
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
argv'
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
argv'
Subprocess -> IO Subprocess
forall (m :: * -> *) a. Monad m => a -> m a
return Subprocess
result'
) (do
(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
argv'
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
argv'
)
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_subprocess_communicate" g_subprocess_communicate ::
Ptr Subprocess ->
Ptr GLib.Bytes.Bytes ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GLib.Bytes.Bytes) ->
Ptr (Ptr GLib.Bytes.Bytes) ->
Ptr (Ptr GError) ->
IO CInt
subprocessCommunicate ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (GLib.Bytes.Bytes)
-> Maybe (b)
-> m ((Maybe GLib.Bytes.Bytes, Maybe GLib.Bytes.Bytes))
subprocessCommunicate :: a -> Maybe Bytes -> Maybe b -> m (Maybe Bytes, Maybe Bytes)
subprocessCommunicate subprocess :: a
subprocess stdinBuf :: Maybe Bytes
stdinBuf cancellable :: Maybe b
cancellable = IO (Maybe Bytes, Maybe Bytes) -> m (Maybe Bytes, Maybe Bytes)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Bytes, Maybe Bytes) -> m (Maybe Bytes, Maybe Bytes))
-> IO (Maybe Bytes, Maybe Bytes) -> m (Maybe Bytes, Maybe Bytes)
forall a b. (a -> b) -> a -> b
$ do
Ptr Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr Bytes
maybeStdinBuf <- case Maybe Bytes
stdinBuf of
Nothing -> Ptr Bytes -> IO (Ptr Bytes)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Bytes
forall a. Ptr a
nullPtr
Just jStdinBuf :: Bytes
jStdinBuf -> do
Ptr Bytes
jStdinBuf' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
jStdinBuf
Ptr Bytes -> IO (Ptr Bytes)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Bytes
jStdinBuf'
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just jCancellable :: b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
Ptr (Ptr Bytes)
stdoutBuf <- IO (Ptr (Ptr Bytes))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr GLib.Bytes.Bytes))
Ptr (Ptr Bytes)
stderrBuf <- IO (Ptr (Ptr Bytes))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr GLib.Bytes.Bytes))
IO (Maybe Bytes, Maybe Bytes)
-> IO () -> IO (Maybe Bytes, Maybe Bytes)
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Subprocess
-> Ptr Bytes
-> Ptr Cancellable
-> Ptr (Ptr Bytes)
-> Ptr (Ptr Bytes)
-> Ptr (Ptr GError)
-> IO CInt
g_subprocess_communicate Ptr Subprocess
subprocess' Ptr Bytes
maybeStdinBuf Ptr Cancellable
maybeCancellable Ptr (Ptr Bytes)
stdoutBuf Ptr (Ptr Bytes)
stderrBuf
Ptr Bytes
stdoutBuf' <- Ptr (Ptr Bytes) -> IO (Ptr Bytes)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Bytes)
stdoutBuf
Maybe Bytes
maybeStdoutBuf' <- Ptr Bytes -> (Ptr Bytes -> IO Bytes) -> IO (Maybe Bytes)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Bytes
stdoutBuf' ((Ptr Bytes -> IO Bytes) -> IO (Maybe Bytes))
-> (Ptr Bytes -> IO Bytes) -> IO (Maybe Bytes)
forall a b. (a -> b) -> a -> b
$ \stdoutBuf'' :: Ptr Bytes
stdoutBuf'' -> do
Bytes
stdoutBuf''' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
stdoutBuf''
Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
stdoutBuf'''
Ptr Bytes
stderrBuf' <- Ptr (Ptr Bytes) -> IO (Ptr Bytes)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Bytes)
stderrBuf
Maybe Bytes
maybeStderrBuf' <- Ptr Bytes -> (Ptr Bytes -> IO Bytes) -> IO (Maybe Bytes)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Bytes
stderrBuf' ((Ptr Bytes -> IO Bytes) -> IO (Maybe Bytes))
-> (Ptr Bytes -> IO Bytes) -> IO (Maybe Bytes)
forall a b. (a -> b) -> a -> b
$ \stderrBuf'' :: Ptr Bytes
stderrBuf'' -> do
Bytes
stderrBuf''' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
stderrBuf''
Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
stderrBuf'''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Maybe Bytes -> (Bytes -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Bytes
stdinBuf Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Ptr (Ptr Bytes) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Bytes)
stdoutBuf
Ptr (Ptr Bytes) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Bytes)
stderrBuf
(Maybe Bytes, Maybe Bytes) -> IO (Maybe Bytes, Maybe Bytes)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Bytes
maybeStdoutBuf', Maybe Bytes
maybeStderrBuf')
) (do
Ptr (Ptr Bytes) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Bytes)
stdoutBuf
Ptr (Ptr Bytes) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Bytes)
stderrBuf
)
#if defined(ENABLE_OVERLOADING)
data SubprocessCommunicateMethodInfo
instance (signature ~ (Maybe (GLib.Bytes.Bytes) -> Maybe (b) -> m ((Maybe GLib.Bytes.Bytes, Maybe GLib.Bytes.Bytes))), MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SubprocessCommunicateMethodInfo a signature where
overloadedMethod = subprocessCommunicate
#endif
foreign import ccall "g_subprocess_communicate_async" g_subprocess_communicate_async ::
Ptr Subprocess ->
Ptr GLib.Bytes.Bytes ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
subprocessCommunicateAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (GLib.Bytes.Bytes)
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
subprocessCommunicateAsync :: a -> Maybe Bytes -> Maybe b -> Maybe AsyncReadyCallback -> m ()
subprocessCommunicateAsync subprocess :: a
subprocess stdinBuf :: Maybe Bytes
stdinBuf cancellable :: Maybe b
cancellable callback :: Maybe AsyncReadyCallback
callback = 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 Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr Bytes
maybeStdinBuf <- case Maybe Bytes
stdinBuf of
Nothing -> Ptr Bytes -> IO (Ptr Bytes)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Bytes
forall a. Ptr a
nullPtr
Just jStdinBuf :: Bytes
jStdinBuf -> do
Ptr Bytes
jStdinBuf' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
jStdinBuf
Ptr Bytes -> IO (Ptr Bytes)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Bytes
jStdinBuf'
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just jCancellable :: b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just jCallback :: AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr Subprocess
-> Ptr Bytes
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_subprocess_communicate_async Ptr Subprocess
subprocess' Ptr Bytes
maybeStdinBuf Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Maybe Bytes -> (Bytes -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Bytes
stdinBuf Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SubprocessCommunicateAsyncMethodInfo
instance (signature ~ (Maybe (GLib.Bytes.Bytes) -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SubprocessCommunicateAsyncMethodInfo a signature where
overloadedMethod = subprocessCommunicateAsync
#endif
foreign import ccall "g_subprocess_communicate_finish" g_subprocess_communicate_finish ::
Ptr Subprocess ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GLib.Bytes.Bytes) ->
Ptr (Ptr GLib.Bytes.Bytes) ->
Ptr (Ptr GError) ->
IO CInt
subprocessCommunicateFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ((Maybe GLib.Bytes.Bytes, Maybe GLib.Bytes.Bytes))
subprocessCommunicateFinish :: a -> b -> m (Maybe Bytes, Maybe Bytes)
subprocessCommunicateFinish subprocess :: a
subprocess result_ :: b
result_ = IO (Maybe Bytes, Maybe Bytes) -> m (Maybe Bytes, Maybe Bytes)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Bytes, Maybe Bytes) -> m (Maybe Bytes, Maybe Bytes))
-> IO (Maybe Bytes, Maybe Bytes) -> m (Maybe Bytes, Maybe Bytes)
forall a b. (a -> b) -> a -> b
$ do
Ptr Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
Ptr (Ptr Bytes)
stdoutBuf <- IO (Ptr (Ptr Bytes))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr GLib.Bytes.Bytes))
Ptr (Ptr Bytes)
stderrBuf <- IO (Ptr (Ptr Bytes))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr GLib.Bytes.Bytes))
IO (Maybe Bytes, Maybe Bytes)
-> IO () -> IO (Maybe Bytes, Maybe Bytes)
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Subprocess
-> Ptr AsyncResult
-> Ptr (Ptr Bytes)
-> Ptr (Ptr Bytes)
-> Ptr (Ptr GError)
-> IO CInt
g_subprocess_communicate_finish Ptr Subprocess
subprocess' Ptr AsyncResult
result_' Ptr (Ptr Bytes)
stdoutBuf Ptr (Ptr Bytes)
stderrBuf
Ptr Bytes
stdoutBuf' <- Ptr (Ptr Bytes) -> IO (Ptr Bytes)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Bytes)
stdoutBuf
Maybe Bytes
maybeStdoutBuf' <- Ptr Bytes -> (Ptr Bytes -> IO Bytes) -> IO (Maybe Bytes)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Bytes
stdoutBuf' ((Ptr Bytes -> IO Bytes) -> IO (Maybe Bytes))
-> (Ptr Bytes -> IO Bytes) -> IO (Maybe Bytes)
forall a b. (a -> b) -> a -> b
$ \stdoutBuf'' :: Ptr Bytes
stdoutBuf'' -> do
Bytes
stdoutBuf''' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
stdoutBuf''
Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
stdoutBuf'''
Ptr Bytes
stderrBuf' <- Ptr (Ptr Bytes) -> IO (Ptr Bytes)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Bytes)
stderrBuf
Maybe Bytes
maybeStderrBuf' <- Ptr Bytes -> (Ptr Bytes -> IO Bytes) -> IO (Maybe Bytes)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Bytes
stderrBuf' ((Ptr Bytes -> IO Bytes) -> IO (Maybe Bytes))
-> (Ptr Bytes -> IO Bytes) -> IO (Maybe Bytes)
forall a b. (a -> b) -> a -> b
$ \stderrBuf'' :: Ptr Bytes
stderrBuf'' -> do
Bytes
stderrBuf''' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
stderrBuf''
Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
stderrBuf'''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
Ptr (Ptr Bytes) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Bytes)
stdoutBuf
Ptr (Ptr Bytes) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Bytes)
stderrBuf
(Maybe Bytes, Maybe Bytes) -> IO (Maybe Bytes, Maybe Bytes)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Bytes
maybeStdoutBuf', Maybe Bytes
maybeStderrBuf')
) (do
Ptr (Ptr Bytes) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Bytes)
stdoutBuf
Ptr (Ptr Bytes) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Bytes)
stderrBuf
)
#if defined(ENABLE_OVERLOADING)
data SubprocessCommunicateFinishMethodInfo
instance (signature ~ (b -> m ((Maybe GLib.Bytes.Bytes, Maybe GLib.Bytes.Bytes))), MonadIO m, IsSubprocess a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo SubprocessCommunicateFinishMethodInfo a signature where
overloadedMethod = subprocessCommunicateFinish
#endif
foreign import ccall "g_subprocess_communicate_utf8" g_subprocess_communicate_utf8 ::
Ptr Subprocess ->
CString ->
Ptr Gio.Cancellable.Cancellable ->
Ptr CString ->
Ptr CString ->
Ptr (Ptr GError) ->
IO CInt
subprocessCommunicateUtf8 ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (T.Text)
-> Maybe (b)
-> m ((Maybe T.Text, Maybe T.Text))
subprocessCommunicateUtf8 :: a -> Maybe Text -> Maybe b -> m (Maybe Text, Maybe Text)
subprocessCommunicateUtf8 subprocess :: a
subprocess stdinBuf :: Maybe Text
stdinBuf cancellable :: Maybe b
cancellable = IO (Maybe Text, Maybe Text) -> m (Maybe Text, Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text, Maybe Text) -> m (Maybe Text, Maybe Text))
-> IO (Maybe Text, Maybe Text) -> m (Maybe Text, Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
Ptr Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
CString
maybeStdinBuf <- case Maybe Text
stdinBuf of
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just jStdinBuf :: Text
jStdinBuf -> do
CString
jStdinBuf' <- Text -> IO CString
textToCString Text
jStdinBuf
CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jStdinBuf'
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just jCancellable :: b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
Ptr CString
stdoutBuf <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CString)
Ptr CString
stderrBuf <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CString)
IO (Maybe Text, Maybe Text) -> IO () -> IO (Maybe Text, Maybe Text)
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Subprocess
-> CString
-> Ptr Cancellable
-> Ptr CString
-> Ptr CString
-> Ptr (Ptr GError)
-> IO CInt
g_subprocess_communicate_utf8 Ptr Subprocess
subprocess' CString
maybeStdinBuf Ptr Cancellable
maybeCancellable Ptr CString
stdoutBuf Ptr CString
stderrBuf
CString
stdoutBuf' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
stdoutBuf
Maybe Text
maybeStdoutBuf' <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
stdoutBuf' ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \stdoutBuf'' :: CString
stdoutBuf'' -> do
Text
stdoutBuf''' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
stdoutBuf''
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
stdoutBuf'''
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
stdoutBuf'
CString
stderrBuf' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
stderrBuf
Maybe Text
maybeStderrBuf' <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
stderrBuf' ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \stderrBuf'' :: CString
stderrBuf'' -> do
Text
stderrBuf''' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
stderrBuf''
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
stderrBuf'''
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
stderrBuf'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeStdinBuf
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
stdoutBuf
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
stderrBuf
(Maybe Text, Maybe Text) -> IO (Maybe Text, Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Text
maybeStdoutBuf', Maybe Text
maybeStderrBuf')
) (do
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeStdinBuf
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
stdoutBuf
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
stderrBuf
)
#if defined(ENABLE_OVERLOADING)
data SubprocessCommunicateUtf8MethodInfo
instance (signature ~ (Maybe (T.Text) -> Maybe (b) -> m ((Maybe T.Text, Maybe T.Text))), MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SubprocessCommunicateUtf8MethodInfo a signature where
overloadedMethod = subprocessCommunicateUtf8
#endif
foreign import ccall "g_subprocess_communicate_utf8_async" g_subprocess_communicate_utf8_async ::
Ptr Subprocess ->
CString ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
subprocessCommunicateUtf8Async ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (T.Text)
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
subprocessCommunicateUtf8Async :: a -> Maybe Text -> Maybe b -> Maybe AsyncReadyCallback -> m ()
subprocessCommunicateUtf8Async subprocess :: a
subprocess stdinBuf :: Maybe Text
stdinBuf cancellable :: Maybe b
cancellable callback :: Maybe AsyncReadyCallback
callback = 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 Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
CString
maybeStdinBuf <- case Maybe Text
stdinBuf of
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just jStdinBuf :: Text
jStdinBuf -> do
CString
jStdinBuf' <- Text -> IO CString
textToCString Text
jStdinBuf
CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jStdinBuf'
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just jCancellable :: b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just jCallback :: AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr Subprocess
-> CString
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_subprocess_communicate_utf8_async Ptr Subprocess
subprocess' CString
maybeStdinBuf Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeStdinBuf
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SubprocessCommunicateUtf8AsyncMethodInfo
instance (signature ~ (Maybe (T.Text) -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SubprocessCommunicateUtf8AsyncMethodInfo a signature where
overloadedMethod = subprocessCommunicateUtf8Async
#endif
foreign import ccall "g_subprocess_communicate_utf8_finish" g_subprocess_communicate_utf8_finish ::
Ptr Subprocess ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr CString ->
Ptr CString ->
Ptr (Ptr GError) ->
IO CInt
subprocessCommunicateUtf8Finish ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ((Maybe T.Text, Maybe T.Text))
subprocessCommunicateUtf8Finish :: a -> b -> m (Maybe Text, Maybe Text)
subprocessCommunicateUtf8Finish subprocess :: a
subprocess result_ :: b
result_ = IO (Maybe Text, Maybe Text) -> m (Maybe Text, Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text, Maybe Text) -> m (Maybe Text, Maybe Text))
-> IO (Maybe Text, Maybe Text) -> m (Maybe Text, Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
Ptr Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
Ptr CString
stdoutBuf <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CString)
Ptr CString
stderrBuf <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CString)
IO (Maybe Text, Maybe Text) -> IO () -> IO (Maybe Text, Maybe Text)
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Subprocess
-> Ptr AsyncResult
-> Ptr CString
-> Ptr CString
-> Ptr (Ptr GError)
-> IO CInt
g_subprocess_communicate_utf8_finish Ptr Subprocess
subprocess' Ptr AsyncResult
result_' Ptr CString
stdoutBuf Ptr CString
stderrBuf
CString
stdoutBuf' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
stdoutBuf
Maybe Text
maybeStdoutBuf' <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
stdoutBuf' ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \stdoutBuf'' :: CString
stdoutBuf'' -> do
Text
stdoutBuf''' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
stdoutBuf''
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
stdoutBuf'''
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
stdoutBuf'
CString
stderrBuf' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
stderrBuf
Maybe Text
maybeStderrBuf' <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
stderrBuf' ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \stderrBuf'' :: CString
stderrBuf'' -> do
Text
stderrBuf''' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
stderrBuf''
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
stderrBuf'''
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
stderrBuf'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
stdoutBuf
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
stderrBuf
(Maybe Text, Maybe Text) -> IO (Maybe Text, Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Text
maybeStdoutBuf', Maybe Text
maybeStderrBuf')
) (do
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
stdoutBuf
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
stderrBuf
)
#if defined(ENABLE_OVERLOADING)
data SubprocessCommunicateUtf8FinishMethodInfo
instance (signature ~ (b -> m ((Maybe T.Text, Maybe T.Text))), MonadIO m, IsSubprocess a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo SubprocessCommunicateUtf8FinishMethodInfo a signature where
overloadedMethod = subprocessCommunicateUtf8Finish
#endif
foreign import ccall "g_subprocess_force_exit" g_subprocess_force_exit ::
Ptr Subprocess ->
IO ()
subprocessForceExit ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a) =>
a
-> m ()
subprocessForceExit :: a -> m ()
subprocessForceExit subprocess :: a
subprocess = 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 Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr Subprocess -> IO ()
g_subprocess_force_exit Ptr Subprocess
subprocess'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SubprocessForceExitMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSubprocess a) => O.MethodInfo SubprocessForceExitMethodInfo a signature where
overloadedMethod = subprocessForceExit
#endif
foreign import ccall "g_subprocess_get_exit_status" g_subprocess_get_exit_status ::
Ptr Subprocess ->
IO Int32
subprocessGetExitStatus ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a) =>
a
-> m Int32
subprocessGetExitStatus :: a -> m Int32
subprocessGetExitStatus subprocess :: a
subprocess = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Int32
result <- Ptr Subprocess -> IO Int32
g_subprocess_get_exit_status Ptr Subprocess
subprocess'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data SubprocessGetExitStatusMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsSubprocess a) => O.MethodInfo SubprocessGetExitStatusMethodInfo a signature where
overloadedMethod = subprocessGetExitStatus
#endif
foreign import ccall "g_subprocess_get_identifier" g_subprocess_get_identifier ::
Ptr Subprocess ->
IO CString
subprocessGetIdentifier ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a) =>
a
-> m T.Text
subprocessGetIdentifier :: a -> m Text
subprocessGetIdentifier subprocess :: a
subprocess = 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 Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
CString
result <- Ptr Subprocess -> IO CString
g_subprocess_get_identifier Ptr Subprocess
subprocess'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "subprocessGetIdentifier" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data SubprocessGetIdentifierMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSubprocess a) => O.MethodInfo SubprocessGetIdentifierMethodInfo a signature where
overloadedMethod = subprocessGetIdentifier
#endif
foreign import ccall "g_subprocess_get_if_exited" g_subprocess_get_if_exited ::
Ptr Subprocess ->
IO CInt
subprocessGetIfExited ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a) =>
a
-> m Bool
subprocessGetIfExited :: a -> m Bool
subprocessGetIfExited subprocess :: a
subprocess = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
CInt
result <- Ptr Subprocess -> IO CInt
g_subprocess_get_if_exited Ptr Subprocess
subprocess'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SubprocessGetIfExitedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSubprocess a) => O.MethodInfo SubprocessGetIfExitedMethodInfo a signature where
overloadedMethod = subprocessGetIfExited
#endif
foreign import ccall "g_subprocess_get_if_signaled" g_subprocess_get_if_signaled ::
Ptr Subprocess ->
IO CInt
subprocessGetIfSignaled ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a) =>
a
-> m Bool
subprocessGetIfSignaled :: a -> m Bool
subprocessGetIfSignaled subprocess :: a
subprocess = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
CInt
result <- Ptr Subprocess -> IO CInt
g_subprocess_get_if_signaled Ptr Subprocess
subprocess'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SubprocessGetIfSignaledMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSubprocess a) => O.MethodInfo SubprocessGetIfSignaledMethodInfo a signature where
overloadedMethod = subprocessGetIfSignaled
#endif
foreign import ccall "g_subprocess_get_status" g_subprocess_get_status ::
Ptr Subprocess ->
IO Int32
subprocessGetStatus ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a) =>
a
-> m Int32
subprocessGetStatus :: a -> m Int32
subprocessGetStatus subprocess :: a
subprocess = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Int32
result <- Ptr Subprocess -> IO Int32
g_subprocess_get_status Ptr Subprocess
subprocess'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data SubprocessGetStatusMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsSubprocess a) => O.MethodInfo SubprocessGetStatusMethodInfo a signature where
overloadedMethod = subprocessGetStatus
#endif
foreign import ccall "g_subprocess_get_stderr_pipe" g_subprocess_get_stderr_pipe ::
Ptr Subprocess ->
IO (Ptr Gio.InputStream.InputStream)
subprocessGetStderrPipe ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a) =>
a
-> m Gio.InputStream.InputStream
subprocessGetStderrPipe :: a -> m InputStream
subprocessGetStderrPipe subprocess :: a
subprocess = IO InputStream -> m InputStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputStream -> m InputStream)
-> IO InputStream -> m InputStream
forall a b. (a -> b) -> a -> b
$ do
Ptr Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr InputStream
result <- Ptr Subprocess -> IO (Ptr InputStream)
g_subprocess_get_stderr_pipe Ptr Subprocess
subprocess'
Text -> Ptr InputStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "subprocessGetStderrPipe" Ptr InputStream
result
InputStream
result' <- ((ManagedPtr InputStream -> InputStream)
-> Ptr InputStream -> IO InputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr InputStream -> InputStream
Gio.InputStream.InputStream) Ptr InputStream
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
InputStream -> IO InputStream
forall (m :: * -> *) a. Monad m => a -> m a
return InputStream
result'
#if defined(ENABLE_OVERLOADING)
data SubprocessGetStderrPipeMethodInfo
instance (signature ~ (m Gio.InputStream.InputStream), MonadIO m, IsSubprocess a) => O.MethodInfo SubprocessGetStderrPipeMethodInfo a signature where
overloadedMethod = subprocessGetStderrPipe
#endif
foreign import ccall "g_subprocess_get_stdin_pipe" g_subprocess_get_stdin_pipe ::
Ptr Subprocess ->
IO (Ptr Gio.OutputStream.OutputStream)
subprocessGetStdinPipe ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a) =>
a
-> m Gio.OutputStream.OutputStream
subprocessGetStdinPipe :: a -> m OutputStream
subprocessGetStdinPipe subprocess :: a
subprocess = IO OutputStream -> m OutputStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO OutputStream -> m OutputStream)
-> IO OutputStream -> m OutputStream
forall a b. (a -> b) -> a -> b
$ do
Ptr Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr OutputStream
result <- Ptr Subprocess -> IO (Ptr OutputStream)
g_subprocess_get_stdin_pipe Ptr Subprocess
subprocess'
Text -> Ptr OutputStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "subprocessGetStdinPipe" Ptr OutputStream
result
OutputStream
result' <- ((ManagedPtr OutputStream -> OutputStream)
-> Ptr OutputStream -> IO OutputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr OutputStream -> OutputStream
Gio.OutputStream.OutputStream) Ptr OutputStream
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
OutputStream -> IO OutputStream
forall (m :: * -> *) a. Monad m => a -> m a
return OutputStream
result'
#if defined(ENABLE_OVERLOADING)
data SubprocessGetStdinPipeMethodInfo
instance (signature ~ (m Gio.OutputStream.OutputStream), MonadIO m, IsSubprocess a) => O.MethodInfo SubprocessGetStdinPipeMethodInfo a signature where
overloadedMethod = subprocessGetStdinPipe
#endif
foreign import ccall "g_subprocess_get_stdout_pipe" g_subprocess_get_stdout_pipe ::
Ptr Subprocess ->
IO (Ptr Gio.InputStream.InputStream)
subprocessGetStdoutPipe ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a) =>
a
-> m Gio.InputStream.InputStream
subprocessGetStdoutPipe :: a -> m InputStream
subprocessGetStdoutPipe subprocess :: a
subprocess = IO InputStream -> m InputStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputStream -> m InputStream)
-> IO InputStream -> m InputStream
forall a b. (a -> b) -> a -> b
$ do
Ptr Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr InputStream
result <- Ptr Subprocess -> IO (Ptr InputStream)
g_subprocess_get_stdout_pipe Ptr Subprocess
subprocess'
Text -> Ptr InputStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "subprocessGetStdoutPipe" Ptr InputStream
result
InputStream
result' <- ((ManagedPtr InputStream -> InputStream)
-> Ptr InputStream -> IO InputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr InputStream -> InputStream
Gio.InputStream.InputStream) Ptr InputStream
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
InputStream -> IO InputStream
forall (m :: * -> *) a. Monad m => a -> m a
return InputStream
result'
#if defined(ENABLE_OVERLOADING)
data SubprocessGetStdoutPipeMethodInfo
instance (signature ~ (m Gio.InputStream.InputStream), MonadIO m, IsSubprocess a) => O.MethodInfo SubprocessGetStdoutPipeMethodInfo a signature where
overloadedMethod = subprocessGetStdoutPipe
#endif
foreign import ccall "g_subprocess_get_successful" g_subprocess_get_successful ::
Ptr Subprocess ->
IO CInt
subprocessGetSuccessful ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a) =>
a
-> m Bool
subprocessGetSuccessful :: a -> m Bool
subprocessGetSuccessful subprocess :: a
subprocess = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
CInt
result <- Ptr Subprocess -> IO CInt
g_subprocess_get_successful Ptr Subprocess
subprocess'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SubprocessGetSuccessfulMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSubprocess a) => O.MethodInfo SubprocessGetSuccessfulMethodInfo a signature where
overloadedMethod = subprocessGetSuccessful
#endif
foreign import ccall "g_subprocess_get_term_sig" g_subprocess_get_term_sig ::
Ptr Subprocess ->
IO Int32
subprocessGetTermSig ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a) =>
a
-> m Int32
subprocessGetTermSig :: a -> m Int32
subprocessGetTermSig subprocess :: a
subprocess = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Int32
result <- Ptr Subprocess -> IO Int32
g_subprocess_get_term_sig Ptr Subprocess
subprocess'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data SubprocessGetTermSigMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsSubprocess a) => O.MethodInfo SubprocessGetTermSigMethodInfo a signature where
overloadedMethod = subprocessGetTermSig
#endif
foreign import ccall "g_subprocess_send_signal" g_subprocess_send_signal ::
Ptr Subprocess ->
Int32 ->
IO ()
subprocessSendSignal ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a) =>
a
-> Int32
-> m ()
subprocessSendSignal :: a -> Int32 -> m ()
subprocessSendSignal subprocess :: a
subprocess signalNum :: Int32
signalNum = 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 Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr Subprocess -> Int32 -> IO ()
g_subprocess_send_signal Ptr Subprocess
subprocess' Int32
signalNum
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SubprocessSendSignalMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsSubprocess a) => O.MethodInfo SubprocessSendSignalMethodInfo a signature where
overloadedMethod = subprocessSendSignal
#endif
foreign import ccall "g_subprocess_wait" g_subprocess_wait ::
Ptr Subprocess ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO CInt
subprocessWait ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> m ()
subprocessWait :: a -> Maybe b -> m ()
subprocessWait subprocess :: a
subprocess cancellable :: Maybe b
cancellable = 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 Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just jCancellable :: b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Subprocess -> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
g_subprocess_wait Ptr Subprocess
subprocess' Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SubprocessWaitMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SubprocessWaitMethodInfo a signature where
overloadedMethod = subprocessWait
#endif
foreign import ccall "g_subprocess_wait_async" g_subprocess_wait_async ::
Ptr Subprocess ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
subprocessWaitAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
subprocessWaitAsync :: a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
subprocessWaitAsync subprocess :: a
subprocess cancellable :: Maybe b
cancellable callback :: Maybe AsyncReadyCallback
callback = 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 Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just jCancellable :: b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just jCallback :: AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr Subprocess
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_subprocess_wait_async Ptr Subprocess
subprocess' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SubprocessWaitAsyncMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SubprocessWaitAsyncMethodInfo a signature where
overloadedMethod = subprocessWaitAsync
#endif
foreign import ccall "g_subprocess_wait_check" g_subprocess_wait_check ::
Ptr Subprocess ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO CInt
subprocessWaitCheck ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> m ()
subprocessWaitCheck :: a -> Maybe b -> m ()
subprocessWaitCheck subprocess :: a
subprocess cancellable :: Maybe b
cancellable = 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 Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just jCancellable :: b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Subprocess -> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
g_subprocess_wait_check Ptr Subprocess
subprocess' Ptr Cancellable
maybeCancellable
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SubprocessWaitCheckMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SubprocessWaitCheckMethodInfo a signature where
overloadedMethod = subprocessWaitCheck
#endif
foreign import ccall "g_subprocess_wait_check_async" g_subprocess_wait_check_async ::
Ptr Subprocess ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
subprocessWaitCheckAsync ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
subprocessWaitCheckAsync :: a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
subprocessWaitCheckAsync subprocess :: a
subprocess cancellable :: Maybe b
cancellable callback :: Maybe AsyncReadyCallback
callback = 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 Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
Just jCancellable :: b
jCancellable -> do
Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just jCallback :: AsyncReadyCallback
jCallback -> do
Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
Ptr Subprocess
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_subprocess_wait_check_async Ptr Subprocess
subprocess' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SubprocessWaitCheckAsyncMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsSubprocess a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SubprocessWaitCheckAsyncMethodInfo a signature where
overloadedMethod = subprocessWaitCheckAsync
#endif
foreign import ccall "g_subprocess_wait_check_finish" g_subprocess_wait_check_finish ::
Ptr Subprocess ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
subprocessWaitCheckFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
subprocessWaitCheckFinish :: a -> b -> m ()
subprocessWaitCheckFinish subprocess :: a
subprocess result_ :: b
result_ = 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 Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Subprocess -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_subprocess_wait_check_finish Ptr Subprocess
subprocess' Ptr AsyncResult
result_'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SubprocessWaitCheckFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsSubprocess a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo SubprocessWaitCheckFinishMethodInfo a signature where
overloadedMethod = subprocessWaitCheckFinish
#endif
foreign import ccall "g_subprocess_wait_finish" g_subprocess_wait_finish ::
Ptr Subprocess ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO CInt
subprocessWaitFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocess a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m ()
subprocessWaitFinish :: a -> b -> m ()
subprocessWaitFinish subprocess :: a
subprocess result_ :: b
result_ = 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 Subprocess
subprocess' <- a -> IO (Ptr Subprocess)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
subprocess
Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Subprocess -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
g_subprocess_wait_finish Ptr Subprocess
subprocess' Ptr AsyncResult
result_'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
subprocess
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SubprocessWaitFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsSubprocess a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo SubprocessWaitFinishMethodInfo a signature where
overloadedMethod = subprocessWaitFinish
#endif