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

A structure containing the result of a map operation such as
'GI.Gst.Structs.Memory.memoryMap'. It contains the data and size.
-}

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

module GI.Gst.Structs.MapInfo
    (

-- * Exported types
    MapInfo(..)                             ,
    newZeroMapInfo                          ,
    noMapInfo                               ,


 -- * Properties
-- ** flags #attr:flags#
{- | flags used when mapping the memory
-}
    getMapInfoFlags                         ,
#if ENABLE_OVERLOADING
    mapInfo_flags                           ,
#endif
    setMapInfoFlags                         ,


-- ** maxsize #attr:maxsize#
{- | the maximum bytes in /@data@/
-}
    getMapInfoMaxsize                       ,
#if ENABLE_OVERLOADING
    mapInfo_maxsize                         ,
#endif
    setMapInfoMaxsize                       ,


-- ** memory #attr:memory#
{- | a pointer to the mapped memory
-}
    clearMapInfoMemory                      ,
    getMapInfoMemory                        ,
#if ENABLE_OVERLOADING
    mapInfo_memory                          ,
#endif
    setMapInfoMemory                        ,


-- ** size #attr:size#
{- | the valid size in /@data@/
-}
    getMapInfoSize                          ,
#if ENABLE_OVERLOADING
    mapInfo_size                            ,
#endif
    setMapInfoSize                          ,




    ) 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.Gst.Flags as Gst.Flags
import {-# SOURCE #-} qualified GI.Gst.Structs.Memory as Gst.Memory

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `MapInfo`.
noMapInfo :: Maybe MapInfo
noMapInfo = Nothing

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

@
'Data.GI.Base.Attributes.get' mapInfo #memory
@
-}
getMapInfoMemory :: MonadIO m => MapInfo -> m (Maybe Gst.Memory.Memory)
getMapInfoMemory s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO (Ptr Gst.Memory.Memory)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newBoxed Gst.Memory.Memory) val'
        return val''
    return result

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

@
'Data.GI.Base.Attributes.set' mapInfo [ #memory 'Data.GI.Base.Attributes.:=' value ]
@
-}
setMapInfoMemory :: MonadIO m => MapInfo -> Ptr Gst.Memory.Memory -> m ()
setMapInfoMemory s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Ptr Gst.Memory.Memory)

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

#if ENABLE_OVERLOADING
data MapInfoMemoryFieldInfo
instance AttrInfo MapInfoMemoryFieldInfo where
    type AttrAllowedOps MapInfoMemoryFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint MapInfoMemoryFieldInfo = (~) (Ptr Gst.Memory.Memory)
    type AttrBaseTypeConstraint MapInfoMemoryFieldInfo = (~) MapInfo
    type AttrGetType MapInfoMemoryFieldInfo = Maybe Gst.Memory.Memory
    type AttrLabel MapInfoMemoryFieldInfo = "memory"
    type AttrOrigin MapInfoMemoryFieldInfo = MapInfo
    attrGet _ = getMapInfoMemory
    attrSet _ = setMapInfoMemory
    attrConstruct = undefined
    attrClear _ = clearMapInfoMemory

mapInfo_memory :: AttrLabelProxy "memory"
mapInfo_memory = AttrLabelProxy

#endif


{- |
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' mapInfo #flags
@
-}
getMapInfoFlags :: MonadIO m => MapInfo -> m [Gst.Flags.MapFlags]
getMapInfoFlags s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CUInt
    let val' = wordToGFlags 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' mapInfo [ #flags 'Data.GI.Base.Attributes.:=' value ]
@
-}
setMapInfoFlags :: MonadIO m => MapInfo -> [Gst.Flags.MapFlags] -> m ()
setMapInfoFlags s val = liftIO $ withManagedPtr s $ \ptr -> do
    let val' = gflagsToWord val
    poke (ptr `plusPtr` 8) (val' :: CUInt)

#if ENABLE_OVERLOADING
data MapInfoFlagsFieldInfo
instance AttrInfo MapInfoFlagsFieldInfo where
    type AttrAllowedOps MapInfoFlagsFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint MapInfoFlagsFieldInfo = (~) [Gst.Flags.MapFlags]
    type AttrBaseTypeConstraint MapInfoFlagsFieldInfo = (~) MapInfo
    type AttrGetType MapInfoFlagsFieldInfo = [Gst.Flags.MapFlags]
    type AttrLabel MapInfoFlagsFieldInfo = "flags"
    type AttrOrigin MapInfoFlagsFieldInfo = MapInfo
    attrGet _ = getMapInfoFlags
    attrSet _ = setMapInfoFlags
    attrConstruct = undefined
    attrClear _ = undefined

mapInfo_flags :: AttrLabelProxy "flags"
mapInfo_flags = AttrLabelProxy

#endif


-- XXX Skipped attribute for "MapInfo:data" :: Not implemented: "Don't know how to unpack C array of type TCArray False (-1) 3 (TBasicType TUInt8)"
{- |
Get the value of the “@size@” field.
When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to

@
'Data.GI.Base.Attributes.get' mapInfo #size
@
-}
getMapInfoSize :: MonadIO m => MapInfo -> m Word64
getMapInfoSize s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO Word64
    return val

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

@
'Data.GI.Base.Attributes.set' mapInfo [ #size 'Data.GI.Base.Attributes.:=' value ]
@
-}
setMapInfoSize :: MonadIO m => MapInfo -> Word64 -> m ()
setMapInfoSize s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 24) (val :: Word64)

#if ENABLE_OVERLOADING
data MapInfoSizeFieldInfo
instance AttrInfo MapInfoSizeFieldInfo where
    type AttrAllowedOps MapInfoSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint MapInfoSizeFieldInfo = (~) Word64
    type AttrBaseTypeConstraint MapInfoSizeFieldInfo = (~) MapInfo
    type AttrGetType MapInfoSizeFieldInfo = Word64
    type AttrLabel MapInfoSizeFieldInfo = "size"
    type AttrOrigin MapInfoSizeFieldInfo = MapInfo
    attrGet _ = getMapInfoSize
    attrSet _ = setMapInfoSize
    attrConstruct = undefined
    attrClear _ = undefined

mapInfo_size :: AttrLabelProxy "size"
mapInfo_size = AttrLabelProxy

#endif


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

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

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

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

#if ENABLE_OVERLOADING
data MapInfoMaxsizeFieldInfo
instance AttrInfo MapInfoMaxsizeFieldInfo where
    type AttrAllowedOps MapInfoMaxsizeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint MapInfoMaxsizeFieldInfo = (~) Word64
    type AttrBaseTypeConstraint MapInfoMaxsizeFieldInfo = (~) MapInfo
    type AttrGetType MapInfoMaxsizeFieldInfo = Word64
    type AttrLabel MapInfoMaxsizeFieldInfo = "maxsize"
    type AttrOrigin MapInfoMaxsizeFieldInfo = MapInfo
    attrGet _ = getMapInfoMaxsize
    attrSet _ = setMapInfoMaxsize
    attrConstruct = undefined
    attrClear _ = undefined

mapInfo_maxsize :: AttrLabelProxy "maxsize"
mapInfo_maxsize = AttrLabelProxy

#endif


-- XXX Skipped attribute for "MapInfo:user_data" :: Not implemented: "Don't know how to unpack C array of type TCArray False 4 (-1) (TBasicType TPtr)"

#if ENABLE_OVERLOADING
instance O.HasAttributeList MapInfo
type instance O.AttributeList MapInfo = MapInfoAttributeList
type MapInfoAttributeList = ('[ '("memory", MapInfoMemoryFieldInfo), '("flags", MapInfoFlagsFieldInfo), '("size", MapInfoSizeFieldInfo), '("maxsize", MapInfoMaxsizeFieldInfo)] :: [(Symbol, *)])
#endif

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

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