{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Base class for input stream implementations that perform some
-- kind of filtering operation on a base stream. Typical examples
-- of filtering operations are character set conversion, compression
-- and byte order flipping.

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

module GI.Gio.Objects.FilterInputStream
    ( 

-- * Exported types
    FilterInputStream(..)                   ,
    IsFilterInputStream                     ,
    toFilterInputStream                     ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [clearPending]("GI.Gio.Objects.InputStream#g:method:clearPending"), [close]("GI.Gio.Objects.InputStream#g:method:close"), [closeAsync]("GI.Gio.Objects.InputStream#g:method:closeAsync"), [closeFinish]("GI.Gio.Objects.InputStream#g:method:closeFinish"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hasPending]("GI.Gio.Objects.InputStream#g:method:hasPending"), [isClosed]("GI.Gio.Objects.InputStream#g:method:isClosed"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [read]("GI.Gio.Objects.InputStream#g:method:read"), [readAll]("GI.Gio.Objects.InputStream#g:method:readAll"), [readAllAsync]("GI.Gio.Objects.InputStream#g:method:readAllAsync"), [readAllFinish]("GI.Gio.Objects.InputStream#g:method:readAllFinish"), [readAsync]("GI.Gio.Objects.InputStream#g:method:readAsync"), [readBytes]("GI.Gio.Objects.InputStream#g:method:readBytes"), [readBytesAsync]("GI.Gio.Objects.InputStream#g:method:readBytesAsync"), [readBytesFinish]("GI.Gio.Objects.InputStream#g:method:readBytesFinish"), [readFinish]("GI.Gio.Objects.InputStream#g:method:readFinish"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [skip]("GI.Gio.Objects.InputStream#g:method:skip"), [skipAsync]("GI.Gio.Objects.InputStream#g:method:skipAsync"), [skipFinish]("GI.Gio.Objects.InputStream#g:method:skipFinish"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getBaseStream]("GI.Gio.Objects.FilterInputStream#g:method:getBaseStream"), [getCloseBaseStream]("GI.Gio.Objects.FilterInputStream#g:method:getCloseBaseStream"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setCloseBaseStream]("GI.Gio.Objects.FilterInputStream#g:method:setCloseBaseStream"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setPending]("GI.Gio.Objects.InputStream#g:method:setPending"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveFilterInputStreamMethod          ,
#endif

-- ** getBaseStream #method:getBaseStream#

#if defined(ENABLE_OVERLOADING)
    FilterInputStreamGetBaseStreamMethodInfo,
#endif
    filterInputStreamGetBaseStream          ,


-- ** getCloseBaseStream #method:getCloseBaseStream#

#if defined(ENABLE_OVERLOADING)
    FilterInputStreamGetCloseBaseStreamMethodInfo,
#endif
    filterInputStreamGetCloseBaseStream     ,


-- ** setCloseBaseStream #method:setCloseBaseStream#

#if defined(ENABLE_OVERLOADING)
    FilterInputStreamSetCloseBaseStreamMethodInfo,
#endif
    filterInputStreamSetCloseBaseStream     ,




 -- * Properties


-- ** baseStream #attr:baseStream#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    FilterInputStreamBaseStreamPropertyInfo ,
#endif
    constructFilterInputStreamBaseStream    ,
#if defined(ENABLE_OVERLOADING)
    filterInputStreamBaseStream             ,
#endif
    getFilterInputStreamBaseStream          ,


-- ** closeBaseStream #attr:closeBaseStream#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    FilterInputStreamCloseBaseStreamPropertyInfo,
#endif
    constructFilterInputStreamCloseBaseStream,
#if defined(ENABLE_OVERLOADING)
    filterInputStreamCloseBaseStream        ,
#endif
    getFilterInputStreamCloseBaseStream     ,
    setFilterInputStreamCloseBaseStream     ,




    ) 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.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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.Coerce as Coerce
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 GHC.Records as R

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

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

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

foreign import ccall "g_filter_input_stream_get_type"
    c_g_filter_input_stream_get_type :: IO B.Types.GType

instance B.Types.TypedObject FilterInputStream where
    glibType :: IO GType
glibType = IO GType
c_g_filter_input_stream_get_type

instance B.Types.GObject FilterInputStream

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

instance O.HasParentTypes FilterInputStream
type instance O.ParentTypes FilterInputStream = '[Gio.InputStream.InputStream, GObject.Object.Object]

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

-- | Convert 'FilterInputStream' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe FilterInputStream) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_filter_input_stream_get_type
    gvalueSet_ :: Ptr GValue -> Maybe FilterInputStream -> IO ()
gvalueSet_ Ptr GValue
gv Maybe FilterInputStream
P.Nothing = Ptr GValue -> Ptr FilterInputStream -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr FilterInputStream
forall a. Ptr a
FP.nullPtr :: FP.Ptr FilterInputStream)
    gvalueSet_ Ptr GValue
gv (P.Just FilterInputStream
obj) = FilterInputStream -> (Ptr FilterInputStream -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FilterInputStream
obj (Ptr GValue -> Ptr FilterInputStream -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe FilterInputStream)
gvalueGet_ Ptr GValue
gv = do
        Ptr FilterInputStream
ptr <- Ptr GValue -> IO (Ptr FilterInputStream)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr FilterInputStream)
        if Ptr FilterInputStream
ptr Ptr FilterInputStream -> Ptr FilterInputStream -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr FilterInputStream
forall a. Ptr a
FP.nullPtr
        then FilterInputStream -> Maybe FilterInputStream
forall a. a -> Maybe a
P.Just (FilterInputStream -> Maybe FilterInputStream)
-> IO FilterInputStream -> IO (Maybe FilterInputStream)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr FilterInputStream -> FilterInputStream)
-> Ptr FilterInputStream -> IO FilterInputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr FilterInputStream -> FilterInputStream
FilterInputStream Ptr FilterInputStream
ptr
        else Maybe FilterInputStream -> IO (Maybe FilterInputStream)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilterInputStream
forall a. Maybe a
P.Nothing
        
    

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

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveFilterInputStreamMethod t FilterInputStream, O.OverloadedMethod info FilterInputStream p, R.HasField t FilterInputStream p) => R.HasField t FilterInputStream p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveFilterInputStreamMethod t FilterInputStream, O.OverloadedMethodInfo info FilterInputStream) => OL.IsLabel t (O.MethodProxy info FilterInputStream) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "base-stream"
   -- Type: TInterface (Name {namespace = "Gio", name = "InputStream"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@base-stream@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' filterInputStream #baseStream
-- @
getFilterInputStreamBaseStream :: (MonadIO m, IsFilterInputStream o) => o -> m Gio.InputStream.InputStream
getFilterInputStreamBaseStream :: forall (m :: * -> *) o.
(MonadIO m, IsFilterInputStream o) =>
o -> m InputStream
getFilterInputStreamBaseStream o
obj = IO InputStream -> m InputStream
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO InputStream -> m InputStream)
-> IO InputStream -> m InputStream
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe InputStream) -> IO InputStream
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getFilterInputStreamBaseStream" (IO (Maybe InputStream) -> IO InputStream)
-> IO (Maybe InputStream) -> IO InputStream
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr InputStream -> InputStream)
-> IO (Maybe InputStream)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"base-stream" ManagedPtr InputStream -> InputStream
Gio.InputStream.InputStream

-- | Construct a `GValueConstruct` with valid value for the “@base-stream@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructFilterInputStreamBaseStream :: (IsFilterInputStream o, MIO.MonadIO m, Gio.InputStream.IsInputStream a) => a -> m (GValueConstruct o)
constructFilterInputStreamBaseStream :: forall o (m :: * -> *) a.
(IsFilterInputStream o, MonadIO m, IsInputStream a) =>
a -> m (GValueConstruct o)
constructFilterInputStreamBaseStream a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"base-stream" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data FilterInputStreamBaseStreamPropertyInfo
instance AttrInfo FilterInputStreamBaseStreamPropertyInfo where
    type AttrAllowedOps FilterInputStreamBaseStreamPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint FilterInputStreamBaseStreamPropertyInfo = IsFilterInputStream
    type AttrSetTypeConstraint FilterInputStreamBaseStreamPropertyInfo = Gio.InputStream.IsInputStream
    type AttrTransferTypeConstraint FilterInputStreamBaseStreamPropertyInfo = Gio.InputStream.IsInputStream
    type AttrTransferType FilterInputStreamBaseStreamPropertyInfo = Gio.InputStream.InputStream
    type AttrGetType FilterInputStreamBaseStreamPropertyInfo = Gio.InputStream.InputStream
    type AttrLabel FilterInputStreamBaseStreamPropertyInfo = "base-stream"
    type AttrOrigin FilterInputStreamBaseStreamPropertyInfo = FilterInputStream
    attrGet = getFilterInputStreamBaseStream
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gio.InputStream.InputStream v
    attrConstruct = constructFilterInputStreamBaseStream
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FilterInputStream.baseStream"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-FilterInputStream.html#g:attr:baseStream"
        })
#endif

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

-- | Get the value of the “@close-base-stream@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' filterInputStream #closeBaseStream
-- @
getFilterInputStreamCloseBaseStream :: (MonadIO m, IsFilterInputStream o) => o -> m Bool
getFilterInputStreamCloseBaseStream :: forall (m :: * -> *) o.
(MonadIO m, IsFilterInputStream o) =>
o -> m Bool
getFilterInputStreamCloseBaseStream o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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-base-stream"

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

-- | Construct a `GValueConstruct` with valid value for the “@close-base-stream@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructFilterInputStreamCloseBaseStream :: (IsFilterInputStream o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructFilterInputStreamCloseBaseStream :: forall o (m :: * -> *).
(IsFilterInputStream o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructFilterInputStreamCloseBaseStream Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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-base-stream" Bool
val

#if defined(ENABLE_OVERLOADING)
data FilterInputStreamCloseBaseStreamPropertyInfo
instance AttrInfo FilterInputStreamCloseBaseStreamPropertyInfo where
    type AttrAllowedOps FilterInputStreamCloseBaseStreamPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint FilterInputStreamCloseBaseStreamPropertyInfo = IsFilterInputStream
    type AttrSetTypeConstraint FilterInputStreamCloseBaseStreamPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint FilterInputStreamCloseBaseStreamPropertyInfo = (~) Bool
    type AttrTransferType FilterInputStreamCloseBaseStreamPropertyInfo = Bool
    type AttrGetType FilterInputStreamCloseBaseStreamPropertyInfo = Bool
    type AttrLabel FilterInputStreamCloseBaseStreamPropertyInfo = "close-base-stream"
    type AttrOrigin FilterInputStreamCloseBaseStreamPropertyInfo = FilterInputStream
    attrGet = getFilterInputStreamCloseBaseStream
    attrSet = setFilterInputStreamCloseBaseStream
    attrTransfer _ v = do
        return v
    attrConstruct = constructFilterInputStreamCloseBaseStream
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FilterInputStream.closeBaseStream"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-FilterInputStream.html#g:attr:closeBaseStream"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FilterInputStream
type instance O.AttributeList FilterInputStream = FilterInputStreamAttributeList
type FilterInputStreamAttributeList = ('[ '("baseStream", FilterInputStreamBaseStreamPropertyInfo), '("closeBaseStream", FilterInputStreamCloseBaseStreamPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
filterInputStreamBaseStream :: AttrLabelProxy "baseStream"
filterInputStreamBaseStream = AttrLabelProxy

filterInputStreamCloseBaseStream :: AttrLabelProxy "closeBaseStream"
filterInputStreamCloseBaseStream = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "g_filter_input_stream_get_base_stream" g_filter_input_stream_get_base_stream :: 
    Ptr FilterInputStream ->                -- stream : TInterface (Name {namespace = "Gio", name = "FilterInputStream"})
    IO (Ptr Gio.InputStream.InputStream)

-- | Gets the base stream for the filter stream.
filterInputStreamGetBaseStream ::
    (B.CallStack.HasCallStack, MonadIO m, IsFilterInputStream a) =>
    a
    -- ^ /@stream@/: a t'GI.Gio.Objects.FilterInputStream.FilterInputStream'.
    -> m Gio.InputStream.InputStream
    -- ^ __Returns:__ a t'GI.Gio.Objects.InputStream.InputStream'.
filterInputStreamGetBaseStream :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFilterInputStream a) =>
a -> m InputStream
filterInputStreamGetBaseStream a
stream = IO InputStream -> m InputStream
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputStream -> m InputStream)
-> IO InputStream -> m InputStream
forall a b. (a -> b) -> a -> b
$ do
    Ptr FilterInputStream
stream' <- a -> IO (Ptr FilterInputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    Ptr InputStream
result <- Ptr FilterInputStream -> IO (Ptr InputStream)
g_filter_input_stream_get_base_stream Ptr FilterInputStream
stream'
    Text -> Ptr InputStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"filterInputStreamGetBaseStream" Ptr InputStream
result
    InputStream
result' <- ((ManagedPtr InputStream -> InputStream)
-> Ptr InputStream -> IO InputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr InputStream -> InputStream
Gio.InputStream.InputStream) Ptr InputStream
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
    InputStream -> IO InputStream
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return InputStream
result'

#if defined(ENABLE_OVERLOADING)
data FilterInputStreamGetBaseStreamMethodInfo
instance (signature ~ (m Gio.InputStream.InputStream), MonadIO m, IsFilterInputStream a) => O.OverloadedMethod FilterInputStreamGetBaseStreamMethodInfo a signature where
    overloadedMethod = filterInputStreamGetBaseStream

instance O.OverloadedMethodInfo FilterInputStreamGetBaseStreamMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FilterInputStream.filterInputStreamGetBaseStream",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-FilterInputStream.html#v:filterInputStreamGetBaseStream"
        })


#endif

-- method FilterInputStream::get_close_base_stream
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FilterInputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFilterInputStream."
--                 , 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_filter_input_stream_get_close_base_stream" g_filter_input_stream_get_close_base_stream :: 
    Ptr FilterInputStream ->                -- stream : TInterface (Name {namespace = "Gio", name = "FilterInputStream"})
    IO CInt

-- | Returns whether the base stream will be closed when /@stream@/ is
-- closed.
filterInputStreamGetCloseBaseStream ::
    (B.CallStack.HasCallStack, MonadIO m, IsFilterInputStream a) =>
    a
    -- ^ /@stream@/: a t'GI.Gio.Objects.FilterInputStream.FilterInputStream'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the base stream will be closed.
filterInputStreamGetCloseBaseStream :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFilterInputStream a) =>
a -> m Bool
filterInputStreamGetCloseBaseStream a
stream = IO Bool -> m Bool
forall a. IO a -> m a
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 FilterInputStream
stream' <- a -> IO (Ptr FilterInputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    CInt
result <- Ptr FilterInputStream -> IO CInt
g_filter_input_stream_get_close_base_stream Ptr FilterInputStream
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data FilterInputStreamGetCloseBaseStreamMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsFilterInputStream a) => O.OverloadedMethod FilterInputStreamGetCloseBaseStreamMethodInfo a signature where
    overloadedMethod = filterInputStreamGetCloseBaseStream

instance O.OverloadedMethodInfo FilterInputStreamGetCloseBaseStreamMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FilterInputStream.filterInputStreamGetCloseBaseStream",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-FilterInputStream.html#v:filterInputStreamGetCloseBaseStream"
        })


#endif

-- method FilterInputStream::set_close_base_stream
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "stream"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FilterInputStream" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GFilterInputStream."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "close_base"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE to close the base stream."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Sets whether the base stream will be closed when /@stream@/ is closed.
filterInputStreamSetCloseBaseStream ::
    (B.CallStack.HasCallStack, MonadIO m, IsFilterInputStream a) =>
    a
    -- ^ /@stream@/: a t'GI.Gio.Objects.FilterInputStream.FilterInputStream'.
    -> Bool
    -- ^ /@closeBase@/: 'P.True' to close the base stream.
    -> m ()
filterInputStreamSetCloseBaseStream :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFilterInputStream a) =>
a -> Bool -> m ()
filterInputStreamSetCloseBaseStream a
stream Bool
closeBase = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr FilterInputStream
stream' <- a -> IO (Ptr FilterInputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
    let closeBase' :: CInt
closeBase' = (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
closeBase
    Ptr FilterInputStream -> CInt -> IO ()
g_filter_input_stream_set_close_base_stream Ptr FilterInputStream
stream' CInt
closeBase'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FilterInputStreamSetCloseBaseStreamMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsFilterInputStream a) => O.OverloadedMethod FilterInputStreamSetCloseBaseStreamMethodInfo a signature where
    overloadedMethod = filterInputStreamSetCloseBaseStream

instance O.OverloadedMethodInfo FilterInputStreamSetCloseBaseStreamMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.FilterInputStream.filterInputStreamSetCloseBaseStream",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Objects-FilterInputStream.html#v:filterInputStreamSetCloseBaseStream"
        })


#endif