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

Each piece of memory that is pushed onto the stack
is cast to a GTrashStack*.
-}

module GI.GLib.Structs.TrashStack
    ( 

-- * Exported types
    TrashStack(..)                          ,
    newZeroTrashStack                       ,
    noTrashStack                            ,


 -- * Methods
-- ** height #method:height#
    trashStackHeight                        ,


-- ** peek #method:peek#
    trashStackPeek                          ,


-- ** pop #method:pop#
    trashStackPop                           ,


-- ** push #method:push#
    trashStackPush                          ,




 -- * Properties
-- ** next #attr:next#
    clearTrashStackNext                     ,
    getTrashStackNext                       ,
    setTrashStackNext                       ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
    trashStack_next                         ,
#endif




    ) 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


newtype TrashStack = TrashStack (ManagedPtr TrashStack)
instance WrappedPtr TrashStack where
    wrappedPtrCalloc = callocBytes 8
    wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 8 >=> wrapPtr TrashStack)
    wrappedPtrFree = Just ptr_to_g_free

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

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


noTrashStack :: Maybe TrashStack
noTrashStack = Nothing

getTrashStackNext :: MonadIO m => TrashStack -> m (Maybe TrashStack)
getTrashStackNext s = liftIO $ withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO (Ptr TrashStack)
    result <- SP.convertIfNonNull val $ \val' -> do
        val'' <- (newPtr TrashStack) val'
        return val''
    return result

setTrashStackNext :: MonadIO m => TrashStack -> Ptr TrashStack -> m ()
setTrashStackNext s val = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (val :: Ptr TrashStack)

clearTrashStackNext :: MonadIO m => TrashStack -> m ()
clearTrashStackNext s = liftIO $ withManagedPtr s $ \ptr -> do
    poke (ptr `plusPtr` 0) (FP.nullPtr :: Ptr TrashStack)

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data TrashStackNextFieldInfo
instance AttrInfo TrashStackNextFieldInfo where
    type AttrAllowedOps TrashStackNextFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint TrashStackNextFieldInfo = (~) (Ptr TrashStack)
    type AttrBaseTypeConstraint TrashStackNextFieldInfo = (~) TrashStack
    type AttrGetType TrashStackNextFieldInfo = Maybe TrashStack
    type AttrLabel TrashStackNextFieldInfo = "next"
    type AttrOrigin TrashStackNextFieldInfo = TrashStack
    attrGet _ = getTrashStackNext
    attrSet _ = setTrashStackNext
    attrConstruct = undefined
    attrClear _ = clearTrashStackNext

trashStack_next :: AttrLabelProxy "next"
trashStack_next = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
instance O.HasAttributeList TrashStack
type instance O.AttributeList TrashStack = TrashStackAttributeList
type TrashStackAttributeList = ('[ '("next", TrashStackNextFieldInfo)] :: [(Symbol, *)])
#endif

-- method TrashStack::height
-- method type : MemberFunction
-- Args : [Arg {argCName = "stack_p", argType = TInterface (Name {namespace = "GLib", name = "TrashStack"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GTrashStack", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "g_trash_stack_height" g_trash_stack_height :: 
    Ptr TrashStack ->                       -- stack_p : TInterface (Name {namespace = "GLib", name = "TrashStack"})
    IO Word32

{-# DEPRECATED trashStackHeight ["(Since version 2.48)","'GI.GLib.Structs.TrashStack.TrashStack' is deprecated without replacement"] #-}
{- |
Returns the height of a 'GI.GLib.Structs.TrashStack.TrashStack'.

Note that execution of this function is of O(N) complexity
where N denotes the number of items on the stack.
-}
trashStackHeight ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TrashStack
    {- ^ /@stackP@/: a 'GI.GLib.Structs.TrashStack.TrashStack' -}
    -> m Word32
    {- ^ __Returns:__ the height of the stack -}
trashStackHeight stackP = liftIO $ do
    stackP' <- unsafeManagedPtrGetPtr stackP
    result <- g_trash_stack_height stackP'
    touchManagedPtr stackP
    return result

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif

-- method TrashStack::peek
-- method type : MemberFunction
-- Args : [Arg {argCName = "stack_p", argType = TInterface (Name {namespace = "GLib", name = "TrashStack"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GTrashStack", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_trash_stack_peek" g_trash_stack_peek :: 
    Ptr TrashStack ->                       -- stack_p : TInterface (Name {namespace = "GLib", name = "TrashStack"})
    IO (Ptr ())

{-# DEPRECATED trashStackPeek ["(Since version 2.48)","'GI.GLib.Structs.TrashStack.TrashStack' is deprecated without replacement"] #-}
{- |
Returns the element at the top of a 'GI.GLib.Structs.TrashStack.TrashStack'
which may be 'Nothing'.
-}
trashStackPeek ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TrashStack
    {- ^ /@stackP@/: a 'GI.GLib.Structs.TrashStack.TrashStack' -}
    -> m (Ptr ())
    {- ^ __Returns:__ the element at the top of the stack -}
trashStackPeek stackP = liftIO $ do
    stackP' <- unsafeManagedPtrGetPtr stackP
    result <- g_trash_stack_peek stackP'
    touchManagedPtr stackP
    return result

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif

-- method TrashStack::pop
-- method type : MemberFunction
-- Args : [Arg {argCName = "stack_p", argType = TInterface (Name {namespace = "GLib", name = "TrashStack"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GTrashStack", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Just (TBasicType TPtr)
-- throws : False
-- Skip return : False

foreign import ccall "g_trash_stack_pop" g_trash_stack_pop :: 
    Ptr TrashStack ->                       -- stack_p : TInterface (Name {namespace = "GLib", name = "TrashStack"})
    IO (Ptr ())

{-# DEPRECATED trashStackPop ["(Since version 2.48)","'GI.GLib.Structs.TrashStack.TrashStack' is deprecated without replacement"] #-}
{- |
Pops a piece of memory off a 'GI.GLib.Structs.TrashStack.TrashStack'.
-}
trashStackPop ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TrashStack
    {- ^ /@stackP@/: a 'GI.GLib.Structs.TrashStack.TrashStack' -}
    -> m (Ptr ())
    {- ^ __Returns:__ the element at the top of the stack -}
trashStackPop stackP = liftIO $ do
    stackP' <- unsafeManagedPtrGetPtr stackP
    result <- g_trash_stack_pop stackP'
    touchManagedPtr stackP
    return result

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif

-- method TrashStack::push
-- method type : MemberFunction
-- Args : [Arg {argCName = "stack_p", argType = TInterface (Name {namespace = "GLib", name = "TrashStack"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GTrashStack", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data_p", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the piece of memory to push on the stack", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}]
-- Lengths : []
-- returnType : Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_trash_stack_push" g_trash_stack_push :: 
    Ptr TrashStack ->                       -- stack_p : TInterface (Name {namespace = "GLib", name = "TrashStack"})
    Ptr () ->                               -- data_p : TBasicType TPtr
    IO ()

{-# DEPRECATED trashStackPush ["(Since version 2.48)","'GI.GLib.Structs.TrashStack.TrashStack' is deprecated without replacement"] #-}
{- |
Pushes a piece of memory onto a 'GI.GLib.Structs.TrashStack.TrashStack'.
-}
trashStackPush ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    TrashStack
    {- ^ /@stackP@/: a 'GI.GLib.Structs.TrashStack.TrashStack' -}
    -> Ptr ()
    {- ^ /@dataP@/: the piece of memory to push on the stack -}
    -> m ()
trashStackPush stackP dataP = liftIO $ do
    stackP' <- unsafeManagedPtrGetPtr stackP
    g_trash_stack_push stackP' dataP
    touchManagedPtr stackP
    return ()

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
#endif

#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
type family ResolveTrashStackMethod (t :: Symbol) (o :: *) :: * where
    ResolveTrashStackMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveTrashStackMethod t TrashStack, O.MethodInfo info TrashStack p) => O.IsLabel t (TrashStack -> 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

#endif