{-# language CPP #-}
module Vulkan.Core10.SharedTypes  ( Offset2D(..)
                                  , Offset3D(..)
                                  , Extent2D(..)
                                  , Extent3D(..)
                                  , ImageSubresourceLayers(..)
                                  , ImageSubresourceRange(..)
                                  , ClearDepthStencilValue(..)
                                  , ClearColorValue(..)
                                  , ClearValue(..)
                                  ) where

import Vulkan.CStruct.Utils (FixedArray)
import Control.Exception.Base (bracket)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Ptr (castPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (runContT)
import Data.Typeable (Typeable)
import Foreign.C.Types (CFloat)
import Foreign.C.Types (CFloat(CFloat))
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Data.Int (Int32)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.CStruct.Utils (lowerArrayPtr)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.ImageAspectFlagBits (ImageAspectFlags)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
-- | VkOffset2D - Structure specifying a two-dimensional offset
--
-- = See Also
--
-- 'Vulkan.Extensions.VK_KHR_display.DisplayPlaneCapabilitiesKHR',
-- 'Vulkan.Core10.CommandBufferBuilding.Rect2D',
-- 'Vulkan.Extensions.VK_KHR_incremental_present.RectLayerKHR'
data Offset2D = Offset2D
  { -- | @x@ is the x offset.
    Offset2D -> Int32
x :: Int32
  , -- | @y@ is the y offset.
    Offset2D -> Int32
y :: Int32
  }
  deriving (Typeable, Offset2D -> Offset2D -> Bool
(Offset2D -> Offset2D -> Bool)
-> (Offset2D -> Offset2D -> Bool) -> Eq Offset2D
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Offset2D -> Offset2D -> Bool
$c/= :: Offset2D -> Offset2D -> Bool
== :: Offset2D -> Offset2D -> Bool
$c== :: Offset2D -> Offset2D -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (Offset2D)
#endif
deriving instance Show Offset2D

instance ToCStruct Offset2D where
  withCStruct :: Offset2D -> (Ptr Offset2D -> IO b) -> IO b
withCStruct x :: Offset2D
x f :: Ptr Offset2D -> IO b
f = Int -> Int -> (Ptr Offset2D -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 8 4 ((Ptr Offset2D -> IO b) -> IO b) -> (Ptr Offset2D -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr Offset2D
p -> Ptr Offset2D -> Offset2D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr Offset2D
p Offset2D
x (Ptr Offset2D -> IO b
f Ptr Offset2D
p)
  pokeCStruct :: Ptr Offset2D -> Offset2D -> IO b -> IO b
pokeCStruct p :: Ptr Offset2D
p Offset2D{..} f :: IO b
f = do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Offset2D
p Ptr Offset2D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Int32)) (Int32
x)
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Offset2D
p Ptr Offset2D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Int32)) (Int32
y)
    IO b
f
  cStructSize :: Int
cStructSize = 8
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr Offset2D -> IO b -> IO b
pokeZeroCStruct p :: Ptr Offset2D
p f :: IO b
f = do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Offset2D
p Ptr Offset2D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Int32)) (Int32
forall a. Zero a => a
zero)
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Offset2D
p Ptr Offset2D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Int32)) (Int32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct Offset2D where
  peekCStruct :: Ptr Offset2D -> IO Offset2D
peekCStruct p :: Ptr Offset2D
p = do
    Int32
x <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr Offset2D
p Ptr Offset2D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Int32))
    Int32
y <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr Offset2D
p Ptr Offset2D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Int32))
    Offset2D -> IO Offset2D
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Offset2D -> IO Offset2D) -> Offset2D -> IO Offset2D
forall a b. (a -> b) -> a -> b
$ Int32 -> Int32 -> Offset2D
Offset2D
             Int32
x Int32
y

instance Storable Offset2D where
  sizeOf :: Offset2D -> Int
sizeOf ~Offset2D
_ = 8
  alignment :: Offset2D -> Int
alignment ~Offset2D
_ = 4
  peek :: Ptr Offset2D -> IO Offset2D
peek = Ptr Offset2D -> IO Offset2D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr Offset2D -> Offset2D -> IO ()
poke ptr :: Ptr Offset2D
ptr poked :: Offset2D
poked = Ptr Offset2D -> Offset2D -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr Offset2D
ptr Offset2D
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero Offset2D where
  zero :: Offset2D
zero = Int32 -> Int32 -> Offset2D
Offset2D
           Int32
forall a. Zero a => a
zero
           Int32
forall a. Zero a => a
zero


-- | VkOffset3D - Structure specifying a three-dimensional offset
--
-- = See Also
--
-- 'Vulkan.Core10.CommandBufferBuilding.BufferImageCopy',
-- 'Vulkan.Core10.CommandBufferBuilding.ImageBlit',
-- 'Vulkan.Core10.CommandBufferBuilding.ImageCopy',
-- 'Vulkan.Core10.CommandBufferBuilding.ImageResolve',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseImageMemoryBind'
data Offset3D = Offset3D
  { -- | @x@ is the x offset.
    Offset3D -> Int32
x :: Int32
  , -- | @y@ is the y offset.
    Offset3D -> Int32
y :: Int32
  , -- | @z@ is the z offset.
    Offset3D -> Int32
z :: Int32
  }
  deriving (Typeable, Offset3D -> Offset3D -> Bool
(Offset3D -> Offset3D -> Bool)
-> (Offset3D -> Offset3D -> Bool) -> Eq Offset3D
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Offset3D -> Offset3D -> Bool
$c/= :: Offset3D -> Offset3D -> Bool
== :: Offset3D -> Offset3D -> Bool
$c== :: Offset3D -> Offset3D -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (Offset3D)
#endif
deriving instance Show Offset3D

instance ToCStruct Offset3D where
  withCStruct :: Offset3D -> (Ptr Offset3D -> IO b) -> IO b
withCStruct x :: Offset3D
x f :: Ptr Offset3D -> IO b
f = Int -> Int -> (Ptr Offset3D -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 12 4 ((Ptr Offset3D -> IO b) -> IO b) -> (Ptr Offset3D -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr Offset3D
p -> Ptr Offset3D -> Offset3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr Offset3D
p Offset3D
x (Ptr Offset3D -> IO b
f Ptr Offset3D
p)
  pokeCStruct :: Ptr Offset3D -> Offset3D -> IO b -> IO b
pokeCStruct p :: Ptr Offset3D
p Offset3D{..} f :: IO b
f = do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Offset3D
p Ptr Offset3D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Int32)) (Int32
x)
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Offset3D
p Ptr Offset3D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Int32)) (Int32
y)
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Offset3D
p Ptr Offset3D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Int32)) (Int32
z)
    IO b
f
  cStructSize :: Int
cStructSize = 12
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr Offset3D -> IO b -> IO b
pokeZeroCStruct p :: Ptr Offset3D
p f :: IO b
f = do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Offset3D
p Ptr Offset3D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Int32)) (Int32
forall a. Zero a => a
zero)
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Offset3D
p Ptr Offset3D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Int32)) (Int32
forall a. Zero a => a
zero)
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Offset3D
p Ptr Offset3D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Int32)) (Int32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct Offset3D where
  peekCStruct :: Ptr Offset3D -> IO Offset3D
peekCStruct p :: Ptr Offset3D
p = do
    Int32
x <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr Offset3D
p Ptr Offset3D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Int32))
    Int32
y <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr Offset3D
p Ptr Offset3D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Int32))
    Int32
z <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr Offset3D
p Ptr Offset3D -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Int32))
    Offset3D -> IO Offset3D
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Offset3D -> IO Offset3D) -> Offset3D -> IO Offset3D
forall a b. (a -> b) -> a -> b
$ Int32 -> Int32 -> Int32 -> Offset3D
Offset3D
             Int32
x Int32
y Int32
z

instance Storable Offset3D where
  sizeOf :: Offset3D -> Int
sizeOf ~Offset3D
_ = 12
  alignment :: Offset3D -> Int
alignment ~Offset3D
_ = 4
  peek :: Ptr Offset3D -> IO Offset3D
peek = Ptr Offset3D -> IO Offset3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr Offset3D -> Offset3D -> IO ()
poke ptr :: Ptr Offset3D
ptr poked :: Offset3D
poked = Ptr Offset3D -> Offset3D -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr Offset3D
ptr Offset3D
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero Offset3D where
  zero :: Offset3D
zero = Int32 -> Int32 -> Int32 -> Offset3D
Offset3D
           Int32
forall a. Zero a => a
zero
           Int32
forall a. Zero a => a
zero
           Int32
forall a. Zero a => a
zero


-- | VkExtent2D - Structure specifying a two-dimensional extent
--
-- = See Also
--
-- 'Vulkan.Extensions.VK_KHR_display.DisplayModeParametersKHR',
-- 'Vulkan.Extensions.VK_KHR_display.DisplayPlaneCapabilitiesKHR',
-- 'Vulkan.Extensions.VK_KHR_display.DisplayPropertiesKHR',
-- 'Vulkan.Extensions.VK_KHR_display.DisplaySurfaceCreateInfoKHR',
-- 'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT',
-- 'Vulkan.Extensions.VK_EXT_fragment_density_map.PhysicalDeviceFragmentDensityMapPropertiesEXT',
-- 'Vulkan.Extensions.VK_EXT_sample_locations.PhysicalDeviceSampleLocationsPropertiesEXT',
-- 'Vulkan.Extensions.VK_NV_shading_rate_image.PhysicalDeviceShadingRateImagePropertiesNV',
-- 'Vulkan.Core10.CommandBufferBuilding.Rect2D',
-- 'Vulkan.Extensions.VK_KHR_incremental_present.RectLayerKHR',
-- 'Vulkan.Extensions.VK_EXT_sample_locations.SampleLocationsInfoEXT',
-- 'Vulkan.Extensions.VK_EXT_display_surface_counter.SurfaceCapabilities2EXT',
-- 'Vulkan.Extensions.VK_KHR_surface.SurfaceCapabilitiesKHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.SwapchainCreateInfoKHR',
-- 'Vulkan.Core10.Pass.getRenderAreaGranularity'
data Extent2D = Extent2D
  { -- | @width@ is the width of the extent.
    Extent2D -> Word32
width :: Word32
  , -- | @height@ is the height of the extent.
    Extent2D -> Word32
height :: Word32
  }
  deriving (Typeable, Extent2D -> Extent2D -> Bool
(Extent2D -> Extent2D -> Bool)
-> (Extent2D -> Extent2D -> Bool) -> Eq Extent2D
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Extent2D -> Extent2D -> Bool
$c/= :: Extent2D -> Extent2D -> Bool
== :: Extent2D -> Extent2D -> Bool
$c== :: Extent2D -> Extent2D -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (Extent2D)
#endif
deriving instance Show Extent2D

instance ToCStruct Extent2D where
  withCStruct :: Extent2D -> (Ptr Extent2D -> IO b) -> IO b
withCStruct x :: Extent2D
x f :: Ptr Extent2D -> IO b
f = Int -> Int -> (Ptr Extent2D -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 8 4 ((Ptr Extent2D -> IO b) -> IO b) -> (Ptr Extent2D -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr Extent2D
p -> Ptr Extent2D -> Extent2D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr Extent2D
p Extent2D
x (Ptr Extent2D -> IO b
f Ptr Extent2D
p)
  pokeCStruct :: Ptr Extent2D -> Extent2D -> IO b -> IO b
pokeCStruct p :: Ptr Extent2D
p Extent2D{..} f :: IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Extent2D
p Ptr Extent2D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
width)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Extent2D
p Ptr Extent2D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
height)
    IO b
f
  cStructSize :: Int
cStructSize = 8
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr Extent2D -> IO b -> IO b
pokeZeroCStruct p :: Ptr Extent2D
p f :: IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Extent2D
p Ptr Extent2D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Extent2D
p Ptr Extent2D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct Extent2D where
  peekCStruct :: Ptr Extent2D -> IO Extent2D
peekCStruct p :: Ptr Extent2D
p = do
    Word32
width <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Extent2D
p Ptr Extent2D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    Word32
height <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Extent2D
p Ptr Extent2D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    Extent2D -> IO Extent2D
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Extent2D -> IO Extent2D) -> Extent2D -> IO Extent2D
forall a b. (a -> b) -> a -> b
$ Word32 -> Word32 -> Extent2D
Extent2D
             Word32
width Word32
height

instance Storable Extent2D where
  sizeOf :: Extent2D -> Int
sizeOf ~Extent2D
_ = 8
  alignment :: Extent2D -> Int
alignment ~Extent2D
_ = 4
  peek :: Ptr Extent2D -> IO Extent2D
peek = Ptr Extent2D -> IO Extent2D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr Extent2D -> Extent2D -> IO ()
poke ptr :: Ptr Extent2D
ptr poked :: Extent2D
poked = Ptr Extent2D -> Extent2D -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr Extent2D
ptr Extent2D
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero Extent2D where
  zero :: Extent2D
zero = Word32 -> Word32 -> Extent2D
Extent2D
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


-- | VkExtent3D - Structure specifying a three-dimensional extent
--
-- = See Also
--
-- 'Vulkan.Core10.CommandBufferBuilding.BufferImageCopy',
-- 'Vulkan.Core10.CommandBufferBuilding.ImageCopy',
-- 'Vulkan.Core10.Image.ImageCreateInfo',
-- 'Vulkan.Core10.DeviceInitialization.ImageFormatProperties',
-- 'Vulkan.Core10.CommandBufferBuilding.ImageResolve',
-- 'Vulkan.Core10.DeviceInitialization.QueueFamilyProperties',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseImageFormatProperties',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseImageMemoryBind'
data Extent3D = Extent3D
  { -- | @width@ is the width of the extent.
    Extent3D -> Word32
width :: Word32
  , -- | @height@ is the height of the extent.
    Extent3D -> Word32
height :: Word32
  , -- | @depth@ is the depth of the extent.
    Extent3D -> Word32
depth :: Word32
  }
  deriving (Typeable, Extent3D -> Extent3D -> Bool
(Extent3D -> Extent3D -> Bool)
-> (Extent3D -> Extent3D -> Bool) -> Eq Extent3D
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Extent3D -> Extent3D -> Bool
$c/= :: Extent3D -> Extent3D -> Bool
== :: Extent3D -> Extent3D -> Bool
$c== :: Extent3D -> Extent3D -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (Extent3D)
#endif
deriving instance Show Extent3D

instance ToCStruct Extent3D where
  withCStruct :: Extent3D -> (Ptr Extent3D -> IO b) -> IO b
withCStruct x :: Extent3D
x f :: Ptr Extent3D -> IO b
f = Int -> Int -> (Ptr Extent3D -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 12 4 ((Ptr Extent3D -> IO b) -> IO b) -> (Ptr Extent3D -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr Extent3D
p -> Ptr Extent3D -> Extent3D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr Extent3D
p Extent3D
x (Ptr Extent3D -> IO b
f Ptr Extent3D
p)
  pokeCStruct :: Ptr Extent3D -> Extent3D -> IO b -> IO b
pokeCStruct p :: Ptr Extent3D
p Extent3D{..} f :: IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Extent3D
p Ptr Extent3D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
width)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Extent3D
p Ptr Extent3D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
height)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Extent3D
p Ptr Extent3D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
depth)
    IO b
f
  cStructSize :: Int
cStructSize = 12
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr Extent3D -> IO b -> IO b
pokeZeroCStruct p :: Ptr Extent3D
p f :: IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Extent3D
p Ptr Extent3D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Extent3D
p Ptr Extent3D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Extent3D
p Ptr Extent3D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct Extent3D where
  peekCStruct :: Ptr Extent3D -> IO Extent3D
peekCStruct p :: Ptr Extent3D
p = do
    Word32
width <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Extent3D
p Ptr Extent3D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    Word32
height <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Extent3D
p Ptr Extent3D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    Word32
depth <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Extent3D
p Ptr Extent3D -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    Extent3D -> IO Extent3D
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Extent3D -> IO Extent3D) -> Extent3D -> IO Extent3D
forall a b. (a -> b) -> a -> b
$ Word32 -> Word32 -> Word32 -> Extent3D
Extent3D
             Word32
width Word32
height Word32
depth

instance Storable Extent3D where
  sizeOf :: Extent3D -> Int
sizeOf ~Extent3D
_ = 12
  alignment :: Extent3D -> Int
alignment ~Extent3D
_ = 4
  peek :: Ptr Extent3D -> IO Extent3D
peek = Ptr Extent3D -> IO Extent3D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr Extent3D -> Extent3D -> IO ()
poke ptr :: Ptr Extent3D
ptr poked :: Extent3D
poked = Ptr Extent3D -> Extent3D -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr Extent3D
ptr Extent3D
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero Extent3D where
  zero :: Extent3D
zero = Word32 -> Word32 -> Word32 -> Extent3D
Extent3D
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


-- | VkImageSubresourceLayers - Structure specifying an image subresource
-- layers
--
-- == Valid Usage
--
-- -   If @aspectMask@ contains
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT', it
--     /must/ not contain either of
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' or
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT'
--
-- -   @aspectMask@ /must/ not contain
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_METADATA_BIT'
--
-- -   @aspectMask@ /must/ not include
--     @VK_IMAGE_ASPECT_MEMORY_PLANE_i_BIT_EXT@ for any index @i@
--
-- -   @layerCount@ /must/ be greater than 0
--
-- == Valid Usage (Implicit)
--
-- -   @aspectMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlagBits' values
--
-- -   @aspectMask@ /must/ not be @0@
--
-- = See Also
--
-- 'Vulkan.Core10.CommandBufferBuilding.BufferImageCopy',
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlags',
-- 'Vulkan.Core10.CommandBufferBuilding.ImageBlit',
-- 'Vulkan.Core10.CommandBufferBuilding.ImageCopy',
-- 'Vulkan.Core10.CommandBufferBuilding.ImageResolve'
data ImageSubresourceLayers = ImageSubresourceLayers
  { -- | @aspectMask@ is a combination of
    -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlagBits', selecting
    -- the color, depth and\/or stencil aspects to be copied.
    ImageSubresourceLayers -> ImageAspectFlags
aspectMask :: ImageAspectFlags
  , -- | @mipLevel@ is the mipmap level to copy from.
    ImageSubresourceLayers -> Word32
mipLevel :: Word32
  , -- | @baseArrayLayer@ and @layerCount@ are the starting layer and number of
    -- layers to copy.
    ImageSubresourceLayers -> Word32
baseArrayLayer :: Word32
  , -- No documentation found for Nested "VkImageSubresourceLayers" "layerCount"
    ImageSubresourceLayers -> Word32
layerCount :: Word32
  }
  deriving (Typeable, ImageSubresourceLayers -> ImageSubresourceLayers -> Bool
(ImageSubresourceLayers -> ImageSubresourceLayers -> Bool)
-> (ImageSubresourceLayers -> ImageSubresourceLayers -> Bool)
-> Eq ImageSubresourceLayers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageSubresourceLayers -> ImageSubresourceLayers -> Bool
$c/= :: ImageSubresourceLayers -> ImageSubresourceLayers -> Bool
== :: ImageSubresourceLayers -> ImageSubresourceLayers -> Bool
$c== :: ImageSubresourceLayers -> ImageSubresourceLayers -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageSubresourceLayers)
#endif
deriving instance Show ImageSubresourceLayers

instance ToCStruct ImageSubresourceLayers where
  withCStruct :: ImageSubresourceLayers
-> (Ptr ImageSubresourceLayers -> IO b) -> IO b
withCStruct x :: ImageSubresourceLayers
x f :: Ptr ImageSubresourceLayers -> IO b
f = Int -> Int -> (Ptr ImageSubresourceLayers -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 4 ((Ptr ImageSubresourceLayers -> IO b) -> IO b)
-> (Ptr ImageSubresourceLayers -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ImageSubresourceLayers
p -> Ptr ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageSubresourceLayers
p ImageSubresourceLayers
x (Ptr ImageSubresourceLayers -> IO b
f Ptr ImageSubresourceLayers
p)
  pokeCStruct :: Ptr ImageSubresourceLayers
-> ImageSubresourceLayers -> IO b -> IO b
pokeCStruct p :: Ptr ImageSubresourceLayers
p ImageSubresourceLayers{..} f :: IO b
f = do
    Ptr ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags)) (ImageAspectFlags
aspectMask)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
mipLevel)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
baseArrayLayer)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) (Word32
layerCount)
    IO b
f
  cStructSize :: Int
cStructSize = 16
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr ImageSubresourceLayers -> IO b -> IO b
pokeZeroCStruct p :: Ptr ImageSubresourceLayers
p f :: IO b
f = do
    Ptr ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags)) (ImageAspectFlags
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct ImageSubresourceLayers where
  peekCStruct :: Ptr ImageSubresourceLayers -> IO ImageSubresourceLayers
peekCStruct p :: Ptr ImageSubresourceLayers
p = do
    ImageAspectFlags
aspectMask <- Ptr ImageAspectFlags -> IO ImageAspectFlags
forall a. Storable a => Ptr a -> IO a
peek @ImageAspectFlags ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags))
    Word32
mipLevel <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    Word32
baseArrayLayer <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    Word32
layerCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ImageSubresourceLayers
p Ptr ImageSubresourceLayers -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32))
    ImageSubresourceLayers -> IO ImageSubresourceLayers
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageSubresourceLayers -> IO ImageSubresourceLayers)
-> ImageSubresourceLayers -> IO ImageSubresourceLayers
forall a b. (a -> b) -> a -> b
$ ImageAspectFlags
-> Word32 -> Word32 -> Word32 -> ImageSubresourceLayers
ImageSubresourceLayers
             ImageAspectFlags
aspectMask Word32
mipLevel Word32
baseArrayLayer Word32
layerCount

instance Storable ImageSubresourceLayers where
  sizeOf :: ImageSubresourceLayers -> Int
sizeOf ~ImageSubresourceLayers
_ = 16
  alignment :: ImageSubresourceLayers -> Int
alignment ~ImageSubresourceLayers
_ = 4
  peek :: Ptr ImageSubresourceLayers -> IO ImageSubresourceLayers
peek = Ptr ImageSubresourceLayers -> IO ImageSubresourceLayers
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr ImageSubresourceLayers -> ImageSubresourceLayers -> IO ()
poke ptr :: Ptr ImageSubresourceLayers
ptr poked :: ImageSubresourceLayers
poked = Ptr ImageSubresourceLayers
-> ImageSubresourceLayers -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageSubresourceLayers
ptr ImageSubresourceLayers
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero ImageSubresourceLayers where
  zero :: ImageSubresourceLayers
zero = ImageAspectFlags
-> Word32 -> Word32 -> Word32 -> ImageSubresourceLayers
ImageSubresourceLayers
           ImageAspectFlags
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


-- | VkImageSubresourceRange - Structure specifying an image subresource
-- range
--
-- = Description
--
-- The number of mipmap levels and array layers /must/ be a subset of the
-- image subresources in the image. If an application wants to use all mip
-- levels or layers in an image after the @baseMipLevel@ or
-- @baseArrayLayer@, it /can/ set @levelCount@ and @layerCount@ to the
-- special values 'Vulkan.Core10.APIConstants.REMAINING_MIP_LEVELS' and
-- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS' without knowing the
-- exact number of mip levels or layers.
--
-- For cube and cube array image views, the layers of the image view
-- starting at @baseArrayLayer@ correspond to faces in the order +X, -X,
-- +Y, -Y, +Z, -Z. For cube arrays, each set of six sequential layers is a
-- single cube, so the number of cube maps in a cube map array view is
-- /@layerCount@ \/ 6/, and image array layer (@baseArrayLayer@ + i) is
-- face index (i mod 6) of cube /i \/ 6/. If the number of layers in the
-- view, whether set explicitly in @layerCount@ or implied by
-- 'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', is not a multiple
-- of 6, the last cube map in the array /must/ not be accessed.
--
-- @aspectMask@ /must/ be only
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT',
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' or
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT' if
-- @format@ is a color, depth-only or stencil-only format, respectively,
-- except if @format@ is a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>.
-- If using a depth\/stencil format with both depth and stencil components,
-- @aspectMask@ /must/ include at least one of
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' and
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT', and
-- /can/ include both.
--
-- When the 'ImageSubresourceRange' structure is used to select a subset of
-- the slices of a 3D image’s mip level in order to create a 2D or 2D array
-- image view of a 3D image created with
-- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_2D_ARRAY_COMPATIBLE_BIT',
-- @baseArrayLayer@ and @layerCount@ specify the first slice index and the
-- number of slices to include in the created image view. Such an image
-- view /can/ be used as a framebuffer attachment that refers only to the
-- specified range of slices of the selected mip level. However, any layout
-- transitions performed on such an attachment view during a render pass
-- instance still apply to the entire subresource referenced which includes
-- all the slices of the selected mip level.
--
-- When using an image view of a depth\/stencil image to populate a
-- descriptor set (e.g. for sampling in the shader, or for use as an input
-- attachment), the @aspectMask@ /must/ only include one bit and selects
-- whether the image view is used for depth reads (i.e. using a
-- floating-point sampler or input attachment in the shader) or stencil
-- reads (i.e. using an unsigned integer sampler or input attachment in the
-- shader). When an image view of a depth\/stencil image is used as a
-- depth\/stencil framebuffer attachment, the @aspectMask@ is ignored and
-- both depth and stencil image subresources are used.
--
-- The 'Vulkan.Core10.ImageView.ComponentMapping' @components@ member
-- describes a remapping from components of the image to components of the
-- vector returned by shader image instructions. This remapping /must/ be
-- identity for storage image descriptors, input attachment descriptors,
-- framebuffer attachments, and any 'Vulkan.Core10.Handles.ImageView' used
-- with a combined image sampler that enables
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>.
--
-- When creating a 'Vulkan.Core10.Handles.ImageView', if
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>
-- is enabled in the sampler, the @aspectMask@ of a @subresourceRange@ used
-- by the 'Vulkan.Core10.Handles.ImageView' /must/ be
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT'.
--
-- When creating a 'Vulkan.Core10.Handles.ImageView', if sampler Y′CBCR
-- conversion is not enabled in the sampler and the image @format@ is
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar>,
-- the image /must/ have been created with
-- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_MUTABLE_FORMAT_BIT',
-- and the @aspectMask@ of the 'Vulkan.Core10.Handles.ImageView'’s
-- @subresourceRange@ /must/ be
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT',
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' or
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'.
--
-- == Valid Usage
--
-- -   If @levelCount@ is not
--     'Vulkan.Core10.APIConstants.REMAINING_MIP_LEVELS', it /must/ be
--     greater than @0@
--
-- -   If @layerCount@ is not
--     'Vulkan.Core10.APIConstants.REMAINING_ARRAY_LAYERS', it /must/ be
--     greater than @0@
--
-- -   If @aspectMask@ includes
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT',
--     then it /must/ not include any of
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT',
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT',
--     or
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'
--
-- -   @aspectMask@ /must/ not include
--     @VK_IMAGE_ASPECT_MEMORY_PLANE_i_BIT_EXT@ for any index @i@
--
-- == Valid Usage (Implicit)
--
-- -   @aspectMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlagBits' values
--
-- -   @aspectMask@ /must/ not be @0@
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlags',
-- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier',
-- 'Vulkan.Core10.ImageView.ImageViewCreateInfo',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdClearColorImage',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdClearDepthStencilImage'
data ImageSubresourceRange = ImageSubresourceRange
  { -- | @aspectMask@ is a bitmask of
    -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlagBits' specifying
    -- which aspect(s) of the image are included in the view.
    ImageSubresourceRange -> ImageAspectFlags
aspectMask :: ImageAspectFlags
  , -- | @baseMipLevel@ is the first mipmap level accessible to the view.
    ImageSubresourceRange -> Word32
baseMipLevel :: Word32
  , -- | @levelCount@ is the number of mipmap levels (starting from
    -- @baseMipLevel@) accessible to the view.
    ImageSubresourceRange -> Word32
levelCount :: Word32
  , -- | @baseArrayLayer@ is the first array layer accessible to the view.
    ImageSubresourceRange -> Word32
baseArrayLayer :: Word32
  , -- | @layerCount@ is the number of array layers (starting from
    -- @baseArrayLayer@) accessible to the view.
    ImageSubresourceRange -> Word32
layerCount :: Word32
  }
  deriving (Typeable, ImageSubresourceRange -> ImageSubresourceRange -> Bool
(ImageSubresourceRange -> ImageSubresourceRange -> Bool)
-> (ImageSubresourceRange -> ImageSubresourceRange -> Bool)
-> Eq ImageSubresourceRange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageSubresourceRange -> ImageSubresourceRange -> Bool
$c/= :: ImageSubresourceRange -> ImageSubresourceRange -> Bool
== :: ImageSubresourceRange -> ImageSubresourceRange -> Bool
$c== :: ImageSubresourceRange -> ImageSubresourceRange -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageSubresourceRange)
#endif
deriving instance Show ImageSubresourceRange

instance ToCStruct ImageSubresourceRange where
  withCStruct :: ImageSubresourceRange
-> (Ptr ImageSubresourceRange -> IO b) -> IO b
withCStruct x :: ImageSubresourceRange
x f :: Ptr ImageSubresourceRange -> IO b
f = Int -> Int -> (Ptr ImageSubresourceRange -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 20 4 ((Ptr ImageSubresourceRange -> IO b) -> IO b)
-> (Ptr ImageSubresourceRange -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ImageSubresourceRange
p -> Ptr ImageSubresourceRange -> ImageSubresourceRange -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageSubresourceRange
p ImageSubresourceRange
x (Ptr ImageSubresourceRange -> IO b
f Ptr ImageSubresourceRange
p)
  pokeCStruct :: Ptr ImageSubresourceRange -> ImageSubresourceRange -> IO b -> IO b
pokeCStruct p :: Ptr ImageSubresourceRange
p ImageSubresourceRange{..} f :: IO b
f = do
    Ptr ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags)) (ImageAspectFlags
aspectMask)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
baseMipLevel)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
levelCount)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) (Word32
baseArrayLayer)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
layerCount)
    IO b
f
  cStructSize :: Int
cStructSize = 20
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr ImageSubresourceRange -> IO b -> IO b
pokeZeroCStruct p :: Ptr ImageSubresourceRange
p f :: IO b
f = do
    Ptr ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags)) (ImageAspectFlags
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct ImageSubresourceRange where
  peekCStruct :: Ptr ImageSubresourceRange -> IO ImageSubresourceRange
peekCStruct p :: Ptr ImageSubresourceRange
p = do
    ImageAspectFlags
aspectMask <- Ptr ImageAspectFlags -> IO ImageAspectFlags
forall a. Storable a => Ptr a -> IO a
peek @ImageAspectFlags ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr ImageAspectFlags))
    Word32
baseMipLevel <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    Word32
levelCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    Word32
baseArrayLayer <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32))
    Word32
layerCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ImageSubresourceRange
p Ptr ImageSubresourceRange -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    ImageSubresourceRange -> IO ImageSubresourceRange
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageSubresourceRange -> IO ImageSubresourceRange)
-> ImageSubresourceRange -> IO ImageSubresourceRange
forall a b. (a -> b) -> a -> b
$ ImageAspectFlags
-> Word32 -> Word32 -> Word32 -> Word32 -> ImageSubresourceRange
ImageSubresourceRange
             ImageAspectFlags
aspectMask Word32
baseMipLevel Word32
levelCount Word32
baseArrayLayer Word32
layerCount

instance Storable ImageSubresourceRange where
  sizeOf :: ImageSubresourceRange -> Int
sizeOf ~ImageSubresourceRange
_ = 20
  alignment :: ImageSubresourceRange -> Int
alignment ~ImageSubresourceRange
_ = 4
  peek :: Ptr ImageSubresourceRange -> IO ImageSubresourceRange
peek = Ptr ImageSubresourceRange -> IO ImageSubresourceRange
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr ImageSubresourceRange -> ImageSubresourceRange -> IO ()
poke ptr :: Ptr ImageSubresourceRange
ptr poked :: ImageSubresourceRange
poked = Ptr ImageSubresourceRange
-> ImageSubresourceRange -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageSubresourceRange
ptr ImageSubresourceRange
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero ImageSubresourceRange where
  zero :: ImageSubresourceRange
zero = ImageAspectFlags
-> Word32 -> Word32 -> Word32 -> Word32 -> ImageSubresourceRange
ImageSubresourceRange
           ImageAspectFlags
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


-- | VkClearDepthStencilValue - Structure specifying a clear depth stencil
-- value
--
-- == Valid Usage
--
-- -   Unless the @VK_EXT_depth_range_unrestricted@ extension is enabled
--     @depth@ /must/ be between @0.0@ and @1.0@, inclusive
--
-- = See Also
--
-- 'ClearValue',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdClearDepthStencilImage'
data ClearDepthStencilValue = ClearDepthStencilValue
  { -- | @depth@ is the clear value for the depth aspect of the depth\/stencil
    -- attachment. It is a floating-point value which is automatically
    -- converted to the attachment’s format.
    ClearDepthStencilValue -> Float
depth :: Float
  , -- | @stencil@ is the clear value for the stencil aspect of the
    -- depth\/stencil attachment. It is a 32-bit integer value which is
    -- converted to the attachment’s format by taking the appropriate number of
    -- LSBs.
    ClearDepthStencilValue -> Word32
stencil :: Word32
  }
  deriving (Typeable, ClearDepthStencilValue -> ClearDepthStencilValue -> Bool
(ClearDepthStencilValue -> ClearDepthStencilValue -> Bool)
-> (ClearDepthStencilValue -> ClearDepthStencilValue -> Bool)
-> Eq ClearDepthStencilValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClearDepthStencilValue -> ClearDepthStencilValue -> Bool
$c/= :: ClearDepthStencilValue -> ClearDepthStencilValue -> Bool
== :: ClearDepthStencilValue -> ClearDepthStencilValue -> Bool
$c== :: ClearDepthStencilValue -> ClearDepthStencilValue -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ClearDepthStencilValue)
#endif
deriving instance Show ClearDepthStencilValue

instance ToCStruct ClearDepthStencilValue where
  withCStruct :: ClearDepthStencilValue
-> (Ptr ClearDepthStencilValue -> IO b) -> IO b
withCStruct x :: ClearDepthStencilValue
x f :: Ptr ClearDepthStencilValue -> IO b
f = Int -> Int -> (Ptr ClearDepthStencilValue -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 8 4 ((Ptr ClearDepthStencilValue -> IO b) -> IO b)
-> (Ptr ClearDepthStencilValue -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ClearDepthStencilValue
p -> Ptr ClearDepthStencilValue
-> ClearDepthStencilValue -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ClearDepthStencilValue
p ClearDepthStencilValue
x (Ptr ClearDepthStencilValue -> IO b
f Ptr ClearDepthStencilValue
p)
  pokeCStruct :: Ptr ClearDepthStencilValue
-> ClearDepthStencilValue -> IO b -> IO b
pokeCStruct p :: Ptr ClearDepthStencilValue
p ClearDepthStencilValue{..} f :: IO b
f = do
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ClearDepthStencilValue
p Ptr ClearDepthStencilValue -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
depth))
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ClearDepthStencilValue
p Ptr ClearDepthStencilValue -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
stencil)
    IO b
f
  cStructSize :: Int
cStructSize = 8
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr ClearDepthStencilValue -> IO b -> IO b
pokeZeroCStruct p :: Ptr ClearDepthStencilValue
p f :: IO b
f = do
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ClearDepthStencilValue
p Ptr ClearDepthStencilValue -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ClearDepthStencilValue
p Ptr ClearDepthStencilValue -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct ClearDepthStencilValue where
  peekCStruct :: Ptr ClearDepthStencilValue -> IO ClearDepthStencilValue
peekCStruct p :: Ptr ClearDepthStencilValue
p = do
    CFloat
depth <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr ClearDepthStencilValue
p Ptr ClearDepthStencilValue -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr CFloat))
    Word32
stencil <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ClearDepthStencilValue
p Ptr ClearDepthStencilValue -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    ClearDepthStencilValue -> IO ClearDepthStencilValue
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ClearDepthStencilValue -> IO ClearDepthStencilValue)
-> ClearDepthStencilValue -> IO ClearDepthStencilValue
forall a b. (a -> b) -> a -> b
$ Float -> Word32 -> ClearDepthStencilValue
ClearDepthStencilValue
             ((\(CFloat a :: Float
a) -> Float
a) CFloat
depth) Word32
stencil

instance Storable ClearDepthStencilValue where
  sizeOf :: ClearDepthStencilValue -> Int
sizeOf ~ClearDepthStencilValue
_ = 8
  alignment :: ClearDepthStencilValue -> Int
alignment ~ClearDepthStencilValue
_ = 4
  peek :: Ptr ClearDepthStencilValue -> IO ClearDepthStencilValue
peek = Ptr ClearDepthStencilValue -> IO ClearDepthStencilValue
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr ClearDepthStencilValue -> ClearDepthStencilValue -> IO ()
poke ptr :: Ptr ClearDepthStencilValue
ptr poked :: ClearDepthStencilValue
poked = Ptr ClearDepthStencilValue
-> ClearDepthStencilValue -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ClearDepthStencilValue
ptr ClearDepthStencilValue
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero ClearDepthStencilValue where
  zero :: ClearDepthStencilValue
zero = Float -> Word32 -> ClearDepthStencilValue
ClearDepthStencilValue
           Float
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


data ClearColorValue
  = Float32 ((Float, Float, Float, Float))
  | Int32 ((Int32, Int32, Int32, Int32))
  | Uint32 ((Word32, Word32, Word32, Word32))
  deriving (Int -> ClearColorValue -> ShowS
[ClearColorValue] -> ShowS
ClearColorValue -> String
(Int -> ClearColorValue -> ShowS)
-> (ClearColorValue -> String)
-> ([ClearColorValue] -> ShowS)
-> Show ClearColorValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClearColorValue] -> ShowS
$cshowList :: [ClearColorValue] -> ShowS
show :: ClearColorValue -> String
$cshow :: ClearColorValue -> String
showsPrec :: Int -> ClearColorValue -> ShowS
$cshowsPrec :: Int -> ClearColorValue -> ShowS
Show)

instance ToCStruct ClearColorValue where
  withCStruct :: ClearColorValue -> (Ptr ClearColorValue -> IO b) -> IO b
withCStruct x :: ClearColorValue
x f :: Ptr ClearColorValue -> IO b
f = Int -> Int -> (Ptr ClearColorValue -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 4 ((Ptr ClearColorValue -> IO b) -> IO b)
-> (Ptr ClearColorValue -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ClearColorValue
p -> Ptr ClearColorValue -> ClearColorValue -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ClearColorValue
p ClearColorValue
x (Ptr ClearColorValue -> IO b
f Ptr ClearColorValue
p)
  pokeCStruct :: Ptr ClearColorValue -> ClearColorValue -> IO a -> IO a
  pokeCStruct :: Ptr ClearColorValue -> ClearColorValue -> IO a -> IO a
pokeCStruct p :: Ptr ClearColorValue
p = (((() -> IO a) -> IO a) -> (IO a -> () -> IO a) -> IO a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> () -> IO a
forall a b. a -> b -> a
const) (((() -> IO a) -> IO a) -> IO a -> IO a)
-> (ClearColorValue -> (() -> IO a) -> IO a)
-> ClearColorValue
-> IO a
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT a IO () -> (() -> IO a) -> IO a
forall k (r :: k) (m :: k -> *) a. ContT r m a -> (a -> m r) -> m r
runContT (ContT a IO () -> (() -> IO a) -> IO a)
-> (ClearColorValue -> ContT a IO ())
-> ClearColorValue
-> (() -> IO a)
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  \case
    Float32 v :: (Float, Float, Float, Float)
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ do
      let pFloat32 :: Ptr CFloat
pFloat32 = Ptr (FixedArray 4 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (Ptr ClearColorValue -> Ptr (FixedArray 4 CFloat)
forall a b. Ptr a -> Ptr b
castPtr @_ @(FixedArray 4 CFloat) Ptr ClearColorValue
p)
      case ((Float, Float, Float, Float)
v) of
        (e0 :: Float
e0, e1 :: Float
e1, e2 :: Float
e2, e3 :: Float
e3) -> do
          Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pFloat32 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0))
          Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pFloat32 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1))
          Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pFloat32 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e2))
          Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pFloat32 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e3))
    Int32 v :: (Int32, Int32, Int32, Int32)
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ do
      let pInt32 :: Ptr Int32
pInt32 = Ptr (FixedArray 4 Int32) -> Ptr Int32
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (Ptr ClearColorValue -> Ptr (FixedArray 4 Int32)
forall a b. Ptr a -> Ptr b
castPtr @_ @(FixedArray 4 Int32) Ptr ClearColorValue
p)
      case ((Int32, Int32, Int32, Int32)
v) of
        (e0 :: Int32
e0, e1 :: Int32
e1, e2 :: Int32
e2, e3 :: Int32
e3) -> do
          Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Int32
pInt32 :: Ptr Int32) (Int32
e0)
          Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Int32
pInt32 Ptr Int32 -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Int32) (Int32
e1)
          Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Int32
pInt32 Ptr Int32 -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Int32) (Int32
e2)
          Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Int32
pInt32 Ptr Int32 -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Int32) (Int32
e3)
    Uint32 v :: (Word32, Word32, Word32, Word32)
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ do
      let pUint32 :: Ptr Word32
pUint32 = Ptr (FixedArray 4 Word32) -> Ptr Word32
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (Ptr ClearColorValue -> Ptr (FixedArray 4 Word32)
forall a b. Ptr a -> Ptr b
castPtr @_ @(FixedArray 4 Word32) Ptr ClearColorValue
p)
      case ((Word32, Word32, Word32, Word32)
v) of
        (e0 :: Word32
e0, e1 :: Word32
e1, e2 :: Word32
e2, e3 :: Word32
e3) -> do
          Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pUint32 :: Ptr Word32) (Word32
e0)
          Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pUint32 Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32) (Word32
e1)
          Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pUint32 Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32) (Word32
e2)
          Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pUint32 Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32) (Word32
e3)
  pokeZeroCStruct :: Ptr ClearColorValue -> IO b -> IO b
  pokeZeroCStruct :: Ptr ClearColorValue -> IO b -> IO b
pokeZeroCStruct _ f :: IO b
f = IO b
f
  cStructSize :: Int
cStructSize = 16
  cStructAlignment :: Int
cStructAlignment = 4

instance Zero ClearColorValue where
  zero :: ClearColorValue
zero = (Float, Float, Float, Float) -> ClearColorValue
Float32 (Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero)


data ClearValue
  = Color ClearColorValue
  | DepthStencil ClearDepthStencilValue
  deriving (Int -> ClearValue -> ShowS
[ClearValue] -> ShowS
ClearValue -> String
(Int -> ClearValue -> ShowS)
-> (ClearValue -> String)
-> ([ClearValue] -> ShowS)
-> Show ClearValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClearValue] -> ShowS
$cshowList :: [ClearValue] -> ShowS
show :: ClearValue -> String
$cshow :: ClearValue -> String
showsPrec :: Int -> ClearValue -> ShowS
$cshowsPrec :: Int -> ClearValue -> ShowS
Show)

instance ToCStruct ClearValue where
  withCStruct :: ClearValue -> (Ptr ClearValue -> IO b) -> IO b
withCStruct x :: ClearValue
x f :: Ptr ClearValue -> IO b
f = Int -> Int -> (Ptr ClearValue -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 4 ((Ptr ClearValue -> IO b) -> IO b)
-> (Ptr ClearValue -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ClearValue
p -> Ptr ClearValue -> ClearValue -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ClearValue
p ClearValue
x (Ptr ClearValue -> IO b
f Ptr ClearValue
p)
  pokeCStruct :: Ptr ClearValue -> ClearValue -> IO a -> IO a
  pokeCStruct :: Ptr ClearValue -> ClearValue -> IO a -> IO a
pokeCStruct p :: Ptr ClearValue
p = (((() -> IO a) -> IO a) -> (IO a -> () -> IO a) -> IO a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> () -> IO a
forall a b. a -> b -> a
const) (((() -> IO a) -> IO a) -> IO a -> IO a)
-> (ClearValue -> (() -> IO a) -> IO a)
-> ClearValue
-> IO a
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT a IO () -> (() -> IO a) -> IO a
forall k (r :: k) (m :: k -> *) a. ContT r m a -> (a -> m r) -> m r
runContT (ContT a IO () -> (() -> IO a) -> IO a)
-> (ClearValue -> ContT a IO ())
-> ClearValue
-> (() -> IO a)
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  \case
    Color v :: ClearColorValue
v -> ((() -> IO a) -> IO a) -> ContT a IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO a) -> IO a) -> ContT a IO ())
-> ((() -> IO a) -> IO a) -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ClearColorValue -> ClearColorValue -> IO a -> IO a
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr ClearValue -> Ptr ClearColorValue
forall a b. Ptr a -> Ptr b
castPtr @_ @ClearColorValue Ptr ClearValue
p) (ClearColorValue
v) (IO a -> IO a) -> ((() -> IO a) -> IO a) -> (() -> IO a) -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO a) -> () -> IO a
forall a b. (a -> b) -> a -> b
$ ())
    DepthStencil v :: ClearDepthStencilValue
v -> ((() -> IO a) -> IO a) -> ContT a IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO a) -> IO a) -> ContT a IO ())
-> ((() -> IO a) -> IO a) -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ClearDepthStencilValue
-> ClearDepthStencilValue -> IO a -> IO a
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr ClearValue -> Ptr ClearDepthStencilValue
forall a b. Ptr a -> Ptr b
castPtr @_ @ClearDepthStencilValue Ptr ClearValue
p) (ClearDepthStencilValue
v) (IO a -> IO a) -> ((() -> IO a) -> IO a) -> (() -> IO a) -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO a) -> () -> IO a
forall a b. (a -> b) -> a -> b
$ ())
  pokeZeroCStruct :: Ptr ClearValue -> IO b -> IO b
  pokeZeroCStruct :: Ptr ClearValue -> IO b -> IO b
pokeZeroCStruct _ f :: IO b
f = IO b
f
  cStructSize :: Int
cStructSize = 16
  cStructAlignment :: Int
cStructAlignment = 4

instance Zero ClearValue where
  zero :: ClearValue
zero = ClearColorValue -> ClearValue
Color ClearColorValue
forall a. Zero a => a
zero