{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (inaki@blueleaf.cc)

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'.
-}

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

module GI.OSTree.Structs.DiffDirsOptions
    (

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


 -- * Properties
-- ** devinoToCsumCache #attr:devinoToCsumCache#
{- | /No description available in the introspection data./
-}
    clearDiffDirsOptionsDevinoToCsumCache   ,
#if ENABLE_OVERLOADING
    diffDirsOptions_devinoToCsumCache       ,
#endif
    getDiffDirsOptionsDevinoToCsumCache     ,
    setDiffDirsOptionsDevinoToCsumCache     ,


-- ** ownerGid #attr:ownerGid#
{- | /No description available in the introspection data./
-}
#if ENABLE_OVERLOADING
    diffDirsOptions_ownerGid                ,
#endif
    getDiffDirsOptionsOwnerGid              ,
    setDiffDirsOptionsOwnerGid              ,


-- ** ownerUid #attr:ownerUid#
{- | /No description available in the introspection data./
-}
#if 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.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 {-# SOURCE #-} qualified GI.OSTree.Structs.RepoDevInoCache as OSTree.RepoDevInoCache

-- | Memory-managed wrapper type.
newtype DiffDirsOptions = DiffDirsOptions (ManagedPtr DiffDirsOptions)
instance WrappedPtr DiffDirsOptions where
    wrappedPtrCalloc = callocBytes 128
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 128 >=> wrapPtr DiffDirsOptions)
    wrappedPtrFree = Just ptr_to_g_free

-- | Construct a `DiffDirsOptions` struct initialized to zero.
newZeroDiffDirsOptions :: MonadIO m => m DiffDirsOptions
newZeroDiffDirsOptions = liftIO $ wrappedPtrCalloc >>= wrapPtr DiffDirsOptions

instance tag ~ 'AttrSet => Constructible DiffDirsOptions tag where
    new _ attrs = do
        o <- newZeroDiffDirsOptions
        GI.Attributes.set o attrs
        return o


-- | A convenience alias for `Nothing` :: `Maybe` `DiffDirsOptions`.
noDiffDirsOptions :: Maybe DiffDirsOptions
noDiffDirsOptions = Nothing

{- |
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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Int32
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Int32)

#if ENABLE_OVERLOADING
data DiffDirsOptionsOwnerUidFieldInfo
instance AttrInfo DiffDirsOptionsOwnerUidFieldInfo where
    type AttrAllowedOps DiffDirsOptionsOwnerUidFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DiffDirsOptionsOwnerUidFieldInfo = (~) Int32
    type AttrBaseTypeConstraint DiffDirsOptionsOwnerUidFieldInfo = (~) DiffDirsOptions
    type AttrGetType DiffDirsOptionsOwnerUidFieldInfo = Int32
    type AttrLabel DiffDirsOptionsOwnerUidFieldInfo = "owner_uid"
    type AttrOrigin DiffDirsOptionsOwnerUidFieldInfo = DiffDirsOptions
    attrGet _ = getDiffDirsOptionsOwnerUid
    attrSet _ = setDiffDirsOptionsOwnerUid
    attrConstruct = undefined
    attrClear _ = undefined

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 4) :: IO Int32
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 4) (val :: Int32)

#if ENABLE_OVERLOADING
data DiffDirsOptionsOwnerGidFieldInfo
instance AttrInfo DiffDirsOptionsOwnerGidFieldInfo where
    type AttrAllowedOps DiffDirsOptionsOwnerGidFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint DiffDirsOptionsOwnerGidFieldInfo = (~) Int32
    type AttrBaseTypeConstraint DiffDirsOptionsOwnerGidFieldInfo = (~) DiffDirsOptions
    type AttrGetType DiffDirsOptionsOwnerGidFieldInfo = Int32
    type AttrLabel DiffDirsOptionsOwnerGidFieldInfo = "owner_gid"
    type AttrOrigin DiffDirsOptionsOwnerGidFieldInfo = DiffDirsOptions
    attrGet _ = getDiffDirsOptionsOwnerGid
    attrSet _ = setDiffDirsOptionsOwnerGid
    attrConstruct = undefined
    attrClear _ = undefined

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (Ptr OSTree.RepoDevInoCache.RepoDevInoCache)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newBoxed OSTree.RepoDevInoCache.RepoDevInoCache) val'
        return val''
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr OSTree.RepoDevInoCache.RepoDevInoCache)

#if ENABLE_OVERLOADING
data DiffDirsOptionsDevinoToCsumCacheFieldInfo
instance AttrInfo DiffDirsOptionsDevinoToCsumCacheFieldInfo where
    type AttrAllowedOps DiffDirsOptionsDevinoToCsumCacheFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint DiffDirsOptionsDevinoToCsumCacheFieldInfo = (~) (Ptr OSTree.RepoDevInoCache.RepoDevInoCache)
    type AttrBaseTypeConstraint DiffDirsOptionsDevinoToCsumCacheFieldInfo = (~) DiffDirsOptions
    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

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 ENABLE_OVERLOADING
instance O.HasAttributeList DiffDirsOptions
type instance O.AttributeList DiffDirsOptions = DiffDirsOptionsAttributeList
type DiffDirsOptionsAttributeList = ('[ '("ownerUid", DiffDirsOptionsOwnerUidFieldInfo), '("ownerGid", DiffDirsOptionsOwnerGidFieldInfo), '("devinoToCsumCache", DiffDirsOptionsDevinoToCsumCacheFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif