{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_depth_clip_enable ( PhysicalDeviceDepthClipEnableFeaturesEXT(..)
, PipelineRasterizationDepthClipStateCreateInfoEXT(..)
, PipelineRasterizationDepthClipStateCreateFlagsEXT(..)
, EXT_DEPTH_CLIP_ENABLE_SPEC_VERSION
, pattern EXT_DEPTH_CLIP_ENABLE_SPEC_VERSION
, EXT_DEPTH_CLIP_ENABLE_EXTENSION_NAME
, pattern EXT_DEPTH_CLIP_ENABLE_EXTENSION_NAME
) where
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showString)
import Numeric (showHex)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
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 GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_CLIP_ENABLE_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_RASTERIZATION_DEPTH_CLIP_STATE_CREATE_INFO_EXT))
data PhysicalDeviceDepthClipEnableFeaturesEXT = PhysicalDeviceDepthClipEnableFeaturesEXT
{
PhysicalDeviceDepthClipEnableFeaturesEXT -> Bool
depthClipEnable :: Bool }
deriving (Typeable, PhysicalDeviceDepthClipEnableFeaturesEXT
-> PhysicalDeviceDepthClipEnableFeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceDepthClipEnableFeaturesEXT
-> PhysicalDeviceDepthClipEnableFeaturesEXT -> Bool
$c/= :: PhysicalDeviceDepthClipEnableFeaturesEXT
-> PhysicalDeviceDepthClipEnableFeaturesEXT -> Bool
== :: PhysicalDeviceDepthClipEnableFeaturesEXT
-> PhysicalDeviceDepthClipEnableFeaturesEXT -> Bool
$c== :: PhysicalDeviceDepthClipEnableFeaturesEXT
-> PhysicalDeviceDepthClipEnableFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDepthClipEnableFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceDepthClipEnableFeaturesEXT
instance ToCStruct PhysicalDeviceDepthClipEnableFeaturesEXT where
withCStruct :: forall b.
PhysicalDeviceDepthClipEnableFeaturesEXT
-> (Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceDepthClipEnableFeaturesEXT
x Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p PhysicalDeviceDepthClipEnableFeaturesEXT
x (Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> IO b
f Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p)
pokeCStruct :: forall b.
Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
-> PhysicalDeviceDepthClipEnableFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p PhysicalDeviceDepthClipEnableFeaturesEXT{Bool
depthClipEnable :: Bool
$sel:depthClipEnable:PhysicalDeviceDepthClipEnableFeaturesEXT :: PhysicalDeviceDepthClipEnableFeaturesEXT -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_CLIP_ENABLE_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
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 PhysicalDeviceDepthClipEnableFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
depthClipEnable))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_CLIP_ENABLE_FEATURES_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
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 PhysicalDeviceDepthClipEnableFeaturesEXT
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 PhysicalDeviceDepthClipEnableFeaturesEXT where
peekCStruct :: Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
-> IO PhysicalDeviceDepthClipEnableFeaturesEXT
peekCStruct Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p = do
Bool32
depthClipEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
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 -> PhysicalDeviceDepthClipEnableFeaturesEXT
PhysicalDeviceDepthClipEnableFeaturesEXT
(Bool32 -> Bool
bool32ToBool Bool32
depthClipEnable)
instance Storable PhysicalDeviceDepthClipEnableFeaturesEXT where
sizeOf :: PhysicalDeviceDepthClipEnableFeaturesEXT -> Int
sizeOf ~PhysicalDeviceDepthClipEnableFeaturesEXT
_ = Int
24
alignment :: PhysicalDeviceDepthClipEnableFeaturesEXT -> Int
alignment ~PhysicalDeviceDepthClipEnableFeaturesEXT
_ = Int
8
peek :: Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
-> IO PhysicalDeviceDepthClipEnableFeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
-> PhysicalDeviceDepthClipEnableFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
ptr PhysicalDeviceDepthClipEnableFeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
ptr PhysicalDeviceDepthClipEnableFeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceDepthClipEnableFeaturesEXT where
zero :: PhysicalDeviceDepthClipEnableFeaturesEXT
zero = Bool -> PhysicalDeviceDepthClipEnableFeaturesEXT
PhysicalDeviceDepthClipEnableFeaturesEXT
forall a. Zero a => a
zero
data PipelineRasterizationDepthClipStateCreateInfoEXT = PipelineRasterizationDepthClipStateCreateInfoEXT
{
PipelineRasterizationDepthClipStateCreateInfoEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
flags :: PipelineRasterizationDepthClipStateCreateFlagsEXT
,
PipelineRasterizationDepthClipStateCreateInfoEXT -> Bool
depthClipEnable :: Bool
}
deriving (Typeable, PipelineRasterizationDepthClipStateCreateInfoEXT
-> PipelineRasterizationDepthClipStateCreateInfoEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PipelineRasterizationDepthClipStateCreateInfoEXT
-> PipelineRasterizationDepthClipStateCreateInfoEXT -> Bool
$c/= :: PipelineRasterizationDepthClipStateCreateInfoEXT
-> PipelineRasterizationDepthClipStateCreateInfoEXT -> Bool
== :: PipelineRasterizationDepthClipStateCreateInfoEXT
-> PipelineRasterizationDepthClipStateCreateInfoEXT -> Bool
$c== :: PipelineRasterizationDepthClipStateCreateInfoEXT
-> PipelineRasterizationDepthClipStateCreateInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineRasterizationDepthClipStateCreateInfoEXT)
#endif
deriving instance Show PipelineRasterizationDepthClipStateCreateInfoEXT
instance ToCStruct PipelineRasterizationDepthClipStateCreateInfoEXT where
withCStruct :: forall b.
PipelineRasterizationDepthClipStateCreateInfoEXT
-> (Ptr PipelineRasterizationDepthClipStateCreateInfoEXT -> IO b)
-> IO b
withCStruct PipelineRasterizationDepthClipStateCreateInfoEXT
x Ptr PipelineRasterizationDepthClipStateCreateInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p PipelineRasterizationDepthClipStateCreateInfoEXT
x (Ptr PipelineRasterizationDepthClipStateCreateInfoEXT -> IO b
f Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p)
pokeCStruct :: forall b.
Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> PipelineRasterizationDepthClipStateCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p PipelineRasterizationDepthClipStateCreateInfoEXT{Bool
PipelineRasterizationDepthClipStateCreateFlagsEXT
depthClipEnable :: Bool
flags :: PipelineRasterizationDepthClipStateCreateFlagsEXT
$sel:depthClipEnable:PipelineRasterizationDepthClipStateCreateInfoEXT :: PipelineRasterizationDepthClipStateCreateInfoEXT -> Bool
$sel:flags:PipelineRasterizationDepthClipStateCreateInfoEXT :: PipelineRasterizationDepthClipStateCreateInfoEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_RASTERIZATION_DEPTH_CLIP_STATE_CREATE_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
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 PipelineRasterizationDepthClipStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT)) (PipelineRasterizationDepthClipStateCreateFlagsEXT
flags)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
depthClipEnable))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> IO b -> IO b
pokeZeroCStruct Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_RASTERIZATION_DEPTH_CLIP_STATE_CREATE_INFO_EXT)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
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 PipelineRasterizationDepthClipStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PipelineRasterizationDepthClipStateCreateInfoEXT where
peekCStruct :: Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> IO PipelineRasterizationDepthClipStateCreateInfoEXT
peekCStruct Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p = do
PipelineRasterizationDepthClipStateCreateFlagsEXT
flags <- forall a. Storable a => Ptr a -> IO a
peek @PipelineRasterizationDepthClipStateCreateFlagsEXT ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT))
Bool32
depthClipEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Bool -> PipelineRasterizationDepthClipStateCreateInfoEXT
PipelineRasterizationDepthClipStateCreateInfoEXT
PipelineRasterizationDepthClipStateCreateFlagsEXT
flags (Bool32 -> Bool
bool32ToBool Bool32
depthClipEnable)
instance Storable PipelineRasterizationDepthClipStateCreateInfoEXT where
sizeOf :: PipelineRasterizationDepthClipStateCreateInfoEXT -> Int
sizeOf ~PipelineRasterizationDepthClipStateCreateInfoEXT
_ = Int
24
alignment :: PipelineRasterizationDepthClipStateCreateInfoEXT -> Int
alignment ~PipelineRasterizationDepthClipStateCreateInfoEXT
_ = Int
8
peek :: Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> IO PipelineRasterizationDepthClipStateCreateInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> PipelineRasterizationDepthClipStateCreateInfoEXT -> IO ()
poke Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
ptr PipelineRasterizationDepthClipStateCreateInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
ptr PipelineRasterizationDepthClipStateCreateInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PipelineRasterizationDepthClipStateCreateInfoEXT where
zero :: PipelineRasterizationDepthClipStateCreateInfoEXT
zero = PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Bool -> PipelineRasterizationDepthClipStateCreateInfoEXT
PipelineRasterizationDepthClipStateCreateInfoEXT
forall a. Zero a => a
zero
forall a. Zero a => a
zero
newtype PipelineRasterizationDepthClipStateCreateFlagsEXT = PipelineRasterizationDepthClipStateCreateFlagsEXT Flags
deriving newtype (PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
$c/= :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
== :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
$c== :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
Eq, Eq PipelineRasterizationDepthClipStateCreateFlagsEXT
PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Ordering
PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
$cmin :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
max :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
$cmax :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
>= :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
$c>= :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
> :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
$c> :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
<= :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
$c<= :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
< :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
$c< :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
compare :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Ordering
$ccompare :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Ordering
Ord, Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO PipelineRasterizationDepthClipStateCreateFlagsEXT
Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> IO PipelineRasterizationDepthClipStateCreateFlagsEXT
Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO ()
Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> IO ()
PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
forall b.
Ptr b
-> Int -> IO PipelineRasterizationDepthClipStateCreateFlagsEXT
forall b.
Ptr b
-> Int
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> IO ()
$cpoke :: Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> IO ()
peek :: Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO PipelineRasterizationDepthClipStateCreateFlagsEXT
$cpeek :: Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO PipelineRasterizationDepthClipStateCreateFlagsEXT
pokeByteOff :: forall b.
Ptr b
-> Int
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO ()
$cpokeByteOff :: forall b.
Ptr b
-> Int
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO ()
peekByteOff :: forall b.
Ptr b
-> Int -> IO PipelineRasterizationDepthClipStateCreateFlagsEXT
$cpeekByteOff :: forall b.
Ptr b
-> Int -> IO PipelineRasterizationDepthClipStateCreateFlagsEXT
pokeElemOff :: Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO ()
$cpokeElemOff :: Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO ()
peekElemOff :: Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> IO PipelineRasterizationDepthClipStateCreateFlagsEXT
$cpeekElemOff :: Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> IO PipelineRasterizationDepthClipStateCreateFlagsEXT
alignment :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
$calignment :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
sizeOf :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
$csizeOf :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
Storable, PipelineRasterizationDepthClipStateCreateFlagsEXT
forall a. a -> Zero a
zero :: PipelineRasterizationDepthClipStateCreateFlagsEXT
$czero :: PipelineRasterizationDepthClipStateCreateFlagsEXT
Zero, Eq PipelineRasterizationDepthClipStateCreateFlagsEXT
PipelineRasterizationDepthClipStateCreateFlagsEXT
Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
PipelineRasterizationDepthClipStateCreateFlagsEXT -> Maybe Int
PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int -> Bool
PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
$cpopCount :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
rotateR :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
$crotateR :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
rotateL :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
$crotateL :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
unsafeShiftR :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
$cunsafeShiftR :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
shiftR :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
$cshiftR :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
unsafeShiftL :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
$cunsafeShiftL :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
shiftL :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
$cshiftL :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
isSigned :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
$cisSigned :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
bitSize :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
$cbitSize :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
bitSizeMaybe :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Maybe Int
$cbitSizeMaybe :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Maybe Int
testBit :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int -> Bool
$ctestBit :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int -> Bool
complementBit :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
$ccomplementBit :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
clearBit :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
$cclearBit :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
setBit :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
$csetBit :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
bit :: Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
$cbit :: Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
zeroBits :: PipelineRasterizationDepthClipStateCreateFlagsEXT
$czeroBits :: PipelineRasterizationDepthClipStateCreateFlagsEXT
rotate :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
$crotate :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
shift :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
$cshift :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT
complement :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
$ccomplement :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
xor :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
$cxor :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
.|. :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
$c.|. :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
.&. :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
$c.&. :: PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
Bits, Bits PipelineRasterizationDepthClipStateCreateFlagsEXT
PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
$ccountTrailingZeros :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
countLeadingZeros :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
$ccountLeadingZeros :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
finiteBitSize :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
$cfiniteBitSize :: PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
FiniteBits)
conNamePipelineRasterizationDepthClipStateCreateFlagsEXT :: String
conNamePipelineRasterizationDepthClipStateCreateFlagsEXT :: String
conNamePipelineRasterizationDepthClipStateCreateFlagsEXT = String
"PipelineRasterizationDepthClipStateCreateFlagsEXT"
enumPrefixPipelineRasterizationDepthClipStateCreateFlagsEXT :: String
enumPrefixPipelineRasterizationDepthClipStateCreateFlagsEXT :: String
enumPrefixPipelineRasterizationDepthClipStateCreateFlagsEXT = String
""
showTablePipelineRasterizationDepthClipStateCreateFlagsEXT :: [(PipelineRasterizationDepthClipStateCreateFlagsEXT, String)]
showTablePipelineRasterizationDepthClipStateCreateFlagsEXT :: [(PipelineRasterizationDepthClipStateCreateFlagsEXT, String)]
showTablePipelineRasterizationDepthClipStateCreateFlagsEXT = []
instance Show PipelineRasterizationDepthClipStateCreateFlagsEXT where
showsPrec :: Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT -> ShowS
showsPrec =
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixPipelineRasterizationDepthClipStateCreateFlagsEXT
[(PipelineRasterizationDepthClipStateCreateFlagsEXT, String)]
showTablePipelineRasterizationDepthClipStateCreateFlagsEXT
String
conNamePipelineRasterizationDepthClipStateCreateFlagsEXT
(\(PipelineRasterizationDepthClipStateCreateFlagsEXT Flags
x) -> Flags
x)
(\Flags
x -> String -> ShowS
showString String
"0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)
instance Read PipelineRasterizationDepthClipStateCreateFlagsEXT where
readPrec :: ReadPrec PipelineRasterizationDepthClipStateCreateFlagsEXT
readPrec =
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixPipelineRasterizationDepthClipStateCreateFlagsEXT
[(PipelineRasterizationDepthClipStateCreateFlagsEXT, String)]
showTablePipelineRasterizationDepthClipStateCreateFlagsEXT
String
conNamePipelineRasterizationDepthClipStateCreateFlagsEXT
Flags -> PipelineRasterizationDepthClipStateCreateFlagsEXT
PipelineRasterizationDepthClipStateCreateFlagsEXT
type EXT_DEPTH_CLIP_ENABLE_SPEC_VERSION = 1
pattern EXT_DEPTH_CLIP_ENABLE_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_DEPTH_CLIP_ENABLE_SPEC_VERSION :: forall a. Integral a => a
$mEXT_DEPTH_CLIP_ENABLE_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_DEPTH_CLIP_ENABLE_SPEC_VERSION = 1
type EXT_DEPTH_CLIP_ENABLE_EXTENSION_NAME = "VK_EXT_depth_clip_enable"
pattern EXT_DEPTH_CLIP_ENABLE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_DEPTH_CLIP_ENABLE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_DEPTH_CLIP_ENABLE_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_DEPTH_CLIP_ENABLE_EXTENSION_NAME = "VK_EXT_depth_clip_enable"