{-# language CPP #-}
module Vulkan.Core11.Promoted_From_VK_KHR_16bit_storage  ( PhysicalDevice16BitStorageFeatures(..)
                                                         , 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 GHC.Generics (Generic)
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_16BIT_STORAGE_FEATURES))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
-- | VkPhysicalDevice16BitStorageFeatures - Structure describing features
-- supported by VK_KHR_16bit_storage
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDevice16BitStorageFeatures = PhysicalDevice16BitStorageFeatures
  { -- | @storageBuffer16BitAccess@ specifies whether objects in the
    -- @StorageBuffer@ or @PhysicalStorageBuffer@ storage class with the
    -- @Block@ decoration /can/ have 16-bit integer and 16-bit floating-point
    -- members. If this feature is not enabled, 16-bit integer or 16-bit
    -- floating-point members /must/ not be used in such objects. This also
    -- specifies whether shader modules /can/ declare the
    -- @StorageBuffer16BitAccess@ capability.
    PhysicalDevice16BitStorageFeatures -> Bool
storageBuffer16BitAccess :: Bool
  , -- | @uniformAndStorageBuffer16BitAccess@ specifies whether objects in the
    -- @Uniform@ storage class with the @Block@ decoration and in the
    -- @StorageBuffer@ or @PhysicalStorageBuffer@ storage class with the same
    -- decoration /can/ have 16-bit integer and 16-bit floating-point members.
    -- If this feature is not enabled, 16-bit integer or 16-bit floating-point
    -- members /must/ not be used in such objects. This also specifies whether
    -- shader modules /can/ declare the @UniformAndStorageBuffer16BitAccess@
    -- capability.
    PhysicalDevice16BitStorageFeatures -> Bool
uniformAndStorageBuffer16BitAccess :: Bool
  , -- | @storagePushConstant16@ specifies whether objects in the @PushConstant@
    -- storage class /can/ have 16-bit integer and 16-bit floating-point
    -- members. If this feature is not enabled, 16-bit integer or
    -- floating-point members /must/ not be used in such objects. This also
    -- specifies whether shader modules /can/ declare the
    -- @StoragePushConstant16@ capability.
    PhysicalDevice16BitStorageFeatures -> Bool
storagePushConstant16 :: Bool
  , -- | @storageInputOutput16@ specifies whether objects in the @Input@ and
    -- @Output@ storage classes /can/ have 16-bit integer and 16-bit
    -- floating-point members. If this feature is not enabled, 16-bit integer
    -- or 16-bit floating-point members /must/ not be used in such objects.
    -- This also specifies whether shader modules /can/ declare the
    -- @StorageInputOutput16@ capability.
    PhysicalDevice16BitStorageFeatures -> Bool
storageInputOutput16 :: Bool
  }
  deriving (Typeable, PhysicalDevice16BitStorageFeatures
-> PhysicalDevice16BitStorageFeatures -> Bool
(PhysicalDevice16BitStorageFeatures
 -> PhysicalDevice16BitStorageFeatures -> Bool)
-> (PhysicalDevice16BitStorageFeatures
    -> PhysicalDevice16BitStorageFeatures -> Bool)
-> Eq PhysicalDevice16BitStorageFeatures
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDevice16BitStorageFeatures
-> PhysicalDevice16BitStorageFeatures -> Bool
$c/= :: PhysicalDevice16BitStorageFeatures
-> PhysicalDevice16BitStorageFeatures -> Bool
== :: PhysicalDevice16BitStorageFeatures
-> PhysicalDevice16BitStorageFeatures -> Bool
$c== :: PhysicalDevice16BitStorageFeatures
-> PhysicalDevice16BitStorageFeatures -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDevice16BitStorageFeatures)
#endif
deriving instance Show PhysicalDevice16BitStorageFeatures

instance ToCStruct PhysicalDevice16BitStorageFeatures where
  withCStruct :: PhysicalDevice16BitStorageFeatures
-> (Ptr PhysicalDevice16BitStorageFeatures -> IO b) -> IO b
withCStruct x :: PhysicalDevice16BitStorageFeatures
x f :: Ptr PhysicalDevice16BitStorageFeatures -> IO b
f = Int
-> Int -> (Ptr PhysicalDevice16BitStorageFeatures -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr PhysicalDevice16BitStorageFeatures -> IO b) -> IO b)
-> (Ptr PhysicalDevice16BitStorageFeatures -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDevice16BitStorageFeatures
p -> Ptr PhysicalDevice16BitStorageFeatures
-> PhysicalDevice16BitStorageFeatures -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevice16BitStorageFeatures
p PhysicalDevice16BitStorageFeatures
x (Ptr PhysicalDevice16BitStorageFeatures -> IO b
f Ptr PhysicalDevice16BitStorageFeatures
p)
  pokeCStruct :: Ptr PhysicalDevice16BitStorageFeatures
-> PhysicalDevice16BitStorageFeatures -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDevice16BitStorageFeatures
p PhysicalDevice16BitStorageFeatures{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_16BIT_STORAGE_FEATURES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storageBuffer16BitAccess))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
uniformAndStorageBuffer16BitAccess))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storagePushConstant16))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storageInputOutput16))
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDevice16BitStorageFeatures -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDevice16BitStorageFeatures
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_16BIT_STORAGE_FEATURES)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDevice16BitStorageFeatures where
  peekCStruct :: Ptr PhysicalDevice16BitStorageFeatures
-> IO PhysicalDevice16BitStorageFeatures
peekCStruct p :: Ptr PhysicalDevice16BitStorageFeatures
p = do
    Bool32
storageBuffer16BitAccess <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    Bool32
uniformAndStorageBuffer16BitAccess <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    Bool32
storagePushConstant16 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32))
    Bool32
storageInputOutput16 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevice16BitStorageFeatures
p Ptr PhysicalDevice16BitStorageFeatures -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32))
    PhysicalDevice16BitStorageFeatures
-> IO PhysicalDevice16BitStorageFeatures
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDevice16BitStorageFeatures
 -> IO PhysicalDevice16BitStorageFeatures)
-> PhysicalDevice16BitStorageFeatures
-> IO PhysicalDevice16BitStorageFeatures
forall a b. (a -> b) -> a -> b
$ Bool -> Bool -> Bool -> Bool -> PhysicalDevice16BitStorageFeatures
PhysicalDevice16BitStorageFeatures
             (Bool32 -> Bool
bool32ToBool Bool32
storageBuffer16BitAccess) (Bool32 -> Bool
bool32ToBool Bool32
uniformAndStorageBuffer16BitAccess) (Bool32 -> Bool
bool32ToBool Bool32
storagePushConstant16) (Bool32 -> Bool
bool32ToBool Bool32
storageInputOutput16)

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

instance Zero PhysicalDevice16BitStorageFeatures where
  zero :: PhysicalDevice16BitStorageFeatures
zero = Bool -> Bool -> Bool -> Bool -> PhysicalDevice16BitStorageFeatures
PhysicalDevice16BitStorageFeatures
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero