{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.UnixInputStream.UnixInputStream' implements t'GI.Gio.Objects.InputStream.InputStream' for reading from a UNIX
-- file descriptor, including asynchronous operations. (If the file
-- descriptor refers to a socket or pipe, this will use @/poll()/@ to do
-- asynchronous I\/O. If it refers to a regular file, it will fall back
-- to doing asynchronous I\/O in another thread.)
-- 
-- Note that @\<gio\/gunixinputstream.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.UnixInputStream
    ( 

-- * Exported types
    UnixInputStream(..)                     ,
    IsUnixInputStream                       ,
    toUnixInputStream                       ,
    noUnixInputStream                       ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveUnixInputStreamMethod            ,
#endif


-- ** getCloseFd #method:getCloseFd#

#if defined(ENABLE_OVERLOADING)
    UnixInputStreamGetCloseFdMethodInfo     ,
#endif
    unixInputStreamGetCloseFd               ,


-- ** getFd #method:getFd#

#if defined(ENABLE_OVERLOADING)
    UnixInputStreamGetFdMethodInfo          ,
#endif
    unixInputStreamGetFd                    ,


-- ** new #method:new#

    unixInputStreamNew                      ,


-- ** setCloseFd #method:setCloseFd#

#if defined(ENABLE_OVERLOADING)
    UnixInputStreamSetCloseFdMethodInfo     ,
#endif
    unixInputStreamSetCloseFd               ,




 -- * Properties
-- ** closeFd #attr:closeFd#
-- | Whether to close the file descriptor when the stream is closed.
-- 
-- /Since: 2.20/

#if defined(ENABLE_OVERLOADING)
    UnixInputStreamCloseFdPropertyInfo      ,
#endif
    constructUnixInputStreamCloseFd         ,
    getUnixInputStreamCloseFd               ,
    setUnixInputStreamCloseFd               ,
#if defined(ENABLE_OVERLOADING)
    unixInputStreamCloseFd                  ,
#endif


-- ** fd #attr:fd#
-- | The file descriptor that the stream reads from.
-- 
-- /Since: 2.20/

#if defined(ENABLE_OVERLOADING)
    UnixInputStreamFdPropertyInfo           ,
#endif
    constructUnixInputStreamFd              ,
    getUnixInputStreamFd                    ,
#if defined(ENABLE_OVERLOADING)
    unixInputStreamFd                       ,
#endif




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.FileDescriptorBased as Gio.FileDescriptorBased
import {-# SOURCE #-} qualified GI.Gio.Interfaces.PollableInputStream as Gio.PollableInputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream

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

instance GObject UnixInputStream where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_unix_input_stream_get_type
    

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

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

instance O.HasParentTypes UnixInputStream
type instance O.ParentTypes UnixInputStream = '[Gio.InputStream.InputStream, GObject.Object.Object, Gio.FileDescriptorBased.FileDescriptorBased, Gio.PollableInputStream.PollableInputStream]

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

-- | A convenience alias for `Nothing` :: `Maybe` `UnixInputStream`.
noUnixInputStream :: Maybe UnixInputStream
noUnixInputStream :: Maybe UnixInputStream
noUnixInputStream = Maybe UnixInputStream
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveUnixInputStreamMethod (t :: Symbol) (o :: *) :: * where
    ResolveUnixInputStreamMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveUnixInputStreamMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveUnixInputStreamMethod "canPoll" o = Gio.PollableInputStream.PollableInputStreamCanPollMethodInfo
    ResolveUnixInputStreamMethod "clearPending" o = Gio.InputStream.InputStreamClearPendingMethodInfo
    ResolveUnixInputStreamMethod "close" o = Gio.InputStream.InputStreamCloseMethodInfo
    ResolveUnixInputStreamMethod "closeAsync" o = Gio.InputStream.InputStreamCloseAsyncMethodInfo
    ResolveUnixInputStreamMethod "closeFinish" o = Gio.InputStream.InputStreamCloseFinishMethodInfo
    ResolveUnixInputStreamMethod "createSource" o = Gio.PollableInputStream.PollableInputStreamCreateSourceMethodInfo
    ResolveUnixInputStreamMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveUnixInputStreamMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveUnixInputStreamMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveUnixInputStreamMethod "hasPending" o = Gio.InputStream.InputStreamHasPendingMethodInfo
    ResolveUnixInputStreamMethod "isClosed" o = Gio.InputStream.InputStreamIsClosedMethodInfo
    ResolveUnixInputStreamMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveUnixInputStreamMethod "isReadable" o = Gio.PollableInputStream.PollableInputStreamIsReadableMethodInfo
    ResolveUnixInputStreamMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveUnixInputStreamMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveUnixInputStreamMethod "read" o = Gio.InputStream.InputStreamReadMethodInfo
    ResolveUnixInputStreamMethod "readAll" o = Gio.InputStream.InputStreamReadAllMethodInfo
    ResolveUnixInputStreamMethod "readAllAsync" o = Gio.InputStream.InputStreamReadAllAsyncMethodInfo
    ResolveUnixInputStreamMethod "readAllFinish" o = Gio.InputStream.InputStreamReadAllFinishMethodInfo
    ResolveUnixInputStreamMethod "readAsync" o = Gio.InputStream.InputStreamReadAsyncMethodInfo
    ResolveUnixInputStreamMethod "readBytes" o = Gio.InputStream.InputStreamReadBytesMethodInfo
    ResolveUnixInputStreamMethod "readBytesAsync" o = Gio.InputStream.InputStreamReadBytesAsyncMethodInfo
    ResolveUnixInputStreamMethod "readBytesFinish" o = Gio.InputStream.InputStreamReadBytesFinishMethodInfo
    ResolveUnixInputStreamMethod "readFinish" o = Gio.InputStream.InputStreamReadFinishMethodInfo
    ResolveUnixInputStreamMethod "readNonblocking" o = Gio.PollableInputStream.PollableInputStreamReadNonblockingMethodInfo
    ResolveUnixInputStreamMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveUnixInputStreamMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveUnixInputStreamMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveUnixInputStreamMethod "skip" o = Gio.InputStream.InputStreamSkipMethodInfo
    ResolveUnixInputStreamMethod "skipAsync" o = Gio.InputStream.InputStreamSkipAsyncMethodInfo
    ResolveUnixInputStreamMethod "skipFinish" o = Gio.InputStream.InputStreamSkipFinishMethodInfo
    ResolveUnixInputStreamMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveUnixInputStreamMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveUnixInputStreamMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveUnixInputStreamMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveUnixInputStreamMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveUnixInputStreamMethod "getCloseFd" o = UnixInputStreamGetCloseFdMethodInfo
    ResolveUnixInputStreamMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveUnixInputStreamMethod "getFd" o = UnixInputStreamGetFdMethodInfo
    ResolveUnixInputStreamMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveUnixInputStreamMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveUnixInputStreamMethod "setCloseFd" o = UnixInputStreamSetCloseFdMethodInfo
    ResolveUnixInputStreamMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveUnixInputStreamMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveUnixInputStreamMethod "setPending" o = Gio.InputStream.InputStreamSetPendingMethodInfo
    ResolveUnixInputStreamMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveUnixInputStreamMethod l o = O.MethodResolutionFailed l o

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

#endif

-- VVV Prop "close-fd"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@close-fd@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' unixInputStream #closeFd
-- @
getUnixInputStreamCloseFd :: (MonadIO m, IsUnixInputStream o) => o -> m Bool
getUnixInputStreamCloseFd :: o -> m Bool
getUnixInputStreamCloseFd obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "close-fd"

-- | Set the value of the “@close-fd@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' unixInputStream [ #closeFd 'Data.GI.Base.Attributes.:=' value ]
-- @
setUnixInputStreamCloseFd :: (MonadIO m, IsUnixInputStream o) => o -> Bool -> m ()
setUnixInputStreamCloseFd :: o -> Bool -> m ()
setUnixInputStreamCloseFd obj :: o
obj val :: Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj "close-fd" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@close-fd@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructUnixInputStreamCloseFd :: (IsUnixInputStream o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructUnixInputStreamCloseFd :: Bool -> m (GValueConstruct o)
constructUnixInputStreamCloseFd val :: Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "close-fd" Bool
val

#if defined(ENABLE_OVERLOADING)
data UnixInputStreamCloseFdPropertyInfo
instance AttrInfo UnixInputStreamCloseFdPropertyInfo where
    type AttrAllowedOps UnixInputStreamCloseFdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint UnixInputStreamCloseFdPropertyInfo = IsUnixInputStream
    type AttrSetTypeConstraint UnixInputStreamCloseFdPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint UnixInputStreamCloseFdPropertyInfo = (~) Bool
    type AttrTransferType UnixInputStreamCloseFdPropertyInfo = Bool
    type AttrGetType UnixInputStreamCloseFdPropertyInfo = Bool
    type AttrLabel UnixInputStreamCloseFdPropertyInfo = "close-fd"
    type AttrOrigin UnixInputStreamCloseFdPropertyInfo = UnixInputStream
    attrGet = getUnixInputStreamCloseFd
    attrSet = setUnixInputStreamCloseFd
    attrTransfer _ v = do
        return v
    attrConstruct = constructUnixInputStreamCloseFd
    attrClear = undefined
#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' unixInputStream #fd
-- @
getUnixInputStreamFd :: (MonadIO m, IsUnixInputStream o) => o -> m Int32
getUnixInputStreamFd :: o -> m Int32
getUnixInputStreamFd obj :: 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 "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`.
constructUnixInputStreamFd :: (IsUnixInputStream o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructUnixInputStreamFd :: Int32 -> m (GValueConstruct o)
constructUnixInputStreamFd val :: 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 "fd" Int32
val

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList UnixInputStream
type instance O.AttributeList UnixInputStream = UnixInputStreamAttributeList
type UnixInputStreamAttributeList = ('[ '("closeFd", UnixInputStreamCloseFdPropertyInfo), '("fd", UnixInputStreamFdPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
unixInputStreamCloseFd :: AttrLabelProxy "closeFd"
unixInputStreamCloseFd = AttrLabelProxy

unixInputStreamFd :: AttrLabelProxy "fd"
unixInputStreamFd = AttrLabelProxy

#endif

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

#endif

-- method UnixInputStream::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "fd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a UNIX file descriptor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "close_fd"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to close the file descriptor when done"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "UnixInputStream" })
-- throws : False
-- Skip return : False

foreign import ccall "g_unix_input_stream_new" g_unix_input_stream_new :: 
    Int32 ->                                -- fd : TBasicType TInt
    CInt ->                                 -- close_fd : TBasicType TBoolean
    IO (Ptr UnixInputStream)

-- | Creates a new t'GI.Gio.Objects.UnixInputStream.UnixInputStream' for the given /@fd@/.
-- 
-- If /@closeFd@/ is 'P.True', the file descriptor will be closed
-- when the stream is closed.
unixInputStreamNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Int32
    -- ^ /@fd@/: a UNIX file descriptor
    -> Bool
    -- ^ /@closeFd@/: 'P.True' to close the file descriptor when done
    -> m UnixInputStream
    -- ^ __Returns:__ a new t'GI.Gio.Objects.UnixInputStream.UnixInputStream'
unixInputStreamNew :: Int32 -> Bool -> m UnixInputStream
unixInputStreamNew fd :: Int32
fd closeFd :: Bool
closeFd = IO UnixInputStream -> m UnixInputStream
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO UnixInputStream -> m UnixInputStream)
-> IO UnixInputStream -> m UnixInputStream
forall a b. (a -> b) -> a -> b
$ do
    let closeFd' :: CInt
closeFd' = (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
closeFd
    Ptr UnixInputStream
result <- Int32 -> CInt -> IO (Ptr UnixInputStream)
g_unix_input_stream_new Int32
fd CInt
closeFd'
    Text -> Ptr UnixInputStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "unixInputStreamNew" Ptr UnixInputStream
result
    UnixInputStream
result' <- ((ManagedPtr UnixInputStream -> UnixInputStream)
-> Ptr UnixInputStream -> IO UnixInputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr UnixInputStream -> UnixInputStream
UnixInputStream) Ptr UnixInputStream
result
    UnixInputStream -> IO UnixInputStream
forall (m :: * -> *) a. Monad m => a -> m a
return UnixInputStream
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "g_unix_input_stream_get_close_fd" g_unix_input_stream_get_close_fd :: 
    Ptr UnixInputStream ->                  -- stream : TInterface (Name {namespace = "Gio", name = "UnixInputStream"})
    IO CInt

-- | Returns whether the file descriptor of /@stream@/ will be
-- closed when the stream is closed.
-- 
-- /Since: 2.20/
unixInputStreamGetCloseFd ::
    (B.CallStack.HasCallStack, MonadIO m, IsUnixInputStream a) =>
    a
    -- ^ /@stream@/: a t'GI.Gio.Objects.UnixInputStream.UnixInputStream'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the file descriptor is closed when done
unixInputStreamGetCloseFd :: a -> m Bool
unixInputStreamGetCloseFd stream :: a
stream = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr UnixInputStream
stream' <- a -> IO (Ptr UnixInputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    CInt
result <- Ptr UnixInputStream -> IO CInt
g_unix_input_stream_get_close_fd Ptr UnixInputStream
stream'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data UnixInputStreamGetCloseFdMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsUnixInputStream a) => O.MethodInfo UnixInputStreamGetCloseFdMethodInfo a signature where
    overloadedMethod = unixInputStreamGetCloseFd

#endif

-- method UnixInputStream::get_fd
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixInputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GUnixInputStream"
--                 , 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_input_stream_get_fd" g_unix_input_stream_get_fd :: 
    Ptr UnixInputStream ->                  -- stream : TInterface (Name {namespace = "Gio", name = "UnixInputStream"})
    IO Int32

-- | Return the UNIX file descriptor that the stream reads from.
-- 
-- /Since: 2.20/
unixInputStreamGetFd ::
    (B.CallStack.HasCallStack, MonadIO m, IsUnixInputStream a) =>
    a
    -- ^ /@stream@/: a t'GI.Gio.Objects.UnixInputStream.UnixInputStream'
    -> m Int32
    -- ^ __Returns:__ The file descriptor of /@stream@/
unixInputStreamGetFd :: a -> m Int32
unixInputStreamGetFd stream :: a
stream = 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 UnixInputStream
stream' <- a -> IO (Ptr UnixInputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    Int32
result <- Ptr UnixInputStream -> IO Int32
g_unix_input_stream_get_fd Ptr UnixInputStream
stream'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data UnixInputStreamGetFdMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsUnixInputStream a) => O.MethodInfo UnixInputStreamGetFdMethodInfo a signature where
    overloadedMethod = unixInputStreamGetFd

#endif

-- method UnixInputStream::set_close_fd
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixInputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GUnixInputStream"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "close_fd"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to close the file descriptor when done"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_unix_input_stream_set_close_fd" g_unix_input_stream_set_close_fd :: 
    Ptr UnixInputStream ->                  -- stream : TInterface (Name {namespace = "Gio", name = "UnixInputStream"})
    CInt ->                                 -- close_fd : TBasicType TBoolean
    IO ()

-- | Sets whether the file descriptor of /@stream@/ shall be closed
-- when the stream is closed.
-- 
-- /Since: 2.20/
unixInputStreamSetCloseFd ::
    (B.CallStack.HasCallStack, MonadIO m, IsUnixInputStream a) =>
    a
    -- ^ /@stream@/: a t'GI.Gio.Objects.UnixInputStream.UnixInputStream'
    -> Bool
    -- ^ /@closeFd@/: 'P.True' to close the file descriptor when done
    -> m ()
unixInputStreamSetCloseFd :: a -> Bool -> m ()
unixInputStreamSetCloseFd stream :: a
stream closeFd :: Bool
closeFd = 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 UnixInputStream
stream' <- a -> IO (Ptr UnixInputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    let closeFd' :: CInt
closeFd' = (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
closeFd
    Ptr UnixInputStream -> CInt -> IO ()
g_unix_input_stream_set_close_fd Ptr UnixInputStream
stream' CInt
closeFd'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data UnixInputStreamSetCloseFdMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsUnixInputStream a) => O.MethodInfo UnixInputStreamSetCloseFdMethodInfo a signature where
    overloadedMethod = unixInputStreamSetCloseFd

#endif