{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Structure used for scatter\/gather data input.
-- You generally pass in an array of @/GInputVectors/@
-- and the operation will store the read data starting in the
-- first buffer, switching to the next as needed.
-- 
-- /Since: 2.22/

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

module GI.Gio.Structs.InputVector
    ( 

-- * Exported types
    InputVector(..)                         ,
    newZeroInputVector                      ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveInputVectorMethod                ,
#endif



 -- * Properties


-- ** buffer #attr:buffer#
-- | Pointer to a buffer where data will be written.

    clearInputVectorBuffer                  ,
    getInputVectorBuffer                    ,
#if defined(ENABLE_OVERLOADING)
    inputVector_buffer                      ,
#endif
    setInputVectorBuffer                    ,


-- ** size #attr:size#
-- | the available size in /@buffer@/.

    getInputVectorSize                      ,
#if defined(ENABLE_OVERLOADING)
    inputVector_size                        ,
#endif
    setInputVectorSize                      ,




    ) 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
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.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
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 qualified GHC.Records as R


-- | Memory-managed wrapper type.
newtype InputVector = InputVector (SP.ManagedPtr InputVector)
    deriving (InputVector -> InputVector -> Bool
(InputVector -> InputVector -> Bool)
-> (InputVector -> InputVector -> Bool) -> Eq InputVector
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputVector -> InputVector -> Bool
$c/= :: InputVector -> InputVector -> Bool
== :: InputVector -> InputVector -> Bool
$c== :: InputVector -> InputVector -> Bool
Eq)

instance SP.ManagedPtrNewtype InputVector where
    toManagedPtr :: InputVector -> ManagedPtr InputVector
toManagedPtr (InputVector ManagedPtr InputVector
p) = ManagedPtr InputVector
p

instance BoxedPtr InputVector where
    boxedPtrCopy :: InputVector -> IO InputVector
boxedPtrCopy = \InputVector
p -> InputVector
-> (Ptr InputVector -> IO InputVector) -> IO InputVector
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr InputVector
p (Int -> Ptr InputVector -> IO (Ptr InputVector)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
16 (Ptr InputVector -> IO (Ptr InputVector))
-> (Ptr InputVector -> IO InputVector)
-> Ptr InputVector
-> IO InputVector
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr InputVector -> InputVector)
-> Ptr InputVector -> IO InputVector
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr InputVector -> InputVector
InputVector)
    boxedPtrFree :: InputVector -> IO ()
boxedPtrFree = \InputVector
x -> InputVector -> (Ptr InputVector -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr InputVector
x Ptr InputVector -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr InputVector where
    boxedPtrCalloc :: IO (Ptr InputVector)
boxedPtrCalloc = Int -> IO (Ptr InputVector)
forall a. Int -> IO (Ptr a)
callocBytes Int
16


-- | Construct a `InputVector` struct initialized to zero.
newZeroInputVector :: MonadIO m => m InputVector
newZeroInputVector :: forall (m :: * -> *). MonadIO m => m InputVector
newZeroInputVector = IO InputVector -> m InputVector
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputVector -> m InputVector)
-> IO InputVector -> m InputVector
forall a b. (a -> b) -> a -> b
$ IO (Ptr InputVector)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr InputVector)
-> (Ptr InputVector -> IO InputVector) -> IO InputVector
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr InputVector -> InputVector)
-> Ptr InputVector -> IO InputVector
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr InputVector -> InputVector
InputVector

instance tag ~ 'AttrSet => Constructible InputVector tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr InputVector -> InputVector)
-> [AttrOp InputVector tag] -> m InputVector
new ManagedPtr InputVector -> InputVector
_ [AttrOp InputVector tag]
attrs = do
        InputVector
o <- m InputVector
forall (m :: * -> *). MonadIO m => m InputVector
newZeroInputVector
        InputVector -> [AttrOp InputVector 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set InputVector
o [AttrOp InputVector tag]
[AttrOp InputVector 'AttrSet]
attrs
        InputVector -> m InputVector
forall (m :: * -> *) a. Monad m => a -> m a
return InputVector
o


-- | Get the value of the “@buffer@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' inputVector #buffer
-- @
getInputVectorBuffer :: MonadIO m => InputVector -> m (Ptr ())
getInputVectorBuffer :: forall (m :: * -> *). MonadIO m => InputVector -> m (Ptr ())
getInputVectorBuffer InputVector
s = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ InputVector -> (Ptr InputVector -> IO (Ptr ())) -> IO (Ptr ())
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr InputVector
s ((Ptr InputVector -> IO (Ptr ())) -> IO (Ptr ()))
-> (Ptr InputVector -> IO (Ptr ())) -> IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ \Ptr InputVector
ptr -> do
    Ptr ()
val <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek (Ptr InputVector
ptr Ptr InputVector -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO (Ptr ())
    Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
val

-- | Set the value of the “@buffer@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' inputVector [ #buffer 'Data.GI.Base.Attributes.:=' value ]
-- @
setInputVectorBuffer :: MonadIO m => InputVector -> Ptr () -> m ()
setInputVectorBuffer :: forall (m :: * -> *). MonadIO m => InputVector -> Ptr () -> m ()
setInputVectorBuffer InputVector
s Ptr ()
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ InputVector -> (Ptr InputVector -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr InputVector
s ((Ptr InputVector -> IO ()) -> IO ())
-> (Ptr InputVector -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr InputVector
ptr -> do
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr InputVector
ptr Ptr InputVector -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Ptr ()
val :: Ptr ())

-- | Set the value of the “@buffer@” 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' #buffer
-- @
clearInputVectorBuffer :: MonadIO m => InputVector -> m ()
clearInputVectorBuffer :: forall (m :: * -> *). MonadIO m => InputVector -> m ()
clearInputVectorBuffer InputVector
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ InputVector -> (Ptr InputVector -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr InputVector
s ((Ptr InputVector -> IO ()) -> IO ())
-> (Ptr InputVector -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr InputVector
ptr -> do
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr InputVector
ptr Ptr InputVector -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Ptr ()
forall a. Ptr a
FP.nullPtr :: Ptr ())

#if defined(ENABLE_OVERLOADING)
data InputVectorBufferFieldInfo
instance AttrInfo InputVectorBufferFieldInfo where
    type AttrBaseTypeConstraint InputVectorBufferFieldInfo = (~) InputVector
    type AttrAllowedOps InputVectorBufferFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint InputVectorBufferFieldInfo = (~) (Ptr ())
    type AttrTransferTypeConstraint InputVectorBufferFieldInfo = (~)(Ptr ())
    type AttrTransferType InputVectorBufferFieldInfo = (Ptr ())
    type AttrGetType InputVectorBufferFieldInfo = Ptr ()
    type AttrLabel InputVectorBufferFieldInfo = "buffer"
    type AttrOrigin InputVectorBufferFieldInfo = InputVector
    attrGet = getInputVectorBuffer
    attrSet = setInputVectorBuffer
    attrConstruct = undefined
    attrClear = clearInputVectorBuffer
    attrTransfer _ v = do
        return v

inputVector_buffer :: AttrLabelProxy "buffer"
inputVector_buffer = AttrLabelProxy

#endif


-- | 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' inputVector #size
-- @
getInputVectorSize :: MonadIO m => InputVector -> m Word64
getInputVectorSize :: forall (m :: * -> *). MonadIO m => InputVector -> m Word64
getInputVectorSize InputVector
s = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ InputVector -> (Ptr InputVector -> IO Word64) -> IO Word64
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr InputVector
s ((Ptr InputVector -> IO Word64) -> IO Word64)
-> (Ptr InputVector -> IO Word64) -> IO Word64
forall a b. (a -> b) -> a -> b
$ \Ptr InputVector
ptr -> do
    Word64
val <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek (Ptr InputVector
ptr Ptr InputVector -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO Word64
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
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' inputVector [ #size 'Data.GI.Base.Attributes.:=' value ]
-- @
setInputVectorSize :: MonadIO m => InputVector -> Word64 -> m ()
setInputVectorSize :: forall (m :: * -> *). MonadIO m => InputVector -> Word64 -> m ()
setInputVectorSize InputVector
s Word64
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ InputVector -> (Ptr InputVector -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr InputVector
s ((Ptr InputVector -> IO ()) -> IO ())
-> (Ptr InputVector -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr InputVector
ptr -> do
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr InputVector
ptr Ptr InputVector -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Word64
val :: Word64)

#if defined(ENABLE_OVERLOADING)
data InputVectorSizeFieldInfo
instance AttrInfo InputVectorSizeFieldInfo where
    type AttrBaseTypeConstraint InputVectorSizeFieldInfo = (~) InputVector
    type AttrAllowedOps InputVectorSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint InputVectorSizeFieldInfo = (~) Word64
    type AttrTransferTypeConstraint InputVectorSizeFieldInfo = (~)Word64
    type AttrTransferType InputVectorSizeFieldInfo = Word64
    type AttrGetType InputVectorSizeFieldInfo = Word64
    type AttrLabel InputVectorSizeFieldInfo = "size"
    type AttrOrigin InputVectorSizeFieldInfo = InputVector
    attrGet = getInputVectorSize
    attrSet = setInputVectorSize
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

inputVector_size :: AttrLabelProxy "size"
inputVector_size = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList InputVector
type instance O.AttributeList InputVector = InputVectorAttributeList
type InputVectorAttributeList = ('[ '("buffer", InputVectorBufferFieldInfo), '("size", InputVectorSizeFieldInfo)] :: [(Symbol, *)])
#endif

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

instance (info ~ ResolveInputVectorMethod t InputVector, O.OverloadedMethod info InputVector p) => OL.IsLabel t (InputVector -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveInputVectorMethod t InputVector, O.OverloadedMethod info InputVector p, R.HasField t InputVector p) => R.HasField t InputVector p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveInputVectorMethod t InputVector, O.OverloadedMethodInfo info InputVector) => OL.IsLabel t (O.MethodProxy info InputVector) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif