{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Vte.Objects.Pty
    ( 

-- * Exported types
    Pty(..)                                 ,
    IsPty                                   ,
    toPty                                   ,


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

#if defined(ENABLE_OVERLOADING)
    ResolvePtyMethod                        ,
#endif


-- ** childSetup #method:childSetup#

#if defined(ENABLE_OVERLOADING)
    PtyChildSetupMethodInfo                 ,
#endif
    ptyChildSetup                           ,


-- ** close #method:close#

#if defined(ENABLE_OVERLOADING)
    PtyCloseMethodInfo                      ,
#endif
    ptyClose                                ,


-- ** getFd #method:getFd#

#if defined(ENABLE_OVERLOADING)
    PtyGetFdMethodInfo                      ,
#endif
    ptyGetFd                                ,


-- ** getSize #method:getSize#

#if defined(ENABLE_OVERLOADING)
    PtyGetSizeMethodInfo                    ,
#endif
    ptyGetSize                              ,


-- ** newForeignSync #method:newForeignSync#

    ptyNewForeignSync                       ,


-- ** newSync #method:newSync#

    ptyNewSync                              ,


-- ** setSize #method:setSize#

#if defined(ENABLE_OVERLOADING)
    PtySetSizeMethodInfo                    ,
#endif
    ptySetSize                              ,


-- ** setUtf8 #method:setUtf8#

#if defined(ENABLE_OVERLOADING)
    PtySetUtf8MethodInfo                    ,
#endif
    ptySetUtf8                              ,


-- ** spawnAsync #method:spawnAsync#

#if defined(ENABLE_OVERLOADING)
    PtySpawnAsyncMethodInfo                 ,
#endif
    ptySpawnAsync                           ,


-- ** spawnFinish #method:spawnFinish#

#if defined(ENABLE_OVERLOADING)
    PtySpawnFinishMethodInfo                ,
#endif
    ptySpawnFinish                          ,




 -- * Properties
-- ** fd #attr:fd#
-- | The file descriptor of the PTY master.

#if defined(ENABLE_OVERLOADING)
    PtyFdPropertyInfo                       ,
#endif
    constructPtyFd                          ,
    getPtyFd                                ,
#if defined(ENABLE_OVERLOADING)
    ptyFd                                   ,
#endif


-- ** flags #attr:flags#
-- | Flags.

#if defined(ENABLE_OVERLOADING)
    PtyFlagsPropertyInfo                    ,
#endif
    constructPtyFlags                       ,
    getPtyFlags                             ,
#if defined(ENABLE_OVERLOADING)
    ptyFlags                                ,
#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.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.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Flags as GLib.Flags
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.Initable as Gio.Initable
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Vte.Flags as Vte.Flags

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

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

foreign import ccall "vte_pty_get_type"
    c_vte_pty_get_type :: IO B.Types.GType

instance B.Types.TypedObject Pty where
    glibType :: IO GType
glibType = IO GType
c_vte_pty_get_type

instance B.Types.GObject Pty

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

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

instance O.HasParentTypes Pty
type instance O.ParentTypes Pty = '[GObject.Object.Object, Gio.Initable.Initable]

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

#if defined(ENABLE_OVERLOADING)
type family ResolvePtyMethod (t :: Symbol) (o :: *) :: * where
    ResolvePtyMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePtyMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePtyMethod "childSetup" o = PtyChildSetupMethodInfo
    ResolvePtyMethod "close" o = PtyCloseMethodInfo
    ResolvePtyMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePtyMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePtyMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePtyMethod "init" o = Gio.Initable.InitableInitMethodInfo
    ResolvePtyMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePtyMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePtyMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePtyMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePtyMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePtyMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePtyMethod "spawnAsync" o = PtySpawnAsyncMethodInfo
    ResolvePtyMethod "spawnFinish" o = PtySpawnFinishMethodInfo
    ResolvePtyMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePtyMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePtyMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePtyMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePtyMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePtyMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePtyMethod "getFd" o = PtyGetFdMethodInfo
    ResolvePtyMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePtyMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePtyMethod "getSize" o = PtyGetSizeMethodInfo
    ResolvePtyMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePtyMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePtyMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePtyMethod "setSize" o = PtySetSizeMethodInfo
    ResolvePtyMethod "setUtf8" o = PtySetUtf8MethodInfo
    ResolvePtyMethod l o = O.MethodResolutionFailed l o

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

#endif

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

-- | Get the value of the “@fd@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pty #fd
-- @
getPtyFd :: (MonadIO m, IsPty o) => o -> m Int32
getPtyFd :: o -> m Int32
getPtyFd o
obj = 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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"fd"

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

#if defined(ENABLE_OVERLOADING)
data PtyFdPropertyInfo
instance AttrInfo PtyFdPropertyInfo where
    type AttrAllowedOps PtyFdPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PtyFdPropertyInfo = IsPty
    type AttrSetTypeConstraint PtyFdPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint PtyFdPropertyInfo = (~) Int32
    type AttrTransferType PtyFdPropertyInfo = Int32
    type AttrGetType PtyFdPropertyInfo = Int32
    type AttrLabel PtyFdPropertyInfo = "fd"
    type AttrOrigin PtyFdPropertyInfo = Pty
    attrGet = getPtyFd
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPtyFd
    attrClear = undefined
#endif

-- VVV Prop "flags"
   -- Type: TInterface (Name {namespace = "Vte", name = "PtyFlags"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pty #flags
-- @
getPtyFlags :: (MonadIO m, IsPty o) => o -> m [Vte.Flags.PtyFlags]
getPtyFlags :: o -> m [PtyFlags]
getPtyFlags o
obj = IO [PtyFlags] -> m [PtyFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [PtyFlags] -> m [PtyFlags]) -> IO [PtyFlags] -> m [PtyFlags]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [PtyFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"flags"

-- | Construct a `GValueConstruct` with valid value for the “@flags@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPtyFlags :: (IsPty o, MIO.MonadIO m) => [Vte.Flags.PtyFlags] -> m (GValueConstruct o)
constructPtyFlags :: [PtyFlags] -> m (GValueConstruct o)
constructPtyFlags [PtyFlags]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> [PtyFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"flags" [PtyFlags]
val

#if defined(ENABLE_OVERLOADING)
data PtyFlagsPropertyInfo
instance AttrInfo PtyFlagsPropertyInfo where
    type AttrAllowedOps PtyFlagsPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PtyFlagsPropertyInfo = IsPty
    type AttrSetTypeConstraint PtyFlagsPropertyInfo = (~) [Vte.Flags.PtyFlags]
    type AttrTransferTypeConstraint PtyFlagsPropertyInfo = (~) [Vte.Flags.PtyFlags]
    type AttrTransferType PtyFlagsPropertyInfo = [Vte.Flags.PtyFlags]
    type AttrGetType PtyFlagsPropertyInfo = [Vte.Flags.PtyFlags]
    type AttrLabel PtyFlagsPropertyInfo = "flags"
    type AttrOrigin PtyFlagsPropertyInfo = Pty
    attrGet = getPtyFlags
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructPtyFlags
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Pty
type instance O.AttributeList Pty = PtyAttributeList
type PtyAttributeList = ('[ '("fd", PtyFdPropertyInfo), '("flags", PtyFlagsPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
ptyFd :: AttrLabelProxy "fd"
ptyFd = AttrLabelProxy

ptyFlags :: AttrLabelProxy "flags"
ptyFlags = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Pty = PtySignalList
type PtySignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method Pty::new_foreign_sync
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "fd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a file descriptor to the PTY"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Vte" , name = "Pty" })
-- throws : True
-- Skip return : False

foreign import ccall "vte_pty_new_foreign_sync" vte_pty_new_foreign_sync :: 
    Int32 ->                                -- fd : TBasicType TInt
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Pty)

-- | Creates a new t'GI.Vte.Objects.Pty.Pty' for the PTY master /@fd@/.
-- 
-- No entry will be made in the lastlog, utmp or wtmp system files.
-- 
-- Note that the newly created t'GI.Vte.Objects.Pty.Pty' will take ownership of /@fd@/
-- and close it on finalize.
ptyNewForeignSync ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.Cancellable.IsCancellable a) =>
    Int32
    -- ^ /@fd@/: a file descriptor to the PTY
    -> Maybe (a)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable', or 'P.Nothing'
    -> m Pty
    -- ^ __Returns:__ a new t'GI.Vte.Objects.Pty.Pty' for /@fd@/, or 'P.Nothing' on error with /@error@/ filled in /(Can throw 'Data.GI.Base.GError.GError')/
ptyNewForeignSync :: Int32 -> Maybe a -> m Pty
ptyNewForeignSync Int32
fd Maybe a
cancellable = IO Pty -> m Pty
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pty -> m Pty) -> IO Pty -> m Pty
forall a b. (a -> b) -> a -> b
$ do
    Ptr Cancellable
maybeCancellable <- case Maybe a
cancellable of
        Maybe a
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just a
jCancellable -> do
            Ptr Cancellable
jCancellable' <- a -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO Pty -> IO () -> IO Pty
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pty
result <- (Ptr (Ptr GError) -> IO (Ptr Pty)) -> IO (Ptr Pty)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pty)) -> IO (Ptr Pty))
-> (Ptr (Ptr GError) -> IO (Ptr Pty)) -> IO (Ptr Pty)
forall a b. (a -> b) -> a -> b
$ Int32 -> Ptr Cancellable -> Ptr (Ptr GError) -> IO (Ptr Pty)
vte_pty_new_foreign_sync Int32
fd Ptr Cancellable
maybeCancellable
        Text -> Ptr Pty -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"ptyNewForeignSync" Ptr Pty
result
        Pty
result' <- ((ManagedPtr Pty -> Pty) -> Ptr Pty -> IO Pty
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pty -> Pty
Pty) Ptr Pty
result
        Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
cancellable a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Pty -> IO Pty
forall (m :: * -> *) a. Monad m => a -> m a
return Pty
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pty::new_sync
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Vte" , name = "PtyFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags from #VtePtyFlags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Vte" , name = "Pty" })
-- throws : True
-- Skip return : False

foreign import ccall "vte_pty_new_sync" vte_pty_new_sync :: 
    CUInt ->                                -- flags : TInterface (Name {namespace = "Vte", name = "PtyFlags"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Pty)

-- | Allocates a new pseudo-terminal.
-- 
-- You can later use @/fork()/@ or the 'GI.GLib.Functions.spawnAsync' family of functions
-- to start a process on the PTY.
-- 
-- If using @/fork()/@, you MUST call 'GI.Vte.Objects.Pty.ptyChildSetup' in the child.
-- 
-- If using 'GI.GLib.Functions.spawnAsync' and friends, you MUST either use
-- 'GI.Vte.Objects.Pty.ptyChildSetup' directly as the child setup function, or call
-- 'GI.Vte.Objects.Pty.ptyChildSetup' from your own child setup function supplied.
-- 
-- When using 'GI.Vte.Objects.Terminal.terminalSpawnSync' with a custom child setup
-- function, 'GI.Vte.Objects.Pty.ptyChildSetup' will be called before the supplied
-- function; you must not call it again.
-- 
-- Also, you MUST pass the 'GI.GLib.Flags.SpawnFlagsDoNotReapChild' flag.
-- 
-- Note that you should set the PTY\'s size using 'GI.Vte.Objects.Pty.ptySetSize' before
-- spawning the child process, so that the child process has the correct
-- size from the start instead of starting with a default size and then
-- shortly afterwards receiving a SIGWINCH signal. You should prefer
-- using 'GI.Vte.Objects.Terminal.terminalPtyNewSync' which does this automatically.
ptyNewSync ::
    (B.CallStack.HasCallStack, MonadIO m, Gio.Cancellable.IsCancellable a) =>
    [Vte.Flags.PtyFlags]
    -- ^ /@flags@/: flags from t'GI.Vte.Flags.PtyFlags'
    -> Maybe (a)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable', or 'P.Nothing'
    -> m Pty
    -- ^ __Returns:__ a new t'GI.Vte.Objects.Pty.Pty', or 'P.Nothing' on error with /@error@/ filled in /(Can throw 'Data.GI.Base.GError.GError')/
ptyNewSync :: [PtyFlags] -> Maybe a -> m Pty
ptyNewSync [PtyFlags]
flags Maybe a
cancellable = IO Pty -> m Pty
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pty -> m Pty) -> IO Pty -> m Pty
forall a b. (a -> b) -> a -> b
$ do
    let flags' :: CUInt
flags' = [PtyFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [PtyFlags]
flags
    Ptr Cancellable
maybeCancellable <- case Maybe a
cancellable of
        Maybe a
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just a
jCancellable -> do
            Ptr Cancellable
jCancellable' <- a -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO Pty -> IO () -> IO Pty
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Pty
result <- (Ptr (Ptr GError) -> IO (Ptr Pty)) -> IO (Ptr Pty)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Pty)) -> IO (Ptr Pty))
-> (Ptr (Ptr GError) -> IO (Ptr Pty)) -> IO (Ptr Pty)
forall a b. (a -> b) -> a -> b
$ CUInt -> Ptr Cancellable -> Ptr (Ptr GError) -> IO (Ptr Pty)
vte_pty_new_sync CUInt
flags' Ptr Cancellable
maybeCancellable
        Text -> Ptr Pty -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"ptyNewSync" Ptr Pty
result
        Pty
result' <- ((ManagedPtr Pty -> Pty) -> Ptr Pty -> IO Pty
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Pty -> Pty
Pty) Ptr Pty
result
        Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
cancellable a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Pty -> IO Pty
forall (m :: * -> *) a. Monad m => a -> m a
return Pty
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Pty::child_setup
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pty"
--           , argType = TInterface Name { namespace = "Vte" , name = "Pty" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #VtePty" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "vte_pty_child_setup" vte_pty_child_setup :: 
    Ptr Pty ->                              -- pty : TInterface (Name {namespace = "Vte", name = "Pty"})
    IO ()

-- | FIXMEchpe
ptyChildSetup ::
    (B.CallStack.HasCallStack, MonadIO m, IsPty a) =>
    a
    -- ^ /@pty@/: a t'GI.Vte.Objects.Pty.Pty'
    -> m ()
ptyChildSetup :: a -> m ()
ptyChildSetup a
pty = 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 Pty
pty' <- a -> IO (Ptr Pty)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pty
    Ptr Pty -> IO ()
vte_pty_child_setup Ptr Pty
pty'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pty
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PtyChildSetupMethodInfo
instance (signature ~ (m ()), MonadIO m, IsPty a) => O.MethodInfo PtyChildSetupMethodInfo a signature where
    overloadedMethod = ptyChildSetup

#endif

-- method Pty::close
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pty"
--           , argType = TInterface Name { namespace = "Vte" , name = "Pty" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #VtePty" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "vte_pty_close" vte_pty_close :: 
    Ptr Pty ->                              -- pty : TInterface (Name {namespace = "Vte", name = "Pty"})
    IO ()

{-# DEPRECATED ptyClose ["(Since version 0.42)"] #-}
-- | Since 0.42 this is a no-op.
ptyClose ::
    (B.CallStack.HasCallStack, MonadIO m, IsPty a) =>
    a
    -- ^ /@pty@/: a t'GI.Vte.Objects.Pty.Pty'
    -> m ()
ptyClose :: a -> m ()
ptyClose a
pty = 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 Pty
pty' <- a -> IO (Ptr Pty)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pty
    Ptr Pty -> IO ()
vte_pty_close Ptr Pty
pty'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pty
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PtyCloseMethodInfo
instance (signature ~ (m ()), MonadIO m, IsPty a) => O.MethodInfo PtyCloseMethodInfo a signature where
    overloadedMethod = ptyClose

#endif

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

foreign import ccall "vte_pty_get_fd" vte_pty_get_fd :: 
    Ptr Pty ->                              -- pty : TInterface (Name {namespace = "Vte", name = "Pty"})
    IO Int32

-- | /No description available in the introspection data./
ptyGetFd ::
    (B.CallStack.HasCallStack, MonadIO m, IsPty a) =>
    a
    -- ^ /@pty@/: a t'GI.Vte.Objects.Pty.Pty'
    -> m Int32
    -- ^ __Returns:__ the file descriptor of the PTY master in /@pty@/. The
    --   file descriptor belongs to /@pty@/ and must not be closed or have
    --   its flags changed
ptyGetFd :: a -> m Int32
ptyGetFd a
pty = 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 Pty
pty' <- a -> IO (Ptr Pty)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pty
    Int32
result <- Ptr Pty -> IO Int32
vte_pty_get_fd Ptr Pty
pty'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pty
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PtyGetFdMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPty a) => O.MethodInfo PtyGetFdMethodInfo a signature where
    overloadedMethod = ptyGetFd

#endif

-- method Pty::get_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pty"
--           , argType = TInterface Name { namespace = "Vte" , name = "Pty" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #VtePty" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rows"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a location to store the number of rows, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "columns"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a location to store the number of columns, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "vte_pty_get_size" vte_pty_get_size :: 
    Ptr Pty ->                              -- pty : TInterface (Name {namespace = "Vte", name = "Pty"})
    Ptr Int32 ->                            -- rows : TBasicType TInt
    Ptr Int32 ->                            -- columns : TBasicType TInt
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Reads the pseudo terminal\'s window size.
-- 
-- If getting the window size failed, /@error@/ will be set to a t'GI.GLib.Enums.IOError'.
ptyGetSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsPty a) =>
    a
    -- ^ /@pty@/: a t'GI.Vte.Objects.Pty.Pty'
    -> m ((Int32, Int32))
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
ptyGetSize :: a -> m (Int32, Int32)
ptyGetSize a
pty = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Pty
pty' <- a -> IO (Ptr Pty)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pty
    Ptr Int32
rows <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
columns <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    IO (Int32, Int32) -> IO () -> IO (Int32, Int32)
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 Pty -> Ptr Int32 -> Ptr Int32 -> Ptr (Ptr GError) -> IO CInt
vte_pty_get_size Ptr Pty
pty' Ptr Int32
rows Ptr Int32
columns
        Int32
rows' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
rows
        Int32
columns' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
columns
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pty
        Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
rows
        Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
columns
        (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
rows', Int32
columns')
     ) (do
        Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
rows
        Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
columns
     )

#if defined(ENABLE_OVERLOADING)
data PtyGetSizeMethodInfo
instance (signature ~ (m ((Int32, Int32))), MonadIO m, IsPty a) => O.MethodInfo PtyGetSizeMethodInfo a signature where
    overloadedMethod = ptyGetSize

#endif

-- method Pty::set_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pty"
--           , argType = TInterface Name { namespace = "Vte" , name = "Pty" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #VtePty" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rows"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the desired number of rows"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "columns"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the desired number of columns"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "vte_pty_set_size" vte_pty_set_size :: 
    Ptr Pty ->                              -- pty : TInterface (Name {namespace = "Vte", name = "Pty"})
    Int32 ->                                -- rows : TBasicType TInt
    Int32 ->                                -- columns : TBasicType TInt
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Attempts to resize the pseudo terminal\'s window size.  If successful, the
-- OS kernel will send @/SIGWINCH/@ to the child process group.
-- 
-- If setting the window size failed, /@error@/ will be set to a t'GI.GLib.Enums.IOError'.
ptySetSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsPty a) =>
    a
    -- ^ /@pty@/: a t'GI.Vte.Objects.Pty.Pty'
    -> Int32
    -- ^ /@rows@/: the desired number of rows
    -> Int32
    -- ^ /@columns@/: the desired number of columns
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
ptySetSize :: a -> Int32 -> Int32 -> m ()
ptySetSize a
pty Int32
rows Int32
columns = 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 Pty
pty' <- a -> IO (Ptr Pty)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pty
    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 Pty -> Int32 -> Int32 -> Ptr (Ptr GError) -> IO CInt
vte_pty_set_size Ptr Pty
pty' Int32
rows Int32
columns
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pty
        () -> 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 PtySetSizeMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsPty a) => O.MethodInfo PtySetSizeMethodInfo a signature where
    overloadedMethod = ptySetSize

#endif

-- method Pty::set_utf8
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pty"
--           , argType = TInterface Name { namespace = "Vte" , name = "Pty" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #VtePty" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "utf8"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether or not the pty is in UTF-8 mode"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "vte_pty_set_utf8" vte_pty_set_utf8 :: 
    Ptr Pty ->                              -- pty : TInterface (Name {namespace = "Vte", name = "Pty"})
    CInt ->                                 -- utf8 : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Tells the kernel whether the terminal is UTF-8 or not, in case it can make
-- use of the info.  Linux 2.6.5 or so defines IUTF8 to make the line
-- discipline do multibyte backspace correctly.
ptySetUtf8 ::
    (B.CallStack.HasCallStack, MonadIO m, IsPty a) =>
    a
    -- ^ /@pty@/: a t'GI.Vte.Objects.Pty.Pty'
    -> Bool
    -- ^ /@utf8@/: whether or not the pty is in UTF-8 mode
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
ptySetUtf8 :: a -> Bool -> m ()
ptySetUtf8 a
pty Bool
utf8 = 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 Pty
pty' <- a -> IO (Ptr Pty)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pty
    let utf8' :: CInt
utf8' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
utf8
    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 Pty -> CInt -> Ptr (Ptr GError) -> IO CInt
vte_pty_set_utf8 Ptr Pty
pty' CInt
utf8'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pty
        () -> 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 PtySetUtf8MethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPty a) => O.MethodInfo PtySetUtf8MethodInfo a signature where
    overloadedMethod = ptySetUtf8

#endif

-- method Pty::spawn_async
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pty"
--           , argType = TInterface Name { namespace = "Vte" , name = "Pty" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #VtePty" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "working_directory"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the name of a directory the command should start\n  in, or %NULL to use the current working directory"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "argv"
--           , argType = TCArray True (-1) (-1) (TBasicType TFileName)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "child's argument vector"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "envv"
--           , argType = TCArray True (-1) (-1) (TBasicType TFileName)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a list of environment\n  variables to be added to the environment before starting the process, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "spawn_flags"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "SpawnFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags from #GSpawnFlags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child_setup"
--           , argType =
--               TInterface
--                 Name { namespace = "GLib" , name = "SpawnChildSetupFunc" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an extra child setup function to run in the child just before exec(), or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 6
--           , argDestroy = 7
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child_setup_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data for @child_setup, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child_setup_data_destroy"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GDestroyNotify for @child_setup_data, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timeout"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a timeout value in ms, or -1 to wait indefinitely"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GCancellable, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeAsync
--           , argClosure = 11
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "vte_pty_spawn_async" vte_pty_spawn_async :: 
    Ptr Pty ->                              -- pty : TInterface (Name {namespace = "Vte", name = "Pty"})
    CString ->                              -- working_directory : TBasicType TUTF8
    Ptr CString ->                          -- argv : TCArray True (-1) (-1) (TBasicType TFileName)
    Ptr CString ->                          -- envv : TCArray True (-1) (-1) (TBasicType TFileName)
    CUInt ->                                -- spawn_flags : TInterface (Name {namespace = "GLib", name = "SpawnFlags"})
    FunPtr GLib.Callbacks.C_SpawnChildSetupFunc -> -- child_setup : TInterface (Name {namespace = "GLib", name = "SpawnChildSetupFunc"})
    Ptr () ->                               -- child_setup_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- child_setup_data_destroy : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    Int32 ->                                -- timeout : TBasicType TInt
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Starts the specified command under the pseudo-terminal /@pty@/.
-- The /@argv@/ and /@envv@/ lists should be 'P.Nothing'-terminated.
-- The \"TERM\" environment variable is automatically set to a default value,
-- but can be overridden from /@envv@/.
-- /@ptyFlags@/ controls logging the session to the specified system log files.
-- 
-- Note that 'GI.GLib.Flags.SpawnFlagsDoNotReapChild' will always be added to /@spawnFlags@/.
-- 
-- Note that all open file descriptors will be closed in the child. If you want
-- to keep some file descriptor open for use in the child process, you need to
-- use a child setup function that unsets the FD_CLOEXEC flag on that file
-- descriptor.
-- 
-- Beginning with 0.60, and on linux only, and unless 'GI.Vte.Constants.SPAWN_NO_SYSTEMD_SCOPE' is
-- passed in /@spawnFlags@/, the newly created child process will be moved to its own
-- systemd user scope; and if 'GI.Vte.Constants.SPAWN_REQUIRE_SYSTEMD_SCOPE' is passed, and creation
-- of the systemd user scope fails, the whole spawn will fail.
-- You can override the options used for the systemd user scope by
-- providing a systemd override file for \'vte-spawn-.scope\' unit. See man:systemd.unit(5)
-- for further information.
-- 
-- See @/vte_pty_new()/@, 'GI.GLib.Functions.spawnAsync' and 'GI.Vte.Objects.Terminal.terminalWatchChild' for more information.
-- 
-- /Since: 0.48/
ptySpawnAsync ::
    (B.CallStack.HasCallStack, MonadIO m, IsPty a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@pty@/: a t'GI.Vte.Objects.Pty.Pty'
    -> Maybe (T.Text)
    -- ^ /@workingDirectory@/: the name of a directory the command should start
    --   in, or 'P.Nothing' to use the current working directory
    -> [[Char]]
    -- ^ /@argv@/: child\'s argument vector
    -> Maybe ([[Char]])
    -- ^ /@envv@/: a list of environment
    --   variables to be added to the environment before starting the process, or 'P.Nothing'
    -> [GLib.Flags.SpawnFlags]
    -- ^ /@spawnFlags@/: flags from t'GI.GLib.Flags.SpawnFlags'
    -> Maybe (GLib.Callbacks.SpawnChildSetupFunc)
    -- ^ /@childSetup@/: an extra child setup function to run in the child just before @/exec()/@, or 'P.Nothing'
    -> Int32
    -- ^ /@timeout@/: a timeout value in ms, or -1 to wait indefinitely
    -> Maybe (b)
    -- ^ /@cancellable@/: a t'GI.Gio.Objects.Cancellable.Cancellable', or 'P.Nothing'
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -> m ()
ptySpawnAsync :: a
-> Maybe Text
-> [String]
-> Maybe [String]
-> [SpawnFlags]
-> Maybe (IO ())
-> Int32
-> Maybe b
-> Maybe AsyncReadyCallback
-> m ()
ptySpawnAsync a
pty Maybe Text
workingDirectory [String]
argv Maybe [String]
envv [SpawnFlags]
spawnFlags Maybe (IO ())
childSetup Int32
timeout Maybe b
cancellable 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 Pty
pty' <- a -> IO (Ptr Pty)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pty
    Ptr CChar
maybeWorkingDirectory <- case Maybe Text
workingDirectory of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jWorkingDirectory -> do
            Ptr CChar
jWorkingDirectory' <- Text -> IO (Ptr CChar)
textToCString Text
jWorkingDirectory
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jWorkingDirectory'
    Ptr (Ptr CChar)
argv' <- [String] -> IO (Ptr (Ptr CChar))
packZeroTerminatedFileNameArray [String]
argv
    Ptr (Ptr CChar)
maybeEnvv <- case Maybe [String]
envv of
        Maybe [String]
Nothing -> Ptr (Ptr CChar) -> IO (Ptr (Ptr CChar))
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr CChar)
forall a. Ptr a
nullPtr
        Just [String]
jEnvv -> do
            Ptr (Ptr CChar)
jEnvv' <- [String] -> IO (Ptr (Ptr CChar))
packZeroTerminatedFileNameArray [String]
jEnvv
            Ptr (Ptr CChar) -> IO (Ptr (Ptr CChar))
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr CChar)
jEnvv'
    let spawnFlags' :: CUInt
spawnFlags' = [SpawnFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [SpawnFlags]
spawnFlags
    FunPtr C_SpawnChildSetupFunc
maybeChildSetup <- case Maybe (IO ())
childSetup of
        Maybe (IO ())
Nothing -> FunPtr C_SpawnChildSetupFunc -> IO (FunPtr C_SpawnChildSetupFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_SpawnChildSetupFunc
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just IO ()
jChildSetup -> do
            Ptr (FunPtr C_SpawnChildSetupFunc)
ptrchildSetup <- IO (Ptr (FunPtr C_SpawnChildSetupFunc))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_SpawnChildSetupFunc))
            FunPtr C_SpawnChildSetupFunc
jChildSetup' <- C_SpawnChildSetupFunc -> IO (FunPtr C_SpawnChildSetupFunc)
GLib.Callbacks.mk_SpawnChildSetupFunc (Maybe (Ptr (FunPtr C_SpawnChildSetupFunc))
-> C_SpawnChildSetupFunc -> C_SpawnChildSetupFunc
GLib.Callbacks.wrap_SpawnChildSetupFunc (Ptr (FunPtr C_SpawnChildSetupFunc)
-> Maybe (Ptr (FunPtr C_SpawnChildSetupFunc))
forall a. a -> Maybe a
Just Ptr (FunPtr C_SpawnChildSetupFunc)
ptrchildSetup) (IO () -> C_SpawnChildSetupFunc
GLib.Callbacks.drop_closures_SpawnChildSetupFunc IO ()
jChildSetup))
            Ptr (FunPtr C_SpawnChildSetupFunc)
-> FunPtr C_SpawnChildSetupFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_SpawnChildSetupFunc)
ptrchildSetup FunPtr C_SpawnChildSetupFunc
jChildSetup'
            FunPtr C_SpawnChildSetupFunc -> IO (FunPtr C_SpawnChildSetupFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_SpawnChildSetupFunc
jChildSetup'
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just 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
        Maybe AsyncReadyCallback
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 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 childSetupData :: Ptr a
childSetupData = Ptr a
forall a. Ptr a
nullPtr
    let childSetupDataDestroy :: FunPtr a
childSetupDataDestroy = FunPtr a
forall a. FunPtr a
FP.nullFunPtr
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr Pty
-> Ptr CChar
-> Ptr (Ptr CChar)
-> Ptr (Ptr CChar)
-> CUInt
-> FunPtr C_SpawnChildSetupFunc
-> Ptr ()
-> FunPtr C_SpawnChildSetupFunc
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> C_SpawnChildSetupFunc
vte_pty_spawn_async Ptr Pty
pty' Ptr CChar
maybeWorkingDirectory Ptr (Ptr CChar)
argv' Ptr (Ptr CChar)
maybeEnvv CUInt
spawnFlags' FunPtr C_SpawnChildSetupFunc
maybeChildSetup Ptr ()
forall a. Ptr a
childSetupData FunPtr C_SpawnChildSetupFunc
forall a. FunPtr a
childSetupDataDestroy Int32
timeout Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pty
    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 CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeWorkingDirectory
    (Ptr CChar -> IO ()) -> Ptr (Ptr CChar) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
argv'
    Ptr (Ptr CChar) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
argv'
    (Ptr CChar -> IO ()) -> Ptr (Ptr CChar) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
maybeEnvv
    Ptr (Ptr CChar) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CChar)
maybeEnvv
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PtySpawnAsyncMethodInfo
instance (signature ~ (Maybe (T.Text) -> [[Char]] -> Maybe ([[Char]]) -> [GLib.Flags.SpawnFlags] -> Maybe (GLib.Callbacks.SpawnChildSetupFunc) -> Int32 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsPty a, Gio.Cancellable.IsCancellable b) => O.MethodInfo PtySpawnAsyncMethodInfo a signature where
    overloadedMethod = ptySpawnAsync

#endif

-- method Pty::spawn_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "pty"
--           , argType = TInterface Name { namespace = "Vte" , name = "Pty" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #VtePty" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncResult" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child_pid"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a location to store the child PID, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "vte_pty_spawn_finish" vte_pty_spawn_finish :: 
    Ptr Pty ->                              -- pty : TInterface (Name {namespace = "Vte", name = "Pty"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr Int32 ->                            -- child_pid : TBasicType TInt
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | /No description available in the introspection data./
-- 
-- /Since: 0.48/
ptySpawnFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsPty a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@pty@/: a t'GI.Vte.Objects.Pty.Pty'
    -> b
    -- ^ /@result@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'
    -> m (Int32)
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
ptySpawnFinish :: a -> b -> m Int32
ptySpawnFinish a
pty b
result_ = 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 Pty
pty' <- a -> IO (Ptr Pty)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
pty
    Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
    Ptr Int32
childPid <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    IO Int32 -> IO () -> IO Int32
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 Pty
-> Ptr AsyncResult -> Ptr Int32 -> Ptr (Ptr GError) -> IO CInt
vte_pty_spawn_finish Ptr Pty
pty' Ptr AsyncResult
result_' Ptr Int32
childPid
        Int32
childPid' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
childPid
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
pty
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
childPid
        Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
childPid'
     ) (do
        Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
childPid
     )

#if defined(ENABLE_OVERLOADING)
data PtySpawnFinishMethodInfo
instance (signature ~ (b -> m (Int32)), MonadIO m, IsPty a, Gio.AsyncResult.IsAsyncResult b) => O.MethodInfo PtySpawnFinishMethodInfo a signature where
    overloadedMethod = ptySpawnFinish

#endif