{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_depth_clamp_zero_one ( PhysicalDeviceDepthClampZeroOneFeaturesEXT(..)
, EXT_DEPTH_CLAMP_ZERO_ONE_SPEC_VERSION
, pattern EXT_DEPTH_CLAMP_ZERO_ONE_SPEC_VERSION
, EXT_DEPTH_CLAMP_ZERO_ONE_EXTENSION_NAME
, pattern EXT_DEPTH_CLAMP_ZERO_ONE_EXTENSION_NAME
) 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.String (IsString)
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_DEPTH_CLAMP_ZERO_ONE_FEATURES_EXT))
data PhysicalDeviceDepthClampZeroOneFeaturesEXT = PhysicalDeviceDepthClampZeroOneFeaturesEXT
{
PhysicalDeviceDepthClampZeroOneFeaturesEXT -> Bool
depthClampZeroOne :: Bool }
deriving (Typeable, PhysicalDeviceDepthClampZeroOneFeaturesEXT
-> PhysicalDeviceDepthClampZeroOneFeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceDepthClampZeroOneFeaturesEXT
-> PhysicalDeviceDepthClampZeroOneFeaturesEXT -> Bool
$c/= :: PhysicalDeviceDepthClampZeroOneFeaturesEXT
-> PhysicalDeviceDepthClampZeroOneFeaturesEXT -> Bool
== :: PhysicalDeviceDepthClampZeroOneFeaturesEXT
-> PhysicalDeviceDepthClampZeroOneFeaturesEXT -> Bool
$c== :: PhysicalDeviceDepthClampZeroOneFeaturesEXT
-> PhysicalDeviceDepthClampZeroOneFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDepthClampZeroOneFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceDepthClampZeroOneFeaturesEXT
instance ToCStruct PhysicalDeviceDepthClampZeroOneFeaturesEXT where
withCStruct :: forall b.
PhysicalDeviceDepthClampZeroOneFeaturesEXT
-> (Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceDepthClampZeroOneFeaturesEXT
x Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
p PhysicalDeviceDepthClampZeroOneFeaturesEXT
x (Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT -> IO b
f Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
-> PhysicalDeviceDepthClampZeroOneFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
p PhysicalDeviceDepthClampZeroOneFeaturesEXT{Bool
depthClampZeroOne :: Bool
$sel:depthClampZeroOne:PhysicalDeviceDepthClampZeroOneFeaturesEXT :: PhysicalDeviceDepthClampZeroOneFeaturesEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_CLAMP_ZERO_ONE_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
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 PhysicalDeviceDepthClampZeroOneFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
depthClampZeroOne))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_CLAMP_ZERO_ONE_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
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 PhysicalDeviceDepthClampZeroOneFeaturesEXT
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 PhysicalDeviceDepthClampZeroOneFeaturesEXT where
peekCStruct :: Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
-> IO PhysicalDeviceDepthClampZeroOneFeaturesEXT
peekCStruct Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
p = do
Bool32
depthClampZeroOne <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
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 -> PhysicalDeviceDepthClampZeroOneFeaturesEXT
PhysicalDeviceDepthClampZeroOneFeaturesEXT
(Bool32 -> Bool
bool32ToBool Bool32
depthClampZeroOne)
instance Storable PhysicalDeviceDepthClampZeroOneFeaturesEXT where
sizeOf :: PhysicalDeviceDepthClampZeroOneFeaturesEXT -> Int
sizeOf ~PhysicalDeviceDepthClampZeroOneFeaturesEXT
_ = Int
24
alignment :: PhysicalDeviceDepthClampZeroOneFeaturesEXT -> Int
alignment ~PhysicalDeviceDepthClampZeroOneFeaturesEXT
_ = Int
8
peek :: Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
-> IO PhysicalDeviceDepthClampZeroOneFeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
-> PhysicalDeviceDepthClampZeroOneFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
ptr PhysicalDeviceDepthClampZeroOneFeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceDepthClampZeroOneFeaturesEXT where
zero :: PhysicalDeviceDepthClampZeroOneFeaturesEXT
zero = Bool -> PhysicalDeviceDepthClampZeroOneFeaturesEXT
PhysicalDeviceDepthClampZeroOneFeaturesEXT
forall a. Zero a => a
zero
type EXT_DEPTH_CLAMP_ZERO_ONE_SPEC_VERSION = 1
pattern EXT_DEPTH_CLAMP_ZERO_ONE_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_DEPTH_CLAMP_ZERO_ONE_SPEC_VERSION :: forall a. Integral a => a
$mEXT_DEPTH_CLAMP_ZERO_ONE_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_DEPTH_CLAMP_ZERO_ONE_SPEC_VERSION = 1
type EXT_DEPTH_CLAMP_ZERO_ONE_EXTENSION_NAME = "VK_EXT_depth_clamp_zero_one"
pattern EXT_DEPTH_CLAMP_ZERO_ONE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_DEPTH_CLAMP_ZERO_ONE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_DEPTH_CLAMP_ZERO_ONE_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_DEPTH_CLAMP_ZERO_ONE_EXTENSION_NAME = "VK_EXT_depth_clamp_zero_one"