{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.ZlibCompressor
(
ZlibCompressor(..) ,
IsZlibCompressor ,
toZlibCompressor ,
noZlibCompressor ,
#if defined(ENABLE_OVERLOADING)
ResolveZlibCompressorMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ZlibCompressorGetFileInfoMethodInfo ,
#endif
zlibCompressorGetFileInfo ,
zlibCompressorNew ,
#if defined(ENABLE_OVERLOADING)
ZlibCompressorSetFileInfoMethodInfo ,
#endif
zlibCompressorSetFileInfo ,
#if defined(ENABLE_OVERLOADING)
ZlibCompressorFileInfoPropertyInfo ,
#endif
clearZlibCompressorFileInfo ,
constructZlibCompressorFileInfo ,
getZlibCompressorFileInfo ,
setZlibCompressorFileInfo ,
#if defined(ENABLE_OVERLOADING)
zlibCompressorFileInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
ZlibCompressorFormatPropertyInfo ,
#endif
constructZlibCompressorFormat ,
getZlibCompressorFormat ,
#if defined(ENABLE_OVERLOADING)
zlibCompressorFormat ,
#endif
#if defined(ENABLE_OVERLOADING)
ZlibCompressorLevelPropertyInfo ,
#endif
constructZlibCompressorLevel ,
getZlibCompressorLevel ,
#if defined(ENABLE_OVERLOADING)
zlibCompressorLevel ,
#endif
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified 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.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Converter as Gio.Converter
import {-# SOURCE #-} qualified GI.Gio.Objects.FileInfo as Gio.FileInfo
newtype ZlibCompressor = ZlibCompressor (ManagedPtr ZlibCompressor)
deriving (ZlibCompressor -> ZlibCompressor -> Bool
(ZlibCompressor -> ZlibCompressor -> Bool)
-> (ZlibCompressor -> ZlibCompressor -> Bool) -> Eq ZlibCompressor
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ZlibCompressor -> ZlibCompressor -> Bool
$c/= :: ZlibCompressor -> ZlibCompressor -> Bool
== :: ZlibCompressor -> ZlibCompressor -> Bool
$c== :: ZlibCompressor -> ZlibCompressor -> Bool
Eq)
foreign import ccall "g_zlib_compressor_get_type"
c_g_zlib_compressor_get_type :: IO GType
instance GObject ZlibCompressor where
gobjectType :: IO GType
gobjectType = IO GType
c_g_zlib_compressor_get_type
instance B.GValue.IsGValue ZlibCompressor where
toGValue :: ZlibCompressor -> IO GValue
toGValue o :: ZlibCompressor
o = do
GType
gtype <- IO GType
c_g_zlib_compressor_get_type
ZlibCompressor -> (Ptr ZlibCompressor -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ZlibCompressor
o (GType
-> (GValue -> Ptr ZlibCompressor -> IO ())
-> Ptr ZlibCompressor
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr ZlibCompressor -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO ZlibCompressor
fromGValue gv :: GValue
gv = do
Ptr ZlibCompressor
ptr <- GValue -> IO (Ptr ZlibCompressor)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr ZlibCompressor)
(ManagedPtr ZlibCompressor -> ZlibCompressor)
-> Ptr ZlibCompressor -> IO ZlibCompressor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ZlibCompressor -> ZlibCompressor
ZlibCompressor Ptr ZlibCompressor
ptr
class (GObject o, O.IsDescendantOf ZlibCompressor o) => IsZlibCompressor o
instance (GObject o, O.IsDescendantOf ZlibCompressor o) => IsZlibCompressor o
instance O.HasParentTypes ZlibCompressor
type instance O.ParentTypes ZlibCompressor = '[GObject.Object.Object, Gio.Converter.Converter]
toZlibCompressor :: (MonadIO m, IsZlibCompressor o) => o -> m ZlibCompressor
toZlibCompressor :: o -> m ZlibCompressor
toZlibCompressor = IO ZlibCompressor -> m ZlibCompressor
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ZlibCompressor -> m ZlibCompressor)
-> (o -> IO ZlibCompressor) -> o -> m ZlibCompressor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ZlibCompressor -> ZlibCompressor)
-> o -> IO ZlibCompressor
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr ZlibCompressor -> ZlibCompressor
ZlibCompressor
noZlibCompressor :: Maybe ZlibCompressor
noZlibCompressor :: Maybe ZlibCompressor
noZlibCompressor = Maybe ZlibCompressor
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveZlibCompressorMethod (t :: Symbol) (o :: *) :: * where
ResolveZlibCompressorMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveZlibCompressorMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveZlibCompressorMethod "convert" o = Gio.Converter.ConverterConvertMethodInfo
ResolveZlibCompressorMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveZlibCompressorMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveZlibCompressorMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveZlibCompressorMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveZlibCompressorMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveZlibCompressorMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveZlibCompressorMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveZlibCompressorMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveZlibCompressorMethod "reset" o = Gio.Converter.ConverterResetMethodInfo
ResolveZlibCompressorMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveZlibCompressorMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveZlibCompressorMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveZlibCompressorMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveZlibCompressorMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveZlibCompressorMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveZlibCompressorMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveZlibCompressorMethod "getFileInfo" o = ZlibCompressorGetFileInfoMethodInfo
ResolveZlibCompressorMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveZlibCompressorMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveZlibCompressorMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveZlibCompressorMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveZlibCompressorMethod "setFileInfo" o = ZlibCompressorSetFileInfoMethodInfo
ResolveZlibCompressorMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveZlibCompressorMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveZlibCompressorMethod t ZlibCompressor, O.MethodInfo info ZlibCompressor p) => OL.IsLabel t (ZlibCompressor -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getZlibCompressorFileInfo :: (MonadIO m, IsZlibCompressor o) => o -> m Gio.FileInfo.FileInfo
getZlibCompressorFileInfo :: o -> m FileInfo
getZlibCompressorFileInfo obj :: o
obj = 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
$ Text -> IO (Maybe FileInfo) -> IO FileInfo
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getZlibCompressorFileInfo" (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 "file-info" ManagedPtr FileInfo -> FileInfo
Gio.FileInfo.FileInfo
setZlibCompressorFileInfo :: (MonadIO m, IsZlibCompressor o, Gio.FileInfo.IsFileInfo a) => o -> a -> m ()
setZlibCompressorFileInfo :: o -> a -> m ()
setZlibCompressorFileInfo obj :: o
obj val :: a
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 -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "file-info" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructZlibCompressorFileInfo :: (IsZlibCompressor o, Gio.FileInfo.IsFileInfo a) => a -> IO (GValueConstruct o)
constructZlibCompressorFileInfo :: a -> IO (GValueConstruct o)
constructZlibCompressorFileInfo val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "file-info" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
clearZlibCompressorFileInfo :: (MonadIO m, IsZlibCompressor o) => o -> m ()
clearZlibCompressorFileInfo :: o -> m ()
clearZlibCompressorFileInfo obj :: o
obj = 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 -> Maybe FileInfo -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "file-info" (Maybe FileInfo
forall a. Maybe a
Nothing :: Maybe Gio.FileInfo.FileInfo)
#if defined(ENABLE_OVERLOADING)
data ZlibCompressorFileInfoPropertyInfo
instance AttrInfo ZlibCompressorFileInfoPropertyInfo where
type AttrAllowedOps ZlibCompressorFileInfoPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint ZlibCompressorFileInfoPropertyInfo = IsZlibCompressor
type AttrSetTypeConstraint ZlibCompressorFileInfoPropertyInfo = Gio.FileInfo.IsFileInfo
type AttrTransferTypeConstraint ZlibCompressorFileInfoPropertyInfo = Gio.FileInfo.IsFileInfo
type AttrTransferType ZlibCompressorFileInfoPropertyInfo = Gio.FileInfo.FileInfo
type AttrGetType ZlibCompressorFileInfoPropertyInfo = Gio.FileInfo.FileInfo
type AttrLabel ZlibCompressorFileInfoPropertyInfo = "file-info"
type AttrOrigin ZlibCompressorFileInfoPropertyInfo = ZlibCompressor
attrGet = getZlibCompressorFileInfo
attrSet = setZlibCompressorFileInfo
attrTransfer _ v = do
unsafeCastTo Gio.FileInfo.FileInfo v
attrConstruct = constructZlibCompressorFileInfo
attrClear = clearZlibCompressorFileInfo
#endif
getZlibCompressorFormat :: (MonadIO m, IsZlibCompressor o) => o -> m Gio.Enums.ZlibCompressorFormat
getZlibCompressorFormat :: o -> m ZlibCompressorFormat
getZlibCompressorFormat obj :: o
obj = IO ZlibCompressorFormat -> m ZlibCompressorFormat
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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 "format"
constructZlibCompressorFormat :: (IsZlibCompressor o) => Gio.Enums.ZlibCompressorFormat -> IO (GValueConstruct o)
constructZlibCompressorFormat :: ZlibCompressorFormat -> IO (GValueConstruct o)
constructZlibCompressorFormat val :: ZlibCompressorFormat
val = String -> ZlibCompressorFormat -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum "format" ZlibCompressorFormat
val
#if defined(ENABLE_OVERLOADING)
data ZlibCompressorFormatPropertyInfo
instance AttrInfo ZlibCompressorFormatPropertyInfo where
type AttrAllowedOps ZlibCompressorFormatPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ZlibCompressorFormatPropertyInfo = IsZlibCompressor
type AttrSetTypeConstraint ZlibCompressorFormatPropertyInfo = (~) Gio.Enums.ZlibCompressorFormat
type AttrTransferTypeConstraint ZlibCompressorFormatPropertyInfo = (~) Gio.Enums.ZlibCompressorFormat
type AttrTransferType ZlibCompressorFormatPropertyInfo = Gio.Enums.ZlibCompressorFormat
type AttrGetType ZlibCompressorFormatPropertyInfo = Gio.Enums.ZlibCompressorFormat
type AttrLabel ZlibCompressorFormatPropertyInfo = "format"
type AttrOrigin ZlibCompressorFormatPropertyInfo = ZlibCompressor
attrGet = getZlibCompressorFormat
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructZlibCompressorFormat
attrClear = undefined
#endif
getZlibCompressorLevel :: (MonadIO m, IsZlibCompressor o) => o -> m Int32
getZlibCompressorLevel :: o -> m Int32
getZlibCompressorLevel obj :: o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "level"
constructZlibCompressorLevel :: (IsZlibCompressor o) => Int32 -> IO (GValueConstruct o)
constructZlibCompressorLevel :: Int32 -> IO (GValueConstruct o)
constructZlibCompressorLevel val :: Int32
val = String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 "level" Int32
val
#if defined(ENABLE_OVERLOADING)
data ZlibCompressorLevelPropertyInfo
instance AttrInfo ZlibCompressorLevelPropertyInfo where
type AttrAllowedOps ZlibCompressorLevelPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint ZlibCompressorLevelPropertyInfo = IsZlibCompressor
type AttrSetTypeConstraint ZlibCompressorLevelPropertyInfo = (~) Int32
type AttrTransferTypeConstraint ZlibCompressorLevelPropertyInfo = (~) Int32
type AttrTransferType ZlibCompressorLevelPropertyInfo = Int32
type AttrGetType ZlibCompressorLevelPropertyInfo = Int32
type AttrLabel ZlibCompressorLevelPropertyInfo = "level"
type AttrOrigin ZlibCompressorLevelPropertyInfo = ZlibCompressor
attrGet = getZlibCompressorLevel
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructZlibCompressorLevel
attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ZlibCompressor
type instance O.AttributeList ZlibCompressor = ZlibCompressorAttributeList
type ZlibCompressorAttributeList = ('[ '("fileInfo", ZlibCompressorFileInfoPropertyInfo), '("format", ZlibCompressorFormatPropertyInfo), '("level", ZlibCompressorLevelPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
zlibCompressorFileInfo :: AttrLabelProxy "fileInfo"
zlibCompressorFileInfo = AttrLabelProxy
zlibCompressorFormat :: AttrLabelProxy "format"
zlibCompressorFormat = AttrLabelProxy
zlibCompressorLevel :: AttrLabelProxy "level"
zlibCompressorLevel = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ZlibCompressor = ZlibCompressorSignalList
type ZlibCompressorSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_zlib_compressor_new" g_zlib_compressor_new ::
CUInt ->
Int32 ->
IO (Ptr ZlibCompressor)
zlibCompressorNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Gio.Enums.ZlibCompressorFormat
-> Int32
-> m ZlibCompressor
zlibCompressorNew :: ZlibCompressorFormat -> Int32 -> m ZlibCompressor
zlibCompressorNew format :: ZlibCompressorFormat
format level :: Int32
level = IO ZlibCompressor -> m ZlibCompressor
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ZlibCompressor -> m ZlibCompressor)
-> IO ZlibCompressor -> m ZlibCompressor
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 ZlibCompressor
result <- CUInt -> Int32 -> IO (Ptr ZlibCompressor)
g_zlib_compressor_new CUInt
format' Int32
level
Text -> Ptr ZlibCompressor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "zlibCompressorNew" Ptr ZlibCompressor
result
ZlibCompressor
result' <- ((ManagedPtr ZlibCompressor -> ZlibCompressor)
-> Ptr ZlibCompressor -> IO ZlibCompressor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ZlibCompressor -> ZlibCompressor
ZlibCompressor) Ptr ZlibCompressor
result
ZlibCompressor -> IO ZlibCompressor
forall (m :: * -> *) a. Monad m => a -> m a
return ZlibCompressor
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_zlib_compressor_get_file_info" g_zlib_compressor_get_file_info ::
Ptr ZlibCompressor ->
IO (Ptr Gio.FileInfo.FileInfo)
zlibCompressorGetFileInfo ::
(B.CallStack.HasCallStack, MonadIO m, IsZlibCompressor a) =>
a
-> m Gio.FileInfo.FileInfo
zlibCompressorGetFileInfo :: a -> m FileInfo
zlibCompressorGetFileInfo compressor :: a
compressor = 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 ZlibCompressor
compressor' <- a -> IO (Ptr ZlibCompressor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
compressor
Ptr FileInfo
result <- Ptr ZlibCompressor -> IO (Ptr FileInfo)
g_zlib_compressor_get_file_info Ptr ZlibCompressor
compressor'
Text -> Ptr FileInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "zlibCompressorGetFileInfo" 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
compressor
FileInfo -> IO FileInfo
forall (m :: * -> *) a. Monad m => a -> m a
return FileInfo
result'
#if defined(ENABLE_OVERLOADING)
data ZlibCompressorGetFileInfoMethodInfo
instance (signature ~ (m Gio.FileInfo.FileInfo), MonadIO m, IsZlibCompressor a) => O.MethodInfo ZlibCompressorGetFileInfoMethodInfo a signature where
overloadedMethod = zlibCompressorGetFileInfo
#endif
foreign import ccall "g_zlib_compressor_set_file_info" g_zlib_compressor_set_file_info ::
Ptr ZlibCompressor ->
Ptr Gio.FileInfo.FileInfo ->
IO ()
zlibCompressorSetFileInfo ::
(B.CallStack.HasCallStack, MonadIO m, IsZlibCompressor a, Gio.FileInfo.IsFileInfo b) =>
a
-> Maybe (b)
-> m ()
zlibCompressorSetFileInfo :: a -> Maybe b -> m ()
zlibCompressorSetFileInfo compressor :: a
compressor fileInfo :: Maybe b
fileInfo = 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 ZlibCompressor
compressor' <- a -> IO (Ptr ZlibCompressor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
compressor
Ptr FileInfo
maybeFileInfo <- case Maybe b
fileInfo of
Nothing -> Ptr FileInfo -> IO (Ptr FileInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FileInfo
forall a. Ptr a
nullPtr
Just jFileInfo :: b
jFileInfo -> do
Ptr FileInfo
jFileInfo' <- b -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFileInfo
Ptr FileInfo -> IO (Ptr FileInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FileInfo
jFileInfo'
Ptr ZlibCompressor -> Ptr FileInfo -> IO ()
g_zlib_compressor_set_file_info Ptr ZlibCompressor
compressor' Ptr FileInfo
maybeFileInfo
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
compressor
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
fileInfo b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ZlibCompressorSetFileInfoMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsZlibCompressor a, Gio.FileInfo.IsFileInfo b) => O.MethodInfo ZlibCompressorSetFileInfoMethodInfo a signature where
overloadedMethod = zlibCompressorSetFileInfo
#endif