{-# 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.UnixOutputStream.UnixOutputStream' implements t'GI.Gio.Objects.OutputStream.OutputStream' for writing to 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\/gunixoutputstream.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.UnixOutputStream
    ( 

-- * Exported types
    UnixOutputStream(..)                    ,
    IsUnixOutputStream                      ,
    toUnixOutputStream                      ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveUnixOutputStreamMethod           ,
#endif


-- ** getCloseFd #method:getCloseFd#

#if defined(ENABLE_OVERLOADING)
    UnixOutputStreamGetCloseFdMethodInfo    ,
#endif
    unixOutputStreamGetCloseFd              ,


-- ** getFd #method:getFd#

#if defined(ENABLE_OVERLOADING)
    UnixOutputStreamGetFdMethodInfo         ,
#endif
    unixOutputStreamGetFd                   ,


-- ** new #method:new#

    unixOutputStreamNew                     ,


-- ** setCloseFd #method:setCloseFd#

#if defined(ENABLE_OVERLOADING)
    UnixOutputStreamSetCloseFdMethodInfo    ,
#endif
    unixOutputStreamSetCloseFd              ,




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

#if defined(ENABLE_OVERLOADING)
    UnixOutputStreamCloseFdPropertyInfo     ,
#endif
    constructUnixOutputStreamCloseFd        ,
    getUnixOutputStreamCloseFd              ,
    setUnixOutputStreamCloseFd              ,
#if defined(ENABLE_OVERLOADING)
    unixOutputStreamCloseFd                 ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    UnixOutputStreamFdPropertyInfo          ,
#endif
    constructUnixOutputStreamFd             ,
    getUnixOutputStreamFd                   ,
#if defined(ENABLE_OVERLOADING)
    unixOutputStreamFd                      ,
#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.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.FileDescriptorBased as Gio.FileDescriptorBased
import {-# SOURCE #-} qualified GI.Gio.Interfaces.PollableOutputStream as Gio.PollableOutputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.OutputStream as Gio.OutputStream

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

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

foreign import ccall "g_unix_output_stream_get_type"
    c_g_unix_output_stream_get_type :: IO B.Types.GType

instance B.Types.TypedObject UnixOutputStream where
    glibType :: IO GType
glibType = IO GType
c_g_unix_output_stream_get_type

instance B.Types.GObject UnixOutputStream

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

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

instance O.HasParentTypes UnixOutputStream
type instance O.ParentTypes UnixOutputStream = '[Gio.OutputStream.OutputStream, GObject.Object.Object, Gio.FileDescriptorBased.FileDescriptorBased, Gio.PollableOutputStream.PollableOutputStream]

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

#if defined(ENABLE_OVERLOADING)
type family ResolveUnixOutputStreamMethod (t :: Symbol) (o :: *) :: * where
    ResolveUnixOutputStreamMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveUnixOutputStreamMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveUnixOutputStreamMethod "canPoll" o = Gio.PollableOutputStream.PollableOutputStreamCanPollMethodInfo
    ResolveUnixOutputStreamMethod "clearPending" o = Gio.OutputStream.OutputStreamClearPendingMethodInfo
    ResolveUnixOutputStreamMethod "close" o = Gio.OutputStream.OutputStreamCloseMethodInfo
    ResolveUnixOutputStreamMethod "closeAsync" o = Gio.OutputStream.OutputStreamCloseAsyncMethodInfo
    ResolveUnixOutputStreamMethod "closeFinish" o = Gio.OutputStream.OutputStreamCloseFinishMethodInfo
    ResolveUnixOutputStreamMethod "createSource" o = Gio.PollableOutputStream.PollableOutputStreamCreateSourceMethodInfo
    ResolveUnixOutputStreamMethod "flush" o = Gio.OutputStream.OutputStreamFlushMethodInfo
    ResolveUnixOutputStreamMethod "flushAsync" o = Gio.OutputStream.OutputStreamFlushAsyncMethodInfo
    ResolveUnixOutputStreamMethod "flushFinish" o = Gio.OutputStream.OutputStreamFlushFinishMethodInfo
    ResolveUnixOutputStreamMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveUnixOutputStreamMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveUnixOutputStreamMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveUnixOutputStreamMethod "hasPending" o = Gio.OutputStream.OutputStreamHasPendingMethodInfo
    ResolveUnixOutputStreamMethod "isClosed" o = Gio.OutputStream.OutputStreamIsClosedMethodInfo
    ResolveUnixOutputStreamMethod "isClosing" o = Gio.OutputStream.OutputStreamIsClosingMethodInfo
    ResolveUnixOutputStreamMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveUnixOutputStreamMethod "isWritable" o = Gio.PollableOutputStream.PollableOutputStreamIsWritableMethodInfo
    ResolveUnixOutputStreamMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveUnixOutputStreamMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveUnixOutputStreamMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveUnixOutputStreamMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveUnixOutputStreamMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveUnixOutputStreamMethod "splice" o = Gio.OutputStream.OutputStreamSpliceMethodInfo
    ResolveUnixOutputStreamMethod "spliceAsync" o = Gio.OutputStream.OutputStreamSpliceAsyncMethodInfo
    ResolveUnixOutputStreamMethod "spliceFinish" o = Gio.OutputStream.OutputStreamSpliceFinishMethodInfo
    ResolveUnixOutputStreamMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveUnixOutputStreamMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveUnixOutputStreamMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveUnixOutputStreamMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveUnixOutputStreamMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveUnixOutputStreamMethod "write" o = Gio.OutputStream.OutputStreamWriteMethodInfo
    ResolveUnixOutputStreamMethod "writeAll" o = Gio.OutputStream.OutputStreamWriteAllMethodInfo
    ResolveUnixOutputStreamMethod "writeAllAsync" o = Gio.OutputStream.OutputStreamWriteAllAsyncMethodInfo
    ResolveUnixOutputStreamMethod "writeAllFinish" o = Gio.OutputStream.OutputStreamWriteAllFinishMethodInfo
    ResolveUnixOutputStreamMethod "writeAsync" o = Gio.OutputStream.OutputStreamWriteAsyncMethodInfo
    ResolveUnixOutputStreamMethod "writeBytes" o = Gio.OutputStream.OutputStreamWriteBytesMethodInfo
    ResolveUnixOutputStreamMethod "writeBytesAsync" o = Gio.OutputStream.OutputStreamWriteBytesAsyncMethodInfo
    ResolveUnixOutputStreamMethod "writeBytesFinish" o = Gio.OutputStream.OutputStreamWriteBytesFinishMethodInfo
    ResolveUnixOutputStreamMethod "writeFinish" o = Gio.OutputStream.OutputStreamWriteFinishMethodInfo
    ResolveUnixOutputStreamMethod "writeNonblocking" o = Gio.PollableOutputStream.PollableOutputStreamWriteNonblockingMethodInfo
    ResolveUnixOutputStreamMethod "writev" o = Gio.OutputStream.OutputStreamWritevMethodInfo
    ResolveUnixOutputStreamMethod "writevAll" o = Gio.OutputStream.OutputStreamWritevAllMethodInfo
    ResolveUnixOutputStreamMethod "writevAllAsync" o = Gio.OutputStream.OutputStreamWritevAllAsyncMethodInfo
    ResolveUnixOutputStreamMethod "writevAllFinish" o = Gio.OutputStream.OutputStreamWritevAllFinishMethodInfo
    ResolveUnixOutputStreamMethod "writevAsync" o = Gio.OutputStream.OutputStreamWritevAsyncMethodInfo
    ResolveUnixOutputStreamMethod "writevFinish" o = Gio.OutputStream.OutputStreamWritevFinishMethodInfo
    ResolveUnixOutputStreamMethod "writevNonblocking" o = Gio.PollableOutputStream.PollableOutputStreamWritevNonblockingMethodInfo
    ResolveUnixOutputStreamMethod "getCloseFd" o = UnixOutputStreamGetCloseFdMethodInfo
    ResolveUnixOutputStreamMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveUnixOutputStreamMethod "getFd" o = UnixOutputStreamGetFdMethodInfo
    ResolveUnixOutputStreamMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveUnixOutputStreamMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveUnixOutputStreamMethod "setCloseFd" o = UnixOutputStreamSetCloseFdMethodInfo
    ResolveUnixOutputStreamMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveUnixOutputStreamMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveUnixOutputStreamMethod "setPending" o = Gio.OutputStream.OutputStreamSetPendingMethodInfo
    ResolveUnixOutputStreamMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveUnixOutputStreamMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveUnixOutputStreamMethod t UnixOutputStream, O.MethodInfo info UnixOutputStream p) => OL.IsLabel t (UnixOutputStream -> 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' unixOutputStream #closeFd
-- @
getUnixOutputStreamCloseFd :: (MonadIO m, IsUnixOutputStream o) => o -> m Bool
getUnixOutputStreamCloseFd :: o -> m Bool
getUnixOutputStreamCloseFd 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 String
"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' unixOutputStream [ #closeFd 'Data.GI.Base.Attributes.:=' value ]
-- @
setUnixOutputStreamCloseFd :: (MonadIO m, IsUnixOutputStream o) => o -> Bool -> m ()
setUnixOutputStreamCloseFd :: o -> Bool -> m ()
setUnixOutputStreamCloseFd o
obj 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 String
"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`.
constructUnixOutputStreamCloseFd :: (IsUnixOutputStream o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructUnixOutputStreamCloseFd :: Bool -> m (GValueConstruct o)
constructUnixOutputStreamCloseFd 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 String
"close-fd" Bool
val

#if defined(ENABLE_OVERLOADING)
data UnixOutputStreamCloseFdPropertyInfo
instance AttrInfo UnixOutputStreamCloseFdPropertyInfo where
    type AttrAllowedOps UnixOutputStreamCloseFdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint UnixOutputStreamCloseFdPropertyInfo = IsUnixOutputStream
    type AttrSetTypeConstraint UnixOutputStreamCloseFdPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint UnixOutputStreamCloseFdPropertyInfo = (~) Bool
    type AttrTransferType UnixOutputStreamCloseFdPropertyInfo = Bool
    type AttrGetType UnixOutputStreamCloseFdPropertyInfo = Bool
    type AttrLabel UnixOutputStreamCloseFdPropertyInfo = "close-fd"
    type AttrOrigin UnixOutputStreamCloseFdPropertyInfo = UnixOutputStream
    attrGet = getUnixOutputStreamCloseFd
    attrSet = setUnixOutputStreamCloseFd
    attrTransfer _ v = do
        return v
    attrConstruct = constructUnixOutputStreamCloseFd
    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' unixOutputStream #fd
-- @
getUnixOutputStreamFd :: (MonadIO m, IsUnixOutputStream o) => o -> m Int32
getUnixOutputStreamFd :: o -> m Int32
getUnixOutputStreamFd 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`.
constructUnixOutputStreamFd :: (IsUnixOutputStream o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructUnixOutputStreamFd :: Int32 -> m (GValueConstruct o)
constructUnixOutputStreamFd 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 UnixOutputStreamFdPropertyInfo
instance AttrInfo UnixOutputStreamFdPropertyInfo where
    type AttrAllowedOps UnixOutputStreamFdPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint UnixOutputStreamFdPropertyInfo = IsUnixOutputStream
    type AttrSetTypeConstraint UnixOutputStreamFdPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint UnixOutputStreamFdPropertyInfo = (~) Int32
    type AttrTransferType UnixOutputStreamFdPropertyInfo = Int32
    type AttrGetType UnixOutputStreamFdPropertyInfo = Int32
    type AttrLabel UnixOutputStreamFdPropertyInfo = "fd"
    type AttrOrigin UnixOutputStreamFdPropertyInfo = UnixOutputStream
    attrGet = getUnixOutputStreamFd
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructUnixOutputStreamFd
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList UnixOutputStream
type instance O.AttributeList UnixOutputStream = UnixOutputStreamAttributeList
type UnixOutputStreamAttributeList = ('[ '("closeFd", UnixOutputStreamCloseFdPropertyInfo), '("fd", UnixOutputStreamFdPropertyInfo)] :: [(Symbol, *)])
#endif

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

unixOutputStreamFd :: AttrLabelProxy "fd"
unixOutputStreamFd = AttrLabelProxy

#endif

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

#endif

-- method UnixOutputStream::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 = "UnixOutputStream" })
-- throws : False
-- Skip return : False

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

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

#if defined(ENABLE_OVERLOADING)
#endif

-- method UnixOutputStream::get_close_fd
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixOutputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GUnixOutputStream"
--                 , 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_output_stream_get_close_fd" g_unix_output_stream_get_close_fd :: 
    Ptr UnixOutputStream ->                 -- stream : TInterface (Name {namespace = "Gio", name = "UnixOutputStream"})
    IO CInt

-- | Returns whether the file descriptor of /@stream@/ will be
-- closed when the stream is closed.
-- 
-- /Since: 2.20/
unixOutputStreamGetCloseFd ::
    (B.CallStack.HasCallStack, MonadIO m, IsUnixOutputStream a) =>
    a
    -- ^ /@stream@/: a t'GI.Gio.Objects.UnixOutputStream.UnixOutputStream'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the file descriptor is closed when done
unixOutputStreamGetCloseFd :: a -> m Bool
unixOutputStreamGetCloseFd 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 UnixOutputStream
stream' <- a -> IO (Ptr UnixOutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    CInt
result <- Ptr UnixOutputStream -> IO CInt
g_unix_output_stream_get_close_fd Ptr UnixOutputStream
stream'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
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 UnixOutputStreamGetCloseFdMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsUnixOutputStream a) => O.MethodInfo UnixOutputStreamGetCloseFdMethodInfo a signature where
    overloadedMethod = unixOutputStreamGetCloseFd

#endif

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

-- | Return the UNIX file descriptor that the stream writes to.
-- 
-- /Since: 2.20/
unixOutputStreamGetFd ::
    (B.CallStack.HasCallStack, MonadIO m, IsUnixOutputStream a) =>
    a
    -- ^ /@stream@/: a t'GI.Gio.Objects.UnixOutputStream.UnixOutputStream'
    -> m Int32
    -- ^ __Returns:__ The file descriptor of /@stream@/
unixOutputStreamGetFd :: a -> m Int32
unixOutputStreamGetFd 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 UnixOutputStream
stream' <- a -> IO (Ptr UnixOutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    Int32
result <- Ptr UnixOutputStream -> IO Int32
g_unix_output_stream_get_fd Ptr UnixOutputStream
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 UnixOutputStreamGetFdMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsUnixOutputStream a) => O.MethodInfo UnixOutputStreamGetFdMethodInfo a signature where
    overloadedMethod = unixOutputStreamGetFd

#endif

-- method UnixOutputStream::set_close_fd
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "UnixOutputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GUnixOutputStream"
--                 , 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_output_stream_set_close_fd" g_unix_output_stream_set_close_fd :: 
    Ptr UnixOutputStream ->                 -- stream : TInterface (Name {namespace = "Gio", name = "UnixOutputStream"})
    CInt ->                                 -- close_fd : TBasicType TBoolean
    IO ()

-- | Sets whether the file descriptor of /@stream@/ shall be closed
-- when the stream is closed.
-- 
-- /Since: 2.20/
unixOutputStreamSetCloseFd ::
    (B.CallStack.HasCallStack, MonadIO m, IsUnixOutputStream a) =>
    a
    -- ^ /@stream@/: a t'GI.Gio.Objects.UnixOutputStream.UnixOutputStream'
    -> Bool
    -- ^ /@closeFd@/: 'P.True' to close the file descriptor when done
    -> m ()
unixOutputStreamSetCloseFd :: a -> Bool -> m ()
unixOutputStreamSetCloseFd a
stream 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 UnixOutputStream
stream' <- a -> IO (Ptr UnixOutputStream)
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 UnixOutputStream -> CInt -> IO ()
g_unix_output_stream_set_close_fd Ptr UnixOutputStream
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 UnixOutputStreamSetCloseFdMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsUnixOutputStream a) => O.MethodInfo UnixOutputStreamSetCloseFdMethodInfo a signature where
    overloadedMethod = unixOutputStreamSetCloseFd

#endif