{-# language CPP #-}
-- | = Name
--
-- VK_EXT_hdr_metadata - device extension
--
-- == VK_EXT_hdr_metadata
--
-- [__Name String__]
--     @VK_EXT_hdr_metadata@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     106
--
-- [__Revision__]
--     2
--
-- [__Extension and Version Dependencies__]
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_swapchain VK_KHR_swapchain>
--
-- [__Contact__]
--
--     -   Courtney Goeltzenleuchter
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_hdr_metadata] @courtney-g%0A*Here describe the issue or question you have about the VK_EXT_hdr_metadata extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2018-12-19
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Courtney Goeltzenleuchter, Google
--
-- == Description
--
-- This extension defines two new structures and a function to assign SMPTE
-- (the Society of Motion Picture and Television Engineers) 2086 metadata
-- and CTA (Consumer Technology Association) 861.3 metadata to a swapchain.
-- The metadata includes the color primaries, white point, and luminance
-- range of the reference monitor, which all together define the color
-- volume containing all the possible colors the reference monitor can
-- produce. The reference monitor is the display where creative work is
-- done and creative intent is established. To preserve such creative
-- intent as much as possible and achieve consistent color reproduction on
-- different viewing displays, it is useful for the display pipeline to
-- know the color volume of the original reference monitor where content
-- was created or tuned. This avoids performing unnecessary mapping of
-- colors that are not displayable on the original reference monitor. The
-- metadata also includes the @maxContentLightLevel@ and
-- @maxFrameAverageLightLevel@ as defined by CTA 861.3.
--
-- While the general purpose of the metadata is to assist in the
-- transformation between different color volumes of different displays and
-- help achieve better color reproduction, it is not in the scope of this
-- extension to define how exactly the metadata should be used in such a
-- process. It is up to the implementation to determine how to make use of
-- the metadata.
--
-- == New Commands
--
-- -   'setHdrMetadataEXT'
--
-- == New Structures
--
-- -   'HdrMetadataEXT'
--
-- -   'XYColorEXT'
--
-- == New Enum Constants
--
-- -   'EXT_HDR_METADATA_EXTENSION_NAME'
--
-- -   'EXT_HDR_METADATA_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_HDR_METADATA_EXT'
--
-- == Issues
--
-- 1) Do we need a query function?
--
-- __PROPOSED__: No, Vulkan does not provide queries for state that the
-- application can track on its own.
--
-- 2) Should we specify default if not specified by the application?
--
-- __PROPOSED__: No, that leaves the default up to the display.
--
-- == Version History
--
-- -   Revision 1, 2016-12-27 (Courtney Goeltzenleuchter)
--
--     -   Initial version
--
-- -   Revision 2, 2018-12-19 (Courtney Goeltzenleuchter)
--
--     -   Correct implicit validity for VkHdrMetadataEXT structure
--
-- == See Also
--
-- 'HdrMetadataEXT', 'XYColorEXT', 'setHdrMetadataEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_EXT_hdr_metadata 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_hdr_metadata  ( setHdrMetadataEXT
                                              , XYColorEXT(..)
                                              , HdrMetadataEXT(..)
                                              , EXT_HDR_METADATA_SPEC_VERSION
                                              , pattern EXT_HDR_METADATA_SPEC_VERSION
                                              , EXT_HDR_METADATA_EXTENSION_NAME
                                              , pattern EXT_HDR_METADATA_EXTENSION_NAME
                                              , SwapchainKHR(..)
                                              ) 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 Data.Coerce (coerce)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
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.C.Types (CFloat)
import Foreign.C.Types (CFloat(..))
import Foreign.C.Types (CFloat(CFloat))
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.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkSetHdrMetadataEXT))
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_HDR_METADATA_EXT))
import Vulkan.Extensions.Handles (SwapchainKHR(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkSetHdrMetadataEXT
  :: FunPtr (Ptr Device_T -> Word32 -> Ptr SwapchainKHR -> Ptr HdrMetadataEXT -> IO ()) -> Ptr Device_T -> Word32 -> Ptr SwapchainKHR -> Ptr HdrMetadataEXT -> IO ()

-- | vkSetHdrMetadataEXT - Set Hdr metadata
--
-- = Description
--
-- The metadata will be applied to the specified
-- 'Vulkan.Extensions.Handles.SwapchainKHR' objects at the next
-- 'Vulkan.Extensions.VK_KHR_swapchain.queuePresentKHR' call using that
-- 'Vulkan.Extensions.Handles.SwapchainKHR' object. The metadata will
-- persist until a subsequent 'setHdrMetadataEXT' changes it.
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkSetHdrMetadataEXT-device-parameter# @device@ /must/ be a
--     valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkSetHdrMetadataEXT-pSwapchains-parameter# @pSwapchains@
--     /must/ be a valid pointer to an array of @swapchainCount@ valid
--     'Vulkan.Extensions.Handles.SwapchainKHR' handles
--
-- -   #VUID-vkSetHdrMetadataEXT-pMetadata-parameter# @pMetadata@ /must/ be
--     a valid pointer to an array of @swapchainCount@ valid
--     'HdrMetadataEXT' structures
--
-- -   #VUID-vkSetHdrMetadataEXT-swapchainCount-arraylength#
--     @swapchainCount@ /must/ be greater than @0@
--
-- -   #VUID-vkSetHdrMetadataEXT-pSwapchains-parent# Each element of
--     @pSwapchains@ /must/ have been created, allocated, or retrieved from
--     @device@
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_hdr_metadata VK_EXT_hdr_metadata>,
-- 'Vulkan.Core10.Handles.Device', 'HdrMetadataEXT',
-- 'Vulkan.Extensions.Handles.SwapchainKHR'
setHdrMetadataEXT :: forall io
                   . (MonadIO io)
                  => -- | @device@ is the logical device where the swapchain(s) were created.
                     Device
                  -> -- | @pSwapchains@ is a pointer to an array of @swapchainCount@
                     -- 'Vulkan.Extensions.Handles.SwapchainKHR' handles.
                     ("swapchains" ::: Vector SwapchainKHR)
                  -> -- | @pMetadata@ is a pointer to an array of @swapchainCount@
                     -- 'HdrMetadataEXT' structures.
                     ("metadata" ::: Vector HdrMetadataEXT)
                  -> io ()
setHdrMetadataEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> ("swapchains" ::: Vector SwapchainKHR)
-> ("metadata" ::: Vector HdrMetadataEXT)
-> io ()
setHdrMetadataEXT Device
device "swapchains" ::: Vector SwapchainKHR
swapchains "metadata" ::: Vector HdrMetadataEXT
metadata = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkSetHdrMetadataEXTPtr :: FunPtr
  (Ptr Device_T
   -> ("swapchainCount" ::: Word32)
   -> ("pSwapchains" ::: Ptr SwapchainKHR)
   -> ("pMetadata" ::: Ptr HdrMetadataEXT)
   -> IO ())
vkSetHdrMetadataEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("swapchainCount" ::: Word32)
      -> ("pSwapchains" ::: Ptr SwapchainKHR)
      -> ("pMetadata" ::: Ptr HdrMetadataEXT)
      -> IO ())
pVkSetHdrMetadataEXT (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("swapchainCount" ::: Word32)
   -> ("pSwapchains" ::: Ptr SwapchainKHR)
   -> ("pMetadata" ::: Ptr HdrMetadataEXT)
   -> IO ())
vkSetHdrMetadataEXTPtr forall a. Eq a => a -> a -> 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 vkSetHdrMetadataEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkSetHdrMetadataEXT' :: Ptr Device_T
-> ("swapchainCount" ::: Word32)
-> ("pSwapchains" ::: Ptr SwapchainKHR)
-> ("pMetadata" ::: Ptr HdrMetadataEXT)
-> IO ()
vkSetHdrMetadataEXT' = FunPtr
  (Ptr Device_T
   -> ("swapchainCount" ::: Word32)
   -> ("pSwapchains" ::: Ptr SwapchainKHR)
   -> ("pMetadata" ::: Ptr HdrMetadataEXT)
   -> IO ())
-> Ptr Device_T
-> ("swapchainCount" ::: Word32)
-> ("pSwapchains" ::: Ptr SwapchainKHR)
-> ("pMetadata" ::: Ptr HdrMetadataEXT)
-> IO ()
mkVkSetHdrMetadataEXT FunPtr
  (Ptr Device_T
   -> ("swapchainCount" ::: Word32)
   -> ("pSwapchains" ::: Ptr SwapchainKHR)
   -> ("pMetadata" ::: Ptr HdrMetadataEXT)
   -> IO ())
vkSetHdrMetadataEXTPtr
  let pSwapchainsLength :: Int
pSwapchainsLength = forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ ("swapchains" ::: Vector SwapchainKHR
swapchains)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ ("metadata" ::: Vector HdrMetadataEXT
metadata)) forall a. Eq a => a -> a -> Bool
== Int
pSwapchainsLength) 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
"pMetadata and pSwapchains must have the same length" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  "pSwapchains" ::: Ptr SwapchainKHR
pPSwapchains <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @SwapchainKHR ((forall a. Vector a -> Int
Data.Vector.length ("swapchains" ::: Vector SwapchainKHR
swapchains)) forall a. Num a => a -> a -> a
* Int
8)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i SwapchainKHR
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pSwapchains" ::: Ptr SwapchainKHR
pPSwapchains forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SwapchainKHR) (SwapchainKHR
e)) ("swapchains" ::: Vector SwapchainKHR
swapchains)
  "pMetadata" ::: Ptr HdrMetadataEXT
pPMetadata <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @HdrMetadataEXT ((forall a. Vector a -> Int
Data.Vector.length ("metadata" ::: Vector HdrMetadataEXT
metadata)) forall a. Num a => a -> a -> a
* Int
64)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i HdrMetadataEXT
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pMetadata" ::: Ptr HdrMetadataEXT
pPMetadata forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
64 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr HdrMetadataEXT) (HdrMetadataEXT
e)) ("metadata" ::: Vector HdrMetadataEXT
metadata)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkSetHdrMetadataEXT" (Ptr Device_T
-> ("swapchainCount" ::: Word32)
-> ("pSwapchains" ::: Ptr SwapchainKHR)
-> ("pMetadata" ::: Ptr HdrMetadataEXT)
-> IO ()
vkSetHdrMetadataEXT'
                                                   (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                   ((forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pSwapchainsLength :: Word32))
                                                   ("pSwapchains" ::: Ptr SwapchainKHR
pPSwapchains)
                                                   ("pMetadata" ::: Ptr HdrMetadataEXT
pPMetadata))
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()


-- | VkXYColorEXT - Specify X,Y chromaticity coordinates
--
-- = Description
--
-- Chromaticity coordinates are as specified in CIE 15:2004 “Calculation of
-- chromaticity coordinates” (Section 7.3) and are limited to between 0 and
-- 1 for real colors for the reference monitor.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_hdr_metadata VK_EXT_hdr_metadata>,
-- 'HdrMetadataEXT'
data XYColorEXT = XYColorEXT
  { -- | @x@ is the x chromaticity coordinate.
    XYColorEXT -> Float
x :: Float
  , -- | @y@ is the y chromaticity coordinate.
    XYColorEXT -> Float
y :: Float
  }
  deriving (Typeable, XYColorEXT -> XYColorEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: XYColorEXT -> XYColorEXT -> Bool
$c/= :: XYColorEXT -> XYColorEXT -> Bool
== :: XYColorEXT -> XYColorEXT -> Bool
$c== :: XYColorEXT -> XYColorEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (XYColorEXT)
#endif
deriving instance Show XYColorEXT

instance ToCStruct XYColorEXT where
  withCStruct :: forall b. XYColorEXT -> (Ptr XYColorEXT -> IO b) -> IO b
withCStruct XYColorEXT
x Ptr XYColorEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
8 forall a b. (a -> b) -> a -> b
$ \Ptr XYColorEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr XYColorEXT
p XYColorEXT
x (Ptr XYColorEXT -> IO b
f Ptr XYColorEXT
p)
  pokeCStruct :: forall b. Ptr XYColorEXT -> XYColorEXT -> IO b -> IO b
pokeCStruct Ptr XYColorEXT
p XYColorEXT{Float
y :: Float
x :: Float
$sel:y:XYColorEXT :: XYColorEXT -> Float
$sel:x:XYColorEXT :: XYColorEXT -> Float
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr XYColorEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
x))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr XYColorEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
y))
    IO b
f
  cStructSize :: Int
cStructSize = Int
8
  cStructAlignment :: Int
cStructAlignment = Int
4
  pokeZeroCStruct :: forall b. Ptr XYColorEXT -> IO b -> IO b
pokeZeroCStruct Ptr XYColorEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr XYColorEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr CFloat)) (Float -> CFloat
CFloat (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr XYColorEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr CFloat)) (Float -> CFloat
CFloat (forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct XYColorEXT where
  peekCStruct :: Ptr XYColorEXT -> IO XYColorEXT
peekCStruct Ptr XYColorEXT
p = do
    CFloat
x <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr XYColorEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr CFloat))
    CFloat
y <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr XYColorEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr CFloat))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Float -> Float -> XYColorEXT
XYColorEXT
             (coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
x) (coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
y)

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

instance Zero XYColorEXT where
  zero :: XYColorEXT
zero = Float -> Float -> XYColorEXT
XYColorEXT
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


-- | VkHdrMetadataEXT - Specify Hdr metadata
--
-- == Valid Usage (Implicit)
--
-- Note
--
-- The validity and use of this data is outside the scope of Vulkan.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_hdr_metadata VK_EXT_hdr_metadata>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'XYColorEXT',
-- 'setHdrMetadataEXT'
data HdrMetadataEXT = HdrMetadataEXT
  { -- | @displayPrimaryRed@ is a 'XYColorEXT' structure specifying the reference
    -- monitor’s red primary in chromaticity coordinates
    HdrMetadataEXT -> XYColorEXT
displayPrimaryRed :: XYColorEXT
  , -- | @displayPrimaryGreen@ is a 'XYColorEXT' structure specifying the
    -- reference monitor’s green primary in chromaticity coordinates
    HdrMetadataEXT -> XYColorEXT
displayPrimaryGreen :: XYColorEXT
  , -- | @displayPrimaryBlue@ is a 'XYColorEXT' structure specifying the
    -- reference monitor’s blue primary in chromaticity coordinates
    HdrMetadataEXT -> XYColorEXT
displayPrimaryBlue :: XYColorEXT
  , -- | @whitePoint@ is a 'XYColorEXT' structure specifying the reference
    -- monitor’s white-point in chromaticity coordinates
    HdrMetadataEXT -> XYColorEXT
whitePoint :: XYColorEXT
  , -- | @maxLuminance@ is the maximum luminance of the reference monitor in nits
    HdrMetadataEXT -> Float
maxLuminance :: Float
  , -- | @minLuminance@ is the minimum luminance of the reference monitor in nits
    HdrMetadataEXT -> Float
minLuminance :: Float
  , -- | @maxContentLightLevel@ is content’s maximum luminance in nits
    HdrMetadataEXT -> Float
maxContentLightLevel :: Float
  , -- | @maxFrameAverageLightLevel@ is the maximum frame average light level in
    -- nits
    HdrMetadataEXT -> Float
maxFrameAverageLightLevel :: Float
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (HdrMetadataEXT)
#endif
deriving instance Show HdrMetadataEXT

instance ToCStruct HdrMetadataEXT where
  withCStruct :: forall b.
HdrMetadataEXT
-> (("pMetadata" ::: Ptr HdrMetadataEXT) -> IO b) -> IO b
withCStruct HdrMetadataEXT
x ("pMetadata" ::: Ptr HdrMetadataEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
64 forall a b. (a -> b) -> a -> b
$ \"pMetadata" ::: Ptr HdrMetadataEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMetadata" ::: Ptr HdrMetadataEXT
p HdrMetadataEXT
x (("pMetadata" ::: Ptr HdrMetadataEXT) -> IO b
f "pMetadata" ::: Ptr HdrMetadataEXT
p)
  pokeCStruct :: forall b.
("pMetadata" ::: Ptr HdrMetadataEXT)
-> HdrMetadataEXT -> IO b -> IO b
pokeCStruct "pMetadata" ::: Ptr HdrMetadataEXT
p HdrMetadataEXT{Float
XYColorEXT
maxFrameAverageLightLevel :: Float
maxContentLightLevel :: Float
minLuminance :: Float
maxLuminance :: Float
whitePoint :: XYColorEXT
displayPrimaryBlue :: XYColorEXT
displayPrimaryGreen :: XYColorEXT
displayPrimaryRed :: XYColorEXT
$sel:maxFrameAverageLightLevel:HdrMetadataEXT :: HdrMetadataEXT -> Float
$sel:maxContentLightLevel:HdrMetadataEXT :: HdrMetadataEXT -> Float
$sel:minLuminance:HdrMetadataEXT :: HdrMetadataEXT -> Float
$sel:maxLuminance:HdrMetadataEXT :: HdrMetadataEXT -> Float
$sel:whitePoint:HdrMetadataEXT :: HdrMetadataEXT -> XYColorEXT
$sel:displayPrimaryBlue:HdrMetadataEXT :: HdrMetadataEXT -> XYColorEXT
$sel:displayPrimaryGreen:HdrMetadataEXT :: HdrMetadataEXT -> XYColorEXT
$sel:displayPrimaryRed:HdrMetadataEXT :: HdrMetadataEXT -> XYColorEXT
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_HDR_METADATA_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
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 (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr XYColorEXT)) (XYColorEXT
displayPrimaryRed)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr XYColorEXT)) (XYColorEXT
displayPrimaryGreen)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr XYColorEXT)) (XYColorEXT
displayPrimaryBlue)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr XYColorEXT)) (XYColorEXT
whitePoint)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
maxLuminance))
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
minLuminance))
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
maxContentLightLevel))
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
maxFrameAverageLightLevel))
    IO b
f
  cStructSize :: Int
cStructSize = Int
64
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. ("pMetadata" ::: Ptr HdrMetadataEXT) -> IO b -> IO b
pokeZeroCStruct "pMetadata" ::: Ptr HdrMetadataEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_HDR_METADATA_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
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 (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr XYColorEXT)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr XYColorEXT)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr XYColorEXT)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr XYColorEXT)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr CFloat)) (Float -> CFloat
CFloat (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr CFloat)) (Float -> CFloat
CFloat (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr CFloat)) (Float -> CFloat
CFloat (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr CFloat)) (Float -> CFloat
CFloat (forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct HdrMetadataEXT where
  peekCStruct :: ("pMetadata" ::: Ptr HdrMetadataEXT) -> IO HdrMetadataEXT
peekCStruct "pMetadata" ::: Ptr HdrMetadataEXT
p = do
    XYColorEXT
displayPrimaryRed <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @XYColorEXT (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr XYColorEXT))
    XYColorEXT
displayPrimaryGreen <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @XYColorEXT (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr XYColorEXT))
    XYColorEXT
displayPrimaryBlue <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @XYColorEXT (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr XYColorEXT))
    XYColorEXT
whitePoint <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @XYColorEXT (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr XYColorEXT))
    CFloat
maxLuminance <- forall a. Storable a => Ptr a -> IO a
peek @CFloat (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr CFloat))
    CFloat
minLuminance <- forall a. Storable a => Ptr a -> IO a
peek @CFloat (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr CFloat))
    CFloat
maxContentLightLevel <- forall a. Storable a => Ptr a -> IO a
peek @CFloat (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr CFloat))
    CFloat
maxFrameAverageLightLevel <- forall a. Storable a => Ptr a -> IO a
peek @CFloat (("pMetadata" ::: Ptr HdrMetadataEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr CFloat))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ XYColorEXT
-> XYColorEXT
-> XYColorEXT
-> XYColorEXT
-> Float
-> Float
-> Float
-> Float
-> HdrMetadataEXT
HdrMetadataEXT
             XYColorEXT
displayPrimaryRed
             XYColorEXT
displayPrimaryGreen
             XYColorEXT
displayPrimaryBlue
             XYColorEXT
whitePoint
             (coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
maxLuminance)
             (coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
minLuminance)
             (coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
maxContentLightLevel)
             (coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
maxFrameAverageLightLevel)

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

instance Zero HdrMetadataEXT where
  zero :: HdrMetadataEXT
zero = XYColorEXT
-> XYColorEXT
-> XYColorEXT
-> XYColorEXT
-> Float
-> Float
-> Float
-> Float
-> HdrMetadataEXT
HdrMetadataEXT
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


type EXT_HDR_METADATA_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_EXT_HDR_METADATA_SPEC_VERSION"
pattern EXT_HDR_METADATA_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_HDR_METADATA_SPEC_VERSION :: forall a. Integral a => a
$mEXT_HDR_METADATA_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_HDR_METADATA_SPEC_VERSION = 2


type EXT_HDR_METADATA_EXTENSION_NAME = "VK_EXT_hdr_metadata"

-- No documentation found for TopLevel "VK_EXT_HDR_METADATA_EXTENSION_NAME"
pattern EXT_HDR_METADATA_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_HDR_METADATA_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_HDR_METADATA_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_HDR_METADATA_EXTENSION_NAME = "VK_EXT_hdr_metadata"