{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.OSTree.Structs.RepoPruneOptions
    ( 

-- * Exported types
    RepoPruneOptions(..)                    ,
    newZeroRepoPruneOptions                 ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveRepoPruneOptionsMethod           ,
#endif



 -- * Properties


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

    getRepoPruneOptionsFlags                ,
#if defined(ENABLE_OVERLOADING)
    repoPruneOptions_flags                  ,
#endif
    setRepoPruneOptionsFlags                ,


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

    clearRepoPruneOptionsReachable          ,
    getRepoPruneOptionsReachable            ,
#if defined(ENABLE_OVERLOADING)
    repoPruneOptions_reachable              ,
#endif
    setRepoPruneOptionsReachable            ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.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.Flags as OSTree.Flags

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

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

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


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

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


-- | Get the value of the “@flags@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' repoPruneOptions #flags
-- @
getRepoPruneOptionsFlags :: MonadIO m => RepoPruneOptions -> m [OSTree.Flags.RepoPruneFlags]
getRepoPruneOptionsFlags :: forall (m :: * -> *).
MonadIO m =>
RepoPruneOptions -> m [RepoPruneFlags]
getRepoPruneOptionsFlags RepoPruneOptions
s = IO [RepoPruneFlags] -> m [RepoPruneFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [RepoPruneFlags] -> m [RepoPruneFlags])
-> IO [RepoPruneFlags] -> m [RepoPruneFlags]
forall a b. (a -> b) -> a -> b
$ RepoPruneOptions
-> (Ptr RepoPruneOptions -> IO [RepoPruneFlags])
-> IO [RepoPruneFlags]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RepoPruneOptions
s ((Ptr RepoPruneOptions -> IO [RepoPruneFlags])
 -> IO [RepoPruneFlags])
-> (Ptr RepoPruneOptions -> IO [RepoPruneFlags])
-> IO [RepoPruneFlags]
forall a b. (a -> b) -> a -> b
$ \Ptr RepoPruneOptions
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr RepoPruneOptions
ptr Ptr RepoPruneOptions -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CUInt
    let val' :: [RepoPruneFlags]
val' = CUInt -> [RepoPruneFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
val
    [RepoPruneFlags] -> IO [RepoPruneFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [RepoPruneFlags]
val'

-- | Set the value of the “@flags@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' repoPruneOptions [ #flags 'Data.GI.Base.Attributes.:=' value ]
-- @
setRepoPruneOptionsFlags :: MonadIO m => RepoPruneOptions -> [OSTree.Flags.RepoPruneFlags] -> m ()
setRepoPruneOptionsFlags :: forall (m :: * -> *).
MonadIO m =>
RepoPruneOptions -> [RepoPruneFlags] -> m ()
setRepoPruneOptionsFlags RepoPruneOptions
s [RepoPruneFlags]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ RepoPruneOptions -> (Ptr RepoPruneOptions -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RepoPruneOptions
s ((Ptr RepoPruneOptions -> IO ()) -> IO ())
-> (Ptr RepoPruneOptions -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr RepoPruneOptions
ptr -> do
    let val' :: CUInt
val' = [RepoPruneFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [RepoPruneFlags]
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr RepoPruneOptions
ptr Ptr RepoPruneOptions -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CUInt
val' :: CUInt)

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

repoPruneOptions_flags :: AttrLabelProxy "flags"
repoPruneOptions_flags = AttrLabelProxy

#endif


-- | Get the value of the “@reachable@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' repoPruneOptions #reachable
-- @
getRepoPruneOptionsReachable :: MonadIO m => RepoPruneOptions -> m (Maybe (Map.Map (Ptr ()) (Ptr ())))
getRepoPruneOptionsReachable :: forall (m :: * -> *).
MonadIO m =>
RepoPruneOptions -> m (Maybe (Map (Ptr ()) (Ptr ())))
getRepoPruneOptionsReachable RepoPruneOptions
s = IO (Maybe (Map (Ptr ()) (Ptr ())))
-> m (Maybe (Map (Ptr ()) (Ptr ())))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe (Map (Ptr ()) (Ptr ())))
 -> m (Maybe (Map (Ptr ()) (Ptr ()))))
-> IO (Maybe (Map (Ptr ()) (Ptr ())))
-> m (Maybe (Map (Ptr ()) (Ptr ())))
forall a b. (a -> b) -> a -> b
$ RepoPruneOptions
-> (Ptr RepoPruneOptions -> IO (Maybe (Map (Ptr ()) (Ptr ()))))
-> IO (Maybe (Map (Ptr ()) (Ptr ())))
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr RepoPruneOptions
s ((Ptr RepoPruneOptions -> IO (Maybe (Map (Ptr ()) (Ptr ()))))
 -> IO (Maybe (Map (Ptr ()) (Ptr ()))))
-> (Ptr RepoPruneOptions -> IO (Maybe (Map (Ptr ()) (Ptr ()))))
-> IO (Maybe (Map (Ptr ()) (Ptr ())))
forall a b. (a -> b) -> a -> b
$ \Ptr RepoPruneOptions
ptr -> do
    Ptr (GHashTable (Ptr ()) (Ptr ()))
val <- Ptr (Ptr (GHashTable (Ptr ()) (Ptr ())))
-> IO (Ptr (GHashTable (Ptr ()) (Ptr ())))
forall a. Storable a => Ptr a -> IO a
peek (Ptr RepoPruneOptions
ptr Ptr RepoPruneOptions
-> Int -> Ptr (Ptr (GHashTable (Ptr ()) (Ptr ())))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO (Ptr (GHashTable (Ptr ()) (Ptr ())))
    Maybe (Map (Ptr ()) (Ptr ()))
result <- Ptr (GHashTable (Ptr ()) (Ptr ()))
-> (Ptr (GHashTable (Ptr ()) (Ptr ()))
    -> IO (Map (Ptr ()) (Ptr ())))
-> IO (Maybe (Map (Ptr ()) (Ptr ())))
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr (GHashTable (Ptr ()) (Ptr ()))
val ((Ptr (GHashTable (Ptr ()) (Ptr ())) -> IO (Map (Ptr ()) (Ptr ())))
 -> IO (Maybe (Map (Ptr ()) (Ptr ()))))
-> (Ptr (GHashTable (Ptr ()) (Ptr ()))
    -> IO (Map (Ptr ()) (Ptr ())))
-> IO (Maybe (Map (Ptr ()) (Ptr ())))
forall a b. (a -> b) -> a -> b
$ \Ptr (GHashTable (Ptr ()) (Ptr ()))
val' -> do
        [(PtrWrapped (Ptr ()), PtrWrapped (Ptr ()))]
val'' <- Ptr (GHashTable (Ptr ()) (Ptr ()))
-> IO [(PtrWrapped (Ptr ()), PtrWrapped (Ptr ()))]
forall a b.
Ptr (GHashTable a b) -> IO [(PtrWrapped a, PtrWrapped b)]
unpackGHashTable Ptr (GHashTable (Ptr ()) (Ptr ()))
val'
        let val''' :: [(Ptr (), PtrWrapped (Ptr ()))]
val''' = (PtrWrapped (Ptr ()) -> Ptr ())
-> [(PtrWrapped (Ptr ()), PtrWrapped (Ptr ()))]
-> [(Ptr (), PtrWrapped (Ptr ()))]
forall a c b. (a -> c) -> [(a, b)] -> [(c, b)]
mapFirst PtrWrapped (Ptr ()) -> Ptr ()
forall a. PtrWrapped (Ptr a) -> Ptr a
ptrUnpackPtr [(PtrWrapped (Ptr ()), PtrWrapped (Ptr ()))]
val''
        let val'''' :: [(Ptr (), Ptr ())]
val'''' = (PtrWrapped (Ptr ()) -> Ptr ())
-> [(Ptr (), PtrWrapped (Ptr ()))] -> [(Ptr (), Ptr ())]
forall b c a. (b -> c) -> [(a, b)] -> [(a, c)]
mapSecond PtrWrapped (Ptr ()) -> Ptr ()
forall a. PtrWrapped (Ptr a) -> Ptr a
ptrUnpackPtr [(Ptr (), PtrWrapped (Ptr ()))]
val'''
        let val''''' :: Map (Ptr ()) (Ptr ())
val''''' = [(Ptr (), Ptr ())] -> Map (Ptr ()) (Ptr ())
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Ptr (), Ptr ())]
val''''
        Map (Ptr ()) (Ptr ()) -> IO (Map (Ptr ()) (Ptr ()))
forall (m :: * -> *) a. Monad m => a -> m a
return Map (Ptr ()) (Ptr ())
val'''''
    Maybe (Map (Ptr ()) (Ptr ())) -> IO (Maybe (Map (Ptr ()) (Ptr ())))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (Map (Ptr ()) (Ptr ()))
result

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

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

#if defined(ENABLE_OVERLOADING)
data RepoPruneOptionsReachableFieldInfo
instance AttrInfo RepoPruneOptionsReachableFieldInfo where
    type AttrBaseTypeConstraint RepoPruneOptionsReachableFieldInfo = (~) RepoPruneOptions
    type AttrAllowedOps RepoPruneOptionsReachableFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint RepoPruneOptionsReachableFieldInfo = (~) (Ptr (GHashTable (Ptr ()) (Ptr ())))
    type AttrTransferTypeConstraint RepoPruneOptionsReachableFieldInfo = (~)(Ptr (GHashTable (Ptr ()) (Ptr ())))
    type AttrTransferType RepoPruneOptionsReachableFieldInfo = (Ptr (GHashTable (Ptr ()) (Ptr ())))
    type AttrGetType RepoPruneOptionsReachableFieldInfo = Maybe (Map.Map (Ptr ()) (Ptr ()))
    type AttrLabel RepoPruneOptionsReachableFieldInfo = "reachable"
    type AttrOrigin RepoPruneOptionsReachableFieldInfo = RepoPruneOptions
    attrGet = getRepoPruneOptionsReachable
    attrSet = setRepoPruneOptionsReachable
    attrConstruct = undefined
    attrClear = clearRepoPruneOptionsReachable
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.OSTree.Structs.RepoPruneOptions.reachable"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ostree-1.0.15/docs/GI-OSTree-Structs-RepoPruneOptions.html#g:attr:reachable"
        })

repoPruneOptions_reachable :: AttrLabelProxy "reachable"
repoPruneOptions_reachable = AttrLabelProxy

#endif


-- XXX Skipped attribute for "RepoPruneOptions:unused_bools"
-- Not implemented: Don't know how to unpack C array of type TCArray False 6 (-1) (TBasicType TBoolean)
-- XXX Skipped attribute for "RepoPruneOptions:unused_ints"
-- Not implemented: Don't know how to unpack C array of type TCArray False 6 (-1) (TBasicType TInt)
-- XXX Skipped attribute for "RepoPruneOptions: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 RepoPruneOptions
type instance O.AttributeList RepoPruneOptions = RepoPruneOptionsAttributeList
type RepoPruneOptionsAttributeList = ('[ '("flags", RepoPruneOptionsFlagsFieldInfo), '("reachable", RepoPruneOptionsReachableFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif

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

#endif