{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An extensible options structure controlling diff dirs. Make sure
-- that owner_uid\/gid is set to -1 when not used. This is used by
-- 'GI.OSTree.Functions.diffDirsWithOptions'.

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

module GI.OSTree.Structs.DiffDirsOptions
    ( 

-- * Exported types
    DiffDirsOptions(..)                     ,
    newZeroDiffDirsOptions                  ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveDiffDirsOptionsMethod            ,
#endif



 -- * Properties


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

    clearDiffDirsOptionsDevinoToCsumCache   ,
#if defined(ENABLE_OVERLOADING)
    diffDirsOptions_devinoToCsumCache       ,
#endif
    getDiffDirsOptionsDevinoToCsumCache     ,
    setDiffDirsOptionsDevinoToCsumCache     ,


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

#if defined(ENABLE_OVERLOADING)
    diffDirsOptions_ownerGid                ,
#endif
    getDiffDirsOptionsOwnerGid              ,
    setDiffDirsOptionsOwnerGid              ,


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

#if defined(ENABLE_OVERLOADING)
    diffDirsOptions_ownerUid                ,
#endif
    getDiffDirsOptionsOwnerUid              ,
    setDiffDirsOptionsOwnerUid              ,




    ) 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 {-# SOURCE #-} qualified GI.OSTree.Structs.RepoDevInoCache as OSTree.RepoDevInoCache

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

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

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


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

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


-- | Get the value of the “@owner_uid@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' diffDirsOptions #ownerUid
-- @
getDiffDirsOptionsOwnerUid :: MonadIO m => DiffDirsOptions -> m Int32
getDiffDirsOptionsOwnerUid :: forall (m :: * -> *). MonadIO m => DiffDirsOptions -> m Int32
getDiffDirsOptionsOwnerUid DiffDirsOptions
s = IO Int32 -> m Int32
forall a. IO a -> m a
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
$ DiffDirsOptions -> (Ptr DiffDirsOptions -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DiffDirsOptions
s ((Ptr DiffDirsOptions -> IO Int32) -> IO Int32)
-> (Ptr DiffDirsOptions -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr DiffDirsOptions
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr DiffDirsOptions
ptr Ptr DiffDirsOptions -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

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

#if defined(ENABLE_OVERLOADING)
data DiffDirsOptionsOwnerUidFieldInfo
instance AttrInfo DiffDirsOptionsOwnerUidFieldInfo where
    type AttrBaseTypeConstraint DiffDirsOptionsOwnerUidFieldInfo = (~) DiffDirsOptions
    type AttrAllowedOps DiffDirsOptionsOwnerUidFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DiffDirsOptionsOwnerUidFieldInfo = (~) Int32
    type AttrTransferTypeConstraint DiffDirsOptionsOwnerUidFieldInfo = (~)Int32
    type AttrTransferType DiffDirsOptionsOwnerUidFieldInfo = Int32
    type AttrGetType DiffDirsOptionsOwnerUidFieldInfo = Int32
    type AttrLabel DiffDirsOptionsOwnerUidFieldInfo = "owner_uid"
    type AttrOrigin DiffDirsOptionsOwnerUidFieldInfo = DiffDirsOptions
    attrGet = getDiffDirsOptionsOwnerUid
    attrSet = setDiffDirsOptionsOwnerUid
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Structs.DiffDirsOptions.ownerUid"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.16/docs/GI-OSTree-Structs-DiffDirsOptions.html#g:attr:ownerUid"
        })

diffDirsOptions_ownerUid :: AttrLabelProxy "ownerUid"
diffDirsOptions_ownerUid = AttrLabelProxy

#endif


-- | Get the value of the “@owner_gid@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' diffDirsOptions #ownerGid
-- @
getDiffDirsOptionsOwnerGid :: MonadIO m => DiffDirsOptions -> m Int32
getDiffDirsOptionsOwnerGid :: forall (m :: * -> *). MonadIO m => DiffDirsOptions -> m Int32
getDiffDirsOptionsOwnerGid DiffDirsOptions
s = IO Int32 -> m Int32
forall a. IO a -> m a
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
$ DiffDirsOptions -> (Ptr DiffDirsOptions -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DiffDirsOptions
s ((Ptr DiffDirsOptions -> IO Int32) -> IO Int32)
-> (Ptr DiffDirsOptions -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr DiffDirsOptions
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr DiffDirsOptions
ptr Ptr DiffDirsOptions -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

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

#if defined(ENABLE_OVERLOADING)
data DiffDirsOptionsOwnerGidFieldInfo
instance AttrInfo DiffDirsOptionsOwnerGidFieldInfo where
    type AttrBaseTypeConstraint DiffDirsOptionsOwnerGidFieldInfo = (~) DiffDirsOptions
    type AttrAllowedOps DiffDirsOptionsOwnerGidFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DiffDirsOptionsOwnerGidFieldInfo = (~) Int32
    type AttrTransferTypeConstraint DiffDirsOptionsOwnerGidFieldInfo = (~)Int32
    type AttrTransferType DiffDirsOptionsOwnerGidFieldInfo = Int32
    type AttrGetType DiffDirsOptionsOwnerGidFieldInfo = Int32
    type AttrLabel DiffDirsOptionsOwnerGidFieldInfo = "owner_gid"
    type AttrOrigin DiffDirsOptionsOwnerGidFieldInfo = DiffDirsOptions
    attrGet = getDiffDirsOptionsOwnerGid
    attrSet = setDiffDirsOptionsOwnerGid
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Structs.DiffDirsOptions.ownerGid"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.16/docs/GI-OSTree-Structs-DiffDirsOptions.html#g:attr:ownerGid"
        })

diffDirsOptions_ownerGid :: AttrLabelProxy "ownerGid"
diffDirsOptions_ownerGid = AttrLabelProxy

#endif


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

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

-- | Set the value of the “@devino_to_csum_cache@” 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' #devinoToCsumCache
-- @
clearDiffDirsOptionsDevinoToCsumCache :: MonadIO m => DiffDirsOptions -> m ()
clearDiffDirsOptionsDevinoToCsumCache :: forall (m :: * -> *). MonadIO m => DiffDirsOptions -> m ()
clearDiffDirsOptionsDevinoToCsumCache DiffDirsOptions
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
$ DiffDirsOptions -> (Ptr DiffDirsOptions -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr DiffDirsOptions
s ((Ptr DiffDirsOptions -> IO ()) -> IO ())
-> (Ptr DiffDirsOptions -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr DiffDirsOptions
ptr -> do
    Ptr (Ptr RepoDevInoCache) -> Ptr RepoDevInoCache -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DiffDirsOptions
ptr Ptr DiffDirsOptions -> Int -> Ptr (Ptr RepoDevInoCache)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr RepoDevInoCache
forall a. Ptr a
FP.nullPtr :: Ptr OSTree.RepoDevInoCache.RepoDevInoCache)

#if defined(ENABLE_OVERLOADING)
data DiffDirsOptionsDevinoToCsumCacheFieldInfo
instance AttrInfo DiffDirsOptionsDevinoToCsumCacheFieldInfo where
    type AttrBaseTypeConstraint DiffDirsOptionsDevinoToCsumCacheFieldInfo = (~) DiffDirsOptions
    type AttrAllowedOps DiffDirsOptionsDevinoToCsumCacheFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint DiffDirsOptionsDevinoToCsumCacheFieldInfo = (~) (Ptr OSTree.RepoDevInoCache.RepoDevInoCache)
    type AttrTransferTypeConstraint DiffDirsOptionsDevinoToCsumCacheFieldInfo = (~)(Ptr OSTree.RepoDevInoCache.RepoDevInoCache)
    type AttrTransferType DiffDirsOptionsDevinoToCsumCacheFieldInfo = (Ptr OSTree.RepoDevInoCache.RepoDevInoCache)
    type AttrGetType DiffDirsOptionsDevinoToCsumCacheFieldInfo = Maybe OSTree.RepoDevInoCache.RepoDevInoCache
    type AttrLabel DiffDirsOptionsDevinoToCsumCacheFieldInfo = "devino_to_csum_cache"
    type AttrOrigin DiffDirsOptionsDevinoToCsumCacheFieldInfo = DiffDirsOptions
    attrGet = getDiffDirsOptionsDevinoToCsumCache
    attrSet = setDiffDirsOptionsDevinoToCsumCache
    attrConstruct = undefined
    attrClear = clearDiffDirsOptionsDevinoToCsumCache
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Structs.DiffDirsOptions.devinoToCsumCache"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.16/docs/GI-OSTree-Structs-DiffDirsOptions.html#g:attr:devinoToCsumCache"
        })

diffDirsOptions_devinoToCsumCache :: AttrLabelProxy "devinoToCsumCache"
diffDirsOptions_devinoToCsumCache = AttrLabelProxy

#endif


-- XXX Skipped attribute for "DiffDirsOptions:unused_bools"
-- Not implemented: Don't know how to unpack C array of type TCArray False 7 (-1) (TBasicType TBoolean)
-- XXX Skipped attribute for "DiffDirsOptions:unused_ints"
-- Not implemented: Don't know how to unpack C array of type TCArray False 6 (-1) (TBasicType TInt)
-- XXX Skipped attribute for "DiffDirsOptions:unused_ptrs"
-- Not implemented: Don't know how to unpack C array of type TCArray False 7 (-1) (TBasicType TPtr)

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DiffDirsOptions
type instance O.AttributeList DiffDirsOptions = DiffDirsOptionsAttributeList
type DiffDirsOptionsAttributeList = ('[ '("ownerUid", DiffDirsOptionsOwnerUidFieldInfo), '("ownerGid", DiffDirsOptionsOwnerGidFieldInfo), '("devinoToCsumCache", DiffDirsOptionsDevinoToCsumCacheFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif

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

#endif