{-# language CPP #-}
-- | = Name
--
-- VK_AMD_display_native_hdr - device extension
--
-- == VK_AMD_display_native_hdr
--
-- [__Name String__]
--     @VK_AMD_display_native_hdr@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     214
--
-- [__Revision__]
--     1
--
-- [__Ratification Status__]
--     Not ratified
--
-- [__Extension and Version Dependencies__]
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_get_physical_device_properties2 VK_KHR_get_physical_device_properties2>
--     and
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_get_surface_capabilities2 VK_KHR_get_surface_capabilities2>
--     and
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_swapchain VK_KHR_swapchain>
--
-- [__Contact__]
--
--     -   Matthaeus G. Chajdas
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_AMD_display_native_hdr] @anteru%0A*Here describe the issue or question you have about the VK_AMD_display_native_hdr extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2018-12-18
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Matthaeus G. Chajdas, AMD
--
--     -   Aaron Hagan, AMD
--
--     -   Aric Cyr, AMD
--
--     -   Timothy Lottes, AMD
--
--     -   Derrick Owens, AMD
--
--     -   Daniel Rakos, AMD
--
-- == Description
--
-- This extension introduces the following display native HDR features to
-- Vulkan:
--
-- -   A new 'Vulkan.Extensions.VK_KHR_surface.ColorSpaceKHR' enum for
--     setting the native display color space. For example, this color
--     space would be set by the swapchain to use the native color space in
--     Freesync2 displays.
--
-- -   Local dimming control
--
-- == New Commands
--
-- -   'setLocalDimmingAMD'
--
-- == New Structures
--
-- -   Extending
--     'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.SurfaceCapabilities2KHR':
--
--     -   'DisplayNativeHdrSurfaceCapabilitiesAMD'
--
-- -   Extending
--     'Vulkan.Extensions.VK_KHR_swapchain.SwapchainCreateInfoKHR':
--
--     -   'SwapchainDisplayNativeHdrCreateInfoAMD'
--
-- == New Enum Constants
--
-- -   'AMD_DISPLAY_NATIVE_HDR_EXTENSION_NAME'
--
-- -   'AMD_DISPLAY_NATIVE_HDR_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Extensions.VK_KHR_surface.ColorSpaceKHR':
--
--     -   'Vulkan.Extensions.VK_KHR_surface.COLOR_SPACE_DISPLAY_NATIVE_AMD'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DISPLAY_NATIVE_HDR_SURFACE_CAPABILITIES_AMD'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_SWAPCHAIN_DISPLAY_NATIVE_HDR_CREATE_INFO_AMD'
--
-- == Issues
--
-- None.
--
-- == Examples
--
-- None.
--
-- == Version History
--
-- -   Revision 1, 2018-12-18 (Daniel Rakos)
--
--     -   Initial revision
--
-- == See Also
--
-- 'DisplayNativeHdrSurfaceCapabilitiesAMD',
-- 'SwapchainDisplayNativeHdrCreateInfoAMD', 'setLocalDimmingAMD'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_AMD_display_native_hdr Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_AMD_display_native_hdr  ( setLocalDimmingAMD
                                                    , DisplayNativeHdrSurfaceCapabilitiesAMD(..)
                                                    , SwapchainDisplayNativeHdrCreateInfoAMD(..)
                                                    , AMD_DISPLAY_NATIVE_HDR_SPEC_VERSION
                                                    , pattern AMD_DISPLAY_NATIVE_HDR_SPEC_VERSION
                                                    , AMD_DISPLAY_NATIVE_HDR_EXTENSION_NAME
                                                    , pattern AMD_DISPLAY_NATIVE_HDR_EXTENSION_NAME
                                                    , SwapchainKHR(..)
                                                    , ColorSpaceKHR(..)
                                                    ) where

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 Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
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 Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
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.FundamentalTypes (Bool32(..))
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkSetLocalDimmingAMD))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Extensions.Handles (SwapchainKHR)
import Vulkan.Extensions.Handles (SwapchainKHR(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DISPLAY_NATIVE_HDR_SURFACE_CAPABILITIES_AMD))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SWAPCHAIN_DISPLAY_NATIVE_HDR_CREATE_INFO_AMD))
import Vulkan.Extensions.VK_KHR_surface (ColorSpaceKHR(..))
import Vulkan.Extensions.Handles (SwapchainKHR(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkSetLocalDimmingAMD
  :: FunPtr (Ptr Device_T -> SwapchainKHR -> Bool32 -> IO ()) -> Ptr Device_T -> SwapchainKHR -> Bool32 -> IO ()

-- | vkSetLocalDimmingAMD - Set Local Dimming
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkSetLocalDimmingAMD-device-parameter# @device@ /must/ be a
--     valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkSetLocalDimmingAMD-swapChain-parameter# @swapChain@ /must/
--     be a valid 'Vulkan.Extensions.Handles.SwapchainKHR' handle
--
-- -   #VUID-vkSetLocalDimmingAMD-swapChain-parent# @swapChain@ /must/ have
--     been created, allocated, or retrieved from @device@
--
-- == Valid Usage
--
-- -   #VUID-vkSetLocalDimmingAMD-localDimmingSupport-04618#
--     'DisplayNativeHdrSurfaceCapabilitiesAMD'::@localDimmingSupport@
--     /must/ be supported
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_AMD_display_native_hdr VK_AMD_display_native_hdr>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32', 'Vulkan.Core10.Handles.Device',
-- 'Vulkan.Extensions.Handles.SwapchainKHR'
setLocalDimmingAMD :: forall io
                    . (MonadIO io)
                   => -- | @device@ is the device associated with @swapChain@.
                      Device
                   -> -- | @swapChain@ handle to enable local dimming.
                      SwapchainKHR
                   -> -- | @localDimmingEnable@ specifies whether local dimming is enabled for the
                      -- swapchain.
                      ("localDimmingEnable" ::: Bool)
                   -> io ()
setLocalDimmingAMD :: forall (io :: * -> *).
MonadIO io =>
Device -> SwapchainKHR -> ("localDimmingEnable" ::: Bool) -> io ()
setLocalDimmingAMD Device
device SwapchainKHR
swapChain "localDimmingEnable" ::: Bool
localDimmingEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkSetLocalDimmingAMDPtr :: FunPtr
  (Ptr Device_T
   -> SwapchainKHR -> ("localDimmingEnable" ::: Bool32) -> IO ())
vkSetLocalDimmingAMDPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> SwapchainKHR -> ("localDimmingEnable" ::: Bool32) -> IO ())
pVkSetLocalDimmingAMD (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (f :: * -> *).
Applicative f =>
("localDimmingEnable" ::: Bool) -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> SwapchainKHR -> ("localDimmingEnable" ::: Bool32) -> IO ())
vkSetLocalDimmingAMDPtr forall a. Eq a => a -> a -> "localDimmingEnable" ::: Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkSetLocalDimmingAMD is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkSetLocalDimmingAMD' :: Ptr Device_T
-> SwapchainKHR -> ("localDimmingEnable" ::: Bool32) -> IO ()
vkSetLocalDimmingAMD' = FunPtr
  (Ptr Device_T
   -> SwapchainKHR -> ("localDimmingEnable" ::: Bool32) -> IO ())
-> Ptr Device_T
-> SwapchainKHR
-> ("localDimmingEnable" ::: Bool32)
-> IO ()
mkVkSetLocalDimmingAMD FunPtr
  (Ptr Device_T
   -> SwapchainKHR -> ("localDimmingEnable" ::: Bool32) -> IO ())
vkSetLocalDimmingAMDPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkSetLocalDimmingAMD" (Ptr Device_T
-> SwapchainKHR -> ("localDimmingEnable" ::: Bool32) -> IO ()
vkSetLocalDimmingAMD'
                                             (Device -> Ptr Device_T
deviceHandle (Device
device))
                                             (SwapchainKHR
swapChain)
                                             (("localDimmingEnable" ::: Bool) -> "localDimmingEnable" ::: Bool32
boolToBool32 ("localDimmingEnable" ::: Bool
localDimmingEnable)))
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()


-- | VkDisplayNativeHdrSurfaceCapabilitiesAMD - Structure describing display
-- native HDR specific capabilities of a surface
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_AMD_display_native_hdr VK_AMD_display_native_hdr>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DisplayNativeHdrSurfaceCapabilitiesAMD = DisplayNativeHdrSurfaceCapabilitiesAMD
  { -- | @localDimmingSupport@ specifies whether the surface supports local
    -- dimming. If this is 'Vulkan.Core10.FundamentalTypes.TRUE',
    -- 'SwapchainDisplayNativeHdrCreateInfoAMD' /can/ be used to explicitly
    -- enable or disable local dimming for the surface. Local dimming may also
    -- be overridden by 'setLocalDimmingAMD' during the lifetime of the
    -- swapchain.
    DisplayNativeHdrSurfaceCapabilitiesAMD
-> "localDimmingEnable" ::: Bool
localDimmingSupport :: Bool }
  deriving (Typeable, DisplayNativeHdrSurfaceCapabilitiesAMD
-> DisplayNativeHdrSurfaceCapabilitiesAMD
-> "localDimmingEnable" ::: Bool
forall a.
(a -> a -> "localDimmingEnable" ::: Bool)
-> (a -> a -> "localDimmingEnable" ::: Bool) -> Eq a
/= :: DisplayNativeHdrSurfaceCapabilitiesAMD
-> DisplayNativeHdrSurfaceCapabilitiesAMD
-> "localDimmingEnable" ::: Bool
$c/= :: DisplayNativeHdrSurfaceCapabilitiesAMD
-> DisplayNativeHdrSurfaceCapabilitiesAMD
-> "localDimmingEnable" ::: Bool
== :: DisplayNativeHdrSurfaceCapabilitiesAMD
-> DisplayNativeHdrSurfaceCapabilitiesAMD
-> "localDimmingEnable" ::: Bool
$c== :: DisplayNativeHdrSurfaceCapabilitiesAMD
-> DisplayNativeHdrSurfaceCapabilitiesAMD
-> "localDimmingEnable" ::: Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DisplayNativeHdrSurfaceCapabilitiesAMD)
#endif
deriving instance Show DisplayNativeHdrSurfaceCapabilitiesAMD

instance ToCStruct DisplayNativeHdrSurfaceCapabilitiesAMD where
  withCStruct :: forall b.
DisplayNativeHdrSurfaceCapabilitiesAMD
-> (Ptr DisplayNativeHdrSurfaceCapabilitiesAMD -> IO b) -> IO b
withCStruct DisplayNativeHdrSurfaceCapabilitiesAMD
x Ptr DisplayNativeHdrSurfaceCapabilitiesAMD -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
p DisplayNativeHdrSurfaceCapabilitiesAMD
x (Ptr DisplayNativeHdrSurfaceCapabilitiesAMD -> IO b
f Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
p)
  pokeCStruct :: forall b.
Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
-> DisplayNativeHdrSurfaceCapabilitiesAMD -> IO b -> IO b
pokeCStruct Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
p DisplayNativeHdrSurfaceCapabilitiesAMD{"localDimmingEnable" ::: Bool
localDimmingSupport :: "localDimmingEnable" ::: Bool
$sel:localDimmingSupport:DisplayNativeHdrSurfaceCapabilitiesAMD :: DisplayNativeHdrSurfaceCapabilitiesAMD
-> "localDimmingEnable" ::: Bool
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DISPLAY_NATIVE_HDR_SURFACE_CAPABILITIES_AMD)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (("localDimmingEnable" ::: Bool) -> "localDimmingEnable" ::: Bool32
boolToBool32 ("localDimmingEnable" ::: Bool
localDimmingSupport))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr DisplayNativeHdrSurfaceCapabilitiesAMD -> IO b -> IO b
pokeZeroCStruct Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DISPLAY_NATIVE_HDR_SURFACE_CAPABILITIES_AMD)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (("localDimmingEnable" ::: Bool) -> "localDimmingEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct DisplayNativeHdrSurfaceCapabilitiesAMD where
  peekCStruct :: Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
-> IO DisplayNativeHdrSurfaceCapabilitiesAMD
peekCStruct Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
p = do
    "localDimmingEnable" ::: Bool32
localDimmingSupport <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr DisplayNativeHdrSurfaceCapabilitiesAMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ("localDimmingEnable" ::: Bool)
-> DisplayNativeHdrSurfaceCapabilitiesAMD
DisplayNativeHdrSurfaceCapabilitiesAMD
             (("localDimmingEnable" ::: Bool32) -> "localDimmingEnable" ::: Bool
bool32ToBool "localDimmingEnable" ::: Bool32
localDimmingSupport)

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

instance Zero DisplayNativeHdrSurfaceCapabilitiesAMD where
  zero :: DisplayNativeHdrSurfaceCapabilitiesAMD
zero = ("localDimmingEnable" ::: Bool)
-> DisplayNativeHdrSurfaceCapabilitiesAMD
DisplayNativeHdrSurfaceCapabilitiesAMD
           forall a. Zero a => a
zero


-- | VkSwapchainDisplayNativeHdrCreateInfoAMD - Structure specifying display
-- native HDR parameters of a newly created swapchain object
--
-- = Description
--
-- If the @pNext@ chain of
-- 'Vulkan.Extensions.VK_KHR_swapchain.SwapchainCreateInfoKHR' does not
-- include this structure, the default value for @localDimmingEnable@ is
-- 'Vulkan.Core10.FundamentalTypes.TRUE', meaning local dimming is
-- initially enabled for the swapchain.
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkSwapchainDisplayNativeHdrCreateInfoAMD-sType-sType# @sType@
--     /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_SWAPCHAIN_DISPLAY_NATIVE_HDR_CREATE_INFO_AMD'
--
-- == Valid Usage
--
-- -   #VUID-VkSwapchainDisplayNativeHdrCreateInfoAMD-localDimmingEnable-04449#
--     It is only valid to set @localDimmingEnable@ to
--     'Vulkan.Core10.FundamentalTypes.TRUE' if
--     'DisplayNativeHdrSurfaceCapabilitiesAMD'::@localDimmingSupport@ is
--     supported
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_AMD_display_native_hdr VK_AMD_display_native_hdr>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data SwapchainDisplayNativeHdrCreateInfoAMD = SwapchainDisplayNativeHdrCreateInfoAMD
  { -- | @localDimmingEnable@ specifies whether local dimming is enabled for the
    -- swapchain.
    SwapchainDisplayNativeHdrCreateInfoAMD
-> "localDimmingEnable" ::: Bool
localDimmingEnable :: Bool }
  deriving (Typeable, SwapchainDisplayNativeHdrCreateInfoAMD
-> SwapchainDisplayNativeHdrCreateInfoAMD
-> "localDimmingEnable" ::: Bool
forall a.
(a -> a -> "localDimmingEnable" ::: Bool)
-> (a -> a -> "localDimmingEnable" ::: Bool) -> Eq a
/= :: SwapchainDisplayNativeHdrCreateInfoAMD
-> SwapchainDisplayNativeHdrCreateInfoAMD
-> "localDimmingEnable" ::: Bool
$c/= :: SwapchainDisplayNativeHdrCreateInfoAMD
-> SwapchainDisplayNativeHdrCreateInfoAMD
-> "localDimmingEnable" ::: Bool
== :: SwapchainDisplayNativeHdrCreateInfoAMD
-> SwapchainDisplayNativeHdrCreateInfoAMD
-> "localDimmingEnable" ::: Bool
$c== :: SwapchainDisplayNativeHdrCreateInfoAMD
-> SwapchainDisplayNativeHdrCreateInfoAMD
-> "localDimmingEnable" ::: Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SwapchainDisplayNativeHdrCreateInfoAMD)
#endif
deriving instance Show SwapchainDisplayNativeHdrCreateInfoAMD

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

instance FromCStruct SwapchainDisplayNativeHdrCreateInfoAMD where
  peekCStruct :: Ptr SwapchainDisplayNativeHdrCreateInfoAMD
-> IO SwapchainDisplayNativeHdrCreateInfoAMD
peekCStruct Ptr SwapchainDisplayNativeHdrCreateInfoAMD
p = do
    "localDimmingEnable" ::: Bool32
localDimmingEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr SwapchainDisplayNativeHdrCreateInfoAMD
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ("localDimmingEnable" ::: Bool)
-> SwapchainDisplayNativeHdrCreateInfoAMD
SwapchainDisplayNativeHdrCreateInfoAMD
             (("localDimmingEnable" ::: Bool32) -> "localDimmingEnable" ::: Bool
bool32ToBool "localDimmingEnable" ::: Bool32
localDimmingEnable)

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

instance Zero SwapchainDisplayNativeHdrCreateInfoAMD where
  zero :: SwapchainDisplayNativeHdrCreateInfoAMD
zero = ("localDimmingEnable" ::: Bool)
-> SwapchainDisplayNativeHdrCreateInfoAMD
SwapchainDisplayNativeHdrCreateInfoAMD
           forall a. Zero a => a
zero


type AMD_DISPLAY_NATIVE_HDR_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_AMD_DISPLAY_NATIVE_HDR_SPEC_VERSION"
pattern AMD_DISPLAY_NATIVE_HDR_SPEC_VERSION :: forall a . Integral a => a
pattern $bAMD_DISPLAY_NATIVE_HDR_SPEC_VERSION :: forall a. Integral a => a
$mAMD_DISPLAY_NATIVE_HDR_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
AMD_DISPLAY_NATIVE_HDR_SPEC_VERSION = 1


type AMD_DISPLAY_NATIVE_HDR_EXTENSION_NAME = "VK_AMD_display_native_hdr"

-- No documentation found for TopLevel "VK_AMD_DISPLAY_NATIVE_HDR_EXTENSION_NAME"
pattern AMD_DISPLAY_NATIVE_HDR_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bAMD_DISPLAY_NATIVE_HDR_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mAMD_DISPLAY_NATIVE_HDR_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
AMD_DISPLAY_NATIVE_HDR_EXTENSION_NAME = "VK_AMD_display_native_hdr"