{-# language CPP #-}
-- | = Name
--
-- VK_EXT_depth_clip_enable - device extension
--
-- == VK_EXT_depth_clip_enable
--
-- [__Name String__]
--     @VK_EXT_depth_clip_enable@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     103
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires Vulkan 1.0
--
-- [__Special Use__]
--
--     -   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#extendingvulkan-compatibility-specialuse D3D support>
--
-- [__Contact__]
--
--     -   Piers Daniell
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_depth_clip_enable] @pdaniell-nv%0A<<Here describe the issue or question you have about the VK_EXT_depth_clip_enable extension>> >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2018-12-20
--
-- [__Contributors__]
--
--     -   Daniel Rakos, AMD
--
--     -   Henri Verbeet, CodeWeavers
--
--     -   Jeff Bolz, NVIDIA
--
--     -   Philip Rebohle, DXVK
--
--     -   Tobias Hector, AMD
--
-- == Description
--
-- This extension allows the depth clipping operation, that is normally
-- implicitly controlled by
-- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo'::@depthClampEnable@,
-- to instead be controlled explicitly by
-- 'PipelineRasterizationDepthClipStateCreateInfoEXT'::@depthClipEnable@.
--
-- This is useful for translating DX content which assumes depth clamping
-- is always enabled, but depth clip can be controlled by the
-- DepthClipEnable rasterization state (D3D12_RASTERIZER_DESC).
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceDepthClipEnableFeaturesEXT'
--
-- -   Extending
--     'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo':
--
--     -   'PipelineRasterizationDepthClipStateCreateInfoEXT'
--
-- == New Bitmasks
--
-- -   'PipelineRasterizationDepthClipStateCreateFlagsEXT'
--
-- == New Enum Constants
--
-- -   'EXT_DEPTH_CLIP_ENABLE_EXTENSION_NAME'
--
-- -   'EXT_DEPTH_CLIP_ENABLE_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_CLIP_ENABLE_FEATURES_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_RASTERIZATION_DEPTH_CLIP_STATE_CREATE_INFO_EXT'
--
-- == Version History
--
-- -   Revision 1, 2018-12-20 (Piers Daniell)
--
--     -   Internal revisions
--
-- == See Also
--
-- 'PhysicalDeviceDepthClipEnableFeaturesEXT',
-- 'PipelineRasterizationDepthClipStateCreateFlagsEXT',
-- 'PipelineRasterizationDepthClipStateCreateInfoEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_depth_clip_enable Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
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 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.Bits (Bits)
import Data.Bits (FiniteBits)
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))
-- | VkPhysicalDeviceDepthClipEnableFeaturesEXT - Structure indicating
-- support for explicit enable of depth clip
--
-- = Members
--
-- This structure describes the following feature:
--
-- = Description
--
-- If the 'PhysicalDeviceDepthClipEnableFeaturesEXT' structure is included
-- in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2',
-- it is filled in to indicate whether each corresponding feature is
-- supported. 'PhysicalDeviceDepthClipEnableFeaturesEXT' /can/ also be used
-- in the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to
-- selectively enable these features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_depth_clip_enable VK_EXT_depth_clip_enable>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceDepthClipEnableFeaturesEXT = PhysicalDeviceDepthClipEnableFeaturesEXT
  { -- | #features-depthClipEnable# @depthClipEnable@ indicates that the
    -- implementation supports setting the depth clipping operation explicitly
    -- via the 'PipelineRasterizationDepthClipStateCreateInfoEXT' pipeline
    -- state. Otherwise depth clipping is only enabled when
    -- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo'::@depthClampEnable@
    -- is set to 'Vulkan.Core10.FundamentalTypes.FALSE'.
    PhysicalDeviceDepthClipEnableFeaturesEXT -> Bool
depthClipEnable :: Bool }
  deriving (Typeable, PhysicalDeviceDepthClipEnableFeaturesEXT
-> PhysicalDeviceDepthClipEnableFeaturesEXT -> Bool
(PhysicalDeviceDepthClipEnableFeaturesEXT
 -> PhysicalDeviceDepthClipEnableFeaturesEXT -> Bool)
-> (PhysicalDeviceDepthClipEnableFeaturesEXT
    -> PhysicalDeviceDepthClipEnableFeaturesEXT -> Bool)
-> Eq PhysicalDeviceDepthClipEnableFeaturesEXT
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 :: PhysicalDeviceDepthClipEnableFeaturesEXT
-> (Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceDepthClipEnableFeaturesEXT
x Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> IO b
f = Int
-> (Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p -> Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
-> PhysicalDeviceDepthClipEnableFeaturesEXT -> IO b -> IO b
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 :: Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
-> PhysicalDeviceDepthClipEnableFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p PhysicalDeviceDepthClipEnableFeaturesEXT{Bool
depthClipEnable :: Bool
$sel:depthClipEnable:PhysicalDeviceDepthClipEnableFeaturesEXT :: PhysicalDeviceDepthClipEnableFeaturesEXT -> Bool
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_CLIP_ENABLE_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> Int -> Ptr Bool32
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 :: Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_CLIP_ENABLE_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
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 <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
p Ptr PhysicalDeviceDepthClipEnableFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    PhysicalDeviceDepthClipEnableFeaturesEXT
-> IO PhysicalDeviceDepthClipEnableFeaturesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceDepthClipEnableFeaturesEXT
 -> IO PhysicalDeviceDepthClipEnableFeaturesEXT)
-> PhysicalDeviceDepthClipEnableFeaturesEXT
-> IO PhysicalDeviceDepthClipEnableFeaturesEXT
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 = Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
-> IO PhysicalDeviceDepthClipEnableFeaturesEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
-> PhysicalDeviceDepthClipEnableFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
ptr PhysicalDeviceDepthClipEnableFeaturesEXT
poked = Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
-> PhysicalDeviceDepthClipEnableFeaturesEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceDepthClipEnableFeaturesEXT
ptr PhysicalDeviceDepthClipEnableFeaturesEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

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


-- | VkPipelineRasterizationDepthClipStateCreateInfoEXT - Structure
-- specifying depth clipping state
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_depth_clip_enable VK_EXT_depth_clip_enable>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'PipelineRasterizationDepthClipStateCreateFlagsEXT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineRasterizationDepthClipStateCreateInfoEXT = PipelineRasterizationDepthClipStateCreateInfoEXT
  { -- | @flags@ is reserved for future use.
    --
    -- #VUID-VkPipelineRasterizationDepthClipStateCreateInfoEXT-flags-zerobitmask#
    -- @flags@ /must/ be @0@
    PipelineRasterizationDepthClipStateCreateInfoEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
flags :: PipelineRasterizationDepthClipStateCreateFlagsEXT
  , -- | @depthClipEnable@ controls whether depth clipping is enabled as
    -- described in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vertexpostproc-clipping Primitive Clipping>.
    PipelineRasterizationDepthClipStateCreateInfoEXT -> Bool
depthClipEnable :: Bool
  }
  deriving (Typeable, PipelineRasterizationDepthClipStateCreateInfoEXT
-> PipelineRasterizationDepthClipStateCreateInfoEXT -> Bool
(PipelineRasterizationDepthClipStateCreateInfoEXT
 -> PipelineRasterizationDepthClipStateCreateInfoEXT -> Bool)
-> (PipelineRasterizationDepthClipStateCreateInfoEXT
    -> PipelineRasterizationDepthClipStateCreateInfoEXT -> Bool)
-> Eq PipelineRasterizationDepthClipStateCreateInfoEXT
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 :: PipelineRasterizationDepthClipStateCreateInfoEXT
-> (Ptr PipelineRasterizationDepthClipStateCreateInfoEXT -> IO b)
-> IO b
withCStruct PipelineRasterizationDepthClipStateCreateInfoEXT
x Ptr PipelineRasterizationDepthClipStateCreateInfoEXT -> IO b
f = Int
-> (Ptr PipelineRasterizationDepthClipStateCreateInfoEXT -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT -> IO b)
 -> IO b)
-> (Ptr PipelineRasterizationDepthClipStateCreateInfoEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p -> Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> PipelineRasterizationDepthClipStateCreateInfoEXT -> IO b -> IO b
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 :: 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
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_RASTERIZATION_DEPTH_CLIP_STATE_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> Int -> Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT)) (PipelineRasterizationDepthClipStateCreateFlagsEXT
flags)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> Int -> Ptr Bool32
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 :: Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> IO b -> IO b
pokeZeroCStruct Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_RASTERIZATION_DEPTH_CLIP_STATE_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
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 <- Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO PipelineRasterizationDepthClipStateCreateFlagsEXT
forall a. Storable a => Ptr a -> IO a
peek @PipelineRasterizationDepthClipStateCreateFlagsEXT ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> Int -> Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT))
    Bool32
depthClipEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
p Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
    PipelineRasterizationDepthClipStateCreateInfoEXT
-> IO PipelineRasterizationDepthClipStateCreateInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineRasterizationDepthClipStateCreateInfoEXT
 -> IO PipelineRasterizationDepthClipStateCreateInfoEXT)
-> PipelineRasterizationDepthClipStateCreateInfoEXT
-> IO PipelineRasterizationDepthClipStateCreateInfoEXT
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 = Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> IO PipelineRasterizationDepthClipStateCreateInfoEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> PipelineRasterizationDepthClipStateCreateInfoEXT -> IO ()
poke Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
ptr PipelineRasterizationDepthClipStateCreateInfoEXT
poked = Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
-> PipelineRasterizationDepthClipStateCreateInfoEXT
-> IO ()
-> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineRasterizationDepthClipStateCreateInfoEXT
ptr PipelineRasterizationDepthClipStateCreateInfoEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

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


-- | VkPipelineRasterizationDepthClipStateCreateFlagsEXT - Reserved for
-- future use
--
-- = Description
--
-- 'PipelineRasterizationDepthClipStateCreateFlagsEXT' is a bitmask type
-- for setting a mask, but is currently reserved for future use.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_depth_clip_enable VK_EXT_depth_clip_enable>,
-- 'PipelineRasterizationDepthClipStateCreateInfoEXT'
newtype PipelineRasterizationDepthClipStateCreateFlagsEXT = PipelineRasterizationDepthClipStateCreateFlagsEXT Flags
  deriving newtype (PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool
(PipelineRasterizationDepthClipStateCreateFlagsEXT
 -> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool)
-> Eq PipelineRasterizationDepthClipStateCreateFlagsEXT
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
Eq PipelineRasterizationDepthClipStateCreateFlagsEXT
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Ordering)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> Ord 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
$cp1Ord :: Eq PipelineRasterizationDepthClipStateCreateFlagsEXT
Ord, Ptr b
-> Int -> IO PipelineRasterizationDepthClipStateCreateFlagsEXT
Ptr b
-> Int
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO ()
Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO PipelineRasterizationDepthClipStateCreateFlagsEXT
Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int -> IO PipelineRasterizationDepthClipStateCreateFlagsEXT
Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Int
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO ()
Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
-> PipelineRasterizationDepthClipStateCreateFlagsEXT -> IO ()
PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int
(PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int)
-> (Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> Int -> IO PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> Int
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> IO ())
-> (forall b.
    Ptr b
    -> Int -> IO PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (forall b.
    Ptr b
    -> Int
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> IO ())
-> (Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> IO PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (Ptr PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT -> IO ())
-> Storable PipelineRasterizationDepthClipStateCreateFlagsEXT
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 :: Ptr b
-> Int
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO ()
$cpokeByteOff :: forall b.
Ptr b
-> Int
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> IO ()
peekByteOff :: 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
PipelineRasterizationDepthClipStateCreateFlagsEXT
-> Zero PipelineRasterizationDepthClipStateCreateFlagsEXT
forall a. a -> Zero a
zero :: PipelineRasterizationDepthClipStateCreateFlagsEXT
$czero :: PipelineRasterizationDepthClipStateCreateFlagsEXT
Zero, Eq PipelineRasterizationDepthClipStateCreateFlagsEXT
PipelineRasterizationDepthClipStateCreateFlagsEXT
Eq PipelineRasterizationDepthClipStateCreateFlagsEXT
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> (Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> Int -> Bool)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT -> Maybe Int)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT -> Bool)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT
    -> Int -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int)
-> Bits 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
$cp1Bits :: Eq PipelineRasterizationDepthClipStateCreateFlagsEXT
Bits, Bits PipelineRasterizationDepthClipStateCreateFlagsEXT
Bits PipelineRasterizationDepthClipStateCreateFlagsEXT
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int)
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT -> Int)
-> FiniteBits 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
$cp1FiniteBits :: Bits PipelineRasterizationDepthClipStateCreateFlagsEXT
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 = String
-> [(PipelineRasterizationDepthClipStateCreateFlagsEXT, String)]
-> String
-> (PipelineRasterizationDepthClipStateCreateFlagsEXT -> Flags)
-> (Flags -> ShowS)
-> Int
-> PipelineRasterizationDepthClipStateCreateFlagsEXT
-> ShowS
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" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)

instance Read PipelineRasterizationDepthClipStateCreateFlagsEXT where
  readPrec :: ReadPrec PipelineRasterizationDepthClipStateCreateFlagsEXT
readPrec = String
-> [(PipelineRasterizationDepthClipStateCreateFlagsEXT, String)]
-> String
-> (Flags -> PipelineRasterizationDepthClipStateCreateFlagsEXT)
-> ReadPrec PipelineRasterizationDepthClipStateCreateFlagsEXT
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

-- No documentation found for TopLevel "VK_EXT_DEPTH_CLIP_ENABLE_SPEC_VERSION"
pattern EXT_DEPTH_CLIP_ENABLE_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_DEPTH_CLIP_ENABLE_SPEC_VERSION :: a
$mEXT_DEPTH_CLIP_ENABLE_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_DEPTH_CLIP_ENABLE_SPEC_VERSION = 1


type EXT_DEPTH_CLIP_ENABLE_EXTENSION_NAME = "VK_EXT_depth_clip_enable"

-- No documentation found for TopLevel "VK_EXT_DEPTH_CLIP_ENABLE_EXTENSION_NAME"
pattern EXT_DEPTH_CLIP_ENABLE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_DEPTH_CLIP_ENABLE_EXTENSION_NAME :: a
$mEXT_DEPTH_CLIP_ENABLE_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_DEPTH_CLIP_ENABLE_EXTENSION_NAME = "VK_EXT_depth_clip_enable"