{- |
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.RollsumMatches
    (

-- * Exported types
    RollsumMatches(..)                      ,
    newZeroRollsumMatches                   ,
    noRollsumMatches                        ,


 -- * Properties
-- ** bufmatches #attr:bufmatches#
{- | /No description available in the introspection data./
-}
    getRollsumMatchesBufmatches             ,
#if ENABLE_OVERLOADING
    rollsumMatches_bufmatches               ,
#endif
    setRollsumMatchesBufmatches             ,


-- ** crcmatches #attr:crcmatches#
{- | /No description available in the introspection data./
-}
    getRollsumMatchesCrcmatches             ,
#if ENABLE_OVERLOADING
    rollsumMatches_crcmatches               ,
#endif
    setRollsumMatchesCrcmatches             ,


-- ** fromRollsums #attr:fromRollsums#
{- | /No description available in the introspection data./
-}
    clearRollsumMatchesFromRollsums         ,
    getRollsumMatchesFromRollsums           ,
#if ENABLE_OVERLOADING
    rollsumMatches_fromRollsums             ,
#endif
    setRollsumMatchesFromRollsums           ,


-- ** matchSize #attr:matchSize#
{- | /No description available in the introspection data./
-}
    getRollsumMatchesMatchSize              ,
#if ENABLE_OVERLOADING
    rollsumMatches_matchSize                ,
#endif
    setRollsumMatchesMatchSize              ,


-- ** matches #attr:matches#
{- | /No description available in the introspection data./
-}
    clearRollsumMatchesMatches              ,
    getRollsumMatchesMatches                ,
#if ENABLE_OVERLOADING
    rollsumMatches_matches                  ,
#endif
    setRollsumMatchesMatches                ,


-- ** toRollsums #attr:toRollsums#
{- | /No description available in the introspection data./
-}
    clearRollsumMatchesToRollsums           ,
    getRollsumMatchesToRollsums             ,
#if ENABLE_OVERLOADING
    rollsumMatches_toRollsums               ,
#endif
    setRollsumMatchesToRollsums             ,


-- ** total #attr:total#
{- | /No description available in the introspection data./
-}
    getRollsumMatchesTotal                  ,
#if ENABLE_OVERLOADING
    rollsumMatches_total                    ,
#endif
    setRollsumMatchesTotal                  ,




    ) 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


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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `RollsumMatches`.
noRollsumMatches :: Maybe RollsumMatches
noRollsumMatches = Nothing

{- |
Get the value of the “@from_rollsums@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' rollsumMatches #fromRollsums
@
-}
getRollsumMatchesFromRollsums :: MonadIO m => RollsumMatches -> m (Maybe (Map.Map (Ptr ()) (Ptr ())))
getRollsumMatchesFromRollsums s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: 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 “@from_rollsums@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' rollsumMatches [ #fromRollsums 'Data.GI.Base.Attributes.:=' value ]
@
-}
setRollsumMatchesFromRollsums :: MonadIO m => RollsumMatches -> Ptr (GHashTable (Ptr ()) (Ptr ())) -> m ()
setRollsumMatchesFromRollsums s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Ptr (GHashTable (Ptr ()) (Ptr ())))

{- |
Set the value of the “@from_rollsums@” 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' #fromRollsums
@
-}
clearRollsumMatchesFromRollsums :: MonadIO m => RollsumMatches -> m ()
clearRollsumMatchesFromRollsums s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullPtr :: Ptr (GHashTable (Ptr ()) (Ptr ())))

#if ENABLE_OVERLOADING
data RollsumMatchesFromRollsumsFieldInfo
instance AttrInfo RollsumMatchesFromRollsumsFieldInfo where
    type AttrAllowedOps RollsumMatchesFromRollsumsFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint RollsumMatchesFromRollsumsFieldInfo = (~) (Ptr (GHashTable (Ptr ()) (Ptr ())))
    type AttrBaseTypeConstraint RollsumMatchesFromRollsumsFieldInfo = (~) RollsumMatches
    type AttrGetType RollsumMatchesFromRollsumsFieldInfo = Maybe (Map.Map (Ptr ()) (Ptr ()))
    type AttrLabel RollsumMatchesFromRollsumsFieldInfo = "from_rollsums"
    type AttrOrigin RollsumMatchesFromRollsumsFieldInfo = RollsumMatches
    attrGet _ = getRollsumMatchesFromRollsums
    attrSet _ = setRollsumMatchesFromRollsums
    attrConstruct = undefined
    attrClear _ = clearRollsumMatchesFromRollsums

rollsumMatches_fromRollsums :: AttrLabelProxy "fromRollsums"
rollsumMatches_fromRollsums = AttrLabelProxy

#endif


{- |
Get the value of the “@to_rollsums@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' rollsumMatches #toRollsums
@
-}
getRollsumMatchesToRollsums :: MonadIO m => RollsumMatches -> m (Maybe (Map.Map (Ptr ()) (Ptr ())))
getRollsumMatchesToRollsums 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 “@to_rollsums@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' rollsumMatches [ #toRollsums 'Data.GI.Base.Attributes.:=' value ]
@
-}
setRollsumMatchesToRollsums :: MonadIO m => RollsumMatches -> Ptr (GHashTable (Ptr ()) (Ptr ())) -> m ()
setRollsumMatchesToRollsums s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (val :: Ptr (GHashTable (Ptr ()) (Ptr ())))

{- |
Set the value of the “@to_rollsums@” 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' #toRollsums
@
-}
clearRollsumMatchesToRollsums :: MonadIO m => RollsumMatches -> m ()
clearRollsumMatchesToRollsums s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr (GHashTable (Ptr ()) (Ptr ())))

#if ENABLE_OVERLOADING
data RollsumMatchesToRollsumsFieldInfo
instance AttrInfo RollsumMatchesToRollsumsFieldInfo where
    type AttrAllowedOps RollsumMatchesToRollsumsFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint RollsumMatchesToRollsumsFieldInfo = (~) (Ptr (GHashTable (Ptr ()) (Ptr ())))
    type AttrBaseTypeConstraint RollsumMatchesToRollsumsFieldInfo = (~) RollsumMatches
    type AttrGetType RollsumMatchesToRollsumsFieldInfo = Maybe (Map.Map (Ptr ()) (Ptr ()))
    type AttrLabel RollsumMatchesToRollsumsFieldInfo = "to_rollsums"
    type AttrOrigin RollsumMatchesToRollsumsFieldInfo = RollsumMatches
    attrGet _ = getRollsumMatchesToRollsums
    attrSet _ = setRollsumMatchesToRollsums
    attrConstruct = undefined
    attrClear _ = clearRollsumMatchesToRollsums

rollsumMatches_toRollsums :: AttrLabelProxy "toRollsums"
rollsumMatches_toRollsums = AttrLabelProxy

#endif


{- |
Get the value of the “@crcmatches@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' rollsumMatches #crcmatches
@
-}
getRollsumMatchesCrcmatches :: MonadIO m => RollsumMatches -> m Word32
getRollsumMatchesCrcmatches s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO Word32
    return val

{- |
Set the value of the “@crcmatches@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' rollsumMatches [ #crcmatches 'Data.GI.Base.Attributes.:=' value ]
@
-}
setRollsumMatchesCrcmatches :: MonadIO m => RollsumMatches -> Word32 -> m ()
setRollsumMatchesCrcmatches s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 16) (val :: Word32)

#if ENABLE_OVERLOADING
data RollsumMatchesCrcmatchesFieldInfo
instance AttrInfo RollsumMatchesCrcmatchesFieldInfo where
    type AttrAllowedOps RollsumMatchesCrcmatchesFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint RollsumMatchesCrcmatchesFieldInfo = (~) Word32
    type AttrBaseTypeConstraint RollsumMatchesCrcmatchesFieldInfo = (~) RollsumMatches
    type AttrGetType RollsumMatchesCrcmatchesFieldInfo = Word32
    type AttrLabel RollsumMatchesCrcmatchesFieldInfo = "crcmatches"
    type AttrOrigin RollsumMatchesCrcmatchesFieldInfo = RollsumMatches
    attrGet _ = getRollsumMatchesCrcmatches
    attrSet _ = setRollsumMatchesCrcmatches
    attrConstruct = undefined
    attrClear _ = undefined

rollsumMatches_crcmatches :: AttrLabelProxy "crcmatches"
rollsumMatches_crcmatches = AttrLabelProxy

#endif


{- |
Get the value of the “@bufmatches@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' rollsumMatches #bufmatches
@
-}
getRollsumMatchesBufmatches :: MonadIO m => RollsumMatches -> m Word32
getRollsumMatchesBufmatches s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 20) :: IO Word32
    return val

{- |
Set the value of the “@bufmatches@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' rollsumMatches [ #bufmatches 'Data.GI.Base.Attributes.:=' value ]
@
-}
setRollsumMatchesBufmatches :: MonadIO m => RollsumMatches -> Word32 -> m ()
setRollsumMatchesBufmatches s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 20) (val :: Word32)

#if ENABLE_OVERLOADING
data RollsumMatchesBufmatchesFieldInfo
instance AttrInfo RollsumMatchesBufmatchesFieldInfo where
    type AttrAllowedOps RollsumMatchesBufmatchesFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint RollsumMatchesBufmatchesFieldInfo = (~) Word32
    type AttrBaseTypeConstraint RollsumMatchesBufmatchesFieldInfo = (~) RollsumMatches
    type AttrGetType RollsumMatchesBufmatchesFieldInfo = Word32
    type AttrLabel RollsumMatchesBufmatchesFieldInfo = "bufmatches"
    type AttrOrigin RollsumMatchesBufmatchesFieldInfo = RollsumMatches
    attrGet _ = getRollsumMatchesBufmatches
    attrSet _ = setRollsumMatchesBufmatches
    attrConstruct = undefined
    attrClear _ = undefined

rollsumMatches_bufmatches :: AttrLabelProxy "bufmatches"
rollsumMatches_bufmatches = AttrLabelProxy

#endif


{- |
Get the value of the “@total@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' rollsumMatches #total
@
-}
getRollsumMatchesTotal :: MonadIO m => RollsumMatches -> m Word32
getRollsumMatchesTotal s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO Word32
    return val

{- |
Set the value of the “@total@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' rollsumMatches [ #total 'Data.GI.Base.Attributes.:=' value ]
@
-}
setRollsumMatchesTotal :: MonadIO m => RollsumMatches -> Word32 -> m ()
setRollsumMatchesTotal s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: Word32)

#if ENABLE_OVERLOADING
data RollsumMatchesTotalFieldInfo
instance AttrInfo RollsumMatchesTotalFieldInfo where
    type AttrAllowedOps RollsumMatchesTotalFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint RollsumMatchesTotalFieldInfo = (~) Word32
    type AttrBaseTypeConstraint RollsumMatchesTotalFieldInfo = (~) RollsumMatches
    type AttrGetType RollsumMatchesTotalFieldInfo = Word32
    type AttrLabel RollsumMatchesTotalFieldInfo = "total"
    type AttrOrigin RollsumMatchesTotalFieldInfo = RollsumMatches
    attrGet _ = getRollsumMatchesTotal
    attrSet _ = setRollsumMatchesTotal
    attrConstruct = undefined
    attrClear _ = undefined

rollsumMatches_total :: AttrLabelProxy "total"
rollsumMatches_total = AttrLabelProxy

#endif


{- |
Get the value of the “@match_size@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' rollsumMatches #matchSize
@
-}
getRollsumMatchesMatchSize :: MonadIO m => RollsumMatches -> m Word64
getRollsumMatchesMatchSize s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO Word64
    return val

{- |
Set the value of the “@match_size@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' rollsumMatches [ #matchSize 'Data.GI.Base.Attributes.:=' value ]
@
-}
setRollsumMatchesMatchSize :: MonadIO m => RollsumMatches -> Word64 -> m ()
setRollsumMatchesMatchSize s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 32) (val :: Word64)

#if ENABLE_OVERLOADING
data RollsumMatchesMatchSizeFieldInfo
instance AttrInfo RollsumMatchesMatchSizeFieldInfo where
    type AttrAllowedOps RollsumMatchesMatchSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint RollsumMatchesMatchSizeFieldInfo = (~) Word64
    type AttrBaseTypeConstraint RollsumMatchesMatchSizeFieldInfo = (~) RollsumMatches
    type AttrGetType RollsumMatchesMatchSizeFieldInfo = Word64
    type AttrLabel RollsumMatchesMatchSizeFieldInfo = "match_size"
    type AttrOrigin RollsumMatchesMatchSizeFieldInfo = RollsumMatches
    attrGet _ = getRollsumMatchesMatchSize
    attrSet _ = setRollsumMatchesMatchSize
    attrConstruct = undefined
    attrClear _ = undefined

rollsumMatches_matchSize :: AttrLabelProxy "matchSize"
rollsumMatches_matchSize = AttrLabelProxy

#endif


{- |
Get the value of the “@matches@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' rollsumMatches #matches
@
-}
getRollsumMatchesMatches :: MonadIO m => RollsumMatches -> m (Maybe ([Ptr ()]))
getRollsumMatchesMatches s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO (Ptr (GPtrArray (Ptr ())))
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- unpackGPtrArray val'
        return val''
    return result

{- |
Set the value of the “@matches@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.set' rollsumMatches [ #matches 'Data.GI.Base.Attributes.:=' value ]
@
-}
setRollsumMatchesMatches :: MonadIO m => RollsumMatches -> Ptr (GPtrArray (Ptr ())) -> m ()
setRollsumMatchesMatches s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (val :: Ptr (GPtrArray (Ptr ())))

{- |
Set the value of the “@matches@” 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' #matches
@
-}
clearRollsumMatchesMatches :: MonadIO m => RollsumMatches -> m ()
clearRollsumMatchesMatches s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 40) (FP.nullPtr :: Ptr (GPtrArray (Ptr ())))

#if ENABLE_OVERLOADING
data RollsumMatchesMatchesFieldInfo
instance AttrInfo RollsumMatchesMatchesFieldInfo where
    type AttrAllowedOps RollsumMatchesMatchesFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint RollsumMatchesMatchesFieldInfo = (~) (Ptr (GPtrArray (Ptr ())))
    type AttrBaseTypeConstraint RollsumMatchesMatchesFieldInfo = (~) RollsumMatches
    type AttrGetType RollsumMatchesMatchesFieldInfo = Maybe ([Ptr ()])
    type AttrLabel RollsumMatchesMatchesFieldInfo = "matches"
    type AttrOrigin RollsumMatchesMatchesFieldInfo = RollsumMatches
    attrGet _ = getRollsumMatchesMatches
    attrSet _ = setRollsumMatchesMatches
    attrConstruct = undefined
    attrClear _ = clearRollsumMatchesMatches

rollsumMatches_matches :: AttrLabelProxy "matches"
rollsumMatches_matches = AttrLabelProxy

#endif



#if ENABLE_OVERLOADING
instance O.HasAttributeList RollsumMatches
type instance O.AttributeList RollsumMatches = RollsumMatchesAttributeList
type RollsumMatchesAttributeList = ('[ '("fromRollsums", RollsumMatchesFromRollsumsFieldInfo), '("toRollsums", RollsumMatchesToRollsumsFieldInfo), '("crcmatches", RollsumMatchesCrcmatchesFieldInfo), '("bufmatches", RollsumMatchesBufmatchesFieldInfo), '("total", RollsumMatchesTotalFieldInfo), '("matchSize", RollsumMatchesMatchSizeFieldInfo), '("matches", RollsumMatchesMatchesFieldInfo)] :: [(Symbol, *)])
#endif

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

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