{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Structs.OutputVector
(
OutputVector(..) ,
newZeroOutputVector ,
noOutputVector ,
#if defined(ENABLE_OVERLOADING)
ResolveOutputVectorMethod ,
#endif
clearOutputVectorBuffer ,
getOutputVectorBuffer ,
#if defined(ENABLE_OVERLOADING)
outputVector_buffer ,
#endif
setOutputVectorBuffer ,
getOutputVectorSize ,
#if defined(ENABLE_OVERLOADING)
outputVector_size ,
#endif
setOutputVectorSize ,
) 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.GI.Base.Signals as B.Signals
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
newtype OutputVector = OutputVector (ManagedPtr OutputVector)
deriving (OutputVector -> OutputVector -> Bool
(OutputVector -> OutputVector -> Bool)
-> (OutputVector -> OutputVector -> Bool) -> Eq OutputVector
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutputVector -> OutputVector -> Bool
$c/= :: OutputVector -> OutputVector -> Bool
== :: OutputVector -> OutputVector -> Bool
$c== :: OutputVector -> OutputVector -> Bool
Eq)
instance WrappedPtr OutputVector where
wrappedPtrCalloc :: IO (Ptr OutputVector)
wrappedPtrCalloc = Int -> IO (Ptr OutputVector)
forall a. Int -> IO (Ptr a)
callocBytes 16
wrappedPtrCopy :: OutputVector -> IO OutputVector
wrappedPtrCopy = \p :: OutputVector
p -> OutputVector
-> (Ptr OutputVector -> IO OutputVector) -> IO OutputVector
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputVector
p (Int -> Ptr OutputVector -> IO (Ptr OutputVector)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 16 (Ptr OutputVector -> IO (Ptr OutputVector))
-> (Ptr OutputVector -> IO OutputVector)
-> Ptr OutputVector
-> IO OutputVector
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr OutputVector -> OutputVector)
-> Ptr OutputVector -> IO OutputVector
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr OutputVector -> OutputVector
OutputVector)
wrappedPtrFree :: Maybe (GDestroyNotify OutputVector)
wrappedPtrFree = GDestroyNotify OutputVector -> Maybe (GDestroyNotify OutputVector)
forall a. a -> Maybe a
Just GDestroyNotify OutputVector
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free
newZeroOutputVector :: MonadIO m => m OutputVector
newZeroOutputVector :: m OutputVector
newZeroOutputVector = IO OutputVector -> m OutputVector
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO OutputVector -> m OutputVector)
-> IO OutputVector -> m OutputVector
forall a b. (a -> b) -> a -> b
$ IO (Ptr OutputVector)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr OutputVector)
-> (Ptr OutputVector -> IO OutputVector) -> IO OutputVector
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr OutputVector -> OutputVector)
-> Ptr OutputVector -> IO OutputVector
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr OutputVector -> OutputVector
OutputVector
instance tag ~ 'AttrSet => Constructible OutputVector tag where
new :: (ManagedPtr OutputVector -> OutputVector)
-> [AttrOp OutputVector tag] -> m OutputVector
new _ attrs :: [AttrOp OutputVector tag]
attrs = do
OutputVector
o <- m OutputVector
forall (m :: * -> *). MonadIO m => m OutputVector
newZeroOutputVector
OutputVector -> [AttrOp OutputVector 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set OutputVector
o [AttrOp OutputVector tag]
[AttrOp OutputVector 'AttrSet]
attrs
OutputVector -> m OutputVector
forall (m :: * -> *) a. Monad m => a -> m a
return OutputVector
o
noOutputVector :: Maybe OutputVector
noOutputVector :: Maybe OutputVector
noOutputVector = Maybe OutputVector
forall a. Maybe a
Nothing
getOutputVectorBuffer :: MonadIO m => OutputVector -> m (Ptr ())
getOutputVectorBuffer :: OutputVector -> m (Ptr ())
getOutputVectorBuffer s :: OutputVector
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
$ OutputVector -> (Ptr OutputVector -> IO (Ptr ())) -> IO (Ptr ())
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputVector
s ((Ptr OutputVector -> IO (Ptr ())) -> IO (Ptr ()))
-> (Ptr OutputVector -> IO (Ptr ())) -> IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputVector
ptr -> do
Ptr ()
val <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek (Ptr OutputVector
ptr Ptr OutputVector -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO (Ptr ())
Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
val
setOutputVectorBuffer :: MonadIO m => OutputVector -> Ptr () -> m ()
setOutputVectorBuffer :: OutputVector -> Ptr () -> m ()
setOutputVectorBuffer s :: OutputVector
s val :: 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
$ OutputVector -> (Ptr OutputVector -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputVector
s ((Ptr OutputVector -> IO ()) -> IO ())
-> (Ptr OutputVector -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputVector
ptr -> do
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OutputVector
ptr Ptr OutputVector -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Ptr ()
val :: Ptr ())
clearOutputVectorBuffer :: MonadIO m => OutputVector -> m ()
clearOutputVectorBuffer :: OutputVector -> m ()
clearOutputVectorBuffer s :: OutputVector
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ OutputVector -> (Ptr OutputVector -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputVector
s ((Ptr OutputVector -> IO ()) -> IO ())
-> (Ptr OutputVector -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputVector
ptr -> do
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OutputVector
ptr Ptr OutputVector -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Ptr ()
forall a. Ptr a
FP.nullPtr :: Ptr ())
#if defined(ENABLE_OVERLOADING)
data OutputVectorBufferFieldInfo
instance AttrInfo OutputVectorBufferFieldInfo where
type AttrBaseTypeConstraint OutputVectorBufferFieldInfo = (~) OutputVector
type AttrAllowedOps OutputVectorBufferFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint OutputVectorBufferFieldInfo = (~) (Ptr ())
type AttrTransferTypeConstraint OutputVectorBufferFieldInfo = (~)(Ptr ())
type AttrTransferType OutputVectorBufferFieldInfo = (Ptr ())
type AttrGetType OutputVectorBufferFieldInfo = Ptr ()
type AttrLabel OutputVectorBufferFieldInfo = "buffer"
type AttrOrigin OutputVectorBufferFieldInfo = OutputVector
attrGet = getOutputVectorBuffer
attrSet = setOutputVectorBuffer
attrConstruct = undefined
attrClear = clearOutputVectorBuffer
attrTransfer _ v = do
return v
outputVector_buffer :: AttrLabelProxy "buffer"
outputVector_buffer = AttrLabelProxy
#endif
getOutputVectorSize :: MonadIO m => OutputVector -> m Word64
getOutputVectorSize :: OutputVector -> m Word64
getOutputVectorSize s :: OutputVector
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
$ OutputVector -> (Ptr OutputVector -> IO Word64) -> IO Word64
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputVector
s ((Ptr OutputVector -> IO Word64) -> IO Word64)
-> (Ptr OutputVector -> IO Word64) -> IO Word64
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputVector
ptr -> do
Word64
val <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek (Ptr OutputVector
ptr Ptr OutputVector -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO Word64
Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
val
setOutputVectorSize :: MonadIO m => OutputVector -> Word64 -> m ()
setOutputVectorSize :: OutputVector -> Word64 -> m ()
setOutputVectorSize s :: OutputVector
s val :: 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
$ OutputVector -> (Ptr OutputVector -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr OutputVector
s ((Ptr OutputVector -> IO ()) -> IO ())
-> (Ptr OutputVector -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr OutputVector
ptr -> do
Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr OutputVector
ptr Ptr OutputVector -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Word64
val :: Word64)
#if defined(ENABLE_OVERLOADING)
data OutputVectorSizeFieldInfo
instance AttrInfo OutputVectorSizeFieldInfo where
type AttrBaseTypeConstraint OutputVectorSizeFieldInfo = (~) OutputVector
type AttrAllowedOps OutputVectorSizeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint OutputVectorSizeFieldInfo = (~) Word64
type AttrTransferTypeConstraint OutputVectorSizeFieldInfo = (~)Word64
type AttrTransferType OutputVectorSizeFieldInfo = Word64
type AttrGetType OutputVectorSizeFieldInfo = Word64
type AttrLabel OutputVectorSizeFieldInfo = "size"
type AttrOrigin OutputVectorSizeFieldInfo = OutputVector
attrGet = getOutputVectorSize
attrSet = setOutputVectorSize
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
outputVector_size :: AttrLabelProxy "size"
outputVector_size = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList OutputVector
type instance O.AttributeList OutputVector = OutputVectorAttributeList
type OutputVectorAttributeList = ('[ '("buffer", OutputVectorBufferFieldInfo), '("size", OutputVectorSizeFieldInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveOutputVectorMethod (t :: Symbol) (o :: *) :: * where
ResolveOutputVectorMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveOutputVectorMethod t OutputVector, O.MethodInfo info OutputVector p) => OL.IsLabel t (OutputVector -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif