{-# language CPP #-}
module Vulkan.Core11.Promoted_From_VK_KHR_16bit_storage ( PhysicalDevice16BitStorageFeatures(..)
, StructureType(..)
) where
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
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.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_16BIT_STORAGE_FEATURES))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
data PhysicalDevice16BitStorageFeatures = PhysicalDevice16BitStorageFeatures
{
PhysicalDevice16BitStorageFeatures -> Bool
storageBuffer16BitAccess :: Bool
,
PhysicalDevice16BitStorageFeatures -> Bool
uniformAndStorageBuffer16BitAccess :: Bool
,
PhysicalDevice16BitStorageFeatures -> Bool
storagePushConstant16 :: Bool
,
PhysicalDevice16BitStorageFeatures -> Bool
storageInputOutput16 :: Bool
}
deriving (Typeable, PhysicalDevice16BitStorageFeatures
-> PhysicalDevice16BitStorageFeatures -> Bool
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 :: forall b.
PhysicalDevice16BitStorageFeatures
-> (Ptr PhysicalDevice16BitStorageFeatures -> IO b) -> IO b
withCStruct PhysicalDevice16BitStorageFeatures
x Ptr PhysicalDevice16BitStorageFeatures -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDevice16BitStorageFeatures
p -> 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 :: forall b.
Ptr PhysicalDevice16BitStorageFeatures
-> PhysicalDevice16BitStorageFeatures -> IO b -> IO b
pokeCStruct Ptr PhysicalDevice16BitStorageFeatures
p PhysicalDevice16BitStorageFeatures{Bool
storageInputOutput16 :: Bool
storagePushConstant16 :: Bool
uniformAndStorageBuffer16BitAccess :: Bool
storageBuffer16BitAccess :: Bool
$sel:storageInputOutput16:PhysicalDevice16BitStorageFeatures :: PhysicalDevice16BitStorageFeatures -> Bool
$sel:storagePushConstant16:PhysicalDevice16BitStorageFeatures :: PhysicalDevice16BitStorageFeatures -> Bool
$sel:uniformAndStorageBuffer16BitAccess:PhysicalDevice16BitStorageFeatures :: PhysicalDevice16BitStorageFeatures -> Bool
$sel:storageBuffer16BitAccess:PhysicalDevice16BitStorageFeatures :: PhysicalDevice16BitStorageFeatures -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_16BIT_STORAGE_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storageBuffer16BitAccess))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
uniformAndStorageBuffer16BitAccess))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storagePushConstant16))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
storageInputOutput16))
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr PhysicalDevice16BitStorageFeatures -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDevice16BitStorageFeatures
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_16BIT_STORAGE_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDevice16BitStorageFeatures where
peekCStruct :: Ptr PhysicalDevice16BitStorageFeatures
-> IO PhysicalDevice16BitStorageFeatures
peekCStruct Ptr PhysicalDevice16BitStorageFeatures
p = do
Bool32
storageBuffer16BitAccess <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
uniformAndStorageBuffer16BitAccess <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
Bool32
storagePushConstant16 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
Bool32
storageInputOutput16 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDevice16BitStorageFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure 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
_ = Int
32
alignment :: PhysicalDevice16BitStorageFeatures -> Int
alignment ~PhysicalDevice16BitStorageFeatures
_ = Int
8
peek :: Ptr PhysicalDevice16BitStorageFeatures
-> IO PhysicalDevice16BitStorageFeatures
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDevice16BitStorageFeatures
-> PhysicalDevice16BitStorageFeatures -> IO ()
poke Ptr PhysicalDevice16BitStorageFeatures
ptr PhysicalDevice16BitStorageFeatures
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDevice16BitStorageFeatures
ptr PhysicalDevice16BitStorageFeatures
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDevice16BitStorageFeatures where
zero :: PhysicalDevice16BitStorageFeatures
zero = Bool -> Bool -> Bool -> Bool -> PhysicalDevice16BitStorageFeatures
PhysicalDevice16BitStorageFeatures
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero