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

/No description available in the introspection data./
-}

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

module GI.OSTree.Structs.RepoPruneOptions
    (

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


 -- * Properties
-- ** flags #attr:flags#
{- | /No description available in the introspection data./
-}
    getRepoPruneOptionsFlags                ,
#if ENABLE_OVERLOADING
    repoPruneOptions_flags                  ,
#endif
    setRepoPruneOptionsFlags                ,


-- ** reachable #attr:reachable#
{- | /No description available in the introspection data./
-}
    clearRepoPruneOptionsReachable          ,
    getRepoPruneOptionsReachable            ,
#if 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.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.Enums as OSTree.Enums

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `RepoPruneOptions`.
noRepoPruneOptions :: Maybe RepoPruneOptions
noRepoPruneOptions = Nothing

{- |
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.Enums.RepoPruneFlags
getRepoPruneOptionsFlags s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CUInt
    let val' = (toEnum . fromIntegral) val
    return 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.Enums.RepoPruneFlags -> m ()
setRepoPruneOptionsFlags s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = (fromIntegral . fromEnum) val
    poke (ptr `plusPtr` 0) (val' :: CUInt)

#if ENABLE_OVERLOADING
data RepoPruneOptionsFlagsFieldInfo
instance AttrInfo RepoPruneOptionsFlagsFieldInfo where
    type AttrAllowedOps RepoPruneOptionsFlagsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint RepoPruneOptionsFlagsFieldInfo = (~) OSTree.Enums.RepoPruneFlags
    type AttrBaseTypeConstraint RepoPruneOptionsFlagsFieldInfo = (~) RepoPruneOptions
    type AttrGetType RepoPruneOptionsFlagsFieldInfo = OSTree.Enums.RepoPruneFlags
    type AttrLabel RepoPruneOptionsFlagsFieldInfo = "flags"
    type AttrOrigin RepoPruneOptionsFlagsFieldInfo = RepoPruneOptions
    attrGet _ = getRepoPruneOptionsFlags
    attrSet _ = setRepoPruneOptionsFlags
    attrConstruct = undefined
    attrClear _ = undefined

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 s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO (Ptr (GHashTable (Ptr ()) (Ptr ())))
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- unpackGHashTable val'
        let val''' = mapFirst ptrUnpackPtr val''
        let val'''' = mapSecond ptrUnpackPtr val'''
        let val''''' = Map.fromList val''''
        return val'''''
    return 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 s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (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 s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr (GHashTable (Ptr ()) (Ptr ())))

#if ENABLE_OVERLOADING
data RepoPruneOptionsReachableFieldInfo
instance AttrInfo RepoPruneOptionsReachableFieldInfo where
    type AttrAllowedOps RepoPruneOptionsReachableFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint RepoPruneOptionsReachableFieldInfo = (~) (Ptr (GHashTable (Ptr ()) (Ptr ())))
    type AttrBaseTypeConstraint RepoPruneOptionsReachableFieldInfo = (~) RepoPruneOptions
    type AttrGetType RepoPruneOptionsReachableFieldInfo = Maybe (Map.Map (Ptr ()) (Ptr ()))
    type AttrLabel RepoPruneOptionsReachableFieldInfo = "reachable"
    type AttrOrigin RepoPruneOptionsReachableFieldInfo = RepoPruneOptions
    attrGet _ = getRepoPruneOptionsReachable
    attrSet _ = setRepoPruneOptionsReachable
    attrConstruct = undefined
    attrClear _ = clearRepoPruneOptionsReachable

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 ENABLE_OVERLOADING
instance O.HasAttributeList RepoPruneOptions
type instance O.AttributeList RepoPruneOptions = RepoPruneOptionsAttributeList
type RepoPruneOptionsAttributeList = ('[ '("flags", RepoPruneOptionsFlagsFieldInfo), '("reachable", RepoPruneOptionsReachableFieldInfo)] :: [(Symbol, *)])
#endif

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

instance (info ~ ResolveRepoPruneOptionsMethod t RepoPruneOptions, O.MethodInfo info RepoPruneOptions p) => OL.IsLabel t (RepoPruneOptions -> 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