{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.OSTree.Structs.RepoPruneOptions
    ( 

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


 -- * Properties
-- ** flags #attr:flags#
    getRepoPruneOptionsFlags                ,
    repoPruneOptions_flags                  ,
    setRepoPruneOptionsFlags                ,


-- ** reachable #attr:reachable#
    clearRepoPruneOptionsReachable          ,
    getRepoPruneOptionsReachable            ,
    repoPruneOptions_reachable              ,
    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.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
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 {-# SOURCE #-} qualified GI.OSTree.Enums as OSTree.Enums

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


noRepoPruneOptions :: Maybe RepoPruneOptions
noRepoPruneOptions = Nothing

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'

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)

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


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

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 ())))

clearRepoPruneOptionsReachable :: MonadIO m => RepoPruneOptions -> m ()
clearRepoPruneOptionsReachable s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr (GHashTable (Ptr ()) (Ptr ())))

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


-- 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)"

instance O.HasAttributeList RepoPruneOptions
type instance O.AttributeList RepoPruneOptions = RepoPruneOptionsAttributeList
type RepoPruneOptionsAttributeList = ('[ '("flags", RepoPruneOptionsFlagsFieldInfo), '("reachable", RepoPruneOptionsReachableFieldInfo)] :: [(Symbol, *)])

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

instance (info ~ ResolveRepoPruneOptionsMethod t RepoPruneOptions, O.MethodInfo info RepoPruneOptions p) => O.IsLabelProxy t (RepoPruneOptions -> p) where
    fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveRepoPruneOptionsMethod t RepoPruneOptions, O.MethodInfo info RepoPruneOptions p) => O.IsLabel t (RepoPruneOptions -> p) where
    fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif