{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Zlib decompression

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

module GI.Gio.Objects.ZlibDecompressor
    ( 

-- * Exported types
    ZlibDecompressor(..)                    ,
    IsZlibDecompressor                      ,
    toZlibDecompressor                      ,


 -- * 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"), [convert]("GI.Gio.Interfaces.Converter#g:method:convert"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [reset]("GI.Gio.Interfaces.Converter#g:method:reset"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [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
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getFileInfo]("GI.Gio.Objects.ZlibDecompressor#g:method:getFileInfo"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveZlibDecompressorMethod           ,
#endif

-- ** getFileInfo #method:getFileInfo#

#if defined(ENABLE_OVERLOADING)
    ZlibDecompressorGetFileInfoMethodInfo   ,
#endif
    zlibDecompressorGetFileInfo             ,


-- ** new #method:new#

    zlibDecompressorNew                     ,




 -- * Properties


-- ** fileInfo #attr:fileInfo#
-- | A t'GI.Gio.Objects.FileInfo.FileInfo' containing the information found in the GZIP header
-- of the data stream processed, or 'P.Nothing' if the header was not yet
-- fully processed, is not present at all, or the compressor\'s
-- t'GI.Gio.Objects.ZlibDecompressor.ZlibDecompressor':@/format/@ property is not 'GI.Gio.Enums.ZlibCompressorFormatGzip'.
-- 
-- /Since: 2.26/

#if defined(ENABLE_OVERLOADING)
    ZlibDecompressorFileInfoPropertyInfo    ,
#endif
    getZlibDecompressorFileInfo             ,
#if defined(ENABLE_OVERLOADING)
    zlibDecompressorFileInfo                ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    ZlibDecompressorFormatPropertyInfo      ,
#endif
    constructZlibDecompressorFormat         ,
    getZlibDecompressorFormat               ,
#if defined(ENABLE_OVERLOADING)
    zlibDecompressorFormat                  ,
#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.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.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 GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Converter as Gio.Converter
import {-# SOURCE #-} qualified GI.Gio.Objects.FileInfo as Gio.FileInfo

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

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

foreign import ccall "g_zlib_decompressor_get_type"
    c_g_zlib_decompressor_get_type :: IO B.Types.GType

instance B.Types.TypedObject ZlibDecompressor where
    glibType :: IO GType
glibType = IO GType
c_g_zlib_decompressor_get_type

instance B.Types.GObject ZlibDecompressor

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

instance O.HasParentTypes ZlibDecompressor
type instance O.ParentTypes ZlibDecompressor = '[GObject.Object.Object, Gio.Converter.Converter]

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

-- | Convert 'ZlibDecompressor' 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 ZlibDecompressor) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_zlib_decompressor_get_type
    gvalueSet_ :: Ptr GValue -> Maybe ZlibDecompressor -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ZlibDecompressor
P.Nothing = Ptr GValue -> Ptr ZlibDecompressor -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr ZlibDecompressor
forall a. Ptr a
FP.nullPtr :: FP.Ptr ZlibDecompressor)
    gvalueSet_ Ptr GValue
gv (P.Just ZlibDecompressor
obj) = ZlibDecompressor -> (Ptr ZlibDecompressor -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ZlibDecompressor
obj (Ptr GValue -> Ptr ZlibDecompressor -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe ZlibDecompressor)
gvalueGet_ Ptr GValue
gv = do
        Ptr ZlibDecompressor
ptr <- Ptr GValue -> IO (Ptr ZlibDecompressor)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr ZlibDecompressor)
        if Ptr ZlibDecompressor
ptr Ptr ZlibDecompressor -> Ptr ZlibDecompressor -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr ZlibDecompressor
forall a. Ptr a
FP.nullPtr
        then ZlibDecompressor -> Maybe ZlibDecompressor
forall a. a -> Maybe a
P.Just (ZlibDecompressor -> Maybe ZlibDecompressor)
-> IO ZlibDecompressor -> IO (Maybe ZlibDecompressor)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr ZlibDecompressor -> ZlibDecompressor)
-> Ptr ZlibDecompressor -> IO ZlibDecompressor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ZlibDecompressor -> ZlibDecompressor
ZlibDecompressor Ptr ZlibDecompressor
ptr
        else Maybe ZlibDecompressor -> IO (Maybe ZlibDecompressor)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ZlibDecompressor
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveZlibDecompressorMethod (t :: Symbol) (o :: *) :: * where
    ResolveZlibDecompressorMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveZlibDecompressorMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveZlibDecompressorMethod "convert" o = Gio.Converter.ConverterConvertMethodInfo
    ResolveZlibDecompressorMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveZlibDecompressorMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveZlibDecompressorMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveZlibDecompressorMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveZlibDecompressorMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveZlibDecompressorMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveZlibDecompressorMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveZlibDecompressorMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveZlibDecompressorMethod "reset" o = Gio.Converter.ConverterResetMethodInfo
    ResolveZlibDecompressorMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveZlibDecompressorMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveZlibDecompressorMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveZlibDecompressorMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveZlibDecompressorMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveZlibDecompressorMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveZlibDecompressorMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveZlibDecompressorMethod "getFileInfo" o = ZlibDecompressorGetFileInfoMethodInfo
    ResolveZlibDecompressorMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveZlibDecompressorMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveZlibDecompressorMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveZlibDecompressorMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveZlibDecompressorMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveZlibDecompressorMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveZlibDecompressorMethod t ZlibDecompressor, O.OverloadedMethod info ZlibDecompressor p) => OL.IsLabel t (ZlibDecompressor -> 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 ~ ResolveZlibDecompressorMethod t ZlibDecompressor, O.OverloadedMethod info ZlibDecompressor p, R.HasField t ZlibDecompressor p) => R.HasField t ZlibDecompressor p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- VVV Prop "file-info"
   -- Type: TInterface (Name {namespace = "Gio", name = "FileInfo"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data ZlibDecompressorFileInfoPropertyInfo
instance AttrInfo ZlibDecompressorFileInfoPropertyInfo where
    type AttrAllowedOps ZlibDecompressorFileInfoPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ZlibDecompressorFileInfoPropertyInfo = IsZlibDecompressor
    type AttrSetTypeConstraint ZlibDecompressorFileInfoPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ZlibDecompressorFileInfoPropertyInfo = (~) ()
    type AttrTransferType ZlibDecompressorFileInfoPropertyInfo = ()
    type AttrGetType ZlibDecompressorFileInfoPropertyInfo = Gio.FileInfo.FileInfo
    type AttrLabel ZlibDecompressorFileInfoPropertyInfo = "file-info"
    type AttrOrigin ZlibDecompressorFileInfoPropertyInfo = ZlibDecompressor
    attrGet = getZlibDecompressorFileInfo
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

-- | Get the value of the “@format@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' zlibDecompressor #format
-- @
getZlibDecompressorFormat :: (MonadIO m, IsZlibDecompressor o) => o -> m Gio.Enums.ZlibCompressorFormat
getZlibDecompressorFormat :: forall (m :: * -> *) o.
(MonadIO m, IsZlibDecompressor o) =>
o -> m ZlibCompressorFormat
getZlibDecompressorFormat o
obj = IO ZlibCompressorFormat -> m ZlibCompressorFormat
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ZlibCompressorFormat -> m ZlibCompressorFormat)
-> IO ZlibCompressorFormat -> m ZlibCompressorFormat
forall a b. (a -> b) -> a -> b
$ o -> String -> IO ZlibCompressorFormat
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"format"

-- | Construct a `GValueConstruct` with valid value for the “@format@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructZlibDecompressorFormat :: (IsZlibDecompressor o, MIO.MonadIO m) => Gio.Enums.ZlibCompressorFormat -> m (GValueConstruct o)
constructZlibDecompressorFormat :: forall o (m :: * -> *).
(IsZlibDecompressor o, MonadIO m) =>
ZlibCompressorFormat -> m (GValueConstruct o)
constructZlibDecompressorFormat ZlibCompressorFormat
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
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 -> ZlibCompressorFormat -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"format" ZlibCompressorFormat
val

#if defined(ENABLE_OVERLOADING)
data ZlibDecompressorFormatPropertyInfo
instance AttrInfo ZlibDecompressorFormatPropertyInfo where
    type AttrAllowedOps ZlibDecompressorFormatPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ZlibDecompressorFormatPropertyInfo = IsZlibDecompressor
    type AttrSetTypeConstraint ZlibDecompressorFormatPropertyInfo = (~) Gio.Enums.ZlibCompressorFormat
    type AttrTransferTypeConstraint ZlibDecompressorFormatPropertyInfo = (~) Gio.Enums.ZlibCompressorFormat
    type AttrTransferType ZlibDecompressorFormatPropertyInfo = Gio.Enums.ZlibCompressorFormat
    type AttrGetType ZlibDecompressorFormatPropertyInfo = Gio.Enums.ZlibCompressorFormat
    type AttrLabel ZlibDecompressorFormatPropertyInfo = "format"
    type AttrOrigin ZlibDecompressorFormatPropertyInfo = ZlibDecompressor
    attrGet = getZlibDecompressorFormat
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructZlibDecompressorFormat
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ZlibDecompressor
type instance O.AttributeList ZlibDecompressor = ZlibDecompressorAttributeList
type ZlibDecompressorAttributeList = ('[ '("fileInfo", ZlibDecompressorFileInfoPropertyInfo), '("format", ZlibDecompressorFormatPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
zlibDecompressorFileInfo :: AttrLabelProxy "fileInfo"
zlibDecompressorFileInfo = AttrLabelProxy

zlibDecompressorFormat :: AttrLabelProxy "format"
zlibDecompressorFormat = AttrLabelProxy

#endif

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

#endif

-- method ZlibDecompressor::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "format"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "ZlibCompressorFormat" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The format to use for the compressed data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "ZlibDecompressor" })
-- throws : False
-- Skip return : False

foreign import ccall "g_zlib_decompressor_new" g_zlib_decompressor_new :: 
    CUInt ->                                -- format : TInterface (Name {namespace = "Gio", name = "ZlibCompressorFormat"})
    IO (Ptr ZlibDecompressor)

-- | Creates a new t'GI.Gio.Objects.ZlibDecompressor.ZlibDecompressor'.
-- 
-- /Since: 2.24/
zlibDecompressorNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Gio.Enums.ZlibCompressorFormat
    -- ^ /@format@/: The format to use for the compressed data
    -> m ZlibDecompressor
    -- ^ __Returns:__ a new t'GI.Gio.Objects.ZlibDecompressor.ZlibDecompressor'
zlibDecompressorNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
ZlibCompressorFormat -> m ZlibDecompressor
zlibDecompressorNew ZlibCompressorFormat
format = IO ZlibDecompressor -> m ZlibDecompressor
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ZlibDecompressor -> m ZlibDecompressor)
-> IO ZlibDecompressor -> m ZlibDecompressor
forall a b. (a -> b) -> a -> b
$ do
    let format' :: CUInt
format' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (ZlibCompressorFormat -> Int) -> ZlibCompressorFormat -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ZlibCompressorFormat -> Int
forall a. Enum a => a -> Int
fromEnum) ZlibCompressorFormat
format
    Ptr ZlibDecompressor
result <- CUInt -> IO (Ptr ZlibDecompressor)
g_zlib_decompressor_new CUInt
format'
    Text -> Ptr ZlibDecompressor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"zlibDecompressorNew" Ptr ZlibDecompressor
result
    ZlibDecompressor
result' <- ((ManagedPtr ZlibDecompressor -> ZlibDecompressor)
-> Ptr ZlibDecompressor -> IO ZlibDecompressor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ZlibDecompressor -> ZlibDecompressor
ZlibDecompressor) Ptr ZlibDecompressor
result
    ZlibDecompressor -> IO ZlibDecompressor
forall (m :: * -> *) a. Monad m => a -> m a
return ZlibDecompressor
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "g_zlib_decompressor_get_file_info" g_zlib_decompressor_get_file_info :: 
    Ptr ZlibDecompressor ->                 -- decompressor : TInterface (Name {namespace = "Gio", name = "ZlibDecompressor"})
    IO (Ptr Gio.FileInfo.FileInfo)

-- | Retrieves the t'GI.Gio.Objects.FileInfo.FileInfo' constructed from the GZIP header data
-- of compressed data processed by /@compressor@/, or 'P.Nothing' if /@decompressor@/\'s
-- t'GI.Gio.Objects.ZlibDecompressor.ZlibDecompressor':@/format/@ property is not 'GI.Gio.Enums.ZlibCompressorFormatGzip',
-- or the header data was not fully processed yet, or it not present in the
-- data stream at all.
-- 
-- /Since: 2.26/
zlibDecompressorGetFileInfo ::
    (B.CallStack.HasCallStack, MonadIO m, IsZlibDecompressor a) =>
    a
    -- ^ /@decompressor@/: a t'GI.Gio.Objects.ZlibDecompressor.ZlibDecompressor'
    -> m Gio.FileInfo.FileInfo
    -- ^ __Returns:__ a t'GI.Gio.Objects.FileInfo.FileInfo', or 'P.Nothing'
zlibDecompressorGetFileInfo :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsZlibDecompressor a) =>
a -> m FileInfo
zlibDecompressorGetFileInfo a
decompressor = IO FileInfo -> m FileInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileInfo -> m FileInfo) -> IO FileInfo -> m FileInfo
forall a b. (a -> b) -> a -> b
$ do
    Ptr ZlibDecompressor
decompressor' <- a -> IO (Ptr ZlibDecompressor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
decompressor
    Ptr FileInfo
result <- Ptr ZlibDecompressor -> IO (Ptr FileInfo)
g_zlib_decompressor_get_file_info Ptr ZlibDecompressor
decompressor'
    Text -> Ptr FileInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"zlibDecompressorGetFileInfo" Ptr FileInfo
result
    FileInfo
result' <- ((ManagedPtr FileInfo -> FileInfo) -> Ptr FileInfo -> IO FileInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FileInfo -> FileInfo
Gio.FileInfo.FileInfo) Ptr FileInfo
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
decompressor
    FileInfo -> IO FileInfo
forall (m :: * -> *) a. Monad m => a -> m a
return FileInfo
result'

#if defined(ENABLE_OVERLOADING)
data ZlibDecompressorGetFileInfoMethodInfo
instance (signature ~ (m Gio.FileInfo.FileInfo), MonadIO m, IsZlibDecompressor a) => O.OverloadedMethod ZlibDecompressorGetFileInfoMethodInfo a signature where
    overloadedMethod = zlibDecompressorGetFileInfo

instance O.OverloadedMethodInfo ZlibDecompressorGetFileInfoMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.ZlibDecompressor.zlibDecompressorGetFileInfo",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-ZlibDecompressor.html#v:zlibDecompressorGetFileInfo"
        }


#endif