{-# language CPP #-}
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 Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
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 Data.Word (Word16)
import Data.Word (Word32)
import Text.Read.Lex (Lexeme(Ident))
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_T)
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetLineStippleEXT))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
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 the dynamic line width state
--
-- == Valid Usage
--
-- -   @lineStippleFactor@ /must/ be in the range [1,256]
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   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> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Graphics                                                                                                              |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- '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
commandBuffer lineStippleFactor :: "lineStippleFactor" ::: Word32
lineStippleFactor lineStipplePattern :: "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 (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  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 "" "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
  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
--
-- The members of the 'PhysicalDeviceLineRasterizationFeaturesEXT'
-- structure describe the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceLineRasterizationFeaturesEXT' structure is
-- included in the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
-- it is filled with values indicating whether the feature is supported.
-- 'PhysicalDeviceLineRasterizationFeaturesEXT' /can/ also be included in
-- the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to enable
-- the feature.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceLineRasterizationFeaturesEXT = PhysicalDeviceLineRasterizationFeaturesEXT
  { -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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
  , -- | @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 x :: PhysicalDeviceLineRasterizationFeaturesEXT
x f :: Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: 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 p :: Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p PhysicalDeviceLineRasterizationFeaturesEXT{..} f :: 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` 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` 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` 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` 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` 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` 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` 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` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
stippledSmoothLines))
    IO b
f
  cStructSize :: Int
cStructSize = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceLineRasterizationFeaturesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceLineRasterizationFeaturesEXT
p f :: 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` 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` 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` 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` 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` 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` 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` 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` 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 p :: 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` 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` 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` 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` 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` 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` 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
_ = 40
  alignment :: PhysicalDeviceLineRasterizationFeaturesEXT -> Int
alignment ~PhysicalDeviceLineRasterizationFeaturesEXT
_ = 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 :: Ptr PhysicalDeviceLineRasterizationFeaturesEXT
ptr poked :: 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
--
-- = Members
--
-- The members of the 'PhysicalDeviceLineRasterizationPropertiesEXT'
-- structure describe the following implementation-dependent limits:
--
-- = Description
--
-- If the 'PhysicalDeviceLineRasterizationPropertiesEXT' structure is
-- included in the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2',
-- it is filled with the implementation-dependent limits.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceLineRasterizationPropertiesEXT = PhysicalDeviceLineRasterizationPropertiesEXT
  { -- | @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 x :: PhysicalDeviceLineRasterizationPropertiesEXT
x f :: Ptr PhysicalDeviceLineRasterizationPropertiesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceLineRasterizationPropertiesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceLineRasterizationPropertiesEXT -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceLineRasterizationPropertiesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: 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 p :: Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p PhysicalDeviceLineRasterizationPropertiesEXT{..} f :: 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` 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` 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` 16 :: Ptr Word32)) ("lineStippleFactor" ::: Word32
lineSubPixelPrecisionBits)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceLineRasterizationPropertiesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceLineRasterizationPropertiesEXT
p f :: 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` 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` 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` 16 :: Ptr Word32)) ("lineStippleFactor" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceLineRasterizationPropertiesEXT where
  peekCStruct :: Ptr PhysicalDeviceLineRasterizationPropertiesEXT
-> IO PhysicalDeviceLineRasterizationPropertiesEXT
peekCStruct p :: 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` 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
_ = 24
  alignment :: PhysicalDeviceLineRasterizationPropertiesEXT -> Int
alignment ~PhysicalDeviceLineRasterizationPropertiesEXT
_ = 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 :: Ptr PhysicalDeviceLineRasterizationPropertiesEXT
ptr poked :: 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
--
-- == Valid Usage
--
-- -   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
--
-- -   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
--
-- -   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
--
-- -   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
--
-- -   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
--
-- -   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
--
-- -   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)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_RASTERIZATION_LINE_STATE_CREATE_INFO_EXT'
--
-- -   @lineRasterizationMode@ /must/ be a valid 'LineRasterizationModeEXT'
--     value
--
-- = See Also
--
-- '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 x :: PipelineRasterizationLineStateCreateInfoEXT
x f :: Ptr PipelineRasterizationLineStateCreateInfoEXT -> IO b
f = Int
-> Int
-> (Ptr PipelineRasterizationLineStateCreateInfoEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr PipelineRasterizationLineStateCreateInfoEXT -> IO b) -> IO b)
-> (Ptr PipelineRasterizationLineStateCreateInfoEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: 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 p :: Ptr PipelineRasterizationLineStateCreateInfoEXT
p PipelineRasterizationLineStateCreateInfoEXT{..} f :: 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` 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` 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` 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` 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` 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` 28 :: Ptr Word16)) ("lineStipplePattern" ::: Word16
lineStipplePattern)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PipelineRasterizationLineStateCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PipelineRasterizationLineStateCreateInfoEXT
p f :: 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` 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` 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` 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` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PipelineRasterizationLineStateCreateInfoEXT where
  peekCStruct :: Ptr PipelineRasterizationLineStateCreateInfoEXT
-> IO PipelineRasterizationLineStateCreateInfoEXT
peekCStruct p :: 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` 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` 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` 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` 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
_ = 32
  alignment :: PipelineRasterizationLineStateCreateInfoEXT -> Int
alignment ~PipelineRasterizationLineStateCreateInfoEXT
_ = 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 :: Ptr PipelineRasterizationLineStateCreateInfoEXT
ptr poked :: 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
--
-- '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 #-}

instance Show LineRasterizationModeEXT where
  showsPrec :: Int -> LineRasterizationModeEXT -> ShowS
showsPrec p :: Int
p = \case
    LINE_RASTERIZATION_MODE_DEFAULT_EXT -> String -> ShowS
showString "LINE_RASTERIZATION_MODE_DEFAULT_EXT"
    LINE_RASTERIZATION_MODE_RECTANGULAR_EXT -> String -> ShowS
showString "LINE_RASTERIZATION_MODE_RECTANGULAR_EXT"
    LINE_RASTERIZATION_MODE_BRESENHAM_EXT -> String -> ShowS
showString "LINE_RASTERIZATION_MODE_BRESENHAM_EXT"
    LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT -> String -> ShowS
showString "LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT"
    LineRasterizationModeEXT x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "LineRasterizationModeEXT " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read LineRasterizationModeEXT where
  readPrec :: ReadPrec LineRasterizationModeEXT
readPrec = ReadPrec LineRasterizationModeEXT
-> ReadPrec LineRasterizationModeEXT
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec LineRasterizationModeEXT)]
-> ReadPrec LineRasterizationModeEXT
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("LINE_RASTERIZATION_MODE_DEFAULT_EXT", LineRasterizationModeEXT -> ReadPrec LineRasterizationModeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure LineRasterizationModeEXT
LINE_RASTERIZATION_MODE_DEFAULT_EXT)
                            , ("LINE_RASTERIZATION_MODE_RECTANGULAR_EXT", LineRasterizationModeEXT -> ReadPrec LineRasterizationModeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure LineRasterizationModeEXT
LINE_RASTERIZATION_MODE_RECTANGULAR_EXT)
                            , ("LINE_RASTERIZATION_MODE_BRESENHAM_EXT", LineRasterizationModeEXT -> ReadPrec LineRasterizationModeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure LineRasterizationModeEXT
LINE_RASTERIZATION_MODE_BRESENHAM_EXT)
                            , ("LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT", LineRasterizationModeEXT -> ReadPrec LineRasterizationModeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure LineRasterizationModeEXT
LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT)]
                     ReadPrec LineRasterizationModeEXT
-> ReadPrec LineRasterizationModeEXT
-> ReadPrec LineRasterizationModeEXT
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec LineRasterizationModeEXT
-> ReadPrec LineRasterizationModeEXT
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "LineRasterizationModeEXT")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       LineRasterizationModeEXT -> ReadPrec LineRasterizationModeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> LineRasterizationModeEXT
LineRasterizationModeEXT Int32
v)))


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"