{-# language CPP #-}
module Vulkan.Core11.Promoted_From_VK_KHR_shader_draw_parameters ( pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_DRAW_PARAMETER_FEATURES
, PhysicalDeviceShaderDrawParametersFeatures(..)
, PhysicalDeviceShaderDrawParameterFeatures
, 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_SHADER_DRAW_PARAMETERS_FEATURES))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
pattern $bSTRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_DRAW_PARAMETER_FEATURES :: StructureType
$mSTRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_DRAW_PARAMETER_FEATURES :: forall {r}. StructureType -> ((# #) -> r) -> ((# #) -> r) -> r
STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_DRAW_PARAMETER_FEATURES = STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_DRAW_PARAMETERS_FEATURES
data PhysicalDeviceShaderDrawParametersFeatures = PhysicalDeviceShaderDrawParametersFeatures
{
PhysicalDeviceShaderDrawParametersFeatures -> Bool
shaderDrawParameters :: Bool }
deriving (Typeable, PhysicalDeviceShaderDrawParametersFeatures
-> PhysicalDeviceShaderDrawParametersFeatures -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceShaderDrawParametersFeatures
-> PhysicalDeviceShaderDrawParametersFeatures -> Bool
$c/= :: PhysicalDeviceShaderDrawParametersFeatures
-> PhysicalDeviceShaderDrawParametersFeatures -> Bool
== :: PhysicalDeviceShaderDrawParametersFeatures
-> PhysicalDeviceShaderDrawParametersFeatures -> Bool
$c== :: PhysicalDeviceShaderDrawParametersFeatures
-> PhysicalDeviceShaderDrawParametersFeatures -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceShaderDrawParametersFeatures)
#endif
deriving instance Show PhysicalDeviceShaderDrawParametersFeatures
instance ToCStruct PhysicalDeviceShaderDrawParametersFeatures where
withCStruct :: forall b.
PhysicalDeviceShaderDrawParametersFeatures
-> (Ptr PhysicalDeviceShaderDrawParametersFeatures -> IO b) -> IO b
withCStruct PhysicalDeviceShaderDrawParametersFeatures
x Ptr PhysicalDeviceShaderDrawParametersFeatures -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceShaderDrawParametersFeatures
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceShaderDrawParametersFeatures
p PhysicalDeviceShaderDrawParametersFeatures
x (Ptr PhysicalDeviceShaderDrawParametersFeatures -> IO b
f Ptr PhysicalDeviceShaderDrawParametersFeatures
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceShaderDrawParametersFeatures
-> PhysicalDeviceShaderDrawParametersFeatures -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceShaderDrawParametersFeatures
p PhysicalDeviceShaderDrawParametersFeatures{Bool
shaderDrawParameters :: Bool
$sel:shaderDrawParameters:PhysicalDeviceShaderDrawParametersFeatures :: PhysicalDeviceShaderDrawParametersFeatures -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderDrawParametersFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_DRAW_PARAMETERS_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderDrawParametersFeatures
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 PhysicalDeviceShaderDrawParametersFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
shaderDrawParameters))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceShaderDrawParametersFeatures -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceShaderDrawParametersFeatures
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderDrawParametersFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_DRAW_PARAMETERS_FEATURES)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceShaderDrawParametersFeatures
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 PhysicalDeviceShaderDrawParametersFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceShaderDrawParametersFeatures where
peekCStruct :: Ptr PhysicalDeviceShaderDrawParametersFeatures
-> IO PhysicalDeviceShaderDrawParametersFeatures
peekCStruct Ptr PhysicalDeviceShaderDrawParametersFeatures
p = do
Bool32
shaderDrawParameters <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceShaderDrawParametersFeatures
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceShaderDrawParametersFeatures
PhysicalDeviceShaderDrawParametersFeatures
(Bool32 -> Bool
bool32ToBool Bool32
shaderDrawParameters)
instance Storable PhysicalDeviceShaderDrawParametersFeatures where
sizeOf :: PhysicalDeviceShaderDrawParametersFeatures -> Int
sizeOf ~PhysicalDeviceShaderDrawParametersFeatures
_ = Int
24
alignment :: PhysicalDeviceShaderDrawParametersFeatures -> Int
alignment ~PhysicalDeviceShaderDrawParametersFeatures
_ = Int
8
peek :: Ptr PhysicalDeviceShaderDrawParametersFeatures
-> IO PhysicalDeviceShaderDrawParametersFeatures
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceShaderDrawParametersFeatures
-> PhysicalDeviceShaderDrawParametersFeatures -> IO ()
poke Ptr PhysicalDeviceShaderDrawParametersFeatures
ptr PhysicalDeviceShaderDrawParametersFeatures
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceShaderDrawParametersFeatures
ptr PhysicalDeviceShaderDrawParametersFeatures
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceShaderDrawParametersFeatures where
zero :: PhysicalDeviceShaderDrawParametersFeatures
zero = Bool -> PhysicalDeviceShaderDrawParametersFeatures
PhysicalDeviceShaderDrawParametersFeatures
forall a. Zero a => a
zero
type PhysicalDeviceShaderDrawParameterFeatures = PhysicalDeviceShaderDrawParametersFeatures