{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Gio.Objects.UnixFDList.UnixFDList' contains a list of file descriptors.  It owns the file
-- descriptors that it contains, closing them when finalized.
-- 
-- It may be wrapped in a t'GI.Gio.Objects.UnixFDMessage.UnixFDMessage' and sent over a t'GI.Gio.Objects.Socket.Socket' in
-- the @/G_SOCKET_ADDRESS_UNIX/@ family by using 'GI.Gio.Objects.Socket.socketSendMessage'
-- and received using 'GI.Gio.Objects.Socket.socketReceiveMessage'.
-- 
-- Note that @\<gio\/gunixfdlist.h>@ belongs to the UNIX-specific GIO
-- interfaces, thus you have to use the @gio-unix-2.0.pc@ pkg-config
-- file when using it.

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

module GI.Gio.Objects.UnixFDList
    ( 

-- * Exported types
    UnixFDList(..)                          ,
    IsUnixFDList                            ,
    toUnixFDList                            ,
    noUnixFDList                            ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveUnixFDListMethod                 ,
#endif


-- ** append #method:append#

#if defined(ENABLE_OVERLOADING)
    UnixFDListAppendMethodInfo              ,
#endif
    unixFDListAppend                        ,


-- ** get #method:get#

#if defined(ENABLE_OVERLOADING)
    UnixFDListGetMethodInfo                 ,
#endif
    unixFDListGet                           ,


-- ** getLength #method:getLength#

#if defined(ENABLE_OVERLOADING)
    UnixFDListGetLengthMethodInfo           ,
#endif
    unixFDListGetLength                     ,


-- ** new #method:new#

    unixFDListNew                           ,


-- ** newFromArray #method:newFromArray#

    unixFDListNewFromArray                  ,


-- ** peekFds #method:peekFds#

#if defined(ENABLE_OVERLOADING)
    UnixFDListPeekFdsMethodInfo             ,
#endif
    unixFDListPeekFds                       ,


-- ** stealFds #method:stealFds#

#if defined(ENABLE_OVERLOADING)
    UnixFDListStealFdsMethodInfo            ,
#endif
    unixFDListStealFds                      ,




    ) 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.GObject.Objects.Object as GObject.Object

-- | Memory-managed wrapper type.
newtype UnixFDList = UnixFDList (ManagedPtr UnixFDList)
    deriving (UnixFDList -> UnixFDList -> Bool
(UnixFDList -> UnixFDList -> Bool)
-> (UnixFDList -> UnixFDList -> Bool) -> Eq UnixFDList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnixFDList -> UnixFDList -> Bool
$c/= :: UnixFDList -> UnixFDList -> Bool
== :: UnixFDList -> UnixFDList -> Bool
$c== :: UnixFDList -> UnixFDList -> Bool
Eq)
foreign import ccall "g_unix_fd_list_get_type"
    c_g_unix_fd_list_get_type :: IO GType

instance GObject UnixFDList where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_unix_fd_list_get_type
    

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

-- | Type class for types which can be safely cast to `UnixFDList`, for instance with `toUnixFDList`.
class (GObject o, O.IsDescendantOf UnixFDList o) => IsUnixFDList o
instance (GObject o, O.IsDescendantOf UnixFDList o) => IsUnixFDList o

instance O.HasParentTypes UnixFDList
type instance O.ParentTypes UnixFDList = '[GObject.Object.Object]

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

-- | A convenience alias for `Nothing` :: `Maybe` `UnixFDList`.
noUnixFDList :: Maybe UnixFDList
noUnixFDList :: Maybe UnixFDList
noUnixFDList = Maybe UnixFDList
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveUnixFDListMethod (t :: Symbol) (o :: *) :: * where
    ResolveUnixFDListMethod "append" o = UnixFDListAppendMethodInfo
    ResolveUnixFDListMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveUnixFDListMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveUnixFDListMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveUnixFDListMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveUnixFDListMethod "get" o = UnixFDListGetMethodInfo
    ResolveUnixFDListMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveUnixFDListMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveUnixFDListMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveUnixFDListMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveUnixFDListMethod "peekFds" o = UnixFDListPeekFdsMethodInfo
    ResolveUnixFDListMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveUnixFDListMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveUnixFDListMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveUnixFDListMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveUnixFDListMethod "stealFds" o = UnixFDListStealFdsMethodInfo
    ResolveUnixFDListMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveUnixFDListMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveUnixFDListMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveUnixFDListMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveUnixFDListMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveUnixFDListMethod "getLength" o = UnixFDListGetLengthMethodInfo
    ResolveUnixFDListMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveUnixFDListMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveUnixFDListMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveUnixFDListMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveUnixFDListMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveUnixFDListMethod l o = O.MethodResolutionFailed l o

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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList UnixFDList
type instance O.AttributeList UnixFDList = UnixFDListAttributeList
type UnixFDListAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method UnixFDList::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "UnixFDList" })
-- throws : False
-- Skip return : False

foreign import ccall "g_unix_fd_list_new" g_unix_fd_list_new :: 
    IO (Ptr UnixFDList)

-- | Creates a new t'GI.Gio.Objects.UnixFDList.UnixFDList' containing no file descriptors.
-- 
-- /Since: 2.24/
unixFDListNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m UnixFDList
    -- ^ __Returns:__ a new t'GI.Gio.Objects.UnixFDList.UnixFDList'
unixFDListNew :: m UnixFDList
unixFDListNew  = IO UnixFDList -> m UnixFDList
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UnixFDList -> m UnixFDList) -> IO UnixFDList -> m UnixFDList
forall a b. (a -> b) -> a -> b
$ do
    Ptr UnixFDList
result <- IO (Ptr UnixFDList)
g_unix_fd_list_new
    Text -> Ptr UnixFDList -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "unixFDListNew" Ptr UnixFDList
result
    UnixFDList
result' <- ((ManagedPtr UnixFDList -> UnixFDList)
-> Ptr UnixFDList -> IO UnixFDList
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr UnixFDList -> UnixFDList
UnixFDList) Ptr UnixFDList
result
    UnixFDList -> IO UnixFDList
forall (m :: * -> *) a. Monad m => a -> m a
return UnixFDList
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method UnixFDList::new_from_array
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "fds"
--           , argType = TCArray False (-1) 1 (TBasicType TInt)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the initial list of file descriptors"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_fds"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the length of #fds, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_fds"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the length of #fds, or -1"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "UnixFDList" })
-- throws : False
-- Skip return : False

foreign import ccall "g_unix_fd_list_new_from_array" g_unix_fd_list_new_from_array :: 
    Ptr Int32 ->                            -- fds : TCArray False (-1) 1 (TBasicType TInt)
    Int32 ->                                -- n_fds : TBasicType TInt
    IO (Ptr UnixFDList)

-- | Creates a new t'GI.Gio.Objects.UnixFDList.UnixFDList' containing the file descriptors given in
-- /@fds@/.  The file descriptors become the property of the new list and
-- may no longer be used by the caller.  The array itself is owned by
-- the caller.
-- 
-- Each file descriptor in the array should be set to close-on-exec.
-- 
-- If /@nFds@/ is -1 then /@fds@/ must be terminated with -1.
-- 
-- /Since: 2.24/
unixFDListNewFromArray ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Int32]
    -- ^ /@fds@/: the initial list of file descriptors
    -> m UnixFDList
    -- ^ __Returns:__ a new t'GI.Gio.Objects.UnixFDList.UnixFDList'
unixFDListNewFromArray :: [Int32] -> m UnixFDList
unixFDListNewFromArray fds :: [Int32]
fds = IO UnixFDList -> m UnixFDList
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UnixFDList -> m UnixFDList) -> IO UnixFDList -> m UnixFDList
forall a b. (a -> b) -> a -> b
$ do
    let nFds :: Int32
nFds = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [Int32] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int32]
fds
    Ptr Int32
fds' <- [Int32] -> IO (Ptr Int32)
forall a. Storable a => [a] -> IO (Ptr a)
packStorableArray [Int32]
fds
    Ptr UnixFDList
result <- Ptr Int32 -> Int32 -> IO (Ptr UnixFDList)
g_unix_fd_list_new_from_array Ptr Int32
fds' Int32
nFds
    Text -> Ptr UnixFDList -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "unixFDListNewFromArray" Ptr UnixFDList
result
    UnixFDList
result' <- ((ManagedPtr UnixFDList -> UnixFDList)
-> Ptr UnixFDList -> IO UnixFDList
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr UnixFDList -> UnixFDList
UnixFDList) Ptr UnixFDList
result
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
fds'
    UnixFDList -> IO UnixFDList
forall (m :: * -> *) a. Monad m => a -> m a
return UnixFDList
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method UnixFDList::append
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GUnixFDList" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a valid open file descriptor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : True
-- Skip return : False

foreign import ccall "g_unix_fd_list_append" g_unix_fd_list_append :: 
    Ptr UnixFDList ->                       -- list : TInterface (Name {namespace = "Gio", name = "UnixFDList"})
    Int32 ->                                -- fd : TBasicType TInt
    Ptr (Ptr GError) ->                     -- error
    IO Int32

-- | Adds a file descriptor to /@list@/.
-- 
-- The file descriptor is duplicated using @/dup()/@. You keep your copy
-- of the descriptor and the copy contained in /@list@/ will be closed
-- when /@list@/ is finalized.
-- 
-- A possible cause of failure is exceeding the per-process or
-- system-wide file descriptor limit.
-- 
-- The index of the file descriptor in the list is returned.  If you use
-- this index with 'GI.Gio.Objects.UnixFDList.unixFDListGet' then you will receive back a
-- duplicated copy of the same file descriptor.
-- 
-- /Since: 2.24/
unixFDListAppend ::
    (B.CallStack.HasCallStack, MonadIO m, IsUnixFDList a) =>
    a
    -- ^ /@list@/: a t'GI.Gio.Objects.UnixFDList.UnixFDList'
    -> Int32
    -- ^ /@fd@/: a valid open file descriptor
    -> m Int32
    -- ^ __Returns:__ the index of the appended fd in case of success, else -1
    --          (and /@error@/ is set) /(Can throw 'Data.GI.Base.GError.GError')/
unixFDListAppend :: a -> Int32 -> m Int32
unixFDListAppend list :: a
list fd :: Int32
fd = 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 UnixFDList
list' <- a -> IO (Ptr UnixFDList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
list
    IO Int32 -> IO () -> IO Int32
forall a b. IO a -> IO b -> IO a
onException (do
        Int32
result <- (Ptr (Ptr GError) -> IO Int32) -> IO Int32
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int32) -> IO Int32)
-> (Ptr (Ptr GError) -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ Ptr UnixFDList -> Int32 -> Ptr (Ptr GError) -> IO Int32
g_unix_fd_list_append Ptr UnixFDList
list' Int32
fd
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
list
        Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data UnixFDListAppendMethodInfo
instance (signature ~ (Int32 -> m Int32), MonadIO m, IsUnixFDList a) => O.MethodInfo UnixFDListAppendMethodInfo a signature where
    overloadedMethod = unixFDListAppend

#endif

-- method UnixFDList::get
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GUnixFDList" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index_"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the index into the list"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : True
-- Skip return : False

foreign import ccall "g_unix_fd_list_get" g_unix_fd_list_get :: 
    Ptr UnixFDList ->                       -- list : TInterface (Name {namespace = "Gio", name = "UnixFDList"})
    Int32 ->                                -- index_ : TBasicType TInt
    Ptr (Ptr GError) ->                     -- error
    IO Int32

-- | Gets a file descriptor out of /@list@/.
-- 
-- /@index_@/ specifies the index of the file descriptor to get.  It is a
-- programmer error for /@index_@/ to be out of range; see
-- 'GI.Gio.Objects.UnixFDList.unixFDListGetLength'.
-- 
-- The file descriptor is duplicated using @/dup()/@ and set as
-- close-on-exec before being returned.  You must call @/close()/@ on it
-- when you are done.
-- 
-- A possible cause of failure is exceeding the per-process or
-- system-wide file descriptor limit.
-- 
-- /Since: 2.24/
unixFDListGet ::
    (B.CallStack.HasCallStack, MonadIO m, IsUnixFDList a) =>
    a
    -- ^ /@list@/: a t'GI.Gio.Objects.UnixFDList.UnixFDList'
    -> Int32
    -- ^ /@index_@/: the index into the list
    -> m Int32
    -- ^ __Returns:__ the file descriptor, or -1 in case of error /(Can throw 'Data.GI.Base.GError.GError')/
unixFDListGet :: a -> Int32 -> m Int32
unixFDListGet list :: a
list index_ :: Int32
index_ = 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 UnixFDList
list' <- a -> IO (Ptr UnixFDList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
list
    IO Int32 -> IO () -> IO Int32
forall a b. IO a -> IO b -> IO a
onException (do
        Int32
result <- (Ptr (Ptr GError) -> IO Int32) -> IO Int32
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int32) -> IO Int32)
-> (Ptr (Ptr GError) -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ Ptr UnixFDList -> Int32 -> Ptr (Ptr GError) -> IO Int32
g_unix_fd_list_get Ptr UnixFDList
list' Int32
index_
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
list
        Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data UnixFDListGetMethodInfo
instance (signature ~ (Int32 -> m Int32), MonadIO m, IsUnixFDList a) => O.MethodInfo UnixFDListGetMethodInfo a signature where
    overloadedMethod = unixFDListGet

#endif

-- method UnixFDList::get_length
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GUnixFDList" , 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 "g_unix_fd_list_get_length" g_unix_fd_list_get_length :: 
    Ptr UnixFDList ->                       -- list : TInterface (Name {namespace = "Gio", name = "UnixFDList"})
    IO Int32

-- | Gets the length of /@list@/ (ie: the number of file descriptors
-- contained within).
-- 
-- /Since: 2.24/
unixFDListGetLength ::
    (B.CallStack.HasCallStack, MonadIO m, IsUnixFDList a) =>
    a
    -- ^ /@list@/: a t'GI.Gio.Objects.UnixFDList.UnixFDList'
    -> m Int32
    -- ^ __Returns:__ the length of /@list@/
unixFDListGetLength :: a -> m Int32
unixFDListGetLength list :: a
list = 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 UnixFDList
list' <- a -> IO (Ptr UnixFDList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
list
    Int32
result <- Ptr UnixFDList -> IO Int32
g_unix_fd_list_get_length Ptr UnixFDList
list'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
list
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data UnixFDListGetLengthMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsUnixFDList a) => O.MethodInfo UnixFDListGetLengthMethodInfo a signature where
    overloadedMethod = unixFDListGetLength

#endif

-- method UnixFDList::peek_fds
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GUnixFDList" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "pointer to the length of the returned\n    array, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "pointer to the length of the returned\n    array, or %NULL"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 1 (TBasicType TInt))
-- throws : False
-- Skip return : False

foreign import ccall "g_unix_fd_list_peek_fds" g_unix_fd_list_peek_fds :: 
    Ptr UnixFDList ->                       -- list : TInterface (Name {namespace = "Gio", name = "UnixFDList"})
    Ptr Int32 ->                            -- length : TBasicType TInt
    IO (Ptr Int32)

-- | Returns the array of file descriptors that is contained in this
-- object.
-- 
-- After this call, the descriptors remain the property of /@list@/.  The
-- caller must not close them and must not free the array.  The array is
-- valid only until /@list@/ is changed in any way.
-- 
-- If /@length@/ is non-'P.Nothing' then it is set to the number of file
-- descriptors in the returned array. The returned array is also
-- terminated with -1.
-- 
-- This function never returns 'P.Nothing'. In case there are no file
-- descriptors contained in /@list@/, an empty array is returned.
-- 
-- /Since: 2.24/
unixFDListPeekFds ::
    (B.CallStack.HasCallStack, MonadIO m, IsUnixFDList a) =>
    a
    -- ^ /@list@/: a t'GI.Gio.Objects.UnixFDList.UnixFDList'
    -> m [Int32]
    -- ^ __Returns:__ an array of file
    --     descriptors
unixFDListPeekFds :: a -> m [Int32]
unixFDListPeekFds list :: a
list = 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 UnixFDList
list' <- a -> IO (Ptr UnixFDList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
list
    Ptr Int32
length_ <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
result <- Ptr UnixFDList -> Ptr Int32 -> IO (Ptr Int32)
g_unix_fd_list_peek_fds Ptr UnixFDList
list' Ptr Int32
length_
    Int32
length_' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
length_
    Text -> Ptr Int32 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "unixFDListPeekFds" Ptr Int32
result
    [Int32]
result' <- (Int32 -> Ptr Int32 -> IO [Int32]
forall a b. (Integral a, Storable b) => a -> Ptr b -> IO [b]
unpackStorableArrayWithLength Int32
length_') Ptr Int32
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
list
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
length_
    [Int32] -> IO [Int32]
forall (m :: * -> *) a. Monad m => a -> m a
return [Int32]
result'

#if defined(ENABLE_OVERLOADING)
data UnixFDListPeekFdsMethodInfo
instance (signature ~ (m [Int32]), MonadIO m, IsUnixFDList a) => O.MethodInfo UnixFDListPeekFdsMethodInfo a signature where
    overloadedMethod = unixFDListPeekFds

#endif

-- method UnixFDList::steal_fds
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "list"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixFDList" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GUnixFDList" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "pointer to the length of the returned\n    array, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "pointer to the length of the returned\n    array, or %NULL"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 1 (TBasicType TInt))
-- throws : False
-- Skip return : False

foreign import ccall "g_unix_fd_list_steal_fds" g_unix_fd_list_steal_fds :: 
    Ptr UnixFDList ->                       -- list : TInterface (Name {namespace = "Gio", name = "UnixFDList"})
    Ptr Int32 ->                            -- length : TBasicType TInt
    IO (Ptr Int32)

-- | Returns the array of file descriptors that is contained in this
-- object.
-- 
-- After this call, the descriptors are no longer contained in
-- /@list@/. Further calls will return an empty list (unless more
-- descriptors have been added).
-- 
-- The return result of this function must be freed with 'GI.GLib.Functions.free'.
-- The caller is also responsible for closing all of the file
-- descriptors.  The file descriptors in the array are set to
-- close-on-exec.
-- 
-- If /@length@/ is non-'P.Nothing' then it is set to the number of file
-- descriptors in the returned array. The returned array is also
-- terminated with -1.
-- 
-- This function never returns 'P.Nothing'. In case there are no file
-- descriptors contained in /@list@/, an empty array is returned.
-- 
-- /Since: 2.24/
unixFDListStealFds ::
    (B.CallStack.HasCallStack, MonadIO m, IsUnixFDList a) =>
    a
    -- ^ /@list@/: a t'GI.Gio.Objects.UnixFDList.UnixFDList'
    -> m [Int32]
    -- ^ __Returns:__ an array of file
    --     descriptors
unixFDListStealFds :: a -> m [Int32]
unixFDListStealFds list :: a
list = 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 UnixFDList
list' <- a -> IO (Ptr UnixFDList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
list
    Ptr Int32
length_ <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
result <- Ptr UnixFDList -> Ptr Int32 -> IO (Ptr Int32)
g_unix_fd_list_steal_fds Ptr UnixFDList
list' Ptr Int32
length_
    Int32
length_' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
length_
    Text -> Ptr Int32 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "unixFDListStealFds" Ptr Int32
result
    [Int32]
result' <- (Int32 -> Ptr Int32 -> IO [Int32]
forall a b. (Integral a, Storable b) => a -> Ptr b -> IO [b]
unpackStorableArrayWithLength Int32
length_') Ptr Int32
result
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
list
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
length_
    [Int32] -> IO [Int32]
forall (m :: * -> *) a. Monad m => a -> m a
return [Int32]
result'

#if defined(ENABLE_OVERLOADING)
data UnixFDListStealFdsMethodInfo
instance (signature ~ (m [Int32]), MonadIO m, IsUnixFDList a) => O.MethodInfo UnixFDListStealFdsMethodInfo a signature where
    overloadedMethod = unixFDListStealFds

#endif