{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GdkPixbufModule@ contains the necessary functions to load and save
-- images in a certain file format.
-- 
-- If @GdkPixbuf@ has been compiled with @GModule@ support, it can be extended
-- by modules which can load (and perhaps also save) new image and animation
-- formats.
-- 
-- == Implementing modules
-- 
-- The @GdkPixbuf@ interfaces needed for implementing modules are contained in
-- @gdk-pixbuf-io.h@ (and @gdk-pixbuf-animation.h@ if the module supports
-- animations). They are not covered by the same stability guarantees as the
-- regular GdkPixbuf API. To underline this fact, they are protected by the
-- @GDK_PIXBUF_ENABLE_BACKEND@ pre-processor symbol.
-- 
-- Each loadable module must contain a @GdkPixbufModuleFillVtableFunc@ function
-- named @fill_vtable@, which will get called when the module
-- is loaded and must set the function pointers of the @GdkPixbufModule@.
-- 
-- In order to make format-checking work before actually loading the modules
-- (which may require calling @dlopen@ to load image libraries), modules export
-- their signatures (and other information) via the @fill_info@ function. An
-- external utility, @gdk-pixbuf-query-loaders@, uses this to create a text
-- file containing a list of all available loaders and  their signatures.
-- This file is then read at runtime by @GdkPixbuf@ to obtain the list of
-- available loaders and their signatures.
-- 
-- Modules may only implement a subset of the functionality available via
-- @GdkPixbufModule@. If a particular functionality is not implemented, the
-- @fill_vtable@ function will simply not set the corresponding
-- function pointers of the @GdkPixbufModule@ structure. If a module supports
-- incremental loading (i.e. provides @begin_load@, @stop_load@ and
-- @load_increment@), it doesn\'t have to implement @load@, since @GdkPixbuf@
-- can supply a generic @load@ implementation wrapping the incremental loading.
-- 
-- == Installing modules
-- 
-- Installing a module is a two-step process:
-- 
--  - copy the module file(s) to the loader directory (normally
--    @$libdir\/gdk-pixbuf-2.0\/$version\/loaders@, unless overridden by the
--    environment variable @GDK_PIXBUF_MODULEDIR@)
--  - call @gdk-pixbuf-query-loaders@ to update the module file (normally
--    @$libdir\/gdk-pixbuf-2.0\/$version\/loaders.cache@, unless overridden
--    by the environment variable @GDK_PIXBUF_MODULE_FILE@)

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

module GI.GdkPixbuf.Structs.PixbufModule
    ( 

-- * Exported types
    PixbufModule(..)                        ,
    newZeroPixbufModule                     ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolvePixbufModuleMethod               ,
#endif



 -- * Properties


-- ** info #attr:info#
-- | a @GdkPixbufFormat@ holding information about the module.

    clearPixbufModuleInfo                   ,
    getPixbufModuleInfo                     ,
#if defined(ENABLE_OVERLOADING)
    pixbufModule_info                       ,
#endif
    setPixbufModuleInfo                     ,


-- ** isSaveOptionSupported #attr:isSaveOptionSupported#
-- | returns whether a save option key is supported by the module

    clearPixbufModuleIsSaveOptionSupported  ,
    getPixbufModuleIsSaveOptionSupported    ,
#if defined(ENABLE_OVERLOADING)
    pixbufModule_isSaveOptionSupported      ,
#endif
    setPixbufModuleIsSaveOptionSupported    ,


-- ** load #attr:load#
-- | loads an image from a file.

    clearPixbufModuleLoad                   ,
    getPixbufModuleLoad                     ,
#if defined(ENABLE_OVERLOADING)
    pixbufModule_load                       ,
#endif
    setPixbufModuleLoad                     ,


-- ** loadAnimation #attr:loadAnimation#
-- | loads an animation from a file.

    clearPixbufModuleLoadAnimation          ,
    getPixbufModuleLoadAnimation            ,
#if defined(ENABLE_OVERLOADING)
    pixbufModule_loadAnimation              ,
#endif
    setPixbufModuleLoadAnimation            ,


-- ** loadIncrement #attr:loadIncrement#
-- | continues an incremental load.

    clearPixbufModuleLoadIncrement          ,
    getPixbufModuleLoadIncrement            ,
#if defined(ENABLE_OVERLOADING)
    pixbufModule_loadIncrement              ,
#endif
    setPixbufModuleLoadIncrement            ,


-- ** loadXpmData #attr:loadXpmData#
-- | loads an image from data in memory.

    clearPixbufModuleLoadXpmData            ,
    getPixbufModuleLoadXpmData              ,
#if defined(ENABLE_OVERLOADING)
    pixbufModule_loadXpmData                ,
#endif
    setPixbufModuleLoadXpmData              ,


-- ** module #attr:module#
-- | the loaded @GModule@.

    clearPixbufModuleModule                 ,
    getPixbufModuleModule                   ,
#if defined(ENABLE_OVERLOADING)
    pixbufModule_module                     ,
#endif
    setPixbufModuleModule                   ,


-- ** moduleName #attr:moduleName#
-- | the name of the module, usually the same as the
--  usual file extension for images of this type, eg. \"xpm\", \"jpeg\" or \"png\".

    clearPixbufModuleModuleName             ,
    getPixbufModuleModuleName               ,
#if defined(ENABLE_OVERLOADING)
    pixbufModule_moduleName                 ,
#endif
    setPixbufModuleModuleName               ,


-- ** modulePath #attr:modulePath#
-- | the path from which the module is loaded.

    clearPixbufModuleModulePath             ,
    getPixbufModuleModulePath               ,
#if defined(ENABLE_OVERLOADING)
    pixbufModule_modulePath                 ,
#endif
    setPixbufModuleModulePath               ,


-- ** save #attr:save#
-- | saves a @GdkPixbuf@ to a file.

    clearPixbufModuleSave                   ,
    getPixbufModuleSave                     ,
#if defined(ENABLE_OVERLOADING)
    pixbufModule_save                       ,
#endif
    setPixbufModuleSave                     ,


-- ** stopLoad #attr:stopLoad#
-- | stops an incremental load.

    clearPixbufModuleStopLoad               ,
    getPixbufModuleStopLoad                 ,
#if defined(ENABLE_OVERLOADING)
    pixbufModule_stopLoad                   ,
#endif
    setPixbufModuleStopLoad                 ,




    ) 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.GModule.Structs.Module as GModule.Module
import qualified GI.GdkPixbuf.Callbacks as GdkPixbuf.Callbacks
import {-# SOURCE #-} qualified GI.GdkPixbuf.Structs.PixbufFormat as GdkPixbuf.PixbufFormat

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

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

instance BoxedPtr PixbufModule where
    boxedPtrCopy :: PixbufModule -> IO PixbufModule
boxedPtrCopy = \PixbufModule
p -> PixbufModule
-> (Ptr PixbufModule -> IO PixbufModule) -> IO PixbufModule
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PixbufModule
p (Int -> Ptr PixbufModule -> IO (Ptr PixbufModule)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
136 (Ptr PixbufModule -> IO (Ptr PixbufModule))
-> (Ptr PixbufModule -> IO PixbufModule)
-> Ptr PixbufModule
-> IO PixbufModule
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr PixbufModule -> PixbufModule)
-> Ptr PixbufModule -> IO PixbufModule
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr PixbufModule -> PixbufModule
PixbufModule)
    boxedPtrFree :: PixbufModule -> IO ()
boxedPtrFree = \PixbufModule
x -> PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr PixbufModule
x Ptr PixbufModule -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr PixbufModule where
    boxedPtrCalloc :: IO (Ptr PixbufModule)
boxedPtrCalloc = Int -> IO (Ptr PixbufModule)
forall a. Int -> IO (Ptr a)
callocBytes Int
136


-- | Construct a `PixbufModule` struct initialized to zero.
newZeroPixbufModule :: MonadIO m => m PixbufModule
newZeroPixbufModule :: forall (m :: * -> *). MonadIO m => m PixbufModule
newZeroPixbufModule = IO PixbufModule -> m PixbufModule
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PixbufModule -> m PixbufModule)
-> IO PixbufModule -> m PixbufModule
forall a b. (a -> b) -> a -> b
$ IO (Ptr PixbufModule)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr PixbufModule)
-> (Ptr PixbufModule -> IO PixbufModule) -> IO PixbufModule
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr PixbufModule -> PixbufModule)
-> Ptr PixbufModule -> IO PixbufModule
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr PixbufModule -> PixbufModule
PixbufModule

instance tag ~ 'AttrSet => Constructible PixbufModule tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr PixbufModule -> PixbufModule)
-> [AttrOp PixbufModule tag] -> m PixbufModule
new ManagedPtr PixbufModule -> PixbufModule
_ [AttrOp PixbufModule tag]
attrs = do
        PixbufModule
o <- m PixbufModule
forall (m :: * -> *). MonadIO m => m PixbufModule
newZeroPixbufModule
        PixbufModule -> [AttrOp PixbufModule 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set PixbufModule
o [AttrOp PixbufModule tag]
[AttrOp PixbufModule 'AttrSet]
attrs
        PixbufModule -> m PixbufModule
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufModule
o


-- | Get the value of the “@module_name@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbufModule #moduleName
-- @
getPixbufModuleModuleName :: MonadIO m => PixbufModule -> m (Maybe T.Text)
getPixbufModuleModuleName :: forall (m :: * -> *). MonadIO m => PixbufModule -> m (Maybe Text)
getPixbufModuleModuleName PixbufModule
s = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ PixbufModule
-> (Ptr PixbufModule -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr PixbufModule -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

-- | Set the value of the “@module_name@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' pixbufModule [ #moduleName 'Data.GI.Base.Attributes.:=' value ]
-- @
setPixbufModuleModuleName :: MonadIO m => PixbufModule -> CString -> m ()
setPixbufModuleModuleName :: forall (m :: * -> *). MonadIO m => PixbufModule -> CString -> m ()
setPixbufModuleModuleName PixbufModule
s CString
val = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CString
val :: CString)

-- | Set the value of the “@module_name@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #moduleName
-- @
clearPixbufModuleModuleName :: MonadIO m => PixbufModule -> m ()
clearPixbufModuleModuleName :: forall (m :: * -> *). MonadIO m => PixbufModule -> m ()
clearPixbufModuleModuleName PixbufModule
s = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data PixbufModuleModuleNameFieldInfo
instance AttrInfo PixbufModuleModuleNameFieldInfo where
    type AttrBaseTypeConstraint PixbufModuleModuleNameFieldInfo = (~) PixbufModule
    type AttrAllowedOps PixbufModuleModuleNameFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PixbufModuleModuleNameFieldInfo = (~) CString
    type AttrTransferTypeConstraint PixbufModuleModuleNameFieldInfo = (~)CString
    type AttrTransferType PixbufModuleModuleNameFieldInfo = CString
    type AttrGetType PixbufModuleModuleNameFieldInfo = Maybe T.Text
    type AttrLabel PixbufModuleModuleNameFieldInfo = "module_name"
    type AttrOrigin PixbufModuleModuleNameFieldInfo = PixbufModule
    attrGet = getPixbufModuleModuleName
    attrSet = setPixbufModuleModuleName
    attrConstruct = undefined
    attrClear = clearPixbufModuleModuleName
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Structs.PixbufModule.moduleName"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Structs-PixbufModule.html#g:attr:moduleName"
        })

pixbufModule_moduleName :: AttrLabelProxy "moduleName"
pixbufModule_moduleName = AttrLabelProxy

#endif


-- | Get the value of the “@module_path@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbufModule #modulePath
-- @
getPixbufModuleModulePath :: MonadIO m => PixbufModule -> m (Maybe T.Text)
getPixbufModuleModulePath :: forall (m :: * -> *). MonadIO m => PixbufModule -> m (Maybe Text)
getPixbufModuleModulePath PixbufModule
s = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ PixbufModule
-> (Ptr PixbufModule -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr PixbufModule -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

-- | Set the value of the “@module_path@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' pixbufModule [ #modulePath 'Data.GI.Base.Attributes.:=' value ]
-- @
setPixbufModuleModulePath :: MonadIO m => PixbufModule -> CString -> m ()
setPixbufModuleModulePath :: forall (m :: * -> *). MonadIO m => PixbufModule -> CString -> m ()
setPixbufModuleModulePath PixbufModule
s CString
val = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
val :: CString)

-- | Set the value of the “@module_path@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #modulePath
-- @
clearPixbufModuleModulePath :: MonadIO m => PixbufModule -> m ()
clearPixbufModuleModulePath :: forall (m :: * -> *). MonadIO m => PixbufModule -> m ()
clearPixbufModuleModulePath PixbufModule
s = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data PixbufModuleModulePathFieldInfo
instance AttrInfo PixbufModuleModulePathFieldInfo where
    type AttrBaseTypeConstraint PixbufModuleModulePathFieldInfo = (~) PixbufModule
    type AttrAllowedOps PixbufModuleModulePathFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PixbufModuleModulePathFieldInfo = (~) CString
    type AttrTransferTypeConstraint PixbufModuleModulePathFieldInfo = (~)CString
    type AttrTransferType PixbufModuleModulePathFieldInfo = CString
    type AttrGetType PixbufModuleModulePathFieldInfo = Maybe T.Text
    type AttrLabel PixbufModuleModulePathFieldInfo = "module_path"
    type AttrOrigin PixbufModuleModulePathFieldInfo = PixbufModule
    attrGet = getPixbufModuleModulePath
    attrSet = setPixbufModuleModulePath
    attrConstruct = undefined
    attrClear = clearPixbufModuleModulePath
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Structs.PixbufModule.modulePath"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Structs-PixbufModule.html#g:attr:modulePath"
        })

pixbufModule_modulePath :: AttrLabelProxy "modulePath"
pixbufModule_modulePath = AttrLabelProxy

#endif


-- | Get the value of the “@module@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbufModule #module
-- @
getPixbufModuleModule :: MonadIO m => PixbufModule -> m (Maybe GModule.Module.Module)
getPixbufModuleModule :: forall (m :: * -> *). MonadIO m => PixbufModule -> m (Maybe Module)
getPixbufModuleModule PixbufModule
s = IO (Maybe Module) -> m (Maybe Module)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Module) -> m (Maybe Module))
-> IO (Maybe Module) -> m (Maybe Module)
forall a b. (a -> b) -> a -> b
$ PixbufModule
-> (Ptr PixbufModule -> IO (Maybe Module)) -> IO (Maybe Module)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO (Maybe Module)) -> IO (Maybe Module))
-> (Ptr PixbufModule -> IO (Maybe Module)) -> IO (Maybe Module)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr Module
val <- Ptr (Ptr Module) -> IO (Ptr Module)
forall a. Storable a => Ptr a -> IO a
peek (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (Ptr Module)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO (Ptr GModule.Module.Module)
    Maybe Module
result <- Ptr Module -> (Ptr Module -> IO Module) -> IO (Maybe Module)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Module
val ((Ptr Module -> IO Module) -> IO (Maybe Module))
-> (Ptr Module -> IO Module) -> IO (Maybe Module)
forall a b. (a -> b) -> a -> b
$ \Ptr Module
val' -> do
        Module
val'' <- ((ManagedPtr Module -> Module) -> Ptr Module -> IO Module
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Module -> Module
GModule.Module.Module) Ptr Module
val'
        Module -> IO Module
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Module
val''
    Maybe Module -> IO (Maybe Module)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Module
result

-- | Set the value of the “@module@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' pixbufModule [ #module 'Data.GI.Base.Attributes.:=' value ]
-- @
setPixbufModuleModule :: MonadIO m => PixbufModule -> Ptr GModule.Module.Module -> m ()
setPixbufModuleModule :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> Ptr Module -> m ()
setPixbufModuleModule PixbufModule
s Ptr Module
val = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (Ptr Module) -> Ptr Module -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (Ptr Module)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Ptr Module
val :: Ptr GModule.Module.Module)

-- | Set the value of the “@module@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #module
-- @
clearPixbufModuleModule :: MonadIO m => PixbufModule -> m ()
clearPixbufModuleModule :: forall (m :: * -> *). MonadIO m => PixbufModule -> m ()
clearPixbufModuleModule PixbufModule
s = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (Ptr Module) -> Ptr Module -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (Ptr Module)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Ptr Module
forall a. Ptr a
FP.nullPtr :: Ptr GModule.Module.Module)

#if defined(ENABLE_OVERLOADING)
data PixbufModuleModuleFieldInfo
instance AttrInfo PixbufModuleModuleFieldInfo where
    type AttrBaseTypeConstraint PixbufModuleModuleFieldInfo = (~) PixbufModule
    type AttrAllowedOps PixbufModuleModuleFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PixbufModuleModuleFieldInfo = (~) (Ptr GModule.Module.Module)
    type AttrTransferTypeConstraint PixbufModuleModuleFieldInfo = (~)(Ptr GModule.Module.Module)
    type AttrTransferType PixbufModuleModuleFieldInfo = (Ptr GModule.Module.Module)
    type AttrGetType PixbufModuleModuleFieldInfo = Maybe GModule.Module.Module
    type AttrLabel PixbufModuleModuleFieldInfo = "module"
    type AttrOrigin PixbufModuleModuleFieldInfo = PixbufModule
    attrGet = getPixbufModuleModule
    attrSet = setPixbufModuleModule
    attrConstruct = undefined
    attrClear = clearPixbufModuleModule
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Structs.PixbufModule.module"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Structs-PixbufModule.html#g:attr:module"
        })

pixbufModule_module :: AttrLabelProxy "module"
pixbufModule_module = AttrLabelProxy

#endif


-- | Get the value of the “@info@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbufModule #info
-- @
getPixbufModuleInfo :: MonadIO m => PixbufModule -> m (Maybe GdkPixbuf.PixbufFormat.PixbufFormat)
getPixbufModuleInfo :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> m (Maybe PixbufFormat)
getPixbufModuleInfo PixbufModule
s = IO (Maybe PixbufFormat) -> m (Maybe PixbufFormat)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PixbufFormat) -> m (Maybe PixbufFormat))
-> IO (Maybe PixbufFormat) -> m (Maybe PixbufFormat)
forall a b. (a -> b) -> a -> b
$ PixbufModule
-> (Ptr PixbufModule -> IO (Maybe PixbufFormat))
-> IO (Maybe PixbufFormat)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO (Maybe PixbufFormat))
 -> IO (Maybe PixbufFormat))
-> (Ptr PixbufModule -> IO (Maybe PixbufFormat))
-> IO (Maybe PixbufFormat)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr PixbufFormat
val <- Ptr (Ptr PixbufFormat) -> IO (Ptr PixbufFormat)
forall a. Storable a => Ptr a -> IO a
peek (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (Ptr PixbufFormat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO (Ptr GdkPixbuf.PixbufFormat.PixbufFormat)
    Maybe PixbufFormat
result <- Ptr PixbufFormat
-> (Ptr PixbufFormat -> IO PixbufFormat) -> IO (Maybe PixbufFormat)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr PixbufFormat
val ((Ptr PixbufFormat -> IO PixbufFormat) -> IO (Maybe PixbufFormat))
-> (Ptr PixbufFormat -> IO PixbufFormat) -> IO (Maybe PixbufFormat)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufFormat
val' -> do
        PixbufFormat
val'' <- ((ManagedPtr PixbufFormat -> PixbufFormat)
-> Ptr PixbufFormat -> IO PixbufFormat
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr PixbufFormat -> PixbufFormat
GdkPixbuf.PixbufFormat.PixbufFormat) Ptr PixbufFormat
val'
        PixbufFormat -> IO PixbufFormat
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufFormat
val''
    Maybe PixbufFormat -> IO (Maybe PixbufFormat)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PixbufFormat
result

-- | Set the value of the “@info@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' pixbufModule [ #info 'Data.GI.Base.Attributes.:=' value ]
-- @
setPixbufModuleInfo :: MonadIO m => PixbufModule -> Ptr GdkPixbuf.PixbufFormat.PixbufFormat -> m ()
setPixbufModuleInfo :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> Ptr PixbufFormat -> m ()
setPixbufModuleInfo PixbufModule
s Ptr PixbufFormat
val = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (Ptr PixbufFormat) -> Ptr PixbufFormat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (Ptr PixbufFormat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (Ptr PixbufFormat
val :: Ptr GdkPixbuf.PixbufFormat.PixbufFormat)

-- | Set the value of the “@info@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #info
-- @
clearPixbufModuleInfo :: MonadIO m => PixbufModule -> m ()
clearPixbufModuleInfo :: forall (m :: * -> *). MonadIO m => PixbufModule -> m ()
clearPixbufModuleInfo PixbufModule
s = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (Ptr PixbufFormat) -> Ptr PixbufFormat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (Ptr PixbufFormat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (Ptr PixbufFormat
forall a. Ptr a
FP.nullPtr :: Ptr GdkPixbuf.PixbufFormat.PixbufFormat)

#if defined(ENABLE_OVERLOADING)
data PixbufModuleInfoFieldInfo
instance AttrInfo PixbufModuleInfoFieldInfo where
    type AttrBaseTypeConstraint PixbufModuleInfoFieldInfo = (~) PixbufModule
    type AttrAllowedOps PixbufModuleInfoFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PixbufModuleInfoFieldInfo = (~) (Ptr GdkPixbuf.PixbufFormat.PixbufFormat)
    type AttrTransferTypeConstraint PixbufModuleInfoFieldInfo = (~)(Ptr GdkPixbuf.PixbufFormat.PixbufFormat)
    type AttrTransferType PixbufModuleInfoFieldInfo = (Ptr GdkPixbuf.PixbufFormat.PixbufFormat)
    type AttrGetType PixbufModuleInfoFieldInfo = Maybe GdkPixbuf.PixbufFormat.PixbufFormat
    type AttrLabel PixbufModuleInfoFieldInfo = "info"
    type AttrOrigin PixbufModuleInfoFieldInfo = PixbufModule
    attrGet = getPixbufModuleInfo
    attrSet = setPixbufModuleInfo
    attrConstruct = undefined
    attrClear = clearPixbufModuleInfo
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Structs.PixbufModule.info"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Structs-PixbufModule.html#g:attr:info"
        })

pixbufModule_info :: AttrLabelProxy "info"
pixbufModule_info = AttrLabelProxy

#endif


-- | Get the value of the “@load@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbufModule #load
-- @
getPixbufModuleLoad :: MonadIO m => PixbufModule -> m (Maybe GdkPixbuf.Callbacks.PixbufModuleLoadFunc)
getPixbufModuleLoad :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> m (Maybe PixbufModuleLoadFunc)
getPixbufModuleLoad PixbufModule
s = IO (Maybe PixbufModuleLoadFunc) -> m (Maybe PixbufModuleLoadFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PixbufModuleLoadFunc) -> m (Maybe PixbufModuleLoadFunc))
-> IO (Maybe PixbufModuleLoadFunc)
-> m (Maybe PixbufModuleLoadFunc)
forall a b. (a -> b) -> a -> b
$ PixbufModule
-> (Ptr PixbufModule -> IO (Maybe PixbufModuleLoadFunc))
-> IO (Maybe PixbufModuleLoadFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO (Maybe PixbufModuleLoadFunc))
 -> IO (Maybe PixbufModuleLoadFunc))
-> (Ptr PixbufModule -> IO (Maybe PixbufModuleLoadFunc))
-> IO (Maybe PixbufModuleLoadFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    FunPtr C_PixbufModuleLoadFunc
val <- Ptr (FunPtr C_PixbufModuleLoadFunc)
-> IO (FunPtr C_PixbufModuleLoadFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (FunPtr C_PixbufModuleLoadFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadFunc)
    Maybe PixbufModuleLoadFunc
result <- FunPtr C_PixbufModuleLoadFunc
-> (FunPtr C_PixbufModuleLoadFunc -> IO PixbufModuleLoadFunc)
-> IO (Maybe PixbufModuleLoadFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_PixbufModuleLoadFunc
val ((FunPtr C_PixbufModuleLoadFunc -> IO PixbufModuleLoadFunc)
 -> IO (Maybe PixbufModuleLoadFunc))
-> (FunPtr C_PixbufModuleLoadFunc -> IO PixbufModuleLoadFunc)
-> IO (Maybe PixbufModuleLoadFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_PixbufModuleLoadFunc
val' -> do
        let val'' :: PixbufModuleLoadFunc
val'' = FunPtr C_PixbufModuleLoadFunc -> PixbufModuleLoadFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_PixbufModuleLoadFunc -> Ptr () -> m Pixbuf
GdkPixbuf.Callbacks.dynamic_PixbufModuleLoadFunc FunPtr C_PixbufModuleLoadFunc
val'
        PixbufModuleLoadFunc -> IO PixbufModuleLoadFunc
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufModuleLoadFunc
val''
    Maybe PixbufModuleLoadFunc -> IO (Maybe PixbufModuleLoadFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PixbufModuleLoadFunc
result

-- | Set the value of the “@load@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' pixbufModule [ #load 'Data.GI.Base.Attributes.:=' value ]
-- @
setPixbufModuleLoad :: MonadIO m => PixbufModule -> FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadFunc -> m ()
setPixbufModuleLoad :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> FunPtr C_PixbufModuleLoadFunc -> m ()
setPixbufModuleLoad PixbufModule
s FunPtr C_PixbufModuleLoadFunc
val = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (FunPtr C_PixbufModuleLoadFunc)
-> FunPtr C_PixbufModuleLoadFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (FunPtr C_PixbufModuleLoadFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (FunPtr C_PixbufModuleLoadFunc
val :: FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadFunc)

-- | Set the value of the “@load@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #load
-- @
clearPixbufModuleLoad :: MonadIO m => PixbufModule -> m ()
clearPixbufModuleLoad :: forall (m :: * -> *). MonadIO m => PixbufModule -> m ()
clearPixbufModuleLoad PixbufModule
s = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (FunPtr C_PixbufModuleLoadFunc)
-> FunPtr C_PixbufModuleLoadFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (FunPtr C_PixbufModuleLoadFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (FunPtr C_PixbufModuleLoadFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadFunc)

#if defined(ENABLE_OVERLOADING)
data PixbufModuleLoadFieldInfo
instance AttrInfo PixbufModuleLoadFieldInfo where
    type AttrBaseTypeConstraint PixbufModuleLoadFieldInfo = (~) PixbufModule
    type AttrAllowedOps PixbufModuleLoadFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PixbufModuleLoadFieldInfo = (~) (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadFunc)
    type AttrTransferTypeConstraint PixbufModuleLoadFieldInfo = (~)(FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadFunc)
    type AttrTransferType PixbufModuleLoadFieldInfo = (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadFunc)
    type AttrGetType PixbufModuleLoadFieldInfo = Maybe GdkPixbuf.Callbacks.PixbufModuleLoadFunc
    type AttrLabel PixbufModuleLoadFieldInfo = "load"
    type AttrOrigin PixbufModuleLoadFieldInfo = PixbufModule
    attrGet = getPixbufModuleLoad
    attrSet = setPixbufModuleLoad
    attrConstruct = undefined
    attrClear = clearPixbufModuleLoad
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Structs.PixbufModule.load"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Structs-PixbufModule.html#g:attr:load"
        })

pixbufModule_load :: AttrLabelProxy "load"
pixbufModule_load = AttrLabelProxy

#endif


-- | Get the value of the “@load_xpm_data@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbufModule #loadXpmData
-- @
getPixbufModuleLoadXpmData :: MonadIO m => PixbufModule -> m (Maybe GdkPixbuf.Callbacks.PixbufModuleLoadXpmDataFunc)
getPixbufModuleLoadXpmData :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> m (Maybe PixbufModuleLoadXpmDataFunc)
getPixbufModuleLoadXpmData PixbufModule
s = IO (Maybe PixbufModuleLoadXpmDataFunc)
-> m (Maybe PixbufModuleLoadXpmDataFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PixbufModuleLoadXpmDataFunc)
 -> m (Maybe PixbufModuleLoadXpmDataFunc))
-> IO (Maybe PixbufModuleLoadXpmDataFunc)
-> m (Maybe PixbufModuleLoadXpmDataFunc)
forall a b. (a -> b) -> a -> b
$ PixbufModule
-> (Ptr PixbufModule -> IO (Maybe PixbufModuleLoadXpmDataFunc))
-> IO (Maybe PixbufModuleLoadXpmDataFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO (Maybe PixbufModuleLoadXpmDataFunc))
 -> IO (Maybe PixbufModuleLoadXpmDataFunc))
-> (Ptr PixbufModule -> IO (Maybe PixbufModuleLoadXpmDataFunc))
-> IO (Maybe PixbufModuleLoadXpmDataFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    FunPtr C_PixbufModuleLoadXpmDataFunc
val <- Ptr (FunPtr C_PixbufModuleLoadXpmDataFunc)
-> IO (FunPtr C_PixbufModuleLoadXpmDataFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr PixbufModule
ptr Ptr PixbufModule
-> Int -> Ptr (FunPtr C_PixbufModuleLoadXpmDataFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) :: IO (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadXpmDataFunc)
    Maybe PixbufModuleLoadXpmDataFunc
result <- FunPtr C_PixbufModuleLoadXpmDataFunc
-> (FunPtr C_PixbufModuleLoadXpmDataFunc
    -> IO PixbufModuleLoadXpmDataFunc)
-> IO (Maybe PixbufModuleLoadXpmDataFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_PixbufModuleLoadXpmDataFunc
val ((FunPtr C_PixbufModuleLoadXpmDataFunc
  -> IO PixbufModuleLoadXpmDataFunc)
 -> IO (Maybe PixbufModuleLoadXpmDataFunc))
-> (FunPtr C_PixbufModuleLoadXpmDataFunc
    -> IO PixbufModuleLoadXpmDataFunc)
-> IO (Maybe PixbufModuleLoadXpmDataFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_PixbufModuleLoadXpmDataFunc
val' -> do
        let val'' :: PixbufModuleLoadXpmDataFunc
val'' = FunPtr C_PixbufModuleLoadXpmDataFunc -> PixbufModuleLoadXpmDataFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_PixbufModuleLoadXpmDataFunc -> [Text] -> m Pixbuf
GdkPixbuf.Callbacks.dynamic_PixbufModuleLoadXpmDataFunc FunPtr C_PixbufModuleLoadXpmDataFunc
val'
        PixbufModuleLoadXpmDataFunc -> IO PixbufModuleLoadXpmDataFunc
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufModuleLoadXpmDataFunc
val''
    Maybe PixbufModuleLoadXpmDataFunc
-> IO (Maybe PixbufModuleLoadXpmDataFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PixbufModuleLoadXpmDataFunc
result

-- | Set the value of the “@load_xpm_data@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' pixbufModule [ #loadXpmData 'Data.GI.Base.Attributes.:=' value ]
-- @
setPixbufModuleLoadXpmData :: MonadIO m => PixbufModule -> FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadXpmDataFunc -> m ()
setPixbufModuleLoadXpmData :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> FunPtr C_PixbufModuleLoadXpmDataFunc -> m ()
setPixbufModuleLoadXpmData PixbufModule
s FunPtr C_PixbufModuleLoadXpmDataFunc
val = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (FunPtr C_PixbufModuleLoadXpmDataFunc)
-> FunPtr C_PixbufModuleLoadXpmDataFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule
-> Int -> Ptr (FunPtr C_PixbufModuleLoadXpmDataFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (FunPtr C_PixbufModuleLoadXpmDataFunc
val :: FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadXpmDataFunc)

-- | Set the value of the “@load_xpm_data@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #loadXpmData
-- @
clearPixbufModuleLoadXpmData :: MonadIO m => PixbufModule -> m ()
clearPixbufModuleLoadXpmData :: forall (m :: * -> *). MonadIO m => PixbufModule -> m ()
clearPixbufModuleLoadXpmData PixbufModule
s = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (FunPtr C_PixbufModuleLoadXpmDataFunc)
-> FunPtr C_PixbufModuleLoadXpmDataFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule
-> Int -> Ptr (FunPtr C_PixbufModuleLoadXpmDataFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (FunPtr C_PixbufModuleLoadXpmDataFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadXpmDataFunc)

#if defined(ENABLE_OVERLOADING)
data PixbufModuleLoadXpmDataFieldInfo
instance AttrInfo PixbufModuleLoadXpmDataFieldInfo where
    type AttrBaseTypeConstraint PixbufModuleLoadXpmDataFieldInfo = (~) PixbufModule
    type AttrAllowedOps PixbufModuleLoadXpmDataFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PixbufModuleLoadXpmDataFieldInfo = (~) (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadXpmDataFunc)
    type AttrTransferTypeConstraint PixbufModuleLoadXpmDataFieldInfo = (~)GdkPixbuf.Callbacks.PixbufModuleLoadXpmDataFunc
    type AttrTransferType PixbufModuleLoadXpmDataFieldInfo = (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadXpmDataFunc)
    type AttrGetType PixbufModuleLoadXpmDataFieldInfo = Maybe GdkPixbuf.Callbacks.PixbufModuleLoadXpmDataFunc
    type AttrLabel PixbufModuleLoadXpmDataFieldInfo = "load_xpm_data"
    type AttrOrigin PixbufModuleLoadXpmDataFieldInfo = PixbufModule
    attrGet = getPixbufModuleLoadXpmData
    attrSet = setPixbufModuleLoadXpmData
    attrConstruct = undefined
    attrClear = clearPixbufModuleLoadXpmData
    attrTransfer _ v = do
        GdkPixbuf.Callbacks.mk_PixbufModuleLoadXpmDataFunc (GdkPixbuf.Callbacks.wrap_PixbufModuleLoadXpmDataFunc Nothing v)
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Structs.PixbufModule.loadXpmData"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Structs-PixbufModule.html#g:attr:loadXpmData"
        })

pixbufModule_loadXpmData :: AttrLabelProxy "loadXpmData"
pixbufModule_loadXpmData = AttrLabelProxy

#endif


-- | Get the value of the “@stop_load@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbufModule #stopLoad
-- @
getPixbufModuleStopLoad :: MonadIO m => PixbufModule -> m (Maybe GdkPixbuf.Callbacks.PixbufModuleStopLoadFunc)
getPixbufModuleStopLoad :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> m (Maybe PixbufModuleStopLoadFunc)
getPixbufModuleStopLoad PixbufModule
s = IO (Maybe PixbufModuleStopLoadFunc)
-> m (Maybe PixbufModuleStopLoadFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PixbufModuleStopLoadFunc)
 -> m (Maybe PixbufModuleStopLoadFunc))
-> IO (Maybe PixbufModuleStopLoadFunc)
-> m (Maybe PixbufModuleStopLoadFunc)
forall a b. (a -> b) -> a -> b
$ PixbufModule
-> (Ptr PixbufModule -> IO (Maybe PixbufModuleStopLoadFunc))
-> IO (Maybe PixbufModuleStopLoadFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO (Maybe PixbufModuleStopLoadFunc))
 -> IO (Maybe PixbufModuleStopLoadFunc))
-> (Ptr PixbufModule -> IO (Maybe PixbufModuleStopLoadFunc))
-> IO (Maybe PixbufModuleStopLoadFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    FunPtr C_PixbufModuleStopLoadFunc
val <- Ptr (FunPtr C_PixbufModuleStopLoadFunc)
-> IO (FunPtr C_PixbufModuleStopLoadFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (FunPtr C_PixbufModuleStopLoadFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) :: IO (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleStopLoadFunc)
    Maybe PixbufModuleStopLoadFunc
result <- FunPtr C_PixbufModuleStopLoadFunc
-> (FunPtr C_PixbufModuleStopLoadFunc
    -> IO PixbufModuleStopLoadFunc)
-> IO (Maybe PixbufModuleStopLoadFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_PixbufModuleStopLoadFunc
val ((FunPtr C_PixbufModuleStopLoadFunc -> IO PixbufModuleStopLoadFunc)
 -> IO (Maybe PixbufModuleStopLoadFunc))
-> (FunPtr C_PixbufModuleStopLoadFunc
    -> IO PixbufModuleStopLoadFunc)
-> IO (Maybe PixbufModuleStopLoadFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_PixbufModuleStopLoadFunc
val' -> do
        let val'' :: PixbufModuleStopLoadFunc
val'' = FunPtr C_PixbufModuleStopLoadFunc -> PixbufModuleStopLoadFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_PixbufModuleStopLoadFunc -> Ptr () -> m ()
GdkPixbuf.Callbacks.dynamic_PixbufModuleStopLoadFunc FunPtr C_PixbufModuleStopLoadFunc
val'
        PixbufModuleStopLoadFunc -> IO PixbufModuleStopLoadFunc
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufModuleStopLoadFunc
val''
    Maybe PixbufModuleStopLoadFunc
-> IO (Maybe PixbufModuleStopLoadFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PixbufModuleStopLoadFunc
result

-- | Set the value of the “@stop_load@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' pixbufModule [ #stopLoad 'Data.GI.Base.Attributes.:=' value ]
-- @
setPixbufModuleStopLoad :: MonadIO m => PixbufModule -> FunPtr GdkPixbuf.Callbacks.C_PixbufModuleStopLoadFunc -> m ()
setPixbufModuleStopLoad :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> FunPtr C_PixbufModuleStopLoadFunc -> m ()
setPixbufModuleStopLoad PixbufModule
s FunPtr C_PixbufModuleStopLoadFunc
val = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (FunPtr C_PixbufModuleStopLoadFunc)
-> FunPtr C_PixbufModuleStopLoadFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (FunPtr C_PixbufModuleStopLoadFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (FunPtr C_PixbufModuleStopLoadFunc
val :: FunPtr GdkPixbuf.Callbacks.C_PixbufModuleStopLoadFunc)

-- | Set the value of the “@stop_load@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #stopLoad
-- @
clearPixbufModuleStopLoad :: MonadIO m => PixbufModule -> m ()
clearPixbufModuleStopLoad :: forall (m :: * -> *). MonadIO m => PixbufModule -> m ()
clearPixbufModuleStopLoad PixbufModule
s = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (FunPtr C_PixbufModuleStopLoadFunc)
-> FunPtr C_PixbufModuleStopLoadFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (FunPtr C_PixbufModuleStopLoadFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (FunPtr C_PixbufModuleStopLoadFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GdkPixbuf.Callbacks.C_PixbufModuleStopLoadFunc)

#if defined(ENABLE_OVERLOADING)
data PixbufModuleStopLoadFieldInfo
instance AttrInfo PixbufModuleStopLoadFieldInfo where
    type AttrBaseTypeConstraint PixbufModuleStopLoadFieldInfo = (~) PixbufModule
    type AttrAllowedOps PixbufModuleStopLoadFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PixbufModuleStopLoadFieldInfo = (~) (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleStopLoadFunc)
    type AttrTransferTypeConstraint PixbufModuleStopLoadFieldInfo = (~)(FunPtr GdkPixbuf.Callbacks.C_PixbufModuleStopLoadFunc)
    type AttrTransferType PixbufModuleStopLoadFieldInfo = (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleStopLoadFunc)
    type AttrGetType PixbufModuleStopLoadFieldInfo = Maybe GdkPixbuf.Callbacks.PixbufModuleStopLoadFunc
    type AttrLabel PixbufModuleStopLoadFieldInfo = "stop_load"
    type AttrOrigin PixbufModuleStopLoadFieldInfo = PixbufModule
    attrGet = getPixbufModuleStopLoad
    attrSet = setPixbufModuleStopLoad
    attrConstruct = undefined
    attrClear = clearPixbufModuleStopLoad
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Structs.PixbufModule.stopLoad"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Structs-PixbufModule.html#g:attr:stopLoad"
        })

pixbufModule_stopLoad :: AttrLabelProxy "stopLoad"
pixbufModule_stopLoad = AttrLabelProxy

#endif


-- | Get the value of the “@load_increment@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbufModule #loadIncrement
-- @
getPixbufModuleLoadIncrement :: MonadIO m => PixbufModule -> m (Maybe GdkPixbuf.Callbacks.PixbufModuleIncrementLoadFunc)
getPixbufModuleLoadIncrement :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> m (Maybe PixbufModuleIncrementLoadFunc)
getPixbufModuleLoadIncrement PixbufModule
s = IO (Maybe PixbufModuleIncrementLoadFunc)
-> m (Maybe PixbufModuleIncrementLoadFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PixbufModuleIncrementLoadFunc)
 -> m (Maybe PixbufModuleIncrementLoadFunc))
-> IO (Maybe PixbufModuleIncrementLoadFunc)
-> m (Maybe PixbufModuleIncrementLoadFunc)
forall a b. (a -> b) -> a -> b
$ PixbufModule
-> (Ptr PixbufModule -> IO (Maybe PixbufModuleIncrementLoadFunc))
-> IO (Maybe PixbufModuleIncrementLoadFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO (Maybe PixbufModuleIncrementLoadFunc))
 -> IO (Maybe PixbufModuleIncrementLoadFunc))
-> (Ptr PixbufModule -> IO (Maybe PixbufModuleIncrementLoadFunc))
-> IO (Maybe PixbufModuleIncrementLoadFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    FunPtr C_PixbufModuleIncrementLoadFunc
val <- Ptr (FunPtr C_PixbufModuleIncrementLoadFunc)
-> IO (FunPtr C_PixbufModuleIncrementLoadFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr PixbufModule
ptr Ptr PixbufModule
-> Int -> Ptr (FunPtr C_PixbufModuleIncrementLoadFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) :: IO (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleIncrementLoadFunc)
    Maybe PixbufModuleIncrementLoadFunc
result <- FunPtr C_PixbufModuleIncrementLoadFunc
-> (FunPtr C_PixbufModuleIncrementLoadFunc
    -> IO PixbufModuleIncrementLoadFunc)
-> IO (Maybe PixbufModuleIncrementLoadFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_PixbufModuleIncrementLoadFunc
val ((FunPtr C_PixbufModuleIncrementLoadFunc
  -> IO PixbufModuleIncrementLoadFunc)
 -> IO (Maybe PixbufModuleIncrementLoadFunc))
-> (FunPtr C_PixbufModuleIncrementLoadFunc
    -> IO PixbufModuleIncrementLoadFunc)
-> IO (Maybe PixbufModuleIncrementLoadFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_PixbufModuleIncrementLoadFunc
val' -> do
        let val'' :: PixbufModuleIncrementLoadFunc
val'' = FunPtr C_PixbufModuleIncrementLoadFunc
-> PixbufModuleIncrementLoadFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_PixbufModuleIncrementLoadFunc
-> Ptr () -> ByteString -> m ()
GdkPixbuf.Callbacks.dynamic_PixbufModuleIncrementLoadFunc FunPtr C_PixbufModuleIncrementLoadFunc
val'
        PixbufModuleIncrementLoadFunc -> IO PixbufModuleIncrementLoadFunc
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufModuleIncrementLoadFunc
val''
    Maybe PixbufModuleIncrementLoadFunc
-> IO (Maybe PixbufModuleIncrementLoadFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PixbufModuleIncrementLoadFunc
result

-- | Set the value of the “@load_increment@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' pixbufModule [ #loadIncrement 'Data.GI.Base.Attributes.:=' value ]
-- @
setPixbufModuleLoadIncrement :: MonadIO m => PixbufModule -> FunPtr GdkPixbuf.Callbacks.C_PixbufModuleIncrementLoadFunc -> m ()
setPixbufModuleLoadIncrement :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> FunPtr C_PixbufModuleIncrementLoadFunc -> m ()
setPixbufModuleLoadIncrement PixbufModule
s FunPtr C_PixbufModuleIncrementLoadFunc
val = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (FunPtr C_PixbufModuleIncrementLoadFunc)
-> FunPtr C_PixbufModuleIncrementLoadFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule
-> Int -> Ptr (FunPtr C_PixbufModuleIncrementLoadFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) (FunPtr C_PixbufModuleIncrementLoadFunc
val :: FunPtr GdkPixbuf.Callbacks.C_PixbufModuleIncrementLoadFunc)

-- | Set the value of the “@load_increment@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #loadIncrement
-- @
clearPixbufModuleLoadIncrement :: MonadIO m => PixbufModule -> m ()
clearPixbufModuleLoadIncrement :: forall (m :: * -> *). MonadIO m => PixbufModule -> m ()
clearPixbufModuleLoadIncrement PixbufModule
s = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (FunPtr C_PixbufModuleIncrementLoadFunc)
-> FunPtr C_PixbufModuleIncrementLoadFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule
-> Int -> Ptr (FunPtr C_PixbufModuleIncrementLoadFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) (FunPtr C_PixbufModuleIncrementLoadFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GdkPixbuf.Callbacks.C_PixbufModuleIncrementLoadFunc)

#if defined(ENABLE_OVERLOADING)
data PixbufModuleLoadIncrementFieldInfo
instance AttrInfo PixbufModuleLoadIncrementFieldInfo where
    type AttrBaseTypeConstraint PixbufModuleLoadIncrementFieldInfo = (~) PixbufModule
    type AttrAllowedOps PixbufModuleLoadIncrementFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PixbufModuleLoadIncrementFieldInfo = (~) (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleIncrementLoadFunc)
    type AttrTransferTypeConstraint PixbufModuleLoadIncrementFieldInfo = (~)(FunPtr GdkPixbuf.Callbacks.C_PixbufModuleIncrementLoadFunc)
    type AttrTransferType PixbufModuleLoadIncrementFieldInfo = (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleIncrementLoadFunc)
    type AttrGetType PixbufModuleLoadIncrementFieldInfo = Maybe GdkPixbuf.Callbacks.PixbufModuleIncrementLoadFunc
    type AttrLabel PixbufModuleLoadIncrementFieldInfo = "load_increment"
    type AttrOrigin PixbufModuleLoadIncrementFieldInfo = PixbufModule
    attrGet = getPixbufModuleLoadIncrement
    attrSet = setPixbufModuleLoadIncrement
    attrConstruct = undefined
    attrClear = clearPixbufModuleLoadIncrement
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Structs.PixbufModule.loadIncrement"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Structs-PixbufModule.html#g:attr:loadIncrement"
        })

pixbufModule_loadIncrement :: AttrLabelProxy "loadIncrement"
pixbufModule_loadIncrement = AttrLabelProxy

#endif


-- | Get the value of the “@load_animation@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbufModule #loadAnimation
-- @
getPixbufModuleLoadAnimation :: MonadIO m => PixbufModule -> m (Maybe GdkPixbuf.Callbacks.PixbufModuleLoadAnimationFunc)
getPixbufModuleLoadAnimation :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> m (Maybe PixbufModuleLoadAnimationFunc)
getPixbufModuleLoadAnimation PixbufModule
s = IO (Maybe PixbufModuleLoadAnimationFunc)
-> m (Maybe PixbufModuleLoadAnimationFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PixbufModuleLoadAnimationFunc)
 -> m (Maybe PixbufModuleLoadAnimationFunc))
-> IO (Maybe PixbufModuleLoadAnimationFunc)
-> m (Maybe PixbufModuleLoadAnimationFunc)
forall a b. (a -> b) -> a -> b
$ PixbufModule
-> (Ptr PixbufModule -> IO (Maybe PixbufModuleLoadAnimationFunc))
-> IO (Maybe PixbufModuleLoadAnimationFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO (Maybe PixbufModuleLoadAnimationFunc))
 -> IO (Maybe PixbufModuleLoadAnimationFunc))
-> (Ptr PixbufModule -> IO (Maybe PixbufModuleLoadAnimationFunc))
-> IO (Maybe PixbufModuleLoadAnimationFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    FunPtr C_PixbufModuleLoadAnimationFunc
val <- Ptr (FunPtr C_PixbufModuleLoadAnimationFunc)
-> IO (FunPtr C_PixbufModuleLoadAnimationFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr PixbufModule
ptr Ptr PixbufModule
-> Int -> Ptr (FunPtr C_PixbufModuleLoadAnimationFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72) :: IO (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadAnimationFunc)
    Maybe PixbufModuleLoadAnimationFunc
result <- FunPtr C_PixbufModuleLoadAnimationFunc
-> (FunPtr C_PixbufModuleLoadAnimationFunc
    -> IO PixbufModuleLoadAnimationFunc)
-> IO (Maybe PixbufModuleLoadAnimationFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_PixbufModuleLoadAnimationFunc
val ((FunPtr C_PixbufModuleLoadAnimationFunc
  -> IO PixbufModuleLoadAnimationFunc)
 -> IO (Maybe PixbufModuleLoadAnimationFunc))
-> (FunPtr C_PixbufModuleLoadAnimationFunc
    -> IO PixbufModuleLoadAnimationFunc)
-> IO (Maybe PixbufModuleLoadAnimationFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_PixbufModuleLoadAnimationFunc
val' -> do
        let val'' :: PixbufModuleLoadAnimationFunc
val'' = FunPtr C_PixbufModuleLoadAnimationFunc
-> PixbufModuleLoadAnimationFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_PixbufModuleLoadAnimationFunc
-> Ptr () -> m PixbufAnimation
GdkPixbuf.Callbacks.dynamic_PixbufModuleLoadAnimationFunc FunPtr C_PixbufModuleLoadAnimationFunc
val'
        PixbufModuleLoadAnimationFunc -> IO PixbufModuleLoadAnimationFunc
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufModuleLoadAnimationFunc
val''
    Maybe PixbufModuleLoadAnimationFunc
-> IO (Maybe PixbufModuleLoadAnimationFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PixbufModuleLoadAnimationFunc
result

-- | Set the value of the “@load_animation@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' pixbufModule [ #loadAnimation 'Data.GI.Base.Attributes.:=' value ]
-- @
setPixbufModuleLoadAnimation :: MonadIO m => PixbufModule -> FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadAnimationFunc -> m ()
setPixbufModuleLoadAnimation :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> FunPtr C_PixbufModuleLoadAnimationFunc -> m ()
setPixbufModuleLoadAnimation PixbufModule
s FunPtr C_PixbufModuleLoadAnimationFunc
val = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (FunPtr C_PixbufModuleLoadAnimationFunc)
-> FunPtr C_PixbufModuleLoadAnimationFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule
-> Int -> Ptr (FunPtr C_PixbufModuleLoadAnimationFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72) (FunPtr C_PixbufModuleLoadAnimationFunc
val :: FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadAnimationFunc)

-- | Set the value of the “@load_animation@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #loadAnimation
-- @
clearPixbufModuleLoadAnimation :: MonadIO m => PixbufModule -> m ()
clearPixbufModuleLoadAnimation :: forall (m :: * -> *). MonadIO m => PixbufModule -> m ()
clearPixbufModuleLoadAnimation PixbufModule
s = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (FunPtr C_PixbufModuleLoadAnimationFunc)
-> FunPtr C_PixbufModuleLoadAnimationFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule
-> Int -> Ptr (FunPtr C_PixbufModuleLoadAnimationFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72) (FunPtr C_PixbufModuleLoadAnimationFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadAnimationFunc)

#if defined(ENABLE_OVERLOADING)
data PixbufModuleLoadAnimationFieldInfo
instance AttrInfo PixbufModuleLoadAnimationFieldInfo where
    type AttrBaseTypeConstraint PixbufModuleLoadAnimationFieldInfo = (~) PixbufModule
    type AttrAllowedOps PixbufModuleLoadAnimationFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PixbufModuleLoadAnimationFieldInfo = (~) (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadAnimationFunc)
    type AttrTransferTypeConstraint PixbufModuleLoadAnimationFieldInfo = (~)(FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadAnimationFunc)
    type AttrTransferType PixbufModuleLoadAnimationFieldInfo = (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleLoadAnimationFunc)
    type AttrGetType PixbufModuleLoadAnimationFieldInfo = Maybe GdkPixbuf.Callbacks.PixbufModuleLoadAnimationFunc
    type AttrLabel PixbufModuleLoadAnimationFieldInfo = "load_animation"
    type AttrOrigin PixbufModuleLoadAnimationFieldInfo = PixbufModule
    attrGet = getPixbufModuleLoadAnimation
    attrSet = setPixbufModuleLoadAnimation
    attrConstruct = undefined
    attrClear = clearPixbufModuleLoadAnimation
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Structs.PixbufModule.loadAnimation"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Structs-PixbufModule.html#g:attr:loadAnimation"
        })

pixbufModule_loadAnimation :: AttrLabelProxy "loadAnimation"
pixbufModule_loadAnimation = AttrLabelProxy

#endif


-- | Get the value of the “@save@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbufModule #save
-- @
getPixbufModuleSave :: MonadIO m => PixbufModule -> m (Maybe GdkPixbuf.Callbacks.PixbufModuleSaveFunc)
getPixbufModuleSave :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> m (Maybe PixbufModuleSaveFunc)
getPixbufModuleSave PixbufModule
s = IO (Maybe PixbufModuleSaveFunc) -> m (Maybe PixbufModuleSaveFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PixbufModuleSaveFunc) -> m (Maybe PixbufModuleSaveFunc))
-> IO (Maybe PixbufModuleSaveFunc)
-> m (Maybe PixbufModuleSaveFunc)
forall a b. (a -> b) -> a -> b
$ PixbufModule
-> (Ptr PixbufModule -> IO (Maybe PixbufModuleSaveFunc))
-> IO (Maybe PixbufModuleSaveFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO (Maybe PixbufModuleSaveFunc))
 -> IO (Maybe PixbufModuleSaveFunc))
-> (Ptr PixbufModule -> IO (Maybe PixbufModuleSaveFunc))
-> IO (Maybe PixbufModuleSaveFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    FunPtr C_PixbufModuleSaveFunc
val <- Ptr (FunPtr C_PixbufModuleSaveFunc)
-> IO (FunPtr C_PixbufModuleSaveFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (FunPtr C_PixbufModuleSaveFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80) :: IO (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleSaveFunc)
    Maybe PixbufModuleSaveFunc
result <- FunPtr C_PixbufModuleSaveFunc
-> (FunPtr C_PixbufModuleSaveFunc -> IO PixbufModuleSaveFunc)
-> IO (Maybe PixbufModuleSaveFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_PixbufModuleSaveFunc
val ((FunPtr C_PixbufModuleSaveFunc -> IO PixbufModuleSaveFunc)
 -> IO (Maybe PixbufModuleSaveFunc))
-> (FunPtr C_PixbufModuleSaveFunc -> IO PixbufModuleSaveFunc)
-> IO (Maybe PixbufModuleSaveFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_PixbufModuleSaveFunc
val' -> do
        let val'' :: PixbufModuleSaveFunc
val'' = FunPtr C_PixbufModuleSaveFunc -> PixbufModuleSaveFunc
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPixbuf a) =>
FunPtr C_PixbufModuleSaveFunc
-> Ptr () -> a -> Maybe [Text] -> Maybe [Text] -> m ()
GdkPixbuf.Callbacks.dynamic_PixbufModuleSaveFunc FunPtr C_PixbufModuleSaveFunc
val'
        PixbufModuleSaveFunc -> IO PixbufModuleSaveFunc
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufModuleSaveFunc
val''
    Maybe PixbufModuleSaveFunc -> IO (Maybe PixbufModuleSaveFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PixbufModuleSaveFunc
result

-- | Set the value of the “@save@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' pixbufModule [ #save 'Data.GI.Base.Attributes.:=' value ]
-- @
setPixbufModuleSave :: MonadIO m => PixbufModule -> FunPtr GdkPixbuf.Callbacks.C_PixbufModuleSaveFunc -> m ()
setPixbufModuleSave :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> FunPtr C_PixbufModuleSaveFunc -> m ()
setPixbufModuleSave PixbufModule
s FunPtr C_PixbufModuleSaveFunc
val = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (FunPtr C_PixbufModuleSaveFunc)
-> FunPtr C_PixbufModuleSaveFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (FunPtr C_PixbufModuleSaveFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80) (FunPtr C_PixbufModuleSaveFunc
val :: FunPtr GdkPixbuf.Callbacks.C_PixbufModuleSaveFunc)

-- | Set the value of the “@save@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #save
-- @
clearPixbufModuleSave :: MonadIO m => PixbufModule -> m ()
clearPixbufModuleSave :: forall (m :: * -> *). MonadIO m => PixbufModule -> m ()
clearPixbufModuleSave PixbufModule
s = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (FunPtr C_PixbufModuleSaveFunc)
-> FunPtr C_PixbufModuleSaveFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule -> Int -> Ptr (FunPtr C_PixbufModuleSaveFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80) (FunPtr C_PixbufModuleSaveFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GdkPixbuf.Callbacks.C_PixbufModuleSaveFunc)

#if defined(ENABLE_OVERLOADING)
data PixbufModuleSaveFieldInfo
instance AttrInfo PixbufModuleSaveFieldInfo where
    type AttrBaseTypeConstraint PixbufModuleSaveFieldInfo = (~) PixbufModule
    type AttrAllowedOps PixbufModuleSaveFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PixbufModuleSaveFieldInfo = (~) (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleSaveFunc)
    type AttrTransferTypeConstraint PixbufModuleSaveFieldInfo = (~)(FunPtr GdkPixbuf.Callbacks.C_PixbufModuleSaveFunc)
    type AttrTransferType PixbufModuleSaveFieldInfo = (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleSaveFunc)
    type AttrGetType PixbufModuleSaveFieldInfo = Maybe GdkPixbuf.Callbacks.PixbufModuleSaveFunc
    type AttrLabel PixbufModuleSaveFieldInfo = "save"
    type AttrOrigin PixbufModuleSaveFieldInfo = PixbufModule
    attrGet = getPixbufModuleSave
    attrSet = setPixbufModuleSave
    attrConstruct = undefined
    attrClear = clearPixbufModuleSave
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Structs.PixbufModule.save"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Structs-PixbufModule.html#g:attr:save"
        })

pixbufModule_save :: AttrLabelProxy "save"
pixbufModule_save = AttrLabelProxy

#endif


-- | Get the value of the “@is_save_option_supported@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' pixbufModule #isSaveOptionSupported
-- @
getPixbufModuleIsSaveOptionSupported :: MonadIO m => PixbufModule -> m (Maybe GdkPixbuf.Callbacks.PixbufModuleSaveOptionSupportedFunc)
getPixbufModuleIsSaveOptionSupported :: forall (m :: * -> *).
MonadIO m =>
PixbufModule -> m (Maybe PixbufModuleSaveOptionSupportedFunc)
getPixbufModuleIsSaveOptionSupported PixbufModule
s = IO (Maybe PixbufModuleSaveOptionSupportedFunc)
-> m (Maybe PixbufModuleSaveOptionSupportedFunc)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PixbufModuleSaveOptionSupportedFunc)
 -> m (Maybe PixbufModuleSaveOptionSupportedFunc))
-> IO (Maybe PixbufModuleSaveOptionSupportedFunc)
-> m (Maybe PixbufModuleSaveOptionSupportedFunc)
forall a b. (a -> b) -> a -> b
$ PixbufModule
-> (Ptr PixbufModule
    -> IO (Maybe PixbufModuleSaveOptionSupportedFunc))
-> IO (Maybe PixbufModuleSaveOptionSupportedFunc)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule
  -> IO (Maybe PixbufModuleSaveOptionSupportedFunc))
 -> IO (Maybe PixbufModuleSaveOptionSupportedFunc))
-> (Ptr PixbufModule
    -> IO (Maybe PixbufModuleSaveOptionSupportedFunc))
-> IO (Maybe PixbufModuleSaveOptionSupportedFunc)
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    FunPtr C_PixbufModuleSaveOptionSupportedFunc
val <- Ptr (FunPtr C_PixbufModuleSaveOptionSupportedFunc)
-> IO (FunPtr C_PixbufModuleSaveOptionSupportedFunc)
forall a. Storable a => Ptr a -> IO a
peek (Ptr PixbufModule
ptr Ptr PixbufModule
-> Int -> Ptr (FunPtr C_PixbufModuleSaveOptionSupportedFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96) :: IO (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleSaveOptionSupportedFunc)
    Maybe PixbufModuleSaveOptionSupportedFunc
result <- FunPtr C_PixbufModuleSaveOptionSupportedFunc
-> (FunPtr C_PixbufModuleSaveOptionSupportedFunc
    -> IO PixbufModuleSaveOptionSupportedFunc)
-> IO (Maybe PixbufModuleSaveOptionSupportedFunc)
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr C_PixbufModuleSaveOptionSupportedFunc
val ((FunPtr C_PixbufModuleSaveOptionSupportedFunc
  -> IO PixbufModuleSaveOptionSupportedFunc)
 -> IO (Maybe PixbufModuleSaveOptionSupportedFunc))
-> (FunPtr C_PixbufModuleSaveOptionSupportedFunc
    -> IO PixbufModuleSaveOptionSupportedFunc)
-> IO (Maybe PixbufModuleSaveOptionSupportedFunc)
forall a b. (a -> b) -> a -> b
$ \FunPtr C_PixbufModuleSaveOptionSupportedFunc
val' -> do
        let val'' :: PixbufModuleSaveOptionSupportedFunc
val'' = FunPtr C_PixbufModuleSaveOptionSupportedFunc
-> PixbufModuleSaveOptionSupportedFunc
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_PixbufModuleSaveOptionSupportedFunc -> Text -> m Bool
GdkPixbuf.Callbacks.dynamic_PixbufModuleSaveOptionSupportedFunc FunPtr C_PixbufModuleSaveOptionSupportedFunc
val'
        PixbufModuleSaveOptionSupportedFunc
-> IO PixbufModuleSaveOptionSupportedFunc
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PixbufModuleSaveOptionSupportedFunc
val''
    Maybe PixbufModuleSaveOptionSupportedFunc
-> IO (Maybe PixbufModuleSaveOptionSupportedFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PixbufModuleSaveOptionSupportedFunc
result

-- | Set the value of the “@is_save_option_supported@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' pixbufModule [ #isSaveOptionSupported 'Data.GI.Base.Attributes.:=' value ]
-- @
setPixbufModuleIsSaveOptionSupported :: MonadIO m => PixbufModule -> FunPtr GdkPixbuf.Callbacks.C_PixbufModuleSaveOptionSupportedFunc -> m ()
setPixbufModuleIsSaveOptionSupported :: forall (m :: * -> *).
MonadIO m =>
PixbufModule
-> FunPtr C_PixbufModuleSaveOptionSupportedFunc -> m ()
setPixbufModuleIsSaveOptionSupported PixbufModule
s FunPtr C_PixbufModuleSaveOptionSupportedFunc
val = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (FunPtr C_PixbufModuleSaveOptionSupportedFunc)
-> FunPtr C_PixbufModuleSaveOptionSupportedFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule
-> Int -> Ptr (FunPtr C_PixbufModuleSaveOptionSupportedFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96) (FunPtr C_PixbufModuleSaveOptionSupportedFunc
val :: FunPtr GdkPixbuf.Callbacks.C_PixbufModuleSaveOptionSupportedFunc)

-- | Set the value of the “@is_save_option_supported@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #isSaveOptionSupported
-- @
clearPixbufModuleIsSaveOptionSupported :: MonadIO m => PixbufModule -> m ()
clearPixbufModuleIsSaveOptionSupported :: forall (m :: * -> *). MonadIO m => PixbufModule -> m ()
clearPixbufModuleIsSaveOptionSupported PixbufModule
s = 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
$ PixbufModule -> (Ptr PixbufModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr PixbufModule
s ((Ptr PixbufModule -> IO ()) -> IO ())
-> (Ptr PixbufModule -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr PixbufModule
ptr -> do
    Ptr (FunPtr C_PixbufModuleSaveOptionSupportedFunc)
-> FunPtr C_PixbufModuleSaveOptionSupportedFunc -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PixbufModule
ptr Ptr PixbufModule
-> Int -> Ptr (FunPtr C_PixbufModuleSaveOptionSupportedFunc)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96) (FunPtr C_PixbufModuleSaveOptionSupportedFunc
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GdkPixbuf.Callbacks.C_PixbufModuleSaveOptionSupportedFunc)

#if defined(ENABLE_OVERLOADING)
data PixbufModuleIsSaveOptionSupportedFieldInfo
instance AttrInfo PixbufModuleIsSaveOptionSupportedFieldInfo where
    type AttrBaseTypeConstraint PixbufModuleIsSaveOptionSupportedFieldInfo = (~) PixbufModule
    type AttrAllowedOps PixbufModuleIsSaveOptionSupportedFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint PixbufModuleIsSaveOptionSupportedFieldInfo = (~) (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleSaveOptionSupportedFunc)
    type AttrTransferTypeConstraint PixbufModuleIsSaveOptionSupportedFieldInfo = (~)GdkPixbuf.Callbacks.PixbufModuleSaveOptionSupportedFunc
    type AttrTransferType PixbufModuleIsSaveOptionSupportedFieldInfo = (FunPtr GdkPixbuf.Callbacks.C_PixbufModuleSaveOptionSupportedFunc)
    type AttrGetType PixbufModuleIsSaveOptionSupportedFieldInfo = Maybe GdkPixbuf.Callbacks.PixbufModuleSaveOptionSupportedFunc
    type AttrLabel PixbufModuleIsSaveOptionSupportedFieldInfo = "is_save_option_supported"
    type AttrOrigin PixbufModuleIsSaveOptionSupportedFieldInfo = PixbufModule
    attrGet = getPixbufModuleIsSaveOptionSupported
    attrSet = setPixbufModuleIsSaveOptionSupported
    attrConstruct = undefined
    attrClear = clearPixbufModuleIsSaveOptionSupported
    attrTransfer _ v = do
        GdkPixbuf.Callbacks.mk_PixbufModuleSaveOptionSupportedFunc (GdkPixbuf.Callbacks.wrap_PixbufModuleSaveOptionSupportedFunc Nothing v)
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GdkPixbuf.Structs.PixbufModule.isSaveOptionSupported"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdkpixbuf-2.0.29/docs/GI-GdkPixbuf-Structs-PixbufModule.html#g:attr:isSaveOptionSupported"
        })

pixbufModule_isSaveOptionSupported :: AttrLabelProxy "isSaveOptionSupported"
pixbufModule_isSaveOptionSupported = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PixbufModule
type instance O.AttributeList PixbufModule = PixbufModuleAttributeList
type PixbufModuleAttributeList = ('[ '("moduleName", PixbufModuleModuleNameFieldInfo), '("modulePath", PixbufModuleModulePathFieldInfo), '("module", PixbufModuleModuleFieldInfo), '("info", PixbufModuleInfoFieldInfo), '("load", PixbufModuleLoadFieldInfo), '("loadXpmData", PixbufModuleLoadXpmDataFieldInfo), '("stopLoad", PixbufModuleStopLoadFieldInfo), '("loadIncrement", PixbufModuleLoadIncrementFieldInfo), '("loadAnimation", PixbufModuleLoadAnimationFieldInfo), '("save", PixbufModuleSaveFieldInfo), '("isSaveOptionSupported", PixbufModuleIsSaveOptionSupportedFieldInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolvePixbufModuleMethod (t :: Symbol) (o :: *) :: * where
    ResolvePixbufModuleMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif