{-# language CPP #-}
module Graphics.Vulkan.Core12.Promoted_From_VK_KHR_shader_float16_int8  ( PhysicalDeviceShaderFloat16Int8Features(..)
                                                                        , StructureType(..)
                                                                        ) where

import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Graphics.Vulkan.Core10.BaseType (bool32ToBool)
import Graphics.Vulkan.Core10.BaseType (boolToBool32)
import Graphics.Vulkan.Core10.BaseType (Bool32)
import Graphics.Vulkan.CStruct (FromCStruct)
import Graphics.Vulkan.CStruct (FromCStruct(..))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType)
import Graphics.Vulkan.CStruct (ToCStruct)
import Graphics.Vulkan.CStruct (ToCStruct(..))
import Graphics.Vulkan.Zero (Zero(..))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_FLOAT16_INT8_FEATURES))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType(..))
-- | VkPhysicalDeviceShaderFloat16Int8Features - Structure describing
-- features supported by VK_KHR_shader_float16_int8
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Graphics.Vulkan.Core10.BaseType.Bool32',
-- 'Graphics.Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceShaderFloat16Int8Features = PhysicalDeviceShaderFloat16Int8Features
  { -- | @shaderFloat16@ indicates whether 16-bit floats (halfs) are supported in
    -- shader code. This also indicates whether shader modules /can/ declare
    -- the @Float16@ capability. However, this only enables a subset of the
    -- storage classes that SPIR-V allows for the @Float16@ SPIR-V capability:
    -- Declaring and using 16-bit floats in the @Private@, @Workgroup@, and
    -- @Function@ storage classes is enabled, while declaring them in the
    -- interface storage classes (e.g., @UniformConstant@, @Uniform@,
    -- @StorageBuffer@, @Input@, @Output@, and @PushConstant@) is not enabled.
    shaderFloat16 :: Bool
  , -- | @shaderInt8@ indicates whether 8-bit integers (signed and unsigned) are
    -- supported in shader code. This also indicates whether shader modules
    -- /can/ declare the @Int8@ capability. However, this only enables a subset
    -- of the storage classes that SPIR-V allows for the @Int8@ SPIR-V
    -- capability: Declaring and using 8-bit integers in the @Private@,
    -- @Workgroup@, and @Function@ storage classes is enabled, while declaring
    -- them in the interface storage classes (e.g., @UniformConstant@,
    -- @Uniform@, @StorageBuffer@, @Input@, @Output@, and @PushConstant@) is
    -- not enabled.
    shaderInt8 :: Bool
  }
  deriving (Typeable)
deriving instance Show PhysicalDeviceShaderFloat16Int8Features

instance ToCStruct PhysicalDeviceShaderFloat16Int8Features where
  withCStruct x f = allocaBytesAligned 24 8 $ \p -> pokeCStruct p x (f p)
  pokeCStruct p PhysicalDeviceShaderFloat16Int8Features{..} f = do
    poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_FLOAT16_INT8_FEATURES)
    poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
    poke ((p `plusPtr` 16 :: Ptr Bool32)) (boolToBool32 (shaderFloat16))
    poke ((p `plusPtr` 20 :: Ptr Bool32)) (boolToBool32 (shaderInt8))
    f
  cStructSize = 24
  cStructAlignment = 8
  pokeZeroCStruct p f = do
    poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_FLOAT16_INT8_FEATURES)
    poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
    poke ((p `plusPtr` 16 :: Ptr Bool32)) (boolToBool32 (zero))
    poke ((p `plusPtr` 20 :: Ptr Bool32)) (boolToBool32 (zero))
    f

instance FromCStruct PhysicalDeviceShaderFloat16Int8Features where
  peekCStruct p = do
    shaderFloat16 <- peek @Bool32 ((p `plusPtr` 16 :: Ptr Bool32))
    shaderInt8 <- peek @Bool32 ((p `plusPtr` 20 :: Ptr Bool32))
    pure $ PhysicalDeviceShaderFloat16Int8Features
             (bool32ToBool shaderFloat16) (bool32ToBool shaderInt8)

instance Storable PhysicalDeviceShaderFloat16Int8Features where
  sizeOf ~_ = 24
  alignment ~_ = 8
  peek = peekCStruct
  poke ptr poked = pokeCStruct ptr poked (pure ())

instance Zero PhysicalDeviceShaderFloat16Int8Features where
  zero = PhysicalDeviceShaderFloat16Int8Features
           zero
           zero