{-# language CPP #-}
-- | = Name
--
-- VK_EXT_line_rasterization - device extension
--
-- == VK_EXT_line_rasterization
--
-- [__Name String__]
--     @VK_EXT_line_rasterization@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     260
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires Vulkan 1.0
--
--     -   Requires @VK_KHR_get_physical_device_properties2@
--
-- [__Special Use__]
--
--     -   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#extendingvulkan-compatibility-specialuse CAD support>
--
-- [__Contact__]
--
--     -   Jeff Bolz
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_line_rasterization] @jeffbolznv%0A<<Here describe the issue or question you have about the VK_EXT_line_rasterization extension>> >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2019-05-09
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Jeff Bolz, NVIDIA
--
--     -   Allen Jensen, NVIDIA
--
--     -   Jason Ekstrand, Intel
--
-- == Description
--
-- This extension adds some line rasterization features that are commonly
-- used in CAD applications and supported in other APIs like OpenGL.
-- Bresenham-style line rasterization is supported, smooth rectangular
-- lines (coverage to alpha) are supported, and stippled lines are
-- supported for all three line rasterization modes.
--
-- == New Commands
--
-- -   'cmdSetLineStippleEXT'
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceLineRasterizationFeaturesEXT'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceLineRasterizationPropertiesEXT'
--
-- -   Extending
--     'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo':
--
--     -   'PipelineRasterizationLineStateCreateInfoEXT'
--
-- == New Enums
--
-- -   'LineRasterizationModeEXT'
--
-- == New Enum Constants
--
-- -   'EXT_LINE_RASTERIZATION_EXTENSION_NAME'
--
-- -   'EXT_LINE_RASTERIZATION_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.DynamicState.DynamicState':
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_LINE_RASTERIZATION_FEATURES_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_LINE_RASTERIZATION_PROPERTIES_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_RASTERIZATION_LINE_STATE_CREATE_INFO_EXT'
--
-- == Issues
--
-- > (1) Do we need to support Bresenham-style and smooth lines with more than
-- > one rasterization sample? i.e. the equivalent of glDisable(GL_MULTISAMPLE)
-- > in OpenGL when the framebuffer has more than one sample?
--
-- > RESOLVED: Yes.
-- > For simplicity, Bresenham line rasterization carries forward a few
-- > restrictions from OpenGL, such as not supporting per-sample shading, alpha
-- > to coverage, or alpha to one.
--
-- == Version History
--
-- -   Revision 1, 2019-05-09 (Jeff Bolz)
--
--     -   Initial draft
--
-- == See Also
--
-- 'LineRasterizationModeEXT',
-- 'PhysicalDeviceLineRasterizationFeaturesEXT',
-- 'PhysicalDeviceLineRasterizationPropertiesEXT',
-- 'PipelineRasterizationLineStateCreateInfoEXT', 'cmdSetLineStippleEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_line_rasterization 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_line_rasterization  ( cmdSetLineStippleEXT
                                                    , PhysicalDeviceLineRasterizationFeaturesEXT(..)
                                                    , PhysicalDeviceLineRasterizationPropertiesEXT(..)
                                                    , PipelineRasterizationLineStateCreateInfoEXT(..)
                                                    , LineRasterizationModeEXT( LINE_RASTERIZATION_MODE_DEFAULT_EXT
                                                                              , LINE_RASTERIZATION_MODE_RECTANGULAR_EXT
                                                                              , LINE_RASTERIZATION_MODE_BRESENHAM_EXT
                                                                              , LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT
                                                                              , ..
                                                                              )
                                                    , EXT_LINE_RASTERIZATION_SPEC_VERSION
                                                    , pattern EXT_LINE_RASTERIZATION_SPEC_VERSION
                                                    , EXT_LINE_RASTERIZATION_EXTENSION_NAME
                                                    , pattern EXT_LINE_RASTERIZATION_EXTENSION_NAME
                                                    ) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showsPrec)
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 Control.Monad.IO.Class (MonadIO)
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 GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Data.Int (Int32)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Word (Word16)
import Data.Word (Word32)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer(CommandBuffer))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetLineStippleEXT))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_LINE_RASTERIZATION_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_LINE_RASTERIZATION_PROPERTIES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_RASTERIZATION_LINE_STATE_CREATE_INFO_EXT))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdSetLineStippleEXT
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word16 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word16 -> IO ()

-- | vkCmdSetLineStippleEXT - Set line stipple dynamically for a command
-- buffer
--
-- = Description
--
-- This command sets the line stipple state for subsequent drawing commands
-- when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_EXT' set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'PipelineRasterizationLineStateCreateInfoEXT'::@lineStippleFactor@ and
-- 'PipelineRasterizationLineStateCreateInfoEXT'::@lineStipplePattern@
-- values used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetLineStippleEXT-lineStippleFactor-02776#
--     @lineStippleFactor@ /must/ be in the range [1,256]
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetLineStippleEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetLineStippleEXT-commandBuffer-recording#
--     @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   #VUID-vkCmdSetLineStippleEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Graphics                                                                                                              |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_line_rasterization VK_EXT_line_rasterization>,
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetLineStippleEXT :: forall io
                      . (MonadIO io)
                     => -- | @commandBuffer@ is the command buffer into which the command will be
                        -- recorded.
                        CommandBuffer
                     -> -- | @lineStippleFactor@ is the repeat factor used in stippled line
                        -- rasterization.
                        ("lineStippleFactor" ::: Word32)
                     -> -- | @lineStipplePattern@ is the bit pattern used in stippled line
                        -- rasterization.
                        ("lineStipplePattern" ::: Word16)
                     -> io ()
cmdSetLineStippleEXT :: CommandBuffer
-> ("lineStippleFactor" ::: Word32)
-> ("lineStipplePattern" ::: Word16)
-> io ()
cmdSetLineStippleEXT CommandBuffer
commandBuffer "lineStippleFactor" ::: Word32
lineStippleFactor "lineStipplePattern" ::: Word16
lineStipplePattern = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetLineStippleEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("lineStippleFactor" ::: Word32)
   -> ("lineStipplePattern" ::: Word16)
   -> IO ())
vkCmdSetLineStippleEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("lineStippleFactor" ::: Word32)
      -> ("lineStipplePattern" ::: Word16)
      -> IO ())
pVkCmdSetLineStippleEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("lineStippleFactor" ::: Word32)
   -> ("lineStipplePattern" ::: Word16)
   -> IO ())
vkCmdSetLineStippleEXTPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("lineStippleFactor" ::: Word32)
   -> ("lineStipplePattern" ::: Word16)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("lineStippleFactor" ::: Word32)
      -> ("lineStipplePattern" ::: Word16)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("lineStippleFactor" ::: Word32)
   -> ("lineStipplePattern" ::: Word16)
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkCmdSetLineStippleEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetLineStippleEXT' :: Ptr CommandBuffer_T
-> ("lineStippleFactor" ::: Word32)
-> ("lineStipplePattern" ::: Word16)
-> IO ()
vkCmdSetLineStippleEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> ("lineStippleFactor" ::: Word32)
   -> ("lineStipplePattern" ::: Word16)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("lineStippleFactor" ::: Word32)
-> ("lineStipplePattern" ::: Word16)
-> IO ()
mkVkCmdSetLineStippleEXT FunPtr
  (Ptr CommandBuffer_T
   -> ("lineStippleFactor" ::: Word32)
   -> ("lineStipplePattern" ::: Word16)
   -> IO ())
vkCmdSetLineStippleEXTPtr
  String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetLineStippleEXT" (Ptr CommandBuffer_T
-> ("lineStippleFactor" ::: Word32)
-> ("lineStipplePattern" ::: Word16)
-> IO ()
vkCmdSetLineStippleEXT' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ("lineStippleFactor" ::: Word32
lineStippleFactor) ("lineStipplePattern" ::: Word16
lineStipplePattern))
  () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- | VkPhysicalDeviceLineRasterizationFeaturesEXT - Structure describing the
-- line rasterization features that can be supported by an implementation
--
-- = Members
--
-- This structure describes the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceLineRasterizationFeaturesEXT' 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. 'PhysicalDeviceLineRasterizationFeaturesEXT' /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_line_rasterization VK_EXT_line_rasterization>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceLineRasterizationFeaturesEXT = PhysicalDeviceLineRasterizationFeaturesEXT
  { -- | #features-rectangularLines# @rectangularLines@ indicates whether the
    -- implementation supports
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-lines rectangular line rasterization>.
    PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
rectangularLines :: Bool
  , -- | #features-bresenhamLines# @bresenhamLines@ indicates whether the
    -- implementation supports
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-lines-bresenham Bresenham-style line rasterization>.
    PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
bresenhamLines :: Bool
  , -- | #features-smoothLines# @smoothLines@ indicates whether the
    -- implementation supports
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-lines-smooth smooth line rasterization>.
    PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
smoothLines :: Bool
  , -- | #features-stippledRectangularLines# @stippledRectangularLines@ indicates
    -- whether the implementation supports
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-lines-stipple stippled line rasterization>
    -- with 'LINE_RASTERIZATION_MODE_RECTANGULAR_EXT' lines, or with
    -- 'LINE_RASTERIZATION_MODE_DEFAULT_EXT' lines if
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@strictLines@
    -- is 'Vulkan.Core10.FundamentalTypes.TRUE'.
    PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
stippledRectangularLines :: Bool
  , -- | #features-stippledBresenhamLines# @stippledBresenhamLines@ indicates
    -- whether the implementation supports
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-lines-stipple stippled line rasterization>
    -- with 'LINE_RASTERIZATION_MODE_BRESENHAM_EXT' lines.
    PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
stippledBresenhamLines :: Bool
  , -- | #features-stippledSmoothLines# @stippledSmoothLines@ indicates whether
    -- the implementation supports
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-lines-stipple stippled line rasterization>
    -- with 'LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT' lines.
    PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
stippledSmoothLines :: Bool
  }
  deriving (Typeable, PhysicalDeviceLineRasterizationFeaturesEXT
-> PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
(PhysicalDeviceLineRasterizationFeaturesEXT
 -> PhysicalDeviceLineRasterizationFeaturesEXT -> Bool)
-> (PhysicalDeviceLineRasterizationFeaturesEXT
    -> PhysicalDeviceLineRasterizationFeaturesEXT -> Bool)
-> Eq PhysicalDeviceLineRasterizationFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceLineRasterizationFeaturesEXT
-> PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
$c/= :: PhysicalDeviceLineRasterizationFeaturesEXT
-> PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
== :: PhysicalDeviceLineRasterizationFeaturesEXT
-> PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
$c== :: PhysicalDeviceLineRasterizationFeaturesEXT
-> PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceLineRasterizationFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceLineRasterizationFeaturesEXT

instance ToCStruct PhysicalDeviceLineRasterizationFeaturesEXT where
  withCStruct :: PhysicalDeviceLineRasterizationFeaturesEXT
-> (Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceLineRasterizationFeaturesEXT
x Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> IO b
f = Int
-> (Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p -> Ptr PhysicalDeviceLineRasterizationFeaturesEXT
-> PhysicalDeviceLineRasterizationFeaturesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p PhysicalDeviceLineRasterizationFeaturesEXT
x (Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> IO b
f Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceLineRasterizationFeaturesEXT
-> PhysicalDeviceLineRasterizationFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p PhysicalDeviceLineRasterizationFeaturesEXT{Bool
stippledSmoothLines :: Bool
stippledBresenhamLines :: Bool
stippledRectangularLines :: Bool
smoothLines :: Bool
bresenhamLines :: Bool
rectangularLines :: Bool
$sel:stippledSmoothLines:PhysicalDeviceLineRasterizationFeaturesEXT :: PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
$sel:stippledBresenhamLines:PhysicalDeviceLineRasterizationFeaturesEXT :: PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
$sel:stippledRectangularLines:PhysicalDeviceLineRasterizationFeaturesEXT :: PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
$sel:smoothLines:PhysicalDeviceLineRasterizationFeaturesEXT :: PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
$sel:bresenhamLines:PhysicalDeviceLineRasterizationFeaturesEXT :: PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
$sel:rectangularLines:PhysicalDeviceLineRasterizationFeaturesEXT :: PhysicalDeviceLineRasterizationFeaturesEXT -> Bool
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_LINE_RASTERIZATION_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT
-> 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 PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
rectangularLines))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
bresenhamLines))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
smoothLines))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
stippledRectangularLines))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
stippledBresenhamLines))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
stippledSmoothLines))
    IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_LINE_RASTERIZATION_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT
-> 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 PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> 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))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> 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))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceLineRasterizationFeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceLineRasterizationFeaturesEXT
-> IO PhysicalDeviceLineRasterizationFeaturesEXT
peekCStruct Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p = do
    Bool32
rectangularLines <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    Bool32
bresenhamLines <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
    Bool32
smoothLines <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
    Bool32
stippledRectangularLines <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32))
    Bool32
stippledBresenhamLines <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32))
    Bool32
stippledSmoothLines <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32))
    PhysicalDeviceLineRasterizationFeaturesEXT
-> IO PhysicalDeviceLineRasterizationFeaturesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceLineRasterizationFeaturesEXT
 -> IO PhysicalDeviceLineRasterizationFeaturesEXT)
-> PhysicalDeviceLineRasterizationFeaturesEXT
-> IO PhysicalDeviceLineRasterizationFeaturesEXT
forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceLineRasterizationFeaturesEXT
PhysicalDeviceLineRasterizationFeaturesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
rectangularLines) (Bool32 -> Bool
bool32ToBool Bool32
bresenhamLines) (Bool32 -> Bool
bool32ToBool Bool32
smoothLines) (Bool32 -> Bool
bool32ToBool Bool32
stippledRectangularLines) (Bool32 -> Bool
bool32ToBool Bool32
stippledBresenhamLines) (Bool32 -> Bool
bool32ToBool Bool32
stippledSmoothLines)

instance Storable PhysicalDeviceLineRasterizationFeaturesEXT where
  sizeOf :: PhysicalDeviceLineRasterizationFeaturesEXT -> Int
sizeOf ~PhysicalDeviceLineRasterizationFeaturesEXT
_ = Int
40
  alignment :: PhysicalDeviceLineRasterizationFeaturesEXT -> Int
alignment ~PhysicalDeviceLineRasterizationFeaturesEXT
_ = Int
8
  peek :: Ptr PhysicalDeviceLineRasterizationFeaturesEXT
-> IO PhysicalDeviceLineRasterizationFeaturesEXT
peek = Ptr PhysicalDeviceLineRasterizationFeaturesEXT
-> IO PhysicalDeviceLineRasterizationFeaturesEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceLineRasterizationFeaturesEXT
-> PhysicalDeviceLineRasterizationFeaturesEXT -> IO ()
poke Ptr PhysicalDeviceLineRasterizationFeaturesEXT
ptr PhysicalDeviceLineRasterizationFeaturesEXT
poked = Ptr PhysicalDeviceLineRasterizationFeaturesEXT
-> PhysicalDeviceLineRasterizationFeaturesEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceLineRasterizationFeaturesEXT
ptr PhysicalDeviceLineRasterizationFeaturesEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

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


-- | VkPhysicalDeviceLineRasterizationPropertiesEXT - Structure describing
-- line rasterization properties supported by an implementation
--
-- = Description
--
-- If the 'PhysicalDeviceLineRasterizationPropertiesEXT' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2',
-- it is filled in with each corresponding implementation-dependent
-- property.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_line_rasterization VK_EXT_line_rasterization>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceLineRasterizationPropertiesEXT = PhysicalDeviceLineRasterizationPropertiesEXT
  { -- | #limits-lineSubPixelPrecisionBits# @lineSubPixelPrecisionBits@ is the
    -- number of bits of subpixel precision in framebuffer coordinates xf and
    -- yf when rasterizing
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-lines line segments>.
    PhysicalDeviceLineRasterizationPropertiesEXT
-> "lineStippleFactor" ::: Word32
lineSubPixelPrecisionBits :: Word32 }
  deriving (Typeable, PhysicalDeviceLineRasterizationPropertiesEXT
-> PhysicalDeviceLineRasterizationPropertiesEXT -> Bool
(PhysicalDeviceLineRasterizationPropertiesEXT
 -> PhysicalDeviceLineRasterizationPropertiesEXT -> Bool)
-> (PhysicalDeviceLineRasterizationPropertiesEXT
    -> PhysicalDeviceLineRasterizationPropertiesEXT -> Bool)
-> Eq PhysicalDeviceLineRasterizationPropertiesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceLineRasterizationPropertiesEXT
-> PhysicalDeviceLineRasterizationPropertiesEXT -> Bool
$c/= :: PhysicalDeviceLineRasterizationPropertiesEXT
-> PhysicalDeviceLineRasterizationPropertiesEXT -> Bool
== :: PhysicalDeviceLineRasterizationPropertiesEXT
-> PhysicalDeviceLineRasterizationPropertiesEXT -> Bool
$c== :: PhysicalDeviceLineRasterizationPropertiesEXT
-> PhysicalDeviceLineRasterizationPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceLineRasterizationPropertiesEXT)
#endif
deriving instance Show PhysicalDeviceLineRasterizationPropertiesEXT

instance ToCStruct PhysicalDeviceLineRasterizationPropertiesEXT where
  withCStruct :: PhysicalDeviceLineRasterizationPropertiesEXT
-> (Ptr PhysicalDeviceLineRasterizationPropertiesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceLineRasterizationPropertiesEXT
x Ptr PhysicalDeviceLineRasterizationPropertiesEXT -> IO b
f = Int
-> (Ptr PhysicalDeviceLineRasterizationPropertiesEXT -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceLineRasterizationPropertiesEXT -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceLineRasterizationPropertiesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p -> Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> PhysicalDeviceLineRasterizationPropertiesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p PhysicalDeviceLineRasterizationPropertiesEXT
x (Ptr PhysicalDeviceLineRasterizationPropertiesEXT -> IO b
f Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> PhysicalDeviceLineRasterizationPropertiesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p PhysicalDeviceLineRasterizationPropertiesEXT{"lineStippleFactor" ::: Word32
lineSubPixelPrecisionBits :: "lineStippleFactor" ::: Word32
$sel:lineSubPixelPrecisionBits:PhysicalDeviceLineRasterizationPropertiesEXT :: PhysicalDeviceLineRasterizationPropertiesEXT
-> "lineStippleFactor" ::: Word32
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_LINE_RASTERIZATION_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("lineStippleFactor" ::: Word32)
-> ("lineStippleFactor" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> Int -> Ptr ("lineStippleFactor" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ("lineStippleFactor" ::: Word32
lineSubPixelPrecisionBits)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr PhysicalDeviceLineRasterizationPropertiesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_LINE_RASTERIZATION_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("lineStippleFactor" ::: Word32)
-> ("lineStippleFactor" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> Int -> Ptr ("lineStippleFactor" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ("lineStippleFactor" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceLineRasterizationPropertiesEXT where
  peekCStruct :: Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> IO PhysicalDeviceLineRasterizationPropertiesEXT
peekCStruct Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p = do
    "lineStippleFactor" ::: Word32
lineSubPixelPrecisionBits <- Ptr ("lineStippleFactor" ::: Word32)
-> IO ("lineStippleFactor" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> Int -> Ptr ("lineStippleFactor" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    PhysicalDeviceLineRasterizationPropertiesEXT
-> IO PhysicalDeviceLineRasterizationPropertiesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceLineRasterizationPropertiesEXT
 -> IO PhysicalDeviceLineRasterizationPropertiesEXT)
-> PhysicalDeviceLineRasterizationPropertiesEXT
-> IO PhysicalDeviceLineRasterizationPropertiesEXT
forall a b. (a -> b) -> a -> b
$ ("lineStippleFactor" ::: Word32)
-> PhysicalDeviceLineRasterizationPropertiesEXT
PhysicalDeviceLineRasterizationPropertiesEXT
             "lineStippleFactor" ::: Word32
lineSubPixelPrecisionBits

instance Storable PhysicalDeviceLineRasterizationPropertiesEXT where
  sizeOf :: PhysicalDeviceLineRasterizationPropertiesEXT -> Int
sizeOf ~PhysicalDeviceLineRasterizationPropertiesEXT
_ = Int
24
  alignment :: PhysicalDeviceLineRasterizationPropertiesEXT -> Int
alignment ~PhysicalDeviceLineRasterizationPropertiesEXT
_ = Int
8
  peek :: Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> IO PhysicalDeviceLineRasterizationPropertiesEXT
peek = Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> IO PhysicalDeviceLineRasterizationPropertiesEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> PhysicalDeviceLineRasterizationPropertiesEXT -> IO ()
poke Ptr PhysicalDeviceLineRasterizationPropertiesEXT
ptr PhysicalDeviceLineRasterizationPropertiesEXT
poked = Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> PhysicalDeviceLineRasterizationPropertiesEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceLineRasterizationPropertiesEXT
ptr PhysicalDeviceLineRasterizationPropertiesEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceLineRasterizationPropertiesEXT where
  zero :: PhysicalDeviceLineRasterizationPropertiesEXT
zero = ("lineStippleFactor" ::: Word32)
-> PhysicalDeviceLineRasterizationPropertiesEXT
PhysicalDeviceLineRasterizationPropertiesEXT
           "lineStippleFactor" ::: Word32
forall a. Zero a => a
zero


-- | VkPipelineRasterizationLineStateCreateInfoEXT - Structure specifying
-- parameters of a newly created pipeline line rasterization state
--
-- = Description
--
-- If @stippledLineEnable@ is 'Vulkan.Core10.FundamentalTypes.FALSE', the
-- values of @lineStippleFactor@ and @lineStipplePattern@ are ignored.
--
-- == Valid Usage
--
-- -   #VUID-VkPipelineRasterizationLineStateCreateInfoEXT-lineRasterizationMode-02768#
--     If @lineRasterizationMode@ is
--     'LINE_RASTERIZATION_MODE_RECTANGULAR_EXT', then the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rectangularLines rectangularLines>
--     feature /must/ be enabled
--
-- -   #VUID-VkPipelineRasterizationLineStateCreateInfoEXT-lineRasterizationMode-02769#
--     If @lineRasterizationMode@ is
--     'LINE_RASTERIZATION_MODE_BRESENHAM_EXT', then the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-bresenhamLines bresenhamLines>
--     feature /must/ be enabled
--
-- -   #VUID-VkPipelineRasterizationLineStateCreateInfoEXT-lineRasterizationMode-02770#
--     If @lineRasterizationMode@ is
--     'LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT', then the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-bresenhamLines smoothLines>
--     feature /must/ be enabled
--
-- -   #VUID-VkPipelineRasterizationLineStateCreateInfoEXT-stippledLineEnable-02771#
--     If @stippledLineEnable@ is 'Vulkan.Core10.FundamentalTypes.TRUE' and
--     @lineRasterizationMode@ is
--     'LINE_RASTERIZATION_MODE_RECTANGULAR_EXT', then the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledRectangularLines stippledRectangularLines>
--     feature /must/ be enabled
--
-- -   #VUID-VkPipelineRasterizationLineStateCreateInfoEXT-stippledLineEnable-02772#
--     If @stippledLineEnable@ is 'Vulkan.Core10.FundamentalTypes.TRUE' and
--     @lineRasterizationMode@ is 'LINE_RASTERIZATION_MODE_BRESENHAM_EXT',
--     then the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledBresenhamLines stippledBresenhamLines>
--     feature /must/ be enabled
--
-- -   #VUID-VkPipelineRasterizationLineStateCreateInfoEXT-stippledLineEnable-02773#
--     If @stippledLineEnable@ is 'Vulkan.Core10.FundamentalTypes.TRUE' and
--     @lineRasterizationMode@ is
--     'LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT', then the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledSmoothLines stippledSmoothLines>
--     feature /must/ be enabled
--
-- -   #VUID-VkPipelineRasterizationLineStateCreateInfoEXT-stippledLineEnable-02774#
--     If @stippledLineEnable@ is 'Vulkan.Core10.FundamentalTypes.TRUE' and
--     @lineRasterizationMode@ is 'LINE_RASTERIZATION_MODE_DEFAULT_EXT',
--     then the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-stippledRectangularLines stippledRectangularLines>
--     feature /must/ be enabled and
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@strictLines@
--     /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkPipelineRasterizationLineStateCreateInfoEXT-sType-sType#
--     @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_RASTERIZATION_LINE_STATE_CREATE_INFO_EXT'
--
-- -   #VUID-VkPipelineRasterizationLineStateCreateInfoEXT-lineRasterizationMode-parameter#
--     @lineRasterizationMode@ /must/ be a valid 'LineRasterizationModeEXT'
--     value
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_line_rasterization VK_EXT_line_rasterization>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32', 'LineRasterizationModeEXT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineRasterizationLineStateCreateInfoEXT = PipelineRasterizationLineStateCreateInfoEXT
  { -- | @lineRasterizationMode@ is a 'LineRasterizationModeEXT' value selecting
    -- the style of line rasterization.
    PipelineRasterizationLineStateCreateInfoEXT
-> LineRasterizationModeEXT
lineRasterizationMode :: LineRasterizationModeEXT
  , -- | @stippledLineEnable@ enables
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-lines-stipple stippled line rasterization>.
    PipelineRasterizationLineStateCreateInfoEXT -> Bool
stippledLineEnable :: Bool
  , -- | @lineStippleFactor@ is the repeat factor used in stippled line
    -- rasterization.
    PipelineRasterizationLineStateCreateInfoEXT
-> "lineStippleFactor" ::: Word32
lineStippleFactor :: Word32
  , -- | @lineStipplePattern@ is the bit pattern used in stippled line
    -- rasterization.
    PipelineRasterizationLineStateCreateInfoEXT
-> "lineStipplePattern" ::: Word16
lineStipplePattern :: Word16
  }
  deriving (Typeable, PipelineRasterizationLineStateCreateInfoEXT
-> PipelineRasterizationLineStateCreateInfoEXT -> Bool
(PipelineRasterizationLineStateCreateInfoEXT
 -> PipelineRasterizationLineStateCreateInfoEXT -> Bool)
-> (PipelineRasterizationLineStateCreateInfoEXT
    -> PipelineRasterizationLineStateCreateInfoEXT -> Bool)
-> Eq PipelineRasterizationLineStateCreateInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PipelineRasterizationLineStateCreateInfoEXT
-> PipelineRasterizationLineStateCreateInfoEXT -> Bool
$c/= :: PipelineRasterizationLineStateCreateInfoEXT
-> PipelineRasterizationLineStateCreateInfoEXT -> Bool
== :: PipelineRasterizationLineStateCreateInfoEXT
-> PipelineRasterizationLineStateCreateInfoEXT -> Bool
$c== :: PipelineRasterizationLineStateCreateInfoEXT
-> PipelineRasterizationLineStateCreateInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineRasterizationLineStateCreateInfoEXT)
#endif
deriving instance Show PipelineRasterizationLineStateCreateInfoEXT

instance ToCStruct PipelineRasterizationLineStateCreateInfoEXT where
  withCStruct :: PipelineRasterizationLineStateCreateInfoEXT
-> (Ptr PipelineRasterizationLineStateCreateInfoEXT -> IO b)
-> IO b
withCStruct PipelineRasterizationLineStateCreateInfoEXT
x Ptr PipelineRasterizationLineStateCreateInfoEXT -> IO b
f = Int
-> (Ptr PipelineRasterizationLineStateCreateInfoEXT -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr PipelineRasterizationLineStateCreateInfoEXT -> IO b) -> IO b)
-> (Ptr PipelineRasterizationLineStateCreateInfoEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PipelineRasterizationLineStateCreateInfoEXT
p -> Ptr PipelineRasterizationLineStateCreateInfoEXT
-> PipelineRasterizationLineStateCreateInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineRasterizationLineStateCreateInfoEXT
p PipelineRasterizationLineStateCreateInfoEXT
x (Ptr PipelineRasterizationLineStateCreateInfoEXT -> IO b
f Ptr PipelineRasterizationLineStateCreateInfoEXT
p)
  pokeCStruct :: Ptr PipelineRasterizationLineStateCreateInfoEXT
-> PipelineRasterizationLineStateCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr PipelineRasterizationLineStateCreateInfoEXT
p PipelineRasterizationLineStateCreateInfoEXT{Bool
"lineStipplePattern" ::: Word16
"lineStippleFactor" ::: Word32
LineRasterizationModeEXT
lineStipplePattern :: "lineStipplePattern" ::: Word16
lineStippleFactor :: "lineStippleFactor" ::: Word32
stippledLineEnable :: Bool
lineRasterizationMode :: LineRasterizationModeEXT
$sel:lineStipplePattern:PipelineRasterizationLineStateCreateInfoEXT :: PipelineRasterizationLineStateCreateInfoEXT
-> "lineStipplePattern" ::: Word16
$sel:lineStippleFactor:PipelineRasterizationLineStateCreateInfoEXT :: PipelineRasterizationLineStateCreateInfoEXT
-> "lineStippleFactor" ::: Word32
$sel:stippledLineEnable:PipelineRasterizationLineStateCreateInfoEXT :: PipelineRasterizationLineStateCreateInfoEXT -> Bool
$sel:lineRasterizationMode:PipelineRasterizationLineStateCreateInfoEXT :: PipelineRasterizationLineStateCreateInfoEXT
-> LineRasterizationModeEXT
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_RASTERIZATION_LINE_STATE_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr LineRasterizationModeEXT -> LineRasterizationModeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr LineRasterizationModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr LineRasterizationModeEXT)) (LineRasterizationModeEXT
lineRasterizationMode)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
stippledLineEnable))
    Ptr ("lineStippleFactor" ::: Word32)
-> ("lineStippleFactor" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr ("lineStippleFactor" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) ("lineStippleFactor" ::: Word32
lineStippleFactor)
    Ptr ("lineStipplePattern" ::: Word16)
-> ("lineStipplePattern" ::: Word16) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr ("lineStipplePattern" ::: Word16)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word16)) ("lineStipplePattern" ::: Word16
lineStipplePattern)
    IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr PipelineRasterizationLineStateCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr PipelineRasterizationLineStateCreateInfoEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_RASTERIZATION_LINE_STATE_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr LineRasterizationModeEXT -> LineRasterizationModeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr LineRasterizationModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr LineRasterizationModeEXT)) (LineRasterizationModeEXT
forall a. Zero a => a
zero)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> 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))
    Ptr ("lineStippleFactor" ::: Word32)
-> ("lineStippleFactor" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr ("lineStippleFactor" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) ("lineStippleFactor" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("lineStipplePattern" ::: Word16)
-> ("lineStipplePattern" ::: Word16) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr ("lineStipplePattern" ::: Word16)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word16)) ("lineStipplePattern" ::: Word16
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PipelineRasterizationLineStateCreateInfoEXT where
  peekCStruct :: Ptr PipelineRasterizationLineStateCreateInfoEXT
-> IO PipelineRasterizationLineStateCreateInfoEXT
peekCStruct Ptr PipelineRasterizationLineStateCreateInfoEXT
p = do
    LineRasterizationModeEXT
lineRasterizationMode <- Ptr LineRasterizationModeEXT -> IO LineRasterizationModeEXT
forall a. Storable a => Ptr a -> IO a
peek @LineRasterizationModeEXT ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr LineRasterizationModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr LineRasterizationModeEXT))
    Bool32
stippledLineEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
    "lineStippleFactor" ::: Word32
lineStippleFactor <- Ptr ("lineStippleFactor" ::: Word32)
-> IO ("lineStippleFactor" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr ("lineStippleFactor" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32))
    "lineStipplePattern" ::: Word16
lineStipplePattern <- Ptr ("lineStipplePattern" ::: Word16)
-> IO ("lineStipplePattern" ::: Word16)
forall a. Storable a => Ptr a -> IO a
peek @Word16 ((Ptr PipelineRasterizationLineStateCreateInfoEXT
p Ptr PipelineRasterizationLineStateCreateInfoEXT
-> Int -> Ptr ("lineStipplePattern" ::: Word16)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Word16))
    PipelineRasterizationLineStateCreateInfoEXT
-> IO PipelineRasterizationLineStateCreateInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineRasterizationLineStateCreateInfoEXT
 -> IO PipelineRasterizationLineStateCreateInfoEXT)
-> PipelineRasterizationLineStateCreateInfoEXT
-> IO PipelineRasterizationLineStateCreateInfoEXT
forall a b. (a -> b) -> a -> b
$ LineRasterizationModeEXT
-> Bool
-> ("lineStippleFactor" ::: Word32)
-> ("lineStipplePattern" ::: Word16)
-> PipelineRasterizationLineStateCreateInfoEXT
PipelineRasterizationLineStateCreateInfoEXT
             LineRasterizationModeEXT
lineRasterizationMode (Bool32 -> Bool
bool32ToBool Bool32
stippledLineEnable) "lineStippleFactor" ::: Word32
lineStippleFactor "lineStipplePattern" ::: Word16
lineStipplePattern

instance Storable PipelineRasterizationLineStateCreateInfoEXT where
  sizeOf :: PipelineRasterizationLineStateCreateInfoEXT -> Int
sizeOf ~PipelineRasterizationLineStateCreateInfoEXT
_ = Int
32
  alignment :: PipelineRasterizationLineStateCreateInfoEXT -> Int
alignment ~PipelineRasterizationLineStateCreateInfoEXT
_ = Int
8
  peek :: Ptr PipelineRasterizationLineStateCreateInfoEXT
-> IO PipelineRasterizationLineStateCreateInfoEXT
peek = Ptr PipelineRasterizationLineStateCreateInfoEXT
-> IO PipelineRasterizationLineStateCreateInfoEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PipelineRasterizationLineStateCreateInfoEXT
-> PipelineRasterizationLineStateCreateInfoEXT -> IO ()
poke Ptr PipelineRasterizationLineStateCreateInfoEXT
ptr PipelineRasterizationLineStateCreateInfoEXT
poked = Ptr PipelineRasterizationLineStateCreateInfoEXT
-> PipelineRasterizationLineStateCreateInfoEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineRasterizationLineStateCreateInfoEXT
ptr PipelineRasterizationLineStateCreateInfoEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PipelineRasterizationLineStateCreateInfoEXT where
  zero :: PipelineRasterizationLineStateCreateInfoEXT
zero = LineRasterizationModeEXT
-> Bool
-> ("lineStippleFactor" ::: Word32)
-> ("lineStipplePattern" ::: Word16)
-> PipelineRasterizationLineStateCreateInfoEXT
PipelineRasterizationLineStateCreateInfoEXT
           LineRasterizationModeEXT
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           "lineStippleFactor" ::: Word32
forall a. Zero a => a
zero
           "lineStipplePattern" ::: Word16
forall a. Zero a => a
zero


-- | VkLineRasterizationModeEXT - Line rasterization modes
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_line_rasterization VK_EXT_line_rasterization>,
-- 'PipelineRasterizationLineStateCreateInfoEXT'
newtype LineRasterizationModeEXT = LineRasterizationModeEXT Int32
  deriving newtype (LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool
(LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool)
-> (LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool)
-> Eq LineRasterizationModeEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool
$c/= :: LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool
== :: LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool
$c== :: LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool
Eq, Eq LineRasterizationModeEXT
Eq LineRasterizationModeEXT
-> (LineRasterizationModeEXT
    -> LineRasterizationModeEXT -> Ordering)
-> (LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool)
-> (LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool)
-> (LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool)
-> (LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool)
-> (LineRasterizationModeEXT
    -> LineRasterizationModeEXT -> LineRasterizationModeEXT)
-> (LineRasterizationModeEXT
    -> LineRasterizationModeEXT -> LineRasterizationModeEXT)
-> Ord LineRasterizationModeEXT
LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool
LineRasterizationModeEXT -> LineRasterizationModeEXT -> Ordering
LineRasterizationModeEXT
-> LineRasterizationModeEXT -> LineRasterizationModeEXT
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 :: LineRasterizationModeEXT
-> LineRasterizationModeEXT -> LineRasterizationModeEXT
$cmin :: LineRasterizationModeEXT
-> LineRasterizationModeEXT -> LineRasterizationModeEXT
max :: LineRasterizationModeEXT
-> LineRasterizationModeEXT -> LineRasterizationModeEXT
$cmax :: LineRasterizationModeEXT
-> LineRasterizationModeEXT -> LineRasterizationModeEXT
>= :: LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool
$c>= :: LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool
> :: LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool
$c> :: LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool
<= :: LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool
$c<= :: LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool
< :: LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool
$c< :: LineRasterizationModeEXT -> LineRasterizationModeEXT -> Bool
compare :: LineRasterizationModeEXT -> LineRasterizationModeEXT -> Ordering
$ccompare :: LineRasterizationModeEXT -> LineRasterizationModeEXT -> Ordering
$cp1Ord :: Eq LineRasterizationModeEXT
Ord, Ptr b -> Int -> IO LineRasterizationModeEXT
Ptr b -> Int -> LineRasterizationModeEXT -> IO ()
Ptr LineRasterizationModeEXT -> IO LineRasterizationModeEXT
Ptr LineRasterizationModeEXT -> Int -> IO LineRasterizationModeEXT
Ptr LineRasterizationModeEXT
-> Int -> LineRasterizationModeEXT -> IO ()
Ptr LineRasterizationModeEXT -> LineRasterizationModeEXT -> IO ()
LineRasterizationModeEXT -> Int
(LineRasterizationModeEXT -> Int)
-> (LineRasterizationModeEXT -> Int)
-> (Ptr LineRasterizationModeEXT
    -> Int -> IO LineRasterizationModeEXT)
-> (Ptr LineRasterizationModeEXT
    -> Int -> LineRasterizationModeEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO LineRasterizationModeEXT)
-> (forall b. Ptr b -> Int -> LineRasterizationModeEXT -> IO ())
-> (Ptr LineRasterizationModeEXT -> IO LineRasterizationModeEXT)
-> (Ptr LineRasterizationModeEXT
    -> LineRasterizationModeEXT -> IO ())
-> Storable LineRasterizationModeEXT
forall b. Ptr b -> Int -> IO LineRasterizationModeEXT
forall b. Ptr b -> Int -> LineRasterizationModeEXT -> 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 LineRasterizationModeEXT -> LineRasterizationModeEXT -> IO ()
$cpoke :: Ptr LineRasterizationModeEXT -> LineRasterizationModeEXT -> IO ()
peek :: Ptr LineRasterizationModeEXT -> IO LineRasterizationModeEXT
$cpeek :: Ptr LineRasterizationModeEXT -> IO LineRasterizationModeEXT
pokeByteOff :: Ptr b -> Int -> LineRasterizationModeEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> LineRasterizationModeEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO LineRasterizationModeEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO LineRasterizationModeEXT
pokeElemOff :: Ptr LineRasterizationModeEXT
-> Int -> LineRasterizationModeEXT -> IO ()
$cpokeElemOff :: Ptr LineRasterizationModeEXT
-> Int -> LineRasterizationModeEXT -> IO ()
peekElemOff :: Ptr LineRasterizationModeEXT -> Int -> IO LineRasterizationModeEXT
$cpeekElemOff :: Ptr LineRasterizationModeEXT -> Int -> IO LineRasterizationModeEXT
alignment :: LineRasterizationModeEXT -> Int
$calignment :: LineRasterizationModeEXT -> Int
sizeOf :: LineRasterizationModeEXT -> Int
$csizeOf :: LineRasterizationModeEXT -> Int
Storable, LineRasterizationModeEXT
LineRasterizationModeEXT -> Zero LineRasterizationModeEXT
forall a. a -> Zero a
zero :: LineRasterizationModeEXT
$czero :: LineRasterizationModeEXT
Zero)

-- | 'LINE_RASTERIZATION_MODE_DEFAULT_EXT' is equivalent to
-- 'LINE_RASTERIZATION_MODE_RECTANGULAR_EXT' if
-- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@strictLines@
-- is 'Vulkan.Core10.FundamentalTypes.TRUE', otherwise lines are drawn as
-- non-@strictLines@ parallelograms. Both of these modes are defined in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-lines-basic Basic Line Segment Rasterization>.
pattern $bLINE_RASTERIZATION_MODE_DEFAULT_EXT :: LineRasterizationModeEXT
$mLINE_RASTERIZATION_MODE_DEFAULT_EXT :: forall r.
LineRasterizationModeEXT -> (Void# -> r) -> (Void# -> r) -> r
LINE_RASTERIZATION_MODE_DEFAULT_EXT            = LineRasterizationModeEXT 0
-- | 'LINE_RASTERIZATION_MODE_RECTANGULAR_EXT' specifies lines drawn as if
-- they were rectangles extruded from the line
pattern $bLINE_RASTERIZATION_MODE_RECTANGULAR_EXT :: LineRasterizationModeEXT
$mLINE_RASTERIZATION_MODE_RECTANGULAR_EXT :: forall r.
LineRasterizationModeEXT -> (Void# -> r) -> (Void# -> r) -> r
LINE_RASTERIZATION_MODE_RECTANGULAR_EXT        = LineRasterizationModeEXT 1
-- | 'LINE_RASTERIZATION_MODE_BRESENHAM_EXT' specifies lines drawn by
-- determining which pixel diamonds the line intersects and exits, as
-- defined in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-lines-bresenham Bresenham Line Segment Rasterization>.
pattern $bLINE_RASTERIZATION_MODE_BRESENHAM_EXT :: LineRasterizationModeEXT
$mLINE_RASTERIZATION_MODE_BRESENHAM_EXT :: forall r.
LineRasterizationModeEXT -> (Void# -> r) -> (Void# -> r) -> r
LINE_RASTERIZATION_MODE_BRESENHAM_EXT          = LineRasterizationModeEXT 2
-- | 'LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT' specifies lines drawn
-- if they were rectangles extruded from the line, with alpha falloff, as
-- defined in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-lines-smooth Smooth Lines>.
pattern $bLINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT :: LineRasterizationModeEXT
$mLINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT :: forall r.
LineRasterizationModeEXT -> (Void# -> r) -> (Void# -> r) -> r
LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT = LineRasterizationModeEXT 3
{-# complete LINE_RASTERIZATION_MODE_DEFAULT_EXT,
             LINE_RASTERIZATION_MODE_RECTANGULAR_EXT,
             LINE_RASTERIZATION_MODE_BRESENHAM_EXT,
             LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT :: LineRasterizationModeEXT #-}

conNameLineRasterizationModeEXT :: String
conNameLineRasterizationModeEXT :: String
conNameLineRasterizationModeEXT = String
"LineRasterizationModeEXT"

enumPrefixLineRasterizationModeEXT :: String
enumPrefixLineRasterizationModeEXT :: String
enumPrefixLineRasterizationModeEXT = String
"LINE_RASTERIZATION_MODE_"

showTableLineRasterizationModeEXT :: [(LineRasterizationModeEXT, String)]
showTableLineRasterizationModeEXT :: [(LineRasterizationModeEXT, String)]
showTableLineRasterizationModeEXT =
  [ (LineRasterizationModeEXT
LINE_RASTERIZATION_MODE_DEFAULT_EXT           , String
"DEFAULT_EXT")
  , (LineRasterizationModeEXT
LINE_RASTERIZATION_MODE_RECTANGULAR_EXT       , String
"RECTANGULAR_EXT")
  , (LineRasterizationModeEXT
LINE_RASTERIZATION_MODE_BRESENHAM_EXT         , String
"BRESENHAM_EXT")
  , (LineRasterizationModeEXT
LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT, String
"RECTANGULAR_SMOOTH_EXT")
  ]

instance Show LineRasterizationModeEXT where
  showsPrec :: Int -> LineRasterizationModeEXT -> ShowS
showsPrec = String
-> [(LineRasterizationModeEXT, String)]
-> String
-> (LineRasterizationModeEXT -> Int32)
-> (Int32 -> ShowS)
-> Int
-> LineRasterizationModeEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixLineRasterizationModeEXT
                            [(LineRasterizationModeEXT, String)]
showTableLineRasterizationModeEXT
                            String
conNameLineRasterizationModeEXT
                            (\(LineRasterizationModeEXT Int32
x) -> Int32
x)
                            (Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read LineRasterizationModeEXT where
  readPrec :: ReadPrec LineRasterizationModeEXT
readPrec = String
-> [(LineRasterizationModeEXT, String)]
-> String
-> (Int32 -> LineRasterizationModeEXT)
-> ReadPrec LineRasterizationModeEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixLineRasterizationModeEXT
                          [(LineRasterizationModeEXT, String)]
showTableLineRasterizationModeEXT
                          String
conNameLineRasterizationModeEXT
                          Int32 -> LineRasterizationModeEXT
LineRasterizationModeEXT


type EXT_LINE_RASTERIZATION_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_EXT_LINE_RASTERIZATION_SPEC_VERSION"
pattern EXT_LINE_RASTERIZATION_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_LINE_RASTERIZATION_SPEC_VERSION :: a
$mEXT_LINE_RASTERIZATION_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_LINE_RASTERIZATION_SPEC_VERSION = 1


type EXT_LINE_RASTERIZATION_EXTENSION_NAME = "VK_EXT_line_rasterization"

-- No documentation found for TopLevel "VK_EXT_LINE_RASTERIZATION_EXTENSION_NAME"
pattern EXT_LINE_RASTERIZATION_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_LINE_RASTERIZATION_EXTENSION_NAME :: a
$mEXT_LINE_RASTERIZATION_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_LINE_RASTERIZATION_EXTENSION_NAME = "VK_EXT_line_rasterization"